source: LMDZ6/branches/Amaury_dev/libf/phylmd/lmdz_clesphys.f90 @ 5157

Last change on this file since 5157 was 5137, checked in by abarral, 8 weeks ago

Put gradsdef.h, tracstoke.h, clesphys.h into modules

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