source: LMDZ5/trunk/libf/phymar/Mod_PHY_DY_kkl.f90 @ 2089

Last change on this file since 2089 was 2089, checked in by Laurent Fairhead, 10 years ago

Inclusion de la physique de MAR


Integration of MAR physics

File size: 3.0 KB
Line 
1      module Mod_PHY_DY_kkl
2
3!--------------------------------------------------------------------------+
4!                                                     Tue  4-Jun-2013  MAR |
5!     module Mod_PHY_DY_kkl contains the main (prognostic) variables of    |
6!                MAR Dynamics Variabbles on MAR Physics Grid               |
7!                                                                          |
8!     version 3.p.4.1 created by H. Gallee,           Tue 12-Mar-2013      |
9!           Last Modification by H. Gallee,           Tue  4-Jun-2013      |
10!                                                                          |
11!--------------------------------------------------------------------------+
12
13
14      use Mod_Real
15
16
17      IMPLICIT NONE
18
19
20
21! Atm_DY INPUT        Variables
22! -----------------------------
23
24      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:)    ::  psa_DY       !  Pressure    Thickness                                    [kPa]
25      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:,:)  ::  ExnrDY       !  Potential   Exner                        pa  **(R/Cp)    [xxx]
26
27      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:,:)  ::  Z___DY       !  Geopotential, level k    , i.e. =  gZ(k)         /  g  [m2/s2]
28      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:,:)  ::  ZmidDY       !  Geopotential, level k-1/2, i.e. = (gZ(k)+gZ(k-1))/(2g) [m2/s2]
29
30      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:,:)  ::  pkt_DY       !  Potential   Temperature, divided by (100 kPa)**(R/Cp)  [K/xxx]
31      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:,:)  ::  TmidDY       !  Temperature , level k+1/2, i.e. = (Ta(k)+Ta(k+1))/ 2       [K]
32      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:,:)  ::  Ta__DY       !  Temperature , level k    , i.e. =  Ta(k)                   [K]
33      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:,:)  ::  windDY       !  Wind Speed, Horizontal                                   [m/s]
34      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:,:)  ::  ua__DY       !  Wind Speed  x-Direction                                  [m/s]
35      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:,:)  ::  va__DY       !  Wind Speed  y-Direction                                  [m/s]
36      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:,:)  ::  wa__DY       !  Wind Speed  z-Direction                                  [m/s]
37      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:,:)  ::  roa_DY       !  Air Volumic Mass, Layer k                              [Mg/m3]
38      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:,:)  ::  roamDY       !  Air Volumic Mass, Level k+1/2                          [Mg/m3]
39
40      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:,:)  ::  qv__DY       !  Specific    Humidity                                   [kg/kg]
41! #LD real(kind=real8), SAVE,ALLOCATABLE ,dimension(:,:)  ::  ld_H2O       !  Loading    (Humidity, Hydrometeors, Aerosols ...)          [-]
42
43
44
45! Atm_DY INPUT/OUTPUT Variables
46! -----------------------------
47
48
49
50! Atm_DY OUTPUT       Variables
51! -----------------------------
52
53
54      end module Mod_PHY_DY_kkl
Note: See TracBrowser for help on using the repository browser.