/[lmdze]/trunk/Sources/phylmd/initphysto.f
ViewVC logotype

Annotation of /trunk/Sources/phylmd/initphysto.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 178 - (hide annotations)
Fri Mar 11 18:47:26 2016 UTC (8 years, 2 months ago) by guez
File size: 5951 byte(s)
Moved variables date0, deltat, datasz_max, ncvar_ids, point, buff_pos,
buffer, regular from module histcom_var to modules where they are
defined.

Removed procedure ioipslmpp, useless for a sequential program.

Added argument datasz_max to histwrite_real (to avoid circular
dependency with histwrite).

Removed useless variables and computations everywhere.

Changed real litteral constants from default kind to double precision
in lwb, lwu, lwvn, sw1s, swtt, swtt1, swu.

Removed unused arguments: paer of sw, sw1s, sw2s, swclr; pcldsw of
sw1s, sw2s; pdsig, prayl of swr; co2_ppm of clmain, clqh; tsol of
transp_lay; nsrf of screenp; kcrit and kknu of gwstress; pstd of
orosetup.

Added output of relative humidity.

1 guez 155 module initphysto_m
2 guez 3
3 guez 155 IMPLICIT NONE
4 guez 3
5 guez 155 contains
6 guez 3
7 guez 155 SUBROUTINE initphysto(infile,rlon,rlat,tstep,t_ops,t_wrt,fileid)
8 guez 3
9 guez 155 ! From phylmd/initphysto.F,v 1.2 2004/06/22 11:45:32
10     ! Routine d'initialisation des ecritures des fichiers histoires LMDZ
11     ! au format IOIPSL
12 guez 3
13 guez 155 ! Appels succesifs des routines: histbeg
14     ! histhori
15     ! histver
16     ! histdef
17     ! histend
18 guez 3
19 guez 155 ! Entree:
20 guez 3
21 guez 155 ! infile: nom du fichier histoire a creer
22     ! day0,anne0: date de reference
23     ! tstep: duree du pas de temps en seconde
24     ! t_ops: frequence de l'operation pour IOIPSL
25     ! t_wrt: frequence d'ecriture sur le fichier
26 guez 3
27 guez 155 ! Sortie:
28     ! fileid: ID du fichier netcdf cree
29     ! filevid:ID du fichier netcdf pour la grille v
30 guez 3
31 guez 155 ! L. Fairhead, 03/99
32 guez 3
33 guez 155 use dynetat0_m, only: day_ref, annee_ref
34     USE histbeg_totreg_m, ONLY : histbeg_totreg
35     USE histdef_m, ONLY : histdef
36     USE histend_m, ONLY : histend
37     use histsync_m, only: histsync
38     USE histvert_m, ONLY : histvert
39     USE dimens_m
40     USE paramet_m
41     USE comconst
42     USE indicesol
43     USE dimphy
44     use conf_gcm_m
45     USE comgeom
46     USE ymds2ju_m
47 guez 3
48 guez 155 ! Arguments
49     CHARACTER(len=*) infile
50     INTEGER nhoriid, i
51     REAL, INTENT (IN) :: tstep
52     REAL t_ops, t_wrt
53     INTEGER fileid
54     INTEGER l
55     REAL nivsigs(llm)
56 guez 3
57 guez 155 ! Variables locales
58 guez 3
59 guez 155 INTEGER tau0
60     REAL zjulian
61     INTEGER zvertiid
62     LOGICAL ok_sync
63     REAL zx_lon(iim,jjm+1), zx_lat(iim,jjm+1)
64 guez 3
65 guez 155 REAL, INTENT (IN) :: rlon(klon), rlat(klon)
66 guez 3
67 guez 155 !-----------------------------------------------------
68 guez 3
69 guez 155 ! Initialisations
70     ok_sync = .TRUE.
71 guez 3
72 guez 155 ! Appel a histbeg: creation du fichier netcdf et initialisations
73     ! diverses
74 guez 3
75 guez 155 CALL ymds2ju(annee_ref,1,day_ref,0.0,zjulian)
76     tau0 = 0
77 guez 3
78 guez 155 CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlon,zx_lon)
79     DO i = 1, iim
80     zx_lon(i,1) = rlon(i+1)
81     zx_lon(i,jjm+1) = rlon(i+1)
82     END DO
83     CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlat,zx_lat)
84 guez 3
85    
86 guez 155 CALL histbeg_totreg(infile,zx_lon(:,1),zx_lat(1,:),1,iim,1,jjm+1,tau0, &
87     zjulian,tstep,nhoriid,fileid)
88 guez 3
89 guez 155 ! Appel a histvert pour la grille verticale
90 guez 3
91 guez 155 DO l = 1, llm
92     nivsigs(l) = float(l)
93     END DO
94 guez 3
95 guez 155 CALL histvert(fileid,'sig_s','Niveaux sigma','sigma_level',nivsigs, &
96     zvertiid)
97 guez 3
98 guez 155 ! Appels a histdef pour la definition des variables a sauvegarder
99 guez 3
100 guez 155 CALL histdef(fileid,'phis','Surface geop. height','-',iim,jjm+1,nhoriid, &
101     1,1,1,-99,'once',t_ops,t_wrt)
102 guez 3
103 guez 155 CALL histdef(fileid,'aire','Grid area','-',iim,jjm+1,nhoriid,1,1,1,-99, &
104     'once',t_ops,t_wrt)
105 guez 3
106 guez 155 CALL histdef(fileid,'dtime','tps phys ','s',1,1,nhoriid,1,1,1,-99, &
107     'once',t_ops,t_wrt)
108 guez 3
109 guez 155 CALL histdef(fileid,'istphy','tps stock','s',1,1,nhoriid,1,1,1,-99, &
110     'once',t_ops,t_wrt)
111 guez 3
112 guez 155 ! T
113 guez 3
114 guez 155 CALL histdef(fileid,'t','Temperature','K',iim,jjm+1,nhoriid,llm,1,llm, &
115     zvertiid,'inst(X)',t_ops,t_wrt)
116 guez 31
117 guez 155 CALL histdef(fileid,'mfu','flx m. pan. mt','kg m/s',iim,jjm+1,nhoriid, &
118     llm,1,llm,zvertiid,'inst(X)',t_ops,t_wrt)
119 guez 31
120 guez 155 CALL histdef(fileid,'mfd','flx m. pan. des','kg m/s',iim,jjm+1,nhoriid, &
121     llm,1,llm,zvertiid,'inst(X)',t_ops,t_wrt)
122 guez 31
123    
124 guez 155 ! en_u
125 guez 31
126 guez 155 CALL histdef(fileid,'en_u','flx ent pan mt','kg m/s',iim,jjm+1,nhoriid, &
127     llm,1,llm,zvertiid,'inst(X)',t_ops,t_wrt)
128 guez 31
129 guez 155 CALL histdef(fileid,'de_u','flx det pan mt','kg m/s',iim,jjm+1,nhoriid, &
130     llm,1,llm,zvertiid,'inst(X)',t_ops,t_wrt)
131 guez 31
132    
133 guez 155 ! en_d
134 guez 31
135 guez 155 CALL histdef(fileid,'en_d','flx ent pan dt','kg m/s',iim,jjm+1,nhoriid, &
136     llm,1,llm,zvertiid,'inst(X)',t_ops,t_wrt)
137 guez 31
138    
139    
140 guez 155 ! de_d
141 guez 31
142 guez 155 CALL histdef(fileid,'de_d','flx det pan dt','kg m/s',iim,jjm+1,nhoriid, &
143     llm,1,llm,zvertiid,'inst(X)',t_ops,t_wrt)
144 guez 31
145 guez 155 ! coefh frac_impa,frac_nucl
146 guez 31
147 guez 155 CALL histdef(fileid,'coefh',' ',' ',iim,jjm+1,nhoriid,llm,1,llm, &
148     zvertiid,'inst(X)',t_ops,t_wrt)
149 guez 31
150 guez 155 ! abderrahmane le 16 09 02
151     CALL histdef(fileid,'fm_th',' ',' ',iim,jjm+1,nhoriid,llm,1,llm, &
152     zvertiid,'inst(X)',t_ops,t_wrt)
153 guez 31
154 guez 155 CALL histdef(fileid,'en_th',' ',' ',iim,jjm+1,nhoriid,llm,1,llm, &
155     zvertiid,'inst(X)',t_ops,t_wrt)
156     ! fin aj
157 guez 31
158 guez 155 CALL histdef(fileid,'frac_impa',' ',' ',iim,jjm+1,nhoriid,llm,1,llm, &
159     zvertiid,'inst(X)',t_ops,t_wrt)
160 guez 31
161 guez 155 CALL histdef(fileid,'frac_nucl',' ',' ',iim,jjm+1,nhoriid,llm,1,llm, &
162     zvertiid,'inst(X)',t_ops,t_wrt)
163 guez 31
164    
165 guez 155 ! pyu1
166 guez 31
167 guez 155 CALL histdef(fileid,'pyu1',' ',' ',iim,jjm+1,nhoriid,1,1,1,-99, &
168     'inst(X)',t_ops,t_wrt)
169 guez 31
170    
171 guez 155 ! pyv1
172 guez 31
173 guez 155 CALL histdef(fileid,'pyv1',' ',' ',iim,jjm+1,nhoriid,1,1,1,-99, &
174     'inst(X)',t_ops,t_wrt)
175 guez 31
176 guez 155 CALL histdef(fileid,'ftsol1',' ',' ',iim,jjm+1,nhoriid,1,1,1,-99, &
177     'inst(X)',t_ops,t_wrt)
178 guez 31
179    
180 guez 155 ! ftsol2
181 guez 31
182 guez 155 CALL histdef(fileid,'ftsol2',' ',' ',iim,jjm+1,nhoriid,1,1,1,-99, &
183     'inst(X)',t_ops,t_wrt)
184 guez 31
185    
186 guez 155 ! ftsol3
187 guez 31
188 guez 155 CALL histdef(fileid,'ftsol3',' ',' ',iim,jjm+1,nhoriid,1,1,1,-99, &
189     'inst(X)',t_ops,t_wrt)
190 guez 31
191    
192 guez 155 ! ftsol4
193 guez 31
194 guez 155 CALL histdef(fileid,'ftsol4',' ',' ',iim,jjm+1,nhoriid,1,1,1,-99, &
195     'inst(X)',t_ops,t_wrt)
196 guez 31
197    
198 guez 155 ! rain
199 guez 31
200 guez 155 CALL histdef(fileid,'rain',' ',' ',iim,jjm+1,nhoriid,1,1,1,-99, &
201     'inst(X)',t_ops,t_wrt)
202 guez 31
203    
204 guez 155 ! psrf1
205 guez 31
206 guez 155 CALL histdef(fileid,'psrf1',' ',' ',iim,jjm+1,nhoriid,1,1,1,-99, &
207     'inst(X)',t_ops,t_wrt)
208 guez 31
209    
210 guez 155 ! psrf2
211 guez 31
212 guez 155 CALL histdef(fileid,'psrf2',' ',' ',iim,jjm+1,nhoriid,1,1,1,-99, &
213     'inst(X)',t_ops,t_wrt)
214 guez 31
215    
216 guez 155 ! psrf3
217 guez 31
218 guez 155 CALL histdef(fileid,'psrf3',' ',' ',iim,jjm+1,nhoriid,1,1,1,-99, &
219     'inst(X)',t_ops,t_wrt)
220 guez 31
221    
222 guez 155 ! psrf4
223 guez 31
224 guez 155 CALL histdef(fileid,'psrf4',' ',' ',iim,jjm+1,nhoriid,1,1,1,-99, &
225     'inst(X)',t_ops,t_wrt)
226    
227     CALL histend(fileid)
228     IF (ok_sync) CALL histsync
229    
230     END SUBROUTINE initphysto
231    
232     end module initphysto_m

  ViewVC Help
Powered by ViewVC 1.1.21