source: LMDZ6/branches/IPSLCM6.0.15/libf/phymar/Mod_PHY____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: 4.3 KB
Line 
1      module Mod_PHY____grd
2
3
4!--------------------------------------------------------------------------+
5!                                                     Mon 17-Jun-2013  MAR |
6!     module Mod_PHY____grd contains the characteristics of the grid for   |
7!            MAR PHYsics                                                   |
8!                                                                          |
9!     version 3.p.4.1 created by H. Gallee,           Sat 16-Feb-2013      |
10!           Last Modification by H. Gallee,           Mon 17-Jun-2013      |
11!                                                                          |
12!--------------------------------------------------------------------------+
13
14
15      use Mod_Real
16
17
18      IMPLICIT NONE
19
20
21
22      logical :: FlagDALLOC = .FALSE.
23
24      integer, SAVE :: YearTU   !
25      integer, SAVE :: Mon_TU   !
26      integer, SAVE :: Day_TU   !
27      integer, SAVE :: HourTU   ! Hour, Universal Time
28      integer, SAVE :: MinuTU   !
29      integer, SAVE :: Sec_TU   !
30
31      integer, SAVE :: it_EXP   ! Nb of iterations    since the beginning of the EXPeriment
32      integer, SAVE :: it_RUN   ! Nb of iterations    since the beginning of the RUN (job)
33
34      integer, SAVE :: mxp      ! Nb of interior      Grid Points, x-Direction
35      integer, SAVE :: mxpp     ! Nb of interior      Grid Points, x-Direction + 1
36      integer, SAVE :: myp      ! Nb of interior      Grid Points, y-Direction
37      integer, SAVE :: mypp     ! Nb of interior      Grid Points, y-Direction + 1
38      integer, SAVE :: ixp1     ! 1er pt en x de la grille dynamique utile dans grille physique
39      integer, SAVE :: jyp1     ! 1er pt en y de la grille dynamique utile dans grille physique
40      integer, SAVE :: kcolp    ! Nb of interior      Vertical Columns (mxp * myp)       
41      integer, SAVE :: mzp      ! Nb of Atmospheric   Levels
42      integer, SAVE :: mzpp     ! Nb of Atmospheric   Levels                   + 1
43
44      integer, SAVE                                        :: i_x0
45      integer, SAVE                                        :: j_y0
46      integer, SAVE                                        :: ikl0
47
48      real(kind=real8), SAVE, ALLOCATABLE, dimension(:)    :: lat__r      !     Latitude                    [radian]
49      real(kind=real8), SAVE, ALLOCATABLE, dimension(:)    :: sinLat      ! sin(Latitude)                        [-]
50      real(kind=real8), SAVE, ALLOCATABLE, dimension(:)    :: cosLat      ! cos(Latitude)                        [-]
51      real(kind=real8), SAVE, ALLOCATABLE, dimension(:)    :: lon__r      !     Longitude                   [radian]
52      real(kind=real8), SAVE, ALLOCATABLE, dimension(:)    :: lon__h      !     Longitude                     [hour]
53
54      real(kind=real8), SAVE                               :: timeTU      ! Time   [HOURS since 1901-01-15 00:00:00]
55      real(kind=real8), SAVE                               :: dxHOST      ! dx
56      real(kind=real8), SAVE                               :: dx2inv      ! 1 / (2 dx)
57      real(kind=real8), SAVE                               :: dy2inv      ! 1 / (2 dy)
58      real(kind=real8), SAVE                               :: pt__DY      ! Model Pressure Top                 [kPa]
59      real(kind=real8), SAVE, ALLOCATABLE, dimension(:)    ::  sigma      ! Vertical Coord. (normalized Pressure)
60      real(kind=real8), SAVE, ALLOCATABLE, dimension(:)    ::  sigmi      !(sigma(k-1  )+sigma(k    )) / 2
61      real(kind=real8), SAVE, ALLOCATABLE, dimension(:)    :: dsigma      ! sigma(k+1  )-sigma(k    )
62      real(kind=real8), SAVE, ALLOCATABLE, dimension(:)    :: dsigmi      ! sigma(k+1/2)-sigma(k-1/2)
63      real(kind=real8), SAVE, ALLOCATABLE, dimension(:)    :: hsigma      ! Height of atmospheric layers      [magl]
64
65      integer, SAVE,          ALLOCATABLE, dimension(:)    :: k1m         ! k - 1
66      integer, SAVE,          ALLOCATABLE, dimension(:)    :: k1p         ! k + 1
67      integer, SAVE,          ALLOCATABLE, dimension(:)    :: k2m         ! k - 2
68
69      integer, SAVE,          ALLOCATABLE, dimension(:)    :: ii__AP      ! WORK   point   i Coordinate
70      integer, SAVE,          ALLOCATABLE, dimension(:)    :: jj__AP      ! WORK   point   i Coordinate
71      integer, SAVE,          ALLOCATABLE, dimension(:,:)  :: ikl_AP      ! WORK   point vec Coordinate
72
73
74
75      end module Mod_PHY____grd
Note: See TracBrowser for help on using the repository browser.