Ignore:
Timestamp:
Oct 30, 2024, 6:34:05 PM (12 months ago)
Author:
abarral
Message:

Turn compar1d.h date_cas.h into module
Move fcg_racmo.h to obsolete

Location:
LMDZ6/trunk/libf/phylmd
Files:
1 edited
1 moved

Legend:

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

    r5285 r5303  
    44SUBROUTINE cv_param(nd)
    55  USE cvthermo_mod_h
     6  USE cvparam_mod_h
    67  IMPLICIT NONE
    78
     
    3738  ! ***                   (DAMP MUST BE LESS THAN 1)                 ***
    3839
    39   include "cvparam.h"
    4040  INTEGER nd
    4141  CHARACTER (LEN=20) :: modname = 'cv_routines'
     
    7777SUBROUTINE cv_prelim(len, nd, ndp1, t, q, p, ph, lv, cpn, tv, gz, h, hm)
    7878  USE cvthermo_mod_h
     79  USE cvparam_mod_h
    7980  IMPLICIT NONE
    8081
     
    9495  INTEGER k, i
    9596  REAL cpx(len, nd)
    96 
    97   include "cvparam.h"
    98 
    9997
    10098  DO k = 1, nlp
     
    134132SUBROUTINE cv_feed(len, nd, t, q, qs, p, hm, gz, nk, icb, icbmax, iflag, tnk, &
    135133    qnk, gznk, plcl)
    136   IMPLICIT NONE
     134USE cvparam_mod_h
     135    IMPLICIT NONE
    137136
    138137  ! ================================================================
     
    140139  ! ================================================================
    141140
    142   include "cvparam.h"
    143141
    144142  ! inputs:
     
    255253SUBROUTINE cv_undilute1(len, nd, t, q, qs, gz, p, nk, icb, icbmax, tp, tvp, &
    256254    clw)
    257   USE cvthermo_mod_h
     255USE cvparam_mod_h
     256    USE cvthermo_mod_h
    258257  IMPLICIT NONE
    259258
    260   include "cvparam.h"
    261259
    262260  ! inputs:
     
    364362
    365363SUBROUTINE cv_trigger(len, nd, icb, cbmf, tv, tvp, iflag)
    366   IMPLICIT NONE
     364USE cvparam_mod_h
     365    IMPLICIT NONE
    367366
    368367  ! -------------------------------------------------------------------
     
    372371  ! -------------------------------------------------------------------
    373372
    374   include "cvparam.h"
    375373
    376374  ! inputs:
     
    397395    tp1, tvp1, clw1, iflag, nk, icb, cbmf, plcl, tnk, qnk, gznk, t, q, qs, u, &
    398396    v, gz, h, lv, cpn, p, ph, tv, tp, tvp, clw, dph)
    399   USE print_control_mod, ONLY: lunout
     397USE cvparam_mod_h
     398    USE print_control_mod, ONLY: lunout
    400399  IMPLICIT NONE
    401400
    402   include "cvparam.h"
    403401
    404402  ! inputs:
     
    482480SUBROUTINE cv_undilute2(nloc, ncum, nd, icb, nk, tnk, qnk, gznk, t, q, qs, &
    483481    gz, p, dph, h, tv, lv, inb, inb1, tp, tvp, clw, hp, ep, sigp, frac)
    484   USE cvthermo_mod_h
     482USE cvparam_mod_h
     483    USE cvthermo_mod_h
    485484  IMPLICIT NONE
    486485
     
    494493  ! FIND THE LEVEL OF NEUTRAL BUOYANCY
    495494  ! ---------------------------------------------------------------------
    496   include "cvparam.h"
    497495
    498496  ! inputs:
     
    765763    cpn, iflag, cbmf)
    766764  USE cvthermo_mod_h
     765  USE cvparam_mod_h
    767766  IMPLICIT NONE
    768767
     
    782781  REAL dtpbl(nloc), dtmin(nloc), tvpplcl(nloc), tvaplcl(nloc)
    783782  REAL work(nloc)
    784   include "cvparam.h"
    785783
    786784  ! -------------------------------------------------------------------
     
    846844    h, lv, qnk, hp, tv, tvp, ep, clw, cbmf, m, ment, qent, uent, vent, nent, &
    847845    sij, elij)
    848   USE cvthermo_mod_h
     846USE cvparam_mod_h
     847    USE cvthermo_mod_h
    849848  IMPLICIT NONE
    850849
    851   include "cvparam.h"
    852850
    853851  ! inputs:
     
    10971095SUBROUTINE cv_unsat(nloc, ncum, nd, inb, t, q, qs, gz, u, v, p, ph, h, lv, &
    10981096    ep, sigp, clw, m, ment, elij, iflag, mp, qp, up, vp, wt, water, evap)
    1099   USE cvthermo_mod_h
     1097USE cvparam_mod_h
     1098    USE cvthermo_mod_h
    11001099  IMPLICIT NONE
    1101   include "cvparam.h"
    11021100
    11031101  ! inputs:
     
    12981296    ment, qent, uent, vent, nent, elij, tv, tvp, iflag, wd, qprime, tprime, &
    12991297    precip, cbmf, ft, fq, fu, fv, ma, qcondc)
    1300   USE cvthermo_mod_h
     1298USE cvparam_mod_h
     1299    USE cvthermo_mod_h
    13011300  IMPLICIT NONE
    13021301
    1303   include "cvparam.h"
    13041302
    13051303  ! inputs
     
    16661664    fq, fu, fv, ma, qcondc, iflag1, precip1, cbmf1, ft1, fq1, fu1, fv1, ma1, &
    16671665    qcondc1)
    1668   IMPLICIT NONE
    1669 
    1670   include "cvparam.h"
     1666USE cvparam_mod_h
     1667    IMPLICIT NONE
     1668
    16711669
    16721670  ! inputs:
  • LMDZ6/trunk/libf/phylmd/cvparam_mod_h.f90

    r5302 r5303  
    1 !
    2 ! $Header$
    3 !
    4 !------------------------------------------------------------
    5 ! Parameters for convectL:
    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 !------------------------------------------------------------
     1MODULE cvparam_mod_h
     2  IMPLICIT NONE; PRIVATE
     3  PUBLIC noff, minorig, nl, nlp, nlm &
     4          , elcrit, tlcrit &
     5          , entp, sigs, sigd &
     6          , omtrain, omtsnow, coeffr, coeffs &
     7          , dtmax, cu, betad, alpha, damp, delta
    118
    12       integer noff, minorig, nl, nlp, nlm
    13       real elcrit, tlcrit
    14       real entp
    15       real sigs, sigd
    16       real omtrain, omtsnow, coeffr, coeffs
    17       real dtmax
    18       real cu
    19       real betad
    20       real alpha, damp
    21       real delta
     9  integer noff, minorig, nl, nlp, nlm
     10  real elcrit, tlcrit
     11  real entp
     12  real sigs, sigd
     13  real omtrain, omtsnow, coeffr, coeffs
     14  real dtmax
     15  real cu
     16  real betad
     17  real alpha, damp
     18  real delta
    2219
    23       COMMON /cvparam/ noff, minorig, nl, nlp, nlm &
    24                       ,elcrit, tlcrit &
    25                       ,entp, sigs, sigd &
    26                       ,omtrain, omtsnow, coeffr, coeffs &
    27                       ,dtmax, cu, betad, alpha, damp, delta
    28 
    29 !$OMP THREADPRIVATE(/cvparam/)
     20  !$OMP THREADPRIVATE(noff, minorig, nl, nlp, nlm &
     21  !$OMP          , elcrit, tlcrit &
     22  !$OMP          , entp, sigs, sigd &
     23  !$OMP          , omtrain, omtsnow, coeffr, coeffs &
     24  !$OMP          , dtmax, cu, betad, alpha, damp, delta)
     25END MODULE cvparam_mod_h
Note: See TracChangeset for help on using the changeset viewer.