source: trunk/LMDZ.GENERIC/libf/phystd/initracer.F @ 1644

Last change on this file since 1644 was 1621, checked in by emillour, 8 years ago

Further work on full dynamics/physics separation.

LMDZ.COMMON:

  • added phy_common/vertical_layers_mod.F90 to store information on vertical grid. This is where routines in the physics should get the information.
  • The contents of vertical_layers_mod intialized via dynphy_lonlat/inigeomphy_mod.F90.

LMDZ.MARS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • created an "ini_tracer_mod" routine in module "tracer_mod" for a cleaner initialization of the later.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.GENERIC:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added nqtot to tracer_h.F90.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.VENUS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics. Initialized via iniphysiq. IMPORTANT: there are some hard-coded constants! These should match what is in cpdet_mod.F90 in the dynamics.
  • got rid of references to moyzon_mod module within the physics. The required variables (tmoy, plevmoy) are passed to the physics as arguments to physiq.

LMDZ.TITAN:

  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics.
  • Extra work required to completely decouple physics and dynamics: moyzon_mod should be cleaned up and information passed from dynamics to physics as as arguments. Likewise moyzon_ch and moyzon_mu should not be queried from logic_mod (which is in the dynamics).

EM

File size: 10.8 KB
Line 
1      SUBROUTINE initracer(ngrid,nq,nametrac)
2
3      use surfdat_h
4      USE tracer_h
5      USE callkeys_mod, only: water
6      IMPLICIT NONE
7c=======================================================================
8c   subject:
9c   --------
10c   Initialization related to tracer
11c   (transported dust, water, chemical species, ice...)
12c
13c   Name of the tracer
14c
15c   Test of dimension :
16c   Initialize COMMON tracer in tracer.h, using tracer names provided
17c   by the argument nametrac
18c
19c   author: F.Forget
20c   ------
21c            Ehouarn Millour (oct. 2008) identify tracers by their names
22c=======================================================================
23
24      integer :: ngrid,nq
25
26!      real qsurf(ngrid,nq)       ! tracer on surface (e.g.  kg.m-2)
27!      real co2ice(ngrid)           ! co2 ice mass on surface (e.g.  kg.m-2)
28      character(len=20) :: txt ! to store some text
29      integer iq,ig,count
30      real r0_lift , reff_lift
31!      logical :: oldnames ! =.true. if old tracer naming convention (q01,...)
32
33      character*20 nametrac(nq)   ! name of the tracer from dynamics
34
35
36c-----------------------------------------------------------------------
37c  radius(nq)      ! aerosol particle radius (m)
38c  rho_q(nq)       ! tracer densities (kg.m-3)
39c  qext(nq)        ! Single Scat. Extinction coeff at 0.67 um
40c  alpha_lift(nq)  ! saltation vertical flux/horiz flux ratio (m-1)
41c  alpha_devil(nq) ! lifting coeeficient by dust devil
42c  rho_dust          ! Mars dust density
43c  rho_ice           ! Water ice density
44c  doubleq           ! if method with mass (iq=1) and number(iq=2) mixing ratio
45c  varian            ! Characteristic variance of log-normal distribution
46c-----------------------------------------------------------------------
47
48       nqtot=nq
49       !! we allocate once for all arrays in common in tracer_h.F90
50       !! (supposedly those are not used before call to initracer)
51       IF (.NOT.ALLOCATED(noms)) ALLOCATE(noms(nq))
52       ALLOCATE(mmol(nq))
53       ALLOCATE(radius(nq))
54       ALLOCATE(rho_q(nq))
55       ALLOCATE(qext(nq))
56       ALLOCATE(alpha_lift(nq))
57       ALLOCATE(alpha_devil(nq))
58       ALLOCATE(qextrhor(nq))
59       ALLOCATE(igcm_dustbin(nq))
60       !! initialization
61       alpha_lift(:)=0.
62       alpha_devil(:)=0.
63
64! Initialization: get tracer names from the dynamics and check if we are
65!                 using 'old' tracer convention ('q01',q02',...)
66!                 or new convention (full tracer names)
67      ! check if tracers have 'old' names
68
69! copy tracer names from dynamics
70        do iq=1,nq
71          noms(iq)=nametrac(iq)
72        enddo
73
74
75! Identify tracers by their names: (and set corresponding values of mmol)
76      ! 0. initialize tracer indexes to zero:
77      ! NB: igcm_* indexes are commons in 'tracer.h'
78      do iq=1,nq
79        igcm_dustbin(iq)=0
80      enddo
81      igcm_dust_mass=0
82      igcm_dust_number=0
83      igcm_h2o_vap=0
84      igcm_h2o_ice=0
85      igcm_co2=0
86      igcm_co=0
87      igcm_o=0
88      igcm_o1d=0
89      igcm_o2=0
90      igcm_o3=0
91      igcm_h=0
92      igcm_h2=0
93      igcm_oh=0
94      igcm_ho2=0
95      igcm_h2o2=0
96      igcm_n2=0
97      igcm_ar=0
98      igcm_ar_n2=0
99      igcm_co2_ice=0
100
101      write(*,*) 'initracer: noms() ', noms
102
103
104      !print*,'Setting dustbin = 0 in initracer.F'
105      !dustbin=0
106
107      ! 1. find dust tracers
108      count=0
109!      if (dustbin.gt.0) then
110!        do iq=1,nq
111!          txt=" "
112!          write(txt,'(a4,i2.2)')'dust',count+1   
113!          if (noms(iq).eq.txt) then
114!            count=count+1
115!            igcm_dustbin(count)=iq
116!            mmol(iq)=100.
117!          endif
118!        enddo !do iq=1,nq
119!      endif ! of if (dustbin.gt.0)
120
121
122!      if (doubleq) then
123!        do iq=1,nq
124!          if (noms(iq).eq."dust_mass") then
125!            igcm_dust_mass=iq
126!            count=count+1
127!          endif
128!          if (noms(iq).eq."dust_number") then
129!            igcm_dust_number=iq
130!            count=count+1
131!          endif
132!        enddo
133!      endif ! of if (doubleq)
134      ! 2. find chemistry and water tracers
135      do iq=1,nq
136        if (noms(iq).eq."co2") then
137          igcm_co2=iq
138          mmol(igcm_co2)=44.
139          count=count+1
140!          write(*,*) 'co2: count=',count
141        endif
142        if (noms(iq).eq."co2_ice") then
143          igcm_co2_ice=iq
144          mmol(igcm_co2_ice)=44.
145          count=count+1
146!          write(*,*) 'co2_ice: count=',count
147        endif
148        if (noms(iq).eq."h2o_vap") then
149          igcm_h2o_vap=iq
150          mmol(igcm_h2o_vap)=18.
151          count=count+1
152!          write(*,*) 'h2o_vap: count=',count
153        endif
154        if (noms(iq).eq."h2o_ice") then
155          igcm_h2o_ice=iq
156          mmol(igcm_h2o_ice)=18.
157          count=count+1
158!          write(*,*) 'h2o_ice: count=',count
159        endif
160      enddo ! of do iq=1,nq
161     
162      ! check that we identified all tracers:
163      if (count.ne.nq) then
164        write(*,*) "initracer: found only ",count," tracers"
165        write(*,*) "               expected ",nq
166        do iq=1,count
167          write(*,*)'      ',iq,' ',trim(noms(iq))
168        enddo
169!        stop
170      else
171        write(*,*) "initracer: found all expected tracers, namely:"
172        do iq=1,nq
173          write(*,*)'      ',iq,' ',trim(noms(iq))
174        enddo
175      endif
176
177
178c------------------------------------------------------------
179c     Initialisation tracers ....
180c------------------------------------------------------------
181      call zerophys(nq,rho_q)
182
183      rho_dust=2500.  ! Mars dust density (kg.m-3)
184      rho_ice=920.    ! Water ice density (kg.m-3)
185      rho_co2=1620.   ! CO2 ice density (kg.m-3)
186
187
188
189c$$$      if (doubleq) then
190c$$$c       "doubleq" technique
191c$$$c       -------------------
192c$$$c      (transport of mass and number mixing ratio)
193c$$$c       iq=1: Q mass mixing ratio, iq=2: N number mixing ratio
194c$$$
195c$$$        if( (nq.lt.2).or.(water.and.(nq.lt.3)) ) then
196c$$$          write(*,*)'initracer: nq is too low : nq=', nq
197c$$$          write(*,*)'water= ',water,' doubleq= ',doubleq   
198c$$$        end if
199c$$$
200c$$$        varian=0.637    ! Characteristic variance   
201c$$$        qext(igcm_dust_mass)=3.04   ! reference extinction at 0.67 um for ref dust
202c$$$        qext(igcm_dust_number)=3.04 ! reference extinction at 0.67 um for ref dust
203c$$$        rho_q(igcm_dust_mass)=rho_dust
204c$$$        rho_q(igcm_dust_number)=rho_dust
205c$$$
206c$$$c       Intermediate calcul for computing geometric mean radius r0
207c$$$c       as a function of mass and number mixing ratio Q and N
208c$$$c       (r0 = (r3n_q * Q/ N)
209c$$$        r3n_q = exp(-4.5*varian**2)*(3./4.)/(pi*rho_dust)
210c$$$
211c$$$c       Intermediate calcul for computing effective radius reff
212c$$$c       from geometric mean radius r0
213c$$$c       (reff = ref_r0 * r0)
214c$$$        ref_r0 = exp(2.5*varian**2)
215c$$$       
216c$$$c       lifted dust :
217c$$$c       '''''''''''
218c$$$        reff_lift = 3.e-6      !  Effective radius of lifted dust (m)
219c$$$        alpha_devil(igcm_dust_mass)=9.e-9   !  dust devil lift mass coeff
220c$$$        alpha_lift(igcm_dust_mass)=3.0e-15  !  Lifted mass coeff
221c$$$
222c$$$        r0_lift = reff_lift/ref_r0
223c$$$        alpha_devil(igcm_dust_number)=r3n_q*
224c$$$     &                        alpha_devil(igcm_dust_mass)/r0_lift**3
225c$$$        alpha_lift(igcm_dust_number)=r3n_q*
226c$$$     &                        alpha_lift(igcm_dust_mass)/r0_lift**3
227c$$$
228c$$$c       Not used:
229c$$$        radius(igcm_dust_mass) = 0.
230c$$$        radius(igcm_dust_number) = 0.
231c$$$
232c$$$      else
233
234
235c$$$       if (dustbin.gt.1) then
236c$$$        print*,'ATTENTION:',
237c$$$     $   ' properties of dust need input in initracer !!!'
238c$$$        stop
239c$$$
240c$$$       else if (dustbin.eq.1) then
241c$$$
242c$$$c       This will be used for 1 dust particle size:
243c$$$c       ------------------------------------------
244c$$$        radius(igcm_dustbin(1))=3.e-6
245c$$$        Qext(igcm_dustbin(1))=3.04
246c$$$        alpha_lift(igcm_dustbin(1))=0.0e-6
247c$$$        alpha_devil(igcm_dustbin(1))=7.65e-9
248c$$$        qextrhor(igcm_dustbin(1))=(3./4.)*Qext(igcm_dustbin(1))
249c$$$     &                         /(rho_dust*radius(igcm_dustbin(1)))
250c$$$        rho_q(igcm_dustbin(1))=rho_dust
251c$$$
252c$$$       endif
253c$$$!      end if    ! (doubleq)
254
255c     Initialization for water vapor
256c     ------------------------------
257      if(water) then
258         radius(igcm_h2o_vap)=0.
259         Qext(igcm_h2o_vap)=0.
260         alpha_lift(igcm_h2o_vap) =0.
261         alpha_devil(igcm_h2o_vap)=0.
262         qextrhor(igcm_h2o_vap)= 0.
263
264c       "Dryness coefficient" controlling the evaporation and
265c        sublimation from the ground water ice (close to 1)
266c        HERE, the goal is to correct for the fact
267c        that the simulated permanent water ice polar caps
268c        is larger than the actual cap and the atmospheric
269c        opacity not always realistic.
270
271
272!         if(ngrid.eq.1)
273
274
275!     to be modified for BC+ version?
276
277         !! this is defined in surfdat_h.F90
278         IF (.not.ALLOCATED(dryness)) ALLOCATE(dryness(ngrid))
279         IF (.not.ALLOCATED(watercaptag)) ALLOCATE(watercaptag(ngrid))
280
281         do ig=1,ngrid
282           if (ngrid.ne.1) watercaptag(ig)=.false.
283           dryness(ig) = 1.
284         enddo
285
286
287
288
289!         IF (caps) THEN
290c Perennial H20 north cap defined by watercaptag=true (allows surface to be
291c hollowed by sublimation in vdifc).
292!         do ig=1,ngrid
293!           if (lati(ig)*180./pi.gt.84) then
294!             if (ngrid.ne.1) watercaptag(ig)=.true.
295!             dryness(ig) = 1.
296c Use the following cap definition for high spatial resolution (latitudinal bin <= 5 deg)
297c             if (lati(ig)*180./pi.lt.85.and.long(ig).ge.0) then
298c               if (ngrid.ne.1) watercaptag(ig)=.true.
299c               dryness(ig) = 1.
300c             endif
301c             if (lati(ig)*180./pi.ge.85) then
302c               if (ngrid.ne.1) watercaptag(ig)=.true.
303c               dryness(ig) = 1.
304c             endif
305!           endif  ! (lati>80 deg)
306!         end do ! (ngrid)
307!        ENDIF ! (caps)
308
309!         if(iceparty.and.(nq.ge.2)) then
310
311           radius(igcm_h2o_ice)=3.e-6
312           rho_q(igcm_h2o_ice)=rho_ice
313           Qext(igcm_h2o_ice)=0.
314!           alpha_lift(igcm_h2o_ice) =0.
315!           alpha_devil(igcm_h2o_ice)=0.
316           qextrhor(igcm_h2o_ice)= (3./4.)*Qext(igcm_h2o_ice)
317     $       / (rho_ice*radius(igcm_h2o_ice))
318
319
320
321!         elseif(iceparty.and.(nq.lt.2)) then
322!            write(*,*) 'nq is too low : nq=', nq
323!            write(*,*) 'water= ',water,' iceparty= ',iceparty
324!         endif
325
326      end if  ! (water)
327
328c     Output for records:
329c     ~~~~~~~~~~~~~~~~~~
330      write(*,*)
331      Write(*,*) '******** initracer : dust transport parameters :'
332      write(*,*) 'alpha_lift = ', alpha_lift
333      write(*,*) 'alpha_devil = ', alpha_devil
334      write(*,*) 'radius  = ', radius
335!      if(doubleq) then
336!        write(*,*) 'reff_lift (um) =  ', reff_lift
337!        write(*,*) 'size distribution variance  = ', varian
338!        write(*,*) 'r3n_q , ref_r0 : ', r3n_q , ref_r0
339!      end if
340      write(*,*) 'Qext  = ', qext
341      write(*,*)
342
343      end
Note: See TracBrowser for help on using the repository browser.