source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/writehist.f90 @ 5118

Last change on this file since 5118 was 5118, checked in by abarral, 8 weeks ago

Replace iniprint.h by lmdz_iniprint.f90
(lint) along the way

  • 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: 2.7 KB
Line 
1! $Id: writehist.f90 5118 2024-07-24 14:39:59Z abarral $
2
3SUBROUTINE writehist(time, vcov, ucov, teta, phi, q, masse, ps, phis)
4
5  USE ioipsl
6  USE infotrac, ONLY: nqtot
7  USE com_io_dyn_mod, ONLY: histid, histvid, histuid
8  USE temps_mod, ONLY: itau_dyn
9  USE lmdz_description, ONLY: descript
10  USE lmdz_iniprint, ONLY: lunout, prt_level
11
12  IMPLICIT NONE
13
14  !
15  !   Ecriture du fichier histoire au format IOIPSL
16  !
17  !   Appels succesifs des routines: histwrite
18  !
19  !   Entree:
20  !  time: temps de l'ecriture
21  !  vcov: vents v covariants
22  !  ucov: vents u covariants
23  !  teta: temperature potentielle
24  !  phi : geopotentiel instantane
25  !  q   : traceurs
26  !  masse: masse
27  !  ps   :pression au sol
28  !  phis : geopotentiel au sol
29  !
30  !
31  !   L. Fairhead, LMD, 03/99
32  !
33  ! =====================================================================
34  !
35  !   Declarations
36  include "dimensions.h"
37  include "paramet.h"
38  include "comgeom.h"
39
40  !
41  !   Arguments
42  !
43
44  REAL :: vcov(ip1jm, llm), ucov(ip1jmp1, llm)
45  REAL :: teta(ip1jmp1, llm), phi(ip1jmp1, llm)
46  REAL :: ps(ip1jmp1), masse(ip1jmp1, llm)
47  REAL :: phis(ip1jmp1)
48  REAL :: q(ip1jmp1, llm, nqtot)
49  INTEGER :: time
50
51
52  ! This routine needs IOIPSL to work
53  !   Variables locales
54  !
55  INTEGER :: iq, ii, ll
56  INTEGER :: ndexu(ip1jmp1 * llm), ndexv(ip1jm * llm), ndex2d(ip1jmp1)
57  LOGICAL :: ok_sync
58  INTEGER :: itau_w
59  REAL :: vnat(ip1jm, llm), unat(ip1jmp1, llm)
60
61  !
62  !  Initialisations
63  !
64  ndexu = 0
65  ndexv = 0
66  ndex2d = 0
67  ok_sync = .TRUE.
68  itau_w = itau_dyn + time
69  !  Passage aux composantes naturelles du vent
70  CALL covnat(llm, ucov, vcov, unat, vnat)
71  !
72  !  Appels a histwrite pour l'ecriture des variables a sauvegarder
73  !
74  !  Vents U
75  !
76  CALL histwrite(histuid, 'u', itau_w, unat, &
77          iip1 * jjp1 * llm, ndexu)
78  !
79  !  Vents V
80  !
81  CALL histwrite(histvid, 'v', itau_w, vnat, &
82          iip1 * jjm * llm, ndexv)
83
84  !
85  !  Temperature potentielle
86  !
87  CALL histwrite(histid, 'teta', itau_w, teta, &
88          iip1 * jjp1 * llm, ndexu)
89  !
90  !  Geopotentiel
91  !
92  CALL histwrite(histid, 'phi', itau_w, phi, &
93          iip1 * jjp1 * llm, ndexu)
94  !
95  !  Traceurs
96  !
97  !    DO iq=1,nqtot
98  !      CALL histwrite(histid, tracers(iq)%longName, itau_w,
99  ! .                   q(:,:,iq), iip1*jjp1*llm, ndexu)
100  !    enddo
101  !C
102  !  Masse
103  !
104  CALL histwrite(histid, 'masse', itau_w, masse, iip1 * jjp1 * llm, ndexu)
105  !
106  !  Pression au sol
107  !
108  CALL histwrite(histid, 'ps', itau_w, ps, iip1 * jjp1, ndex2d)
109  !
110  !  Geopotentiel au sol
111  !
112  !  CALL histwrite(histid, 'phis', itau_w, phis, iip1*jjp1, ndex2d)
113  !
114  !  Fin
115  !
116  IF (ok_sync) THEN
117    CALL histsync(histid)
118    CALL histsync(histvid)
119    CALL histsync(histuid)
120  ENDIF
121  RETURN
122END SUBROUTINE writehist
Note: See TracBrowser for help on using the repository browser.