source: trunk/WRF.COMMON/WRFV2/mars_lmd/libf/phymars/co2snow.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: 3.9 KB
Line 
1      SUBROUTINE co2snow (ngrid,nlayer,ptimestep,
2     &          emisref,condsub,pplev,
3     &        pcondicea,pcondices,pfallice,pemisurf)
4
5       IMPLICIT NONE
6
7
8c*****WRF: ligne trop longue
9
10c=======================================================================
11c     Program for simulate the impact of the CO2 snow fall on
12c     the surface infrared emission (emissivity)  and on
13c     the airborne dust
14c     F.Forget 1996
15c=======================================================================
16
17c Declarations
18c ------------
19
20#include "dimensions.h"
21#include "dimphys.h"
22#include "comcstfi.h"
23#include "surfdat.h"
24#include "callkeys.h"
25
26c     input
27c     -----
28
29      INTEGER ngrid,nlayer
30      REAL ptimestep , emisref(ngrid) ! grd or ice  emissivity without snow
31      logical condsub(ngrid)
32
33      REAL pplev(ngrid,nlayer+1)
34      REAL pcondicea(ngrid,nlayer), pcondices(ngrid)
35      REAL pfallice(ngrid,nlayer+1)
36
37c     output
38c     ------
39
40      REAL pemisurf(ngrid)
41
42c     local
43c     -----
44      integer ig , l , icap
45
46      REAL zdemisurf ,dtemis
47      REAL sumdaer
48
49c     saved
50c     -----
51      REAL Kscat(2), scaveng
52      LOGICAL firstcall
53      SAVE firstcall
54      save Kscat , scaveng
55      DATA firstcall/.true./
56
57c --------------
58c Initialisation
59c --------------
60
61      if (firstcall) then
62
63c   Kscat : coefficient for decreasing the surface emissivity
64c           =(0.001/3.)*alpha/iceradius ,
65c           with 0.3< alpha < 0.6, set to 0.45 (coeff from emis = f (tau))
66c           and iceradius the mean radius of the
67c           scaterring particles  (200.e-6<iceradius<10.e-6)
68
69            Kscat(1)=(0.001/3.)*0.45/iceradius(1)
70            Kscat(2)=(0.001/3.)*0.45/iceradius(2)
71
72c          Scavenging Ratio (dust concentration in the air / in the snow)
73           scaveng = 100.0
74           
75c          Collision Scavenging coefficient  (m2.kg-1)
76c          Csca  = 2.3  ! not used yet !!!!!!!!!!!
77           firstcall = .false.
78
79      end if
80
81
82c     LOOP on grid points
83c     -------------------
84      do ig=1,ngrid
85         if (condsub(ig)) then
86
87c         IF (scavenging) then
88c          Airborne Dust
89c          -------------
90c          sumdaer=0.
91c          do l=nlayer, 1, -1
92c             pdaerosol(ig,l)= -paerosol(ig,l,1)*
93c    &              (1-exp(-scaveng*pcondicea(ig,l)*ptimestep*g/
94c    &               (pplev(ig,l)-pplev(ig,l+1))))/ptimestep 
95
96c    &           - Csca*paerosol(ig,l,1) ! Scavenging by collision
97c    &           * 0.5*(pfallice(ig,l)) ! not included
98
99c             test to avoid releasing to much dust when subliming:
100c             if(pdaerosol(ig,l).gt.-sumdaer)pdaerosol(ig,l)=-sumdaer
101c             sumdaer=sumdaer + pdaerosol(ig,l)
102
103c            if (-pdaerosol(ig,l)*ptimestep.gt.paerosol(ig,l,1)) then
104c                write(*,*) 'ds co2snow: aerosol < 0.0 !!!'
105c                write(*,*) 'ig =' , ig
106c            end if
107c          end do
108c         END IF
109
110c          Surface emissivity
111c          ------------------
112c   dtemis: Time scale for increasing the ice emissivity
113
114           IF(ig.GT.ngrid/2+1) THEN
115              icap=2
116           ELSE
117              icap=1
118           ENDIF
119
120           zdemisurf =
121     &    (emisref(ig)-pemisurf(ig))/(dtemisice(icap)*daysec)
122c Using directly the diferential equation:
123c    &       -Kscat(icap)*emisref(ig)*
124c    &      (pemisurf(ig)/emisref(ig))**4 *pfallice(ig,1)
125c Using an integrated form for numerical safety instead
126     & +(emisref(ig)* ((pemisurf(ig)/emisref(ig))**(-3)+3.*Kscat(icap)*
127     & pfallice(ig,1)*ptimestep)**(-1/3.) -pemisurf(ig))/ptimestep   
128
129
130           pemisurf(ig) = pemisurf(ig) + zdemisurf*ptimestep
131
132           if (pemisurf(ig).lt.0.1) then
133                 write(*,*) 'ds co2snow: emis < 0.1 !!!'
134                 write(*,*) 'ig =' , ig
135                 write(*,*)'pemisurf(ig)',pemisurf(ig)
136                 write(*,*) 'zdemisurf*ptimestep',zdemisurf*ptimestep
137           end if
138         else
139           pemisurf(ig) = emisref(ig)
140         end if
141      end do
142
143      return
144      end
Note: See TracBrowser for help on using the repository browser.