source: LMDZ6/trunk/libf/phylmd/cospv2/lmdz_cosp_output_write_mod.F90 @ 3723

Last change on this file since 3723 was 3723, checked in by idelkadi, 4 years ago

Debugging COSP v2 for simulators Calipso, Parasol, Cloudsat

File size: 38.7 KB
Line 
1!!!! Abderrahmane Idelkadi aout 2013 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2! Module pour definir (au 1er appel) et ecrire les variables dans les fichiers de sortie cosp
3!
4! R.Guzman jan 2019 (mise a jour pour COSPv2)
5! On change le nom du module a "lmdz_cosp_output_write_mod" et celui de la routine a "lmdz_cosp_output_write"
6! pour qu on sache qu il s agit d un module specifique a l implementation de COSP dans LMDZ
7!
8!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
9   MODULE lmdz_cosp_output_write_mod
10
11   USE lmdz_cosp_output_mod
12   USE mod_cosp_config, only : R_UNDEF, CLOUDSAT_DBZE_BINS, SR_BINS, PARASOL_NREFL, &
13                              isccp_histPresCenters,tau_binCenters, LIDAR_NTEMP, &
14                              LIDAR_PHASE_TEMP,misr_histHgtCenters,numMISRHgtBins, &
15                              numMODISReffIceBins,reffICE_binCenters, &
16                              numMODISReffLiqBins, reffLIQ_binCenters
17
18   IMPLICIT NONE
19
20   INTEGER, SAVE  :: itau_iocosp
21!$OMP THREADPRIVATE(itau_iocosp)
22   INTEGER, save        :: Nlevout, Ncolout
23!$OMP THREADPRIVATE(Nlevout, Ncolout)
24
25!  INTERFACE histwrite_cosp
26!    MODULE PROCEDURE histwrite2d_cosp,histwrite3d_cosp
27!  END INTERFACE
28
29   CONTAINS
30
31  SUBROUTINE lmdz_cosp_output_write(Nlevlmdz, Npoints, Ncolumns, itap, dtime, freq_COSP, missing_cosp, &
32                                    cfg, Nlvgrid, cospOUT)
33
34
35    USE ioipsl
36    USE time_phylmdz_mod, ONLY: itau_phy, start_time, day_step_phy
37    USE print_control_mod, ONLY: lunout,prt_level
38    USE lmdz_cosp_read_outputkeys, only: cosp_config
39!COSPv2
40  use cosp_kinds, only: wp
41  use mod_cosp,   only: cosp_outputs
42
43    USE wxios, only: wxios_closedef
44    USE xios, only: xios_update_calendar, xios_field_is_active
45  IMPLICIT NONE 
46!!! Variables d'entree
47  integer               :: itap, Nlevlmdz, Ncolumns, Npoints, Nlvgrid
48  real                  :: freq_COSP, dtime, missing_val, missing_cosp
49  type(cosp_config)     :: cfg     ! Control outputs
50  type(cosp_outputs)    :: &
51       cospOUT           ! COSP simulator outputs
52
53
54!!! Variables locales
55  integer               :: icl,k,ip
56  logical               :: ok_sync
57  integer               :: itau_wcosp, iff
58  real, dimension(Npoints,PARASOL_NREFL) :: parasolcrefl, Ncref
59
60! Variables locals intermidiaires pour inverser les axes des champs 4D
61! Compatibilite avec sorties CMIP
62  real, dimension(Npoints,Nlvgrid,SR_BINS) :: tmp_fi4da_cfadL, tmp_fi4da_cfadLgr, tmp_fi4da_cfadLatlid
63  real, dimension(Npoints,Nlvgrid,CLOUDSAT_DBZE_BINS) :: tmp_fi4da_cfadR
64  real, dimension(Npoints,numMISRHgtBins,7) :: tmp_fi4da_misr
65
66  missing_val=missing_cosp
67
68  Nlevout = Nlvgrid
69  Ncolout = Ncolumns
70
71! A refaire
72       itau_wcosp = itau_phy + itap + start_time * day_step_phy
73        if (prt_level >= 10) then
74             WRITE(lunout,*)'itau_wcosp, itap, start_time, day_step_phy =', &
75                             itau_wcosp, itap, start_time, day_step_phy
76        endif
77
78! On le donne a  cosp_output_write_mod pour que les histwrite y aient acces:
79       CALL set_itau_iocosp(itau_wcosp)
80        if (prt_level >= 10) then
81              WRITE(lunout,*)'itau_iocosp =',itau_iocosp
82        endif
83
84    ok_sync = .TRUE.
85   
86!!!! Sorties Calipso
87 if (cfg%Lcalipso) then
88
89!   print*,'Appel histwrite2d_cosp'
90   if (cfg%Lcllcalipso) then
91      where(cospOUT%calipso_cldlayer(:,1) == R_UNDEF) cospOUT%calipso_cldlayer(:,1) = missing_val
92      CALL histwrite2d_cosp(o_cllcalipso,cospOUT%calipso_cldlayer(:,1))
93   endif
94   if (cfg%Lclhcalipso) then
95      where(cospOUT%calipso_cldlayer(:,3) == R_UNDEF) cospOUT%calipso_cldlayer(:,3) = missing_val
96      CALL histwrite2d_cosp(o_clhcalipso,cospOUT%calipso_cldlayer(:,3))
97   endif
98   if (cfg%Lclmcalipso) then
99      where(cospOUT%calipso_cldlayer(:,2) == R_UNDEF) cospOUT%calipso_cldlayer(:,2) = missing_val
100      CALL histwrite2d_cosp(o_clmcalipso,cospOUT%calipso_cldlayer(:,2))
101   endif
102   if (cfg%Lcltcalipso) then
103      where(cospOUT%calipso_cldlayer(:,4) == R_UNDEF) cospOUT%calipso_cldlayer(:,4) = missing_val
104      CALL histwrite2d_cosp(o_cltcalipso,cospOUT%calipso_cldlayer(:,4))
105   endif
106   if (cfg%Lclcalipso) then
107      where(cospOUT%calipso_lidarcld == R_UNDEF)    cospOUT%calipso_lidarcld = missing_val
108      CALL histwrite3d_cosp(o_clcalipso,cospOUT%calipso_lidarcld,nvert)
109   endif
110   if (cfg%Lclcalipsotmp) then
111      where(cospOUT%calipso_lidarcldtmp(:,:,1) == R_UNDEF) cospOUT%calipso_lidarcldtmp(:,:,1) = missing_val
112      CALL histwrite3d_cosp(o_clcalipsotmp,cospOUT%calipso_lidarcldtmp(:,:,1),nverttemp)
113   endif
114
115   if (cfg%Lcllcalipsoice) then
116      where(cospOUT%calipso_cldlayerphase(:,1,1) == R_UNDEF) cospOUT%calipso_cldlayerphase(:,1,1) = missing_val
117      CALL histwrite2d_cosp(o_cllcalipsoice,cospOUT%calipso_cldlayerphase(:,1,1))
118   endif
119   if (cfg%Lclhcalipsoice) then
120      where(cospOUT%calipso_cldlayerphase(:,3,1) == R_UNDEF) cospOUT%calipso_cldlayerphase(:,3,1) = missing_val
121      CALL histwrite2d_cosp(o_clhcalipsoice,cospOUT%calipso_cldlayerphase(:,3,1))
122   endif
123   if (cfg%Lclmcalipsoice) then
124      where(cospOUT%calipso_cldlayerphase(:,2,1) == R_UNDEF) cospOUT%calipso_cldlayerphase(:,2,1) = missing_val
125      CALL histwrite2d_cosp(o_clmcalipsoice,cospOUT%calipso_cldlayerphase(:,2,1))
126   endif
127   if (cfg%Lcltcalipsoice) then
128      where(cospOUT%calipso_cldlayerphase(:,4,1) == R_UNDEF) cospOUT%calipso_cldlayerphase(:,4,1) = missing_val
129      CALL histwrite2d_cosp(o_cltcalipsoice,cospOUT%calipso_cldlayerphase(:,4,1))
130   endif
131   if (cfg%Lclcalipsoice) then
132      where(cospOUT%calipso_lidarcldphase(:,:,1) == R_UNDEF) cospOUT%calipso_lidarcldphase(:,:,1) = missing_val
133      CALL histwrite3d_cosp(o_clcalipsoice,cospOUT%calipso_lidarcldphase(:,:,1),nvert)
134   endif
135   if (cfg%Lclcalipsotmpice) then
136      where(cospOUT%calipso_lidarcldtmp(:,:,2) == R_UNDEF) cospOUT%calipso_lidarcldtmp(:,:,2) = missing_val
137      CALL histwrite3d_cosp(o_clcalipsotmpice,cospOUT%calipso_lidarcldtmp(:,:,2),nverttemp)
138   endif
139
140   if (cfg%Lcllcalipsoliq) then
141      where(cospOUT%calipso_cldlayerphase(:,1,2) == R_UNDEF) cospOUT%calipso_cldlayerphase(:,1,2) = missing_val
142      CALL histwrite2d_cosp(o_cllcalipsoliq,cospOUT%calipso_cldlayerphase(:,1,2))
143   endif
144   if (cfg%Lclhcalipsoliq) then
145      where(cospOUT%calipso_cldlayerphase(:,3,2) == R_UNDEF) cospOUT%calipso_cldlayerphase(:,3,2) = missing_val
146      CALL histwrite2d_cosp(o_clhcalipsoliq,cospOUT%calipso_cldlayerphase(:,3,2))
147   endif
148   if (cfg%Lclmcalipsoliq) then
149      where(cospOUT%calipso_cldlayerphase(:,2,2) == R_UNDEF) cospOUT%calipso_cldlayerphase(:,2,2) = missing_val
150      CALL histwrite2d_cosp(o_clmcalipsoliq,cospOUT%calipso_cldlayerphase(:,2,2))
151   endif
152   if (cfg%Lcltcalipsoliq) then
153      where(cospOUT%calipso_cldlayerphase(:,4,2) == R_UNDEF) cospOUT%calipso_cldlayerphase(:,4,2) = missing_val
154      CALL histwrite2d_cosp(o_cltcalipsoliq,cospOUT%calipso_cldlayerphase(:,4,2))
155   endif
156   if (cfg%Lclcalipsoliq) then
157      where(cospOUT%calipso_lidarcldphase(:,:,2) == R_UNDEF) cospOUT%calipso_lidarcldphase(:,:,2) = missing_val
158      CALL histwrite3d_cosp(o_clcalipsoliq,cospOUT%calipso_lidarcldphase(:,:,2),nvert)
159   endif
160   if (cfg%Lclcalipsotmpliq) then
161      where(cospOUT%calipso_lidarcldtmp(:,:,3) == R_UNDEF) cospOUT%calipso_lidarcldtmp(:,:,3) = missing_val
162      CALL histwrite3d_cosp(o_clcalipsotmpliq,cospOUT%calipso_lidarcldtmp(:,:,3),nverttemp)
163   endif
164   if (cfg%Lcllcalipsoun) then
165      where(cospOUT%calipso_cldlayerphase(:,1,3) == R_UNDEF) cospOUT%calipso_cldlayerphase(:,1,3) = missing_val
166      CALL histwrite2d_cosp(o_cllcalipsoun,cospOUT%calipso_cldlayerphase(:,1,3))
167   endif
168   if (cfg%Lclhcalipsoun) then
169      where(cospOUT%calipso_cldlayerphase(:,3,3) == R_UNDEF) cospOUT%calipso_cldlayerphase(:,3,3) = missing_val
170      CALL histwrite2d_cosp(o_clhcalipsoun,cospOUT%calipso_cldlayerphase(:,3,3))
171   endif
172   if (cfg%Lclmcalipsoun) then
173      where(cospOUT%calipso_cldlayerphase(:,2,3) == R_UNDEF) cospOUT%calipso_cldlayerphase(:,2,3) = missing_val
174      CALL histwrite2d_cosp(o_clmcalipsoun,cospOUT%calipso_cldlayerphase(:,2,3))
175   endif
176   if (cfg%Lcltcalipsoun) then
177      where(cospOUT%calipso_cldlayerphase(:,4,3) == R_UNDEF) cospOUT%calipso_cldlayerphase(:,4,3) = missing_val
178      CALL histwrite2d_cosp(o_cltcalipsoun,cospOUT%calipso_cldlayerphase(:,4,3))
179   endif
180   if (cfg%Lclcalipsoun) then
181      where(cospOUT%calipso_lidarcldphase(:,:,3) == R_UNDEF) cospOUT%calipso_lidarcldphase(:,:,3) = missing_val
182      CALL histwrite3d_cosp(o_clcalipsoun,cospOUT%calipso_lidarcldphase(:,:,3),nvert)
183   endif
184   if (cfg%Lclcalipsotmpun) then
185      where(cospOUT%calipso_lidarcldtmp(:,:,4) == R_UNDEF) cospOUT%calipso_lidarcldtmp(:,:,4) = missing_val
186      CALL histwrite3d_cosp(o_clcalipsotmpun,cospOUT%calipso_lidarcldtmp(:,:,4),nverttemp)
187   endif
188
189   if (cfg%Lclopaquecalipso) then
190      where(cospOUT%calipso_cldtype(:,1) == R_UNDEF) cospOUT%calipso_cldtype(:,1) = missing_val
191      CALL histwrite2d_cosp(o_clopaquecalipso,cospOUT%calipso_cldtype(:,1))
192   endif
193   if (cfg%Lclthincalipso) then
194      where(cospOUT%calipso_cldtype(:,2) == R_UNDEF) cospOUT%calipso_cldtype(:,2) = missing_val
195      CALL histwrite2d_cosp(o_clthincalipso,cospOUT%calipso_cldtype(:,2))   
196   endif
197   if (cfg%Lclzopaquecalipso) then
198      where(cospOUT%calipso_cldtype(:,3) == R_UNDEF) cospOUT%calipso_cldtype(:,3) = missing_val     
199      CALL histwrite2d_cosp(o_clzopaquecalipso,cospOUT%calipso_cldtype(:,3))
200   endif
201   if (cfg%Lclcalipsoopaque) then
202      where(cospOUT%calipso_lidarcldtype(:,:,1) == R_UNDEF) cospOUT%calipso_lidarcldtype(:,:,1) = missing_val     
203      CALL histwrite3d_cosp(o_clcalipsoopaque,cospOUT%calipso_lidarcldtype(:,:,1),nvert)
204   endif
205   if (cfg%Lclcalipsothin) then
206      where(cospOUT%calipso_lidarcldtype(:,:,2) == R_UNDEF) cospOUT%calipso_lidarcldtype(:,:,2) = missing_val
207      CALL histwrite3d_cosp(o_clcalipsothin,cospOUT%calipso_lidarcldtype(:,:,2),nvert) 
208   endif
209   if (cfg%Lclcalipsozopaque) then
210      where(cospOUT%calipso_lidarcldtype(:,:,3) == R_UNDEF) cospOUT%calipso_lidarcldtype(:,:,3) = missing_val
211      CALL histwrite3d_cosp(o_clcalipsozopaque,cospOUT%calipso_lidarcldtype(:,:,3),nvert)
212   endif
213   if (cfg%Lclcalipsoopacity) then
214      where(cospOUT%calipso_lidarcldtype(:,:,4) == R_UNDEF) cospOUT%calipso_lidarcldtype(:,:,4) = missing_val
215      CALL histwrite3d_cosp(o_clcalipsoopacity,cospOUT%calipso_lidarcldtype(:,:,4),nvert)
216   endif
217
218   if (cfg%Lclopaquetemp) then
219      where(cospOUT%calipso_cldtypetemp(:,1) == R_UNDEF) cospOUT%calipso_cldtypetemp(:,1) = missing_val
220      CALL histwrite2d_cosp(o_clopaquetemp,cospOUT%calipso_cldtypetemp(:,1))
221   endif
222   if (cfg%Lclthintemp) then
223      where(cospOUT%calipso_cldtypetemp(:,2) == R_UNDEF) cospOUT%calipso_cldtypetemp(:,2) = missing_val
224      CALL histwrite2d_cosp(o_clthintemp,cospOUT%calipso_cldtypetemp(:,2))
225   endif
226   if (cfg%Lclzopaquetemp) then
227      where(cospOUT%calipso_cldtypetemp(:,3) == R_UNDEF) cospOUT%calipso_cldtypetemp(:,3) = missing_val
228      CALL histwrite2d_cosp(o_clzopaquetemp,cospOUT%calipso_cldtypetemp(:,3))
229   endif
230   if (cfg%Lclopaquemeanz) then
231      where(cospOUT%calipso_cldtypemeanz(:,1) == R_UNDEF) cospOUT%calipso_cldtypemeanz(:,1) = missing_val
232      CALL histwrite2d_cosp(o_clopaquemeanz,cospOUT%calipso_cldtypemeanz(:,1))
233   endif
234   if (cfg%Lclthinmeanz) then
235      where(cospOUT%calipso_cldtypemeanz(:,2) == R_UNDEF) cospOUT%calipso_cldtypemeanz(:,2) = missing_val
236      CALL histwrite2d_cosp(o_clthinmeanz,cospOUT%calipso_cldtypemeanz(:,2))
237   endif
238   if (cfg%Lclthinemis) then
239      where(cospOUT%calipso_cldthinemis == R_UNDEF) cospOUT%calipso_cldthinemis = missing_val
240      CALL histwrite2d_cosp(o_clthinemis,cospOUT%calipso_cldthinemis)
241   endif
242   if (cfg%Lclopaquemeanzse) then
243      where(cospOUT%calipso_cldtypemeanzse(:,1) == R_UNDEF) cospOUT%calipso_cldtypemeanzse(:,1) = missing_val
244      CALL histwrite2d_cosp(o_clopaquemeanzse,cospOUT%calipso_cldtypemeanzse(:,1))
245   endif
246   if (cfg%Lclthinmeanzse) then
247      where(cospOUT%calipso_cldtypemeanzse(:,2) == R_UNDEF) cospOUT%calipso_cldtypemeanzse(:,2) = missing_val
248      CALL histwrite2d_cosp(o_clthinmeanzse,cospOUT%calipso_cldtypemeanzse(:,2))
249   endif
250   if (cfg%Lclzopaquecalipsose) then
251      where(cospOUT%calipso_cldtypemeanzse(:,3) == R_UNDEF) cospOUT%calipso_cldtypemeanzse(:,3) = missing_val
252      CALL histwrite2d_cosp(o_clzopaquecalipsose,cospOUT%calipso_cldtypemeanzse(:,3))
253   endif
254
255
256   if (cfg%LcfadLidarsr532) then
257     where(cospOUT%calipso_cfad_sr == R_UNDEF) cospOUT%calipso_cfad_sr = missing_val
258   
259     do icl=1,SR_BINS
260      do k=1,Nlvgrid
261       do ip=1,Npoints
262        tmp_fi4da_cfadL(ip,k,icl)=cospOUT%calipso_cfad_sr(ip,icl,k)
263       enddo
264      enddo
265     enddo
266!   if (cfg%LcfadLidarsr532) CALL histwrite4d_cosp(o_cfad_lidarsr532,stlidar%cfad_sr)
267    CALL histwrite4d_cosp(o_cfadLidarsr532,tmp_fi4da_cfadL)   !!! "_" enleve
268   endif
269
270   if (cfg%Latb532) then 
271     where(cospOUT%calipso_beta_tot == R_UNDEF) cospOUT%calipso_beta_tot = missing_val
272     CALL histwrite4d_cosp(o_atb532,cospOUT%calipso_beta_tot)
273   endif
274   if (cfg%LlidarBetaMol532) then
275     where(cospOUT%calipso_tau_tot == R_UNDEF) cospOUT%calipso_tau_tot = missing_val
276     CALL histwrite3d_cosp(o_lidarBetaMol532,cospOUT%calipso_beta_mol,nvertmcosp)
277   endif
278
279 endif !Calipso
280
281
282!!!! Sorties Ground Lidar
283 if (cfg%LgrLidar532) then
284
285   where(cospOUT%grLidar532_beta_tot == R_UNDEF) cospOUT%grLidar532_beta_tot = missing_val
286   where(cospOUT%grLidar532_cfad_sr == R_UNDEF) cospOUT%grLidar532_cfad_sr = missing_val
287   where(cospOUT%grLidar532_lidarcld == R_UNDEF) cospOUT%grLidar532_lidarcld = missing_val
288   where(cospOUT%grLidar532_cldlayer == R_UNDEF) cospOUT%grLidar532_cldlayer = missing_val
289   where(cospOUT%grLidar532_beta_mol == R_UNDEF) cospOUT%grLidar532_beta_mol = missing_val
290   where(cospOUT%grLidar532_srbval == R_UNDEF) cospOUT%grLidar532_srbval = missing_val
291
292   if (cfg%LcllgrLidar532) CALL histwrite2d_cosp(o_cllgrLidar532,cospOUT%grLidar532_cldlayer(:,1))
293   if (cfg%LclmgrLidar532) CALL histwrite2d_cosp(o_clmgrLidar532,cospOUT%grLidar532_cldlayer(:,2))
294   if (cfg%LclhgrLidar532) CALL histwrite2d_cosp(o_clhgrLidar532,cospOUT%grLidar532_cldlayer(:,3))
295   if (cfg%LcltgrLidar532) CALL histwrite2d_cosp(o_cltgrLidar532,cospOUT%grLidar532_cldlayer(:,4))
296
297   if (cfg%LclgrLidar532) CALL histwrite3d_cosp(o_clgrLidar532,cospOUT%grLidar532_lidarcld,nvert)
298   if (cfg%LlidarBetaMol532gr) CALL histwrite3d_cosp(o_lidarBetaMol532gr,cospOUT%grLidar532_beta_mol,nvertmcosp)
299
300   do icl=1,SR_BINS
301      do k=1,Nlvgrid
302       do ip=1,Npoints
303         tmp_fi4da_cfadLgr(ip,k,icl)=cospOUT%grLidar532_cfad_sr(ip,icl,k)
304       enddo
305      enddo
306   enddo
307   if (cfg%LcfadLidarsr532gr) CALL histwrite4d_cosp(o_cfadLidarsr532gr,tmp_fi4da_cfadLgr)
308
309   if (cfg%Latb532gr) CALL histwrite4d_cosp(o_atb532gr,cospOUT%grLidar532_beta_tot)
310
311endif ! Ground Lidar 532 nm
312
313
314!!!! Sorties Atlid
315 if (cfg%Latlid) then
316
317   where(cospOUT%atlid_beta_tot == R_UNDEF) cospOUT%atlid_beta_tot = missing_val
318   where(cospOUT%atlid_cfad_sr == R_UNDEF) cospOUT%atlid_cfad_sr = missing_val
319   where(cospOUT%atlid_lidarcld == R_UNDEF) cospOUT%atlid_lidarcld = missing_val
320   where(cospOUT%atlid_cldlayer == R_UNDEF) cospOUT%atlid_cldlayer = missing_val
321   where(cospOUT%atlid_beta_mol == R_UNDEF) cospOUT%atlid_beta_mol = missing_val
322   where(cospOUT%atlid_srbval == R_UNDEF) cospOUT%atlid_srbval = missing_val
323
324   if (cfg%Lcllatlid) CALL histwrite2d_cosp(o_cllatlid,cospOUT%atlid_cldlayer(:,1))
325   if (cfg%Lclmatlid) CALL histwrite2d_cosp(o_clmatlid,cospOUT%atlid_cldlayer(:,2))
326   if (cfg%Lclhatlid) CALL histwrite2d_cosp(o_clhatlid,cospOUT%atlid_cldlayer(:,3))
327   if (cfg%Lcltatlid) CALL histwrite2d_cosp(o_cltatlid,cospOUT%atlid_cldlayer(:,4))
328
329   if (cfg%Lclatlid) CALL histwrite3d_cosp(o_clatlid,cospOUT%atlid_lidarcld,nvert)
330   if (cfg%LlidarBetaMol355) CALL histwrite3d_cosp(o_lidarBetaMol355,cospOUT%atlid_beta_mol,nvertmcosp)
331
332   do icl=1,SR_BINS
333      do k=1,Nlvgrid
334       do ip=1,Npoints
335          tmp_fi4da_cfadLatlid(ip,k,icl)=cospOUT%atlid_cfad_sr(ip,icl,k)
336       enddo
337      enddo
338   enddo
339   if (cfg%LcfadLidarsr355) CALL histwrite4d_cosp(o_cfadlidarsr355,tmp_fi4da_cfadLatlid)
340
341   if (cfg%Latb355) CALL histwrite4d_cosp(o_atb355,cospOUT%atlid_beta_tot)
342
343endif ! Atlid
344
345
346 if (cfg%Lparasol) then
347   if (cfg%LparasolRefl) then
348! Ces 2 diagnostics sont controles par la clef logique "LparasolRefl"
349
350!!!   if (cfg%LparasolRefl) CALL histwrite3d_cosp(o_parasolrefl,cospOUT%parasolrefl,nvertp)
351     CALL histwrite3d_cosp(o_parasolGrid_refl,cospOUT%parasolGrid_refl,nvertp)
352
353     CALL histwrite4d_cosp(o_parasolPix_refl,cospOUT%parasolPix_refl)
354
355    endif ! LparasolRefl
356   endif ! Parasol
357
358!  if (cfg%LparasolRefl) then
359!    do k=1,PARASOL_NREFL
360!     do ip=1, Npoints
361!      if (stlidar%cldlayer(ip,4).gt.1.and.stlidar%parasolrefl(ip,k).ne.missing_val) then
362!        parasolcrefl(ip,k)=(stlidar%parasolrefl(ip,k)-0.03*(1.-stlidar%cldlayer(ip,4)/100.))/ &
363!                             (stlidar%cldlayer(ip,4)/100.)
364!         Ncref(ip,k) = 1.
365!      else
366!         parasolcrefl(ip,k)=missing_val
367!         Ncref(ip,k) = 0.
368!      endif
369!     enddo
370!    enddo
371!    CALL histwrite3d_cosp(o_Ncrefl,Ncref,nvertp)
372!    CALL histwrite3d_cosp(o_parasol_crefl,parasolcrefl,nvertp)
373!  endif
374
375
376!!! Sorties CloudSat
377 if (cfg%Lcloudsat) then
378
379   where(cospOUT%cloudsat_Ze_tot == R_UNDEF) cospOUT%cloudsat_Ze_tot = missing_val
380   where(cospOUT%cloudsat_cfad_ze == R_UNDEF) cospOUT%cloudsat_cfad_ze = missing_val
381   where(cospOUT%cloudsat_precip_cover == R_UNDEF) cospOUT%cloudsat_precip_cover = missing_val
382   where(cospOUT%cloudsat_pia == R_UNDEF) cospOUT%cloudsat_pia = missing_val
383
384   if (cfg%Lptradarflag0) CALL histwrite2d_cosp(o_ptradarflag0,cospOUT%cloudsat_precip_cover(:,1))
385   if (cfg%Lptradarflag1) CALL histwrite2d_cosp(o_ptradarflag1,cospOUT%cloudsat_precip_cover(:,2))
386   if (cfg%Lptradarflag2) CALL histwrite2d_cosp(o_ptradarflag2,cospOUT%cloudsat_precip_cover(:,3))
387   if (cfg%Lptradarflag3) CALL histwrite2d_cosp(o_ptradarflag3,cospOUT%cloudsat_precip_cover(:,4))
388   if (cfg%Lptradarflag4) CALL histwrite2d_cosp(o_ptradarflag4,cospOUT%cloudsat_precip_cover(:,5))
389   if (cfg%Lptradarflag5) CALL histwrite2d_cosp(o_ptradarflag5,cospOUT%cloudsat_precip_cover(:,6))
390   if (cfg%Lptradarflag6) CALL histwrite2d_cosp(o_ptradarflag6,cospOUT%cloudsat_precip_cover(:,7))
391   if (cfg%Lptradarflag7) CALL histwrite2d_cosp(o_ptradarflag7,cospOUT%cloudsat_precip_cover(:,8))
392   if (cfg%Lptradarflag8) CALL histwrite2d_cosp(o_ptradarflag8,cospOUT%cloudsat_precip_cover(:,9))
393   if (cfg%Lptradarflag9) CALL histwrite2d_cosp(o_ptradarflag9,cospOUT%cloudsat_precip_cover(:,10))
394   if (cfg%Lradarpia) CALL histwrite2d_cosp(o_radarpia,cospOUT%cloudsat_pia)
395
396   do icl=1,CLOUDSAT_DBZE_BINS
397      do k=1,Nlvgrid
398       do ip=1,Npoints
399         tmp_fi4da_cfadR(ip,k,icl)=cospOUT%cloudsat_cfad_ze(ip,icl,k)
400       enddo
401      enddo
402   enddo
403   if (cfg%Ldbze94) CALL histwrite4d_cosp(o_dbze94,cospOUT%cloudsat_Ze_tot)
404!   if (cfg%LcfadDbze94) CALL histwrite4d_cosp(o_cfadDbze94,stradar%cfad_ze)
405   if (cfg%LcfadDbze94) CALL histwrite4d_cosp(o_cfadDbze94,tmp_fi4da_cfadR)
406 endif
407! endif pour CloudSat
408
409
410!!! Sorties combinees Cloudsat et Calipso
411 if (cfg%Lcalipso .and. cfg%Lcloudsat) then
412   where(cospOUT%lidar_only_freq_cloud == R_UNDEF) &
413                           cospOUT%lidar_only_freq_cloud = missing_val
414   where(cospOUT%cloudsat_tcc == R_UNDEF) &
415                           cospOUT%cloudsat_tcc = missing_val
416   where(cospOUT%cloudsat_tcc2 == R_UNDEF) &
417                           cospOUT%cloudsat_tcc2 = missing_val
418   where(cospOUT%radar_lidar_tcc == R_UNDEF) &
419                           cospOUT%radar_lidar_tcc = missing_val
420
421   if (cfg%Lclcalipso2) CALL histwrite3d_cosp(o_clcalipso2,cospOUT%lidar_only_freq_cloud,nvert)
422   if (cfg%Lcloudsat_tcc) CALL histwrite2d_cosp(o_cloudsat_tcc,cospOUT%cloudsat_tcc)
423   if (cfg%Lcloudsat_tcc2) CALL histwrite2d_cosp(o_cloudsat_tcc2,cospOUT%cloudsat_tcc2)
424   if (cfg%Lcltlidarradar) CALL histwrite2d_cosp(o_cltlidarradar,cospOUT%radar_lidar_tcc)
425 endif
426
427
428!!! Sorties Isccp
429 if (cfg%Lisccp) then
430  where(cospOUT%isccp_totalcldarea == R_UNDEF) cospOUT%isccp_totalcldarea = missing_val
431  where(cospOUT%isccp_meanptop == R_UNDEF) cospOUT%isccp_meanptop = missing_val
432  where(cospOUT%isccp_meantaucld == R_UNDEF) cospOUT%isccp_meantaucld = missing_val
433  where(cospOUT%isccp_meanalbedocld == R_UNDEF) cospOUT%isccp_meanalbedocld = missing_val
434  where(cospOUT%isccp_meantb == R_UNDEF) cospOUT%isccp_meantb = missing_val
435  where(cospOUT%isccp_meantbclr == R_UNDEF) cospOUT%isccp_meantbclr = missing_val
436  where(cospOUT%isccp_fq == R_UNDEF) cospOUT%isccp_fq = missing_val
437  where(cospOUT%isccp_boxtau == R_UNDEF) cospOUT%isccp_boxtau = missing_val
438  where(cospOUT%isccp_boxptop == R_UNDEF) cospOUT%isccp_boxptop = missing_val
439
440!   CALL histwrite2d_cosp(o_sunlit,gbx%sunlit)
441  if (cfg%Lclisccp) CALL histwrite4d_cosp(o_clisccp,cospOUT%isccp_fq)
442
443   if (cfg%Lboxtauisccp) CALL histwrite3d_cosp(o_boxtauisccp,cospOUT%isccp_boxtau,nvertcol)
444   if (cfg%Lboxptopisccp) CALL histwrite3d_cosp(o_boxptopisccp,cospOUT%isccp_boxptop,nvertcol)
445   if (cfg%Lcltisccp) CALL histwrite2d_cosp(o_cltisccp,cospOUT%isccp_totalcldarea)
446   if (cfg%Lpctisccp) CALL histwrite2d_cosp(o_pctisccp,cospOUT%isccp_meanptop)
447   if (cfg%Ltauisccp) CALL histwrite2d_cosp(o_tauisccp,cospOUT%isccp_meantaucld)
448   if (cfg%Lalbisccp) CALL histwrite2d_cosp(o_albisccp,cospOUT%isccp_meanalbedocld)
449   if (cfg%Lmeantbisccp) CALL histwrite2d_cosp(o_meantbisccp,cospOUT%isccp_meantb)
450   if (cfg%Lmeantbclrisccp) CALL histwrite2d_cosp(o_meantbclrisccp,cospOUT%isccp_meantbclr)
451 endif ! Isccp
452
453
454!!! MISR simulator
455 if (cfg%Lmisr) then
456
457   if (cfg%LclMISR) then
458! Ces 3 diagnostics sont controles par la clef logique "LclMISR"
459   where(cospOUT%misr_fq == R_UNDEF) cospOUT%misr_fq = missing_val
460!   where(cospOUT%misr_dist_model_layertops == R_UNDEF) cospOUT%misr_dist_model_layertops = missing_val
461   where(cospOUT%misr_meanztop == R_UNDEF) cospOUT%misr_meanztop = missing_val
462   where(cospOUT%misr_cldarea == R_UNDEF) cospOUT%misr_cldarea = missing_val
463
464   do icl=1,numMISRHgtBins
465      do k=1,Nlvgrid
466       do ip=1,Npoints   
467      tmp_fi4da_misr(ip,icl,k)=cospOUT%misr_fq(ip,k,icl)
468       enddo
469      enddo
470   enddo
471!   if (cfg%LclMISR) CALL histwrite4d_cosp(o_clMISR,misr%fq_MISR)
472!   if (cfg%LclMISR) CALL histwrite4d_cosp(o_clMISR,tmp_fi4da_misr)
473   CALL histwrite4d_cosp(o_misr_fq,tmp_fi4da_misr)
474
475   CALL histwrite2d_cosp(o_misr_meanztop,cospOUT%misr_meanztop)
476   CALL histwrite2d_cosp(o_misr_cldarea,cospOUT%misr_cldarea)
477  endif ! LclMISR
478
479 endif ! Misr
480
481
482!!! Modis simulator
483 if (cfg%Lmodis) then
484  where(cospOUT%modis_Cloud_Fraction_Low_Mean == R_UNDEF) &
485        cospOUT%modis_Cloud_Fraction_Low_Mean = missing_val
486  where(cospOUT%modis_Cloud_Fraction_High_Mean == R_UNDEF) &
487        cospOUT%modis_Cloud_Fraction_High_Mean = missing_val
488  where(cospOUT%modis_Cloud_Fraction_Mid_Mean == R_UNDEF) &
489        cospOUT%modis_Cloud_Fraction_Mid_Mean = missing_val
490  where(cospOUT%modis_Cloud_Fraction_Total_Mean == R_UNDEF) &
491        cospOUT%modis_Cloud_Fraction_Total_Mean = missing_val
492  where(cospOUT%modis_Cloud_Fraction_Water_Mean == R_UNDEF) &
493        cospOUT%modis_Cloud_Fraction_Water_Mean = missing_val
494  where(cospOUT%modis_Cloud_Fraction_Ice_Mean == R_UNDEF) &
495        cospOUT%modis_Cloud_Fraction_Ice_Mean = missing_val
496  where(cospOUT%modis_Optical_Thickness_Total_Mean == R_UNDEF) &
497        cospOUT%modis_Optical_Thickness_Total_Mean = missing_val
498  where(cospOUT%modis_Optical_Thickness_Water_Mean == R_UNDEF) &
499        cospOUT%modis_Optical_Thickness_Water_Mean = missing_val
500  where(cospOUT%modis_Optical_Thickness_Ice_Mean == R_UNDEF) &
501        cospOUT%modis_Optical_Thickness_Ice_Mean = missing_val
502  where(cospOUT%modis_Cloud_Particle_Size_Water_Mean == R_UNDEF) &
503        cospOUT%modis_Cloud_Particle_Size_Water_Mean = missing_val
504  where(cospOUT%modis_Cloud_Particle_Size_Ice_Mean == R_UNDEF) &
505        cospOUT%modis_Cloud_Particle_Size_Ice_Mean = missing_val
506  where(cospOUT%modis_Cloud_Top_Pressure_Total_Mean == R_UNDEF) &
507        cospOUT%modis_Cloud_Top_Pressure_Total_Mean = missing_val
508  where(cospOUT%modis_Liquid_Water_Path_Mean == R_UNDEF) &
509        cospOUT%modis_Liquid_Water_Path_Mean = missing_val
510  where(cospOUT%modis_Ice_Water_Path_Mean == R_UNDEF) &
511        cospOUT%modis_Ice_Water_Path_Mean = missing_val
512  where(cospOUT%modis_Optical_Thickness_Total_LogMean == R_UNDEF) &
513          cospOUT%modis_Optical_Thickness_Total_LogMean = missing_val
514  where(cospOUT%modis_Optical_Thickness_Water_LogMean == R_UNDEF) &
515          cospOUT%modis_Optical_Thickness_Water_LogMean = missing_val
516  where(cospOUT%modis_Optical_Thickness_Ice_LogMean == R_UNDEF) &
517          cospOUT%modis_Optical_Thickness_Ice_LogMean = missing_val
518   
519  if (cfg%Lcllmodis) CALL histwrite2d_cosp(o_cllmodis,cospOUT%modis_Cloud_Fraction_Low_Mean)
520  if (cfg%Lclhmodis) CALL histwrite2d_cosp(o_clhmodis,cospOUT%modis_Cloud_Fraction_High_Mean)
521  if (cfg%Lclmmodis) CALL histwrite2d_cosp(o_clmmodis,cospOUT%modis_Cloud_Fraction_Mid_Mean)
522  if (cfg%Lcltmodis) CALL histwrite2d_cosp(o_cltmodis,cospOUT%modis_Cloud_Fraction_Total_Mean)
523  if (cfg%Lclwmodis) CALL histwrite2d_cosp(o_clwmodis,cospOUT%modis_Cloud_Fraction_Water_Mean)
524  if (cfg%Lclimodis) CALL histwrite2d_cosp(o_climodis,cospOUT%modis_Cloud_Fraction_Ice_Mean)
525  if (cfg%Ltautmodis) CALL histwrite2d_cosp(o_tautmodis,cospOUT%modis_Optical_Thickness_Total_Mean)
526  if (cfg%Ltauwmodis) CALL histwrite2d_cosp(o_tauwmodis,cospOUT%modis_Optical_Thickness_Water_Mean)
527  if (cfg%Ltauimodis) CALL histwrite2d_cosp(o_tauimodis,cospOUT%modis_Optical_Thickness_Ice_Mean)
528  if (cfg%Ltautlogmodis) CALL histwrite2d_cosp(o_tautlogmodis,cospOUT%modis_Optical_Thickness_Total_LogMean) 
529  if (cfg%Ltauwlogmodis) CALL histwrite2d_cosp(o_tauwlogmodis,cospOUT%modis_Optical_Thickness_Water_LogMean)
530  if (cfg%Ltauilogmodis) CALL histwrite2d_cosp(o_tauilogmodis,cospOUT%modis_Optical_Thickness_Ice_LogMean)
531  if (cfg%Lreffclwmodis) CALL histwrite2d_cosp(o_reffclwmodis,cospOUT%modis_Cloud_Particle_Size_Water_Mean)
532  if (cfg%Lreffclimodis) CALL histwrite2d_cosp(o_reffclimodis,cospOUT%modis_Cloud_Particle_Size_Ice_Mean)
533  if (cfg%Lpctmodis) CALL histwrite2d_cosp(o_pctmodis,cospOUT%modis_Cloud_Top_Pressure_Total_Mean)
534  if (cfg%Llwpmodis) CALL histwrite2d_cosp(o_lwpmodis,cospOUT%modis_Liquid_Water_Path_Mean)
535  if (cfg%Liwpmodis) CALL histwrite2d_cosp(o_iwpmodis,cospOUT%modis_Ice_Water_Path_Mean)
536
537  if (cfg%Lclmodis) then
538! Ces 3 diagnostics sont controles par la clef logique "Lclmodis"
539    where(cospOUT%modis_Optical_Thickness_vs_Cloud_Top_Pressure == R_UNDEF) &
540          cospOUT%modis_Optical_Thickness_vs_Cloud_Top_Pressure = missing_val
541    where(cospOUT%modis_Optical_Thickness_vs_ReffICE == R_UNDEF) &
542          cospOUT%modis_Optical_Thickness_vs_ReffICE = missing_val
543    where(cospOUT%modis_Optical_thickness_vs_ReffLIQ == R_UNDEF) &
544          cospOUT%modis_Optical_thickness_vs_ReffLIQ = missing_val
545
546    CALL histwrite4d_cosp(o_modis_ot_vs_ctp,cospOUT%modis_Optical_Thickness_vs_Cloud_Top_Pressure)
547    CALL histwrite4d_cosp(o_modis_ot_vs_reffice,cospOUT%modis_Optical_Thickness_vs_ReffICE)
548    CALL histwrite4d_cosp(o_modis_ot_vs_reffliq,cospOUT%modis_Optical_thickness_vs_ReffLIQ)
549
550  endif ! Lclmodis
551
552 endif !modis
553
554
555 IF(.NOT.cosp_varsdefined) THEN
556!$OMP MASTER
557! Fermeture dans phys_output_write
558!#ifdef 1
559            !On finalise l'initialisation:
560            !CALL wxios_closedef()
561!#endif
562
563!$OMP END MASTER
564!$OMP BARRIER
565            cosp_varsdefined = .TRUE.
566 END IF
567
568    IF(cosp_varsdefined) THEN
569! On synchronise les fichiers pour IOIPSL
570    ENDIF  !cosp_varsdefined
571
572    END SUBROUTINE lmdz_cosp_output_write
573
574
575! ug Routine pour definir itau_iocosp depuis cosp_output_write_mod:
576  SUBROUTINE set_itau_iocosp(ito)
577      IMPLICIT NONE
578      INTEGER, INTENT(IN) :: ito
579      itau_iocosp = ito
580  END SUBROUTINE
581
582  SUBROUTINE histdef2d_cosp (iff,var)
583
584    USE ioipsl
585    USE dimphy
586    use iophy
587    USE mod_phys_lmdz_para
588    USE mod_grid_phy_lmdz, ONLY: nbp_lon
589    USE print_control_mod, ONLY: lunout,prt_level
590  USE wxios
591
592    IMPLICIT NONE
593
594    INCLUDE "clesphys.h"
595
596    INTEGER                          :: iff
597    TYPE(ctrl_outcosp)               :: var
598
599    REAL zstophym
600    CHARACTER(LEN=20) :: typeecrit
601
602    ! ug On récupère le type écrit de la structure:
603    !       Assez moche, Ã|  refaire si meilleure méthode...
604    IF (INDEX(var%cosp_typeecrit(iff), "once") > 0) THEN
605       typeecrit = 'once'
606    ELSE IF(INDEX(var%cosp_typeecrit(iff), "t_min") > 0) THEN
607       typeecrit = 't_min(X)'
608    ELSE IF(INDEX(var%cosp_typeecrit(iff), "t_max") > 0) THEN
609       typeecrit = 't_max(X)'
610    ELSE IF(INDEX(var%cosp_typeecrit(iff), "inst") > 0) THEN
611       typeecrit = 'inst(X)'
612    ELSE
613       typeecrit = cosp_outfiletypes(iff)
614    ENDIF
615
616    IF (typeecrit=='inst(X)'.OR.typeecrit=='once') THEN
617       zstophym=zoutm_cosp(iff)
618    ELSE
619       zstophym=zdtimemoy_cosp
620    ENDIF
621
622     IF (.not. ok_all_xml) then
623       IF ( var%cles(iff) ) THEN
624         if (prt_level >= 10) then
625              WRITE(lunout,*)'Appel wxios_add_field_to_file var%name =',var%name
626         endif
627        CALL wxios_add_field_to_file(var%name, 2, cosp_nidfiles(iff), cosp_outfilenames(iff), &
628                                     var%description, var%unit, 1, typeecrit)
629       ENDIF
630     ENDIF
631
632
633  END SUBROUTINE histdef2d_cosp
634
635
636 SUBROUTINE histdef3d_cosp (iff,var,nvertsave,ncols)
637    USE ioipsl
638    USE dimphy
639    use iophy
640    USE mod_phys_lmdz_para
641    USE mod_grid_phy_lmdz, ONLY: nbp_lon
642    USE print_control_mod, ONLY: lunout,prt_level
643
644  USE wxios
645
646
647    IMPLICIT NONE
648
649    INCLUDE "clesphys.h"
650
651    INTEGER                        :: iff, klevs
652    INTEGER, INTENT(IN), OPTIONAL  :: ncols ! ug RUSTINE POUR LES variables 4D
653    INTEGER, INTENT(IN)           :: nvertsave
654    TYPE(ctrl_outcosp)             :: var
655
656    REAL zstophym
657    CHARACTER(LEN=20) :: typeecrit, nomi
658    CHARACTER(LEN=20) :: nom
659    character(len=2) :: str2
660    CHARACTER(len=20) :: nam_axvert
661
662! Axe vertical
663      IF (nvertsave.eq.nvertp(iff)) THEN
664          klevs=PARASOL_NREFL
665          nam_axvert="sza"
666      ELSE IF (nvertsave.eq.nvertisccp(iff)) THEN
667          klevs=7
668          nam_axvert="pressure2"
669      ELSE IF (nvertsave.eq.nvertcol(iff)) THEN
670          klevs=Ncolout
671          nam_axvert="column"
672      ELSE IF (nvertsave.eq.nverttemp(iff)) THEN
673          klevs=LIDAR_NTEMP
674          nam_axvert="temp"
675      ELSE IF (nvertsave.eq.nvertmisr(iff)) THEN
676          klevs=numMISRHgtBins
677          nam_axvert="cth16"
678      ELSE IF (nvertsave.eq.nvertReffIce(iff)) THEN
679          klevs= numMODISReffIceBins
680          nam_axvert="ReffIce"
681      ELSE IF (nvertsave.eq.nvertReffLiq(iff)) THEN
682          klevs= numMODISReffLiqBins
683          nam_axvert="ReffLiq"
684      ELSE
685           klevs=Nlevout
686           nam_axvert="presnivs"
687      ENDIF
688
689! ug RUSTINE POUR LES Champs 4D
690      IF (PRESENT(ncols)) THEN
691               write(str2,'(i2.2)')ncols
692               nomi=var%name
693               nom="c"//str2//"_"//nomi
694      ELSE
695               nom=var%name
696      END IF
697
698    ! ug On récupère le type écrit de la structure:
699    !       Assez moche, Ã|  refaire si meilleure méthode...
700    IF (INDEX(var%cosp_typeecrit(iff), "once") > 0) THEN
701       typeecrit = 'once'
702    ELSE IF(INDEX(var%cosp_typeecrit(iff), "t_min") > 0) THEN
703       typeecrit = 't_min(X)'
704    ELSE IF(INDEX(var%cosp_typeecrit(iff), "t_max") > 0) THEN
705       typeecrit = 't_max(X)'
706    ELSE IF(INDEX(var%cosp_typeecrit(iff), "inst") > 0) THEN
707       typeecrit = 'inst(X)'
708    ELSE
709       typeecrit = cosp_outfiletypes(iff)
710    ENDIF
711
712    IF (typeecrit=='inst(X)'.OR.typeecrit=='once') THEN
713       zstophym=zoutm_cosp(iff)
714    ELSE
715       zstophym=zdtimemoy_cosp
716    ENDIF
717
718      IF (.not. ok_all_xml) then
719        IF ( var%cles(iff) ) THEN
720          if (prt_level >= 10) then
721              WRITE(lunout,*)'Appel wxios_add_field_to_file 3d nom variable nam_axvert = ',nom, nam_axvert
722          endif
723          CALL wxios_add_field_to_file(nom, 3, cosp_nidfiles(iff), cosp_outfilenames(iff), &
724                                       var%description, var%unit, 1, typeecrit, nam_axvert)
725        ENDIF
726      ENDIF
727
728
729  END SUBROUTINE histdef3d_cosp
730
731
732 SUBROUTINE histwrite2d_cosp(var,field)
733  USE dimphy
734  USE mod_phys_lmdz_para
735  USE ioipsl
736  use iophy
737  USE mod_grid_phy_lmdz, ONLY: nbp_lon
738  USE print_control_mod, ONLY: lunout,prt_level
739
740  USE xios, only: xios_send_field
741
742  IMPLICIT NONE
743  INCLUDE 'clesphys.h'
744
745    TYPE(ctrl_outcosp), INTENT(IN) :: var
746    REAL, DIMENSION(:), INTENT(IN) :: field
747
748    INTEGER :: iff
749
750    REAL,DIMENSION(klon_mpi) :: buffer_omp
751    INTEGER, allocatable, DIMENSION(:) :: index2d
752    REAL :: Field2d(nbp_lon,jj_nb)
753    CHARACTER(LEN=20) ::  nomi, nom
754    character(len=2) :: str2
755    LOGICAL, SAVE  :: firstx
756!$OMP THREADPRIVATE(firstx)
757
758    IF (prt_level >= 9) WRITE(lunout,*)'Begin histrwrite2d ',var%name
759
760  ! On regarde si on est dans la phase de définition ou d'écriture:
761  IF(.NOT.cosp_varsdefined) THEN
762!$OMP MASTER
763      print*,'var, cosp_varsdefined dans cosp_varsdefined ',var%name, cosp_varsdefined
764      !Si phase de définition.... on définit
765      CALL conf_cospoutputs(var%name,var%cles)
766      DO iff=1, 3
767         IF (cosp_outfilekeys(iff)) THEN
768            CALL histdef2d_cosp(iff, var)
769         ENDIF
770      ENDDO
771!$OMP END MASTER
772  ELSE
773    !Et sinon on.... écrit
774    IF (SIZE(field)/=klon) &
775  CALL abort_physic('iophy::histwrite2d_cosp','Field first DIMENSION not equal to klon',1)
776
777    CALL Gather_omp(field,buffer_omp)
778!$OMP MASTER
779    CALL grid1Dto2D_mpi(buffer_omp,Field2d)
780
781! La boucle sur les fichiers:
782      firstx=.true.
783      DO iff=1, 3
784           IF (var%cles(iff) .AND. cosp_outfilekeys(iff)) THEN
785                ALLOCATE(index2d(nbp_lon*jj_nb))
786                deallocate(index2d)
787              IF (.not. ok_all_xml) then
788                 if (firstx) then
789                  if (prt_level >= 10) then
790                    WRITE(lunout,*)'xios_send_field variable ',var%name
791                  endif
792                  CALL xios_send_field(var%name, Field2d)
793                   firstx=.false.
794                 endif
795              ENDIF
796           ENDIF
797      ENDDO
798
799      IF (ok_all_xml) THEN
800        if (prt_level >= 1) then
801              WRITE(lunout,*)'xios_send_field variable ',var%name
802        endif
803       CALL xios_send_field(var%name, Field2d)
804      ENDIF
805
806!$OMP END MASTER   
807  ENDIF ! vars_defined
808  IF (prt_level >= 9) WRITE(lunout,*)'End histrwrite2d_cosp ',var%name
809  END SUBROUTINE histwrite2d_cosp
810
811
812! ug NOUVELLE VERSION DES WRITE AVEC LA BOUCLE DO RENTREE
813! AI sept 2013
814  SUBROUTINE histwrite3d_cosp(var, field, nverts, ncols)
815  USE dimphy
816  USE mod_phys_lmdz_para
817  USE ioipsl
818  use iophy
819  USE mod_grid_phy_lmdz, ONLY: nbp_lon
820  USE print_control_mod, ONLY: lunout,prt_level
821
822  USE xios, only: xios_send_field
823
824
825  IMPLICIT NONE
826  INCLUDE 'clesphys.h'
827
828    TYPE(ctrl_outcosp), INTENT(IN)    :: var
829    REAL, DIMENSION(:,:), INTENT(IN)  :: field ! --> field(klon,:)
830    INTEGER, INTENT(IN), OPTIONAL     :: ncols ! ug RUSTINE POUR LES Champs 4D.....
831    INTEGER, DIMENSION(3), INTENT(IN) :: nverts
832
833    INTEGER :: iff, k
834
835    REAL,DIMENSION(klon_mpi,SIZE(field,2)) :: buffer_omp
836    REAL :: Field3d(nbp_lon,jj_nb,SIZE(field,2))
837    INTEGER :: ip, n, nlev
838    INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
839    CHARACTER(LEN=20) ::  nomi, nom
840    character(len=2) :: str2
841    LOGICAL, SAVE  :: firstx
842!$OMP THREADPRIVATE(firstx)
843
844  IF (prt_level >= 9) write(lunout,*)'Begin histrwrite3d ',var%name
845
846! ug RUSTINE POUR LES STD LEVS.....
847      IF (PRESENT(ncols)) THEN
848              write(str2,'(i2.2)')ncols
849              nomi=var%name
850              nom="c"//str2//"_"//nomi
851      ELSE
852               nom=var%name
853      END IF
854  ! On regarde si on est dans la phase de définition ou d'écriture:
855  IF(.NOT.cosp_varsdefined) THEN
856      !Si phase de définition.... on définit
857!$OMP MASTER
858      CALL conf_cospoutputs(var%name,var%cles)
859      DO iff=1, 3
860        IF (cosp_outfilekeys(iff)) THEN
861          CALL histdef3d_cosp(iff, var, nverts(iff), ncols)
862        ENDIF
863      ENDDO
864!$OMP END MASTER
865  ELSE
866    !Et sinon on.... écrit
867    IF (SIZE(field,1)/=klon) &
868   CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)                                 
869    nlev=SIZE(field,2)
870
871
872    CALL Gather_omp(field,buffer_omp)
873!$OMP MASTER
874    CALL grid1Dto2D_mpi(buffer_omp,field3d)
875
876! BOUCLE SUR LES FICHIERS
877     firstx=.true.
878     DO iff=1, 3
879        IF (var%cles(iff) .AND. cosp_outfilekeys(iff)) THEN
880           ALLOCATE(index3d(nbp_lon*jj_nb*nlev))
881
882          IF (.not. ok_all_xml) then
883           IF (firstx) THEN
884               CALL xios_send_field(nom, Field3d(:,:,1:nlev))
885               IF (prt_level >= 9) WRITE(lunout,*)'xios_send_field ',var%name
886               firstx=.FALSE.
887           ENDIF
888          ENDIF
889         deallocate(index3d)
890        ENDIF
891      ENDDO
892    IF (ok_all_xml) THEN
893     CALL xios_send_field(nom, Field3d(:,:,1:nlev))
894     IF (prt_level >= 1) WRITE(lunout,*)'xios_send_field ',var%name
895    ENDIF
896
897!$OMP END MASTER   
898  ENDIF ! vars_defined
899  IF (prt_level >= 9) write(lunout,*)'End histrwrite3d_cosp ',nom
900  END SUBROUTINE histwrite3d_cosp
901
902
903! ug NOUVELLE VERSION DES WRITE AVEC LA BOUCLE DO RENTREE
904! AI sept 2013
905  SUBROUTINE histwrite4d_cosp(var, field)
906  USE dimphy
907  USE mod_phys_lmdz_para
908  USE ioipsl
909  use iophy
910  USE mod_grid_phy_lmdz, ONLY: nbp_lon
911  USE print_control_mod, ONLY: lunout,prt_level
912
913  USE xios, only: xios_send_field
914
915
916  IMPLICIT NONE
917  INCLUDE 'clesphys.h'
918
919    TYPE(ctrl_outcosp), INTENT(IN)    :: var
920    REAL, DIMENSION(:,:,:), INTENT(IN)  :: field ! --> field(klon,:)
921
922    INTEGER :: iff, k
923
924    REAL,DIMENSION(klon_mpi,SIZE(field,2),SIZE(field,3)) :: buffer_omp
925    REAL :: field4d(nbp_lon,jj_nb,SIZE(field,2),SIZE(field,3))
926    INTEGER :: ip, n, nlev, nlev2
927    INTEGER, ALLOCATABLE, DIMENSION(:) :: index4d
928    CHARACTER(LEN=20) ::  nomi, nom
929
930  IF (prt_level >= 9) write(lunout,*)'Begin histrwrite4d ',var%name
931
932  IF(cosp_varsdefined) THEN
933    !Et sinon on.... écrit
934    IF (SIZE(field,1)/=klon) &
935   CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)           
936
937    nlev=SIZE(field,2)
938    nlev2=SIZE(field,3)
939    CALL Gather_omp(field,buffer_omp)
940!$OMP MASTER
941    CALL grid1Dto2D_mpi(buffer_omp,field4d)
942
943!    IF (ok_all_xml) THEN
944     CALL xios_send_field(var%name, Field4d(:,:,1:nlev,1:nlev2))
945     IF (prt_level >= 1) WRITE(lunout,*)'xios_send_field ',var%name
946!    ENDIF
947
948!$OMP END MASTER   
949  ENDIF ! vars_defined
950  IF (prt_level >= 9) write(lunout,*)'End histrwrite4d_cosp ',nom
951  END SUBROUTINE histwrite4d_cosp
952
953  SUBROUTINE conf_cospoutputs(nam_var,cles_var)
954!!! Lecture des noms et cles de sortie des variables dans config.def
955    !   en utilisant les routines getin de IOIPSL 
956    use ioipsl
957    USE print_control_mod, ONLY: lunout,prt_level
958
959    IMPLICIT NONE
960
961   CHARACTER(LEN=20)               :: nam_var, nnam_var
962   LOGICAL, DIMENSION(3)           :: cles_var
963
964! Lecture dans config.def ou output.def de cles_var et name_var
965    CALL getin('cles_'//nam_var,cles_var)
966    CALL getin('name_'//nam_var,nam_var)
967    IF(prt_level>10) WRITE(lunout,*)'nam_var cles_var ',nam_var,cles_var(:)
968
969  END SUBROUTINE conf_cospoutputs
970
971 END MODULE lmdz_cosp_output_write_mod
Note: See TracBrowser for help on using the repository browser.