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

Last change on this file since 2616 was 2616, checked in by romain.vande, 3 years ago

LMDZ_MARS RV : Open_MP;
Put all the "save" variables as "!$OMP THREADPRIVATE" in phymars.
The code can now be tested, see README for more info

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