SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
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, PDIR_ALB, PSCA_ALB, &
7  plw, prn, &
8  pswd, pswu, pswbd, pswbu, plwd, plwu )
9 ! ###############################################################################
10 !
11 !!**** *DIAG_SURF_BUDGET_ISBA * - Computes diagnostics over ISBA
12 !!
13 !! PURPOSE
14 !! -------
15 !
16 !!** METHOD
17 !! ------
18 !!
19 !! REFERENCE
20 !! ---------
21 !!
22 !!
23 !! AUTHOR
24 !! ------
25 !! P. Le Moigne
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! Original 04/2006
30 !! Modified 08/2008 (B. Decharme) LWU diag
31 !!------------------------------------------------------------------
32 !
33 USE modd_csts, ONLY : xstefan
34 !
35 !
36 !
37 USE yomhook ,ONLY : lhook, dr_hook
38 USE parkind1 ,ONLY : jprb
39 !
40 IMPLICIT NONE
41 !
42 !* 0.1 declarations of arguments
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) :: pdir_alb ! direct albedo for each spectral band (-)
50 REAL, DIMENSION(:,:),INTENT(IN) :: psca_alb ! diffuse albedo for each spectral band (-)
51 REAL, DIMENSION(:), INTENT(IN) :: prn ! Surface net radiation
52 !
53 REAL, DIMENSION(:,:), INTENT(OUT):: pswbd ! incoming short wave radiation by spectral band (W/m2)
54 REAL, DIMENSION(:,:), INTENT(OUT):: pswbu ! upward short wave radiation by spectral band (W/m2)
55 REAL, DIMENSION(:), INTENT(OUT) :: pswd ! total incoming short wave radiation (W/m2)
56 REAL, DIMENSION(:), INTENT(OUT) :: pswu ! total upward short wave radiation (W/m2)
57 REAL, DIMENSION(:), INTENT(OUT) :: plwd ! Downward long wave radiation (W/m2)
58 REAL, DIMENSION(:), INTENT(OUT) :: plwu ! upward long wave radiation (W/m2)
59 !
60 !
61 !* 0.2 declarations of local variables
62 !
63 INTEGER :: iswb ! number of SW bands
64 INTEGER :: jswb ! loop counter on number of SW bands
65 REAL(KIND=JPRB) :: zhook_handle
66 !-------------------------------------------------------------------------------------
67 !
68 !
69 IF (lhook) CALL dr_hook('DIAG_SURF_BUDGET_ISBA',0,zhook_handle)
70 iswb = SIZE(pdir_sw,2)
71 !
72 !* total incoming and outgoing SW
73 !
74 DO jswb=1,iswb
75  pswbd(:,jswb) = pdir_sw(:,jswb) + psca_sw(:,jswb)
76  pswbu(:,jswb) = pdir_sw(:,jswb) * pdir_alb(:,jswb) + psca_sw(:,jswb) * psca_alb(:,jswb)
77 ENDDO
78 !
79 pswd(:) = 0.
80 pswu(:) = 0.
81 DO jswb=1,iswb
82  pswd(:)=pswd(:)+pswbd(:,jswb)
83  pswu(:)=pswu(:)+pswbu(:,jswb)
84 ENDDO
85 !
86 !*incoming outgoing LW
87 !
88 !Wrong old diag : LWU=EMIS*STEFAN*Ts**4 + (1.-EMIS)*LW
89 !Due to e_budget.f90 linearization, LWU can not be calculated using actual Ts
90 !
91 plwd(:)=plw(:)
92 plwu(:)=pswd(:)-pswu(:)+plwd(:)-prn(:)
93 IF (lhook) CALL dr_hook('DIAG_SURF_BUDGET_ISBA',1,zhook_handle)
94 !
95 !-------------------------------------------------------------------------------------
96 !
97 END SUBROUTINE diag_surf_budget_isba
subroutine diag_surf_budget_isba(PDIR_SW, PSCA_SW, PDIR_ALB, PSCA_ALB, PLW, PRN, PSWD, PSWU, PSWBD, PSWBU, PLWD, PLWU)