LMDZ
writedynav_loc.F
Go to the documentation of this file.
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
15  implicit none
16 
17 C
18 C Ecriture du fichier histoire au format IOIPSL
19 C
20 C Appels succesifs des routines: histwrite
21 C
22 C Entree:
23 C histid: ID du fichier histoire
24 C time: temps de l'ecriture
25 C vcov: vents v covariants
26 C ucov: vents u covariants
27 C teta: temperature potentielle
28 C phi : geopotentiel instantane
29 C q : traceurs
30 C masse: masse
31 C ps :pression au sol
32 C phis : geopotentiel au sol
33 C
34 C
35 C Sortie:
36 C fileid: ID du fichier netcdf cree
37 C
38 C L. Fairhead, LMD, 03/99
39 C
40 C =====================================================================
41 C
42 C Declarations
43 #include "dimensions.h"
44 #include "paramet.h"
45 #include "comconst.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 
55 C
56 C Arguments
57 C
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
70 C Variables locales
71 C
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 
82 C
83 C Initialisations
84 C
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_u:ije_u,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 
107 C Passage aux composantes naturelles du vent
108  call covnat_loc(llm, ucov, vcov, unat, vnat)
109 
110 C
111 C Appels a histwrite pour l'ecriture des variables a sauvegarder
112 C
113 C Vents U
114 C
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 
126 C
127 C Vents V
128 C
129 
130 !$OMP BARRIER
131 !$OMP MASTER
132  call histwrite(histvaveid, 'v', itau_w, vnat(ijb:ije,:),
133  . iip1*jjn*llm, ndexv)
134 !$OMP END MASTER
135 
136 
137 C
138 C Temperature potentielle moyennee
139 C
140 !$OMP MASTER
141  call histwrite(histaveid, 'theta', itau_w, teta(ijb:ije,:),
142  . iip1*jjn*llm, ndexu)
143 !$OMP END MASTER
144 
145 C
146 C Temperature moyennee
147 C
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 C
164 C Geopotentiel
165 C
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 C
173 C Traceurs
174 C
175 !!$OMP MASTER
176 ! DO iq=1,nqtot
177 ! call histwrite(histaveid, ttext(iq), itau_w, q(ijb:ije,:,iq),
178 ! . iip1*jjn*llm, ndexu)
179 ! enddo
180 !!$OMP END MASTER
181 
182 
183 C
184 C Masse
185 C
186 !$OMP MASTER
187  call histwrite(histaveid, 'masse', itau_w, masse(ijb:ije,:),
188  . iip1*jjn, ndexu)
189 !$OMP END MASTER
190 
191 
192 C
193 C Pression au sol
194 C
195 !$OMP MASTER
196 
197  call histwrite(histaveid, 'ps', itau_w, ps(ijb:ije),
198  . iip1*jjn, ndex2d)
199 !$OMP END MASTER
200 
201 C
202 C Geopotentiel au sol
203 C
204 !$OMP MASTER
205  call histwrite(histaveid, 'phis', itau_w, phis(ijb:ije),
206  . iip1*jjn, ndexu)
207 !$OMP END MASTER
208 
209 C
210 C Fin
211 C
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 #else
220  write(lunout,*)'writedynav_p: Needs IOIPSL to function'
221 #endif
222 ! #endif of #ifdef CPP_IOIPSL
223  return
224  end
!$Id && itau_dyn
Definition: temps.h:15
character(len=23), dimension(:), allocatable, save ttext
Definition: infotrac.F90:19
integer, save ij_end
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga u_toga vq_toga w_prof vq_prof llm day day1 day day1 *dt_dice endif!time annee_ref dt_dice swup_dice vg_dice omega_dice tg_prof vg_profd w_profd omega_profd!do llm!print llm l llm
integer, save nqtot
Definition: infotrac.F90:6
integer, save ijb_v
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
Definition: calcul_STDlev.h:26
subroutine writedynav_loc(time, vcov, ucov, teta, ppk, phi, q, masse, ps, phis)
Definition: writedynav_loc.F:6
!$Id mode_top_bound COMMON comconstr cpp
Definition: comconst.h:7
!$Id ***************************************!ECRITURE DU phis
Definition: write_histrac.h:9
integer, save jj_nb
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
integer, save ij_begin
integer, save ije_v
integer, save ijnb_v
subroutine covnat_loc(klevel, ucov, vcov, unat, vnat)
Definition: covnat_loc.F:5
logical, save adjust
Definition: misc_mod.F90:3
integer, save ije_u
integer, save ijnb_u
!$Header!gestion des impressions de sorties et de débogage la sortie standard prt_level COMMON comprint lunout
Definition: iniprint.h:7
integer, save ijb_u