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

Last change on this file since 3739 was 3739, checked in by emillour, 7 weeks ago

Mars PCM:
Code tidying: put routines in modules, remove useless "return" statements, etc.
EM

File size: 5.0 KB
Line 
1      MODULE co2snow_mod
2     
3      IMPLICIT NONE
4     
5      CONTAINS
6c=======================================================================
7c     Program for simulate the impact of the CO2 snow fall on
8c     the surface infrared emission (emissivity)
9c-----------------------------------------------------------------------
10c     Algorithme:
11c     1 - Initialization
12c     2 - Compute the surface emissivity
13c-----------------------------------------------------------------------
14c     Author: F. Forget
15c-----------------------------------------------------------------------
16c     Reference paper:
17c     Francois Forget and James B. Pollack
18c
19c     "Thermal infrared observations of the condensing Martian polar
20c     caps: CO2 ice temperatures and radiative budget"
21c
22c     JOURNAL OF GEOPHYSICAL RESEARCH, VOL. 101, NO. E7, PAGES 16,
23c     865-16,879, JULY 25, 1996
24c=======================================================================
25
26      SUBROUTINE co2snow(ngrid, nlayer, ptimestep, emisref, condsub,
27     &                   pplev, pcondicea, pcondices, pfallice,
28     &                   pemisurf)
29     
30      use surfdat_h, only: iceradius, dtemisice
31      use geometry_mod, only: latitude ! grid point latitudes (rad)
32      use time_phylmdz_mod, only: daysec
33
34      IMPLICIT NONE
35
36c=======================================================================
37c     Variables
38c=======================================================================
39c     Inputs:
40c     -------
41      integer, intent(in) ::
42     &   ngrid, ! number of atmospheric columns
43     &   nlayer ! number of atmospheric layers
44                       
45      real, intent(in) ::
46     &   ptimestep,               ! timestep of the physics (s)
47     &   emisref(ngrid),          ! grd or ice emissivity without snow
48     &   pplev(ngrid,nlayer+1),   ! interlayer pressure (Pa)
49     &   pcondicea(ngrid,nlayer), ! CO2 condensation rate in layers
50                                  !   (kg/m2/s)
51     &   pcondices(ngrid),        ! CO2 condensation rate on the surface
52                                  !   (kg/m2/s)       
53     &   pfallice(ngrid,nlayer+1) ! falling CO2 ice (kg/m2/s)
54
55      logical, intent(in) ::
56     &   condsub(ngrid) ! true if there is CO2 condensation or
57                        ! sublimation in the column
58
59c     Output:
60c     -------
61      real, intent(out) ::
62     &   pemisurf(ngrid) ! surface emissivity
63
64c     local:
65c     ------
66      integer ::
67     &   l,
68     &   ig,
69     &   icap
70
71      real ::
72     &   sumdaer,
73     &   zdemisurf
74
75      real, parameter ::
76     &   alpha = 0.45
77
78c     saved:
79c     ------
80      real, save ::
81     &   Kscat(2) ! Kscat: coefficient for decreasing the surface
82c                 !        emissivity
83c                 !
84c                 ! Kscat = (0.001/3.) * alpha / iceradius
85c                 !          with 0.3 < alpha < 0.6
86c                 !
87c                 ! alpha set to 0.45 (coeff from emis = f (tau)) and
88c                 ! iceradius the mean radius of the scaterring
89c                 ! particles (200.e-6 < iceradius < 10.e-6)
90c                 !
91c                 ! (2) = N and S hemispheres
92
93      logical, save ::
94     &   firstcall = .true.
95     
96!$OMP THREADPRIVATE(Kscat,firstcall)     
97
98c=======================================================================
99c BEGIN
100c=======================================================================
101c 1 - Initialization
102c=======================================================================
103      if (firstcall) then
104        Kscat(1) = (0.001/3.) * alpha / iceradius(1)
105        Kscat(2) = (0.001/3.) * alpha / iceradius(2)
106                   
107        firstcall = .false.
108      end if
109c=======================================================================
110c 2 - Compute the surface emissivity
111c=======================================================================
112      do ig = 1, ngrid
113        if (condsub(ig)) then
114
115          if (latitude(ig).lt.0.) then
116              icap = 2 ! Southern hemisphere
117          else
118              icap = 1 ! Northern Hemisphere
119          end if
120
121          ! compute zdemisurf using an integrated form for numerical
122          ! safety instead
123          zdemisurf =
124     &     (emisref(ig) - pemisurf(ig)) / (dtemisice(icap) * daysec)
125     &     +
126     &     ( emisref(ig) *
127     &              ( (pemisurf(ig)/emisref(ig))**(-3) +
128     &                3.*Kscat(icap)*pfallice(ig,1)*ptimestep )**(-1/3.)
129     &       - pemisurf(ig)
130     &      ) / ptimestep
131          pemisurf(ig) = pemisurf(ig) + zdemisurf * ptimestep
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 ! if condsub(ig) is false
139           pemisurf(ig) = emisref(ig)
140        end if
141      end do ! ngrid
142c=======================================================================
143c END
144c=======================================================================
145      end subroutine co2snow
146
147      END MODULE co2snow_mod
Note: See TracBrowser for help on using the repository browser.