GCC Code Coverage Report


Directory: ./
File: rad/suinit.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 53 53 100.0%
Branches: 66 128 51.6%

Line Branch Exec Source
1 1 SUBROUTINE SUINIT(klon,klev)
2
3 USE PARKIND1 ,ONLY : JPIM ,JPRB
4 !#include "tsmbkind.h"
5
6 USE PARDIM, ONLY : JPMXLE
7 USE YOMCT0B , ONLY : LECMWF
8 USE YOMRIP , ONLY : NINDAT ,NSSSSS
9 USE YOMDIM
10 USE YOMDPHY
11 ! MPL 29042010: NDLNPR,RHYDR0 non initialises et pour ne pas mettre tout sudyn.F90
12 USE YOMDYN , ONLY : TSTEP , NDLNPR , RHYDR0 ! MPL 29042010
13 !USE YOMEVOL , ONLY : TECH ,FREQFS ,FREQFE , FREQDDH
14 !USE YOMCT0 , ONLY : LFROG
15 ! quelques ajouts qui viennent de suallo
16 USE YOMGEM , ONLY : VDELA , VDELB ,VC ,NLOEN ,NLOENG ,NGPTOT
17 USE YOMSTA , ONLY : STZ ,STPREH ,STPRE ,STPHI ,STTEM ,STDEN
18 USE YOEAERD , ONLY : CVDAES ,CVDAEL ,CVDAEU ,CVDAED
19 USE YOEOVLP , ONLY : RA1OVLP
20 USE YOECLD , ONLY : CETA
21 USE YOECND , ONLY : CEVAPCU
22 USE YOMTOPH , ONLY : RMESOU ,RMESOT ,RMESOQ
23 USE YOMGC , ONLY : GEMU ,GELAM ,GELAT ,GECLO ,GESLO ,GM ,GAW
24
25
26 IMPLICIT NONE
27 LOGICAL LLTRACE, LLDEBUG
28 integer klon,klev
29 CHARACTER*200 CFICP
30 CHARACTER*200 CFLUX
31 CHARACTER*200 CLIST
32 CHARACTER*200 CFDDH
33 CHARACTER*80 CNMEXP
34
35
36 LLTRACE=.TRUE.
37 LLDEBUG=.TRUE.
38
39 ! ------------------------
40 ! * READ NAMELISTS.
41 ! ------------------------
42
43 !----------------------------------------------------------------
44 ! Elements indispensables de SUNAM pour faire tourner RRTM dans LMDZ
45 !-------------------------------------------------------------------
46 1 CFICP='Profile'
47 1 CFLUX='Output'
48 1 CLIST='Listing'
49 1 CFDDH='DHFDL'
50 1 CNMEXP='SCM'
51 1 TSTEP=450
52 ! MPL 29042010 - RHYDR0 - upper boundary contition for hydrostatic
53 1 RHYDR0=1._JPRB
54 ! MPL 29042010
55 ! NDLNPR : NDLNPR=0: conventional formulation of delta, i.e. ln(P(l)/P(l-1)).
56 ! NDLNPR=1: formulation of delta used in non hydrostatic model,
57 1 NDLNPR=0
58 1 print *,'SUINIT: RHYDR0 NDLNPR',RHYDR0,NDLNPR
59
60 !----------------------------------------------------------------
61 ! Elements indispensables de SUDIM pour faire tourner RRTM dans LMDZ
62 !-------------------------------------------------------------------
63 1 NDLON=klon
64 1 NFLEVG=klev
65 1 NPROMA=klon
66
67 !-------------------------------------------------------------------
68 !JV Initialize constants
69 ! ---------------------
70 !JV
71 1 IF (LLTRACE) WRITE(*,*) " coucou SUINIT : avant SUCST"
72 1 WRITE(*,FMT='('' ---------------- '')')
73 1 WRITE(*,FMT='('' SUCST : '')')
74 1 WRITE(*,FMT='('' ---------------- '')')
75 1 NINDAT=20090408 !!!!! A REVOIR (MPL)
76 1 NSSSSS=0 ! LMDZ demarre tjrs a 00h -- MPL 15.04.09
77 1 CALL SUCST(6,NINDAT,NSSSSS,1)
78 1 print *,'SUINIT: NINDAT, NSSSSS',NINDAT, NSSSSS
79
80 IF (LLDEBUG) THEN
81 1 WRITE(*,FMT='('' SUINIT / apres : SUCST '')')
82 ENDIF
83
84
85 ! ------------------------
86 ! * ALLOCATES RECUPERES DE SUALLO
87 ! ------------------------
88
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(VDELA (MAX(JPMXLE,NFLEVG)))
89
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(VDELB (MAX(JPMXLE,NFLEVG)))
90
2/2
✓ Branch 0 taken 200 times.
✓ Branch 1 taken 1 times.
201 VDELB = 0 !ym missing init
91
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( VC (NFLEVG) )
92
2/2
✓ Branch 0 taken 39 times.
✓ Branch 1 taken 1 times.
40 VC = 0 !ym missing init
93
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( NLOEN (NPROMA) )
94
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE( NLOENG (NPROMA) )
95
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE( STZ (NFLEVG) )
96
4/8
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✓ Branch 5 taken 1 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 1 times.
1 ALLOCATE( CVDAES (NFLEVG+1))
97
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE( CVDAEL (NFLEVG+1))
98
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE( CVDAEU (NFLEVG+1))
99
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE( CVDAED (NFLEVG+1))
100
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(RA1OVLP(NFLEVG))
101
102
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(STPREH(0:NFLEVG)) ! Nouvel ajout MPL 22062010
103
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(STPRE(NFLEVG))
104
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(STPHI(NFLEVG))
105
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(STTEM(NFLEVG))
106
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(STDEN(NFLEVG))
107
108
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(CETA(NFLEVG)) ! Nouvel ajout MPL 28062010
109
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(CEVAPCU(NFLEVG))
110
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(RMESOU(NFLEVG))
111
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(RMESOT(NFLEVG))
112
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(RMESOQ(NFLEVG))
113
114 ! ------------------------
115 ! * ALLOCATES RECUPERES DE SUGEM2
116 ! ------------------------
117
118
3/6
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
1 ALLOCATE(GEMU (NGPTOT)) ! Nouvel ajout MPL 28062010
119
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(GELAM (NGPTOT))
120
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(GELAT (NGPTOT))
121
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(GECLO (NGPTOT))
122
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(GESLO (NGPTOT))
123
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(GM (NGPTOT))
124
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(GAW (NGPTOT))
125 !
126 ! ------------------------------------------------------------------
127
128 1 END SUBROUTINE SUINIT
129