source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/config/ppsrc/dyn/writedynav_p.f @ 224

Last change on this file since 224 was 224, checked in by ymipsl, 10 years ago
File size: 12.2 KB
Line 
1!
2! $Id: writedynav_p.F 1279 2009-12-10 09:02:56Z fairhead $
3!
4      subroutine writedynav_p( histid, time, vcov, 
5     ,                          ucov,teta,ppk,phi,q,masse,ps,phis)
6
7
8
9
10
11      USE parallel_lmdz
12      USE misc_mod
13      USE infotrac
14      implicit none
15
16C
17C   Ecriture du fichier histoire au format IOIPSL
18C
19C   Appels succesifs des routines: histwrite
20C
21C   Entree:
22C      histid: ID du fichier histoire
23C      time: temps de l'ecriture
24C      vcov: vents v covariants
25C      ucov: vents u covariants
26C      teta: temperature potentielle
27C      phi : geopotentiel instantane
28C      q   : traceurs
29C      masse: masse
30C      ps   :pression au sol
31C      phis : geopotentiel au sol
32C     
33C
34C   Sortie:
35C      fileid: ID du fichier netcdf cree
36C
37C   L. Fairhead, LMD, 03/99
38C
39C =====================================================================
40C
41C   Declarations
42!-----------------------------------------------------------------------
43!   INCLUDE 'dimensions.h'
44!
45!   dimensions.h contient les dimensions du modele
46!   ndm est tel que iim=2**ndm
47!-----------------------------------------------------------------------
48
49      INTEGER iim,jjm,llm,ndm
50
51      PARAMETER (iim= 128,jjm=96,llm=64,ndm=1)
52
53!-----------------------------------------------------------------------
54!
55! $Header$
56!
57!
58!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
59!                 veillez  n'utiliser que des ! pour les commentaires
60!                 et  bien positionner les & des lignes de continuation
61!                 (les placer en colonne 6 et en colonne 73)
62!
63!
64!-----------------------------------------------------------------------
65!   INCLUDE 'paramet.h'
66
67      INTEGER  iip1,iip2,iip3,jjp1,llmp1,llmp2,llmm1
68      INTEGER  kftd,ip1jm,ip1jmp1,ip1jmi1,ijp1llm
69      INTEGER  ijmllm,mvar
70      INTEGER jcfil,jcfllm
71
72      PARAMETER( iip1= iim+1,iip2=iim+2,iip3=iim+3                       &
73     &    ,jjp1=jjm+1-1/jjm)
74      PARAMETER( llmp1 = llm+1,  llmp2 = llm+2, llmm1 = llm-1 )
75      PARAMETER( kftd  = iim/2 -ndm )
76      PARAMETER( ip1jm  = iip1*jjm,  ip1jmp1= iip1*jjp1 )
77      PARAMETER( ip1jmi1= ip1jm - iip1 )
78      PARAMETER( ijp1llm= ip1jmp1 * llm, ijmllm= ip1jm * llm )
79      PARAMETER( mvar= ip1jmp1*( 2*llm+1) + ijmllm )
80      PARAMETER( jcfil=jjm/2+5, jcfllm=jcfil*llm )
81
82!-----------------------------------------------------------------------
83!
84! $Id: comconst.h 1437 2010-09-30 08:29:10Z emillour $
85!
86!-----------------------------------------------------------------------
87! INCLUDE comconst.h
88
89      COMMON/comconsti/im,jm,lllm,imp1,jmp1,lllmm1,lllmp1,lcl,          &
90     &                 iflag_top_bound,mode_top_bound
91      COMMON/comconstr/dtvr,daysec,                                     &
92     & pi,dtphys,dtdiss,rad,r,kappa,cotot,unsim,g,omeg                  &
93     & ,dissip_fac_mid,dissip_fac_up,dissip_deltaz,dissip_hdelta        &
94     & ,dissip_pupstart  ,tau_top_bound,                                &
95     & daylen,molmass, ihf
96      COMMON/cpdetvenus/cpp,nu_venus,t0_venus
97
98      INTEGER im,jm,lllm,imp1,jmp1,lllmm1,lllmp1,lcl
99      REAL dtvr ! dynamical time step (in s)
100      REAL daysec !length (in s) of a standard day
101      REAL pi    ! something like 3.14159....
102      REAL dtphys ! (s) time step for the physics
103      REAL dtdiss ! (s) time step for the dissipation
104      REAL rad ! (m) radius of the planet
105      REAL r ! Reduced Gas constant r=R/mu
106             ! with R=8.31.. J.K-1.mol-1, mu: mol mass of atmosphere (kg/mol)
107      REAL cpp   ! Cp
108      REAL kappa ! kappa=R/Cp
109      REAL cotot
110      REAL unsim ! = 1./iim
111      REAL g ! (m/s2) gravity
112      REAL omeg ! (rad/s) rotation rate of the planet
113! Dissipation factors, for Earth model:
114      REAL dissip_factz,dissip_zref !dissip_deltaz
115! Dissipation factors, for other planets:
116      REAL dissip_fac_mid,dissip_fac_up,dissip_deltaz,dissip_hdelta
117      REAL dissip_pupstart
118      INTEGER iflag_top_bound,mode_top_bound
119      REAL tau_top_bound
120      REAL daylen ! length of solar day, in 'standard' day length
121      REAL molmass ! (g/mol) molar mass of the atmosphere
122
123      REAL nu_venus,t0_venus ! coeffs needed for Cp(T), Venus atmosphere
124      REAL ihf  ! (W/m2) intrinsic heat flux for giant planets
125
126
127!-----------------------------------------------------------------------
128!
129! $Id: comvert.h 1654 2012-09-24 15:07:18Z aslmd $
130!
131!-----------------------------------------------------------------------
132!   INCLUDE 'comvert.h'
133
134      COMMON/comvertr/ap(llm+1),bp(llm+1),presnivs(llm),dpres(llm),     &
135     &               pa,preff,nivsigs(llm),nivsig(llm+1),               &
136     &               aps(llm),bps(llm),scaleheight,pseudoalt(llm)
137
138      common/comverti/disvert_type, pressure_exner
139
140      real ap     ! hybrid pressure contribution at interlayers
141      real bp     ! hybrid sigma contribution at interlayer
142      real presnivs ! (reference) pressure at mid-layers
143      real dpres
144      real pa     ! reference pressure (Pa) at which hybrid coordinates
145                  ! become purely pressure
146      real preff  ! reference surface pressure (Pa)
147      real nivsigs
148      real nivsig
149      real aps    ! hybrid pressure contribution at mid-layers
150      real bps    ! hybrid sigma contribution at mid-layers
151      real scaleheight ! atmospheric (reference) scale height (km)
152      real pseudoalt ! pseudo-altitude of model levels (km), based on presnivs(),
153                     ! preff and scaleheight
154
155      integer disvert_type ! type of vertical discretization:
156                           ! 1: Earth (default for planet_type==earth),
157                           !     automatic generation
158                           ! 2: Planets (default for planet_type!=earth),
159                           !     using 'z2sig.def' (or 'esasig.def) file
160
161      logical pressure_exner
162!     compute pressure inside layers using Exner function, else use mean
163!     of pressure values at interfaces
164
165 !-----------------------------------------------------------------------
166!
167! $Header$
168!
169!CDK comgeom
170      COMMON/comgeom/                                                   &
171     & cu(ip1jmp1),cv(ip1jm),unscu2(ip1jmp1),unscv2(ip1jm),             &
172     & aire(ip1jmp1),airesurg(ip1jmp1),aireu(ip1jmp1),                  &
173     & airev(ip1jm),unsaire(ip1jmp1),apoln,apols,                       &
174     & unsairez(ip1jm),airuscv2(ip1jm),airvscu2(ip1jm),                 &
175     & aireij1(ip1jmp1),aireij2(ip1jmp1),aireij3(ip1jmp1),              &
176     & aireij4(ip1jmp1),alpha1(ip1jmp1),alpha2(ip1jmp1),                &
177     & alpha3(ip1jmp1),alpha4(ip1jmp1),alpha1p2(ip1jmp1),               &
178     & alpha1p4(ip1jmp1),alpha2p3(ip1jmp1),alpha3p4(ip1jmp1),           &
179     & fext(ip1jm),constang(ip1jmp1),rlatu(jjp1),rlatv(jjm),            &
180     & rlonu(iip1),rlonv(iip1),cuvsurcv(ip1jm),cvsurcuv(ip1jm),         &
181     & cvusurcu(ip1jmp1),cusurcvu(ip1jmp1),cuvscvgam1(ip1jm),           &
182     & cuvscvgam2(ip1jm),cvuscugam1(ip1jmp1),                           &
183     & cvuscugam2(ip1jmp1),cvscuvgam(ip1jm),cuscvugam(ip1jmp1),         &
184     & unsapolnga1,unsapolnga2,unsapolsga1,unsapolsga2,                 &
185     & unsair_gam1(ip1jmp1),unsair_gam2(ip1jmp1),unsairz_gam(ip1jm),    &
186     & aivscu2gam(ip1jm),aiuscv2gam(ip1jm),xprimu(iip1),xprimv(iip1)
187
188!
189        REAL                                                            &
190     & cu,cv,unscu2,unscv2,aire,airesurg,aireu,airev,unsaire,apoln     ,&
191     & apols,unsairez,airuscv2,airvscu2,aireij1,aireij2,aireij3,aireij4,&
192     & alpha1,alpha2,alpha3,alpha4,alpha1p2,alpha1p4,alpha2p3,alpha3p4 ,&
193     & fext,constang,rlatu,rlatv,rlonu,rlonv,cuvscvgam1,cuvscvgam2     ,&
194     & cvuscugam1,cvuscugam2,cvscuvgam,cuscvugam,unsapolnga1,unsapolnga2&
195     & ,unsapolsga1,unsapolsga2,unsair_gam1,unsair_gam2,unsairz_gam    ,&
196     & aivscu2gam ,aiuscv2gam,cuvsurcv,cvsurcuv,cvusurcu,cusurcvu,xprimu&
197     & , xprimv
198!
199!
200! $Id: temps.h 1577 2011-10-20 15:06:47Z fairhead $
201!
202!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
203!                 veillez  n'utiliser que des ! pour les commentaires
204!                 et  bien positionner les & des lignes de continuation
205!                 (les placer en colonne 6 et en colonne 73)
206!
207!
208! jD_ref = jour julien de la date de reference (lancement de l'experience)
209! hD_ref = "heure" julienne de la date de reference
210!-----------------------------------------------------------------------
211! INCLUDE 'temps.h'
212
213      COMMON/temps_r/dt,jD_ref,jH_ref,start_time,hour_ini
214      COMMON/temps_i/day_ini,day_end,annee_ref,day_ref,                 &
215     &             itau_dyn,itau_phy,itaufin
216      COMMON/temps_c/calend
217
218
219      INTEGER   itaufin ! total number of dynamical steps for the run
220      INTEGER   itau_dyn, itau_phy
221      INTEGER   day_ini ! initial day # of simulation sequence
222      INTEGER   day_end ! final day # ; i.e. day # when this simulation ends
223      INTEGER   annee_ref
224      INTEGER   day_ref
225      REAL      dt ! (dynamics) time step (changes if doing Matsuno or LF step)
226      REAL      jD_ref, jH_ref, start_time
227      CHARACTER (len=10) :: calend
228
229      ! Additionnal Mars stuff:
230      real hour_ini ! initial fraction of day of simulation sequence (0=<hour_ini<1)
231
232!-----------------------------------------------------------------------
233!
234! $Id: ener.h 1447 2010-10-22 16:18:27Z jghattas $
235!
236!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
237!                 veillez à n'utiliser que des ! pour les commentaires
238!                 et à bien positionner les & des lignes de continuation
239!                 (les placer en colonne 6 et en colonne 73)
240!
241! INCLUDE 'ener.h'
242
243      COMMON/ener/ang0,etot0,ptot0,ztot0,stot0,                         &
244     &            ang,etot,ptot,ztot,stot,rmsdpdt ,                     &
245     &            rmsv,gtot(llmm1)
246
247      REAL ang0,etot0,ptot0,ztot0,stot0,                                &
248     &     ang,etot,ptot,ztot,stot,rmsdpdt,rmsv,gtot
249
250!-----------------------------------------------------------------------
251!
252! $Id: logic.h 1520 2011-05-23 11:37:09Z emillour $
253!
254!
255! NB: keep items of different kinds in seperate common blocs to avoid
256!     "misaligned commons" issues
257!-----------------------------------------------------------------------
258! INCLUDE 'logic.h'
259
260      COMMON/logicl/ purmats,forward,leapf,apphys,                      &
261     &  statcl,conser,apdiss,apdelq,saison,ecripar,fxyhypb,ysinus       &
262     &  ,read_start,ok_guide,ok_strato,tidal,ok_gradsfile               &
263     &  ,ok_limit,ok_etat0,hybrid                                       &
264     &  ,moyzon_mu,moyzon_ch
265
266      COMMON/logici/ iflag_phys,iflag_trac
267     
268      LOGICAL purmats,forward,leapf,apphys,statcl,conser,               &
269     & apdiss,apdelq,saison,ecripar,fxyhypb,ysinus                      &
270     &  ,read_start,ok_guide,ok_strato,tidal,ok_gradsfile               &
271     &  ,ok_limit,ok_etat0
272      logical hybrid ! vertical coordinate is hybrid if true (sigma otherwise)
273                     ! (only used if disvert_type==2)
274      logical moyzon_mu,moyzon_ch ! used for zonal averages in Titan
275
276      integer iflag_phys,iflag_trac
277!$OMP THREADPRIVATE(/logicl/)
278!$OMP THREADPRIVATE(/logici/)
279!-----------------------------------------------------------------------
280!
281! $Header$
282!
283      character *120 descript
284      common /titre/descript
285!
286! $Header$
287!
288!c
289!c
290!c..include serre.h
291!c
292       REAL clon,clat,transx,transy,alphax,alphay,pxo,pyo,              &
293     &  grossismx, grossismy, dzoomx, dzoomy,taux,tauy
294       COMMON/serre/clon,clat,transx,transy,alphax,alphay,pxo,pyo ,     &
295     &  grossismx, grossismy, dzoomx, dzoomy,taux,tauy
296!
297! $Header$
298!
299!
300! gestion des impressions de sorties et de débogage
301! lunout:    unité du fichier dans lequel se font les sorties
302!                           (par defaut 6, la sortie standard)
303! prt_level: niveau d'impression souhaité (0 = minimum)
304!
305      INTEGER lunout, prt_level
306      COMMON /comprint/ lunout, prt_level
307
308C
309C   Arguments
310C
311
312      INTEGER histid
313      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) 
314      REAL teta(ip1jmp1,llm),phi(ip1jmp1,llm),ppk(ip1jmp1,llm)                 
315      REAL ps(ip1jmp1),masse(ip1jmp1,llm)                   
316      REAL phis(ip1jmp1)                 
317      REAL q(ip1jmp1,llm,nqtot)
318      integer time
319
320
321      write(lunout,*)'writedynav_p: Needs IOIPSL to function'
322! #endif of #ifdef CPP_IOIPSL
323      return
324      end
Note: See TracBrowser for help on using the repository browser.