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