source: trunk/LMDZ.MARS/libf/phymars/suaer.F90 @ 2266

Last change on this file since 2266 was 2199, checked in by mvals, 5 years ago

Mars GCM:
Implementation of a new parametrization of the dust entrainment by slope winds above the sub-grid scale topography. The parametrization is activated with the flag slpwind=.true. (set to "false" by
default) in callphys.def. The new parametrization involves the new tracers topdust_mass and topdust_number.
MV

File size: 19.4 KB
Line 
1SUBROUTINE suaer
2use dimradmars_mod, only: longrefvis, longrefir, nsizemax, long1vis, &
3                    long2vis, long3vis, long1ir, long2ir, long1co2, &
4                    long2co2, nsun, nir,&
5                    naerkind, name_iaer, &
6                    iaer_dust_conrath,iaer_dust_doubleq,&
7                    iaer_dust_submicron,iaer_h2o_ice,&
8                    iaer_stormdust_doubleq,iaer_topdust_doubleq,&
9                    file_id,radiustab, gvis, omegavis, &
10                    QVISsQREF, gIR, omegaIR, &
11                    QIRsQREF, QREFvis, QREFir, &
12                    omegaREFvis, omegaREFir, &
13                    nsize
14use datafile_mod, only: datadir
15IMPLICIT NONE
16!==================================================================
17!     Purpose.
18!     --------
19!     initialize yomaer, the common that contains the
20!     radiative characteristics of the aerosols
21!     
22!     AUTHORS.
23!     --------
24!     Richard Fournier (1996) Francois Forget (1996)
25!     Frederic Hourdin
26!     Jean-jacques morcrette *ECMWF*
27!     MODIF Francois Forget (2000)
28!     MODIF Franck Montmessin (add water ice)
29!     MODIF J.-B. Madeleine 2008W27
30!       - Optical properties read in ASCII files
31!       - Add varying radius of the particules
32!
33!    Summary.
34!    --------
35!
36!    Read the optical properties -> Mean  -> Variable assignment
37!                  (ASCII files)                  (see yomaer.h)
38!    wvl(nwvl)                      longsun
39!    ep(nwvl)                       epav     QVISsQREF(nsun)
40!    omeg(nwvl)                     omegav   omegavis(nsun)
41!    gfactor(nwvl)                  gav      gvis(nsun)
42!   
43!==================================================================
44
45! Includes:
46
47include "callkeys.h"
48
49! Optical properties (read in external ASCII files)
50INTEGER          :: nwvl     ! Number of wavelengths in
51                             ! the domain (VIS or IR)
52REAL, DIMENSION(:),&
53  ALLOCATABLE, SAVE :: wvl       ! Wavelength axis
54REAL, DIMENSION(:),&
55  ALLOCATABLE, SAVE :: radiusdyn ! Particle size axis
56
57REAL, DIMENSION(:,:),&
58  ALLOCATABLE, SAVE :: ep,&    ! Extinction coefficient Qext
59                       omeg,&  ! Single Scattering Albedo
60                       gfactor ! Assymetry Factor
61
62! Local variables:
63
64INTEGER :: iaer                ! Aerosol index
65INTEGER :: idomain             ! Domain index (1=VIS,2=IR)
66INTEGER :: iir                 ! IR channel index
67                               ! iir=1: 15um CO2 bands
68                               ! iir=2 : CO2 band wings
69                               ! iir=3 : 9 um band
70                               ! iir=4 : Far IR
71INTEGER :: isun                ! Solar band index
72INTEGER :: isize               ! Particle size index
73INTEGER :: jfile               ! ASCII file scan index
74INTEGER :: file_unit = 60
75LOGICAL :: file_ok, endwhile
76CHARACTER(LEN=132) :: scanline ! ASCII file scanning line
77INTEGER :: read_ok
78
79! I/O  of "aerave" (subroutine averaging spectrally
80!   sing.scat.parameters)
81
82REAL tsun            ! Sun brightness temperature (for SW)
83REAL tsol            ! Surface reference brightness temp (LW)
84REAL longref         ! reference wavelengths
85REAL longsun(nsun+1) ! solar band boundaries
86REAL longir(nir+1)   ! IR band boundaries
87REAL epref           ! reference extinction ep
88                     ! at wavelength "longref"
89REAL epav(nir)       ! average ep
90                     ! (= <Qext>/Qext(longref) if epref=1)
91REAL omegav(nir)     ! Average sing.scat.albedo
92REAL gav(nir)        ! Average assymetry parameter
93
94!==================================================================
95!---- Please indicate the names of the optical property files below
96!     Please also choose the reference wavelengths of each aerosol
97
98      DO iaer = 1, naerkind ! Loop on aerosol kind
99        aerkind: SELECT CASE (name_iaer(iaer))
100!==================================================================
101        CASE("dust_conrath") aerkind      ! Typical dust profile
102!==================================================================
103!       Visible domain:
104        file_id(iaer,1) = 'optprop_dustvis_TM.dat'     !M.Wolff TM
105!       file_id(iaer,1) = 'optprop_dustvis_clancy.dat' !Clancy-Lee
106!       file_id(iaer,1) = 'optprop_dustvis_ockert.dat' !Ockert-Bell
107!       Infrared domain:
108        file_id(iaer,2) = 'optprop_dustir_TM.dat'      !M.Wolff TM
109!       Toon-Forget + solsir=2 using Clancy-Lee
110!       file_id(iaer,2) = 'optprop_dustir_clancy.dat'
111!       Toon-Forget + solsir=2 using Ockert-Bell
112!       file_id(iaer,2) = 'optprop_dustir_ockert.dat'
113!       Reference wavelength in the visible:
114        longrefvis(iaer)=0.67E-6
115!                     For dust: change readtesassim accordingly;
116!       Reference wavelength in the infrared:
117        longrefir(iaer)=dustrefir
118!==================================================================
119        CASE("dust_doubleq") aerkind! Two-moment scheme for dust
120!==================================================================
121!       Visible domain:
122        file_id(iaer,1) = 'optprop_dustvis_TM_n50.dat' !T-Matrix
123!       file_id(iaer,1) = 'optprop_dustvis_n50.dat'    !Mie
124!       Infrared domain:
125        file_id(iaer,2) = 'optprop_dustir_n50.dat'     !Mie
126!       Reference wavelength in the visible:
127        longrefvis(iaer)=0.67E-6
128!       If not equal to 0.67e-6 -> change readtesassim accordingly;
129!       Reference wavelength in the infrared:
130        longrefir(iaer)=dustrefir
131!==================================================================
132        CASE("dust_submicron") aerkind   ! Small dust population
133!==================================================================
134!       Visible domain:
135        file_id(iaer,1) = 'optprop_dustvis_01um_TM.dat' !M.Wolff
136!       Infrared domain:
137        file_id(iaer,2) = 'optprop_dustir_01um_TM.dat'  !M.Wolff
138!       Reference wavelength in the visible:
139        longrefvis(iaer)=0.67E-6
140!       If not equal to 0.67e-6 -> change readtesassim accordingly;
141!       Reference wavelength in the infrared:
142        longrefir(iaer)=dustrefir
143!==================================================================
144        CASE("h2o_ice") aerkind             ! Water ice crystals
145!==================================================================
146!       Visible domain:
147        file_id(iaer,1) = 'optprop_icevis_n30.dat' !Warren
148!       file_id(iaer,1) = 'optprop_icevis.dat'     !Warren
149!       Infrared domain:
150        file_id(iaer,2) = 'optprop_iceir_n30.dat'  !Warren
151!       file_id(iaer,2) = 'optprop_iceir.dat'      !Warren
152!       Reference wavelength in the visible:
153        longrefvis(iaer)=0.67E-6  ! 1.5um OMEGA/MEx
154!       Reference wavelength in the infrared:
155        longrefir(iaer)=12.1E-6  ! 825cm-1 TES/MGS
156!==================================================================
157        CASE("stormdust_doubleq") aerkind   ! Two-moment scheme for stormdust - radiative properties
158!==================================================================
159!       Visible domain:
160        file_id(iaer,1) = 'optprop_dustvis_TM_n50.dat' !T-Matrix
161!       Infrared domain:
162        file_id(iaer,2) = 'optprop_dustir_n50.dat'     !Mie
163!       Reference wavelength in the visible:
164        longrefvis(iaer)=0.67E-6
165!       If not equal to 0.67e-6 -> change readtesassim accordingly;
166!       Reference wavelength in the infrared:
167        longrefir(iaer)=dustrefir
168!==================================================================
169        CASE("topdust_doubleq") aerkind   ! Two-moment scheme for topdust - radiative properties
170!==================================================================
171!       Visible domain:
172        file_id(iaer,1) = 'optprop_dustvis_TM_n50.dat' !T-Matrix
173!       Infrared domain:
174        file_id(iaer,2) = 'optprop_dustir_n50.dat'     !Mie
175!       Reference wavelength in the visible:
176        longrefvis(iaer)=0.67E-6
177!       If not equal to 0.67e-6 -> change readtesassim accordingly;
178!       Reference wavelength in the infrared:
179        longrefir(iaer)=dustrefir
180!==================================================================
181        END SELECT aerkind
182!==================================================================
183        WRITE(*,*) "Scatterer: ",trim(name_iaer(iaer))
184        WRITE(*,*) "  corresponding files: "
185        WRITE(*,*) "VIS: ",trim(file_id(iaer,1))
186        WRITE(*,*) "IR : ",trim(file_id(iaer,2))
187!==================================================================
188      ENDDO ! iaer (loop on aerosol kind)
189
190! Initializations:
191
192radiustab(1:naerkind,1:2,1:nsizemax)=0
193
194gvis(1:nsun,1:naerkind,1:nsizemax)=0
195omegavis(1:nsun,1:naerkind,1:nsizemax)=0
196QVISsQREF(1:nsun,1:naerkind,1:nsizemax)=0
197
198gIR(1:nir,1:naerkind,1:nsizemax)=0
199omegaIR(1:nir,1:naerkind,1:nsizemax)=0
200QIRsQREF(1:nir,1:naerkind,1:nsizemax)=0
201
202QREFvis(1:naerkind,1:nsizemax)=0
203QREFir(1:naerkind,1:nsizemax)=0
204omegaREFvis(1:naerkind,1:nsizemax)=0
205omegaREFir(1:naerkind,1:nsizemax)=0
206
207DO iaer = 1, naerkind ! Loop on aerosol kind
208  DO idomain = 1, 2   ! Loop on radiation domain (VIS or IR)
209!==================================================================
210! 1. READ OPTICAL PROPERTIES
211!==================================================================
212
213!       1.1 Open the ASCII file
214
215INQUIRE(FILE=TRIM(datadir)//&
216  '/'//TRIM(file_id(iaer,idomain)),&
217  EXIST=file_ok)
218IF(.NOT.file_ok) THEN
219  write(*,*)'Problem opening ',&
220    TRIM(file_id(iaer,idomain))
221  write(*,*)'It should be in: ',&
222    TRIM(datadir)
223  write(*,*)'1) You can change this directory address in callfis.def with'
224  write(*,*)'   datadir=/path/to/datafiles'
225  write(*,*)'2) If ',&
226    TRIM(file_id(iaer,idomain)),&
227    ' is a LMD reference datafile, it'
228  write(*,*)' can be obtained online on:'
229  write(*,*)' http://www.lmd.jussieu.fr/',&
230    '~lmdz/planets/mars/datadir'
231  write(*,*)'3) If the name of the file is wrong, you can'
232  write(*,*)' change it in file phymars/suaer.F90. Just'
233  write(*,*)' modify the variable called file_id.'
234  CALL ABORT
235ENDIF
236OPEN(UNIT=file_unit,&
237  FILE=TRIM(datadir)//&
238  '/'//TRIM(file_id(iaer,idomain)),&
239  FORM='formatted')
240
241!       1.2 Allocate the optical property table
242
243jfile = 1
244endwhile = .false.
245DO WHILE (.NOT.endwhile)
246  READ(file_unit,*,iostat=read_ok) scanline
247  if (read_ok.ne.0) then
248    write(*,*)' readoptprop: Error reading file',&
249    TRIM(datadir)//&
250    '/'//TRIM(file_id(iaer,idomain))
251    call abort
252  endif
253  IF ((scanline(1:1) .ne. '#').and.&
254    (scanline(1:1) .ne. ' ')) THEN
255    BACKSPACE(file_unit)
256    reading1_seq: SELECT CASE (jfile) ! ====================
257    CASE(1) reading1_seq ! nwvl ----------------------------
258        read(file_unit,*,iostat=read_ok) nwvl
259        if (read_ok.ne.0) then
260          write(*,*)' readoptprop: Error while reading line:',&
261          trim(scanline)
262          write(*,*)'   of file',&
263          TRIM(datadir)//&
264          '/'//TRIM(file_id(iaer,idomain))
265          call abort
266        endif
267        jfile = jfile+1
268    CASE(2) reading1_seq ! nsize ---------------------------
269        read(file_unit,*,iostat=read_ok) nsize(iaer,idomain)
270        if (read_ok.ne.0) then
271          write(*,*)' readoptprop: Error while reading line:',&
272          trim(scanline)
273          write(*,*)'   of file',&
274          TRIM(datadir)//&
275          '/'//TRIM(file_id(iaer,idomain))
276          call abort
277        endif
278        endwhile = .true.
279    CASE DEFAULT reading1_seq ! ----------------------------
280        WRITE(*,*) 'readoptprop: ',&
281          'Error while loading optical properties.'
282        CALL ABORT
283    END SELECT reading1_seq ! ==============================
284  ENDIF
285ENDDO
286
287ALLOCATE(wvl(nwvl))                            ! wvl
288ALLOCATE(radiusdyn(nsize(iaer,idomain)))       ! radiusdyn
289ALLOCATE(ep(nwvl,nsize(iaer,idomain)))         ! ep
290ALLOCATE(omeg(nwvl,nsize(iaer,idomain)))       ! omeg
291ALLOCATE(gfactor(nwvl,nsize(iaer,idomain)))    ! g
292
293!       1.3 Read the data
294
295jfile = 1
296endwhile = .false.
297DO WHILE (.NOT.endwhile)
298   READ(file_unit,*) scanline
299  IF ((scanline(1:1) .ne. '#').and.&
300    (scanline(1:1) .ne. ' ')) THEN
301    BACKSPACE(file_unit)
302    reading2_seq: SELECT CASE (jfile) ! ====================
303    CASE(1) reading2_seq ! wvl -----------------------------
304        read(file_unit,*) wvl
305        jfile = jfile+1
306    CASE(2) reading2_seq ! radiusdyn -----------------------
307        read(file_unit,*) radiusdyn
308        jfile = jfile+1
309    CASE(3) reading2_seq ! ep ------------------------------
310        isize = 1
311        DO WHILE (isize .le. nsize(iaer,idomain))
312          READ(file_unit,*) scanline
313          IF ((scanline(1:1) .ne. '#').and.&
314            (scanline(1:1) .ne. ' ')) THEN
315          BACKSPACE(file_unit)
316          read(file_unit,*) ep(:,isize)
317          isize = isize + 1
318          ENDIF
319        ENDDO
320        jfile = jfile+1
321    CASE(4) reading2_seq ! omeg ----------------------------
322        isize = 1
323        DO WHILE (isize .le. nsize(iaer,idomain))
324          READ(file_unit,*) scanline
325          IF ((scanline(1:1) .ne. '#').and.&
326            (scanline(1:1) .ne. ' ')) THEN
327          BACKSPACE(file_unit)
328          read(file_unit,*) omeg(:,isize)
329          isize = isize + 1
330          ENDIF
331        ENDDO
332        jfile = jfile+1
333    CASE(5) reading2_seq ! gfactor -------------------------
334        isize = 1
335        DO WHILE (isize .le. nsize(iaer,idomain))
336          READ(file_unit,*) scanline
337          IF ((scanline(1:1) .ne. '#').and.&
338            (scanline(1:1) .ne. ' ')) THEN
339          BACKSPACE(file_unit)
340          read(file_unit,*) gfactor(:,isize)
341          isize = isize + 1
342          ENDIF
343        ENDDO
344        endwhile = .true.
345    CASE DEFAULT reading2_seq ! ----------------------------
346        WRITE(*,*) 'suaer.F90: ',&
347          'Error while loading optical properties.'
348        CALL ABORT
349    END SELECT reading2_seq ! ==============================
350  ENDIF
351ENDDO
352
353!       1.4 Close the file
354
355CLOSE(file_unit)
356
357!==================================================================
358! 2. AVERAGED PROPERTIES AND VARIABLE ASSIGNMENTS
359!==================================================================
360domain: SELECT CASE (idomain)
361!==================================================================
362CASE(1) domain !                   VISIBLE DOMAIN (idomain=1)
363!==================================================================
364
365! 2.1 Parameters
366  tsun=6000.E+0
367  longsun(1)=long1vis
368  longsun(2)=long2vis
369  longsun(3)=long3vis
370  longref=longrefvis(iaer)
371  epref=1.E+0
372
373DO isize=1,nsize(iaer,idomain)
374! test that there is enough room to store the data
375 if (isize.gt.nsizemax) then
376   write(*,*) "suaer: Error ! nsizemax is too small!"
377   write(*,*) "       nsizemax=",nsizemax
378   write(*,*) "       you must increase the value of nsizemax"
379   write(*,*) "       in dimradmars_mod !"
380   stop
381 endif
382! ------------------------------------------------
383! 2.2 Save the particle sizes
384  radiustab(iaer,idomain,isize)=radiusdyn(isize)
385! 2.3 Averaged optical properties (GCM channels)
386! Notice: Aerave also computes the extinction coefficient and
387!   single scattering albedo at reference wavelength
388!   (called QREFvis and OMEGAREFvis, same in the IR,
389!   and not epref, which is a different parameter);
390!   Reference wavelengths are defined for each aerosol in
391!   dimradmars_mod.
392
393  CALL aerave ( nwvl,&
394       wvl(:),ep(:,isize),omeg(:,isize),gfactor(:,isize),&
395       longref,epref,tsun,&
396       nsun,longsun, epav,omegav,gav,&
397       QREFvis(iaer,isize),omegaREFvis(iaer,isize) )
398! 2.4 Variable assignements (declared by yomaer.h)
399  DO isun=1,nsun
400    QVISsQREF(isun,iaer,isize)=epav(isun)
401    gvis(isun,iaer,isize)=gav(isun)
402    omegavis(isun,iaer,isize)=omegav(isun)
403  END DO
404! 2.5 Output display
405!  WRITE(*,*) 'Les donnees spectrales :'
406!  WRITE(*,*) 'Solaire (SW) ---->'
407!  WRITE(*,*) 'Aerosol number: ', iaer
408!  WRITE(*,*) 'Rayon aerosol: ', radiustab(iaer,idomain,isize)
409!  WRITE(*,*) '<Qext>/Qext(longrefvis) ; omega ; g'
410!  DO isun=1,nsun
411!    WRITE(*,*) QVISsQREF(isun,iaer,isize),&
412!         omegavis(isun,iaer,isize),&
413!         gvis(isun,iaer,isize)
414!  ENDDO
415!  WRITE(*,*) 'QREFvis(',iaer,isize,') = ',QREFvis(iaer,isize)
416!  WRITE(*,*) 'omegaREFvis(',iaer,isize,') = ',&
417!                                      omegaREFvis(iaer,isize)
418! ------------------------------------------------
419ENDDO
420
421!==================================================================
422CASE(2) domain !                  INFRARED DOMAIN (idomain=2)
423!==================================================================
424
425DO isize=1,nsize(iaer,idomain) ! ----------------------------------
426
427! 2.1 solsir is not used anymore; division of Qext(IR) by solsir
428!     has to be done in the input ASCII files (if necessary).
429
430! 2.2 Save the particle sizes
431  radiustab(iaer,idomain,isize)=radiusdyn(isize)
432
433! 2.3 Parameters
434
435  tsol=215.D+0
436  longir(1)=long1ir
437  longir(2)=long1co2
438  longir(3)=long2co2
439  longir(4)=long2ir
440  longref=longrefir(iaer)
441  epref=1.E+0
442
443! 2.4 Averaged optical properties (GCM channels)
444!           epav is <QIR>/Qext(longrefir) since epref=1
445! Notice: Aerave also Computes the extinction coefficient at
446!   reference wavelength (called QREFvis or QREFir,
447!   and not epref, which is a different parameter);
448!   Reference wavelengths are defined for each aerosol in
449!   dimradmar_mod.
450
451  CALL aerave ( nwvl,&
452       wvl(:),ep(:,isize),omeg(:,isize),gfactor(:,isize),&
453       longref,epref,tsol,&
454       nir-1,longir,epav,omegav,gav,&
455       QREFir(iaer,isize),omegaREFir(iaer,isize) )
456!  WRITE(*,*) 'QREFir(',iaer,isize,') = ',QREFir(iaer,isize)
457!  WRITE(*,*) 'omegaREFir(',iaer,isize,') = ',&
458!                                      omegaREFir(iaer,isize)
459
460! 2.5 Computing  <QIR>/Qext(longrefvis)
461
462  DO iir=1,nir-1
463!    WRITE(*,*) 'QIRsQREFir Channel ',iir,': ',epav(iir)
464    epav(iir)=  epav(iir) * QREFir(iaer,isize) / &
465                            QREFvis(iaer,isize)
466  ENDDO
467!  WRITE(*,*) 'Aerosol number', iaer
468!  WRITE(*,*) 'Particle size: ',radiustab(iaer,idomain,isize)
469!  WRITE(*,*) 'Rapport Solaire/IR:',&
470!             QREFvis(iaer,isize) / QREFir(iaer,isize)
471
472! 2.6 Variable assignements
473!           (variables are declared by yomaer.h)
474
475!         Single scattering properties
476!           in each of the "nir" bands
477!           (cf. dimradmars_mod)
478
479! iir=1 : central 15um CO2 bands   
480  QIRsQREF(1,iaer,isize)=epav(2)
481  omegaIR(1,iaer,isize)=omegav(2)
482  gIR(1,iaer,isize)=gav(2)
483
484! iir=2 : CO2 band wings
485!           (same properties than for central part)
486  QIRsQREF(2,iaer,isize)=epav(2)
487  omegaIR(2,iaer,isize)=omegav(2)
488  gIR(2,iaer,isize)=gav(2)
489
490! iir=3 : 9 um band [long1ir - long1co2]
491  QIRsQREF(3,iaer,isize)=epav(1)
492  omegaIR(3,iaer,isize)=omegav(1)
493  gIR(3,iaer,isize)=gav(1)
494
495! iir=4 : Far IR    [long2co2 - long2ir]
496  QIRsQREF(4,iaer,isize)=epav(3)
497  omegaIR(4,iaer,isize)=omegav(3)
498  gIR(4,iaer,isize)=gav(3)
499
500! 2.7 Output display
501
502!  WRITE(*,*) 'AEROSOL PROPERTIES: Number ',iaer
503!  WRITE(*,*) 'Thermal IR (LW) ---->'
504!  WRITE(*,*) 'Particle size: ',radiustab(iaer,idomain,isize)
505!  WRITE(*,*) '<Qext>/Qext(longrefvis) ; omega ; g'
506!  DO iir=1,nir
507!    WRITE(*,*) QIRsQREF(iir,iaer,isize),omegaIR(iir,iaer,isize),&
508!         gIR(iir,iaer,isize)
509!  ENDDO
510!  WRITE(*,*) 'CO2: <Qabs>/Qext(longrefvis) = ',&
511!       QIRsQREF(1,iaer,isize)*(1-omegaIR(1,iaer,isize))
512!  WRITE(*,*) ''
513
514ENDDO ! isize (particle size) -------------------------------------
515
516END SELECT domain
517!==================================================================
518! 3. Deallocate temporary variables (read in ASCII files)
519!==================================================================
520
521DEALLOCATE(wvl)        ! wvl
522DEALLOCATE(radiusdyn)  ! radiusdyn
523DEALLOCATE(ep)         ! ep
524DEALLOCATE(omeg)       ! omeg
525DEALLOCATE(gfactor)    ! g
526
527  END DO ! Loop on iaer
528END DO   ! Loop on idomain
529!==================================================================
530RETURN
531END
Note: See TracBrowser for help on using the repository browser.