source: trunk/LMDZ.MARS/libf/phymars/dustlift.F @ 1038

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

MESOSCALE
LMDZ.MARS

--> Performed the necessary modifications for dynamic tracers

to work with the mesoscale model (new physics).

--> Added precompiling flag MESOSCALE around pressure modifications

done in revision 883. This makes the mesoscale model become crazy.

--> Added an option -e in makemeso to erase a configuration and start over.

NOTE
--> not sure recent versions (rev>1000) are compliant with nesting compilation.
--> use mesoscale model + new physics with caution. still not stabilized.

File size: 4.7 KB
Line 
1      SUBROUTINE dustlift(ngrid,nlay,nq,rho,
2     $                  pcdh_true,pcdh,co2ice,
3     $                  dqslift)
4
5#ifndef MESOSCALE
6      use tracer_mod, only: alpha_lift, radius
7#else
8      use tracer_mod, only: alpha_lift, radius,
9     &                      igcm_dust_mass, igcm_dust_number,
10     &                      ref_r0,r3n_q
11#endif
12      IMPLICIT NONE
13
14c=======================================================================
15c
16c  Dust lifting by surface winds
17c  Computing flux to the middle of the first layer
18c  (Called by vdifc)
19c
20c=======================================================================
21
22c-----------------------------------------------------------------------
23c   declarations:
24c   -------------
25
26#include "dimensions.h"
27#include "dimphys.h"
28#include "comcstfi.h"
29!#include "tracer.h"
30
31c
32c   arguments:
33c   ----------
34
35c   INPUT
36      integer ngrid, nlay, nq 
37      real rho(ngrid)  ! density (kg.m-3) at surface
38      real pcdh_true(ngrid) ! Cd
39      real pcdh(ngrid) ! Cd * |V|
40      real co2ice(ngrid)
41
42c   OUTPUT
43      real dqslift(ngrid,nq) !surface dust flux to mid-layer (<0 when lifing)
44c     real pb(ngrid,nlay) ! diffusion to surface coeff.
45
46c   local:
47c   ------
48      INTEGER ig,iq
49      REAL fhoriz(ngridmx)  ! Horizontal dust flux
50      REAL ust,us
51      REAL stress_seuil
52      SAVE stress_seuil
53      DATA stress_seuil/0.0225/   ! stress seuil soulevement (N.m2)
54
55#ifdef MESOSCALE
56!!!! AS: In the mesoscale model we'd like to easily set
57!!!! AS: ... stress for lifting
58!!!! AS: you have to compile with -DMESOSCALE to do so
59      REAL alpha
60      REAL r0_lift
61      INTEGER ierr
62      REAL ulim
63        OPEN(99,file='stress.def',status='old',form='formatted'
64     .   ,iostat=ierr)
65        !!! no file => default values
66        IF(ierr.EQ.0) THEN
67          READ(99,*) ulim !ulim = sqrt(stress_seuil/rho) avec rho = 0.02.
68                          !prendre ulim = 1.061 m/s pour avoir stress_seuil = 0.0225
69          READ(99,*) alpha
70          stress_seuil = 0.02 * ulim * ulim
71          write(*,*) 'USER-DEFINED threshold: ', stress_seuil, alpha
72          CLOSE(99)
73          alpha_lift(igcm_dust_mass) = alpha
74          r0_lift = radius(igcm_dust_mass) / ref_r0
75          alpha_lift(igcm_dust_number)=r3n_q*
76     &                        alpha_lift(igcm_dust_mass)/r0_lift**3
77          write(*,*) 'set dust number: ', alpha_lift(igcm_dust_number)
78        ENDIF
79#endif
80
81c     ---------------------------------
82c     Computing horizontal flux: fhoriz
83c     ---------------------------------
84
85      do ig=1,ngrid
86          fhoriz(ig) = 0.      ! initialisation
87
88c         Selection of points where surface dust is available
89c         ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
90c         if (latid(ig).ge.80.) goto 99  ! N permanent  polar caps
91c         if (latid(ig).le.-80.) goto 99 ! S polar deposits
92c         if  ((longd(ig).ge.-141. .and. longd(ig).le.-127.)
93c    &   .and.(latid(ig).ge.12.   .and. latid(ig).le.23.))goto 99 ! olympus
94c         if  ((longd(ig).ge.-125. .and. longd(ig).le.-118.)
95c    &   .and.(latid(ig).ge.-12.   .and. latid(ig).le.-6.))goto 99 ! Arsia
96c         if  ((longd(ig).ge.-116. .and. longd(ig).le.-109.)
97c    &   .and.(latid(ig).ge.-5.   .and. latid(ig).le. 5.))goto 99 ! pavonis
98c         if  ((longd(ig).ge.-109. .and. longd(ig).le.-100.)
99c    &   .and.(latid(ig).ge. 7.   .and. latid(ig).le. 16.))goto 99 ! ascraeus
100c         if  ((longd(ig).ge.  61. .and. longd(ig).le.  63.)
101c    &   .and.(latid(ig).ge. 63. .and. latid(ig).le. 64.))goto 99 !weird point
102          if (co2ice(ig).gt.0.) goto 99
103
104
105c         Is the wind strong enough ?
106c         ~~~~~~~~~~~~~~~~~~~~~~~~~~~
107          ust = sqrt(stress_seuil/rho(ig))
108          us = pcdh(ig) /  sqrt(pcdh_true(ig)) ! ustar=cd*v /sqrt(cd)
109          if (us.gt.ust) then
110c            If lifting ?
111c            Calcul du flux suivant Marticorena ( en fait white (1979))
112
113             fhoriz(ig) = 2.61*(rho(ig)/g) *
114     &      (us -ust) * (us + ust)**2
115          end if
116 99      continue
117      end do
118
119c     -------------------------------------
120c     Computing vertical flux and diffusion
121c     -------------------------------------
122 
123       do iq=1,nq
124         do ig=1,ngrid
125             dqslift(ig,iq)= -alpha_lift(iq)* fhoriz(ig)
126
127
128cc  le  flux vertical remplace le terme de diffusion turb. qui est mis a zero
129c            zb(ig,1) = 0.
130cc           If surface deposition by turbulence diffusion (impaction...)
131cc           if(fhoriz(ig).ne.0) then
132cc           zb(ig,1) = zcdh(ig)*zb0(ig,1)
133cc           AMount of Surface deposition !
134cc           pdqs_dif(ig,iq)=pdqs_dif(ig,iq) +
135cc    &      zb(ig,1)*zq(ig,1,iq)/ptimestep
136cc          write(*,*) 'zb(1)  = ' ,  zb(ig,1),zcdh(ig),zb0(ig,1)
137cc
138
139         enddo
140       enddo
141
142      RETURN
143      END
144
Note: See TracBrowser for help on using the repository browser.