SURFEX v8.1
General documentation of Surfex
diag_surf_budget_isba.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_isba (PDIR_SW, PSCA_SW, PLW, K, DK )
7 ! ###############################################################################
8 !
9 !!**** *DIAG_SURF_BUDGET_ISBA * - Computes diagnostics over ISBA
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!** METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !!
21 !! AUTHOR
22 !! ------
23 !! P. Le Moigne
24 !!
25 !! MODIFICATIONS
26 !! -------------
27 !! Original 04/2006
28 !! Modified 08/2008 (B. Decharme) LWU diag
29 !!------------------------------------------------------------------
30 !
31 USE modd_diag_n, ONLY : diag_t
32 USE modd_isba_n, ONLY : isba_k_t
33 !
34 USE modd_csts, ONLY : xstefan
35 !
36 USE yomhook ,ONLY : lhook, dr_hook
37 USE parkind1 ,ONLY : jprb
38 !
39 IMPLICIT NONE
40 !
41 !* 0.1 declarations of arguments
42 !
43 REAL, DIMENSION(:,:),INTENT(IN) :: PDIR_SW ! direct solar radiation (on horizontal surf.)
44 ! ! (W/m2)
45 REAL, DIMENSION(:,:),INTENT(IN) :: PSCA_SW ! diffuse solar radiation (on horizontal surf.)
46 ! ! (W/m2)
47 REAL, DIMENSION(:), INTENT(IN) :: PLW ! longwave radiation (on horizontal surf.)
48 !
49 TYPE(isba_k_t), INTENT(INOUT) :: K
50 TYPE(diag_t), INTENT(INOUT) :: DK
51 !
52 !* 0.2 declarations of local variables
53 !
54 INTEGER :: ISWB ! number of SW bands
55 INTEGER :: JSWB ! loop counter on number of SW bands
56 REAL(KIND=JPRB) :: ZHOOK_HANDLE
57 !-------------------------------------------------------------------------------------
58 !
59 !
60 IF (lhook) CALL dr_hook('DIAG_SURF_BUDGET_ISBA',0,zhook_handle)
61 iswb = SIZE(pdir_sw,2)
62 !
63 !* total incoming and outgoing SW
64 !
65 DO jswb=1,iswb
66  dk%XSWBD(:,jswb) = pdir_sw(:,jswb) + psca_sw(:,jswb)
67  dk%XSWBU(:,jswb) = pdir_sw(:,jswb) * k%XDIR_ALB_WITH_SNOW(:,jswb) + &
68  psca_sw(:,jswb) * k%XSCA_ALB_WITH_SNOW(:,jswb)
69 ENDDO
70 !
71 dk%XSWD(:) = 0.
72 dk%XSWU(:) = 0.
73 DO jswb=1,iswb
74  dk%XSWD(:) = dk%XSWD(:) + dk%XSWBD(:,jswb)
75  dk%XSWU(:) = dk%XSWU(:) + dk%XSWBU(:,jswb)
76 ENDDO
77 !
78 !*incoming outgoing LW
79 !
80 !Wrong old diag : LWU=EMIS*STEFAN*Ts**4 + (1.-EMIS)*LW
81 !Due to e_budget.f90 linearization, LWU can not be calculated using actual Ts
82 !
83 dk%XLWD(:) = plw(:)
84 dk%XLWU(:) = dk%XSWD(:) - dk%XSWU(:) + dk%XLWD(:) - dk%XRN(:)
85 !
86 IF (lhook) CALL dr_hook('DIAG_SURF_BUDGET_ISBA',1,zhook_handle)
87 !
88 !-------------------------------------------------------------------------------------
89 !
90 END SUBROUTINE diag_surf_budget_isba
subroutine diag_surf_budget_isba(PDIR_SW, PSCA_SW, PLW, K, DK)
real, save xstefan
Definition: modd_csts.F90:59
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15