SURFEX v8.1
General documentation of Surfex
diag_isba_to_rout.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 ! ############################
7  SUBROUTINE diag_isba_to_rout (PMESH_SIZE, &
8  PVARC,PVARCP,PVARROUT)
9 ! ############################
10 !
11 !!**** *DIAG_ISBA_TO_ROUT*
12 !!
13 !! PURPOSE
14 !! -------
15 !
16 !!** METHOD
17 !! ------
18 !
19 !! EXTERNAL
20 !! --------
21 !!
22 !! none
23 !!
24 !! IMPLICIT ARGUMENTS
25 !! ------------------
26 !!
27 !!
28 !!
29 !!
30 !!
31 !! REFERENCE
32 !! ---------
33 !!
34 !!
35 !!
36 !! AUTHOR
37 !! ------
38 !!
39 !! K. Chancibault * Meteo-France *
40 !!
41 !! MODIFICATIONS
42 !! -------------
43 !!
44 !! Original 10/11/2006
45 !-------------------------------------------------------------------------------
46 !
47 !* 0. DECLARATIONS
48 ! ------------
49 !
50 !
52 !
53 USE modd_surf_par, ONLY: xundef
54 USE modd_csts, ONLY: xrholw
55 USE modd_topodyn, ONLY : xtopd_step
56 !
57 USE modi_abor1_sfx
58 !
59 USE yomhook ,ONLY : lhook, dr_hook
60 USE parkind1 ,ONLY : jprb
61 !
62 IMPLICIT NONE
63 !
64 !* 0.1 declarations of arguments
65 !
66 !
67 REAL, DIMENSION(:), INTENT(IN) :: PMESH_SIZE
68 !
69 REAL,DIMENSION(:),INTENT(IN) :: PVARC ! Current time step cumulated diagnostic from SurfEx
70 REAL,DIMENSION(:),INTENT(IN) :: PVARCP ! Previous time step cumulated diagnostic from SurfEx
71 REAL,DIMENSION(:),INTENT(OUT) :: PVARROUT ! Not cumulated diagnostic (m3/s)
72 !
73 !* 0.2 declarations of local variables
74 !
75 REAL(KIND=JPRB) :: ZHOOK_HANDLE
76 !-------------------------------------------------------------------------------
77 IF (lhook) CALL dr_hook('DIAG_ISBA_TO_ROUT',0,zhook_handle)
78 !
79 !* 0. Initialization:
80 ! ---------------
81 pvarrout=xundef
82 !
83 IF ( SIZE(pvarc,1)==SIZE(pvarcp,1) ) THEN
84  !
85  WHERE ( pvarc/=xundef )
86  pvarrout = pvarc - pvarcp
87  pvarrout = pvarrout / xtopd_step
88  pvarrout = pvarrout * pmesh_size / xrholw
89  ENDWHERE
90  !
91 ELSE
92  !
93  WRITE(*,*) 'Pb with diagnostic to rout'
94  CALL abor1_sfx("DIAG_ISBA_TO_ROUT: PB WITH DIAGNOSTIC TO ROUT ")
95  !
96 ENDIF
97 !
98 WHERE (pvarrout<0.) pvarrout = 0.
99 !
100 IF (lhook) CALL dr_hook('DIAG_ISBA_TO_ROUT',1,zhook_handle)
101 !
102 END SUBROUTINE diag_isba_to_rout
subroutine diag_isba_to_rout(PMESH_SIZE, PVARC, PVARCP, PVARROUT)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
real, save xrholw
Definition: modd_csts.F90:64