source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/writedynav_loc.f90 @ 5208

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

Correct r5192, some lmdz_description cases were missing

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