source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/lmdz_writehist.f90 @ 5209

Last change on this file since 5209 was 5192, checked in by abarral, 4 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: 2.8 KB
Line 
1MODULE lmdz_writehist
2  IMPLICIT NONE; PRIVATE
3  PUBLIC writehist
4
5CONTAINS
6
7  SUBROUTINE writehist(time, vcov, ucov, teta, phi, q, masse, ps, phis)
8
9    USE ioipsl
10    USE lmdz_infotrac, ONLY: nqtot
11    USE com_io_dyn_mod, ONLY: histid, histvid, histuid
12    USE temps_mod, ONLY: itau_dyn
13    USE lmdz_iniprint, ONLY: lunout, prt_level
14    USE lmdz_comgeom
15
16    USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
17    USE lmdz_paramet
18    USE lmdz_covnat, ONLY: covnat
19
20    IMPLICIT NONE
21
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
39    !   L. Fairhead, LMD, 03/99
40
41    ! =====================================================================
42
43    !   Declarations
44
45
46
47
48    !   Arguments
49    !
50
51    REAL :: vcov(ip1jm, llm), ucov(ip1jmp1, llm)
52    REAL :: teta(ip1jmp1, llm), phi(ip1jmp1, llm)
53    REAL :: ps(ip1jmp1), masse(ip1jmp1, llm)
54    REAL :: phis(ip1jmp1)
55    REAL :: q(ip1jmp1, llm, nqtot)
56    INTEGER :: time
57
58
59    ! This routine needs IOIPSL to work
60    !   Variables locales
61
62    INTEGER :: iq, ii, ll
63    INTEGER :: ndexu(ip1jmp1 * llm), ndexv(ip1jm * llm), ndex2d(ip1jmp1)
64    LOGICAL :: ok_sync
65    INTEGER :: itau_w
66    REAL :: vnat(ip1jm, llm), unat(ip1jmp1, llm)
67
68
69    !  Initialisations
70
71    ndexu = 0
72    ndexv = 0
73    ndex2d = 0
74    ok_sync = .TRUE.
75    itau_w = itau_dyn + time
76    !  Passage aux composantes naturelles du vent
77    CALL covnat(llm, ucov, vcov, unat, vnat)
78
79    !  Appels a histwrite pour l'ecriture des variables a sauvegarder
80
81    !  Vents U
82
83    CALL histwrite(histuid, 'u', itau_w, unat, &
84            iip1 * jjp1 * llm, ndexu)
85
86    !  Vents V
87
88    CALL histwrite(histvid, 'v', itau_w, vnat, &
89            iip1 * jjm * llm, ndexv)
90
91
92    !  Temperature potentielle
93
94    CALL histwrite(histid, 'teta', itau_w, teta, &
95            iip1 * jjp1 * llm, ndexu)
96
97    !  Geopotentiel
98
99    CALL histwrite(histid, 'phi', itau_w, phi, &
100            iip1 * jjp1 * llm, ndexu)
101
102    !  Traceurs
103
104    !    DO iq=1,nqtot
105    !      CALL histwrite(histid, tracers(iq)%longName, itau_w,
106    ! .                   q(:,:,iq), iip1*jjp1*llm, ndexu)
107    !    enddo
108    !C
109    !  Masse
110
111    CALL histwrite(histid, 'masse', itau_w, masse, iip1 * jjp1 * llm, ndexu)
112
113    !  Pression au sol
114
115    CALL histwrite(histid, 'ps', itau_w, ps, iip1 * jjp1, ndex2d)
116
117    !  Geopotentiel au sol
118
119    !  CALL histwrite(histid, 'phis', itau_w, phis, iip1*jjp1, ndex2d)
120
121    !  Fin
122
123    IF (ok_sync) THEN
124      CALL histsync(histid)
125      CALL histsync(histvid)
126      CALL histsync(histuid)
127    ENDIF
128    RETURN
129  END SUBROUTINE writehist
130
131
132END MODULE lmdz_writehist
Note: See TracBrowser for help on using the repository browser.