source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/writehist_loc.f90 @ 5185

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

(WIP) Replace REPROBUS CPP KEY by logical
properly name 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
File size: 4.3 KB
Line 
1! $Id: writedynav_p.F 1279 2009-12-10 09:02:56Z fairhead $
2
3SUBROUTINE writehist_loc(time, vcov, ucov, teta, ppk, phi, q, masse, ps, phis)
4  USE ioipsl
5  USE parallel_lmdz
6  USE misc_mod
7  USE lmdz_infotrac, ONLY: nqtot
8  USE com_io_dyn_mod, ONLY: histid, histvid, histuid
9  USE comconst_mod, ONLY: cpp
10  USE temps_mod, ONLY: itau_dyn
11  USE lmdz_description, ONLY: descript
12  USE lmdz_iniprint, ONLY: lunout, prt_level
13  USE lmdz_comgeom
14
15  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
16  USE lmdz_paramet
17  IMPLICIT NONE
18
19
20  !   Ecriture du fichier histoire au format IOIPSL
21
22  !   Appels succesifs des routines: histwrite
23
24  !   Entree:
25  !  histid: ID du fichier histoire
26  !  time: temps de l'ecriture
27  !  vcov: vents v covariants
28  !  ucov: vents u covariants
29  !  teta: temperature potentielle
30  !  phi : geopotentiel instantane
31  !  q   : traceurs
32  !  masse: masse
33  !  ps   :pression au sol
34  !  phis : geopotentiel au sol
35
36
37  !   Sortie:
38  !  fileid: ID du fichier netcdf cree
39
40  !   L. Fairhead, LMD, 03/99
41
42  ! =====================================================================
43
44  !   Declarations
45
46
47
48
49  !   Arguments
50  !
51
52  REAL :: vcov(ijb_v:ije_v, llm), ucov(ijb_u:ije_u, llm)
53  REAL :: teta(ijb_u:ije_u, llm), phi(ijb_u:ije_u, llm)
54  REAL :: ppk(ijb_u:ije_u, llm)
55  REAL :: ps(ijb_u:ije_u), masse(ijb_u:ije_u, llm)
56  REAL :: phis(ijb_u:ije_u)
57  REAL :: q(ijb_u:ije_u, llm, nqtot)
58  INTEGER :: time
59
60
61  ! This routine needs IOIPSL
62  !   Variables locales
63
64  INTEGER, SAVE, ALLOCATABLE :: ndex2d(:), ndexu(:), ndexv(:)
65  INTEGER :: iq, ii, ll
66  REAL, SAVE, ALLOCATABLE :: tm(:, :)
67  REAL, SAVE, ALLOCATABLE :: vnat(:, :), unat(:, :)
68  LOGICAL :: ok_sync
69  INTEGER :: itau_w
70  INTEGER :: ijb, ije, jjn
71  LOGICAL, SAVE :: first = .TRUE.
72  !$OMP THREADPRIVATE(first)
73
74
75  !  Initialisations
76
77  IF (adjust) return
78
79  IF (first) THEN
80    !$OMP BARRIER
81    !$OMP MASTER
82    ALLOCATE(unat(ijb_u:ije_u, llm))
83    ALLOCATE(vnat(ijb_v:ije_v, llm))
84    ALLOCATE(tm(ijb_u:ije_u, llm))
85    ALLOCATE(ndex2d(ijnb_u * llm))
86    ALLOCATE(ndexu(ijnb_u * llm))
87    ALLOCATE(ndexv(ijnb_v * llm))
88    ndex2d = 0
89    ndexu = 0
90    ndexv = 0
91    !$OMP END MASTER
92    !$OMP BARRIER
93    first = .FALSE.
94  ENDIF
95
96  ok_sync = .TRUE.
97  itau_w = itau_dyn + time
98
99  ! Passage aux composantes naturelles du vent
100  CALL covnat_loc(llm, ucov, vcov, unat, vnat)
101
102
103  !  Appels a histwrite pour l'ecriture des variables a sauvegarder
104
105  !  Vents U
106  !
107
108  !$OMP BARRIER
109  !$OMP MASTER
110  ijb = ij_begin
111  ije = ij_end
112  jjn = jj_nb
113
114  CALL histwrite(histuid, 'u', itau_w, unat(ijb:ije, :), &
115          iip1 * jjn * llm, ndexu)
116  !$OMP END MASTER
117
118
119  !  Vents V
120
121  ije = ij_end
122  IF (pole_sud) jjn = jj_nb - 1
123  IF (pole_sud) ije = ij_end - iip1
124  !$OMP BARRIER
125  !$OMP MASTER
126  CALL histwrite(histvid, 'v', itau_w, vnat(ijb:ije, :), &
127          iip1 * jjn * llm, ndexv)
128  !$OMP END MASTER
129
130
131
132  !  Temperature potentielle
133
134  ijb = ij_begin
135  ije = ij_end
136  jjn = jj_nb
137  !$OMP MASTER
138  CALL histwrite(histid, 'theta', itau_w, teta(ijb:ije, :), &
139          iip1 * jjn * llm, ndexu)
140  !$OMP END MASTER
141
142
143  !  Temperature
144  !
145
146  !$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
147  DO ll = 1, llm
148    DO ii = ijb, ije
149      tm(ii, ll) = teta(ii, ll) * ppk(ii, ll) / cpp
150    enddo
151  enddo
152  !$OMP ENDDO
153
154  !$OMP MASTER
155  CALL histwrite(histid, 'temp', itau_w, tm(ijb:ije, :), &
156          iip1 * jjn * llm, ndexu)
157  !$OMP END MASTER
158
159
160
161  !  Geopotentiel
162
163  !$OMP MASTER
164  CALL histwrite(histid, 'phi', itau_w, phi(ijb:ije, :), &
165          iip1 * jjn * llm, ndexu)
166  !$OMP END MASTER
167
168
169
170  !  Traceurs
171
172  !!$OMP MASTER
173  !    DO iq=1,nqtot
174  !      CALL histwrite(histid, tracers(iq)%longName, itau_w,
175  ! .                   q(ijb:ije,:,iq), iip1*jjn*llm, ndexu)
176  !    enddo
177  !!$OMP END MASTER
178
179
180
181  !  Masse
182
183  !$OMP MASTER
184  CALL histwrite(histid, 'masse', itau_w, masse(ijb:ije, :), &
185          iip1 * jjn * llm, ndexu)
186  !$OMP END MASTER
187
188
189
190  !  Pression au sol
191
192  !$OMP MASTER
193  CALL histwrite(histid, 'ps', itau_w, ps(ijb:ije), &
194          iip1 * jjn, ndex2d)
195  !$OMP END MASTER
196
197
198  !  Geopotentiel au sol
199
200  !$OMP MASTER
201  ! CALL histwrite(histid, 'phis', itau_w, phis(ijb:ije),
202  ! .                 iip1*jjn, ndex2d)
203  !$OMP END MASTER
204
205
206  !  Fin
207
208  !$OMP MASTER
209  IF (ok_sync) THEN
210    CALL histsync(histid)
211    CALL histsync(histvid)
212    CALL histsync(histuid)
213  ENDIF
214  !$OMP END MASTER
215END SUBROUTINE writehist_loc
Note: See TracBrowser for help on using the repository browser.