source: LMDZ5/trunk/libf/phylmd/cosp/cosp_output_write_mod.F90 @ 2428

Last change on this file since 2428 was 2428, checked in by idelkadi, 8 years ago

Mise a jour du simulateur COSP (passage de la version v3.2 a la version v1.4) :

  • mise a jour des sources pour ISCCP, CALIPSO et PARASOL
  • prise en compte des changements de phases pour les nuages (Calipso)
  • rajout de plusieurs diagnostiques (fraction nuageuse en fonction de la temperature, ...)

http://lmdz.lmd.jussieu.fr/Members/aidelkadi/cosp

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