Changeset 2467


Ignore:
Timestamp:
Mar 15, 2016, 11:00:01 AM (8 years ago)
Author:
idelkadi
Message:

Utilisiation de la routine getin pour lire des parametres de la parametrization de la convection et nuages.
Passage des fichiers conv_param.data et ep_param.data a conv_param.def et de wake_param.data a wake_param.def

Location:
LMDZ5/trunk
Files:
2 added
3 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/DefLists/run.def

    r1907 r2467  
    33## Fichier de configuration general
    44##
     5INCLUDEDEF=gcm.def
    56INCLUDEDEF=physiq.def
    6 INCLUDEDEF=gcm.def
     7INCLUDEDEF=conv_param.def
     8INCLUDEDEF=wake_param.def
    79INCLUDEDEF=orchidee.def
    810INCLUDEDEF=output.def
  • LMDZ5/trunk/libf/phylmd/cv3_routines.F90

    r2459 r2467  
    77SUBROUTINE cv3_param(nd, k_upper, delt)
    88
     9  USE IOIPSL, ONLY : getin
    910  use mod_phys_lmdz_para
    1011  IMPLICIT NONE
     
    3940  INTEGER, INTENT(IN)              :: k_upper
    4041  REAL, INTENT(IN)                 :: delt ! timestep (seconds)
     42
     43! Var interm pour le getin
     44  REAL, SAVE :: dpbase_omp=-40.
     45  REAL, SAVE :: pbcrit_omp=150.0           
     46  REAL, SAVE :: ptcrit_omp=500.0
     47  REAL, SAVE :: sigdz_omp=0.01
     48  REAL, SAVE :: spfac_omp=0.15
     49  REAL, SAVE :: tau_omp=8000.
     50  INTEGER, SAVE :: flag_wb_omp=1
     51  REAL, SAVE :: wbmax_omp=6.
     52  LOGICAL, SAVE :: ok_convstop_omp=.False.
     53  REAL, SAVE :: tau_stop_omp=15000.
     54  REAL, SAVE :: ok_intermittent_omp=.False.
     55  REAL, SAVE :: coef_peel_omp=0.25
     56  INTEGER, SAVE :: flag_epKEorig_omp=1   
     57  REAL, SAVE :: elcrit_omp=0.0003
     58  REAL, SAVE :: tlcrit_omp=-55.0
     59!$OMP
     60!THREADPRIVATE(dpbase_omp,pbcrit_omp,ptcrit_omp,sigdz_omp,spfac_omp,tau_omp,flag_wb_omp)
     61!THREADPRIVATE(wbmax_omp,ok_convstop_omp,tau_stop_omp,ok_intermittent_omp,coef_peel_omp)
     62!THREADPRIVATE(flag_epKEorig_omp,elcrit_omp,tlcrit_omp)
    4163
    4264
     
    6587
    6688  IF (first) THEN
    67 
    6889! -- "microphysical" parameters:
    69     sigdz = 0.01
    70     spfac = 0.15
    71     pbcrit = 150.0
    72     ptcrit = 500.0
    7390! IM beg: ajout fis. reglage ep
    74     flag_epkeorig = 1
    75     elcrit = 0.0003
    76     tlcrit = -55.0
    7791! CR+JYG: shedding coefficient (used when iflag_mix_adiab=1)
    78     coef_peel = 0.25
    7992! IM lu dans physiq.def via conf_phys.F90     epmax  = 0.993
    8093
     
    8295
    8396! -- misc:
    84 
    8597    dtovsh = -0.2 ! dT for overshoot
    86     dpbase = -40. ! definition cloud base (400m above LCL)
    8798! cc      dttrig = 5.   ! (loose) condition for triggering
    8899    dttrig = 10. ! (loose) condition for triggering
    89     flag_wb = 1
    90     wbmax = 6. ! (m/s) adiab updraught speed at LFC (used in cv3p1_closure)
    91 
    92 ! -- rate of approach to quasi-equilibrium:
    93 
    94100    dtcrit = -2.0
    95     tau = 8000.
    96101
    97102! -- end of convection
    98103
    99     tau_stop = 15000.
    100     ok_convstop = .False.
    101 
    102     ok_intermittent = .False.
    103 
    104104! -- interface cloud parameterization:
    105105
     
    111111
    112112   !$OMP MASTER
    113     OPEN (99, FILE='conv_param.data', STATUS='old', FORM='formatted', ERR=9999)
    114     READ (99, *, END=9998) dpbase
    115     READ (99, *, END=9998) pbcrit
    116     READ (99, *, END=9998) ptcrit
    117     READ (99, *, END=9998) sigdz
    118     READ (99, *, END=9998) spfac
    119     READ (99, *, END=9998) tau
    120     READ (99, *, END=9998) flag_wb
    121     READ (99, *, END=9998) wbmax
    122     READ (99, *, END=9998) ok_convstop
    123     READ (99, *, END=9998) tau_stop
    124     READ (99, *, END=9998) ok_intermittent
    125     READ (99, *, END=9998) coef_peel
    126 9998 CONTINUE
    127     CLOSE (99)
    128 9999 CONTINUE
    129     WRITE (*, *) 'dpbase=', dpbase
    130     WRITE (*, *) 'pbcrit=', pbcrit
    131     WRITE (*, *) 'ptcrit=', ptcrit
    132     WRITE (*, *) 'sigdz=', sigdz
    133     WRITE (*, *) 'spfac=', spfac
    134     WRITE (*, *) 'tau=', tau
    135     WRITE (*, *) 'flag_wb =', flag_wb
    136     WRITE (*, *) 'wbmax =', wbmax
    137     WRITE (*, *) 'ok_convstop =', ok_convstop
    138     WRITE (*, *) 'tau_stop =', tau_stop
    139     WRITE (*, *) 'ok_intermittent =', ok_intermittent
    140     WRITE (*, *) 'coef_peel =', coef_peel
    141 
    142 ! IM Lecture du fichier ep_param.data
    143     OPEN (79, FILE='ep_param.data', STATUS='old', FORM='formatted', ERR=7999)
    144     READ (79, *, END=7998) flag_epkeorig
    145     READ (79, *, END=7998) elcrit
    146     READ (79, *, END=7998) tlcrit
    147 7998 CONTINUE
    148     CLOSE (79)
    149 7999 CONTINUE
    150     WRITE (*, *) 'flag_epKEorig', flag_epkeorig
    151     WRITE (*, *) 'elcrit=', elcrit
    152     WRITE (*, *) 'tlcrit=', tlcrit
    153 ! IM end: ajout fis. reglage ep
    154   !$OMP END MASTER
    155 
    156    CALL bcast(dpbase)
    157    CALL bcast(pbcrit)
    158    CALL bcast(ptcrit)
    159    CALL bcast(sigdz)
    160    CALL bcast(spfac)
    161    CALL bcast(tau)
    162    CALL bcast(flag_wb)
    163    CALL bcast(wbmax)
    164    CALL bcast(ok_convstop)
    165    CALL bcast(tau_stop)
    166    CALL bcast(ok_intermittent)
    167 
    168    CALL bcast(flag_epkeorig)
    169    CALL bcast(elcrit)
    170    CALL bcast(tlcrit)
     113    CALL getin('dpbase',dpbase_omp)
     114     CALL getin('pbcrit',pbcrit_omp)
     115     CALL getin('ptcrit',ptcrit_omp)
     116     CALL getin('sigdz',sigdz_omp)
     117     CALL getin('spfac',spfac_omp)
     118     CALL getin('tau',tau_omp)
     119     CALL getin('flag_wb',flag_wb_omp)
     120     CALL getin('wbmax',wbmax_omp)
     121     CALL getin('ok_convstop',ok_convstop_omp)
     122     CALL getin('tau_stop',tau_stop_omp)
     123     CALL getin('ok_intermittent',ok_intermittent_omp)
     124     CALL getin('coef_peel',coef_peel_omp)
     125     CALL getin('flag_epKEorig',flag_epKEorig_omp)
     126     CALL getin('elcrit',elcrit_omp)
     127     CALL getin('tlcrit',tlcrit_omp)
     128   !$OMP END MASTER
     129   !$OMP BARRIER
     130     dpbase=dpbase_omp
     131     pbcrit=pbcrit_omp
     132     ptcrit=ptcrit_omp
     133     sigdz=sigdz_omp
     134     spfac=spfac_omp
     135     tau=tau_omp
     136     flag_wb=flag_wb_omp
     137     wbmax=wbmax_omp
     138     ok_convstop=ok_convstop_omp
     139     tau_stop=tau_stop_omp
     140     ok_intermittent=ok_intermittent_omp
     141     coef_peel=coef_peel_omp
     142     flag_epKEorig=flag_epKEorig_omp
     143     elcrit=elcrit_omp
     144     tlcrit=tlcrit_omp
    171145
    172146    first = .FALSE.
    173 
    174147  END IF ! (first)
    175148
     
    186159
    187160  RETURN
    188 END SUBROUTINE cv3_param
     161END SUBROUTINE cv3/_param
    189162
    190163SUBROUTINE cv3_incrcount(len, nd, delt, sig)
  • LMDZ5/trunk/libf/phylmd/wake.F90

    r2346 r2467  
    2121  ! **************************************************************
    2222
     23  USE IOIPSL, ONLY : getin
    2324  USE dimphy
    2425  use mod_phys_lmdz_para
     
    161162  REAL, SAVE ::  stark, wdens_ref, coefgw, alpk, crep_upper, crep_sol 
    162163  !$OMP THREADPRIVATE(stark, wdens_ref, coefgw, alpk, crep_upper, crep_sol)
     164  REAL, SAVE ::  stark_omp=0.33
     165  REAL, SAVE ::  alpk_omp=0.25
     166  REAL, SAVE ::  wdens_ref_omp=8.E-12
     167  REAL, SAVE ::  coefgw_omp=4.
     168  !$OMP THREADPRIVATE(stark_omp,alpk_omp,wdens_ref_omp,coefgw_omp)
     169
    163170  REAL delta_t_min
    164171  INTEGER nsub
     
    286293
    287294 if (first) then
    288   stark = 0.33
    289   alpk = 0.25
    290   wdens_ref = 8.E-12
    291   coefgw = 4.
    292295  crep_upper = 0.9
    293296  crep_sol = 1.0
     
    295298  ! cc nrlmd Lecture du fichier wake_param.data
    296299 !$OMP MASTER
    297   OPEN (99, FILE='wake_param.data', STATUS='old', FORM='formatted', ERR=9999)
    298   READ (99, *, END=9998) stark
    299   READ (99, *, END=9998) alpk
    300   READ (99, *, END=9998) wdens_ref
    301   READ (99, *, END=9998) coefgw
    302 9998 CONTINUE
    303   CLOSE (99)
    304 9999 CONTINUE
     300  CALL getin('stark',stark_omp)
     301  CALL getin('alpk',alpk_omp)
     302  CALL getin('wdens_ref',wdens_ref_omp)
     303  CALL getin('coefgw',coefgw_omp)
    305304 !$OMP END MASTER
    306   CALL bcast(stark)
    307   CALL bcast(alpk)
    308   CALL bcast(wdens_ref)
    309   CALL bcast(coefgw)
    310 
     305 !$OMP BARRIER
     306  stark=stark_omp
     307  alpk=alpk_omp
     308  wdens_ref=wdens_ref_omp
     309  coefgw=coefgw_omp
    311310  first=.false.
    312311 endif
Note: See TracChangeset for help on using the changeset viewer.