/[lmdze]/trunk/src_gcm
ViewVC logotype

Annotation of /trunk/src_gcm

Parent Directory Parent Directory | Revision Log Revision Log


Revision 157 - (hide annotations)
Mon Jul 20 16:01:49 2015 UTC (8 years, 9 months ago) by guez
File size: 3622 byte(s)
Just encapsulated SUBROUTINE vlsplt in a module and cleaned it.

In procedure vlx, local variables dxqu and adxqu only need indices
iip2:ip1jm. Otherwise, just cleaned vlx.

Procedures dynredem0 and dynredem1 no longer have argument fichnom,
they just operate on a file named "restart.nc". The programming
guideline here is that gcm should not be more complex than it needs by
itself, other programs (ce0l etc.) just have to adapt to gcm. So ce0l
now creates files "restart.nc" and "restartphy.nc".

In order to facilitate decentralizing the writing of "restartphy.nc",
created a procedure phyredem0 out of phyredem. phyredem0 creates the
NetCDF header of "restartphy.nc" while phyredem writes the NetCDF
variables. As the global attribute itau_phy needs to be filled in
phyredem0, at the beginnig of the run, we must compute its value
instead of just using itap. So we have a dummy argument lmt_pas of
phyredem0. Also, the ncid of "startphy.nc" is upgraded from local
variable of phyetat0 to dummy argument. phyetat0 no longer closes
"startphy.nc".

Following the same decentralizing objective, the ncid of "restart.nc"
is upgraded from local variable of dynredem0 to module variable of
dynredem0_m. "restart.nc" is not closed at the end of dynredem0 nor
opened at the beginning of dynredem1.

In procedure etat0, instead of creating many vectors of size klon
which will be filled with zeroes, just create one array null_array.

In procedure phytrac, instead of writing trs(: 1) to a text file,
write it to "restartphy.nc" (following LMDZ). This is better because
now trs(: 1) is next to its coordinates. We can write to
"restartphy.nc" from phytrac directly, and not add trs(: 1) to the
long list of variables in physiq, thanks to the decentralizing of
"restartphy.nc".

In procedure phyetat0, we no longer write to standard output the
minimum and maximum values of read arrays. It is ok to check input and
abort on invalid values but just printing statistics on input seems too
much useless computation and out of place clutter.

