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

Last change on this file since 5114 was 5114, checked in by abarral, 8 weeks ago

Rename modules in misc from *_mod > lmdz_*
Turn description.h into lmdz_description.f90

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