source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/lmdz_writedynav.f90 @ 5192

Last change on this file since 5192 was 5192, checked in by abarral, 5 days ago

Remove obsolete lmdz_description.f90
Remove unused exner_hyb_m.F90 in 1D
Re-remove filtre from source in 1D makelmdz_fcm

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