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

Last change on this file since 3651 was 3308, checked in by idelkadi, 6 years ago

Corrections des diagnostiques de sorties pour les champs 4D (pour la compatibilite avec DR CMIP6) :

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