source: LMDZ6/trunk/libf/phylmd/cosp/cosp_output_write_mod.F90

Last change on this file was 4619, checked in by yann meurdesoif, 12 months ago

Suppress usage of preprocessing key CPP_XIOS.
Wrapper file is used to suppress XIOS symbol when xios is not linked and not used (-io ioipsl)
The CPP_XIOS key is replaced in model by "using_xios" boolean variable to switch between IOIPSL or XIOS output.

YM

File size: 31.0 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   MODULE cosp_output_write_mod
5 
6   USE cosp_output_mod
7 
8   IMPLICIT NONE
9
10   INTEGER, SAVE  :: itau_iocosp
11!$OMP THREADPRIVATE(itau_iocosp)
12   INTEGER, save        :: Nlevout, Ncolout
13!$OMP THREADPRIVATE(Nlevout, Ncolout)
14
15!  INTERFACE histwrite_cosp
16!    MODULE PROCEDURE histwrite2d_cosp,histwrite3d_cosp
17!  END INTERFACE
18
19   CONTAINS
20
21  SUBROUTINE cosp_output_write(Nlevlmdz, Npoints, Ncolumns, itap, dtime, freq_COSP, missing_cosp, &
22                               cfg, gbx, vgrid, sglidar, sgradar, stlidar, stradar, &
23                               isccp, misr, modis)
24
25    USE ioipsl
26    USE time_phylmdz_mod, ONLY: itau_phy, start_time, day_step_phy
27    USE print_control_mod, ONLY: lunout,prt_level
28    USE wxios, only: wxios_closedef
29    USE lmdz_xios, only: xios_update_calendar, xios_field_is_active, using_xios
30  IMPLICIT NONE 
31!!! Variables d'entree
32  integer               :: itap, Nlevlmdz, Ncolumns, Npoints
33  real                  :: freq_COSP, dtime, missing_val, missing_cosp
34  type(cosp_config)     :: cfg     ! Control outputs
35  type(cosp_gridbox)    :: gbx     ! Gridbox information. Input for COSP
36  type(cosp_sglidar)    :: sglidar ! Output from lidar simulator
37  type(cosp_sgradar)    :: sgradar ! Output from radar simulator
38  type(cosp_isccp)      :: isccp   ! Output from ISCCP simulator
39  type(cosp_lidarstats) :: stlidar ! Summary statistics from lidar simulator
40  type(cosp_radarstats) :: stradar
41  type(cosp_misr)       :: misr    ! Output from MISR
42  type(cosp_modis)      :: modis   ! Outputs from Modis
43  type(cosp_vgrid)      :: vgrid   ! Information on vertical grid of stats
44
45!!! Variables locales
46  integer               :: icl,k,ip
47  logical               :: ok_sync
48  integer               :: itau_wcosp, iff
49  real, dimension(Npoints,PARASOL_NREFL) :: parasolcrefl, Ncref
50
51! Variables locals intermidiaires pour inverser les axes des champs 4D
52! Compatibilite avec sorties CMIP
53  real, dimension(Npoints,Nlevout,SR_BINS) :: tmp_fi4da_cfadL
54  real, dimension(Npoints,Nlevout,DBZE_BINS) :: tmp_fi4da_cfadR
55  real, dimension(Npoints,MISR_N_CTH,7) :: tmp_fi4da_misr
56
57  IF (using_xios) THEN
58    missing_val=missing_cosp
59  ELSE
60    missing_val=0.
61  ENDIF
62
63  Nlevout = vgrid%Nlvgrid
64  Ncolout = Ncolumns
65
66! A refaire
67       itau_wcosp = itau_phy + itap + start_time * day_step_phy
68        if (prt_level >= 10) then
69             WRITE(lunout,*)'itau_wcosp, itap, start_time, day_step_phy =', &
70                             itau_wcosp, itap, start_time, day_step_phy
71        endif
72
73! On le donne a  cosp_output_write_mod pour que les histwrite y aient acces:
74       CALL set_itau_iocosp(itau_wcosp)
75        if (prt_level >= 10) then
76              WRITE(lunout,*)'itau_iocosp =',itau_iocosp
77        endif
78
79    ok_sync = .TRUE.
80   
81!DO iinit=1, iinitend
82! AI sept 2014 cette boucle supprimee
83! On n'ecrit pas quand itap=1 (cosp)
84
85!   if (prt_level >= 10) then
86!         WRITE(lunout,*)'DO iinit=1, iinitend ',iinitend
87!   endif
88
89!!IF (using_xios) THEN
90! !$OMP MASTER
91!IF (cosp_varsdefined) THEN
92!   if (prt_level >= 10) then
93!         WRITE(lunout,*)'Apell xios_update_calendar cosp_varsdefined iinitend ', &
94!                         cosp_varsdefined,iinitend
95!   endif
96!    CALL xios_update_calendar(itau_wcosp)
97!ENDIF
98!  !$OMP END MASTER
99!  !$OMP BARRIER
100!!ENDIF
101
102!!!! Sorties Calipso
103 if (cfg%Llidar_sim) then
104!!! AI 02 2018
105! Traitement missing_val
106   where(stlidar%lidarcld == R_UNDEF) stlidar%lidarcld = missing_val
107   where(stlidar%proftemp == R_UNDEF) stlidar%proftemp = missing_val   !TIBO 
108   where(stlidar%profSR == R_UNDEF) stlidar%profSR = missing_val       !TIBO2
109   where(sglidar%beta_mol == R_UNDEF) sglidar%beta_mol = missing_val 
110   where(sglidar%beta_tot == R_UNDEF) sglidar%beta_tot = missing_val
111   where(stlidar%cldlayer == R_UNDEF) stlidar%cldlayer = missing_val
112   where(stlidar%cldtype == R_UNDEF) stlidar%cldtype = missing_val     !OPAQ
113   where(stlidar%cfad_sr == R_UNDEF) stlidar%cfad_sr = missing_val
114! AI 11 / 2015
115   where(stlidar%parasolrefl == R_UNDEF) stlidar%parasolrefl = missing_val
116   where(stlidar%lidarcldtmp == R_UNDEF) stlidar%lidarcldtmp = missing_val
117   where(stlidar%cldlayerphase == R_UNDEF) stlidar%cldlayerphase = missing_val
118   where(stlidar%lidarcldphase == R_UNDEF) stlidar%lidarcldphase = missing_val
119   where(stlidar%lidarcldtype == R_UNDEF) stlidar%lidarcldtype = missing_val   !OPAQ
120   where(stlidar%lidarcldtmp == R_UNDEF) stlidar%lidarcldtmp = missing_val
121 
122!   print*,'Appel histwrite2d_cosp'
123   if (cfg%Lcllcalipso) CALL histwrite2d_cosp(o_cllcalipso,stlidar%cldlayer(:,1))
124   if (cfg%Lclhcalipso) CALL histwrite2d_cosp(o_clhcalipso,stlidar%cldlayer(:,3))
125   if (cfg%Lclmcalipso) CALL histwrite2d_cosp(o_clmcalipso,stlidar%cldlayer(:,2))
126   if (cfg%Lcltcalipso) CALL histwrite2d_cosp(o_cltcalipso,stlidar%cldlayer(:,4))
127   if (cfg%Lclcalipso) CALL histwrite3d_cosp(o_clcalipso,stlidar%lidarcld,nvert)
128   if (cfg%Lclcalipsotmp) CALL histwrite3d_cosp(o_clcalipsotmp,stlidar%lidarcldtmp(:,:,1),nverttemp)
129
130   if (cfg%Lcllcalipsoice) CALL histwrite2d_cosp(o_cllcalipsoice,stlidar%cldlayerphase(:,1,1))
131   if (cfg%Lclhcalipsoice) CALL histwrite2d_cosp(o_clhcalipsoice,stlidar%cldlayerphase(:,3,1))
132   if (cfg%Lclmcalipsoice) CALL histwrite2d_cosp(o_clmcalipsoice,stlidar%cldlayerphase(:,2,1))
133   if (cfg%Lcltcalipsoice) CALL histwrite2d_cosp(o_cltcalipsoice,stlidar%cldlayerphase(:,4,1))
134   if (cfg%Lclcalipsoice) CALL histwrite3d_cosp(o_clcalipsoice,stlidar%lidarcldphase(:,:,1),nvert)
135   if (cfg%Lclcalipsotmpice) CALL histwrite3d_cosp(o_clcalipsotmpice,stlidar%lidarcldtmp(:,:,2),nverttemp)
136
137   if (cfg%Lcllcalipsoliq) CALL histwrite2d_cosp(o_cllcalipsoliq,stlidar%cldlayerphase(:,1,2))
138   if (cfg%Lclhcalipsoliq) CALL histwrite2d_cosp(o_clhcalipsoliq,stlidar%cldlayerphase(:,3,2))
139   if (cfg%Lclmcalipsoliq) CALL histwrite2d_cosp(o_clmcalipsoliq,stlidar%cldlayerphase(:,2,2))
140   if (cfg%Lcltcalipsoliq) CALL histwrite2d_cosp(o_cltcalipsoliq,stlidar%cldlayerphase(:,4,2))
141   if (cfg%Lclcalipsoliq) CALL histwrite3d_cosp(o_clcalipsoliq,stlidar%lidarcldphase(:,:,2),nvert)
142   if (cfg%Lclcalipsotmpliq) CALL histwrite3d_cosp(o_clcalipsotmpliq,stlidar%lidarcldtmp(:,:,3),nverttemp)
143
144   if (cfg%Lcllcalipsoun) CALL histwrite2d_cosp(o_cllcalipsoun,stlidar%cldlayerphase(:,1,3))
145   if (cfg%Lclhcalipsoun) CALL histwrite2d_cosp(o_clhcalipsoun,stlidar%cldlayerphase(:,3,3))
146   if (cfg%Lclmcalipsoun) CALL histwrite2d_cosp(o_clmcalipsoun,stlidar%cldlayerphase(:,2,3))
147   if (cfg%Lcltcalipsoun) CALL histwrite2d_cosp(o_cltcalipsoun,stlidar%cldlayerphase(:,4,3))
148   if (cfg%Lclcalipsoun) CALL histwrite3d_cosp(o_clcalipsoun,stlidar%lidarcldphase(:,:,3),nvert)
149   if (cfg%Lclcalipsotmpun) CALL histwrite3d_cosp(o_clcalipsotmpun,stlidar%lidarcldtmp(:,:,4),nverttemp)
150
151   if (cfg%Lclopaquecalipso) CALL histwrite2d_cosp(o_clopaquecalipso,stlidar%cldtype(:,1))               !OPAQ
152   if (cfg%Lclthincalipso) CALL histwrite2d_cosp(o_clthincalipso,stlidar%cldtype(:,2))                 !OPAQ
153   if (cfg%Lclzopaquecalipso) CALL histwrite2d_cosp(o_clzopaquecalipso,stlidar%cldtype(:,3))              !OPAQ
154
155   if (cfg%Lclcalipsoopaque) CALL histwrite3d_cosp(o_clcalipsoopaque,stlidar%lidarcldtype(:,:,1),nvert)  !OPAQ
156   if (cfg%Lclcalipsothin) CALL histwrite3d_cosp(o_clcalipsothin,stlidar%lidarcldtype(:,:,2),nvert)    !OPAQ
157   if (cfg%Lclcalipsozopaque) CALL histwrite3d_cosp(o_clcalipsozopaque,stlidar%lidarcldtype(:,:,3),nvert) !OPAQ
158   if (cfg%Lclcalipsoopacity) CALL histwrite3d_cosp(o_clcalipsoopacity,stlidar%lidarcldtype(:,:,4),nvert) !OPAQ
159
160   if (cfg%Lproftemp) CALL histwrite3d_cosp(o_proftemp,stlidar%proftemp,nvert)                    !TIBO
161
162   IF (using_xios) THEN
163     do icl=1,SR_BINS
164        tmp_fi4da_cfadL(:,:,icl)=stlidar%cfad_sr(:,icl,:)
165     enddo
166  !   if (cfg%LcfadLidarsr532) CALL histwrite4d_cosp(o_cfad_lidarsr532,stlidar%cfad_sr)
167     if (cfg%LcfadLidarsr532) CALL histwrite4d_cosp(o_cfad_lidarsr532,tmp_fi4da_cfadL)
168     if (cfg%LprofSR) CALL histwrite4d_cosp(o_profSR,stlidar%profSR)                              !TIBO
169   ELSE
170     if (cfg%LcfadLidarsr532) then
171       do icl=1,SR_BINS
172          CALL histwrite3d_cosp(o_cfad_lidarsr532,stlidar%cfad_sr(:,icl,:),nvert,icl)
173       enddo
174     endif
175     if (cfg%LprofSR) then
176       do icl=1,Ncolumns                                                              !TIBO
177          CALL histwrite3d_cosp(o_profSR,stlidar%profSR(:,icl,:),nvert,icl)           !TIBO
178       enddo                                                                          !TIBO
179      endif
180   ENDIF
181
182   if (cfg%LparasolRefl) CALL histwrite3d_cosp(o_parasol_refl,stlidar%parasolrefl,nvertp)
183
184  if (cfg%LparasolRefl) then
185    do k=1,PARASOL_NREFL
186     do ip=1, Npoints
187      if (stlidar%cldlayer(ip,4).gt.0.01.and.stlidar%parasolrefl(ip,k).ne.missing_val) then
188        parasolcrefl(ip,k)=(stlidar%parasolrefl(ip,k)-0.03*(1.-stlidar%cldlayer(ip,4)))/ &
189                             stlidar%cldlayer(ip,4)
190         Ncref(ip,k) = 1.
191      else
192         parasolcrefl(ip,k)=missing_val
193         Ncref(ip,k) = 0.
194      endif
195     enddo
196    enddo
197    CALL histwrite3d_cosp(o_Ncrefl,Ncref,nvertp)
198    CALL histwrite3d_cosp(o_parasol_crefl,parasolcrefl,nvertp)
199  endif
200
201   IF (using_xios) THEN
202     if (cfg%Latb532) CALL histwrite4d_cosp(o_atb532,sglidar%beta_tot)
203   ELSE
204     if (cfg%Latb532) then 
205       do icl=1,Ncolumns
206          CALL histwrite3d_cosp(o_atb532,sglidar%beta_tot(:,icl,:),nvertmcosp,icl)
207       enddo
208     endif
209   ENDIF
210
211   if (cfg%LlidarBetaMol532) CALL histwrite3d_cosp(o_beta_mol532,sglidar%beta_mol,nvertmcosp)
212
213 endif !Lidar
214
215!!! Sorties Cloudsat
216 if (cfg%Lradar_sim) then
217
218   where(stradar%cfad_ze == R_UNDEF) stradar%cfad_ze = missing_val
219   IF (using_xios) THEN
220     do icl=1,DBZE_BINS
221       tmp_fi4da_cfadR(:,:,icl)=stradar%cfad_ze(:,icl,:)
222     enddo
223     if (cfg%Ldbze94) CALL histwrite4d_cosp(o_dbze94,sgradar%Ze_tot)
224  !  if (cfg%LcfadDbze94) CALL histwrite4d_cosp(o_cfadDbze94,stradar%cfad_ze)
225     if (cfg%LcfadDbze94) CALL histwrite4d_cosp(o_cfadDbze94,tmp_fi4da_cfadR)
226   ELSE
227     if (cfg%Ldbze94) then
228       do icl=1,Ncolumns
229         CALL histwrite3d_cosp(o_dbze94,sgradar%Ze_tot(:,icl,:),nvert,icl)
230       enddo
231     endif
232     if (cfg%LcfadDbze94) then
233       do icl=1,DBZE_BINS
234         CALL histwrite3d_cosp(o_cfadDbze94,stradar%cfad_ze(:,icl,:),nvert,icl)
235       enddo
236     endif
237   ENDIF
238 endif
239! endif pour radar
240
241!!! Sorties combinees Cloudsat et Calipso
242 if (cfg%Llidar_sim .and. cfg%Lradar_sim) then
243   where(stradar%lidar_only_freq_cloud == R_UNDEF) &
244                           stradar%lidar_only_freq_cloud = missing_val
245   if (cfg%Lclcalipso) CALL histwrite3d_cosp(o_clcalipso2,stradar%lidar_only_freq_cloud,nvert)
246   where(stradar%radar_lidar_tcc == R_UNDEF) &
247                           stradar%radar_lidar_tcc = missing_val
248   if (cfg%Lcltlidarradar) CALL histwrite2d_cosp(o_cltlidarradar,stradar%radar_lidar_tcc)
249 endif
250
251!!! Sorties Isccp
252 if (cfg%Lisccp_sim) then
253  where(isccp%totalcldarea == R_UNDEF) isccp%totalcldarea = missing_val
254  where(isccp%meanptop == R_UNDEF) isccp%meanptop = missing_val
255  where(isccp%meantaucld == R_UNDEF) isccp%meantaucld = missing_val
256  where(isccp%meanalbedocld == R_UNDEF) isccp%meanalbedocld = missing_val
257  where(isccp%meantb == R_UNDEF) isccp%meantb = missing_val
258  where(isccp%meantbclr == R_UNDEF) isccp%meantbclr = missing_val
259  where(isccp%fq_isccp == R_UNDEF) isccp%fq_isccp = missing_val
260  where(isccp%boxtau == R_UNDEF) isccp%boxtau = missing_val
261  where(isccp%boxptop == R_UNDEF) isccp%boxptop = missing_val
262
263   CALL histwrite2d_cosp(o_sunlit,gbx%sunlit)
264   IF (using_xios) THEN
265     if (cfg%Lclisccp) CALL histwrite4d_cosp(o_clisccp2,isccp%fq_isccp)
266   ELSE
267     if (cfg%Lclisccp) then
268       do icl=1,7
269         CALL histwrite3d_cosp(o_clisccp2,isccp%fq_isccp(:,icl,:),nvertisccp,icl)
270       enddo
271     endif
272   ENDIF
273
274   if (cfg%Lboxtauisccp) CALL histwrite3d_cosp(o_boxtauisccp,isccp%boxtau,nvertcol)
275   if (cfg%Lboxptopisccp) CALL histwrite3d_cosp(o_boxptopisccp,isccp%boxptop,nvertcol)
276   if (cfg%Lcltisccp) CALL histwrite2d_cosp(o_tclisccp,isccp%totalcldarea)
277   if (cfg%Lpctisccp) CALL histwrite2d_cosp(o_ctpisccp,isccp%meanptop)
278   if (cfg%Ltauisccp) CALL histwrite2d_cosp(o_tauisccp,isccp%meantaucld)
279   if (cfg%Lalbisccp) CALL histwrite2d_cosp(o_albisccp,isccp%meanalbedocld)
280   if (cfg%Lmeantbisccp) CALL histwrite2d_cosp(o_meantbisccp,isccp%meantb)
281   if (cfg%Lmeantbclrisccp) CALL histwrite2d_cosp(o_meantbclrisccp,isccp%meantbclr)
282 endif ! Isccp
283
284!!! MISR simulator
285 if (cfg%Lmisr_sim) then
286   where(misr%fq_MISR == R_UNDEF) misr%fq_MISR = missing_val
287
288   IF (using_xios) THEN
289     do icl=1,MISR_N_CTH
290        tmp_fi4da_misr(:,icl,:)=misr%fq_MISR(:,:,icl)
291     enddo
292  !   if (cfg%LclMISR) CALL histwrite4d_cosp(o_clMISR,misr%fq_MISR)
293     if (cfg%LclMISR) CALL histwrite4d_cosp(o_clMISR,tmp_fi4da_misr)
294   ELSE
295     if (cfg%LclMISR) then
296      do icl=1,7
297        CALL histwrite3d_cosp(o_clMISR,misr%fq_MISR(:,icl,:),nvertmisr,icl)
298      enddo
299     endif
300   ENDIF
301 endif
302! endif pour Misr
303
304!!! Modis simulator
305 if (cfg%Lmodis_sim) then
306  where(modis%Cloud_Fraction_Low_Mean == R_UNDEF) &
307        modis%Cloud_Fraction_Low_Mean = missing_val
308  where(modis%Cloud_Fraction_High_Mean == R_UNDEF) &
309        modis%Cloud_Fraction_High_Mean = missing_val
310  where(modis%Cloud_Fraction_Mid_Mean == R_UNDEF) &
311        modis%Cloud_Fraction_Mid_Mean = missing_val
312  where(modis%Cloud_Fraction_Total_Mean == R_UNDEF) &
313        modis%Cloud_Fraction_Total_Mean = missing_val
314  where(modis%Cloud_Fraction_Water_Mean == R_UNDEF) &
315        modis%Cloud_Fraction_Water_Mean = missing_val
316  where(modis%Cloud_Fraction_Ice_Mean == R_UNDEF) &
317        modis%Cloud_Fraction_Ice_Mean = missing_val
318  where(modis%Optical_Thickness_Total_Mean == R_UNDEF) &
319        modis%Optical_Thickness_Total_Mean = missing_val
320  where(modis%Optical_Thickness_Water_Mean == R_UNDEF) &
321        modis%Optical_Thickness_Water_Mean = missing_val
322  where(modis%Optical_Thickness_Ice_Mean == R_UNDEF) &
323        modis%Optical_Thickness_Ice_Mean = missing_val
324  where(modis%Cloud_Particle_Size_Water_Mean == R_UNDEF) &
325        modis%Cloud_Particle_Size_Water_Mean = missing_val
326  where(modis%Cloud_Particle_Size_Ice_Mean == R_UNDEF) &
327        modis%Cloud_Particle_Size_Ice_Mean = missing_val
328  where(modis%Cloud_Top_Pressure_Total_Mean == R_UNDEF) &
329        modis%Cloud_Top_Pressure_Total_Mean = missing_val
330  where(modis%Liquid_Water_Path_Mean == R_UNDEF) &
331        modis%Liquid_Water_Path_Mean = missing_val
332  where(modis%Ice_Water_Path_Mean == R_UNDEF) &
333        modis%Ice_Water_Path_Mean = missing_val
334
335  where(modis%Optical_Thickness_Total_LogMean == R_UNDEF) &
336          modis%Optical_Thickness_Total_LogMean = missing_val
337           
338  where(modis%Optical_Thickness_Water_LogMean == R_UNDEF) &
339          modis%Optical_Thickness_Water_LogMean = missing_val
340
341  where(modis%Optical_Thickness_Ice_LogMean == R_UNDEF) &
342          modis%Optical_Thickness_Ice_LogMean = missing_val
343   
344  if (cfg%Lcllmodis) CALL histwrite2d_cosp(o_cllmodis,modis%Cloud_Fraction_Low_Mean)
345  if (cfg%Lclhmodis) CALL histwrite2d_cosp(o_clhmodis,modis%Cloud_Fraction_High_Mean)
346  if (cfg%Lclmmodis) CALL histwrite2d_cosp(o_clmmodis,modis%Cloud_Fraction_Mid_Mean)
347  if (cfg%Lcltmodis) CALL histwrite2d_cosp(o_cltmodis,modis%Cloud_Fraction_Total_Mean)
348  if (cfg%Lclwmodis) CALL histwrite2d_cosp(o_clwmodis,modis%Cloud_Fraction_Water_Mean)
349  if (cfg%Lclimodis) CALL histwrite2d_cosp(o_climodis,modis%Cloud_Fraction_Ice_Mean)
350  if (cfg%Ltautmodis)  CALL histwrite2d_cosp(o_tautmodis,modis%Optical_Thickness_Total_Mean)
351  if (cfg%Ltauwmodis) CALL histwrite2d_cosp(o_tauwmodis,modis%Optical_Thickness_Water_Mean)
352  if (cfg%Ltauimodis) CALL histwrite2d_cosp(o_tauimodis,modis%Optical_Thickness_Ice_Mean)
353  if (cfg%Ltautlogmodis) CALL histwrite2d_cosp(o_tautlogmodis,modis%Optical_Thickness_Total_LogMean) 
354  if (cfg%Ltauwlogmodis) CALL histwrite2d_cosp(o_tauwlogmodis,modis%Optical_Thickness_Water_LogMean)
355  if (cfg%Ltauilogmodis) CALL histwrite2d_cosp(o_tauilogmodis,modis%Optical_Thickness_Ice_LogMean)
356  if (cfg%Lreffclwmodis) CALL histwrite2d_cosp(o_reffclwmodis,modis%Cloud_Particle_Size_Water_Mean)
357  if (cfg%Lreffclimodis) CALL histwrite2d_cosp(o_reffclimodis,modis%Cloud_Particle_Size_Ice_Mean)
358  if (cfg%Lpctmodis) CALL histwrite2d_cosp(o_pctmodis,modis%Cloud_Top_Pressure_Total_Mean)
359  if (cfg%Llwpmodis) CALL histwrite2d_cosp(o_lwpmodis,modis%Liquid_Water_Path_Mean)
360  if (cfg%Liwpmodis) CALL histwrite2d_cosp(o_iwpmodis,modis%Ice_Water_Path_Mean)
361
362    where(modis%Optical_Thickness_vs_Cloud_Top_Pressure == R_UNDEF) &
363          modis%Optical_Thickness_vs_Cloud_Top_Pressure = missing_val
364
365   IF (using_xios) THEN
366     if (cfg%Lclmodis) CALL histwrite4d_cosp(o_clmodis,modis%Optical_Thickness_vs_Cloud_Top_Pressure)
367   ELSE
368     if (cfg%Lclmodis) then
369       do icl=1,7
370         CALL histwrite3d_cosp(o_clmodis, &
371         modis%Optical_Thickness_vs_Cloud_Top_Pressure(:,icl,:),nvertisccp,icl)           
372       enddo
373      endif
374   ENDIF
375
376    where(modis%Optical_Thickness_vs_ReffIce == R_UNDEF) &
377          modis%Optical_Thickness_vs_ReffIce = missing_val
378
379    where(modis%Optical_Thickness_vs_ReffLiq == R_UNDEF) &
380          modis%Optical_Thickness_vs_ReffLiq = missing_val
381
382   IF (using_xios) THEN
383     if (cfg%Lcrimodis) CALL histwrite4d_cosp(o_crimodis,modis%Optical_Thickness_vs_ReffIce)
384     if (cfg%Lcrlmodis) CALL histwrite4d_cosp(o_crlmodis,modis%Optical_Thickness_vs_ReffLiq)
385   ELSE
386     if (cfg%Lcrimodis) then
387       do icl=1,7
388         CALL histwrite3d_cosp(o_crimodis, &
389            modis%Optical_Thickness_vs_ReffIce(:,icl,:),nvertReffIce,icl)
390       enddo
391     endif
392     if (cfg%Lcrlmodis) then
393       do icl=1,7
394         CALL histwrite3d_cosp(o_crlmodis, &
395            modis%Optical_Thickness_vs_ReffLiq(:,icl,:),nvertReffLiq,icl)
396       enddo
397     endif
398   ENDIF
399 endif !modis
400
401 IF(.NOT.cosp_varsdefined) THEN
402!$OMP MASTER
403#ifndef CPP_IOIPSL_NO_OUTPUT
404            DO iff=1,3
405                IF (cosp_outfilekeys(iff)) THEN
406                  CALL histend(cosp_nidfiles(iff))
407                ENDIF ! cosp_outfilekeys
408            ENDDO !  iff
409#endif
410
411!$OMP END MASTER
412!$OMP BARRIER
413            cosp_varsdefined = .TRUE.
414 END IF
415
416    IF(cosp_varsdefined) THEN
417! On synchronise les fichiers pour IOIPSL
418#ifndef CPP_IOIPSL_NO_OUTPUT
419!$OMP MASTER
420     DO iff=1,3
421         IF (ok_sync .AND. cosp_outfilekeys(iff)) THEN
422             CALL histsync(cosp_nidfiles(iff))
423         ENDIF
424     END DO
425!$OMP END MASTER
426#endif
427    ENDIF  !cosp_varsdefined
428
429    END SUBROUTINE cosp_output_write
430
431! ug Routine pour definir itau_iocosp depuis cosp_output_write_mod:
432  SUBROUTINE set_itau_iocosp(ito)
433      IMPLICIT NONE
434      INTEGER, INTENT(IN) :: ito
435      itau_iocosp = ito
436  END SUBROUTINE
437
438  SUBROUTINE histdef2d_cosp (iff,var)
439
440    USE ioipsl
441    USE dimphy
442    use iophy
443    USE mod_phys_lmdz_para
444    USE mod_grid_phy_lmdz, ONLY: nbp_lon
445    USE print_control_mod, ONLY: lunout,prt_level
446    USE wxios
447
448    IMPLICIT NONE
449
450    INCLUDE "clesphys.h"
451
452    INTEGER                          :: iff
453    TYPE(ctrl_outcosp)               :: var
454
455    REAL zstophym
456    CHARACTER(LEN=20) :: typeecrit
457
458    ! ug On récupère le type écrit de la structure:
459    !       Assez moche, Ã|  refaire si meilleure méthode...
460    IF (INDEX(var%cosp_typeecrit(iff), "once") > 0) THEN
461       typeecrit = 'once'
462    ELSE IF(INDEX(var%cosp_typeecrit(iff), "t_min") > 0) THEN
463       typeecrit = 't_min(X)'
464    ELSE IF(INDEX(var%cosp_typeecrit(iff), "t_max") > 0) THEN
465       typeecrit = 't_max(X)'
466    ELSE IF(INDEX(var%cosp_typeecrit(iff), "inst") > 0) THEN
467       typeecrit = 'inst(X)'
468    ELSE
469       typeecrit = cosp_outfiletypes(iff)
470    ENDIF
471
472    IF (typeecrit=='inst(X)'.OR.typeecrit=='once') THEN
473       zstophym=zoutm_cosp(iff)
474    ELSE
475       zstophym=zdtimemoy_cosp
476    ENDIF
477
478    IF (using_xios) THEN
479      IF (.not. ok_all_xml) then
480        IF ( var%cles(iff) ) THEN
481          if (prt_level >= 10) then
482            WRITE(lunout,*)'Appel wxios_add_field_to_file var%name =',var%name
483          endif
484          CALL wxios_add_field_to_file(var%name, 2, cosp_nidfiles(iff), cosp_outfilenames(iff), &
485                                     var%description, var%unit, 1, typeecrit)
486        ENDIF
487      ENDIF
488    ENDIF
489
490#ifndef CPP_IOIPSL_NO_OUTPUT
491       IF ( var%cles(iff) ) THEN
492          CALL histdef (cosp_nidfiles(iff), var%name, var%description, var%unit, &
493               nbp_lon,jj_nb,nhoricosp(iff), 1,1,1, -99, 32, &
494               typeecrit, zstophym,zoutm_cosp(iff))
495       ENDIF
496#endif
497
498  END SUBROUTINE histdef2d_cosp
499
500 SUBROUTINE histdef3d_cosp (iff,var,nvertsave,ncols)
501    USE ioipsl
502    USE dimphy
503    use iophy
504    USE mod_phys_lmdz_para
505    USE mod_grid_phy_lmdz, ONLY: nbp_lon
506    USE print_control_mod, ONLY: lunout,prt_level
507    USE wxios
508
509    IMPLICIT NONE
510
511    INCLUDE "clesphys.h"
512
513    INTEGER                        :: iff, klevs
514    INTEGER, INTENT(IN), OPTIONAL  :: ncols ! ug RUSTINE POUR LES variables 4D
515    INTEGER, INTENT(IN)           :: nvertsave
516    TYPE(ctrl_outcosp)             :: var
517
518    REAL zstophym
519    CHARACTER(LEN=20) :: typeecrit, nomi
520    CHARACTER(LEN=20) :: nom
521    character(len=2) :: str2
522    CHARACTER(len=20) :: nam_axvert
523
524! Axe vertical
525      IF (nvertsave.eq.nvertp(iff)) THEN
526          klevs=PARASOL_NREFL
527          nam_axvert="sza"
528      ELSE IF (nvertsave.eq.nvertisccp(iff)) THEN
529          klevs=7
530          nam_axvert="pressure2"
531      ELSE IF (nvertsave.eq.nvertcol(iff)) THEN
532          klevs=Ncolout
533          nam_axvert="column"
534      ELSE IF (nvertsave.eq.nverttemp(iff)) THEN
535          klevs=LIDAR_NTEMP
536          nam_axvert="temp"
537      ELSE IF (nvertsave.eq.nvertmisr(iff)) THEN
538          klevs=MISR_N_CTH
539          nam_axvert="cth16"
540      ELSE IF (nvertsave.eq.nvertReffIce(iff)) THEN
541          klevs= numMODISReffIceBins
542          nam_axvert="ReffIce"
543      ELSE IF (nvertsave.eq.nvertReffLiq(iff)) THEN
544          klevs= numMODISReffLiqBins
545          nam_axvert="ReffLiq"
546      ELSE
547           klevs=Nlevout
548           nam_axvert="presnivs"
549      ENDIF
550
551! ug RUSTINE POUR LES Champs 4D
552      IF (PRESENT(ncols)) THEN
553               write(str2,'(i2.2)')ncols
554               nomi=var%name
555               nom="c"//str2//"_"//nomi
556      ELSE
557               nom=var%name
558      END IF
559
560    ! ug On récupère le type écrit de la structure:
561    !       Assez moche, Ã|  refaire si meilleure méthode...
562    IF (INDEX(var%cosp_typeecrit(iff), "once") > 0) THEN
563       typeecrit = 'once'
564    ELSE IF(INDEX(var%cosp_typeecrit(iff), "t_min") > 0) THEN
565       typeecrit = 't_min(X)'
566    ELSE IF(INDEX(var%cosp_typeecrit(iff), "t_max") > 0) THEN
567       typeecrit = 't_max(X)'
568    ELSE IF(INDEX(var%cosp_typeecrit(iff), "inst") > 0) THEN
569       typeecrit = 'inst(X)'
570    ELSE
571       typeecrit = cosp_outfiletypes(iff)
572    ENDIF
573
574    IF (typeecrit=='inst(X)'.OR.typeecrit=='once') THEN
575       zstophym=zoutm_cosp(iff)
576    ELSE
577       zstophym=zdtimemoy_cosp
578    ENDIF
579
580    IF (using_xios) THEN
581      IF (.not. ok_all_xml) then
582        IF ( var%cles(iff) ) THEN
583          if (prt_level >= 10) then
584              WRITE(lunout,*)'Appel wxios_add_field_to_file 3d nom variable nam_axvert = ',nom, nam_axvert
585          endif
586          CALL wxios_add_field_to_file(nom, 3, cosp_nidfiles(iff), cosp_outfilenames(iff), &
587                                       var%description, var%unit, 1, typeecrit, nam_axvert)
588        ENDIF
589      ENDIF
590    ENDIF
591
592#ifndef CPP_IOIPSL_NO_OUTPUT
593       IF ( var%cles(iff) ) THEN
594          CALL histdef (cosp_nidfiles(iff), nom, var%description, var%unit, &
595               nbp_lon, jj_nb, nhoricosp(iff), klevs, 1, &
596               klevs, nvertsave, 32, typeecrit, &
597               zstophym, zoutm_cosp(iff))
598       ENDIF
599#endif
600
601  END SUBROUTINE histdef3d_cosp
602
603 SUBROUTINE histwrite2d_cosp(var,field)
604  USE dimphy
605  USE mod_phys_lmdz_para
606  USE ioipsl
607  use iophy
608  USE mod_grid_phy_lmdz, ONLY: nbp_lon
609  USE print_control_mod, ONLY: lunout,prt_level
610  USE lmdz_xios, only: xios_send_field, using_xios
611
612  IMPLICIT NONE
613  INCLUDE 'clesphys.h'
614
615    TYPE(ctrl_outcosp), INTENT(IN) :: var
616    REAL, DIMENSION(:), INTENT(IN) :: field
617
618    INTEGER :: iff
619
620    REAL,DIMENSION(klon_mpi) :: buffer_omp
621    INTEGER, allocatable, DIMENSION(:) :: index2d
622    REAL :: Field2d(nbp_lon,jj_nb)
623    CHARACTER(LEN=20) ::  nomi, nom
624    character(len=2) :: str2
625    LOGICAL, SAVE  :: firstx
626!$OMP THREADPRIVATE(firstx)
627
628    IF (prt_level >= 9) WRITE(lunout,*)'Begin histrwrite2d ',var%name
629
630  ! On regarde si on est dans la phase de définition ou d'écriture:
631  IF(.NOT.cosp_varsdefined) THEN
632!$OMP MASTER
633      !Si phase de définition.... on définit
634      CALL conf_cospoutputs(var%name,var%cles)
635      DO iff=1, 3
636         IF (cosp_outfilekeys(iff)) THEN
637            CALL histdef2d_cosp(iff, var)
638         ENDIF
639      ENDDO
640!$OMP END MASTER
641  ELSE
642    !Et sinon on.... écrit
643    IF (SIZE(field)/=klon) &
644  CALL abort_physic('iophy::histwrite2d_cosp','Field first DIMENSION not equal to klon',1)
645
646    CALL Gather_omp(field,buffer_omp)
647!$OMP MASTER
648    CALL grid1Dto2D_mpi(buffer_omp,Field2d)
649
650! La boucle sur les fichiers:
651      firstx=.true.
652      DO iff=1, 3
653           IF (var%cles(iff) .AND. cosp_outfilekeys(iff)) THEN
654                ALLOCATE(index2d(nbp_lon*jj_nb))
655#ifndef CPP_IOIPSL_NO_OUTPUT
656        CALL histwrite(cosp_nidfiles(iff),var%name,itau_iocosp,Field2d,nbp_lon*jj_nb,index2d)
657#endif
658            deallocate(index2d)
659            IF (using_xios) THEN
660              IF (.not. ok_all_xml) then
661                 if (firstx) then
662                  if (prt_level >= 10) then
663                    WRITE(lunout,*)'xios_send_field variable ',var%name
664                  endif
665                  CALL xios_send_field(var%name, Field2d)
666                   firstx=.false.
667                 endif
668              ENDIF
669            ENDIF
670          ENDIF
671      ENDDO
672
673    IF (using_xios) THEN
674      IF (ok_all_xml) THEN
675        if (prt_level >= 1) then
676              WRITE(lunout,*)'xios_send_field variable ',var%name
677        endif
678       CALL xios_send_field(var%name, Field2d)
679      ENDIF
680    ENDIF
681
682!$OMP END MASTER   
683  ENDIF ! vars_defined
684  IF (prt_level >= 9) WRITE(lunout,*)'End histrwrite2d_cosp ',var%name
685  END SUBROUTINE histwrite2d_cosp
686
687! ug NOUVELLE VERSION DES WRITE AVEC LA BOUCLE DO RENTREE
688! AI sept 2013
689  SUBROUTINE histwrite3d_cosp(var, field, nverts, ncols)
690  USE dimphy
691  USE mod_phys_lmdz_para
692  USE ioipsl
693  use iophy
694  USE mod_grid_phy_lmdz, ONLY: nbp_lon
695  USE print_control_mod, ONLY: lunout,prt_level
696  USE lmdz_xios, only: xios_send_field, using_xios
697
698  IMPLICIT NONE
699  INCLUDE 'clesphys.h'
700
701    TYPE(ctrl_outcosp), INTENT(IN)    :: var
702    REAL, DIMENSION(:,:), INTENT(IN)  :: field ! --> field(klon,:)
703    INTEGER, INTENT(IN), OPTIONAL     :: ncols ! ug RUSTINE POUR LES Champs 4D.....
704    INTEGER, DIMENSION(3), INTENT(IN) :: nverts
705
706    INTEGER :: iff, k
707
708    REAL,DIMENSION(klon_mpi,SIZE(field,2)) :: buffer_omp
709    REAL :: Field3d(nbp_lon,jj_nb,SIZE(field,2))
710    INTEGER :: ip, n, nlev
711    INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
712    CHARACTER(LEN=20) ::  nomi, nom
713    character(len=2) :: str2
714    LOGICAL, SAVE  :: firstx
715!$OMP THREADPRIVATE(firstx)
716
717  IF (prt_level >= 9) write(lunout,*)'Begin histrwrite3d ',var%name
718
719! ug RUSTINE POUR LES STD LEVS.....
720      IF (PRESENT(ncols)) THEN
721              write(str2,'(i2.2)')ncols
722              nomi=var%name
723              nom="c"//str2//"_"//nomi
724      ELSE
725               nom=var%name
726      END IF
727  ! On regarde si on est dans la phase de définition ou d'écriture:
728  IF(.NOT.cosp_varsdefined) THEN
729      !Si phase de définition.... on définit
730!$OMP MASTER
731      CALL conf_cospoutputs(var%name,var%cles)
732      DO iff=1, 3
733        IF (cosp_outfilekeys(iff)) THEN
734          CALL histdef3d_cosp(iff, var, nverts(iff), ncols)
735        ENDIF
736      ENDDO
737!$OMP END MASTER
738  ELSE
739    !Et sinon on.... écrit
740    IF (SIZE(field,1)/=klon) &
741   CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)                                 
742    nlev=SIZE(field,2)
743
744
745    CALL Gather_omp(field,buffer_omp)
746!$OMP MASTER
747    CALL grid1Dto2D_mpi(buffer_omp,field3d)
748
749! BOUCLE SUR LES FICHIERS
750     firstx=.true.
751     DO iff=1, 3
752        IF (var%cles(iff) .AND. cosp_outfilekeys(iff)) THEN
753           ALLOCATE(index3d(nbp_lon*jj_nb*nlev))
754#ifndef CPP_IOIPSL_NO_OUTPUT
755    CALL histwrite(cosp_nidfiles(iff),nom,itau_iocosp,Field3d,nbp_lon*jj_nb*nlev,index3d)
756#endif
757
758        IF (using_xios) THEN
759          IF (.not. ok_all_xml) then
760           IF (firstx) THEN
761               CALL xios_send_field(nom, Field3d(:,:,1:nlev))
762               IF (prt_level >= 9) WRITE(lunout,*)'xios_send_field ',var%name
763               firstx=.FALSE.
764           ENDIF
765          ENDIF
766        ENDIF
767         deallocate(index3d)
768        ENDIF
769      ENDDO
770
771  IF (using_xios) THEN
772    IF (ok_all_xml) THEN
773     CALL xios_send_field(nom, Field3d(:,:,1:nlev))
774     IF (prt_level >= 1) WRITE(lunout,*)'xios_send_field ',var%name
775    ENDIF
776  ENDIF
777
778!$OMP END MASTER   
779  ENDIF ! vars_defined
780  IF (prt_level >= 9) write(lunout,*)'End histrwrite3d_cosp ',nom
781  END SUBROUTINE histwrite3d_cosp
782
783! ug NOUVELLE VERSION DES WRITE AVEC LA BOUCLE DO RENTREE
784! AI sept 2013
785  SUBROUTINE histwrite4d_cosp(var, field)
786  USE dimphy
787  USE mod_phys_lmdz_para
788  USE ioipsl
789  use iophy
790  USE mod_grid_phy_lmdz, ONLY: nbp_lon
791  USE print_control_mod, ONLY: lunout,prt_level
792  USE lmdz_xios, only: xios_send_field, using_xios
793
794  IMPLICIT NONE
795  INCLUDE 'clesphys.h'
796
797    TYPE(ctrl_outcosp), INTENT(IN)    :: var
798    REAL, DIMENSION(:,:,:), INTENT(IN)  :: field ! --> field(klon,:)
799
800    INTEGER :: iff, k
801
802    REAL,DIMENSION(klon_mpi,SIZE(field,2),SIZE(field,3)) :: buffer_omp
803    REAL :: field4d(nbp_lon,jj_nb,SIZE(field,2),SIZE(field,3))
804    INTEGER :: ip, n, nlev, nlev2
805    INTEGER, ALLOCATABLE, DIMENSION(:) :: index4d
806    CHARACTER(LEN=20) ::  nomi, nom
807
808  IF (prt_level >= 9) write(lunout,*)'Begin histrwrite4d ',var%name
809
810  IF(cosp_varsdefined) THEN
811    !Et sinon on.... écrit
812    IF (SIZE(field,1)/=klon) &
813   CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)           
814
815    nlev=SIZE(field,2)
816    nlev2=SIZE(field,3)
817    CALL Gather_omp(field,buffer_omp)
818!$OMP MASTER
819    CALL grid1Dto2D_mpi(buffer_omp,field4d)
820
821   IF (using_xios) THEN
822!    IF (ok_all_xml) THEN
823     CALL xios_send_field(var%name, Field4d(:,:,1:nlev,1:nlev2))
824     IF (prt_level >= 1) WRITE(lunout,*)'xios_send_field ',var%name
825!    ENDIF
826   ENDIF
827
828!$OMP END MASTER   
829  ENDIF ! vars_defined
830  IF (prt_level >= 9) write(lunout,*)'End histrwrite4d_cosp ',nom
831  END SUBROUTINE histwrite4d_cosp
832
833  SUBROUTINE conf_cospoutputs(nam_var,cles_var)
834!!! Lecture des noms et cles de sortie des variables dans config.def
835    !   en utilisant les routines getin de IOIPSL 
836    use ioipsl
837    USE print_control_mod, ONLY: lunout,prt_level
838
839    IMPLICIT NONE
840
841   CHARACTER(LEN=20)               :: nam_var, nnam_var
842   LOGICAL, DIMENSION(3)           :: cles_var
843
844! Lecture dans config.def ou output.def de cles_var et name_var
845    CALL getin('cles_'//nam_var,cles_var)
846    CALL getin('name_'//nam_var,nam_var)
847    IF(prt_level>10) WRITE(lunout,*)'nam_var cles_var ',nam_var,cles_var(:)
848
849  END SUBROUTINE conf_cospoutputs
850
851 END MODULE cosp_output_write_mod
Note: See TracBrowser for help on using the repository browser.