source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/inithist_loc.F90 @ 5209

Last change on this file since 5209 was 5195, checked in by abarral, 4 days ago

Correct r5192, some lmdz_description cases were missing

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 6.9 KB
Line 
1! $Id: initdynav_p.F 1279 2009-12-10 09:02:56Z fairhead $
2
3SUBROUTINE inithist_loc(day0, anne0, tstep, t_ops, t_wrt)
4
5  ! This routine needs IOIPSL
6  USE IOIPSL
7  USE parallel_lmdz
8  USE lmdz_write_field
9  USE misc_mod
10  USE com_io_dyn_mod, ONLY: histid, histvid, histuid, &
11          dynhist_file, dynhistv_file, dynhistu_file
12  USE comconst_mod, ONLY: pi
13  USE comvert_mod, ONLY: presnivs
14  USE temps_mod, ONLY: itau_dyn
15  USE lmdz_iniprint, ONLY: lunout, prt_level
16  USE lmdz_comgeom
17
18  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
19  USE lmdz_paramet
20  IMPLICIT NONE
21
22
23  !   Routine d'initialisation des ecritures des fichiers histoires LMDZ
24  !   au format IOIPSL
25
26  !   Appels succesifs des routines: histbeg
27  !                              histhori
28  !                              histver
29  !                              histdef
30  !                              histend
31
32  !   Entree:
33
34  !  day0,anne0: date de reference
35  !  tstep: duree du pas de temps en seconde
36  !  t_ops: frequence de l'operation pour IOIPSL
37  !  t_wrt: frequence d'ecriture sur le fichier
38  !  nq: nombre de traceurs
39
40
41  !   L. Fairhead, LMD, 03/99
42
43  ! =====================================================================
44
45  !   Declarations
46
47
48
49  !   Arguments
50
51  INTEGER :: day0, anne0
52  REAL :: tstep, t_ops, t_wrt
53
54  ! This routine needs IOIPSL
55  !   Variables locales
56
57  INTEGER :: tau0
58  REAL :: zjulian
59  INTEGER :: iq
60  REAL :: rlong(iip1, jjp1), rlat(iip1, jjp1)
61  INTEGER :: uhoriid, vhoriid, thoriid
62  INTEGER :: zvertiid, zvertiidv, zvertiidu
63  INTEGER :: ii, jj
64  INTEGER :: zan, dayref
65  INTEGER :: jjb, jje, jjn
66
67  ! definition du domaine d'ecriture pour le rebuild
68
69  INTEGER, DIMENSION(2) :: ddid
70  INTEGER, DIMENSION(2) :: dsg
71  INTEGER, DIMENSION(2) :: dsl
72  INTEGER, DIMENSION(2) :: dpf
73  INTEGER, DIMENSION(2) :: dpl
74  INTEGER, DIMENSION(2) :: dhs
75  INTEGER, DIMENSION(2) :: dhe
76
77  INTEGER :: dynhist_domain_id
78  INTEGER :: dynhistv_domain_id
79  INTEGER :: dynhistu_domain_id
80
81  IF (adjust) return
82
83
84  !  Initialisations
85
86  pi = 4. * atan (1.)
87
88  !  Appel a histbeg: creation du fichier netcdf et initialisations diverses
89  !
90
91  zan = anne0
92  dayref = day0
93  CALL ymds2ju(zan, 1, dayref, 0.0, zjulian)
94  tau0 = itau_dyn
95
96  DO jj = 1, jjp1
97    DO ii = 1, iip1
98      rlong(ii, jj) = rlonv(ii) * 180. / pi
99      rlat(ii, jj) = rlatu(jj) * 180. / pi
100    enddo
101  enddo
102
103
104  ! Creation de 3 fichiers pour les differentes grilles horizontales
105  ! Restriction de IOIPSL: seulement 2 coordonnees dans le meme fichier
106  ! Grille Scalaire
107
108  jjb = jj_begin
109  jje = jj_end
110  jjn = jj_nb
111
112  ddid = (/ 1, 2 /)
113  dsg = (/ iip1, jjp1 /)
114  dsl = (/ iip1, jjn /)
115  dpf = (/ 1, jjb /)
116  dpl = (/ iip1, jje /)
117  dhs = (/ 0, 0 /)
118  dhe = (/ 0, 0 /)
119
120  CALL flio_dom_set(mpi_size, mpi_rank, ddid, dsg, dsl, dpf, dpl, dhs, dhe, &
121          'box', dynhist_domain_id)
122
123  CALL histbeg(dynhist_file, iip1, rlong(:, 1), jjn, &
124          rlat(1, jjb:jje), 1, iip1, 1, jjn, tau0, &
125          zjulian, tstep, thoriid, &
126          histid, dynhist_domain_id)
127
128
129  !  Creation du fichier histoire pour les grilles en V et U (oblige pour l'instant,
130  !  IOIPSL ne permet pas de grilles avec des nombres de point differents dans
131  !  un meme fichier)
132  ! Grille V
133
134  jjb = jj_begin
135  jje = jj_end
136  jjn = jj_nb
137  IF (pole_sud) jjn = jjn - 1
138  IF (pole_sud) jje = jje - 1
139
140  DO jj = jjb, jje
141    DO ii = 1, iip1
142      rlong(ii, jj) = rlonv(ii) * 180. / pi
143      rlat(ii, jj) = rlatv(jj) * 180. / pi
144    enddo
145  enddo
146
147  ddid = (/ 1, 2 /)
148  dsg = (/ iip1, jjm /)
149  dsl = (/ iip1, jjn /)
150  dpf = (/ 1, jjb /)
151  dpl = (/ iip1, jje /)
152  dhs = (/ 0, 0 /)
153  dhe = (/ 0, 0 /)
154
155  CALL flio_dom_set(mpi_size, mpi_rank, ddid, dsg, dsl, dpf, dpl, dhs, dhe, &
156          'box', dynhistv_domain_id)
157
158  CALL histbeg(dynhistv_file, iip1, rlong(:, 1), jjn, &
159          rlat(1, jjb:jje), 1, iip1, 1, jjn, tau0, &
160          zjulian, tstep, vhoriid, &
161          histvid, dynhistv_domain_id)
162
163  ! Grille U
164
165  DO jj = 1, jjp1
166    DO ii = 1, iip1
167      rlong(ii, jj) = rlonu(ii) * 180. / pi
168      rlat(ii, jj) = rlatu(jj) * 180. / pi
169    enddo
170  enddo
171
172  jjb = jj_begin
173  jje = jj_end
174  jjn = jj_nb
175
176  ddid = (/ 1, 2 /)
177  dsg = (/ iip1, jjp1 /)
178  dsl = (/ iip1, jjn /)
179  dpf = (/ 1, jjb /)
180  dpl = (/ iip1, jje /)
181  dhs = (/ 0, 0 /)
182  dhe = (/ 0, 0 /)
183
184  CALL flio_dom_set(mpi_size, mpi_rank, ddid, dsg, dsl, dpf, dpl, dhs, dhe, &
185          'box', dynhistu_domain_id)
186
187  CALL histbeg(dynhistu_file, iip1, rlong(:, 1), jjn, &
188          rlat(1, jjb:jje), 1, iip1, 1, jjn, tau0, &
189          zjulian, tstep, uhoriid, &
190          histuid, dynhistu_domain_id)
191
192
193  ! -------------------------------------------------------------
194  !  Appel a histvert pour la grille verticale
195  ! -------------------------------------------------------------
196  CALL histvert(histid, 'presnivs', 'Niveaux pression', 'mb', &
197          llm, presnivs / 100., zvertiid, 'down')
198  CALL histvert(histvid, 'presnivs', 'Niveaux pression', 'mb', &
199          llm, presnivs / 100., zvertiidv, 'down')
200  CALL histvert(histuid, 'presnivs', 'Niveaux pression', 'mb', &
201          llm, presnivs / 100., zvertiidu, 'down')
202
203
204  ! -------------------------------------------------------------
205  !  Appels a histdef pour la definition des variables a sauvegarder
206  ! -------------------------------------------------------------
207
208  !  Vents U
209
210  jjn = jj_nb
211  CALL histdef(histuid, 'u', 'vent u', &
212          'm/s', iip1, jjn, uhoriid, llm, 1, llm, zvertiidu, &
213          32, 'inst(X)', t_ops, t_wrt)
214
215
216  !  Vents V
217
218  IF (pole_sud) jjn = jj_nb - 1
219  CALL histdef(histvid, 'v', 'vent v', &
220          'm/s', iip1, jjn, vhoriid, llm, 1, llm, zvertiidv, &
221          32, 'inst(X)', t_ops, t_wrt)
222
223
224  !  Temperature
225
226  jjn = jj_nb
227  CALL histdef(histid, 'temp', 'temperature', 'K', &
228          iip1, jjn, thoriid, llm, 1, llm, zvertiid, &
229          32, 'inst(X)', t_ops, t_wrt)
230
231  !  Temperature potentielle
232
233  CALL histdef(histid, 'theta', 'temperature potentielle', 'K', &
234          iip1, jjn, thoriid, llm, 1, llm, zvertiid, &
235          32, 'inst(X)', t_ops, t_wrt)
236
237
238
239  !  Geopotentiel
240
241  CALL histdef(histid, 'phi', 'geopotentiel', '-', &
242          iip1, jjn, thoriid, llm, 1, llm, zvertiid, &
243          32, 'inst(X)', t_ops, t_wrt)
244
245  !  Traceurs
246
247  !    DO iq=1,nqtot
248  !      CALL histdef(histid, tracers(iq)%name,
249  ! .             tracers(iq)%longName, '-',
250  ! .             iip1, jjn, thoriid, llm, 1, llm, zvertiid,
251  ! .             32, 'inst(X)', t_ops, t_wrt)
252  !    enddo
253
254  !  Masse
255
256  CALL histdef(histid, 'masse', 'masse', 'kg', &
257          iip1, jjn, thoriid, llm, 1, llm, zvertiid, &
258          32, 'inst(X)', t_ops, t_wrt)
259
260  !  Pression au sol
261
262  CALL histdef(histid, 'ps', 'pression naturelle au sol', 'Pa', &
263          iip1, jjn, thoriid, 1, 1, 1, -99, &
264          32, 'inst(X)', t_ops, t_wrt)
265
266  !  Geopotentiel au sol
267
268  !  CALL histdef(histid, 'phis', 'geopotentiel au sol', '-',
269  ! .             iip1, jjn, thoriid, 1, 1, 1, -99,
270  ! .             32, 'inst(X)', t_ops, t_wrt)
271
272  !  Fin
273
274  CALL histend(histid)
275  CALL histend(histuid)
276  CALL histend(histvid)
277END SUBROUTINE  inithist_loc
Note: See TracBrowser for help on using the repository browser.