source: trunk/WRF.COMMON/WRFV2/mars_lmd/libf/phymars/initracer.F @ 2756

Last change on this file since 2756 was 11, checked in by aslmd, 14 years ago

spiga@svn-planeto:ajoute le modele meso-echelle martien

File size: 9.7 KB
Line 
1      SUBROUTINE initracer(qsurf,co2ice)
2
3       IMPLICIT NONE
4c=======================================================================
5c   subject:
6c   --------
7c   Initialisation related to tracer
8c (transported dust, water, chemical species, ice...)
9c
10c   Name of the tracer
11c
12c   Test of dimension :
13c   Initialise COMMON tracer in tracer.h
14c
15c   If water=T : q(iq=nqmx) is the water mass mixing ratio
16c   If water=T and iceparty=T : q(iq=nqmx-1) is the ice mass mixing ratio
17
18c   If there is transported dust, it uses iq=1 to iq=dustbin
19c   If there is no transported dust : dustbin=0
20c   If doubleq=T : q(iq=1) is the dust mass mixing ratio
21c                  q(iq=2) is the dust number mixing ratio
22
23c   If (photochem.or.thermochem) there is "ncomp" chemical species (ncomp
24c   is set in aeronomars/chimiedata.h) using the ncomp iq values starting at
25c      iq=nqchem_min = dustbin+1   (nqchem_min is defined in inifis.F)
26c   
27c
28c   author: F.Forget
29c   ------
30c    Modifs: Franck Montmessin, Sebastien Lebonnois (june 2003)
31c
32c=======================================================================
33
34
35#include "dimensions.h"
36#include "dimphys.h"
37#include "comcstfi.h"
38#include "callkeys.h"
39#include "tracer.h"
40
41#include "comgeomfi.h"
42#include "watercap.h"
43#include "aerice.h"
44#include "fisice.h"
45#include "chimiedata.h"
46
47
48      real qsurf(ngridmx,nqmx)       ! tracer on surface (e.g.  kg.m-2)
49      real co2ice(ngridmx)           ! co2 ice mass on surface (e.g.  kg.m-2)
50      integer iq,ig
51      real r0_lift , reff_lift
52
53c-----------------------------------------------------------------------
54c  radius(nqmx)      ! aerosol particle radius (m)
55c  qext(nqmx)        ! Single Scat. Extinction coeff at 0.67 um
56c  alpha_lift(nqmx)  ! saltation vertical flux/horiz flux ratio (m-1)
57c  alpha_devil(nqmx) ! lifting coeeficient by dust devil
58c  rho_dust          ! Mars dust density
59c  rho_ice           ! Water ice density
60c  doubleq           ! if method with mass (iq=1) and number(iq=2) mixing ratio
61c  varian            ! Characteristic variance of log-normal distribution
62c-----------------------------------------------------------------------
63
64
65c------------------------------------------------------------
66c     Test Dimensions tracers
67c------------------------------------------------------------
68
69      if(photochem.or.thermochem) then
70          if (iceparty) then
71              if ((nqchem_min+ncomp+1).ne.nqmx) then
72                 print*,'********* Dimension problem! ********'
73                 print*,"nqchem_min+ncomp+1).ne.nqmx"
74                 print*,"ncomp: ",ncomp
75                 print*,"nqchem_min: ",nqchem_min
76                 print*,"nqmx: ",nqmx
77                 print*,'Change ncomp in chimiedata.h'
78               endif
79          else
80               if ((nqchem_min+ncomp).ne.nqmx) then
81                 print*,'********* Dimension problem! ********'
82                 print*,"nqchem_min+ncomp).ne.nqmx"
83                 print*,"ncomp: ",ncomp
84                 print*,"nqchem_min: ",nqchem_min
85                 print*,"nqmx: ",nqmx
86                 print*,'Change ncomp in chimiedata.h'
87                 STOP
88               endif
89            endif
90          endif
91
92c------------------------------------------------------------
93c         NAME and molar mass of the tracer
94c------------------------------------------------------------
95
96c noms and mmol vectors:
97      if (water) then
98         mmol(nqmx) = 18.
99         noms(nqmx)   = 'h2o'
100      end if
101      if (iceparty) then
102         noms(nqmx-1) = 'ice'
103         mmol(nqmx-1) = 18.
104      end if
105      if(photochem.or.thermochem) then
106         do iq=nqchem_min, nqchem_min+ncomp-1
107             noms(iq) = nomchem(iq-nqchem_min+1)
108             mmol(iq) = mmolchem(iq-nqchem_min+1)
109         enddo
110      end if
111      if (dustbin.ge.1) then
112          do iq=1,dustbin
113            noms(iq) = 'dust'
114            mmol(iq) = 100.
115          enddo
116          if (doubleq) then
117           noms(1) = 'dust mass mix. ratio'
118           noms(dustbin) = 'dust number mix. ratio'
119          end if
120      end if
121
122c     Simulation of CO2 + neutral gaz
123      if ((dustbin.eq.0).and.(.not.water)) then
124         noms(1) = 'co2'
125         mmol(1) = 44
126         if (nqmx.eq.2)then
127            noms(nqmx) = 'Ar_N2'
128            mmol(nqmx) = 30
129         end if
130      end if
131   
132
133c------------------------------------------------------------
134c     Initialisation tracers ....
135c------------------------------------------------------------
136
137      rho_dust=2500.  ! Mars dust density (kg.m-3)
138      rho_ice=920.    ! Water ice density (kg.m-3)
139
140      if (doubleq) then
141c       "doubleq" technique
142c       -------------------
143c      (transport of mass and number mixing ratio)
144c       iq=1: Q mass mixing ratio, iq=2: N number mixing ratio
145
146        if( (nqmx.lt.2).or.(water.and.(nqmx.lt.3)) ) then
147            write(*,*) 'nqmx is too low : nqmx=', nqmx
148            write(*,*) 'water= ',water,' doubleq= ',doubleq   
149        end if
150
151        varian=0.637    ! Characteristic variance   
152        qext(1)=3.04    ! reference extinction at 0.67 um for ref dust
153        qext(2)=3.04    ! reference extinction at 0.67 um for ref dust
154
155c       Intermediate calcul for computing geometric mean radius r0
156c       as a function of mass and number mixing ratio Q and N
157c       (r0 = (r3n_q * Q/ N)
158        r3n_q = exp(-4.5*varian**2)*(3./4.)/(pi*rho_dust)
159
160c       Intermediate calcul for computing effective radius reff
161c       from geometric mean radius r0
162c       (reff = ref_r0 * r0)
163        ref_r0 = exp(2.5*varian**2)
164       
165c       lifted dust :
166c       '''''''''''
167        reff_lift = 3.e-6      !  Effective radius of lifted dust (m)
168        alpha_devil(1)=9.e-9   !  dust devil lift mass coeff
169        alpha_lift(1)=3.0e-15  !  Lifted mass coeff
170
171        r0_lift = reff_lift/ref_r0
172        alpha_devil(2)= r3n_q * alpha_devil(1)/r0_lift**3
173        alpha_lift(2)= r3n_q * alpha_lift(1)/r0_lift**3
174
175c       Not used:
176        radius(1) = 0.
177        radius(2) = 0.
178
179      else
180
181       if (dustbin.gt.1) then
182        print*,'ATTENTION:',
183     $   ' properties of dust need input in initracer !!!'
184        stop
185
186       else if (dustbin.eq.1) then
187
188c       This will be used for 1 dust particle size:
189c       ------------------------------------------
190cc        radius(1)=3.e-6
191cc        Qext(1)=3.04
192cc        alpha_lift(1)=0.0e-6
193cc        alpha_devil(1)=7.65e-9
194        radius(1)=1.e-6
195        Qext(1)=3.04       
196        alpha_lift(1)=1.
197        alpha_devil(1)=0.0e-9       
198        qextrhor(1)= (3./4.)*Qext(1) / (rho_dust*radius(1))
199
200       endif
201      end if    ! (doubleq)
202
203c     Initialization for photochemistry:
204c     ---------------------------------
205      if (photochem) then
206        do iq=nqchem_min,nqmx
207         radius(iq)=0.
208         Qext(iq)=0.
209         alpha_lift(iq) =0.
210         alpha_devil(iq)=0.
211         qextrhor(iq)= 0.
212        enddo
213      endif
214
215c     Initialization for water vapor
216c     ------------------------------
217      if(water) then
218         radius(nqmx)=0.
219         Qext(nqmx)=0.
220         alpha_lift(nqmx) =0.
221         alpha_devil(nqmx)=0.
222         qextrhor(nqmx)= 0.
223
224c       "Dryness coefficient" controlling the evaporation and
225c        sublimation from the ground water ice (close to 1)
226c        HERE, the goal is to correct for the fact
227c        that the simulated permanent water ice polar caps
228c        is larger than the actual cap and the atmospheric
229c        opacity not always realistic.
230
231         do ig=1,ngridmx
232           if (ngridmx.ne.1) watercaptag(ig)=.false.
233           dryness(ig) = 1.
234           if (activice) pclc(ig)=1.
235         enddo
236
237         IF (caps) THEN
238c Perennial H20 north cap defined by watercaptag=true (allows surface to be
239c hollowed by sublimation in vdifc).
240c Cloud area fraction (pclc) is defined here.
241         do ig=1,ngridmx
242           if (lati(ig)*180./pi.gt.84) then
243             if (ngridmx.ne.1) watercaptag(ig)=.true.
244             dryness(ig) = 1.
245             if (activice)then
246               pclc(ig)=1.
247               print*,'Cloud area ratio : ',pclc(ig),' at lat '
248     $        ,lati(ig)*180./pi
249             endif
250c Use the following cap definition for high spatial resolution (latitudinal bin <= 5 deg)
251c             if (lati(ig)*180./pi.lt.85.and.long(ig).ge.0) then
252c               if (ngridmx.ne.1) watercaptag(ig)=.true.
253c               pclc(ig)=.3
254c               dryness(ig) = 1.
255c               print*,'Cloud area ratio : ',pclc(ig),' at lat '
256c             endif
257c             if (lati(ig)*180./pi.ge.85) then
258c               if (ngridmx.ne.1) watercaptag(ig)=.true.
259c               dryness(ig) = 1.
260c               pclc(ig)=.3
261c               print*,'Cloud area ratio : ',pclc(ig),' at lat '
262c             endif
263           endif  ! (lati>80 deg)
264         end do ! (ngridmx)
265        ENDIF ! (caps)
266
267         if(iceparty.and.nqmx.ge.2) then
268           radius(nqmx-1)=3.e-6
269           Qext(nqmx-1)=0.
270           alpha_lift(nqmx-1) =0.
271           alpha_devil(nqmx-1)=0.
272           if (activice) then
273             radius(nqmx-1)=rcrystal
274             Qext(nqmx-1)=qrefice
275           endif
276           qextrhor(nqmx-1)= (3./4.)*Qext(nqmx-1)
277     $       / (rho_ice*radius(nqmx-1))
278         elseif(iceparty.and.nqmx.lt.2) then
279            write(*,*) 'nqmx is too low : nqmx=', nqmx
280            write(*,*) 'water= ',water,' iceparty= ',iceparty
281         endif
282
283      end if  ! (water)
284
285c     Output for records:
286c     ~~~~~~~~~~~~~~~~~~
287      write(*,*)
288      Write(*,*) '******** initracer : dust transport parameters :'
289      write(*,*) 'alpha_lift = ', alpha_lift
290      write(*,*) 'alpha_devil = ', alpha_devil
291      write(*,*) 'radius  = ', radius
292      if(doubleq) then
293        write(*,*) 'reff_lift (um) =  ', reff_lift
294        write(*,*) 'size distribution variance  = ', varian
295        write(*,*) 'r3n_q , ref_r0 : ', r3n_q , ref_r0
296      end if
297      write(*,*) 'Qext  = ', qext
298      write(*,*)
299
300      end
Note: See TracBrowser for help on using the repository browser.