Ignore:
Timestamp:
Jul 29, 2024, 12:37:08 PM (3 months ago)
Author:
abarral
Message:

Put cvthermo.h, cv30param.h, cv3param.h into modules

Location:
LMDZ6/branches/Amaury_dev/libf/phylmdiso
Files:
1 deleted
9 edited
3 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/cv3_enthalpmix.F90

    r5117 r5141  
    1717  ! modified by :  Filiberti M-A 06/2005 vectorisation          *
    1818  ! **************************************************************
     19USE lmdz_cvthermo
    1920
    2021  IMPLICIT NONE
     
    2930  ! ===============================================================
    3031
    31   include "cvthermo.h"
    3232  include "YOETHF.h"
    3333  include "YOMCST.h"
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/cv3_estatmix.F90

    r5117 r5141  
    1818  ! modified by :  Filiberti M-A 06/2005 vectorisation              *
    1919  ! ****************************************************************
     20USE lmdz_cvthermo
    2021
    2122  IMPLICIT NONE
     
    3031  ! ===============================================================
    3132
    32   include "cvthermo.h"
    3333  include "YOETHF.h"
    3434  include "YOMCST.h"
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/cv3_routines.F90

    r5140 r5141  
    1111  USE lmdz_conema3
    1212  USE lmdz_cvflag
     13  USE lmdz_cv3param
    1314
    1415  IMPLICIT NONE
     
    3637!***                 APPROACH TO QUASI-EQUILIBRIUM           ***
    3738!***                     IT MUST BE LESS THAN 0              ***
    38 
    39   include "cv3param.h"
    4039
    4140  INTEGER, INTENT(IN)              :: nd
     
    184183SUBROUTINE cv3_incrcount(len, nd, delt, sig)
    185184  USE lmdz_cvflag
     185  USE lmdz_cv3param
    186186
    187187IMPLICIT NONE
     
    190190!  Increment the counter sig(nd)
    191191! =====================================================================
    192 
    193   include "cv3param.h"
    194192
    195193!inputs:
     
    224222SUBROUTINE cv3_prelim(len, nd, ndp1, t, q, p, ph, &
    225223                      lv, lf, cpn, tv, gz, h, hm, th)
     224  USE lmdz_cvthermo
     225  USE lmdz_cv3param
     226
    226227  IMPLICIT NONE
    227228
     
    246247  REAL tvx, tvy ! convect3
    247248  REAL cpx(len, nd)
    248 
    249   include "cvthermo.h"
    250   include "cv3param.h"
    251 
    252249
    253250! ori      do 110 k=1,nlp
     
    324321  USE add_phys_tend_mod, ONLY: fl_cor_ebil
    325322  USE lmdz_print_control, ONLY: prt_level
     323USE lmdz_cvthermo
     324USE lmdz_cv3param
     325
    326326  IMPLICIT NONE
    327327
     
    340340! - A,B explicitely defined (!...)
    341341! ================================================================
    342 
    343   include "cv3param.h"
    344   include "cvthermo.h"
    345342
    346343!inputs:
     
    699696#endif
    700697#endif
     698USE lmdz_cvthermo
     699USE lmdz_cv3param
     700
    701701  IMPLICIT NONE
    702702
     
    713713!    - if icbs=icb, compute also tp(icb+1),tvp(icb+1) & clw(icb+1)
    714714! ----------------------------------------------------------------
    715 
    716   include "cvthermo.h"
    717   include "cv3param.h"
    718715
    719716! inputs:
     
    11461143SUBROUTINE cv3_trigger(len, nd, icb, plcl, p, th, tv, tvp, thnk, &
    11471144                       pbase, buoybase, iflag, sig, w0)
     1145  USE lmdz_cv3param
     1146
    11481147  IMPLICIT NONE
    11491148
     
    11621161! -> the buoyancy below cloud base not (yet) set to the cloud base buoyancy
    11631162! -------------------------------------------------------------------
    1164 
    1165   include "cv3param.h"
    11661163
    11671164! input:
     
    12781275#endif
    12791276#endif
     1277
     1278USE lmdz_cv3param
     1279
    12801280  IMPLICIT NONE
    1281 
    1282   include "cv3param.h"
    12831281
    12841282!inputs:
     
    14871485#endif
    14881486USE lmdz_cvflag
     1487USE lmdz_cvthermo
     1488USE lmdz_cv3param
     1489
    14891490  IMPLICIT NONE
    14901491
     
    15071508! ---------------------------------------------------------------------
    15081509
    1509   include "cvthermo.h"
    1510   include "cv3param.h"
    15111510  include "YOMCST2.h"
    15121511
     
    25092508END SUBROUTINE cv3_undilute2
    25102509
    2511 SUBROUTINE cv3_closure(nloc, ncum, nd, icb, inb, &
    2512                        pbase, p, ph, tv, buoy, &
     2510SUBROUTINE cv3_closure(nloc, ncum, nd, icb, inb, pbase, p, ph, tv, buoy, &
    25132511                       sig, w0, cape, m, iflag)
     2512  USE lmdz_cvthermo
     2513  USE lmdz_cv3param
     2514
    25142515  IMPLICIT NONE
    25152516
     
    25192520! vectorization: S. Bony
    25202521! ===================================================================
    2521 
    2522   include "cvthermo.h"
    2523   include "cv3param.h"
    25242522
    25252523!input:
     
    27842782#endif
    27852783USE lmdz_cvflag
     2784USE lmdz_cvthermo
     2785USE lmdz_cv3param
     2786
    27862787  IMPLICIT NONE
    27872788
     
    27902791! - vectorisation de la partie normalisation des flux (do 789...)
    27912792! ---------------------------------------------------------------------
    2792 
    2793   include "cvthermo.h"
    2794   include "cv3param.h"
    27952793
    27962794!inputs:
     
    36123610#endif
    36133611USE lmdz_cvflag
     3612USE lmdz_cvthermo
     3613USE lmdz_cv3param
     3614
    36143615  IMPLICIT NONE
    3615 
    3616 
    3617   include "cvthermo.h"
    3618   include "cv3param.h"
    36193616
    36203617!inputs:
     
    47184715#endif
    47194716USE lmdz_cvflag
     4717USE lmdz_cvthermo
     4718USE lmdz_cv3param
     4719
    47204720  IMPLICIT NONE
    4721 
    4722   include "cvthermo.h"
    4723   include "cv3param.h"
    47244721
    47254722!inputs:
     
    72747271                      ep, Vprecip, elij, clw, epmlmMm, eplaMm, &
    72757272                      icb, inb)
     7273  USE lmdz_cv3param
     7274
    72767275  IMPLICIT NONE
    7277 
    7278   include "cv3param.h"
    72797276
    72807277!inputs:
     
    74097406#endif
    74107407#endif
     7408USE lmdz_cv3param
     7409
    74117410  IMPLICIT NONE
    7412 
    7413   include "cv3param.h"
    74147411
    74157412!inputs:
     
    75977594                  USE lmdz_conema3
    75987595                  USE lmdz_cvflag
     7596                  USE lmdz_cvthermo
     7597                  USE lmdz_cv3param
    75997598
    76007599        IMPLICIT NONE
     
    76057604        ! qui en depend
    76067605        ! Toutes les autres variables fn de ep sont calculees plus bas.
    7607 
    7608   include "cvthermo.h"
    7609   include "cv3param.h" 
    76107606
    76117607! inputs:
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/cv3a_compress.F90

    r5132 r5141  
    4141#endif
    4242  USE lmdz_abort_physic, ONLY: abort_physic
     43USE lmdz_cv3param
     44
    4345  IMPLICIT NONE
    44 
    45   include "cv3param.h"
    4646
    4747  ! inputs:
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/cv3a_uncompress.F90

    r5117 r5141  
    5656  USE infotrac_phy, ONLY: ntraciso=>ntiso
    5757#endif
     58USE lmdz_cv3param
     59
    5860  IMPLICIT NONE
    59 
    60   include "cv3param.h"
    6161
    6262  ! inputs:
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/cv3p_mixing.F90

    r5140 r5141  
    4040#endif
    4141USE lmdz_cvflag
     42  USE lmdz_cvthermo
     43  USE lmdz_cv3param
     44
    4245  IMPLICIT NONE
    4346
    44   include "cvthermo.h"
    45   include "cv3param.h"
    4647  include "YOMCST2.h"
    4748
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/cv_driver.F90

    r5140 r5141  
    4242#endif
    4343#endif
     44USE lmdz_cv30, ONLY: cv30_param, cv30_prelim, cv30_feed, cv30_undilute1, cv30_trigger, cv30_compress, cv30_undilute2, &
     45          cv30_closure, cv30_epmax_fn_cape, cv30_mixing, cv30_unsat, cv30_yield, cv30_tracer, cv30_uncompress
     46
    4447  IMPLICIT NONE
    4548
     
    12611264! ==================================================================
    12621265SUBROUTINE cv_thermo(iflag_con)
     1266  USE lmdz_cvthermo
     1267
    12631268  IMPLICIT NONE
    12641269
     
    12681273
    12691274  include "YOMCST.h"
    1270   include "cvthermo.h"
    12711275
    12721276  INTEGER iflag_con
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/cv_routines.F90

    r5132 r5141  
    7373
    7474SUBROUTINE cv_prelim(len, nd, ndp1, t, q, p, ph, lv, cpn, tv, gz, h, hm)
     75  USE lmdz_cvthermo
     76
    7577  IMPLICIT NONE
    7678
     
    9193  REAL cpx(len, nd)
    9294
    93   include "cvthermo.h"
    9495  include "cvparam.h"
    9596
     
    249250SUBROUTINE cv_undilute1(len, nd, t, q, qs, gz, p, nk, icb, icbmax, tp, tvp, &
    250251        clw)
     252  USE lmdz_cvthermo
     253
    251254  IMPLICIT NONE
    252255
    253   include "cvthermo.h"
    254256  include "cvparam.h"
    255257
     
    472474SUBROUTINE cv_undilute2(nloc, ncum, nd, icb, nk, tnk, qnk, gznk, t, q, qs, &
    473475        gz, p, dph, h, tv, lv, inb, inb1, tp, tvp, clw, hp, ep, sigp, frac)
     476  USE lmdz_cvthermo
     477
    474478  IMPLICIT NONE
    475479
     
    484488  ! ---------------------------------------------------------------------
    485489
    486   include "cvthermo.h"
    487490  include "cvparam.h"
    488491
     
    752755SUBROUTINE cv_closure(nloc, ncum, nd, nk, icb, tv, tvp, p, ph, dph, plcl, &
    753756        cpn, iflag, cbmf)
     757  USE lmdz_cvthermo
     758
    754759  IMPLICIT NONE
    755760
     
    770775  REAL work(nloc)
    771776
    772   include "cvthermo.h"
    773777  include "cvparam.h"
    774778
     
    834838        h, lv, qnk, hp, tv, tvp, ep, clw, cbmf, m, ment, qent, uent, vent, nent, &
    835839        sij, elij)
     840  USE lmdz_cvthermo
     841
    836842  IMPLICIT NONE
    837843
    838   include "cvthermo.h"
    839844  include "cvparam.h"
    840845
     
    10831088SUBROUTINE cv_unsat(nloc, ncum, nd, inb, t, q, qs, gz, u, v, p, ph, h, lv, &
    10841089        ep, sigp, clw, m, ment, elij, iflag, mp, qp, up, vp, wt, water, evap)
     1090  USE lmdz_cvthermo
     1091
    10851092  IMPLICIT NONE
    10861093
    1087   include "cvthermo.h"
    10881094  include "cvparam.h"
    10891095
     
    12821288        ment, qent, uent, vent, nent, elij, tv, tvp, iflag, wd, qprime, tprime, &
    12831289        precip, cbmf, ft, fq, fu, fv, ma, qcondc)
     1290  USE lmdz_cvthermo
     1291
    12841292  IMPLICIT NONE
    12851293
    1286   include "cvthermo.h"
    12871294  include "cvparam.h"
    12881295
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/lmdz_cv30.F90

    r5140 r5141  
     1! $Id$
     2
     3MODULE lmdz_cv30
     4  !------------------------------------------------------------
     5  ! Parameters for convectL, iflag_con=30:
     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
     12  IMPLICIT NONE; PRIVATE
     13  PUBLIC sigd, spfac, pbcrit, ptcrit, omtrain, dtovsh, dpbase, dttrig, dtcrit, &
     14          tau, beta, alpha, delta, betad, noff, minorig, nl, nlp, nlm, &
     15          cv30_param, cv30_prelim, cv30_feed, cv30_undilute1, cv30_trigger, &
     16          cv30_compress, cv30_undilute2, cv30_closure, cv30_mixing, cv30_unsat, &
     17          cv30_yield, cv30_tracer, cv30_uncompress, cv30_epmax_fn_cape
     18
     19  INTEGER noff, minorig, nl, nlp, nlm
     20  REAL sigd, spfac
     21  REAL pbcrit, ptcrit
     22  REAL omtrain
     23  REAL dtovsh, dpbase, dttrig
     24  REAL dtcrit, tau, beta, alpha
     25  REAL delta
     26  REAL betad
     27
     28  !$OMP THREADPRIVATE(sigd, spfac, pbcrit, ptcrit, omtrain, dtovsh, dpbase, dttrig, dtcrit, &
     29  !$OMP      tau, beta, alpha, delta, betad, noff, minorig, nl, nlp, nlm)
     30CONTAINS
     31
    132
    233! $Id$
     
    3162  ! ***                 APPROACH TO QUASI-EQUILIBRIUM           ***
    3263  ! ***                     IT MUST BE LESS THAN 0              ***
    33 
    34   include "cv30param.h"
    35 
     64 
    3665  INTEGER nd
    3766  REAL delt ! timestep (seconds)
     
    86115SUBROUTINE cv30_prelim(len, nd, ndp1, t, q, p, ph, lv, cpn, tv, gz, h, hm, &
    87116    th)
     117
     118  USE lmdz_cvthermo
    88119  IMPLICIT NONE
    89120
     
    108139  REAL tvx, tvy ! convect3
    109140  REAL cpx(len, nd)
    110 
    111   include "cvthermo.h"
    112   include "cv30param.h"
    113141
    114142
     
    184212  ! ================================================================
    185213
    186   include "cv30param.h"
     214 
    187215
    188216  ! inputs:
     
    389417#endif
    390418#endif
     419USE lmdz_cvthermo
    391420
    392421  IMPLICIT NONE
     
    405434  ! ----------------------------------------------------------------
    406435
    407   include "cvthermo.h"
    408   include "cv30param.h"
    409436
    410437  ! inputs:
     
    851878  ! -------------------------------------------------------------------
    852879
    853   include "cv30param.h"
     880 
    854881
    855882  ! input:
     
    961988  IMPLICIT NONE
    962989
    963   include "cv30param.h"
     990 
    964991
    965992  ! inputs:
     
    11541181#endif
    11551182#endif
     1183USE lmdz_cvthermo
    11561184  IMPLICIT NONE
    11571185
     
    11731201  ! - no inb1, ONLY inb in output
    11741202  ! ---------------------------------------------------------------------
    1175 
    1176   include "cvthermo.h"
    1177   include "cv30param.h"
    11781203
    11791204  ! inputs:
     
    16181643SUBROUTINE cv30_closure(nloc, ncum, nd, icb, inb, pbase, p, ph, tv, buoy, &
    16191644    sig, w0, cape, m)
     1645  USE lmdz_cvthermo
     1646
    16201647  IMPLICIT NONE
    16211648
     
    16251652  ! vectorization: S. Bony
    16261653  ! ===================================================================
    1627 
    1628   include "cvthermo.h"
    1629   include "cv30param.h"
    16301654
    16311655  ! input:
     
    18541878#endif
    18551879#endif
     1880USE lmdz_cvthermo
     1881
    18561882  IMPLICIT NONE
    18571883
     
    18611887  ! - vectorisation de la partie normalisation des flux (do 789...)
    18621888  ! ---------------------------------------------------------------------
    1863 
    1864   include "cvthermo.h"
    1865   include "cv30param.h"
    18661889
    18671890  ! inputs:
     
    26702693#endif
    26712694USE lmdz_cvflag
     2695USE lmdz_cvthermo
    26722696
    26732697  IMPLICIT NONE
    2674 
    2675 
    2676   include "cvthermo.h"
    2677   include "cv30param.h"
    26782698
    26792699  ! inputs:
     
    34023422#endif
    34033423USE lmdz_cvflag
     3424USE lmdz_cvthermo
    34043425
    34053426  IMPLICIT NONE
    3406 
    3407   include "cvthermo.h"
    3408   include "cv30param.h"
    3409 
    34103427  ! inputs:
    34113428  INTEGER ncum, nd, na, ntra, nloc
     
    59725989  IMPLICIT NONE
    59735990
    5974   include "cv30param.h"
     5991 
    59755992
    59765993  ! inputs:
     
    61146131  IMPLICIT NONE
    61156132
    6116   include "cv30param.h"
     6133 
    61176134
    61186135  ! inputs:
     
    63386355        USE lmdz_abort_physic, ONLY: abort_physic
    63396356                USE lmdz_conema3
     6357        USE lmdz_cvthermo
    63406358
    63416359        IMPLICIT NONE
     
    63456363        ! qui en depend
    63466364        ! Toutes les autres variables fn de ep sont calculees plus bas.
    6347 
    6348  include "cvthermo.h"
    6349  include "cv30param.h"
    63506365
    63516366! inputs:
     
    64216436
    64226437
     6438
     6439
     6440
     6441
     6442END MODULE lmdz_cv30
     6443
     6444
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/lmdz_cv3param.f90

    r5140 r5141  
    1 link ../phylmd/cv3param.h
     1link ../phylmd/lmdz_cv3param.f90
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/lmdz_cvthermo.f90

    r5140 r5141  
    1 link ../phylmd/cvthermo.h
     1link ../phylmd/lmdz_cvthermo.f90
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/lmdz_wake.F90

    r5117 r5141  
    4141#endif
    4242#endif
     43USE lmdz_cvthermo
     44
    4345  IMPLICIT NONE
    4446  ! ============================================================================
     
    136138
    137139  include "YOMCST.h"
    138   include "cvthermo.h"
    139140
    140141  ! Arguments en entree
Note: See TracChangeset for help on using the changeset viewer.