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

Last change on this file since 2156 was 1974, checked in by mvals, 6 years ago

Mars GCM:
Integration of the detached dust layer parametrizations (rocket dust storm, slope wind lifting, CW, and dust injection scheme, DB).
Still experimental, default behaviour (rdstorm=.false., dustinjection=0) identical to previous revision.
NB: Updated newstart requires an updated "surface.nc" containing the "hmons" field.
EM+MV

File size: 18.7 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,&
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        END SELECT aerkind
170!==================================================================
171        WRITE(*,*) "Scatterer: ",trim(name_iaer(iaer))
172        WRITE(*,*) "  corresponding files: "
173        WRITE(*,*) "VIS: ",trim(file_id(iaer,1))
174        WRITE(*,*) "IR : ",trim(file_id(iaer,2))
175!==================================================================
176      ENDDO ! iaer (loop on aerosol kind)
177
178! Initializations:
179
180radiustab(1:naerkind,1:2,1:nsizemax)=0
181
182gvis(1:nsun,1:naerkind,1:nsizemax)=0
183omegavis(1:nsun,1:naerkind,1:nsizemax)=0
184QVISsQREF(1:nsun,1:naerkind,1:nsizemax)=0
185
186gIR(1:nir,1:naerkind,1:nsizemax)=0
187omegaIR(1:nir,1:naerkind,1:nsizemax)=0
188QIRsQREF(1:nir,1:naerkind,1:nsizemax)=0
189
190QREFvis(1:naerkind,1:nsizemax)=0
191QREFir(1:naerkind,1:nsizemax)=0
192omegaREFvis(1:naerkind,1:nsizemax)=0
193omegaREFir(1:naerkind,1:nsizemax)=0
194
195DO iaer = 1, naerkind ! Loop on aerosol kind
196  DO idomain = 1, 2   ! Loop on radiation domain (VIS or IR)
197!==================================================================
198! 1. READ OPTICAL PROPERTIES
199!==================================================================
200
201!       1.1 Open the ASCII file
202
203INQUIRE(FILE=TRIM(datadir)//&
204  '/'//TRIM(file_id(iaer,idomain)),&
205  EXIST=file_ok)
206IF(.NOT.file_ok) THEN
207  write(*,*)'Problem opening ',&
208    TRIM(file_id(iaer,idomain))
209  write(*,*)'It should be in: ',&
210    TRIM(datadir)
211  write(*,*)'1) You can change this directory address in callfis.def with'
212  write(*,*)'   datadir=/path/to/datafiles'
213  write(*,*)'2) If ',&
214    TRIM(file_id(iaer,idomain)),&
215    ' is a LMD reference datafile, it'
216  write(*,*)' can be obtained online on:'
217  write(*,*)' http://www.lmd.jussieu.fr/',&
218    '~lmdz/planets/mars/datadir'
219  write(*,*)'3) If the name of the file is wrong, you can'
220  write(*,*)' change it in file phymars/suaer.F90. Just'
221  write(*,*)' modify the variable called file_id.'
222  CALL ABORT
223ENDIF
224OPEN(UNIT=file_unit,&
225  FILE=TRIM(datadir)//&
226  '/'//TRIM(file_id(iaer,idomain)),&
227  FORM='formatted')
228
229!       1.2 Allocate the optical property table
230
231jfile = 1
232endwhile = .false.
233DO WHILE (.NOT.endwhile)
234  READ(file_unit,*,iostat=read_ok) scanline
235  if (read_ok.ne.0) then
236    write(*,*)' readoptprop: Error reading file',&
237    TRIM(datadir)//&
238    '/'//TRIM(file_id(iaer,idomain))
239    call abort
240  endif
241  IF ((scanline(1:1) .ne. '#').and.&
242    (scanline(1:1) .ne. ' ')) THEN
243    BACKSPACE(file_unit)
244    reading1_seq: SELECT CASE (jfile) ! ====================
245    CASE(1) reading1_seq ! nwvl ----------------------------
246        read(file_unit,*,iostat=read_ok) nwvl
247        if (read_ok.ne.0) then
248          write(*,*)' readoptprop: Error while reading line:',&
249          trim(scanline)
250          write(*,*)'   of file',&
251          TRIM(datadir)//&
252          '/'//TRIM(file_id(iaer,idomain))
253          call abort
254        endif
255        jfile = jfile+1
256    CASE(2) reading1_seq ! nsize ---------------------------
257        read(file_unit,*,iostat=read_ok) nsize(iaer,idomain)
258        if (read_ok.ne.0) then
259          write(*,*)' readoptprop: Error while reading line:',&
260          trim(scanline)
261          write(*,*)'   of file',&
262          TRIM(datadir)//&
263          '/'//TRIM(file_id(iaer,idomain))
264          call abort
265        endif
266        endwhile = .true.
267    CASE DEFAULT reading1_seq ! ----------------------------
268        WRITE(*,*) 'readoptprop: ',&
269          'Error while loading optical properties.'
270        CALL ABORT
271    END SELECT reading1_seq ! ==============================
272  ENDIF
273ENDDO
274
275ALLOCATE(wvl(nwvl))                            ! wvl
276ALLOCATE(radiusdyn(nsize(iaer,idomain)))       ! radiusdyn
277ALLOCATE(ep(nwvl,nsize(iaer,idomain)))         ! ep
278ALLOCATE(omeg(nwvl,nsize(iaer,idomain)))       ! omeg
279ALLOCATE(gfactor(nwvl,nsize(iaer,idomain)))    ! g
280
281!       1.3 Read the data
282
283jfile = 1
284endwhile = .false.
285DO WHILE (.NOT.endwhile)
286   READ(file_unit,*) scanline
287  IF ((scanline(1:1) .ne. '#').and.&
288    (scanline(1:1) .ne. ' ')) THEN
289    BACKSPACE(file_unit)
290    reading2_seq: SELECT CASE (jfile) ! ====================
291    CASE(1) reading2_seq ! wvl -----------------------------
292        read(file_unit,*) wvl
293        jfile = jfile+1
294    CASE(2) reading2_seq ! radiusdyn -----------------------
295        read(file_unit,*) radiusdyn
296        jfile = jfile+1
297    CASE(3) reading2_seq ! ep ------------------------------
298        isize = 1
299        DO WHILE (isize .le. nsize(iaer,idomain))
300          READ(file_unit,*) scanline
301          IF ((scanline(1:1) .ne. '#').and.&
302            (scanline(1:1) .ne. ' ')) THEN
303          BACKSPACE(file_unit)
304          read(file_unit,*) ep(:,isize)
305          isize = isize + 1
306          ENDIF
307        ENDDO
308        jfile = jfile+1
309    CASE(4) reading2_seq ! omeg ----------------------------
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,*) omeg(:,isize)
317          isize = isize + 1
318          ENDIF
319        ENDDO
320        jfile = jfile+1
321    CASE(5) reading2_seq ! gfactor -------------------------
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,*) gfactor(:,isize)
329          isize = isize + 1
330          ENDIF
331        ENDDO
332        endwhile = .true.
333    CASE DEFAULT reading2_seq ! ----------------------------
334        WRITE(*,*) 'suaer.F90: ',&
335          'Error while loading optical properties.'
336        CALL ABORT
337    END SELECT reading2_seq ! ==============================
338  ENDIF
339ENDDO
340
341!       1.4 Close the file
342
343CLOSE(file_unit)
344
345!==================================================================
346! 2. AVERAGED PROPERTIES AND VARIABLE ASSIGNMENTS
347!==================================================================
348domain: SELECT CASE (idomain)
349!==================================================================
350CASE(1) domain !                   VISIBLE DOMAIN (idomain=1)
351!==================================================================
352
353! 2.1 Parameters
354  tsun=6000.E+0
355  longsun(1)=long1vis
356  longsun(2)=long2vis
357  longsun(3)=long3vis
358  longref=longrefvis(iaer)
359  epref=1.E+0
360
361DO isize=1,nsize(iaer,idomain)
362! test that there is enough room to store the data
363 if (isize.gt.nsizemax) then
364   write(*,*) "suaer: Error ! nsizemax is too small!"
365   write(*,*) "       nsizemax=",nsizemax
366   write(*,*) "       you must increase the value of nsizemax"
367   write(*,*) "       in dimradmars_mod !"
368   stop
369 endif
370! ------------------------------------------------
371! 2.2 Save the particle sizes
372  radiustab(iaer,idomain,isize)=radiusdyn(isize)
373! 2.3 Averaged optical properties (GCM channels)
374! Notice: Aerave also computes the extinction coefficient and
375!   single scattering albedo at reference wavelength
376!   (called QREFvis and OMEGAREFvis, same in the IR,
377!   and not epref, which is a different parameter);
378!   Reference wavelengths are defined for each aerosol in
379!   dimradmars_mod.
380
381  CALL aerave ( nwvl,&
382       wvl(:),ep(:,isize),omeg(:,isize),gfactor(:,isize),&
383       longref,epref,tsun,&
384       nsun,longsun, epav,omegav,gav,&
385       QREFvis(iaer,isize),omegaREFvis(iaer,isize) )
386! 2.4 Variable assignements (declared by yomaer.h)
387  DO isun=1,nsun
388    QVISsQREF(isun,iaer,isize)=epav(isun)
389    gvis(isun,iaer,isize)=gav(isun)
390    omegavis(isun,iaer,isize)=omegav(isun)
391  END DO
392! 2.5 Output display
393!  WRITE(*,*) 'Les donnees spectrales :'
394!  WRITE(*,*) 'Solaire (SW) ---->'
395!  WRITE(*,*) 'Aerosol number: ', iaer
396!  WRITE(*,*) 'Rayon aerosol: ', radiustab(iaer,idomain,isize)
397!  WRITE(*,*) '<Qext>/Qext(longrefvis) ; omega ; g'
398!  DO isun=1,nsun
399!    WRITE(*,*) QVISsQREF(isun,iaer,isize),&
400!         omegavis(isun,iaer,isize),&
401!         gvis(isun,iaer,isize)
402!  ENDDO
403!  WRITE(*,*) 'QREFvis(',iaer,isize,') = ',QREFvis(iaer,isize)
404!  WRITE(*,*) 'omegaREFvis(',iaer,isize,') = ',&
405!                                      omegaREFvis(iaer,isize)
406! ------------------------------------------------
407ENDDO
408
409!==================================================================
410CASE(2) domain !                  INFRARED DOMAIN (idomain=2)
411!==================================================================
412
413DO isize=1,nsize(iaer,idomain) ! ----------------------------------
414
415! 2.1 solsir is not used anymore; division of Qext(IR) by solsir
416!     has to be done in the input ASCII files (if necessary).
417
418! 2.2 Save the particle sizes
419  radiustab(iaer,idomain,isize)=radiusdyn(isize)
420
421! 2.3 Parameters
422
423  tsol=215.D+0
424  longir(1)=long1ir
425  longir(2)=long1co2
426  longir(3)=long2co2
427  longir(4)=long2ir
428  longref=longrefir(iaer)
429  epref=1.E+0
430
431! 2.4 Averaged optical properties (GCM channels)
432!           epav is <QIR>/Qext(longrefir) since epref=1
433! Notice: Aerave also Computes the extinction coefficient at
434!   reference wavelength (called QREFvis or QREFir,
435!   and not epref, which is a different parameter);
436!   Reference wavelengths are defined for each aerosol in
437!   dimradmar_mod.
438
439  CALL aerave ( nwvl,&
440       wvl(:),ep(:,isize),omeg(:,isize),gfactor(:,isize),&
441       longref,epref,tsol,&
442       nir-1,longir,epav,omegav,gav,&
443       QREFir(iaer,isize),omegaREFir(iaer,isize) )
444!  WRITE(*,*) 'QREFir(',iaer,isize,') = ',QREFir(iaer,isize)
445!  WRITE(*,*) 'omegaREFir(',iaer,isize,') = ',&
446!                                      omegaREFir(iaer,isize)
447
448! 2.5 Computing  <QIR>/Qext(longrefvis)
449
450  DO iir=1,nir-1
451!    WRITE(*,*) 'QIRsQREFir Channel ',iir,': ',epav(iir)
452    epav(iir)=  epav(iir) * QREFir(iaer,isize) / &
453                            QREFvis(iaer,isize)
454  ENDDO
455!  WRITE(*,*) 'Aerosol number', iaer
456!  WRITE(*,*) 'Particle size: ',radiustab(iaer,idomain,isize)
457!  WRITE(*,*) 'Rapport Solaire/IR:',&
458!             QREFvis(iaer,isize) / QREFir(iaer,isize)
459
460! 2.6 Variable assignements
461!           (variables are declared by yomaer.h)
462
463!         Single scattering properties
464!           in each of the "nir" bands
465!           (cf. dimradmars_mod)
466
467! iir=1 : central 15um CO2 bands   
468  QIRsQREF(1,iaer,isize)=epav(2)
469  omegaIR(1,iaer,isize)=omegav(2)
470  gIR(1,iaer,isize)=gav(2)
471
472! iir=2 : CO2 band wings
473!           (same properties than for central part)
474  QIRsQREF(2,iaer,isize)=epav(2)
475  omegaIR(2,iaer,isize)=omegav(2)
476  gIR(2,iaer,isize)=gav(2)
477
478! iir=3 : 9 um band [long1ir - long1co2]
479  QIRsQREF(3,iaer,isize)=epav(1)
480  omegaIR(3,iaer,isize)=omegav(1)
481  gIR(3,iaer,isize)=gav(1)
482
483! iir=4 : Far IR    [long2co2 - long2ir]
484  QIRsQREF(4,iaer,isize)=epav(3)
485  omegaIR(4,iaer,isize)=omegav(3)
486  gIR(4,iaer,isize)=gav(3)
487
488! 2.7 Output display
489
490!  WRITE(*,*) 'AEROSOL PROPERTIES: Number ',iaer
491!  WRITE(*,*) 'Thermal IR (LW) ---->'
492!  WRITE(*,*) 'Particle size: ',radiustab(iaer,idomain,isize)
493!  WRITE(*,*) '<Qext>/Qext(longrefvis) ; omega ; g'
494!  DO iir=1,nir
495!    WRITE(*,*) QIRsQREF(iir,iaer,isize),omegaIR(iir,iaer,isize),&
496!         gIR(iir,iaer,isize)
497!  ENDDO
498!  WRITE(*,*) 'CO2: <Qabs>/Qext(longrefvis) = ',&
499!       QIRsQREF(1,iaer,isize)*(1-omegaIR(1,iaer,isize))
500!  WRITE(*,*) ''
501
502ENDDO ! isize (particle size) -------------------------------------
503
504END SELECT domain
505!==================================================================
506! 3. Deallocate temporary variables (read in ASCII files)
507!==================================================================
508
509DEALLOCATE(wvl)        ! wvl
510DEALLOCATE(radiusdyn)  ! radiusdyn
511DEALLOCATE(ep)         ! ep
512DEALLOCATE(omeg)       ! omeg
513DEALLOCATE(gfactor)    ! g
514
515  END DO ! Loop on iaer
516END DO   ! Loop on idomain
517!==================================================================
518RETURN
519END
Note: See TracBrowser for help on using the repository browser.