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

Last change on this file since 1036 was 1036, checked in by emillour, 11 years ago

Mars GCM: (a first step towards using parallel dynamics)

  • IMPORTANT CHANGE: Implemented dynamic tracers. It is no longer necessary to compile the model with the '-t #' option, number of tracers is simply read from tracer.def file (as before). Adapted makegcm_* scripts (and co.) accordingly. Technical aspects of the switch to dynamic tracers are:
    • advtrac.h (in dyn3d) removed and replaced by module infotrac.F
    • tracer.h (in phymars) removed and replaced by module tracer_mod.F90 (which contains nqmx, the number of tracers, etc. and can be used anywhere in the physics).
  • Included some side cleanups: removed unused files (in dyn3d) anldoppler2.F, anl_mcdstats.F and anl_stats-diag.F, and all the unecessary dimensions.* files in grid/dimension.
  • Checked that changes are clean and that GCM yields identical results (in debug mode) to previous svn version.

EM

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