source: trunk/LMDZ.VENUS/libf/phyvenus/suaer_corrk.F90 @ 3567

Last change on this file since 3567 was 2560, checked in by slebonnois, 3 years ago

SL: Implementation of SW computation based on generic model. Switch between this new SW module or old module that reads R. Haus tables implemented with a key (solarchoice)

File size: 13.2 KB
Line 
1      subroutine suaer_corrk
2
3      ! inputs
4      use radinc_h,    only: L_NSPECTV,nsizemax,naerkind
5      use radcommon_h, only: blamv,lamrefvis
6      use datafile_mod, only: datadir, aerdir
7
8      ! outputs
9      use radcommon_h, only: QVISsQREF,omegavis,gvis
10      use radcommon_h, only: radiustab,nsize,tstellar
11      use radcommon_h, only: qrefvis
12      use aerosol_mod
13
14      implicit none
15
16!==================================================================
17!     Purpose
18!     -------
19!     Initialize all radiative aerosol properties
20!
21!     Notes
22!     -----
23!     Reads the optical properties -> Mean  -> Variable assignment
24!     (ASCII files)                  (see radcommon_h.F90)
25!     wvl(nwvl)                      longsun
26!     ep(nwvl)                       epav     QVISsQREF(L_NSPECTV)
27!     omeg(nwvl)                     omegav   omegavis(L_NSPECTV)
28!     gfactor(nwvl)                  gav      gvis(L_NSPECTV)
29!     
30!     Authors
31!     -------
32!     Richard Fournier (1996) Francois Forget (1996)
33!     Frederic Hourdin
34!     Jean-jacques morcrette *ECMWF*
35!     MODIF Francois Forget (2000)
36!     MODIF Franck Montmessin (add water ice)
37!     MODIF J.-B. Madeleine 2008W27
38!     - Optical properties read in ASCII files
39!     - Add varying radius of the particules
40!     - Add water ice clouds
41!     MODIF R. Wordsworth (2009)
42!     - generalisation to arbitrary spectral bands
43!
44!==================================================================
45
46!     Optical properties (read in external ASCII files)
47      INTEGER,SAVE      :: nwvl  ! Number of wavelengths in
48                                ! the domain (VIS or IR), read by master
49
50!      REAL             :: solsir ! visible to infrared ratio
51!                                ! (tau_0.67um/tau_9um)
52
53      REAL, DIMENSION(:),&
54      ALLOCATABLE, SAVE :: wvl  ! Wavelength axis, read by master
55      REAL, DIMENSION(:),&
56      ALLOCATABLE, SAVE :: radiusdyn ! Particle size axis, read by master
57
58      REAL, DIMENSION(:,:),&
59      ALLOCATABLE, SAVE :: ep,& ! Extinction coefficient Qext, read by master
60      omeg,&                    ! Single Scattering Albedo, read by master
61      gfactor                   ! Assymetry Factor, read by master
62
63!     Local variables:
64
65      INTEGER :: iaer           ! Aerosol index
66      INTEGER :: idomain        ! Domain index (1=VIS,2=IR)
67      INTEGER :: ilw            ! longwave index
68      INTEGER :: isw            ! shortwave index
69      INTEGER :: isize          ! Particle size index
70      INTEGER :: jfile          ! ASCII file scan index
71      INTEGER :: file_unit = 60
72      LOGICAL :: file_ok, endwhile
73      CHARACTER(LEN=132) :: scanline ! ASCII file scanning line
74
75!     I/O  of "aerave" (subroutine that spectrally averages
76!     the single scattering parameters)
77
78      REAL lamref                      ! reference wavelengths
79      REAL epref                       ! reference extinction ep
80
81      REAL epavVI(L_NSPECTV)            ! Average ep (= <Qext>/Qext(lamrefvis) if epref=1)
82      REAL omegavVI(L_NSPECTV)          ! Average single scattering albedo
83      REAL gavVI(L_NSPECTV)             ! Average assymetry parameter
84
85      logical forgetit                  ! use francois' data?
86      integer iwvl, ia
87
88!     Local saved variables:
89
90      character(len=100) :: message
91      character(len=10),parameter :: subname="suaercorrk"
92
93      CHARACTER(LEN=50), DIMENSION(naerkind,2), SAVE :: file_id
94!$OMP THREADPRIVATE(file_id)
95!---- Please indicate the names of the optical property files below
96!     Please also choose the reference wavelengths of each aerosol     
97
98!--------- README TO UNDERSTAND WHAT FOLLOWS (JVO 20) -------
99!     The lamref variables comes from the Martian model
100!     where the visible one is the one used for computing
101!     and the IR one is used to output scaled opacity to
102!     match instrumental data ... This is done (at least
103!     for now) in the generic, so lamrefir is dummy*!
104
105!     The important one is the VISIBLE one as it will be used
106!     to rescale the values in callcork.F90 assuming 'aerosol' is
107!     at this visible reference wavelenght.
108
109!     *Actually if you change lamrefir here there is a
110!     slight sensitvity in the outputs because of some
111!     machine precision differences that amplifys and lead
112!     up to 10-6 differences in the radiative balance...
113!     This could be good to clean the code but would require
114!     a lot of modifs and to take care !
115
116!--------------------------------------------------------------
117! VENUS, ONLY VISIBLE
118
119      do iaer = 1, naerkind     ! Loop on aerosol kind
120
121       if (iaer.eq.iaero_venus1) then
122         print*, 'naerkind= venus1', iaer
123!     visible
124         file_id(iaer,1) = 'optprop_h2so4vis_n50.dat'
125         lamrefvis(iaer)=1.5E-6   ! no idea, must find
126       endif
127
128       if (iaer.eq.iaero_venus2) then
129         print*, 'naerkind= venus2', iaer
130!     visible
131         file_id(iaer,1) = 'optprop_h2so4vis_n50.dat'
132         lamrefvis(iaer)=1.5E-6   ! no idea, must find
133       endif
134
135       if (iaer.eq.iaero_venus2p) then
136         print*, 'naerkind= venus2p', iaer
137!     visible
138         file_id(iaer,1) = 'optprop_h2so4vis_n50.dat'
139         lamrefvis(iaer)=1.5E-6   ! no idea, must find
140       endif
141
142       if (iaer.eq.iaero_venus3) then
143         print*, 'naerkind= venus3', iaer
144!     visible
145         file_id(iaer,1) = 'optprop_h2so4vis_n50.dat'
146         lamrefvis(iaer)=1.5E-6   ! no idea, must find
147       endif
148
149       if (iaer.eq.iaero_venusUV) then
150         print*, 'naerkind= venusUV', iaer
151!     visible
152         file_id(iaer,1) = 'optprop_venusUVvis.dat'
153         lamrefvis(iaer)=3.5E-7   ! Haus et al. 2015
154       endif
155     
156      enddo
157
158!------------------------------------------------------------------
159
160!     Initializations:
161
162      radiustab(:,:,:) = 0.0
163      gvis(:,:,:)      = 0.0
164      omegavis(:,:,:)  = 0.0
165      QVISsQREF(:,:,:) = 0.0
166
167      DO iaer = 1, naerkind     ! Loop on aerosol kind
168!         DO idomain = 1, 2      ! Loop on radiation domain (VIS or IR)
169         idomain=1
170!==================================================================
171!     1. READ OPTICAL PROPERTIES
172!==================================================================
173
174!     1.1 Open the ASCII file
175
176!$OMP MASTER
177
178            INQUIRE(FILE=TRIM(datadir)//'/'//TRIM(aerdir)//&
179                    '/'//TRIM(file_id(iaer,idomain)),&
180                    EXIST=file_ok)
181            IF (file_ok) THEN
182              OPEN(UNIT=file_unit,&
183                   FILE=TRIM(datadir)//'/'//TRIM(aerdir)//&
184                        '/'//TRIM(file_id(iaer,idomain)),&
185                   FORM='formatted')
186            ELSE
187             ! In ye old days these files were stored in datadir;
188             ! let's be retro-compatible
189              INQUIRE(FILE=TRIM(datadir)//&
190                      '/'//TRIM(file_id(iaer,idomain)),&
191                      EXIST=file_ok)
192              IF (file_ok) THEN
193                OPEN(UNIT=file_unit,&
194                     FILE=TRIM(datadir)//&
195                          '/'//TRIM(file_id(iaer,idomain)),&
196                     FORM='formatted')
197              ENDIF             
198            ENDIF
199            IF(.NOT.file_ok) THEN
200               write(*,*)'suaer_corrk: Problem opening ',&
201               TRIM(file_id(iaer,idomain))
202               write(*,*)'It should be in: ',TRIM(datadir)//'/'//TRIM(aerdir)
203               write(*,*)'1) You can set this directory address ',&
204               'in callphys.def with:'
205               write(*,*)' datadir = /absolute/path/to/datagcm'
206               write(*,*)'2) If ',&
207              TRIM(file_id(iaer,idomain)),&
208               ' is a LMD reference datafile, it'
209               write(*,*)' can be obtained online at:'
210               message=' http://www.lmd.jussieu.fr/~lmdz/planets/LMDZ.GENERIC/datagcm/'
211               call abort_physic(subname,message,1)
212            ENDIF
213
214!     1.2 Allocate the optical property table
215
216            jfile = 1
217            endwhile = .false.
218            DO WHILE (.NOT.endwhile)
219               READ(file_unit,*) scanline
220               IF ((scanline(1:1) .ne. '#').and.&
221               (scanline(1:1) .ne. ' ')) THEN
222               BACKSPACE(file_unit)
223               reading1_seq: SELECT CASE (jfile) ! ====================
224            CASE(1) reading1_seq ! nwvl ----------------------------
225               read(file_unit,*) nwvl
226               jfile = jfile+1
227            CASE(2) reading1_seq ! nsize ---------------------------
228               read(file_unit,*) nsize(iaer,idomain)
229               endwhile = .true.
230            CASE DEFAULT reading1_seq ! ----------------------------
231               message='readoptprop: Error while loading optical properties.'
232               call abort_physic(subname,message,1)
233            END SELECT reading1_seq ! ==============================
234         ENDIF
235      ENDDO
236
237      ALLOCATE(wvl(nwvl))       ! wvl
238      ALLOCATE(radiusdyn(nsize(iaer,idomain))) ! radiusdyn
239      ALLOCATE(ep(nwvl,nsize(iaer,idomain))) ! ep
240      ALLOCATE(omeg(nwvl,nsize(iaer,idomain))) ! omeg
241      ALLOCATE(gfactor(nwvl,nsize(iaer,idomain))) ! g
242
243
244!     1.3 Read the data
245
246      jfile = 1
247      endwhile = .false.
248      DO WHILE (.NOT.endwhile)
249         READ(file_unit,*) scanline
250         IF ((scanline(1:1) .ne. '#').and.&
251         (scanline(1:1) .ne. ' ')) THEN
252         BACKSPACE(file_unit)
253         reading2_seq: SELECT CASE (jfile) ! ====================
254      CASE(1) reading2_seq      ! wvl -----------------------------
255         read(file_unit,*) wvl
256         jfile = jfile+1
257      CASE(2) reading2_seq      ! radiusdyn -----------------------
258         read(file_unit,*) radiusdyn
259         jfile = jfile+1
260      CASE(3) reading2_seq      ! ep ------------------------------
261         isize = 1
262         DO WHILE (isize .le. nsize(iaer,idomain))
263            READ(file_unit,*) scanline
264            IF ((scanline(1:1) .ne. '#').and.&
265            (scanline(1:1) .ne. ' ')) THEN
266            BACKSPACE(file_unit)
267            read(file_unit,*) ep(:,isize)
268            isize = isize + 1
269         ENDIF
270      ENDDO
271
272      jfile = jfile+1
273      CASE(4) reading2_seq      ! omeg ----------------------------
274         isize = 1
275         DO WHILE (isize .le. nsize(iaer,idomain))
276            READ(file_unit,*) scanline
277            IF ((scanline(1:1) .ne. '#').and.&
278            (scanline(1:1) .ne. ' ')) THEN
279            BACKSPACE(file_unit)
280            read(file_unit,*) omeg(:,isize)
281            isize = isize + 1
282         ENDIF
283      ENDDO
284
285      jfile = jfile+1
286      CASE(5) reading2_seq      ! gfactor -------------------------
287         isize = 1
288         DO WHILE (isize .le. nsize(iaer,idomain))
289            READ(file_unit,*) scanline
290            IF ((scanline(1:1) .ne. '#').and.&
291            (scanline(1:1) .ne. ' ')) THEN
292            BACKSPACE(file_unit)
293            read(file_unit,*) gfactor(:,isize)
294            isize = isize + 1
295         ENDIF
296      ENDDO
297
298      jfile = jfile+1
299      IF ((idomain.NE.iaero_co2).OR.(iaer.NE.iaero_co2)) THEN
300         endwhile = .true.
301      ENDIF
302      CASE(6) reading2_seq
303         endwhile = .true.
304      CASE DEFAULT reading2_seq ! ----------------------------
305         message='readoptprop: Error while loading optical properties.'
306         call abort_physic(subname,message,1)
307      END SELECT reading2_seq   ! ==============================
308      ENDIF
309      ENDDO
310
311!     1.4 Close the file
312
313      CLOSE(file_unit)
314
315!$OMP END MASTER
316!$OMP BARRIER
317
318
319
320
321
322!==================================================================
323!     2. AVERAGED PROPERTIES AND VARIABLE ASSIGNMENTS
324!==================================================================
325!      domain: SELECT CASE (idomain)
326!==================================================================
327!      CASE(1) domain            !       VISIBLE DOMAIN (idomain=1)
328!==================================================================
329
330         lamref=lamrefvis(iaer)
331         epref=1.E+0
332
333         DO isize=1,nsize(iaer,idomain)
334
335!     Save the particle sizes
336            radiustab(iaer,idomain,isize)=radiusdyn(isize)
337
338!     Averaged optical properties (GCM channels)
339
340            CALL aerave_new ( nwvl,&
341            wvl(:),ep(:,isize),omeg(:,isize),gfactor(:,isize),&
342            lamref,epref,tstellar,&
343            L_NSPECTV,blamv,epavVI,&
344            omegavVI,gavVI,QREFvis(iaer,isize))
345
346!     Variable assignments (declared in radcommon)
347            DO isw=1,L_NSPECTV
348               QVISsQREF(isw,iaer,isize)=epavVI(isw)
349               gvis(isw,iaer,isize)=gavVI(isw)
350               omegavis(isw,iaer,isize)=omegavVI(isw)
351            END DO
352
353         ENDDO
354
355! Only visible for Venus
356
357!      END SELECT domain
358
359!========================================================================
360!     3. Deallocate temporary variables that were read in the ASCII files
361!========================================================================
362
363!$OMP BARRIER
364!$OMP MASTER
365      IF (ALLOCATED(wvl)) DEALLOCATE(wvl)                 ! wvl
366      IF (ALLOCATED(radiusdyn)) DEALLOCATE(radiusdyn)     ! radiusdyn
367      IF (ALLOCATED(ep)) DEALLOCATE(ep)                   ! ep
368      IF (ALLOCATED(omeg)) DEALLOCATE(omeg)               ! omeg
369      IF (ALLOCATED(gfactor)) DEALLOCATE(gfactor)         ! g
370!$OMP END MASTER
371!$OMP BARRIER
372
373      END DO                    ! Loop on iaer
374!      END DO                    ! Loop on idomain
375!========================================================================
376
377      RETURN
378
379
380
381    END subroutine suaer_corrk
382     
Note: See TracBrowser for help on using the repository browser.