source: LMDZ6/trunk/libf/dyn3d_common/inithist.f90 @ 5282

Last change on this file since 5282 was 5282, checked in by abarral, 6 hours ago

Turn iniprint.h clesphys.h into modules
Remove unused description.h

  • 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!
2! $Id: inithist.f90 5282 2024-10-28 12:11:48Z abarral $
3!
4subroutine inithist(day0,anne0,tstep,t_ops,t_wrt)
5
6   USE iniprint_mod_h
7  USE comgeom_mod_h
8  USE IOIPSL
9   USE infotrac, ONLY : nqtot
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
16  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
17USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
18          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
19implicit none
20
21  !
22  !   Routine d'initialisation des ecritures des fichiers histoires LMDZ
23  !   au format IOIPSL
24  !
25  !   Appels succesifs des routines: histbeg
26  !                              histhori
27  !                              histver
28  !                              histdef
29  !                              histend
30  !
31  !   Entree:
32  !
33  !  infile: nom du fichier histoire a creer
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  !   Arguments
49  !
50  integer :: day0, anne0
51  real :: tstep, t_ops, t_wrt
52
53  ! This routine needs IOIPSL to work
54  !   Variables locales
55  !
56  integer :: tau0
57  real :: zjulian
58  integer :: iq
59  real :: rlong(iip1,jjp1), rlat(iip1,jjp1)
60  integer :: uhoriid, vhoriid, thoriid, zvertiid
61  integer :: ii,jj
62  integer :: zan, dayref
63  !
64  !  Initialisations
65  !
66  pi = 4. * atan (1.)
67  !
68  !  Appel a histbeg: creation du fichier netcdf et initialisations diverses
69  !
70
71  zan = anne0
72  dayref = day0
73  CALL ymds2ju(zan, 1, dayref, 0.0, zjulian)
74  tau0 = itau_dyn
75
76  ! -------------------------------------------------------------
77  ! Creation des 3 fichiers pour les grilles horizontales U,V,Scal
78  ! -------------------------------------------------------------
79  !Grille U
80  do jj = 1, jjp1
81    do ii = 1, iip1
82      rlong(ii,jj) = rlonu(ii) * 180. / pi
83      rlat(ii,jj) = rlatu(jj) * 180. / pi
84    enddo
85  enddo
86
87  call histbeg(dynhistu_file, iip1, rlong(:,1), jjp1, rlat(1,:), &
88        1, iip1, 1, jjp1, &
89        tau0, zjulian, tstep, uhoriid, histuid)
90
91  ! Grille V
92  do jj = 1, jjm
93    do ii = 1, iip1
94      rlong(ii,jj) = rlonv(ii) * 180. / pi
95      rlat(ii,jj) = rlatv(jj) * 180. / pi
96    enddo
97  enddo
98
99  call histbeg(dynhistv_file, iip1, rlong(:,1), jjm, rlat(1,:), &
100        1, iip1, 1, jjm, &
101        tau0, zjulian, tstep, vhoriid, histvid)
102
103  !Grille Scalaire
104  do jj = 1, jjp1
105    do ii = 1, iip1
106      rlong(ii,jj) = rlonv(ii) * 180. / pi
107      rlat(ii,jj) = rlatu(jj) * 180. / pi
108    enddo
109  enddo
110
111  call histbeg(dynhist_file, iip1, rlong(:,1), jjp1, rlat(1,:), &
112        1, iip1, 1, jjp1, &
113        tau0, zjulian, tstep, thoriid, histid)
114  ! -------------------------------------------------------------
115  !  Appel a histvert pour la grille verticale
116  ! -------------------------------------------------------------
117  call histvert(histid, 'presnivs', 'Niveaux pression','mb', &
118        llm, presnivs/100., zvertiid,'down')
119  call histvert(histvid, 'presnivs', 'Niveaux pression','mb', &
120        llm, presnivs/100., zvertiid,'down')
121  call histvert(histuid, 'presnivs', 'Niveaux pression','mb', &
122        llm, presnivs/100., zvertiid,'down')
123  !
124  ! -------------------------------------------------------------
125  !  Appels a histdef pour la definition des variables a sauvegarder
126  ! -------------------------------------------------------------
127  !
128  !  Vents U
129  !
130  call histdef(histuid, 'u', 'vent u', 'm/s', &
131        iip1, jjp1, uhoriid, llm, 1, llm, zvertiid, &
132        32, 'inst(X)', t_ops, t_wrt)
133  !
134  !  Vents V
135  !
136  call histdef(histvid, 'v', 'vent v', 'm/s', &
137        iip1, jjm, vhoriid, llm, 1, llm, zvertiid, &
138        32, 'inst(X)', t_ops, t_wrt)
139
140  !
141  !  Temperature potentielle
142  !
143  call histdef(histid, 'teta', 'temperature potentielle', '-', &
144        iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
145        32, 'inst(X)', t_ops, t_wrt)
146  !
147  !  Geopotentiel
148  !
149  call histdef(histid, 'phi', 'geopotentiel', '-', &
150        iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
151        32, 'inst(X)', t_ops, t_wrt)
152  !
153  !  Traceurs
154  !
155  !
156  !    DO iq=1,nqtot
157  !      call histdef(histid, tracers(iq)%name,
158  !                           tracers(iq)%longName, '-',
159  ! .             iip1, jjp1, thoriid, llm, 1, llm, zvertiid,
160  ! .             32, 'inst(X)', t_ops, t_wrt)
161  !    enddo
162  !C
163  !  Masse
164  !
165  call histdef(histid, 'masse', 'masse', 'kg', &
166        iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
167        32, 'inst(X)', t_ops, t_wrt)
168  !
169  !  Pression au sol
170  !
171  call histdef(histid, 'ps', 'pression naturelle au sol', 'Pa', &
172        iip1, jjp1, thoriid, 1, 1, 1, -99, &
173        32, 'inst(X)', t_ops, t_wrt)
174  !
175  !  Geopotentiel au sol
176  !C
177  !  call histdef(histid, 'phis', 'geopotentiel au sol', '-',
178  ! .             iip1, jjp1, thoriid, 1, 1, 1, -99,
179  ! .             32, 'inst(X)', t_ops, t_wrt)
180  !C
181  !  Fin
182  !
183  call histend(histid)
184  call histend(histuid)
185  call histend(histvid)
186
187
188  return
189end subroutine inithist
Note: See TracBrowser for help on using the repository browser.