source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/inithist.F90 @ 5186

Last change on this file since 5186 was 5182, checked in by abarral, 10 days ago

(WIP) Replace REPROBUS CPP KEY by logical
properly name modules

  • 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.1 KB
RevLine 
[1279]1! $Id: inithist.F90 5182 2024-09-10 14:25:29Z abarral $
[5099]2
[5103]3SUBROUTINE inithist(day0, anne0, tstep, t_ops, t_wrt)
[524]4
[5114]5  USE IOIPSL
[5182]6  USE lmdz_infotrac, ONLY: nqtot
[5114]7  USE com_io_dyn_mod, ONLY: histid, histvid, histuid, &
[5101]8          dynhist_file, dynhistv_file, dynhistu_file
9  USE comconst_mod, ONLY: pi
10  USE comvert_mod, ONLY: presnivs
11  USE temps_mod, ONLY: itau_dyn
[5114]12  USE lmdz_description, ONLY: descript
[5118]13  USE lmdz_iniprint, ONLY: lunout, prt_level
[5136]14  USE lmdz_comgeom
[524]15
[5159]16  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
17  USE lmdz_paramet
[5113]18  IMPLICIT NONE
[524]19
[5159]20
[5101]21  !   Routine d'initialisation des ecritures des fichiers histoires LMDZ
22  !   au format IOIPSL
[5159]23
[5101]24  !   Appels succesifs des routines: histbeg
25  !                              histhori
26  !                              histver
27  !                              histdef
28  !                              histend
[5159]29
[5101]30  !   Entree:
[5159]31
[5101]32  !  infile: nom du fichier histoire a creer
33  !  day0,anne0: date de reference
34  !  tstep: duree du pas de temps en seconde
35  !  t_ops: frequence de l'operation pour IOIPSL
36  !  t_wrt: frequence d'ecriture sur le fichier
37  !  nq: nombre de traceurs
[5159]38
39
[5101]40  !   L. Fairhead, LMD, 03/99
[5159]41
[5101]42  ! =====================================================================
[5159]43
[5101]44  !   Declarations
[524]45
[5159]46
47
[5101]48  !   Arguments
[5159]49
[5116]50  INTEGER :: day0, anne0
51  REAL :: tstep, t_ops, t_wrt
[5101]52
53  ! This routine needs IOIPSL to work
54  !   Variables locales
[5159]55
[5116]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
[5159]63
[5101]64  !  Initialisations
[5159]65
[5101]66  pi = 4. * atan (1.)
[5159]67
[5101]68  !  Appel a histbeg: creation du fichier netcdf et initialisations diverses
69  !
[524]70
[5101]71  zan = anne0
72  dayref = day0
73  CALL ymds2ju(zan, 1, dayref, 0.0, zjulian)
74  tau0 = itau_dyn
[524]75
[5101]76  ! -------------------------------------------------------------
77  ! Creation des 3 fichiers pour les grilles horizontales U,V,Scal
78  ! -------------------------------------------------------------
79  !Grille U
[5158]80  DO jj = 1, jjp1
81    DO ii = 1, iip1
[5114]82      rlong(ii, jj) = rlonu(ii) * 180. / pi
83      rlat(ii, jj) = rlatu(jj) * 180. / pi
[5101]84    enddo
85  enddo
[524]86
[5114]87  CALL histbeg(dynhistu_file, iip1, rlong(:, 1), jjp1, rlat(1, :), &
88          1, iip1, 1, jjp1, &
89          tau0, zjulian, tstep, uhoriid, histuid)
[1403]90
[5101]91  ! Grille V
[5158]92  DO jj = 1, jjm
93    DO ii = 1, iip1
[5114]94      rlong(ii, jj) = rlonv(ii) * 180. / pi
95      rlat(ii, jj) = rlatv(jj) * 180. / pi
[5101]96    enddo
97  enddo
[524]98
[5114]99  CALL histbeg(dynhistv_file, iip1, rlong(:, 1), jjm, rlat(1, :), &
100          1, iip1, 1, jjm, &
101          tau0, zjulian, tstep, vhoriid, histvid)
[524]102
[5101]103  !Grille Scalaire
[5158]104  DO jj = 1, jjp1
105    DO ii = 1, iip1
[5114]106      rlong(ii, jj) = rlonv(ii) * 180. / pi
107      rlat(ii, jj) = rlatu(jj) * 180. / pi
[5101]108    enddo
109  enddo
[5099]110
[5114]111  CALL histbeg(dynhist_file, iip1, rlong(:, 1), jjp1, rlat(1, :), &
112          1, iip1, 1, jjp1, &
113          tau0, zjulian, tstep, thoriid, histid)
[5101]114  ! -------------------------------------------------------------
115  !  Appel a histvert pour la grille verticale
116  ! -------------------------------------------------------------
[5114]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')
[5159]123
[5101]124  ! -------------------------------------------------------------
125  !  Appels a histdef pour la definition des variables a sauvegarder
126  ! -------------------------------------------------------------
[5159]127
[5101]128  !  Vents U
[5159]129
[5101]130  CALL histdef(histuid, 'u', 'vent u', 'm/s', &
[5114]131          iip1, jjp1, uhoriid, llm, 1, llm, zvertiid, &
132          32, 'inst(X)', t_ops, t_wrt)
[5159]133
[5101]134  !  Vents V
[5159]135
[5101]136  CALL histdef(histvid, 'v', 'vent v', 'm/s', &
[5114]137          iip1, jjm, vhoriid, llm, 1, llm, zvertiid, &
138          32, 'inst(X)', t_ops, t_wrt)
[5101]139
[5159]140
[5101]141  !  Temperature potentielle
[5159]142
[5101]143  CALL histdef(histid, 'teta', 'temperature potentielle', '-', &
[5114]144          iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
145          32, 'inst(X)', t_ops, t_wrt)
[5159]146
[5101]147  !  Geopotentiel
[5159]148
[5101]149  CALL histdef(histid, 'phi', 'geopotentiel', '-', &
[5114]150          iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
151          32, 'inst(X)', t_ops, t_wrt)
[5159]152
[5101]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
[5159]164
[5101]165  CALL histdef(histid, 'masse', 'masse', 'kg', &
[5114]166          iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
167          32, 'inst(X)', t_ops, t_wrt)
[5159]168
[5101]169  !  Pression au sol
[5159]170
[5101]171  CALL histdef(histid, 'ps', 'pression naturelle au sol', 'Pa', &
[5114]172          iip1, jjp1, thoriid, 1, 1, 1, -99, &
173          32, 'inst(X)', t_ops, t_wrt)
[5159]174
[5101]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
[5159]182
[5101]183  CALL histend(histid)
184  CALL histend(histuid)
185  CALL histend(histvid)
[5103]186END SUBROUTINE  inithist
Note: See TracBrowser for help on using the repository browser.