source: LMDZ5/trunk/libf/phylmd/cosp/cosp_output_mod.F90 @ 2297

Last change on this file since 2297 was 2297, checked in by musat, 9 years ago

RRTM :
Correction bug interface avec rrtm (radlwsw_m.F90)
Ajouter la possibilite d'utilsation d'anciennes proprites optique dans le cas RRTM 2bandes (readaerosol_optic_rrtm.F90)
Correction rrtm (rrtm_rtrn1a_140gp.F90)

COSP :
Modifications pour traiter les valeurs indefines :
mise a 0 en cas d'utilisation de IOIPSL
mise a la valeur recuperee dans .xml en cas d'utilisation de XIOS

File size: 11.9 KB
Line 
1! A.Idelkadi sept 2013 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2!! Module pour declarer et initialiser les parametres de controle des fichiers de sorties et des champs a sortir
3!! La routine cosp_output_open (appelee 1 seule fois dans phy_cosp.F90) permet :
4!! de creer les fichiers avec leurs grilles horizontales et verticales
5!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
6  MODULE cosp_output_mod
7
8  USE MOD_COSP_CONSTANTS
9  USE MOD_COSP_TYPES
10
11! cosp_output_mod
12      INTEGER, PRIVATE             :: i
13!!!!!!! Controle des fichier de sorties Cosp !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
14      LOGICAL, DIMENSION(3), SAVE  :: cosp_outfilekeys
15      INTEGER, DIMENSION(3), SAVE  :: cosp_nidfiles
16!$OMP THREADPRIVATE(cosp_outfilekeys, cosp_nidfiles)
17      INTEGER, DIMENSION(3), SAVE  :: nhoricosp, nvert, nvertmcosp, nvertcol, nvertisccp, nvertp
18      REAL, DIMENSION(3), SAVE                :: zoutm_cosp
19!$OMP THREADPRIVATE(nhoricosp, nvert, nvertmcosp, nvertcol, nvertisccp, nvertp, zoutm_cosp)
20      REAL, SAVE                   :: zdtimemoy_cosp
21!$OMP THREADPRIVATE(zdtimemoy_cosp)
22      CHARACTER(LEN=20), DIMENSION(3), SAVE  :: cosp_outfiletypes
23      CHARACTER(LEN=20), DIMENSION(3), SAVE  :: cosp_outfilenames
24      REAL, DIMENSION(3), SAVE               :: cosp_ecritfiles
25!$OMP THREADPRIVATE(cosp_outfiletypes, cosp_outfilenames, cosp_ecritfiles)
26
27!!!!  Controle des variables a sortir dans les fichiers !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
28  TYPE ctrl_outcosp
29     LOGICAL,DIMENSION(3)                 :: cles             !!! Sortir ou non le champs
30     CHARACTER(len=20)                    :: name       
31     CHARACTER(len=150)                   :: description      !!! Nom
32     CHARACTER(len=20)                    :: unit             !!! Unite
33     CHARACTER(len=20),DIMENSION(3)  :: cosp_typeecrit        !!! Operation (ave, inst, ...)
34  END TYPE ctrl_outcosp
35! CALIPSO vars
36  TYPE(ctrl_outcosp), SAVE :: o_cllcalipso = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
37         "cllcalipso", "Lidar Low-level Cloud Fraction", "1", (/ ('', i=1, 3) /))                                   
38  TYPE(ctrl_outcosp), SAVE :: o_clmcalipso = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
39         "clmcalipso", "Lidar Mid-level Cloud Fraction", "1", (/ ('', i=1, 3) /))
40  TYPE(ctrl_outcosp), SAVE :: o_clhcalipso = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
41         "clhcalipso", "Lidar Hight-level Cloud Fraction", "1", (/ ('', i=1, 3) /))
42  TYPE(ctrl_outcosp), SAVE :: o_cltcalipso = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
43         "cltcalipso", "Lidar Total Cloud Fraction", "1", (/ ('', i=1, 3) /))
44  TYPE(ctrl_outcosp), SAVE :: o_clcalipso = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
45         "clcalipso", "Lidar Cloud Fraction (532 nm)", "1", (/ ('', i=1, 3) /))
46  TYPE(ctrl_outcosp), SAVE :: o_cfad_lidarsr532 = ctrl_outcosp((/ .FALSE., .FALSE., .FALSE. /), &
47         "cfad_lidarsr532", "Lidar Scattering Ratio CFAD (532 nm)", "1", (/ ('', i=1, 3) /))   
48  TYPE(ctrl_outcosp), SAVE :: o_parasol_refl = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
49         "parasol_refl", "PARASOL-like mono-directional reflectance","1", (/ ('', i=1, 3) /))
50  TYPE(ctrl_outcosp), SAVE :: o_parasol_crefl = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &             
51         "parasol_crefl", "PARASOL-like mono-directional reflectance (integral)","1", (/ ('', i=1, 3) /))                 
52  TYPE(ctrl_outcosp), SAVE :: o_Ncrefl = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
53         "Ncrefl", "Nb PARASOL-like mono-directional reflectance (integral)","1", (/ ('', i=1, 3) /))
54  TYPE(ctrl_outcosp), SAVE :: o_atb532 = ctrl_outcosp((/ .FALSE., .FALSE., .FALSE. /), &
55         "atb532", "Lidar Attenuated Total Backscatter (532 nm)","1", (/ ('', i=1, 3) /))
56  TYPE(ctrl_outcosp), SAVE :: o_beta_mol532 = ctrl_outcosp((/ .FALSE., .FALSE., .FALSE. /), &
57         "beta_mol532", "Lidar Molecular Backscatter (532 nm)","m-1 sr-1", (/ ('', i=1, 3) /))
58! ISCCP vars
59  TYPE(ctrl_outcosp), SAVE :: o_sunlit = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
60         "sunlit", "1 for day points, 0 for nightime","1",(/ ('', i=1, 3) /))                   
61  TYPE(ctrl_outcosp), SAVE :: o_clisccp2 = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
62         "clisccp2", "Cloud Fraction as Calculated by the ISCCP Simulator","1", (/ ('', i=1, 3) /))
63  TYPE(ctrl_outcosp), SAVE :: o_boxtauisccp = ctrl_outcosp((/ .FALSE., .FALSE., .FALSE. /), &
64         "boxtauisccp", "Optical Depth in Each Column as Calculated by the ISCCP Simulator","1", (/ ('', i=1, 3) /))
65  TYPE(ctrl_outcosp), SAVE :: o_boxptopisccp = ctrl_outcosp((/ .FALSE., .FALSE., .FALSE. /), &
66         "boxptopisccp", "Cloud Top Pressure in Each Column as Calculated by the ISCCP Simulator","Pa", (/ ('', i=1, 3) /))
67  TYPE(ctrl_outcosp), SAVE :: o_tclisccp = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
68          "tclisccp", "Total Cloud Fraction as Calculated by the ISCCP Simulator", "1", (/ ('', i=1, 3) /))
69  TYPE(ctrl_outcosp), SAVE :: o_ctpisccp = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
70          "ctpisccp", "Mean Cloud Top Pressure as Calculated by the ISCCP Simulator", "Pa", (/ ('', i=1, 3) /))
71  TYPE(ctrl_outcosp), SAVE :: o_tauisccp = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
72          "tauisccp", "Optical Depth as Calculated by the ISCCP Simulator", "1", (/ ('', i=1, 3) /))
73  TYPE(ctrl_outcosp), SAVE :: o_albisccp = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
74          "albisccp", "Mean Cloud Albedo as Calculated by the ISCCP Simulator", "1", (/ ('', i=1, 3) /))
75  TYPE(ctrl_outcosp), SAVE :: o_meantbisccp = ctrl_outcosp((/ .FALSE., .FALSE., .FALSE. /), &
76          "meantbisccp", " Mean all-sky 10.5 micron brightness temperature as calculated &
77           by the ISCCP Simulator","K", (/ ('', i=1, 3) /))
78  TYPE(ctrl_outcosp), SAVE :: o_meantbclrisccp = ctrl_outcosp((/ .FALSE., .FALSE., .FALSE. /), &
79          "meantbclrisccp", "Mean clear-sky 10.5 micron brightness temperature as calculated &
80           by the ISCCP Simulator","K", (/ ('', i=1, 3) /))
81
82  LOGICAL, SAVE :: cosp_varsdefined = .FALSE. ! ug PAS THREADPRIVATE ET C'EST NORMAL
83  REAL, SAVE  :: Cosp_fill_value
84!$OMP THREADPRIVATE(Cosp_fill_value)
85 
86
87CONTAINS
88
89!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
90!!!!!!!!! Ouverture des fichier et definition des  axes!!!!!!!!
91  !! histbeg, histvert
92!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
93
94  SUBROUTINE cosp_output_open(Nlevlmdz, Ncolumns, presnivs, dtime, freq_cosp, &
95                              ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, ok_all_xml,  &
96                              ecrit_mth, ecrit_day, ecrit_hf, use_vgrid, vgrid)
97
98
99  USE iophy
100  USE ioipsl
101  USE phys_cal_mod
102
103#ifdef CPP_XIOS
104    ! ug Pour les sorties XIOS
105    USE wxios
106#endif
107
108  IMPLICIT NONE
109
110!!! Variables d'entree
111  integer                  :: Nlevlmdz, Ncolumns      ! Number of levels
112  real,dimension(Nlevlmdz) :: presnivs
113  real                     :: dtime, freq_cosp, ecrit_day, ecrit_hf, ecrit_mth
114  logical                  :: ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, use_vgrid, ok_all_xml                   
115  type(cosp_vgrid)   :: vgrid   ! Information on vertical grid of stats
116
117!!! Variables locales
118  integer                  :: idayref, iff, ii
119  real                     :: zjulian,zjulian_start
120  real,dimension(Ncolumns) :: column_ax
121  CHARACTER(LEN=20), DIMENSION(3)  :: chfreq = (/ '1day', '1d', '3h' /)           
122
123!!! Variables d'entree
124  include "temps.h"
125  INCLUDE 'iniprint.h'
126
127#ifdef CPP_XIOS
128    ! ug Variables utilisées pour récupérer le calendrier pour xios
129    INTEGER :: x_an, x_mois, x_jour
130    REAL :: x_heure
131    INTEGER :: ini_an, ini_mois, ini_jour
132    REAL :: ini_heure
133#endif
134
135    WRITE(lunout,*) 'Debut cosp_output_mod.F90'
136    print*,'cosp_varsdefined',cosp_varsdefined
137    ! Initialisations (Valeurs par defaut)
138
139    do ii=1,Ncolumns
140      column_ax(ii) = real(ii)
141    enddo
142
143
144    cosp_outfilenames(1) = 'histmthCOSP'
145    cosp_outfilenames(2) = 'histdayCOSP'
146    cosp_outfilenames(3) = 'histhfCOSP'
147
148    cosp_outfiletypes(1) = 'ave(X)'
149    cosp_outfiletypes(2) = 'ave(X)'
150    cosp_outfiletypes(3) = 'ave(X)'
151
152    cosp_outfilekeys(1) = ok_mensuelCOSP
153    cosp_outfilekeys(2) = ok_journeCOSP
154    cosp_outfilekeys(3) = ok_hfCOSP
155
156    cosp_ecritfiles(1) = mth_len*86400.
157    cosp_ecritfiles(2) = 1.*86400.
158    cosp_ecritfiles(3) = 0.125*86400.
159
160! Lecture des parametres dans output.def ou config.def
161
162    CALL getin('cosp_outfilenames',cosp_outfilenames)
163    CALL getin('cosp_outfilekeys',cosp_outfilekeys)
164    CALL getin('cosp_ecritfiles',cosp_ecritfiles)
165    CALL getin('cosp_outfiletypes',cosp_outfiletypes)
166
167    WRITE(lunout,*)'cosp_outfilenames=',cosp_outfilenames
168    WRITE(lunout,*)'cosp_outfilekeys=',cosp_outfilekeys
169    WRITE(lunout,*)'cosp_ecritfiles=',cosp_ecritfiles
170    WRITE(lunout,*)'cosp_outfiletypes=',cosp_outfiletypes
171   
172    idayref = day_ref
173    CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
174    CALL ymds2ju(annee_ref, 1, day_ini, start_time, zjulian_start)
175
176#ifdef CPP_XIOS
177   
178! recuperer la valeur indefine Xios
179    CALL xios_get_field_attr("clcalipso",default_value=Cosp_fill_value)
180    ! ug R\'eglage du calendrier xios
181    !Temps julian => an, mois, jour, heure
182!    CALL ju2ymds(zjulian, x_an, x_mois, x_jour, x_heure)
183!    CALL ju2ymds(zjulian_start, ini_an, ini_mois, ini_jour, ini_heure)
184!    CALL wxios_set_cal(dtime, calend, x_an, x_mois, x_jour, x_heure, ini_an, &
185!                       ini_mois, ini_jour, ini_heure )
186       ! ug d�claration des axes verticaux de chaque fichier:
187!    if (use_vgrid) then
188        CALL wxios_add_vaxis("height", vgrid%Nlvgrid, vgrid%z)
189!    else
190!         WRITE(lunout,*) 'wxios_add_vaxis "presnivs", vgrid%Nlvgrid ',vgrid%Nlvgrid
191!        CALL wxios_add_vaxis("presnivs", vgrid%Nlvgrid, presnivs)
192!    endif
193    WRITE(lunout,*) 'wxios_add_vaxis height_mlev, Nlevlmdz ',Nlevlmdz
194    CALL wxios_add_vaxis("height_mlev", Nlevlmdz, vgrid%mz)
195    WRITE(lunout,*) 'wxios_add_vaxis sza, PARASOL_NREFL ',PARASOL_NREFL
196    CALL wxios_add_vaxis("sza", PARASOL_NREFL, PARASOL_SZA)
197    WRITE(lunout,*) 'wxios_add_vaxis pressure2 ',7
198    CALL wxios_add_vaxis("pressure2", 7, ISCCP_PC)
199    WRITE(lunout,*) 'wxios_add_vaxis column ',Ncolumns
200    CALL wxios_add_vaxis("column", Ncolumns, column_ax)
201#endif
202   
203    zdtimemoy_cosp = freq_COSP         ! Frequence ou l on moyenne
204
205    DO iff=1,3
206       zoutm_cosp(iff) = cosp_ecritfiles(iff) ! Frequence ou l on ecrit en seconde
207
208       IF (cosp_outfilekeys(iff)) THEN
209           CALL histbeg_phy_all(cosp_outfilenames(iff),itau_phy,zjulian,&
210             dtime,nhoricosp(iff),cosp_nidfiles(iff))
211           print*,'histbeg_phy nhoricosp(iff),cosp_nidfiles(iff)', &
212                    nhoricosp(iff),cosp_nidfiles(iff)
213
214#ifdef CPP_XIOS
215        IF (.not. ok_all_xml) then
216         WRITE(lunout,*) 'wxios_add_file ',cosp_outfilenames(iff)
217         CALL wxios_add_file(cosp_outfilenames(iff),chfreq(iff),10)
218        ENDIF
219#endif
220
221#ifndef CPP_IOIPSL_NO_OUTPUT
222! Definition de l'axe vertical
223       if (use_vgrid) then
224! Axe vertical Cosp 40 niveaux (en m)
225      CALL histvert(cosp_nidfiles(iff),"height","height","m",vgrid%Nlvgrid,vgrid%z,nvert(iff))
226       else
227! Axe vertical modele LMDZ presnivs
228      CALL histvert(cosp_nidfiles(iff),"presnivs","Vertical levels","Pa",vgrid%Nlvgrid,presnivs,nvert(iff),"down")
229       endif
230! Axe vertical niveaux modele (en m)
231      CALL histvert(cosp_nidfiles(iff),"height_mlev","height_mlev","m",Nlevlmdz,vgrid%mz,nvertmcosp(iff))
232
233      CALL histvert(cosp_nidfiles(iff),"sza","solar_zenith_angle","degrees",PARASOL_NREFL,PARASOL_SZA,nvertp(iff))
234
235      CALL histvert(cosp_nidfiles(iff),"pressure2","pressure","mb",7,ISCCP_PC,nvertisccp(iff),"down")
236
237      CALL histvert(cosp_nidfiles(iff),"column","column","count",Ncolumns,column_ax(1:Ncolumns),nvertcol(iff))
238
239!!! Valeur indefinie en cas IOIPSL
240     Cosp_fill_value=0.
241
242#endif
243
244      ENDIF
245  ENDDO
246
247    end SUBROUTINE cosp_output_open
248
249 END MODULE cosp_output_mod
Note: See TracBrowser for help on using the repository browser.