1 guez 123 aaam_bud.f
2     abort_gcm.f
3     academic.f
4     acc.f
5     adaptdt.f
6     addfi.f
7     advect.f
8     advn.f
9     advtrac.f
10     advx.f
11     advxp.f
12     advy.f
13     advyp.f
14     advz.f
15     advzp.f
16     aeropt.f
17     ajsec.f
18     alboc_cd.f
19     alboc.f
20     albsno.f
21     bernoui.f
22     bilan_dyn.f
23     buildop.f
24     caladvtrac.f
25     calbeta.f
26     calcul_fluxs.f
27     caldyn.f
28     calendar.f
29     calfis.f
30     calltherm.f
31     chem.f
32     clcdrag.f
33     cleanstr.f
34     clesphys2.f
35     clesphys.f
36     clmain.f
37     clouds_gno.f
38     clqh.f
39     cltrac.f
40     cltracrn.f
41     clvent.f
42     coefcdrag.f
43     coefkz2.f
44     coefkz.f
45     coefkzmin.f
46     coefpoly.f
47     comconst.f
48     comdissnew.f
49     comfisrtilp.f
50     comgeom.f
51     comgeomphy.f
52     com_io_dyn.f
53     concvl.f
54     conema3_m.f
55     conf_gcm.f
56     conf_guide.f
57     conflx.f
58     conf_phys.f
59     convflu.f
60     convmas.f
61     coordij.f
62     correctbid.f
63     covcont.f
64     covnat.f
65     createnewfield.f
66     ctherm.f
67     cv3_closure.f
68     cv3_compress.f
69     cv3_feed.f
70     cv3_mixing.f
71     cv3_param.f
72     cv3_prelim.f
73     cv3_tracer.f
74     cv3_trigger.f
75     cv3_uncompress.f
76     cv3_undilute1.f
77     cv3_undilute2.f
78     cv3_unsat.f
79     cv3_yield.f
80     cv_closure.f
81     cv_compress.f
82     cv_driver.f
83     cv_feed.f
84     cv_flag.f
85     cvflag.f
86     cvltr.f
87     cv_mixing.f
88     cv_param.f
89     cv_prelim.f
90     cv_thermo.f
91     cvthermo.f
92     cv_trigger.f
93     cv_uncompress.f
94     cv_undilute1.f
95     cv_undilute2.f
96     cv_unsat.f
97     cv_yield.f
98     decoop.f
99     diagcld1.f
100     diagcld2.f
101     diagetpq.f
102     diagphy.f
103     dimens_m.f
104     dimphy.f
105     dimsoil.f
106     dissip.f
107     disvert.f
108     divergf.f
109     diverg_gam.f
110     divgrad2.f
111     dqthermcell2.f
112     dqthermcell.f
113     drag_noro.f
114     dteta1.f
115     dudv1.f
116     dudv2.f
117     dvthermcell2.f
118     dynetat0.f
119     dynredem0.f
120     dynredem1.f
121     enercin.f
122     ener.f
123     errioipsl.f
124     exner_hyb.f
125     FCTTRE.f
126 guez 136 filtreg_hemisph.f
127 guez 137 filtreg_scal.f
128     filtreg_v.f
129 guez 123 findsep.f
130     find_str.f
131     fisrtilp.f
132     flumass.f
133     fluxstokenc.f
134     flxadjtq.f
135     flxasc.f
136     flxbase.f
137     flxddraf.f
138     flxdlfs.f
139     flxdtdq.f
140     flxflux.f
141     flxini.f
142     flxmain.f
143     fonte_neige.f
144     gcm.f
145     geopot.f
146     getfieldindex.f
147     getso4fromfile.f
148     grad.f
149     gradiv2.f
150     gradsdef.f
151     gr_fi_ecrit.f
152     grid_change.f
153     groupe.f
154     groupeun.f
155     gr_phy_write_3d.f
156     gr_u_scal.f
157     gr_v_scal.f
158     guide.f
159     gwprofil.f
160     gwstress.f
161     hbtm.f
162     heavyside.f
163     hgardfou.f
164     histbeg_totreg.f
165     histclo.f
166     histcom_var.f
167     histdef.f
168     histend.f
169     histhori_regular.f
170     histsync.f
171     histvar_seq.f
172     histvert.f
173     histwrite.f
174     histwrite_real.f
175     indicesol.f
176     iniadvtrac.f
177     inidissip.f
178     inifgn.f
179     inifilr.f
180     ini_histins.f
181     ini_histrac.f
182     initdynav.f
183     init_dynzon.f
184     initfluxsto.f
185     inithist.f
186     initial0.f
187     initphysto.f
188     initrrnpb.f
189     init_tau2alpha.f
190     integrd.f
191     interface_surf.f
192     interfoce_lim.f
193     interfsurf_hq.f
194     interfsur_lim.f
195     interpost.f
196     interpre.f
197 guez 131 invert_zoom_x.f
198 guez 123 ioconf_calendar.f
199     ioget_calendar.f
200     ioipslmpp.f
201     isittime.f
202     ismax.f
203     ismin.f
204     itau2date.f
205     ju2ymds.f
206     laplacien.f
207     laplacien_gam.f
208     laplacien_rot.f
209     laplacien_rotgam.f
210     leapfrog.f
211     lift_noro.f
212     limx.f
213     limy.f
214     limz.f
215     lwb.f
216     lwbv.f
217     lwc.f
218     lw.f
219     lwtt.f
220     lwttm.f
221     lwu.f
222     lwvb.f
223     lwvd.f
224     lwv.f
225     lwvn.f
226     massbar.f
227     massbarxy.f
228     massdair.f
229     mathelp.f
230     mathop2.f
231     mathop.f
232     minmax.f
233     minmaxqfi.f
234     moycum.f
235     nat2gcm.f
236     newmicro.f
237     nflxtr.f
238     nuage.f
239     nxgrad.f
240     nxgrad_gam.f
241     nxgraro2.f
242     o3_chem.f
243     orbite.f
244     orodrag.f
245     orolift.f
246     orosetup.f
247     ozonecm.f
248     paramet_m.f
249     pentes_ini.f
250     phyetat0.f
251     phyredem.f
252 guez 157 phyredem0.f
253 guez 123 physiq.f
254     phystokenc.f
255     phytrac.f
256     ppm3d.f
257     prather.f
258     pres2lev.f
259     press_coefoz.f
260     pressure_var.f
261 guez 124 principal_cshift.f
262 guez 123 printflag.f
263     qcheck.f
264     qminimum.f
265     q_sat.f
266     raddim.f
267     raddimlw.f
268     radepsi.f
269     radiornpb.f
270     radlwsw.f
271     radopt.f
272     read_reanalyse.f
273     readsulfate.f
274     readsulfate_preind.f
275     reanalyse2nat.f
276     regr_pr_av.f
277     regr_pr_comb_coefoz.f
278     regr_pr_int.f
279     rotatf.f
280     rotat_nfil.f
281     scopy.f
282     screenc.f
283     screenp.f
284     soil.f
285     sortvarc.f
286     ssum.f
287     stdlevvar.f
288     strlowercase.f
289     sugwd.f
290     suphec.f
291     sw1s.f
292     sw2s.f
293     swclr.f
294     swde.f
295     sw.f
296     swr.f
297     swtt1.f
298     swtt.f
299     swu.f
300     tau2alpha.f
301     temps.f
302     thermcell.f
303     tourpot.f
304     tracstoke.f
305     trans_buff.f
306     transp.f
307     transp_lay.f
308     unit_nml_m.f
309     ustarhb.f
310     vdif_kcay.f
311     vitvert.f
312     vlsplt.f
313     vlspltqs.f
314     vlx.f
315     vlxqs.f
316     vly.f
317     vlyqs.f
318     vlz.f
319     writedynav.f
320     writefield.f
321     writehist.f
322     yamada4.f
323     yamada.f
324     ymds2ju.f
325     YOECUMF.f
326     YOEGWD.f
327     yoethf.f
328     YOMCST.f
329     zenang.f
330     zilch.f

  ViewVC Help
Powered by ViewVC 1.1.21