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

Last change on this file since 2740 was 2616, checked in by romain.vande, 3 years ago

LMDZ_MARS RV : Open_MP;
Put all the "save" variables as "!$OMP THREADPRIVATE" in phymars.
The code can now be tested, see README for more info

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