source: LMDZ6/trunk/libf/dyn3d_common/initdynav.f90 @ 5272

Last change on this file since 5272 was 5272, checked in by abarral, 23 hours ago

Turn paramet.h into a module

  • 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.2 KB
Line 
1! $Id: initdynav.f90 5272 2024-10-24 15:53:15Z abarral $
2
3subroutine initdynav(day0,anne0,tstep,t_ops,t_wrt)
4
5  USE IOIPSL
6  USE infotrac, ONLY : nqtot
7  use com_io_dyn_mod, only : histaveid,histvaveid,histuaveid, &
8       dynhistave_file,dynhistvave_file,dynhistuave_file
9  USE comconst_mod, ONLY: pi
10  USE comvert_mod, ONLY: presnivs
11  USE temps_mod, ONLY: itau_dyn
12 
13  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
14USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
15          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
16implicit none
17
18
19  !   Routine d'initialisation des ecritures des fichiers histoires LMDZ
20  !   au format IOIPSL. Initialisation du fichier histoire moyenne.
21
22  !   Appels succesifs des routines: histbeg
23  !                                  histhori
24  !                                  histver
25  !                                  histdef
26  !                                  histend
27
28  !   Entree:
29
30  !      infile: nom du fichier histoire a creer
31  !      day0,anne0: date de reference
32  !      tstep : frequence d'ecriture
33  !      t_ops: frequence de l'operation pour IOIPSL
34  !      t_wrt: frequence d'ecriture sur le fichier
35
36
37  !   L. Fairhead, LMD, 03/99
38
39
40
41  include "comgeom.h"
42  include "description.h"
43  include "iniprint.h"
44
45  !   Arguments
46
47  integer day0, anne0
48  real tstep, t_ops, t_wrt
49
50  ! This routine needs IOIPSL to work
51  !   Variables locales
52
53  integer tau0
54  real zjulian
55  integer iq
56  real rlong(iip1,jjp1), rlat(iip1,jjp1)
57  integer uhoriid, vhoriid, thoriid, zvertiid
58  integer ii,jj
59  integer zan, dayref
60
61  !--------------------------------------------------------------------
62
63  !  Initialisations
64
65  pi = 4. * atan (1.)
66
67  !  Appel a histbeg: creation du fichier netcdf et initialisations diverses
68
69
70  zan = anne0
71  dayref = day0
72  CALL ymds2ju(zan, 1, dayref, 0.0, zjulian)
73  tau0 = itau_dyn
74
75  do jj = 1, jjp1
76     do ii = 1, iip1
77        rlong(ii,jj) = rlonv(ii) * 180. / pi
78        rlat(ii,jj)  = rlatu(jj) * 180. / pi
79     enddo
80  enddo
81
82  ! Creation de 3 fichiers pour les differentes grilles horizontales
83  ! Restriction de IOIPSL: seulement 2 coordonnees dans le meme fichier
84  ! Grille Scalaire
85  call histbeg(dynhistave_file, iip1, rlong(:,1), jjp1, rlat(1,:), &
86       1, iip1, 1, jjp1, &
87       tau0, zjulian, tstep, thoriid,histaveid)
88
89  ! Creation du fichier histoire pour les grilles en V et U (oblige
90  ! pour l'instant, IOIPSL ne permet pas de grilles avec des nombres
91  ! de point differents dans  un meme fichier)
92  ! Grille V
93  do jj = 1, jjm
94     do ii = 1, iip1
95        rlong(ii,jj) = rlonv(ii) * 180. / pi
96        rlat(ii,jj) = rlatv(jj) * 180. / pi
97     enddo
98  enddo
99
100  call histbeg(dynhistvave_file, iip1, rlong(:,1), jjm, rlat(1,:), &
101       1, iip1, 1, jjm, &
102       tau0, zjulian, tstep, vhoriid,histvaveid)
103  ! Grille U
104  do jj = 1, jjp1
105     do ii = 1, iip1
106        rlong(ii,jj) = rlonu(ii) * 180. / pi
107        rlat(ii,jj) = rlatu(jj) * 180. / pi
108     enddo
109  enddo
110
111  call histbeg(dynhistuave_file, iip1, rlong(:,1),jjp1, rlat(1,:), &
112       1, iip1, 1, jjp1, &
113       tau0, zjulian, tstep, uhoriid,histuaveid)
114
115  !  Appel a histvert pour la grille verticale
116
117  call histvert(histaveid,'presnivs','Niveaux Pression approximatifs','mb', &
118       llm, presnivs/100., zvertiid,'down')
119  call histvert(histuaveid,'presnivs','Niveaux Pression approximatifs','mb', &
120       llm, presnivs/100., zvertiid,'down')
121  call histvert(histvaveid,'presnivs','Niveaux Pression approximatifs','mb', &
122       llm, presnivs/100., zvertiid,'down')
123
124  !  Appels a histdef pour la definition des variables a sauvegarder
125
126  !  Vents U
127
128  call histdef(histuaveid, 'u', 'vent u moyen ', &
129       'm/s', iip1, jjp1, uhoriid, llm, 1, llm, zvertiid, &
130       32, 'ave(X)', t_ops, t_wrt)
131
132  !  Vents V
133
134  call histdef(histvaveid, 'v', 'vent v moyen', &
135       'm/s', iip1, jjm, vhoriid, llm, 1, llm, zvertiid, &
136       32, 'ave(X)', t_ops, t_wrt)
137
138
139  !  Temperature
140
141  call histdef(histaveid, 'temp', 'temperature moyenne', 'K', &
142       iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
143       32, 'ave(X)', t_ops, t_wrt)
144
145  !  Temperature potentielle
146
147  call histdef(histaveid, 'theta', 'temperature potentielle', 'K', &
148       iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
149       32, 'ave(X)', t_ops, t_wrt)
150
151  !  Geopotentiel
152
153  call histdef(histaveid, 'phi', 'geopotentiel moyen', '-', &
154       iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
155       32, 'ave(X)', t_ops, t_wrt)
156
157  !  Traceurs
158
159  !        DO iq=1,nqtot
160  !          call histdef(histaveid, tracers(iq)%name, &
161  !                                  tracers(iq)%longName, '-',  &
162  !                  iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
163  !                  32, 'ave(X)', t_ops, t_wrt)
164  !        enddo
165
166  !  Masse
167
168  call histdef(histaveid, 'masse', 'masse', 'kg', &
169       iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
170       32, 'ave(X)', t_ops, t_wrt)
171
172  !  Pression au sol
173
174  call histdef(histaveid, 'ps', 'pression naturelle au sol', 'Pa', &
175       iip1, jjp1, thoriid, 1, 1, 1, -99, &
176       32, 'ave(X)', t_ops, t_wrt)
177
178  !  Geopotentiel au sol
179
180  !      call histdef(histaveid, 'phis', 'geopotentiel au sol', '-', &
181  !                  iip1, jjp1, thoriid, 1, 1, 1, -99, &
182  !                  32, 'ave(X)', t_ops, t_wrt)
183
184  call histend(histaveid)
185  call histend(histuaveid)
186  call histend(histvaveid)
187
188
189
190end subroutine initdynav
Note: See TracBrowser for help on using the repository browser.