LMDZ
ocean_albedo.F90
Go to the documentation of this file.
1 !
2 ! $Id$
3 !
4 
5 ! #########
6 
7 subroutine ocean_albedo(knon,zrmu0,knindex,pwind,SFRWL,alb_dir_new,alb_dif_new)
8 
9 
10 ! ##################################################################
11 !
12 !!**** *ALBEDO_RS14*
13 !!
14 !! PURPOSE
15 !! -------
16 ! computes the direct & diffuse albedo over open water
17 !
18 !
19 !!** METHOD
20 !! ------
21 !
22 !! EXTERNAL
23 !! --------
24 !!
25 !! IMPLICIT ARGUMENTS
26 !! ------------------
27 !!
28 !!
29 !! REFERENCE
30 !! ---------
31 !!
32 !!
33 !! AUTHOR
34 !! ------
35 !! R. Séférian * Meteo-France *
36 !!
37 !! MODIFICATIONS
38 !! -------------
39 !! Original 03/2014
40 ! 05/2014 R. Séférian & B. Decharme :: Adaptation to spectral
41 ! computation for diffuse and direct albedo
42 ! 08/2014 S. Baek :: for wider wavelength range 200-4000nm and
43 ! adaptation to LMDZ + whitecap effect by Koepke + chrolophyll
44 ! map from climatology file
45 !
46 !-------------------------------------------------------------------------------
47 !
48 !* DECLARATIONS
49 ! ------------
50 !
52 use dimphy
53 !LF USE PARKIND1 ,ONLY : JPIM ,JPRB
54 use phys_state_var_mod, only : chl_con
55 !
56 !
57 IMPLICIT NONE
58 !
59 !* 0.1 declarations of arguments
60 ! -------------------------
61 !
62 
63 include "clesphys.h"
64 
65 integer, intent(in) :: knon
66 integer, dimension(klon), intent(in) :: knindex
67 real, dimension(klon), intent(in) :: zrmu0,pwind
68 real, dimension(klon,nsw), intent(out) :: alb_dir_new,alb_dif_new
69 real, dimension(6),intent(in) :: SFRWL
70 
71 
72 !=== LOCAL VARIABLES
73 
74 REAL, parameter :: XPI=4.*atan(1.)
75 
76 !
77 !* 0.2 declarations of local variables
78 ! -------------------------
79 !
80 REAL, DIMENSION(klon) :: ZCHL ! surface chlorophyll
81 REAL, DIMENSION(klon,NNWL) :: ZDIR_ALB ! direct ocean surface albedo (spectral)
82 REAL, DIMENSION(klon,NNWL) :: ZSCA_ALB ! diffuse ocean surface albedo (spectral)
83 !
84 INTEGER :: JI, JWL ! indexes
85 REAL :: ZWL ! input parameter: wavelength and diffuse/direct fraction of light
86 REAL:: ZSIG, ZREFM, ZXX2, ZR00, ZRR0, ZRRR ! computation variables
87 REAL:: ZR22, ZUE, ZUE2, ZR11DF, ZALBT, ZFWC ! computation variables
88 REAL:: ZCHLABS, ZAW, ZBW, ZAP, ZYLMD, ZBP550 ! computation variables
89 REAL:: ZBBP, ZNU, ZHB ! computation variables
90 REAL:: ZCOSZEN ! Cosine of the zenith solar angle
91 REAL:: ZR11, ZRW, ZRWDF, ZRDF ! 4 components of the OSA
92 ! new damping coefficient
93 REAL:: ZDAMP
94 
95 !
96 REAL :: ZWORK ! dummy variable
97 !
98 !LF REAL(KIND=JPRB) :: ZHOOK_HANDLE
99 !
100 !-------------------------------------------------------------------------------
101 !
102 !
103 
104 
105 
106 !
107 alb_dir_new(:,:) = 0.
108 alb_dif_new(:,:) = 0.
109 !
110 zdir_alb(:,:) = 0.
111 zsca_alb(:,:) = 0.
112 !
113 !
114 
115 !ZCHL(:) = CHL_CON!0.05 ! averaged global values for surface chlorophyll
116 if(ok_chlorophyll)then
117  do ji=1,knon
118  zchl(ji)=chl_con(knindex(ji))
119  enddo
120 else
121  zchl(:) = 0.05
122 endif
123 
124 
125 !
126 DO jwl=1,nnwl ! loop over the wavelength
127 !
128  DO ji=1,knon ! loop over the grid points
129 
130 
131  !---------------------------------------------------------------------------------
132  ! 0- Compute baseline values
133  !---------------------------------------------------------------------------------
134 
135  ! Get refractive index for the correspoding wavelength
136  zwl=xakwl(jwl) !!!---------- wavelength value
137  zrefm= xakrefm(jwl) !!!--------- refraction index value
138 
139 
140  ! compute the cosine of the solar zenith angle
141 ! ZCOSZEN = COS(XPI/2 - PZENITH(JI))
142  zcoszen = zrmu0(knindex(ji))
143  ! Compute sigma derived from wind speed (Cox & Munk reflectance model)
144  zsig=sqrt(0.003+0.00512*pwind(ji))
145 
146 
147  !---------------------------------------------------------------------------------
148  ! 1- Compute direct surface albedo (ZR11)
149  !---------------------------------------------------------------------------------
150  !
151  zxx2=sqrt(1.0-(1.0-zcoszen**2)/zrefm**2)
152  zrr0=0.50*(((zxx2-zrefm*zcoszen)/(zxx2+zrefm*zcoszen))**2 +((zcoszen-zrefm*zxx2)/(zcoszen+zrefm*zxx2))**2)
153  zrrr=0.50*(((zxx2-1.34*zcoszen)/(zxx2+1.34*zcoszen))**2 +((zcoszen-1.34*zxx2)/(zcoszen+1.34*zxx2))**2)
154  zr11=zrr0-(0.0152-1.7873*zcoszen+6.8972*zcoszen**2-8.5778*zcoszen**3+4.071*zsig-7.6446*zcoszen*zsig) &
155  & * exp(0.1643-7.8409*zcoszen-3.5639*zcoszen**2-2.3588*zsig+10.0538*zcoszen*zsig)*zrr0/zrrr
156  !
157  !---------------------------------------------------------------------------------
158  ! 2- Compute surface diffuse albedo (ZRDF)
159  !---------------------------------------------------------------------------------
160  ! Diffuse albedo from Jin et al., 2006 + estimation from diffuse fraction of
161  ! light (relying later on AOD)
162  zrdf=-0.1482-0.012*zsig+0.1609*zrefm-0.0244*zsig*zrefm ! surface diffuse (Eq 5a-5b)
163 
164  !---------------------------------------------------------------------------------
165  ! *- Determine absorption and backscattering
166  ! coefficients to determine reflectance below the surface (Ro) once for all
167  !
168  ! *.1- Absorption by chlorophyll
169  zchlabs= xakachl(jwl)
170  ! *.2- Absorption by seawater
171  zaw= xakaw3(jwl)
172  ! *.3- Backscattering by seawater
173  zbw= xakbw(jwl)
174  ! *.4- Backscattering by chlorophyll
175  zylmd = exp(0.014*(440.0-zwl))
176  zwork= exp(log(zchl(ji))*0.65)
177  zap = 0.06*zchlabs*zwork +0.2*(xaw440+0.06*zwork)*zylmd
178  zbp550 = 0.416 * exp(log(zchl(ji))*0.766)
179 
180  IF ( zchl(ji) > 2. ) THEN
181  znu=0.
182  ELSE
183  IF ( zchl(ji) > 0.02 ) THEN
184  zwork=log10(zchl(ji))
185  znu=0.5*(zwork-0.3)
186  zbbp=(0.002+0.01*(0.5-0.25*zwork)*(zwl/550.)**znu)*zbp550
187  ELSE
188  zbbp=0.019*(550./zwl)*zbp550 !ZBBPf=0.0113 at chl<=0.02
189  ENDIF
190  ENDIF
191 
192  ! Morel-Gentili(1991), Eq (12)
193  ! ZHB=h/(h+2*ZBBPf*(1.-h))
194  zhb=0.5*zbw/(0.5*zbw+zbbp)
195 
196  !---------------------------------------------------------------------------------
197  ! 3- Compute direct water-leaving albedo (ZRW)
198  !---------------------------------------------------------------------------------
199  ! Based on Morel & Gentilli 1991 parametrization
200  zr22=0.48168549-0.014894708*zsig-0.20703885*zsig**2
201  ! Use Morel 91 formula to compute the direct reflectance
202  ! below the surface
203  zr00=(0.5*zbw+zbbp)/(zaw+zap) *(0.6279-0.2227*zhb-0.0513*zhb**2 + (-0.3119+0.2465*zhb)*zcoszen)
204  zrw=zr00*(1.-zr22)*(1.-zr11)/(1.-zr00*zr22)
205 
206  zrw=zr00*(1.-zr22)/(1.-zr00*zr22)
207  !---------------------------------------------------------------------------------
208  ! 4- Compute diffuse water-leaving albedo (ZRWDF)
209  !---------------------------------------------------------------------------------
210  ! as previous water-leaving computation but assumes a uniform incidence of
211  ! shortwave at surface (ue)
212  zue=0.676 ! equivalent u_unif for diffuse incidence
213  zue2=sqrt(1.0-(1.0-zue**2)/zrefm**2)
214  zrr0=0.50*(((zue2-zrefm*zue)/(zue2+zrefm*zue))**2 +((zue-zrefm*zue2)/(zue+zrefm*zue2))**2)
215  zrrr=0.50*(((zue2-1.34*zue)/(zue2+1.34*zue))**2 +((zue-1.34*zue2)/(zue+1.34*zue2))**2)
216  zr11df=zrr0-(0.0152-1.7873*zue+6.8972*zue**2-8.5778*zue**3+4.071*zsig-7.6446*zue*zsig) &
217  & * exp(0.1643-7.8409*zue-3.5639*zue**2-2.3588*zsig+10.0538*zue*zsig)*zrr0/zrrr
218  ! Use Morel 91 formula to compute the diffuse
219  ! reflectance below the surface
220  zr00=(0.5*zbw+zbbp)/(zaw+zap) *(0.6279-0.2227*zhb-0.0513*zhb**2 + (-0.3119+0.2465*zhb)*zue)
221  zrwdf=zr00*(1.-zr22)*(1.-zr11df)/(1.-zr00*zr22)
222 
223  ! original : correction for foam (Eq 16-17)
224  zfwc=3.97e-4*pwind(ji)**(1.59) ! Salisbury 2014 eq(2) at 37GHz, value in fraction
225  ! has to be update once we have information from wave model (discussion with G. Madec)
226 
227  ! --------------------------------------------------------------------
228  ! *- OSA estimation
229  ! --------------------------------------------------------------------
230  ! partitionning direct and diffuse albedo
231  !
232 
233  ! excluding diffuse albedo ZRW on ZDIR_ALB
234  zdir_alb(ji,jwl) = xfrwl(jwl) *((1.-zfwc) * (zr11+zrw) +zfwc*xrwc(jwl))
235  zsca_alb(ji,jwl) = xfrwl(jwl) *((1.-zfwc) * (zrdf+zrwdf) + zfwc*xrwc(jwl))
236 
237  ! print*,ji,ZFWC,ZDIR_ALB(JI,JWL),ZSCA_ALB(JI,JWL),pwind(ji)
238  ENDDO ! end of the loop over grid points
239 
240 ENDDO ! ending loop over wavelengths
241 
242 
243 ! integral for each nsw band
244 
245 select case(nsw)
246 case(2)
247  do ji=1,knon
248  alb_dir_new(ji,1)=sum(zdir_alb(ji,1:49))/sfrwl(1) ! from 200nm to 680nm
249  alb_dir_new(ji,2)=sum(zdir_alb(ji,50:381))/sfrwl(2) ! from 690nm to 4000 nm
250 
251  alb_dif_new(ji,1)=sum(zsca_alb(ji,1:49))/sfrwl(1) ! from 200nm to 680nm
252  alb_dif_new(ji,2)=sum(zsca_alb(ji,50:381))/sfrwl(2) ! from 690nm to 4000 nm
253  enddo
254 case(4)
255  do ji=1,knon
256  alb_dir_new(ji,1)=sum(zdir_alb(ji,1:49))/sfrwl(1) ! from 200nm to 680nm
257  alb_dir_new(ji,2)=sum(zdir_alb(ji,50:99))/sfrwl(2) ! from 690nm to 1180 nm
258  alb_dir_new(ji,3)=sum(zdir_alb(ji,100:218))/sfrwl(3) ! from 1190nm to 2370 nm
259  alb_dir_new(ji,4)=sum(zdir_alb(ji,219:381))/sfrwl(4) ! from 2380nm to 4000 nm
260 
261  alb_dif_new(ji,1)=sum(zsca_alb(ji,1:49))/sfrwl(1) ! from 200nm to 680nm
262  alb_dif_new(ji,2)=sum(zsca_alb(ji,50:99))/sfrwl(2) ! from 690nm to 1180 nm
263  alb_dif_new(ji,3)=sum(zsca_alb(ji,100:218))/sfrwl(3) ! from 1190nm to 2370 nm
264  alb_dif_new(ji,4)=sum(zsca_alb(ji,219:381))/sfrwl(4) ! from 2380nm to 4000 nm
265  enddo
266 case(6)
267  do ji=1,knon
268  alb_dir_new(ji,1)=sum(zdir_alb(ji,1:5))/sfrwl(1) ! from 200nm to 240nm
269  alb_dir_new(ji,2)=sum(zdir_alb(ji,6:24))/sfrwl(2) ! from 250nm to 430 nm
270  alb_dir_new(ji,3)=sum(zdir_alb(ji,25:49))/sfrwl(3) ! from 440nm to 680 nm
271  alb_dir_new(ji,4)=sum(zdir_alb(ji,50:99))/sfrwl(4) ! from 690nm to 1180 nm
272  alb_dir_new(ji,5)=sum(zdir_alb(ji,100:218))/sfrwl(5) ! from 1190nm to 2370 nm
273  alb_dir_new(ji,6)=sum(zdir_alb(ji,219:381))/sfrwl(6) ! from 2380nm to 4000 nm
274 
275  alb_dif_new(ji,1)=sum(zsca_alb(ji,1:5))/sfrwl(1) ! from 200nm to 240nm
276  alb_dif_new(ji,2)=sum(zsca_alb(ji,6:24))/sfrwl(2) ! from 250nm to 430 nm
277  alb_dif_new(ji,3)=sum(zsca_alb(ji,25:49))/sfrwl(3) ! from 440nm to 680 nm
278  alb_dif_new(ji,4)=sum(zsca_alb(ji,50:99))/sfrwl(4) ! from 690nm to 1180 nm
279  alb_dif_new(ji,5)=sum(zsca_alb(ji,100:218))/sfrwl(5) ! from 1190nm to 2370 nm
280  alb_dif_new(ji,6)=sum(zsca_alb(ji,219:381))/sfrwl(6) ! from 2380nm to 4000 nm
281  enddo
282 end select
283 
284 
285 
286 END subroutine ocean_albedo
287 
real, dimension(nnwl), parameter xakwl
real, dimension(nnwl), parameter xrwc
real, dimension(nnwl), parameter xakrefm
subroutine ocean_albedo(knon, zrmu0, knindex, pwind, SFRWL, alb_dir_new, alb_dif_new)
Definition: ocean_albedo.F90:8
real, dimension(nnwl), parameter xakaw3
real, dimension(nnwl), parameter xfrwl
real, dimension(nnwl), parameter xakbw
real, dimension(:), allocatable, save chl_con
integer, parameter nnwl
real, dimension(nnwl), parameter xakachl
real, parameter xaw440
Definition: dimphy.F90:1