| 1 | ! $Id: $ |
|---|
| 2 | |
|---|
| 3 | MODULE vertical_layers_mod |
|---|
| 4 | |
|---|
| 5 | REAL,SAVE :: preff ! reference surface pressure (Pa) |
|---|
| 6 | REAL,SAVE :: scaleheight ! atmospheric reference scale height (km) |
|---|
| 7 | REAL,SAVE,ALLOCATABLE :: ap(:) ! hybrid (pressure contribution) coordinate |
|---|
| 8 | ! at layer interfaces (Pa) |
|---|
| 9 | REAL,SAVE,ALLOCATABLE :: bp(:) ! hybrid (sigma contribution) coordinate |
|---|
| 10 | ! at layer interfaces (Pa) |
|---|
| 11 | REAL,SAVE,ALLOCATABLE :: aps(:) ! hybrid (pressure contribution) coordinate |
|---|
| 12 | ! at mid-layer (Pa) |
|---|
| 13 | REAL,SAVE,ALLOCATABLE :: bps(:) ! hybrid (sigma contribution) coordinate |
|---|
| 14 | ! at mid-layer |
|---|
| 15 | REAL,SAVE,ALLOCATABLE :: presnivs(:) ! reference pressure at mid-layer (Pa), |
|---|
| 16 | ! based on preff, ap and bp |
|---|
| 17 | REAL,SAVE,ALLOCATABLE :: presinter(:) ! reference pressure at interface (Pa), |
|---|
| 18 | ! based on preff, ap and bp |
|---|
| 19 | REAL,SAVE,ALLOCATABLE :: pseudoalt(:) ! pseudo-altitude of model layers (km), |
|---|
| 20 | ! based on preff and scaleheight |
|---|
| 21 | |
|---|
| 22 | !$OMP THREADPRIVATE(preff,scaleheight,ap,bp,aps,bps,presnivs,presinter,pseudoalt) |
|---|
| 23 | |
|---|
| 24 | |
|---|
| 25 | CONTAINS |
|---|
| 26 | |
|---|
| 27 | SUBROUTINE init_vertical_layers(nlayer,preff_,scaleheight_,ap_,bp_,& |
|---|
| 28 | aps_,bps_,presnivs_, presinter_, pseudoalt_) |
|---|
| 29 | IMPLICIT NONE |
|---|
| 30 | INTEGER,INTENT(IN) :: nlayer ! number of atmospheric layers |
|---|
| 31 | REAL,INTENT(IN) :: preff_ ! reference surface pressure (Pa) |
|---|
| 32 | REAL,INTENT(IN) :: scaleheight_ ! atmospheric scale height (km) |
|---|
| 33 | REAL,INTENT(IN) :: ap_(nlayer+1) ! hybrid coordinate at interfaces |
|---|
| 34 | REAL,INTENT(IN) :: bp_(nlayer+1) ! hybrid coordinate at interfaces |
|---|
| 35 | REAL,INTENT(IN) :: aps_(nlayer) ! hybrid coordinate at mid-layer |
|---|
| 36 | REAL,INTENT(IN) :: bps_(nlayer) ! hybrid coordinate at mid-layer |
|---|
| 37 | REAL,INTENT(IN) :: presnivs_(nlayer) ! Appproximative pressure of atm. layers (Pa) |
|---|
| 38 | REAL,INTENT(IN) :: presinter_(nlayer+1) ! Appproximative pressure of atm. layers (Pa) |
|---|
| 39 | REAL,INTENT(IN) :: pseudoalt_(nlayer) ! pseudo-altitude of atm. layers (km) |
|---|
| 40 | |
|---|
| 41 | ALLOCATE(ap(nlayer+1)) |
|---|
| 42 | ALLOCATE(bp(nlayer+1)) |
|---|
| 43 | ALLOCATE(aps(nlayer)) |
|---|
| 44 | ALLOCATE(bps(nlayer)) |
|---|
| 45 | ALLOCATE(presnivs(nlayer)) |
|---|
| 46 | ALLOCATE(presinter(nlayer+1)) |
|---|
| 47 | ALLOCATE(pseudoalt(nlayer)) |
|---|
| 48 | |
|---|
| 49 | preff = preff_ |
|---|
| 50 | scaleheight=scaleheight_ |
|---|
| 51 | ap(:) = ap_(:) |
|---|
| 52 | bp(:) = bp_(:) |
|---|
| 53 | aps(:) = aps_(:) |
|---|
| 54 | bps(:) = bps_(:) |
|---|
| 55 | presnivs(:) = presnivs_(:) |
|---|
| 56 | presinter(:) = presinter_(:) |
|---|
| 57 | pseudoalt(:) = pseudoalt_(:) |
|---|
| 58 | |
|---|
| 59 | END SUBROUTINE init_vertical_layers |
|---|
| 60 | |
|---|
| 61 | END MODULE vertical_layers_mod |
|---|