source: trunk/LMDZ.GENERIC/libf/phystd/aerosol_mod.F90 @ 2987

Last change on this file since 2987 was 2972, checked in by emillour, 18 months ago

Generic PCM:
Make number of scatterers fully dynamic (i.e. set in callphys.def
and no longer by compilation option "-s #").
One should now specify
naerkind = #
in callphys.def (default is 0).
EM

File size: 6.1 KB
Line 
1!==================================================================
2module aerosol_mod
3implicit none
4
5!==================================================================
6
7!  aerosol indexes: these are initialized to be 0 if the
8!                 corresponding aerosol was not activated in callphys.def
9!                 -- otherwise a value is set via iniaerosol
10      integer, save, protected :: iaero_co2 = 0
11      integer, save, protected :: iaero_h2o = 0
12      integer, save, protected :: iaero_dust = 0
13      integer, save, protected :: iaero_h2so4 = 0
14      logical, save, protected :: noaero = .false.
15!$OMP THREADPRIVATE(iaero_co2,iaero_h2o,iaero_dust,iaero_h2so4,noaero)
16
17! two-layer simple aerosol model
18      integer, save, protected :: iaero_back2lay = 0
19 ! NH3 cloud
20      integer, save, protected :: iaero_nh3 = 0
21! N-layer aerosol model (replaces the 2-layer and hard-coded clouds)
22      integer,dimension(:), allocatable, save, protected :: iaero_nlay
23! Auroral aerosols
24      integer, save, protected :: iaero_aurora = 0
25!$OMP THREADPRIVATE(iaero_back2lay,iaero_nh3,iaero_nlay,iaero_aurora)
26
27! Generic aerosols
28      integer, dimension(:), allocatable, save, protected :: iaero_generic
29      integer, dimension(:), allocatable, save, protected :: i_rgcs_ice
30!$OMP THREADPRIVATE(iaero_generic,i_rgcs_ice)
31
32! Venus clouds
33      integer, save, protected :: iaero_venus1 = 0
34      integer, save, protected :: iaero_venus2 = 0
35      integer, save, protected :: iaero_venus2p = 0
36      integer, save, protected :: iaero_venus3 = 0
37      integer, save, protected :: iaero_venusUV = 0
38!$OMP THREADPRIVATE(iaero_venus1,iaero_venus2,iaero_venus2p)
39!$OMP THREADPRIVATE(iaero_venus3,iaero_venusUV)
40
41!==================================================================
42
43contains
44
45  SUBROUTINE iniaerosol
46
47  use mod_phys_lmdz_para, only : is_master
48  use radinc_h, only: naerkind
49  use tracer_h, only: n_rgcs, nqtot, is_rgcs
50  use callkeys_mod, only: aeroco2, aeroh2o, dusttau, aeroh2so4, &
51                          aeroback2lay, aeronh3, nlayaero, aeronlay, &
52                          aeroaurora, aerogeneric, &
53                          aerovenus1, aerovenus2, aerovenus2p, &
54                          aerovenus3, aerovenusUV
55
56  IMPLICIT NONE
57!=======================================================================
58!   subject:
59!   --------
60!   Initialization related to aerosols
61!   (CO2 aerosols, dust, water, chemical species, ice...)   
62!
63!   author: Laura Kerber, S. Guerlet
64!   ------
65!       
66!=======================================================================
67
68  integer :: i, ia, iq
69
70  ! Special case, dyn. allocation for n-layer depending on callphys.def
71  IF(.NOT.ALLOCATED(iaero_nlay)) ALLOCATE(iaero_nlay(nlayaero))
72  iaero_nlay(:) = 0
73  ! Do the same for iaero_generic and i_rgcs_ice
74  IF (.not. allocated(iaero_generic)) allocate(iaero_generic(aerogeneric))
75  if (.not. allocated(i_rgcs_ice)) allocate(i_rgcs_ice(aerogeneric))
76
77  ! Init of i_rgcs_ice
78  i_rgcs_ice(:) =0
79  ia = 1
80  do iq=1,nqtot
81    if (is_rgcs(iq) .eq. 1) then
82        i_rgcs_ice(ia)=iq
83        ia = ia+1
84     endif
85  enddo
86
87  iaero_generic(:)=0
88  ia=0
89  if (aeroco2) then
90     ia=ia+1
91     iaero_co2=ia
92  endif
93  if (is_master) write(*,*) '--- CO2 aerosol = ', iaero_co2
94
95  if (aeroh2o) then
96     ia=ia+1
97     iaero_h2o=ia
98      endif
99  if (is_master) write(*,*) '--- H2O aerosol = ', iaero_h2o
100
101  if (dusttau.gt.0) then
102     ia=ia+1
103     iaero_dust=ia
104  endif
105  if (is_master) write(*,*) '--- Dust aerosol = ', iaero_dust
106
107  if (aeroh2so4) then
108     ia=ia+1
109     iaero_h2so4=ia
110  endif
111  if (is_master) write(*,*) '--- H2SO4 aerosol = ', iaero_h2so4
112     
113  if (aeroback2lay) then
114     ia=ia+1
115     iaero_back2lay=ia
116  endif
117  if (is_master) write(*,*) '--- Two-layer aerosol = ', iaero_back2lay
118
119  if (aeronh3) then
120     ia=ia+1
121     iaero_nh3=ia
122  endif
123  if (is_master) write(*,*) '--- NH3 Cloud = ', iaero_nh3
124
125  if (aeronlay) then
126     do i=1,nlayaero
127       ia=ia+1
128       iaero_nlay(i)=ia
129     enddo
130  endif
131  if (is_master) write(*,*) '--- N-layer aerosol = ', iaero_nlay
132
133  if (aeroaurora) then
134     ia=ia+1
135     iaero_aurora=ia
136  endif
137  if (is_master) write(*,*) '--- Auroral aerosols = ', iaero_aurora
138
139  if (aerovenus1) then
140     ia=ia+1
141     iaero_venus1=ia
142  endif
143  if (is_master) write(*,*) '--- Venus cloud, mode 1 aerosol = ', iaero_venus1
144
145  if (aerovenus2) then
146     ia=ia+1
147     iaero_venus2=ia
148  endif
149  if (is_master) write(*,*) '--- Venus cloud, mode 2 aerosol = ', iaero_venus2
150
151  if (aerovenus2p) then
152     ia=ia+1
153     iaero_venus2p=ia
154  endif
155  if (is_master) write(*,*) '--- Venus cloud, mode 2p aerosol = ', iaero_venus2p
156
157  if (aerovenus3) then
158     ia=ia+1
159     iaero_venus3=ia
160  endif
161  if (is_master) write(*,*) '--- Venus cloud, mode 3 aerosol = ', iaero_venus3
162
163  if (aerovenusUV) then
164     ia=ia+1
165     iaero_venusUV=ia
166  endif
167  if (is_master) write(*,*) '--- Venus cloud, UV absorber = ', iaero_venusUV
168
169  if (aerogeneric .ne. 0) then
170     do i=1,aerogeneric
171        ia = ia+1
172        iaero_generic(i) = ia
173     enddo
174  endif
175     
176  if (is_master) then
177    write(*,*)'--- Radiative Generic Condensable Species = ',iaero_generic
178
179    write(*,*) '=== Number of aerosols= ', ia
180  endif ! of is_master
181
182! For the zero aerosol case, we currently make a dummy co2 aerosol which is zero everywhere.
183! (See aeropacity.F90 for how this works). A better solution would be to turn off the
184! aerosol machinery in the no aerosol case, but this would be complicated. LK
185
186  if (ia.eq.0) then  !For the zero aerosol case.
187     ia = 1
188     noaero = .true.
189     iaero_co2=ia
190  endif
191
192  if (ia.ne.naerkind) then
193    if (is_master) then
194      print*, 'Aerosols counted not equal to naerkind'
195      print*, 'set correct value for nearkind in callphys.def'
196      print*, 'which should be ',ia
197      print*, 'according to current options in callphys.def'
198      print*, 'or change/correct incompatible options there'
199      print*, 'Abort in iniaerosol'
200    endif
201    call abort_physic("iniaerosl",'wrong number of aerosols',1)
202  endif ! of if (ia.ne.naerkind)
203
204  END SUBROUTINE iniaerosol
205
206end module aerosol_mod
207!==================================================================
Note: See TracBrowser for help on using the repository browser.