source: LMDZ6/trunk/libf/dyn3dmem/writehist_loc.f90 @ 5271

Last change on this file since 5271 was 5271, checked in by abarral, 26 hours ago

Move dimensions.h into a module
Nb: doesn't compile yet

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