/[lmdze]/trunk/libf/dyn3d/gcm.f90
ViewVC logotype

Contents of /trunk/libf/dyn3d/gcm.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 7 - (show annotations)
Mon Mar 31 12:24:17 2008 UTC (16 years, 1 month ago) by guez
File size: 6966 byte(s)
This revision is not in working order. Pending some moving of files.

Important changes. In the program "etat0_lim": ozone coefficients from
Mobidic are regridded in time instead of pressure ; consequences in
"etat0". In the program "gcm", ozone coefficients from Mobidic are
read once per day only for the current day and regridded in pressure ;
consequences in "o3_chem_m", "regr_pr_coefoz", "phytrac" and
"regr_pr_comb_coefoz_m".

NetCDF95 is a library and does not export NetCDF.

New variables "nag_gl_options", "nag_fcalls_options" and
"nag_cross_options" in "nag_tools.mk".

"check_coefoz.jnl" rewritten entirely for new version of
"coefoz_LMDZ.nc".

Target "obj_etat0_lim" moved from "GNUmakefile" to "nag_rules.mk".

Added some "intent" attributes in "calfis", "clmain", "clqh",
"cltrac", "cltracrn", "cvltr", "ini_undefSTD", "moy_undefSTD",
"nflxtr", "phystokenc", "phytrac", "readsulfate", "readsulfate_preind"
and "undefSTD".

In "dynetat0", "dynredem0" and "gcm", "phis" has rank 2 instead of
1. "phis" has assumed shape in "dynredem0".

Added module containing "dynredem0". Changed some calls with NetCDF
Fortran 77 interface to calls with NetCDF95 interface.

Replaced calls to "ssum" by calls to "sum" in "inigeom".

In "make.sh", new option "-c" to change compiler.

In "aaam_bud", argument "rjour" deleted.

In "physiq": renamed some variables; deleted variable "xjour".

In "phytrac": renamed some variables; new argument "lmt_pas".

