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

Last change on this file since 1619 was 1543, checked in by emillour, 9 years ago

All models: Further adaptations to keep up with changes in LMDZ5 concerning
physics/dynamics separation:

  • dyn3d:
  • adapted gcm.F so that all physics initializations are now done in iniphysiq.
  • dyn3dpar:
  • adapted gcm.F so that all physics initializations are now done in iniphysiq.
  • updated calfis_p.F to follow up with changes.
  • copied over updated "bands.F90" from LMDZ5.
  • dynphy_lonlat:
  • calfis_p.F90, mod_interface_dyn_phys.F90, follow up of changes in phy_common/mod_* routines
  • phy_common:
  • added "geometry_mod.F90" to store information about the grid (replaces phy*/comgeomphy.F90) and give variables friendlier names: rlond => longitude , rlatd => latitude, airephy => cell_area, cuphy => dx , cvphy => dy
  • added "physics_distribution_mod.F90"
  • updated "mod_grid_phy_lmdz.F90", "mod_phys_lmdz_mpi_data.F90", "mod_phys_lmdz_para.F90", "mod_phys_lmdz_mpi_transfert.F90", "mod_grid_phy_lmdz.F90", "mod_phys_lmdz_omp_data.F90", "mod_phys_lmdz_omp_transfert.F90", "write_field_phy.F90" and "ioipsl_getin_p_mod.F90" to LMDZ5 versions.
  • phy[venus/titan/mars/std]:
  • removed "init_phys_lmdz.F90", "comgeomphy.F90"; adapted routines to use geometry_mod (longitude, latitude, cell_area, etc.)

EM

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      if (firstcall) then
55
56c   Kscat : coefficient for decreasing the surface emissivity
57c           =(0.001/3.)*alpha/iceradius ,
58c           with 0.3< alpha < 0.6, set to 0.45 (coeff from emis = f (tau))
59c           and iceradius the mean radius of the
60c           scaterring particles  (200.e-6<iceradius<10.e-6)
61
62            Kscat(1)=(0.001/3.)*0.45/iceradius(1)
63            Kscat(2)=(0.001/3.)*0.45/iceradius(2)
64
65c          Scavenging Ratio (dust concentration in the air / in the snow)
66           scaveng = 100.0
67           
68c          Collision Scavenging coefficient  (m2.kg-1)
69c          Csca  = 2.3  ! not used yet !!!!!!!!!!!
70           firstcall = .false.
71
72      end if
73
74
75c     LOOP on grid points
76c     -------------------
77      do ig=1,ngrid
78         if (condsub(ig)) then
79
80c         IF (scavenging) then
81c          Airborne Dust
82c          -------------
83c          sumdaer=0.
84c          do l=nlayer, 1, -1
85c             pdaerosol(ig,l)= -paerosol(ig,l,1)*
86c    &              (1-exp(-scaveng*pcondicea(ig,l)*ptimestep*g/
87c    &               (pplev(ig,l)-pplev(ig,l+1))))/ptimestep 
88
89c    &           - Csca*paerosol(ig,l,1) ! Scavenging by collision
90c    &           * 0.5*(pfallice(ig,l)) ! not included
91
92c             test to avoid releasing to much dust when subliming:
93c             if(pdaerosol(ig,l).gt.-sumdaer)pdaerosol(ig,l)=-sumdaer
94c             sumdaer=sumdaer + pdaerosol(ig,l)
95
96c            if (-pdaerosol(ig,l)*ptimestep.gt.paerosol(ig,l,1)) then
97c                write(*,*) 'ds co2snow: aerosol < 0.0 !!!'
98c                write(*,*) 'ig =' , ig
99c            end if
100c          end do
101c         END IF
102
103c          Surface emissivity
104c          ------------------
105c   dtemis: Time scale for increasing the ice emissivity
106
107           IF(latitude(ig).LT. 0.) THEN
108              icap=2 ! Southern hemisphere
109           ELSE
110              icap=1 ! Northern Hemisphere
111           ENDIF
112
113           zdemisurf =
114     &    (emisref(ig)-pemisurf(ig))/(dtemisice(icap)*daysec)
115c Using directly the diferential equation:
116c    &       -Kscat(icap)*emisref(ig)*
117c    &      (pemisurf(ig)/emisref(ig))**4 *pfallice(ig,1)
118c Using an integrated form for numerical safety instead
119     & +(emisref(ig)* ((pemisurf(ig)/emisref(ig))**(-3)+3.*Kscat(icap)*
120     & pfallice(ig,1)*ptimestep)**(-1/3.) -pemisurf(ig))/ptimestep   
121
122
123           pemisurf(ig) = pemisurf(ig) + zdemisurf*ptimestep
124
125           if (pemisurf(ig).lt.0.1) then
126                 write(*,*) 'ds co2snow: emis < 0.1 !!!'
127                 write(*,*) 'ig =' , ig
128                 write(*,*)'pemisurf(ig)',pemisurf(ig)
129                 write(*,*) 'zdemisurf*ptimestep',zdemisurf*ptimestep
130           end if
131         else
132           pemisurf(ig) = emisref(ig)
133         end if
134      end do
135
136      return
137      end
Note: See TracBrowser for help on using the repository browser.