source: trunk/WRF.COMMON/WRFV2/mars_lmd/libf/phymars/dustlift.F @ 3094

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

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

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