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

Last change on this file since 1130 was 1130, checked in by emillour, 11 years ago

Mars GCM:
Series of changes to enable running in parallel (using LMDZ.COMMON dynamics);
Current LMDZ.MARS can still notheless be compiled and run in serial mode
"as previously".
Summary of main changes:

  • Main programs (newstart, start2archive, xvik) that used to be in dyn3d have been moved to phymars.
  • dyn3d/control.h is now module control_mod.F90
  • rearanged input/outputs routines everywhere to handle serial/MPI cases. physdem.F => phyredem.F90 , phyetat0.F => phyetat0.F90 ; all read/write routines for startfi files are gathered in module iostart.F90
  • added parallelism related routines init_phys_lmdz.F90, comgeomphy.F90, dimphy.F90, iniphysiq.F90, mod_grid_phy_lmdz.F90, mod_phys_lmdz_mpi_data.F90, mod_phys_lmdz_mpi_transfert.F90, mod_phys_lmdz_omp_data.F90, mod_phys_lmdz_omp_transfert.F90, mod_phys_lmdz_para.F90, mod_phys_lmdz_transfert_para.F90 in phymars and mod_const_mpi.F90 in dyn3d (for compliance with parallel case)
  • created generic routines 'planetwide_maxval' and 'planetwide_minval', in module "planetwide_mod", that enable obtaining the min and max of a field over the whole planet.

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