SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
diag_surf_budgetc_sea.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_budgetc_sea (DGS, &
7  ptstep, prn, ph, ple, ple_ice, pgflux,&
8  pswd, pswu, plwd, plwu, pfmu, pfmv, &
9  pevap, psubl, ohandle_sic, &
10  prn_ice, ph_ice, pgflux_ice, &
11  pswu_ice, plwu_ice, pfmu_ice, pfmv_ice)
12 ! ########################################################################
13 !
14 !!**** *DIAG_SURF_BUDGETC_SEA * - Computes cumulated diagnostics over sea
15 !!
16 !! PURPOSE
17 !! -------
18 !
19 !!** METHOD
20 !! ------
21 !!
22 !! REFERENCE
23 !! ---------
24 !!
25 !!
26 !! AUTHOR
27 !! ------
28 !! B. Decharme
29 !!
30 !! MODIFICATIONS
31 !! -------------
32 !! Original 08/2009
33 !! S.Senesi 01/2014 Add fluxes on seaice
34 !!------------------------------------------------------------------
35 !
36 !
37 !
38 !
40 !
41 USE yomhook ,ONLY : lhook, dr_hook
42 USE parkind1 ,ONLY : jprb
43 !
44 IMPLICIT NONE
45 !
46 !* 0.1 declarations of arguments
47 !
48 !
49 TYPE(diag_seaflux_t), INTENT(INOUT) :: dgs
50 !
51 REAL, INTENT(IN) :: ptstep
52 REAL, DIMENSION(:), INTENT(IN) :: prn ! net radiation (W/m2)
53 REAL, DIMENSION(:), INTENT(IN) :: ph ! sensible heat flux (W/m2)
54 REAL, DIMENSION(:), INTENT(IN) :: ple ! total latent heat flux (W/m2)
55 REAL, DIMENSION(:), INTENT(IN) :: ple_ice ! sublimation latent heat flux (W/m2)
56 REAL, DIMENSION(:), INTENT(IN) :: pgflux ! storage flux (W/m2)
57 REAL, DIMENSION(:), INTENT(IN) :: pevap ! total evaporation (kg/m2/s)
58 REAL, DIMENSION(:), INTENT(IN) :: psubl ! sublimation (kg/m2/s)
59 REAL, DIMENSION(:), INTENT(IN) :: pswd ! total incoming short wave radiation (W/m2)
60 REAL, DIMENSION(:), INTENT(IN) :: pswu ! total upward short wave radiation (W/m2)
61 REAL, DIMENSION(:), INTENT(IN) :: plwd ! Downward long wave radiation (W/m2)
62 REAL, DIMENSION(:), INTENT(IN) :: plwu ! upward long wave radiation (W/m2)
63 REAL, DIMENSION(:), INTENT(IN) :: pfmu ! zonal wind stress
64 REAL, DIMENSION(:), INTENT(IN) :: pfmv ! meridian wind stress
65 !
66 LOGICAL, INTENT(IN) :: ohandle_sic ! Do we weight seaice and open sea fluxes
67 !
68 REAL, DIMENSION(:), INTENT(IN) :: prn_ice ! net radiation (W/m2)
69 REAL, DIMENSION(:), INTENT(IN) :: ph_ice ! sensible heat flux (W/m2)
70 REAL, DIMENSION(:), INTENT(IN) :: pgflux_ice!storage flux (W/m2)
71 REAL, DIMENSION(:), INTENT(IN) :: pswu_ice ! total upward short wave radiation (W/m2)
72 REAL, DIMENSION(:), INTENT(IN) :: plwu_ice ! upward long wave radiation (W/m2)
73 REAL, DIMENSION(:), INTENT(IN) :: pfmu_ice ! zonal wind stress
74 REAL, DIMENSION(:), INTENT(IN) :: pfmv_ice ! meridian wind stress
75 !
76 !
77 !* 0.2 declarations of local variables
78 !
79 REAL(KIND=JPRB) :: zhook_handle
80 !
81 !-------------------------------------------------------------------------------------
82 !
83 IF (lhook) CALL dr_hook('DIAG_SURF_BUDGETC_SEA',0,zhook_handle)
84 !
85 !* total incoming and outgoing SW
86 !
87 dgs%XSWDC(:) = dgs%XSWDC(:) + pswd(:) * ptstep
88 dgs%XSWUC(:) = dgs%XSWUC(:) + pswu(:) * ptstep
89 !
90 !*incoming outgoing LW
91 !
92 dgs%XLWDC(:) = dgs%XLWDC(:) + plwd(:) * ptstep
93 dgs%XLWUC(:) = dgs%XLWUC(:) + plwu(:) * ptstep
94 !
95 !* net radiation
96 !
97 dgs%XRNC(:) = dgs%XRNC(:) + prn(:) * ptstep
98 !
99 !* sensible heat flux
100 !
101 dgs%XHC(:) = dgs%XHC(:) + ph(:) * ptstep
102 !
103 !* latent heat flux (J/m2)
104 !
105 dgs%XLEC (:) = dgs%XLEC (:) + ple(:) * ptstep
106 dgs%XLEC_ICE(:) = dgs%XLEC_ICE(:) + ple_ice(:) * ptstep
107 !
108 !* evaporation and sublimation (kg/m2)
109 !
110 dgs%XEVAPC(:) = dgs%XEVAPC(:) + pevap(:) * ptstep
111 dgs%XSUBLC(:) = dgs%XSUBLC(:) + psubl(:) * ptstep
112 !
113 !* storage flux
114 !
115 dgs%XGFLUXC(:) = dgs%XGFLUXC(:) + pgflux(:) * ptstep
116 !
117 !* wind stress
118 !
119 dgs%XFMUC(:) = dgs%XFMUC(:) + pfmu(:) * ptstep
120 dgs%XFMVC(:) = dgs%XFMVC(:) + pfmv(:) * ptstep
121 !
122 IF (ohandle_sic) THEN
123 !
124 !* total incoming and outgoing SW
125 !
126  dgs%XSWUC_ICE(:) = dgs%XSWUC_ICE(:) + pswu_ice(:) * ptstep
127 !
128 !*incoming outgoing LW
129 !
130  dgs%XLWUC_ICE(:) = dgs%XLWUC_ICE(:) + plwu_ice(:) * ptstep
131 !
132 !* net radiation
133 !
134  dgs%XRNC_ICE(:) = dgs%XRNC_ICE(:) + prn_ice(:) * ptstep
135 !
136 !* sensible heat flux
137 !
138  dgs%XHC_ICE(:) = dgs%XHC_ICE(:) + ph_ice(:) * ptstep
139 !
140 !* storage flux
141 !
142  dgs%XGFLUXC_ICE(:) = dgs%XGFLUXC_ICE(:) + pgflux_ice(:) * ptstep
143 !
144 !* wind stress
145 !
146  dgs%XFMUC_ICE(:) = dgs%XFMUC_ICE(:) + pfmu_ice(:) * ptstep
147  dgs%XFMVC_ICE(:) = dgs%XFMVC_ICE(:) + pfmv_ice(:) * ptstep
148 !
149 ENDIF
150 !
151 IF (lhook) CALL dr_hook('DIAG_SURF_BUDGETC_SEA',1,zhook_handle)
152 !
153 !-------------------------------------------------------------------------------------
154 !
155 END SUBROUTINE diag_surf_budgetc_sea
subroutine diag_surf_budgetc_sea(DGS, PTSTEP, PRN, PH, PLE, PLE_ICE, PGFLUX, PSWD, PSWU, PLWD, PLWU, PFMU, PFMV, PEVAP, PSUBL, OHANDLE_SIC, PRN_ICE, PH_ICE, PGFLUX_ICE, PSWU_ICE, PLWU_ICE, PFMU_ICE, PFMV_ICE)