source: LMDZ6/trunk/libf/dyn3d_common/comvert_mod.f90 @ 5403

Last change on this file since 5403 was 5271, checked in by abarral, 7 weeks ago

Move dimensions.h into a module
Nb: doesn't compile yet

  • 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
RevLine 
[524]1!
[1279]2! $Id: comvert_mod.f90 5271 2024-10-24 14:25:39Z abarral $
[524]3!
[2600]4MODULE comvert_mod
[524]5
[5271]6USE dimensions_mod, ONLY: iim, jjm, llm, ndm
7IMPLICIT NONE
[524]8
[2602]9PRIVATE
[524]10
[5271]11
[2602]12PUBLIC :: ap,bp,presnivs,dpres,sig,ds,pa,preff,nivsigs,nivsig, &
[4228]13          aps,bps,scaleheight,pseudoalt,disvert_type, pressure_exner, &
14          presinter
[2602]15
[2600]16REAL ap(llm+1) ! hybrid pressure contribution at interlayers
17REAL bp (llm+1) ! hybrid sigma contribution at interlayer
18REAL presnivs(llm) ! (reference) pressure at mid-layers
[4228]19REAL presinter(llm+1) ! (reference) pressure at interlayers
[2600]20REAL dpres(llm)
21REAL sig(llm+1)
22REAL ds(llm)
23REAL pa ! reference pressure (Pa) at which hybrid coordinates
24        ! become purely pressure (more or less)
25REAL preff  ! reference surface pressure (Pa)
26REAL nivsigs(llm)
27REAL nivsig(llm+1)
28REAL aps(llm) ! hybrid pressure contribution at mid-layers
29REAL bps(llm) ! hybrid sigma contribution at mid-layers
30REAL scaleheight ! atmospheric (reference) scale height (km)
31REAL pseudoalt(llm) ! pseudo-altitude of model levels (km), based on presnivs(),
[1793]32                     ! preff and scaleheight
[1520]33
[2600]34INTEGER disvert_type ! type of vertical discretization:
35                     ! 1: Earth (default for planet_type==earth),
36                     !     automatic generation
37                     ! 2: Planets (default for planet_type!=earth),
38                     !     using 'z2sig.def' (or 'esasig.def) file
[1520]39
[2600]40LOGICAL pressure_exner
[1625]41!     compute pressure inside layers using Exner function, else use mean
42!     of pressure values at interfaces
43
[2600]44END MODULE comvert_mod
Note: See TracBrowser for help on using the repository browser.