source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/writedynav_loc.F @ 5103

Last change on this file since 5103 was 5103, checked in by abarral, 2 months ago

Handle CPP_INLANDSIS in lmdz_cppkeys_wrapper.F90
Remove obsolete key wrgrads_thermcell, _ADV_HALO, _ADV_HALLO, isminmax
Remove redundant uses of CPPKEY_INCA (thanks acozic)
Remove obsolete misc/write_field.F90
Remove unused ioipsl_* wrappers
Remove calls to WriteField_u with wrong signature
Convert .F -> .[fF]90
(lint) uppercase fortran operators
[note: 1d and iso still broken - working on it]

  • 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.6 KB
RevLine 
[5099]1
[1632]2! $Id: writedynav_p.F 1279 2009-12-10 09:02:56Z fairhead $
[5099]3
[5103]4      SUBROUTINE writedynav_loc( time, vcov, ucov,teta,ppk,phi,q,
[1632]5     .                           masse,ps,phis)
6
7! This routine needs IOIPSL
8      USE ioipsl
[1823]9      USE parallel_lmdz
[1632]10      USE misc_mod
[5101]11      USE infotrac, ONLY: nqtot
12      use com_io_dyn_mod, ONLY: histaveid,histvaveid,histuaveid
[2597]13      USE comconst_mod, ONLY: cpp
[2601]14      USE temps_mod, ONLY: itau_dyn
15     
[1632]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
[2597]44      include "dimensions.h"
45      include "paramet.h"
46      include "comgeom.h"
47      include "description.h"
48      include "iniprint.h"
[1632]49
50C
51C   Arguments
52C
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
64C   Variables locales
65C
66      INTEGER,SAVE,ALLOCATABLE :: ndex2d(:),ndexu(:),ndexv(:)
67      INTEGER :: iq, ii, ll
68      REAL,SAVE,ALLOCATABLE :: tm(:,:)
[5103]69      REAL,SAVE,ALLOCATABLE :: vnat(:,:),unat(:,:)
[1632]70      logical ok_sync
71      integer itau_w
72      integer :: ijb,ije,jjn
73      LOGICAL,SAVE :: first=.TRUE.
74!$OMP THREADPRIVATE(first)
75
76C
77C  Initialisations
78C
79      if (adjust) return
[5103]80
[1632]81      IF (first) THEN
82!$OMP BARRIER
83!$OMP MASTER
84        ALLOCATE(unat(ijb_u:ije_u,llm))
[5103]85        ALLOCATE(vnat(ijb_v:ije_v,llm))
[1632]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
[5103]97
[1632]98      ok_sync = .TRUE.
99      itau_w = itau_dyn + time
100
101C Passage aux composantes naturelles du vent
[5101]102      CALL covnat_loc(llm, ucov, vcov, unat, vnat)
[1632]103
104C
105C  Appels a histwrite pour l'ecriture des variables a sauvegarder
106C
107C  Vents U
108C
109
[5103]110!$OMP BARRIER
[1632]111!$OMP MASTER
112      ijb=ij_begin
113      ije=ij_end
114      jjn=jj_nb
[5103]115
[5101]116      CALL histwrite(histuaveid, 'u', itau_w, unat(ijb:ije,:),
[1632]117     .               iip1*jjn*llm, ndexu)
[5103]118!$OMP END MASTER
[1632]119
120C
121C  Vents V
122C
[2475]123      ije=ij_end
124      if (pole_sud) jjn=jj_nb-1
125      if (pole_sud) ije=ij_end-iip1
[1632]126!$OMP BARRIER
[5103]127!$OMP MASTER
[5101]128      CALL histwrite(histvaveid, 'v', itau_w, vnat(ijb:ije,:),
[1632]129     .               iip1*jjn*llm, ndexv)
[5103]130!$OMP END MASTER
[1632]131
132
133C
134C  Temperature potentielle moyennee
135C
[2475]136      ijb=ij_begin
137      ije=ij_end
138      jjn=jj_nb
[5103]139!$OMP MASTER
[5101]140      CALL histwrite(histaveid, 'theta', itau_w, teta(ijb:ije,:),
[1632]141     .                iip1*jjn*llm, ndexu)
[5103]142!$OMP END MASTER
[1632]143
144C
145C  Temperature moyennee
146C
147
[5103]148!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
[1632]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
[5103]156!$OMP MASTER
[5101]157      CALL histwrite(histaveid, 'temp', itau_w, tm(ijb:ije,:),
[1632]158     .                iip1*jjn*llm, ndexu)
159!$OMP END MASTER
160
161
162C
163C  Geopotentiel
164C
[5103]165!$OMP MASTER
[5101]166      CALL histwrite(histaveid, 'phi', itau_w, phi(ijb:ije,:),
[1632]167     .                iip1*jjn*llm, ndexu)
168!$OMP END MASTER
169
170
171C
172C  Traceurs
173C
[5103]174!!$OMP MASTER
[1632]175!        DO iq=1,nqtot
[5101]176!          CALL histwrite(histaveid, tracers(iq)%longName, itau_w, &
[4046]177!     .                   q(ijb:ije,:,iq), iip1*jjn*llm, ndexu)
[1632]178!        enddo
179!!$OMP END MASTER
180
181
182C
183C  Masse
184C
[5103]185!$OMP MASTER
[5101]186       CALL histwrite(histaveid, 'masse', itau_w, masse(ijb:ije,:),
[2475]187     .                iip1*jjn*llm, ndexu)
[1632]188!$OMP END MASTER
189
190
191C
192C  Pression au sol
193C
[5103]194!$OMP MASTER
[1632]195
[5101]196       CALL histwrite(histaveid, 'ps', itau_w, ps(ijb:ije),
[1632]197     .                 iip1*jjn, ndex2d)
198!$OMP END MASTER
199
200C
201C  Geopotentiel au sol
202C
[5103]203!$OMP MASTER
[5101]204!       CALL histwrite(histaveid, 'phis', itau_w, phis(ijb:ije),
[2475]205!     .                 iip1*jjn, ndex2d)
[1632]206!$OMP END MASTER
207
208C
209C  Fin
210C
[5103]211!$OMP MASTER
[1632]212      if (ok_sync) then
[5101]213          CALL histsync(histaveid)
214          CALL histsync(histvaveid)
215          CALL histsync(histuaveid)
[1632]216      ENDIF
217!$OMP END MASTER
218      end
Note: See TracBrowser for help on using the repository browser.