source: branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/routing.f90 @ 7509

Last change on this file since 7509 was 7500, checked in by josefine.ghattas, 2 years ago

Correction to allow routing scheme to work on the south pole: Check if resoultion(ib,1)=0 and if so, calculate the area in a different way.
Solution done by Sebastien Nguyen. See ticket #811

  • Property svn:keywords set to Revision Date HeadURL Date Author Revision
File size: 371.7 KB
Line 
1! =================================================================================================================================
2! MODULE       : routing
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF       This module routes the water over the continents into the oceans and computes the water
10!!             stored in floodplains or taken for irrigation.
11!!
12!!\n DESCRIPTION: None
13!!
14!! RECENT CHANGE(S): None
15!!
16!! REFERENCE(S) :
17!!
18!! SVN          :
19!! $HeadURL$
20!! $Date$
21!! $Revision$
22!! \n
23!_ ================================================================================================================================
24!
25!
26! Histoire Salee
27!---------------
28! La douce riviere
29! Sortant de son lit
30! S'est jetee ma chere
31! dans les bras mais oui
32! du beau fleuve
33!
34! L'eau coule sous les ponts
35! Et puis les flots s'emeuvent
36! - N'etes vous pas au courant ?
37! Il parait que la riviere
38! Va devenir mer
39!                       Roland Bacri
40!
41
42
43MODULE routing
44
45  USE ioipsl   
46  USE xios_orchidee
47  USE ioipsl_para 
48  USE constantes
49  USE time, ONLY : one_day, dt_sechiba
50  USE constantes_soil
51  USE pft_parameters
52  USE sechiba_io_p
53  USE interpol_help
54  USE grid
55  USE mod_orchidee_para
56
57
58  IMPLICIT NONE
59  PRIVATE
60  PUBLIC :: routing_main, routing_initialize, routing_finalize, routing_clear, routing_names
61
62!! PARAMETERS
63  INTEGER(i_std), PARAMETER                                  :: nbasmax=5                   !! The maximum number of basins we wish to have per grid box (truncation of the model) (unitless)
64  INTEGER(i_std), SAVE                                       :: nbvmax                      !! The maximum number of basins we can handle at any time during the generation of the maps (unitless)
65!$OMP THREADPRIVATE(nbvmax)
66  REAL(r_std), SAVE                                          :: fast_tcst = 3.0             !! Property of the fast reservoir, (day/m)
67!$OMP THREADPRIVATE(fast_tcst)
68  REAL(r_std), SAVE                                          :: slow_tcst = 25.0            !! Property of the slow reservoir, (day/m)
69!$OMP THREADPRIVATE(slow_tcst)
70  REAL(r_std), SAVE                                          :: stream_tcst = 0.24          !! Property of the stream reservoir, (day/m)
71!$OMP THREADPRIVATE(stream_tcst)
72  REAL(r_std), SAVE                                          :: flood_tcst = 4.0            !! Property of the floodplains reservoir, (day/m)
73!$OMP THREADPRIVATE(flood_tcst)
74  REAL(r_std), SAVE                                          :: swamp_cst = 0.2             !! Fraction of the river transport that flows to the swamps (unitless;0-1)
75!$OMP THREADPRIVATE(swamp_cst)
76  !
77  !  Relation between volume and fraction of floodplains
78  !
79  REAL(r_std), SAVE                                          :: beta = 2.0                  !! Parameter to fix the shape of the floodplain (>1 for convex edges, <1 for concave edges) (unitless)
80!$OMP THREADPRIVATE(beta)
81  REAL(r_std), SAVE                                          :: betap = 0.5                 !! Ratio of the basin surface intercepted by ponds and the maximum surface of ponds (unitless;0-1)
82!$OMP THREADPRIVATE(betap)
83  REAL(r_std), SAVE                                          :: floodcri = 2000.0           !! Potential height for which all the basin is flooded (mm)
84!$OMP THREADPRIVATE(floodcri)
85  !
86  !  Relation between maximum surface of ponds and basin surface, and drainage (mm/j) to the slow_res
87  !
88  REAL(r_std), PARAMETER                                     :: pond_bas = 50.0             !! [DISPENSABLE] - not used
89  REAL(r_std), SAVE                                          :: pondcri = 2000.0            !! Potential height for which all the basin is a pond (mm)
90!$OMP THREADPRIVATE(pondcri)
91  !
92  REAL(r_std), PARAMETER                                     :: maxevap_lake = 7.5/86400.   !! Maximum evaporation rate from lakes (kg/m^2/s)
93  !
94  REAL(r_std),SAVE                                           :: dt_routing                  !! Routing time step (s)
95!$OMP THREADPRIVATE(dt_routing)
96  !
97  INTEGER(i_std), SAVE                                       :: diagunit = 87               !! Diagnostic file unit (unitless)
98!$OMP THREADPRIVATE(diagunit)
99  !
100  ! Logicals to control model configuration
101  !
102  LOGICAL, SAVE                                              :: dofloodinfilt = .FALSE.     !! Logical to choose if floodplains infiltration is activated or not (true/false)
103!$OMP THREADPRIVATE(dofloodinfilt)
104  LOGICAL, SAVE                                              :: doswamps = .FALSE.          !! Logical to choose if swamps are activated or not (true/false)
105!$OMP THREADPRIVATE(doswamps)
106  LOGICAL, SAVE                                              :: doponds = .FALSE.           !! Logical to choose if ponds are activated or not (true/false)
107!$OMP THREADPRIVATE(doponds)
108  !
109  ! The variables describing the basins and their routing, need to be in the restart file.
110  !
111  INTEGER(i_std), SAVE                                       :: num_largest                 !! Number of largest river basins which should be treated as independently as rivers
112                                                                                            !! (not flow into ocean as diffusion coastal flow) (unitless)
113!$OMP THREADPRIVATE(num_largest)
114  REAL(r_std), SAVE                                          :: time_counter                !! Time counter (s)
115!$OMP THREADPRIVATE(time_counter)
116  REAL(r_std), SAVE, ALLOCATABLE, TARGET, DIMENSION(:,:)     :: routing_area_loc            !! Surface of basin (m^2)
117!$OMP THREADPRIVATE(routing_area_loc)
118  REAL(r_std), SAVE, ALLOCATABLE, TARGET, DIMENSION(:,:)     :: topo_resid_loc              !! Topographic index of the retention time (m)
119!$OMP THREADPRIVATE(topo_resid_loc)
120  INTEGER(i_std), SAVE, ALLOCATABLE, TARGET, DIMENSION(:,:)  :: route_togrid_loc            !! Grid into which the basin flows (unitless)
121!$OMP THREADPRIVATE(route_togrid_loc)
122  INTEGER(i_std), SAVE, ALLOCATABLE, TARGET, DIMENSION(:,:)  :: route_tobasin_loc           !! Basin in to which the water goes (unitless)
123!$OMP THREADPRIVATE(route_tobasin_loc)
124  INTEGER(i_std), SAVE, ALLOCATABLE, TARGET, DIMENSION(:,:)  :: route_nbintobas_loc         !! Number of basin into current one (unitless)
125!$OMP THREADPRIVATE(route_nbintobas_loc)
126  INTEGER(i_std), SAVE, ALLOCATABLE, TARGET, DIMENSION(:,:)  :: global_basinid_loc          !! ID of basin (unitless)
127!$OMP THREADPRIVATE(global_basinid_loc)
128  INTEGER(i_std), SAVE, ALLOCATABLE, TARGET, DIMENSION(:,:)  :: hydrodiag_loc               !! Variable to diagnose the hydrographs
129!$OMP THREADPRIVATE(hydrodiag_loc)
130  REAL(r_std), SAVE, ALLOCATABLE, TARGET, DIMENSION(:)       :: hydroupbasin_loc            !! The area upstream of the gauging station (m^2)
131!$OMP THREADPRIVATE(hydroupbasin_loc)
132  !
133  ! parallelism
134  REAL(r_std), SAVE, ALLOCATABLE, TARGET, DIMENSION(:,:)     :: routing_area_glo            !! Surface of basin (m^2)
135!$OMP THREADPRIVATE(routing_area_glo)
136  REAL(r_std), SAVE, ALLOCATABLE, TARGET, DIMENSION(:,:)     :: topo_resid_glo              !! Topographic index of the retention time (m)
137!$OMP THREADPRIVATE(topo_resid_glo)
138  INTEGER(i_std), SAVE, ALLOCATABLE, TARGET, DIMENSION(:,:)  :: route_togrid_glo            !! Grid into which the basin flows (unitless)
139!$OMP THREADPRIVATE(route_togrid_glo)
140  INTEGER(i_std), SAVE, ALLOCATABLE, TARGET, DIMENSION(:,:)  :: route_tobasin_glo           !! Basin in to which the water goes (unitless)
141!$OMP THREADPRIVATE(route_tobasin_glo)
142  INTEGER(i_std), SAVE, ALLOCATABLE, TARGET, DIMENSION(:,:)  :: route_nbintobas_glo         !! Number of basin into current one (unitless)
143!$OMP THREADPRIVATE(route_nbintobas_glo)
144  INTEGER(i_std), SAVE, ALLOCATABLE, TARGET, DIMENSION(:,:)  :: global_basinid_glo          !! ID of basin (unitless)
145!$OMP THREADPRIVATE(global_basinid_glo)
146  INTEGER(i_std), SAVE, ALLOCATABLE, TARGET, DIMENSION(:,:)  :: hydrodiag_glo               !! Variable to diagnose the hydrographs
147!$OMP THREADPRIVATE(hydrodiag_glo)
148  REAL(r_std), SAVE, ALLOCATABLE, TARGET, DIMENSION(:)       :: hydroupbasin_glo            !! The area upstream of the gauging station (m^2)
149!$OMP THREADPRIVATE(hydroupbasin_glo)
150  !
151  REAL(r_std), SAVE, POINTER, DIMENSION(:,:)                 :: routing_area                !! Surface of basin (m^2)
152!$OMP THREADPRIVATE(routing_area)
153  REAL(r_std), SAVE, POINTER, DIMENSION(:,:)                 :: topo_resid                  !! Topographic index of the retention time (m)
154!$OMP THREADPRIVATE(topo_resid)
155  INTEGER(i_std), SAVE, POINTER, DIMENSION(:,:)              :: route_togrid                !! Grid into which the basin flows (unitless)
156!$OMP THREADPRIVATE(route_togrid)
157  INTEGER(i_std), SAVE, POINTER, DIMENSION(:,:)              :: route_tobasin               !! Basin in to which the water goes (unitless)
158!$OMP THREADPRIVATE(route_tobasin)
159  INTEGER(i_std), SAVE, POINTER, DIMENSION(:,:)              :: route_nbintobas             !! Number of basin into current one (unitless)
160!$OMP THREADPRIVATE(route_nbintobas)
161  INTEGER(i_std), SAVE, POINTER, DIMENSION(:,:)              :: global_basinid              !! ID of basin (unitless)
162!$OMP THREADPRIVATE(global_basinid)
163  INTEGER(i_std), SAVE, POINTER, DIMENSION(:,:)              :: hydrodiag                   !! Variable to diagnose the hydrographs
164!$OMP THREADPRIVATE(hydrodiag)
165  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: slowflow_diag               !! Diagnostic slow flow hydrographs (kg/dt)
166!$OMP THREADPRIVATE(slowflow_diag) 
167  REAL(r_std), SAVE, POINTER, DIMENSION(:)                   :: hydroupbasin                !! The area upstream of the gauging station (m^2)
168!$OMP THREADPRIVATE(hydroupbasin)
169  !
170  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: irrigated                   !! Area equipped for irrigation in each grid box (m^2)
171!$OMP THREADPRIVATE(irrigated)
172  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: floodplains                 !! Maximal surface which can be inundated in each grid box (m^2)
173!$OMP THREADPRIVATE(floodplains)
174  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: swamp                       !! Maximal surface of swamps in each grid box (m^2)
175!$OMP THREADPRIVATE(swamp)
176  !
177  ! The reservoirs, also to be put into the restart file.
178  !
179  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:,:)             :: fast_reservoir              !! Water amount in the fast reservoir (kg)
180!$OMP THREADPRIVATE(fast_reservoir)
181  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:,:)             :: slow_reservoir              !! Water amount in the slow reservoir (kg)
182!$OMP THREADPRIVATE(slow_reservoir)
183  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:,:)             :: stream_reservoir            !! Water amount in the stream reservoir (kg)
184!$OMP THREADPRIVATE(stream_reservoir)
185  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:,:)             :: flood_reservoir             !! Water amount in the floodplains reservoir (kg)
186!$OMP THREADPRIVATE(flood_reservoir)
187  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: lake_reservoir              !! Water amount in the lake reservoir (kg)
188!$OMP THREADPRIVATE(lake_reservoir)
189  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: pond_reservoir              !! Water amount in the pond reservoir (kg)
190!$OMP THREADPRIVATE(pond_reservoir)
191  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:,:)             :: flood_frac_bas              !! Flooded fraction per basin (unitless;0-1)
192!$OMP THREADPRIVATE(flood_frac_bas)
193  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: pond_frac                   !! Pond fraction per grid box (unitless;0-1)
194!$OMP THREADPRIVATE(pond_frac)
195  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: flood_height                !! Floodplain height (mm)
196!$OMP THREADPRIVATE(flood_height)
197  !
198  ! The accumulated fluxes.
199  !
200  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: floodout_mean               !! Accumulated flow out of floodplains (kg/m^2/dt)
201!$OMP THREADPRIVATE(floodout_mean)
202  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: runoff_mean                 !! Accumulated runoff (kg/m^2/dt)
203!$OMP THREADPRIVATE(runoff_mean)
204  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: drainage_mean               !! Accumulated drainage (kg/m^2/dt)
205!$OMP THREADPRIVATE(drainage_mean)
206  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: transpot_mean               !! Mean potential transpiration from the plants (kg/m^2/dt)
207!$OMP THREADPRIVATE(transpot_mean)
208  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: precip_mean                 !! Accumulated precipitation (kg/m^2/dt)
209!$OMP THREADPRIVATE(precip_mean)
210  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: humrel_mean                 !! Mean soil moisture stress, mean root extraction potential (unitless)
211!$OMP THREADPRIVATE(humrel_mean)
212  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: totnobio_mean               !! Mean last total fraction of no bio (unitless;0-1)
213!$OMP THREADPRIVATE(totnobio_mean)
214  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: vegtot_mean                 !! Mean potentially vegetated fraction (unitless;0-1)
215!$OMP THREADPRIVATE(vegtot_mean)
216  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: k_litt_mean                 !! Mean averaged conductivity for saturated infiltration in the 'litter' layer (kg/m^2/dt)
217!$OMP THREADPRIVATE(k_litt_mean)
218  !
219  ! The averaged outflow fluxes.
220  !
221  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: lakeinflow_mean              !! Mean lake inflow (kg/m^2/dt)
222!$OMP THREADPRIVATE(lakeinflow_mean)
223  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: returnflow_mean              !! Mean water flow from lakes and swamps which returns to the grid box.
224                                                                                             !! This water will go back into the hydrol module to allow re-evaporation (kg/m^2/dt)
225!$OMP THREADPRIVATE(returnflow_mean)
226  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: reinfiltration_mean          !! Mean water flow which returns to the grid box (kg/m^2/dt)
227!$OMP THREADPRIVATE(reinfiltration_mean)
228  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: irrigation_mean              !! Mean irrigation flux.
229                                                                                             !! This is the water taken from the reservoirs and beeing put into the upper layers of the soil (kg/m^2/dt)
230!$OMP THREADPRIVATE(irrigation_mean)
231  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: riverflow_mean               !! Mean Outflow of the major rivers.
232                                                                                             !! The flux will be located on the continental grid but this should be a coastal point (kg/dt)
233!$OMP THREADPRIVATE(riverflow_mean)
234  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: coastalflow_mean             !! Mean outflow on coastal points by small basins.
235                                                                                             !! This is the water which flows in a disperse way into the ocean (kg/dt)
236!$OMP THREADPRIVATE(coastalflow_mean)
237  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: floodtemp                    !! Temperature to decide if floodplains work (K)
238!$OMP THREADPRIVATE(floodtemp)
239  INTEGER(i_std), SAVE                                       :: floodtemp_lev                !! Temperature level to decide if floodplains work (K)
240!$OMP THREADPRIVATE(floodtemp_lev)
241  !
242  ! Diagnostic variables ... well sort of !
243  !
244  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: irrig_netereq                !! Irrigation requirement (water requirements by the crop for its optimal growth (kg/m^2/dt)
245!$OMP THREADPRIVATE(irrig_netereq)
246  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: hydrographs                  !! Hydrographs at the outflow of the grid box for major basins (kg/dt)
247!$OMP THREADPRIVATE(hydrographs)
248  !
249  ! Diagnostics for the various reservoirs we use (Kg/m^2)
250  !
251  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: fast_diag                    !! Diagnostic for the fast reservoir (kg/m^2)
252!$OMP THREADPRIVATE(fast_diag)
253  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: slow_diag                    !! Diagnostic for the slow reservoir (kg/m^2)
254!$OMP THREADPRIVATE(slow_diag)
255  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: stream_diag                  !! Diagnostic for the stream reservoir (kg/m^2)
256!$OMP THREADPRIVATE(stream_diag)
257  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: flood_diag                   !! Diagnostic for the floodplain reservoir (kg/m^2)
258!$OMP THREADPRIVATE(flood_diag)
259  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: pond_diag                    !! Diagnostic for the pond reservoir (kg/m^2)
260!$OMP THREADPRIVATE(pond_diag)
261  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: lake_diag                    !! Diagnostic for the lake reservoir (kg/m^2)
262!$OMP THREADPRIVATE(lake_diag)
263
264  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: mask_coast                   !! Mask with coastal gridcells on local grid(1/0)
265!$OMP THREADPRIVATE(mask_coast)
266  REAL(r_std), SAVE                                          :: max_lake_reservoir           !! Maximum limit of water in lake_reservoir [kg/m2]
267  !$OMP THREADPRIVATE(max_lake_reservoir)
268  INTEGER(i_std), SAVE                                       :: nb_coast_gridcells           !! Number of gridcells which can receive coastalflow
269!$OMP THREADPRIVATE(nb_coast_gridcells)
270
271
272CONTAINS
273  !!  =============================================================================================================================
274  !! SUBROUTINE:         routing_initialize
275  !!
276  !>\BRIEF               Initialize the routing module
277  !!
278  !! DESCRIPTION:        Initialize the routing module. Read from restart file or read the routing.nc file to initialize the
279  !!                     routing scheme.
280  !!
281  !! RECENT CHANGE(S)
282  !!
283  !! REFERENCE(S)
284  !!
285  !! FLOWCHART   
286  !! \n
287  !_ ==============================================================================================================================
288
289  SUBROUTINE routing_initialize( kjit,       nbpt,           index,                 &
290                                rest_id,     hist_id,        hist2_id,   lalo,      &
291                                neighbours,  resolution,     contfrac,   stempdiag, &
292                                returnflow,  reinfiltration, irrigation, riverflow, &
293                                coastalflow, flood_frac,     flood_res )
294       
295    IMPLICIT NONE
296   
297    !! 0.1 Input variables
298    INTEGER(i_std), INTENT(in)     :: kjit                 !! Time step number (unitless)
299    INTEGER(i_std), INTENT(in)     :: nbpt                 !! Domain size (unitless)
300    INTEGER(i_std), INTENT(in)     :: index(nbpt)          !! Indices of the points on the map (unitless)
301    INTEGER(i_std),INTENT(in)      :: rest_id              !! Restart file identifier (unitless)
302    INTEGER(i_std),INTENT(in)      :: hist_id              !! Access to history file (unitless)
303    INTEGER(i_std),INTENT(in)      :: hist2_id             !! Access to history file 2 (unitless)
304    REAL(r_std), INTENT(in)        :: lalo(nbpt,2)         !! Vector of latitude and longitudes (beware of the order !)
305
306    INTEGER(i_std), INTENT(in)     :: neighbours(nbpt,NbNeighb) !! Vector of neighbours for each grid point
307                                                           !! (1=N, 2=NE, 3=E, 4=SE, 5=S, 6=SW, 7=W, 8=NW) (unitless)
308    REAL(r_std), INTENT(in)        :: resolution(nbpt,2)   !! The size of each grid box in X and Y (m)
309    REAL(r_std), INTENT(in)        :: contfrac(nbpt)       !! Fraction of land in each grid box (unitless;0-1)
310    REAL(r_std), INTENT(in)        :: stempdiag(nbpt,nslm) !! Diagnostic soil temperature profile
311
312    !! 0.2 Output variables
313    REAL(r_std), INTENT(out)       :: returnflow(nbpt)     !! The water flow from lakes and swamps which returns to the grid box.
314                                                           !! This water will go back into the hydrol module to allow re-evaporation (kg/m^2/dt)
315    REAL(r_std), INTENT(out)       :: reinfiltration(nbpt) !! Water flow from ponds and floodplains which returns to the grid box (kg/m^2/dt)
316    REAL(r_std), INTENT(out)       :: irrigation(nbpt)     !! Irrigation flux. This is the water taken from the reservoirs and beeing put into the upper layers of the soil (kg/m^2/dt)
317    REAL(r_std), INTENT(out)       :: riverflow(nbpt)      !! Outflow of the major rivers. The flux will be located on the continental grid but this should be a coastal point (kg/dt)
318
319    REAL(r_std), INTENT(out)       :: coastalflow(nbpt)    !! Outflow on coastal points by small basins. This is the water which flows in a disperse way into the ocean (kg/dt)
320    REAL(r_std), INTENT(out)       :: flood_frac(nbpt)     !! Flooded fraction of the grid box (unitless;0-1)
321    REAL(r_std), INTENT(out)       :: flood_res(nbpt)      !! Diagnostic of water amount in the floodplains reservoir (kg)
322   
323    !! 0.3 Local variables
324    REAL(r_std), DIMENSION(nbp_glo):: mask_coast_glo       !! Mask with coastal gridcells on global grid (1/0)
325    LOGICAL                        :: init_irrig           !! Logical to initialize the irrigation (true/false)
326    LOGICAL                        :: init_flood           !! Logical to initialize the floodplains (true/false)
327    LOGICAL                        :: init_swamp           !! Logical to initialize the swamps (true/false)
328    INTEGER                        :: ig, ib, rtg, rtb     !! Index
329    INTEGER                        :: ier                  !! Error handeling
330!_ ================================================================================================================================
331
332    !
333    ! do initialisation
334    !
335    nbvmax = 440
336    ! Here we will allocate the memory and get the fixed fields from the restart file.
337    ! If the info is not found then we will compute the routing map.
338    !
339
340    CALL routing_init (kjit, nbpt, index, returnflow, reinfiltration, irrigation, &
341         riverflow, coastalflow, flood_frac, flood_res, stempdiag, rest_id)
342
343    routing_area => routing_area_loc 
344    topo_resid => topo_resid_loc
345    route_togrid => route_togrid_loc
346    route_tobasin => route_tobasin_loc
347    global_basinid => global_basinid_loc
348    hydrodiag => hydrodiag_loc
349   
350    ! This routine computes the routing map if the route_togrid_glo is undefined. This means that the
351    ! map has not been initialized during the restart process..
352    !
353    !! Reads in the map of the basins and flow directions to construct the catchments of each grid box
354    !
355    IF ( COUNT(route_togrid_glo .GE. undef_int) .GT. 0 ) THEN
356       CALL routing_basins_p(nbpt, lalo, neighbours, resolution, contfrac)
357    ENDIF
358
359    !! Create a mask containing all possible coastal gridcells and count total number of coastal gridcells
360    IF (is_root_prc) THEN
361       mask_coast_glo(:)=0
362       DO ib=1,nbasmax
363          DO ig=1,nbp_glo
364             rtg = route_togrid_glo(ig,ib)
365             rtb = route_tobasin_glo(ig,ib)
366             ! Coastal gridcells are stored in nbasmax+2
367             IF (rtb == nbasmax+2) THEN
368                mask_coast_glo(rtg) = 1
369             END IF
370          END DO
371       END DO
372       nb_coast_gridcells=SUM(mask_coast_glo)
373       IF (printlev>=3) WRITE(numout,*) 'Number of coastal gridcells = ', nb_coast_gridcells
374    ENDIF
375    CALL bcast(nb_coast_gridcells)
376
377    ALLOCATE(mask_coast(nbpt), stat=ier)
378    IF (ier /= 0) CALL ipslerr_p(3,'routing_inititalize','Pb in allocate for mask_coast','','')
379    CALL scatter(mask_coast_glo, mask_coast)
380    CALL xios_orchidee_send_field("mask_coast",mask_coast)
381
382
383    !
384    ! Do we have what we need if we want to do irrigation
385    !! Initialisation of flags for irrigated land, flood plains and swamps
386    !
387    init_irrig = .FALSE.
388    IF ( do_irrigation ) THEN
389       IF (COUNT(irrigated .GE. undef_sechiba-1) > 0) init_irrig = .TRUE.
390    END IF
391   
392    init_flood = .FALSE.
393    IF ( do_floodplains ) THEN
394       IF (COUNT(floodplains .GE. undef_sechiba-1) > 0) init_flood = .TRUE.
395    END IF
396   
397    init_swamp = .FALSE.
398    IF ( doswamps ) THEN
399       IF (COUNT(swamp .GE. undef_sechiba-1) > 0 ) init_swamp = .TRUE.
400    END IF
401       
402    !! If we have irrigated land, flood plains or swamps then we need to interpolate the 0.5 degree
403    !! base data set to the resolution of the model.
404   
405    IF ( init_irrig .OR. init_flood .OR. init_swamp ) THEN
406       CALL routing_irrigmap(nbpt, index, lalo, neighbours, resolution, &
407            contfrac, init_irrig, irrigated, init_flood, floodplains, init_swamp, swamp, hist_id, hist2_id)
408    ENDIF
409   
410    IF ( do_irrigation ) THEN
411       CALL xios_orchidee_send_field("irrigmap",irrigated)
412       
413       IF (printlev >= 3) WRITE(numout,*) 'Verification : range of irrigated : ', MINVAL(irrigated), MAXVAL(irrigated) 
414       IF ( .NOT. almaoutput ) THEN
415          CALL histwrite_p(hist_id, 'irrigmap', 1, irrigated, nbpt, index)
416       ELSE
417          CALL histwrite_p(hist_id, 'IrrigationMap', 1, irrigated, nbpt, index)
418       ENDIF
419       IF ( hist2_id > 0 ) THEN
420          IF ( .NOT. almaoutput ) THEN
421             CALL histwrite_p(hist2_id, 'irrigmap', 1, irrigated, nbpt, index)
422          ELSE
423             CALL histwrite_p(hist2_id, 'IrrigationMap', 1, irrigated, nbpt, index)
424          ENDIF
425       ENDIF
426    ENDIF
427   
428    IF ( do_floodplains ) THEN
429       CALL xios_orchidee_send_field("floodmap",floodplains)
430       
431       IF (printlev>=3) WRITE(numout,*) 'Verification : range of floodplains : ', MINVAL(floodplains), MAXVAL(floodplains) 
432       IF ( .NOT. almaoutput ) THEN
433          CALL histwrite_p(hist_id, 'floodmap', 1, floodplains, nbpt, index)
434       ELSE
435          CALL histwrite_p(hist_id, 'FloodplainsMap', 1, floodplains, nbpt, index)
436       ENDIF
437       IF ( hist2_id > 0 ) THEN
438          IF ( .NOT. almaoutput ) THEN
439             CALL histwrite_p(hist2_id, 'floodmap', 1, floodplains, nbpt, index)
440          ELSE
441             CALL histwrite_p(hist2_id, 'FloodplainsMap', 1, floodplains, nbpt, index)
442          ENDIF
443       ENDIF
444    ENDIF
445   
446    IF ( doswamps ) THEN
447       CALL xios_orchidee_send_field("swampmap",swamp)
448       
449       IF (printlev>=3) WRITE(numout,*) 'Verification : range of swamp : ', MINVAL(swamp), MAXVAL(swamp) 
450       IF ( .NOT. almaoutput ) THEN
451          CALL histwrite_p(hist_id, 'swampmap', 1, swamp, nbpt, index)
452       ELSE
453          CALL histwrite_p(hist_id, 'SwampMap', 1, swamp, nbpt, index)
454       ENDIF
455       IF ( hist2_id > 0 ) THEN
456          IF ( .NOT. almaoutput ) THEN
457             CALL histwrite_p(hist2_id, 'swampmap', 1, swamp, nbpt, index)
458          ELSE
459             CALL histwrite_p(hist2_id, 'SwampMap', 1, swamp, nbpt, index)
460          ENDIF
461       ENDIF
462    ENDIF
463   
464    !! This routine gives a diagnostic of the basins used.
465    CALL routing_diagnostic_p(nbpt, index, lalo, resolution, contfrac, hist_id, hist2_id)
466   
467  END SUBROUTINE routing_initialize
468
469!! ================================================================================================================================
470!! SUBROUTINE   : routing_main
471!!
472!>\BRIEF          This module routes the water over the continents (runoff and
473!!                drainage produced by the hydrol module) into the oceans.
474!!
475!! DESCRIPTION (definitions, functional, design, flags):
476!! The routing scheme (Polcher, 2003) carries the water from the runoff and drainage simulated by SECHIBA
477!! to the ocean through reservoirs, with some delay. The routing scheme is based on
478!! a parametrization of the water flow on a global scale (Miller et al., 1994; Hagemann
479!! and Dumenil, 1998). Given the global map of the main watersheds (Oki et al., 1999;
480!! Fekete et al., 1999; Vorosmarty et al., 2000) which delineates the boundaries of subbasins
481!! and gives the eight possible directions of water flow within the pixel, the surface
482!! runoff and the deep drainage are routed to the ocean. The time-step of the routing is one day.
483!! The scheme also diagnoses how much water is retained in the foodplains and thus return to soil
484!! moisture or is taken out of the rivers for irrigation. \n
485!!
486!! RECENT CHANGE(S): None
487!!
488!! MAIN OUTPUT VARIABLE(S):
489!! The result of the routing are 3 fluxes :
490!! - riverflow   : The water which flows out from the major rivers. The flux will be located
491!!                 on the continental grid but this should be a coastal point.
492!! - coastalflow : This is the water which flows in a disperse way into the ocean. Essentially these
493!!                 are the outflows from all of the small rivers.
494!! - returnflow  : This is the water which flows into a land-point - typically rivers which end in
495!!                 the desert. This water will go back into the hydrol module to allow re-evaporation.
496!! - irrigation  : This is water taken from the reservoir and is being put into the upper
497!!                 layers of the soil.
498!! The two first fluxes are in kg/dt and the last two fluxes are in kg/(m^2dt).\n
499!!
500!! REFERENCE(S) :
501!! - Miller JR, Russell GL, Caliri G (1994)
502!!   Continental-scale river flow in climate models.
503!!   J. Clim., 7:914-928
504!! - Hagemann S and Dumenil L. (1998)
505!!   A parametrization of the lateral waterflow for the global scale.
506!!   Clim. Dyn., 14:17-31
507!! - Oki, T., T. Nishimura, and P. Dirmeyer (1999)
508!!   Assessment of annual runoff from land surface models using total runoff integrating pathways (TRIP)
509!!   J. Meteorol. Soc. Jpn., 77, 235-255
510!! - Fekete BM, Charles V, Grabs W (2000)
511!!   Global, composite runoff fields based on observed river discharge and simulated water balances.
512!!   Technical report, UNH/GRDC, Global Runoff Data Centre, Koblenz
513!! - Vorosmarty, C., B. Fekete, B. Meybeck, and R. Lammers (2000)
514!!   Global system of rivers: Its role in organizing continental land mass and defining land-to-ocean linkages
515!!   Global Biogeochem. Cycles, 14, 599-621
516!! - Vivant, A-C. (?? 2002)
517!!   Développement du schéma de routage et des plaines d'inondation, MSc Thesis, Paris VI University
518!! - J. Polcher (2003)
519!!   Les processus de surface a l'echelle globale et leurs interactions avec l'atmosphere
520!!   Habilitation a diriger les recherches, Paris VI University, 67pp.
521!!
522!! FLOWCHART    :
523!! \latexonly
524!! \includegraphics[scale=0.75]{routing_main_flowchart.png}
525!! \endlatexonly
526!! \n
527!_ ================================================================================================================================
528
529SUBROUTINE routing_main(kjit, nbpt, index, &
530       & lalo, neighbours, resolution, contfrac, totfrac_nobio, veget_max, floodout, runoff, &
531       & drainage, transpot, precip_rain, humrel, k_litt, flood_frac, flood_res, &
532       & stempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id)
533
534    IMPLICIT NONE
535
536    !! 0.1 Input variables
537    INTEGER(i_std), INTENT(in)     :: kjit                 !! Time step number (unitless)
538    INTEGER(i_std), INTENT(in)     :: nbpt                 !! Domain size (unitless)
539    INTEGER(i_std),INTENT(in)      :: rest_id              !! Restart file identifier (unitless)
540    INTEGER(i_std),INTENT(in)      :: hist_id              !! Access to history file (unitless)
541    INTEGER(i_std),INTENT(in)      :: hist2_id             !! Access to history file 2 (unitless)
542    INTEGER(i_std), INTENT(in)     :: index(nbpt)          !! Indices of the points on the map (unitless)
543    REAL(r_std), INTENT(in)        :: lalo(nbpt,2)         !! Vector of latitude and longitudes (beware of the order !)
544    INTEGER(i_std), INTENT(in)     :: neighbours(nbpt,NbNeighb)   !! Vector of neighbours for each grid point (1=N, 2=NE, 3=E, 4=SE, 5=S, 6=SW, 7=W, 8=NW) (unitless)
545    REAL(r_std), INTENT(in)        :: resolution(nbpt,2)   !! The size of each grid box in X and Y (m)
546    REAL(r_std), INTENT(in)        :: contfrac(nbpt)       !! Fraction of land in each grid box (unitless;0-1)
547    REAL(r_std), INTENT(in)        :: totfrac_nobio(nbpt)  !! Total fraction of no-vegetation (continental ice, lakes ...) (unitless;0-1)
548    REAL(r_std), INTENT(in)        :: veget_max(nbpt,nvm)  !! Maximal fraction of vegetation (unitless;0-1)
549    REAL(r_std), INTENT(in)        :: floodout(nbpt)       !! Grid-point flow out of floodplains (kg/m^2/dt)
550    REAL(r_std), INTENT(in)        :: runoff(nbpt)         !! Grid-point runoff (kg/m^2/dt)
551    REAL(r_std), INTENT(in)        :: drainage(nbpt)       !! Grid-point drainage (kg/m^2/dt)
552    REAL(r_std), INTENT(in)        :: transpot(nbpt,nvm)   !! Potential transpiration of the vegetation (kg/m^2/dt)
553    REAL(r_std), INTENT(in)        :: precip_rain(nbpt)    !! Rainfall (kg/m^2/dt)
554    REAL(r_std), INTENT(in)        :: k_litt(nbpt)         !! Averaged conductivity for saturated infiltration in the 'litter' layer (kg/m^2/dt)
555    REAL(r_std), INTENT(in)        :: humrel(nbpt,nvm)     !! Soil moisture stress, root extraction potential (unitless)
556    REAL(r_std), INTENT(in)        :: stempdiag(nbpt,nslm) !! Diagnostic soil temperature profile
557    REAL(r_std), INTENT(in)        :: reinf_slope(nbpt)    !! Coefficient which determines the reinfiltration ratio in the grid box due to flat areas (unitless;0-1)
558
559    !! 0.2 Output variables
560    REAL(r_std), INTENT(out)       :: returnflow(nbpt)     !! The water flow from lakes and swamps which returns to the grid box.
561                                                           !! This water will go back into the hydrol module to allow re-evaporation (kg/m^2/dt)
562    REAL(r_std), INTENT(out)       :: reinfiltration(nbpt) !! Water flow from ponds and floodplains which returns to the grid box (kg/m^2/dt)
563    REAL(r_std), INTENT(out)       :: irrigation(nbpt)     !! Irrigation flux. This is the water taken from the reservoirs and beeing put into the upper layers of the soil (kg/m^2/dt)
564    REAL(r_std), INTENT(out)       :: riverflow(nbpt)      !! Outflow of the major rivers. The flux will be located on the continental grid but this should be a coastal point (kg/dt)
565    REAL(r_std), INTENT(out)       :: coastalflow(nbpt)    !! Outflow on coastal points by small basins. This is the water which flows in a disperse way into the ocean (kg/dt)
566    REAL(r_std), INTENT(out)       :: flood_frac(nbpt)     !! Flooded fraction of the grid box (unitless;0-1)
567    REAL(r_std), INTENT(out)       :: flood_res(nbpt)      !! Diagnostic of water amount in the floodplains reservoir (kg)
568
569    !! 0.3 Local variables
570    CHARACTER(LEN=30)              :: var_name             !! To store variables names for I/O (unitless)
571    REAL(r_std), DIMENSION(1)      :: tmp_day              !!
572    REAL(r_std), DIMENSION(nbpt)   :: return_lakes         !! Water from lakes flowing back into soil moisture (kg/m^2/dt)
573
574    INTEGER(i_std)                 :: ig, jv               !! Indices (unitless)
575    REAL(r_std), DIMENSION(nbpt)   :: tot_vegfrac_nowoody  !! Total fraction occupied by grass (0-1,unitless)
576
577    REAL(r_std), DIMENSION(nbpt)   :: fast_diag_old        !! Reservoir in the beginning of the time step
578    REAL(r_std), DIMENSION(nbpt)   :: slow_diag_old        !! Reservoir in the beginning of the time step
579    REAL(r_std), DIMENSION(nbpt)   :: stream_diag_old      !! Reservoir in the beginning of the time step
580    REAL(r_std), DIMENSION(nbpt)   :: lake_diag_old        !! Reservoir in the beginning of the time step
581    REAL(r_std), DIMENSION(nbpt)   :: pond_diag_old        !! Reservoir in the beginning of the time step
582    REAL(r_std), DIMENSION(nbpt)   :: flood_diag_old       !! Reservoir in the beginning of the time step
583
584    !! For water budget check in the three routing reservoirs (positive if input > output)
585    !! Net fluxes averaged over each grid cell in kg/m^2/dt
586    REAL(r_std), DIMENSION(nbpt)   :: netflow_stream_diag  !! Input - Output flow to stream reservoir
587    REAL(r_std), DIMENSION(nbpt)   :: netflow_fast_diag    !! Input - Output flow to fast reservoir
588    REAL(r_std), DIMENSION(nbpt)   :: netflow_slow_diag    !! Input - Output flow to slow reservoir
589
590
591!_ ================================================================================================================================
592
593    ! Save reservoirs in beginning of time step to calculate the water budget
594    fast_diag_old   = fast_diag
595    slow_diag_old   = slow_diag
596    stream_diag_old = stream_diag
597    lake_diag_old   = lake_diag
598    pond_diag_old   = pond_diag
599    flood_diag_old  = flood_diag
600
601    !
602    !! Computes the variables averaged between routing time steps and which will be used in subsequent calculations
603    !
604    floodout_mean(:) = floodout_mean(:) + floodout(:)
605    runoff_mean(:) = runoff_mean(:) + runoff(:)
606    drainage_mean(:) = drainage_mean(:) + drainage(:)
607    floodtemp(:) = stempdiag(:,floodtemp_lev)
608    precip_mean(:) =  precip_mean(:) + precip_rain(:)
609    !
610    !! Computes the total fraction occupied by the grasses and the crops for each grid cell
611    tot_vegfrac_nowoody(:) = zero
612    DO jv  = 1, nvm
613       IF ( (jv /= ibare_sechiba) .AND. .NOT.(is_tree(jv)) ) THEN
614          tot_vegfrac_nowoody(:) = tot_vegfrac_nowoody(:) + veget_max(:,jv) 
615       END IF
616    END DO
617
618    DO ig = 1, nbpt
619       IF ( tot_vegfrac_nowoody(ig) .GT. min_sechiba ) THEN
620          DO jv = 1,nvm
621             IF ( (jv /= ibare_sechiba) .AND. .NOT.(is_tree(jv)) ) THEN
622                transpot_mean(ig) = transpot_mean(ig) + transpot(ig,jv) * veget_max(ig,jv)/tot_vegfrac_nowoody(ig) 
623             END IF
624          END DO
625       ELSE
626          IF (MAXVAL(veget_max(ig,2:nvm)) .GT. min_sechiba) THEN
627             DO jv = 2, nvm
628                transpot_mean(ig) = transpot_mean(ig) + transpot(ig,jv) * veget_max(ig,jv)/ SUM(veget_max(ig,2:nvm))
629             ENDDO
630          ENDIF
631       ENDIF
632    ENDDO
633
634    !
635    ! Averaged variables (i.e. *dt_sechiba/dt_routing). This accounts for the difference between the shorter
636    ! timestep dt_sechiba of other parts of the model and the long dt_routing timestep (set to one day at present)
637    !
638    totnobio_mean(:) = totnobio_mean(:) + totfrac_nobio(:)*dt_sechiba/dt_routing
639    k_litt_mean(:) = k_litt_mean(:) + k_litt(:)*dt_sechiba/dt_routing
640    !
641    ! Only potentially vegetated surfaces are taken into account. At the start of
642    ! the growing seasons we will give more weight to these areas.
643    !
644    DO jv=2,nvm
645       DO ig=1,nbpt
646          humrel_mean(ig) = humrel_mean(ig) + humrel(ig,jv)*veget_max(ig,jv)*dt_sechiba/dt_routing
647          vegtot_mean(ig) = vegtot_mean(ig) + veget_max(ig,jv)*dt_sechiba/dt_routing
648       ENDDO
649    ENDDO
650    !
651    time_counter = time_counter + dt_sechiba 
652    !
653    ! If the time has come we do the routing.
654    !
655    IF ( NINT(time_counter) .GE. NINT(dt_routing) ) THEN 
656       !
657       !! Computes the transport of water in the various reservoirs
658       !
659       CALL routing_flow(nbpt, dt_routing, lalo, floodout_mean, runoff_mean, drainage_mean, &
660            & vegtot_mean, totnobio_mean, transpot_mean, precip_mean, humrel_mean, k_litt_mean, floodtemp, reinf_slope, &
661            & lakeinflow_mean, returnflow_mean, reinfiltration_mean, irrigation_mean, riverflow_mean, &
662            & coastalflow_mean, hydrographs, slowflow_diag, flood_frac, flood_res, &
663            & netflow_stream_diag, netflow_fast_diag, netflow_slow_diag)
664       !
665       !! Responsible for storing the water in lakes
666       !
667       CALL routing_lake(nbpt, dt_routing, lakeinflow_mean, humrel_mean, return_lakes)
668       !
669       returnflow_mean(:) = returnflow_mean(:) + return_lakes(:)
670
671       time_counter = zero
672       !
673       floodout_mean(:) = zero
674       runoff_mean(:) = zero
675       drainage_mean(:) = zero
676       transpot_mean(:) = zero
677       precip_mean(:) = zero
678       !
679       humrel_mean(:) = zero
680       totnobio_mean(:) = zero
681       k_litt_mean(:) = zero
682       vegtot_mean(:) = zero
683
684       ! Change the units of the routing fluxes from kg/dt_routing into kg/dt_sechiba
685       hydrographs(:) = hydrographs(:)/dt_routing*dt_sechiba
686       slowflow_diag(:) = slowflow_diag(:)/dt_routing*dt_sechiba
687
688       ! Change the units of the routing fluxes from kg/m^2/dt_routing into kg/m^2/dt_sechiba
689       returnflow_mean(:) = returnflow_mean(:)/dt_routing*dt_sechiba
690       reinfiltration_mean(:) = reinfiltration_mean(:)/dt_routing*dt_sechiba
691       irrigation_mean(:) = irrigation_mean(:)/dt_routing*dt_sechiba
692       irrig_netereq(:) = irrig_netereq(:)/dt_routing*dt_sechiba
693       
694       ! Change units as above but at the same time transform the kg/dt_routing to m^3/dt_sechiba
695       riverflow_mean(:) = riverflow_mean(:)/dt_routing*dt_sechiba/mille
696       coastalflow_mean(:) = coastalflow_mean(:)/dt_routing*dt_sechiba/mille
697
698       ! Water budget residu of the three routing reservoirs (in kg/m^2/s)
699       ! Note that these diagnostics are done using local variables only calculated
700       ! during the time steps when the routing is calculated
701       CALL xios_orchidee_send_field("wbr_stream",(stream_diag - stream_diag_old - netflow_stream_diag)/dt_routing)
702       CALL xios_orchidee_send_field("wbr_fast",  (fast_diag   - fast_diag_old - netflow_fast_diag)/dt_routing)
703       CALL xios_orchidee_send_field("wbr_slow",  (slow_diag   - slow_diag_old - netflow_slow_diag)/dt_routing)
704       CALL xios_orchidee_send_field("wbr_lake",  (lake_diag   - lake_diag_old - &
705                                                   lakeinflow_mean + return_lakes)/dt_routing)
706    ENDIF
707
708    !
709    ! Return the fraction of routed water for this time step.
710    !
711    returnflow(:) = returnflow_mean(:)
712    reinfiltration(:) = reinfiltration_mean(:)
713    irrigation(:) = irrigation_mean(:)
714    riverflow(:) = riverflow_mean(:)
715    coastalflow(:) = coastalflow_mean(:)
716
717    !
718    ! Write diagnostics
719    !
720
721    ! Water storage in reservoirs [kg/m^2]
722    CALL xios_orchidee_send_field("fastr",fast_diag)
723    CALL xios_orchidee_send_field("slowr",slow_diag)
724    CALL xios_orchidee_send_field("streamr",stream_diag)
725    CALL xios_orchidee_send_field("laker",lake_diag)
726    CALL xios_orchidee_send_field("pondr",pond_diag)
727    CALL xios_orchidee_send_field("floodr",flood_diag)
728    CALL xios_orchidee_send_field("floodh",flood_height)
729
730    ! Difference between the end and the beginning of the routing time step [kg/m^2]
731    CALL xios_orchidee_send_field("delfastr",   fast_diag   - fast_diag_old)
732    CALL xios_orchidee_send_field("delslowr",   slow_diag   - slow_diag_old)
733    CALL xios_orchidee_send_field("delstreamr", stream_diag - stream_diag_old)
734    CALL xios_orchidee_send_field("dellaker",   lake_diag   - lake_diag_old)
735    CALL xios_orchidee_send_field("delpondr",   pond_diag   - pond_diag_old)
736    CALL xios_orchidee_send_field("delfloodr",  flood_diag  - flood_diag_old)
737
738    ! Water fluxes converted from kg/m^2/dt_sechiba into kg/m^2/s
739    CALL xios_orchidee_send_field("irrigation",irrigation/dt_sechiba)
740    CALL xios_orchidee_send_field("netirrig",irrig_netereq/dt_sechiba)
741    CALL xios_orchidee_send_field("riversret",returnflow/dt_sechiba)
742    CALL xios_orchidee_send_field("reinfiltration",reinfiltration/dt_sechiba)
743
744    ! Transform from kg/dt_sechiba into m^3/s
745    CALL xios_orchidee_send_field("hydrographs",hydrographs/mille/dt_sechiba)
746    CALL xios_orchidee_send_field("slowflow",slowflow_diag/mille/dt_sechiba) ! previous id name: Qb
747    CALL xios_orchidee_send_field("coastalflow",coastalflow/dt_sechiba)
748    CALL xios_orchidee_send_field("riverflow",riverflow/dt_sechiba)
749
750    IF ( .NOT. almaoutput ) THEN
751       !
752       CALL histwrite_p(hist_id, 'riversret', kjit, returnflow, nbpt, index)
753       IF (do_floodplains .OR. doponds) THEN
754          CALL histwrite_p(hist_id, 'reinfiltration', kjit, reinfiltration, nbpt, index)
755       ENDIF
756       CALL histwrite_p(hist_id, 'hydrographs', kjit, hydrographs/mille, nbpt, index)
757       !
758       CALL histwrite_p(hist_id, 'fastr', kjit, fast_diag, nbpt, index)
759       CALL histwrite_p(hist_id, 'slowr', kjit, slow_diag, nbpt, index)
760       CALL histwrite_p(hist_id, 'streamr', kjit, stream_diag, nbpt, index)
761       IF ( do_floodplains ) THEN
762          CALL histwrite_p(hist_id, 'floodr', kjit, flood_diag, nbpt, index)
763          CALL histwrite_p(hist_id, 'floodh', kjit, flood_height, nbpt, index)
764       ENDIF
765       CALL histwrite_p(hist_id, 'pondr', kjit, pond_diag, nbpt, index)
766       CALL histwrite_p(hist_id, 'lakevol', kjit, lake_diag, nbpt, index)
767       !
768       IF ( do_irrigation ) THEN
769          CALL histwrite_p(hist_id, 'irrigation', kjit, irrigation, nbpt, index)
770          CALL histwrite_p(hist_id, 'returnflow', kjit, returnflow, nbpt, index)
771          CALL histwrite_p(hist_id, 'netirrig', kjit, irrig_netereq, nbpt, index)
772       ENDIF
773       !
774    ELSE
775       CALL histwrite_p(hist_id, 'SurfStor', kjit, flood_diag+pond_diag+lake_diag, nbpt, index)
776       CALL histwrite_p(hist_id, 'Dis', kjit, hydrographs/mille, nbpt, index)
777       !
778       CALL histwrite_p(hist_id, 'slowr', kjit, slow_diag, nbpt, index)
779       CALL histwrite_p(hist_id, 'fastr', kjit, fast_diag, nbpt, index)
780       CALL histwrite_p(hist_id, 'streamr', kjit, stream_diag, nbpt, index)
781       CALL histwrite_p(hist_id, 'lakevol', kjit, lake_diag, nbpt, index)
782       CALL histwrite_p(hist_id, 'pondr', kjit, pond_diag, nbpt, index)
783       !
784       IF ( do_irrigation ) THEN
785          CALL histwrite_p(hist_id, 'Qirrig', kjit, irrigation, nbpt, index)
786          CALL histwrite_p(hist_id, 'Qirrig_req', kjit, irrig_netereq, nbpt, index)
787       ENDIF
788       !
789    ENDIF
790    IF ( hist2_id > 0 ) THEN
791       IF ( .NOT. almaoutput ) THEN
792          !
793          CALL histwrite_p(hist2_id, 'riversret', kjit, returnflow, nbpt, index)
794          IF (do_floodplains .OR. doponds) THEN
795             CALL histwrite_p(hist2_id, 'reinfiltration', kjit, reinfiltration, nbpt, index)
796          ENDIF
797          CALL histwrite_p(hist2_id, 'hydrographs', kjit, hydrographs/mille, nbpt, index)
798          !
799          CALL histwrite_p(hist2_id, 'fastr', kjit, fast_diag, nbpt, index)
800          CALL histwrite_p(hist2_id, 'slowr', kjit, slow_diag, nbpt, index)
801          IF ( do_floodplains ) THEN
802             CALL histwrite_p(hist2_id, 'floodr', kjit, flood_diag, nbpt, index)
803             CALL histwrite_p(hist2_id, 'floodh', kjit, flood_height, nbpt, index)
804          ENDIF
805          CALL histwrite_p(hist2_id, 'pondr', kjit, pond_diag, nbpt, index)
806          CALL histwrite_p(hist2_id, 'streamr', kjit, stream_diag, nbpt, index)
807          CALL histwrite_p(hist2_id, 'lakevol', kjit, lake_diag, nbpt, index)
808          !
809          IF ( do_irrigation ) THEN
810             CALL histwrite_p(hist2_id, 'irrigation', kjit, irrigation, nbpt, index)
811             CALL histwrite_p(hist2_id, 'returnflow', kjit, returnflow, nbpt, index)
812             CALL histwrite_p(hist2_id, 'netirrig', kjit, irrig_netereq, nbpt, index)
813          ENDIF
814          !
815       ELSE
816          !
817          CALL histwrite_p(hist2_id, 'SurfStor', kjit, flood_diag+pond_diag+lake_diag, nbpt, index)
818          CALL histwrite_p(hist2_id, 'Dis', kjit, hydrographs/mille, nbpt, index)
819          !
820       ENDIF
821    ENDIF
822    !
823    !
824  END SUBROUTINE routing_main
825 
826  !!  =============================================================================================================================
827  !! SUBROUTINE:         routing_finalize
828  !!
829  !>\BRIEF               Write to restart file
830  !!
831  !! DESCRIPTION:        Write module variables to restart file
832  !!
833  !! RECENT CHANGE(S)
834  !!
835  !! REFERENCE(S)
836  !!
837  !! FLOWCHART   
838  !! \n
839  !_ ==============================================================================================================================
840
841  SUBROUTINE routing_finalize( kjit, nbpt, rest_id, flood_frac, flood_res )
842   
843    IMPLICIT NONE
844   
845    !! 0.1 Input variables
846    INTEGER(i_std), INTENT(in)     :: kjit                 !! Time step number (unitless)
847    INTEGER(i_std), INTENT(in)     :: nbpt                 !! Domain size (unitless)
848    INTEGER(i_std),INTENT(in)      :: rest_id              !! Restart file identifier (unitless)
849    REAL(r_std), INTENT(in)        :: flood_frac(nbpt)     !! Flooded fraction of the grid box (unitless;0-1)
850    REAL(r_std), INTENT(in)        :: flood_res(nbpt)      !! Diagnostic of water amount in the floodplains reservoir (kg)
851   
852    !! 0.2 Local variables
853    REAL(r_std), DIMENSION(1)      :: tmp_day             
854
855!_ ================================================================================================================================
856   
857    !
858    ! Write restart variables
859    !
860    tmp_day(1) = time_counter
861    IF (is_root_prc) CALL restput (rest_id, 'routingcounter', 1, 1, 1, kjit, tmp_day)
862
863    CALL restput_p (rest_id, 'routingarea', nbp_glo, nbasmax, 1, kjit, routing_area, 'scatter',  nbp_glo, index_g)
864    CALL restput_p (rest_id, 'routetogrid', nbp_glo, nbasmax, 1, kjit, REAL(route_togrid,r_std), 'scatter', &
865         nbp_glo, index_g)
866    CALL restput_p (rest_id, 'routetobasin', nbp_glo, nbasmax, 1, kjit, REAL(route_tobasin,r_std), 'scatter', &
867         nbp_glo, index_g)
868    CALL restput_p (rest_id, 'basinid', nbp_glo, nbasmax, 1, kjit, REAL(global_basinid,r_std), 'scatter', &
869         nbp_glo, index_g)
870    CALL restput_p (rest_id, 'topoindex', nbp_glo, nbasmax, 1, kjit, topo_resid, 'scatter',  nbp_glo, index_g)
871    CALL restput_p (rest_id, 'fastres', nbp_glo, nbasmax, 1, kjit, fast_reservoir, 'scatter',  nbp_glo, index_g)
872    CALL restput_p (rest_id, 'slowres', nbp_glo, nbasmax, 1, kjit, slow_reservoir, 'scatter',  nbp_glo, index_g)
873    CALL restput_p (rest_id, 'streamres', nbp_glo, nbasmax, 1, kjit, stream_reservoir, 'scatter',nbp_glo,index_g)
874    CALL restput_p (rest_id, 'floodres', nbp_glo, nbasmax, 1, kjit, flood_reservoir, 'scatter',  nbp_glo, index_g)
875    CALL restput_p (rest_id, 'floodh', nbp_glo, 1, 1, kjit, flood_height, 'scatter',  nbp_glo, index_g)
876    CALL restput_p (rest_id, 'flood_frac_bas', nbp_glo, nbasmax, 1, kjit, flood_frac_bas, 'scatter',  nbp_glo, index_g)
877    CALL restput_p (rest_id, 'pond_frac', nbp_glo, 1, 1, kjit, pond_frac, 'scatter',  nbp_glo, index_g)
878    CALL restput_p (rest_id, 'flood_frac', nbp_glo, 1, 1, kjit, flood_frac, 'scatter',  nbp_glo, index_g)
879    CALL restput_p (rest_id, 'flood_res', nbp_glo, 1, 1, kjit, flood_res, 'scatter', nbp_glo, index_g)
880
881    CALL restput_p (rest_id, 'lakeres', nbp_glo, 1, 1, kjit, lake_reservoir, 'scatter',  nbp_glo, index_g)
882    CALL restput_p (rest_id, 'pondres', nbp_glo, 1, 1, kjit, pond_reservoir, 'scatter',  nbp_glo, index_g)
883
884    CALL restput_p (rest_id, 'lakeinflow', nbp_glo, 1, 1, kjit, lakeinflow_mean, 'scatter',  nbp_glo, index_g)
885    CALL restput_p (rest_id, 'returnflow', nbp_glo, 1, 1, kjit, returnflow_mean, 'scatter',  nbp_glo, index_g)
886    CALL restput_p (rest_id, 'reinfiltration', nbp_glo, 1, 1, kjit, reinfiltration_mean, 'scatter',  nbp_glo, index_g)
887    CALL restput_p (rest_id, 'riverflow', nbp_glo, 1, 1, kjit, riverflow_mean, 'scatter',  nbp_glo, index_g)
888    CALL restput_p (rest_id, 'coastalflow', nbp_glo, 1, 1, kjit, coastalflow_mean, 'scatter',  nbp_glo, index_g)
889    CALL restput_p (rest_id, 'hydrographs', nbp_glo, 1, 1, kjit, hydrographs, 'scatter',  nbp_glo, index_g)
890    CALL restput_p (rest_id, 'slowflow_diag', nbp_glo, 1, 1, kjit, slowflow_diag, 'scatter',  nbp_glo, index_g)
891    !
892    ! Keep track of the accumulated variables
893    !
894    CALL restput_p (rest_id, 'floodout_route', nbp_glo, 1, 1, kjit, floodout_mean, 'scatter',  nbp_glo, index_g)
895    CALL restput_p (rest_id, 'runoff_route', nbp_glo, 1, 1, kjit, runoff_mean, 'scatter',  nbp_glo, index_g)
896    CALL restput_p (rest_id, 'drainage_route', nbp_glo, 1, 1, kjit, drainage_mean, 'scatter',  nbp_glo, index_g)
897    CALL restput_p (rest_id, 'transpot_route', nbp_glo, 1, 1, kjit, transpot_mean, 'scatter',  nbp_glo, index_g)
898    CALL restput_p (rest_id, 'precip_route', nbp_glo, 1, 1, kjit, precip_mean, 'scatter',  nbp_glo, index_g)
899    CALL restput_p (rest_id, 'humrel_route', nbp_glo, 1, 1, kjit, humrel_mean, 'scatter',  nbp_glo, index_g)
900    CALL restput_p (rest_id, 'totnobio_route', nbp_glo, 1, 1, kjit, totnobio_mean, 'scatter',  nbp_glo, index_g)
901    CALL restput_p (rest_id, 'k_litt_route', nbp_glo, 1, 1, kjit, k_litt_mean, 'scatter',  nbp_glo, index_g)
902    CALL restput_p (rest_id, 'vegtot_route', nbp_glo, 1, 1, kjit, vegtot_mean, 'scatter',  nbp_glo, index_g)
903
904    IF ( do_irrigation ) THEN
905       CALL restput_p (rest_id, 'irrigated', nbp_glo, 1, 1, kjit, irrigated, 'scatter',  nbp_glo, index_g)
906       CALL restput_p (rest_id, 'irrigation', nbp_glo, 1, 1, kjit, irrigation_mean, 'scatter',  nbp_glo, index_g)
907    ENDIF
908
909    IF ( do_floodplains ) THEN
910       CALL restput_p (rest_id, 'floodplains', nbp_glo, 1, 1, kjit, floodplains, 'scatter',  nbp_glo, index_g)
911    ENDIF
912    IF ( doswamps ) THEN
913       CALL restput_p (rest_id, 'swamp', nbp_glo, 1, 1, kjit, swamp, 'scatter',  nbp_glo, index_g)
914    ENDIF
915 
916  END SUBROUTINE routing_finalize
917
918!! ================================================================================================================================
919!! SUBROUTINE   : routing_init
920!!
921!>\BRIEF         This subroutine allocates the memory and get the fixed fields from the restart file.
922!!
923!! DESCRIPTION (definitions, functional, design, flags) : None
924!!
925!! RECENT CHANGE(S): None
926!!
927!! MAIN OUTPUT VARIABLE(S):
928!!
929!! REFERENCES   : None
930!!
931!! FLOWCHART    :None
932!! \n
933!_ ================================================================================================================================
934
935  SUBROUTINE routing_init(kjit, nbpt, index, returnflow, reinfiltration, irrigation, &
936       &                  riverflow, coastalflow, flood_frac, flood_res, stempdiag, rest_id)
937    !
938    IMPLICIT NONE
939    !
940    ! interface description
941    !
942!! INPUT VARIABLES
943    INTEGER(i_std), INTENT(in)                   :: kjit           !! Time step number (unitless)
944    INTEGER(i_std), INTENT(in)                   :: nbpt           !! Domain size (unitless)
945    INTEGER(i_std), DIMENSION (nbpt), INTENT(in) :: index          !! Indices of the points on the map (unitless)
946    REAL(r_std), DIMENSION(nbpt,nslm),INTENT(in) :: stempdiag      !! Temperature profile in soil
947    INTEGER(i_std), INTENT(in)                   :: rest_id        !! Restart file identifier (unitless)
948    !
949!! OUTPUT VARIABLES
950    REAL(r_std), DIMENSION (nbpt),INTENT(out)    :: returnflow     !! The water flow from lakes and swamps which returns into the grid box.
951                                                                   !! This water will go back into the hydrol module to allow re-evaporation (kg/m^2/dt)
952    REAL(r_std), DIMENSION (nbpt),INTENT(out)    :: reinfiltration !! Water flow from ponds and floodplains which returns to the grid box (kg/m^2/dt)
953    REAL(r_std), DIMENSION (nbpt),INTENT(out)    :: irrigation     !! Irrigation flux. This is the water taken from the reservoirs and beeing put into the upper layers of the soil.(kg/m^2/dt)
954    REAL(r_std), DIMENSION (nbpt),INTENT(out)    :: riverflow      !! Outflow of the major rivers. The flux will be located on the continental grid but this should be a coastal point (kg/dt)
955    REAL(r_std), DIMENSION (nbpt),INTENT(out)    :: coastalflow    !! Outflow on coastal points by small basins. This is the water which flows in a disperse way into the ocean (kg/dt)
956    REAL(r_std), DIMENSION (nbpt),INTENT(out)    :: flood_frac     !! Flooded fraction of the grid box (unitless;0-1)
957    REAL(r_std), DIMENSION (nbpt),INTENT(out)    :: flood_res      !! Diagnostic of water amount in the floodplains reservoir (kg)
958    !
959!! LOCAL VARIABLES
960    CHARACTER(LEN=80)                            :: var_name       !! To store variables names for I/O (unitless)
961    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)     :: tmp_real_g     !! A temporary real array for the integers
962    REAL(r_std), DIMENSION(1)                    :: tmp_day        !!
963    REAL(r_std)                                  :: ratio          !! Diagnostic ratio to check that dt_routing is a multiple of dt_sechiba (unitless)
964    REAL(r_std)                                  :: totarea        !! Total area of basin (m^2)
965    INTEGER(i_std)                               :: ier, ig, ib, ipn(1) !! Indices (unitless)
966
967!_ ================================================================================================================================
968    !
969    !
970    ! These variables will require the configuration infrastructure
971    !
972    !Config Key   = DT_ROUTING
973    !Config If    = RIVER_ROUTING
974    !Config Desc  = Time step of the routing scheme
975    !Config Def   = one_day
976    !Config Help  = This values gives the time step in seconds of the routing scheme.
977    !Config         It should be multiple of the main time step of ORCHIDEE. One day
978    !Config         is a good value.
979    !Config Units = [seconds]
980    !
981    dt_routing = one_day
982    CALL getin_p('DT_ROUTING', dt_routing)
983    !
984    !Config Key   = ROUTING_RIVERS
985    !Config If    = RIVER_ROUTING
986    !Config Desc  = Number of rivers
987    !Config Def   = 50
988    !Config Help  = This parameter chooses the number of largest river basins
989    !Config         which should be treated as independently as rivers and not
990    !Config         flow into the oceans as diffusion coastal flow.
991    !Config Units = [-]
992    num_largest = 50
993    CALL getin_p('ROUTING_RIVERS', num_largest)
994    !
995    !Config Key   = DO_FLOODINFILT
996    !Config Desc  = Should floodplains reinfiltrate into the soil
997    !Config If    = RIVER_ROUTING
998    !Config Def   = n
999    !Config Help  = This parameters allows the user to ask the model
1000    !Config         to take into account the flood plains reinfiltration
1001    !Config         into the soil moisture. It then can go
1002    !Config         back to the slow and fast reservoirs
1003    !Config Units = [FLAG]
1004    !
1005    dofloodinfilt = .FALSE.
1006    CALL getin_p('DO_FLOODINFILT', dofloodinfilt)
1007    !
1008    !Config Key   = DO_SWAMPS
1009    !Config Desc  = Should we include swamp parameterization
1010    !Config If    = RIVER_ROUTING
1011    !Config Def   = n
1012    !Config Help  = This parameters allows the user to ask the model
1013    !Config         to take into account the swamps and return
1014    !Config         the water into the bottom of the soil. It then can go
1015    !Config         back to the atmopshere. This tried to simulate
1016    !Config         internal deltas of rivers.
1017    !Config Units = [FLAG]
1018    !
1019    doswamps = .FALSE.
1020    CALL getin_p('DO_SWAMPS', doswamps)
1021    !
1022    !Config Key   = DO_PONDS
1023    !Config Desc  = Should we include ponds
1024    !Config If    = RIVER_ROUTING
1025    !Config Def   = n
1026    !Config Help  = This parameters allows the user to ask the model
1027    !Config         to take into account the ponds and return
1028    !Config         the water into the soil moisture. It then can go
1029    !Config         back to the atmopshere. This tried to simulate
1030    !Config         little ponds especially in West Africa.
1031    !Config Units = [FLAG]
1032    !
1033    doponds = .FALSE.
1034    CALL getin_p('DO_PONDS', doponds)
1035
1036
1037    !Config Key   = SLOW_TCST
1038    !Config Desc  = Time constant for the slow reservoir
1039    !Config If    = RIVER_ROUTING
1040    !Config Def   = 25.0
1041    !Config Help  = This parameters allows the user to fix the
1042    !Config         time constant (in days) of the slow reservoir
1043    !Config         in order to get better river flows for
1044    !Config         particular regions.
1045    !Config Units = [days]
1046    !
1047!> A value for property of each reservoir (in day/m) is given to compute a time constant (in day)
1048!> for each reservoir (product of tcst and topo_resid).
1049!> The value of tcst has been calibrated for the three reservoirs over the Senegal river basin only,
1050!> during the 1 degree NCEP Corrected by Cru (NCC) resolution simulations (Ngo-Duc et al., 2005, Ngo-Duc et al., 2006) and
1051!> generalized for all the basins of the world. The "slow reservoir" and the "fast reservoir"
1052!> have the highest value in order to simulate the groundwater.
1053!> The "stream reservoir", which represents all the water of the stream, has the lowest value.
1054!> Those figures are the same for all the basins of the world.
1055!> The value of slow_tcst is equal to fast_tcst when CWRR is activated.
1056!> This assumption should be re-discussed.
1057    !
1058    CALL getin_p('SLOW_TCST', slow_tcst)
1059    !
1060    !Config Key   = FAST_TCST
1061    !Config Desc  = Time constant for the fast reservoir
1062    !Config If    = RIVER_ROUTING
1063    !Config Def   = 3.0
1064    !Config Help  = This parameters allows the user to fix the
1065    !Config         time constant (in days) of the fast reservoir
1066    !Config         in order to get better river flows for
1067    !Config         particular regions.
1068    !Config Units = [days]
1069    CALL getin_p('FAST_TCST', fast_tcst)
1070   
1071    !Config Key   = STREAM_TCST
1072    !Config Desc  = Time constant for the stream reservoir
1073    !Config If    = RIVER_ROUTING
1074    !Config Def   = 0.24
1075    !Config Help  = This parameters allows the user to fix the
1076    !Config         time constant (in days) of the stream reservoir
1077    !Config         in order to get better river flows for
1078    !Config         particular regions.
1079    !Config Units = [days]
1080    CALL getin_p('STREAM_TCST', stream_tcst)
1081   
1082    !Config Key   = FLOOD_TCST
1083    !Config Desc  = Time constant for the flood reservoir
1084    !Config If    = RIVER_ROUTING
1085    !Config Def   = 4.0
1086    !Config Help  = This parameters allows the user to fix the
1087    !Config         time constant (in days) of the flood reservoir
1088    !Config         in order to get better river flows for
1089    !Config         particular regions.
1090    !Config Units = [days]
1091    CALL getin_p('FLOOD_TCST', flood_tcst)
1092   
1093    !Config Key   = SWAMP_CST
1094    !Config Desc  = Fraction of the river that flows back to swamps
1095    !Config If    = RIVER_ROUTING
1096    !Config Def   = 0.2
1097    !Config Help  = This parameters allows the user to fix the
1098    !Config         fraction of the river transport
1099    !Config         that flows to swamps
1100    !Config Units = [-]
1101    CALL getin_p('SWAMP_CST', swamp_cst)
1102   
1103    !Config Key   = FLOOD_BETA
1104    !Config Desc  = Parameter to fix the shape of the floodplain 
1105    !Config If    = RIVER_ROUTING
1106    !Config Def   = 2.0
1107    !Config Help  = Parameter to fix the shape of the floodplain
1108    !Config         (>1 for convex edges, <1 for concave edges)
1109    !Config Units = [-]
1110    CALL getin_p("FLOOD_BETA", beta)
1111    !
1112    !Config Key   = POND_BETAP
1113    !Config Desc  = Ratio of the basin surface intercepted by ponds and the maximum surface of ponds
1114    !Config If    = RIVER_ROUTING
1115    !Config Def   = 0.5
1116    !Config Help  =
1117    !Config Units = [-]
1118    CALL getin_p("POND_BETAP", betap)   
1119    !
1120    !Config Key   = FLOOD_CRI
1121    !Config Desc  = Potential height for which all the basin is flooded
1122    !Config If    = DO_FLOODPLAINS or DO_PONDS
1123    !Config Def   = 2000.
1124    !Config Help  =
1125    !Config Units = [mm]
1126    CALL getin_p("FLOOD_CRI", floodcri)
1127    !
1128    !Config Key   = POND_CRI
1129    !Config Desc  = Potential height for which all the basin is a pond
1130    !Config If    = DO_FLOODPLAINS or DO_PONDS
1131    !Config Def   = 2000.
1132    !Config Help  =
1133    !Config Units = [mm]
1134    CALL getin_p("POND_CRI", pondcri)
1135
1136    !Config Key   = MAX_LAKE_RESERVOIR
1137    !Config Desc  = Maximum limit of water in lake_reservoir
1138    !Config If    = RIVER_ROUTING
1139    !Config Def   = 7000
1140    !Config Help  =
1141    !Config Units = [kg/m2(routing area)]
1142    max_lake_reservoir = 7000
1143    CALL getin_p("MAX_LAKE_RESERVOIR", max_lake_reservoir)
1144
1145    !
1146    !
1147    ! In order to simplify the time cascade check that dt_routing
1148    ! is a multiple of dt_sechiba
1149    !
1150    ratio = dt_routing/dt_sechiba
1151    IF ( ABS(NINT(ratio) - ratio) .GT. 10*EPSILON(ratio)) THEN
1152       WRITE(numout,*) 'WARNING -- WARNING -- WARNING -- WARNING'
1153       WRITE(numout,*) "The chosen time step for the routing is not a multiple of the"
1154       WRITE(numout,*) "main time step of the model. We will change dt_routing so that"
1155       WRITE(numout,*) "this condition os fulfilled"
1156       dt_routing = NINT(ratio) * dt_sechiba
1157       WRITE(numout,*) 'THE NEW DT_ROUTING IS : ', dt_routing
1158    ENDIF
1159    !
1160    IF ( dt_routing .LT. dt_sechiba) THEN
1161       WRITE(numout,*) 'WARNING -- WARNING -- WARNING -- WARNING'
1162       WRITE(numout,*) 'The routing timestep can not be smaller than the one'
1163       WRITE(numout,*) 'of the model. We reset its value to the model''s timestep.'
1164       WRITE(numout,*) 'The old DT_ROUTING is : ', dt_routing
1165       dt_routing = dt_sechiba
1166       WRITE(numout,*) 'THE NEW DT_ROUTING IS : ', dt_routing
1167    ENDIF
1168    !
1169    var_name ="routingcounter"
1170    IF (is_root_prc) THEN
1171       CALL ioconf_setatt('UNITS', 's')
1172       CALL ioconf_setatt('LONG_NAME','Time counter for the routing scheme')
1173       CALL restget (rest_id, var_name, 1, 1, 1, kjit, .TRUE., tmp_day)
1174       IF (tmp_day(1) == val_exp) THEN
1175          ! The variable was not found in restart file, initialize to zero
1176          time_counter = zero
1177       ELSE
1178          ! Take the value from restart file
1179          time_counter = tmp_day(1) 
1180       ENDIF
1181    ENDIF
1182    CALL bcast(time_counter)
1183
1184   
1185    ALLOCATE (routing_area_loc(nbpt,nbasmax), stat=ier)
1186    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for routing_area_loc','','')
1187
1188    ALLOCATE (routing_area_glo(nbp_glo,nbasmax))
1189    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for routing_area_glo','','')
1190    var_name = 'routingarea'
1191    IF (is_root_prc) THEN
1192       CALL ioconf_setatt('UNITS', 'm^2')
1193       CALL ioconf_setatt('LONG_NAME','Area of basin')
1194       CALL restget (rest_id, var_name, nbp_glo, nbasmax, 1, kjit, .TRUE., routing_area_glo, "gather", nbp_glo, index_g)
1195    ENDIF
1196    CALL scatter(routing_area_glo,routing_area_loc)
1197    routing_area=>routing_area_loc
1198
1199    ALLOCATE (tmp_real_g(nbp_glo,nbasmax), stat=ier)
1200    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for tmp_real_g','','')
1201
1202    ALLOCATE (route_togrid_loc(nbpt,nbasmax), stat=ier)
1203    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for route_togrid_loc','','')
1204    ALLOCATE (route_togrid_glo(nbp_glo,nbasmax), stat=ier)      ! used in global in routing_flow
1205    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for route_togrid_glo','','')
1206
1207    IF (is_root_prc) THEN
1208       var_name = 'routetogrid'
1209       CALL ioconf_setatt('UNITS', '-')
1210       CALL ioconf_setatt('LONG_NAME','Grid into which the basin flows')
1211       CALL restget (rest_id, var_name, nbp_glo, nbasmax, 1, kjit, .TRUE., tmp_real_g, "gather", nbp_glo, index_g)
1212       route_togrid_glo(:,:) = undef_int
1213       WHERE ( tmp_real_g .LT. val_exp )
1214          route_togrid_glo = NINT(tmp_real_g)
1215    ENDWHERE
1216    ENDIF
1217    CALL bcast(route_togrid_glo)                      ! used in global in routing_flow
1218    CALL scatter(route_togrid_glo,route_togrid_loc)
1219    route_togrid=>route_togrid_loc
1220    !
1221    ALLOCATE (route_tobasin_loc(nbpt,nbasmax), stat=ier)
1222    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for route_tobasin_loc','','')
1223
1224    ALLOCATE (route_tobasin_glo(nbp_glo,nbasmax), stat=ier)
1225    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for route_tobasin_glo','','')
1226
1227    IF (is_root_prc) THEN
1228       var_name = 'routetobasin'
1229       CALL ioconf_setatt('UNITS', '-')
1230       CALL ioconf_setatt('LONG_NAME','Basin in to which the water goes')
1231       CALL restget (rest_id, var_name, nbp_glo, nbasmax, 1, kjit, .TRUE., tmp_real_g, "gather", nbp_glo, index_g)
1232       route_tobasin_glo = undef_int
1233       WHERE ( tmp_real_g .LT. val_exp )
1234         route_tobasin_glo = NINT(tmp_real_g)
1235      ENDWHERE
1236    ENDIF
1237    CALL scatter(route_tobasin_glo,route_tobasin_loc)
1238    route_tobasin=>route_tobasin_loc
1239    !
1240    ! nbintobasin
1241    !
1242    ALLOCATE (route_nbintobas_loc(nbpt,nbasmax), stat=ier)
1243    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for route_nbintobas_loc','','')
1244    ALLOCATE (route_nbintobas_glo(nbp_glo,nbasmax), stat=ier)
1245    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for route_nbintobas_glo','','')
1246
1247    IF (is_root_prc) THEN
1248       var_name = 'routenbintobas'
1249       CALL ioconf_setatt('UNITS', '-')
1250       CALL ioconf_setatt('LONG_NAME','Number of basin into current one')
1251       CALL restget (rest_id, var_name, nbp_glo, nbasmax, 1, kjit, .TRUE., tmp_real_g, "gather", nbp_glo, index_g)
1252       route_nbintobas_glo = undef_int
1253       WHERE ( tmp_real_g .LT. val_exp )
1254         route_nbintobas_glo = NINT(tmp_real_g)
1255      ENDWHERE
1256    ENDIF
1257    CALL scatter(route_nbintobas_glo,route_nbintobas_loc)
1258    route_nbintobas=>route_nbintobas_loc
1259    !
1260    ALLOCATE (global_basinid_loc(nbpt,nbasmax), stat=ier)
1261    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for global_basinid_loc','','')
1262    ALLOCATE (global_basinid_glo(nbp_glo,nbasmax), stat=ier)
1263    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for global_basinid_glo','','')
1264
1265    IF (is_root_prc) THEN
1266       var_name = 'basinid'
1267       CALL ioconf_setatt('UNITS', '-')
1268       CALL ioconf_setatt('LONG_NAME','ID of basin')
1269       CALL restget (rest_id, var_name, nbp_glo, nbasmax, 1, kjit, .TRUE., tmp_real_g, "gather", nbp_glo, index_g)
1270       global_basinid_glo = undef_int
1271       WHERE ( tmp_real_g .LT. val_exp )
1272          global_basinid_glo = NINT(tmp_real_g)
1273       ENDWHERE
1274    ENDIF
1275    CALL scatter(global_basinid_glo,global_basinid_loc)
1276    global_basinid=>global_basinid_loc
1277    !
1278    ALLOCATE (topo_resid_loc(nbpt,nbasmax), stat=ier)
1279    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for topo_resid_loc','','')
1280    ALLOCATE (topo_resid_glo(nbp_glo,nbasmax), stat=ier)
1281    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for topo_resid_glo','','')
1282
1283    IF (is_root_prc) THEN
1284       var_name = 'topoindex'
1285       CALL ioconf_setatt('UNITS', 'm')
1286       CALL ioconf_setatt('LONG_NAME','Topographic index of the residence time')
1287       CALL restget (rest_id, var_name, nbp_glo, nbasmax, 1, kjit, .TRUE., topo_resid_glo, "gather", nbp_glo, index_g)
1288    ENDIF
1289    CALL scatter(topo_resid_glo,topo_resid_loc)
1290    topo_resid=>topo_resid_loc
1291
1292    ALLOCATE (fast_reservoir(nbpt,nbasmax), stat=ier)
1293    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for fast_reservoir','','')
1294    var_name = 'fastres'
1295    CALL ioconf_setatt_p('UNITS', 'Kg')
1296    CALL ioconf_setatt_p('LONG_NAME','Water in the fast reservoir')
1297    CALL restget_p (rest_id, var_name, nbp_glo, nbasmax, 1, kjit, .TRUE., fast_reservoir, "gather", nbp_glo, index_g)
1298    CALL setvar_p (fast_reservoir, val_exp, 'NO_KEYWORD', zero)
1299
1300    ALLOCATE (slow_reservoir(nbpt,nbasmax), stat=ier)
1301    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for slow_reservoir','','')
1302    var_name = 'slowres'
1303    CALL ioconf_setatt_p('UNITS', 'Kg')
1304    CALL ioconf_setatt_p('LONG_NAME','Water in the slow reservoir')
1305    CALL restget_p (rest_id, var_name, nbp_glo, nbasmax, 1, kjit, .TRUE., slow_reservoir, "gather", nbp_glo, index_g)
1306    CALL setvar_p (slow_reservoir, val_exp, 'NO_KEYWORD', zero)
1307
1308    ALLOCATE (stream_reservoir(nbpt,nbasmax), stat=ier)
1309    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for stream_reservoir','','')
1310    var_name = 'streamres'
1311    CALL ioconf_setatt_p('UNITS', 'Kg')
1312    CALL ioconf_setatt_p('LONG_NAME','Water in the stream reservoir')
1313    CALL restget_p (rest_id, var_name, nbp_glo, nbasmax, 1, kjit, .TRUE., stream_reservoir, "gather", nbp_glo, index_g)
1314    CALL setvar_p (stream_reservoir, val_exp, 'NO_KEYWORD', zero)
1315
1316    ALLOCATE (flood_reservoir(nbpt,nbasmax), stat=ier)
1317    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for flood_reservoir','','')
1318    var_name = 'floodres'
1319    CALL ioconf_setatt_p('UNITS', 'Kg')
1320    CALL ioconf_setatt_p('LONG_NAME','Water in the flood reservoir')
1321    CALL restget_p (rest_id, var_name, nbp_glo, nbasmax, 1, kjit, .TRUE., flood_reservoir, "gather", nbp_glo, index_g)
1322    CALL setvar_p (flood_reservoir, val_exp, 'NO_KEYWORD', zero)
1323
1324    ALLOCATE (flood_frac_bas(nbpt,nbasmax), stat=ier)
1325    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for flood_frac_bas','','')
1326    var_name = 'flood_frac_bas'
1327    CALL ioconf_setatt_p('UNITS', '-')
1328    CALL ioconf_setatt_p('LONG_NAME','Flooded fraction per basin')
1329    CALL restget_p (rest_id, var_name, nbp_glo, nbasmax, 1, kjit, .TRUE., flood_frac_bas, "gather", nbp_glo, index_g)
1330    CALL setvar_p (flood_frac_bas, val_exp, 'NO_KEYWORD', zero)
1331
1332    ALLOCATE (flood_height(nbpt), stat=ier)
1333    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for flood_height','','')
1334    var_name = 'floodh'
1335    CALL ioconf_setatt_p('UNITS', '-')
1336    CALL ioconf_setatt_p('LONG_NAME','')
1337    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., flood_height, "gather", nbp_glo, index_g)
1338    CALL setvar_p (flood_height, val_exp, 'NO_KEYWORD', zero)
1339   
1340    ALLOCATE (pond_frac(nbpt), stat=ier)
1341    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for pond_frac','','')
1342    var_name = 'pond_frac'
1343    CALL ioconf_setatt_p('UNITS', '-')
1344    CALL ioconf_setatt_p('LONG_NAME','Pond fraction per grid box')
1345    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., pond_frac, "gather", nbp_glo, index_g)
1346    CALL setvar_p (pond_frac, val_exp, 'NO_KEYWORD', zero)
1347   
1348    var_name = 'flood_frac'
1349    CALL ioconf_setatt_p('UNITS', '-')
1350    CALL ioconf_setatt_p('LONG_NAME','Flooded fraction per grid box')
1351    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., flood_frac, "gather", nbp_glo, index_g)
1352    CALL setvar_p (flood_frac, val_exp, 'NO_KEYWORD', zero)
1353   
1354    var_name = 'flood_res'
1355    CALL ioconf_setatt_p('UNITS','mm')
1356    CALL ioconf_setatt_p('LONG_NAME','Flooded quantity (estimation)')
1357    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., flood_res, "gather", nbp_glo, index_g)
1358    CALL setvar_p (flood_res, val_exp, 'NO_KEYWORD', zero)
1359!    flood_res = zero
1360   
1361    ALLOCATE (lake_reservoir(nbpt), stat=ier)
1362    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for lake_reservoir','','')
1363    var_name = 'lakeres'
1364    CALL ioconf_setatt_p('UNITS', 'Kg')
1365    CALL ioconf_setatt_p('LONG_NAME','Water in the lake reservoir')
1366    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., lake_reservoir, "gather", nbp_glo, index_g)
1367    CALL setvar_p (lake_reservoir, val_exp, 'NO_KEYWORD', zero)
1368   
1369    ALLOCATE (pond_reservoir(nbpt), stat=ier)
1370    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for pond_reservoir','','')
1371    var_name = 'pondres'
1372    CALL ioconf_setatt_p('UNITS', 'Kg')
1373    CALL ioconf_setatt_p('LONG_NAME','Water in the pond reservoir')
1374    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., pond_reservoir, "gather", nbp_glo, index_g)
1375    CALL setvar_p (pond_reservoir, val_exp, 'NO_KEYWORD', zero)
1376    !
1377    ! Map of irrigated areas
1378    !
1379    IF ( do_irrigation ) THEN
1380       ALLOCATE (irrigated(nbpt), stat=ier)
1381       IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for irrigated','','')
1382       var_name = 'irrigated'
1383       CALL ioconf_setatt_p('UNITS', 'm^2')
1384       CALL ioconf_setatt_p('LONG_NAME','Surface of irrigated area')
1385       CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., irrigated, "gather", nbp_glo, index_g)
1386       CALL setvar_p (irrigated, val_exp, 'NO_KEYWORD', undef_sechiba)
1387    ENDIF
1388   
1389    IF ( do_floodplains ) THEN
1390       ALLOCATE (floodplains(nbpt), stat=ier)
1391       IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for floodplains','','')
1392       var_name = 'floodplains'
1393       CALL ioconf_setatt_p('UNITS', 'm^2')
1394       CALL ioconf_setatt_p('LONG_NAME','Surface which can be flooded')
1395       CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., floodplains, "gather", nbp_glo, index_g)
1396       CALL setvar_p (floodplains, val_exp, 'NO_KEYWORD', undef_sechiba)
1397    ENDIF
1398    IF ( doswamps ) THEN
1399       ALLOCATE (swamp(nbpt), stat=ier)
1400       IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for swamp','','')
1401       var_name = 'swamp'
1402       CALL ioconf_setatt_p('UNITS', 'm^2')
1403       CALL ioconf_setatt_p('LONG_NAME','Surface which can become swamp')
1404       CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., swamp, "gather", nbp_glo, index_g)
1405       CALL setvar_p (swamp, val_exp, 'NO_KEYWORD', undef_sechiba)
1406    ENDIF
1407    !
1408    ! Put into the restart file the fluxes so that they can be regenerated at restart.
1409    !
1410    ALLOCATE (lakeinflow_mean(nbpt), stat=ier)
1411    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for lakeinflow_mean','','')
1412    var_name = 'lakeinflow'
1413    CALL ioconf_setatt_p('UNITS', 'Kg/dt')
1414    CALL ioconf_setatt_p('LONG_NAME','Lake inflow')
1415    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., lakeinflow_mean, "gather", nbp_glo, index_g)
1416    CALL setvar_p (lakeinflow_mean, val_exp, 'NO_KEYWORD', zero)
1417   
1418    ALLOCATE (returnflow_mean(nbpt), stat=ier)
1419    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for returnflow_mean','','')
1420    var_name = 'returnflow'
1421    CALL ioconf_setatt_p('UNITS', 'Kg/m^2/dt')
1422    CALL ioconf_setatt_p('LONG_NAME','Deep return flux')
1423    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., returnflow_mean, "gather", nbp_glo, index_g)
1424    CALL setvar_p (returnflow_mean, val_exp, 'NO_KEYWORD', zero)
1425    returnflow(:) = returnflow_mean(:)
1426   
1427    ALLOCATE (reinfiltration_mean(nbpt), stat=ier)
1428    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for reinfiltration_mean','','')
1429    var_name = 'reinfiltration'
1430    CALL ioconf_setatt_p('UNITS', 'Kg/m^2/dt')
1431    CALL ioconf_setatt_p('LONG_NAME','Top return flux')
1432    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., reinfiltration_mean, "gather", nbp_glo, index_g)
1433    CALL setvar_p (reinfiltration_mean, val_exp, 'NO_KEYWORD', zero)
1434    reinfiltration(:) = reinfiltration_mean(:)
1435   
1436    ALLOCATE (irrigation_mean(nbpt), stat=ier)
1437    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for irrigation_mean','','')
1438    ALLOCATE (irrig_netereq(nbpt), stat=ier)
1439    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for irrig_netereq','','')
1440    irrig_netereq(:) = zero
1441   
1442    IF ( do_irrigation ) THEN
1443       var_name = 'irrigation'
1444       CALL ioconf_setatt_p('UNITS', 'Kg/dt')
1445       CALL ioconf_setatt_p('LONG_NAME','Artificial irrigation flux')
1446       CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., irrigation_mean, "gather", nbp_glo, index_g)
1447       CALL setvar_p (irrigation_mean, val_exp, 'NO_KEYWORD', zero)
1448    ELSE
1449       irrigation_mean(:) = zero
1450    ENDIF
1451    irrigation(:) = irrigation_mean(:) 
1452   
1453    ALLOCATE (riverflow_mean(nbpt), stat=ier)
1454    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for riverflow_mean','','')
1455    var_name = 'riverflow'
1456    CALL ioconf_setatt_p('UNITS', 'Kg/dt')
1457    CALL ioconf_setatt_p('LONG_NAME','River flux into the sea')
1458    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., riverflow_mean, "gather", nbp_glo, index_g)
1459    CALL setvar_p (riverflow_mean, val_exp, 'NO_KEYWORD', zero)
1460    riverflow(:) = riverflow_mean(:)
1461   
1462    ALLOCATE (coastalflow_mean(nbpt), stat=ier)
1463    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for coastalflow_mean','','')
1464    var_name = 'coastalflow'
1465    CALL ioconf_setatt_p('UNITS', 'Kg/dt')
1466    CALL ioconf_setatt_p('LONG_NAME','Diffuse flux into the sea')
1467    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., coastalflow_mean, "gather", nbp_glo, index_g)
1468    CALL setvar_p (coastalflow_mean, val_exp, 'NO_KEYWORD', zero)
1469    coastalflow(:) = coastalflow_mean(:)
1470   
1471    ! Locate it at the 2m level
1472    ipn = MINLOC(ABS(diaglev-2))
1473    floodtemp_lev = ipn(1)
1474    ALLOCATE (floodtemp(nbpt), stat=ier)
1475    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for floodtemp','','')
1476    floodtemp(:) = stempdiag(:,floodtemp_lev)
1477   
1478    ALLOCATE(hydrographs(nbpt), stat=ier)
1479    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for hydrographs','','')
1480    var_name = 'hydrographs'
1481    CALL ioconf_setatt_p('UNITS', 'kg/dt_sechiba')
1482    CALL ioconf_setatt_p('LONG_NAME','Hydrograph at outlow of grid')
1483    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., hydrographs, "gather", nbp_glo, index_g)
1484    CALL setvar_p (hydrographs, val_exp, 'NO_KEYWORD', zero)
1485 
1486    ALLOCATE(slowflow_diag(nbpt), stat=ier)
1487    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for slowflow_diag','','')
1488    var_name = 'slowflow_diag'
1489    CALL ioconf_setatt_p('UNITS', 'kg/dt_sechiba')
1490    CALL ioconf_setatt_p('LONG_NAME','Slowflow hydrograph at outlow of grid')
1491    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE.,slowflow_diag, "gather", nbp_glo, index_g)
1492    CALL setvar_p (slowflow_diag, val_exp, 'NO_KEYWORD', zero)
1493
1494    !
1495    ! The diagnostic variables, they are initialized from the above restart variables.
1496    !
1497    ALLOCATE(fast_diag(nbpt), slow_diag(nbpt), stream_diag(nbpt), flood_diag(nbpt), &
1498         & pond_diag(nbpt), lake_diag(nbpt), stat=ier)
1499    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for fast_diag,..','','')
1500   
1501    fast_diag(:) = zero
1502    slow_diag(:) = zero
1503    stream_diag(:) = zero
1504    flood_diag(:) = zero
1505    pond_diag(:) = zero
1506    lake_diag(:) = zero
1507   
1508    DO ig=1,nbpt
1509       totarea = zero
1510       DO ib=1,nbasmax
1511          totarea = totarea + routing_area(ig,ib)
1512          fast_diag(ig) = fast_diag(ig) + fast_reservoir(ig,ib)
1513          slow_diag(ig) = slow_diag(ig) + slow_reservoir(ig,ib)
1514          stream_diag(ig) = stream_diag(ig) + stream_reservoir(ig,ib)
1515          flood_diag(ig) = flood_diag(ig) + flood_reservoir(ig,ib)
1516       ENDDO
1517       !
1518       fast_diag(ig) = fast_diag(ig)/totarea
1519       slow_diag(ig) = slow_diag(ig)/totarea
1520       stream_diag(ig) = stream_diag(ig)/totarea
1521       flood_diag(ig) = flood_diag(ig)/totarea
1522       !
1523       ! This is the volume of the lake scaled to the entire grid.
1524       ! It would be better to scale it to the size of the lake
1525       ! but this information is not yet available.
1526       !
1527       lake_diag(ig) = lake_reservoir(ig)/totarea
1528       !
1529    ENDDO
1530    !
1531    ! Get from the restart the fluxes we accumulated.
1532    !
1533    ALLOCATE (floodout_mean(nbpt), stat=ier)
1534    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for floodout_mean','','')
1535    var_name = 'floodout_route'
1536    CALL ioconf_setatt_p('UNITS', 'Kg')
1537    CALL ioconf_setatt_p('LONG_NAME','Accumulated flow out of floodplains for routing')
1538    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., floodout_mean, "gather", nbp_glo, index_g)
1539    CALL setvar_p (floodout_mean, val_exp, 'NO_KEYWORD', zero)
1540   
1541    ALLOCATE (runoff_mean(nbpt), stat=ier)
1542    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for runoff_mean','','')
1543    var_name = 'runoff_route'
1544    CALL ioconf_setatt_p('UNITS', 'Kg')
1545    CALL ioconf_setatt_p('LONG_NAME','Accumulated runoff for routing')
1546    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., runoff_mean, "gather", nbp_glo, index_g)
1547    CALL setvar_p (runoff_mean, val_exp, 'NO_KEYWORD', zero)
1548   
1549    ALLOCATE(drainage_mean(nbpt), stat=ier)
1550    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for drainage_mean','','')
1551    var_name = 'drainage_route'
1552    CALL ioconf_setatt_p('UNITS', 'Kg')
1553    CALL ioconf_setatt_p('LONG_NAME','Accumulated drainage for routing')
1554    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., drainage_mean, "gather", nbp_glo, index_g)
1555    CALL setvar_p (drainage_mean, val_exp, 'NO_KEYWORD', zero)
1556   
1557    ALLOCATE(transpot_mean(nbpt), stat=ier)
1558    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for transpot_mean','','')
1559    var_name = 'transpot_route'
1560    CALL ioconf_setatt_p('UNITS', 'Kg/m^2')
1561    CALL ioconf_setatt_p('LONG_NAME','Accumulated potential transpiration for routing/irrigation')
1562    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., transpot_mean, "gather", nbp_glo, index_g)
1563    CALL setvar_p (transpot_mean, val_exp, 'NO_KEYWORD', zero)
1564
1565    ALLOCATE(precip_mean(nbpt), stat=ier)
1566    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for precip_mean','','')
1567    var_name = 'precip_route'
1568    CALL ioconf_setatt_p('UNITS', 'Kg/m^2')
1569    CALL ioconf_setatt_p('LONG_NAME','Accumulated rain precipitation for irrigation')
1570    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., precip_mean, "gather", nbp_glo, index_g)
1571    CALL setvar_p (precip_mean, val_exp, 'NO_KEYWORD', zero)
1572   
1573    ALLOCATE(humrel_mean(nbpt), stat=ier)
1574    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for humrel_mean','','')
1575    var_name = 'humrel_route'
1576    CALL ioconf_setatt_p('UNITS', '-')
1577    CALL ioconf_setatt_p('LONG_NAME','Mean humrel for irrigation')
1578    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., humrel_mean, "gather", nbp_glo, index_g)
1579    CALL setvar_p (humrel_mean, val_exp, 'NO_KEYWORD', un)
1580   
1581    ALLOCATE(k_litt_mean(nbpt), stat=ier)
1582    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for k_litt_mean','','')
1583    var_name = 'k_litt_route'
1584    CALL ioconf_setatt_p('UNITS', '-')
1585    CALL ioconf_setatt_p('LONG_NAME','Mean cond. for litter')
1586    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., k_litt_mean, "gather", nbp_glo, index_g)
1587    CALL setvar_p (k_litt_mean, val_exp, 'NO_KEYWORD', zero)
1588   
1589    ALLOCATE(totnobio_mean(nbpt), stat=ier)
1590    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for totnobio_mean','','')
1591    var_name = 'totnobio_route'
1592    CALL ioconf_setatt_p('UNITS', '-')
1593    CALL ioconf_setatt_p('LONG_NAME','Last Total fraction of no bio for irrigation')
1594    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., totnobio_mean, "gather", nbp_glo, index_g)
1595    CALL setvar_p (totnobio_mean, val_exp, 'NO_KEYWORD', zero)
1596   
1597    ALLOCATE(vegtot_mean(nbpt), stat=ier)
1598    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for vegtot_mean','','')
1599    var_name = 'vegtot_route'
1600    CALL ioconf_setatt_p('UNITS', '-')
1601    CALL ioconf_setatt_p('LONG_NAME','Last Total fraction of vegetation')
1602    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., vegtot_mean, "gather", nbp_glo, index_g)
1603    CALL setvar_p (vegtot_mean, val_exp, 'NO_KEYWORD', un)
1604    !
1605    !
1606    DEALLOCATE(tmp_real_g)
1607    !
1608    ! Allocate diagnostic variables
1609    !
1610    ALLOCATE(hydrodiag_loc(nbpt,nbasmax),hydrodiag_glo(nbp_glo,nbasmax),stat=ier)
1611    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for hydrodiag_glo','','')
1612    hydrodiag=>hydrodiag_loc
1613
1614    ALLOCATE(hydroupbasin_loc(nbpt),hydroupbasin_glo(nbp_glo), stat=ier)
1615    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for hydroupbasin_glo','','')
1616    hydroupbasin=>hydroupbasin_loc
1617
1618  END SUBROUTINE routing_init
1619  !
1620!! ================================================================================================================================
1621!! SUBROUTINE   : routing_clear
1622!!
1623!>\BRIEF        : This subroutine deallocates the block memory previously allocated.
1624!! \n
1625!_ ================================================================================================================================
1626
1627  SUBROUTINE routing_clear()
1628
1629    IF (ALLOCATED(routing_area_loc)) DEALLOCATE(routing_area_loc)
1630    IF (ALLOCATED(route_togrid_loc)) DEALLOCATE(route_togrid_loc)
1631    IF (ALLOCATED(route_tobasin_loc)) DEALLOCATE(route_tobasin_loc)
1632    IF (ALLOCATED(route_nbintobas_loc)) DEALLOCATE(route_nbintobas_loc)
1633    IF (ALLOCATED(global_basinid_loc)) DEALLOCATE(global_basinid_loc)
1634    IF (ALLOCATED(topo_resid_loc)) DEALLOCATE(topo_resid_loc)
1635    IF (ALLOCATED(routing_area_glo)) DEALLOCATE(routing_area_glo)
1636    IF (ALLOCATED(route_togrid_glo)) DEALLOCATE(route_togrid_glo)
1637    IF (ALLOCATED(route_tobasin_glo)) DEALLOCATE(route_tobasin_glo)
1638    IF (ALLOCATED(route_nbintobas_glo)) DEALLOCATE(route_nbintobas_glo)
1639    IF (ALLOCATED(global_basinid_glo)) DEALLOCATE(global_basinid_glo)
1640    IF (ALLOCATED(topo_resid_glo)) DEALLOCATE(topo_resid_glo)
1641    IF (ALLOCATED(fast_reservoir)) DEALLOCATE(fast_reservoir)
1642    IF (ALLOCATED(slow_reservoir)) DEALLOCATE(slow_reservoir)
1643    IF (ALLOCATED(stream_reservoir)) DEALLOCATE(stream_reservoir)
1644    IF (ALLOCATED(flood_reservoir)) DEALLOCATE(flood_reservoir)
1645    IF (ALLOCATED(flood_frac_bas)) DEALLOCATE(flood_frac_bas)
1646    IF (ALLOCATED(flood_height)) DEALLOCATE(flood_height)
1647    IF (ALLOCATED(pond_frac)) DEALLOCATE(pond_frac)
1648    IF (ALLOCATED(lake_reservoir)) DEALLOCATE(lake_reservoir)
1649    IF (ALLOCATED(pond_reservoir)) DEALLOCATE(pond_reservoir)
1650    IF (ALLOCATED(returnflow_mean)) DEALLOCATE(returnflow_mean)
1651    IF (ALLOCATED(reinfiltration_mean)) DEALLOCATE(reinfiltration_mean)
1652    IF (ALLOCATED(riverflow_mean)) DEALLOCATE(riverflow_mean)
1653    IF (ALLOCATED(coastalflow_mean)) DEALLOCATE(coastalflow_mean)
1654    IF (ALLOCATED(lakeinflow_mean)) DEALLOCATE(lakeinflow_mean)
1655    IF (ALLOCATED(runoff_mean)) DEALLOCATE(runoff_mean)
1656    IF (ALLOCATED(floodout_mean)) DEALLOCATE(floodout_mean)
1657    IF (ALLOCATED(drainage_mean)) DEALLOCATE(drainage_mean)
1658    IF (ALLOCATED(transpot_mean)) DEALLOCATE(transpot_mean)
1659    IF (ALLOCATED(precip_mean)) DEALLOCATE(precip_mean)
1660    IF (ALLOCATED(humrel_mean)) DEALLOCATE(humrel_mean)
1661    IF (ALLOCATED(k_litt_mean)) DEALLOCATE(k_litt_mean)
1662    IF (ALLOCATED(totnobio_mean)) DEALLOCATE(totnobio_mean)
1663    IF (ALLOCATED(vegtot_mean)) DEALLOCATE(vegtot_mean)
1664    IF (ALLOCATED(floodtemp)) DEALLOCATE(floodtemp)
1665    IF (ALLOCATED(hydrodiag_loc)) DEALLOCATE(hydrodiag_loc)
1666    IF (ALLOCATED(hydrodiag_glo)) DEALLOCATE(hydrodiag_glo)
1667    IF (ALLOCATED(hydroupbasin_loc)) DEALLOCATE(hydroupbasin_loc)   
1668    IF (ALLOCATED(hydroupbasin_glo)) DEALLOCATE(hydroupbasin_glo)
1669    IF (ALLOCATED(hydrographs)) DEALLOCATE(hydrographs)
1670    IF (ALLOCATED(slowflow_diag)) DEALLOCATE(slowflow_diag)
1671    IF (ALLOCATED(irrigation_mean)) DEALLOCATE(irrigation_mean)
1672    IF (ALLOCATED(irrigated)) DEALLOCATE(irrigated)
1673    IF (ALLOCATED(floodplains)) DEALLOCATE(floodplains)
1674    IF (ALLOCATED(swamp)) DEALLOCATE(swamp)
1675    IF (ALLOCATED(fast_diag)) DEALLOCATE(fast_diag)
1676    IF (ALLOCATED(slow_diag)) DEALLOCATE(slow_diag)
1677    IF (ALLOCATED(stream_diag)) DEALLOCATE(stream_diag)
1678    IF (ALLOCATED(flood_diag)) DEALLOCATE(flood_diag)
1679    IF (ALLOCATED(pond_diag)) DEALLOCATE(pond_diag)
1680    IF (ALLOCATED(lake_diag)) DEALLOCATE(lake_diag)
1681
1682  END SUBROUTINE routing_clear
1683  !
1684
1685!! ================================================================================================================================
1686!! SUBROUTINE   : routing_flow
1687!!
1688!>\BRIEF         This subroutine computes the transport of water in the various reservoirs
1689!!                (including ponds and floodplains) and the water withdrawals from the reservoirs for irrigation.
1690!!
1691!! DESCRIPTION (definitions, functional, design, flags) :
1692!! This will first compute the amount of water which flows out of each of the 3 reservoirs using the assumption of an
1693!! exponential decrease of water in the reservoir (see Hagemann S and Dumenil L. (1998)). Then we compute the fluxes
1694!! for floodplains and ponds. All this will then be used in order to update each of the basins : taking water out of
1695!! the up-stream basin and adding it to the down-stream one.
1696!! As this step happens globaly we have to stop the parallel processing in order to exchange the information. Once
1697!! all reservoirs are updated we deal with irrigation. The final step is to compute diagnostic fluxes. Among them
1698!! the hydrographs of the largest rivers we have chosen to monitor.
1699!!
1700!! RECENT CHANGE(S): None
1701!!
1702!! MAIN OUTPUT VARIABLE(S): lakeinflow, returnflow, reinfiltration, irrigation, riverflow, coastalflow, hydrographs, flood_frac, flood_res
1703!!
1704!! REFERENCES   :
1705!! - Ngo-Duc, T., K. Laval, G. Ramillien, J. Polcher, and A. Cazenave (2007)
1706!!   Validation of the land water storage simulated by Organising Carbon and Hydrology in Dynamic Ecosystems (ORCHIDEE) with Gravity Recovery and Climate Experiment (GRACE) data.
1707!!   Water Resour. Res., 43, W04427, doi:10.1029/2006WR004941.
1708!! * Irrigation:
1709!! - de Rosnay, P., J. Polcher, K. Laval, and M. Sabre (2003)
1710!!   Integrated parameterization of irrigation in the land surface model ORCHIDEE. Validation over Indian Peninsula.
1711!!   Geophys. Res. Lett., 30(19), 1986, doi:10.1029/2003GL018024.
1712!! - A.C. Vivant (2003)
1713!!   Les plaines d'inondations et l'irrigation dans ORCHIDEE, impacts de leur prise en compte.
1714!!   , , 51pp.
1715!! - N. Culson (2004)
1716!!   Impact de l'irrigation sur le cycle de l'eau
1717!!   Master thesis, Paris VI University, 55pp.
1718!! - X.-T. Nguyen-Vinh (2005)
1719!!   Analyse de l'impact de l'irrigation en Amerique du Nord - plaine du Mississippi - sur la climatologie regionale
1720!!   Master thesis, Paris VI University, 33pp.
1721!! - M. Guimberteau (2006)
1722!!   Analyse et modifications proposees de la modelisation de l'irrigation dans un modele de surface.
1723!!   Master thesis, Paris VI University, 46pp.
1724!! - Guimberteau M. (2010)
1725!!   Modelisation de l'hydrologie continentale et influences de l'irrigation sur le cycle de l'eau.
1726!!   Ph.D. thesis, Paris VI University, 195pp.
1727!! - Guimberteau M., Laval K., Perrier A. and Polcher J. (2011).
1728!!   Global effect of irrigation and its impact on the onset of the Indian summer monsoon.
1729!!   In press, Climate Dynamics, doi: 10.1007/s00382-011-1252-5.
1730!! * Floodplains:
1731!! - A.C. Vivant (2002)
1732!!   L'ecoulement lateral de l'eau sur les surfaces continentales. Prise en compte des plaines d'inondations dans ORCHIDEE.
1733!!   Master thesis, Paris VI University, 46pp.
1734!! - A.C. Vivant (2003)
1735!!   Les plaines d'inondations et l'irrigation dans ORCHIDEE, impacts de leur prise en compte.
1736!!   , , 51pp.
1737!! - T. d'Orgeval (2006)
1738!!   Impact du changement climatique sur le cycle de l'eau en Afrique de l'Ouest: modelisation et incertitudes.
1739!!   Ph.D. thesis, Paris VI University, 188pp.
1740!! - T. d'Orgeval, J. Polcher, and P. de Rosnay (2008)
1741!!   Sensitivity of the West African hydrological cycle in ORCHIDEE to infiltration processes.
1742!!   Hydrol. Earth Syst. Sci., 12, 1387-1401
1743!! - M. Guimberteau, G. Drapeau, J. Ronchail, B. Sultan, J. Polcher, J.-M. Martinez, C. Prigent, J.-L. Guyot, G. Cochonneau,
1744!!   J. C. Espinoza, N. Filizola, P. Fraizy, W. Lavado, E. De Oliveira, R. Pombosa, L. Noriega, and P. Vauchel (2011)
1745!!   Discharge simulation in the sub-basins of the Amazon using ORCHIDEE forced by new datasets.
1746!!   Hydrol. Earth Syst. Sci. Discuss., 8, 11171-11232, doi:10.5194/hessd-8-11171-2011
1747!!
1748!! FLOWCHART    :None
1749!! \n
1750!_ ================================================================================================================================
1751
1752  SUBROUTINE routing_flow(nbpt, dt_routing, lalo, floodout, runoff, drainage, &
1753       &                  vegtot, totnobio, transpot_mean, precip, humrel, k_litt, floodtemp, reinf_slope, &
1754       &                  lakeinflow, returnflow, reinfiltration, irrigation, riverflow, &
1755       &                  coastalflow, hydrographs, slowflow_diag, flood_frac, flood_res, &
1756                          netflow_stream_diag, netflow_fast_diag, netflow_slow_diag)
1757    !
1758    IMPLICIT NONE
1759    !
1760!! INPUT VARIABLES
1761    INTEGER(i_std), INTENT(in)                   :: nbpt                      !! Domain size (unitless)
1762    REAL(r_std), INTENT (in)                     :: dt_routing                !! Routing time step (s)
1763    REAL(r_std), INTENT(in)                      :: lalo(nbpt,2)              !! Vector of latitude and longitudes
1764    REAL(r_std), INTENT(in)                      :: runoff(nbpt)              !! Grid-point runoff (kg/m^2/dt)
1765    REAL(r_std), INTENT(in)                      :: floodout(nbpt)            !! Grid-point flow out of floodplains (kg/m^2/dt)
1766    REAL(r_std), INTENT(in)                      :: drainage(nbpt)            !! Grid-point drainage (kg/m^2/dt)
1767    REAL(r_std), INTENT(in)                      :: vegtot(nbpt)              !! Potentially vegetated fraction (unitless;0-1)
1768    REAL(r_std), INTENT(in)                      :: totnobio(nbpt)            !! Other areas which can not have vegetation
1769    REAL(r_std), INTENT(in)                      :: transpot_mean(nbpt)       !! Mean potential transpiration of the vegetation (kg/m^2/dt)
1770    REAL(r_std), INTENT(in)                      :: precip(nbpt)              !! Rainfall (kg/m^2/dt)
1771    REAL(r_std), INTENT(in)                      :: humrel(nbpt)              !! Soil moisture stress, root extraction potential (unitless)
1772    REAL(r_std), INTENT(in)                      :: k_litt(nbpt)              !! Averaged conductivity for saturated infiltration in the 'litter' layer (kg/m^2/dt)
1773    REAL(r_std), INTENT(in)                      :: floodtemp(nbpt)           !! Temperature to decide if floodplains work (K)
1774    REAL(r_std), INTENT(in)                      :: reinf_slope(nbpt)         !! Coefficient which determines the reinfiltration ratio in the grid box due to flat areas (unitless;0-1)
1775    REAL(r_std), INTENT(out)                     :: lakeinflow(nbpt)          !! Water inflow to the lakes (kg/dt)
1776    !
1777!! OUTPUT VARIABLES
1778    REAL(r_std), INTENT(out)                     :: returnflow(nbpt)          !! The water flow from lakes and swamps which returns into the grid box.
1779                                                                              !! This water will go back into the hydrol module to allow re-evaporation (kg/m^2/dt_routing)
1780    REAL(r_std), INTENT(out)                     :: reinfiltration(nbpt)      !! Water flow from ponds and floodplains which returns to the grid box (kg/m^2/dt)
1781    REAL(r_std), INTENT(out)                     :: irrigation(nbpt)          !! Irrigation flux. This is the water taken from the reservoirs and beeing put into the upper layers of the soil (kg/m^2/dt_routing)
1782    REAL(r_std), INTENT(out)                     :: riverflow(nbpt)           !! Outflow of the major rivers. The flux will be located on the continental grid but this should be a coastal point (kg/dt_routing)
1783    REAL(r_std), INTENT(out)                     :: coastalflow(nbpt)         !! Outflow on coastal points by small basins. This is the water which flows in a disperse way into the ocean (kg/dt_routing)
1784    REAL(r_std), INTENT(out)                     :: hydrographs(nbpt)         !! Hydrographs at the outflow of the grid box for major basins (kg/dt)
1785    REAL(r_std), INTENT(out)                     :: slowflow_diag(nbpt)       !! Hydrographs of slow_flow = routed slow_flow for major basins (kg/dt)
1786    REAL(r_std), INTENT(out)                     :: flood_frac(nbpt)          !! Flooded fraction of the grid box (unitless;0-1)
1787    REAL(r_std), INTENT(out)                     :: flood_res(nbpt)           !! Diagnostic of water amount in the floodplains reservoir (kg)
1788
1789    REAL(r_std), INTENT(out)                     :: netflow_stream_diag(nbpt) !! Input - Output flow to stream reservoir
1790    REAL(r_std), INTENT(out)                     :: netflow_fast_diag(nbpt)   !! Input - Output flow to fast reservoir
1791    REAL(r_std), INTENT(out)                     :: netflow_slow_diag(nbpt)   !! Input - Output flow to slow reservoir
1792    !
1793!! LOCAL VARIABLES
1794    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: fast_flow                 !! Outflow from the fast reservoir (kg/dt)
1795    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: slow_flow                 !! Outflow from the slow reservoir (kg/dt)
1796    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: stream_flow               !! Outflow from the stream reservoir (kg/dt)
1797    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: flood_flow                !! Outflow from the floodplain reservoir (kg/dt)
1798    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: pond_inflow               !! Inflow to the pond reservoir (kg/dt)
1799    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: pond_drainage             !! Drainage from pond (kg/m^2/dt)
1800    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: flood_drainage            !! Drainage from floodplains (kg/m^2/dt)
1801    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: return_swamp              !! Inflow to the swamp (kg/dt)
1802    !
1803    ! Irrigation per basin
1804    !
1805    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: irrig_needs               !! Total irrigation requirement (water requirements by the crop for its optimal growth) (kg)
1806    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: irrig_actual              !! Possible irrigation according to the water availability in the reservoirs (kg)
1807    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: irrig_deficit             !! Amount of water missing for irrigation (kg)
1808    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: irrig_adduct              !! Amount of water carried over from other basins for irrigation (kg)
1809    !
1810    REAL(r_std), DIMENSION(nbpt, 0:nbasmax+3)    :: transport                 !! Water transport between basins (kg/dt)
1811    REAL(r_std), DIMENSION(nbp_glo, 0:nbasmax+3) :: transport_glo             !! Water transport between basins (kg/dt)
1812    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: floods                    !! Water flow in to the floodplains (kg/dt)
1813    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: potflood                  !! Potential inflow to the swamps (kg/dt)
1814    REAL(r_std), DIMENSION(nbpt)                 :: tobeflooded               !! Maximal surface which can be inundated in each grid box (m^2)
1815    REAL(r_std), DIMENSION(nbpt)                 :: totarea                   !! Total area of basin (m^2)
1816    REAL(r_std), DIMENSION(nbpt)                 :: totflood                  !! Total amount of water in the floodplains reservoir (kg)
1817    REAL(r_std), DIMENSION(nbasmax)              :: pond_excessflow           !!
1818    REAL(r_std)                                  :: flow                      !! Outflow computation for the reservoirs (kg/dt)
1819    REAL(r_std)                                  :: floodindex                !! Fraction of grid box area inundated (unitless;0-1)
1820    REAL(r_std)                                  :: pondex                    !!
1821    REAL(r_std)                                  :: flood_frac_pot            !! Total fraction of the grid box which is flooded at optimum repartition (unitless;0-1)
1822    REAL(r_std)                                  :: stream_tot                !! Total water amount in the stream reservoirs (kg)
1823    REAL(r_std)                                  :: adduction                 !! Importation of water from a stream reservoir of a neighboring grid box (kg)
1824    REAL(r_std), DIMENSION(nbp_glo)              :: lake_overflow_g           !! Removed water from lake reservoir on global grid (kg/gridcell/dt_routing)
1825    REAL(r_std), DIMENSION(nbpt)                 :: lake_overflow             !! Removed water from lake reservoir on local grid (kg/gridcell/dt_routing)
1826    REAL(r_std), DIMENSION(nbpt)                 :: lake_overflow_coast       !! lake_overflow distributed on coast gridcells, only diag(kg/gridcell/dt_routing)
1827    REAL(r_std)                                  :: total_lake_overflow       !! Sum of lake_overflow over full grid (kg)
1828    REAL(r_std), DIMENSION(8,nbasmax)            :: streams_around            !! Stream reservoirs of the neighboring grid boxes (kg)
1829    INTEGER(i_std), DIMENSION(8)                 :: igrd                      !!
1830    INTEGER(i_std), DIMENSION(2)                 :: ff                        !!
1831    INTEGER(i_std), DIMENSION(1)                 :: fi                        !!
1832    INTEGER(i_std)                               :: ig, ib, ib2, ig2          !! Indices (unitless)
1833    INTEGER(i_std)                               :: rtg, rtb, in              !! Indices (unitless)
1834    INTEGER(i_std)                               :: ier                       !! Error handling
1835    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)     :: fast_flow_g               !! Outflow from the fast reservoir (kg/dt)
1836    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)     :: slow_flow_g               !! Outflow from the slow reservoir (kg/dt)
1837    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)     :: stream_flow_g             !! Outflow from the stream reservoir (kg/dt)
1838    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)     :: irrig_deficit_glo         !! Amount of water missing for irrigation (kg)
1839    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)     :: stream_reservoir_glo      !! Water amount in the stream reservoir (kg)
1840    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)     :: irrig_adduct_glo          !! Amount of water carried over from other basins for irrigation (kg)
1841
1842    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: netflow_stream            !! Input - Output flow to stream reservoir
1843    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: netflow_fast              !! Input - Output flow to fast reservoir
1844    REAL(r_std), DIMENSION(nbpt, nbasmax)        :: netflow_slow              !! Input - Output flow to slow reservoir
1845
1846
1847    !! PARAMETERS
1848    LOGICAL, PARAMETER                           :: check_reservoir = .FALSE. !! Logical to choose if we write informations when a negative amount of water is occurring in a reservoir (true/false)
1849!_ ================================================================================================================================
1850    !
1851    transport(:,:) = zero
1852    transport_glo(:,:) = zero
1853    irrig_netereq(:) = zero
1854    irrig_needs(:,:) = zero
1855    irrig_actual(:,:) = zero
1856    irrig_deficit(:,:) = zero
1857    irrig_adduct(:,:) = zero
1858    totarea(:) = zero
1859    totflood(:) = zero
1860    !
1861    ! Compute all the fluxes
1862    !
1863    DO ib=1,nbasmax
1864       DO ig=1,nbpt
1865          !
1866          totarea(ig) = totarea(ig) + routing_area(ig,ib)
1867          totflood(ig) = totflood(ig) + flood_reservoir(ig,ib)
1868       ENDDO
1869    ENDDO
1870          !
1871!> The outflow fluxes from the three reservoirs are computed.
1872!> The outflow of volume of water Vi into the reservoir i is assumed to be linearly related to its volume.
1873!> The water travel simulated by the routing scheme is dependent on the water retention index topo_resid
1874!> given by a 0.5 degree resolution map for each pixel performed from a simplification of Manning's formula
1875!> (Dingman, 1994; Ducharne et al., 2003).
1876!> The resulting product of tcst (in day/m) and topo_resid (in m) represents the time constant (day)
1877!> which is an e-folding time, the time necessary for the water amount
1878!> in the stream reservoir to decrease by a factor e. Hence, it gives an order of
1879!> magnitude of the travel time through this reservoir between
1880!> the sub-basin considered and its downstream neighbor.
1881
1882    DO ib=1,nbasmax
1883       DO ig=1,nbpt
1884          IF ( route_tobasin(ig,ib) .GT. 0 ) THEN
1885             !
1886             ! Each of the fluxes is limited by the water in the reservoir and a small margin
1887             ! (min_reservoir) to avoid rounding errors.
1888             !
1889             flow = MIN(fast_reservoir(ig,ib)/((topo_resid(ig,ib)/1000.)*fast_tcst*one_day/dt_routing),&
1890                  & fast_reservoir(ig,ib)-min_sechiba)
1891             fast_flow(ig,ib) = MAX(flow, zero)
1892
1893             flow = MIN(slow_reservoir(ig,ib)/((topo_resid(ig,ib)/1000.)*slow_tcst*one_day/dt_routing),&
1894                  & slow_reservoir(ig,ib)-min_sechiba)
1895             slow_flow(ig,ib) = MAX(flow, zero)
1896
1897             flow = MIN(stream_reservoir(ig,ib)/((topo_resid(ig,ib)/1000.)*stream_tcst* & 
1898                  & MAX(un-SQRT(flood_frac_bas(ig,ib)),min_sechiba)*one_day/dt_routing),&
1899                  & stream_reservoir(ig,ib)-min_sechiba)
1900             stream_flow(ig,ib) = MAX(flow, zero)
1901             !
1902          ELSE
1903             fast_flow(ig,ib) = zero
1904             slow_flow(ig,ib) = zero
1905             stream_flow(ig,ib) = zero
1906          ENDIF
1907       ENDDO
1908    ENDDO
1909    !-
1910    !- Compute the fluxes out of the floodplains and ponds if they exist.
1911    !-
1912    IF (do_floodplains .OR. doponds) THEN
1913       DO ig=1,nbpt
1914          IF (flood_frac(ig) .GT. min_sechiba) THEN
1915             !
1916             flow = MIN(floodout(ig)*totarea(ig)*pond_frac(ig)/flood_frac(ig), pond_reservoir(ig)+totflood(ig))
1917             pondex = MAX(flow - pond_reservoir(ig), zero)
1918             pond_reservoir(ig) = pond_reservoir(ig) - (flow - pondex) 
1919             !
1920             ! If demand was over reservoir size, we will take it out from floodplains
1921             !
1922             pond_excessflow(:) = zero
1923             DO ib=1,nbasmax
1924                pond_excessflow(ib) = MIN(pondex*flood_frac_bas(ig,ib)/(flood_frac(ig)-pond_frac(ig)),&
1925                     &                    flood_reservoir(ig,ib))
1926                pondex = pondex - pond_excessflow(ib)
1927             ENDDO
1928             !
1929             IF ( pondex .GT. min_sechiba) THEN
1930                WRITE(numout,*) "Unable to redistribute the excess pond outflow over the water available in the floodplain."
1931                WRITE(numout,*) "Pondex = ", pondex
1932                WRITE(numout,*) "pond_excessflow(:) = ", pond_excessflow(:)
1933             ENDIF
1934             !
1935             DO ib=1,nbasmax
1936                !
1937                flow = floodout(ig)*routing_area(ig,ib)*flood_frac_bas(ig,ib)/flood_frac(ig) + pond_excessflow(ib)
1938                !
1939                flood_reservoir(ig,ib) = flood_reservoir(ig,ib) - flow
1940                !
1941                !
1942                IF (flood_reservoir(ig,ib) .LT. min_sechiba) THEN
1943                   flood_reservoir(ig,ib) = zero
1944                ENDIF
1945                IF (pond_reservoir(ig) .LT. min_sechiba) THEN
1946                   pond_reservoir(ig) = zero
1947                ENDIF
1948             ENDDO
1949          ENDIF
1950       ENDDO
1951    ENDIF
1952
1953    !-
1954    !- Computing the drainage and outflow from floodplains
1955!> Drainage from floodplains is depending on a averaged conductivity (k_litt)
1956!> for saturated infiltration in the 'litter' layer. Flood_drainage will be
1957!> a component of the total reinfiltration that leaves the routing scheme.
1958    !-
1959    IF (do_floodplains) THEN
1960       IF (dofloodinfilt) THEN
1961          DO ib=1,nbasmax
1962             DO ig=1,nbpt
1963                flood_drainage(ig,ib) = MAX(zero, MIN(flood_reservoir(ig,ib), &
1964                     & flood_frac(ig)*routing_area(ig,ib)*k_litt(ig)*dt_routing/one_day))
1965                flood_reservoir(ig,ib) = flood_reservoir(ig,ib) - flood_drainage(ig,ib)
1966             ENDDO
1967          ENDDO
1968       ELSE
1969          DO ib=1,nbasmax
1970             DO ig=1,nbpt
1971                flood_drainage(ig,ib) = zero 
1972             ENDDO
1973          ENDDO
1974       ENDIF
1975!> Outflow from floodplains is computed depending a delay. This delay is characterized by a time constant
1976!> function of the surface of the floodplains and the product of topo_resid and flood_tcst. flood_tcst
1977!> has been calibrated through observations in the Niger Inner Delta (D'Orgeval, 2006).
1978!
1979       DO ib=1,nbasmax
1980          DO ig=1,nbpt
1981             IF ( route_tobasin(ig,ib) .GT. 0 ) THEN
1982                IF (flood_frac_bas(ig,ib) .GT. min_sechiba) THEN
1983                   flow = MIN(flood_reservoir(ig,ib)  &
1984                        & /((topo_resid(ig,ib)/1000.)*flood_tcst* &
1985                        & flood_frac_bas(ig,ib)*one_day/dt_routing),&
1986                        & flood_reservoir(ig,ib))
1987                ELSE
1988                   flow = zero
1989                ENDIF
1990                flood_flow(ig,ib) = flow
1991             ELSE
1992                flood_flow(ig,ib) = zero
1993             ENDIF
1994          ENDDO
1995       ENDDO
1996    ELSE
1997       DO ib=1,nbasmax
1998          DO ig=1,nbpt
1999             flood_drainage(ig,ib) = zero
2000             flood_flow(ig,ib) = zero
2001             flood_reservoir(ig,ib) = zero
2002          ENDDO
2003       ENDDO
2004    ENDIF
2005
2006    !-
2007    !- Computing drainage and inflow for ponds
2008!> Drainage from ponds is computed in the same way than for floodplains.
2009!> Reinfiltrated fraction from the runoff (i.e. the outflow from the fast reservoir)
2010!> is the inflow of the pond reservoir.
2011    !-
2012    IF (doponds) THEN
2013       ! If used, the slope coef is not used in hydrol for water2infilt
2014       DO ib=1,nbasmax
2015          DO ig=1,nbpt
2016             pond_inflow(ig,ib) = fast_flow(ig,ib) * reinf_slope(ig)
2017             pond_drainage(ig,ib) = MIN(pond_reservoir(ig)*routing_area(ig,ib)/totarea(ig), &
2018                  & pond_frac(ig)*routing_area(ig,ib)*k_litt(ig)*dt_routing/one_day)
2019             fast_flow(ig,ib) = fast_flow(ig,ib) - pond_inflow(ig,ib) 
2020          ENDDO
2021       ENDDO
2022    ELSE
2023       DO ib=1,nbasmax
2024          DO ig=1,nbpt
2025             pond_inflow(ig,ib) = zero
2026             pond_drainage(ig,ib) = zero
2027             pond_reservoir(ig) = zero
2028          ENDDO
2029       ENDDO
2030    ENDIF
2031
2032!ym cette methode conserve les erreurs d'arrondie
2033!ym mais n'est pas la plus efficace
2034
2035    !-
2036    !- Compute the transport from one basin to another
2037    !-
2038
2039    IF (is_root_prc)  THEN
2040       ALLOCATE( fast_flow_g(nbp_glo, nbasmax), slow_flow_g(nbp_glo, nbasmax), &
2041            stream_flow_g(nbp_glo, nbasmax), stat=ier)
2042    ELSE
2043       ALLOCATE( fast_flow_g(1,1), slow_flow_g(1,1), &
2044            stream_flow_g(1, 1), stat=ier)
2045    ENDIF
2046    IF (ier /= 0) CALL ipslerr_p(3,'routing_flow','Pb in allocate for fast_flow_g','','')
2047       
2048    CALL gather(fast_flow,fast_flow_g)
2049    CALL gather(slow_flow,slow_flow_g)
2050    CALL gather(stream_flow,stream_flow_g)
2051
2052    IF (is_root_prc) THEN
2053       DO ib=1,nbasmax
2054          DO ig=1,nbp_glo
2055             !
2056             rtg = route_togrid_glo(ig,ib)
2057             rtb = route_tobasin_glo(ig,ib)
2058             transport_glo(rtg,rtb) = transport_glo(rtg,rtb) + fast_flow_g(ig,ib) + slow_flow_g(ig,ib) + &
2059                  & stream_flow_g(ig,ib)
2060             !
2061          ENDDO
2062       ENDDO
2063    ENDIF
2064
2065    DEALLOCATE( fast_flow_g, slow_flow_g, stream_flow_g )
2066   
2067    CALL scatter(transport_glo,transport)
2068
2069    !-
2070    !- Do the floodings - First initialize
2071    !-
2072    return_swamp(:,:)=zero
2073    floods(:,:)=zero
2074    !-
2075!> Over swamp areas, a fraction of water (return_swamp) is withdrawn from the river depending on the
2076!> parameter swamp_cst.
2077!> It will be transferred into soil moisture and thus does not return directly to the river.
2078    !
2079    !- 1. Swamps: Take out water from the river to put it to the swamps
2080    !-
2081    !
2082    IF ( doswamps ) THEN
2083       tobeflooded(:) = swamp(:)
2084       DO ib=1,nbasmax
2085          DO ig=1,nbpt
2086             potflood(ig,ib) = transport(ig,ib) 
2087             !
2088             IF ( tobeflooded(ig) > 0. .AND. potflood(ig,ib) > 0. .AND. floodtemp(ig) > tp_00 ) THEN
2089                !
2090                IF (routing_area(ig,ib) > tobeflooded(ig)) THEN
2091                   floodindex = tobeflooded(ig) / routing_area(ig,ib)
2092                ELSE
2093                   floodindex = 1.0
2094                ENDIF
2095                return_swamp(ig,ib) = swamp_cst * potflood(ig,ib) * floodindex
2096                !
2097                tobeflooded(ig) = tobeflooded(ig) - routing_area(ig,ib) 
2098                !
2099             ENDIF
2100          ENDDO
2101       ENDDO
2102    ENDIF
2103    !-
2104    !- 2. Floodplains: Update the reservoir with the flux computed above.
2105    !-
2106    IF ( do_floodplains ) THEN
2107       DO ig=1,nbpt
2108          IF (floodplains(ig) .GT. min_sechiba .AND. floodtemp(ig) .GT. tp_00) THEN
2109             DO ib=1,nbasmax
2110                floods(ig,ib) = transport(ig,ib) - return_swamp(ig,ib) 
2111             ENDDO
2112          ENDIF
2113       ENDDO
2114    ENDIF
2115    !
2116    ! Update all reservoirs
2117!> The slow and deep reservoir (slow_reservoir) collect the deep drainage whereas the
2118!> fast_reservoir collects the computed surface runoff. Both discharge into a third reservoir
2119!> (stream_reservoir) of the next sub-basin downstream.
2120!> Water from the floodplains reservoir (flood_reservoir) flows also into the stream_reservoir of the next sub-basin downstream.
2121!> Water that flows into the pond_reservoir is withdrawn from the fast_reservoir.
2122    !
2123    DO ig=1,nbpt
2124       DO ib=1,nbasmax
2125          !
2126          fast_reservoir(ig,ib) =  fast_reservoir(ig,ib) + runoff(ig)*routing_area(ig,ib) - &
2127               & fast_flow(ig,ib) - pond_inflow(ig,ib)
2128          !
2129          slow_reservoir(ig,ib) = slow_reservoir(ig,ib) + drainage(ig)*routing_area(ig,ib) - &
2130               & slow_flow(ig,ib)
2131          !
2132          stream_reservoir(ig,ib) = stream_reservoir(ig,ib) + flood_flow(ig,ib) + transport(ig,ib) - &
2133               & stream_flow(ig,ib) - return_swamp(ig,ib) - floods(ig,ib)
2134          !
2135          flood_reservoir(ig,ib) = flood_reservoir(ig,ib) + floods(ig,ib) - &
2136               & flood_flow(ig,ib) 
2137          !
2138          pond_reservoir(ig) = pond_reservoir(ig) + pond_inflow(ig,ib) - pond_drainage(ig,ib)
2139          !
2140          IF ( flood_reservoir(ig,ib) .LT. zero ) THEN
2141             IF ( check_reservoir ) THEN
2142                WRITE(numout,*) "WARNING : negative flood reservoir at :", ig, ib, ". Problem is being corrected."
2143                WRITE(numout,*) "flood_reservoir, floods, flood_flow : ", flood_reservoir(ig,ib), floods(ig,ib), &
2144                     & flood_flow(ig,ib) 
2145             ENDIF
2146             stream_reservoir(ig,ib) = stream_reservoir(ig,ib) + flood_reservoir(ig,ib)
2147             flood_reservoir(ig,ib) = zero
2148          ENDIF
2149          !
2150          IF ( stream_reservoir(ig,ib) .LT. zero ) THEN
2151             IF ( check_reservoir ) THEN
2152                WRITE(numout,*) "WARNING : negative stream reservoir at :", ig, ib, ". Problem is being corrected."
2153                WRITE(numout,*) "stream_reservoir, flood_flow, transport : ", stream_reservoir(ig,ib), flood_flow(ig,ib), &
2154                     &  transport(ig,ib)
2155                WRITE(numout,*) "stream_flow, return_swamp, floods :", stream_flow(ig,ib), return_swamp(ig,ib), floods(ig,ib)
2156             ENDIF
2157             fast_reservoir(ig,ib) =  fast_reservoir(ig,ib) + stream_reservoir(ig,ib)
2158             stream_reservoir(ig,ib) = zero
2159          ENDIF
2160          !
2161          IF ( fast_reservoir(ig,ib) .LT. zero ) THEN
2162             IF ( check_reservoir ) THEN
2163                WRITE(numout,*) "WARNING : negative fast reservoir at :", ig, ib, ". Problem is being corrected."
2164                WRITE(numout,*) "fast_reservoir, runoff, fast_flow, ponf_inflow  : ", fast_reservoir(ig,ib), &
2165                     &runoff(ig), fast_flow(ig,ib), pond_inflow(ig,ib)
2166             ENDIF
2167             slow_reservoir(ig,ib) =  slow_reservoir(ig,ib) + fast_reservoir(ig,ib)
2168             fast_reservoir(ig,ib) = zero
2169          ENDIF
2170
2171          IF ( slow_reservoir(ig,ib) .LT. - min_sechiba ) THEN
2172             WRITE(numout,*) 'WARNING : There is a negative reservoir at :', ig, ib,lalo(ig,:)
2173             WRITE(numout,*) 'WARNING : slowr, slow_flow, drainage', &
2174                  & slow_reservoir(ig,ib), slow_flow(ig,ib), drainage(ig)
2175             WRITE(numout,*) 'WARNING : pondr, pond_inflow, pond_drainage', &
2176                  & pond_reservoir(ig), pond_inflow(ig,ib), pond_drainage(ig,ib)
2177             CALL ipslerr_p(2, 'routing_flow', 'WARNING negative slow_reservoir.','','')
2178          ENDIF
2179
2180       ENDDO
2181    ENDDO
2182
2183
2184    totflood(:) = zero
2185    DO ig=1,nbpt
2186       DO ib=1,nbasmax
2187          totflood(ig) = totflood(ig) + flood_reservoir(ig,ib)
2188       ENDDO
2189    ENDDO
2190
2191    !-
2192    !- Computes the fraction of floodplains and ponds according to their volume
2193    !-
2194    IF (do_floodplains .OR. doponds) THEN
2195       flood_frac(:) = zero
2196       flood_height(:) = zero
2197       flood_frac_bas(:,:) = zero
2198       DO ig=1, nbpt
2199          IF (totflood(ig) .GT. min_sechiba) THEN
2200             ! We first compute the total fraction of the grid box which is flooded at optimum repartition
2201             flood_frac_pot = (totflood(ig) / (totarea(ig)*floodcri/(beta+un)))**(beta/(beta+un))
2202             flood_frac(ig) = MIN(floodplains(ig) / totarea(ig), flood_frac_pot)
2203             ! Then we diagnose the fraction for each basin with the size of its flood_reservoir
2204             ! (flood_frac_bas may be > 1)
2205             DO ib=1,nbasmax
2206                IF (routing_area(ig,ib) .GT. min_sechiba) THEN
2207                   flood_frac_bas(ig,ib) = flood_frac(ig) * &
2208                        & (flood_reservoir(ig,ib) / totflood(ig)) / (routing_area(ig,ib) / totarea(ig))
2209                ENDIF
2210             ENDDO
2211             ! We diagnose the maximum height of floodplain
2212             flood_height(ig) = (beta/(beta+1))*floodcri*(flood_frac(ig))**(un/beta) + totflood(ig)/(totarea(ig)*flood_frac(ig)) 
2213             ! And finally add the pond surface
2214             pond_frac(ig) = MIN(un-flood_frac(ig), ((betap+1)*pond_reservoir(ig) / (pondcri*totarea(ig)))**(betap/(betap+1)) ) 
2215             flood_frac(ig) = flood_frac(ig) + pond_frac(ig)
2216             !
2217          ENDIF
2218       ENDDO
2219    ELSE
2220       flood_frac(:) = zero
2221       flood_height(:) = zero
2222       flood_frac_bas(:,:) = zero
2223    ENDIF
2224
2225    !-
2226    !- Compute the total reinfiltration and returnflow to the grid box
2227!> A term of returnflow is computed including the water from the swamps that does not return directly to the river
2228!> but will be put into soil moisture (see hydrol module).
2229!> A term of reinfiltration is computed including the water that reinfiltrated from the ponds and floodplains areas.
2230!> It will be put into soil moisture (see hydrol module).
2231    !-
2232    IF (do_floodplains .OR. doswamps .OR. doponds) THEN
2233       returnflow(:) = zero
2234       reinfiltration(:) = zero
2235       !
2236       DO ib=1,nbasmax
2237          DO ig=1,nbpt
2238             returnflow(ig) =  returnflow(ig) + return_swamp(ig,ib)
2239             reinfiltration(ig) =  reinfiltration(ig) + pond_drainage(ig,ib) + flood_drainage(ig,ib) 
2240          ENDDO
2241       ENDDO
2242       !
2243       DO ig=1,nbpt
2244          returnflow(ig) = returnflow(ig)/totarea(ig)
2245          reinfiltration(ig) = reinfiltration(ig)/totarea(ig)
2246       ENDDO
2247    ELSE
2248       returnflow(:) = zero
2249       reinfiltration(:) = zero
2250    ENDIF
2251
2252    !
2253    ! Compute the net irrigation requirement from Univ of Kassel
2254    !
2255    ! This is a very low priority process and thus only applies if
2256    ! there is some water left in the reservoirs after all other things.
2257    !
2258!> The computation of the irrigation is performed here.
2259!> * First step
2260!> In a first time, the water requirements (irrig_netereq) by the crops for their optimal growth are calculated
2261!> over each irrigated fraction (irrigated(ig)/totarea(ig)). It is the difference
2262!> between the maximal water loss by the crops (transpot_mean) and the net water amount kept by the soil
2263!> (precipitation and reinfiltration). Transpot_mean is computed in the routines enerbil and diffuco. It
2264!> is derived from the effective transpiration parametrization under stress-free conditions, called potential transpiration.
2265!> Crop_coef was used by a previous parametrization of irrigation in the code. Here, its value is equal to one.
2266!> The crop coefficient was constant in space and time to represent a mean resistance of the vegetation to the potential evaporation.
2267!> Now, the term crop_coef*Epot is substituted by transpot_mean (see Guimberteau et al., 2011).
2268!> * Second step
2269!> We compute irrigation needs in order to supply Irrig_netereq. Water for irrigation (irrig_actual) is withdrawn
2270!> from the reservoirs. The amount of water is withdrawn in priority from the stream reservoir.
2271!> If the irrigation requirement is higher than the water availability of the reservoir, water is withdrawn
2272!> from the fast reservoir or, in the extreme case, from the slow reservoir.
2273!> * Third step
2274!> We compute a deficit in water for irrigation. If it is positive, irrigation (depending on water availibility in the reservoirs)
2275!> has not supplied the crops requirements.
2276!
2277    IF ( do_irrigation ) THEN
2278       DO ig=1,nbpt
2279          !
2280          IF ((vegtot(ig) .GT. min_sechiba) .AND. (humrel(ig) .LT. un-min_sechiba) .AND. &
2281               & (runoff(ig) .LT. min_sechiba) ) THEN
2282             
2283             irrig_netereq(ig) = (irrigated(ig) / totarea(ig) ) * MAX(zero, transpot_mean(ig) - &
2284                  & (precip(ig)+reinfiltration(ig)) )
2285             
2286          ENDIF
2287          !
2288          DO ib=1,nbasmax
2289             IF ( routing_area(ig,ib) .GT. 0 ) THEN
2290             
2291                irrig_needs(ig,ib) = irrig_netereq(ig) * routing_area(ig,ib)
2292
2293                irrig_actual(ig,ib) = MIN(irrig_needs(ig,ib),&
2294                     &   stream_reservoir(ig,ib) + fast_reservoir(ig,ib) + slow_reservoir(ig,ib) )
2295               
2296                slow_reservoir(ig,ib) = MAX(zero, slow_reservoir(ig,ib) + &
2297                     & MIN(zero, fast_reservoir(ig,ib) + MIN(zero, stream_reservoir(ig,ib)-irrig_actual(ig,ib))))
2298
2299                fast_reservoir(ig,ib) = MAX( zero, &
2300                     &  fast_reservoir(ig,ib) + MIN(zero, stream_reservoir(ig,ib)-irrig_actual(ig,ib)))
2301
2302                stream_reservoir(ig,ib) = MAX(zero, stream_reservoir(ig,ib)-irrig_actual(ig,ib) )
2303
2304                irrig_deficit(ig,ib) = irrig_needs(ig,ib)-irrig_actual(ig,ib)
2305
2306             ENDIF
2307          ENDDO
2308          !
2309          ! Check if we cannot find the missing water in another basin of the same grid (stream reservoir only).
2310          ! If we find that then we create some adduction from that subbasin to the one where we need it for
2311          ! irrigation.
2312          !
2313!> If crops water requirements have not been supplied (irrig_deficit>0), we check if we cannot find the missing water
2314!> in another basin of the same grid. If there is water in the stream reservoir of this subbasin, we create some adduction
2315!> from that subbasin to the one where we need it for irrigation.
2316!>
2317          DO ib=1,nbasmax
2318
2319             stream_tot = SUM(stream_reservoir(ig,:))
2320
2321             DO WHILE ( irrig_deficit(ig,ib) > min_sechiba .AND. stream_tot > min_sechiba)
2322               
2323                fi = MAXLOC(stream_reservoir(ig,:))
2324                ib2 = fi(1)
2325
2326                irrig_adduct(ig,ib) = MIN(irrig_deficit(ig,ib), stream_reservoir(ig,ib2))
2327                stream_reservoir(ig,ib2) = stream_reservoir(ig,ib2)-irrig_adduct(ig,ib)
2328                irrig_deficit(ig,ib) = irrig_deficit(ig,ib)-irrig_adduct(ig,ib)
2329             
2330                stream_tot = SUM(stream_reservoir(ig,:))
2331               
2332             ENDDO
2333             
2334          ENDDO
2335          !
2336       ENDDO
2337       !
2338       ! If we are at higher resolution we might need to look at neighboring grid boxes to find the streams
2339       ! which can feed irrigation
2340!
2341!> At higher resolution (grid box smaller than 100x100km), we can import water from neighboring grid boxes
2342!> to the one where we need it for irrigation.
2343       !
2344       IF (is_root_prc) THEN
2345          ALLOCATE(irrig_deficit_glo(nbp_glo, nbasmax), stream_reservoir_glo(nbp_glo, nbasmax), &
2346               &        irrig_adduct_glo(nbp_glo, nbasmax), stat=ier)
2347       ELSE
2348          ALLOCATE(irrig_deficit_glo(0, 0), stream_reservoir_glo(0, 0), &
2349               &        irrig_adduct_glo(0, 0), stat=ier)
2350       ENDIF
2351       IF (ier /= 0) CALL ipslerr_p(3,'routing_flow','Pb in allocate for irrig_deficit_glo, stream_reservoir_glo,...','','')
2352
2353       CALL gather(irrig_deficit, irrig_deficit_glo)
2354       CALL gather(stream_reservoir,  stream_reservoir_glo)
2355       CALL gather(irrig_adduct, irrig_adduct_glo)
2356
2357       IF (is_root_prc) THEN
2358          !
2359          DO ig=1,nbp_glo
2360             ! Only work if the grid box is smaller than 100x100km. Else the piplines we build
2361             ! here would be too long to be reasonable.
2362             IF ( resolution_g(ig,1) < 100000. .AND. resolution_g(ig,2) < 100000. ) THEN
2363                DO ib=1,nbasmax
2364                   !
2365                   IF ( irrig_deficit_glo(ig,ib)  > min_sechiba ) THEN
2366                      !
2367                      streams_around(:,:) = zero
2368                      !
2369                      DO in=1,NbNeighb
2370                         ig2 = neighbours_g(ig,in)
2371                         IF (ig2 .GT. 0 ) THEN
2372                            streams_around(in,:) = stream_reservoir_glo(ig2,:)
2373                            igrd(in) = ig2
2374                         ENDIF
2375                      ENDDO
2376                      !
2377                      IF ( MAXVAL(streams_around) .GT. zero ) THEN
2378                         !
2379                         ff=MAXLOC(streams_around)
2380                         ig2=igrd(ff(1))
2381                         ib2=ff(2)
2382                         !
2383                         IF ( routing_area_glo(ig2,ib2) .GT. 0 .AND. stream_reservoir_glo(ig2,ib2) > zero ) THEN
2384                            adduction = MIN(irrig_deficit_glo(ig,ib), stream_reservoir_glo(ig2,ib2))
2385                            stream_reservoir_glo(ig2,ib2) = stream_reservoir_glo(ig2,ib2) - adduction
2386                            irrig_deficit_glo(ig,ib) = irrig_deficit_glo(ig,ib) - adduction
2387                            irrig_adduct_glo(ig,ib) = irrig_adduct_glo(ig,ib) + adduction
2388                         ENDIF
2389                         !
2390                      ENDIF
2391                      !
2392                   ENDIF
2393                   !
2394                ENDDO
2395             ENDIF
2396          ENDDO
2397          !
2398       ENDIF
2399       !
2400
2401       CALL scatter(irrig_deficit_glo, irrig_deficit)
2402       CALL scatter(stream_reservoir_glo,  stream_reservoir)
2403       CALL scatter(irrig_adduct_glo, irrig_adduct)
2404
2405       DEALLOCATE(irrig_deficit_glo, stream_reservoir_glo, irrig_adduct_glo)
2406
2407    ENDIF
2408
2409    !! Calculate the net water flow to each routing reservoir (in kg/dt)
2410    !! to further diagnose the corresponding water budget residu
2411    !! in routing_main
2412
2413    netflow_fast_diag(:) = zero
2414    netflow_slow_diag(:) = zero
2415    netflow_stream_diag(:) = zero
2416
2417    DO ib=1,nbasmax
2418       DO ig=1,nbpt
2419          netflow_fast_diag(ig) = netflow_fast_diag(ig) + runoff(ig)*routing_area(ig,ib) &
2420               - fast_flow(ig,ib) - pond_inflow(ig,ib)
2421          netflow_slow_diag(ig) = netflow_slow_diag(ig) + drainage(ig)*routing_area(ig,ib) &
2422               - slow_flow(ig,ib)
2423          netflow_stream_diag(ig) = netflow_stream_diag(ig) + flood_flow(ig,ib) + transport(ig,ib) &
2424               - stream_flow(ig,ib) - return_swamp(ig,ib) - floods(ig,ib)
2425       ENDDO
2426    ENDDO
2427
2428    !! Grid cell averaging
2429    DO ig=1,nbpt
2430       netflow_fast_diag(ig) = netflow_fast_diag(ig)/totarea(ig)
2431       netflow_slow_diag(ig) = netflow_slow_diag(ig)/totarea(ig)
2432       netflow_stream_diag(ig) = netflow_stream_diag(ig)/totarea(ig)
2433    ENDDO
2434
2435    !
2436    !
2437    ! Compute the fluxes which leave the routing scheme
2438    !
2439    ! Lakeinflow is in Kg/dt
2440    ! returnflow is in Kg/m^2/dt
2441    !
2442    hydrographs(:) = zero
2443    slowflow_diag(:) = zero
2444    fast_diag(:) = zero
2445    slow_diag(:) = zero
2446    stream_diag(:) = zero
2447    flood_diag(:) =  zero
2448    pond_diag(:) =  zero
2449    irrigation(:) = zero
2450    !
2451    !
2452    DO ib=1,nbasmax
2453       !
2454       DO ig=1,nbpt
2455          IF (hydrodiag(ig,ib) > 0 ) THEN
2456             hydrographs(ig) = hydrographs(ig) + fast_flow(ig,ib) + slow_flow(ig,ib) + & 
2457                  &  stream_flow(ig,ib) 
2458             slowflow_diag(ig) = slowflow_diag(ig) + slow_flow(ig,ib)
2459          ENDIF
2460          fast_diag(ig) = fast_diag(ig) + fast_reservoir(ig,ib)
2461          slow_diag(ig) = slow_diag(ig) + slow_reservoir(ig,ib)
2462          stream_diag(ig) = stream_diag(ig) + stream_reservoir(ig,ib)
2463          flood_diag(ig) = flood_diag(ig) + flood_reservoir(ig,ib)
2464          irrigation (ig) = irrigation (ig) + irrig_actual(ig,ib) + irrig_adduct(ig,ib)
2465       ENDDO
2466    ENDDO
2467    !
2468    DO ig=1,nbpt
2469       fast_diag(ig) = fast_diag(ig)/totarea(ig)
2470       slow_diag(ig) = slow_diag(ig)/totarea(ig)
2471       stream_diag(ig) = stream_diag(ig)/totarea(ig)
2472       flood_diag(ig) = flood_diag(ig)/totarea(ig)
2473       pond_diag(ig) = pond_reservoir(ig)/totarea(ig)
2474       !
2475       irrigation(ig) = irrigation(ig)/totarea(ig)
2476       !
2477       ! The three output types for the routing : endoheric basins,, rivers and
2478       ! diffuse coastal flow.
2479       !
2480       lakeinflow(ig) = transport(ig,nbasmax+1)
2481       coastalflow(ig) = transport(ig,nbasmax+2)
2482       riverflow(ig) = transport(ig,nbasmax+3)
2483       !
2484    ENDDO
2485    !
2486    flood_res = flood_diag + pond_diag
2487   
2488
2489    !! Remove water from lake reservoir if it exceeds the maximum limit and distribute it
2490    !! uniformly over all possible the coastflow gridcells
2491   
2492    ! Calculate lake_overflow and remove it from lake_reservoir
2493    DO ig=1,nbpt
2494       lake_overflow(ig) = MAX(0., lake_reservoir(ig) - max_lake_reservoir*totarea(ig))
2495       lake_reservoir(ig) = lake_reservoir(ig) - lake_overflow(ig)
2496    END DO
2497    ! Transform lake_overflow from kg/grid-cell/dt_routing into kg/m^2/s
2498    CALL xios_orchidee_send_field("lake_overflow",lake_overflow(:)/totarea(:)/dt_routing)
2499
2500    ! Calculate the sum of the lake_overflow and distribute it uniformly over all gridboxes
2501    CALL gather(lake_overflow,lake_overflow_g)
2502    IF (is_root_prc) THEN
2503       total_lake_overflow=SUM(lake_overflow_g)
2504    END IF
2505    CALL bcast(total_lake_overflow)
2506
2507    ! Distribute the lake_overflow uniformly over all coastal gridcells
2508    ! lake_overflow_coast is only calculated to be used as diagnostics if needed
2509    DO ig=1,nbpt
2510       coastalflow(ig) = coastalflow(ig) + total_lake_overflow/nb_coast_gridcells * mask_coast(ig)
2511       lake_overflow_coast(ig) = total_lake_overflow/nb_coast_gridcells * mask_coast(ig)
2512    END DO
2513    ! Transform from kg/grid-cell/dt_routing into m^3/grid-cell/s to match output unit of coastalflow
2514    CALL xios_orchidee_send_field("lake_overflow_coast",lake_overflow_coast/mille/dt_routing)
2515   
2516
2517  END SUBROUTINE routing_flow
2518  !
2519!! ================================================================================================================================
2520!! SUBROUTINE   : routing_lake
2521!!
2522!>\BRIEF        : This subroutine stores water in lakes so that it does not cycle through the runoff.
2523!!                For the moment it only works for endoheric lakes but I can be extended in the future.
2524!!
2525!! DESCRIPTION (definitions, functional, design, flags): The return flow to the soil moisture reservoir
2526!! is based on a maximum lake evaporation rate (maxevap_lake). \n
2527!!
2528!! RECENT CHANGE(S): None
2529!!
2530!! MAIN OUTPUT VARIABLE(S):
2531!!
2532!! REFERENCES   : None
2533!!
2534!! FLOWCHART    :None
2535!! \n
2536!_ ================================================================================================================================
2537
2538  SUBROUTINE routing_lake(nbpt, dt_routing, lakeinflow, humrel, return_lakes)
2539    !
2540    IMPLICIT NONE
2541    !
2542!! INPUT VARIABLES
2543    INTEGER(i_std), INTENT(in) :: nbpt               !! Domain size (unitless)
2544    REAL(r_std), INTENT (in)   :: dt_routing         !! Routing time step (s)
2545    REAL(r_std), INTENT(out)    :: lakeinflow(nbpt)   !! Water inflow to the lakes (kg/dt)
2546    REAL(r_std), INTENT(in)    :: humrel(nbpt)       !! Soil moisture stress, root extraction potential (unitless)
2547    !
2548!! OUTPUT VARIABLES
2549    REAL(r_std), INTENT(out)   :: return_lakes(nbpt) !! Water from lakes flowing back into soil moisture (kg/m^2/dt)
2550    !
2551!! LOCAL VARIABLES
2552    INTEGER(i_std)             :: ig                 !! Indices (unitless)
2553    REAL(r_std)                :: refill             !!
2554    REAL(r_std)                :: total_area         !! Sum of all the surfaces of the basins (m^2)
2555
2556!_ ================================================================================================================================
2557    !
2558    !
2559    DO ig=1,nbpt
2560       !
2561       total_area = SUM(routing_area(ig,:))
2562       !
2563       lake_reservoir(ig) = lake_reservoir(ig) + lakeinflow(ig)
2564       
2565       IF ( doswamps ) THEN
2566          ! Calculate a return flow that will be extracted from the lake reservoir and reinserted in the soil in hydrol
2567          ! Uptake in Kg/dt
2568          refill = MAX(zero, maxevap_lake * (un - humrel(ig)) * dt_routing * total_area)
2569          return_lakes(ig) = MIN(refill, lake_reservoir(ig))
2570          lake_reservoir(ig) = lake_reservoir(ig) - return_lakes(ig)
2571          ! Return in Kg/m^2/dt
2572          return_lakes(ig) = return_lakes(ig)/total_area
2573       ELSE
2574          return_lakes(ig) = zero
2575       ENDIF
2576
2577       ! This is the volume of the lake scaled to the entire grid.
2578       ! It would be better to scale it to the size of the lake
2579       ! but this information is not yet available.
2580       lake_diag(ig) = lake_reservoir(ig)/total_area
2581
2582       lakeinflow(ig) = lakeinflow(ig)/total_area
2583
2584    ENDDO
2585    !
2586  END SUBROUTINE routing_lake
2587  !
2588
2589!! ================================================================================================================================
2590!! SUBROUTINE   : routing_diagnostic_p
2591!!
2592!>\BRIEF         This parallelized subroutine gives a diagnostic of the basins used
2593!!
2594!! DESCRIPTION (definitions, functional, design, flags) : None
2595!!
2596!! RECENT CHANGE(S): None
2597!!
2598!! MAIN OUTPUT VARIABLE(S):
2599!!
2600!! REFERENCES   : None
2601!!
2602!! FLOWCHART    : None
2603!! \n
2604!_ ================================================================================================================================
2605
2606  SUBROUTINE routing_diagnostic_p(nbpt, index, lalo, resolution, contfrac, hist_id, hist2_id)
2607    !
2608    IMPLICIT NONE
2609   
2610!! INPUT VARIABLES
2611    INTEGER(i_std), INTENT(in)      :: nbpt               !! Domain size (unitless)
2612    INTEGER(i_std), INTENT(in)      :: index(nbpt)        !! Indices of the points on the map (unitless)
2613    REAL(r_std), INTENT(in)         :: lalo(nbpt,2)       !! Vector of latitude and longitudes (beware of the order !)
2614    REAL(r_std), INTENT(in)         :: resolution(nbpt,2) !! The size of each grid box in X and Y (m)
2615    REAL(r_std), INTENT(in)         :: contfrac(nbpt)     !! Fraction of land in each grid box (unitless;0-1)
2616    INTEGER(i_std),INTENT (in)      :: hist_id            !! Access to history file (unitless)
2617    INTEGER(i_std),INTENT (in)      :: hist2_id           !! Access to history file 2 (unitless)
2618    !
2619!! LOCAL VARIABLES
2620    REAL(r_std), DIMENSION(nbpt)    :: nbrivers           !! Number of rivers in the grid (unitless)
2621    REAL(r_std), DIMENSION(nbpt)    :: basinmap           !! Map of basins (unitless)
2622    REAL(r_std), DIMENSION(nbp_glo) :: nbrivers_g         !! Number of rivers in the grid (unitless)
2623    REAL(r_std), DIMENSION(nbp_glo) :: basinmap_g         !! Map of basins (unitless)
2624
2625!_ ================================================================================================================================
2626    routing_area => routing_area_glo 
2627    topo_resid => topo_resid_glo
2628    route_togrid => route_togrid_glo
2629    route_tobasin => route_tobasin_glo
2630    route_nbintobas => route_nbintobas_glo
2631    global_basinid => global_basinid_glo
2632    hydrodiag=>hydrodiag_glo
2633    hydroupbasin=>hydroupbasin_glo
2634   
2635    IF (is_root_prc) CALL routing_diagnostic(nbp_glo, index_g, lalo_g, resolution_g, contfrac_g, nbrivers_g,basinmap_g)
2636
2637    routing_area => routing_area_loc 
2638    topo_resid => topo_resid_loc
2639    route_togrid => route_togrid_loc
2640    route_tobasin => route_tobasin_loc
2641    route_nbintobas => route_nbintobas_loc
2642    global_basinid => global_basinid_loc
2643    hydrodiag=>hydrodiag_loc
2644    hydroupbasin=>hydroupbasin_loc
2645   
2646    CALL scatter(nbrivers_g,nbrivers)
2647    CALL scatter(basinmap_g,basinmap)
2648    CALL scatter(hydrodiag_glo,hydrodiag_loc)
2649    CALL scatter(hydroupbasin_glo,hydroupbasin_loc)
2650       
2651    CALL xios_orchidee_send_field("basinmap",basinmap)
2652    CALL xios_orchidee_send_field("nbrivers",nbrivers)
2653
2654    IF ( .NOT. almaoutput ) THEN
2655       CALL histwrite_p(hist_id, 'basinmap', 1, basinmap, nbpt, index)
2656       CALL histwrite_p(hist_id, 'nbrivers', 1, nbrivers, nbpt, index)
2657    ELSE
2658    ENDIF
2659    IF ( hist2_id > 0 ) THEN
2660       IF ( .NOT. almaoutput ) THEN
2661          CALL histwrite_p(hist2_id, 'basinmap', 1, basinmap, nbpt, index)
2662          CALL histwrite_p(hist2_id, 'nbrivers', 1, nbrivers, nbpt, index)
2663       ELSE
2664       ENDIF
2665    ENDIF
2666   
2667       
2668  END SUBROUTINE routing_diagnostic_p
2669
2670!! ================================================================================================================================
2671!! SUBROUTINE   : routing_diagnostic
2672!!
2673!>\BRIEF         This non-parallelized subroutine gives a diagnostic of the basins used. This produces some information
2674!!               on the rivers which are being diagnosed.
2675!!
2676!! DESCRIPTION (definitions, functional, design, flags) : As not all rivers can be monitored in the model, we will only
2677!! archive num_largest rivers. In this routine we will diagnose the num_largest largest rivers and print to the standard
2678!! output the names of these basins and their area. The list of names of these largest rivers are taken from a list coded in the
2679!! routine routing_names. As this standard output is not sufficient, we will also write it to a netCDF file with the routine
2680!! routing_diagncfile. It is important to keep for diagnostic the fraction of the largest basins in each grid box and keep information
2681!! how they are linked one to the other.
2682!!
2683!! RECENT CHANGE(S): None
2684!!
2685!! MAIN OUTPUT VARIABLE(S): No output variables.
2686!!
2687!! REFERENCES   : None
2688!!
2689!! FLOWCHART    :None
2690!! \n
2691!_ ================================================================================================================================
2692
2693  SUBROUTINE routing_diagnostic(nbpt, l_index, lalo, resolution, contfrac, nbrivers, basinmap)
2694    !
2695    IMPLICIT NONE
2696    !
2697!! INPUT VARIABLES
2698    INTEGER(i_std), INTENT(in)                   :: nbpt                !! Domain size  (unitless)
2699    INTEGER(i_std), INTENT(in)                   :: l_index(nbpt)       !! Indices of the points on the map (unitless)
2700    REAL(r_std), INTENT(in)                      :: lalo(nbpt,2)        !! Vector of latitude and longitudes (beware of the order !)
2701    REAL(r_std), INTENT(in)                      :: resolution(nbpt,2)  !! The size of each grid box in X and Y (m)
2702    REAL(r_std), INTENT(in)                      :: contfrac(nbpt)      !! Fraction of land in each grid box (unitless;0-1)
2703    !
2704!! OUTPUT VARIABLES
2705    REAL(r_std), DIMENSION(nbpt), INTENT(out)    :: nbrivers            !! Number of rivers in the grid (unitless)
2706    REAL(r_std), DIMENSION(nbpt), INTENT(out)    :: basinmap            !! Map of basins (unitless)
2707    !
2708!! LOCAL VARIABLES
2709    INTEGER(i_std), DIMENSION(nbpt,nbasmax)      :: outids              !! IDs of river to which this basin contributes (unitless)
2710    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:)  :: pts                 !! List the points belonging to the basin (unitless)
2711    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:)  :: ptbas               !! List the basin number for this point (unitless)
2712    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:)  :: outpt               !! Outflow point for each basin (unitless)
2713    INTEGER(i_std), ALLOCATABLE, DIMENSION(:)    :: nb_pts              !! Number of points in the basin (unitless)
2714    REAL(r_std), ALLOCATABLE, DIMENSION(:)       :: totarea             !! Total area of basin (m^2)
2715    REAL(r_std), ALLOCATABLE, DIMENSION(:)       :: tmparea             !!
2716    INTEGER(i_std), ALLOCATABLE, DIMENSION(:)    :: topids              !! The IDs of the first num_largest basins (unitless)
2717    CHARACTER(LEN=25), ALLOCATABLE, DIMENSION(:) :: basin_names         !! Names of the rivers (unitless)
2718    CHARACTER(LEN=25)                            :: name_str            !!
2719    !
2720    LOGICAL                                      :: river_file          !! Choose to write a description of the rivers (true/false)
2721    CHARACTER(LEN=80)                            :: river_file_name     !! Filename in which we write the description of the rivers (unitless)
2722    !
2723    CHARACTER(LEN=25), ALLOCATABLE, DIMENSION(:)  :: sorted_names       !!
2724    INTEGER(i_std), ALLOCATABLE, DIMENSION(:)     :: streams_nb         !! Number of streams in basin (unitless)
2725    INTEGER(i_std), ALLOCATABLE, DIMENSION(:)     :: streams_avehops    !! Average number of hops in streams (unitless)
2726    INTEGER(i_std), ALLOCATABLE, DIMENSION(:)     :: streams_minhops    !! Minimum number of hops in streams (unitless)
2727    INTEGER(i_std), ALLOCATABLE, DIMENSION(:)     :: streams_maxhops    !! Minimum number of hops in streams (unitless)
2728    REAL(r_std), ALLOCATABLE, DIMENSION(:)        :: streams_resid      !! Average residence time
2729    !
2730    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: lbasin_area        !!
2731    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: lbasin_uparea      !!
2732    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:)   :: lrivercode         !!
2733    !
2734    INTEGER(i_std)                                :: ig, ib, og, ob, ign, ibn, ff(1), ic, icc, nb_small, idbas, slen, ii !! Indices (unitless)
2735    INTEGER(i_std)                                :: ier                !! Error handling
2736    CHARACTER(LEN=3)                              :: nn                 !!
2737    INTEGER(i_std)                                :: name_found         !!
2738    !
2739    REAL(r_std)                                   :: averesid           !!
2740    REAL(r_std), DIMENSION(nbasmax)               :: tmpbas             !!
2741    REAL(r_std), DIMENSION(nbpt,nbasmax)          :: areaupbasin        !!
2742    INTEGER(i_std), ALLOCATABLE, DIMENSION(:)     :: sortedrivs         !!
2743    !
2744    ! Variables for the river coding
2745    !
2746    INTEGER(i_std)                               :: longest_river       !!
2747    INTEGER(i_std)                               :: nbmax               !!
2748    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:)  :: allstreams          !!
2749    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)     :: upstreamchange      !!
2750    INTEGER(i_std), ALLOCATABLE, DIMENSION(:)    :: tstreams, tslen, tpts, tptbas, tcode !!
2751    REAL(r_std), ALLOCATABLE, DIMENSION(:)       :: tuparea             !!
2752    REAL(r_std), ALLOCATABLE, DIMENSION(:)       :: tupstreamchange     !!
2753    !
2754    LOGICAL                                      :: err_nbpt_grid_basin !! (true/false)
2755    LOGICAL                                      :: err_basin_number    !! (true/false)
2756
2757!_ ================================================================================================================================
2758    !
2759    !
2760    ALLOCATE(pts(num_largest, nbpt), stat=ier)
2761    IF (ier /= 0) CALL ipslerr_p(3,'routing_diagnostic','Pb in allocate for pts','','')
2762
2763    ALLOCATE(ptbas(num_largest, nbpt), stat=ier)
2764    IF (ier /= 0) CALL ipslerr_p(3,'routing_diagnostic','Pb in allocate for ptbas','','')
2765
2766    ALLOCATE(outpt(num_largest, 2), stat=ier)
2767    IF (ier /= 0) CALL ipslerr_p(3,'routing_diagnostic','Pb in allocate for outpt','','')
2768
2769    ALLOCATE(nb_pts(num_largest), stat=ier)
2770    IF (ier /= 0) CALL ipslerr_p(3,'routing_diagnostic','Pb in allocate for nb_pts','','')
2771
2772    ALLOCATE(totarea(num_largest), tmparea(num_largest), stat=ier)
2773    IF (ier /= 0) CALL ipslerr_p(3,'routing_diagnostic','Pb in allocate for totarea','','')
2774
2775    ALLOCATE(topids(num_largest), stat=ier)
2776    IF (ier /= 0) CALL ipslerr_p(3,'routing_diagnostic','Pb in allocate for topids','','')
2777
2778    ALLOCATE(sortedrivs(num_largest), stat=ier)
2779    IF (ier /= 0) CALL ipslerr_p(3,'routing_diagnostic','Pb in allocate for sortedrivs','','')
2780
2781    ALLOCATE(sorted_names(num_largest), stat=ier)
2782    IF (ier /= 0) CALL ipslerr_p(3,'routing_diagnostic','Pb in allocate for sorted_names','','')
2783
2784    ALLOCATE(streams_nb(num_largest), streams_avehops(num_largest), streams_minhops(num_largest), stat=ier)
2785    IF (ier /= 0) CALL ipslerr_p(3,'routing_diagnostic','Pb in allocate for streams_nb','','')
2786
2787    ALLOCATE(streams_maxhops(num_largest), stat=ier)
2788    IF (ier /= 0) CALL ipslerr_p(3,'routing_diagnostic','Pb in allocate for streams_maxhops','','')
2789
2790    ALLOCATE(streams_resid(num_largest), stat=ier)
2791    IF (ier /= 0) CALL ipslerr_p(3,'routing_diagnostic','Pb in allocate for streams_resid','','')
2792   
2793    ALLOCATE(lbasin_area(num_largest,nbpt), lbasin_uparea(num_largest,nbpt), lrivercode(num_largest,nbpt), stat=ier)
2794    IF (ier /= 0) CALL ipslerr_p(3,'routing_diagnostic','Pb in allocate for lbasin_area','','')
2795   
2796    IF ( .NOT. is_root_prc) THEN
2797       WRITE(numout,*) "routing_diagnostic is not suitable for running in parallel"
2798       WRITE(numout,*) "We are here on a non root processor. is_root_prc = ", is_root_prc
2799       WRITE(numout,*) "STOP from routing_diagnostic"
2800       CALL ipslerr_p(3,'routing_diagnostic','This routine is not suitable for running in parallel','','')
2801    ENDIF
2802   
2803   
2804    !Config Key   = RIVER_DESC
2805    !Config Desc  = Writes out a description of the rivers
2806    !Config If    = RIVER_ROUTING
2807    !Config Def   = n
2808    !Config Help  = This flag allows to write out a file containing the list of
2809    !Config         rivers which are beeing simulated. It provides location of outflow
2810    !Config         drainage area, name and ID.
2811    !Config Units = [FLAG]
2812    !
2813    river_file=.FALSE.
2814    CALL getin('RIVER_DESC', river_file)
2815    !
2816    !Config Key   = RIVER_DESC_FILE
2817    !Config Desc  = Filename in which we write the description of the rivers. If suffix is ".nc" a netCDF file is created
2818    !Config If    = RIVER_DESC
2819    !Config Def   = river_desc.nc
2820    !Config Help  = File name where we will write the information. If the suffix is ".nc" a netCDF file is generated. Else
2821    !Config         a simple text file will contain some information. The netCDF file is valuable for post-processing the
2822    !               data as it will contain the fraction of the large basins in each grid box.
2823    !Config Units = [FILE]
2824    !
2825    river_file_name="river_desc.nc"
2826    CALL getin('RIVER_DESC_FILE', river_file_name)
2827    !
2828    !
2829    ! First we get the list of all river outflow points
2830    ! We work under the assumption that we only have num_largest basins finishing with
2831    ! nbasmax+3. This is checked in routing_truncate.
2832    !
2833    nb_small = 1
2834    outpt(:,:) = -1
2835    ic = 0
2836    DO ig=1,nbpt
2837       DO ib=1,nbasmax
2838          ign = route_togrid(ig, ib)
2839          ibn = route_tobasin(ig, ib)
2840          IF ( ibn .EQ. nbasmax+3) THEN
2841             ic = ic + 1
2842             outpt(ic,1) = ig
2843             outpt(ic,2) = ib
2844             !
2845             ! Get the largest id of the basins we call a river. This is
2846             ! to extract the names of all rivers.
2847             !
2848             IF ( global_basinid(ig,ib) > nb_small ) THEN
2849                nb_small = global_basinid(ig,ib)
2850             ENDIF
2851          ENDIF
2852       ENDDO
2853    ENDDO
2854   
2855    nb_small = MIN(nb_small, 349)
2856   
2857    ALLOCATE(basin_names(nb_small), stat=ier)
2858    IF (ier /= 0) CALL ipslerr_p(3,'routing_diagnostic','Pb in allocate for basins_names','','')
2859
2860    CALL routing_names(nb_small, basin_names)
2861    !
2862    ! Go through all points and basins to see if they outflow as a river and store the
2863    ! information needed in the various arrays.
2864    !
2865    nb_pts(:) = 0
2866    totarea(:) = zero
2867    hydrodiag(:,:) = 0
2868    areaupbasin(:,:) = zero
2869    outids(:,:) = -1
2870    ob = -1
2871    og = -1
2872    lbasin_area(:,:) = zero
2873    lbasin_uparea(:,:) = zero
2874    longest_river = 0
2875    !
2876    err_nbpt_grid_basin = .FALSE.
2877    loopgridbasin : DO ig=1,nbpt
2878       !
2879       DO ib=1,nbasmax
2880          IF ( routing_area(ig,ib) .GT. zero ) THEN
2881             ic = 0
2882             ign = ig
2883             ibn = ib
2884             ! Locate outflow point
2885             DO WHILE (ibn .GT. 0 .AND. ibn .LE. nbasmax .AND. ic .LT. nbasmax*nbpt)
2886                ic = ic + 1
2887                og = ign
2888                ob = ibn
2889                ign = route_togrid(og, ob)
2890                ibn = route_tobasin(og, ob)
2891                areaupbasin(og, ob) = areaupbasin(og, ob) + routing_area(ig,ib)
2892             ENDDO
2893             !
2894             longest_river = MAX(longest_river, ic)
2895             !
2896             ! Now that we have an outflow check if it is one of the num_largest rivers.
2897             ! In this case we keeps the location so we diagnose it.
2898             !
2899             IF ( ibn .EQ. nbasmax + 3) THEN
2900                DO icc = 1,num_largest
2901                   IF ( outpt(icc,1) .EQ. og .AND. outpt(icc,2) .EQ. ob ) THEN
2902                      !
2903                      ! We only keep this point for our map if it is large enough.
2904                      !
2905                      nb_pts(icc) = nb_pts(icc) + 1
2906                      !
2907                      !
2908                      IF ( nb_pts(icc) > nbpt ) THEN
2909                         err_nbpt_grid_basin = .TRUE.
2910                         EXIT loopgridbasin
2911                      ENDIF
2912                      !
2913                      pts(icc, nb_pts(icc)) = ig
2914                      ptbas(icc, nb_pts(icc)) = ib
2915                      totarea(icc) = totarea(icc) + routing_area(ig,ib)
2916                      !
2917                      lbasin_area(icc,nb_pts(icc)) = routing_area(ig,ib)
2918                      !
2919                      ! ID of the river is taken from the last point before the outflow.
2920                      topids(icc) = global_basinid(og,ob)
2921                      outids(ig,ib) = global_basinid(og,ob)
2922                      !
2923                      ! On this gridbox and basin we will diagnose the hydrograph
2924                      !
2925                      hydrodiag(ig, ib) = 1
2926                      !
2927                   ENDIF
2928                ENDDO
2929             ENDIF
2930          ENDIF
2931          !
2932       ENDDO
2933       !
2934    ENDDO loopgridbasin
2935    !
2936    IF ( err_nbpt_grid_basin ) THEN
2937       WRITE(numout, *) "routing_diagnostic : The number of grid points in basin ", icc
2938       WRITE(numout, *) "routing_diagnostic : is larger than anticiped. "
2939       CALL ipslerr_p(3, 'routing_diagnostic', 'We are heading for a out of bounds in arrays pts, ptsbas and lbasin_area.',&
2940                     & 'Increase the last dimension of these arrays.','')
2941    ENDIF
2942    !
2943    ! Now we decide which points we will keep from the largest basins
2944    !
2945    ! Temporary fix
2946    route_nbintobas(:,:) = 0
2947    !
2948    basinmap(:) = zero
2949    DO ig=1,nbpt
2950       !
2951       ! Look for the dominant basin in this grid. This information only affects some
2952       ! diagnostics : hydrographs and saved area upstream.
2953       !
2954       icc = 0
2955       idbas = -1
2956       !
2957       DO ib=1,nbasmax
2958          IF ( outids(ig,ib) > 0 ) THEN
2959             IF ( COUNT(outids(ig,:) == outids(ig,ib)) > icc ) THEN
2960                icc = COUNT(outids(ig,:) == outids(ig,ib))
2961                idbas = outids(ig,ib)
2962             ENDIF
2963          ENDIF
2964       ENDDO
2965       !
2966       ! If we have found a point from the large basins and decided which one
2967       ! takes over this grid then we note it on the map.
2968       ! Clean-up a little the hydrodiag array
2969       !
2970       IF ( idbas > 0 ) THEN
2971          basinmap(ig) = REAL(idbas, r_std)
2972       ENDIF
2973       !
2974       ! Now place the hydrograph diagnostic on the point closest to the
2975       ! ocean.
2976       !
2977       tmpbas(:) = zero
2978       DO ib=1,nbasmax
2979          IF ( outids(ig,ib) .EQ. idbas) THEN
2980             tmpbas(ib) = areaupbasin(ig,ib)
2981          ENDIF
2982       ENDDO
2983       hydrodiag(ig,:) = 0
2984       ff=MAXLOC(tmpbas)
2985       hydrodiag(ig,ff(1)) = 1
2986       hydroupbasin(ig) = areaupbasin(ig,ff(1))
2987       !
2988    ENDDO
2989    !
2990    !
2991    !
2992    tmparea(:) = totarea(:)
2993    DO icc = 1, num_largest
2994       ff = MAXLOC(tmparea)
2995       sortedrivs(icc) = ff(1)
2996       tmparea(ff(1)) = 0.0
2997    ENDDO
2998    !
2999    ! Diagnose the complexity of the basins obtained and determine their code in the Pfafstetter system
3000    !
3001    nbmax=MAXVAL(nb_pts)
3002    ALLOCATE(allstreams(nbmax, longest_river), upstreamchange(nbmax, longest_river), stat=ier)
3003    IF (ier /= 0) CALL ipslerr_p(3,'routing_diagnostic','Pb in allocate for allstreams','','')
3004
3005    ALLOCATE(tstreams(longest_river), tupstreamchange(longest_river), stat=ier)
3006    IF (ier /= 0) CALL ipslerr_p(3,'routing_diagnostic','Pb in allocate for tstreams','','')
3007
3008    ALLOCATE(tslen(nbmax), tpts(nbmax), tptbas(nbmax), tuparea(nbmax), stat=ier)
3009    IF (ier /= 0) CALL ipslerr_p(3,'routing_diagnostic','Pb in allocate for tslen','','')
3010
3011    ALLOCATE(tcode(nbmax), stat=ier)
3012    IF (ier /= 0) CALL ipslerr_p(3,'routing_diagnostic','Pb in allocate for tcode','','')
3013
3014    DO icc = 1, num_largest
3015       !
3016       ! Work through the largest basins
3017       !
3018       idbas = sortedrivs(icc)
3019       !
3020       streams_nb(idbas) = 0
3021       streams_avehops(idbas) = 0
3022       streams_minhops(idbas) = undef_int
3023       streams_maxhops(idbas) = 0
3024       streams_resid(idbas) = zero
3025       tslen(:) = 0
3026       !
3027       allstreams(:,:) = 0
3028       upstreamchange(:,:) = zero
3029       !
3030       DO ii=1,nb_pts(idbas)
3031          !
3032          ig = pts(idbas, ii)
3033          ib = ptbas(idbas, ii)
3034          !
3035          lbasin_uparea(idbas,ii) = areaupbasin(ig,ib)
3036          !
3037          slen = 0
3038          ign = ig
3039          ibn = ib
3040          og = ig
3041          ob = ib
3042          !
3043          averesid = zero
3044          tupstreamchange(:) = zero
3045          ! go to outflow point to count the number of hops
3046          DO WHILE (ibn .GT. 0 .AND. ibn .LE. nbasmax)
3047             ! Store data
3048             slen = slen + 1
3049             tstreams(slen) = ign
3050             tupstreamchange(slen) = areaupbasin(ign,ibn)-areaupbasin(og,ob)
3051             ! Move to next point
3052             og = ign
3053             ob = ibn
3054             ign = route_togrid(og, ob)
3055             ibn = route_tobasin(og, ob)
3056             averesid = averesid + topo_resid(og, ob)**2
3057          ENDDO
3058          !
3059          allstreams(ii,1:slen) = tstreams(slen:1:-1)
3060          upstreamchange(ii,1:slen) = tupstreamchange(slen:1:-1)
3061          tslen(ii) = slen
3062          !
3063          ! Save diagnostics
3064          !
3065          streams_nb(idbas) = streams_nb(idbas) + 1
3066          streams_avehops(idbas) = streams_avehops(idbas) + slen
3067          streams_resid(idbas) = streams_resid(idbas) + SQRT(averesid)
3068          IF ( slen < streams_minhops(idbas) ) THEN
3069             streams_minhops(idbas) = slen
3070          ENDIF
3071          IF ( slen > streams_maxhops(idbas) ) THEN
3072             streams_maxhops(idbas) = slen
3073          ENDIF
3074          !
3075       ENDDO
3076       ! build the average
3077       IF ( streams_nb(idbas) > 0 ) THEN
3078          streams_avehops(idbas) = streams_avehops(idbas)/streams_nb(idbas)
3079          streams_resid(idbas) = streams_resid(idbas)/REAL(streams_nb(idbas), r_std)
3080       ELSE
3081          ! River without streams ... very rare but happens
3082          streams_avehops(idbas) = zero
3083          streams_resid(idbas) = zero
3084          streams_maxhops(idbas) = zero
3085          streams_minhops(idbas) = zero
3086       ENDIF
3087       !
3088       !
3089       ii=nb_pts(idbas)
3090       tpts(:) = 0
3091       tpts(1:ii) = pts(idbas,1:ii)
3092       tptbas(:) = 0
3093       tptbas(1:ii) = ptbas(idbas,1:ii)
3094       tuparea(:) = 0
3095       tuparea(1:ii) = lbasin_uparea(idbas,1:ii)
3096       !
3097       CALL routing_diagcode(ii, tpts, tptbas, tuparea, tslen, MAXVAL(tslen), allstreams, upstreamchange, tcode) 
3098       !
3099       lrivercode(idbas,:) = 0
3100       lrivercode(idbas,1:ii) = tcode(1:ii)
3101       !
3102    ENDDO
3103    !
3104    ! Create the sorted list of names
3105    !
3106    err_basin_number = .FALSE.
3107    DO icc = 1, num_largest
3108       !
3109       ib=sortedrivs(icc)
3110       !
3111       IF ( topids(ib) .GT. nb_small ) THEN
3112          IF (topids(ib) <= 99 ) THEN
3113             WRITE(sorted_names(icc), '("Nb_",I2.2)') topids(ib)
3114          ELSE IF (topids(ib) <= 999 ) THEN
3115             WRITE(sorted_names(icc), '("Nb_",I3.3)') topids(ib)
3116          ELSE IF (topids(ib) <= 9999 ) THEN
3117             WRITE(sorted_names(icc), '("Nb_",I4.4)') topids(ib)
3118          ELSE IF (topids(ib) <= 99999 ) THEN
3119             WRITE(sorted_names(icc), '("Nb_",I5.5)') topids(ib)
3120          ELSE IF (topids(ib) <= 999999 ) THEN
3121             WRITE(sorted_names(icc), '("Nb_",I6.6)') topids(ib)
3122          ELSE
3123             err_basin_number = .TRUE.
3124             EXIT
3125          ENDIF
3126
3127       ELSE
3128          IF (topids(ib) <= -1 ) THEN
3129             WRITE(sorted_names(icc), '("Ne_",I2.2)') -1*topids(ib)
3130          ELSE
3131             IF (printlev >=6) WRITE(numout,*) ">>> nb_small, ib, topids :", nb_small, ib, topids(ib)
3132             sorted_names(icc) = basin_names(topids(ib))
3133          ENDIF
3134       ENDIF
3135       !
3136    ENDDO
3137    !
3138    IF ( err_basin_number ) THEN
3139       CALL ipslerr_p(3, 'routing_diagnostic', 'We found a basin number larger than 999999.',&
3140            & 'This is impossible. Please verify your configuration.','')
3141    ENDIF
3142    !
3143    ! Check for doubles and rename if needed
3144    !
3145    DO icc = 1, num_largest
3146       name_found=0
3147       DO ic=1, num_largest
3148          IF ( TRIM(sorted_names(icc)) == TRIM(sorted_names(ic)) ) THEN
3149             name_found = name_found + 1
3150          ENDIF
3151       ENDDO
3152       
3153       IF ( name_found > 1 ) THEN
3154          DO ic=num_largest,1,-1
3155             IF ( TRIM(sorted_names(icc)) == TRIM(sorted_names(ic)) .AND. name_found > 1 ) THEN
3156                IF ( name_found < 10 ) THEN
3157                   WRITE(nn,'(I1)')  name_found
3158                ELSE IF ( name_found < 100 ) THEN
3159                   WRITE(nn,'(I2)')  name_found
3160                ELSE IF ( name_found < 1000 ) THEN
3161                   WRITE(nn,'(I3)')  name_found
3162                ELSE
3163                   ! Make sur to increase nn size when adding more cases
3164                   CALL ipslerr_p(3, 'routing_diagnostic', &
3165                        'Non of the previous values can fit in the new char', &
3166                        'Add a new condition to deal with it', '')
3167                ENDIF
3168                sorted_names(ic) = TRIM(sorted_names(ic))//TRIM(nn)
3169                name_found = name_found - 1
3170             ENDIF
3171          ENDDO
3172       ENDIF
3173       
3174    ENDDO
3175    !
3176    ! Print to stdout on ROOT_PROC the diagnostics for the largest basins we have found.
3177    !
3178    IF (printlev>=1) THEN
3179       DO icc = 1, num_largest
3180          IF ( nb_pts(sortedrivs(icc)) .GT. 2 ) THEN
3181             name_str = sorted_names(icc)
3182             WRITE(numout,'("Basin ID ", I5," ", A15, " Area [km^2] : ", F13.4, " Nb points : ", I4)')&
3183                  & topids(sortedrivs(icc)), name_str(1:15), totarea(sortedrivs(icc))/1.e6,  nb_pts(sortedrivs(icc))
3184          ENDIF
3185       ENDDO
3186    END IF
3187    !
3188    ! Save some of the basin information into files.
3189    !
3190    IF ( river_file ) THEN
3191
3192       IF ( INDEX(river_file_name,".nc") > 1 ) THEN
3193
3194          CALL routing_diagncfile(river_file_name, nbpt, lalo, nb_pts, topids, sorted_names, sortedrivs, &
3195               &                  pts, lbasin_area, lbasin_uparea, lrivercode, outpt, streams_nb, streams_avehops, &
3196               &                  streams_minhops, streams_maxhops, streams_resid)
3197
3198       ELSE
3199
3200          OPEN(diagunit, FILE=river_file_name)
3201          WRITE(diagunit,'(A)') "Basin ID, Area [km^2], Nb points, Lon and Lat of outflow"
3202          WRITE(diagunit,'(A)') "Nb streams, total number of hops, min, ave and max number of hops per stream"
3203          !
3204          DO icc = 1, num_largest
3205             !
3206             IF ( nb_pts(sortedrivs(icc)) .GT. 2 ) THEN
3207                !
3208                name_str = sorted_names(icc)
3209                !
3210                WRITE(diagunit,'(I5,A25,F14.5,I5,2F9.2)') topids(sortedrivs(icc)), name_str(1:15), totarea(sortedrivs(icc))/1.e6, &
3211                     &    nb_pts(sortedrivs(icc)), lalo(outpt(sortedrivs(icc),1),2), lalo(outpt(sortedrivs(icc),1),1)
3212                WRITE(diagunit,'(5I9,F16.4)') streams_nb(sortedrivs(icc)), &
3213                     & streams_avehops(sortedrivs(icc))*streams_nb(sortedrivs(icc)), &
3214                     & streams_minhops(sortedrivs(icc)), &
3215                     & streams_avehops(sortedrivs(icc)), &
3216                     & streams_maxhops(sortedrivs(icc)), streams_resid(sortedrivs(icc))
3217                !
3218             ENDIF
3219             !
3220          ENDDO
3221          !
3222          CLOSE(diagunit)
3223          !
3224       ENDIF
3225       !
3226    ENDIF
3227    !
3228    !
3229    nbrivers(:) = zero
3230    DO ig=1,nbpt
3231       nbrivers(ig) = COUNT(route_tobasin(ig,1:nbasmax) == nbasmax+3)
3232    ENDDO
3233    DO ig=1,nbpt
3234       IF ( nbrivers(ig) > 1 ) THEN
3235          WRITE(numout,*) 'Grid box ', ig, ' has ', NINT(nbrivers(ig)), ' outflow points.'
3236          WRITE(numout,*) 'The rivers which flow into the ocean at this point are :'
3237          DO icc=1,nbasmax
3238             IF ( route_tobasin(ig,icc) == nbasmax+3) THEN
3239                IF ( global_basinid(ig,icc) <= nb_small ) THEN
3240                   WRITE(numout,*) 'ID = ',global_basinid(ig,icc), ' Name = ', basin_names(global_basinid(ig,icc))
3241                ELSE
3242                   WRITE(numout,*) 'ID = ',global_basinid(ig,icc), ' Problem ===== ID is larger than possible'
3243                ENDIF
3244             ENDIF
3245          ENDDO
3246       ENDIF
3247    ENDDO
3248    !
3249    ic = COUNT(topo_resid .GT. 0.)
3250    IF (printlev>=1) THEN
3251       WRITE(numout,*) 'Maximum topographic index :', MAXVAL(topo_resid)
3252       WRITE(numout,*) 'Mean topographic index :', SUM(topo_resid, MASK=topo_resid .GT. zero)/ic
3253       WRITE(numout,*) 'Minimum topographic index :', MINVAL(topo_resid, MASK=topo_resid .GT. zero)
3254    END IF
3255   
3256    DEALLOCATE(pts)
3257    DEALLOCATE(outpt)
3258    DEALLOCATE(nb_pts)
3259    DEALLOCATE(totarea, tmparea)
3260    DEALLOCATE(streams_nb, streams_avehops, streams_minhops, streams_maxhops)
3261    !
3262    DEALLOCATE(lbasin_area, lbasin_uparea, lrivercode)
3263    !
3264    DEALLOCATE(allstreams)
3265    DEALLOCATE(tstreams)
3266    DEALLOCATE(tslen, tpts, tptbas, tuparea)
3267    DEALLOCATE(tcode)
3268    !
3269    ic = COUNT(topo_resid .GT. 0.)
3270    IF (printlev>=1) THEN
3271       WRITE(numout,*) 'Maximum topographic index :', MAXVAL(topo_resid)
3272       WRITE(numout,*) 'Mean topographic index :', SUM(topo_resid, MASK=topo_resid .GT. 0.)/ic
3273       WRITE(numout,*) 'Minimum topographic index :', MINVAL(topo_resid, MASK=topo_resid .GT. 0.)
3274    END IF
3275   
3276  END SUBROUTINE routing_diagnostic
3277  !
3278!! ================================================================================================================================
3279!! SUBROUTINE   : routing_diagcode
3280!!
3281!>\BRIEF       This subroutine determines the code in the Pfafstetter system for all points
3282!!              within the given catchment. 
3283!!
3284!! DESCRIPTION (definitions, functional, design, flags) : None
3285!!
3286!! RECENT CHANGE(S): None
3287!!
3288!! MAIN OUTPUT VARIABLE(S): streamcode
3289!!
3290!! REFERENCES   : None
3291!!
3292!! FLOWCHART    :None
3293!! \n
3294!_ ================================================================================================================================
3295
3296  SUBROUTINE routing_diagcode(ip, tpts, tpbas, tuparea, tslen, ls, allstreams, upstreamchange, streamcode) 
3297    !
3298    IMPLICIT NONE
3299    !
3300!! INPUT VARIABLES
3301    INTEGER(i_std), INTENT(in)                   :: ip             !!
3302    INTEGER(i_std), INTENT(in)                   :: ls             !!
3303    INTEGER(i_std), DIMENSION(ip), INTENT(in)    :: tpts           !!
3304    INTEGER(i_std), DIMENSION(ip), INTENT(in)    :: tpbas          !!
3305    REAL(r_std), DIMENSION(ip), INTENT(in)       :: tuparea        !!
3306    INTEGER(i_std), DIMENSION(ip), INTENT(in)    :: tslen          !!
3307    INTEGER(i_std), DIMENSION(ip,ls), INTENT(in) :: allstreams     !!
3308    REAL(r_std), DIMENSION(ip,ls), INTENT(in)    :: upstreamchange !!
3309    !
3310!! OUTPUT VARIABLES
3311    INTEGER(i_std), DIMENSION(ip), INTENT(out)   :: streamcode     !!
3312    !
3313!! LOCAL VARIABLES
3314    INTEGER(i_std)                               :: ilev, cntsubbas, ib, ic, i, it, ilevmax, imaxlen, nbzero !!
3315    INTEGER(i_std)                               :: tstreamcode(ip)!!
3316    INTEGER(i_std)                               :: indsubbas(ip)  !!
3317    INTEGER(i_std)                               :: iw(ip)         !!
3318    INTEGER(i_std)                               :: tdiff(ip)      !!
3319    INTEGER(i_std)                               :: tmpjunc(4)     !!
3320    INTEGER(i_std)                               :: junction(4)    !!
3321    INTEGER(i_std)                               :: ff(1)          !!
3322    INTEGER(i_std)                               :: ll             !!
3323    REAL(r_std)                                  :: chguparea(ip)  !!
3324    REAL(r_std)                                  :: largest        !!
3325
3326!_ ================================================================================================================================
3327    !
3328    streamcode(:) = 0
3329    !
3330    ! If we accept 4 grid boxes per coded basin then per level we need at least
3331    ! 4*9=36 boxes.
3332    !
3333    ilevmax = 0
3334    it = ip
3335    DO WHILE (it >= 36)
3336       ilevmax = ilevmax+1
3337       it = it/9
3338    ENDDO
3339    !
3340    DO ilev=1,ilevmax
3341       !
3342       ! Count number of sub-basins we already have
3343       !
3344       cntsubbas=0
3345       tstreamcode(:) = streamcode(:)
3346       DO WHILE ( COUNT(tstreamcode(:) >= 0) > 0 )
3347         cntsubbas=cntsubbas+1
3348         indsubbas(cntsubbas) = MAXVAL(tstreamcode(:))
3349         WHERE ( tstreamcode(:) == indsubbas(cntsubbas) ) tstreamcode = -1
3350       ENDDO
3351       !
3352       ! Go through all these basins in order to find the next Pfafstetter numbers
3353       !
3354       DO ib=1,cntsubbas
3355          !
3356          ! Get all the streams which have the current Pfadstetter number
3357          !
3358          it=0
3359          DO ic=1,ip
3360             IF ( streamcode(ic) == indsubbas(ib) ) THEN
3361                it =it+1
3362                iw(it)=ic 
3363             ENDIF
3364          ENDDO
3365          !
3366          ! Which is the longest stream in this basin ?
3367          !
3368          ff=MAXLOC(tslen(iw(1:it)))
3369          imaxlen=iw(ff(1))
3370          chguparea(:) = zero
3371          chguparea(1:tslen(imaxlen)) = upstreamchange(imaxlen, 1:tslen(imaxlen))
3372          !
3373          IF ( COUNT(chguparea(1:tslen(imaxlen)) > 0) < 4 ) THEN
3374             !
3375             ! If this subbasin is too small we just set all points to zero
3376             !
3377             DO i=1,it
3378                streamcode(iw(i)) = streamcode(iw(i))*10
3379             ENDDO
3380          ELSE
3381             !
3382             ! Else do the Pfafstetter numbering
3383             !
3384             !
3385             ! Where do we have the 4 largest change in upstream area on this stream.
3386             ! This must be the confluence of 2 rivers and thus a junction point.
3387             !
3388             largest=pi*R_Earth*R_Earth
3389             DO i=1,4
3390                ff = MAXLOC(chguparea(1:tslen(imaxlen)), MASK = chguparea(1:tslen(imaxlen)) < largest)
3391                tmpjunc(i) = ff(1)
3392                largest=chguparea(tmpjunc(i))
3393             ENDDO
3394             ! sort junctions to go from the outflow up-stream
3395             ff(1)=0
3396             DO i=1,4
3397                junction(i) = MINVAL(tmpjunc, MASK=tmpjunc > ff(1))
3398                ff(1) = junction(i)
3399             ENDDO
3400             !
3401             ! Find all streams which are identical up to that junction and increase their code accordingly
3402             !
3403             DO i=1,it
3404                ll=MIN(tslen(imaxlen),tslen(iw(i)))
3405                tdiff(1:ll) = allstreams(imaxlen,1:ll)-allstreams(iw(i),1:ll)
3406                nbzero = COUNT(tdiff(1:ll) == 0)
3407                IF (nbzero < junction(1) ) THEN
3408                   ! Before first of the 4 largest basins
3409                   streamcode(iw(i)) = streamcode(iw(i))*10+1
3410                ELSE IF (nbzero == junction(1) ) THEN
3411                   ! Stream part of the first largest basin
3412                   streamcode(iw(i)) = streamcode(iw(i))*10+2
3413                ELSE IF (nbzero < junction(2) ) THEN
3414                   ! Between first and second stream
3415                   streamcode(iw(i)) = streamcode(iw(i))*10+3
3416                ELSE IF (nbzero == junction(2) ) THEN
3417                   ! Stream part of the second basin
3418                   streamcode(iw(i)) = streamcode(iw(i))*10+4
3419                ELSE IF (nbzero < junction(3) ) THEN
3420                   ! In between stream 2 and 3
3421                   streamcode(iw(i)) = streamcode(iw(i))*10+5
3422                ELSE IF (nbzero == junction(3) ) THEN
3423                   ! Part of 3rd basin
3424                   streamcode(iw(i)) = streamcode(iw(i))*10+6
3425                ELSE IF (nbzero < junction(4) ) THEN
3426                   ! In between 3 and 4th basins
3427                   streamcode(iw(i)) = streamcode(iw(i))*10+7
3428                ELSE IF (nbzero == junction(4) ) THEN
3429                   ! Final of the 4 largest basins
3430                   streamcode(iw(i)) = streamcode(iw(i))*10+8
3431                ELSE
3432                   ! The rest of the points and also the basin of the longest stream
3433                   streamcode(iw(i)) = streamcode(iw(i))*10+9
3434                ENDIF
3435             ENDDO
3436          ENDIF
3437       ENDDO
3438       !
3439    ENDDO
3440    !
3441    !
3442  END SUBROUTINE routing_diagcode
3443  !
3444!! ================================================================================================================================
3445!! SUBROUTINE   : routing_diagncfile
3446!!
3447!>\BRIEF         This subroutine creates a netCDF file containing all the informations
3448!!                on the largest rivers which can be used for a refined analysis.
3449!!
3450!! DESCRIPTION (definitions, functional, design, flags) : None
3451!!
3452!! RECENT CHANGE(S): None
3453!!
3454!! MAIN OUTPUT VARIABLE(S): None
3455!!
3456!! REFERENCES   : None
3457!!
3458!! FLOWCHART    : None
3459!! \n
3460!_ ================================================================================================================================
3461
3462  SUBROUTINE routing_diagncfile(river_file_name, nbpt, lalo, nb_pts, topids, sorted_names, sortedrivs, &
3463       &       lbasin_index, lbasin_area, lbasin_uparea, lrivercode, outpt, streams_nb, streams_avehops, &
3464       &       streams_minhops, streams_maxhops, streams_resid)
3465    !
3466    USE netcdf
3467    !
3468    IMPLICIT NONE
3469    !
3470    !
3471!! INPUT VARIABLES
3472    REAL(r_std), INTENT(in)                     :: lalo(nbpt,2)             !! Vector of latitude and longitudes (beware of the order !)
3473
3474!! LOCAL VARIABLES
3475    CHARACTER(LEN=80)                           :: river_file_name          !! Filename in which we write the description of the rivers (1)
3476    INTEGER(i_std)                              :: nbpt                     !! Domain size  (unitless)
3477    INTEGER(i_std), DIMENSION(num_largest)      :: nb_pts                   !! Number of points in the basin (unitless)
3478    INTEGER(i_std), DIMENSION(num_largest)      :: topids                   !! The IDs of the first num_largest basins (unitless)
3479    CHARACTER(LEN=25), DIMENSION(num_largest)   :: sorted_names             !! Names of the basins to be put into the file (unitless)
3480    INTEGER(i_std), DIMENSION(num_largest)      :: sortedrivs               !!
3481    INTEGER(i_std), DIMENSION(num_largest,nbpt) :: lbasin_index             !!
3482    REAL(r_std), DIMENSION(num_largest,nbpt)    :: lbasin_area              !!
3483    REAL(r_std), DIMENSION(num_largest,nbpt)    :: lbasin_uparea            !!
3484    INTEGER(i_std), DIMENSION(num_largest,nbpt) :: lrivercode               !!
3485    !
3486    INTEGER(i_std), DIMENSION(num_largest,2)    :: outpt                    !! Outflow point for each basin (unitless)
3487    INTEGER(i_std), DIMENSION(num_largest)      :: streams_nb               !! Number of streams in basin (unitless)
3488    INTEGER(i_std), DIMENSION(num_largest)      :: streams_avehops          !! Average number of hops in streams (unitless)
3489    INTEGER(i_std), DIMENSION(num_largest)      :: streams_minhops          !! Minimum number of hops in streams (unitless)
3490    INTEGER(i_std), DIMENSION(num_largest)      :: streams_maxhops          !! Minimum number of hops in streams (unitless)
3491    REAL(r_std), DIMENSION(num_largest)         :: streams_resid            !! Average residence time
3492    !
3493    INTEGER(i_std)                              :: icc, fid, iret, ierr_tot, ib, ij, ik, i, j, lcc !! Indices (unitless)
3494    INTEGER(i_std)                              :: nlonid, nlatid, varid, varid2, varid3
3495    INTEGER(i_std)                              :: dims(2)                  !!
3496    REAL(r_std)                                 :: lon_min, lon_max, lat_min, lat_max
3497    CHARACTER(LEN=80)                           :: lon_name, lat_name, var_name, long_name, nc_name, att_str
3498
3499    REAL(r_std)                                 :: basinfrac(iim_g,jjm_g)   !!
3500    REAL(r_std)                                 :: basinuparea(iim_g,jjm_g) !!
3501    INTEGER(i_std)                              :: basincode(iim_g,jjm_g)   !!
3502    !
3503    LOGICAL                                     :: check=.FALSE.            !! (true/false)
3504    !
3505!! PARAMETERS
3506    INTEGER(i_std),PARAMETER                    :: kind_r_diag=NF90_REAL8   !!
3507    INTEGER(i_std),PARAMETER                    :: kind_i_diag=NF90_INT     !!
3508
3509!_ ================================================================================================================================
3510    !
3511    !
3512    ! 1.0 Create the NETCDF file and store the coordinates.
3513    !
3514    iret = NF90_CREATE(TRIM(river_file_name), NF90_CLOBBER, fid)
3515    IF (iret /= NF90_NOERR) THEN
3516       CALL ipslerr_p (3,'routing_diagncfile', 'Could not create file :', &
3517            & TRIM(river_file_name), '(Problem with disk place or filename ?)')
3518    ENDIF
3519    !
3520    ! 1.1 Define dimensions
3521    !
3522    IF ( grid_type == regular_lonlat ) THEN
3523       !
3524       ! 1.1.1 regular grid
3525       !
3526       iret = NF90_DEF_DIM(fid, 'lon', iim_g, dims(1))
3527       IF (iret /= NF90_NOERR) THEN
3528          CALL ipslerr_p (3,'routing_diagncfile', 'Dimension "x" can not be defined for the file : ', &
3529               &         TRIM(river_file_name),'(Solution ?)')
3530       ENDIF
3531       iret = NF90_DEF_DIM(fid, 'lat', jjm_g, dims(2))
3532       IF (iret /= NF90_NOERR) THEN
3533          CALL ipslerr_p (3,'routing_diagncfile', 'Dimension "y" can not be defined for the file : ', &
3534               &         TRIM(river_file_name),'(Solution ?)')
3535       ENDIF
3536    ELSE
3537       !
3538       ! 1.1.2 irregular grid
3539       !
3540       iret = NF90_DEF_DIM(fid, 'x', iim_g, dims(1))
3541       IF (iret /= NF90_NOERR) THEN
3542          CALL ipslerr_p (3,'routing_diagncfile', 'Dimension "x" can not be defined for the file : ', &
3543               &         TRIM(river_file_name),'(Solution ?)')
3544       ENDIF
3545       
3546       iret = NF90_DEF_DIM(fid, 'y', jjm_g, dims(2))
3547       IF (iret /= NF90_NOERR) THEN
3548          CALL ipslerr_p (3,'routing_diagncfile', 'Dimension "y" can not be defined for the file : ', &
3549               &         TRIM(river_file_name),'(Solution ?)')
3550       ENDIF
3551    ENDIF
3552    !
3553    !
3554    ! 1.2 Define variables and attributes
3555    !
3556    IF ( grid_type == regular_lonlat ) THEN
3557       !
3558       ! 1.2.1 regular grid
3559       !
3560       lon_name = 'lon'
3561       !
3562       iret = NF90_DEF_VAR(fid, lon_name, kind_r_diag, dims(1), nlonid)
3563       IF (iret /= NF90_NOERR) THEN
3564          CALL ipslerr_p (3,'routing_diagncfile', 'Variable '//lon_name//' can not be defined for the file : ', &
3565               &         TRIM(river_file_name),'(Solution ?)')
3566       ENDIF
3567       !
3568       lat_name = 'lat'
3569       iret = NF90_DEF_VAR(fid, lat_name, kind_r_diag, dims(2), nlatid)
3570       IF (iret /= NF90_NOERR) THEN
3571          CALL ipslerr_p (3,'routing_diagncfile', 'Variable '//lat_name//' can not be defined for the file : ', &
3572               &         TRIM(river_file_name),'(Solution ?)')
3573       ENDIF
3574       !
3575    ELSE
3576       !
3577       ! 1.2.2 irregular grid
3578       !
3579       lon_name = 'nav_lon'
3580       !
3581       iret = NF90_DEF_VAR(fid, lon_name, kind_r_diag, dims, nlonid)
3582       IF (iret /= NF90_NOERR) THEN
3583          CALL ipslerr_p (3,'routing_diagncfile', 'Variable '//lon_name//' can not be defined for the file : ', &
3584               &         TRIM(river_file_name),'(Solution ?)')
3585       ENDIF
3586       !
3587       lat_name = 'nav_lat'
3588       iret = NF90_DEF_VAR(fid, lat_name, kind_r_diag, dims, nlatid)
3589       IF (iret /= NF90_NOERR) THEN
3590          CALL ipslerr_p (3,'routing_diagncfile', 'Variable '//lat_name//' can not be defined for the file : ', &
3591               &         TRIM(river_file_name),'(Solution ?)')
3592       ENDIF
3593       !
3594    ENDIF
3595    !
3596    ! 1.3 Add attributes to the coordinate variables
3597    !
3598    iret = NF90_PUT_ATT(fid, nlonid, 'units', "degrees_east") 
3599    IF (iret /= NF90_NOERR) THEN
3600       CALL ipslerr_p (3,'routing_diagncfile', 'Could not add attribut to variable '//lon_name//' for the file :', &
3601            &          TRIM(river_file_name),'(Solution ?)')
3602    ENDIF
3603    !
3604    lon_min = -180.
3605    lon_max = 180.
3606    !
3607    iret = NF90_PUT_ATT(fid, nlonid, 'valid_min', lon_min)
3608    IF (iret /= NF90_NOERR) THEN
3609       CALL ipslerr_p (3,'routing_diagncfile', 'Could not add attribut to variable '//lon_name//' for the file :', &
3610            &          TRIM(river_file_name),'(Solution ?)')
3611    ENDIF
3612    iret = NF90_PUT_ATT(fid, nlonid, 'valid_max', lon_max)
3613    IF (iret /= NF90_NOERR) THEN
3614       CALL ipslerr_p (3,'routing_diagncfile', 'Could not add attribut to variable '//lon_name//' for the file :', &
3615            &          TRIM(river_file_name),'(Solution ?)')
3616    ENDIF
3617    !
3618    iret = NF90_PUT_ATT(fid, nlonid, 'long_name', "Longitude")
3619    IF (iret /= NF90_NOERR) THEN
3620       CALL ipslerr_p (3,'routing_diagncfile', 'Could not add attribut to variable '//lon_name//' for the file :', &
3621            &          TRIM(river_file_name),'(Solution ?)')
3622    ENDIF
3623    iret = NF90_PUT_ATT(fid, nlatid, 'units', "degrees_north")
3624    IF (iret /= NF90_NOERR) THEN
3625       CALL ipslerr_p (3,'routing_diagncfile', 'Could not add attribut to variable '//lat_name//' for the file :', &
3626            &          TRIM(river_file_name),'(Solution ?)')
3627    ENDIF
3628    !
3629    lat_max = 90.
3630    lat_min = -90.
3631    !
3632    iret = NF90_PUT_ATT(fid, nlatid, 'valid_min', lat_min)
3633    IF (iret /= NF90_NOERR) THEN
3634       CALL ipslerr_p (3,'routing_diagncfile', 'Could not add attribut to variable '//lat_name//' for the file :', &
3635            &          TRIM(river_file_name),'(Solution ?)')
3636    ENDIF
3637    iret = NF90_PUT_ATT(fid, nlatid, 'valid_max', lat_max)
3638    IF (iret /= NF90_NOERR) THEN
3639       CALL ipslerr_p (3,'routing_diagncfile', 'Could not add attribut to variable '//lat_name//' for the file :', &
3640            &          TRIM(river_file_name),'(Solution ?)')
3641    ENDIF
3642    iret = NF90_PUT_ATT(fid, nlatid, 'long_name', "Latitude")
3643    IF (iret /= NF90_NOERR) THEN
3644       CALL ipslerr_p (3,'routing_diagncfile', 'Could not add attribut to variable '//lat_name//' for the file :', &
3645            &          TRIM(river_file_name),'(Solution ?)')
3646    ENDIF
3647    !
3648    iret = NF90_ENDDEF(fid)
3649    IF (iret /= NF90_NOERR) THEN
3650       CALL ipslerr_p (3,'routing_diagncfile', 'Could not end definitions in the file : ', &
3651 &          TRIM(river_file_name),'(Solution ?)')
3652    ENDIF
3653    !
3654    !  1.4 Write coordinates
3655    !
3656    IF ( grid_type == regular_lonlat ) THEN
3657       !
3658       ! 1.4.1 regular grid
3659       !
3660       iret = NF90_PUT_VAR(fid, nlonid, lon_g(1:iim_g,1))
3661       IF (iret /= NF90_NOERR) THEN
3662          CALL ipslerr_p (3,'routing_diagncfile', 'Could not put variable nav_lon  in the file : ', &
3663               &          TRIM(river_file_name),'(Solution ?)')
3664       ENDIF
3665       !
3666       iret = NF90_PUT_VAR(fid, nlatid, lat_g(1,1:jjm_g))
3667       IF (iret /= NF90_NOERR) THEN
3668          CALL ipslerr_p (3,'routing_diagncfile', 'Could not put variable nav_lat  in the file : ', &
3669               &          TRIM(river_file_name),'(Solution ?)')
3670       ENDIF
3671    ELSE
3672       !
3673       ! 1.4.2 irregular grid
3674       !
3675       iret = NF90_PUT_VAR(fid, nlonid, lon_g)
3676       IF (iret /= NF90_NOERR) THEN
3677          CALL ipslerr_p (3,'routing_diagncfile', 'Could not put variable nav_lon  in the file : ', &
3678               &          TRIM(river_file_name),'(Solution ?)')
3679       ENDIF
3680       !
3681       iret = NF90_PUT_VAR(fid, nlatid, lat_g)
3682       IF (iret /= NF90_NOERR) THEN
3683          CALL ipslerr_p (3,'routing_diagncfile', 'Could not put variable nav_lat  in the file : ', &
3684               &          TRIM(river_file_name),'(Solution ?)')
3685       ENDIF
3686    ENDIF
3687    !
3688    ! 2.0 Go through all basins and wirte the information into the netCDF file.
3689    !
3690    DO icc = 1, num_largest
3691       !
3692       ! 2.1 Compute the fields to be saved in the file
3693       !
3694       ib=sortedrivs(icc)
3695       !
3696       !
3697       IF ( nb_pts(ib) > 2 ) THEN
3698          !
3699          basinfrac(:,:) = zero
3700          basinuparea(:,:) = zero
3701          basincode(:,:) = zero
3702          !
3703          DO ij=1, nb_pts(ib)
3704
3705             ik=lbasin_index(ib,ij)
3706
3707             j = ((index_g(ik)-1)/iim_g) + 1
3708             i = (index_g(ik)-(j-1)*iim_g)
3709
3710             IF ( resolution_g(ik,1) == 0 ) THEN
3711                basinfrac(i,j) = basinfrac(i,j) + lbasin_area(ib,ij)/(resolution_g(ik,2)*resolution_g(ik,2)*pi)
3712             ELSE
3713                basinfrac(i,j) = basinfrac(i,j) + lbasin_area(ib,ij)/(resolution_g(ik,1)*resolution_g(ik,2))
3714             ENDIF
3715             basinuparea(i,j) = MAX(basinuparea(i,j), lbasin_uparea(ib,ij))
3716             basincode(i,j) = lrivercode(ib,ij)
3717
3718          ENDDO
3719          !
3720          DO i=1,iim_g
3721             DO j=1,jjm_g
3722                IF ( basinfrac(i,j) <= EPSILON(zero) ) THEN
3723                   basinfrac(i,j) = undef_sechiba
3724                   basinuparea(i,j)  = undef_sechiba
3725                   basincode(i,j)  = undef_int
3726                ELSE
3727                   basinfrac(i,j) = MIN(basinfrac(i,j), un)
3728                ENDIF
3729             ENDDO
3730          ENDDO
3731          !
3732          !
3733          ! 2.2 Define the variables in the netCDF file
3734          !
3735          iret = NF90_REDEF(fid)
3736          IF (iret /= NF90_NOERR) THEN
3737             CALL ipslerr_p (3,'routing_diagncfile', &
3738                  &          'Could not restart definitions in the file : ', &
3739                  &          TRIM(river_file_name),'(Solution ?)')
3740          ENDIF
3741          !
3742          ! Create a name more suitable for a variable in a netCDF file
3743          !
3744          nc_name =  TRIM(sorted_names(icc))
3745          ! Take out all character which could cause problems
3746          lcc=LEN_TRIM(nc_name)
3747          DO ij=1,lcc
3748             IF ( nc_name(ij:ij) == " " ) nc_name(ij:ij) = "_"
3749             IF ( nc_name(ij:ij) == "(" ) nc_name(ij:ij) = "_"
3750             IF ( nc_name(ij:ij) == ")" ) nc_name(ij:ij) = "_"
3751          ENDDO
3752          ! reduce redundant "__"
3753          DO ij=1,lcc
3754             IF ( nc_name(ij:ij+1) == "__" ) nc_name(ij+1:)=nc_name(ij+2:lcc)
3755          ENDDO
3756          lcc=LEN_TRIM(nc_name)
3757          IF ( nc_name(lcc:lcc) == "_" ) nc_name(lcc:lcc) = " "
3758          !
3759          !
3760          ! 2.3 Fraction variable
3761          !
3762          IF (check) WRITE(numout,*) "Define Fraction variable and add attributes"
3763          !
3764          var_name =  TRIM(nc_name)//"_frac"
3765          !
3766          iret = NF90_DEF_VAR(fid, TRIM(var_name), kind_r_diag, dims, varid)
3767          IF (iret /= NF90_NOERR) THEN
3768             CALL ipslerr_p (3,'routing_diagncfile', 'Variable '//TRIM(var_name)//' can not be defined for the file : ', &
3769                  &         TRIM(river_file_name),'(Solution ?)')
3770          ENDIF
3771          !
3772          ierr_tot = 0
3773          ! Units
3774          iret = NF90_PUT_ATT(fid, varid, 'units', "-")
3775          IF (iret /= NF90_NOERR) THEN
3776             WRITE(numout,*) 'Units',  iret
3777             WRITE(numout,*) TRIM(NF90_STRERROR(iret))
3778             ierr_tot = ierr_tot + 1
3779          ENDIF
3780          ! Long name
3781          long_name = "Fraction of basin "//TRIM(sorted_names(icc))//" per grid box"
3782          iret = NF90_PUT_ATT(fid, varid, 'long_name', long_name)
3783          IF (iret /= NF90_NOERR) THEN
3784             WRITE(numout,*) 'Long_Name', long_name, iret
3785             WRITE(numout,*) TRIM(NF90_STRERROR(iret))
3786             ierr_tot = ierr_tot + 1
3787          ENDIF
3788          ! Missing value
3789          iret = NF90_PUT_ATT(fid, varid, 'missing_value', undef_sechiba)
3790          IF (iret /= NF90_NOERR) THEN
3791             WRITE(numout,*) 'Missing value', undef_sechiba, iret
3792             WRITE(numout,*) TRIM(NF90_STRERROR(iret))
3793             ierr_tot = ierr_tot + 1
3794          ENDIF
3795          !
3796          ib=sortedrivs(icc)
3797          IF ( check ) WRITE(numout,*) "Doing basin ", icc," corrsdponding to index = ", ib, "num_largest : ", num_largest
3798          !
3799          ! Nb of grid points in basin
3800          att_str='Nb_of_grid_points_in_basin'
3801          iret = NF90_PUT_ATT(fid, varid, att_str, nb_pts(ib))
3802          IF (iret /= NF90_NOERR) THEN
3803             WRITE(numout,*) 'Nb of grid points in basin', nb_pts(ib), iret
3804             WRITE(numout,*) TRIM(NF90_STRERROR(iret))
3805             ierr_tot = ierr_tot + 1
3806          ENDIF
3807          !
3808          ! Longitude of outflow point
3809          att_str='Longitude_of_outflow_point'
3810          iret = NF90_PUT_ATT(fid, varid, att_str, lalo(outpt(ib,1),2))
3811          IF (iret /= NF90_NOERR) THEN
3812             WRITE(numout,*) 'Longitude of outflow point', lalo(outpt(ib,1),2), iret
3813             WRITE(numout,*) TRIM(NF90_STRERROR(iret))
3814             ierr_tot = ierr_tot + 1
3815          ENDIF
3816          !
3817          ! Latitide of outflow point
3818          att_str='Latitude_of_outflow_point'
3819          iret = NF90_PUT_ATT(fid, varid, att_str, lalo(outpt(ib,1),1))
3820          IF (iret /= NF90_NOERR) THEN
3821             WRITE(numout,*) 'Latitude of outflow point',  lalo(outpt(ib,1),1), iret
3822             WRITE(numout,*) TRIM(NF90_STRERROR(iret))
3823             ierr_tot = ierr_tot + 1
3824          ENDIF
3825          !
3826          ! Number of streams
3827          att_str= 'Number_of_streams'
3828          iret = NF90_PUT_ATT(fid, varid, att_str, streams_nb(ib))
3829          IF (iret /= NF90_NOERR) THEN
3830             WRITE(numout,*) 'Number of streams', streams_nb(ib), iret
3831             WRITE(numout,*) TRIM(NF90_STRERROR(iret))
3832             ierr_tot = ierr_tot + 1
3833          ENDIF
3834          !
3835          ! Total number of hops to go to the oceans
3836          att_str='Total_number_of_hops_to_ocean'
3837          iret = NF90_PUT_ATT(fid, varid, att_str, streams_avehops(ib)*streams_nb(ib))
3838          IF (iret /= NF90_NOERR) THEN
3839             WRITE(numout,*) 'Total number of hops to go to the oceans ', streams_avehops(ib)*streams_nb(ib), iret
3840             ierr_tot = ierr_tot + 1
3841          ENDIF
3842          !
3843          ! Minimum number of hops to go to the ocean for any stream
3844          att_str='Minimum_number_of_hops_to_ocean_for_any_stream'
3845          iret = NF90_PUT_ATT(fid, varid, att_str, streams_minhops(ib))
3846          IF (iret /= NF90_NOERR) THEN
3847             WRITE(numout,*) 'Minimum number of hops to go tp the ocean for any stream', streams_minhops(ib), iret
3848             ierr_tot = ierr_tot + 1
3849          ENDIF
3850          !
3851          ! Average number of hops to go to the ocean for any stream
3852          att_str='Average_number_of_hops_to_ocean_for_any_stream'
3853          iret = NF90_PUT_ATT(fid, varid, att_str, streams_avehops(ib))
3854          IF (iret /= NF90_NOERR) THEN
3855             WRITE(numout,*) 'Average number of hops to go tp the ocean for any stream', streams_avehops(ib), iret
3856             ierr_tot = ierr_tot + 1
3857          ENDIF
3858          !
3859          ! Maximum number of hops to go to the ocean for any stream
3860          att_str='Maximum_number_of_hops_to_ocean_for_any_stream'
3861          iret = NF90_PUT_ATT(fid, varid, att_str, streams_maxhops(ib))
3862          IF (iret /= NF90_NOERR) THEN
3863             WRITE(numout,*) 'Maximum number of hops to go tp the ocean for any stream', streams_maxhops(ib), iret
3864             ierr_tot = ierr_tot + 1
3865          ENDIF
3866          !
3867          ! Average residence time in the basin
3868          att_str='Average_residence_time_in_basin'
3869          iret = NF90_PUT_ATT(fid, varid, att_str, streams_resid(ib))
3870          IF (iret /= NF90_NOERR) THEN
3871             WRITE(numout,*) 'Average residence time in the basin', streams_resid(ib), iret
3872             ierr_tot = ierr_tot + 1
3873          ENDIF
3874          !
3875          IF (ierr_tot > 0 ) THEN
3876             CALL ipslerr_p (3,'routing_diagncfile', 'Could not add some attributes to variable '//var_name//' for the file :', &
3877                  &          TRIM(river_file_name),'(Solution ?)')
3878          ENDIF
3879          !
3880          ! 2.4 Upstream area variable variable
3881          !
3882          IF (check) WRITE(numout,*) "Define Upstream variable and add attributes"
3883          !
3884          ! Create a name more suitable for a variable in a netCDF file
3885          !
3886          var_name =  TRIM(nc_name)//"_upstream"
3887          DO ij=1,LEN_TRIM(var_name)
3888             IF ( var_name(ij:ij) == " " ) var_name(ij:ij) = "_"
3889          ENDDO
3890          !
3891          iret = NF90_DEF_VAR(fid, TRIM(var_name), kind_r_diag, dims, varid2)
3892          IF (iret /= NF90_NOERR) THEN
3893             CALL ipslerr_p (3,'routing_diagncfile', 'Variable '//TRIM(var_name)//' can not be defined for the file : ', &
3894                  &         TRIM(river_file_name),'(Solution ?)')
3895          ENDIF
3896          !
3897          ierr_tot = 0
3898          ! Units
3899          iret = NF90_PUT_ATT(fid, varid2, 'units', "m^2")
3900          IF (iret /= NF90_NOERR) ierr_tot = ierr_tot + 1
3901          ! Long name
3902          long_name = "Upstream area of basin "//TRIM(sorted_names(icc))//" in the grid box"
3903          iret = NF90_PUT_ATT(fid, varid2, 'long_name', long_name)
3904          IF (iret /= NF90_NOERR) ierr_tot = ierr_tot + 1
3905          ! Missing value
3906          iret = NF90_PUT_ATT(fid, varid2, 'missing_value', undef_sechiba)
3907          IF (iret /= NF90_NOERR) ierr_tot = ierr_tot + 1
3908          !
3909          IF (ierr_tot > 0 ) THEN
3910             CALL ipslerr_p (3,'routing_diagncfile', 'Could not add some attributes to variable '//var_name//' for the file :', &
3911                  &          TRIM(river_file_name),'(Solution ?)')
3912          ENDIF
3913          !
3914          ! 2.5 Pfafstetter codes for basins
3915          !
3916          IF (check) WRITE(numout,*) "Define Pfafstetter codes variable and add attributes"
3917          !
3918          var_name =  TRIM(nc_name)//"_coding"
3919          DO ij=1,LEN_TRIM(var_name)
3920             IF ( var_name(ij:ij) == " " ) var_name(ij:ij) = "_"
3921          ENDDO
3922          !
3923          iret = NF90_DEF_VAR(fid, TRIM(var_name), kind_i_diag, dims, varid3)
3924          IF (iret /= NF90_NOERR) THEN
3925             CALL ipslerr_p (3,'routing_diagncfile', 'Variable '//TRIM(var_name)//' can not be defined for the file : ', &
3926                  &         TRIM(river_file_name),'(Solution ?)')
3927          ENDIF
3928          !
3929          ierr_tot = 0
3930          ! Units
3931          iret = NF90_PUT_ATT(fid, varid3, 'units', "-")
3932          IF (iret /= NF90_NOERR) ierr_tot = ierr_tot + 1
3933          ! Long name
3934          long_name = "Pfafstetter codes of grid boxes in basin "//TRIM(sorted_names(icc))
3935          iret = NF90_PUT_ATT(fid, varid3, 'long_name', long_name)
3936          IF (iret /= NF90_NOERR) ierr_tot = ierr_tot + 1
3937          ! Missing value
3938          iret = NF90_PUT_ATT(fid, varid3, 'missing_value', undef_int)
3939          IF (iret /= NF90_NOERR) ierr_tot = ierr_tot + 1
3940          !
3941          IF (ierr_tot > 0 ) THEN
3942             CALL ipslerr_p (3,'routing_diagncfile', 'Could not add some attributes to variable '//var_name//' for the file :', &
3943                  &          TRIM(river_file_name),'(Solution ?)')
3944          ENDIF
3945          !
3946          ! 2.6 ENDDEF of netCDF file
3947          !
3948          IF (check) WRITE(numout,*) "END define"
3949          !
3950          iret = NF90_ENDDEF(fid)
3951          IF (iret /= NF90_NOERR) THEN
3952             CALL ipslerr_p (3,'routing_diagncfile', &
3953                  &          'Could not end definitions in the file : ', &
3954                  &          TRIM(river_file_name),'(Solution ?)')
3955          ENDIF
3956          !
3957          ! 2.7 Write the data to the file
3958          !
3959          IF (check) WRITE(numout,*) "Put basinfrac"
3960          iret = NF90_PUT_VAR(fid, varid, basinfrac)
3961          IF (iret /= NF90_NOERR) THEN
3962             CALL ipslerr_p (3,'routing_diagncfile', 'Could not put variable basinfrac in the file : ', &
3963                  &          TRIM(river_file_name),'(Solution ?)')
3964          ENDIF
3965
3966          IF (check) WRITE(numout,*) "Put basinuparea"
3967          iret = NF90_PUT_VAR(fid, varid2, basinuparea)
3968          IF (iret /= NF90_NOERR) THEN
3969             CALL ipslerr_p (3,'routing_diagncfile', 'Could not put variable basinuparea in the file : ', &
3970                  &          TRIM(river_file_name),'(Solution ?)')
3971          ENDIF
3972
3973          IF (check) WRITE(numout,*) "Put basincode"
3974          iret = NF90_PUT_VAR(fid, varid3, basincode)
3975          IF (iret /= NF90_NOERR) THEN
3976             CALL ipslerr_p (3,'routing_diagfile', 'Could not put variable basincode in the file : ', &
3977                  &          TRIM(river_file_name),'(Solution ?)')
3978          ENDIF
3979          !
3980       ENDIF
3981       !
3982    ENDDO
3983    !
3984    IF (check) WRITE(numout,*) "Close file"
3985    !
3986    ! Close netCDF file and do some memory management.
3987    !
3988    iret = NF90_CLOSE(fid)
3989    IF (iret /= NF90_NOERR) THEN
3990       CALL ipslerr_p (3,'routing_diagncfile', &
3991            &          'Could not end definitions in the file : ', &
3992            &          TRIM(river_file_name),'(Solution ?)')
3993    ENDIF
3994    !
3995    !
3996  END SUBROUTINE routing_diagncfile
3997  !
3998!! ================================================================================================================================
3999!! SUBROUTINE   : routing_basins_p
4000!!
4001!>\BRIEF        This parallelized subroutine computes the routing map if needed.
4002!!
4003!! DESCRIPTION (definitions, functional, design, flags) : None
4004!!
4005!! RECENT CHANGE(S): None
4006!!
4007!! MAIN OUTPUT VARIABLE(S):
4008!!
4009!! REFERENCES   : None
4010!!
4011!! FLOWCHART    : None
4012!! \n
4013!_ ================================================================================================================================
4014
4015  SUBROUTINE routing_basins_p(nbpt, lalo, neighbours, resolution, contfrac)
4016    !
4017    IMPLICIT NONE
4018    !
4019!! INPUT VARIABLES
4020    INTEGER(i_std), INTENT(in) :: nbpt               !! Domain size (unitless)
4021    REAL(r_std), INTENT(in)    :: lalo(nbpt,2)       !! Vector of latitude and longitudes (beware of the order !)
4022    INTEGER(i_std), INTENT(in) :: neighbours(nbpt,NbNeighb) !! Vector of neighbours for each grid point (1=North and then clockwise) (unitless)
4023    REAL(r_std), INTENT(in)    :: resolution(nbpt,2) !! The size of each grid box in X and Y (m)
4024    REAL(r_std), INTENT(in)    :: contfrac(nbpt)     !! Fraction of land in each grid box (unitless;0-1)
4025
4026!_ ================================================================================================================================
4027
4028!    INTEGER(i_std)    :: neighbours_tmp(nbpt,8)
4029!    INTEGER(i_std) :: i,j
4030   
4031!    DO i=1,nbp_loc
4032!      DO j=1,NbNeighb
4033!       IF (neighbours(i,j)==-1) THEN
4034!         neighbours_tmp(i,j)=neighbours(i,j)
4035!       ELSE
4036!         neighbours_tmp(i,j)=neighbours(i,j)+nbp_para_begin(mpi_rank)-1
4037!       ENDIF 
4038!      ENDDO
4039!    ENDDO
4040
4041    routing_area => routing_area_glo 
4042    topo_resid => topo_resid_glo
4043    route_togrid => route_togrid_glo
4044    route_tobasin => route_tobasin_glo
4045    route_nbintobas => route_nbintobas_glo
4046    global_basinid => global_basinid_glo
4047 
4048    IF (is_root_prc) CALL routing_basins(nbp_glo,lalo_g, neighbours_g, resolution_g, contfrac_g)
4049
4050    routing_area => routing_area_loc 
4051    topo_resid => topo_resid_loc
4052    route_togrid => route_togrid_loc
4053    route_tobasin => route_tobasin_loc
4054    route_nbintobas => route_nbintobas_loc
4055    global_basinid => global_basinid_loc
4056
4057    CALL scatter(routing_area_glo,routing_area_loc)
4058    CALL scatter(topo_resid_glo,topo_resid_loc)
4059    CALL scatter(route_togrid_glo,route_togrid_loc)
4060    CALL scatter(route_tobasin_glo,route_tobasin_loc)
4061    CALL scatter(route_nbintobas_glo,route_nbintobas_loc)
4062    CALL scatter(global_basinid_glo,global_basinid_loc)
4063   
4064  END SUBROUTINE routing_basins_p
4065  !
4066 
4067!! ================================================================================================================================
4068!! SUBROUTINE   : routing_basins
4069!!
4070!>\BRIEF        This non-parallelized subroutine reads in the map of basins and flow direction to construct
4071!!              the catchments of each grid box.
4072!!
4073!! DESCRIPTION (definitions, functional, design, flags) :
4074!! The work is done in a number of steps which are performed locally on the
4075!! GCM grid:
4076!!  1) First we find the grid-points of the high resolution routing grid which are
4077!!     within the coarser grid of the GCM.
4078!!  2) When we have these grid points we decompose them into basins in the routine
4079!!     routing_findbasins. A number of simplifications are done if needed.
4080!!  3) In the routine routing_globalize we put the basin information of this grid
4081!!     into the global fields.
4082!! Then we work on the global grid to perform the following tasks :
4083!!  1) We link up the basins of the various grid points and check the global consistency.
4084!!  2) The area of each outflow point is computed.
4085!!  3) The final step is to reduce the number of basins in order to fit into the truncation.\n
4086!!
4087!! RECENT CHANGE(S): None
4088!!
4089!! MAIN OUTPUT VARIABLE(S): None, as the routine puts information into the global variables of the module.
4090!!
4091!! REFERENCES   : None
4092!!
4093!! FLOWCHART    : None
4094!! \n
4095!_ ================================================================================================================================
4096
4097SUBROUTINE routing_basins(nbpt, lalo, neighbours, resolution, contfrac)
4098    !
4099    IMPLICIT NONE
4100    !
4101!! INPUT VARIABLES
4102    INTEGER(i_std), INTENT(in)                    :: nbpt                  !! Domain size (unitless)
4103    REAL(r_std), INTENT(in)                       :: lalo(nbpt,2)          !! Vector of latitude and longitudes (beware of the order !)
4104    INTEGER(i_std), INTENT(in)                    :: neighbours(nbpt,NbNeighb)!! Vector of neighbours for each grid point
4105                                                                           !! (1=North and then cloxkwise)
4106    REAL(r_std), INTENT(in)                       :: resolution(nbpt,2)    !! The size of each grid box in X and Y (m)
4107    REAL(r_std), INTENT(in)                       :: contfrac(nbpt)        !! Fraction of land in each grid box (unitless;0-1)
4108    !
4109!! LOCAL VARIABLES
4110    CHARACTER(LEN=80)                             :: filename              !! Name of the netcdf file (unitless)
4111    INTEGER(i_std)                                :: iml, jml, lml, tml, fid, ib, ip, jp, fopt !! Indices (unitless)
4112    REAL(r_std)                                   :: lev(1), date, dt, coslat
4113    INTEGER(i_std)                                :: itau(1)               !!
4114    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: trip                  !! The trip field (unitless)
4115    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: basins                !! The basin field (unitless)
4116    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: topoindex             !! Topographic index of the residence time (m)
4117    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: hierarchy             !!
4118    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: lat_rel               !!
4119    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: lon_rel               !!
4120    !
4121    INTEGER(i_std)                                :: nbi, nbj              !! Number of point in x and y within the grid (unitless)
4122    REAL(r_std)                                   :: min_topoind           !! The current minimum of topographic index (m)
4123    REAL(r_std)                                   :: max_basins            !!
4124    REAL(r_std)                                   :: invented_basins       !!
4125    !
4126    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: area_bx               !! Area of each small box in the grid box (m^2)
4127    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: hierarchy_bx          !! Level in the basin of the point
4128    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: lon_bx                !!
4129    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: lat_bx                !!
4130    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: topoind_bx            !! Topographic index of the residence time for each of the smaller boxes (m)
4131    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:)   :: trip_bx               !! The trip field for each of the smaller boxes (unitless)
4132    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:)   :: basin_bx              !!
4133    INTEGER(i_std), ALLOCATABLE, DIMENSION(:)     :: coast_pts             !! The coastal flow points (unitless)
4134    !
4135    INTEGER(i_std), ALLOCATABLE, DIMENSION(:)     :: basin_count           !!
4136    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:)   :: basin_id              !!
4137    REAL(r_std),  ALLOCATABLE, DIMENSION(:,:)     :: basin_area            !!
4138    REAL(r_std),  ALLOCATABLE, DIMENSION(:,:)     :: basin_hierarchy       !!
4139    REAL(r_std),  ALLOCATABLE, DIMENSION(:,:)     :: basin_topoind         !! Topographic index of the residence time for a basin (m)
4140    REAL(r_std),  ALLOCATABLE, DIMENSION(:,:)     :: fetch_basin           !!
4141    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:)   :: basin_flowdir         !! Water flow directions in the basin (unitless)
4142    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:)   :: outflow_grid          !! Type of outflow on the grid box (unitless)
4143    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:)   :: outflow_basin         !!
4144    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:)   :: inflow_number         !!
4145    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:,:) :: inflow_basin          !!
4146    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:,:) :: inflow_grid           !!
4147    INTEGER(i_std), ALLOCATABLE, DIMENSION(:)     :: nbcoastal             !!
4148    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:)   :: coastal_basin         !!
4149    !
4150    ! Interpolation help variables
4151    !
4152    INTEGER(i_std)                                :: nix, njx              !!
4153    CHARACTER(LEN=30)                             :: callsign              !!
4154    REAL(r_std), ALLOCATABLE, DIMENSION(:,:,:)    :: resol_lu              !! Resolution
4155    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:)   :: mask                  !! Mask to exclude some points (unitless)
4156    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: sub_area              !! Area on the fine grid (m^2)
4157    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:,:) :: sub_index             !! Indices of the points we need on the fine grid (unitless)
4158    INTEGER(i_std), ALLOCATABLE, DIMENSION(:)     :: sub_pts               !! Number of high resolution points on this grid (unitless)
4159    INTEGER                                       :: ALLOC_ERR             !!
4160    LOGICAL                                       :: ok_interpol = .FALSE. !! Flag for interpolation (true/false)
4161    !
4162    INTEGER(i_std)                                :: nb_basin              !! Number of sub-basins (unitless)
4163    INTEGER(i_std)                                :: nwbas                 !!
4164    INTEGER(i_std), ALLOCATABLE, DIMENSION(:)     :: basin_inbxid          !!
4165    INTEGER(i_std), ALLOCATABLE, DIMENSION(:)     :: basin_sz              !!
4166    INTEGER(i_std), ALLOCATABLE, DIMENSION(:)     :: basin_bxout           !!
4167    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:,:) :: basin_pts             !!
4168    CHARACTER(LEN=7)                              :: fmt                   !!
4169    LOGICAL                                       :: debug = .FALSE.       !! (true/false)
4170    !
4171    INTEGER(i_std), DIMENSION(2)                  :: diagbox = (/ 1, 2 /)  !!
4172
4173!_ ================================================================================================================================
4174    !
4175    !
4176    IF ( .NOT. is_root_prc) THEN
4177       WRITE(numout,*) "is_root_prc = ", is_root_prc
4178       CALL ipslerr_p (3,'routing_basins', &
4179            &          'routing_basins is not suitable for running in parallel', &
4180            &          'We are here on a non root processor. ','(STOP from routing_basins)')
4181    ENDIF
4182    !
4183    ! Test on diagbox and nbpt
4184    !
4185    IF (debug) THEN
4186       IF (ANY(diagbox .GT. nbpt)) THEN
4187          WRITE(numout,*) "Debug diganostics : nbpt, diagbox", nbpt, diagbox
4188          call ipslerr_p(3,'routing_basin', &
4189               &      'Problem with diagbox in debug mode.', & 
4190               &      'diagbox values can''t be greater than land points number.', &
4191               &      '(decrease diagbox wrong value)')
4192       ENDIF
4193    ENDIF
4194    !
4195    !
4196    !  Needs to be a configurable variable
4197    !
4198    !
4199    !Config Key   = ROUTING_FILE
4200    !Config Desc  = Name of file which contains the routing information
4201    !Config If    = RIVER_ROUTING
4202    !Config Def   = routing.nc
4203    !Config Help  = The file provided here should alow the routing module to
4204    !Config         read the high resolution grid of basins and the flow direction
4205    !Config         from one mesh to the other.
4206    !Config Units = [FILE]
4207    !
4208    filename = 'routing.nc'
4209    CALL getin('ROUTING_FILE',filename)
4210    !
4211    CALL flininfo(filename,iml, jml, lml, tml, fid)
4212    CALL flinclo(fid)
4213    !
4214    ! soils_param.nc file is 1° soit texture file.
4215    !
4216    ALLOCATE(lat_rel(iml,jml), STAT=ALLOC_ERR)
4217    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for lat_rel','','')
4218
4219    ALLOCATE(lon_rel(iml,jml), STAT=ALLOC_ERR)
4220    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for lon_rel','','')
4221
4222    ALLOCATE (trip(iml,jml), STAT=ALLOC_ERR)
4223    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for trip','','')
4224
4225    ALLOCATE (basins(iml,jml), STAT=ALLOC_ERR)
4226    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for basins','','')
4227
4228    ALLOCATE (topoindex(iml,jml), STAT=ALLOC_ERR)
4229    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for topoindex','','')
4230
4231    ALLOCATE (hierarchy(iml,jml), STAT=ALLOC_ERR)
4232    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for hierarchy','','')
4233
4234    !
4235    CALL flinopen(filename, .FALSE., iml, jml, lml, lon_rel, lat_rel, lev, tml, itau, date, dt, fid)
4236    !!
4237    !! From the basin description data we will read the following variables :
4238    !!
4239    !! Trip : Provides the flow direction following the convention :
4240    !! trip = 1 : flow = N
4241    !! trip = 2 : flow = NE
4242    !! trip = 3 : flow = E
4243    !! trip = 4 : flow = SE
4244    !! trip = 5 : flow = S
4245    !! trip = 6 : flow = SW
4246    !! trip = 7 : flow = W
4247    !! trip = 8 : flow = NW
4248    !! trip = 97 : return flow into the ground
4249    !! trip = 98 : coastal flow (diffuse flow into the oceans)
4250    !! trip = 99 : river flow into the oceans
4251    !!
4252    !! Basins : Provides a uniqe ID for each basin. These IDs are also used to get
4253    !! the name of the basin from the table in routine routing_names.
4254    !!
4255    !! Topoind :  is the topographic index for the retention time of the water in the
4256    !! grid box. It has been computed with the following formula : 1000 x sqrt(d^3/Dz)
4257    !! where d is the distance of the river from the current grid box to the next one
4258    !! as indicated by the variable trip.
4259    !! Dz the hight difference between between the two grid boxes.
4260    !! All these variables are in meters.
4261    !! Furthermore  we have to limit the height difference to 5m in order to avoid any unpleasant
4262    !! surprises. If dz < 5m then dz=5.
4263    !!
4264    !
4265    CALL flinget(fid, 'trip', iml, jml, lml, tml, 1, 1, trip)
4266    !
4267    CALL flinget(fid, 'basins', iml, jml, lml, tml, 1, 1, basins)
4268    !
4269    CALL flinget(fid, 'topoind', iml, jml, lml, tml, 1, 1, topoindex)
4270    !
4271    CALL flinclo(fid)
4272    !
4273    min_topoind = MINVAL(topoindex, MASK=topoindex .LT. undef_sechiba-un)
4274    !
4275    DO ip=1,iml
4276       DO jp=1,jml
4277          IF ( trip(ip,jp) < 1.e10 .AND. topoindex(ip,jp) > 1.e10) THEN
4278             WRITE(numout,*) 'trip exists but not topoind :'
4279             WRITE(numout,*) 'ip, jp :', ip, jp
4280             WRITE(numout,*) 'trip, topoind : ', trip(ip,jp), topoindex(ip,jp)
4281             CALL ipslerr_p(3,'routing_basins','trip exists but not topoind','','')
4282          ENDIF
4283       ENDDO
4284    ENDDO
4285
4286    ALLOCATE(resol_lu(iml,jml,2), STAT=ALLOC_ERR)
4287    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for resol_lu','','')
4288
4289    ALLOCATE(mask(iml,jml), STAT=ALLOC_ERR)
4290    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for mask','','')
4291    !
4292    ! Consider all points a priori
4293    !
4294    mask(:,:) = 0
4295    !
4296    DO ip=1,iml
4297       DO jp=1,jml
4298          !
4299          ! Determine the land mask of the basin map read from the file ROUTING_FILE
4300          !
4301          IF ( trip(ip,jp) < 1.e10 ) THEN
4302             mask(ip,jp) = 1
4303          ENDIF
4304          !
4305          ! Resolution in longitude
4306          !
4307          coslat = MAX( COS( lat_rel(ip,jp) * pi/180. ), mincos )     
4308          IF ( ip .EQ. 1 ) THEN
4309             resol_lu(ip,jp,1) = ABS( lon_rel(ip+1,jp) - lon_rel(ip,jp) ) * pi/180. * R_Earth * coslat
4310          ELSEIF ( ip .EQ. iml ) THEN
4311             resol_lu(ip,jp,1) = ABS( lon_rel(ip,jp) - lon_rel(ip-1,jp) ) * pi/180. * R_Earth * coslat
4312          ELSE
4313             resol_lu(ip,jp,1) = ABS( lon_rel(ip+1,jp) - lon_rel(ip-1,jp) )/2. * pi/180. * R_Earth * coslat
4314          ENDIF
4315          !
4316          ! Resolution in latitude
4317          !
4318          IF ( jp .EQ. 1 ) THEN
4319             resol_lu(ip,jp,2) = ABS( lat_rel(ip,jp) - lat_rel(ip,jp+1) ) * pi/180. * R_Earth
4320          ELSEIF ( jp .EQ. jml ) THEN
4321             resol_lu(ip,jp,2) = ABS( lat_rel(ip,jp-1) - lat_rel(ip,jp) ) * pi/180. * R_Earth
4322          ELSE
4323             resol_lu(ip,jp,2) =  ABS( lat_rel(ip,jp-1) - lat_rel(ip,jp+1) )/2. * pi/180. * R_Earth
4324          ENDIF
4325          !
4326       ENDDO
4327    ENDDO
4328    !
4329    ! The maximum number of points of the source map (basin description here) which can fit into
4330    ! any grid point of the ORCHIDEE grid is stimated here.
4331    ! Some margin is taken.
4332    !
4333    callsign = "routing_basins"
4334    ok_interpol = .FALSE.
4335   
4336    nix=INT(MAXVAL(resolution_g(:,1))/MAXVAL(resol_lu(:,:,1)))+2
4337    njx=INT(MAXVAL(resolution_g(:,2))/MAXVAL(resol_lu(:,:,2)))+2
4338    nbvmax = nix*njx*2
4339    !
4340    ! We are on the root processor here as this routine is not in parallel. So no need to broadcast.
4341    !
4342    IF (printlev >=1) THEN
4343       WRITE(numout,*) "Projection arrays for ",callsign," : "
4344       WRITE(numout,*) "Routing : nbvmax = ", nbvmax
4345    END IF
4346
4347    ALLOCATE (sub_area(nbpt,nbvmax), STAT=ALLOC_ERR)
4348    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for sub_area','','')
4349    sub_area(:,:)=zero
4350
4351    ALLOCATE (sub_index(nbpt,nbvmax,2), STAT=ALLOC_ERR)
4352    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for sub_index','','')
4353    sub_index(:,:,:)=0
4354
4355    ALLOCATE (sub_pts(nbpt), STAT=ALLOC_ERR)
4356    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for sub_pts','','')
4357    sub_pts(:)=0
4358    !
4359    ! routine aggregate will for each point of the ORCHIDEE grid determine which points
4360    ! of the source grid (basin definitions here) fit in there and which fraction of
4361    ! of the ORCHIDEE grid it represents.
4362    !
4363    CALL aggregate(nbpt, lalo, neighbours, resolution, contfrac, &
4364         &                iml, jml, lon_rel, lat_rel, mask, callsign, &
4365         &                nbvmax, sub_index, sub_area, ok_interpol)
4366    !
4367    WHERE (sub_area < 0) sub_area=zero
4368    !
4369    ! Some verifications
4370    !
4371    DO ib=1,nbpt
4372       sub_pts(ib) = COUNT(sub_area(ib,:) > zero)
4373       DO fopt=1,sub_pts(ib)
4374          IF (sub_area(ib, fopt) == 0 ) THEN
4375             WRITE(numout,*) "Zero Area - Sub_area > 0 : ", ib, fopt
4376             WRITE(numout,*) "Zero Area - lon : ",lalo(ib,2)
4377             WRITE(numout,*) "Zero Area - lon_rel : ", lon_rel(sub_index(ib, fopt, 1),sub_index(ib, fopt, 2))
4378             WRITE(numout,*) "Zero Area - lat : ",lalo(ib,1)
4379             WRITE(numout,*) "Zero Area - lat_rel : ", lat_rel(sub_index(ib, fopt, 1),sub_index(ib, fopt, 2))
4380          ENDIF
4381       ENDDO
4382    ENDDO
4383    !
4384    ! Do some memory management.
4385    !
4386    nwbas = MAX(MAXVAL(sub_pts), NbNeighb+1)
4387    !
4388    ALLOCATE (area_bx(nbvmax,nbvmax), stat=ALLOC_ERR)
4389    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for area_bx','','')
4390    ALLOCATE (hierarchy_bx(nbvmax,nbvmax), stat=ALLOC_ERR)
4391    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for hierarchy_bx','','')
4392    ALLOCATE (lon_bx(nbvmax,nbvmax), stat=ALLOC_ERR)
4393    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for lon_bx','','')
4394    ALLOCATE (lat_bx(nbvmax,nbvmax), stat=ALLOC_ERR)
4395    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for lat_bx','','')
4396    ALLOCATE (topoind_bx(nbvmax,nbvmax), stat=ALLOC_ERR)
4397    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for topoind_bx','','')
4398    ALLOCATE (trip_bx(nbvmax,nbvmax), stat=ALLOC_ERR)
4399    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for trip_bx','','')
4400    ALLOCATE (basin_bx(nbvmax,nbvmax), stat=ALLOC_ERR)
4401    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for basin_bx','','')
4402    ALLOCATE (coast_pts(nbvmax), stat=ALLOC_ERR)
4403    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for coast_pts','','')
4404    ALLOCATE (basin_inbxid(nbvmax), stat=ALLOC_ERR)
4405    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for basin_inbxid','','')
4406    ALLOCATE (basin_sz(nbvmax), stat=ALLOC_ERR)
4407    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for basin_sz','','')
4408    ALLOCATE (basin_pts(nbvmax,nbvmax,2), stat=ALLOC_ERR)
4409    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for basin_pts','','')
4410    ALLOCATE (basin_bxout(nbvmax), stat=ALLOC_ERR)
4411    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for basin_bxout','','')
4412    ALLOCATE (basin_count(nbpt), stat=ALLOC_ERR)
4413    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for basin_count','','')
4414    ALLOCATE (basin_area(nbpt,nwbas), basin_hierarchy(nbpt,nwbas), basin_topoind(nbpt,nwbas), stat=ALLOC_ERR)
4415    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for basin_area','','')
4416    ALLOCATE (fetch_basin(nbpt,nwbas), stat=ALLOC_ERR)
4417    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for fetch_basin','','')
4418    ALLOCATE (basin_id(nbpt,nwbas),  basin_flowdir(nbpt,nwbas), stat=ALLOC_ERR)
4419    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for basin_id','','')
4420    ALLOCATE (outflow_grid(nbpt,nwbas),outflow_basin(nbpt,nwbas), stat=ALLOC_ERR)
4421    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for outflow_grid','','')
4422    ALLOCATE (inflow_number(nbpt,nwbas), stat=ALLOC_ERR)
4423    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for inflow_number','','')
4424    ALLOCATE (inflow_basin(nbpt,nwbas,nbvmax), inflow_grid(nbpt,nwbas,nbvmax), stat=ALLOC_ERR)
4425    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for inflow_basin','','')
4426    ALLOCATE (nbcoastal(nbpt), coastal_basin(nbpt,nwbas), stat=ALLOC_ERR)
4427    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_basins','Pb in allocate for nbcoastal','','')
4428   
4429    !    Order all sub points in each grid_box and find the sub basins
4430    !
4431    !    before we start we set the maps to empty
4432    !
4433    basin_id(:,:) = undef_int
4434    basin_count(:) = 0
4435    hierarchy(:,:) = undef_sechiba
4436    max_basins = MAXVAL(basins, MASK=basins .LT. 1.e10)
4437    invented_basins = max_basins
4438    nbcoastal(:) = 0
4439    !
4440    !! Finds,in each grid box, the distance to the outflow point ... this defines the order in which
4441    !! the water will go through the sub-basins and grid boxes.
4442    !
4443    CALL routing_hierarchy(iml, jml, trip, topoindex, hierarchy)
4444    !
4445    !
4446    DO ib =1, nbpt
4447       !
4448       !
4449       !  extract the information for this grid box
4450       !
4451       !! Extracts from the global high resolution fields the data for the current grid box.
4452       !
4453       CALL routing_getgrid(nbpt, iml, jml, ib, sub_pts, sub_index, sub_area, max_basins, min_topoind, &
4454            & lon_rel, lat_rel, lalo, resolution, contfrac, trip, basins, topoindex, hierarchy, &
4455            & nbi, nbj, area_bx, trip_bx, basin_bx, topoind_bx, hierarchy_bx, lon_bx, lat_bx)
4456       !
4457       !! Finds the basins: returns the list of all points which are within the same basin of the grid box.
4458       !
4459       CALL routing_findbasins(nbi, nbj, trip_bx, basin_bx, hierarchy_bx, topoind_bx,&
4460            & nb_basin, basin_inbxid, basin_sz, basin_bxout, basin_pts, coast_pts)
4461       !
4462       !  Deal with the case where nb_basin=0 for this grid box. In this case all goes into coastal flow.
4463       !
4464       IF ( debug .AND. (COUNT(diagbox .EQ. ib) .GT. 0) ) THEN
4465          WRITE(numout,*) '===================== IB = :', ib
4466          WRITE(numout,*) "sub_pts(ib) :", sub_pts(ib), "sub_area(ib,:) :",sub_area(ib,1:2)
4467          WRITE(numout,*) 'LON LAT of GCM :', lalo(ib,2), lalo(ib,1)
4468          WRITE(numout,*) 'Neighbor options :',  neighbours(ib,1:NbNeighb)
4469          WRITE(numout,*) 'Resolution :', resolution(ib,1:2)
4470          WRITE(fmt,"('(',I3,'I6)')") nbi
4471          WRITE(numout,*) '-------------> trip ', trip_bx(1,1)
4472          DO jp=1,nbj
4473             WRITE(numout,fmt) trip_bx(1:nbi,jp)
4474          ENDDO
4475          WRITE(numout,*) '-------------> basin ',basin_bx(1,1)
4476          DO jp=1,nbj
4477             WRITE(numout,fmt) basin_bx(1:nbi,jp)
4478          ENDDO
4479          WRITE(numout,*) '-------------> hierarchy ',hierarchy_bx(1,1)
4480          DO jp=1,nbj
4481             WRITE(numout,fmt) INT(hierarchy_bx(1:nbi,jp)/1000.)
4482          ENDDO
4483          WRITE(numout,*) '-------------> topoindex ',topoind_bx(1,1)
4484          DO jp=1,nbj
4485             WRITE(numout,fmt) INT(topoind_bx(1:nbi,jp)/1000.)
4486          ENDDO
4487          !
4488          WRITE(numout,*) '------------> The basins we retain'
4489          DO jp=1,nb_basin
4490             WRITE(numout,*) 'index, size, bxout, coast :', basin_inbxid(jp), basin_sz(jp),&
4491                  & basin_bxout(jp), coast_pts(jp)
4492          ENDDO
4493          !
4494       ENDIF
4495       !
4496       !! Puts the basins found for the current grid box in the context of the global map.
4497       !
4498       CALL routing_globalize(nbpt, ib, neighbours, area_bx, trip_bx, hierarchy_bx, topoind_bx, min_topoind,&
4499            & nb_basin, basin_inbxid, basin_sz, basin_pts, basin_bxout, coast_pts, nwbas, basin_count,&
4500            & basin_area, basin_hierarchy, basin_topoind, basin_id, basin_flowdir, outflow_grid,&
4501            & nbcoastal, coastal_basin) 
4502       !
4503       !
4504       IF ( debug .AND. (COUNT(diagbox .EQ. ib) .GT. 0) ) THEN
4505          WRITE(numout,*) 'GLOBAL information after routing_globalize for grid ', ib
4506          DO jp=1,basin_count(ib)
4507             WRITE(numout,*) 'Basin ID : ', basin_id(ib, jp)
4508             WRITE(numout,*) 'Basin flowdir :', basin_flowdir(ib, jp)
4509             WRITE(numout,*) 'Basin hierarchy :', basin_hierarchy(ib, jp)
4510             WRITE(numout,*) 'Basin topoindex :', basin_topoind(ib, jp)
4511             WRITE(numout,*) 'Basin outflow grid :', outflow_grid(ib,jp)
4512          ENDDO
4513       ENDIF
4514       !
4515    ENDDO
4516    !
4517    !! Makes the connections between the bains and ensures global coherence.
4518    !
4519    CALL routing_linkup(nbpt, contfrac, neighbours, nwbas, basin_count, basin_area, basin_id, basin_flowdir, &
4520         & basin_hierarchy, outflow_grid, outflow_basin, inflow_number, inflow_grid, inflow_basin, &
4521         & nbcoastal, coastal_basin, invented_basins)
4522    !
4523    !
4524    IF (printlev>=1) WRITE(numout,*) 'The maximum number of basins in any grid :', MAXVAL(basin_count)
4525    !
4526    IF ( debug ) THEN
4527       DO ib=1,SIZE(diagbox)
4528          IF ( diagbox(ib) .GT. 0 ) THEN
4529             WRITE(numout,*) 'After routing_linkup information for grid ', diagbox(ib)
4530             DO jp=1,basin_count(diagbox(ib))
4531                WRITE(numout,*) 'Basin ID : ', basin_id(diagbox(ib), jp)
4532                WRITE(numout,*) 'Basin outflow_grid :', outflow_grid(diagbox(ib), jp)
4533                WRITE(numout,*) 'Basin outflow_basin:', outflow_basin(diagbox(ib), jp)
4534                WRITE(numout,*) 'Basin hierarchy :', basin_hierarchy(diagbox(ib), jp)
4535             ENDDO
4536          ENDIF
4537       ENDDO
4538    ENDIF
4539    !
4540    !! Computes the fetch of each basin, upstream area in known.
4541    !
4542    CALL routing_fetch(nbpt, resolution, contfrac, nwbas, basin_count, basin_area, basin_id, outflow_grid, &
4543         & outflow_basin, fetch_basin)
4544    !
4545    !
4546    IF (printlev >=3) WRITE(numout,*) "Start reducing the number of basins per grid to meet the required truncation."
4547    !
4548    !! Reduces the number of basins per grid to the value chosen by the user.
4549    !
4550    CALL routing_truncate(nbpt, resolution, contfrac, nwbas, basin_count, basin_area, basin_topoind,&
4551         & fetch_basin, basin_id, basin_flowdir, outflow_grid, outflow_basin, inflow_number,&
4552         & inflow_grid, inflow_basin)
4553    !
4554    DEALLOCATE (lat_rel)
4555    DEALLOCATE (lon_rel)
4556    !
4557    DEALLOCATE (trip)
4558    DEALLOCATE (basins)
4559    DEALLOCATE (topoindex)
4560    DEALLOCATE (hierarchy)
4561    !
4562    DEALLOCATE (sub_area)
4563    DEALLOCATE (sub_index)
4564    DEALLOCATE (sub_pts)
4565    !
4566    DEALLOCATE (mask)
4567    DEALLOCATE (resol_lu)
4568    !
4569    DEALLOCATE (basin_count)
4570    DEALLOCATE (basin_area, basin_hierarchy, basin_topoind, fetch_basin)
4571    DEALLOCATE (basin_id,  basin_flowdir)
4572    DEALLOCATE (outflow_grid,outflow_basin)
4573    DEALLOCATE (inflow_number)
4574    DEALLOCATE (inflow_basin, inflow_grid)
4575    DEALLOCATE (nbcoastal, coastal_basin)
4576
4577  END SUBROUTINE routing_basins
4578
4579
4580!! ================================================================================================================================
4581!! SUBROUTINE   : routing_getgrid
4582!!
4583!>\BRIEF         This subroutine extracts from the global high resolution fields
4584!!               the data for the current grid box we are dealing with.
4585!!
4586!! DESCRIPTION (definitions, functional, design, flags) :
4587!! Convention for trip on the input :
4588!! The trip field follows the following convention for the flow of the water :
4589!! trip = 1 : flow = N
4590!! trip = 2 : flow = NE
4591!! trip = 3 : flow = E
4592!! trip = 4 : flow = SE
4593!! trip = 5 : flow = S
4594!! trip = 6 : flow = SW
4595!! trip = 7 : flow = W
4596!! trip = 8 : flow = NW
4597!! trip = 97 : return flow into the ground
4598!! trip = 98 : coastal flow (diffuse flow into the oceans) These values are created here
4599!! trip = 99 : river flow into the oceans
4600!!
4601!! On output, the grid boxes of the basin map which flow out of the GCM grid are identified
4602!! by numbers larger than 100 :
4603!! trip = 101 : flow = N out of the coarse grid
4604!! trip = 102 : flow = NE out of the coarse grid
4605!! trip = 103 : flow = E out of the coarse grid
4606!! trip = 104 : flow = SE out of the coarse grid
4607!! trip = 105 : flow = S out of the coarse grid
4608!! trip = 106 : flow = SW out of the coarse grid
4609!! trip = 107 : flow = W out of the coarse grid
4610!! trip = 108 : flow = NW out of the coarse grid
4611!! Inside the grid the convention remains the same as above (ie between 1 and 99).:\n
4612!!
4613!! RECENT CHANGE(S): None
4614!!
4615!! MAIN OUTPUT VARIABLE(S):
4616!!
4617!! REFERENCES   : None
4618!!
4619!! FLOWCHART    : None
4620!! \n
4621!_ ================================================================================================================================
4622
4623  SUBROUTINE routing_getgrid(nbpt, iml, jml, ib, sub_pts, sub_index, sub_area, max_basins, min_topoind, &
4624       & lon_rel, lat_rel, lalo, resolution, contfrac, trip, basins, topoindex, hierarchy, &
4625       & nbi, nbj, area_bx, trip_bx, basin_bx, topoind_bx, hierarchy_bx, lon_bx, lat_bx)
4626    !
4627    IMPLICIT NONE
4628    !
4629!!  INPUT VARIABLES
4630    INTEGER(i_std), INTENT(in)  :: nbpt                        !! Domain size (unitless)
4631    INTEGER(i_std), INTENT(in)  :: iml                         !! X resolution of the high resolution grid
4632    INTEGER(i_std), INTENT(in)  :: jml                         !! Y resolution of the high resolution grid
4633    INTEGER(i_std), INTENT(in)  :: ib                          !! Current basin (unitless)
4634    INTEGER(i_std), INTENT(in)  :: sub_pts(nbpt)               !! Number of high resolution points on this grid (unitless)
4635    INTEGER(i_std), INTENT(in)  :: sub_index(nbpt,nbvmax,2)    !! Indices of the points we need on the fine grid (unitless)
4636    REAL(r_std), INTENT(inout)  :: max_basins                  !! The current maximum of basins
4637    REAL(r_std), INTENT(in)     :: min_topoind                 !! The current minimum of topographic index (m)
4638    REAL(r_std), INTENT(in)     :: sub_area(nbpt,nbvmax)       !! Area on the fine grid (m^2)
4639    REAL(r_std), INTENT(in)     :: lon_rel(iml,jml)            !!
4640    REAL(r_std), INTENT(in)     :: lat_rel(iml,jml)            !! coordinates of the fine grid
4641    REAL(r_std), INTENT(in)     :: lalo(nbpt,2)                !! Vector of latitude and longitudes (beware of the order !)
4642    REAL(r_std), INTENT(in)     :: resolution(nbpt,2)          !! The size of each grid box in X and Y (m)
4643    REAL(r_std), INTENT(in)     :: contfrac(nbpt)              !! Fraction of land in each grid box (unitless;0-1)
4644    REAL(r_std), INTENT(inout)  :: trip(iml,jml)               !! The trip field (unitless)
4645    REAL(r_std), INTENT(inout)  :: basins(iml,jml)             !! data on the fine grid
4646    REAL(r_std), INTENT(inout)  :: topoindex(iml,jml)          !! Topographic index of the residence time (m)
4647    REAL(r_std), INTENT(inout)  :: hierarchy(iml, jml)         !! data on the fine grid
4648    !
4649!!  OUTPUT VARIABLES
4650    INTEGER(i_std), INTENT(out) :: nbi, nbj                    !! Number of point in x and y within the grid (unitless)
4651    REAL(r_std), INTENT(out)    :: area_bx(nbvmax,nbvmax)      !! Area of each small box in the grid box (m^2)
4652    REAL(r_std), INTENT(out)    :: hierarchy_bx(nbvmax,nbvmax) !! Level in the basin of the point
4653    REAL(r_std), INTENT(out)    :: lon_bx(nbvmax,nbvmax)       !!
4654    REAL(r_std), INTENT(out)    :: lat_bx(nbvmax,nbvmax)       !!
4655    REAL(r_std), INTENT(out)    :: topoind_bx(nbvmax,nbvmax)   !! Topographic index of the residence time for each of the smaller boxes (m)
4656    INTEGER(i_std), INTENT(out) :: trip_bx(nbvmax,nbvmax)      !! The trip field for each of the smaller boxes (unitless)
4657    INTEGER(i_std), INTENT(out) :: basin_bx(nbvmax,nbvmax)     !!
4658    !
4659!! LOCAL VARIABLES
4660    INTEGER(i_std)              :: ip, jp, ll(1), iloc, jloc   !! Indices (unitless)
4661    REAL(r_std)                 :: lonstr(nbvmax*nbvmax)       !!
4662    REAL(r_std)                 :: latstr(nbvmax*nbvmax)       !!
4663
4664!_ ================================================================================================================================
4665
4666    !
4667    ! Set everything to undef to locate easily empty points
4668    !
4669    trip_bx(:,:) = undef_int
4670    basin_bx(:,:) = undef_int
4671    topoind_bx(:,:) = undef_sechiba
4672    area_bx(:,:) = undef_sechiba
4673    hierarchy_bx(:,:) = undef_sechiba
4674    !
4675    IF ( sub_pts(ib) > 0 ) THEN
4676       !
4677       DO ip=1,sub_pts(ib)
4678          lonstr(ip) = lon_rel(sub_index(ib, ip, 1), sub_index(ib, ip, 2))
4679          latstr(ip) = lat_rel(sub_index(ib, ip, 1), sub_index(ib, ip, 2))
4680       ENDDO
4681       !
4682       !  Get the size of the area and order the coordinates to go from North to South and West to East
4683       !
4684       CALL routing_sortcoord(sub_pts(ib), lonstr, 'WE', nbi)
4685       CALL routing_sortcoord(sub_pts(ib), latstr, 'NS', nbj)
4686       !
4687       ! Transfer the data in such a way that (1,1) is the North Western corner and
4688       ! (nbi, nbj) the South Eastern.
4689       !
4690       DO ip=1,sub_pts(ib)
4691          ll = MINLOC(ABS(lonstr(1:nbi) - lon_rel(sub_index(ib, ip, 1), sub_index(ib, ip, 2))))
4692          iloc = ll(1)
4693          ll = MINLOC(ABS(latstr(1:nbj) - lat_rel(sub_index(ib, ip, 1), sub_index(ib, ip, 2))))
4694          jloc = ll(1)
4695          trip_bx(iloc, jloc) = NINT(trip(sub_index(ib, ip, 1), sub_index(ib, ip, 2)))
4696          basin_bx(iloc, jloc) = NINT(basins(sub_index(ib, ip, 1), sub_index(ib, ip, 2)))
4697          area_bx(iloc, jloc) = sub_area(ib, ip)
4698          topoind_bx(iloc, jloc) = topoindex(sub_index(ib, ip, 1), sub_index(ib, ip, 2))
4699          hierarchy_bx(iloc, jloc) = hierarchy(sub_index(ib, ip, 1), sub_index(ib, ip, 2))
4700          lon_bx(iloc, jloc) = lon_rel(sub_index(ib, ip, 1), sub_index(ib, ip, 2))
4701          lat_bx(iloc, jloc) = lat_rel(sub_index(ib, ip, 1), sub_index(ib, ip, 2))
4702       ENDDO
4703    ELSE
4704       !
4705       ! This is the case where the model invented a continental point
4706       !
4707       nbi = 1
4708       nbj = 1
4709       iloc = 1
4710       jloc = 1
4711       trip_bx(iloc, jloc) = 98
4712       basin_bx(iloc, jloc) = NINT(max_basins + 1)
4713       max_basins = max_basins + 1
4714       ! Check if we are at the poles : resolution(ib,1) = 0
4715       IF ( resolution(ib,1) == 0 ) THEN
4716          ! compute the pole cell area as the circle surface
4717          area_bx(iloc, jloc) = pi*resolution(ib,2)*resolution(ib,2)*contfrac(ib)
4718       ELSE
4719          area_bx(iloc, jloc) = resolution(ib,1)*resolution(ib,2)*contfrac(ib)
4720       ENDIF
4721       topoind_bx(iloc, jloc) = min_topoind
4722       hierarchy_bx(iloc, jloc) =  min_topoind
4723       lon_bx(iloc, jloc) = lalo(ib,2)
4724       lat_bx(iloc, jloc) = lalo(ib,1)
4725       !
4726    ENDIF
4727    !
4728    ! Tag in trip all the outflow conditions. The table is thus :
4729    ! trip = 100+n : Outflow into another grid box
4730    ! trip = 99    : River outflow into the ocean
4731    ! trip = 98    : This will be coastal flow (not organized as a basin)
4732    ! trip = 97    : return flow into the soil (local)
4733    !
4734    DO jp=1,nbj
4735       IF ( trip_bx(1,jp) .EQ. 8 .OR. trip_bx(1,jp) .EQ. 7 .OR. trip_bx(1,jp) .EQ. 6) THEN
4736          trip_bx(1,jp) = trip_bx(1,jp) + 100
4737       ENDIF
4738       IF ( trip_bx(nbi,jp) .EQ. 2 .OR. trip_bx(nbi,jp) .EQ. 3 .OR. trip_bx(nbi,jp) .EQ. 4) THEN
4739          trip_bx(nbi,jp) = trip_bx(nbi,jp) + 100
4740       ENDIF
4741    ENDDO
4742    DO ip=1,nbi
4743       IF ( trip_bx(ip,1) .EQ. 8 .OR. trip_bx(ip,1) .EQ. 1 .OR. trip_bx(ip,1) .EQ. 2) THEN
4744          trip_bx(ip,1) = trip_bx(ip,1) + 100
4745       ENDIF
4746       IF ( trip_bx(ip,nbj) .EQ. 6 .OR. trip_bx(ip,nbj) .EQ. 5 .OR. trip_bx(ip,nbj) .EQ. 4) THEN
4747          trip_bx(ip,nbj) = trip_bx(ip,nbj) + 100
4748       ENDIF
4749    ENDDO
4750    !
4751    !
4752    !  We simplify the outflow. We only need the direction normal to the
4753    !     box boundary and the 4 corners.
4754    !
4755    ! Northern border
4756    IF ( trip_bx(1,1) .EQ. 102 ) trip_bx(1,1) = 101
4757    IF ( trip_bx(nbi,1) .EQ. 108 ) trip_bx(nbi,1) = 101
4758    DO ip=2,nbi-1
4759       IF ( trip_bx(ip,1) .EQ. 108 .OR. trip_bx(ip,1) .EQ. 102 ) trip_bx(ip,1) = 101
4760    ENDDO
4761    ! Southern border
4762    IF ( trip_bx(1,nbj) .EQ. 104 ) trip_bx(1,nbj) = 105
4763    IF ( trip_bx(nbi,nbj) .EQ. 106 ) trip_bx(nbi,nbj) = 105
4764    DO ip=2,nbi-1
4765       IF ( trip_bx(ip,nbj) .EQ. 104 .OR. trip_bx(ip,nbj) .EQ. 106 ) trip_bx(ip,nbj) = 105
4766    ENDDO
4767    ! Eastern border
4768    IF ( trip_bx(nbi,1) .EQ. 104) trip_bx(nbi,1) = 103
4769    IF ( trip_bx(nbi,nbj) .EQ. 102) trip_bx(nbi,nbj) = 103
4770    DO jp=2,nbj-1
4771       IF ( trip_bx(nbi,jp) .EQ. 104 .OR. trip_bx(nbi,jp) .EQ. 102 ) trip_bx(nbi,jp) = 103
4772    ENDDO
4773    ! Western border
4774    IF ( trip_bx(1,1) .EQ. 106) trip_bx(1,1) = 107
4775    IF ( trip_bx(1,nbj) .EQ. 108) trip_bx(1,nbj) = 107
4776    DO jp=2,nbj-1
4777       IF ( trip_bx(1,jp) .EQ. 106 .OR. trip_bx(1,jp) .EQ. 108 ) trip_bx(1,jp) = 107
4778    ENDDO       
4779    !
4780    !
4781  END SUBROUTINE routing_getgrid
4782!
4783!! ================================================================================================================================
4784!! SUBROUTINE   : routing_sortcoord
4785!!
4786!>\BRIEF         This subroutines orders the coordinates to go from North to South and West to East.
4787!!
4788!! DESCRIPTION (definitions, functional, design, flags) : None
4789!!
4790!! RECENT CHANGE(S): None
4791!!
4792!! MAIN OUTPUT VARIABLE(S):
4793!!
4794!! REFERENCES   : None
4795!!
4796!! FLOWCHART    : None
4797!! \n
4798!_ ================================================================================================================================
4799
4800  SUBROUTINE routing_sortcoord(nb_in, coords, direction, nb_out)
4801    !
4802    IMPLICIT NONE
4803    !
4804!! INPUT VARIABLES
4805    INTEGER(i_std), INTENT(in)   :: nb_in             !!
4806    REAL(r_std), INTENT(inout)   :: coords(nb_in)     !!
4807    !
4808!! OUTPUT VARIABLES
4809    INTEGER(i_std), INTENT(out)  :: nb_out            !!
4810    !
4811!! LOCAL VARIABLES
4812    CHARACTER(LEN=2)             :: direction         !!
4813    INTEGER(i_std)               :: ipos              !!
4814    REAL(r_std)                  :: coords_tmp(nb_in) !!
4815    INTEGER(i_std), DIMENSION(1) :: ll                !!
4816    INTEGER(i_std)               :: ind(nb_in)        !!
4817
4818!_ ================================================================================================================================
4819    !
4820    ipos = 1
4821    nb_out = nb_in
4822    !
4823    ! Compress the coordinates array
4824    !
4825    DO WHILE ( ipos < nb_in )
4826       IF ( coords(ipos+1) /= undef_sechiba) THEN
4827         IF ( COUNT(coords(ipos:nb_out) == coords(ipos)) > 1 ) THEN
4828            coords(ipos:nb_out-1) = coords(ipos+1:nb_out) 
4829            coords(nb_out:nb_in) = undef_sechiba
4830            nb_out = nb_out - 1
4831         ELSE
4832            ipos = ipos + 1
4833         ENDIF
4834      ELSE
4835         EXIT
4836      ENDIF
4837    ENDDO
4838    !
4839    ! Sort it now
4840    !
4841    ! First we get ready and adjust for the periodicity in longitude
4842    !
4843    coords_tmp(:) = undef_sechiba
4844    IF ( INDEX(direction, 'WE') == 1 .OR.  INDEX(direction, 'EW') == 1) THEN
4845       IF ( MAXVAL(ABS(coords(1:nb_out))) .GT. 160 ) THEN
4846          coords_tmp(1:nb_out) = MOD(coords(1:nb_out) + 360.0, 360.0)
4847       ELSE
4848          coords_tmp(1:nb_out) = coords(1:nb_out)
4849       ENDIF
4850    ELSE IF ( INDEX(direction, 'NS') == 1 .OR.  INDEX(direction, 'SN') == 1) THEN
4851       coords_tmp(1:nb_out) = coords(1:nb_out)
4852    ELSE
4853       WRITE(numout,*) 'The chosen direction (', direction,') is not recognized'
4854       CALL ipslerr_p(3,'routing_sortcoord','The chosen direction is not recognized','First section','')
4855    ENDIF
4856    !
4857    ! Get it sorted out now
4858    !
4859    ipos = 1
4860    !
4861    IF ( INDEX(direction, 'WE') == 1 .OR. INDEX(direction, 'SN') == 1) THEN
4862       DO WHILE (COUNT(ABS(coords_tmp(:)-undef_sechiba) > EPSILON(undef_sechiba)*10.) >= 1)
4863          ll = MINLOC(coords_tmp(:), coords_tmp /= undef_sechiba)
4864          ind(ipos) = ll(1) 
4865          coords_tmp(ll(1)) = undef_sechiba
4866          ipos = ipos + 1
4867       ENDDO
4868    ELSE IF ( INDEX(direction, 'EW') == 1 .OR. INDEX(direction, 'NS') == 1) THEN
4869       DO WHILE (COUNT(ABS(coords_tmp(:)-undef_sechiba) > EPSILON(undef_sechiba)*10.) >= 1)
4870          ll = MAXLOC(coords_tmp(:), coords_tmp /= undef_sechiba)
4871          ind(ipos) = ll(1) 
4872          coords_tmp(ll(1)) = undef_sechiba
4873          ipos = ipos + 1
4874       ENDDO
4875    ELSE
4876       WRITE(numout,*) 'The chosen direction (', direction,') is not recognized (second)'
4877       CALL ipslerr_p(3,'routing_sortcoord','The chosen direction is not recognized','Second section','')
4878    ENDIF
4879    !
4880    coords(1:nb_out) = coords(ind(1:nb_out))
4881    IF (nb_out < nb_in) THEN
4882       coords(nb_out+1:nb_in) = zero
4883    ENDIF
4884    !
4885  END SUBROUTINE routing_sortcoord
4886  !
4887
4888!! ================================================================================================================================
4889!! SUBROUTINE   : routing_findbasins
4890!!
4891!>\BRIEF         This subroutine finds the basins and does some clean up.
4892!!               The aim is to return the list off all points which are within the
4893!!               same basin of the grid box.
4894!!
4895!! DESCRIPTION (definitions, functional, design, flags) :
4896!!  We will also collect all points which directly flow into the ocean in one basin
4897!!  Make sure that we do not have a basin with two outflows and other exceptions.
4898!!  At this stage no effort is made to come down to the truncation of the model.
4899!!
4900!! Convention for trip    \n
4901!! -------------------    \n
4902!! Inside of the box :    \n
4903!! trip = 1 : flow = N    \n
4904!! trip = 2 : flow = NE    \n
4905!! trip = 3 : flow = E    \n
4906!! trip = 4 : flow = SE    \n
4907!! trip = 5 : flow = S    \n
4908!! trip = 6 : flow = SW    \n
4909!! trip = 7 : flow = W    \n
4910!! trip = 8 : flow = NW    \n
4911!! trip = 97 : return flow into the ground    \n
4912!! trip = 98 : coastal flow (diffuse flow into the oceans) These values are created here    \n
4913!! trip = 99 : river flow into the oceans    \n
4914!!
4915!! Out flow from the grid :    \n
4916!! trip = 101 : flow = N out of the coarse grid    \n
4917!! trip = 102 : flow = NE out of the coarse grid    \n
4918!! trip = 103 : flow = E out of the coarse grid    \n
4919!! trip = 104 : flow = SE out of the coarse grid    \n
4920!! trip = 105 : flow = S out of the coarse grid    \n
4921!! trip = 106 : flow = SW out of the coarse grid    \n
4922!! trip = 107 : flow = W out of the coarse grid    \n
4923!! trip = 108 : flow = NW out of the coarse grid!    \n
4924!! RECENT CHANGE(S): None
4925!!
4926!! MAIN OUTPUT VARIABLE(S):
4927!!
4928!! REFERENCES   : None
4929!!
4930!! FLOWCHART    : None
4931!! \n
4932!_ ================================================================================================================================
4933
4934  SUBROUTINE routing_findbasins(nbi, nbj, trip, basin, hierarchy, topoind, nb_basin, basin_inbxid, basin_sz,&
4935       & basin_bxout, basin_pts, coast_pts)
4936    !
4937    IMPLICIT NONE
4938    !
4939!! INPUT VARIABLES
4940    INTEGER(i_std), INTENT(in)    :: nbi                          !! Number of point in x within the grid (unitless)
4941    INTEGER(i_std), INTENT(in)    :: nbj                          !! Number of point in y within the grid (unitless)
4942    REAL(r_std), INTENT(in)       :: hierarchy(:,:)               !!
4943    REAL(r_std), INTENT(in)       :: topoind(:,:)                 !! Topographic index of the residence time (m)
4944    !
4945    !  Modified
4946    INTEGER(i_std), INTENT(inout) :: trip(:,:)                    !! The trip field (unitless)
4947    INTEGER(i_std), INTENT(inout) :: basin(:,:)                   !!
4948    !
4949!! OUTPUT VARIABLES
4950    INTEGER(i_std), INTENT(out)   :: nb_basin                     !! Number of sub-basins (unitless)
4951    INTEGER(i_std), INTENT(out)   :: basin_inbxid(nbvmax)         !!
4952    INTEGER(i_std), INTENT(out)   :: basin_sz(nbvmax)             !!
4953    INTEGER(i_std), INTENT(out)   :: basin_bxout(nbvmax)          !!
4954    INTEGER(i_std), INTENT(out)   :: basin_pts(nbvmax, nbvmax, 2) !!
4955    INTEGER(i_std), INTENT(out)   :: coast_pts(nbvmax)            !! The coastal flow points (unitless)
4956    !
4957!! LOCAL VARIABLES
4958    INTEGER(i_std)                :: ibas, ilf, nbb, nb_in        !!
4959    INTEGER(i_std)                :: bname(nbvmax)                !!
4960    INTEGER(i_std)                :: sz(nbvmax)                   !!
4961    INTEGER(i_std)                :: pts(nbvmax,nbvmax,2)         !!
4962    INTEGER(i_std)                :: nbout(nbvmax)                !!
4963    INTEGER(i_std)                :: new_nb                       !!
4964    INTEGER(i_std)                :: new_bname(nbvmax)            !!
4965    INTEGER(i_std)                :: new_sz(nbvmax)               !!
4966    INTEGER(i_std)                :: new_pts(nbvmax,nbvmax,2)     !!
4967    INTEGER(i_std)                :: itrans                       !!
4968    INTEGER(i_std)                :: trans(nbvmax)                !!
4969    INTEGER(i_std)                :: outdir(nbvmax)               !!
4970    INTEGER(i_std)                :: tmpsz(nbvmax)                !!
4971    INTEGER(i_std)                :: ip, jp, jpp(1), ipb          !!
4972    INTEGER(i_std)                :: sortind(nbvmax)              !!
4973    CHARACTER(LEN=7)              :: fmt                          !!
4974
4975!_ ================================================================================================================================
4976    !
4977    nbb = 0
4978    ibas = -1
4979    bname(:) = undef_int
4980    sz(:) = 0
4981    nbout(:) = 0
4982    new_pts(:,:,:) = 0
4983    !
4984    ! 1.0 Find all basins within this grid box
4985    !     Sort the variables per basin so that we can more easily
4986    !     access data from the same basin (The variables are :
4987    !     bname, sz, pts, nbout)
4988    !
4989    DO ip=1,nbi
4990       DO jp=1,nbj
4991          IF ( basin(ip,jp) .LT. undef_int) THEN
4992             IF ( COUNT(basin(ip,jp) .EQ. bname(:)) .EQ. 0 ) THEN
4993                nbb = nbb + 1
4994                IF ( nbb .GT. nbvmax ) CALL ipslerr_p(3,'routing_findbasins','nbvmax too small','first section','')
4995                bname(nbb) = basin(ip,jp)
4996                sz(nbb) = 0
4997             ENDIF
4998             !
4999             DO ilf=1,nbb
5000                IF ( basin(ip,jp) .EQ. bname(ilf) ) THEN
5001                   ibas = ilf
5002                ENDIF
5003             ENDDO
5004             !
5005             sz(ibas) = sz(ibas) + 1
5006             IF ( sz(ibas) .GT. nbvmax ) CALL ipslerr_p(3,'routing_findbasins','nbvmax too small','second section','')
5007             pts(ibas, sz(ibas), 1) = ip
5008             pts(ibas, sz(ibas), 2) = jp
5009             ! We deal only with outflow and leave flow back into the grid box for later.
5010             IF ( trip(ip,jp) .GE. 97 ) THEN
5011                nbout(ibas) = nbout(ibas) + 1
5012             ENDIF
5013             !
5014          ENDIF
5015          !
5016       ENDDO
5017    ENDDO
5018    !
5019    ! 2.0 All basins which have size 1 and flow to the ocean are put together.
5020    !
5021    itrans = 0
5022    coast_pts(:) = undef_int
5023    ! Get all the points we can collect
5024    DO ip=1,nbb
5025       IF ( sz(ip) .EQ. 1 .AND. trip(pts(ip,1,1),pts(ip,1,2)) .EQ. 99) THEN
5026          itrans = itrans + 1
5027          trans(itrans) = ip
5028          trip(pts(ip,1,1),pts(ip,1,2)) = 98
5029       ENDIF
5030    ENDDO
5031    ! put everything in the first basin
5032    IF ( itrans .GT. 1) THEN
5033       ipb = trans(1)
5034       coast_pts(sz(ipb)) = bname(ipb)
5035       bname(ipb) = -1
5036       DO ip=2,itrans
5037          sz(ipb) = sz(ipb) + 1
5038          coast_pts(sz(ipb)) = bname(trans(ip))
5039          sz(trans(ip)) = 0
5040          pts(ipb, sz(ipb), 1) = pts(trans(ip), 1, 1) 
5041          pts(ipb, sz(ipb), 2) = pts(trans(ip), 1, 2) 
5042       ENDDO
5043    ENDIF
5044    !
5045    ! 3.0 Make sure that we have only one outflow point in each basin
5046    !
5047    ! nbb is the number of basins on this grid box.
5048    new_nb = 0
5049    DO ip=1,nbb
5050       ! We only do this for grid-points which have more than one outflow
5051       IF ( sz(ip) .GT. 1 .AND. nbout(ip) .GT. 1) THEN
5052          !
5053          ! Pick up all points needed and store them in trans
5054          !
5055          itrans = 0
5056          DO jp=1,sz(ip)
5057             IF ( trip(pts(ip,jp,1),pts(ip,jp,2)) .GE. 97) THEN
5058                itrans = itrans + 1
5059                trans(itrans) = trip(pts(ip,jp,1),pts(ip,jp,2))
5060             ENDIF
5061          ENDDO
5062          !
5063          ! First issue : We have more than one point of the basin which flows into
5064          ! the ocean. In this case we put everything into coastal flow. It will go into
5065          ! a separate basin in the routing_globalize routine.
5066          !
5067          IF ( (COUNT(trans(1:itrans) .EQ. 99) + COUNT(trans(1:itrans) .EQ. 98)) .GT. 1) THEN
5068             DO jp=1,sz(ip)
5069                IF ( trip(pts(ip,jp,1),pts(ip,jp,2)) .EQ. 99 ) THEN
5070                   trip(pts(ip,jp,1),pts(ip,jp,2)) = 98
5071                   trans(itrans) = trip(pts(ip,jp,1),pts(ip,jp,2))
5072                ENDIF
5073             ENDDO
5074          ENDIF
5075          !
5076          ! Second issue : We have redundant outflows at the boundaries. That is two small grid
5077          ! boxes flowing into the same GCM grid box.
5078          !
5079          IF ( COUNT(trans(1:itrans) .GT. 100) .GE. 1) THEN
5080             CALL routing_simplify(nbi, nbj, trip, basin, hierarchy, bname(ip))
5081             itrans = 0
5082             DO jp=1,sz(ip)
5083                IF ( trip(pts(ip,jp,1),pts(ip,jp,2)) .GE. 9) THEN
5084                   itrans = itrans + 1
5085                   trans(itrans) = trip(pts(ip,jp,1),pts(ip,jp,2))
5086                ENDIF
5087             ENDDO
5088          ENDIF
5089          !
5090          ! Third issue : we have more than one outflow from the boxes. This could be
5091          !             - flow into 2 or more neighboring GCM grids
5092          !             - flow into a neighboring GCM grids and into the ocean or be a return flow (=97. =98, =99)
5093          !             - flow into a neighboring GCM grids or ocean and back into the same GCM grid box
5094          ! The only solution is to cut the basin up in as many parts.
5095          !
5096          IF ( COUNT(trans(1:itrans) .GE. 97) .GT. 1) THEN
5097             !
5098             nb_in =  new_nb
5099             CALL routing_cutbasin(nbi, nbj, nbb, trip, basin, bname(ip), new_nb, new_bname, new_sz, new_pts)
5100             !
5101             ! If we have split the basin then we need to cancel the old one
5102             !
5103             IF ( nb_in .NE. new_nb) THEN
5104                sz(ip) = 0
5105             ENDIF
5106             !
5107          ENDIF
5108          !
5109       ENDIF
5110    ENDDO
5111    !
5112    !  Add the new basins to the end of the list
5113    !
5114    If ( nbb+new_nb .LE. nbvmax) THEN
5115       DO ip=1,new_nb
5116          bname(nbb+ip) = new_bname(ip)
5117          sz(nbb+ip) = new_sz(ip)
5118          pts(nbb+ip,:,:) = new_pts(ip,:,:)
5119       ENDDO
5120       nbb = nbb+new_nb
5121    ELSE
5122       WRITE(numout,*) 'Increase nbvmax. It is too small to contain all the basins (routing_findbasins)'
5123       CALL ipslerr_p(3,'routing_findbasins','Increase nbvmax.','It is too small to contain all the basins','')
5124    ENDIF
5125    !
5126    ! Keep the output direction
5127    !
5128    DO ip=1,nbb
5129       IF ( sz(ip) .GT. 0 ) THEN
5130          trans(:) = 0
5131          DO jp=1,sz(ip)
5132             trans(jp) = trip(pts(ip,jp,1),pts(ip,jp,2))
5133          ENDDO
5134          outdir(ip) = MAXVAL(trans(1:sz(ip)))
5135          IF ( outdir(ip) .GE. 97 ) THEN
5136             outdir(ip) = outdir(ip) - 100
5137          ELSE
5138             WRITE(numout,*) 'Why are we here and can not find a trip larger than 96'
5139             WRITE(numout,*) 'Does this mean that the basin does not have any outflow ', ip, bname(ip)
5140             WRITE(fmt,"('(',I3,'I9)')") nbi
5141             WRITE(numout,*) '-----------------------> trip'
5142             DO jp=1,nbj
5143                WRITE(numout,fmt) trip(1:nbi,jp)
5144             ENDDO
5145             WRITE(numout,*) '-----------------------> basin'
5146             DO jp=1,nbj
5147                WRITE(numout,fmt) basin(1:nbi,jp)
5148             ENDDO
5149             CALL ipslerr_p(3,'routing_findbasins','Probleme finding trip','','')
5150          ENDIF
5151       ENDIF
5152    ENDDO
5153    !
5154    !
5155    ! Sort the output by size of the various basins.
5156    !
5157    nb_basin = COUNT(sz(1:nbb) .GT. 0)
5158    tmpsz(:) = -1
5159    tmpsz(1:nbb) = sz(1:nbb)
5160    DO ip=1,nbb
5161       jpp = MAXLOC(tmpsz(:))
5162       IF ( sz(jpp(1)) .GT. 0) THEN
5163          sortind(ip) = jpp(1)
5164          tmpsz(jpp(1)) = -1
5165       ENDIF
5166    ENDDO
5167    basin_inbxid(1:nb_basin) = bname(sortind(1:nb_basin))
5168    basin_sz(1:nb_basin) = sz(sortind(1:nb_basin))
5169    basin_pts(1:nb_basin,:,:) = pts(sortind(1:nb_basin),:,:)
5170    basin_bxout(1:nb_basin) = outdir(sortind(1:nb_basin))
5171    !
5172    ! We can only check if we have at least as many outflows as basins
5173    !
5174    ip = COUNT(trip(1:nbi,1:nbj) .GE. 97 .AND. trip(1:nbi,1:nbj) .LT. undef_int)
5175!!    ip = ip + COUNT(trip(1:nbi,1:nbj) .EQ. 97)
5176!!    IF ( COUNT(trip(1:nbi,1:nbj) .EQ. 98) .GT. 0) ip = ip + 1
5177    IF ( ip .LT. nb_basin ) THEN
5178       WRITE(numout,*) 'We have less outflow points than basins :', ip
5179       WRITE(fmt,"('(',I3,'I9)')") nbi
5180       WRITE(numout,*) '-----------------------> trip'
5181       DO jp=1,nbj
5182          WRITE(numout,fmt) trip(1:nbi,jp)
5183       ENDDO
5184       WRITE(numout,*) '-----------------------> basin'
5185       DO jp=1,nbj
5186          WRITE(numout,fmt) basin(1:nbi,jp)
5187       ENDDO
5188       WRITE(numout,*) 'nb_basin :', nb_basin
5189       WRITE(numout,*) 'Basin sized :', basin_sz(1:nb_basin)
5190       CALL ipslerr_p(3,'routing_findbasins','Probleme less outflow points than basins','','')
5191    ENDIF
5192   
5193  END SUBROUTINE routing_findbasins
5194  !
5195!! ================================================================================================================================
5196!! SUBROUTINE   : routing_simplify
5197!!
5198!>\BRIEF         This subroutine symplifies the routing out of each basin by taking
5199!!               out redundancies at the borders of the GCM box.
5200!!               The aim is to have only one outflow point per basin and grid box.
5201!!               But here we will not change the direction of the outflow. 
5202!!
5203!! DESCRIPTION (definitions, functional, design, flags) : None
5204!!
5205!! RECENT CHANGE(S): None
5206!!
5207!! MAIN OUTPUT VARIABLE(S):
5208!!
5209!! REFERENCES   : None
5210!!
5211!! FLOWCHART    : None
5212!! \n
5213!_ ================================================================================================================================
5214
5215SUBROUTINE routing_simplify(nbi, nbj, trip, basin, hierarchy, basin_inbxid)
5216    !
5217    IMPLICIT NONE
5218    !
5219!! LOCAL VARIABLES
5220    INTEGER(i_std)                             :: nbi                        !! Number of point in x within the grid (unitless)
5221    INTEGER(i_std)                             :: nbj                        !! Number of point in y within the grid (unitless)
5222    INTEGER(i_std)                             :: trip(:,:)                  !! The trip field (unitless)
5223    INTEGER(i_std)                             :: basin(:,:)                 !!
5224    REAL(r_std)                                :: hierarchy(:,:)             !!
5225    INTEGER(i_std)                             :: basin_inbxid               !!
5226    !
5227    INTEGER(i_std)                             :: ip, jp, nbout, basin_sz, iborder !!
5228    INTEGER(i_std), DIMENSION(nbvmax,nbvmax)   :: trip_tmp                   !! Temporary trip field which only contains the values for the basin on which we currently work (1)
5229    INTEGER(i_std), DIMENSION(nbvmax,nbvmax,2) :: trip_flow                  !!
5230    INTEGER(i_std), DIMENSION(nbvmax,2)        :: outflow                    !!
5231    INTEGER(i_std), DIMENSION(nbvmax)          :: outsz                      !!
5232    CHARACTER(LEN=7)                           :: fmt                        !!
5233    !
5234    INTEGER(i_std), DIMENSION(8,2)             :: inc                        !!
5235    INTEGER(i_std)                             :: itodo, ill(1), icc, ismall, ibas, iip, jjp, ib, id !! Indices (unitless)
5236    INTEGER(i_std), DIMENSION(nbvmax)          :: todopt                     !!
5237!!$, todosz
5238    REAL(r_std), DIMENSION(nbvmax)             :: todohi                     !!
5239    LOGICAL                                    :: not_found, debug = .FALSE. !! (true/false)
5240
5241!_ ================================================================================================================================
5242    !
5243    !
5244    !  The routing code (i=1, j=2)
5245    !
5246    inc(1,1) = 0
5247    inc(1,2) = -1
5248    inc(2,1) = 1
5249    inc(2,2) = -1
5250    inc(3,1) = 1
5251    inc(3,2) = 0
5252    inc(4,1) = 1
5253    inc(4,2) = 1
5254    inc(5,1) = 0
5255    inc(5,2) = 1
5256    inc(6,1) = -1
5257    inc(6,2) = 1
5258    inc(7,1) = -1
5259    inc(7,2) = 0
5260    inc(8,1) = -1
5261    inc(8,2) = -1
5262    !
5263    !
5264    !  Symplify the outflow conditions first. We are only interested in the
5265    !  outflows which go to different GCM grid boxes.
5266    !
5267    IF ( debug ) THEN
5268       WRITE(numout,*) '+++++++++++++++++++ BEFORE ANYTHING ++++++++++++++++++++'
5269       WRITE(fmt,"('(',I3,'I6)')") nbi
5270       DO jp=1,nbj
5271          WRITE(numout,fmt) trip_tmp(1:nbi,jp)
5272       ENDDO
5273    ENDIF
5274    !
5275    !  transfer the trips into an array which only contains the basin we are interested in
5276    !
5277    trip_tmp(:,:) = -1
5278    basin_sz = 0
5279    DO ip=1,nbi
5280       DO jp=1,nbj
5281          IF ( basin(ip,jp) .EQ. basin_inbxid) THEN
5282             trip_tmp(ip,jp) = trip(ip,jp)
5283             basin_sz = basin_sz + 1
5284          ENDIF
5285       ENDDO
5286    ENDDO
5287    !
5288    ! Determine for each point where it flows to
5289    !
5290    CALL routing_findrout(nbi, nbj, trip_tmp, basin_sz, basin_inbxid, nbout, outflow, trip_flow, outsz)
5291    !
5292    !
5293    !
5294    !
5295    ! Over the width of a GCM grid box we can have many outflows but we are interested
5296    ! in only one for each basin. Thus we wish to collect them all to form only one outflow
5297    ! to the neighboring grid box.
5298    !
5299    DO iborder = 101,107,2
5300       !
5301       ! If we have more than one of these outflows then we need to merge the sub-basins
5302       !
5303       icc = COUNT(trip_tmp .EQ. iborder)-1
5304       DO WHILE ( icc .GT. 0)
5305          ! Pick out all the points we will have to do
5306          itodo = 0
5307          DO ip=1,nbout
5308             IF (trip_tmp(outflow(ip,1),outflow(ip,2)) .EQ. iborder) THEN
5309                itodo = itodo + 1
5310                todopt(itodo) = ip
5311!!$                todosz(itodo) = outsz(ip)
5312                ! We take the hierarchy of the outflow point as we will try to
5313                ! minimize if for the outflow of the entire basin.
5314                todohi(itodo) = hierarchy(outflow(ip,1),outflow(ip,2))
5315             ENDIF
5316          ENDDO
5317          !
5318          ! We change the direction of the smallest basin.
5319          !
5320          ill=MAXLOC(todohi(1:itodo))
5321          ismall = todopt(ill(1))
5322          !
5323          DO ip=1,nbi
5324             DO jp=1,nbj
5325                IF ( trip_flow(ip,jp,1) .EQ. outflow(ismall,1) .AND.&
5326                     & trip_flow(ip,jp,2) .EQ. outflow(ismall,2) ) THEN
5327                   ! Now that we have found a point of the smallest sub-basin we
5328                   ! look around for another sub-basin
5329                   ib = 1
5330                   not_found = .TRUE.
5331                   DO WHILE ( not_found .AND. ib .LE. itodo ) 
5332                      IF ( ib .NE. ill(1) ) THEN
5333                         ibas = todopt(ib)
5334                         DO id=1,8
5335                            iip = ip + inc(id,1)
5336                            jjp = jp + inc(id,2)
5337                            ! Can we look at this points or is there any need to ?
5338                            IF ( iip .GE. 1 .AND. iip .LE. nbi .AND. &
5339                                 & jjp .GE. 1 .AND. jjp .LE. nbj .AND. not_found) THEN
5340                               ! Is this point the one we look for ?
5341                               IF ( trip_flow(iip,jjp,1) .EQ. outflow(ibas,1) .AND. &
5342                                    & trip_flow(iip,jjp,2) .EQ. outflow(ibas,2)) THEN
5343                                  trip_flow(ip,jp,1) = outflow(ibas,1)
5344                                  trip_flow(ip,jp,2) = outflow(ibas,2)
5345                                  trip_tmp(ip,jp) = id
5346                                  ! This last line ensures that we do not come back to this point
5347                                  ! and that in the end the outer while will stop
5348                                  not_found = .FALSE.
5349                               ENDIF
5350                            ENDIF
5351                         ENDDO
5352                      ENDIF
5353                      ib = ib + 1
5354                   ENDDO
5355                ENDIF
5356             ENDDO
5357          ENDDO
5358          !
5359          icc = icc - 1
5360       ENDDO
5361       !
5362       !
5363    ENDDO
5364    !
5365    IF ( debug ) THEN
5366       WRITE(numout,*) '+++++++++++++++++++ AFTER +++++++++++++++++++++++++++++'
5367       WRITE(fmt,"('(',I3,'I6)')") nbi
5368       DO jp=1,nbj
5369          WRITE(numout,fmt) trip_tmp(1:nbi,jp)
5370       ENDDO
5371    ENDIF
5372    !
5373    !  Put trip_tmp back into trip
5374    !
5375    DO ip=1,nbi
5376       DO jp=1,nbj
5377          IF ( trip_tmp(ip,jp) .GT. 0) THEN
5378             trip(ip,jp) = trip_tmp(ip,jp)
5379          ENDIF
5380       ENDDO
5381    ENDDO
5382    !
5383  END SUBROUTINE routing_simplify
5384!
5385!! ================================================================================================================================
5386!! SUBROUTINE   : routing_cutbasin
5387!!
5388!>\BRIEF        This subroutine cuts the original basin which has more than one outflow
5389!!              into as many subbasins as outflow directions. 
5390!!
5391!! DESCRIPTION (definitions, functional, design, flags) : None
5392!!
5393!! RECENT CHANGE(S): None
5394!!
5395!! MAIN OUTPUT VARIABLE(S):
5396!!
5397!! REFERENCES   : None
5398!!
5399!! FLOWCHART    : None
5400!! \n
5401!_ ================================================================================================================================
5402
5403SUBROUTINE routing_cutbasin (nbi, nbj, nbbasins, trip, basin, basin_inbxid, nb, bname, sz, pts)
5404    !
5405    IMPLICIT NONE
5406    !
5407!! INPUT VARIABLES
5408    INTEGER(i_std), INTENT(in)                 :: nbi, nbj             !! Number of point in x and y within the grid (unitless)
5409    INTEGER(i_std), INTENT(in)                 :: nbbasins             !!
5410    INTEGER(i_std), INTENT(in)                 :: basin_inbxid         !!
5411    !
5412    !  Modified
5413    INTEGER(i_std), INTENT(inout)              :: trip(:,:)            !! The trip field (unitless)
5414    INTEGER(i_std), INTENT(inout)              :: basin(:,:)           !!
5415    !
5416!! OUTPUT VARIABLES
5417    INTEGER(i_std), INTENT(out)                :: nb                   !!
5418    INTEGER(i_std), INTENT(out)                :: bname(nbvmax)        !!
5419    INTEGER(i_std), INTENT(out)                :: sz(nbvmax)           !!
5420    INTEGER(i_std), INTENT(out)                :: pts(nbvmax,nbvmax,2) !!
5421    !
5422!! LOCAL VARIABLES
5423    INTEGER(i_std)                             :: ip, jp, iip, jjp, ib, ibb, id, nbout !! Indices (unitless)
5424    INTEGER(i_std)                             :: basin_sz             !!
5425    INTEGER(i_std)                             :: nb_in                !!
5426    INTEGER(i_std), DIMENSION(nbvmax,nbvmax)   :: trip_tmp             !! Temporary trip field which only contains the values for the basin on which we currently work (unitless)
5427    INTEGER(i_std), DIMENSION(nbvmax,nbvmax,2) :: trip_flow            !!
5428    INTEGER(i_std), DIMENSION(nbvmax,2)        :: outflow              !!
5429    INTEGER(i_std), DIMENSION(nbvmax)          :: outsz                !!
5430    CHARACTER(LEN=7)                           :: fmt                  !!
5431    LOGICAL                                    :: not_found            !! (true/false)
5432    LOGICAL                                    :: debug=.FALSE.        !! (true/false)
5433    !
5434    INTEGER(i_std), DIMENSION(8,2)             :: inc                  !!
5435
5436!_ ================================================================================================================================
5437    !
5438    !
5439    !  The routing code (i=1, j=2)
5440    !
5441    inc(1,1) = 0
5442    inc(1,2) = -1
5443    inc(2,1) = 1
5444    inc(2,2) = -1
5445    inc(3,1) = 1
5446    inc(3,2) = 0
5447    inc(4,1) = 1
5448    inc(4,2) = 1
5449    inc(5,1) = 0
5450    inc(5,2) = 1
5451    inc(6,1) = -1
5452    inc(6,2) = 1
5453    inc(7,1) = -1
5454    inc(7,2) = 0
5455    inc(8,1) = -1
5456    inc(8,2) = -1
5457    !
5458    ! Set up a temporary trip field which only contains the values
5459    ! for the basin on which we currently work.
5460    !
5461    trip_tmp(:,:) = -1
5462    basin_sz = 0
5463    DO ip=1,nbi
5464       DO jp=1,nbj
5465          IF ( basin(ip,jp) .EQ. basin_inbxid) THEN
5466             trip_tmp(ip,jp) = trip(ip,jp)
5467             basin_sz = basin_sz + 1
5468          ENDIF
5469       ENDDO
5470    ENDDO
5471    !
5472    CALL routing_findrout(nbi, nbj, trip_tmp, basin_sz, basin_inbxid, nbout, outflow, trip_flow, outsz)
5473    !
5474!    IF ( debug ) THEN
5475!       DO ib = nb_in+1,nb
5476!          DO ip=1,sz(ib)
5477!             trip_tmp(pts(ib, ip, 1),pts(ib, ip, 2)) = ib*(-1)-900
5478!          ENDDO
5479!       ENDDO
5480!       WRITE(fmt,"('(',I3,'I6)')") nbi
5481!       WRITE(numout,*)  'BEFORE ------------> New basins '
5482!       WRITE(numout,*) nb, ' sz :', sz(1:nb)
5483!       DO jp=1,nbj
5484!          WRITE(numout,fmt) trip_tmp(1:nbi,jp)
5485!       ENDDO
5486!    ENDIF
5487    !
5488    !  Take out the small sub-basins. That is those which have only one grid box
5489    !  This is only done if we need to save space in the number of basins. Else we
5490    !  can take it easy and keep diverging sub-basins for the moment.
5491    !
5492    IF ( nbbasins .GE. nbasmax ) THEN
5493       DO ib=1,nbout
5494          ! If the sub-basin is of size one and its larger neighbor is flowing into another
5495          ! direction then we put them together.
5496          IF ( outsz(ib) .EQ. 1 .AND. trip(outflow(ib,1), outflow(ib,2)) .GT. 99 ) THEN
5497             !
5498             not_found = .TRUE.
5499             DO id=1,8
5500                ip = outflow(ib,1)
5501                jp = outflow(ib,2)
5502                iip = ip + inc(id,1)
5503                jjp = jp + inc(id,2)
5504                ! Can we look at this points ?
5505                IF ( iip .GE. 1 .AND. iip .LE. nbi .AND. &
5506                     & jjp .GE. 1 .AND. jjp .LE. nbj .AND. not_found) THEN
5507                   ! Did we find a direct neighbor which is an outflow point ?
5508                   IF ( trip_tmp(iip,jjp) .GT. 100 ) THEN
5509                      ! IF so direct the flow towards it and update the tables.
5510                      not_found = .FALSE.
5511                      trip(ip,jp) = id
5512                      trip_tmp(ip,jp) = id
5513                      outsz(ib) = 0
5514                      ! update the table of this basin
5515                      DO ibb=1,nbout
5516                         IF ( iip .EQ. outflow(ibb,1) .AND. jjp .EQ. outflow(ibb,2) ) THEN
5517                            outsz(ibb) = outsz(ibb)+1 
5518                            trip_flow(ip,jp,1) = outflow(ibb,1)
5519                            trip_flow(ip,jp,2) = outflow(ibb,2)
5520                         ENDIF
5521                      ENDDO
5522                   ENDIF
5523                ENDIF
5524             ENDDO
5525          ENDIF
5526       ENDDO
5527    ENDIF
5528    !
5529    !
5530    !  Cut the basin if we have more than 1 left.
5531    !
5532    !
5533    IF ( COUNT(outsz(1:nbout) .GT. 0) .GT. 1 ) THEN
5534       !
5535       nb_in = nb
5536       !
5537       DO ib = 1,nbout
5538          IF ( outsz(ib) .GT. 0) THEN
5539             nb = nb+1
5540             IF ( nb .GT. nbvmax) THEN
5541                WRITE(numout,*) 'nbvmax too small, increase it (routing_cutbasin)'
5542             ENDIF
5543             bname(nb) = basin_inbxid
5544             sz(nb) = 0
5545             DO ip=1,nbi
5546                DO jp=1,nbj
5547                   IF ( (trip_flow(ip,jp,1) + trip_flow(ip,jp,1)) .GT. 0 .AND. &
5548                      & trip_flow(ip,jp,1) .EQ. outflow(ib,1) .AND. &
5549                      & trip_flow(ip,jp,2) .EQ. outflow(ib,2) ) THEN
5550                      sz(nb) = sz(nb) + 1
5551                      pts(nb, sz(nb), 1) = ip
5552                      pts(nb, sz(nb), 2) = jp
5553                   ENDIF
5554                ENDDO
5555             ENDDO
5556          ENDIF
5557       ENDDO
5558       ! A short verification
5559       IF ( SUM(sz(nb_in+1:nb)) .NE. basin_sz) THEN
5560          WRITE(numout,*) 'Lost some points while spliting the basin'
5561          WRITE(numout,*) 'nbout :', nbout
5562          DO ib = nb_in+1,nb
5563             WRITE(numout,*) 'ib, SZ :', ib, sz(ib)
5564          ENDDO
5565          WRITE(fmt,"('(',I3,'I6)')") nbi
5566          WRITE(numout,*)  '-------------> trip '
5567          DO jp=1,nbj
5568             WRITE(numout,fmt) trip_tmp(1:nbi,jp)
5569          ENDDO
5570          CALL ipslerr_p(3,'routing_cutbasin','Lost some points while spliting the basin','','')
5571       ENDIF
5572       
5573       IF ( debug ) THEN
5574          DO ib = nb_in+1,nb
5575             DO ip=1,sz(ib)
5576                trip_tmp(pts(ib, ip, 1),pts(ib, ip, 2)) = ib*(-1)-900
5577             ENDDO
5578          ENDDO
5579          WRITE(fmt,"('(',I3,'I6)')") nbi
5580          WRITE(numout,*)  'AFTER-------------> New basins '
5581          WRITE(numout,*) nb, ' sz :', sz(1:nb)
5582          DO jp=1,nbj
5583             WRITE(numout,fmt) trip_tmp(1:nbi,jp)
5584          ENDDO
5585          IF ( MAXVAl(trip_tmp(1:nbi,1:nbj)) .GT. 0) THEN
5586             CALL ipslerr_p(3,'routing_cutbasin','Error in debug checking','','')
5587          ENDIF
5588       ENDIF
5589    ENDIF
5590    !
5591  END SUBROUTINE routing_cutbasin
5592  !
5593!! ================================================================================================================================
5594!! SUBROUTINE   : routing_hierarchy
5595!!
5596!>\BRIEF        This subroutine finds, for each point, the distance to the outflow
5597!!               point along the flowlines of the basin.
5598!!
5599!! DESCRIPTION (definitions, functional, design, flags) : None
5600!!
5601!! RECENT CHANGE(S): None
5602!!
5603!! MAIN OUTPUT VARIABLE(S):
5604!!
5605!! REFERENCES   : None
5606!!
5607!! FLOWCHART    : None
5608!! \n
5609!_ ================================================================================================================================
5610
5611SUBROUTINE routing_hierarchy(iml, jml, trip, topoindex, hierarchy)
5612    !
5613    IMPLICIT NONE
5614    !
5615!! LOCAL VARIABLES
5616    INTEGER(i_std)                  :: iml          !! X resolution of the high resolution grid
5617    INTEGER(i_std)                  :: jml          !! Y resolution of the high resolution grid
5618    REAL(r_std), DIMENSION(iml,jml) :: trip         !! The trip field (unitless)
5619    REAL(r_std), DIMENSION(iml,jml) :: hierarchy    !!
5620    REAL(r_std), DIMENSION(iml,jml) :: topoindex    !! Topographic index of the residence time (m)
5621    !
5622    INTEGER(i_std), DIMENSION(8,2)  :: inc          !!
5623    INTEGER(i_std)                  :: ip, jp, ib, ntripi, ntripj, cnt, trp !!
5624    REAL(r_std)                     :: topohier     !! The new value of topographically weighted hierarchy (m)
5625    REAL(r_std)                     :: topohier_old !! The old value of topographically weighted hierarchy (m)
5626    CHARACTER(LEN=7)                :: fmt          !!
5627
5628!_ ================================================================================================================================
5629    !
5630    !  The routing code (i=1, j=2)
5631    !
5632    inc(1,1) = 0
5633    inc(1,2) = -1
5634    inc(2,1) = 1
5635    inc(2,2) = -1
5636    inc(3,1) = 1
5637    inc(3,2) = 0
5638    inc(4,1) = 1
5639    inc(4,2) = 1
5640    inc(5,1) = 0
5641    inc(5,2) = 1
5642    inc(6,1) = -1
5643    inc(6,2) = 1
5644    inc(7,1) = -1
5645    inc(7,2) = 0
5646    inc(8,1) = -1
5647    inc(8,2) = -1
5648    !
5649    DO ip=1,iml
5650       DO jp=1,jml
5651          IF ( trip(ip,jp) .LT. undef_sechiba ) THEN
5652             ntripi = ip
5653             ntripj = jp
5654             trp = NINT(trip(ip,jp))
5655             cnt = 1
5656             ! Warn for extreme numbers
5657             IF (  topoindex(ip,jp) .GT. 1.e10 ) THEN
5658                WRITE(numout,*) 'We have a very large topographic index for point ', ip, jp
5659                WRITE(numout,*) 'This can not be right :', topoindex(ip,jp)
5660                CALL ipslerr_p(3,'routing_hierarchy','Too large topographic index','','')
5661             ELSE
5662                topohier = topoindex(ip,jp)
5663             ENDIF
5664             !
5665             DO WHILE ( trp .GT. 0 .AND. trp .LT. 9 .AND. cnt .LT. iml*jml) 
5666                cnt = cnt + 1
5667                ntripi = ntripi + inc(trp,1)
5668                IF ( ntripi .LT. 1) ntripi = iml
5669                IF ( ntripi .GT. iml) ntripi = 1
5670                ntripj = ntripj + inc(trp,2)
5671                topohier_old = topohier
5672                topohier = topohier + topoindex(ntripi, ntripj)
5673                IF ( topohier_old .GT. topohier) THEN
5674                   WRITE(numout,*) 'Big Problem, how comes we climb up a hill ?'
5675                   WRITE(numout,*) 'The old value of topographicaly weighted hierarchy was : ', topohier_old
5676                   WRITE(numout,*) 'The new one is :', topohier
5677                   CALL ipslerr_p(3,'routing_hierarchy','Big Problem, how comes we climb up a hill ?','','')
5678                ENDIF
5679                trp = NINT(trip(ntripi, ntripj))
5680             ENDDO
5681             
5682             IF ( cnt .EQ. iml*jml) THEN
5683                WRITE(numout,*) 'We could not route point (routing_findrout) :', ip, jp
5684                WRITE(numout,*) '-------------> trip '
5685                WRITE(fmt,"('(',I3,'I6)')") iml
5686                DO ib=1,jml
5687                   WRITE(numout,fmt) trip(1:iml,ib)
5688                ENDDO
5689                CALL ipslerr_p(3,'routing_hierarchy','We could not route point','','')
5690             ENDIF
5691             
5692             hierarchy(ip,jp) = topohier
5693             
5694          ENDIF
5695       ENDDO
5696    ENDDO
5697    !
5698    !
5699  END SUBROUTINE routing_hierarchy
5700  !
5701!! ================================================================================================================================
5702!! SUBROUTINE   : routing_findrout
5703!!
5704!>\BRIEF        This subroutine simply computes the route to each outflow point
5705!!              and returns the outflow point for each point in the basin. 
5706!!
5707!! DESCRIPTION (definitions, functional, design, flags) : None
5708!!
5709!! RECENT CHANGE(S): None
5710!!
5711!! MAIN OUTPUT VARIABLE(S):
5712!!
5713!! REFERENCES   : None
5714!!
5715!! FLOWCHART    : None
5716!! \n
5717!_ ================================================================================================================================
5718
5719SUBROUTINE routing_findrout(nbi, nbj, trip, basin_sz, basinid, nbout, outflow, trip_flow, outsz)
5720    !
5721    IMPLICIT NONE
5722    !
5723!! INPUT VARIABLES
5724    INTEGER(i_std)                                          :: nbi       !! Number of point in x within the grid (unitless)
5725    INTEGER(i_std)                                          :: nbj       !! Number of point in y within the grid (unitless)
5726    INTEGER(i_std), DIMENSION(nbvmax,nbvmax)                :: trip      !! The trip field (unitless)
5727    INTEGER(i_std)                                          :: basin_sz  !!
5728    INTEGER(i_std)                                          :: basinid   !!
5729    !
5730!! OUTPUT VARIABLES
5731    INTEGER(i_std), DIMENSION(nbvmax,2), INTENT(out)        :: outflow   !!
5732    INTEGER(i_std), DIMENSION(nbvmax,nbvmax,2), INTENT(out) :: trip_flow !!
5733    INTEGER(i_std), INTENT(out)                             :: nbout     !!
5734    INTEGER(i_std), DIMENSION(nbvmax), INTENT(out)          :: outsz     !!
5735    !
5736!! LOCAL VARIABLES
5737    INTEGER(i_std), DIMENSION(8,2)                          :: inc       !!
5738    INTEGER(i_std)                                          :: ip, jp, ib, cnt, trp, totsz !! Indices (unitless)
5739    CHARACTER(LEN=7)                                        :: fmt       !!
5740
5741!_ ================================================================================================================================
5742    !
5743    !
5744    !  The routing code (i=1, j=2)
5745    !
5746    inc(1,1) = 0
5747    inc(1,2) = -1
5748    inc(2,1) = 1
5749    inc(2,2) = -1
5750    inc(3,1) = 1
5751    inc(3,2) = 0
5752    inc(4,1) = 1
5753    inc(4,2) = 1
5754    inc(5,1) = 0
5755    inc(5,2) = 1
5756    inc(6,1) = -1
5757    inc(6,2) = 1
5758    inc(7,1) = -1
5759    inc(7,2) = 0
5760    inc(8,1) = -1
5761    inc(8,2) = -1
5762    !
5763    !
5764    !  Get the outflows and determine for each point to which outflow point it belong
5765    !
5766    nbout = 0
5767    trip_flow(:,:,:) = 0
5768    DO ip=1,nbi
5769       DO jp=1,nbj
5770          IF ( trip(ip,jp) .GT. 9) THEN
5771             nbout = nbout + 1
5772             outflow(nbout,1) = ip
5773             outflow(nbout,2) = jp
5774          ENDIF
5775          IF ( trip(ip,jp) .GT. 0) THEN
5776             trip_flow(ip,jp,1) = ip
5777             trip_flow(ip,jp,2) = jp
5778          ENDIF
5779       ENDDO
5780    ENDDO
5781    !
5782    ! Follow the flow of the water
5783    !
5784    DO ip=1,nbi
5785       DO jp=1,nbj
5786          IF ( (trip_flow(ip,jp,1) + trip_flow(ip,jp,2)) .GT. 0) THEN
5787             trp = trip(trip_flow(ip,jp,1), trip_flow(ip,jp,2))
5788             cnt = 0
5789             DO WHILE ( trp .GT. 0 .AND. trp .LT. 9 .AND. cnt .LT. nbi*nbj) 
5790                cnt = cnt + 1
5791                trip_flow(ip,jp,1) = trip_flow(ip,jp,1) + inc(trp,1)
5792                trip_flow(ip,jp,2) = trip_flow(ip,jp,2) + inc(trp,2)
5793                trp = trip(trip_flow(ip,jp,1), trip_flow(ip,jp,2))
5794             ENDDO
5795             IF ( cnt .EQ. nbi*nbj) THEN
5796                WRITE(numout,*) 'We could not route point (routing_findrout) :', ip, jp
5797                WRITE(numout,*) '-------------> trip '
5798                WRITE(fmt,"('(',I3,'I6)')") nbi
5799                DO ib=1,nbj
5800                   WRITE(numout,fmt) trip(1:nbi,ib)
5801                ENDDO
5802                CALL ipslerr_p(3,'routing_findrout','We could not route point','','')
5803             ENDIF
5804          ENDIF
5805       ENDDO
5806    ENDDO
5807    !
5808    !  What is the size of the region behind each outflow point ?
5809    !
5810    totsz = 0
5811    DO ip=1,nbout
5812       outsz(ip) = COUNT(trip_flow(:,:,1) .EQ. outflow(ip,1) .AND. trip_flow(:,:,2) .EQ. outflow(ip,2))
5813       totsz = totsz + outsz(ip)
5814    ENDDO
5815    IF ( basin_sz .NE. totsz) THEN
5816       WRITE(numout,*) 'Water got lost while I tried to follow it '
5817       WRITE(numout,*) basin_sz, totsz
5818       WRITE(numout,*) 'Basin id :', basinid
5819       DO ip=1,nbout
5820          WRITE(numout,*) 'ip :', ip, ' outsz :', outsz(ip), ' outflow :', outflow(ip,1), outflow(ip,2)
5821       ENDDO
5822       WRITE(numout,*) '-------------> trip '
5823       WRITE(fmt,"('(',I3,'I6)')") nbi
5824       DO jp=1,nbj
5825          WRITE(numout,fmt) trip(1:nbi,jp)
5826       ENDDO
5827       CALL ipslerr_p(3,'routing_findrout','Water got lost while I tried to follow it','','')
5828    ENDIF
5829    !
5830  END SUBROUTINE routing_findrout
5831  !
5832!! ================================================================================================================================
5833!! SUBROUTINE   : routing_globalize
5834!!
5835!>\BRIEF        This subroutine puts the basins found for grid box in the global map.
5836!!               Connection can only be made later when all information is together.
5837!!
5838!! DESCRIPTION (definitions, functional, design, flags) : None
5839!!
5840!! RECENT CHANGE(S): None
5841!!
5842!! MAIN OUTPUT VARIABLE(S):
5843!! One of the outputs is basin_flowdir. Its convention is 1-8 for the directions from North to North
5844!! West going through South. The negative values will be -3 for return flow, -2 for coastal flow
5845!!
5846!! REFERENCES   : None
5847!!
5848!! FLOWCHART    : None
5849!! \n
5850!_ ================================================================================================================================
5851
5852SUBROUTINE routing_globalize(nbpt, ib, neighbours, area_bx, trip_bx, hierarchy_bx, topoind_bx, min_topoind,&
5853       & nb_basin, basin_inbxid, basin_sz, basin_pts, basin_bxout, coast_pts, nwbas, basin_count,&
5854       & basin_area, basin_hierarchy, basin_topoind, basin_id, basin_flowdir, outflow_grid,&
5855       & nbcoastal, coastal_basin)
5856    !
5857    IMPLICIT NONE
5858    !
5859!! INPUT VARIABLES
5860    INTEGER(i_std), INTENT (in)                :: nbpt                   !! Domain size (unitless)
5861    INTEGER(i_std), INTENT (in)                :: ib                     !! Current basin (unitless)
5862    INTEGER(i_std), INTENT(in)                 :: neighbours(nbpt,NbNeighb)!! Vector of neighbours for each grid point
5863                                                                         !! (1=North and then clockwise)
5864!! LOCAL VARIABLES
5865    REAL(r_std), DIMENSION(nbvmax,nbvmax)      :: area_bx                !! Area of each small box in the grid box (m^2)
5866    INTEGER(i_std), DIMENSION(nbvmax,nbvmax)   :: trip_bx                !! The trip field for each of the smaller boxes (unitless)
5867    REAL(r_std), DIMENSION(nbvmax,nbvmax)      :: hierarchy_bx           !! Level in the basin of the point
5868    REAL(r_std), DIMENSION(nbvmax,nbvmax)      :: topoind_bx             !! Topographic index of the residence time for each of the smaller boxes (m)
5869    REAL(r_std)                                :: min_topoind            !! The current minimum of topographic index (m)
5870    INTEGER(i_std)                             :: nb_basin               !! Number of sub-basins (unitless)
5871    INTEGER(i_std), DIMENSION(nbvmax)          :: basin_inbxid, basin_sz !! ID of basin, number of points in the basin
5872    INTEGER(i_std), DIMENSION(nbvmax,nbvmax,2) :: basin_pts              !! Points in each basin
5873    INTEGER(i_std), DIMENSION(nbvmax)          :: basin_bxout            !! outflow direction
5874    INTEGER(i_std)                             :: coast_pts(nbvmax)      !! The coastal flow points (unitless)
5875    ! global maps
5876    INTEGER(i_std)                             :: nwbas                  !!
5877    INTEGER(i_std), DIMENSION(nbpt)            :: basin_count            !!
5878    INTEGER(i_std), DIMENSION(nbpt,nwbas)      :: basin_id               !!
5879    INTEGER(i_std), DIMENSION(nbpt,nwbas)      :: basin_flowdir          !! Water flow directions in the basin (unitless)
5880    REAL(r_std), DIMENSION(nbpt,nwbas)         :: basin_area             !!
5881    REAL(r_std), DIMENSION(nbpt,nwbas)         :: basin_hierarchy        !!
5882    REAL(r_std), DIMENSION(nbpt,nwbas)         :: basin_topoind          !! Topographic index of the residence time for a basin (m)
5883    INTEGER(i_std), DIMENSION(nbpt,nwbas)      :: outflow_grid           !! Type of outflow on the grid box (unitless)
5884    INTEGER(i_std), DIMENSION(nbpt)            :: nbcoastal              !!
5885    INTEGER(i_std), DIMENSION(nbpt,nwbas)      :: coastal_basin          !!
5886    !
5887    INTEGER(i_std)                             :: ij, iz                 !! Indices (unitless)
5888    CHARACTER(LEN=4)                           :: hierar_method = 'OUTP' !!
5889
5890!_ ================================================================================================================================
5891    !
5892    !
5893    DO ij=1, nb_basin
5894       !
5895       ! Count the basins and keep their ID
5896       !
5897       basin_count(ib) = basin_count(ib)+1
5898       if (basin_count(ib) > nwbas) then
5899          WRITE(numout,*) 'ib=',ib
5900          call ipslerr_p(3,'routing_globalize', &
5901               &      'Problem with basin_count : ', & 
5902               &      'It is greater than number of allocated basin nwbas.', &
5903               &      '(stop to count basins)')
5904       endif
5905       basin_id(ib,basin_count(ib)) = basin_inbxid(ij)
5906       !
5907       ! Transfer the list of basins which flow into the ocean as coastal flow.
5908       !
5909       IF ( basin_id(ib,basin_count(ib)) .LT. 0) THEN
5910          nbcoastal(ib) = basin_sz(ij)
5911          coastal_basin(ib,1:nbcoastal(ib)) = coast_pts(1:nbcoastal(ib))
5912       ENDIF
5913       !
5914       !
5915       ! Compute the area of the basin
5916       !
5917       basin_area(ib,ij) = zero
5918       basin_hierarchy(ib,ij) = zero
5919       !
5920       SELECT CASE (hierar_method)
5921          !
5922          CASE("MINI")
5923             basin_hierarchy(ib,ij) = undef_sechiba
5924          !
5925       END SELECT
5926       basin_topoind(ib,ij) = zero
5927       !
5928       DO iz=1,basin_sz(ij)
5929          !
5930          basin_area(ib,ij) = basin_area(ib,ij) + area_bx(basin_pts(ij,iz,1),basin_pts(ij,iz,2))
5931          basin_topoind(ib,ij) = basin_topoind(ib,ij) + topoind_bx(basin_pts(ij,iz,1),basin_pts(ij,iz,2))
5932          !
5933          ! There are a number of ways to determine the hierarchy of the entire basin.
5934          ! We allow for three here :
5935          !     - Take the mean value
5936          !     - Take the minimum value within the basin
5937          !     - Take the value at the outflow point
5938          ! Probably taking the value of the outflow point is the best solution.
5939          !
5940          SELECT CASE (hierar_method)
5941             !
5942             CASE("MEAN")
5943                ! Mean hierarchy of the basin
5944                basin_hierarchy(ib,ij) = basin_hierarchy(ib,ij) + &
5945                     & hierarchy_bx(basin_pts(ij,iz,1),basin_pts(ij,iz,2))
5946             CASE("MINI")
5947                ! The smallest value of the basin
5948                IF ( hierarchy_bx(basin_pts(ij,iz,1),basin_pts(ij,iz,2)) .LT. basin_hierarchy(ib,ij)) THEN
5949                   basin_hierarchy(ib,ij) = hierarchy_bx(basin_pts(ij,iz,1),basin_pts(ij,iz,2))
5950                ENDIF
5951             CASE("OUTP")
5952                ! Value at the outflow point
5953                IF ( trip_bx(basin_pts(ij,iz,1),basin_pts(ij,iz,2)) .GT. 100 ) THEN
5954                   basin_hierarchy(ib,ij) = hierarchy_bx(basin_pts(ij,iz,1),basin_pts(ij,iz,2))
5955                ENDIF
5956             CASE DEFAULT
5957                WRITE(numout,*) 'Unknown method for computing the hierarchy of the basin'
5958                CALL ipslerr_p(3,'routing_globalize','Unknown method for computing the hierarchy of the basin','','')
5959          END SELECT
5960          !
5961       ENDDO
5962       !
5963       basin_topoind(ib,ij) = basin_topoind(ib,ij)/REAL(basin_sz(ij),r_std)
5964       !
5965       SELECT CASE (hierar_method)
5966          !
5967          CASE("MEAN")
5968             basin_hierarchy(ib,ij) = basin_hierarchy(ib,ij)/REAL(basin_sz(ij),r_std)
5969          !
5970       END SELECT
5971       !
5972       ! To make sure that it has the lowest number if this is an outflow point we reset  basin_hierarchy
5973       !
5974       IF (basin_bxout(ij) .LT. 0) THEN
5975          basin_hierarchy(ib,ij) = min_topoind
5976          basin_topoind(ib,ij) = min_topoind
5977       ENDIF
5978       !
5979       !
5980       ! Keep the outflow boxes and basin
5981       !
5982       basin_flowdir(ib,ij) = basin_bxout(ij)
5983       IF (basin_bxout(ij) .GT. 0) THEN
5984          outflow_grid(ib,ij) = neighbours(ib,basin_bxout(ij))
5985       ELSE
5986          outflow_grid(ib,ij) = basin_bxout(ij)
5987       ENDIF
5988       !
5989       !
5990    ENDDO
5991    !
5992
5993    !
5994  END SUBROUTINE routing_globalize
5995  !
5996!! ================================================================================================================================
5997!! SUBROUTINE   : routing_linkup
5998!!
5999!>\BRIEF         This subroutine makes the connections between the basins and ensure global coherence.
6000!!
6001!! DESCRIPTION (definitions, functional, design, flags) :
6002!! The convention for outflow_grid is :
6003!! outflow_grid = -1 : River flow
6004!! outflow_grid = -2 : Coastal flow
6005!! outflow_grid = -3 : Return flow\n
6006!!
6007!! RECENT CHANGE(S): None
6008!!
6009!! MAIN OUTPUT VARIABLE(S):
6010!!
6011!! REFERENCES   : None
6012!!
6013!! FLOWCHART    : None
6014!! \n
6015!_ ================================================================================================================================
6016
6017SUBROUTINE routing_linkup(nbpt, contfrac, neighbours, nwbas, basin_count, basin_area, basin_id, basin_flowdir, &
6018       & basin_hierarchy, outflow_grid, outflow_basin, inflow_number, inflow_grid, inflow_basin, nbcoastal,&
6019       & coastal_basin, invented_basins)
6020    !
6021    IMPLICIT NONE
6022    !
6023!! INPUT VARIABLES
6024    INTEGER(i_std), INTENT (in)                    :: nbpt                  !! Domain size  (unitless)
6025    REAL(r_std), DIMENSION(nbpt)                   :: contfrac
6026    INTEGER(i_std), DIMENSION(nbpt,NbNeighb), INTENT (in) :: neighbours            !!
6027    REAL(r_std), INTENT(in)                        :: invented_basins       !!
6028    !
6029    INTEGER(i_std)                                 :: nwbas                 !!
6030    INTEGER(i_std), DIMENSION(nbpt)                :: basin_count           !!
6031    INTEGER(i_std), DIMENSION(nbpt,nwbas)          :: basin_id              !!
6032    INTEGER(i_std), DIMENSION(nbpt,nwbas)          :: basin_flowdir         !! Water flow directions in the basin (unitless)
6033    REAL(r_std), DIMENSION(nbpt,nwbas)             :: basin_area            !!
6034    REAL(r_std), DIMENSION(nbpt,nwbas)             :: basin_hierarchy       !!
6035    INTEGER(i_std), DIMENSION(nbpt,nwbas)          :: outflow_grid          !! Type of outflow on the grid box (unitless)
6036    INTEGER(i_std), DIMENSION(nbpt,nwbas)          :: outflow_basin         !!
6037    INTEGER(i_std), DIMENSION(nbpt,nwbas)          :: inflow_number         !!
6038    INTEGER(i_std), DIMENSION(nbpt,nwbas,nbvmax)   :: inflow_basin          !!
6039    INTEGER(i_std), DIMENSION(nbpt,nwbas,nbvmax)   :: inflow_grid           !!
6040    INTEGER(i_std), DIMENSION(nbpt)                :: nbcoastal             !!
6041    INTEGER(i_std), DIMENSION(nbpt,nwbas)          :: coastal_basin         !!
6042    !
6043!! LOCAL VARIABLES
6044    INTEGER(i_std)                                 :: sp, sb, sbl, inp, bid, outdm1, outdp1 !! Indices (unitless)
6045    INTEGER(i_std)                                 :: dp1, dm1, dm1i, dp1i, bp1, bm1 !! Indices (unitless)
6046    INTEGER(i_std)                                 :: dop, bop              !!
6047    INTEGER(i_std)                                 :: fbas(nwbas), nbfbas   !!
6048    REAL(r_std)                                    :: fbas_hierarchy(nwbas) !!
6049    REAL(r_std)                                    :: angle
6050    INTEGER(i_std)                                 :: ff(1)                 !!
6051    !
6052    ! ERRORS
6053    LOGICAL                                        :: error1, error2, error3, error4, error5 !! (true/false)
6054    !
6055!! PARAMETERS
6056    LOGICAL, PARAMETER                             :: check = .TRUE.       !! (true/false)
6057
6058!_ ================================================================================================================================   
6059    error1=.FALSE.
6060    error2=.FALSE.
6061    error3=.FALSE.
6062    error4=.FALSE.
6063    error5=.FALSE.
6064
6065    outflow_basin(:,:) = undef_int
6066    inflow_number(:,:) = 0
6067    !
6068    DO sp=1,nbpt
6069       DO sb=1,basin_count(sp)
6070          !
6071          inp = outflow_grid(sp,sb)
6072          bid = basin_id(sp,sb)
6073          !
6074          ! We only work on this point if it does not flow into the ocean
6075          ! At this point any of the outflows is designated by a negative values in
6076          ! outflow_grid
6077          !
6078          IF ( inp .GT. 0 ) THEN
6079             !
6080             ! Now find the basin in the onflow point (inp)
6081             !
6082             nbfbas = 0
6083             !
6084             !
6085             DO sbl=1,basin_count(inp)
6086                !
6087                ! Either it is a standard basin or one aggregated from ocean flow points.
6088                ! If we flow into a another grid box we have to make sure that its hierarchy in the
6089                ! basin is lower.
6090                !
6091                !
6092                IF ( basin_id(inp,sbl) .GT. 0 ) THEN
6093                   IF ( basin_id(inp,sbl) .EQ. bid .OR. basin_id(inp,sbl) .GT. invented_basins) THEN
6094                      nbfbas =nbfbas + 1
6095                      fbas(nbfbas) = sbl
6096                      fbas_hierarchy(nbfbas) = basin_hierarchy(inp,sbl)
6097                   ENDIF
6098                ELSE
6099                   IF ( COUNT(coastal_basin(inp,1:nbcoastal(inp)) .EQ. bid) .GT. 0 ) THEN
6100                      nbfbas =nbfbas + 1
6101                      fbas(nbfbas) = sbl
6102                      fbas_hierarchy(nbfbas) = basin_hierarchy(inp,sbl)
6103                   ENDIF
6104                ENDIF
6105                !
6106             ENDDO
6107             !
6108             !  If we have more than one basin we will take the one which is lowest
6109             !  in the hierarchy.
6110             !
6111             IF (nbfbas .GE. 1) THEN
6112                ff = MINLOC(fbas_hierarchy(1:nbfbas))
6113                sbl = fbas(ff(1))
6114                !
6115                bop = undef_int
6116                IF ( basin_hierarchy(inp,sbl) .LE. basin_hierarchy(sp,sb) ) THEN
6117                   IF ( basin_hierarchy(inp,sbl) .LT. basin_hierarchy(sp,sb) ) THEN
6118                      bop = sbl
6119                   ELSE
6120                      ! The same hierarchy is allowed if both grids flow in about
6121                      ! the same direction :
6122                      IF ( ( MOD(basin_flowdir(inp,sbl)+1-1, 8)+1 .EQ. basin_flowdir(sp,sb)).OR. &
6123                           & ( basin_flowdir(inp,sbl) .EQ. basin_flowdir(sp,sb)).OR. &
6124                           & ( MOD(basin_flowdir(inp,sbl)+7-1, 8)+1 .EQ. basin_flowdir(sp,sb)) ) THEN
6125                         bop = sbl
6126                      ENDIF
6127                   ENDIF
6128                ENDIF
6129                !
6130                ! If the basin is suitable (bop < undef_int) then take it
6131                !
6132                IF ( bop .LT. undef_int ) THEN
6133                   outflow_basin(sp,sb) = bop
6134                   inflow_number(inp,bop) =  inflow_number(inp,bop) + 1
6135                   IF ( inflow_number(inp,bop) .LE. nbvmax ) THEN
6136                      inflow_grid(inp, bop, inflow_number(inp,bop)) = sp
6137                      inflow_basin(inp, bop, inflow_number(inp,bop)) = sb
6138                   ELSE
6139                      error1=.TRUE.
6140                      EXIT
6141                   ENDIF
6142                ENDIF
6143             ENDIF
6144             !
6145             !
6146          ENDIF
6147          !
6148          !
6149          !
6150          ! Did we find it ?
6151          !
6152          ! In case the outflow point was ocean or we did not find the correct basin we start to look
6153          ! around. We find two options for the outflow direction (dp1 & dm1) and the corresponding
6154          ! basin index (bp1 & bm1).
6155          !
6156          !
6157          IF ( outflow_basin(sp,sb) .EQ. undef_int &
6158               & .AND. basin_flowdir(sp,sb) .GT. 0) THEN
6159             !
6160             dp1i = MOD(basin_flowdir(sp,sb)+1-1, NbNeighb)+1
6161             dp1 = neighbours(sp,dp1i)
6162             dm1i = MOD(basin_flowdir(sp,sb)+7-1, NbNeighb)+1
6163             IF ( dm1i .LT. 1 ) dm1i = 8
6164             dm1 = neighbours(sp,dm1i)
6165             !
6166             !
6167             bp1 = -1
6168             IF ( dp1 .GT. 0 ) THEN
6169                DO sbl=1,basin_count(dp1)
6170                   IF (basin_id(dp1,sbl) .EQ. bid .AND.&
6171                        & basin_hierarchy(sp,sb) .GE. basin_hierarchy(dp1,sbl) .AND. &
6172                        & bp1 .LT. 0) THEN
6173                      IF ( basin_hierarchy(sp,sb) .GT. basin_hierarchy(dp1,sbl) ) THEN
6174                         bp1 = sbl
6175                      ELSE
6176                         ! The same hierarchy is allowed if both grids flow in about
6177                         ! the same direction :
6178                         angle=MODULO(basin_flowdir(dp1,sbl)-basin_flowdir(sp,sb)+8,8)
6179                         IF ( angle >= 4 ) angle = angle-8
6180                         !
6181                         IF ( ABS(angle) <= 1 ) THEN
6182                            bp1 = sbl
6183                         ENDIF
6184                      ENDIF
6185                   ENDIF
6186                ENDDO
6187             ENDIF
6188             !
6189             bm1 = -1
6190             IF ( dm1 .GT. 0 ) THEN
6191                DO sbl=1,basin_count(dm1)
6192                   IF (basin_id(dm1,sbl) .EQ. bid .AND.&
6193                        & basin_hierarchy(sp,sb) .GE. basin_hierarchy(dm1,sbl) .AND. &
6194                        & bm1 .LT. 0) THEN
6195                      IF ( basin_hierarchy(sp,sb) .GT. basin_hierarchy(dm1,sbl) ) THEN
6196                         bm1 = sbl
6197                      ELSE                         
6198                         ! The same hierarchy is allowed if both grids flow in about
6199                         ! the same direction :
6200                         angle=MODULO(basin_flowdir(dm1,sbl)-basin_flowdir(sp,sb)+8,8)
6201                         IF ( angle >= 4 ) angle = angle-8
6202                         !
6203                         IF ( ABS(angle) <= 1 ) THEN
6204                            bm1 = sbl
6205                         ENDIF
6206                      ENDIF
6207                   ENDIF
6208                ENDDO
6209             ENDIF
6210             !
6211             !
6212             ! First deal with the case on land.
6213             !
6214             ! For that we need to check if the water will be able to flow out of the grid dp1 or dm1
6215             ! and not return to our current grid. If it is the current grid
6216             ! then we can not do anything with that neighbour. Thus we set the
6217             ! value of outdm1 and outdp1 back to -1
6218             !
6219             outdp1 = undef_int
6220             IF ( dp1 .GT. 0 .AND. bp1 .GT. 0 ) THEN
6221                ! if the outflow is into the ocean then we put something less than undef_int in outdp1!
6222                IF (basin_flowdir(dp1,bp1) .GT. 0) THEN
6223                   outdp1 = neighbours(dp1,basin_flowdir(dp1,bp1))
6224                   IF ( outdp1 .EQ. sp ) outdp1 = undef_int 
6225                ELSE
6226                   outdp1 = nbpt + 1
6227                ENDIF
6228             ENDIF
6229             outdm1 = undef_int
6230             IF ( dm1 .GT. 0 .AND. bm1 .GT. 0 ) THEN
6231                IF (basin_flowdir(dm1,bm1) .GT. 0) THEN
6232                   outdm1 = neighbours(dm1,basin_flowdir(dm1,bm1))
6233                   IF ( outdm1 .EQ. sp )  outdm1 = undef_int
6234                ELSE
6235                   outdm1 = nbpt + 1
6236                ENDIF
6237             ENDIF
6238             !
6239             ! Now that we know our options we need go through them.
6240             !
6241             dop = undef_int
6242             bop = undef_int
6243             IF ( outdp1 .LT. undef_int .AND. outdm1 .LT. undef_int) THEN
6244                !
6245                ! In this case we let the current basin flow into the smaller one
6246                !
6247                IF ( basin_area(dp1,bp1) .LT.  basin_area(dm1,bm1) ) THEN
6248                   dop = dp1
6249                   bop = bp1
6250                ELSE
6251                   dop = dm1
6252                   bop = bm1
6253                ENDIF
6254                !
6255                !
6256             ELSE IF (  outdp1 .LT. undef_int ) THEN
6257                ! If only the first one is possible
6258                dop = dp1
6259                bop = bp1
6260             ELSE IF ( outdm1 .LT. undef_int ) THEN
6261                ! If only the second one is possible
6262                dop = dm1
6263                bop = bm1
6264             ELSE
6265                !
6266                ! Now we are at the point where none of the neighboring points is suitable
6267                ! or we have a coastal point.
6268                !
6269                ! If there is an option to put the water into the ocean go for it.
6270                !
6271                IF ( outflow_grid(sp,sb) .LT. 0 .OR. dm1 .LT. 0 .OR. dp1 .LT. 0 ) THEN
6272                   dop = -1
6273                ELSE
6274                   !
6275                   ! If we are on a land point with only land neighbors but no one suitable to let the
6276                   ! water flow into we have to look for a solution in the current grid box.
6277                   !
6278                   !
6279                   IF ( bp1 .LT. 0 .AND. bm1 .LT. 0 ) THEN
6280                      !
6281                      ! Do we have more than one basin with the same ID ?
6282                      !
6283                      IF ( COUNT(basin_id(sp,1:basin_count(sp)) .EQ. bid) .GE. 2) THEN
6284                         !
6285                         ! Now we can try the option of flowing into the basin of the same grid box.
6286                         !
6287                         DO sbl=1,basin_count(sp)
6288                            IF (sbl .NE. sb .AND. basin_id(sp,sbl) .EQ. bid) THEN
6289                               ! In case this basin has a lower hierarchy or flows into a totaly
6290                               ! different direction we go for it.
6291                               IF ( (basin_hierarchy(sp,sb) .GE. basin_hierarchy(sp,sbl)) .OR. &
6292                                    & (basin_flowdir(sp,sbl) .LT. dm1i .AND.&
6293                                    & basin_flowdir(sp,sbl) .GT. dp1i) ) THEN
6294                                  dop = sp
6295                                  bop = sbl
6296                                  IF (check) THEN
6297                                     IF (basin_hierarchy(sp,sb) .LT. basin_hierarchy(sp,sbl)) THEN
6298                                        WRITE(numout,*) '>>>>>>> POINT CORRECTED against hierarchy :',&
6299                                             & sp, sb, 'into', sbl
6300                                     ENDIF
6301                                  ENDIF
6302                               ENDIF
6303                               !
6304                            ENDIF
6305                         ENDDO
6306                         !
6307                      ENDIF
6308                   ENDIF
6309                ENDIF
6310                !
6311                IF ( dop .EQ. undef_int .AND. bop .EQ. undef_int ) THEN
6312                   IF (check) THEN
6313                      WRITE(numout,*) 'Why are we here with point ', sp, sb
6314                      WRITE(numout,*) 'Coordinates : (lon,lat) = ', lalo_g(sp,2), lalo_g(sp,1)
6315                      WRITE(numout,*) 'neighbours :', neighbours_g(sp,:)
6316                      WRITE(numout,*) 'Contfrac : = ', contfrac(sp)
6317                      WRITE(numout,*) 'Local Basin ID :', basin_id(sp,1:basin_count(sp))
6318                      WRITE(numout,*) 'Local hierarchies :', basin_hierarchy(sp,1:basin_count(sp))
6319                      WRITE(numout,*) 'Local basin_flowdir :', basin_flowdir(sp,1:basin_count(sp))
6320                      WRITE(numout,*) 'Local outflowgrid :', outflow_grid(sp,1:basin_count(sp))
6321                      WRITE(numout,*) 'outflow_grid :', inp
6322                      WRITE(numout,*) 'Coodinates outflow : (lon,lat) = ', lalo_g(inp,2), lalo_g(inp,1)
6323                      WRITE(numout,*) 'Contfrac : = ', contfrac(inp)
6324                      WRITE(numout,*) 'Outflow Basin ID :', basin_id(inp,1:basin_count(inp))
6325                      WRITE(numout,*) 'Outflow hierarchies :', basin_hierarchy(inp,1:basin_count(inp))
6326                      WRITE(numout,*) 'Outflow basin_flowdir :', basin_flowdir(inp,1:basin_count(inp))
6327                      WRITE(numout,*) 'Explored options +1 :', dp1, bp1, outdp1
6328                      WRITE(numout,*) 'Explored +1 Basin ID :', basin_id(dp1,1:basin_count(dp1))
6329                      WRITE(numout,*) 'Explored +1 hierarchies :', basin_hierarchy(dp1,1:basin_count(dp1))
6330                      WRITE(numout,*) 'Explored +1 basin_flowdir :', basin_flowdir(dp1,1:basin_count(dp1))
6331                      WRITE(numout,*) 'Explored options -1 :', dm1, bm1, outdm1
6332                      WRITE(numout,*) 'Explored -1 Basin ID :', basin_id(dm1,1:basin_count(dm1))
6333                      WRITE(numout,*) 'Explored -1 hierarchies :', basin_hierarchy(dm1,1:basin_count(dm1))
6334                      WRITE(numout,*) 'Explored -1 basin_flowdir :', basin_flowdir(dm1,1:basin_count(dm1))
6335                      WRITE(numout,*) '****************************'
6336                      CALL FLUSH(numout)
6337                   ENDIF
6338                   IF ( contfrac(sp) > 0.01 ) THEN
6339                      error2=.TRUE.
6340                      EXIT
6341                   ENDIF
6342                ENDIF
6343                !
6344             ENDIF
6345             !
6346             ! Now that we know where we want the water to flow to we write the
6347             ! the information in the right fields.
6348             !
6349             IF ( dop .GT. 0 .AND. dop .NE. undef_int ) THEN
6350                outflow_grid(sp,sb) = dop
6351                outflow_basin(sp,sb) = bop
6352                inflow_number(dop,bop) =  inflow_number(dop,bop) + 1
6353                IF ( inflow_number(dop,bop) .LE. nbvmax ) THEN
6354                   inflow_grid(dop, bop, inflow_number(dop,bop)) = sp
6355                   inflow_basin(dop, bop, inflow_number(dop,bop)) = sb
6356                ELSE
6357                   error3=.TRUE.
6358                   EXIT
6359                ENDIF
6360                !
6361             ELSE
6362                outflow_grid(sp,sb) = -2
6363                outflow_basin(sp,sb) = undef_int
6364             ENDIF
6365             !
6366          ENDIF
6367          !
6368          !
6369          ! If we still have not found anything then we have to check that there is not a basin
6370          ! within the same grid box which has a lower hierarchy.
6371          !
6372          !
6373          IF ( outflow_grid(sp,sb) .GT. 0 .AND. outflow_basin(sp,sb) .EQ. undef_int &
6374               & .AND. basin_flowdir(sp,sb) .GT. 0) THEN
6375             !
6376             
6377             IF (check) &
6378                  WRITE(numout,*) 'There is no reason to here, this part of the code should be dead :', sp,sb
6379             !
6380             DO sbl=1,basin_count(sp)
6381                !
6382                ! Three conditions are needed to let the water flow into another basin of the
6383                ! same grid :
6384                ! - another basin than the current one
6385                ! - same ID
6386                ! - of lower hierarchy.
6387                !
6388                IF ( (sbl .NE. sb) .AND. (basin_id(sp,sbl) .EQ. bid)&
6389                     & .AND. (basin_hierarchy(sp,sb) .GT. basin_hierarchy(sp,sbl)) ) THEN
6390                   outflow_basin(sp,sb) = sbl
6391                   inflow_number(sp,sbl) =  inflow_number(sp,sbl) + 1
6392                   IF ( inflow_number(sp,sbl) .LE. nbvmax ) THEN
6393                      IF ( sp .EQ. 42 .AND. sbl .EQ. 1) THEN
6394                         IF (check) &
6395                              WRITE(numout,*) 'ADD INFLOW (3):', sp, sb
6396                      ENDIF
6397                      inflow_grid(sp, sbl, inflow_number(sp,sbl)) = sp
6398                      inflow_basin(sp, sbl, inflow_number(sp,sbl)) = sb
6399                   ELSE
6400                      error4=.TRUE.
6401                      EXIT
6402                   ENDIF
6403                ENDIF
6404             ENDDO
6405          ENDIF
6406          !
6407          ! Ok that is it, we give up :-)
6408          !
6409          IF ( outflow_grid(sp,sb) .GT. 0 .AND. outflow_basin(sp,sb) .EQ. undef_int &
6410               & .AND. basin_flowdir(sp,sb) .GT. 0) THEN
6411             !
6412             error5=.TRUE.
6413             EXIT
6414          ENDIF
6415       ENDDO
6416       !
6417    ENDDO
6418    IF (error1) THEN
6419       WRITE(numout,*) " routing_linkup : bop .LT. undef_int",bop
6420       CALL ipslerr_p(3,'routing_linkup', &
6421            "bop .LT. undef_int",'Increase nbvmax','stop routing_linkup')
6422    ENDIF
6423    IF (error2) THEN
6424       CALL ipslerr_p(3,'routing_linkup', &
6425            &      'In the routine which make connections between the basins and ensure global coherence,', & 
6426            &      'there is a problem with outflow linkup without any valid direction. Try with check=.TRUE.', &
6427            &      '(Perhaps there is a problem with the grid.)')
6428    ENDIF
6429    IF (error3) THEN
6430       WRITE(numout,*) " routing_linkup : dop .GT. 0 .AND. dop .NE. undef_int",dop
6431       CALL ipslerr_p(3,'routing_linkup', &
6432            "dop .GT. 0 .AND. dop .NE. undef_int",'Increase nbvmax. Try with check=.TRUE.','stop routing_linkup')
6433    ENDIF
6434    IF (error4) THEN
6435       WRITE(numout,*) " routing_linkup : (sbl .NE. sb) .AND. (basin_id(sp,sbl) .EQ. bid) ", & 
6436            &  " .AND. (basin_hierarchy(sp,sb) .GT. basin_hierarchy(sp,sbl))",sbl,sb,basin_id(sp,sbl),bid, & 
6437            &  basin_hierarchy(sp,sb),basin_hierarchy(sp,sbl)
6438       CALL ipslerr_p(3,'routing_linkup', &
6439            "(sbl .NE. sb) .AND. (basin_id(sp,sbl) .EQ. bid) .AND. (basin_hierarchy(sp,sb) .GT. basin_hierarchy(sp,sbl))" &
6440            ,'Increase nbvmax. Try with check=.TRUE.','stop routing_linkup')
6441    ENDIF
6442    IF (error5) THEN
6443       WRITE(numout,*) 'We could not find the basin into which we need to flow'
6444       WRITE(numout,*) 'Grid point ', sp, ' and basin ', sb
6445       WRITE(numout,*) 'Explored neighbours :', dm1, dp1 
6446       WRITE(numout,*) 'Outflow direction :', basin_flowdir(sp,sb)
6447       WRITE(numout,*) 'Outlfow grid :', outflow_grid(sp,sb)
6448       WRITE(numout,*) 'Outlfow basin :',outflow_basin(sp,sb)
6449       WRITE(numout,*) 'basin ID:',basin_id(sp,sb)
6450       WRITE(numout,*) 'Hierarchy :', basin_hierarchy(sp,sb)
6451       CALL ipslerr_p(3,'routing_linkup', &
6452            "We could not find the basin into which we need to flow",'Try with check=.TRUE.','stop routing_linkup')
6453    ENDIF
6454    !
6455    ! Check for each outflow basin that it exists
6456    !
6457    DO sp=1,nbpt
6458       DO sb=1,basin_count(sp)
6459          !
6460          inp = outflow_grid(sp,sb)
6461          sbl = outflow_basin(sp,sb)
6462          IF ( inp .GE. 0 ) THEN
6463             IF ( basin_count(inp) .LT. sbl ) THEN
6464                WRITE(numout,*) 'point :', sp, ' basin :', sb
6465                WRITE(numout,*) 'Flows into point :', inp, ' basin :', sbl
6466                WRITE(numout,*) 'But it flows into now here as basin count = ', basin_count(inp)
6467                CALL ipslerr_p(3,'routing_linkup','Problem with outflow','','')
6468             ENDIF
6469          ENDIF
6470       ENDDO
6471    ENDDO
6472    !
6473  END SUBROUTINE routing_linkup
6474  !
6475!! ================================================================================================================================
6476!! SUBROUTINE   : routing_fetch
6477!!
6478!>\BRIEF        This subroutine computes the fetch of each basin. This means that for each basin we
6479!!               will know how much area is upstream. It will help decide how to procede with the
6480!!               the truncation later and allow to set correctly in outflow_grid the distinction
6481!!               between coastal and river flow.
6482!!
6483!! DESCRIPTION (definitions, functional, design, flags) : None
6484!!
6485!! RECENT CHANGE(S): None
6486!!
6487!! MAIN OUTPUT VARIABLE(S):
6488!!
6489!! REFERENCES   : None
6490!!
6491!! FLOWCHART    : None
6492!! \n
6493!_ ================================================================================================================================
6494
6495SUBROUTINE routing_fetch(nbpt, resolution, contfrac, nwbas, basin_count, basin_area, basin_id,&
6496       & outflow_grid, outflow_basin, fetch_basin)
6497    !
6498    IMPLICIT NONE
6499    !
6500!! INPUT VARIABLES
6501    INTEGER(i_std), INTENT(in)                           :: nbpt          !! Domain size  (unitless)
6502    !
6503    REAL(r_std), DIMENSION(nbpt,2), INTENT(in)           :: resolution    !! The size of each grid box in X and Y (m)
6504    REAL(r_std), DIMENSION(nbpt), INTENT(in)             :: contfrac      !! Fraction of land in each grid box (unitless;0-1)
6505    !
6506    INTEGER(i_std)                                       :: nwbas         !!
6507    INTEGER(i_std), DIMENSION(nbpt), INTENT(in)          :: basin_count   !!
6508    REAL(r_std), DIMENSION(nbpt,nwbas), INTENT(inout)    :: basin_area    !!
6509    INTEGER(i_std), DIMENSION(nbpt,nwbas), INTENT(in)    :: basin_id      !!
6510    INTEGER(i_std), DIMENSION(nbpt,nwbas), INTENT(inout) :: outflow_grid  !! Type of outflow on the grid box (unitless)
6511    INTEGER(i_std), DIMENSION(nbpt,nwbas), INTENT(in)    :: outflow_basin !!
6512!
6513!! OUTPUT VARIABLES
6514    REAL(r_std), DIMENSION(nbpt,nwbas), INTENT(out)      :: fetch_basin   !!
6515    !
6516!! LOCAL VARIABLES
6517    INTEGER(i_std)                                        :: ib, ij, ff(1), it, itt, igrif, ibasf, nboutflow !! Indices (unitless)
6518    REAL(r_std)                                           :: contarea     !!
6519    REAL(r_std)                                           :: totbasins    !!
6520    REAL(r_std), DIMENSION(nbpt*nbvmax)                   :: tmp_area     !!
6521    INTEGER(i_std), DIMENSION(nbpt*nbvmax,2)              :: tmpindex     !!
6522
6523!_ ================================================================================================================================
6524    !
6525    !
6526    ! Normalize the area of all basins
6527    !
6528    DO ib=1,nbpt
6529       !
6530       totbasins = SUM(basin_area(ib,1:basin_count(ib)))
6531       ! Check if we are at the poles (resolution(ib,1) = 0
6532       IF ( resolution(ib,1) == 0 ) THEN
6533          ! Hack to approximate the pole cell area by a circle
6534          contarea = pi*resolution(ib,2)*resolution(ib,2)*contfrac(ib)
6535       ELSE
6536          contarea = resolution(ib,1)*resolution(ib,2)*contfrac(ib)
6537       ENDIF
6538       !
6539       DO ij=1,basin_count(ib)
6540          basin_area(ib,ij) = basin_area(ib,ij)/totbasins*contarea
6541       ENDDO
6542       !
6543    ENDDO
6544    WRITE(numout,*) 'Normalization done'
6545    !
6546    ! Compute the area upstream of each basin
6547    !
6548    fetch_basin(:,:) = zero
6549    !
6550    !
6551    DO ib=1,nbpt
6552       !
6553       DO ij=1,basin_count(ib)
6554          !
6555          fetch_basin(ib, ij) = fetch_basin(ib, ij) + basin_area(ib,ij)
6556          !
6557          igrif = outflow_grid(ib,ij)
6558          ibasf = outflow_basin(ib,ij)
6559          !
6560          itt = 0
6561          DO WHILE (igrif .GT. 0)
6562             fetch_basin(igrif,ibasf) =  fetch_basin(igrif,ibasf) + basin_area(ib, ij)
6563             it = outflow_grid(igrif, ibasf)
6564             ibasf = outflow_basin(igrif, ibasf)
6565             igrif = it
6566             itt = itt + 1
6567             IF ( itt .GT. 500) THEN
6568                WRITE(numout,&
6569                     "('Grid ',I5, ' and basin ',I5, 'did not converge after iteration ',I5)") ib, ij, itt
6570                WRITE(numout,*) 'Basin ID :', basin_id(igrif,ibasf)
6571                WRITE(numout,&
6572                     "('We are stuck with the flow into grid ',I5,' and basin ',I5)") igrif, ibasf
6573                WRITE(numout,*) "Coordinates : ", lalo_g(igrif,2), lalo_g(igrif,1)
6574                IF ( itt .GT. 510) THEN
6575                   CALL ipslerr_p(3,'routing_fetch','Problem...','','')
6576                ENDIF
6577             ENDIF
6578          ENDDO
6579          !
6580       ENDDO
6581       !
6582    ENDDO
6583    !
6584    WRITE(numout,*) 'The smallest FETCH :', MINVAL(fetch_basin)
6585    WRITE(numout,*) 'The largest FETCH :', MAXVAL(fetch_basin)
6586    !
6587    ! Now we set for the 'num_largest' largest basins the outflow condition as stream flow
6588    ! (i.e. outflow_grid = -1) and all other outflow basins are set to coastal flow
6589    ! (i.e. outflow_grid = -2). The return flow is not touched.
6590    !
6591    nboutflow = 0
6592    !
6593    DO ib=1,nbpt
6594       !
6595       DO ij=1,basin_count(ib)
6596          !
6597          ! We do not need any more the river flow flag as we are going to reset it.
6598          !
6599          IF ( outflow_grid(ib,ij) .EQ. -1) THEN
6600             outflow_grid(ib,ij) = -2
6601          ENDIF
6602          !
6603          IF ( outflow_grid(ib,ij) .EQ. -2) THEN
6604             !
6605             nboutflow = nboutflow + 1
6606             tmp_area(nboutflow) = fetch_basin(ib,ij)
6607             tmpindex(nboutflow,1) = ib
6608             tmpindex(nboutflow,2) = ij
6609             !
6610          ENDIF
6611          !
6612       ENDDO
6613    ENDDO
6614    !
6615    DO ib=1, num_largest
6616       ff = MAXLOC(tmp_area(1:nboutflow))
6617       outflow_grid(tmpindex(ff(1),1), tmpindex(ff(1),2)) = -1
6618       tmp_area(ff(1)) = zero
6619    ENDDO
6620    !
6621  END SUBROUTINE routing_fetch
6622  !
6623!! ================================================================================================================================
6624!! SUBROUTINE   : routing_truncate
6625!!
6626!>\BRIEF         This subroutine reduces the number of basins per grid to the value chosen by the user.
6627!!               It also computes the final field which will be used to route the water at the
6628!!               requested truncation. 
6629!!
6630!! DESCRIPTION (definitions, functional, design, flags) :
6631!! Truncate if needed and find the path closest to the high resolution data.
6632!!
6633!! The algorithm :
6634!!
6635!! We only go through this procedure only as many times as there are basins to take out at most.
6636!! This is important as it allows the simplifications to spread from one grid to the other.
6637!! The for each step of the iteration and at each grid point we check the following options for
6638!! simplifying the pathways of water :
6639!! 1) If the basin of a grid flows into another basin of the same grid. Kill the one which only
6640!!    served as a transition
6641!! 2) If in one grid box we have a number of basins which flow into the ocean as coastal flow.
6642!!    We kill the smallest one and put into the largest basin. There is no need to manage many
6643!!    basins going into the ocean as coastal flows.
6644!! 3) If we have streams run in parallel from one gird box to the others (that is these are
6645!!    different basins) we will put the smaller one in the larger one. This may hapen at any
6646!!    level of the flow but in theory it should propagate downstream.
6647!! 4) If we have two basins with the same ID but flow into different grid boxes we sacrifice
6648!!    the smallest one and route it through the largest.
6649!!
6650!! Obviously if any of the options find something then we skip the rest and take out the basin.:\n
6651!!
6652!! RECENT CHANGE(S): None
6653!!
6654!! MAIN OUTPUT VARIABLE(S):
6655!!
6656!! REFERENCES   : None
6657!!
6658!! FLOWCHART    : None
6659!! \n
6660!_ ================================================================================================================================
6661
6662SUBROUTINE routing_truncate(nbpt, resolution, contfrac, nwbas, basin_count, basin_area, basin_topoind,&
6663       & fetch_basin, basin_id, basin_flowdir, outflow_grid, outflow_basin, inflow_number,&
6664       & inflow_grid, inflow_basin)
6665    !
6666    IMPLICIT NONE
6667    !
6668!! PARAMETERS
6669    INTEGER(i_std), PARAMETER                       :: pickmax = 200  !!
6670
6671!! INPUT VARIABLES
6672    INTEGER(i_std)                                  :: nbpt           !! Domain size  (unitless)
6673    !
6674    REAL(r_std), DIMENSION(nbpt,2)                  :: resolution     !! The size of each grid box in X and Y (m)
6675    REAL(r_std), DIMENSION(nbpt), INTENT(in)        :: contfrac       !! Fraction of land in each grid box (unitless;0-1)
6676    !
6677    INTEGER(i_std)                                  :: nwbas          !!
6678    INTEGER(i_std), DIMENSION(nbpt)                 :: basin_count    !!
6679    INTEGER(i_std), DIMENSION(nbpt,nwbas)           :: basin_id       !!
6680    INTEGER(i_std), DIMENSION(nbpt,nwbas)           :: basin_flowdir  !! Water flow directions in the basin (unitless)
6681    REAL(r_std), DIMENSION(nbpt,nwbas)              :: basin_area     !!
6682    REAL(r_std), DIMENSION(nbpt,nwbas)              :: basin_topoind  !! Topographic index of the residence time for a basin (m)
6683    REAL(r_std), DIMENSION(nbpt,nwbas)              :: fetch_basin    !!
6684    INTEGER(i_std), DIMENSION(nbpt,nwbas)           :: outflow_grid   !! Type of outflow on the grid box (unitless)
6685    INTEGER(i_std), DIMENSION(nbpt,nwbas)           :: outflow_basin  !!
6686    INTEGER(i_std), DIMENSION(nbpt,nwbas)           :: inflow_number  !!
6687    INTEGER(i_std), DIMENSION(nbpt,nwbas,nwbas)     :: inflow_basin   !!
6688    INTEGER(i_std), DIMENSION(nbpt,nwbas,nwbas)     :: inflow_grid    !!
6689    !
6690!! LOCAL VARIABLES
6691    INTEGER(i_std)                                  :: ib, ij, ibf, ijf, igrif, ibasf, cnt, pold, bold, ff(2) !! Indices (unitless)
6692    INTEGER(i_std)                                  :: ii, kbas, sbas, ik, iter, ibt, obj !! Indices (unitless)
6693    REAL(r_std), DIMENSION(nbpt,nbasmax)            :: floflo         !!
6694    REAL(r_std), DIMENSION(nbpt)                    :: gridarea       !!
6695    REAL(r_std), DIMENSION(nbpt)                    :: gridbasinarea  !!
6696    REAL(r_std)                                     :: ratio          !!
6697    INTEGER(i_std), DIMENSION(pickmax,2)            :: largest_basins !!
6698    INTEGER(i_std), DIMENSION(pickmax)              :: tmp_ids        !!
6699    INTEGER(i_std)                                  :: multbas        !!
6700    INTEGER(i_std)                                  :: iml(1)         !! X resolution of the high resolution grid
6701    INTEGER(i_std), DIMENSION(pickmax)              :: multbas_sz     !!
6702    REAL(r_std), DIMENSION(pickmax)                 :: tmp_area       !!
6703    INTEGER(i_std), DIMENSION(pickmax,pickmax)      :: multbas_list   !!
6704    !
6705    INTEGER(i_std)                                  :: nbtruncate     !!
6706    INTEGER(i_std), SAVE, ALLOCATABLE, DIMENSION(:) :: indextrunc     !!
6707!$OMP THREADPRIVATE(indextrunc)
6708
6709!_ ================================================================================================================================
6710    !
6711    !
6712    IF ( .NOT. ALLOCATED(indextrunc)) THEN
6713       ALLOCATE(indextrunc(nbpt))
6714    ENDIF
6715    !
6716    ! We have to go through the grid as least as often as we have to reduce the number of basins
6717    ! For good measure we add 3 more passages.
6718    !
6719    !
6720    DO iter = 1, MAXVAL(basin_count) - nbasmax +3
6721       !
6722       ! Get the points over which we wish to truncate
6723       !
6724       nbtruncate = 0
6725       DO ib = 1, nbpt
6726          IF ( basin_count(ib) .GT. nbasmax ) THEN
6727             nbtruncate = nbtruncate + 1
6728             indextrunc(nbtruncate) = ib
6729          ENDIF
6730       ENDDO
6731       !
6732       ! Go through the basins which need to be truncated.       
6733       !
6734       DO ibt=1,nbtruncate
6735          !
6736          ib = indextrunc(ibt)
6737          !
6738          ! Check if we have basin which flows into a basin in the same grid
6739          ! kbas = basin we will have to kill
6740          ! sbas = basin which takes over kbas
6741          !
6742          kbas = 0
6743          sbas = 0
6744          !
6745          ! 1) Can we find a basin which flows into a basin of the same grid ?
6746          !
6747          DO ij=1,basin_count(ib)
6748             DO ii=1,basin_count(ib)
6749                IF ( outflow_grid(ib,ii) .EQ. ib .AND. outflow_basin(ib, ii) .EQ. ij .AND. kbas*sbas .NE. 0) THEN
6750                   kbas = ii
6751                   sbas = ij
6752                ENDIF
6753             ENDDO
6754          ENDDO
6755          !
6756          ! 2) Merge two basins which flow into the ocean as coastal or return flow
6757          ! (outflow_grid = -2 or -3). Well obviously only if we have more than 1 and
6758          ! have not found anything yet!
6759          !
6760          IF ( (COUNT(outflow_grid(ib,1:basin_count(ib)) .EQ. -2) .GT. 1 .OR.&
6761               & COUNT(outflow_grid(ib,1:basin_count(ib)) .EQ. -3) .GT. 1) .AND.&
6762               & kbas*sbas .EQ. 0) THEN
6763             !
6764             multbas = 0
6765             multbas_sz(:) = 0
6766             !
6767             IF ( COUNT(outflow_grid(ib,1:basin_count(ib)) .EQ. -2) .GT. 1 ) THEN
6768                obj = -2
6769             ELSE
6770                obj = -3
6771             ENDIF
6772             !
6773             ! First we get the list of all basins which go out as coastal or return flow (obj)
6774             !
6775             DO ij=1,basin_count(ib)
6776                IF ( outflow_grid(ib,ij) .EQ. obj ) THEN
6777                   multbas = multbas + 1
6778                   multbas_sz(multbas) = ij
6779                   tmp_area(multbas) = fetch_basin(ib,ij)
6780                ENDIF
6781             ENDDO
6782             !
6783             ! Now the take the smallest to be transfered to the largest
6784             !
6785             iml = MAXLOC(tmp_area(1:multbas), MASK = tmp_area(1:multbas) .GT. zero)
6786             sbas = multbas_sz(iml(1))
6787             iml = MINLOC(tmp_area(1:multbas), MASK = tmp_area(1:multbas) .GT. zero)
6788             kbas = multbas_sz(iml(1))
6789             !
6790          ENDIF
6791          !
6792          !   3) If we have basins flowing into the same grid but different basins then we put them
6793          !   together. Obviously we first work with the grid which has most streams running into it
6794          !   and putting the smallest in the largests catchments.
6795          !
6796          IF ( kbas*sbas .EQ. 0) THEN
6797             !
6798             tmp_ids(1:basin_count(ib)) = outflow_grid(ib,1:basin_count(ib))
6799             multbas = 0
6800             multbas_sz(:) = 0
6801             !
6802             ! First obtain the list of basins which flow into the same basin
6803             !
6804             DO ij=1,basin_count(ib)
6805                IF ( outflow_grid(ib,ij) .GT. 0 .AND.&
6806                     & COUNT(tmp_ids(1:basin_count(ib)) .EQ. outflow_grid(ib,ij)) .GT. 1) THEN
6807                   multbas = multbas + 1
6808                   DO ii=1,basin_count(ib)
6809                      IF ( tmp_ids(ii) .EQ. outflow_grid(ib,ij)) THEN
6810                         multbas_sz(multbas) = multbas_sz(multbas) + 1
6811                         multbas_list(multbas,multbas_sz(multbas)) = ii
6812                         tmp_ids(ii) = -99
6813                      ENDIF
6814                   ENDDO
6815                ELSE
6816                   tmp_ids(ij) = -99
6817                ENDIF
6818             ENDDO
6819             !
6820             ! Did we come up with any basins to deal with this way ?
6821             !
6822             IF ( multbas .GT. 0 ) THEN
6823                !
6824                iml = MAXLOC(multbas_sz(1:multbas))
6825                ik = iml(1)
6826                !
6827                ! Take the smallest and largest of these basins !
6828                !
6829                DO ii=1,multbas_sz(ik)
6830                   tmp_area(ii) = fetch_basin(ib, multbas_list(ik,ii))
6831                ENDDO
6832                !
6833                iml = MAXLOC(tmp_area(1:multbas_sz(ik)), MASK = tmp_area(1:multbas_sz(ik)) .GT. zero)
6834                sbas = multbas_list(ik,iml(1))
6835                iml = MINLOC(tmp_area(1:multbas_sz(ik)), MASK = tmp_area(1:multbas_sz(ik)) .GT. zero)
6836                kbas = multbas_list(ik,iml(1))
6837                !
6838             ENDIF
6839             !
6840          ENDIF
6841          !
6842          !   4) If we have twice the same basin we put them together even if they flow into different
6843          !   directions. If one of them goes to the ocean it takes the advantage.
6844          !
6845          IF ( kbas*sbas .EQ. 0) THEN
6846             !
6847             tmp_ids(1:basin_count(ib)) = basin_id(ib,1:basin_count(ib))
6848             multbas = 0
6849             multbas_sz(:) = 0
6850             !
6851             ! First obtain the list of basins which have sub-basins in this grid box.
6852             ! (these are identified by their IDs)
6853             !
6854             DO ij=1,basin_count(ib)
6855                IF ( COUNT(tmp_ids(1:basin_count(ib)) .EQ. basin_id(ib,ij)) .GT. 1) THEN
6856                   multbas = multbas + 1
6857                   DO ii=1,basin_count(ib)
6858                      IF ( tmp_ids(ii) .EQ. basin_id(ib,ij)) THEN
6859                         multbas_sz(multbas) = multbas_sz(multbas) + 1
6860                         multbas_list(multbas,multbas_sz(multbas)) = ii
6861                         tmp_ids(ii) = -99
6862                      ENDIF
6863                   ENDDO
6864                ELSE
6865                   tmp_ids(ij) = -99
6866                ENDIF
6867             ENDDO
6868             !
6869             ! We are going to work on the basin with the largest number of sub-basins.
6870             ! (IF we have a basin which has subbasins !)
6871             !
6872             IF ( multbas .GT. 0 ) THEN
6873                !
6874                iml = MAXLOC(multbas_sz(1:multbas))
6875                ik = iml(1)
6876                !
6877                ! If one of the basins goes to the ocean then it is going to have the priority
6878                !
6879                tmp_area(:) = zero
6880                IF ( COUNT(outflow_grid(ib,multbas_list(ik,1:multbas_sz(ik))) .LT. 0) .GT. 0) THEN
6881                   DO ii=1,multbas_sz(ik)
6882                      IF ( outflow_grid(ib,multbas_list(ik,ii)) .LT. 0 .AND. sbas .EQ. 0 ) THEN
6883                         sbas = multbas_list(ik,ii)
6884                      ELSE
6885                         tmp_area(ii) = fetch_basin(ib, multbas_list(ik,ii))
6886                      ENDIF
6887                   ENDDO
6888                   ! take the smallest of the subbasins
6889                   iml = MINLOC(tmp_area(1:multbas_sz(ik)), MASK = tmp_area(1:multbas_sz(ik)) .GT. zero)
6890                   kbas = multbas_list(ik,iml(1))
6891                ELSE
6892                   !
6893                   ! Else we take simply the largest and smallest
6894                   !
6895                   DO ii=1,multbas_sz(ik)
6896                      tmp_area(ii) = fetch_basin(ib, multbas_list(ik,ii))
6897                   ENDDO
6898                   iml = MAXLOC(tmp_area(1:multbas_sz(ik)), MASK = tmp_area(1:multbas_sz(ik)) .GT. zero)
6899                   sbas = multbas_list(ik,iml(1))
6900                   iml = MINLOC(tmp_area(1:multbas_sz(ik)), MASK = tmp_area(1:multbas_sz(ik)) .GT. zero)
6901                   kbas = multbas_list(ik,iml(1))
6902                   !
6903                ENDIF
6904                !
6905                !
6906             ENDIF
6907          ENDIF
6908          !
6909          !
6910          !
6911          ! Then we call routing_killbas to clean up the basins in this grid
6912          !
6913          IF ( kbas .GT. 0 .AND. sbas .GT. 0 ) THEN
6914             CALL routing_killbas(nbpt, ib, kbas, sbas, nwbas, basin_count, basin_area, basin_topoind,&
6915                  & fetch_basin, basin_id, basin_flowdir, outflow_grid, outflow_basin, inflow_number,&
6916                  & inflow_grid, inflow_basin)
6917          ENDIF
6918          !
6919       ENDDO
6920       !
6921       !     
6922    ENDDO
6923    !
6924    ! If there are any grids left with too many basins we need to take out the big hammer !
6925    ! We will only do it if this represents less than 5% of all points.
6926    !
6927    IF ( COUNT(basin_count .GT. nbasmax) .GT. 0 ) THEN
6928       !
6929       !
6930       IF ( COUNT(basin_count .GT. nbasmax)/nbpt*100 .GT. 5 ) THEN
6931          WRITE(numout,*) 'We have ', COUNT(basin_count .GT. nbasmax)/nbpt*100, '% of all points which do not yet'
6932          WRITE(numout,*) 'have the right trunctaction. That is too much to apply a brutal method'
6933          DO ib = 1, nbpt
6934             IF ( basin_count(ib) .GT. nbasmax ) THEN
6935                !
6936                WRITE(numout,*) 'We did not find a basin which could be supressed. We will'
6937                WRITE(numout,*) 'not be able to reduce the truncation in grid ', ib
6938                DO ij=1,basin_count(ib)
6939                   WRITE(numout,*) 'grid, basin nb and id :', ib, ij, basin_id(ib,ij)
6940                   WRITE(numout,*) 'Outflow grid and basin ->', outflow_grid(ib,ij), outflow_basin(ib, ij)
6941                ENDDO
6942             ENDIF
6943          ENDDO
6944          CALL ipslerr_p(3,'routing_truncate','No basin found which could be supressed.','','')
6945       ELSE
6946          !
6947          !
6948          DO ib = 1,nbpt
6949             DO WHILE ( basin_count(ib) .GT. nbasmax )
6950                !
6951                IF (printlev>=3) WRITE(numout,*) 'HAMMER, ib, basin_count :', ib, basin_count(ib)
6952                !
6953                ! Here we simply put the smallest basins into the largest ones. It is really a brute force
6954                ! method but it will only be applied if everything has failed.
6955                !
6956                DO ii = 1,basin_count(ib)
6957                   tmp_area(ii) = fetch_basin(ib, ii)
6958                ENDDO
6959                !
6960                iml = MAXLOC(tmp_area(1:basin_count(ib)), MASK = tmp_area(1:basin_count(ib)) .GT. 0.)
6961                sbas =iml(1)
6962                iml = MINLOC(tmp_area(1:basin_count(ib)), MASK = tmp_area(1:basin_count(ib)) .GT. 0.)
6963                kbas = iml(1)
6964                !
6965                IF ( kbas .GT. 0 .AND. sbas .GT. 0 ) THEN
6966                   CALL routing_killbas(nbpt, ib, kbas, sbas, nwbas, basin_count, basin_area, basin_topoind,&
6967                        & fetch_basin, basin_id, basin_flowdir, outflow_grid, outflow_basin, inflow_number,&
6968                        & inflow_grid, inflow_basin)
6969                ENDIF
6970             ENDDO
6971          ENDDO
6972          !
6973       ENDIF
6974       !
6975       !
6976    ENDIF
6977    !
6978    ! Now that we have reached the right truncation (resolution) we will start
6979    ! to produce the variables we will use to route the water.
6980    !
6981    DO ib=1,nbpt
6982       !
6983       ! For non existing basins the route_tobasin variable is put to zero. This will allow us
6984       ! to pick up the number of basin afterwards.
6985       !
6986       route_togrid(ib,:) = ib
6987       route_tobasin(ib,:) = 0
6988       routing_area(ib,:) = zero
6989       !
6990    ENDDO
6991    !
6992    ! Transfer the info into the definitive variables
6993    !
6994    DO ib=1,nbpt
6995       DO ij=1,basin_count(ib)
6996          routing_area(ib,ij) = basin_area(ib,ij)
6997          topo_resid(ib,ij) = basin_topoind(ib,ij)
6998          global_basinid(ib,ij) = basin_id(ib,ij)
6999          route_togrid(ib,ij) = outflow_grid(ib,ij)
7000          route_tobasin(ib,ij) = outflow_basin(ib,ij)
7001       ENDDO
7002    ENDDO
7003    !
7004    !
7005    ! Set the new convention for the outflow conditions
7006    ! Now it is based in the outflow basin and the outflow grid will
7007    ! be the same as the current.
7008    ! returnflow to the grid : nbasmax + 1
7009    ! coastal flow           : nbasmax + 2
7010    ! river outflow          : nbasmax + 3
7011    !
7012    ! Here we put everything here in coastal flow. It is later where we will
7013    ! put the largest basins into river outflow.
7014    !
7015    DO ib=1,nbpt
7016       DO ij=1,basin_count(ib)
7017          ! River flows
7018          IF ( route_togrid(ib,ij) .EQ. -1 ) THEN
7019             route_tobasin(ib,ij) = nbasmax + 2
7020             route_togrid(ib,ij) = ib
7021          ! Coastal flows
7022          ELSE IF ( route_togrid(ib,ij) .EQ. -2 ) THEN
7023             route_tobasin(ib,ij) = nbasmax + 2
7024             route_togrid(ib,ij) = ib
7025          ! Return flow
7026          ELSE IF ( route_togrid(ib,ij) .EQ. -3 ) THEN
7027             route_tobasin(ib,ij) = nbasmax + 1
7028             route_togrid(ib,ij) = ib
7029          ENDIF
7030       ENDDO
7031    ENDDO
7032    !
7033    ! A second check on the data. Just make sure that each basin flows somewhere.
7034    !
7035    DO ib=1,nbpt
7036       DO ij=1,basin_count(ib)
7037          ibf = route_togrid(ib,ij)
7038          ijf = route_tobasin(ib,ij)
7039          IF ( ijf .GT. basin_count(ibf) .AND.  ijf .LE. nbasmax) THEN
7040             WRITE(numout,*) 'Second check'
7041             WRITE(numout,*) 'point :', ib, ' basin :', ij
7042             WRITE(numout,*) 'Flows into point :', ibf, ' basin :', ijf
7043             WRITE(numout,*) 'But it flows into now here as basin count = ', basin_count(ibf)
7044             CALL ipslerr_p(3,'routing_truncate','Problem with routing..','','')
7045          ENDIF
7046       ENDDO
7047    ENDDO
7048    !
7049    ! Verify areas of the continents
7050    !
7051    floflo(:,:) = zero
7052    ! if we are at the poles : resolution(:,1) = 0
7053    WHERE (resolution(:,1) == 0)
7054        ! compute grid area as the circle of radius resolution(:,2)
7055        gridarea(:) = contfrac(:)*pi*resolution(:,2)*resolution(:,2)
7056    ELSEWHERE
7057        gridarea(:) = contfrac(:)*resolution(:,1)*resolution(:,2)
7058    END WHERE
7059    DO ib=1,nbpt
7060       gridbasinarea(ib) = SUM(routing_area(ib,:))
7061    ENDDO
7062    !
7063    DO ib=1,nbpt
7064       DO ij=1,basin_count(ib)
7065          cnt = 0
7066          igrif = ib
7067          ibasf = ij
7068          DO WHILE (ibasf .LE. nbasmax .AND. cnt .LT. nbasmax*nbpt)
7069             cnt = cnt + 1
7070             pold = igrif
7071             bold = ibasf
7072             igrif = route_togrid(pold, bold)
7073             ibasf = route_tobasin(pold, bold)
7074             IF ( ibasf .GT. basin_count(igrif)  .AND.  ibasf .LE. nbasmax) THEN
7075                WRITE(numout,*) 'We should not be here as the basin flows into the pampa'
7076                WRITE(numout,*) 'Last correct point :', pold, bold
7077                WRITE(numout,*) 'It pointed to in the new variables :', route_togrid(pold, bold),route_tobasin(pold, bold) 
7078                WRITE(numout,*) 'The old variables gave :', outflow_grid(pold, bold), outflow_basin(pold, bold) 
7079                WRITE(numout,*) 'Where we ended up :', igrif,ibasf
7080                CALL ipslerr_p(3,'routing_truncate','Problem with routing..','','')
7081             ENDIF
7082          ENDDO
7083          !
7084          IF ( ibasf .GT. nbasmax ) THEN
7085             floflo(igrif,bold) = floflo(igrif,bold) + routing_area(ib,ij)
7086          ELSE
7087             WRITE(numout,*) 'The flow did not end up in the ocean or in the grid cell.'
7088             WRITE(numout,*) 'For grid ', ib, ' and basin ', ij
7089             WRITE(numout,*) 'The last grid was ', igrif, ' and basin ', ibasf
7090             CALL ipslerr_p(3,'routing_truncate','Problem with routing..','','')
7091          ENDIF
7092       ENDDO
7093    ENDDO
7094    !
7095    DO ib=1,nbpt
7096       IF ( gridbasinarea(ib) > zero ) THEN
7097          ratio = gridarea(ib)/gridbasinarea(ib)
7098          routing_area(ib,:) = routing_area(ib,:)*ratio
7099       ELSE
7100          WRITE(numout,*) 'gridbasinarea(ib) <= zero. We should stop here :', ib
7101       ENDIF
7102    ENDDO
7103    !
7104    WRITE(numout,*) 'Sum of area of all outflow areas :',SUM(routing_area)
7105    WRITE(numout,*) 'Surface of all continents :', SUM(gridarea)
7106    !
7107    ! Redo the the distinction between river outflow and coastal flow. We can not
7108    ! take into account the return flow points.
7109    !
7110    ibf = 0
7111    DO ib=1, pickmax
7112       ff = MAXLOC(floflo)
7113       ! tdo - To take into account rivers that do not flow to the oceans
7114       IF ( route_tobasin(ff(1), ff(2)) .GT. nbasmax ) THEN
7115!       IF ( route_tobasin(ff(1), ff(2)) .EQ. nbasmax + 2) THEN
7116          ibf = ibf + 1
7117          largest_basins(ibf,:) = ff(:)
7118       ENDIF
7119       floflo(ff(1), ff(2)) = zero
7120    ENDDO
7121    !
7122    ! Put the largest basins into river flows.
7123    !
7124    IF ( ibf .LT.  num_largest) THEN
7125       WRITE(numout,*) 'Not enough basins to choose the ',  num_largest, 'largest'
7126       CALL ipslerr_p(3,'routing_truncate','Not enough basins','','')
7127    ENDIF
7128    !
7129    !
7130    !
7131    DO ib=1, num_largest
7132       route_tobasin(largest_basins(ib,1),largest_basins(ib,2)) = nbasmax + 3
7133    ENDDO
7134    !
7135    WRITE(numout,*) 'NUMBER OF RIVERS :', COUNT(route_tobasin .GE. nbasmax + 3)
7136    !
7137  END SUBROUTINE  routing_truncate
7138  !
7139!! ================================================================================================================================
7140!! SUBROUTINE   : routing_killbas
7141!!
7142!>\BRIEF        The aim of this subroutine is to kill a basin (that is put into another larger one).
7143!!              When we do this we need to be careful and change all associated variables. 
7144!!
7145!! DESCRIPTION (definitions, functional, design, flags) : None
7146!!
7147!! RECENT CHANGE(S): None
7148!!
7149!! MAIN OUTPUT VARIABLE(S):
7150!!
7151!! REFERENCES   : None
7152!!
7153!! FLOWCHART    : None
7154!! \n
7155!_ ================================================================================================================================
7156
7157SUBROUTINE routing_killbas(nbpt, ib, tokill, totakeover, nwbas, basin_count, basin_area, basin_topoind,&
7158       & fetch_basin, basin_id, basin_flowdir, outflow_grid, outflow_basin, inflow_number,&
7159       & inflow_grid, inflow_basin)
7160    !
7161    !
7162    IMPLICIT NONE
7163    !
7164    INTEGER(i_std)                              :: tokill        !!
7165    INTEGER(i_std)                              :: totakeover    !!
7166    INTEGER(i_std)                              :: nbpt          !! Domain size  (unitless)
7167    INTEGER(i_std)                              :: ib            !! Current basin (unitless)
7168    !
7169    INTEGER(i_std)                              :: nwbas         !!
7170    INTEGER(i_std), DIMENSION(nbpt)             :: basin_count   !!
7171    INTEGER(i_std), DIMENSION(nbpt,nwbas)       :: basin_id      !!
7172    INTEGER(i_std), DIMENSION(nbpt,nwbas)       :: basin_flowdir !! Water flow directions in the basin (unitless)
7173    REAL(r_std), DIMENSION(nbpt,nwbas)          :: basin_area    !!
7174    REAL(r_std), DIMENSION(nbpt,nwbas)          :: basin_topoind !! Topographic index of the residence time for a basin (m)
7175    REAL(r_std), DIMENSION(nbpt,nwbas)          :: fetch_basin   !!
7176    INTEGER(i_std), DIMENSION(nbpt,nwbas)       :: outflow_grid  !! Type of outflow on the grid box (unitless)
7177    INTEGER(i_std), DIMENSION(nbpt,nwbas)       :: outflow_basin !!
7178    INTEGER(i_std), DIMENSION(nbpt,nwbas)       :: inflow_number !!
7179    INTEGER(i_std), DIMENSION(nbpt,nwbas,nwbas) :: inflow_basin  !!
7180    INTEGER(i_std), DIMENSION(nbpt,nwbas,nwbas) :: inflow_grid   !!
7181    !
7182!! LOCAL VARIABLES
7183    INTEGER(i_std)                              :: inf, ibs, ing, inb, ibasf, igrif, it !! Indices (unitless)
7184    LOGICAL                                     :: doshift       !! (true/false)
7185
7186!_ ================================================================================================================================
7187    !
7188    ! Update the information needed in the basin "totakeover"
7189    ! For the moment only area
7190    !
7191    IF (printlev>=3) THEN
7192       WRITE(numout,*) 'KILL BASIN :', ib, tokill, totakeover, basin_id(ib,tokill), basin_id(ib,totakeover)
7193    END IF
7194    !
7195    basin_area(ib, totakeover) = basin_area(ib, totakeover) +  basin_area(ib, tokill)
7196    basin_topoind(ib, totakeover) = (basin_topoind(ib, totakeover) + basin_topoind(ib, tokill))/2.0
7197    !
7198    ! Add the fetch of the basin will kill to the one which gets the water
7199    !
7200    fetch_basin(ib, totakeover) = fetch_basin(ib, totakeover) + fetch_basin(ib, tokill)
7201    igrif = outflow_grid(ib,totakeover)
7202    ibasf = outflow_basin(ib,totakeover)
7203    !
7204    inf = 0
7205    DO WHILE (igrif .GT. 0)
7206       fetch_basin(igrif,ibasf) =  fetch_basin(igrif,ibasf) + fetch_basin(ib, tokill) 
7207       it = outflow_grid(igrif, ibasf)
7208       ibasf = outflow_basin(igrif, ibasf)
7209       igrif = it
7210       inf = inf + 1
7211    ENDDO
7212    !
7213    ! Take out the basin we have just rerouted from the fetch of the basins in which it used to flow.
7214    !
7215    igrif = outflow_grid(ib,tokill)
7216    ibasf = outflow_basin(ib,tokill)
7217    !
7218    DO WHILE (igrif .GT. 0)
7219       fetch_basin(igrif,ibasf) =  fetch_basin(igrif,ibasf) - fetch_basin(ib, tokill)
7220       it = outflow_grid(igrif, ibasf)
7221       ibasf = outflow_basin(igrif, ibasf)
7222       igrif = it
7223    ENDDO   
7224    !
7225    !  Redirect the flows which went into the basin to be killed before we change everything
7226    !
7227    DO inf = 1, inflow_number(ib, tokill)
7228       outflow_basin(inflow_grid(ib, tokill, inf), inflow_basin(ib, tokill, inf)) = totakeover
7229       inflow_number(ib, totakeover) = inflow_number(ib, totakeover) + 1
7230       inflow_grid(ib, totakeover,  inflow_number(ib, totakeover)) = inflow_grid(ib, tokill, inf)
7231       inflow_basin(ib, totakeover,  inflow_number(ib, totakeover)) = inflow_basin(ib, tokill, inf)
7232    ENDDO
7233    !
7234    ! Take out the basin to be killed from the list of inflow basins of the downstream basin
7235    ! (In case the basin does not flow into an ocean or lake)
7236    !
7237    IF ( outflow_grid(ib,tokill) .GT. 0) THEN
7238       !
7239       ing = outflow_grid(ib, tokill)
7240       inb = outflow_basin(ib, tokill)
7241       doshift = .FALSE.
7242       !
7243       DO inf = 1, inflow_number(ing, inb)
7244          IF ( doshift ) THEN
7245             inflow_grid(ing, inb, inf-1) = inflow_grid(ing, inb, inf)
7246             inflow_basin(ing, inb, inf-1) = inflow_basin(ing, inb, inf)
7247          ENDIF
7248          IF ( inflow_grid(ing, inb, inf) .EQ. ib .AND. inflow_basin(ing, inb, inf) .EQ. tokill) THEN
7249             doshift = .TRUE.
7250          ENDIF
7251       ENDDO
7252       !
7253       ! This is only to allow for the last check
7254       !
7255       inf = inflow_number(ing, inb)
7256       IF ( inflow_grid(ing, inb, inf) .EQ. ib .AND. inflow_basin(ing, inb, inf) .EQ. tokill) THEN
7257          doshift = .TRUE.
7258       ENDIF
7259       !
7260       IF ( .NOT. doshift ) THEN
7261          WRITE(numout,*) 'Strange we did not find the basin to kill in the downstream basin'
7262          CALL ipslerr_p(3,'routing_killbas','Basin not found','','')
7263       ENDIF
7264       inflow_number(ing, inb) = inflow_number(ing, inb) - 1
7265       
7266    ENDIF
7267    !
7268    ! Now remove from the arrays the information of basin "tokill"
7269    !
7270    basin_id(ib, tokill:basin_count(ib)-1) = basin_id(ib, tokill+1:basin_count(ib))
7271    basin_flowdir(ib, tokill:basin_count(ib)-1) = basin_flowdir(ib, tokill+1:basin_count(ib))
7272    basin_area(ib, tokill:basin_count(ib)-1) = basin_area(ib, tokill+1:basin_count(ib))
7273    basin_area(ib, basin_count(ib):nwbas) = zero
7274    basin_topoind(ib, tokill:basin_count(ib)-1) = basin_topoind(ib, tokill+1:basin_count(ib))
7275    basin_topoind(ib, basin_count(ib):nwbas) = zero
7276    fetch_basin(ib, tokill:basin_count(ib)-1) = fetch_basin(ib, tokill+1:basin_count(ib))
7277    fetch_basin(ib, basin_count(ib):nwbas) = zero
7278    !
7279    ! Before we remove the information from the outflow fields we have to correct the corresponding inflow fields
7280    ! of the grids into which the flow goes
7281    !
7282    DO ibs = tokill+1,basin_count(ib)
7283       ing = outflow_grid(ib, ibs)
7284       inb = outflow_basin(ib, ibs)
7285       IF ( ing .GT. 0 ) THEN
7286          DO inf = 1, inflow_number(ing, inb)
7287             IF ( inflow_grid(ing,inb,inf) .EQ. ib .AND. inflow_basin(ing,inb,inf) .EQ. ibs) THEN
7288                inflow_basin(ing,inb,inf) = ibs - 1
7289             ENDIF
7290          ENDDO
7291       ENDIF
7292    ENDDO
7293    outflow_grid(ib, tokill:basin_count(ib)-1) = outflow_grid(ib, tokill+1:basin_count(ib))
7294    outflow_basin(ib, tokill:basin_count(ib)-1) = outflow_basin(ib, tokill+1:basin_count(ib))
7295    !
7296    ! Basins which moved down also need to redirect their incoming flows.
7297    !
7298    DO ibs=tokill+1, basin_count(ib)
7299       DO inf = 1, inflow_number(ib, ibs)
7300          outflow_basin(inflow_grid(ib, ibs, inf), inflow_basin(ib, ibs, inf)) = ibs-1
7301       ENDDO
7302    ENDDO
7303    !
7304    ! Shift the inflow basins
7305    !
7306    DO it = tokill+1,basin_count(ib)
7307       inflow_grid(ib, it-1, 1:inflow_number(ib,it)) =  inflow_grid(ib, it, 1:inflow_number(ib,it))
7308       inflow_basin(ib, it-1, 1:inflow_number(ib,it)) =  inflow_basin(ib, it, 1:inflow_number(ib,it))
7309       inflow_number(ib,it-1) = inflow_number(ib,it)
7310    ENDDO
7311    !
7312    basin_count(ib) = basin_count(ib) - 1
7313    !
7314  END SUBROUTINE routing_killbas 
7315  !
7316!! ================================================================================================================================
7317!! SUBROUTINE   : routing_names
7318!!
7319!>\BRIEF         This subroutine lists the name of the largest basins which are explicitly listed in the basin
7320!!               description file used by ORCHIDEE.
7321!!
7322!! DESCRIPTION (definitions, functional, design, flags) : None
7323!!
7324!! RECENT CHANGE(S): None
7325!!
7326!! MAIN OUTPUT VARIABLE(S):
7327!!
7328!! REFERENCES   : None
7329!!
7330!! FLOWCHART    : None
7331!! \n
7332!_ ================================================================================================================================
7333
7334SUBROUTINE routing_names(numlar, basin_names)
7335    !
7336    IMPLICIT NONE
7337    !
7338    ! Arguments
7339    !
7340    INTEGER(i_std), INTENT(in)             :: numlar              !!
7341    CHARACTER(LEN=*), INTENT(inout)        :: basin_names(numlar) !! Name of the basins (unitless)
7342!! PARAMETERS
7343    INTEGER(i_std), PARAMETER              :: listleng=349        !!
7344    !
7345!! LOCAL VARIABLES
7346    INTEGER(i_std)                         :: lenstr, i           !!
7347    CHARACTER(LEN=60), DIMENSION(listleng) :: list_names          !!
7348    CHARACTER(LEN=60)                      :: tmp_str             !!
7349
7350!_ ================================================================================================================================
7351    !
7352
7353    lenstr = LEN(basin_names(1))
7354    !
7355    list_names(1) = "Amazon"
7356    list_names(2) = "Nile"
7357    list_names(3) = "Zaire"
7358    list_names(4) = "Mississippi"
7359    list_names(5) = "Amur"
7360    list_names(6) = "Parana"
7361    list_names(7) = "Yenisei"
7362    list_names(8) = "Ob"
7363    list_names(9) = "Lena"
7364    list_names(10) = "Niger"
7365    list_names(11) = "Zambezi"
7366    list_names(12) = "Erg Iguidi (Sahara)"
7367    list_names(13) = "Chang Jiang (Yangtze)"
7368    list_names(14) = "Mackenzie"
7369    list_names(15) = "Ganges"
7370    list_names(16) = "Chari"
7371    list_names(17) = "Volga"
7372    list_names(18) = "St. Lawrence"
7373    list_names(19) = "Indus"
7374    list_names(20) = "Syr-Darya"
7375    list_names(21) = "Nelson"
7376    list_names(22) = "Orinoco"
7377    list_names(23) = "Murray"
7378    list_names(24) = "Great Artesian Basin"
7379    list_names(25) = "Shatt el Arab"
7380    list_names(26) = "Orange"
7381    list_names(27) = "Huang He"
7382    list_names(28) = "Yukon"
7383    list_names(29) = "Senegal"
7384    list_names(30) = "Chott Jerid"
7385    list_names(31) = "Jubba"
7386    list_names(32) = "Colorado (Ari)"
7387    list_names(33) = "Rio Grande (US)"
7388    list_names(34) = "Danube"
7389    list_names(35) = "Mekong"
7390    list_names(36) = "Tocantins"
7391    list_names(37) = "Wadi al Farigh"
7392    list_names(38) = "Tarim"
7393    list_names(39) = "Columbia"
7394    list_names(40) = "Komadugu Yobe (Tchad)"
7395    list_names(41) = "Kolyma"
7396    list_names(42) = "Sao Francisco"
7397    list_names(43) = "Amu-Darya"
7398    list_names(44) = "GHAASBasin51"
7399    list_names(45) = "Dnepr"
7400    list_names(46) = "GHAASBasin61"
7401    list_names(47) = "Don"
7402    list_names(48) = "Colorado (Arg)"
7403    list_names(49) = "Limpopo"
7404    list_names(50) = "GHAASBasin50"
7405    list_names(51) = "Zhujiang"
7406    list_names(52) = "Irrawaddy"
7407    list_names(53) = "Volta"
7408    list_names(54) = "GHAASBasin54"
7409    list_names(55) = "Farah"
7410    list_names(56) = "Khatanga"
7411    list_names(57) = "Dvina"
7412    list_names(58) = "Urugay"
7413    list_names(59) = "Qarqan"
7414    list_names(60) = "GHAASBasin75"
7415    list_names(61) = "Parnaiba"
7416    list_names(62) = "GHAASBasin73"
7417    list_names(63) = "Indigirka"
7418    list_names(64) = "Churchill (Hud)"
7419    list_names(65) = "Godavari"
7420    list_names(66) = "Pur - Taz"
7421    list_names(67) = "Pechora"
7422    list_names(68) = "Baker"
7423    list_names(69) = "Ural"
7424    list_names(70) = "Neva"
7425    list_names(71) = "Liao"
7426    list_names(72) = "Salween"
7427    list_names(73) = "GHAASBasin73"
7428    list_names(74) = "Jordan"
7429    list_names(75) = "GHAASBasin78"
7430    list_names(76) = "Magdalena"
7431    list_names(77) = "Krishna"
7432    list_names(78) = "Salado"
7433    list_names(79) = "Fraser"
7434    list_names(80) = "Hai Ho"
7435    list_names(81) = "Huai"
7436    list_names(82) = "Yana"
7437    list_names(83) = "GHAASBasin95"
7438    list_names(84) = "GHAASBasin105"
7439    list_names(85) = "Kura"
7440    list_names(86) = "Olenek"
7441    list_names(87) = "Ogooue"
7442    list_names(88) = "Taymyr"
7443    list_names(89) = "Negro Arg"
7444    list_names(90) = "Chubut"
7445    list_names(91) = "GHAASBasin91"
7446    list_names(92) = "GHAASBasin122"
7447    list_names(93) = "GHAASBasin120"
7448    list_names(94) = "Sacramento"
7449    list_names(95) = "Fitzroy West"
7450    list_names(96) = "Grande de Santiago"
7451    list_names(97) = "Rufiji"
7452    list_names(98) = "Wisla"
7453    list_names(99) = "GHAASBasin47"
7454    list_names(100) = "GHAASBasin127"
7455    list_names(101) = "Hong"
7456    list_names(102) = "GHAASBasin97"
7457    list_names(103) = "Swan-Avon"
7458    list_names(104) = "Rhine"
7459    list_names(105) = "Cuanza"
7460    list_names(106) = "GHAASBasin106"
7461    list_names(107) = "GHAASBasin142"
7462    list_names(108) = "Roviuna"
7463    list_names(109) = "Essequibo"
7464    list_names(110) = "Elbe"
7465    list_names(111) = "Koksoak"
7466    list_names(112) = "Chao Phraya"
7467    list_names(113) = "Brahmani"
7468    list_names(114) = "GHAASBasin165"
7469    list_names(115) = "Pyasina"
7470    list_names(116) = "Fitzroy East"
7471    list_names(117) = "GHAASBasin173"
7472    list_names(118) = "Albany"
7473    list_names(119) = "Sanaga"
7474    list_names(120) = "GHAASBasin120"
7475    list_names(121) = "GHAASBasin178"
7476    list_names(122) = "GHAASBasin148"
7477    list_names(123) = "Brazos (Tex)"
7478    list_names(124) = "GHAASBasin124"
7479    list_names(125) = "Alabama"
7480    list_names(126) = "GHAASBasin174"
7481    list_names(127) = "GHAASBasin179"
7482    list_names(128) = "Balsas"
7483    list_names(129) = "GHAASBasin172"
7484    list_names(130) = "Burdekin"
7485    list_names(131) = "Colorado (Texas)"
7486    list_names(132) = "GHAASBasin150"
7487    list_names(133) = "Odra"
7488    list_names(134) = "Loire"
7489    list_names(135) = "GHAASBasin98"
7490    list_names(136) = "Galana"
7491    list_names(137) = "Kuskowin"
7492    list_names(138) = "Moose"
7493    list_names(139) = "Narmada"
7494    list_names(140) = "GHAASBasin140"
7495    list_names(141) = "GHAASBasin141"
7496    list_names(142) = "Flinders"
7497    list_names(143) = "Kizil Irmak"
7498    list_names(144) = "GHAASBasin144"
7499    list_names(145) = "Save"
7500    list_names(146) = "Roper"
7501    list_names(147) = "Churchill (Atlantic)"
7502    list_names(148) = "GHAASBasin148"
7503    list_names(149) = "Victoria"
7504    list_names(150) = "Back"
7505    list_names(151) = "Bandama"
7506    list_names(152) = "Severn (Can)"
7507    list_names(153) = "Po"
7508    list_names(154) = "GHAASBasin154"
7509    list_names(155) = "GHAASBasin155"
7510    list_names(156) = "GHAASBasin156"
7511    list_names(157) = "Rhone"
7512    list_names(158) = "Tana (Ken)"
7513    list_names(159) = "La Grande"
7514    list_names(160) = "GHAASBasin160"
7515    list_names(161) = "Cunene"
7516    list_names(162) = "Douro"
7517    list_names(163) = "GHAASBasin163"
7518    list_names(164) = "Nemanus"
7519    list_names(165) = "GHAASBasin165"
7520    list_names(166) = "Anabar"
7521    list_names(167) = "Hayes"
7522    list_names(168) = "Mearim"
7523    list_names(169) = "GHAASBasin169"
7524    list_names(170) = "Panuco"
7525    list_names(171) = "GHAASBasin171"
7526    list_names(172) = "Doce"
7527    list_names(173) = "Gasgoyne"
7528    list_names(174) = "GHAASBasin174"
7529    list_names(175) = "GHAASBasin175"
7530    list_names(176) = "Ashburton"
7531    list_names(177) = "GHAASBasin177"
7532    list_names(178) = "Peel"
7533    list_names(179) = "Daugava"
7534    list_names(180) = "GHAASBasin180"
7535    list_names(181) = "Ebro"
7536    list_names(182) = "Comoe"
7537    list_names(183) = "Jacui"
7538    list_names(184) = "GHAASBasin184"
7539    list_names(185) = "Kapuas"
7540    list_names(186) = "GHAASBasin186"
7541    list_names(187) = "Penzhina"
7542    list_names(188) = "Cauweri"
7543    list_names(189) = "GHAASBasin189"
7544    list_names(190) = "Mamberamo"
7545    list_names(191) = "Sepik"
7546    list_names(192) = "GHAASBasin192"
7547    list_names(193) = "Sassandra"
7548    list_names(194) = "GHAASBasin194"
7549    list_names(195) = "GHAASBasin195"
7550    list_names(196) = "Nottaway"
7551    list_names(197) = "Barito"
7552    list_names(198) = "GHAASBasin198"
7553    list_names(199) = "Seine"
7554    list_names(200) = "Tejo"
7555    list_names(201) = "GHAASBasin201"
7556    list_names(202) = "Gambia"
7557    list_names(203) = "Susquehanna"
7558    list_names(204) = "Dnestr"
7559    list_names(205) = "Murchinson"
7560    list_names(206) = "Deseado"
7561    list_names(207) = "Mitchell"
7562    list_names(208) = "Mahakam"
7563    list_names(209) = "GHAASBasin209"
7564    list_names(210) = "Pangani"
7565    list_names(211) = "GHAASBasin211"
7566    list_names(212) = "GHAASBasin212"
7567    list_names(213) = "GHAASBasin213"
7568    list_names(214) = "GHAASBasin214"
7569    list_names(215) = "GHAASBasin215"
7570    list_names(216) = "Bug"
7571    list_names(217) = "GHAASBasin217"
7572    list_names(218) = "Usumacinta"
7573    list_names(219) = "Jequitinhonha"
7574    list_names(220) = "GHAASBasin220"
7575    list_names(221) = "Corantijn"
7576    list_names(222) = "Fuchun Jiang"
7577    list_names(223) = "Copper"
7578    list_names(224) = "Tapti"
7579    list_names(225) = "Menjiang"
7580    list_names(226) = "Karun"
7581    list_names(227) = "Mezen"
7582    list_names(228) = "Guadiana"
7583    list_names(229) = "Maroni"
7584    list_names(230) = "GHAASBasin230"
7585    list_names(231) = "Uda"
7586    list_names(232) = "GHAASBasin232"
7587    list_names(233) = "Kuban"
7588    list_names(234) = "Colville"
7589    list_names(235) = "Thaane"
7590    list_names(236) = "Alazeya"
7591    list_names(237) = "Paraiba do Sul"
7592    list_names(238) = "GHAASBasin238"
7593    list_names(239) = "Fortesque"
7594    list_names(240) = "GHAASBasin240"
7595    list_names(241) = "GHAASBasin241"
7596    list_names(242) = "Winisk"
7597    list_names(243) = "GHAASBasin243"
7598    list_names(244) = "GHAASBasin244"
7599    list_names(245) = "Ikopa"
7600    list_names(246) = "Gilbert"
7601    list_names(247) = "Kouilou"
7602    list_names(248) = "Fly"
7603    list_names(249) = "GHAASBasin249"
7604    list_names(250) = "GHAASBasin250"
7605    list_names(251) = "GHAASBasin251"
7606    list_names(252) = "Mangoky"
7607    list_names(253) = "Damodar"
7608    list_names(254) = "Onega"
7609    list_names(255) = "Moulouya"
7610    list_names(256) = "GHAASBasin256"
7611    list_names(257) = "Ord"
7612    list_names(258) = "GHAASBasin258"
7613    list_names(259) = "GHAASBasin259"
7614    list_names(260) = "GHAASBasin260"
7615    list_names(261) = "GHAASBasin261"
7616    list_names(262) = "Narva"
7617    list_names(263) = "GHAASBasin263"
7618    list_names(264) = "Seal"
7619    list_names(265) = "Cheliff"
7620    list_names(266) = "Garonne"
7621    list_names(267) = "Rupert"
7622    list_names(268) = "GHAASBasin268"
7623    list_names(269) = "Brahmani"
7624    list_names(270) = "Sakarya"
7625    list_names(271) = "Gourits"
7626    list_names(272) = "Sittang"
7627    list_names(273) = "Rajang"
7628    list_names(274) = "Evros"
7629    list_names(275) = "Appalachicola"
7630    list_names(276) = "Attawapiskat"
7631    list_names(277) = "Lurio"
7632    list_names(278) = "Daly"
7633    list_names(279) = "Penner"
7634    list_names(280) = "GHAASBasin280"
7635    list_names(281) = "GHAASBasin281"
7636    list_names(282) = "Guadalquivir"
7637    list_names(283) = "Nadym"
7638    list_names(284) = "GHAASBasin284"
7639    list_names(285) = "Saint John"
7640    list_names(286) = "GHAASBasin286"
7641    list_names(287) = "Cross"
7642    list_names(288) = "Omoloy"
7643    list_names(289) = "Oueme"
7644    list_names(290) = "GHAASBasin290"
7645    list_names(291) = "Gota"
7646    list_names(292) = "Nueces"
7647    list_names(293) = "Stikine"
7648    list_names(294) = "Yalu"
7649    list_names(295) = "Arnaud"
7650    list_names(296) = "GHAASBasin296"
7651    list_names(297) = "Jequitinhonha"
7652    list_names(298) = "Kamchatka"
7653    list_names(299) = "GHAASBasin299"
7654    list_names(300) = "Grijalva"
7655    list_names(301) = "GHAASBasin301"
7656    list_names(302) = "Kemijoki"
7657    list_names(303) = "Olifants"
7658    list_names(304) = "GHAASBasin304"
7659    list_names(305) = "Tsiribihina"
7660    list_names(306) = "Coppermine"
7661    list_names(307) = "GHAASBasin307"
7662    list_names(308) = "GHAASBasin308"
7663    list_names(309) = "Kovda"
7664    list_names(310) = "Trinity"
7665    list_names(311) = "Glama"
7666    list_names(312) = "GHAASBasin312"
7667    list_names(313) = "Luan"
7668    list_names(314) = "Leichhardt"
7669    list_names(315) = "GHAASBasin315"
7670    list_names(316) = "Gurupi"
7671    list_names(317) = "GR Baleine"
7672    list_names(318) = "Aux Feuilles"
7673    list_names(319) = "GHAASBasin319"
7674    list_names(320) = "Weser"
7675    list_names(321) = "GHAASBasin321"
7676    list_names(322) = "GHAASBasin322"
7677    list_names(323) = "Yesil"
7678    list_names(324) = "Incomati"
7679    list_names(325) = "GHAASBasin325"
7680    list_names(326) = "GHAASBasin326"
7681    list_names(327) = "Pungoe"
7682    list_names(328) = "GHAASBasin328"
7683    list_names(329) = "Meuse"
7684    list_names(330) = "Eastmain"
7685    list_names(331) = "Araguari"
7686    list_names(332) = "Hudson"
7687    list_names(333) = "GHAASBasin333"
7688    list_names(334) = "GHAASBasin334"
7689    list_names(335) = "GHAASBasin335"
7690    list_names(336) = "GHAASBasin336"
7691    list_names(337) = "Kobuk"
7692    list_names(338) = "Altamaha"
7693    list_names(339) = "GHAASBasin339"
7694    list_names(340) = "Mand"
7695    list_names(341) = "Santee"
7696    list_names(342) = "GHAASBasin342"
7697    list_names(343) = "GHAASBasin343"
7698    list_names(344) = "GHAASBasin344"
7699    list_names(345) = "Hari"
7700    list_names(346) = "GHAASBasin346"
7701    list_names(347) = "Wami"
7702    list_names(348) = "GHAASBasin348"
7703    list_names(349) = "GHAASBasin349"
7704    !
7705    basin_names(:) = '    '
7706    !
7707    DO i=1,numlar
7708       tmp_str = list_names(i)
7709       basin_names(i) = tmp_str(1:MIN(lenstr,LEN_TRIM(tmp_str)))
7710    ENDDO
7711    !
7712  END SUBROUTINE routing_names
7713  !
7714!! ================================================================================================================================
7715!! SUBROUTINE   : routing_irrigmap
7716!!
7717!>\BRIEF         This  subroutine interpolates the 0.5x0.5 degree based map of irrigated areas to the resolution of the model.
7718!!
7719!! DESCRIPTION (definitions, functional, design, flags) : None
7720!!
7721!! RECENT CHANGE(S): None
7722!!
7723!! MAIN OUTPUT VARIABLE(S):
7724!!
7725!! REFERENCES   : None
7726!!
7727!! FLOWCHART    : None
7728!! \n
7729!_ ================================================================================================================================
7730
7731SUBROUTINE routing_irrigmap (nbpt, index, lalo, neighbours, resolution, contfrac, &
7732       &                       init_irrig, irrigated, init_flood, floodplains, init_swamp, swamp, hist_id, hist2_id)
7733    !
7734    IMPLICIT NONE
7735    !
7736!! PARAMETERS
7737    INTEGER(i_std), PARAMETER                      :: ilake = 1             !! Number of type of lakes area (unitless)
7738    INTEGER(i_std), PARAMETER                      :: idam = 2              !! Number of type of dams area (unitless)
7739    INTEGER(i_std), PARAMETER                      :: iflood = 3            !! Number of type of floodplains area (unitless)
7740    INTEGER(i_std), PARAMETER                      :: iswamp = 4            !! Number of type of swamps area (unitless)
7741    INTEGER(i_std), PARAMETER                      :: isal = 5              !! Number of type of salines area (unitless)
7742    INTEGER(i_std), PARAMETER                      :: ipond = 6             !! Number of type of ponds area (unitless)
7743    INTEGER(i_std), PARAMETER                      :: ntype = 6             !! Number of types of flooded surfaces (unitless)
7744
7745!! INPUT VARIABLES
7746    INTEGER(i_std), INTENT(in)                     :: nbpt                  !! Domain size  (unitless)
7747    INTEGER(i_std), INTENT(in)                     :: index(nbpt)           !! Index on the global map.
7748    REAL(r_std), INTENT(in)                        :: lalo(nbpt,2)          !! Vector of latitude and longitudes (beware of the order !)
7749    INTEGER(i_std), INTENT(in)                     :: neighbours(nbpt,NbNeighb)!! Vector of neighbours for each grid point
7750    REAL(r_std), INTENT(in)                        :: resolution(nbpt,2)    !! The size of each grid box in X and Y (m)
7751    REAL(r_std), INTENT(in)                        :: contfrac(nbpt)        !! Fraction of land in each grid box (unitless;0-1)
7752    INTEGER(i_std), INTENT(in)                     :: hist_id               !! Access to history file (unitless)
7753    INTEGER(i_std), INTENT(in)                     :: hist2_id              !! Access to history file 2 (unitless)
7754    LOGICAL, INTENT(in)                            :: init_irrig            !! Logical to initialize the irrigation (true/false)
7755    LOGICAL, INTENT(in)                            :: init_flood            !! Logical to initialize the floodplains (true/false)
7756    LOGICAL, INTENT(in)                            :: init_swamp            !! Logical to initialize the swamps (true/false)
7757    !
7758!! OUTPUT VARIABLES
7759    REAL(r_std), INTENT(out)                       :: irrigated(:)          !! Irrigated surface in each grid box (m^2)
7760    REAL(r_std), INTENT(out)                       :: floodplains(:)        !! Surface which can be inundated in each grid box (m^2)
7761    REAL(r_std), INTENT(out)                       :: swamp(:)              !! Surface which can be swamp in each grid box (m^2)
7762    !
7763!! LOCAL VARIABLES
7764    ! Interpolation variables
7765    !
7766    INTEGER(i_std)                                 :: nbpmax, nix, njx, fopt !!
7767    CHARACTER(LEN=30)                              :: callsign              !!
7768    REAL(r_std), ALLOCATABLE, DIMENSION(:,:,:)     :: resol_lu              !! Resolution read on the map
7769    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:)    :: mask                  !! Mask to exclude some points (unitless)
7770    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)       :: irrsub_area           !! Area on the fine grid (m^2)
7771    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:,:)  :: irrsub_index          !! Indices of the points we need on the fine grid (unitless)
7772    INTEGER                                        :: ALLOC_ERR             !!
7773    LOGICAL                                        :: ok_interpol = .FALSE. !! Flag for interpolation (true/false)
7774    !
7775    CHARACTER(LEN=80)                              :: filename              !! Name of the netcdf file (unitless)
7776    INTEGER(i_std)                                 :: iml, jml, lml, tml, fid, ib, ip, jp, itype !! Indices (unitless)
7777    REAL(r_std)                                    :: lev(1), date, dt, coslat !!
7778    INTEGER(i_std)                                 :: itau(1)               !!
7779    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)       :: latrel                !! Latitude
7780    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)       :: lonrel                !! Longitude
7781    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)       :: irrigated_frac        !! Irrigated fraction of the grid box (unitless;0-1)
7782    REAL(r_std), ALLOCATABLE, DIMENSION(:,:,:)     :: flood_fracmax         !! Maximal flooded fraction of the grid box (unitless;0-1)
7783    REAL(r_std)                                    :: area_irrig            !! Irrigated surface in the grid box (m^2)
7784    REAL(r_std)                                    :: area_flood(ntype)     !! Flooded surface in the grid box (m^2)
7785    REAL(r_std)                                    :: resolution_1          !! temporary variable
7786!!$    REAL(r_std)                                :: irrigmap(nbpt)
7787!!$    REAL(r_std)                                :: floodmap(nbpt)
7788!!$    REAL(r_std)                                :: swampmap(nbpt)
7789
7790!_ ================================================================================================================================
7791
7792    !
7793    !Config Key   = IRRIGATION_FILE
7794    !Config Desc  = Name of file which contains the map of irrigated areas
7795    !Config Def   = floodplains.nc
7796    !Config If    = DO_IRRIGATION OR DO_FLOODPLAINS
7797    !Config Help  = The name of the file to be opened to read the field
7798    !Config         with the area in m^2 of the area irrigated within each
7799    !Config         0.5 0.5 deg grid box. The map currently used is the one
7800    !Config         developed by the Center for Environmental Systems Research
7801    !Config         in Kassel (1995).
7802    !Config Units = [FILE]
7803    !
7804    filename = 'floodplains.nc'
7805    CALL getin_p('IRRIGATION_FILE',filename)
7806    !
7807    IF (is_root_prc) THEN
7808       CALL flininfo(filename,iml, jml, lml, tml, fid)
7809       CALL flinclo(fid)
7810    ELSE
7811       iml = 0
7812       jml = 0
7813       lml = 0
7814       tml = 0
7815    ENDIF
7816    !
7817    CALL bcast(iml)
7818    CALL bcast(jml)
7819    CALL bcast(lml)
7820    CALL bcast(tml)
7821    !
7822    !
7823    !
7824    ALLOCATE (latrel(iml,jml), STAT=ALLOC_ERR)
7825    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_irrigmap','Pb in allocate for latrel','','')
7826
7827    ALLOCATE (lonrel(iml,jml), STAT=ALLOC_ERR)
7828    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_irrigmap','Pb in allocate for lonrel','','')
7829
7830    ALLOCATE (irrigated_frac(iml,jml), STAT=ALLOC_ERR)
7831    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_irrigmap','Pb in allocate for irrigated_frac','','')
7832
7833    ALLOCATE (flood_fracmax(iml,jml,ntype), STAT=ALLOC_ERR)
7834    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_irrigmap','Pb in allocate for flood_fracmax','','')
7835
7836    IF (is_root_prc) CALL flinopen(filename, .FALSE., iml, jml, lml, lonrel, latrel, lev, tml, itau, date, dt, fid)
7837
7838    CALL bcast(lonrel)
7839    CALL bcast(latrel)
7840    !
7841    IF (is_root_prc) CALL flinget(fid, 'irrig', iml, jml, lml, tml, 1, 1, irrigated_frac)
7842    CALL bcast(irrigated_frac)
7843    IF (is_root_prc) CALL flinget(fid, 'lake', iml, jml, lml, tml, 1, 1, flood_fracmax(:,:,ilake))
7844    IF (is_root_prc) CALL flinget(fid, 'dam', iml, jml, lml, tml, 1, 1, flood_fracmax(:,:,idam))
7845    IF (is_root_prc) CALL flinget(fid, 'flood', iml, jml, lml, tml, 1, 1, flood_fracmax(:,:,iflood))
7846    IF (is_root_prc) CALL flinget(fid, 'swamp', iml, jml, lml, tml, 1, 1, flood_fracmax(:,:,iswamp))
7847    IF (is_root_prc) CALL flinget(fid, 'saline', iml, jml, lml, tml, 1, 1, flood_fracmax(:,:,isal))
7848    IF (is_root_prc) CALL flinget(fid, 'pond', iml, jml, lml, tml, 1, 1, flood_fracmax(:,:,ipond))
7849    CALL bcast(flood_fracmax)
7850    !
7851    IF (is_root_prc) CALL flinclo(fid)
7852    !
7853    ! Set to zero all fraction which are less than 0.5%
7854    !
7855    DO ip=1,iml
7856       DO jp=1,jml
7857          !
7858          IF ( irrigated_frac(ip,jp) .LT. undef_sechiba-un) THEN
7859             irrigated_frac(ip,jp) = irrigated_frac(ip,jp)/100.
7860             IF ( irrigated_frac(ip,jp) < 0.005 ) irrigated_frac(ip,jp) = zero
7861          ENDIF
7862          !
7863          DO itype=1,ntype
7864             IF ( flood_fracmax(ip,jp,itype) .LT. undef_sechiba-1.) THEN
7865                flood_fracmax(ip,jp,itype) = flood_fracmax(ip,jp,itype)/100
7866                IF ( flood_fracmax(ip,jp,itype) < 0.005 )  flood_fracmax(ip,jp,itype) = zero
7867             ENDIF
7868          ENDDO
7869          !
7870       ENDDO
7871    ENDDO
7872   
7873    IF (printlev>=2) THEN
7874       WRITE(numout,*) 'lonrel : ', MAXVAL(lonrel), MINVAL(lonrel)
7875       WRITE(numout,*) 'latrel : ', MAXVAL(latrel), MINVAL(latrel)
7876       WRITE(numout,*) 'irrigated_frac : ', MINVAL(irrigated_frac, MASK=irrigated_frac .GT. 0), &
7877            MAXVAL(irrigated_frac, MASK=irrigated_frac .LT. undef_sechiba)
7878       WRITE(numout,*) 'flood_fracmax : ', MINVAL(flood_fracmax, MASK=flood_fracmax .GT. 0), &
7879            MAXVAL(flood_fracmax, MASK=flood_fracmax .LT. undef_sechiba)
7880    END IF
7881
7882    ! Consider all points a priori
7883    !
7884    ALLOCATE(resol_lu(iml,jml,2), STAT=ALLOC_ERR)
7885    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_irrigmap','Pb in allocate for resol_lu','','')
7886
7887    ALLOCATE(mask(iml,jml), STAT=ALLOC_ERR)
7888    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_irrigmap','Pb in allocate for mask','','')
7889    mask(:,:) = 0
7890
7891    DO ip=1,iml
7892       DO jp=1,jml
7893          !
7894          ! Exclude the points where we are close to the missing value.
7895          !
7896!MG This condition cannot be applied in floodplains/swamps configuration because
7897!   the same mask would be used for the interpolation of irrigation, floodplains and swamps maps.
7898!          IF ( irrigated_frac(ip,jp) < undef_sechiba ) THEN
7899             mask(ip,jp) = 1
7900!          ENDIF
7901          !
7902          ! Resolution in longitude
7903          !
7904          coslat = MAX( COS( latrel(ip,jp) * pi/180. ), mincos )     
7905          IF ( ip .EQ. 1 ) THEN
7906             resol_lu(ip,jp,1) = ABS( lonrel(ip+1,jp) - lonrel(ip,jp) ) * pi/180. * R_Earth * coslat
7907          ELSEIF ( ip .EQ. iml ) THEN
7908             resol_lu(ip,jp,1) = ABS( lonrel(ip,jp) - lonrel(ip-1,jp) ) * pi/180. * R_Earth * coslat
7909          ELSE
7910             resol_lu(ip,jp,1) = ABS( lonrel(ip+1,jp) - lonrel(ip-1,jp) )/2. * pi/180. * R_Earth * coslat
7911          ENDIF
7912          !
7913          ! Resolution in latitude
7914          !
7915          IF ( jp .EQ. 1 ) THEN
7916             resol_lu(ip,jp,2) = ABS( latrel(ip,jp) - latrel(ip,jp+1) ) * pi/180. * R_Earth
7917          ELSEIF ( jp .EQ. jml ) THEN
7918             resol_lu(ip,jp,2) = ABS( latrel(ip,jp-1) - latrel(ip,jp) ) * pi/180. * R_Earth
7919          ELSE
7920             resol_lu(ip,jp,2) =  ABS( latrel(ip,jp-1) - latrel(ip,jp+1) )/2. * pi/180. * R_Earth
7921          ENDIF
7922          !
7923       ENDDO
7924    ENDDO
7925    !
7926    ! The number of maximum vegetation map points in the GCM grid is estimated.
7927    ! Some lmargin is taken.
7928    !
7929    callsign = 'Irrigation map'
7930    ok_interpol = .FALSE.
7931    IF (is_root_prc) THEN
7932       nix=INT(MAXVAL(resolution_g(:,1))/MAXVAL(resol_lu(:,:,1)))+2
7933       njx=INT(MAXVAL(resolution_g(:,2))/MAXVAL(resol_lu(:,:,2)))+2
7934       nbpmax = nix*njx*2
7935       IF (printlev>=1) THEN
7936          WRITE(numout,*) "Projection arrays for ",callsign," : "
7937          WRITE(numout,*) "nbpmax = ",nbpmax, nix, njx
7938       END IF
7939    ENDIF
7940    CALL bcast(nbpmax)
7941
7942    ALLOCATE(irrsub_index(nbpt, nbpmax, 2), STAT=ALLOC_ERR)
7943    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_irrigmap','Pb in allocate for irrsub_index','','')
7944    irrsub_index(:,:,:)=0
7945
7946    ALLOCATE(irrsub_area(nbpt, nbpmax), STAT=ALLOC_ERR)
7947    IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'routing_irrigmap','Pb in allocate for irrsub_area','','')
7948    irrsub_area(:,:)=zero
7949
7950    CALL aggregate_p(nbpt, lalo, neighbours, resolution, contfrac, &
7951         &                iml, jml, lonrel, latrel, mask, callsign, &
7952         &                nbpmax, irrsub_index, irrsub_area, ok_interpol)
7953    !
7954    !
7955    WHERE (irrsub_area < 0) irrsub_area=zero
7956   
7957    ! Test here if not all sub_area are larger than 0 if so, then we need to increase nbpmax
7958    !
7959    DO ib=1,nbpt
7960       !
7961       area_irrig = 0.0
7962       area_flood = 0.0
7963       !
7964       DO fopt=1,COUNT(irrsub_area(ib,:) > zero)
7965          !
7966          ip = irrsub_index(ib, fopt, 1)
7967          jp = irrsub_index(ib, fopt, 2)
7968          !
7969          IF (irrigated_frac(ip,jp) .LT. undef_sechiba-1.) THEN
7970             area_irrig = area_irrig + irrsub_area(ib,fopt)*irrigated_frac(ip,jp)
7971          ENDIF
7972          !
7973          DO itype=1,ntype
7974             IF (flood_fracmax(ip,jp,itype) .LT. undef_sechiba-1.) THEN
7975                area_flood(itype) = area_flood(itype) + irrsub_area(ib,fopt)*flood_fracmax(ip,jp,itype)
7976             ENDIF
7977          ENDDO
7978       ENDDO
7979       !
7980       ! Put the total irrigated and flooded areas in the output variables
7981       !
7982       IF ( init_irrig ) THEN
7983          ! if we are at the poles resolution(ib,1) = 0
7984          IF (resolution(ib,1) == 0) THEN
7985             ! use pi*resolution(ib,2) to get the disc area
7986             resolution_1 = pi*resolution(ib,2)
7987          ELSE
7988             resolution_1 = resolution(ib,1)
7989          END IF
7990          irrigated(ib) = MIN(area_irrig, resolution_1*resolution(ib,2)*contfrac(ib))
7991          IF ( irrigated(ib) < 0 ) THEN
7992             WRITE(numout,*) 'We have a problem here : ', irrigated(ib) 
7993             WRITE(numout,*) 'resolution :', resolution_1, resolution(ib,2)
7994             WRITE(numout,*) area_irrig
7995             CALL ipslerr_p(3,'routing_irrigmap','Problem with irrigated...','','')
7996          ENDIF
7997!!$          ! Compute a diagnostic of the map.
7998!!$          IF(contfrac(ib).GT.zero) THEN
7999!!$             irrigmap (ib) = irrigated(ib) / ( resolution(ib,1)*resolution(ib,2)*contfrac(ib) )
8000!!$          ELSE
8001!!$             irrigmap (ib) = zero
8002!!$          ENDIF
8003          !
8004       ENDIF
8005       !
8006       IF ( init_flood ) THEN
8007          ! if we are at the poles resolution(ib,1) = 0
8008          IF (resolution(ib,1) == 0) THEN 
8009             ! use pi*resolution(ib,2) to get the disc area
8010             resolution_1 = pi*resolution(ib,2)
8011          ELSE
8012             resolution_1 = resolution(ib,1)
8013          END IF
8014          floodplains(ib) = MIN(area_flood(iflood)+area_flood(idam)+area_flood(isal), &
8015               & resolution_1*resolution(ib,2)*contfrac(ib))
8016          IF ( floodplains(ib) < 0 ) THEN
8017             WRITE(numout,*) 'We have a problem here : ', floodplains(ib) 
8018             WRITE(numout,*) 'resolution :', resolution_1, resolution(ib,2)
8019             WRITE(numout,*) area_flood
8020             CALL ipslerr_p(3,'routing_irrigmap','Problem with floodplains..','','')
8021          ENDIF
8022!!$          ! Compute a diagnostic of the map.
8023!!$          IF(contfrac(ib).GT.zero) THEN
8024!!$             floodmap(ib) = floodplains(ib) / ( resolution(ib,1)*resolution(ib,2)*contfrac(ib) )
8025!!$          ELSE
8026!!$             floodmap(ib) = 0.0
8027!!$          ENDIF
8028       ENDIF
8029       !
8030       IF ( init_swamp ) THEN
8031          ! if we are at the poles resolution(ib,1) = 0
8032          IF (resolution(ib,1) == 0) THEN 
8033             ! use pi*resolution(ib,2) to get the disc area
8034             resolution_1 = pi*resolution(ib,2)
8035          ELSE
8036             resolution_1 = resolution(ib,1)
8037          END IF
8038          swamp(ib) = MIN(area_flood(iswamp), resolution_1*resolution(ib,2)*contfrac(ib))
8039          IF ( swamp(ib) < 0 ) THEN
8040             WRITE(numout,*) 'We have a problem here : ', swamp(ib) 
8041             WRITE(numout,*) 'resolution :', resolution_1, resolution(ib,2)
8042             WRITE(numout,*) area_flood
8043             CALL ipslerr_p(3,'routing_irrigmap','Problem with swamp...','','')
8044          ENDIF
8045!!$          ! Compute a diagnostic of the map.
8046!!$          IF(contfrac(ib).GT.zero) THEN
8047!!$             swampmap(ib) = swamp(ib) / ( resolution(ib,1)*resolution(ib,2)*contfrac(ib) )
8048!!$          ELSE
8049!!$             swampmap(ib) = zero
8050!!$          ENDIF
8051       ENDIF
8052       !
8053       !
8054    ENDDO
8055    !
8056    !
8057   
8058    IF (printlev>=1) THEN
8059       IF ( init_irrig ) WRITE(numout,*) "Diagnostics irrigated :", MINVAL(irrigated), MAXVAL(irrigated)
8060       IF ( init_flood ) WRITE(numout,*) "Diagnostics floodplains :", MINVAL(floodplains), MAXVAL(floodplains)
8061       IF ( init_swamp ) WRITE(numout,*) "Diagnostics swamp :", MINVAL(swamp), MAXVAL(swamp)
8062    END IF
8063
8064! No compensation is done for overlapping floodplains, swamp and irrig. At least overlapping will not
8065! happen between floodplains and swamp alone
8066!    IF ( init_irrig .AND. init_flood ) THEN
8067!       DO ib = 1, nbpt
8068!          surp = (floodplains(ib)+swamp(ib)+irrigated(ib)) / (resolution(ib,1)*resolution(ib,2)*contfrac(ib))
8069!          IF ( surp .GT. un ) THEN
8070!             floodplains(ib) = floodplains(ib) / surp
8071!             swamp(ib) = swamp(ib) / surp
8072!             irrigated(ib) = irrigated(ib) / surp
8073!          ENDIF
8074!       ENDDO
8075!    ENDIF
8076    !
8077    DEALLOCATE (irrsub_area)
8078    DEALLOCATE (irrsub_index)
8079    !
8080    DEALLOCATE (mask)
8081    DEALLOCATE (resol_lu)
8082    !
8083    DEALLOCATE (lonrel)
8084    DEALLOCATE (latrel)
8085    !
8086  END SUBROUTINE routing_irrigmap
8087  !
8088!! ================================================================================================================================
8089!! SUBROUTINE   : routing_waterbal
8090!!
8091!>\BRIEF         This subroutine checks the water balance in the routing module.
8092!!
8093!! DESCRIPTION (definitions, functional, design, flags) : None
8094!!
8095!! RECENT CHANGE(S): None
8096!!
8097!! MAIN OUTPUT VARIABLE(S):
8098!!
8099!! REFERENCES   : None
8100!!
8101!! FLOWCHART    : None
8102!! \n
8103!_ ================================================================================================================================
8104
8105SUBROUTINE routing_waterbal(nbpt, reinit, floodout, runoff, drainage, returnflow, &
8106               & reinfiltration, irrigation, riverflow, coastalflow)
8107    !
8108    IMPLICIT NONE
8109    !
8110!! INPUT VARIABLES
8111    INTEGER(i_std), INTENT(in) :: nbpt                 !! Domain size  (unitless)
8112    LOGICAL, INTENT(in)        :: reinit               !! Controls behaviour (true/false)
8113    REAL(r_std), INTENT(in)    :: floodout(nbpt)       !! Grid-point flow out of floodplains (kg/m^2/dt)
8114    REAL(r_std), INTENT(in)    :: runoff(nbpt)         !! Grid-point runoff (kg/m^2/dt)
8115    REAL(r_std), INTENT(in)    :: drainage(nbpt)       !! Grid-point drainage (kg/m^2/dt)
8116    REAL(r_std), INTENT(in)    :: returnflow(nbpt)     !! The water flow from lakes and swamps which returns to the grid box.
8117                                                       !! This water will go back into the hydrol module to allow re-evaporation (kg/m^2/dt)
8118    REAL(r_std), INTENT(in)    :: reinfiltration(nbpt) !! Water flow from ponds and floodplains which returns to the grid box (kg/m^2/dt)
8119    REAL(r_std), INTENT(in)    :: irrigation(nbpt)     !! Irrigation flux. This is the water taken from the reservoirs and beeing put into the upper layers of the soil (kg/m^2/dt)
8120    REAL(r_std), INTENT(in)    :: riverflow(nbpt)      !! Outflow of the major rivers. The flux will be located on the continental grid but this should be a coastal point (kg/dt)
8121    REAL(r_std), INTENT(in)    :: coastalflow(nbpt)    !! Outflow on coastal points by small basins. This is the water which flows in a disperse way into the ocean (kg/dt)
8122    !
8123    ! We sum-up all the water we have in the warious reservoirs
8124    !
8125    REAL(r_std), SAVE          :: totw_flood           !! Sum of all the water amount in the floodplains reservoirs (kg)
8126!$OMP THREADPRIVATE(totw_flood)
8127    REAL(r_std), SAVE          :: totw_stream          !! Sum of all the water amount in the stream reservoirs (kg)
8128!$OMP THREADPRIVATE(totw_stream)
8129    REAL(r_std), SAVE          :: totw_fast            !! Sum of all the water amount in the fast reservoirs (kg)
8130!$OMP THREADPRIVATE(totw_fast)
8131    REAL(r_std), SAVE          :: totw_slow            !! Sum of all the water amount in the slow reservoirs (kg)
8132!$OMP THREADPRIVATE(totw_slow)
8133    REAL(r_std), SAVE          :: totw_lake            !! Sum of all the water amount in the lake reservoirs (kg)
8134!$OMP THREADPRIVATE(totw_lake)
8135    REAL(r_std), SAVE          :: totw_pond            !! Sum of all the water amount in the pond reservoirs (kg)
8136!$OMP THREADPRIVATE(totw_pond)
8137    REAL(r_std), SAVE          :: totw_in              !! Sum of the water flow in to the routing scheme
8138!$OMP THREADPRIVATE(totw_in)
8139    REAL(r_std), SAVE          :: totw_out             !! Sum of the water flow out to the routing scheme
8140!$OMP THREADPRIVATE(totw_out)
8141    REAL(r_std), SAVE          :: totw_return          !!
8142!$OMP THREADPRIVATE(totw_return)
8143    REAL(r_std), SAVE          :: totw_irrig           !!
8144!$OMP THREADPRIVATE(totw_irrig)
8145    REAL(r_std), SAVE          :: totw_river           !!
8146!$OMP THREADPRIVATE(totw_river)
8147    REAL(r_std), SAVE          :: totw_coastal         !!
8148!$OMP THREADPRIVATE(totw_coastal)
8149    REAL(r_std)                :: totarea              !! Total area of basin (m^2)
8150    REAL(r_std)                :: area                 !! Total area of routing (m^2)
8151    INTEGER(i_std)             :: ig                   !!
8152    !
8153    ! Just to make sure we do not get too large numbers !
8154    !
8155!! PARAMETERS
8156    REAL(r_std), PARAMETER     :: scaling = 1.0E+6     !!
8157    REAL(r_std), PARAMETER     :: allowed_err = 50.    !!
8158
8159!_ ================================================================================================================================
8160    !
8161    IF ( reinit ) THEN
8162       !
8163       totw_flood = zero
8164       totw_stream = zero
8165       totw_fast = zero
8166       totw_slow = zero
8167       totw_lake = zero
8168       totw_pond = zero 
8169       totw_in = zero
8170       !
8171       DO ig=1,nbpt
8172          !
8173          totarea = SUM(routing_area(ig,:))
8174          !
8175          totw_flood = totw_flood + SUM(flood_reservoir(ig,:)/scaling)
8176          totw_stream = totw_stream + SUM(stream_reservoir(ig,:)/scaling)
8177          totw_fast = totw_fast + SUM(fast_reservoir(ig,:)/scaling)
8178          totw_slow = totw_slow + SUM(slow_reservoir(ig,:)/scaling)
8179          totw_lake = totw_lake + lake_reservoir(ig)/scaling
8180          totw_pond = totw_pond + pond_reservoir(ig)/scaling
8181          !
8182          totw_in = totw_in + (runoff(ig)*totarea + drainage(ig)*totarea - floodout(ig)*totarea)/scaling
8183          !
8184       ENDDO
8185       !
8186    ELSE
8187       !
8188       totw_out = zero
8189       totw_return = zero
8190       totw_irrig = zero
8191       totw_river = zero
8192       totw_coastal = zero
8193       area = zero
8194       !
8195       DO ig=1,nbpt
8196          !
8197          totarea = SUM(routing_area(ig,:))
8198          !
8199          totw_flood = totw_flood - SUM(flood_reservoir(ig,:)/scaling)
8200          totw_stream = totw_stream - SUM(stream_reservoir(ig,:)/scaling)
8201          totw_fast = totw_fast - SUM(fast_reservoir(ig,:)/scaling)
8202          totw_slow = totw_slow - SUM(slow_reservoir(ig,:)/scaling)
8203          totw_lake = totw_lake - lake_reservoir(ig)/scaling
8204          totw_pond = totw_pond - pond_reservoir(ig)/scaling
8205          !
8206          totw_return = totw_return + (reinfiltration(ig)+returnflow(ig))*totarea/scaling
8207          totw_irrig = totw_irrig + irrigation(ig)*totarea/scaling
8208          totw_river = totw_river + riverflow(ig)/scaling
8209          totw_coastal = totw_coastal + coastalflow(ig)/scaling
8210          !
8211          area = area + totarea
8212          !
8213       ENDDO
8214       totw_out = totw_return + totw_irrig + totw_river + totw_coastal
8215       !
8216       ! Now we have all the information to balance our water
8217       !
8218       IF ( ABS((totw_flood + totw_stream + totw_fast + totw_slow + totw_lake + totw_pond) - &
8219            & (totw_out - totw_in)) > allowed_err ) THEN
8220          WRITE(numout,*) 'WARNING : Water not conserved in routing. Limit at ', allowed_err, ' 10^6 kg'
8221          WRITE(numout,*) '--Water-- change : flood stream fast ', totw_flood, totw_stream, totw_fast
8222          WRITE(numout,*) '--Water-- change : slow, lake ', totw_slow, totw_lake
8223          WRITE(numout,*) '--Water>>> change in the routing res. : ', totw_flood + totw_stream + totw_fast + totw_slow + totw_lake
8224          WRITE(numout,*) '--Water input : ', totw_in
8225          WRITE(numout,*) '--Water output : ', totw_out
8226          WRITE(numout,*) '--Water output : return, irrig ', totw_return, totw_irrig
8227          WRITE(numout,*) '--Water output : river, coastal ',totw_river, totw_coastal
8228          WRITE(numout,*) '--Water>>> change by fluxes : ', totw_out - totw_in, ' Diff [mm/dt]: ',   &
8229               & ((totw_flood + totw_stream + totw_fast + totw_slow + totw_lake) - (totw_out - totw_in))/area
8230
8231          ! Stop the model
8232          CALL ipslerr_p(3, 'routing_waterbal', 'Water is not conserved in routing.','','')
8233       ENDIF
8234       !
8235    ENDIF
8236    !
8237  END SUBROUTINE routing_waterbal
8238  !
8239  !
8240END MODULE routing
Note: See TracBrowser for help on using the repository browser.