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

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

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