source: LMDZ6/trunk/libf/phymar/Mod_SISVAT_gpt.f90 @ 3942

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

Inclusion de la physique de MAR


Integration of MAR physics

File size: 2.8 KB
Line 
1      module Mod_SISVAT_gpt
2
3!--------------------------------------------------------------------------+
4!                                                     Wed 26-Jun-2013  MAR |
5!     module Mod_SISVAT_gpt contains the Grid Point           variables of |
6!                Soil/Ice Snow Vegetation Atmosphere Transfer Scheme       |
7!                                                                          |
8!     version 3.p.4.1 created by H. Gallee,           Sat 22-Jun-2013      |
9!           Last Modification by H. Gallee,           Wed 26-Jun-2013      |
10!                                                                          |
11!--------------------------------------------------------------------------+
12
13
14      use Mod_Real
15
16
17      IMPLICIT NONE
18
19
20
21! SISVAT INPUT        Variables
22! -----------------------------
23
24      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:)      ::  sst_SB      ! Ocean  FORCING (SST)                         [K]
25      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:)      ::  sif_SB      ! Ocean  FORCING (Sea-Ice Fraction)            [-]
26      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:)      ::  MaskSV_gpt  ! Land(1)-Sea(0) Mask         (Cell value)     [-]
27
28
29
30! SISVAT INPUT/OUTPUT Variables
31! -----------------------------
32
33
34
35
36! SISVAT OUTPUT       Variables
37! -----------------------------
38
39      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:)      ::  Alb_SV_gpt  ! Surface  Albedo             (Cell average)   [-]
40      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:)      ::  EmisSV_gpt  ! LongWave Surface Emissivity (Cell average)   [-]
41      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:)      ::  Tas_SV_gpt  ! Surface  Air    Temperature (Cell average)   [K]
42
43      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:)      ::  HSenSV_gpt  ! Sensible Heat   Flux (+ => Downward)      [W/m2]
44      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:)      ::  HLatSV_gpt  ! Latent   Heat   Flux (+ => Downward)      [W/m2]
45      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:)      ::  LMO_SV_gpt  ! Obukhov  Length             (Cell average)   [m]
46      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:)      ::  us__SV_gpt  ! Friction Velocity                          [m/s]
47      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:)      ::  uts_SV_gpt  ! Sensible Heat   Flux Turbulent Scale     [K m/s]
48      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:)      ::  uqs_SV_gpt  ! Latent   Heat   Flux Turbulent Scale [kg/kg m/s]
49      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:)      ::  WE2aSV_gpt  ! Cumulative H2O  Flux from the Surface  [mm w.e.]
50      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:)      ::  hFraSV_gpt  ! Frazil   Thickness                           [m]
51
52      real(kind=real8), SAVE,ALLOCATABLE ,dimension(:,:)    ::  dpktSV_gpt  ! Reduced  Potential Temperature Tendency   [KX/s]
53
54
55
56      end module Mod_SISVAT_gpt
Note: See TracBrowser for help on using the repository browser.