source: branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/routing_native.f90 @ 8227

Last change on this file since 8227 was 8227, checked in by yann.meurdesoif, 9 months ago

New version of routing simple => become routing_native ; after validation routing_simple will be supress

  • more robust routing scheme on native grid
  • rearchitecturing of routing by spliting routing sub-process into separate file/module => smaller file
  • works on global as well on regional (orchidee) grid.
  • works on standard 50km routing grid and highres routing MERIT grid (1-2km), for regional studies
  • integrate irrigation old scheme et new scheme (pedro arboleda)
  • more water conservative (1e-16 Vs 1e-7 relative for simple routing)
  • To be tested : ICOLMDZOR grid and ICOLAMDZ-LAM grid that are expeted to work also.

It is a first guess, not the definitive native routing package that will continue to evolve.
No side effect is expected on other configurations since it is just some files adding.
Native routing is activated using the run.def key :
ROUTING_METHOD=native

YM

File size: 25.2 KB
Line 
1! =================================================================================================================================
2! MODULE       : routing_simple
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: The subroutines in this subroutine is only called when ROUTING_METHOD=simple is set in run.def.
13!!                The method can be used for regular latitude-longitude grid or for unstructured grid.
14!!
15!! RECENT CHANGE(S): None
16!!
17!! REFERENCE(S) :
18!!
19!! SVN          :
20!! $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/perso/pedro.arboleda/ORCHIDEE/src_sechiba/routing_simple.f90 $
21!! $Date: 2022-06-07 19:03:47 +0200 (Tue, 07 Jun 2022) $
22!! $Revision: 7644 $
23!! \n
24!_ ================================================================================================================================
25
26 
27
28! Histoire Salee
29!---------------
30! La douce riviere
31! Sortant de son lit
32! S'est jetee ma chere
33! dans les bras mais oui
34! du beau fleuve
35!
36! L'eau coule sous les ponts
37! Et puis les flots s'emeuvent
38! - N'etes vous pas au courant ?
39! Il parait que la riviere
40! Va devenir mer
41!                       Roland Bacri
42!
43
44
45MODULE routing_native_mod
46
47  USE ioipsl   
48  USE xios_orchidee
49  USE ioipsl_para 
50  USE constantes
51  USE constantes_soil
52  USE pft_parameters
53  USE sechiba_io_p
54  USE interpol_help
55  USE grid
56  USE mod_orchidee_para
57
58
59  IMPLICIT NONE
60  PRIVATE
61  PUBLIC :: routing_native_main, routing_native_xios_initialize
62  PUBLIC :: routing_native_initialize, routing_native_finalize, routing_native_clear
63
64  REAL,SAVE :: dt_routing
65  !$OMP THREADPRIVATE(dt_routing)
66
67  INTEGER,SAVE :: nbpt
68  !$OMP THREADPRIVATE(nbpt)
69 
70  INTEGER,SAVE :: nbpt_r
71  !$OMP THREADPRIVATE(nbpt_r)
72 
73  LOGICAL,SAVE :: dofloodinfilt
74  !$OMP THREADPRIVATE(dofloodinfilt)   
75
76  LOGICAL,SAVE :: doswamps
77  !$OMP THREADPRIVATE(doswamps) 
78
79  LOGICAL,SAVE :: doponds
80  !$OMP THREADPRIVATE(doponds) 
81
82
83  REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: returnflow_mean              !! Mean water flow from lakes and swamps which returns to the grid box.
84 !$OMP THREADPRIVATE(returnflow_mean)
85
86 REAL, SAVE :: time_counter = 0
87 !$OMP THREADPRIVATE(time_counter) 
88   
89CONTAINS
90
91!!  =============================================================================================================================
92!! SUBROUTINE:    routing_native_xios_initialize
93!!
94!>\BRIEF          Initialize xios dependant defintion before closing context defintion
95!!
96!! DESCRIPTION:   Initialize xios dependant defintion before closing context defintion.
97!!                This subroutine is called before the xios context is closed.
98!!
99!! RECENT CHANGE(S): None
100!!
101!! REFERENCE(S): None
102!!
103!! FLOWCHART: None
104!! \n
105!_ ==============================================================================================================================
106
107  SUBROUTINE routing_native_xios_initialize
108    USE xios
109    USE routing_native_flow_mod
110    IMPLICIT NONE     
111
112     CALL routing_flow_xios_initialize
113     
114   END SUBROUTINE routing_native_xios_initialize
115
116
117
118
119
120
121
122  !!  =============================================================================================================================
123  !! SUBROUTINE:         routing_simple_initialize
124  !!
125  !>\BRIEF               Initialize the routing_simple module
126  !!
127  !! DESCRIPTION:        Initialize the routing_simple module. Read from restart file or read the routing.nc file to initialize the
128  !!                     routing scheme.
129  !!
130  !! RECENT CHANGE(S)
131  !!
132  !! REFERENCE(S)
133  !!
134  !! FLOWCHART   
135  !! \n
136  !_ ==============================================================================================================================
137
138  SUBROUTINE routing_native_initialize( kjit,       nbpt,           index,                 &
139       rest_id,     hist_id,        hist2_id,   lalo,      &
140       neighbours,  resolution,     contfrac,   stempdiag, &
141       returnflow,  reinfiltration, irrigation, riverflow, &
142       coastalflow, flood_frac,     flood_res , irrigated_next)
143   
144    USE routing_native_flow_mod, ONLY : routing_flow_initialize
145    USE routing_native_irrig_mod, ONLY : irrigation_initialize
146    USE routing_native_lake_mod, ONLY : routing_lake_initialize
147    USE routing_native_para, ONLY: routing_para_initialize
148    IMPLICIT NONE
149
150    !! 0 Variable and parameter description
151    !! 0.1 Input variables
152    INTEGER(i_std), INTENT(in)     :: kjit                 !! Time step number (unitless)
153    INTEGER(i_std), INTENT(in)     :: nbpt                 !! Domain size (unitless)
154    INTEGER(i_std), INTENT(in)     :: index(nbpt)          !! Indices of the points on the map (unitless)
155    INTEGER(i_std),INTENT(in)      :: rest_id              !! Restart file identifier (unitless)
156    INTEGER(i_std),INTENT(in)      :: hist_id              !! Access to history file (unitless)
157    INTEGER(i_std),INTENT(in)      :: hist2_id             !! Access to history file 2 (unitless)
158    REAL(r_std), INTENT(in)        :: lalo(nbpt,2)         !! Vector of latitude and longitudes (beware of the order !)
159
160    INTEGER(i_std), INTENT(in)     :: neighbours(nbpt,8)   !! Vector of neighbours for each grid point
161                                                           !! (1=N, 2=NE, 3=E, 4=SE, 5=S, 6=SW, 7=W, 8=NW) (unitless)
162    REAL(r_std), INTENT(in)        :: resolution(nbpt,2)   !! The size of each grid box in X and Y (m)
163    REAL(r_std), INTENT(in)        :: contfrac(nbpt)       !! Fraction of land in each grid box (unitless;0-1)
164    REAL(r_std), INTENT(in)        :: stempdiag(nbpt,nslm) !! Diagnostic soil temperature profile
165
166    !! 0.2 Output variables
167    REAL(r_std), INTENT(out)       :: returnflow(nbpt)     !! The water flow from lakes and swamps which returns to the grid box.
168                                                           !! This water will go back into the hydrol or hydrolc module to allow re-evaporation (kg/m^2/dt)
169    REAL(r_std), INTENT(out)       :: reinfiltration(nbpt) !! Water flow from ponds and floodplains which returns to the grid box (kg/m^2/dt)
170    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)
171    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)
172
173    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)
174    REAL(r_std), INTENT(out)       :: flood_frac(nbpt)     !! Flooded fraction of the grid box (unitless;0-1)
175    REAL(r_std), INTENT(out)       :: flood_res(nbpt)      !! Diagnostic of water amount in the floodplains reservoir (kg)
176    REAL(r_std), INTENT(in)        :: irrigated_next (nbpt)  !! Dynamic irrig. area, calculated in slowproc and passed to routing!
177
178    !_ ================================================================================================================================
179   
180   
181      CALL routing_para_initialize 
182      CALL routing_native_init_local(kjit, rest_id, nbpt, contfrac)
183      CALL routing_flow_initialize(kjit, rest_id, nbpt, dt_routing, contfrac, nbpt_r, riverflow, coastalflow)
184      CALL routing_lake_initialize(kjit, rest_id, nbpt, contfrac)
185      CALL irrigation_initialize(kjit, rest_id, nbpt, nbpt_r,irrigated_next )
186     
187      reinfiltration(:)=0
188      irrigation(:)=0
189      flood_frac(:)=0
190      flood_res(:)=0
191      returnflow(:)=returnflow_mean(:)
192
193    END SUBROUTINE routing_native_initialize
194   
195   
196  !! ================================================================================================================================
197  !! SUBROUTINE         : routing_simple_initialize
198  !!
199  !>\BRIEF         This subroutine allocates the memory and get the fixed fields from the restart file.
200  !!
201  !! DESCRIPTION:         Privat subroutine to the module routing_simple. This subroutine is called in the begining
202  !!                      of routing_simple_initialize
203  !!
204  !! RECENT CHANGE(S): None
205  !!
206  !! MAIN OUTPUT VARIABLE(S):
207  !!
208  !! REFERENCES   : None
209  !!
210  !! FLOWCHART    :None
211  !! \n
212  !_ ================================================================================================================================
213
214  SUBROUTINE routing_native_init_local(kjit, rest_id, nbpt_, contfrac)
215  USE time, ONLY : dt_sechiba 
216  USE routing_native_flow_mod   
217  IMPLICIT NONE
218    INTEGER(i_std),INTENT(in)      :: kjit
219    INTEGER(i_std),INTENT(in)      :: rest_id              !! Restart file identifier (unitless)
220    INTEGER,INTENT(in) :: nbpt_             !! nb points native grid
221    REAL,INTENT(in)    :: contfrac(nbpt)   !! fraction of land
222
223    INTEGER :: ier   
224    CHARACTER(LEN=80)   :: var_name       !! To store variables names for I/O (unitless)
225 
226    REAL(r_std) ::ratio
227   
228    nbpt = nbpt_
229
230    ALLOCATE (returnflow_mean(nbpt), stat=ier)
231    IF (ier /= 0) CALL ipslerr_p(3,'routing_init','Pb in allocate for returnflow_mean','','')
232    var_name = 'returnflow'
233    CALL ioconf_setatt_p('UNITS', 'Kg/m^2/dt')
234    CALL ioconf_setatt_p('LONG_NAME','Deep return flux')
235    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., returnflow_mean, "gather", nbp_glo, index_g)
236    CALL setvar_p (returnflow_mean, val_exp, 'NO_KEYWORD', zero)
237   
238    !_ ================================================================================================================================
239    !
240    !
241    ! These variables will require the configuration infrastructure
242    !
243    !Config Key   = DT_ROUTING
244    !Config If    = RIVER_ROUTING
245    !Config Desc  = Time step of the routing scheme
246    !Config Def   = one_day
247    !Config Help  = This values gives the time step in seconds of the routing scheme.
248    !Config         It should be multiple of the main time step of ORCHIDEE. One day
249    !Config         is a good value.
250    !Config Units = [seconds]
251    !
252    dt_routing = one_day
253    CALL getin_p('DT_ROUTING', dt_routing)
254
255    !
256    !Config Key   = DO_FLOODINFILT
257    !Config Desc  = Should floodplains reinfiltrate into the soil
258    !Config If    = RIVER_ROUTING
259    !Config Def   = n
260    !Config Help  = This parameters allows the user to ask the model
261    !Config         to take into account the flood plains reinfiltration
262    !Config         into the soil moisture. It then can go
263    !Config         back to the slow and fast reservoirs
264    !Config Units = [FLAG]
265    !
266    dofloodinfilt = .FALSE.
267    CALL getin_p('DO_FLOODINFILT', dofloodinfilt)
268    !
269    !Config Key   = DO_SWAMPS
270    !Config Desc  = Should we include swamp parameterization
271    !Config If    = RIVER_ROUTING
272    !Config Def   = n
273    !Config Help  = This parameters allows the user to ask the model
274    !Config         to take into account the swamps and return
275    !Config         the water into the bottom of the soil. It then can go
276    !Config         back to the atmopshere. This tried to simulate
277    !Config         internal deltas of rivers.
278    !Config Units = [FLAG]
279    !
280    doswamps = .FALSE.
281    CALL getin_p('DO_SWAMPS', doswamps)
282    !
283    !Config Key   = DO_PONDS
284    !Config Desc  = Should we include ponds
285    !Config If    = RIVER_ROUTING
286    !Config Def   = n
287    !Config Help  = This parameters allows the user to ask the model
288    !Config         to take into account the ponds and return
289    !Config         the water into the soil moisture. It then can go
290    !Config         back to the atmopshere. This tried to simulate
291    !Config         little ponds especially in West Africa.
292    !Config Units = [FLAG]
293    !
294    doponds = .FALSE.
295    CALL getin_p('DO_PONDS', doponds)
296
297    ratio = dt_routing/dt_sechiba
298    IF ( ABS(NINT(ratio) - ratio) .GT. 10*EPSILON(ratio)) THEN
299       WRITE(numout,*) 'WARNING -- WARNING -- WARNING -- WARNING'
300       WRITE(numout,*) "The chosen time step for the routing is not a multiple of the"
301       WRITE(numout,*) "main time step of the model. We will change dt_routing so that"
302       WRITE(numout,*) "this condition os fulfilled"
303       dt_routing = NINT(ratio) * dt_sechiba
304       WRITE(numout,*) 'THE NEW DT_ROUTING IS : ', dt_routing
305    ENDIF
306    !
307    IF ( dt_routing .LT. dt_sechiba) THEN
308       WRITE(numout,*) 'WARNING -- WARNING -- WARNING -- WARNING'
309       WRITE(numout,*) 'The routing timestep can not be smaller than the one'
310       WRITE(numout,*) 'of the model. We reset its value to the model''s timestep.'
311       WRITE(numout,*) 'The old DT_ROUTING is : ', dt_routing
312       dt_routing = dt_sechiba
313       WRITE(numout,*) 'THE NEW DT_ROUTING IS : ', dt_routing
314    ENDIF
315   
316  END SUBROUTINE routing_native_init_local
317 
318
319
320  !! ================================================================================================================================
321  !! SUBROUTINE   : routing_simple_main
322  !!
323  !>\BRIEF          This module routes the water over the continents (runoff and
324  !!                drainage produced by the hydrolc or hydrol module) into the oceans.
325  !!
326  !! DESCRIPTION (definitions, functional, design, flags):
327  !! The routing scheme (Polcher, 2003) carries the water from the runoff and drainage simulated by SECHIBA
328  !! to the ocean through reservoirs, with some delay. The routing scheme is based on
329  !! a parametrization of the water flow on a global scale (Miller et al., 1994; Hagemann
330  !! and Dumenil, 1998). Given the global map of the main watersheds (Oki et al., 1999;
331  !! Fekete et al., 1999; Vorosmarty et al., 2000) which delineates the boundaries of subbasins
332  !! and gives the eight possible directions of water flow within the pixel, the surface
333  !! runoff and the deep drainage are routed to the ocean. The time-step of the routing is one day.
334  !! The scheme also diagnoses how much water is retained in the foodplains and thus return to soil
335  !! moisture or is taken out of the rivers for irrigation. \n
336  !!
337  !! RECENT CHANGE(S): None
338  !!
339  !! MAIN OUTPUT VARIABLE(S):
340  !! The result of the routing are 3 fluxes :
341  !! - riverflow   : The water which flows out from the major rivers. The flux will be located
342  !!                 on the continental grid but this should be a coastal point.
343  !! - coastalflow : This is the water which flows in a disperse way into the ocean. Essentially these
344  !!                 are the outflows from all of the small rivers.
345  !! - returnflow  : This is the water which flows into a land-point - typically rivers which end in
346  !!                 the desert. This water will go back into the hydrol module to allow re-evaporation.
347  !! - irrigation  : This is water taken from the reservoir and is being put into the upper
348  !!                 layers of the soil.
349  !! The two first fluxes are in kg/dt and the last two fluxes are in kg/(m^2dt).\n
350  !!
351  !! REFERENCE(S) :
352  !! - Miller JR, Russell GL, Caliri G (1994)
353  !!   Continental-scale river flow in climate models.
354  !!   J. Clim., 7:914-928
355  !! - Hagemann S and Dumenil L. (1998)
356  !!   A parametrization of the lateral waterflow for the global scale.
357  !!   Clim. Dyn., 14:17-31
358  !! - Oki, T., T. Nishimura, and P. Dirmeyer (1999)
359  !!   Assessment of annual runoff from land surface models using total runoff integrating pathways (TRIP)
360  !!   J. Meteorol. Soc. Jpn., 77, 235-255
361  !! - Fekete BM, Charles V, Grabs W (2000)
362  !!   Global, composite runoff fields based on observed river discharge and simulated water balances.
363  !!   Technical report, UNH/GRDC, Global Runoff Data Centre, Koblenz
364  !! - Vorosmarty, C., B. Fekete, B. Meybeck, and R. Lammers (2000)
365  !!   Global system of rivers: Its role in organizing continental land mass and defining land-to-ocean linkages
366  !!   Global Biogeochem. Cycles, 14, 599-621
367  !! - Vivant, A-C. (?? 2002)
368  !!   Développement du schéma de routage et des plaines d'inondation, MSc Thesis, Paris VI University
369  !! - J. Polcher (2003)
370  !!   Les processus de surface a l'echelle globale et leurs interactions avec l'atmosphere
371  !!   Habilitation a diriger les recherches, Paris VI University, 67pp.
372  !!
373  !! FLOWCHART    :
374  !! \latexonly
375  !! \includegraphics[scale=0.75]{routing_main_flowchart.png}
376  !! \endlatexonly
377  !! \n
378  !_ ================================================================================================================================
379
380
381  SUBROUTINE routing_native_main(kjit, nbpt, index, &
382                                 lalo, neighbours, resolution, contfrac, totfrac_nobio, veget_max, floodout, runoff, &
383                                 drainage, transpot, precip_rain, humrel, k_litt, flood_frac, flood_res, &
384                                 stempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, &
385                                 rest_id, hist_id, hist2_id ,&
386                                 soiltile, root_deficit, irrigated_next, irrig_frac, fraction_aeirrig_sw) 
387
388    USE routing_native_flow_mod,ONLY : routing_flow_make_mean, routing_flow_main, riverflow_mean, coastalflow_mean, lakeinflow_mean, &
389                                routing_flow_get, routing_flow_set
390    USE routing_native_irrig_mod, ONLY: irrigation_mean_make, irrigation_main, irrigation_get
391    USE routing_native_lake_mod, ONLY: routing_lake_mean_make, routing_lake_route_coast, routing_lake_main
392    USE routing_native_para, ONLY: routing_para_initialize
393    USE xios
394    IMPLICIT NONE
395
396    !! 0 Variable and parameter description
397    !! 0.1 Input variables
398
399    INTEGER(i_std), INTENT(in)     :: kjit                 !! Time step number (unitless)
400    INTEGER(i_std), INTENT(in)     :: nbpt                 !! Domain size (unitless)
401    INTEGER(i_std),INTENT(in)      :: rest_id              !! Restart file identifier (unitless)
402    INTEGER(i_std),INTENT(in)      :: hist_id              !! Access to history file (unitless)
403    INTEGER(i_std),INTENT(in)      :: hist2_id             !! Access to history file 2 (unitless)
404    INTEGER(i_std), INTENT(in)     :: index(nbpt)          !! Indices of the points on the map (unitless)
405    REAL(r_std), INTENT(in)        :: lalo(nbpt,2)         !! Vector of latitude and longitudes (beware of the order !)
406    INTEGER(i_std), INTENT(in)     :: neighbours(nbpt,8)   !! Vector of neighbours for each grid point (1=N, 2=NE, 3=E, 4=SE, 5=S, 6=SW, 7=W, 8=NW) (unitless)
407    REAL(r_std), INTENT(in)        :: resolution(nbpt,2)   !! The size of each grid box in X and Y (m)
408    REAL(r_std), INTENT(in)        :: contfrac(nbpt)       !! Fraction of land in each grid box (unitless;0-1)
409    REAL(r_std), INTENT(in)        :: totfrac_nobio(nbpt)  !! Total fraction of no-vegetation (continental ice, lakes ...) (unitless;0-1)
410    REAL(r_std), INTENT(in)        :: veget_max(nbpt,nvm)  !! Maximal fraction of vegetation (unitless;0-1)
411    REAL(r_std), INTENT(in)        :: floodout(nbpt)       !! Grid-point flow out of floodplains (kg/m^2/dt)
412    REAL(r_std), INTENT(in)        :: runoff(nbpt)         !! Grid-point runoff (kg/m^2/dt)
413    REAL(r_std), INTENT(in)        :: drainage(nbpt)       !! Grid-point drainage (kg/m^2/dt)
414    REAL(r_std), INTENT(in)        :: transpot(nbpt,nvm)   !! Potential transpiration of the vegetation (kg/m^2/dt)
415    REAL(r_std), INTENT(in)        :: precip_rain(nbpt)    !! Rainfall (kg/m^2/dt)
416    REAL(r_std), INTENT(in)        :: k_litt(nbpt)         !! Averaged conductivity for saturated infiltration in the 'litter' layer (kg/m^2/dt)
417    REAL(r_std), INTENT(in)        :: humrel(nbpt,nvm)     !! Soil moisture stress, root extraction potential (unitless)
418    REAL(r_std), INTENT(in)        :: stempdiag(nbpt,nslm) !! Diagnostic soil temperature profile
419    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)
420    REAL(r_std), INTENT(in)        :: root_deficit(nbpt)   !! soil water deficit
421    REAL(r_std), INTENT(in)        :: soiltile(nbpt,nstm)  !! Fraction of each soil tile within vegtot (0-1, unitless)
422    REAL(r_std), INTENT(in)        :: irrig_frac(nbpt)     !! Irrig. fraction interpolated in routing, and saved to pass to slowproc if irrigated_soiltile = .TRUE.
423    REAL(r_std), INTENT(in)        :: irrigated_next (nbpt)!! Dynamic irrig. area, calculated in slowproc and passed to routing
424    REAL(r_std), INTENT(in)        :: fraction_aeirrig_sw(nbpt) !! Fraction of area equipped for irrigation from surface water, of irrig_frac
425
426    !! 0.2 Output variables
427    REAL(r_std), INTENT(out)       :: returnflow(nbpt)     !! The water flow from lakes and swamps which returns to the grid box.
428    !! This water will go back into the hydrol or hydrolc module to allow re-evaporation (kg/m^2/dt)
429    REAL(r_std), INTENT(out)       :: reinfiltration(nbpt) !! Water flow from ponds and floodplains which returns to the grid box (kg/m^2/dt)
430    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)
431    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)
432    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)
433    REAL(r_std), INTENT(out)       :: flood_frac(nbpt)     !! Flooded fraction of the grid box (unitless;0-1)
434    REAL(r_std), INTENT(out)       :: flood_res(nbpt)      !! Diagnostic of water amount in the floodplains reservoir (kg)
435
436    !! 0.3 Local variables
437    REAL(r_std), DIMENSION(nbpt)   :: return_lakes         !! Water from lakes flowing back into soil moisture (kg/m^2/dt)
438    REAL(r_std)                    :: lakeinflow(nbpt)
439 
440 
441    CALL routing_flow_make_mean(runoff, drainage)
442    CALL irrigation_mean_make(dt_routing, veget_max, humrel, transpot, runoff , precip_rain)
443    CALL routing_lake_mean_make(dt_routing, humrel, veget_max)
444       
445    time_counter = time_counter + dt_sechiba
446   
447    reinfiltration(:)= 0 ! for now
448   
449    ! If the time has come we do the routing.
450    IF ( NINT(time_counter) .GE. NINT(dt_routing) ) THEN
451       returnflow_mean(:)=0
452 
453       CALL routing_flow_main(dt_routing)
454
455       CALL routing_flow_get(coastalflow_mean=coastalflow)
456       CALL routing_lake_route_coast(contfrac,coastalflow)
457       CALL routing_flow_set(coastalflow_mean=coastalflow)
458     
459       CALL irrigation_main( dt_routing, reinfiltration, irrigated_next, irrig_frac, root_deficit, soiltile, &
460                             fraction_aeirrig_sw )
461       
462       CALL routing_flow_get(lakeinflow_mean=lakeinflow)
463       CALL routing_lake_main(dt_routing, contfrac, lakeinflow, return_lakes)
464       CALL routing_flow_set(lakeinflow_mean=lakeinflow)
465       
466       returnflow_mean(:)=returnflow_mean(:)+return_lakes(:)
467       
468       time_counter = 0
469    ENDIF
470
471    CALL routing_flow_get(riverflow_mean=riverflow, coastalflow_mean=coastalflow, lakeinflow_mean=lakeinflow)
472    CALL irrigation_get(irrigation_mean=irrigation)
473
474
475    returnflow  = returnflow/dt_routing*dt_sechiba
476    riverflow   = riverflow/dt_routing*dt_sechiba
477    coastalflow = coastalflow/dt_routing*dt_sechiba
478    irrigation = irrigation/dt_routing*dt_sechiba
479   
480    CALL xios_send_field("irrigation", irrigation/dt_sechiba)
481   
482    returnflow(:) = 0
483    reinfiltration(:) =0
484    flood_frac(:) = 0
485    flood_res(:) = 0
486 
487  END SUBROUTINE routing_native_main
488
489  !!  =============================================================================================================================
490  !! SUBROUTINE:         routing_simple_finalize
491  !!
492  !>\BRIEF               Write to restart file
493  !!
494  !! DESCRIPTION:        Write module variables to restart file
495  !!
496  !! RECENT CHANGE(S)
497  !!
498  !! REFERENCE(S)
499  !!
500  !! FLOWCHART   
501  !! \n
502  !_ ==============================================================================================================================
503
504  SUBROUTINE routing_native_finalize(kjit, nbpt_, rest_id, flood_frac, flood_res )
505    USE routing_native_flow_mod
506    USE routing_native_lake_mod
507    USE routing_native_irrig_mod
508    IMPLICIT NONE
509    INTEGER, INTENT(IN)          :: kjit
510    INTEGER,INTENT(IN)           :: nbpt_
511    INTEGER, INTENT(IN)          :: rest_id
512    REAL(r_std), INTENT(in)      :: flood_frac(nbpt)     !! Flooded fraction of the grid box (unitless;0-1)
513    REAL(r_std), INTENT(in)      :: flood_res(nbpt)      !! Diagnostic of water amount in the floodplains reservoir (kg)
514
515    CALL routing_native_local_finalize(kjit, rest_id)
516    CALL routing_flow_finalize(kjit, rest_id)
517    CALL routing_lake_finalize(kjit, rest_id)
518    CALL irrigation_finalize(kjit, rest_id)
519
520  END SUBROUTINE routing_native_finalize
521
522  SUBROUTINE routing_native_local_finalize(kjit,rest_id)
523    USE ioipsl_para
524    USE grid
525    IMPLICIT NONE
526    INTEGER, INTENT(IN) :: kjit
527    INTEGER, INTENT(IN) :: rest_id
528
529    CALL restput_p (rest_id, 'returnflow', nbp_glo, 1, 1, kjit, returnflow_mean, 'scatter',  nbp_glo, index_g)
530    DEALLOCATE(returnflow_mean)
531
532  END SUBROUTINE routing_native_local_finalize
533
534
535  SUBROUTINE routing_native_clear
536    USE xios
537    IMPLICIT NONE
538
539
540
541  END SUBROUTINE routing_native_clear
542 
543END MODULE routing_native_mod
Note: See TracBrowser for help on using the repository browser.