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

Last change on this file since 310 was 310, checked in by aslmd, 13 years ago

MESOSCALE:
-- Code in storm scenario corresponds to 'OMEGA' reference case [Julien Faure]
-- Easier settings for dust lifting without the need to recompile [see below]
-- A few modifications to plot and dust-devil detection PYTHON routines

29/09/11 == AS

--> To easily explore sensitivity to lifting thresholds: in dustlift.F, ustar_seuil=sqrt(stress/rho)

and alpha_lift[dust_mass] can be prescribed through an external stress.def parameter file.
--- alpha_lift[dust_number] is computed from alpha_lift[dust_mass] as in initracer.F
--- ustar_seuil is more user-friendly than stress because direct comparison with ustar from model

--> For the moment this is MESOSCALE only, but potentially useful to everyone

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