Changeset 5346


Ignore:
Timestamp:
Nov 28, 2024, 8:41:47 PM (25 hours ago)
Author:
fhourdin
Message:

Debut de replaysation de la convection profonde.

Regroupement de cvparam, cv3param et cvthermo (récemment
passés de statut de .h à module, dans un unique module
lmdz_cv_ini.f90

Location:
LMDZ6/trunk/libf/phylmd
Files:
1 added
3 deleted
15 edited

Legend:

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

    r5283 r5346  
    107107  SUBROUTINE cv30_prelim(len, nd, ndp1, t, q, p, ph, lv, cpn, tv, gz, h, hm, &
    108108          th)
    109     USE cvthermo_mod_h
     109   USE lmdz_cv_ini, ONLY : rrd,rrv,lv0,eps,cpv,cpd,clmcpv,cl,rrv
    110110
    111111    IMPLICIT NONE
     
    360360  SUBROUTINE cv30_undilute1(len, nd, t, q, qs, gz, plcl, p, nk, icb, tp, tvp, &
    361361          clw, icbs)
    362     USE cvthermo_mod_h
     362   USE lmdz_cv_ini, ONLY : cl,clmcpv,cpd,cpv,eps,lv0,rrv
    363363
    364364    IMPLICIT NONE
     
    853853    ! epmax_cape: ajout arguments
    854854    USE conema3_mod_h
    855     USE cvthermo_mod_h
     855   USE lmdz_cv_ini, ONLY : eps,lv0,rrv,cl,clmcpv,cpd,cpv
    856856
    857857    IMPLICIT NONE
     
    12231223  SUBROUTINE cv30_closure(nloc, ncum, nd, icb, inb, pbase, p, ph, tv, buoy, &
    12241224          sig, w0, cape, m)
    1225     USE cvthermo_mod_h
     1225   USE lmdz_cv_ini, ONLY : rrd
    12261226
    12271227    IMPLICIT NONE
     
    14291429          u, v, tra, h, lv, qnk, hp, tv, tvp, ep, clw, m, sig, ment, qent, uent, &
    14301430          vent, sij, elij, ments, qents, traent)
    1431     USE cvthermo_mod_h
     1431   USE lmdz_cv_ini, ONLY : cpd,cpv,rrv
    14321432
    14331433    IMPLICIT NONE
     
    18271827          , wdtraina, wdtrainm) ! 26/08/10  RomP-jyg
    18281828    USE cvflag_mod_h
    1829     USE cvthermo_mod_h
     1829   USE lmdz_cv_ini, ONLY : cpd,grav,ginv
    18301830
    18311831    IMPLICIT NONE
     
    21902190    USE conema3_mod_h
    21912191    USE cvflag_mod_h
    2192     USE cvthermo_mod_h
     2192   USE lmdz_cv_ini, ONLY : cl,cpd,rrv,rrd,rowl,grav,cpv
    21932193
    21942194    IMPLICIT NONE
     
    32713271          , epmax_diag)
    32723272    USE conema3_mod_h
    3273     USE cvthermo_mod_h
     3273   USE lmdz_cv_ini, ONLY : cpd, cpv
    32743274
    32753275    IMPLICIT NONE
  • LMDZ6/trunk/libf/phylmd/cv3_buoy.f90

    r5304 r5346  
    1111
    1212USE yomcst2_mod_h
    13   USE cv3param_mod_h
    14     USE cvthermo_mod_h
     13   USE lmdz_cv_ini, ONLY : grav,nl
    1514  IMPLICIT NONE
    1615
  • LMDZ6/trunk/libf/phylmd/cv3_cine.f90

    r5299 r5346  
    1515  ! **************************************************************
    1616
    17 USE cv3param_mod_h
    18     USE cvthermo_mod_h
     17   USE lmdz_cv_ini, ONLY : nl
     18
    1919  USE yomcst_mod_h
    2020IMPLICIT NONE
  • LMDZ6/trunk/libf/phylmd/cv3_crit.f90

    r5299 r5346  
    1010  ! **************************************************************
    1111
    12 USE cv3param_mod_h
     12   USE lmdz_cv_ini, ONLY : nl
    1313    IMPLICIT NONE
    1414
  • LMDZ6/trunk/libf/phylmd/cv3_enthalpmix.f90

    r5285 r5346  
    1111  ! **************************************************************
    1212
    13   USE cvthermo_mod_h
     13   USE lmdz_cv_ini, ONLY : cpd,cpv,rrd,rrv
    1414  USE yomcst_mod_h
    1515  USE yoethf_mod_h
  • LMDZ6/trunk/libf/phylmd/cv3_estatmix.f90

    r5285 r5346  
    1212  ! ****************************************************************
    1313
    14   USE cvthermo_mod_h
     14   USE lmdz_cv_ini, ONLY : cpd,cpv,rrd,rrv
    1515  USE yomcst_mod_h
    1616  USE yoethf_mod_h
  • LMDZ6/trunk/libf/phylmd/cv3_mixscale.f90

    r5299 r5346  
    99  ! **************************************************************
    1010
    11 USE cv3param_mod_h
     11   USE lmdz_cv_ini, ONLY : nl
    1212    IMPLICIT NONE
    1313
  • LMDZ6/trunk/libf/phylmd/cv3_routines.f90

    r5305 r5346  
    1111  use mod_phys_lmdz_para
    1212  USE conema3_mod_h
    13   USE cv3param_mod_h
     13  USE lmdz_cv_ini, ONLY : alpha,alpha1,beta,betad,coef_peel,cv_flag_feed,delta,dpbase,dtcrit,dtovsh,dttrig,ejectice,ejectliq,elcrit,flag_epkeorig,flag_wb,minorig,nl,nlm,nlp,noconv_stop,noff,omtrain,pbcrit,ptcrit,sigdz,spfac,t_top_max,tau,tau_stop,tlcrit,wbmax
     14
     15
    1416  IMPLICIT NONE
    1517
     
    182184SUBROUTINE cv3_incrcount(len, nd, delt, sig)
    183185
    184 USE cvthermo_mod_h
     186  USE lmdz_cv_ini, ONLY : noconv_stop
    185187  USE cvflag_mod_h
    186 USE cv3param_mod_h
    187188  IMPLICIT NONE
    188189
     
    222223SUBROUTINE cv3_prelim(len, nd, ndp1, t, q, p, ph, &
    223224                      lv, lf, cpn, tv, gz, h, hm, th)
    224   USE cvthermo_mod_h
    225   USE cv3param_mod_h
     225  USE lmdz_cv_ini, ONLY : cl,clmci,clmcpv,cpd,cpv,eps,lf0,lv0,nl,nlp,rrd,rrv
    226226  IMPLICIT NONE
    227227
     
    308308  USE add_phys_tend_mod, ONLY: fl_cor_ebil
    309309  USE print_control_mod, ONLY: prt_level
    310   USE cvthermo_mod_h
    311   USE cv3param_mod_h
     310  USE lmdz_cv_ini, ONLY : cpd,cpv,cv_flag_feed,minorig,nl,nlm,cl
    312311  IMPLICIT NONE
    313312
     
    598597SUBROUTINE cv3_undilute1(len, nd, t, qs, gz, plcl, p, icb, tnk, qnk, gznk, &
    599598                         tp, tvp, clw, icbs)
    600   USE cvthermo_mod_h
    601599  USE cvflag_mod_h
    602   USE cv3param_mod_h
     600  USE lmdz_cv_ini, ONLY : cl,rrv,clmcpv,cpd,cpv,eps,lv0,minorig,nl
    603601  IMPLICIT NONE
    604602
     
    874872SUBROUTINE cv3_trigger(len, nd, icb, plcl, p, th, tv, tvp, thnk, &
    875873                       pbase, buoybase, iflag, sig, w0)
    876   USE cv3param_mod_h
     874  USE lmdz_cv_ini, ONLY : alpha,beta,dpbase,dtcrit,dttrig,nl
    877875  IMPLICIT NONE
    878876
     
    987985                        h, lv, cpn, p, ph, tv, tp, tvp, clw, &
    988986                        sig, w0)
    989 USE cv3param_mod_h
     987  USE lmdz_cv_ini, ONLY : nl
    990988    USE print_control_mod, ONLY: lunout
    991989  IMPLICIT NONE
     
    11301128  USE print_control_mod, ONLY: prt_level
    11311129  USE cvflag_mod_h
    1132   USE cvthermo_mod_h
    11331130  USE conema3_mod_h
    1134   USE cv3param_mod_h
     1131  USE lmdz_cv_ini, ONLY : cl,clmci,clmcpv,cpd,cpv,dtovsh,ejectice,ejectliq,elcrit
     1132  USE lmdz_cv_ini, ONLY : eps,flag_epkeorig,lf0,lv0,minorig,nl,nlp,pbcrit,ptcrit,rrd,rrv,spfac,t0,t_top_max,tlcrit
    11351133  USE yomcst2_mod_h
    11361134  IMPLICIT NONE
     
    20382036                       pbase, p, ph, tv, buoy, &
    20392037                       sig, w0, cape, m, iflag)
    2040 USE cv3param_mod_h
    2041     USE cvthermo_mod_h
     2038  USE lmdz_cv_ini, ONLY : alpha,beta,dtcrit,minorig,nl,rrd
    20422039  USE cvflag_mod_h
    20432040  IMPLICIT NONE
     
    22822279                      ment, qent, uent, vent, nent, sij, elij, ments, qents, traent)
    22832280  USE cvflag_mod_h
    2284   USE cvthermo_mod_h
    2285   USE cv3param_mod_h
     2281  USE lmdz_cv_ini, ONLY : cpd,cpv,minorig,nl,rrv,cpd,ginv,grav
    22862282  IMPLICIT NONE
    22872283
     
    27022698                     faci, b, sigd, &
    27032699                     wdtrainA, wdtrainS, wdtrainM)                                      ! RomP
    2704 USE cv3param_mod_h
    2705     USE cvthermo_mod_h
     2700  USE lmdz_cv_ini, ONLY : cpd,ginv,grav,nl,nlp,sigdz
    27062701  USE cvflag_mod_h
    27072702  USE print_control_mod, ONLY: prt_level, lunout
     
    34453440                     ftd, fqd, qta, qtc, sigt, detrain, tau_cld_cv, coefw_cld_cv)
    34463441
    3447 USE cv3param_mod_h
    34483442  USE conema3_mod_h
    34493443      USE print_control_mod, ONLY: lunout, prt_level
    34503444    USE add_phys_tend_mod, only : fl_cor_ebil
    34513445    USE cvflag_mod_h
    3452     USE cvthermo_mod_h
     3446   USE lmdz_cv_ini, ONLY : grav,minorig,nl,nlp,rowl,rrd,nl,ci,cl,cpd,cpv
    34533447  IMPLICIT NONE
    34543448
     
    49424936                      ep, Vprecip, elij, clw, epmlmMm, eplaMm, &
    49434937                      icb, inb)
    4944 USE cv3param_mod_h
    4945     USE cvthermo_mod_h
     4938   USE lmdz_cv_ini, ONLY : nl
    49464939  USE cvflag_mod_h
    49474940  IMPLICIT NONE
     
    50515044                          Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, cape1, &
    50525045                          epmax_diag1) ! epmax_cape
    5053 USE cv3param_mod_h
     5046   USE lmdz_cv_ini, ONLY : nl
    50545047    IMPLICIT NONE
    50555048
     
    51305123                 , pbase, p, ph, tv, buoy, sig, w0,iflag &
    51315124                 , epmax_diag)
    5132 USE cv3param_mod_h
    51335125  USE conema3_mod_h
    51345126            USE cvflag_mod_h
    5135           USE cvthermo_mod_h
     5127   USE lmdz_cv_ini, ONLY : nl,minorig,cpd,cpv
    51365128        implicit none
    51375129
  • LMDZ6/trunk/libf/phylmd/cv3a_compress.f90

    r5299 r5346  
    2929  ! **************************************************************
    3030
    31 USE cv3param_mod_h
     31   USE lmdz_cv_ini, ONLY : nl
    3232    IMPLICIT NONE
    3333
  • LMDZ6/trunk/libf/phylmd/cv3a_uncompress.f90

    r5299 r5346  
    3838  ! **************************************************************
    3939
    40 USE cv3param_mod_h
     40   USE lmdz_cv_ini, ONLY : nl,nlp
    4141    IMPLICIT NONE
    4242
  • LMDZ6/trunk/libf/phylmd/cv3p1_closure.f90

    r5304 r5346  
    2020
    2121USE yomcst2_mod_h
    22   USE cv3param_mod_h
     22   USE lmdz_cv_ini, ONLY : pbcrit,wbmax,rrd,minorig,flag_wb,alpha,alpha1,beta,coef_peel,nl
    2323  USE conema3_mod_h
    24     USE cvthermo_mod_h
    2524  USE print_control_mod, ONLY: prt_level, lunout
    2625  USE yomcst_mod_h
  • LMDZ6/trunk/libf/phylmd/cv3p2_closure.f90

    r5304 r5346  
    1919
    2020USE yomcst2_mod_h
    21   USE cv3param_mod_h
     21   USE lmdz_cv_ini, ONLY : alpha,alpha1,beta,flag_wb,minorig,nl,noconv_stop,pbcrit,rrd,wbmax,coef_peel
    2222  USE conema3_mod_h
    23     USE cvthermo_mod_h
    2423  USE cvflag_mod_h
    2524  USE print_control_mod, ONLY: prt_level, lunout
  • LMDZ6/trunk/libf/phylmd/cv3p_mixing.f90

    r5304 r5346  
    1414
    1515USE yomcst2_mod_h
    16   USE cv3param_mod_h
    17     USE cvthermo_mod_h
     16   USE lmdz_cv_ini, ONLY : cpd,cpv,minorig,nl,rrv
    1817  USE cvflag_mod_h
    1918  USE print_control_mod, ONLY: mydebug=>debug , lunout, prt_level
  • LMDZ6/trunk/libf/phylmd/cv_driver.F90

    r5285 r5346  
    684684SUBROUTINE cv_flag(iflag_ice_thermo)
    685685
    686   USE cvthermo_mod_h
    687686  USE cvflag_mod_h
    688687  USE ioipsl_getin_p_mod, ONLY : getin_p
     
    719718SUBROUTINE cv_thermo(iflag_con)
    720719  USE yomcst_mod_h
    721   USE cvthermo_mod_h
     720  USE lmdz_cv_ini, ONLY : ci,cl,clmci,clmcpd,clmcpv,cpd,cpdmcp,cpv,cpvmcl,cpvmcpd,eps,epsi,epsim1,g,ginv,grav,hrd,lf0,lv0,rowl,rrd,rrv,t0
     721
    722722IMPLICIT NONE
    723723
  • LMDZ6/trunk/libf/phylmd/cv_routines.f90

    r5303 r5346  
    33
    44SUBROUTINE cv_param(nd)
    5   USE cvthermo_mod_h
    6   USE cvparam_mod_h
     5  USE lmdz_cv_ini, ONLY : alpha,betad,coeffr,coeffs,cu,damp,delta,dtmax,elcrit,entp,minorig,nl,nlm,nlp,noff,omtrain,omtsnow,sigd,sigs,tlcrit
     6
    77  IMPLICIT NONE
    88
     
    7676
    7777SUBROUTINE cv_prelim(len, nd, ndp1, t, q, p, ph, lv, cpn, tv, gz, h, hm)
    78   USE cvthermo_mod_h
    79   USE cvparam_mod_h
     78  USE lmdz_cv_ini, ONLY : cl,clmcpv,cpd,cpv,epsim1,hrd,lv0,nlp,t0
     79
    8080  IMPLICIT NONE
    8181
     
    132132SUBROUTINE cv_feed(len, nd, t, q, qs, p, hm, gz, nk, icb, icbmax, iflag, tnk, &
    133133    qnk, gznk, plcl)
    134 USE cvparam_mod_h
     134   USE lmdz_cv_ini, ONLY : minorig,nl,nlm,nlp
     135
    135136    IMPLICIT NONE
    136137
     
    253254SUBROUTINE cv_undilute1(len, nd, t, q, qs, gz, p, nk, icb, icbmax, tp, tvp, &
    254255    clw)
    255 USE cvparam_mod_h
    256     USE cvthermo_mod_h
     256  USE lmdz_cv_ini, ONLY : cl,clmcpv,cpd,cpv,eps,epsi,lv0,minorig,rrv,t0
     257
    257258  IMPLICIT NONE
    258259
     
    362363
    363364SUBROUTINE cv_trigger(len, nd, icb, cbmf, tv, tvp, iflag)
    364 USE cvparam_mod_h
     365   USE lmdz_cv_ini, ONLY : dtmax
    365366    IMPLICIT NONE
    366367
     
    395396    tp1, tvp1, clw1, iflag, nk, icb, cbmf, plcl, tnk, qnk, gznk, t, q, qs, u, &
    396397    v, gz, h, lv, cpn, p, ph, tv, tp, tvp, clw, dph)
    397 USE cvparam_mod_h
     398   USE lmdz_cv_ini, ONLY : nl
    398399    USE print_control_mod, ONLY: lunout
    399400  IMPLICIT NONE
     
    480481SUBROUTINE cv_undilute2(nloc, ncum, nd, icb, nk, tnk, qnk, gznk, t, q, qs, &
    481482    gz, p, dph, h, tv, lv, inb, inb1, tp, tvp, clw, hp, ep, sigp, frac)
    482 USE cvparam_mod_h
    483     USE cvthermo_mod_h
     483  USE lmdz_cv_ini, ONLY : nl,cl,clmcpv,cpd,cpv,elcrit,eps,epsi,lv0,minorig,nlp,rrv,sigs,t0,tlcrit
     484
    484485  IMPLICIT NONE
    485486
     
    762763SUBROUTINE cv_closure(nloc, ncum, nd, nk, icb, tv, tvp, p, ph, dph, plcl, &
    763764    cpn, iflag, cbmf)
    764   USE cvthermo_mod_h
    765   USE cvparam_mod_h
     765  USE lmdz_cv_ini, ONLY : alpha,damp,dtmax,minorig,rrd
     766
    766767  IMPLICIT NONE
    767768
     
    844845    h, lv, qnk, hp, tv, tvp, ep, clw, cbmf, m, ment, qent, uent, vent, nent, &
    845846    sij, elij)
    846 USE cvparam_mod_h
    847     USE cvthermo_mod_h
     847  USE lmdz_cv_ini, ONLY : cpd,cpv,entp,minorig,nl,nlp,rrv
     848
    848849  IMPLICIT NONE
    849850
     
    10951096SUBROUTINE cv_unsat(nloc, ncum, nd, inb, t, q, qs, gz, u, v, p, ph, h, lv, &
    10961097    ep, sigp, clw, m, ment, elij, iflag, mp, qp, up, vp, wt, water, evap)
    1097 USE cvparam_mod_h
    1098     USE cvthermo_mod_h
     1098  USE lmdz_cv_ini, ONLY : cl,coeffr,coeffs,cpd,g,ginv,nl,omtrain,omtsnow,sigd
     1099
    10991100  IMPLICIT NONE
    11001101
     
    12961297    ment, qent, uent, vent, nent, elij, tv, tvp, iflag, wd, qprime, tprime, &
    12971298    precip, cbmf, ft, fq, fu, fv, ma, qcondc)
    1298 USE cvparam_mod_h
    1299     USE cvthermo_mod_h
     1299  USE lmdz_cv_ini, ONLY : g,lv0,nl,rrd,sigd,betad,cl,cpd,cpv,cu,delta
     1300
    13001301  IMPLICIT NONE
    13011302
     
    16641665    fq, fu, fv, ma, qcondc, iflag1, precip1, cbmf1, ft1, fq1, fu1, fv1, ma1, &
    16651666    qcondc1)
    1666 USE cvparam_mod_h
     1667   USE lmdz_cv_ini, ONLY : nl
    16671668    IMPLICIT NONE
    16681669
Note: See TracChangeset for help on using the changeset viewer.