SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
albedo_from_nir_vis.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6  SUBROUTINE albedo_from_nir_vis(PSW_BANDS,PALBNIR,PALBVIS,PALBUV,PDIR_ALB,PSCA_ALB)
7 ! ###########################################################################
8 !
9 !!**** *ALBEDO_FROM_NIR_VIS* - routine to initialize albedo for
10 !! any wavelength from near-infra-red,
11 !! visible and UV albedo
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !!** METHOD
17 !! ------
18 !!
19 !! EXTERNAL
20 !! --------
21 !!
22 !!
23 !! IMPLICIT ARGUMENTS
24 !! ------------------
25 !!
26 !! REFERENCE
27 !! ---------
28 !!
29 !!
30 !! AUTHOR
31 !! ------
32 !! V. Masson *Meteo France*
33 !!
34 !! MODIFICATIONS
35 !! -------------
36 !! Original 02/2003
37 !-------------------------------------------------------------------------------
38 !
39 !* 0. DECLARATIONS
40 ! ------------
41 !
42 USE modd_isba_par, ONLY : xred_edge, xuv_edge
43 USE modd_surf_par, ONLY : xundef
44 !
45 !
46 USE yomhook ,ONLY : lhook, dr_hook
47 USE parkind1 ,ONLY : jprb
48 !
49 IMPLICIT NONE
50 !
51 !* 0.1 Declarations of arguments
52 ! -------------------------
53 !
54 REAL, DIMENSION(:), INTENT(IN) :: psw_bands ! mean wavelength of each shortwave band (m)
55 REAL, DIMENSION(:), INTENT(IN) :: palbnir ! near infra-red albedo
56 REAL, DIMENSION(:), INTENT(IN) :: palbvis ! visible albedo
57 REAL, DIMENSION(:), INTENT(IN) :: palbuv ! UV albedo
58 REAL, DIMENSION(:,:), INTENT(OUT):: pdir_alb ! direct albedo for each wavelength
59 REAL, DIMENSION(:,:), INTENT(OUT):: psca_alb ! diffuse albedo for each wavelength
60 !
61 !* 0.2 Declarations of local variables
62 ! -------------------------------
63 !
64 INTEGER :: iswb ! number of SW spectral bands
65 INTEGER :: jswb ! loop counter on number of SW spectral bands
66 REAL(KIND=JPRB) :: zhook_handle
67 !-------------------------------------------------------------------------------
68 !
69 IF (lhook) CALL dr_hook('ALBEDO_FROM_NIR_VIS',0,zhook_handle)
70 iswb = SIZE(psw_bands)
71 !
72 pdir_alb(:,:) = xundef
73 psca_alb(:,:) = xundef
74 !
75 IF (iswb==1) THEN
76  WHERE(palbnir(:)/= xundef) pdir_alb(:,1) = 0.5*(palbnir(:)+palbvis(:))
77 ELSE
78  DO jswb=1,iswb
79  IF (psw_bands(jswb)>xred_edge ) THEN ! XRED_EDGE=0.7 micro-m
80  pdir_alb(:,jswb) = palbnir(:)
81  ELSE IF (psw_bands(jswb)<xuv_edge ) THEN ! XUV_EDGE=0.25 micro-m
82  pdir_alb(:,jswb) = palbuv(:)
83  ELSE
84  pdir_alb(:,jswb) = palbvis(:)
85  END IF
86  END DO
87 END IF
88 !
89 psca_alb(:,:) = pdir_alb(:,:)
90 IF (lhook) CALL dr_hook('ALBEDO_FROM_NIR_VIS',1,zhook_handle)
91 !-------------------------------------------------------------------------------
92 !
93 END SUBROUTINE albedo_from_nir_vis
subroutine albedo_from_nir_vis(PSW_BANDS, PALBNIR, PALBVIS, PALBUV, PDIR_ALB, PSCA_ALB)