SURFEX v8.1
General documentation of Surfex
topd_to_isba_slope.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 topd_to_isba_slope (PSSO_SLOPE, KI)
8 ! ####################
9 !
10 !!**** *TOPD_TO_ISBA*
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 !
16 !
17 !
18 !!** METHOD
19 !! ------
20 !
21 !! EXTERNAL
22 !! --------
23 !!
24 !! none
25 !!
26 !! IMPLICIT ARGUMENTS
27 !! ------------------
28 !!
29 !!
30 !!
31 !!
32 !!
33 !! REFERENCE
34 !! ---------
35 !!
36 !!
37 !!
38 !! AUTHOR
39 !! ------
40 !!
41 !! B. Vincendon * Meteo-France *
42 !!
43 !! MODIFICATIONS
44 !! -------------
45 !!
46 !! Original 12/11/2012
47 !-------------------------------------------------------------------------------
48 !
49 !* 0. DECLARATIONS
50 ! ------------
51 !
52 !
53 USE modd_topodyn, ONLY : nncat, nnmc, xtanb
55 USE modd_surf_par, ONLY : nundef
56 !
57 USE yomhook ,ONLY : lhook, dr_hook
58 USE parkind1 ,ONLY : jprb
59 !
60 IMPLICIT NONE
61 !
62 !* 0.1 declarations of arguments
63 !
64 !
65 REAL, DIMENSION(:), INTENT(INOUT) :: PSSO_SLOPE
66 !
67 INTEGER, INTENT(IN) :: KI ! Grid dimensions
68 !
69 !* 0.2 declarations of local variables
70 !
71 !
72 INTEGER :: JCAT,JPIX,JJ ! loop control
73 REAL, DIMENSION(KI) :: ZCOUNT ! TOPO pixel number in an ISBA pixel
74  ! on the full grid
75 REAL, DIMENSION(KI) :: ZSSO_SLOPE
76 REAL(KIND=JPRB) :: ZHOOK_HANDLE
77 !-------------------------------------------------------------------------------
78 !
79 IF (lhook) CALL dr_hook('TOPD_TO_ISBA_SLOPE',0,zhook_handle)
80 !
81 !* 1.0 Compute Mean slope over each ISBA_MESH
82 ! ----------------------------------------------------------------------
83 !
84 !write(*,*) 'pente avt topmodel',MINVAL(XSSO_SLOPE),MAXVAL(XSSO_SLOPE),SUM(XSSO_SLOPE,MASK=XSSO_SLOPE/=XUNDEF)
85 !
86 zsso_slope = psso_slope
87 !
88 zcount(:) = REAL(nnpix(:))
89 
90 WHERE (zcount /= 0.0)
91  zsso_slope = 0.
92 ENDWHERE
93 !
94 DO jcat=1,nncat
95  DO jpix=1,nnmc(jcat)
96  IF (nmaskt(jcat,jpix) /= nundef) THEN
97  zsso_slope(nmaskt(jcat,jpix)) = zsso_slope(nmaskt(jcat,jpix)) + xtanb(jcat,jpix)
98  ENDIF
99  ENDDO
100 ENDDO
101 !
102 WHERE (zcount /= 0.0)
103  zsso_slope = zsso_slope / zcount
104 ENDWHERE
105 !
106 psso_slope = zsso_slope
107 !
108 !write(*,*) 'pente apres modification', &
109 ! MINVAL(XSSO_SLOPE),MAXVAL(XSSO_SLOPE),COUNT(ZCOUNT/=0.0),SUM(XSSO_SLOPE,MASK=XSSO_SLOPE/=XUNDEF)
110 !
111 IF (lhook) CALL dr_hook('TOPD_TO_ISBA_SLOPE',1,zhook_handle)
112 !
113 END SUBROUTINE topd_to_isba_slope
integer, dimension(:), allocatable nnpix
real, dimension(:,:), allocatable xtanb
integer, parameter jprb
Definition: parkind1.F90:32
integer, parameter nundef
logical lhook
Definition: yomhook.F90:15
subroutine topd_to_isba_slope(PSSO_SLOPE, KI)
integer, dimension(:,:), allocatable nmaskt
integer, dimension(:), allocatable nnmc