source: LMDZ6/branches/IPSLCM6.0.15/libf/phymar/Mod_SISVAT_grd.f90 @ 3607

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

Inclusion de la physique de MAR


Integration of MAR physics

File size: 3.5 KB
Line 
1      module Mod_SISVAT_grd
2
3
4!--------------------------------------------------------------------------+
5!                                                     Fri  7-Jun-2013  MAR |
6!     module Mod_SISVAT_grd contains the dimensions of the domain of       |
7!                Soil/Ice Snow Vegetation Atmosphere Transfer Scheme       |
8!                                                                          |
9!     version 3.p.4.1 created by H. Gallee,           Wed 27-Feb-2013      |
10!                    modified by H. Gallee,           Fri  7-Jun-2013      |
11!                                                                          |
12!--------------------------------------------------------------------------+
13
14
15      use Mod_Real
16
17
18      IMPLICIT NONE
19
20
21
22      integer, SAVE                                       ::  mwp         ! Nb of mosaic in one         Grid Cell
23      integer, SAVE                                       ::  n2          ! Nb of mosaic in one Oceanic Grid Cell (min is 2)
24      integer, SAVE                                       ::  kcolv       ! Nb of interior      Vertical Columns
25      integer, SAVE                                       ::  nsoil       ! Nb of Soil          Levels beneath the Surface Level
26      integer, SAVE                                       ::  nvege       ! Nb of Vegetation    Types
27      integer, SAVE                                       ::  nsnow       ! Max Nb of Snow      Layers
28      integer, SAVE                                       ::  nbPts       ! Nb of dumped        Grid     Points
29      integer, SAVE                                       ::  nbwri       ! Nb of dumped        Vertical Columns
30      integer, SAVE                                       ::  ntave       ! Nb of Time Steps over which SBL relevant parameters  are averaged
31      integer, SAVE                                       ::  ntavz       ! Nb of Time Steps over which z0, r0, ...  parameters  are averaged
32      integer, SAVE                                       ::  nLimi       ! Nb of Time Steps over which Water Vapor Flux to limit is averaged
33
34      integer, SAVE                                       ::  jt__SV      ! Number of DYnamical Time Steps for one SISVAT                       [-]
35      real(kind=real8), SAVE                              ::  dt__SV      ! Time Step of Surface     Physics      (SISVAT)                      [s]
36
37      integer, SAVE                                       ::  k_zb
38      real(kind=real8), SAVE                              ::  z_zb = 25.  ! Level of negligible blowing particles concentration
39
40      integer, SAVE                                       ::  k_SL        ! Parameter used in the Interpolation of V(10 m)
41      real(kind=real8), SAVE                              ::  r_SL10      ! Parameter used in the Interpolation of V(10 m)
42
43      integer, SAVE                                       ::  iwr_SV
44      integer, SAVE                                       ::  jwr_SV
45      integer, SAVE                                       ::  nwr_SV
46      integer, SAVE         ,ALLOCATABLE ,dimension(:)    ::  ii__SV      ! Mosaic point   i Coordinate
47      integer, SAVE         ,ALLOCATABLE ,dimension(:)    ::  jj__SV      ! Mosaic point   j Coordinate
48      integer, SAVE         ,ALLOCATABLE ,dimension(:)    ::  nn__SV      ! Mosaic point   n Coordinate
49      integer, SAVE         ,ALLOCATABLE ,dimension(:)    ::  ikp_SV      ! Grid Cell Column Index of a SISVAT Column
50      integer, SAVE         ,ALLOCATABLE ,dimension(:,:,:)::  ikl_SV      ! SISVAT    Column Index     
51
52      end module Mod_SISVAT_grd
Note: See TracBrowser for help on using the repository browser.