GCC Code Coverage Report


Directory: ./
File: phys/ocean_albedo.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 53 61 86.9%
Branches: 74 90 82.2%

Line Branch Exec Source
1 !
2 ! $Id$
3 !
4
5 960 SUBROUTINE ocean_albedo(knon,zrmu0,knindex,pwind,SFRWL,alb_dir_new,alb_dif_new)
6 !!
7 !!**** *ALBEDO_RS14*
8 !!
9 !! PURPOSE
10 !! -------
11 !! computes the direct & diffuse albedo over open water
12 !!
13 !!** METHOD
14 !! ------
15 !!
16 !! EXTERNAL
17 !! --------
18 !!
19 !! IMPLICIT ARGUMENTS
20 !! ------------------
21 !!
22 !! REFERENCE
23 !! ---------
24 !!
25 !! AUTHOR
26 !! ------
27 !! R. Séférian * Meteo-France *
28 !!
29 !! MODIFICATIONS
30 !! -------------
31 !! Original 03/2014
32 !! 05/2014 R. Séférian & B. Decharme :: Adaptation to spectral
33 !! computation for diffuse and direct albedo
34 !! 08/2014 S. Baek :: for wider wavelength range 200-4000nm and
35 !! adaptation to LMDZ + whitecap effect by Koepke + chrolophyll
36 !! map from climatology file
37 !! 10/2016 O. Boucher :: some optimisation following R.
38 !! Seferian's work in the CNRM Model
39 !!
40 !-------------------------------------------------------------------------------
41 !
42 !* DECLARATIONS
43 ! ------------
44 !
45 USE ocean_albedo_para
46 USE dimphy
47 USE phys_state_var_mod, ONLY : chl_con
48 !
49 !
50 IMPLICIT NONE
51 !
52 !* 0.1 declarations of arguments
53 ! -------------------------
54 !
55 include "clesphys.h"
56 !
57 INTEGER, INTENT(IN) :: knon
58 INTEGER, DIMENSION(klon), INTENT(IN) :: knindex
59 REAL, DIMENSION(klon), INTENT(IN) :: zrmu0 !--cos(SZA) on full vector
60 REAL, DIMENSION(klon), INTENT(IN) :: pwind !--wind speed on compressed vector
61 REAL, DIMENSION(6),INTENT(IN) :: SFRWL
62 REAL, DIMENSION(klon,nsw), INTENT(OUT) :: alb_dir_new, alb_dif_new
63 !
64 !* 0.2 declarations of local variables
65 ! -------------------------
66 !
67 960 REAL, DIMENSION(klon) :: ZCHL ! surface chlorophyll
68 960 REAL, DIMENSION(klon) :: ZCOSZEN ! Cosine of the zenith solar angle
69 !
70 INTEGER :: JWL, INU ! indexes
71 INTEGER :: JI
72 REAL :: ZWL ! input parameter: wavelength and diffuse/direct fraction of light
73 REAL:: ZCHLABS, ZAW, ZBW, ZREFM, ZYLMD, ZUE, ZUE2 ! scalar computation variables
74 !
75 960 REAL, DIMENSION(klon) :: ZAP, ZXX2, ZR00, ZRR0, ZRRR ! computation variables
76 960 REAL, DIMENSION(klon) :: ZR22, ZR11DF ! computation variables
77 960 REAL, DIMENSION(klon) :: ZBBP, ZNU, ZHB ! computation variables
78 960 REAL, DIMENSION(klon) :: ZR11, ZRW, ZRWDF, ZRDF ! 4 components of the OSA
79 REAL, DIMENSION(klon) :: ZSIG, ZFWC, ZWORK1, ZWORK2, ZWORK3
80 !
81 !--initialisations-------------
82 !
83
84
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 480 times.
480 IF (knon==0) RETURN ! A verifier pourquoi on en a besoin...
85
86
4/4
✓ Branch 0 taken 2880 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 2862720 times.
✓ Branch 3 taken 2880 times.
2866080 alb_dir_new(:,:) = 0.
87
4/4
✓ Branch 0 taken 2880 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 2862720 times.
✓ Branch 3 taken 2880 times.
2866080 alb_dif_new(:,:) = 0.
88 !
89 ! Initialisation of chlorophyll content
90 ! ZCHL(:) = CHL_CON!0.05 ! averaged global values for surface chlorophyll
91
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 480 times.
480 IF (ok_chlorophyll) THEN
92 ZCHL(1:knon)=CHL_CON(knindex(1:knon))
93 ELSE
94
2/2
✓ Branch 0 taken 362977 times.
✓ Branch 1 taken 480 times.
363457 ZCHL(1:knon) = 0.05
95 ENDIF
96
97 ! variables that do not depend on wavelengths
98 ! loop over the grid points
99 ! functions of chlorophyll content
100
2/2
✓ Branch 0 taken 362977 times.
✓ Branch 1 taken 480 times.
363457 ZWORK1(1:knon)= EXP(LOG(ZCHL(1:knon))*0.65)
101
2/2
✓ Branch 0 taken 362977 times.
✓ Branch 1 taken 480 times.
363457 ZWORK2(1:knon)= 0.416 * EXP(LOG(ZCHL(1:knon))*0.766)
102
2/2
✓ Branch 0 taken 362977 times.
✓ Branch 1 taken 480 times.
363457 ZWORK3(1:knon)= LOG10(ZCHL(1:knon))
103 ! store the cosine of the solar zenith angle
104
2/2
✓ Branch 0 taken 362977 times.
✓ Branch 1 taken 480 times.
363457 ZCOSZEN(1:knon) = zrmu0(knindex(1:knon))
105 ! Compute sigma derived from wind speed (Cox & Munk reflectance model)
106
2/2
✓ Branch 0 taken 362977 times.
✓ Branch 1 taken 480 times.
363457 ZSIG(1:knon)=SQRT(0.003+0.00512*PWIND(1:knon))
107 ! original : correction for foam (Eq 16-17)
108 ! has to be update once we have information from wave model (discussion with G. Madec)
109
2/2
✓ Branch 0 taken 362977 times.
✓ Branch 1 taken 480 times.
363457 ZFWC(1:knon)=3.97e-4*PWIND(1:knon)**1.59 ! Salisbury 2014 eq(2) at 37GHz, value in fraction
110 !
111
2/2
✓ Branch 0 taken 182880 times.
✓ Branch 1 taken 480 times.
183360 DO JWL=1,NNWL ! loop over the wavelengths
112 !
113 !---------------------------------------------------------------------------------
114 ! 0- Compute baseline values
115 !---------------------------------------------------------------------------------
116
117 ! Get refractive index for the correspoding wavelength
118 182880 ZWL=XAKWL(JWL) !!!--------- wavelength value
119 182880 ZREFM= XAKREFM(JWL) !!!--------- refraction index value
120
121 !---------------------------------------------------------------------------------
122 ! 1- Compute direct surface albedo (ZR11)
123 !---------------------------------------------------------------------------------
124 !
125
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477117 ZXX2(1:knon)=SQRT(1.0-(1.0-ZCOSZEN(1:knon)**2)/ZREFM**2)
126 ZRR0(1:knon)=0.50*(((ZXX2(1:knon)-ZREFM*ZCOSZEN(1:knon))/(ZXX2(1:knon)+ZREFM*ZCOSZEN(1:knon)))**2 + &
127
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477117 ((ZCOSZEN(1:knon)-ZREFM*ZXX2(1:knon))/(ZCOSZEN(1:knon)+ZREFM*ZXX2(1:knon)))**2)
128 ZRRR(1:knon)=0.50*(((ZXX2(1:knon)-1.34*ZCOSZEN(1:knon))/(ZXX2(1:knon)+1.34*ZCOSZEN(1:knon)))**2 + &
129
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477117 ((ZCOSZEN(1:knon)-1.34*ZXX2(1:knon))/(ZCOSZEN(1:knon)+1.34*ZXX2(1:knon)))**2)
130 ZR11(1:knon)=ZRR0(1:knon)-(0.0152-1.7873*ZCOSZEN(1:knon)+6.8972*ZCOSZEN(1:knon)**2-8.5778*ZCOSZEN(1:knon)**3+ &
131 4.071*ZSIG(1:knon)-7.6446*ZCOSZEN(1:knon)*ZSIG(1:knon)) * &
132 EXP(0.1643-7.8409*ZCOSZEN(1:knon)-3.5639*ZCOSZEN(1:knon)**2-2.3588*ZSIG(1:knon)+ &
133
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477117 10.0538*ZCOSZEN(1:knon)*ZSIG(1:knon))*ZRR0(1:knon)/ZRRR(1:knon)
134 !
135 !---------------------------------------------------------------------------------
136 ! 2- Compute surface diffuse albedo (ZRDF)
137 !---------------------------------------------------------------------------------
138 ! Diffuse albedo from Jin et al., 2006 + estimation from diffuse fraction of
139 ! light (relying later on AOD). CNRM model has opted for Eq 5b
140
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477117 ZRDF(1:knon)=-0.1482-0.012*ZSIG(1:knon)+0.1609*ZREFM-0.0244*ZSIG(1:knon)*ZREFM ! surface diffuse (Eq 5a)
141 !!ZRDF(1:knon)=-0.1479+0.1502*ZREFM-0.0176*ZSIG(1:knon)*ZREFM ! surface diffuse (Eq 5b)
142
143 !---------------------------------------------------------------------------------
144 ! *- Determine absorption and backscattering
145 ! coefficients to determine reflectance below the surface (Ro) once for all
146 !
147 ! *.1- Absorption by chlorophyll
148 182880 ZCHLABS= XAKACHL(JWL)
149 ! *.2- Absorption by seawater
150 182880 ZAW= XAKAW3(JWL)
151 ! *.3- Backscattering by seawater
152 182880 ZBW= XAKBW(JWL)
153 ! *.4- Backscattering by chlorophyll
154 182880 ZYLMD = EXP(0.014*(440.0-ZWL))
155
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477117 ZAP(1:knon) = 0.06*ZCHLABS*ZWORK1(1:knon) +0.2*(XAW440+0.06*ZWORK1(1:knon))*ZYLMD
156
157 !! WHERE ( ZCHL(1:knon) > 0.02 )
158 !! ZNU(:)=MIN(0.0,0.5*(ZWORK3(:)-0.3))
159 !! ZBBP(:)=(0.002+0.01*(0.5-0.25*ZWORK3(:))*(ZWL/550.)**ZNU(:))*ZWORK2(:)
160 !! ELSEWHERE
161 !! ZBBP(:)=0.019*(550./ZWL)*ZWORK2(:) !ZBBPf=0.0113 at chl<=0.02
162 !! ENDWHERE
163
164
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477117 do JI = 1, knon
165
1/2
✓ Branch 0 taken 138294237 times.
✗ Branch 1 not taken.
138477117 IF (ZCHL(JI) > 0.02) THEN
166 138294237 ZNU(JI)=MIN(0.0,0.5*(ZWORK3(JI)-0.3))
167 ZBBP(JI)=(0.002+0.01*(0.5-0.25*ZWORK3(JI))*(ZWL/550.)**ZNU(JI)) &
168 138294237 *ZWORK2(JI)
169 ELSE
170 ZBBP(JI)=0.019*(550./ZWL)*ZWORK2(JI) !ZBBPf=0.0113 at chl<=0.02
171 ENDIF
172 ENDDO
173
174 ! Morel-Gentili(1991), Eq (12)
175 ! ZHB=h/(h+2*ZBBPf*(1.-h))
176
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477117 ZHB(1:knon)=0.5*ZBW/(0.5*ZBW+ZBBP(1:knon))
177
178 !---------------------------------------------------------------------------------
179 ! 3- Compute direct water-leaving albedo (ZRW)
180 !---------------------------------------------------------------------------------
181 ! Based on Morel & Gentilli 1991 parametrization
182
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477117 ZR22(1:knon)=0.48168549-0.014894708*ZSIG(1:knon)-0.20703885*ZSIG(1:knon)**2
183
184 ! Use Morel 91 formula to compute the direct reflectance
185 ! below the surface
186 ZR00(1:knon)=(0.5*ZBW+ZBBP(1:knon))/(ZAW+ZAP(1:knon)) * &
187 (0.6279-0.2227*ZHB(1:knon)-0.0513*ZHB(1:knon)**2 + &
188
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477117 (-0.3119+0.2465*ZHB(1:knon))*ZCOSZEN(1:knon))
189
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477117 ZRW(1:knon)=ZR00(1:knon)*(1.-ZR22(1:knon))/(1.-ZR00(1:knon)*ZR22(1:knon))
190
191 !---------------------------------------------------------------------------------
192 ! 4- Compute diffuse water-leaving albedo (ZRWDF)
193 !---------------------------------------------------------------------------------
194 ! as previous water-leaving computation but assumes a uniform incidence of
195 ! shortwave at surface (ue)
196 ZUE=0.676 ! equivalent u_unif for diffuse incidence
197 182880 ZUE2=SQRT(1.0-(1.0-ZUE**2)/ZREFM**2)
198
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477117 ZRR0(1:knon)=0.50*(((ZUE2-ZREFM*ZUE)/(ZUE2+ZREFM*ZUE))**2 +((ZUE-ZREFM*ZUE2)/(ZUE+ZREFM*ZUE2))**2)
199
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477117 ZRRR(1:knon)=0.50*(((ZUE2-1.34*ZUE)/(ZUE2+1.34*ZUE))**2 +((ZUE-1.34*ZUE2)/(ZUE+1.34*ZUE2))**2)
200 ZR11DF(1:knon)=ZRR0(1:knon)-(0.0152-1.7873*ZUE+6.8972*ZUE**2-8.5778*ZUE**3+4.071*ZSIG(1:knon)-7.6446*ZUE*ZSIG(1:knon)) * &
201
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477117 EXP(0.1643-7.8409*ZUE-3.5639*ZUE**2-2.3588*ZSIG(1:knon)+10.0538*ZUE*ZSIG(1:knon))*ZRR0(1:knon)/ZRRR(1:knon)
202
203 ! Use Morel 91 formula to compute the diffuse
204 ! reflectance below the surface
205 ZR00(1:knon) = (0.5*ZBW+ZBBP(1:knon)) / (ZAW+ZAP(1:knon)) &
206 * (0.6279-0.2227*ZHB(1:knon)-0.0513*ZHB(1:knon)**2 &
207
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477117 + (-0.3119+0.2465*ZHB(1:knon))*ZUE)
208
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477117 ZRWDF(1:knon)=ZR00(1:knon)*(1.-ZR22(1:knon))*(1.-ZR11DF(1:knon))/(1.-ZR00(1:knon)*ZR22(1:knon))
209
210 ! get waveband index inu for each nsw band
211 SELECT CASE(nsw)
212 CASE(2)
213 IF (JWL.LE.49) THEN ! from 200 to 680 nm
214 inu=1
215 ELSE ! from 690 to 4000 nm
216 inu=2
217 ENDIF
218 CASE(4)
219 IF (JWL.LE.49) THEN ! from 200 to 680 nm
220 inu=1
221 ELSE IF (JWL.LE.99) THEN ! from 690 to 1180 nm
222 inu=2
223 ELSE IF (JWL.LE.218) THEN ! from 1190 to 2370 nm
224 inu=3
225 ELSE ! from 2380 to 4000 nm
226 inu=4
227 ENDIF
228 CASE(6)
229
3/6
✗ Branch 0 not taken.
✗ Branch 1 not taken.
✓ Branch 2 taken 182880 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 180480 times.
✓ Branch 5 taken 2400 times.
182880 IF (JWL.LE.5) THEN ! from 200 to 240 nm
230 inu=1
231
2/2
✓ Branch 0 taken 171360 times.
✓ Branch 1 taken 9120 times.
180480 ELSE IF (JWL.LE.24) THEN ! from 250 to 430 nm
232 inu=2
233
2/2
✓ Branch 0 taken 159360 times.
✓ Branch 1 taken 12000 times.
171360 ELSE IF (JWL.LE.49) THEN ! from 440 to 680 nm
234 inu=3
235
2/2
✓ Branch 0 taken 135360 times.
✓ Branch 1 taken 24000 times.
159360 ELSE IF (JWL.LE.99) THEN ! from 690 to 1180 nm
236 inu=4
237
2/2
✓ Branch 0 taken 78240 times.
✓ Branch 1 taken 57120 times.
135360 ELSE IF (JWL.LE.218) THEN ! from 1190 to 2370 nm
238 inu=5
239 ELSE ! from 2380 to 4000 nm
240 inu=6
241 ENDIF
242 END SELECT
243
244 ! partitionning direct and diffuse albedo
245 ! excluding diffuse albedo ZRW on ZDIR_ALB
246
247 !--direct
248 alb_dir_new(1:knon,inu)=alb_dir_new(1:knon,inu) + &
249
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477117 ( XFRWL(JWL) * ((1.-ZFWC(1:knon)) * (ZR11(1:knon)+ZRW(1:knon)) + ZFWC(1:knon)*XRWC(JWL)) )/SFRWL(inu)
250 !--diffuse
251 alb_dif_new(1:knon,inu)=alb_dif_new(1:knon,inu) + &
252
2/2
✓ Branch 0 taken 138294237 times.
✓ Branch 1 taken 182880 times.
138477597 ( XFRWL(JWL) * ((1.-ZFWC(1:knon)) * (ZRDF(1:knon)+ZRWDF(1:knon)) + ZFWC(1:knon)*XRWC(JWL)) )/SFRWL(inu)
253
254 ENDDO ! ending loop over wavelengths
255
256 480 END SUBROUTINE ocean_albedo
257