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

Last change on this file since 2596 was 2447, checked in by cmathe, 4 years ago

CO2 microphysics: correction r_sedim (co2cloud.F); add: co2 cloud radiatively active

File size: 4.9 KB
RevLine 
[2362]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=======================================================================
[38]20
[2362]21      SUBROUTINE co2snow(ngrid, nlayer, ptimestep, emisref, condsub,
22     &                   pplev, pcondicea, pcondices, pfallice,
23     &                   pemisurf)
24     
[1047]25      use surfdat_h, only: iceradius, dtemisice
[1543]26      use geometry_mod, only: latitude ! grid point latitudes (rad)
[1524]27      use time_phylmdz_mod, only: daysec
[2362]28
[1047]29      IMPLICIT NONE
[38]30
31#include "callkeys.h"
32
[2362]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)
[2447]51
[2362]52      logical, intent(in) ::
53     &   condsub(ngrid) ! true if there is CO2 condensation or
54                        ! sublimation in the column
[38]55
[2362]56c     Output:
57c     -------
58      real, intent(out) ::
59     &   pemisurf(ngrid) ! surface emissivity
[38]60
[2362]61c     local:
62c     ------
63      integer ::
64     &   l,
65     &   ig,
66     &   icap
[38]67
[2362]68      real ::
69     &   sumdaer,
70     &   zdemisurf
[38]71
[2362]72      real, parameter ::
73     &   alpha = 0.45
[38]74
[2362]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
[38]89
[2362]90      logical, save ::
91     &   firstcall = .true.
92c=======================================================================
93c BEGIN
94c=======================================================================
95c 1 - Initialization
96c=======================================================================
[38]97      if (firstcall) then
[2362]98        Kscat(1) = (0.001/3.) * alpha / iceradius(1)
99        Kscat(2) = (0.001/3.) * alpha / iceradius(2)
100                   
101        firstcall = .false.
[38]102      end if
[2362]103c=======================================================================
104c 2 - Compute the surface emissivity
105c=======================================================================
106      do ig = 1, ngrid
107        if (condsub(ig)) then
[2447]108
[2362]109          if (latitude(ig).lt.0.) then
110              icap = 2 ! Southern hemisphere
111          else
112              icap = 1 ! Northern Hemisphere
113          end if
[38]114
[2362]115          ! compute zdemisurf using an integrated form for numerical
116          ! safety instead
117          zdemisurf =
118     &     (emisref(ig) - pemisurf(ig)) / (dtemisice(icap) * daysec)
119     &     +
120     &     ( emisref(ig) *
121     &              ( (pemisurf(ig)/emisref(ig))**(-3) +
122     &                3.*Kscat(icap)*pfallice(ig,1)*ptimestep )**(-1/3.)
123     &       - pemisurf(ig)
124     &      ) / ptimestep
125          pemisurf(ig) = pemisurf(ig) + zdemisurf * ptimestep
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 ! if condsub(ig) is false
[38]133           pemisurf(ig) = emisref(ig)
[2362]134        end if
135      end do ! ngrid
136c=======================================================================
137c END
138c=======================================================================
[38]139      return
140      end
Note: See TracBrowser for help on using the repository browser.