source: LMDZ6/trunk/libf/dyn3dmem/writedynav_loc.f90 @ 5300

Last change on this file since 5300 was 5285, checked in by abarral, 4 days ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

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