source: trunk/LMDZ.PLUTO.old/libf/phypluto/initracer.F @ 3436

Last change on this file since 3436 was 3175, checked in by emillour, 11 months ago

Pluto PCM:
Add the old Pluto LMDZ for reference (required prior step to making
an LMDZ.PLUTO using the same framework as the other physics packages).
TB+EM

File size: 8.3 KB
Line 
1      SUBROUTINE initracer()
2
3      use comgeomfi_h
4      use aerosol_mod
5      IMPLICIT NONE
6c=======================================================================
7c   subject:
8c   --------
9c   Initialization related to tracer
10c   (transported dust, water, chemical species, ice...)
11c
12c   Name of the tracer
13c
14c   Test of dimension :
15c   Initialize COMMON tracer in tracer.h, using tracer names provided
16c   by the dynamics in "advtrac.h"
17c
18c   author: F.Forget
19c   ------
20c            Ehouarn Millour (oct. 2008) identify tracers by their names
21c            Tanguy Bertrand (oct. 2014) Adaptation Pluto
22c            Tanguy Bertrand (dec. 2014) Adding tracers for haze
23c                                            -precurseur
24c                                            -haze
25c=======================================================================
26
27
28#include "dimensions.h"
29#include "dimphys.h"
30#include "comcstfi.h"
31#include "callkeys.h"
32#include "tracer.h"
33#include "advtrac.h"
34#include "fisice.h"
35#include "surfdat.h"
36
37!      real qsurf(ngridmx,nqmx)       ! tracer on surface (e.g.  kg.m-2)
38      character(len=20) :: txt ! to store some text
39      integer iq,ig,count,i
40      real r0_lift , reff_lift, rho_haze
41      integer nqhaze(nqmx)               ! to store haze tracers
42!      logical :: oldnames ! =.true. if old tracer naming convention (q01,...)
43      integer ia, block
44      CHARACTER(LEN=20) :: tracername ! to temporarily store text
45
46c-----------------------------------------------------------------------
47c  radius(nqmx)      ! aerosol particle radius (m)
48c  rho_q(nqmx)       ! tracer densities (kg.m-3)
49c  rho_ch4_ice           ! ch4 ice density
50c  rho_co_ice           ! co ice density
51c  varian            ! Characteristic variance of log-normal distribution
52c-----------------------------------------------------------------------
53
54! Initialization: get tracer names from the dynamics and check if we are
55!                 using 'old' tracer convention ('q01',q02',...)
56!                 or new convention (full tracer names)
57
58       ! copy tracer names from dynamics
59        do iq=1,nqmx
60          noms(iq)=tnom(iq)
61        enddo
62
63        print*,'initracer : number of tracers nqmx=',nqmx
64      ! Identify tracers by their names: (and set corresponding values of mmol)
65      ! 0. initialize tracer indexes to zero:
66      ! NB: igcm_* indexes are commons in 'tracer.h'
67      igcm_n2=0
68      igcm_ch4_gas=0
69      igcm_ch4_ice=0
70      igcm_prec_haze=0
71      igcm_co_gas=0
72      igcm_co_ice=0
73
74      nqhaze(:)=0
75      i=0
76      DO iq=1,nqmx
77         txt=noms(iq)
78         IF (txt(1:4).eq."haze") THEN
79            i=i+1
80            nqhaze(i)=iq
81         ENDIF
82      ENDDO
83      if ((haze.or.fasthaze).and.i==0) then
84         print*, 'Haze active but no haze tracer in traceur.def'
85         stop
86      endif
87      igcm_haze=0
88      igcm_haze10=0
89      igcm_haze30=0
90      igcm_haze50=0
91      igcm_haze100=0
92
93!     Eddy diffusion tracers
94      igcm_eddy1e6=0
95      igcm_eddy1e7=0
96      igcm_eddy5e7=0
97      igcm_eddy1e8=0
98      igcm_eddy5e8=0
99      write(*,*) 'initracer: noms() ', noms
100
101c     Radius and densities
102      rho_n2=1000        ! n2 ice
103      rho_ch4_ice=520.       ! rho ch4 ice
104      rho_co_ice=520.       ! rho ch4 ice
105      rho_haze=800.     ! haze
106      ! first initialization
107      call zerophys(nqmx,rho_q)
108      call zerophys(nqmx,radius)
109
110      ! find tracers
111      count=0
112      do iq=1,nqmx
113        if (noms(iq).eq."n2") then
114          igcm_n2=iq
115          mmol(igcm_n2)=28.
116          count=count+1
117          write(*,*) 'Tracer ',count,' = n2'
118        endif
119        if (noms(iq).eq."ch4_gas") then
120          igcm_ch4_gas=iq
121          mmol(igcm_ch4_gas)=16.
122          count=count+1
123          write(*,*) 'Tracer ',count,' = ch4 gas'
124        endif
125        if (noms(iq).eq."ch4_ice") then
126          igcm_ch4_ice=iq
127          mmol(igcm_ch4_ice)=16.
128          radius(iq)=3.e-6
129          rho_q(iq)=rho_ch4_ice
130          count=count+1
131          write(*,*) 'Tracer ',count,' = ch4 ice'
132        endif
133        if (noms(iq).eq."co_gas") then
134          igcm_co_gas=iq
135          mmol(igcm_co_gas)=28.
136          count=count+1
137          write(*,*) 'Tracer ',count,' = co gas'
138        endif
139        if (noms(iq).eq."co_ice") then
140          igcm_co_ice=iq
141          mmol(igcm_co_ice)=28.
142          radius(iq)=3.e-6
143          rho_q(iq)=rho_co_ice
144          count=count+1
145          write(*,*) 'Tracer ',count,' = co ice'
146        endif
147        if (noms(iq).eq."prec_haze") then
148          igcm_prec_haze=iq
149          count=count+1
150          write(*,*) 'Tracer ',count,' = prec haze'
151        endif
152        if (noms(iq).eq."haze") then
153          igcm_haze=iq
154          count=count+1
155          radius(iq)=rad_haze
156          rho_q(iq)=rho_haze
157          write(*,*) 'Tracer ',count,' = haze'
158        endif
159        if (noms(iq).eq."haze10") then
160          igcm_haze10=iq
161          count=count+1
162          radius(iq)=10.e-9
163          rho_q(iq)=rho_haze
164          write(*,*) 'Tracer ',count,' = haze10'
165        endif
166        if (noms(iq).eq."haze30") then
167          igcm_haze30=iq
168          count=count+1
169          radius(iq)=30.e-9
170          rho_q(iq)=rho_haze
171          write(*,*) 'Tracer ',count,' = haze30'
172        endif
173        if (noms(iq).eq."haze50") then
174          igcm_haze50=iq
175          count=count+1
176          radius(iq)=50.e-9
177          rho_q(iq)=rho_haze
178          write(*,*) 'Tracer ',count,' = haze50'
179        endif
180        if (noms(iq).eq."haze100") then
181          igcm_haze100=iq
182          count=count+1
183          radius(iq)=100.e-9
184          rho_q(iq)=rho_haze
185          write(*,*) 'Tracer ',count,' = haze100'
186        endif
187!       Eddy diffusion tracers
188        if (noms(iq).eq."eddy1e6") then
189          igcm_eddy1e6=iq
190          count=count+1
191          write(*,*) 'Tracer ',count,' = eddy1e6'
192        endif
193        if (noms(iq).eq."eddy1e7") then
194          igcm_eddy1e7=iq
195          count=count+1
196          write(*,*) 'Tracer ',count,' = eddy1e7'
197        endif
198        if (noms(iq).eq."eddy5e7") then
199          igcm_eddy5e7=iq
200          count=count+1
201          write(*,*) 'Tracer ',count,' = eddy5e7'
202        endif
203        if (noms(iq).eq."eddy1e8") then
204          igcm_eddy1e8=iq
205          count=count+1
206          write(*,*) 'Tracer ',count,' = eddy1e8'
207        endif
208        if (noms(iq).eq."eddy5e8") then
209          igcm_eddy5e8=iq
210          count=count+1
211          write(*,*) 'Tracer ',count,' = eddy5e8'
212        endif
213      enddo ! of do iq=1,nqmx
214     
215      ! check that we identified all tracers:
216      if (count.ne.nqmx) then
217        write(*,*) "initracer: found only ",count," tracers"
218        write(*,*) "               expected ",nqmx
219        do iq=1,count
220          write(*,*)'      ',iq,' ',trim(noms(iq))
221        enddo
222        stop
223      else
224        write(*,*) "initracer: found all expected tracers, namely:"
225        do iq=1,nqmx
226          write(*,*)'      ',iq,' ',trim(noms(iq))
227        enddo
228      endif
229
230c------------------------------------------------------------
231c     Initialisation tracers ....
232c------------------------------------------------------------
233
234c     Other initializations
235c     ------------------------------
236
237c     Latent heat :
238      lw_co=274000.
239      lw_ch4=586700.
240      lw_n2=2.5e5
241
242c     HAZE:
243      if (haze) then
244         ! the sedimentation radius remains radius(igcm_haze)
245         if (fractal) then
246            nmono=nb_monomer
247         else
248            nmono=1
249         endif 
250
251         ia=0
252         if (aerohaze) then
253            ia=ia+1
254            iaero_haze=ia
255            write(*,*) '--- number of haze aerosol = ', iaero_haze
256
257            block=0  ! Only one type of haze is active : the first one set in traceur.def
258            do iq=1,nqmx
259              tracername=noms(iq)
260              write(*,*) "--> tracername ",iq,'/',nqmx,' = ',tracername
261              if (tracername(1:4).eq."haze".and.block.eq.0) then
262                i_haze=iq
263                block=1
264                write(*,*) "i_haze=",i_haze
265                write(*,*) "Careful: if you set many haze traceurs in
266     & traceur.def,only ",tracername," will be radiatively active
267     & (first one in traceur.def)"
268              endif
269            enddo
270         endif
271      endif
272
273c     Output for records:
274c     ~~~~~~~~~~~~~~~~~~
275      write(*,*)
276      Write(*,*) '******** initracer :  parameters :'
277      write(*,*) 'radius  = ', radius
278      write(*,*) 'density = ', rho_q
279      write(*,*)
280      write(*,*) 'monomers = ', nmono
281
282      end
Note: See TracBrowser for help on using the repository browser.