SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
diag_surf_budget_water.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_water (PTT, PTS, PRHOA, PSFTH, PSFTQ, &
7  pdir_sw, psca_sw, plw, &
8  pdir_alb, psca_alb, pemis, ptrad, &
9  psfzon, psfmer, &
10  prn, ph, ple, plei, pgflux, &
11  pswd, pswu, pswbd, pswbu, plwd, plwu, &
12  pfmu, pfmv, pevap, psubl )
13 ! ###############################################################################
14 !
15 !!**** *DIAG_SURF_BUDGET_WATER * - Computes diagnostics over water
16 !!
17 !! PURPOSE
18 !! -------
19 !
20 !!** METHOD
21 !! ------
22 !!
23 !! REFERENCE
24 !! ---------
25 !!
26 !!
27 !! AUTHOR
28 !! ------
29 !! V. Masson
30 !!
31 !! MODIFICATIONS
32 !! -------------
33 !! Original 01/2004
34 ! B. decharme 04/2013 : Add EVAP and SUBL diag
35 ! Ts instead of Tsrad
36 !!------------------------------------------------------------------
37 !
38 
39 !
40 !
41 USE modd_csts, ONLY : xstefan, xlstt, xlvtt, xcpd
42 !
43 !
44 !
45 USE yomhook ,ONLY : lhook, dr_hook
46 USE parkind1 ,ONLY : jprb
47 !
48 IMPLICIT NONE
49 !
50 !* 0.1 declarations of arguments
51 !
52 REAL, INTENT(IN) :: ptt ! freezing temperature of water surface
53 REAL, DIMENSION(:), INTENT(IN) :: pts ! surface temperature (K)
54 REAL, DIMENSION(:), INTENT(IN) :: prhoa ! air density
55 REAL, DIMENSION(:), INTENT(IN) :: psfth ! heat flux
56 REAL, DIMENSION(:), INTENT(IN) :: psftq ! water flux
57 REAL, DIMENSION(:,:),INTENT(IN):: pdir_sw ! direct solar radiation (on horizontal surf.)
58 ! ! (W/m2)
59 REAL, DIMENSION(:,:),INTENT(IN):: psca_sw ! diffuse solar radiation (on horizontal surf.)
60 ! ! (W/m2)
61 REAL, DIMENSION(:), INTENT(IN) :: plw ! longwave radiation (on horizontal surf.)
62 REAL, DIMENSION(:), INTENT(IN) :: ptrad ! radiative temperature (K)
63 REAL, DIMENSION(:,:),INTENT(IN):: pdir_alb ! direct albedo for each spectral band (-)
64 REAL, DIMENSION(:,:),INTENT(IN):: psca_alb ! diffuse albedo for each spectral band (-)
65 REAL, DIMENSION(:), INTENT(IN) :: pemis ! emissivity (-)
66 REAL, DIMENSION(:), INTENT(IN) :: psfzon ! zonal friction
67 REAL, DIMENSION(:), INTENT(IN) :: psfmer ! meridional friction
68 !
69 REAL, DIMENSION(:), INTENT(OUT):: prn ! net radiation (W/m2)
70 REAL, DIMENSION(:), INTENT(OUT):: ph ! sensible heat flux (W/m2)
71 REAL, DIMENSION(:), INTENT(OUT):: ple ! total latent heat flux (W/m2)
72 REAL, DIMENSION(:), INTENT(OUT):: plei ! sublimation latent heat flux (W/m2)
73 REAL, DIMENSION(:), INTENT(OUT):: pgflux ! storage flux (W/m2)
74 REAL, DIMENSION(:), INTENT(OUT):: pevap ! total evaporation (kg/m2/s)
75 REAL, DIMENSION(:), INTENT(OUT):: psubl ! sublimation (kg/m2/s)
76 !
77 REAL, DIMENSION(:,:), INTENT(OUT):: pswbd ! incoming short wave radiation by spectral band (W/m2)
78 REAL, DIMENSION(:,:), INTENT(OUT):: pswbu ! upward short wave radiation by spectral band (W/m2)
79 REAL, DIMENSION(:), INTENT(OUT):: pswd ! total incoming short wave radiation (W/m2)
80 REAL, DIMENSION(:), INTENT(OUT):: pswu ! total upward short wave radiation (W/m2)
81 REAL, DIMENSION(:), INTENT(OUT):: plwd ! Downward long wave radiation (W/m2)
82 REAL, DIMENSION(:), INTENT(OUT):: plwu ! upward long wave radiation (W/m2)
83 !
84 REAL, DIMENSION(:), INTENT(OUT):: pfmu ! zonal friction
85 REAL, DIMENSION(:), INTENT(OUT):: pfmv ! meridional friction
86 !
87 !* 0.2 declarations of local variables
88 !
89 INTEGER :: iswb ! number of SW bands
90 INTEGER :: jswb ! loop counter on number of SW bands
91 REAL(KIND=JPRB) :: zhook_handle
92 !-------------------------------------------------------------------------------------
93 !
94 !
95 IF (lhook) CALL dr_hook('DIAG_SURF_BUDGET_WATER',0,zhook_handle)
96 iswb = SIZE(pdir_sw,2)
97 !
98 !* total incoming and outgoing SW
99 !
100 DO jswb=1,iswb
101  pswbd(:,jswb) = pdir_sw(:,jswb) + psca_sw(:,jswb)
102  pswbu(:,jswb) = pdir_sw(:,jswb) * pdir_alb(:,jswb) + psca_sw(:,jswb) * psca_alb(:,jswb)
103 ENDDO
104 !
105 pswd(:) = 0.
106 pswu(:) = 0.
107 DO jswb=1,iswb
108  pswd(:)=pswd(:)+pswbd(:,jswb)
109  pswu(:)=pswu(:)+pswbu(:,jswb)
110 ENDDO
111 !
112 !*incoming outgoing LW
113 !
114 plwd(:)=plw(:)
115 plwu(:)=pemis(:)*xstefan*ptrad(:)**4 + (1.-pemis(:))*plw(:)
116 !
117 !* net radiation
118 !
119 prn = pswd(:) - pswu(:) + plwd(:) - plwu(:)
120 !
121 !* sensible heat flux
122 !
123 ph = psfth(:)
124 !
125 !* latent heat flux
126 !
127 WHERE (pts<ptt )
128  ple = psftq * xlstt
129  plei = psftq * xlstt
130  pevap = psftq
131  psubl = psftq
132 ELSEWHERE
133  ple = psftq * xlvtt
134  plei = 0.0
135  pevap = psftq
136  psubl = 0.0
137 END WHERE
138 !
139 !* storage flux
140 !
141 pgflux = prn - ph - ple
142 !
143 !* wind stress
144 !
145 pfmu = psfzon
146 !
147 pfmv = psfmer
148 IF (lhook) CALL dr_hook('DIAG_SURF_BUDGET_WATER',1,zhook_handle)
149 !
150 !-------------------------------------------------------------------------------------
151 !
152 END SUBROUTINE diag_surf_budget_water
subroutine diag_surf_budget_water(PTT, PTS, PRHOA, PSFTH, PSFTQ, PDIR_SW, PSCA_SW, PLW, PDIR_ALB, PSCA_ALB, PEMIS, PTRAD, PSFZON, PSFMER, PRN, PH, PLE, PLEI, PGFLUX, PSWD, PSWU, PSWBD, PSWBU, PLWD, PLWU, PFMU, PFMV, PEVAP, PSUBL)