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

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

LMDZ.MARS
IMPORTANT CHANGE

  • Remove all reference/use of nlayermx and dimphys.h
  • Made use of automatic arrays whenever arrays are needed with dimension nlayer
  • Remove lots of obsolete reference to dimensions.h
  • Converted iono.h and param_v4.h into corresponding modules

(with embedded subroutine to allocate arrays)
(no arrays allocated if thermosphere not used)

  • Deleted param.h and put contents into module param_v4_h
  • Adapted testphys1d, newstart, etc...
  • Made DATA arrays in param_read to be initialized by subroutine

fill_data_thermos in module param_v4_h

  • Optimized computations in paramfoto_compact (twice less dlog10 calculations)
  • Checked consistency before/after modification in debug mode
  • Checked performance is not impacted (same as before)
File size: 4.6 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#ifdef MESOSCALE
52!!!! AS: In the mesoscale model we'd like to easily set
53!!!! AS: ... stress for lifting
54!!!! AS: you have to compile with -DMESOSCALE to do so
55      REAL alpha
56      REAL r0_lift
57      INTEGER ierr
58      REAL ulim
59        OPEN(99,file='stress.def',status='old',form='formatted'
60     .   ,iostat=ierr)
61        !!! no file => default values
62        IF(ierr.EQ.0) THEN
63          READ(99,*) ulim !ulim = sqrt(stress_seuil/rho) avec rho = 0.02.
64                          !prendre ulim = 1.061 m/s pour avoir stress_seuil = 0.0225
65          READ(99,*) alpha
66          stress_seuil = 0.02 * ulim * ulim
67          write(*,*) 'USER-DEFINED threshold: ', stress_seuil, alpha
68          CLOSE(99)
69          alpha_lift(igcm_dust_mass) = alpha
70          r0_lift = radius(igcm_dust_mass) / ref_r0
71          alpha_lift(igcm_dust_number)=r3n_q*
72     &                        alpha_lift(igcm_dust_mass)/r0_lift**3
73          write(*,*) 'set dust number: ', alpha_lift(igcm_dust_number)
74        ENDIF
75#endif
76
77c     ---------------------------------
78c     Computing horizontal flux: fhoriz
79c     ---------------------------------
80
81      do ig=1,ngrid
82          fhoriz(ig) = 0.      ! initialisation
83
84c         Selection of points where surface dust is available
85c         ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
86c         if (latid(ig).ge.80.) goto 99  ! N permanent  polar caps
87c         if (latid(ig).le.-80.) goto 99 ! S polar deposits
88c         if  ((longd(ig).ge.-141. .and. longd(ig).le.-127.)
89c    &   .and.(latid(ig).ge.12.   .and. latid(ig).le.23.))goto 99 ! olympus
90c         if  ((longd(ig).ge.-125. .and. longd(ig).le.-118.)
91c    &   .and.(latid(ig).ge.-12.   .and. latid(ig).le.-6.))goto 99 ! Arsia
92c         if  ((longd(ig).ge.-116. .and. longd(ig).le.-109.)
93c    &   .and.(latid(ig).ge.-5.   .and. latid(ig).le. 5.))goto 99 ! pavonis
94c         if  ((longd(ig).ge.-109. .and. longd(ig).le.-100.)
95c    &   .and.(latid(ig).ge. 7.   .and. latid(ig).le. 16.))goto 99 ! ascraeus
96c         if  ((longd(ig).ge.  61. .and. longd(ig).le.  63.)
97c    &   .and.(latid(ig).ge. 63. .and. latid(ig).le. 64.))goto 99 !weird point
98          if (co2ice(ig).gt.0.) goto 99
99
100
101c         Is the wind strong enough ?
102c         ~~~~~~~~~~~~~~~~~~~~~~~~~~~
103          ust = sqrt(stress_seuil/rho(ig))
104          us = pcdh(ig) /  sqrt(pcdh_true(ig)) ! ustar=cd*v /sqrt(cd)
105          if (us.gt.ust) then
106c            If lifting ?
107c            Calcul du flux suivant Marticorena ( en fait white (1979))
108
109             fhoriz(ig) = 2.61*(rho(ig)/g) *
110     &      (us -ust) * (us + ust)**2
111          end if
112 99      continue
113      end do
114
115c     -------------------------------------
116c     Computing vertical flux and diffusion
117c     -------------------------------------
118 
119       do iq=1,nq
120         do ig=1,ngrid
121             dqslift(ig,iq)= -alpha_lift(iq)* fhoriz(ig)
122
123
124cc  le  flux vertical remplace le terme de diffusion turb. qui est mis a zero
125c            zb(ig,1) = 0.
126cc           If surface deposition by turbulence diffusion (impaction...)
127cc           if(fhoriz(ig).ne.0) then
128cc           zb(ig,1) = zcdh(ig)*zb0(ig,1)
129cc           AMount of Surface deposition !
130cc           pdqs_dif(ig,iq)=pdqs_dif(ig,iq) +
131cc    &      zb(ig,1)*zq(ig,1,iq)/ptimestep
132cc          write(*,*) 'zb(1)  = ' ,  zb(ig,1),zcdh(ig),zb0(ig,1)
133cc
134
135         enddo
136       enddo
137
138      RETURN
139      END
140
Note: See TracBrowser for help on using the repository browser.