source: LMDZ5/trunk/libf/dyn3dmem/writedynav_loc.F @ 2602

Last change on this file since 2602 was 2601, checked in by Ehouarn Millour, 8 years ago

Cleanup in the dynamics: turn temps.h into module temps_mod.F90
EM

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