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

Last change on this file was 5272, checked in by abarral, 27 hours ago

Turn paramet.h into a module

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