source: trunk/LMDZ.UNIVERSAL/libf/phygeneric/phyredem.F90 @ 965

Last change on this file since 965 was 965, checked in by emillour, 12 years ago

Common dynamics and generic/universal GCM:

  • LMDZ.COMMON: minor bug fix on the computation of physics mesh area in gcm.F
  • LMDZ.UNIVERSAL: missing clean initialization of tab_cntrl(:) array in phyredem.F90
  • LMDZ.GENERIC: minor bug fix in hydrol.F90, only output runoff if it is used. Update output routines so that all outputs files (stats, diagfi.nc, diagsoil.nc, diagspecIR.nc and diagspecVI.nc) can be generated when running LMDZ.UNIVERSAL in MPI mode.

EM

File size: 6.1 KB
Line 
1!
2! $Id: $
3!
4SUBROUTINE phyredem (ngrid,filename,    &
5                         phystep,pday,                    &
6                         time,tsurf,tsoil,emis,q2,qsurf,      &
7                         cloudfrac,totcloudfrac,hice)
8!! creates the physics (re-)start file "restartfi.nc"
9USE dimphy
10USE mod_grid_phy_lmdz
11USE mod_phys_lmdz_para
12USE iophy
13!      USE phys_state_var_mod ! not used in generic model (yet?!) field passed as input arguments
14USE iostart, only : open_restartphy,close_restartphy, &
15                          put_var,put_field
16USE infotrac, only: nqtot
17USE comgeomphy,  only: rlatd,rlond,airephy
18USE control_mod, only: raz_date
19USE comsoil_h, only: mlayer,inertiedat,volcapa
20USE surfdat_h, only: albedodat,phisfi,albedice,emisice,emissiv,iceradius,dtemisice, &
21                     zmea,zstd,zsig,zgam,zthe
22USE tracer_h, only: noms
23implicit none
24
25!======================================================================
26#include "dimensions.h"
27#include "netcdf.inc"
28!!#include "dimsoil.h"
29!!#include "clesphys.h"
30!!#include "tabcontrol.h"
31#include "temps.h"
32#include "comcstfi.h"
33#include "planete.h"
34!======================================================================
35integer,intent(in) :: ngrid
36character(len=*),intent(in) :: filename
37!real,intent(in) :: latfi(ngrid), lonfi(ngrid)
38!integer,intent(in) :: nsoil,nq
39real,intent(in) :: phystep,pday,time
40real,intent(in) :: tsurf(ngrid)
41real,intent(in) :: tsoil(ngrid,nsoil),emis(ngrid)
42real,intent(in) :: q2(ngrid,klev+1),qsurf(ngrid,nqtot)
43!real,intent(in) :: airefi(ngrid)
44!real,intent(in) :: alb(ngrid),ith(ngrid,nsoil)
45!real,intent(in) :: pzmea(ngrid),pzstd(ngrid)
46!real,intent(in) :: pzsig(ngrid),pzgam(ngrid),pzthe(ngrid)
47REAL,intent(in) :: hice(ngrid),cloudfrac(ngrid,klev)
48REAL,intent(in) :: totcloudfrac(ngrid)
49!character(len=*),intent(in) :: nametrac(nqtot)   ! name of the tracer
50
51! local variables
52integer :: iq
53integer,parameter :: length=100
54real :: tab_cntrl(length)
55
56!
57! open file
58      CALL open_restartphy(filename)
59
60! tab_cntrl() contains run parameters
61      tab_cntrl(:)=0 ! initialization
62!cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
63! Fill control array tab_cntrl(:) with paramleters for this run
64!cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
65! Informations on the physics grid
66      tab_cntrl(1) = float(klon_glo)  ! number of nodes on physics grid
67      tab_cntrl(2) = float(klev) ! number of atmospheric layers
68      tab_cntrl(3) = pday + int(time)         ! initial day
69      tab_cntrl(4) = time -int(time)            ! initiale time of day
70
71! Informations about Mars, used by dynamics and physics
72      tab_cntrl(5) = rad      ! radius of Mars (m) ~3397200
73      tab_cntrl(6) = omeg     ! rotation rate (rad.s-1)
74      tab_cntrl(7) = g        ! gravity (m.s-2) ~3.72
75      tab_cntrl(8) = mugaz    ! Molar mass of the atmosphere (g.mol-1) ~43.49
76      tab_cntrl(9) = rcp      !  = r/cp  ~0.256793 (=kappa dans dynamique)
77      tab_cntrl(10) = daysec  ! length of a sol (s)  ~88775
78
79      tab_cntrl(11) = phystep  ! time step in the physics
80      tab_cntrl(12) = 0.
81      tab_cntrl(13) = 0.
82
83! Informations about Mars, only for physics
84      tab_cntrl(14) = year_day  ! length of year (sols) ~668.6
85      tab_cntrl(15) = periastr  ! min. star-planet distance (AU)
86      tab_cntrl(16) = apoastr   ! max. star-planet distance (AU)
87      tab_cntrl(17) = peri_day  ! date of periastron (sols since N. spring)
88      tab_cntrl(18) = obliquit  ! Obliquity of the planet (deg) ~23.98
89
90! Boundary layer and turbulence
91      tab_cntrl(19) = z0        ! surface roughness (m) ~0.01
92      tab_cntrl(20) = lmixmin   ! mixing length ~100
93      tab_cntrl(21) = emin_turb ! minimal energy ~1.e-8
94
95! Optical properties of polar caps and ground emissivity
96      tab_cntrl(22) = albedice(1)  ! Albedo of northern cap ~0.5
97      tab_cntrl(23) = albedice(2)  ! Albedo of southern cap ~0.5
98      tab_cntrl(24) = emisice(1)   ! Emissivity of northern cap ~0.95
99      tab_cntrl(25) = emisice(2)   ! Emissivity of southern cap ~0.95
100      tab_cntrl(26) = emissiv      ! Emissivity of martian soil ~.95
101      tab_cntrl(31) = iceradius(1) ! mean scat radius of CO2 snow (north)
102      tab_cntrl(32) = iceradius(2) ! mean scat radius of CO2 snow (south)
103      tab_cntrl(33) = dtemisice(1) ! time scale for snow metamorphism (north)
104      tab_cntrl(34) = dtemisice(2) ! time scale for snow metamorphism (south)
105
106      tab_cntrl(28) = 0.
107      tab_cntrl(29) = 0.
108      tab_cntrl(30) = 0.
109
110! Soil properties:
111      tab_cntrl(35) = volcapa ! soil volumetric heat capacity
112     
113      CALL put_var("controle","Control parameters",tab_cntrl)
114
115! coordinates
116
117      CALL put_var("soildepth","Soil mid-layer depth",mlayer)
118      CALL put_field("longitude", &
119                     "Longitudes of physics grid",rlond)
120      CALL put_field("latitude","Latitudes of physics grid",rlatd)
121
122! variables
123
124      CALL put_field("area","Mesh area",airephy)
125      CALL put_field("phisfi","Geopotential at the surface",phisfi)
126      CALL put_field("albedodat","Albedo of bare ground",albedodat)
127
128! F. Lott GW parametrizations
129      CALL put_field("ZMEA","Relief: mean relief",zmea)
130      CALL put_field("ZSTD","Relief: standard deviation",zstd)
131      CALL put_field("ZSIG","Relief: sigma parameter",zsig)
132      CALL put_field("ZGAM","Relief: gamma parameter",zgam)
133      CALL put_field("ZTHE","Relief: theta parameter",zthe)
134
135! Sub-surface variables
136      CALL put_field("inertiedat","Soil thermal inertia",inertiedat)
137      CALL put_field("tsurf","Surface temperature",tsurf)
138      CALL put_field("tsoil","Soil temperature",tsoil)
139      CALL put_field("emis","Surface emissivity",emis)
140
141! PBL:
142      CALL put_field("q2","pbl wind variance",q2)
143
144! cloud fraction and sea ice (NB: these should be optional... to be improved)
145      CALL put_field("cloudfrac","Cloud fraction",cloudfrac)
146      CALL put_field("totcloudfrac","Total fraction",totcloudfrac)
147      CALL put_field("hice","Height of oceanic ice",hice)
148
149! tracers
150      if (nqtot>0) then
151        do iq=1,nqtot
152          CALL put_field(noms(iq),"tracer on surface",qsurf(:,iq))
153        enddo
154      endif ! of if (nqtot>0)
155
156! close file
157      CALL close_restartphy
158!$OMP BARRIER
159
160      END SUBROUTINE phyredem
Note: See TracBrowser for help on using the repository browser.