GCC Code Coverage Report


Directory: ./
File: phys/surf_land_bucket_mod.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 38 45 84.4%
Branches: 38 56 67.9%

Line Branch Exec Source
1 !
2 MODULE surf_land_bucket_mod
3 !
4 ! Surface land bucket module
5 !
6 ! This module is used when no external land model is choosen.
7 !
8 IMPLICIT NONE
9
10 CONTAINS
11
12 248640 SUBROUTINE surf_land_bucket(itime, jour, knon, knindex, debut, dtime,&
13 tsurf, p1lay, tq_cdrag, precip_rain, precip_snow, temp_air, &
14 spechum, petAcoef, peqAcoef, petBcoef, peqBcoef, pref, &
15 u1, v1, gustiness, rugoro, swnet, lwnet, &
16 snow, qsol, agesno, tsoil, &
17 480 qsurf, z0_new, alb1_new, alb2_new, evap, &
18 fluxsens, fluxlat, tsurf_new, dflux_s, dflux_l)
19
20 USE limit_read_mod
21 USE surface_data
22 USE fonte_neige_mod
23 USE calcul_fluxs_mod
24 USE cpl_mod
25 USE dimphy
26 USE geometry_mod, ONLY: longitude,latitude
27 USE mod_grid_phy_lmdz
28 USE mod_phys_lmdz_para
29 USE indice_sol_mod
30 !****************************************************************************************
31 ! Bucket calculations for surface.
32 !
33 INCLUDE "clesphys.h"
34 INCLUDE "dimsoil.h"
35 INCLUDE "YOMCST.h"
36
37 ! Input variables
38 !****************************************************************************************
39 INTEGER, INTENT(IN) :: itime, jour, knon
40 INTEGER, DIMENSION(klon), INTENT(IN) :: knindex
41 LOGICAL, INTENT(IN) :: debut
42 REAL, INTENT(IN) :: dtime
43 REAL, DIMENSION(klon), INTENT(IN) :: tsurf
44 REAL, DIMENSION(klon), INTENT(IN) :: p1lay
45 REAL, DIMENSION(klon), INTENT(IN) :: tq_cdrag
46 REAL, DIMENSION(klon), INTENT(IN) :: precip_rain, precip_snow
47 REAL, DIMENSION(klon), INTENT(IN) :: temp_air, spechum
48 REAL, DIMENSION(klon), INTENT(IN) :: petAcoef, peqAcoef
49 REAL, DIMENSION(klon), INTENT(IN) :: petBcoef, peqBcoef
50 REAL, DIMENSION(klon), INTENT(IN) :: pref
51 REAL, DIMENSION(klon), INTENT(IN) :: u1, v1, gustiness
52 REAL, DIMENSION(klon), INTENT(IN) :: rugoro
53 REAL, DIMENSION(klon), INTENT(IN) :: swnet, lwnet
54
55 ! In/Output variables
56 !****************************************************************************************
57 REAL, DIMENSION(klon), INTENT(INOUT) :: snow, qsol
58 REAL, DIMENSION(klon), INTENT(INOUT) :: agesno
59 REAL, DIMENSION(klon, nsoilmx), INTENT(INOUT) :: tsoil
60
61 ! Output variables
62 !****************************************************************************************
63 REAL, DIMENSION(klon), INTENT(OUT) :: qsurf
64 REAL, DIMENSION(klon), INTENT(OUT) :: z0_new
65 REAL, DIMENSION(klon), INTENT(OUT) :: alb1_new, alb2_new
66 REAL, DIMENSION(klon), INTENT(OUT) :: evap, fluxsens, fluxlat
67 REAL, DIMENSION(klon), INTENT(OUT) :: tsurf_new
68 REAL, DIMENSION(klon), INTENT(OUT) :: dflux_s, dflux_l
69
70 ! Local variables
71 !****************************************************************************************
72 960 REAL, DIMENSION(klon) :: soilcap, soilflux
73 960 REAL, DIMENSION(klon) :: cal, beta, dif_grnd, capsol
74 960 REAL, DIMENSION(klon) :: alb_neig, alb_lim
75 960 REAL, DIMENSION(klon) :: zfra
76 960 REAL, DIMENSION(klon) :: radsol ! total net radiance at surface
77 960 REAL, DIMENSION(klon) :: u0, v0, u1_lay, v1_lay
78 960 REAL, DIMENSION(klon) :: dummy_riverflow,dummy_coastalflow
79 INTEGER :: i
80 !
81 !****************************************************************************************
82
83
84 !
85 !* Read from limit.nc : albedo(alb_lim), length of rugosity(z0_new)
86 !
87 CALL limit_read_rug_alb(itime, dtime, jour,&
88 knon, knindex, &
89 480 z0_new, alb_lim)
90 !
91 !* Calcultaion of fluxes
92 !
93
94 ! calculate total absorbed radiance at surface
95
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 radsol(:) = 0.0
96
2/2
✓ Branch 0 taken 247680 times.
✓ Branch 1 taken 480 times.
248160 radsol(1:knon) = swnet(1:knon) + lwnet(1:knon)
97
98 ! calculate constants
99 480 CALL calbeta(dtime, is_ter, knon, snow, qsol, beta, capsol, dif_grnd)
100
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 480 times.
480 if (type_veget=='betaclim') then
101 CALL calbeta_clim(knon,jour,latitude(knindex(1:knon)),beta)
102 endif
103
104 ! calculate temperature, heat capacity and conduction flux in soil
105
1/2
✓ Branch 0 taken 480 times.
✗ Branch 1 not taken.
480 IF (soil_model) THEN
106 CALL soil(dtime, is_ter, knon, snow, tsurf, qsol, &
107
5/6
✓ Branch 0 taken 480 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 247680 times.
✓ Branch 3 taken 480 times.
✓ Branch 4 taken 247680 times.
✓ Branch 5 taken 480 times.
495840 & longitude(knindex(1:knon)), latitude(knindex(1:knon)), tsoil, soilcap, soilflux)
108
109
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 247680 times.
248160 DO i=1, knon
110 247680 cal(i) = RCPD / soilcap(i)
111 248160 radsol(i) = radsol(i) + soilflux(i)
112 END DO
113 ELSE
114 cal(:) = RCPD * capsol(:)
115 IF (klon_glo .EQ. 1) THEN
116 cal(:) = 0.
117 ENDIF
118 ENDIF
119
120 ! Suppose zero surface speed
121
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 u0(:)=0.0
122
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 v0(:)=0.0
123
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 u1_lay(:) = u1(:) - u0(:)
124
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 v1_lay(:) = v1(:) - v0(:)
125
126 CALL calcul_fluxs(knon, is_ter, dtime, &
127 tsurf, p1lay, cal, beta, tq_cdrag, tq_cdrag, pref, &
128 precip_rain, precip_snow, snow, qsurf, &
129 radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, gustiness, &
130 1.,petAcoef, peqAcoef, petBcoef, peqBcoef, &
131 480 tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
132
133 !
134 !* Calculate snow height, run_off, age of snow
135 !
136 CALL fonte_neige( knon, is_ter, knindex, dtime, &
137 tsurf, precip_rain, precip_snow, &
138 480 snow, qsol, tsurf_new, evap)
139 !
140 !* Calculate the age of snow
141 !
142 480 CALL albsno(klon,knon,dtime,agesno(:),alb_neig(:), precip_snow(:))
143
144
4/4
✓ Branch 0 taken 247680 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 183073 times.
✓ Branch 3 taken 64607 times.
248160 WHERE (snow(1 : knon) .LT. 0.0001) agesno(1 : knon) = 0.
145
146
2/2
✓ Branch 0 taken 247680 times.
✓ Branch 1 taken 480 times.
248160 DO i=1, knon
147 247680 zfra(i) = MAX(0.0,MIN(1.0, snow(i)/(snow(i)+10.0)))
148 248160 alb_lim(i) = alb_neig(i) *zfra(i) + alb_lim(i)*(1.0-zfra(i))
149 END DO
150
151 !
152 !* Return albedo :
153 ! alb1_new and alb2_new are here given the same values
154 !
155
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 alb1_new(:) = 0.0
156
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 alb2_new(:) = 0.0
157
2/2
✓ Branch 0 taken 247680 times.
✓ Branch 1 taken 480 times.
248160 alb1_new(1:knon) = alb_lim(1:knon)
158
2/2
✓ Branch 0 taken 247680 times.
✓ Branch 1 taken 480 times.
248160 alb2_new(1:knon) = alb_lim(1:knon)
159
160 !
161 !* Calculate the rugosity
162 !
163
2/2
✓ Branch 0 taken 247680 times.
✓ Branch 1 taken 480 times.
248160 DO i = 1, knon
164 248160 z0_new(i) = MAX(1.5e-05,SQRT(z0_new(i)**2 + rugoro(i)**2))
165 END DO
166
167 !* Send to coupler
168 ! The run-off from river and coast are not calculated in the bucket modele.
169 ! For testing purpose of the coupled modele we put the run-off to zero.
170
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 480 times.
480 IF (type_ocean=='couple') THEN
171 dummy_riverflow(:) = 0.0
172 dummy_coastalflow(:) = 0.0
173 CALL cpl_send_land_fields(itime, knon, knindex, &
174 dummy_riverflow, dummy_coastalflow)
175 ENDIF
176
177 !
178 !* End
179 !
180 480 END SUBROUTINE surf_land_bucket
181 !
182 !****************************************************************************************
183 !
184 END MODULE surf_land_bucket_mod
185