SURFEX v8.1
General documentation of Surfex
modd_topodyn.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  MODULE modd_topodyn
8 ! ##################
9 !
10 !!**** *MODD_TOPODYN - declaration of variables used by Topodyn
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 !!
16 !!** IMPLICIT ARGUMENTS
17 !! ------------------
18 !! None
19 !!
20 !! REFERENCE
21 !! ---------
22 !!
23 !! AUTHOR
24 !! ------
25 !! F. Habets and K. Chancibault
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! Original 29/09/03
30 !! BV: modifications 2006: division in two part (some variables are
31 ! now in modd_coupling_topo_n
32 !! BV: modifications 04/2007: addition of XTOPD_STEP and NNB_TOPD_STEP
33 !
34 !* 0. DECLARATIONS
35 ! ------------
36 !
37 USE modd_topd_par, ONLY : jpcat
38 !
39 IMPLICIT NONE
40 !
41 !-------------------------------------------------------------------------------
42 ! Variables specific to Topodyn
43 !
44  CHARACTER(LEN=15), DIMENSION(JPCAT) :: ccat ! base name for topographic files
45 INTEGER :: nncat ! catchments number
46 !
47 INTEGER :: nnb_topd_step ! number of TOPODYN time steps
48 REAL :: xtopd_step ! TOPODYN time step
49 !
50 INTEGER :: nmesht ! maximal number of catchments meshes
51 
52 REAL, ALLOCATABLE, DIMENSION(:,:) :: xdmaxt ! maximal deficit on TOPODYN grid (m)
53 REAL, ALLOCATABLE, DIMENSION(:) :: xdxt ! catchment grid mesh size (m)
54 REAL, ALLOCATABLE, DIMENSION(:) :: xmpara ! M parameter on TOPODYN grid (m)
55 
56 INTEGER, ALLOCATABLE, DIMENSION(:) :: nnmc ! catchments pixels number
57 REAL, ALLOCATABLE, DIMENSION(:,:,:) :: xconn ! pixels reference number and
58  ! connections between
59 INTEGER, ALLOCATABLE, DIMENSION(:,:):: nline ! second index of the pixel in the array
60  ! XCONN
61 REAL, ALLOCATABLE, DIMENSION(:,:) :: xtanb ! pixels topographic slope (Tan(Beta))
62 REAL, ALLOCATABLE, DIMENSION(:,:) :: xslop ! pixels topographic slope/length flow
63 
64 !Variables à priori inutiles
65 REAL, ALLOCATABLE, DIMENSION(:,:) :: xdarea ! drainage area (aire drainee)
66 
67 ! Variables defining the catchments
68 
69 INTEGER, ALLOCATABLE, DIMENSION(:) :: nnxc ! number of topographic grid points on
70  ! abscissa axis
71 INTEGER, ALLOCATABLE, DIMENSION(:) :: nnyc ! number of topographic grid points on ordinate
72  ! axis
73 INTEGER, ALLOCATABLE, DIMENSION(:) :: nnpt ! number of pixels in the topographic
74  ! domain
75 INTEGER :: npmax ! maximal number of pixels in the
76  ! topographic grid
77 
78 REAL, ALLOCATABLE, DIMENSION(:) :: xx0,xy0 ! coordinates bottom-left pixel of each
79  ! topographic domain
80 
81 REAL, ALLOCATABLE, DIMENSION(:) :: xnul ! undefined value in topographic files
82 
83 REAL, ALLOCATABLE, DIMENSION(:,:) :: xtopd ! topographic values in topographic files
84 REAL, DIMENSION(JPCAT) :: xrtop_d2 ! depth used by topodyn for lateral transfers
85  ! (expressed in ratio of isba d2)
86  !
87 ! Variables used in routing module
88 INTEGER, ALLOCATABLE, DIMENSION(:) :: nniso ! number of time step for the isochrones
89 REAL, ALLOCATABLE, DIMENSION(:,:) :: xciso ! isochrones routing constants
90 
91 REAL, DIMENSION(JPCAT) :: xqinit ! Initial discharge at the outlet of the catchments
92 REAL, ALLOCATABLE, DIMENSION(:,:) :: xqtot ! Total discharge at the outlet of the catchments
93 
94 REAL, DIMENSION(JPCAT) :: xspeedr,xspeedh ! River and hillslope speed
95 REAL, DIMENSION(JPCAT) :: xspeedg ! Ground speed
96 REAL, ALLOCATABLE, DIMENSION(:,:) :: xdriv, xdhil ! River and hillslope distances
97 REAL, ALLOCATABLE, DIMENSION(:,:) :: xdgrd ! Ground distance
98 REAL, ALLOCATABLE, DIMENSION(:,:) :: xtime_topd ! Time to go to the outlet
99  ! at the soil surface
100 REAL, ALLOCATABLE, DIMENSION(:,:) :: xtime_topd_drain! Time to go to the outlet in the ground
101 
102 INTEGER, ALLOCATABLE, DIMENSION(:) :: nx_step_rout ! number of maximal time step to join the outlet of
103  ! any catchment
104 
105 ! Variables used in exfiltration module
106 REAL, ALLOCATABLE, DIMENSION(:,:) :: xlambda ! pure topographic index
107 REAL, ALLOCATABLE, DIMENSION(:,:) :: xcstopt ! hydraulic conductivity at saturation on
108  ! TOP-LAT grid
109  !ludo
110 REAL, ALLOCATABLE, DIMENSION(:,:) :: xqb_dr
111 REAL, ALLOCATABLE, DIMENSION(:,:) :: xqb_run
112 ! for topodyn alone
113 REAL, ALLOCATABLE, DIMENSION(:) :: xri,xri_prev! recharge on ISBA grid
114 REAL, ALLOCATABLE, DIMENSION(:) :: xsrfull! reservoir of interception for
115 !TOPODYN only
116 REAL, ALLOCATABLE, DIMENSION(:,:) :: xdeft! pixel deficit
117 !
118 !-------------------------------------------------------------------------------------
119 !
120 END MODULE modd_topodyn
121 
real, dimension(:,:), allocatable xlambda
real, dimension(jpcat) xspeedh
real, dimension(:,:), allocatable xdriv
real, dimension(:,:), allocatable xtopd
real, dimension(:), allocatable xmpara
real, dimension(jpcat) xspeedr
real, dimension(:), allocatable xx0
character(len=15), dimension(jpcat) ccat
real, dimension(:,:), allocatable xslop
real, dimension(jpcat) xqinit
real, dimension(:,:), allocatable xqb_dr
real, dimension(:,:), allocatable xqb_run
real, dimension(:,:), allocatable xdmaxt
real, dimension(:,:), allocatable xdarea
real, dimension(:), allocatable xri
integer nnb_topd_step
real, dimension(:,:), allocatable xtanb
integer, dimension(:,:), allocatable nline
real, dimension(:,:), allocatable xcstopt
integer nmesht
real, dimension(:), allocatable xri_prev
real, dimension(:,:), allocatable xdeft
real, dimension(:), allocatable xdxt
integer, dimension(:), allocatable nx_step_rout
real, dimension(:,:), allocatable xdhil
real, dimension(:), allocatable xsrfull
integer, dimension(:), allocatable nnyc
real, dimension(:), allocatable xnul
integer, dimension(:), allocatable nnxc
real, dimension(:), allocatable xy0
integer, dimension(:), allocatable nnpt
real, dimension(:,:), allocatable xtime_topd_drain
real, dimension(jpcat) xspeedg
integer, dimension(:), allocatable nniso
real, dimension(:,:), allocatable xtime_topd
integer, parameter jpcat
real, dimension(:,:,:), allocatable xconn
real, dimension(:,:), allocatable xdgrd
real, dimension(:,:), allocatable xciso
integer, dimension(:), allocatable nnmc
real, dimension(jpcat) xrtop_d2
real, dimension(:,:), allocatable xqtot