SURFEX v8.1
General documentation of Surfex
modd_coupling_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 ! ###########################
7 ! ###########################
8 !
9 !!**** *MODD_COUPLING_TOPD - declaration of exchanged variables from Topodyn to ISBA
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!
15 !!** IMPLICIT ARGUMENTS
16 !! ------------------
17 !! None
18 !!
19 !! REFERENCE
20 !! ---------
21 !!
22 !! AUTHOR
23 !! ------
24 !! F. Habets and K. Chancibault
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 29/09/03
29 !! 03/2014 (B. Vincendon) new variable to create a mask for N patches
30 !
31 !* 0. DECLARATIONS
32 ! ------------
33 !
34 IMPLICIT NONE
35 !
36 !-------------------------------------------------------------------------------
37 !
38 LOGICAL :: lcoupl_topd !if T, performs coupling with Topmodel
39 LOGICAL :: lbudget_topd !if T, computes budget
40 LOGICAL :: ltopd_step
41 !
42 INTEGER :: ntopd_step
43 INTEGER :: nfreq_maps_wg !frequency of output WG maps
44 INTEGER :: nfreq_maps_asat !frequency of output ASAT maps
45 INTEGER :: nfreq_maps_runoff !frequency of output RUNOFF maps
46 !
47 INTEGER :: nnb_topd ! Ratio between Time steps of Topmodel and ISBA
48 !
49 INTEGER :: nimax ! number of ISBA grid points on
50  ! abscissa axis
51 INTEGER :: njmax ! number of ISBA grid points on ordinate
52  ! axis
53 REAL, ALLOCATABLE, DIMENSION(:) :: xxi ! Extended Lambert II coordinates of Isba
54 REAL, ALLOCATABLE, DIMENSION(:) :: xyi ! nodes
55 !
56 INTEGER, ALLOCATABLE, DIMENSION(:) :: nnpix ! Number of Topmodel pixels in an ISBA mesh
57 INTEGER, ALLOCATABLE, DIMENSION(:,:,:) :: nmaski ! pixel number of each catchment in each isba mesh
58 INTEGER, ALLOCATABLE, DIMENSION(:,:) :: nmaskt ! mask
59 INTEGER, ALLOCATABLE, DIMENSION(:) :: nmaskt_patch ! mask
60 !
61 REAL, ALLOCATABLE, DIMENSION(:) :: xas_nature ! Packed contributive area fraction on Nature grid
62 REAL, ALLOCATABLE, DIMENSION(:) :: xatop ! Packed area fraction WITH TOPMODEL on Nature grid
63 !
64 INTEGER, ALLOCATABLE, DIMENSION(:,:) :: nnbv_in_mesh ! Number of pixel of a partical cathment in an ISBA mesh
65 REAL, ALLOCATABLE, DIMENSION(:,:) :: xbv_in_mesh ! Area of the ISBA meshes covered by a partical cathment
66 REAL, ALLOCATABLE, DIMENSION(:) :: xtotbv_in_mesh ! Area of the ISBA meshes covered by all cathments
67 !
68 REAL, ALLOCATABLE, DIMENSION(:) :: xdtopi ! depth of the soil for lateral
69  ! distribution on ISBA grid (m)
70 REAL, ALLOCATABLE, DIMENSION(:,:) :: xdtopt ! depth of the Isba soil on TOP-LAT
71  ! grid (m)
72 !
73 REAL, ALLOCATABLE, DIMENSION(:) :: xwg_full ! Water content from Isba on the full domain
74 REAL, ALLOCATABLE, DIMENSION(:,:) :: xwgt ! ISBA water content
75 !
76 REAL, ALLOCATABLE, DIMENSION(:) :: xwstopi ! total water content at saturation (m3/m3)
77  ! on XDTOPI on ISBA grid
78 REAL, ALLOCATABLE, DIMENSION(:,:) :: xwstopt ! total water content at saturation (m3/m3)
79  ! on XDTOPT on TOP-LAT grid
80 REAL, ALLOCATABLE, DIMENSION(:) :: xwfctopi ! total field capacity on XDTOPI (m3/m3)
81 REAL, ALLOCATABLE, DIMENSION(:,:) :: xwfctopt ! total field capacity on XDTOPT (m3/m3)
82 REAL, ALLOCATABLE, DIMENSION(:) :: xcstopi ! hydraulic conductivity at saturation on
83  ! Isba grid, on XDTOPI
84 REAL, ALLOCATABLE, DIMENSION(:,:) :: xwtopt ! water storage on TOP-LAT grid, after
85  ! lateral distribution
86 !
87 ! * pour bilans
88 REAL, ALLOCATABLE, DIMENSION(:) :: xavg_runoffcm !cumulated runoff (kg/m2) at t-dt
89 REAL, ALLOCATABLE, DIMENSION(:) :: xavg_draincm ! cumulated drainage calculated from Isba (kg/m2) at t-dt
90 !
91 REAL, ALLOCATABLE, DIMENSION(:,:) :: xka_pre ! Hydrological indexes at the previous time step
92 REAL, ALLOCATABLE, DIMENSION(:) :: xkac_pre ! Hydrological index at saturation at the previous time step
93 !
94 REAL, ALLOCATABLE, DIMENSION(:,:) :: xdmaxfc ! Deficit at the field capacity level
95 REAL, ALLOCATABLE, DIMENSION(:) :: xwsupsat ! pour calculer le volume d'eau perdu au-dessus de la saturation
96 !
97 REAL, ALLOCATABLE, DIMENSION(:) :: xdrain_top ! Value of drainage on TOPMODEL grid
98 REAL, ALLOCATABLE, DIMENSION(:) :: xrunoff_top! Value of runoff on TOPMODEL grid
99 !
100 REAL, ALLOCATABLE, DIMENSION(:) :: xfrac_d2 ! fraction of the second layer concerned with lateral transferts
101 REAL, ALLOCATABLE, DIMENSION(:) :: xfrac_d3 ! fraction of the third layer concerned with lateral transferts
102 !
103 REAL, ALLOCATABLE, DIMENSION(:) :: xwgi_full ! soil ice content
104 !
105 REAL, ALLOCATABLE, DIMENSION(:,:) :: xrun_torout,xdr_torout
106 !
107 LOGICAL :: lstock_topd ! true to stock runoff and drainage values (for another simulation)
108 !
109 INTEGER :: nnb_stp_restart ! number of time step to restart from a previous simulation
110 INTEGER :: nnb_stp_stock ! number of time step to write for the next simulation
111 !
112 INTEGER, DIMENSION(:), ALLOCATABLE :: nyear ! Year of the beginning of the simulation.
113 INTEGER, DIMENSION(:), ALLOCATABLE :: nmonth ! Month of the beginning of the simulation.
114 INTEGER, DIMENSION(:), ALLOCATABLE :: nday ! Date of the beginning of the simulation.
115 INTEGER, DIMENSION(:), ALLOCATABLE :: nh ! Hour of the beginning of the simulation.
116 INTEGER, DIMENSION(:), ALLOCATABLE :: nm ! Minutes of the beginning of the simulation.
117 !
118 ! **** For special f, dc exponential profile
119 REAL, DIMENSION(:), ALLOCATABLE :: xf_param
120 REAL, DIMENSION(:), ALLOCATABLE :: xc_depth_ratio
121 !
122 END MODULE modd_coupling_topd
123 
real, dimension(:,:), allocatable xwtopt
real, dimension(:,:), allocatable xbv_in_mesh
real, dimension(:), allocatable xcstopi
real, dimension(:), allocatable xfrac_d2
real, dimension(:), allocatable xyi
real, dimension(:), allocatable xkac_pre
integer, dimension(:), allocatable nm
real, dimension(:), allocatable xdrain_top
integer, dimension(:), allocatable nnpix
real, dimension(:,:), allocatable xdmaxfc
real, dimension(:), allocatable xrunoff_top
integer, dimension(:), allocatable nyear
real, dimension(:), allocatable xtotbv_in_mesh
integer, dimension(:), allocatable nh
real, dimension(:,:), allocatable xdtopt
real, dimension(:), allocatable xwsupsat
integer, dimension(:), allocatable nmaskt_patch
real, dimension(:), allocatable xwg_full
real, dimension(:), allocatable xas_nature
real, dimension(:), allocatable xf_param
real, dimension(:,:), allocatable xka_pre
real, dimension(:), allocatable xdtopi
real, dimension(:), allocatable xavg_draincm
real, dimension(:), allocatable xfrac_d3
real, dimension(:), allocatable xxi
real, dimension(:), allocatable xwfctopi
real, dimension(:,:), allocatable xdr_torout
real, dimension(:,:), allocatable xwfctopt
real, dimension(:), allocatable xavg_runoffcm
integer, dimension(:), allocatable nday
real, dimension(:,:), allocatable xwstopt
real, dimension(:), allocatable xatop
real, dimension(:), allocatable xwgi_full
real, dimension(:), allocatable xc_depth_ratio
integer, dimension(:,:,:), allocatable nmaski
real, dimension(:,:), allocatable xrun_torout
integer, dimension(:,:), allocatable nnbv_in_mesh
integer, dimension(:,:), allocatable nmaskt
real, dimension(:,:), allocatable xwgt
integer, dimension(:), allocatable nmonth
real, dimension(:), allocatable xwstopi