SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
make_mask_isba_to_topd.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 make_mask_isba_to_topd(KI)
8 ! #######################
9 !
10 !!**** *MAKE_MASK_ISBA_TO_TOPD*
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 ! Create a mask for each Surfex mesh and each catchment.
16 !
17 !
18 !!** METHOD
19 !! ------
20 !
21 !! EXTERNAL
22 !! --------
23 !!
24 !! none
25 !!
26 !! IMPLICIT ARGUMENTS
27 !! ------------------
28 !!
29 !! REFERENCE
30 !! ---------
31 
32 !! AUTHOR
33 !! ------
34 !!
35 !! K. Chancibault * CNRM *
36 !!
37 !! MODIFICATIONS
38 !! -------------
39 !!
40 !! Original 16/03/2005
41 !! 11/2011 : Loops simplified (Vincendon)
42 !-------------------------------------------------------------------------------
43 !
44 !* 0. DECLARATIONS
45 ! ------------
46 !
47 USE modd_topodyn, ONLY : nncat, nnmc
48 USE modd_coupling_topd, ONLY : nmaskt, nmaski, nnpix
49 USE modd_surf_par, ONLY : nundef
50 !
51 USE yomhook ,ONLY : lhook, dr_hook
52 USE parkind1 ,ONLY : jprb
53 !
54 IMPLICIT NONE
55 !
56 !* 0.1 declarations of arguments
57 !
58 INTEGER, INTENT(IN) :: ki ! Grid dimensions
59 !
60 !* 0.2 declarations of local variables
61 !
62 INTEGER, DIMENSION(KI) :: inbpix_in_mesh ! number of pixel in each ISBA mesh
63 INTEGER :: jcat, jpix, inumpix
64 REAL(KIND=JPRB) :: zhook_handle
65 !-------------------------------------------------------------------------------
66 IF (lhook) CALL dr_hook('MAKE_MASK_ISBA_TO_TOPD',0,zhook_handle)
67 !
68 inumpix=maxval(nnpix)
69 !
70 ALLOCATE(nmaski(ki,nncat,inumpix))
71 nmaski(:,:,:) = nundef
72 !
73 inbpix_in_mesh(:) = 0
74 !
75 DO jcat = 1,nncat
76  !
77  DO jpix = 1,nnmc(jcat)
78  !si le point du bassin versant est dans une maille isba
79  IF ((nmaskt(jcat,jpix)/=0).AND.(nmaskt(jcat,jpix)/=nundef)) THEN
80  !indice du point du bassin versant dans la maille isba
81  inbpix_in_mesh(nmaskt(jcat,jpix)) = inbpix_in_mesh(nmaskt(jcat,jpix)) + 1
82  ! nmaski associe à la maille isba, au bassin versant et au numéro du point
83  ! du bassin versant dans la maille isba, l'indice du point dans le bassin
84  ! versant
85  nmaski(nmaskt(jcat,jpix),jcat,inbpix_in_mesh(nmaskt(jcat,jpix))) = jpix
86  ENDIF
87  !
88  ENDDO
89  !
90 ENDDO
91 ! write(*,*) 'NMASKT min et max',MINVAL(NMASKT(1,:)),MAXVAL(NMASKT(1,:))
92 ! write(*,*) 'NMASKT min et max',MINVAL(NMASKT(2,:)),MAXVAL(NMASKT(2,:))
93 ! write(*,*) 'NMASKT min et max',MINVAL(NMASKT(3,:)),MAXVAL(NMASKT(3,:))
94 ! write(*,*) 'NMASKT min et max',MINVAL(NMASKT(4,:)),MAXVAL(NMASKT(4,:))
95 ! write(*,*) 'NMASKI 3132 min et max',MINVAL(NMASKI(MINVAL(NMASKT(1,:)),1,:)),MAXVAL(NMASKI(MINVAL(NMASKT(1,:)),1,:))
96 ! write(*,*) 'NMASKI 6662 min et max',MINVAL(NMASKI(MAXVAL(NMASKT(1,:)),1,:)),MAXVAL(NMASKI(MAXVAL(NMASKT(1,:)),1,:))
97 ! stop
98 !
99 IF (lhook) CALL dr_hook('MAKE_MASK_ISBA_TO_TOPD',1,zhook_handle)
100 !
101 END SUBROUTINE make_mask_isba_to_topd
102 
103 
104 
105 
106 
107 
108 
subroutine make_mask_isba_to_topd(KI)