source: LMDZ6/trunk/libf/phylmd/clesphys_mod_h.f90

Last change on this file was 5282, checked in by abarral, 4 days ago

Turn iniprint.h clesphys.h into modules
Remove unused description.h

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 10.8 KB
Line 
1! Replaces clesphys.h
2
3MODULE clesphys_mod_h
4  IMPLICIT NONE; PRIVATE
5
6  PUBLIC co2_ppm, solaire                                           &
7          , RCO2, RCH4, RN2O, RCFC11, RCFC12                           &
8          , RCO2_act, RCH4_act, RN2O_act, RCFC11_act, RCFC12_act       &
9          , RCO2_per, RCH4_per, RN2O_per, RCFC11_per, RCFC12_per       &
10          , CH4_ppb, N2O_ppb, CFC11_ppt, CFC12_ppt                     &
11          , CH4_ppb_per, N2O_ppb_per, CFC11_ppt_per, CFC12_ppt_per     &
12          , cdmmax, cdhmax, ksta, ksta_ter, f_ri_cd_min                    &
13          , fmagic, pmagic                                             &
14          , f_cdrag_ter, f_cdrag_oce, f_rugoro, z0min, tau_gl              &
15          , min_wind_speed, f_gust_wk, f_gust_bl, f_qsat_oce, f_z0qh_oce   &
16          , z0m_seaice, z0h_seaice, z0m_landice, z0h_landice              &
17          , freq_outNMC, freq_calNMC                                   &
18          , lonmin_ins, lonmax_ins, latmin_ins, latmax_ins             &
19          , freq_ISCCP, ecrit_ISCCP, freq_COSP, freq_AIRS              &
20          , cvl_corr                                                   &
21          , qsol0, albsno0, evap0                                        &
22          , co2_ppm0                                                   &
23          , tau_thermals                                               &
24          , Cd_frein, zrel_oro_t, zpmm_orodr_t, zpmm_orolf_t, zstd_orodr_t &
25          , ecrit_LES                                                  &
26          , ecrit_ins, ecrit_hf, ecrit_day                             &
27          , ecrit_mth, ecrit_tra, ecrit_reg                            &
28          , top_height                                                 &
29          , iflag_cycle_diurne, soil_model, new_oliq                   &
30          , ok_orodr, ok_orolf, ok_limitvrai, nbapp_rad                &
31          , iflag_con, nbapp_cv, nbapp_wk                              &
32          , choix_bulk, nit_bulk, kz0                                  &
33          , iflag_ener_conserv                                         &
34          , ok_suntime_rrtm                                            &
35          , overlap                                                    &
36          , ok_kzmin                                                   &
37          , lev_histhf, lev_histday, lev_histmth                       &
38          , lev_histins, lev_histLES, lev_histdayNMC, levout_histNMC   &
39          , ok_histNMC                                                 &
40          , type_run, ok_regdyn, ok_cosp, ok_airs                      &
41          , ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP                     &
42          , ip_ebil_phy                                                &
43          , iflag_gusts, iflag_z0_oce                                  &
44          , ok_lic_melt, ok_lic_cond, aer_type                         &
45          , iflag_rrtm, ok_strato, ok_hines, ok_qch4                    &
46          , iflag_ice_thermo, ok_ice_supersat                            &
47          , ok_plane_h2o, ok_plane_contrail                            &
48          , ok_gwd_rando, NSW, iflag_albedo                            &
49          , ok_chlorophyll, ok_conserv_q, adjust_tropopause             &
50          , ok_daily_climoz, ok_all_xml, ok_lwoff                      &
51          , iflag_phytrac, ok_new_lscp, ok_bs, ok_rad_bs               &
52          , iflag_thermals, nsplit_thermals              &
53          , iflag_physiq, ok_3Deffect, ok_water_mass_fixer
54
55
56  ! threshold on to activate SSO schemes
57  ! threshold on to activate SSO schemes
58  REAL zrel_oro_t, zpmm_orodr_t, zpmm_orolf_t, zstd_orodr_t
59  INTEGER iflag_cycle_diurne
60  LOGICAL soil_model, new_oliq, ok_orodr, ok_orolf
61  LOGICAL ok_limitvrai
62  LOGICAL ok_all_xml
63  LOGICAL ok_lwoff
64  INTEGER nbapp_rad, iflag_con, nbapp_cv, nbapp_wk, iflag_ener_conserv
65  REAL co2_ppm, co2_ppm0, solaire
66  INTEGER iflag_thermals, nsplit_thermals
67  INTEGER iflag_physiq
68  REAL tau_thermals
69
70  !FC
71  REAL Cd_frein
72  LOGICAL ok_suntime_rrtm
73  REAL(kind = 8) RCO2, RCH4, RN2O, RCFC11, RCFC12
74  REAL(kind = 8) RCO2_act, RCH4_act, RN2O_act, RCFC11_act, RCFC12_act
75  REAL(kind = 8) CH4_ppb, N2O_ppb, CFC11_ppt, CFC12_ppt
76  !IM ajout CFMIP2/CMIP5ok_bs
77  REAL(kind = 8) RCO2_per, RCH4_per, RN2O_per, RCFC11_per, RCFC12_per
78  REAL(kind = 8) CH4_ppb_per, N2O_ppb_per, CFC11_ppt_per, CFC12_ppt_per
79
80  !OM ---> correction du bilan d'eau global
81  !OM Correction sur precip KE
82  REAL cvl_corr
83  !OM Fonte calotte dans bilan eau
84  LOGICAL ok_lic_melt
85  !OB Depot de vapeur d eau sur la calotte pour le bilan eau
86  LOGICAL ok_lic_cond
87
88  !IM simulateur ISCCP
89  INTEGER top_height, overlap
90  !IM seuils cdrm, cdrh
91  REAL cdmmax, cdhmax
92  !IM pour les params différentes Olivier Torres
93  INTEGER choix_bulk, nit_bulk, kz0
94  !IM param. stabilite s/ terres et en dehors
95  REAL ksta, ksta_ter, f_ri_cd_min
96  !IM ok_kzmin : clef calcul Kzmin dans la CL de surface cf FH
97  LOGICAL ok_kzmin
98  !IM, MAFo fmagic, pmagic : parametres - additionnel et multiplicatif -
99  !                          pour regler l albedo sur ocean
100  REAL fmagic, pmagic
101  ! Hauteur (imposee) du contenu en eau du sol
102  REAL qsol0, albsno0, evap0
103  ! Frottement au sol (Cdrag)
104  Real f_cdrag_ter, f_cdrag_oce
105  REAL min_wind_speed, f_gust_wk, f_gust_bl, f_qsat_oce, f_z0qh_oce
106  REAL z0m_seaice, z0h_seaice
107  REAL z0m_landice, z0h_landice
108  INTEGER iflag_gusts, iflag_z0_oce
109
110  ! Rugoro
111  Real f_rugoro, z0min
112
113  ! tau_gl : constante de rappel de la temperature a la surface de la glace
114  REAL tau_gl
115
116  !IM lev_histhf  : niveau sorties 6h
117  !IM lev_histday : niveau sorties journalieres
118  !IM lev_histmth : niveau sorties mensuelles
119  !IM lev_histdayNMC : on peut sortir soit sur 8 (comme AR5) ou bien
120  !                    sur 17 niveaux de pression
121  INTEGER lev_histhf, lev_histday, lev_histmth
122  INTEGER lev_histdayNMC
123  Integer lev_histins, lev_histLES
124  !IM ok_histNMC  : sortie fichiers niveaux de pression (histmthNMC, histdayNMC, histhfNMC)
125  !IM freq_outNMC : frequences de sortie fichiers niveaux de pression (histmthNMC, histdayNMC, histhfNMC)
126  !IM freq_calNMC : frequences de calcul fis. hist*NMC.nc
127  LOGICAL ok_histNMC(3)
128  INTEGER levout_histNMC(3)
129  REAL freq_outNMC(3), freq_calNMC(3)
130  CHARACTER(len = 4) type_run
131  ! aer_type: pour utiliser un fichier constant dans readaerosol
132  CHARACTER(len = 8) :: aer_type
133  LOGICAL ok_regdyn
134  REAL lonmin_ins, lonmax_ins, latmin_ins, latmax_ins
135  REAL ecrit_ins, ecrit_hf, ecrit_day
136  REAL ecrit_mth, ecrit_tra, ecrit_reg
137  REAL ecrit_LES
138  REAL freq_ISCCP, ecrit_ISCCP
139  REAL freq_COSP, freq_AIRS
140  LOGICAL :: ok_cosp, ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP
141  LOGICAL :: ok_airs
142  INTEGER :: ip_ebil_phy, iflag_rrtm, iflag_ice_thermo, NSW, iflag_albedo
143  LOGICAL :: ok_ice_supersat, ok_plane_h2o, ok_plane_contrail
144  LOGICAL :: ok_chlorophyll
145  LOGICAL :: ok_strato
146  LOGICAL :: ok_hines, ok_gwd_rando
147  LOGICAL :: ok_qch4
148  LOGICAL :: ok_conserv_q
149  LOGICAL :: adjust_tropopause
150  LOGICAL :: ok_daily_climoz
151  LOGICAL :: ok_new_lscp
152  LOGICAL :: ok_bs, ok_rad_bs
153  ! flag to bypass or not the phytrac module
154  INTEGER :: iflag_phytrac
155
156  !AI flags pour ECRAD
157  LOGICAL :: ok_3Deffect
158
159  !OB flag to activate water mass fixer in physiq
160  LOGICAL :: ok_water_mass_fixer
161
162
163  !$OMP THREADPRIVATE(co2_ppm, solaire                                           &
164  !$OMP      , RCO2, RCH4, RN2O, RCFC11, RCFC12                           &
165  !$OMP      , RCO2_act, RCH4_act, RN2O_act, RCFC11_act, RCFC12_act       &
166  !$OMP      , RCO2_per, RCH4_per, RN2O_per, RCFC11_per, RCFC12_per       &
167  !$OMP      , CH4_ppb, N2O_ppb, CFC11_ppt, CFC12_ppt                     &
168  !$OMP      , CH4_ppb_per, N2O_ppb_per, CFC11_ppt_per, CFC12_ppt_per     &
169  !$OMP      , cdmmax, cdhmax, ksta, ksta_ter, f_ri_cd_min                    &
170  !$OMP      , fmagic, pmagic                                             &
171  !$OMP      , f_cdrag_ter, f_cdrag_oce, f_rugoro, z0min, tau_gl              &
172  !$OMP      , min_wind_speed, f_gust_wk, f_gust_bl, f_qsat_oce, f_z0qh_oce   &
173  !$OMP      , z0m_seaice, z0h_seaice, z0m_landice, z0h_landice              &
174  !$OMP      , freq_outNMC, freq_calNMC                                   &
175  !$OMP      , lonmin_ins, lonmax_ins, latmin_ins, latmax_ins             &
176  !$OMP      , freq_ISCCP, ecrit_ISCCP, freq_COSP, freq_AIRS              &
177  !$OMP      , cvl_corr                                                   &
178  !$OMP      , qsol0, albsno0, evap0                                        &
179  !$OMP      , co2_ppm0                                                   &
180  !$OMP      , tau_thermals                                               &
181  !$OMP      , Cd_frein, zrel_oro_t, zpmm_orodr_t, zpmm_orolf_t, zstd_orodr_t &
182  !$OMP      , ecrit_LES                                                  &
183  !$OMP      , ecrit_ins, ecrit_hf, ecrit_day                             &
184  !$OMP      , ecrit_mth, ecrit_tra, ecrit_reg                            &
185  !$OMP      , top_height                                                 &
186  !$OMP      , iflag_cycle_diurne, soil_model, new_oliq                   &
187  !$OMP      , ok_orodr, ok_orolf, ok_limitvrai, nbapp_rad                &
188  !$OMP      , iflag_con, nbapp_cv, nbapp_wk                              &
189  !$OMP      , choix_bulk, nit_bulk, kz0                                  &
190  !$OMP      , iflag_ener_conserv                                         &
191  !$OMP      , ok_suntime_rrtm                                            &
192  !$OMP      , overlap                                                    &
193  !$OMP      , ok_kzmin                                                   &
194  !$OMP      , lev_histhf, lev_histday, lev_histmth                       &
195  !$OMP      , lev_histins, lev_histLES, lev_histdayNMC, levout_histNMC   &
196  !$OMP      , ok_histNMC                                                 &
197  !$OMP      , type_run, ok_regdyn, ok_cosp, ok_airs                      &
198  !$OMP      , ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP                     &
199  !$OMP      , ip_ebil_phy                                                &
200  !$OMP      , iflag_gusts, iflag_z0_oce                                  &
201  !$OMP      , ok_lic_melt, ok_lic_cond, aer_type                         &
202  !$OMP      , iflag_rrtm, ok_strato, ok_hines, ok_qch4                    &
203  !$OMP      , iflag_ice_thermo, ok_ice_supersat                            &
204  !$OMP      , ok_plane_h2o, ok_plane_contrail                            &
205  !$OMP      , ok_gwd_rando, NSW, iflag_albedo                            &
206  !$OMP      , ok_chlorophyll, ok_conserv_q, adjust_tropopause             &
207  !$OMP      , ok_daily_climoz, ok_all_xml, ok_lwoff                      &
208  !$OMP      , iflag_phytrac, ok_new_lscp, ok_bs, ok_rad_bs               &
209  !$OMP      , iflag_thermals, nsplit_thermals              &
210  !$OMP      , iflag_physiq, ok_3Deffect, ok_water_mass_fixer)
211
212END MODULE clesphys_mod_h
Note: See TracBrowser for help on using the repository browser.