source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/initfluxsto.f90 @ 5116

Last change on this file since 5116 was 5116, checked in by abarral, 2 months ago

rename modules properly lmdz_*
move ismin, ismax, minmax into new lmdz_libmath.f90
(lint) uppercase fortran keywords

  • 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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.6 KB
Line 
1! $Id: initfluxsto.f90 5116 2024-07-24 12:54:37Z abarral $
2
3SUBROUTINE initfluxsto &
4        (infile, tstep, t_ops, t_wrt, &
5        fileid, filevid, filedid)
6
7  USE IOIPSL
8  USE comconst_mod, ONLY: pi
9  USE comvert_mod, ONLY: nivsigs
10  USE temps_mod, ONLY: annee_ref, day_ref, itau_dyn
11  USE lmdz_description, ONLY: descript
12
13  IMPLICIT NONE
14
15  !
16  !   Routine d'initialisation des ecritures des fichiers histoires LMDZ
17  !   au format IOIPSL
18  !
19  !   Appels succesifs des routines: histbeg
20  !                              histhori
21  !                              histver
22  !                              histdef
23  !                              histend
24  !
25  !   Entree:
26  !
27  !  infile: nom du fichier histoire a creer
28  !  day0,anne0: date de reference
29  !  tstep: duree du pas de temps en seconde
30  !  t_ops: frequence de l'operation pour IOIPSL
31  !  t_wrt: frequence d'ecriture sur le fichier
32  !
33  !   Sortie:
34  !  fileid: ID du fichier netcdf cree
35  !  filevid:ID du fichier netcdf pour la grille v
36  !
37  !   L. Fairhead, LMD, 03/99
38  !
39  ! =====================================================================
40  !
41  !   Declarations
42  include "dimensions.h"
43  include "paramet.h"
44  include "comgeom.h"
45  include "iniprint.h"
46
47  !   Arguments
48  !
49  CHARACTER(LEN = *) :: infile
50  REAL :: tstep, t_ops, t_wrt
51  INTEGER :: fileid, filevid, filedid
52
53  ! This routine needs IOIPSL to work
54  !   Variables locales
55  !
56  REAL :: nivd(1)
57  INTEGER :: tau0
58  REAL :: zjulian
59  CHARACTER(LEN = 3) :: str
60  CHARACTER(LEN = 10) :: ctrac
61  INTEGER :: iq
62  REAL :: rlong(iip1, jjp1), rlat(iip1, jjp1), rl(1, 1)
63  INTEGER :: uhoriid, vhoriid, thoriid, zvertiid, dhoriid, dvertiid
64  INTEGER :: ii, jj
65  INTEGER :: zan, idayref
66  logical :: ok_sync
67  !
68  !  Initialisations
69  !
70  pi = 4. * atan (1.)
71  str = 'q  '
72  ctrac = 'traceur   '
73  ok_sync = .TRUE.
74  !
75  !  Appel a histbeg: creation du fichier netcdf et initialisations diverses
76  !
77
78  zan = annee_ref
79  idayref = day_ref
80  CALL ymds2ju(zan, 1, idayref, 0.0, zjulian)
81  tau0 = itau_dyn
82
83  do jj = 1, jjp1
84    do ii = 1, iip1
85      rlong(ii, jj) = rlonu(ii) * 180. / pi
86      rlat(ii, jj) = rlatu(jj) * 180. / pi
87    enddo
88  enddo
89
90  CALL histbeg(infile, iip1, rlong(:, 1), jjp1, rlat(1, :), &
91          1, iip1, 1, jjp1, &
92          tau0, zjulian, tstep, uhoriid, fileid)
93  !
94  !  Creation du fichier histoire pour la grille en V (oblige pour l'instant,
95  !  IOIPSL ne permet pas de grilles avec des nombres de point differents dans
96  !  un meme fichier)
97
98  do jj = 1, jjm
99    do ii = 1, iip1
100      rlong(ii, jj) = rlonv(ii) * 180. / pi
101      rlat(ii, jj) = rlatv(jj) * 180. / pi
102    enddo
103  enddo
104
105  CALL histbeg('fluxstokev.nc', iip1, rlong(:, 1), jjm, rlat(1, :), &
106          1, iip1, 1, jjm, &
107          tau0, zjulian, tstep, vhoriid, filevid)
108
109  rl(1, 1) = 1.
110  CALL histbeg('defstoke.nc', 1, rl, 1, rl, &
111          1, 1, 1, 1, &
112          tau0, zjulian, tstep, dhoriid, filedid)
113
114  !
115  !  Appel a histhori pour rajouter les autres grilles horizontales
116  !
117  do jj = 1, jjp1
118    do ii = 1, iip1
119      rlong(ii, jj) = rlonv(ii) * 180. / pi
120      rlat(ii, jj) = rlatu(jj) * 180. / pi
121    enddo
122  enddo
123
124  CALL histhori(fileid, iip1, rlong, jjp1, rlat, 'scalar', &
125          'Grille points scalaires', thoriid)
126
127  !
128  !  Appel a histvert pour la grille verticale
129  !
130  CALL histvert(fileid, 'sig_s', 'Niveaux sigma', &
131          'sigma_level', &
132          llm, nivsigs, zvertiid)
133  ! Pour le fichier V
134  CALL histvert(filevid, 'sig_s', 'Niveaux sigma', &
135          'sigma_level', &
136          llm, nivsigs, zvertiid)
137  ! pour le fichier def
138  nivd(1) = 1
139  CALL histvert(filedid, 'sig_s', 'Niveaux sigma', &
140          'sigma_level', &
141          1, nivd, dvertiid)
142
143  !
144  !  Appels a histdef pour la definition des variables a sauvegarder
145
146  CALL histdef(fileid, "phis", "Surface geop. height", "-", &
147          iip1, jjp1, thoriid, 1, 1, 1, -99, 32, &
148          "once", t_ops, t_wrt)
149
150  CALL histdef(fileid, "aire", "Grid area", "-", &
151          iip1, jjp1, thoriid, 1, 1, 1, -99, 32, &
152          "once", t_ops, t_wrt)
153
154  CALL histdef(filedid, "dtvr", "tps dyn", "s", &
155          1, 1, dhoriid, 1, 1, 1, -99, 32, &
156          "once", t_ops, t_wrt)
157
158  CALL histdef(filedid, "istdyn", "tps stock", "s", &
159          1, 1, dhoriid, 1, 1, 1, -99, 32, &
160          "once", t_ops, t_wrt)
161
162  CALL histdef(filedid, "istphy", "tps stock phy", "s", &
163          1, 1, dhoriid, 1, 1, 1, -99, 32, &
164          "once", t_ops, t_wrt)
165
166
167  !
168  ! Masse
169  !
170  CALL histdef(fileid, 'masse', 'Masse', 'kg', &
171          iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
172          32, 'inst(X)', t_ops, t_wrt)
173  !
174  !  Pbaru
175  !
176  CALL histdef(fileid, 'pbaru', 'flx de masse zonal', 'kg m/s', &
177          iip1, jjp1, uhoriid, llm, 1, llm, zvertiid, &
178          32, 'inst(X)', t_ops, t_wrt)
179
180  !
181  !  Pbarv
182  !
183  CALL histdef(filevid, 'pbarv', 'flx de masse mer', 'kg m/s', &
184          iip1, jjm, vhoriid, llm, 1, llm, zvertiid, &
185          32, 'inst(X)', t_ops, t_wrt)
186  !
187  !  w
188  !
189  CALL histdef(fileid, 'w', 'flx de masse vert', 'kg m/s', &
190          iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
191          32, 'inst(X)', t_ops, t_wrt)
192
193  !
194  !  Temperature potentielle
195  !
196  CALL histdef(fileid, 'teta', 'temperature potentielle', '-', &
197          iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
198          32, 'inst(X)', t_ops, t_wrt)
199  !
200
201  !
202  ! Geopotentiel
203  !
204  CALL histdef(fileid, 'phi', 'geopotentiel instantane', '-', &
205          iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
206          32, 'inst(X)', t_ops, t_wrt)
207  !
208  !  Fin
209  !
210  CALL histend(fileid)
211  CALL histend(filevid)
212  CALL histend(filedid)
213  if (ok_sync) THEN
214    CALL histsync(fileid)
215    CALL histsync(filevid)
216    CALL histsync(filedid)
217  endif
218
219  RETURN
220END SUBROUTINE initfluxsto
Note: See TracBrowser for help on using the repository browser.