GCC Code Coverage Report


Directory: ./
File: phy_common/vertical_layers_mod.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 17 17 100.0%
Branches: 35 58 60.3%

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