SURFEX v8.1
General documentation of Surfex
diag_surf_budget_teb.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 diag_surf_budget_teb (D, PDIR_SW, PSCA_SW, PDIR_ALB, PSCA_ALB, &
7  PLW, PEMIS, PTRAD )
8 ! ###############################################################################
9 !
10 !!**** *DIAG_SURF_BUDGET_TEB * - Computes diagnostics over TEB
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 !!** METHOD
16 !! ------
17 !!
18 !! REFERENCE
19 !! ---------
20 !!
21 !!
22 !! AUTHOR
23 !! ------
24 !! P. Le Moigne
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 04/2006
29 !!------------------------------------------------------------------
30 !
31 USE modd_diag_n, ONLY : diag_t
32 !
33 USE modd_csts, ONLY : xstefan
34 !
35 USE yomhook ,ONLY : lhook, dr_hook
36 USE parkind1 ,ONLY : jprb
37 !
38 IMPLICIT NONE
39 !
40 !* 0.1 declarations of arguments
41 !
42 TYPE(diag_t), INTENT(INOUT) :: D
43 !
44 REAL, DIMENSION(:,:),INTENT(IN) :: PDIR_SW ! direct solar radiation (on horizontal surf.)
45 ! ! (W/m2)
46 REAL, DIMENSION(:,:),INTENT(IN) :: PSCA_SW ! diffuse solar radiation (on horizontal surf.)
47 ! ! (W/m2)
48 REAL, DIMENSION(:), INTENT(IN) :: PLW ! longwave radiation (on horizontal surf.)
49 REAL, DIMENSION(:), INTENT(IN) :: PTRAD ! radiative temperature (K)
50 REAL, DIMENSION(:,:),INTENT(IN) :: PDIR_ALB ! direct albedo for each spectral band (-)
51 REAL, DIMENSION(:,:),INTENT(IN) :: PSCA_ALB ! diffuse albedo for each spectral band (-)
52 REAL, DIMENSION(:), INTENT(IN) :: PEMIS ! emissivity (-)
53 !
54 !* 0.2 declarations of local variables
55 !
56 INTEGER :: ISWB ! number of SW bands
57 INTEGER :: JSWB ! loop counter on number of SW bands
58 REAL(KIND=JPRB) :: ZHOOK_HANDLE
59 !-------------------------------------------------------------------------------------
60 !
61 !
62 IF (lhook) CALL dr_hook('DIAG_SURF_BUDGET_TEB',0,zhook_handle)
63 iswb = SIZE(pdir_sw,2)
64 !
65 !* total incoming and outgoing SW
66 !
67 DO jswb=1,iswb
68  d%XSWBD(:,jswb) = pdir_sw(:,jswb) + psca_sw(:,jswb)
69  d%XSWBU(:,jswb) = pdir_sw(:,jswb) * pdir_alb(:,jswb) + psca_sw(:,jswb) * psca_alb(:,jswb)
70 ENDDO
71 !
72 d%XSWD(:) = 0.
73 d%XSWU(:) = 0.
74 DO jswb=1,iswb
75  d%XSWD(:)=d%XSWD(:)+d%XSWBD(:,jswb)
76  d%XSWU(:)=d%XSWU(:)+d%XSWBU(:,jswb)
77 ENDDO
78 !
79 !*incoming outgoing LW
80 !
81 d%XLWD(:)=plw(:)
82 d%XLWU(:)=pemis(:)*xstefan*ptrad(:)**4 + (1.-pemis(:))*plw(:)
83 !
84 IF (lhook) CALL dr_hook('DIAG_SURF_BUDGET_TEB',1,zhook_handle)
85 !
86 !-------------------------------------------------------------------------------------
87 !
88 END SUBROUTINE diag_surf_budget_teb
real, save xstefan
Definition: modd_csts.F90:59
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
subroutine diag_surf_budget_teb(D, PDIR_SW, PSCA_SW, PDIR_ALB, PSCA_ALB, PLW, PEMIS, PTRAD)