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

Last change on this file since 8227 was 8227, checked in by yann.meurdesoif, 8 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

  • Property svn:keywords set to Date Revision HeadURL
File size: 20.8 KB
Line 
1! ================================================================================================================================
2!  MODULE       : routing_wrapper
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          Interfaces to all routing schemes.
10!!
11!!\n DESCRIPTION: This module contains uniformed subroutines called from sechiba. These subroutines make the swich the between
12!!                the different existing routing modules.
13!!               
14!!                Depending on the key world ROUTING_METHOD set in run.def, this module calls one of the
15!!                available routing modules:
16!!                - ROUTING_METOD=standard for the standard routing scheme available in module routing.
17!!                - ROUTING_METHOD=simple for the routing scheme in module routing_simple.
18!!                - ROUTING_METHOD=highres for the high resolution routing scheme in module routing_highres.
19!!
20!! REFERENCE(S) : None
21!!
22!! SVN          :
23!! $HeadURL$
24!! $Date$
25!! $Revision$
26!! \n
27!_ ================================================================================================================================
28
29MODULE routing_wrapper
30
31  USE defprec
32  USE pft_parameters
33  USE grid
34  USE routing
35  USE routing_highres
36  USE routing_simple
37  USE routing_native_mod
38  USE constantes_soil
39
40  IMPLICIT NONE
41
42  CHARACTER(LEN=255), SAVE :: routing_method                      !! 'standard', 'highres' or 'simple': Character string used to switch between routing modules
43  !$OMP THREADPRIVATE(routing_method)
44
45  PUBLIC :: routing_wrapper_xios_initialize, routing_wrapper_initialize, &
46            routing_wrapper_main, routing_wrapper_finalize, routing_wrapper_clear 
47  PRIVATE
48
49CONTAINS
50
51!!  =============================================================================================================================
52!! SUBROUTINE:    routing_wrapper_xios_initialize
53!!
54!>\BRIEF          First initialization phase of the choosen routing module
55!!
56!! DESCRIPTION:   Read ROUTING_METHOD from run.def and call the xios initialization subroutine from corresponding routing module.
57!!                This subroutine is called before the xios context is closed.
58!!                It is called from sechiba_initialize only if 1 is activated.
59!!
60!! RECENT CHANGE(S): None
61!!
62!! REFERENCE(S): None
63!!
64!! FLOWCHART: None
65!! \n
66!_ ==============================================================================================================================
67  SUBROUTINE routing_wrapper_xios_initialize()
68
69    ! Get ROUTING_METHOD from run.def. Note that this is also done in
70    ! routing_wrapper_initialize because current subroutine is not alwyas called.
71    routing_method='standard'
72    CALL getin_p("ROUTING_METHOD",routing_method)
73    IF(routing_method=='standard') THEN
74       CALL routing_xios_initialize
75    ELSEIF(routing_method=='highres') THEN
76       CALL routing_highres_xios_initialize
77    ELSEIF(routing_method=='simple') THEN 
78       CALL routing_simple_xios_initialize
79    ELSEIF(routing_method=='native') THEN
80       CALL routing_native_xios_initialize
81    ENDIF
82
83  END SUBROUTINE routing_wrapper_xios_initialize
84
85
86
87
88!!  =============================================================================================================================
89!! SUBROUTINE:    routing_wrapper_initialize
90!!
91!>\BRIEF          Initialize the choosen routing module
92!!
93!! DESCRIPTION:   Read ROUTING_METHOD from run.def and call the initialization subroutine from corresponding routing module
94!!
95!! RECENT CHANGE(S): None
96!!
97!! REFERENCE(S): None
98!!
99!! FLOWCHART: None
100!! \n
101!_ ==============================================================================================================================
102  SUBROUTINE routing_wrapper_initialize( &
103       kjit,        nbpt,           index,                 &
104       rest_id,     hist_id,        hist2_id,   lalo,      &
105       neighbours,  resolution,     contfrac,   stempdiag, ftempdiag, &
106       soiltile,    irrig_frac,     veget_max,  irrigated_next, &   
107       returnflow,  reinfiltration, irrigation, riverflow, &
108       coastalflow, flood_frac,     flood_res )
109
110
111    !! 0.1 Input variables
112    INTEGER(i_std), INTENT(in)     :: kjit                 !! Time step number (unitless)
113    INTEGER(i_std), INTENT(in)     :: nbpt                 !! Domain size (unitless)
114    INTEGER(i_std), INTENT(in)     :: index(nbpt)          !! Indices of the points on the map (unitless)
115    INTEGER(i_std),INTENT(in)      :: rest_id              !! Restart file identifier (unitless)
116    INTEGER(i_std),INTENT(in)      :: hist_id              !! Access to history file (unitless)
117    INTEGER(i_std),INTENT(in)      :: hist2_id             !! Access to history file 2 (unitless)
118    REAL(r_std), INTENT(in)        :: lalo(nbpt,2)         !! Vector of latitude and longitudes (beware of the order !)
119
120    INTEGER(i_std), INTENT(in)     :: neighbours(nbpt,8)   !! Vector of neighbours for each grid point
121                                                           !! (1=N, 2=NE, 3=E, 4=SE, 5=S, 6=SW, 7=W, 8=NW) (unitless)
122    REAL(r_std), INTENT(in)        :: resolution(nbpt,2)   !! The size of each grid box in X and Y (m)
123    REAL(r_std), INTENT(in)        :: contfrac(nbpt)       !! Fraction of land in each grid box (unitless;0-1)
124    REAL(r_std), INTENT(in)        :: stempdiag(nbpt,nslm) !! Diagnostic soil temperature profile
125    REAL(r_std), INTENT(in)        :: ftempdiag(nbpt,ngrnd)!! Diagnostic soil temperature profile over full column
126    REAL(r_std), INTENT(in)        :: soiltile(nbpt,nstm)  !! Fraction of each soil tile within vegtot (0-1, unitless)
127    REAL(r_std), INTENT(in)        :: veget_max(nbpt,nvm)  !! Maximal fraction of vegetation (unitless;0-1) !
128    REAL(r_std), INTENT(in)        :: irrigated_next (nbpt)!! Dynamic irrig. area, calculated in slowproc and passed to routing!
129    REAL(r_std), INTENT(in)        :: irrig_frac(nbpt)     !! Irrig. fraction interpolated in routing, and saved to pass to slowproc if irrigated_soiltile = .TRUE.
130
131
132    !! 0.2 Output variables
133    REAL(r_std), INTENT(out)       :: returnflow(nbpt)     !! The water flow from lakes and swamps which returns to the grid box.
134                                                           !! This water will go back into the hydrol or hydrolc module to allow re-evaporation (kg/m^2/dt)
135    REAL(r_std), INTENT(out)       :: reinfiltration(nbpt) !! Water flow from ponds and floodplains which returns to the grid box (kg/m^2/dt)
136    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)
137    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)
138    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)
139    REAL(r_std), INTENT(out)       :: flood_frac(nbpt)     !! Flooded fraction of the grid box (unitless;0-1)
140    REAL(r_std), INTENT(out)       :: flood_res(nbpt)      !! Diagnostic of water amount in the floodplains reservoir (kg)
141
142
143    !_ ================================================================================================================================
144
145    !! 1. Get routing_method from run.def
146    !!    This variable will switch between the existing modules for the routing scheme.
147
148    !Config Key   = ROUTING_METHOD
149    !Config Desc  = Choice of routing module to be used
150    !Config If    = RIVER_ROUTING=T
151    !Config Def   = standard
152    !Config Help  = Possible options are standard and simple
153    !Config Units = character string
154
155    routing_method='standard'
156    CALL getin_p("ROUTING_METHOD",routing_method)
157
158
159    !! 2. Initialize the choosen routing module
160    IF (routing_method == 'standard') THEN
161
162       CALL routing_initialize(  kjit,        nbpt,           index,                 &
163                                 rest_id,     hist_id,        hist2_id,   lalo,      &
164                                 neighbours,  resolution,     contfrac,   stempdiag, &
165                                 returnflow,  reinfiltration, irrigation, riverflow, &
166                                 coastalflow, flood_frac,     flood_res,  soiltile,  &
167                                 irrig_frac,  veget_max,      irrigated_next)
168
169    ELSE IF (routing_method == 'highres') THEN
170
171       CALL routing_highres_initialize(  kjit,        nbpt,           index,                 &
172                                 rest_id,     hist_id,        hist2_id,   lalo,      &
173                                 neighbours,  resolution,     contfrac,   stempdiag, &
174                                 returnflow,  reinfiltration, irrigation, riverflow, &
175                                 coastalflow, flood_frac,     flood_res )
176
177    ELSE IF(routing_method== 'simple') THEN
178
179       CALL routing_simple_initialize(    kjit,        nbpt,           index,                 &
180                                          rest_id,     hist_id,        hist2_id,   lalo,      &
181                                          neighbours,  resolution,     contfrac,   stempdiag, &
182                                          returnflow,  reinfiltration, irrigation, riverflow, &
183                                          coastalflow, flood_frac,     flood_res )
184
185       riverflow(:) = zero
186       coastalflow(:) = zero
187       returnflow(:) = zero
188       reinfiltration(:) = zero
189       irrigation(:) = zero
190       flood_frac(:) = zero
191       flood_res(:) = zero
192   
193    ELSE IF(routing_method== 'native') THEN
194
195       CALL routing_native_initialize(    kjit,        nbpt,           index,                 &
196                                          rest_id,     hist_id,        hist2_id,   lalo,      &
197                                          neighbours,  resolution,     contfrac,   stempdiag, &
198                                          returnflow,  reinfiltration, irrigation, riverflow, &
199                                          coastalflow, flood_frac,     flood_res , irrigated_next)
200
201       riverflow(:) = zero
202       coastalflow(:) = zero
203       returnflow(:) = zero
204       reinfiltration(:) = zero
205       irrigation(:) = zero
206       flood_frac(:) = zero
207       flood_res(:) = zero
208
209    ELSE
210       ! Bad choice of routing_method. Exit the model now.
211       WRITE(numout,*) 'Following routing method is not implemented, ROUTING_METHOD=',routing_method
212       CALL ipslerr_p(3,'routing_wrapper_inititalize','ROUTING_METHOD can only be standard or simple','Error in run.def','')
213    ENDIF
214
215  END SUBROUTINE routing_wrapper_initialize
216
217
218
219!!  =============================================================================================================================
220!! SUBROUTINE:    routing_wrapper_main
221!!
222!>\BRIEF          Call the main subroutine for the choosen routing module
223!!
224!! DESCRIPTION:   Call the main subroutine for the choosen routing module according to ROUTING_METHOD
225!!
226!! RECENT CHANGE(S): None
227!!
228!! REFERENCE(S): None
229!!
230!! FLOWCHART: None
231!! \n
232!_ ==============================================================================================================================
233  SUBROUTINE routing_wrapper_main(kjit, nbpt, index, &
234       lalo, neighbours, resolution, contfrac, totfrac_nobio, veget_max, floodout, runoff, &
235       drainage, transpot, precip_rain, humrel, k_litt, flood_frac, flood_res, stempdiag, &
236       ftempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id, &
237       soiltile, root_deficit, irrigated_next, irrig_frac, fraction_aeirrig_sw) 
238
239    IMPLICIT NONE
240
241    !! 0.1 Input variables
242    INTEGER(i_std), INTENT(in)     :: kjit                 !! Time step number (unitless)
243    INTEGER(i_std), INTENT(in)     :: nbpt                 !! Domain size (unitless)
244    INTEGER(i_std),INTENT(in)      :: rest_id              !! Restart file identifier (unitless)
245    INTEGER(i_std),INTENT(in)      :: hist_id              !! Access to history file (unitless)
246    INTEGER(i_std),INTENT(in)      :: hist2_id             !! Access to history file 2 (unitless)
247    INTEGER(i_std), INTENT(in)     :: index(nbpt)          !! Indices of the points on the map (unitless)
248    REAL(r_std), INTENT(in)        :: lalo(nbpt,2)         !! Vector of latitude and longitudes (beware of the order !)
249    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)
250    REAL(r_std), INTENT(in)        :: resolution(nbpt,2)   !! The size of each grid box in X and Y (m)
251    REAL(r_std), INTENT(in)        :: contfrac(nbpt)       !! Fraction of land in each grid box (unitless;0-1)
252    REAL(r_std), INTENT(in)        :: totfrac_nobio(nbpt)  !! Total fraction of no-vegetation (continental ice, lakes ...) (unitless;0-1)
253    REAL(r_std), INTENT(in)        :: veget_max(nbpt,nvm)  !! Maximal fraction of vegetation (unitless;0-1)
254    REAL(r_std), INTENT(in)        :: floodout(nbpt)       !! Grid-point flow out of floodplains (kg/m^2/dt)
255    REAL(r_std), INTENT(in)        :: runoff(nbpt)         !! Grid-point runoff (kg/m^2/dt)
256    REAL(r_std), INTENT(in)        :: drainage(nbpt)       !! Grid-point drainage (kg/m^2/dt)
257    REAL(r_std), INTENT(in)        :: transpot(nbpt,nvm)   !! Potential transpiration of the vegetation (kg/m^2/dt)
258    REAL(r_std), INTENT(in)        :: precip_rain(nbpt)    !! Rainfall (kg/m^2/dt)
259    REAL(r_std), INTENT(in)        :: k_litt(nbpt)         !! Averaged conductivity for saturated infiltration in the 'litter' layer (kg/m^2/dt)
260    REAL(r_std), INTENT(in)        :: humrel(nbpt,nvm)     !! Soil moisture stress, root extraction potential (unitless)
261    REAL(r_std), INTENT(in)        :: stempdiag(nbpt,nslm) !! Diagnostic soil temperature profile
262    REAL(r_std), INTENT(in)        :: ftempdiag(nbpt,ngrnd)!! Diagnostic soil temperature profile over full column
263    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)
264    REAL(r_std), INTENT(in)        :: root_deficit(nbpt)   !! soil water deficit
265    REAL(r_std), INTENT(in)        :: soiltile(nbpt,nstm)  !! Fraction of each soil tile within vegtot (0-1, unitless)
266    REAL(r_std), INTENT(in)        :: irrig_frac(nbpt)     !! Irrig. fraction interpolated in routing, and saved to pass to slowproc if irrigated_soiltile = .TRUE.
267    REAL(r_std), INTENT(in)        :: irrigated_next (nbpt)!! Dynamic irrig. area, calculated in slowproc and passed to routing
268    REAL(r_std), INTENT(in)        :: fraction_aeirrig_sw(nbpt) !! Fraction of area equipped for irrigation from surface water, of irrig_frac
269
270    !! 0.2 Output variables
271    REAL(r_std), INTENT(out)       :: returnflow(nbpt)     !! The water flow from lakes and swamps which returns to the grid box.
272    !! This water will go back into the hydrol module to allow re-evaporation (kg/m^2/dt)
273    REAL(r_std), INTENT(out)       :: reinfiltration(nbpt) !! Water flow from ponds and floodplains which returns to the grid box (kg/m^2/dt)
274    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)
275    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)
276    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)
277    REAL(r_std), INTENT(out)       :: flood_frac(nbpt)     !! Flooded fraction of the grid box (unitless;0-1)
278    REAL(r_std), INTENT(out)       :: flood_res(nbpt)      !! Diagnostic of water amount in the floodplains reservoir (kg)
279
280    !_ ================================================================================================================================
281
282    !! 1. Call the main subroutine from the routing module corresponding to the choice of ROUTING_METHOD
283
284    IF (routing_method=='standard') THEN
285
286       CALL routing_main (kjit, nbpt, index, &
287            lalo, neighbours, resolution, contfrac, totfrac_nobio, veget_max, floodout, runoff, &
288            drainage, transpot, precip_rain, humrel, k_litt, flood_frac, flood_res, &
289            stempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id, &
290            soiltile, root_deficit, irrigated_next, irrig_frac, fraction_aeirrig_sw)
291
292    ELSE IF (routing_method=='highres') THEN
293
294       CALL routing_highres_main (kjit, nbpt, index, &
295            lalo, neighbours, resolution, contfrac, totfrac_nobio, veget_max, floodout, runoff, &
296            drainage, transpot, precip_rain, humrel, k_litt, flood_frac, flood_res, &
297            ftempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, rest_id, hist_id, hist2_id)
298
299    ELSE IF(routing_method=='simple') THEN
300
301       CALL routing_simple_main (kjit, nbpt, index, &
302            lalo, neighbours, resolution, contfrac, totfrac_nobio, veget_max, floodout, runoff, &
303            drainage, transpot, precip_rain, humrel, k_litt, flood_frac, flood_res, &
304            stempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, &
305            rest_id, hist_id, hist2_id) 
306
307    ELSE IF(routing_method=='native') THEN
308
309       CALL routing_native_main (kjit, nbpt, index, &
310            lalo, neighbours, resolution, contfrac, totfrac_nobio, veget_max, floodout, runoff, &
311            drainage, transpot, precip_rain, humrel, k_litt, flood_frac, flood_res, &
312            stempdiag, reinf_slope, returnflow, reinfiltration, irrigation, riverflow, coastalflow, &
313            rest_id, hist_id, hist2_id, &
314            soiltile, root_deficit, irrigated_next, irrig_frac, fraction_aeirrig_sw) 
315    ENDIF
316
317
318  END SUBROUTINE routing_wrapper_main
319
320
321!!  =============================================================================================================================
322!! SUBROUTINE:    routing_wrapper_finalize
323!!
324!>\BRIEF          Call the finalization subroutine for the choosen routing module
325!!
326!! DESCRIPTION:   Call the subroutine for finalization for the choosen routing module according to ROUTING_METHOD
327!!
328!! RECENT CHANGE(S): None
329!!
330!! REFERENCE(S): None
331!!
332!! FLOWCHART: None
333!! \n
334!_ ==============================================================================================================================
335  SUBROUTINE routing_wrapper_finalize( kjit, nbpt, rest_id, flood_frac, flood_res )
336
337    IMPLICIT NONE
338    !! 0.1 Input variables
339    INTEGER(i_std), INTENT(in)     :: kjit                 !! Time step number (unitless)
340    INTEGER(i_std), INTENT(in)     :: nbpt                 !! Domain size (unitless)
341    INTEGER(i_std),INTENT(in)      :: rest_id              !! Restart file identifier (unitless)
342    REAL(r_std), INTENT(in)        :: flood_frac(nbpt)     !! Flooded fraction of the grid box (unitless;0-1)
343    REAL(r_std), INTENT(in)        :: flood_res(nbpt)      !! Diagnostic of water amount in the floodplains reservoir (kg)
344
345    !_ ================================================================================================================================
346
347    !! 1. Call the finalization subroutine from the routing module corresponding to the choice of ROUTING_METHOD
348
349    IF (routing_method=='standard') THEN
350
351       CALL routing_finalize( kjit, nbpt, rest_id, flood_frac, flood_res )
352
353    ELSE IF (routing_method=='highres') THEN
354
355       CALL routing_highres_finalize( kjit, nbpt, rest_id, flood_frac, flood_res )
356
357    ELSE IF(routing_method=='simple') THEN
358
359       CALL routing_simple_finalize( kjit, nbpt, rest_id, flood_frac, flood_res )
360
361    ELSE IF(routing_method=='native') THEN
362
363       CALL routing_native_finalize( kjit, nbpt, rest_id, flood_frac, flood_res )
364
365    ENDIF
366
367  END SUBROUTINE routing_wrapper_finalize
368
369
370!!  =============================================================================================================================
371!! SUBROUTINE:    routing_wrapper_clear
372!!
373!>\BRIEF          Call the clear subroutine for the choosen routing module
374!!
375!! DESCRIPTION:   Call the clear subroutine for the choosen routing module according to ROUTING_METHOD
376!!
377!! RECENT CHANGE(S): None
378!!
379!! REFERENCE(S): None
380!!
381!! FLOWCHART: None
382!! \n
383!_ ==============================================================================================================================
384  SUBROUTINE routing_wrapper_clear
385
386    IF (routing_method=='standard') THEN
387
388       CALL routing_clear
389
390    ELSE IF (routing_method=='highres') THEN
391
392       CALL routing_highres_clear
393
394    ELSE IF(routing_method=='simple') THEN
395
396       CALL routing_simple_clear
397   
398    ELSE IF(routing_method=='native') THEN
399
400       CALL routing_native_clear
401    ENDIF
402
403  END SUBROUTINE routing_wrapper_clear
404
405END MODULE routing_wrapper
Note: See TracBrowser for help on using the repository browser.