source: LMDZ6/trunk/libf/dyn3d_common/writehist.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: 2.7 KB
Line 
1!
2! $Id: writehist.f90 5272 2024-10-24 15:53:15Z abarral $
3!
4subroutine writehist(time,vcov,ucov,teta,phi,q,masse,ps,phis)
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 dimensions_mod, ONLY: iim, jjm, llm, ndm
10USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
11          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
12implicit 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
37  include "comgeom.h"
38  include "description.h"
39  include "iniprint.h"
40
41  !
42  !   Arguments
43  !
44
45  REAL :: vcov(ip1jm,llm),ucov(ip1jmp1,llm)
46  REAL :: teta(ip1jmp1,llm),phi(ip1jmp1,llm)
47  REAL :: ps(ip1jmp1),masse(ip1jmp1,llm)
48  REAL :: phis(ip1jmp1)
49  REAL :: q(ip1jmp1,llm,nqtot)
50  integer :: time
51
52
53  ! This routine needs IOIPSL to work
54  !   Variables locales
55  !
56  integer :: iq, ii, ll
57  integer :: ndexu(ip1jmp1*llm),ndexv(ip1jm*llm),ndex2d(ip1jmp1)
58  logical :: ok_sync
59  integer :: itau_w
60  REAL :: vnat(ip1jm,llm),unat(ip1jmp1,llm)
61
62  !
63  !  Initialisations
64  !
65  ndexu = 0
66  ndexv = 0
67  ndex2d = 0
68  ok_sync =.TRUE.
69  itau_w = itau_dyn + time
70  !  Passage aux composantes naturelles du vent
71  call covnat(llm, ucov, vcov, unat, vnat)
72  !
73  !  Appels a histwrite pour l'ecriture des variables a sauvegarder
74  !
75  !  Vents U
76  !
77  call histwrite(histuid, 'u', itau_w, unat, &
78        iip1*jjp1*llm, ndexu)
79  !
80  !  Vents V
81  !
82  call histwrite(histvid, 'v', itau_w, vnat, &
83        iip1*jjm*llm, ndexv)
84
85  !
86  !  Temperature potentielle
87  !
88  call histwrite(histid, 'teta', itau_w, teta, &
89        iip1*jjp1*llm, ndexu)
90  !
91  !  Geopotentiel
92  !
93  call histwrite(histid, 'phi', itau_w, phi, &
94        iip1*jjp1*llm, ndexu)
95  !
96  !  Traceurs
97  !
98  !    DO iq=1,nqtot
99  !      call histwrite(histid, tracers(iq)%longName, itau_w,
100  ! .                   q(:,:,iq), iip1*jjp1*llm, ndexu)
101  !    enddo
102  !C
103  !  Masse
104  !
105  call histwrite(histid,'masse',itau_w, masse,iip1*jjp1*llm,ndexu)
106  !
107  !  Pression au sol
108  !
109  call histwrite(histid, 'ps', itau_w, ps, iip1*jjp1, ndex2d)
110  !
111  !  Geopotentiel au sol
112  !
113  !  call histwrite(histid, 'phis', itau_w, phis, iip1*jjp1, ndex2d)
114  !
115  !  Fin
116  !
117  if (ok_sync) then
118    call histsync(histid)
119    call histsync(histvid)
120    call histsync(histuid)
121  endif
122
123
124  return
125end subroutine writehist
Note: See TracBrowser for help on using the repository browser.