source: trunk/LMDZ.MARS/libf/phymars/co2snow.F @ 2156

Last change on this file since 2156 was 1779, checked in by aslmd, 7 years ago

LMDZ.MARS (purely comments) marked the absolute firstcalls not supposed to change with runtime (e.g. not domain-related). this is most of them. those firstcall can stay local and do not need to be linked with the caller's general firstcall.

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