source: LMDZ6/trunk/libf/phylmd/cv3param_mod_h.f90 @ 5308

Last change on this file since 5308 was 5299, checked in by abarral, 39 hours ago

Turn cv3param.h into module

  • 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: 1.5 KB
Line 
1! Replaces cv3param.h
2
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
16
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
35
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
Note: See TracBrowser for help on using the repository browser.