1 PROGRAM gcm
2
3 ! General circulation model of LMD
4
5 ! From "gcm.F", version 1.4, 2006/04/04 15:05:16
6
7 ! Avec coordonnées verticales hybrides, avec nouveaux opérateurs de
8 ! dissipation * (gradiv2, divgrad2, nxgraro2)
9
10 ! Authors: P. Le Van, L. Fairhead, F. Hourdin
11
12 ! Possibilité de choisir le schéma pour l'advection de "q", en
13 ! modifiant "iadv" dans "traceur.def".
14
15 ! Pour Van-Leer plus vapeur d'eau saturée : iadv(1)=4
16 ! Pour Van-Leer : iadv=10
17
18 USE IOIPSL, only: ioconf_calendar
19 use dimens_m, only: iim, jjm, llm, nqmx
20 use dimphy, only: klon
21 use paramet_m, only: ip1jm, ip1jmp1
22 use comconst, only: daysec, cpp, dtvr, dtphys, g, rad, r, initialize
23
24 use comdissnew, only: lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
25 tetagrot, tetatemp
26
27 use conf_gcm_m, only: day_step, iperiod, anneeref, dayref, iecri, iphysiq, &
28 nday, raz_date, periodav, conf_gcm
29
30 use logic, only: iflag_phys
31 use comgeom, only: rlatu, aire_2d, cu_2d, cv_2d, rlonv
32 use temps, only: day_ref, annee_ref, day_ini, day_end, itau_phy, itau_dyn
33 use com_io_dyn, only: histid, histvid, histaveid
34 use tracstoke, only: istdyn, istphy
35 use abort_gcm_m, only: abort_gcm
36 use inithist_m, only: inithist
37 use initdynav_m, only: initdynav
38 use dynetat0_m, only: dynetat0
39 use grid_change, only: dyn_phy, init_dyn_phy
40 use advtrac_m, only: iniadvtrac
41 use leapfrog_m, only: leapfrog
42 use dynredem0_m, only: dynredem0
43
44 IMPLICIT NONE
45
46 REAL clesphy0(20)
47 REAL zdtvr ! time step for dynamics, in s
48
49 ! Variables dynamiques :
50 REAL vcov(ip1jm, llm), ucov(ip1jmp1, llm) ! vents covariants
51 REAL teta(ip1jmp1, llm) ! température potentielle
52 REAL q(ip1jmp1, llm, nqmx) ! champs advectés
53 REAL ps(ip1jmp1) ! pression au sol (Pa)
54
55 REAL masse(ip1jmp1, llm) ! masse d'air
56 REAL phis(iim + 1, jjm + 1) ! géopotentiel au sol
57
58 ! Variables pour le fichier histoire :
59 REAL time_0
60
61 !!INTEGER i
62
63 ! Calendrier :
64 LOGICAL:: true_calendar = .false. ! default value
65
66 ! Variables pour l'initialisation de la physique :
67 integer nq
68 REAL zcufi(klon), zcvfi(klon) ! "cu" and "cv" values on the scalar grid
69 REAL latfi(klon), lonfi(klon)
70 REAL airefi(klon)
71
72 logical mask_v(iim + 1, jjm)
73 ! (mask for points in the "v" grid, first index is for longitude,
74 ! second index is for latitude)
75
76 namelist /main_nml/true_calendar
77
78 !------------------------------------------------------------
79
80 print *, "Enter namelist 'main_nml'."
81 read (unit=*, nml=main_nml)
82 write(unit=*, nml=main_nml)
83
84 ! Initialisations:
85 call initialize
86
87 ! Choix du calendrier :
88 if (true_calendar) then
89 call ioconf_calendar('gregorian')
90 else
91 call ioconf_calendar('360d')
92 endif
93
94 ! Lecture des fichiers "gcm.def" ou "run.def" :
95 CALL conf_gcm(clesphy0)
96
97 ! Initialisation des traceurs
98 ! Choix du schéma pour l'advection dans le fichier "traceur.def" ou via INCA
99 call iniadvtrac(nq)
100
101 ! Lecture du fichier "start.nc" :
102 CALL dynetat0(vcov, ucov, teta, q, masse, ps, phis, time_0)
103 ! Begin special experiment
104 !!$ print *, "This is a special experiment."
105 !!$ print *, "We are setting:"
106 !!$ print *, "ucov = vcov = 0, q = 0, ps = 101325"
107 !!$ print *, "We are averaging 'teta' horizontally."
108 !!$ ucov = 0.
109 !!$ vcov = 0.
110 !!$ q = 0.
111 !!$ ps = 101325.
112 ! Average teta over all longitudes and latitudes:
113 !!$ forall(i = 1:llm) teta(:,i) = sum(teta(:,i)) / ip1jmp1
114 ! (it would be better to weight each element with an associated
115 ! surface area)
116 ! End special experiment
117
118 ! Lecture des paramètres de contrôle pour la simulation :
119 ! on recalcule éventuellement le pas de temps
120 IF (MOD(day_step, iperiod) /= 0) THEN
121 call abort_gcm(modname = "gcm", message = &
122 'Il faut choisir un nombre de pas par jour multiple de "iperiod".', &
123 ierr = 1)
124 ENDIF
125
126 IF (MOD(day_step,iphysiq)/=0) THEN
127 call abort_gcm(modname = "gcm", message = &
128 'Il faut choisir un nombre de pas par jour multiple de "iphysiq".', &
129 ierr = 1)
130 ENDIF
131
132 ! On remet le calendrier à zero si demandé:
133 if (annee_ref /= anneeref .or. day_ref /= dayref) then
134 print *, 'Attention : les dates initiales lues dans le fichier ' // &
135 '"start" ne correspondent pas à celles lues dans "gcm.def".'
136 if (raz_date /= 1) then
137 print *, 'On garde les dates du fichier "start".'
138 else
139 print *, 'On réinitialise à la date lue dans "gcm.def".'
140 annee_ref = anneeref
141 day_ref = dayref
142 day_ini = dayref
143 itau_dyn = 0
144 itau_phy = 0
145 time_0 = 0.
146 endif
147 ELSE
148 raz_date = 0
149 endif
150
151 ! Initialisation des constantes dynamiques :
152 zdtvr = daysec / REAL(day_step)
153 IF (dtvr /= zdtvr) THEN
154 print *, 'Warning: the time steps in the ".def" file and in ' // &
155 '"start.nc" are different'
156 print *, 'dtvr (from "start.nc") = ', dtvr
157 print *, 'zdtvr (from ".def") = ', zdtvr
158 print *, 'Using the value from the ".def" file.'
159 dtvr = zdtvr
160 ENDIF
161 CALL iniconst
162
163 ! Initialisation de la géometrie :
164 CALL inigeom
165
166 ! Initialisation du filtre :
167 CALL inifilr
168
169 ! Initialisation de la dissipation :
170 CALL inidissip(lstardis, nitergdiv, nitergrot, niterh, tetagdiv, tetagrot, &
171 tetatemp)
172
173 call init_dyn_phy
174
175 ! Initialisation de la physique :
176 IF (iflag_phys == 1) THEN
177 latfi(1)=rlatu(1)
178 latfi(2:klon-1) = pack(spread(rlatu(2:jjm), 1, iim), .true.)
179 latfi(klon)= rlatu(jjm + 1)
180
181 lonfi(1)=0.
182 lonfi(2:klon-1) = pack(spread(rlonv(:iim), 2, jjm - 1), .true.)
183 lonfi(klon)= 0.
184
185 zcufi = pack(cu_2d, dyn_phy)
186
187 ! Construct a mask for points in the "v" grid:
188 mask_v = .true.
189 mask_v(2:, 1) = .false.
190 mask_v(iim + 1, 2:) = .false.
191
192 zcvfi(:klon - 1) = pack(cv_2d, mask_v)
193 zcvfi(klon) = cv_2d(1, jjm)
194 ! (that value of "cv_2d" is used twice in "zcvfi")
195
196 airefi = pack(aire_2d, dyn_phy)
197 print *, 'Attention : vitesse verticale nulle dans la physique.'
198 CALL iniphysiq(klon, llm, daysec, day_ini, dtphys, latfi, lonfi, airefi, &
199 zcufi, zcvfi, rad, g, r, cpp)
200 ENDIF
201
202 ! Numéro de stockage pour les fichiers de redémarrage :
203 ! Initialisation des entrées-sorties :
204 day_end = day_ini + nday
205 print *, "day_ini = ", day_ini
206 print *, "day_end = ", day_end
207
208 CALL dynredem0("restart.nc", day_end, phis)
209 CALL inithist(day_ref, annee_ref, zdtvr, nqmx, histid, histvid, &
210 infile="dyn_hist.nc", t_ops = iecri * daysec, t_wrt = iecri * daysec)
211 CALL initdynav(day_ref, annee_ref, zdtvr, nqmx, histaveid, &
212 infile='dyn_hist_ave.nc', t_ops = iperiod * zdtvr, &
213 t_wrt = periodav * daysec)
214
215 ! Choix des fréquences de stockage pour le hors-ligne :
216 istdyn = day_step / 4 ! stockage toutes les 6 h = 1 jour / 4
217 istphy = istdyn / iphysiq
218
219 ! Intégration temporelle du modèle :
220 CALL leapfrog(ucov, vcov, teta, ps, masse, phis, nq, q, clesphy0, time_0)
221
222 END PROGRAM gcm

  ViewVC Help
Powered by ViewVC 1.1.21