SURFEX v8.1
General documentation of Surfex
trip_diag_cpl_esm.F90
Go to the documentation of this file.
1 SUBROUTINE trip_diag_cpl_esm (TP, TPG, &
2  PTSTEP_RUN,PDISCHARGE,PCALVING,PWTD,PFWTD)
3 ! #################################################################
4 !
5 !!**** *TRIP_DIAG_CPL_ESM*
6 !!
7 !! PURPOSE
8 !! -------
9 !
10 ! TRIP cpl diag compuation
11 !
12 !!
13 !! AUTHOR
14 !! ------
15 !! B. Decharme
16 !!
17 !! MODIFICATIONS
18 !! -------------
19 !! Original 12/12/13
20 !! B. Decharme 10/2016 bug surface/groundwater coupling
21 !-------------------------------------------------------------------------------
22 !
23 !* 0. DECLARATIONS
24 ! ------------
25 !
26 !
27 USE modd_trip, ONLY : trip_t
28 USE modd_trip_grid, ONLY : trip_grid_t
29 !
30 USE modd_trip_par, ONLY : xundef, xrholw
31 !
34 !
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 !
44 TYPE(trip_t), INTENT(INOUT) :: TP
45 TYPE(trip_grid_t), INTENT(INOUT) :: TPG
46 !
47 REAL, INTENT(IN) :: PTSTEP_RUN !Run timestep [s]
48 REAL, DIMENSION(:,:), INTENT(IN) :: PDISCHARGE !Cumulated river discharges [kg]
49 REAL, DIMENSION(:,:), INTENT(IN) :: PCALVING !Input claving flux from glacier [kg/s]
50 REAL, DIMENSION(:,:), INTENT(IN) :: PWTD !Water table depth [m]
51 REAL, DIMENSION(:,:), INTENT(IN) :: PFWTD !Fraction of Water table to rise
52 !
53 !* 0.2 declarations of local variables
54 !
55 REAL(KIND=JPRB) :: ZHOOK_HANDLE
56 !
57 !-------------------------------------------------------------------------------
58 !
59 IF (lhook) CALL dr_hook('TRIP_DIAG_CPL_ESM',0,zhook_handle)
60 !
61 !* 1. Actualisation of sea coupling diagnostic:
62 ! ------------------------------------------
63 !
64 !
65 ! River discharges to ocean [kg/m2]
66 !
67 IF(lcpl_sea)THEN
68  WHERE(tpg%NGRCN(:,:)==9.OR.tpg%NGRCN(:,:)==12)
69  tp%XCPL_RIVDIS(:,:) = tp%XCPL_RIVDIS(:,:) + pdischarge(:,:) / tpg%XAREA(:,:)
70  ENDWHERE
71 ENDIF
72 !
73 ! Calving flux over greenland and antarctica [kg/m2]
74 !
75 IF(lcpl_calvsea)THEN
76  WHERE(tpg%GMASK_GRE(:,:))
77  tp%XCPL_CALVGRE(:,:) = tp%XCPL_CALVGRE(:,:) + pcalving(:,:) * ptstep_run / tpg%XAREA(:,:)
78  ENDWHERE
79  WHERE(tpg%GMASK_ANT(:,:))
80  tp%XCPL_CALVANT(:,:) = tp%XCPL_CALVANT(:,:) + pcalving(:,:) * ptstep_run / tpg%XAREA(:,:)
81  ENDWHERE
82 ENDIF
83 !
84 !-------------------------------------------------------------------------------
85 !
86 !* 2. Actualisation of land coupling diagnostic:
87 ! -------------------------------------------
88 !
89 IF(lcpl_land)THEN
90 !
91 ! Water table depth (negative above the surface) and fraction of water table to rise
92 !
93  IF(lcpl_gw)THEN
94  WHERE(tpg%GMASK_GW(:,:))
95  tp%XCPL_WTD (:,:) = pwtd(:,:)
96  tp%XCPL_FWTD(:,:) = pfwtd(:,:)
97  ELSEWHERE(tpg%GMASK(:,:))
98  tp%XCPL_WTD (:,:) = xundef
99  tp%XCPL_FWTD(:,:) = 0.0
100  ENDWHERE
101  ENDIF
102 !
103 ! Flood fraction [-] and potential infiltration [kg/m2]
104 !
105  IF(lcpl_flood)THEN
106  tp%XCPL_FFLOOD (:,:) = tp%XFFLOOD (:,:)
107  tp%XCPL_PIFLOOD(:,:) = tp%XFLOOD_STO (:,:) / tpg%XAREA(:,:)
108  ENDIF
109 !
110 ENDIF
111 !
112 IF (lhook) CALL dr_hook('TRIP_DIAG_CPL_ESM',1,zhook_handle)
113 !
114 !-------------------------------------------------------------------------------
115 END SUBROUTINE trip_diag_cpl_esm
subroutine trip_diag_cpl_esm(TP, TPG, PTSTEP_RUN, PDISCHARGE, PCALVING, PWTD, PFWTD)
real, save xrholw
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
real, save xundef