SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
diag_surf_budget_flake.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_flake (PRHOA, PSFTH, &
7  pdir_sw, psca_sw, plw, &
8  pdir_alb, psca_alb, plwup, &
9  psfzon, psfmer, ple, &
10  prn, ph, pgflux, &
11  pswd, pswu, pswbd, pswbu, plwd, plwu, &
12  pfmu, pfmv )
13 ! ###############################################################################
14 !
15 !!**** *DIAG_SURF_BUDGET_FLAKE * - Computes diagnostics over lake
16 !!
17 !! PURPOSE
18 !! -------
19 !
20 !!** METHOD
21 !! ------
22 !!
23 !! REFERENCE
24 !! ---------
25 !!
26 !!
27 !! AUTHOR
28 !! ------
29 !! B. Decharme
30 !!
31 !! MODIFICATIONS
32 !! -------------
33 !! Original 04/2013
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) :: prhoa ! air density
45 REAL, DIMENSION(:), INTENT(IN) :: psfth ! heat flux
46 REAL, DIMENSION(:,:),INTENT(IN):: pdir_sw ! direct solar radiation (on horizontal surf.)
47 ! ! (W/m2)
48 REAL, DIMENSION(:,:),INTENT(IN):: psca_sw ! diffuse solar radiation (on horizontal surf.)
49 ! ! (W/m2)
50 REAL, DIMENSION(:), INTENT(IN) :: plw ! longwave radiation (on horizontal surf.)
51 REAL, DIMENSION(:), INTENT(IN) :: plwup ! upward longwave radiation (W/m2)
52 REAL, DIMENSION(:,:),INTENT(IN):: pdir_alb ! direct albedo for each spectral band (-)
53 REAL, DIMENSION(:,:),INTENT(IN):: psca_alb ! diffuse albedo for each spectral band (-)
54 REAL, DIMENSION(:), INTENT(IN) :: psfzon ! zonal friction
55 REAL, DIMENSION(:), INTENT(IN) :: psfmer ! meridional friction
56 !
57 REAL, DIMENSION(:), INTENT(IN) :: ple ! total latent heat flux (W/m2)
58 !
59 REAL, DIMENSION(:), INTENT(OUT):: prn ! net radiation (W/m2)
60 REAL, DIMENSION(:), INTENT(OUT):: ph ! sensible heat flux (W/m2)
61 REAL, DIMENSION(:), INTENT(OUT):: pgflux ! storage flux (W/m2)
62 !
63 REAL, DIMENSION(:,:), INTENT(OUT):: pswbd ! incoming short wave radiation by spectral band (W/m2)
64 REAL, DIMENSION(:,:), INTENT(OUT):: pswbu ! upward short wave radiation by spectral band (W/m2)
65 REAL, DIMENSION(:), INTENT(OUT):: pswd ! total incoming short wave radiation (W/m2)
66 REAL, DIMENSION(:), INTENT(OUT):: pswu ! total upward short wave radiation (W/m2)
67 REAL, DIMENSION(:), INTENT(OUT):: plwd ! Downward long wave radiation (W/m2)
68 REAL, DIMENSION(:), INTENT(OUT):: plwu ! upward long wave radiation (W/m2)
69 !
70 REAL, DIMENSION(:), INTENT(OUT):: pfmu ! zonal friction
71 REAL, DIMENSION(:), INTENT(OUT):: pfmv ! meridional friction
72 !
73 !* 0.2 declarations of local variables
74 !
75 INTEGER :: iswb ! number of SW bands
76 INTEGER :: jswb ! loop counter on number of SW bands
77 REAL(KIND=JPRB) :: zhook_handle
78 !-------------------------------------------------------------------------------------
79 !
80 !
81 IF (lhook) CALL dr_hook('DIAG_SURF_BUDGET_FLAKE',0,zhook_handle)
82 iswb = SIZE(pdir_sw,2)
83 !
84 !* total incoming and outgoing SW
85 !
86 DO jswb=1,iswb
87  pswbd(:,jswb) = pdir_sw(:,jswb) + psca_sw(:,jswb)
88  pswbu(:,jswb) = pdir_sw(:,jswb) * pdir_alb(:,jswb) + psca_sw(:,jswb) * psca_alb(:,jswb)
89 ENDDO
90 !
91 pswd(:) = 0.
92 pswu(:) = 0.
93 DO jswb=1,iswb
94  pswd(:)=pswd(:)+pswbd(:,jswb)
95  pswu(:)=pswu(:)+pswbu(:,jswb)
96 ENDDO
97 !
98 !*incoming outgoing LW
99 !
100 plwd(:)=plw(:)
101 plwu(:)=plwup(:)
102 !
103 !* net radiation
104 !
105 prn = pswd(:) - pswu(:) + plwd(:) - plwu(:)
106 !
107 !* sensible heat flux
108 !
109 ph = psfth(:)
110 !
111 !* storage flux
112 !
113 pgflux = prn - ph - ple
114 !
115 !* wind stress
116 !
117 pfmu = psfzon
118 !
119 pfmv = psfmer
120 IF (lhook) CALL dr_hook('DIAG_SURF_BUDGET_FLAKE',1,zhook_handle)
121 !
122 !-------------------------------------------------------------------------------------
123 !
124 END SUBROUTINE diag_surf_budget_flake
subroutine diag_surf_budget_flake(PRHOA, PSFTH, PDIR_SW, PSCA_SW, PLW, PDIR_ALB, PSCA_ALB, PLWUP, PSFZON, PSFMER, PLE, PRN, PH, PGFLUX, PSWD, PSWU, PSWBD, PSWBU, PLWD, PLWU, PFMU, PFMV)