Changeset 5299


Ignore:
Timestamp:
Oct 30, 2024, 2:31:56 PM (25 hours ago)
Author:
abarral
Message:

Turn cv3param.h into module

Location:
LMDZ6/trunk/libf
Files:
14 edited
2 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/cv3_buoy.f90

    r5285 r5299  
    1010  ! **************************************************************
    1111
    12   USE cvthermo_mod_h
     12USE cv3param_mod_h
     13    USE cvthermo_mod_h
    1314  IMPLICIT NONE
    1415
    15   include "cv3param.h"
    1616  include "YOMCST2.h"
    1717
  • LMDZ6/trunk/libf/phylmd/cv3_cine.f90

    r5285 r5299  
    1515  ! **************************************************************
    1616
    17   USE cvthermo_mod_h
     17USE cv3param_mod_h
     18    USE cvthermo_mod_h
    1819  USE yomcst_mod_h
    1920IMPLICIT NONE
    2021
    2122
    22   include "cv3param.h"
    2323  ! input:
    2424  INTEGER ncum, nd, nloc
  • LMDZ6/trunk/libf/phylmd/cv3_crit.f90

    r5268 r5299  
    1010  ! **************************************************************
    1111
    12   IMPLICIT NONE
     12USE cv3param_mod_h
     13    IMPLICIT NONE
    1314
    14   include "cv3param.h"
    1515
    1616  ! input:
  • LMDZ6/trunk/libf/phylmd/cv3_mixscale.f90

    r5268 r5299  
    99  ! **************************************************************
    1010
    11   IMPLICIT NONE
     11USE cv3param_mod_h
     12    IMPLICIT NONE
    1213
    13   include "cv3param.h"
    1414
    1515!inputs:
  • LMDZ6/trunk/libf/phylmd/cv3_routines.f90

    r5285 r5299  
    1111  use mod_phys_lmdz_para
    1212  USE conema3_mod_h
     13  USE cv3param_mod_h
    1314  IMPLICIT NONE
    1415
     
    3536!***                 APPROACH TO QUASI-EQUILIBRIUM           ***
    3637!***                     IT MUST BE LESS THAN 0              ***
    37 
    38   include "cv3param.h"
    3938
    4039  INTEGER, INTENT(IN)              :: nd
     
    185184USE cvthermo_mod_h
    186185  USE cvflag_mod_h
     186USE cv3param_mod_h
    187187  IMPLICIT NONE
    188188
     
    190190!  Increment the counter sig(nd)
    191191! =====================================================================
    192 
    193   include "cv3param.h"
    194192
    195193!inputs:
     
    225223                      lv, lf, cpn, tv, gz, h, hm, th)
    226224  USE cvthermo_mod_h
     225  USE cv3param_mod_h
    227226  IMPLICIT NONE
    228227
     
    247246  REAL tvx, tvy ! convect3
    248247  REAL cpx(len, nd)
    249 
    250   include "cv3param.h"
    251 
    252 
    253248! ori      do 110 k=1,nlp
    254249! abderr     do 110 k=1,nl ! convect3
     
    314309  USE print_control_mod, ONLY: prt_level
    315310  USE cvthermo_mod_h
     311  USE cv3param_mod_h
    316312  IMPLICIT NONE
    317313
     
    330326! - A,B explicitely defined (!...)
    331327! ================================================================
    332 
    333   include "cv3param.h"
    334328
    335329!inputs:
     
    606600  USE cvthermo_mod_h
    607601  USE cvflag_mod_h
     602  USE cv3param_mod_h
    608603  IMPLICIT NONE
    609604
     
    620615!    - if icbs=icb, compute also tp(icb+1),tvp(icb+1) & clw(icb+1)
    621616! ----------------------------------------------------------------
    622 
    623   include "cv3param.h"
    624617
    625618! inputs:
     
    881874SUBROUTINE cv3_trigger(len, nd, icb, plcl, p, th, tv, tvp, thnk, &
    882875                       pbase, buoybase, iflag, sig, w0)
     876  USE cv3param_mod_h
    883877  IMPLICIT NONE
    884878
     
    897891! -> the buoyancy below cloud base not (yet) set to the cloud base buoyancy
    898892! -------------------------------------------------------------------
    899 
    900   include "cv3param.h"
    901893
    902894! input:
     
    995987                        h, lv, cpn, p, ph, tv, tp, tvp, clw, &
    996988                        sig, w0)
    997   USE print_control_mod, ONLY: lunout
     989USE cv3param_mod_h
     990    USE print_control_mod, ONLY: lunout
    998991  IMPLICIT NONE
    999992
    1000   include "cv3param.h"
    1001993
    1002994!inputs:
     
    11401132  USE cvthermo_mod_h
    11411133  USE conema3_mod_h
     1134  USE cv3param_mod_h
    11421135  IMPLICIT NONE
    11431136
     
    11601153! ---------------------------------------------------------------------
    11611154
    1162   include "cv3param.h"
    11631155  include "YOMCST2.h"
    11641156
     
    20472039                       pbase, p, ph, tv, buoy, &
    20482040                       sig, w0, cape, m, iflag)
    2049   USE cvthermo_mod_h
     2041USE cv3param_mod_h
     2042    USE cvthermo_mod_h
    20502043  USE cvflag_mod_h
    20512044  IMPLICIT NONE
     
    20572050! ===================================================================
    20582051
    2059   include "cv3param.h"
    20602052
    20612053!input:
     
    22922284  USE cvflag_mod_h
    22932285  USE cvthermo_mod_h
     2286  USE cv3param_mod_h
    22942287  IMPLICIT NONE
    22952288
     
    22982291! - vectorisation de la partie normalisation des flux (do 789...)
    22992292! ---------------------------------------------------------------------
    2300 
    2301   include "cv3param.h"
    23022293
    23032294!inputs:
     
    27122703                     faci, b, sigd, &
    27132704                     wdtrainA, wdtrainS, wdtrainM)                                      ! RomP
    2714   USE cvthermo_mod_h
     2705USE cv3param_mod_h
     2706    USE cvthermo_mod_h
    27152707  USE cvflag_mod_h
    27162708  USE print_control_mod, ONLY: prt_level, lunout
    27172709  IMPLICIT NONE
    27182710
    2719   include "cv3param.h"
    27202711  include "nuage.h"
    27212712
     
    34563447                     ftd, fqd, qta, qtc, sigt, detrain, tau_cld_cv, coefw_cld_cv)
    34573448
    3458 USE conema3_mod_h
     3449USE cv3param_mod_h
     3450  USE conema3_mod_h
    34593451      USE print_control_mod, ONLY: lunout, prt_level
    34603452    USE add_phys_tend_mod, only : fl_cor_ebil
     
    34633455  IMPLICIT NONE
    34643456
    3465   include "cv3param.h"
    34663457
    34673458!inputs:
     
    49534944                      ep, Vprecip, elij, clw, epmlmMm, eplaMm, &
    49544945                      icb, inb)
    4955   USE cvthermo_mod_h
     4946USE cv3param_mod_h
     4947    USE cvthermo_mod_h
    49564948  USE cvflag_mod_h
    49574949  IMPLICIT NONE
    49584950
    4959   include "cv3param.h"
    49604951
    49614952!inputs:
     
    50625053                          Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, cape1, &
    50635054                          epmax_diag1) ! epmax_cape
    5064   IMPLICIT NONE
    5065 
    5066   include "cv3param.h"
     5055USE cv3param_mod_h
     5056    IMPLICIT NONE
     5057
    50675058
    50685059!inputs:
     
    51415132                 , pbase, p, ph, tv, buoy, sig, w0,iflag &
    51425133                 , epmax_diag)
    5143 USE conema3_mod_h
     5134USE cv3param_mod_h
     5135  USE conema3_mod_h
    51445136            USE cvflag_mod_h
    51455137          USE cvthermo_mod_h
     
    51515143        ! Toutes les autres variables fn de ep sont calcul�es plus bas.
    51525144
    5153   include "cv3param.h"
    51545145
    51555146! inputs:
  • LMDZ6/trunk/libf/phylmd/cv3a_compress.f90

    r5268 r5299  
    2929  ! **************************************************************
    3030
    31   IMPLICIT NONE
    32 
    33   include "cv3param.h"
     31USE cv3param_mod_h
     32    IMPLICIT NONE
     33
    3434
    3535  ! inputs:
  • LMDZ6/trunk/libf/phylmd/cv3a_uncompress.f90

    r5268 r5299  
    3838  ! **************************************************************
    3939
    40   IMPLICIT NONE
    41 
    42   include "cv3param.h"
     40USE cv3param_mod_h
     41    IMPLICIT NONE
     42
    4343
    4444  ! inputs:
  • LMDZ6/trunk/libf/phylmd/cv3p1_closure.f90

    r5285 r5299  
    1919  ! **************************************************************
    2020
    21 USE conema3_mod_h
     21USE cv3param_mod_h
     22  USE conema3_mod_h
    2223    USE cvthermo_mod_h
    2324  USE print_control_mod, ONLY: prt_level, lunout
     
    2526IMPLICIT NONE
    2627
    27   include "cv3param.h"
    2828  include "YOMCST2.h"
    2929
  • LMDZ6/trunk/libf/phylmd/cv3p2_closure.f90

    r5285 r5299  
    1818  ! **************************************************************
    1919
    20 USE conema3_mod_h
     20USE cv3param_mod_h
     21  USE conema3_mod_h
    2122    USE cvthermo_mod_h
    2223  USE cvflag_mod_h
     
    2526IMPLICIT NONE
    2627
    27   include "cv3param.h"
    2828  include "YOMCST2.h"
    2929
  • LMDZ6/trunk/libf/phylmd/cv3p_mixing.f90

    r5285 r5299  
    1313! **************************************************************
    1414
    15   USE cvthermo_mod_h
     15USE cv3param_mod_h
     16    USE cvthermo_mod_h
    1617  USE cvflag_mod_h
    1718  USE print_control_mod, ONLY: mydebug=>debug , lunout, prt_level
     
    2122  IMPLICIT NONE
    2223
    23   include "cv3param.h"
    2424  include "YOMCST2.h"
    2525
  • LMDZ6/trunk/libf/phylmd/cv3param_mod_h.f90

    r5298 r5299  
    1 !------------------------------------------------------------
    2 ! Parameters for convectL, iflag_con=3:
    3 ! (includes - microphysical parameters,
    4 !                       - parameters that control the rate of approach
    5 !               to quasi-equilibrium)
    6 !                       - noff & minorig (previously in input of convect1)
    7 !------------------------------------------------------------
     1! Replaces cv3param.h
    82
    9       integer flag_epKEorig
    10       real flag_wb
    11       integer cv_flag_feed
    12       integer noff, minorig, nl, nlp, nlm
    13       real sigdz, spfac
    14       real pbcrit, ptcrit
    15       real elcrit, tlcrit
    16       real coef_peel
    17       real omtrain
    18       real dtovsh, dpbase, dttrig
    19       real dtcrit, tau, beta, alpha, alpha1
    20       real T_top_max
    21       real tau_stop, noconv_stop
    22       real wbmax
    23       real delta
    24       real betad
    25       real ejectliq
    26       real ejectice
     3MODULE cv3param_mod_h
     4  !------------------------------------------------------------
     5  ! Parameters for convectL, iflag_con=3:
     6  ! (includes - microphysical parameters,
     7  !            - parameters that control the rate of approach
     8  !               to quasi-equilibrium)
     9  !            - noff & minorig (previously in input of convect1)
     10  !------------------------------------------------------------
     11  IMPLICIT NONE; PRIVATE
     12  PUBLIC sigdz, spfac, pbcrit, ptcrit, elcrit, tlcrit, coef_peel, omtrain, dtovsh, dpbase, &
     13          dttrig, dtcrit, tau, beta, alpha, alpha1, T_top_max, tau_stop, noconv_stop, wbmax, &
     14          delta, betad, ejectliq, ejectice, flag_wb, flag_epKEorig, cv_flag_feed, noff, minorig, &
     15          nl, nlp, nlm
    2716
    28       COMMON /cv3param/ sigdz, spfac &
    29                       ,pbcrit, ptcrit &
    30                       ,elcrit, tlcrit &
    31                       ,coef_peel &
    32                       ,omtrain &
    33                       ,dtovsh, dpbase, dttrig &
    34                       ,dtcrit, tau, beta, alpha, alpha1 &
    35                       ,T_top_max &
    36                       ,tau_stop, noconv_stop &
    37                       ,wbmax &
    38                       ,delta, betad  &
    39                       ,ejectliq, ejectice &
    40                       ,flag_epKEorig &
    41                       ,flag_wb, cv_flag_feed &
    42                       ,noff, minorig, nl, nlp, nlm
    43 !$OMP THREADPRIVATE(/cv3param/)
     17  INTEGER flag_epKEorig
     18  REAL flag_wb
     19  INTEGER cv_flag_feed
     20  INTEGER noff, minorig, nl, nlp, nlm
     21  REAL sigdz, spfac
     22  REAL pbcrit, ptcrit
     23  REAL elcrit, tlcrit
     24  REAL coef_peel
     25  REAL omtrain
     26  REAL dtovsh, dpbase, dttrig
     27  REAL dtcrit, tau, beta, alpha, alpha1
     28  REAL T_top_max
     29  REAL tau_stop, noconv_stop
     30  REAL wbmax
     31  REAL delta
     32  REAL betad
     33  REAL ejectliq
     34  REAL ejectice
    4435
     36  !$OMP THREADPRIVATE(sigdz, spfac, pbcrit, ptcrit, elcrit, tlcrit, coef_peel, omtrain, dtovsh, dpbase, &
     37  !$OMP      dttrig, dtcrit, tau, beta, alpha, alpha1, T_top_max, tau_stop, noconv_stop, wbmax, &
     38  !$OMP      delta, betad, ejectliq, ejectice, flag_wb, flag_epKEorig, cv_flag_feed, noff, minorig, &
     39  !$OMP      nl, nlp, nlm)
     40END MODULE cv3param_mod_h
     41
     42
     43
     44
  • LMDZ6/trunk/libf/phylmdiso/cv3_routines.F90

    r5285 r5299  
    1111  use mod_phys_lmdz_para
    1212  USE conema3_mod_h
     13  USE cv3param_mod_h
    1314  IMPLICIT NONE
    1415
     
    3536!***                 APPROACH TO QUASI-EQUILIBRIUM           ***
    3637!***                     IT MUST BE LESS THAN 0              ***
    37 
    38   include "cv3param.h"
    3938
    4039  INTEGER, INTENT(IN)              :: nd
     
    185184USE cvthermo_mod_h
    186185  USE cvflag_mod_h
     186USE cv3param_mod_h
    187187  IMPLICIT NONE
    188188
     
    190190!  Increment the counter sig(nd)
    191191! =====================================================================
    192 
    193   include "cv3param.h"
    194192
    195193!inputs:
     
    225223                      lv, lf, cpn, tv, gz, h, hm, th)
    226224  USE cvthermo_mod_h
     225  USE cv3param_mod_h
    227226  IMPLICIT NONE
    228227
     
    247246  REAL tvx, tvy ! convect3
    248247  REAL cpx(len, nd)
    249 
    250   include "cv3param.h"
    251 
    252248
    253249! ori      do 110 k=1,nlp
     
    325321  USE add_phys_tend_mod, ONLY: fl_cor_ebil
    326322  USE print_control_mod, ONLY: prt_level
     323  USE cv3param_mod_h
    327324  IMPLICIT NONE
    328325
     
    341338! - A,B explicitely defined (!...)
    342339! ================================================================
    343 
    344   include "cv3param.h"
    345340
    346341!inputs:
     
    700695#endif
    701696  USE cvthermo_mod_h
     697  USE cv3param_mod_h
    702698  IMPLICIT NONE
    703699
     
    714710!    - if icbs=icb, compute also tp(icb+1),tvp(icb+1) & clw(icb+1)
    715711! ----------------------------------------------------------------
    716 
    717   include "cv3param.h"
    718712
    719713! inputs:
     
    11461140SUBROUTINE cv3_trigger(len, nd, icb, plcl, p, th, tv, tvp, thnk, &
    11471141                       pbase, buoybase, iflag, sig, w0)
     1142  USE cv3param_mod_h
    11481143  IMPLICIT NONE
    11491144
     
    11621157! -> the buoyancy below cloud base not (yet) set to the cloud base buoyancy
    11631158! -------------------------------------------------------------------
    1164 
    1165   include "cv3param.h"
    11661159
    11671160! input:
     
    12761269#endif
    12771270#endif
    1278   IMPLICIT NONE
    1279 
    1280   include "cv3param.h"
     1271USE cv3param_mod_h
     1272    IMPLICIT NONE
     1273
    12811274
    12821275!inputs:
     
    14851478  USE cvflag_mod_h
    14861479  USE conema3_mod_h
     1480USE cv3param_mod_h
    14871481  IMPLICIT NONE
    14881482
     
    15041498!   - no inb1, only inb in output
    15051499! ---------------------------------------------------------------------
    1506 
    1507   include "cv3param.h"
    1508   include "YOMCST2.h"
     1500 include "YOMCST2.h"
    15091501
    15101502!inputs:
     
    25102502                       pbase, p, ph, tv, buoy, &
    25112503                       sig, w0, cape, m, iflag)
    2512   USE cvthermo_mod_h
     2504USE cv3param_mod_h
     2505    USE cvthermo_mod_h
    25132506  IMPLICIT NONE
    25142507
     
    25192512! ===================================================================
    25202513
    2521   include "cv3param.h"
    25222514
    25232515!input:
     
    27832775  USE cvthermo_mod_h
    27842776  USE cvflag_mod_h
     2777  USE cv3param_mod_h
    27852778  IMPLICIT NONE
    27862779
     
    27892782! - vectorisation de la partie normalisation des flux (do 789...)
    27902783! ---------------------------------------------------------------------
    2791 
    2792   include "cv3param.h"
    27932784
    27942785!inputs:
     
    36083599#endif
    36093600#endif
    3610   USE cvthermo_mod_h
     3601USE cv3param_mod_h
     3602    USE cvthermo_mod_h
    36113603  USE cvflag_mod_h
    36123604  IMPLICIT NONE
    36133605
    36143606
    3615   include "cv3param.h"
    36163607  include "nuage.h"
    36173608
     
    47204711#endif
    47214712#endif
    4722 USE conema3_mod_h
     4713USE cv3param_mod_h
     4714  USE conema3_mod_h
    47234715    USE cvthermo_mod_h
    47244716  USE cvflag_mod_h
    47254717  IMPLICIT NONE
    47264718
    4727   include "cv3param.h"
    47284719
    47294720!inputs:
     
    72897280                      ep, Vprecip, elij, clw, epmlmMm, eplaMm, &
    72907281                      icb, inb)
    7291   IMPLICIT NONE
    7292 
    7293   include "cv3param.h"
     7282USE cv3param_mod_h
     7283    IMPLICIT NONE
     7284
    72947285
    72957286!inputs:
     
    74247415#endif
    74257416#endif
    7426   IMPLICIT NONE
    7427 
    7428   include "cv3param.h"
     7417USE cv3param_mod_h
     7418    IMPLICIT NONE
     7419
    74297420
    74307421!inputs:
     
    76097600                 , pbase, p, ph, tv, buoy, sig, w0,iflag &
    76107601                 , epmax_diag)
    7611 USE conema3_mod_h
     7602USE cv3param_mod_h
     7603  USE conema3_mod_h
    76127604          USE cvthermo_mod_h
    76137605  USE cvflag_mod_h
     
    76197611        ! Toutes les autres variables fn de ep sont calculees plus bas.
    76207612
    7621   include "cv3param.h"
    76227613
    76237614! inputs:
  • LMDZ6/trunk/libf/phylmdiso/cv3a_compress.F90

    r4143 r5299  
    4141#endif
    4242
    43   IMPLICIT NONE
    44 
    45   include "cv3param.h"
     43USE cv3param_mod_h
     44    IMPLICIT NONE
     45
    4646
    4747  ! inputs:
  • LMDZ6/trunk/libf/phylmdiso/cv3a_uncompress.F90

    r4613 r5299  
    5656  USE infotrac_phy, ONLY : ntraciso=>ntiso
    5757#endif
    58   IMPLICIT NONE
    59 
    60   include "cv3param.h"
     58USE cv3param_mod_h
     59    IMPLICIT NONE
     60
    6161
    6262  ! inputs:
  • LMDZ6/trunk/libf/phylmdiso/cv3p_mixing.F90

    r5285 r5299  
    3939#endif
    4040#endif
    41   USE cvthermo_mod_h
     41USE cv3param_mod_h
     42    USE cvthermo_mod_h
    4243  USE cvflag_mod_h
    4344  IMPLICIT NONE
    4445
    45   include "cv3param.h"
    4646  include "YOMCST2.h"
    4747
  • LMDZ6/trunk/libf/phylmdiso/cv3param_mod_h.f90

    r5298 r5299  
    1 link ../phylmd/cv3param.h
     1link ../phylmd/cv3param_mod_h.f90
Note: See TracChangeset for help on using the changeset viewer.