source: LMDZ6/trunk/libf/phylmd/cosp2/cosp_output_write_mod.F90 @ 4666

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