source: dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/vertical_layers_mod.f90 @ 3983

Last change on this file since 3983 was 3825, checked in by ymipsl, 10 years ago

Reorganize geometry and grid modules. Prepare physics for unstructutured grid support. Simplify initialization of physics from dynamic.
Compiled only with dynd3dmem, but not tested for moment.

YM

File size: 1.2 KB
Line 
1MODULE vertical_layers_mod
2
3   REAL,SAVE             :: preff  ! reference surface pressure (Pa)
4   REAL,SAVE,ALLOCATABLE :: ap(:)
5   REAL,SAVE,ALLOCATABLE :: bp(:)
6   REAL,SAVE,ALLOCATABLE :: presnivs(:)
7   REAL,SAVE,ALLOCATABLE :: pseudoalt(:)
8!$OMP THREADPRIVATE(preff,ap,bp,presnivs,pseudoalt)
9
10
11CONTAINS
12
13  SUBROUTINE init_vertical_layers(nlayer,preff_,ap_,bp_,&
14                                 presnivs_, pseudoalt_)
15    IMPLICIT NONE
16    INTEGER,INTENT(IN) :: nlayer ! number of atmospheric layers
17    REAL,INTENT(IN)    :: preff_ ! reference surface pressure (Pa)
18    REAL,INTENT(IN)    :: ap_(nlayer+1) ! hybrid coordinate at interfaces
19    REAL,INTENT(IN)    :: bp_(nlayer+1) ! hybrid coordinate at interfaces
20    REAL,INTENT(IN)    :: presnivs_(nlayer) ! Appproximative pressure of atm. layers (Pa)
21    REAL,INTENT(IN)    :: pseudoalt_(nlayer) ! pseudo-altitude of atm. layers (km)
22 
23    ALLOCATE(ap(nlayer+1))
24    ALLOCATE(bp(nlayer+1))
25    ALLOCATE(presnivs(nlayer))
26    ALLOCATE(pseudoalt(nlayer))
27 
28    preff = preff_
29    ap(:) = ap_(:)
30    bp(:) = bp_(:)
31    presnivs(:) = presnivs_(:)
32    pseudoalt(:) = pseudoalt_(:)
33
34  END SUBROUTINE init_vertical_layers
35
36END MODULE vertical_layers_mod
Note: See TracBrowser for help on using the repository browser.