source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/writedynav.F90 @ 5159

Last change on this file since 5159 was 5159, checked in by abarral, 3 months ago

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