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

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

Integration of temperature of water in highres routing scheme. Done by Jan Polcer and Lucia Rinchiuso

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