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