Newer
Older
Delaigue Olivier
committed
!------------------------------------------------------------------------------
! Subroutines relative to the annual GR5J model
!------------------------------------------------------------------------------
! TITLE : airGR
! PROJECT : airGR
! FILE : frun_GR5J.f
!------------------------------------------------------------------------------
! AUTHORS
! Original code: N. Le Moine
! Cleaning and formatting for airGR: L. Coron
! Further cleaning: G. Thirel
!------------------------------------------------------------------------------
! Creation date: 2006
! Last modified: 25/11/2019
Delaigue Olivier
committed
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
!------------------------------------------------------------------------------
! REFERENCES
! Le Moine, N. (2008). Le bassin versant de surface vu par le souterrain : une
! voie d'amélioration des performances et du réalisme des modèles
! pluie-débit ? PhD thesis (French), UPMC, Paris, France.
!
! Pushpalatha, R., C. Perrin, N. Le Moine, T. Mathevet, and V. Andréassian
! (2011). A downward structural sensitivity analysis of hydrological models to
! improve low-flow simulation. Journal of Hydrology, 411(1-2), 66-76.
! doi:10.1016/j.jhydrol.2011.09.034.
!------------------------------------------------------------------------------
! Quick description of public procedures:
! 1. frun_gr5j
! 2. MOD_GR5J
!------------------------------------------------------------------------------
SUBROUTINE frun_gr5j(LInputs,InputsPrecip,InputsPE,NParam,Param,
& NStates,StateStart,NOutputs,IndOutputs,
& Outputs,StateEnd)
! Subroutine that initializes GR5J, get its parameters, performs the call
! to the MOD_GR5J subroutine at each time step, and stores the final states
! Inputs
! LInputs ! Integer, length of input and output series
! InputsPrecip ! Vector of real, input series of total precipitation [mm/day]
! InputsPE ! Vector of real, input series of potential evapotranspiration (PE) [mm/day]
! NParam ! Integer, number of model parameters
! Param ! Vector of real, parameter set
! NStates ! Integer, number of state variables
! StateStart ! Vector of real, state variables used when the model run starts (store levels [mm] and Unit Hydrograph (UH) storages [mm])
! NOutputs ! Integer, number of output series
! IndOutputs ! Vector of integer, indices of output series
! Outputs
! Outputs ! Vector of real, output series
! StateEnd ! Vector of real, state variables at the end of the model run (store levels [mm] and Unit Hydrograph (UH) storages [mm])
Delaigue Olivier
committed
!DEC$ ATTRIBUTES DLLEXPORT :: frun_gr5j
Delaigue Olivier
committed
!! dummies
! in
integer, intent(in) :: LInputs,NParam,NStates,NOutputs
Delaigue Olivier
committed
doubleprecision, dimension(LInputs), intent(in) :: InputsPrecip
doubleprecision, dimension(LInputs), intent(in) :: InputsPE
doubleprecision, dimension(NParam), intent(in) :: Param
doubleprecision, dimension(NStates), intent(in) :: StateStart
integer, dimension(NOutputs), intent(in) :: IndOutputs
! out
doubleprecision, dimension(NStates), intent(out) :: StateEnd
doubleprecision, dimension(LInputs,NOutputs),
& intent(out) :: Outputs
!! locals
integer :: I,K
integer, parameter :: NH=20,NMISC=30
doubleprecision, dimension(2) :: St
doubleprecision, dimension(2*NH) :: StUH2, OrdUH2
doubleprecision, dimension(NMISC) :: MISC
doubleprecision :: D,P1,E,Q
!--------------------------------------------------------------
! Initializations
!--------------------------------------------------------------
! initialization of model states to zero
! initialization of model states using StateStart
Delaigue Olivier
committed
St(1) = StateStart(1)
St(2) = StateStart(2)
StUH2(I)=StateStart(7+NH+I)
! parameter values
! Param(1) : production store capacity (X1 - PROD) [mm]
! Param(2) : intercatchment exchange coefficient (X2 - CES1) [mm/d]
! Param(3) : routing store capacity (X3 - ROUT) [mm]
! Param(4) : time constant of unit hydrograph (X4 - TB) [day]
! Param(5) : intercatchment exchange threshold (X5 - CES2) [-]
Delaigue Olivier
committed
OrdUH2 = 0.
! initialization of model outputs
! StateEnd = -999.999 !initialization made in R
! Outputs = -999.999 !initialization made in R
!--------------------------------------------------------------
!--------------------------------------------------------------
DO k=1,LInputs
P1=InputsPrecip(k)
E =InputsPE(k)
! Q = -999.999
! MISC = -999.999
! model run on one time step
CALL MOD_GR5J(St,StUH2,OrdUH2,Param,P1,E,Q,MISC)
! storage of outputs
Outputs(k,I)=MISC(IndOutputs(I))
! model states at the end of the run
Delaigue Olivier
committed
StateEnd(1) = St(1)
StateEnd(2) = St(2)
StateEnd(7+NH+K)=StUH2(K)
ENDDO
RETURN
ENDSUBROUTINE
!################################################################################################################################
!**********************************************************************
SUBROUTINE MOD_GR5J(St,StUH2,OrdUH2,Param,P1,E,Q,
&MISC)
Delaigue Olivier
committed
! Calculation of streamflow on a single time step (day) with the GR5J model
Delaigue Olivier
committed
! St Vector of real, model states in stores at the beginning of the time step [mm]
! StUH2 Vector of real, model states in Unit Hydrograph 2 at the beginning of the time step [mm]
! OrdUH2 Vector of real, ordinates in UH2 [-]
! Param Vector of real, model parameters [various units]
! P1 Real, value of rainfall during the time step [mm]
! E Real, value of potential evapotranspiration during the time step [mm]
Delaigue Olivier
committed
! St Vector of real, model states in stores at the end of the time step [mm]
! StUH2 Vector of real, model states in Unit Hydrograph 2 at the end of the time step [mm]
! Q Real, value of simulated flow at the catchment outlet for the time step [mm/day]
! MISC Vector of real, model outputs for the time step [mm or mm/day]
!**********************************************************************
Delaigue Olivier
committed
!! locals
integer, parameter :: NParam=5,NMISC=30,NH=20
Delaigue Olivier
committed
doubleprecision :: A,EN,ER,PN,PR,PS,WS,tanHyp
Delaigue Olivier
committed
doubleprecision :: PERC,EXCH,QR,QD,Q1,Q9
doubleprecision :: AE,AEXCH1,AEXCH2
integer :: K
Delaigue Olivier
committed
doubleprecision, parameter :: B=0.9
doubleprecision, parameter :: stored_val=25.62890625
Delaigue Olivier
committed
doubleprecision :: expWS, TWS, Sr, Rr ! speed-up
Delaigue Olivier
committed
!! dummies
! in
doubleprecision, dimension(NParam), intent(in) :: Param
doubleprecision, intent(in) :: P1,E
doubleprecision, dimension(2*NH), intent(inout) :: OrdUH2
! inout
doubleprecision, dimension(2), intent(inout) :: St
doubleprecision, dimension(2*NH), intent(inout) :: StUH2
! out
doubleprecision, intent(out) :: Q
doubleprecision, dimension(NMISC), intent(out) :: MISC
! Interception and production store
EN=E-P1
PN=0.
WS=EN/A
IF(WS.GT.13.) WS=13.
Delaigue Olivier
committed
! speed-up
Delaigue Olivier
committed
expWS = exp(2.*WS)
TWS = (expWS - 1.)/(expWS + 1.)
Delaigue Olivier
committed
Sr = St(1)/A
ER=St(1)*(2.-Sr)*TWS/(1.+(1.-Sr)*TWS)
! ER=X(2)*(2.-X(2)/A)*tanHyp(WS)/(1.+(1.-X(2)/A)*tanHyp(WS))
Delaigue Olivier
committed
AE=ER+P1
St(1)=St(1)-ER
PS=0.
PR=0.
Delaigue Olivier
committed
EN=0.
AE=E
PN=P1-E
WS=PN/A
IF(WS.GT.13.) WS=13.
Delaigue Olivier
committed
! speed-up
Delaigue Olivier
committed
expWS = exp(2.*WS)
TWS = (expWS - 1.)/(expWS + 1.)
Delaigue Olivier
committed
Sr = St(1)/A
PS=A*(1.-Sr*Sr)*TWS/(1.+Sr*TWS)
! PS=A*(1.-(X(2)/A)**2.)*tanHyp(WS)/(1.+X(2)/A*tanHyp(WS))
Delaigue Olivier
committed
PR=PN-PS
St(1)=St(1)+PS
! Percolation from production store
IF(St(1).LT.0.) St(1)=0.
Delaigue Olivier
committed
Delaigue Olivier
committed
! speed-up
! (9/4)**4 = 25.62890625 = stored_val
Delaigue Olivier
committed
Sr = St(1)/Param(1)
Sr = Sr * Sr
Sr = Sr * Sr
PERC=St(1)*(1.-1./SQRT(SQRT(1.+Sr/stored_val)))
Delaigue Olivier
committed
! PERC=X(2)*(1.-(1.+(X(2)/(9./4.*Param(1)))**4.)**(-0.25))
Delaigue Olivier
committed
! Convolution of unit hydrograph UH2
DO K=1,MAX(1,MIN(2*NH-1,2*INT(Param(4)+1.)))
Delaigue Olivier
committed
StUH2(K)=StUH2(K+1)+OrdUH2(K)*PR
! Split of unit hydrograph first component into the two routing components
Q9=StUH2(1)*B
Q1=StUH2(1)*(1.-B)
! Potential intercatchment semi-exchange
EXCH=Param(2)*(St(2)/Param(3)-Param(5))
! Routing store
IF((St(2)+Q9+EXCH).LT.0.) AEXCH1=-St(2)-Q9
IF(St(2).LT.0.) St(2)=0.
Delaigue Olivier
committed
Delaigue Olivier
committed
! speed-up
Rr = St(2)/Param(3)
Rr = Rr * Rr
Rr = Rr * Rr
QR = St(2)*(1.-1./SQRT(SQRT(1.+Rr)))
Delaigue Olivier
committed
! QR=X(1)*(1.-(1.+(X(1)/Param(3))**4.)**(-1./4.))
Delaigue Olivier
committed
! Runoff from direct branch QD
IF((Q1+EXCH).LT.0.) AEXCH2=-Q1
QD=MAX(0.d0,Q1+EXCH)
! Variables storage
MISC( 1)=E ! PE ! observed potential evapotranspiration [mm/day]
MISC( 2)=P1 ! Precip ! observed total precipitation [mm/day]
MISC( 3)=St(1) ! Prod ! production store level (St(1)) [mm]
unknown
committed
MISC( 4)=PN ! Pn ! net rainfall [mm/day]
MISC( 5)=PS ! Ps ! part of Ps filling the production store [mm/day]
MISC( 6)=AE ! AE ! actual evapotranspiration [mm/day]
MISC( 7)=PERC ! Perc ! percolation (PERC) [mm/day]
MISC( 8)=PR ! PR ! PR=PN-PS+PERC [mm/day]
Delaigue Olivier
committed
MISC( 9)=Q9 ! Q9 ! outflow from UH1 (Q9) [mm/day]
MISC(10)=Q1 ! Q1 ! outflow from UH2 (Q1) [mm/day]
unknown
committed
MISC(11)=St(2) ! Rout ! routing store level (St(2)) [mm]
MISC(12)=EXCH ! Exch ! potential semi-exchange between catchments (EXCH) [mm/day]
Delaigue Olivier
committed
MISC(13)=AEXCH1 ! AExch1 ! actual exchange between catchments from branch 1 (AEXCH1) [mm/day]
unknown
committed
MISC(14)=AEXCH2 ! AExch2 ! actual exchange between catchments from branch 2 (AEXCH2) [mm/day]
MISC(15)=AEXCH1+AEXCH2 ! AExch ! actual total exchange between catchments (AEXCH1+AEXCH2) [mm/day]
MISC(16)=QR ! QR ! outflow from routing store (QR) [mm/day]
MISC(17)=QD ! QD ! outflow from UH2 branch after exchange (QD) [mm/day]
MISC(18)=Q ! Qsim ! simulated outflow at catchment outlet [mm/day]