! ! $Id$ ! SUBROUTINE conf_planete ! ! if not using IOIPSL, we still need to use (a local version of) getin USE ioipsl_getincom IMPLICIT NONE ! ! ! Declarations : ! -------------- !----------------------------------------------------------------------- ! INCLUDE 'dimensions.h' ! ! dimensions.h contient les dimensions du modele ! ndm est tel que iim=2**ndm !----------------------------------------------------------------------- INTEGER iim,jjm,llm,ndm PARAMETER (iim= 128,jjm=96,llm=64,ndm=1) !----------------------------------------------------------------------- ! ! $Id: comconst.h 1437 2010-09-30 08:29:10Z emillour $ ! !----------------------------------------------------------------------- ! INCLUDE comconst.h COMMON/comconsti/im,jm,lllm,imp1,jmp1,lllmm1,lllmp1,lcl, & & iflag_top_bound,mode_top_bound COMMON/comconstr/dtvr,daysec, & & pi,dtphys,dtdiss,rad,r,kappa,cotot,unsim,g,omeg & & ,dissip_fac_mid,dissip_fac_up,dissip_deltaz,dissip_hdelta & & ,dissip_pupstart ,tau_top_bound, & & daylen,molmass, ihf COMMON/cpdetvenus/cpp,nu_venus,t0_venus INTEGER im,jm,lllm,imp1,jmp1,lllmm1,lllmp1,lcl REAL dtvr ! dynamical time step (in s) REAL daysec !length (in s) of a standard day REAL pi ! something like 3.14159.... REAL dtphys ! (s) time step for the physics REAL dtdiss ! (s) time step for the dissipation REAL rad ! (m) radius of the planet REAL r ! Reduced Gas constant r=R/mu ! with R=8.31.. J.K-1.mol-1, mu: mol mass of atmosphere (kg/mol) REAL cpp ! Cp REAL kappa ! kappa=R/Cp REAL cotot REAL unsim ! = 1./iim REAL g ! (m/s2) gravity REAL omeg ! (rad/s) rotation rate of the planet ! Dissipation factors, for Earth model: REAL dissip_factz,dissip_zref !dissip_deltaz ! Dissipation factors, for other planets: REAL dissip_fac_mid,dissip_fac_up,dissip_deltaz,dissip_hdelta REAL dissip_pupstart INTEGER iflag_top_bound,mode_top_bound REAL tau_top_bound REAL daylen ! length of solar day, in 'standard' day length REAL molmass ! (g/mol) molar mass of the atmosphere REAL nu_venus,t0_venus ! coeffs needed for Cp(T), Venus atmosphere REAL ihf ! (W/m2) intrinsic heat flux for giant planets !----------------------------------------------------------------------- ! ! $Id: comvert.h 1654 2012-09-24 15:07:18Z aslmd $ ! !----------------------------------------------------------------------- ! INCLUDE 'comvert.h' COMMON/comvertr/ap(llm+1),bp(llm+1),presnivs(llm),dpres(llm), & & pa,preff,nivsigs(llm),nivsig(llm+1), & & aps(llm),bps(llm),scaleheight,pseudoalt(llm) common/comverti/disvert_type, pressure_exner real ap ! hybrid pressure contribution at interlayers real bp ! hybrid sigma contribution at interlayer real presnivs ! (reference) pressure at mid-layers real dpres real pa ! reference pressure (Pa) at which hybrid coordinates ! become purely pressure real preff ! reference surface pressure (Pa) real nivsigs real nivsig real aps ! hybrid pressure contribution at mid-layers real bps ! hybrid sigma contribution at mid-layers real scaleheight ! atmospheric (reference) scale height (km) real pseudoalt ! pseudo-altitude of model levels (km), based on presnivs(), ! preff and scaleheight integer disvert_type ! type of vertical discretization: ! 1: Earth (default for planet_type==earth), ! automatic generation ! 2: Planets (default for planet_type!=earth), ! using 'z2sig.def' (or 'esasig.def) file logical pressure_exner ! compute pressure inside layers using Exner function, else use mean ! of pressure values at interfaces !----------------------------------------------------------------------- ! ! local: ! ------ real :: year_day_dyn ! --------------------------------------------- ! Initialisations de constantes de la dynamique ! --------------------------------------------- ! Pi pi=2.*asin(1.) !Reference surface pressure (Pa) preff=101325. CALL getin('preff', preff) ! Reference pressure at which hybrid coord. become purely pressure ! pa=50000. pa=preff/2. CALL getin('pa', pa) ! Gravity g=9.80665 CALL getin('g',g) ! Molar mass of the atmosphere molmass = 28.9644 CALL getin('molmass',molmass) ! kappa=R/Cp et Cp kappa = 2./7. CALL getin('kappa',kappa) cpp=8.3145/molmass/kappa*1000. CALL getin('cpp',cpp) ! Radius of the planet rad = 6371229. CALL getin('radius',rad) ! Length of a standard day (s) daysec=86400. CALL getin('daysec',daysec) ! Rotation rate of the planet: ! Length of a solar day, in standard days daylen = 1. CALL getin('daylen',daylen) ! Number of days (standard) per year: year_day_dyn = 365.25 CALL getin('year_day',year_day_dyn) ! Omega ! omeg=2.*pi/86400. omeg=2.*pi/daysec*(1./daylen+1./year_day_dyn) CALL getin('omeg',omeg) ! Intrinsic heat flux [default is none] ! Aymeric -- for giant planets ! [matters only if planet_type="giant"] ihf = 0. CALL getin('ihf',ihf) END SUBROUTINE conf_planete