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

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