diff --git a/DESCRIPTION b/DESCRIPTION
index 892dd5b154ae5f88ac2193bcbdacf19126a3478a..6c0b84d88d8674f7ad6f395e55e00e52f770ce64 100644
--- a/DESCRIPTION
+++ b/DESCRIPTION
@@ -1,8 +1,8 @@
 Package: airGR
 Type: Package
 Title: Suite of GR Hydrological Models for Precipitation-Runoff Modelling
-Version: 1.0.9.42
-Date: 2017-09-07
+Version: 1.0.9.43
+Date: 2017-09-12
 Authors@R: c(
   person("Laurent", "Coron", role = c("aut", "trl")),
   person("Charles", "Perrin", role = c("aut", "ths")),
diff --git a/R/RunModel_CemaNeigeGR6J.R b/R/RunModel_CemaNeigeGR6J.R
index 24f7224bfcf4c0f7cb0582a86dbe1f939645250e..0bbef76f9cbb9e1f9d9fea39e874ac6b329d43ff 100644
--- a/R/RunModel_CemaNeigeGR6J.R
+++ b/R/RunModel_CemaNeigeGR6J.R
@@ -3,7 +3,7 @@ RunModel_CemaNeigeGR6J <- function(InputsModel,RunOptions,Param){
     NParam <- 8;
     FortranOutputsCemaNeige <- c("Pliq","Psol","SnowPack","ThermalState","Gratio","PotMelt","Melt","PliqAndMelt", "Temp");
     FortranOutputsMod       <- c("PotEvap", "Precip", "Prod", "Pn", "Ps", "AE", "Perc", "PR", "Q9", "Q1",
-			"Rout", "Exch", "AExch1", "AExch2", "AExch", "QR", "QR1", "Exp", "QD", "Qsim");
+			"Rout", "Exch", "AExch1", "AExch2", "AExch", "QR", "QRExp", "Exp", "QD", "Qsim");
 
     ##Arguments_check
       if(inherits(InputsModel,"InputsModel")==FALSE){ stop("InputsModel must be of class 'InputsModel' \n"); return(NULL); }  
diff --git a/R/RunModel_GR6J.R b/R/RunModel_GR6J.R
index d65e80a483cca688c1ced82d74883e06acd9f859..5014ba4807db1f51a0a4be98a460a17679eca812 100644
--- a/R/RunModel_GR6J.R
+++ b/R/RunModel_GR6J.R
@@ -2,7 +2,7 @@ RunModel_GR6J <- function(InputsModel,RunOptions,Param){
 
     NParam <- 6;
     FortranOutputs <- c("PotEvap", "Precip", "Prod", "Pn", "Ps", "AE", "Perc", "PR", "Q9", "Q1",
-			"Rout", "Exch", "AExch1", "AExch2", "AExch", "QR", "QR1", "Exp", "QD", "Qsim");
+			"Rout", "Exch", "AExch1", "AExch2", "AExch", "QR", "QRExp", "Exp", "QD", "Qsim");
 
     ##Arguments_check
       if(inherits(InputsModel,"InputsModel")==FALSE){ stop("InputsModel must be of class 'InputsModel' \n"); return(NULL); }  
diff --git a/man/RunModel_CemaNeigeGR6J.Rd b/man/RunModel_CemaNeigeGR6J.Rd
index c7819ee8a9be21ed6e772c2c97c0895bb3f10e5a..2f3c8410bce75a6d1b7926ccf1217e7a4d47b69a 100644
--- a/man/RunModel_CemaNeigeGR6J.Rd
+++ b/man/RunModel_CemaNeigeGR6J.Rd
@@ -19,15 +19,15 @@ RunModel_CemaNeigeGR6J(InputsModel, RunOptions, Param)
 \item{RunOptions}{[object of class \emph{RunOptions}] see \code{\link{CreateRunOptions}} for details}
 
 \item{Param}{[numeric] vector of 8 parameters
-\tabular{ll}{                                                                      
-GR6J X1      \tab production store capacity [mm]                                \cr
-GR6J X2      \tab intercatchment exchange coefficient [mm/d]                  \cr
-GR6J X3      \tab routing store capacity [mm]                                   \cr
-GR6J X4      \tab unit hydrograph time constant [d]                             \cr
-GR6J X5      \tab intercatchment exchange threshold [-]                     \cr
-GR6J X6      \tab coefficient for emptying exponential store [mm]               \cr
-CemaNeige X1 \tab weighting coefficient for snow pack thermal state [-]         \cr
-CemaNeige X2 \tab degree-day melt coefficient [mm/°C/d]                       \cr
+\tabular{ll}{                                                                  
+GR6J X1      \tab production store capacity [mm]                        \cr
+GR6J X2      \tab intercatchment exchange coefficient [mm/d]            \cr
+GR6J X3      \tab routing store capacity [mm]                           \cr
+GR6J X4      \tab unit hydrograph time constant [d]                     \cr
+GR6J X5      \tab intercatchment exchange threshold [-]                 \cr
+GR6J X6      \tab coefficient for emptying exponential store [mm]       \cr
+CemaNeige X1 \tab weighting coefficient for snow pack thermal state [-] \cr
+CemaNeige X2 \tab degree-day melt coefficient [mm/°C/d]                 \cr
 }}
 }
 
@@ -35,37 +35,37 @@ CemaNeige X2 \tab degree-day melt coefficient [mm/°C/d]                       \
 \value{
 [list] list containing the function outputs organised as follows:                                         
          \tabular{ll}{                                                                                         
-         \emph{$DatesR  }          \tab [POSIXlt] series of dates                                                     \cr
-         \emph{$PotEvap }          \tab [numeric] series of input potential evapotranspiration [mm/d]                 \cr
-         \emph{$Precip  }          \tab [numeric] series of input total precipitation [mm/d]                          \cr
-         \emph{$Prod    }          \tab [numeric] series of production store level [mm]                        \cr
-         \emph{$Pn      }          \tab [numeric] series of net rainfall [mm/d]                         			  \cr
-         \emph{$Ps      }          \tab [numeric] series of the part of Ps filling the production store [mm/d]        \cr
-         \emph{$AE      }          \tab [numeric] series of actual evapotranspiration [mm/d]                          \cr
-         \emph{$Perc    }          \tab [numeric] series of percolation (PERC) [mm/d]                                 \cr
-         \emph{$PR      }          \tab [numeric] series of PR=PN-PS+PERC [mm/d]                                      \cr
-         \emph{$Q9      }          \tab [numeric] series of UH1 outflow (Q9) [mm/d]                                   \cr
-         \emph{$Q1      }          \tab [numeric] series of UH2 outflow (Q1) [mm/d]                                   \cr
-         \emph{$Rout    }          \tab [numeric] series of routing store level [mm]                           \cr
-         \emph{$Exch    }          \tab [numeric] series of potential semi-exchange between catchments [mm/d]         \cr
-         \emph{$AExch1  }          \tab [numeric] series of actual exchange between catchments for branch 1 [mm/d]    \cr
-         \emph{$AExch2  }          \tab [numeric] series of actual exchange between catchments for branch 2 [mm/d]    \cr
-         \emph{$AExch   }          \tab [numeric] series of actual exchange between catchments (1+2) [mm/d]           \cr
-         \emph{$QR      }          \tab [numeric] series of routing store outflow (QR) [mm/d]                         \cr
-         \emph{$QR1     }          \tab [numeric] series of exponential store outflow (QR1) [mm/d]                    \cr
-         \emph{$Exp     }          \tab [numeric] series of exponential store level (negative) [mm]            \cr
-         \emph{$QD      }          \tab [numeric] series of direct flow from UH2 after exchange (QD) [mm/d]           \cr
-         \emph{$Qsim    }          \tab [numeric] series of Qsim [mm/d]                                               \cr
-         \emph{$CemaNeigeLayers}   \tab [list] list of CemaNeige outputs (1 list per layer)                          \cr
-         \emph{$CemaNeigeLayers[[iLayer]]$Pliq         }   \tab [numeric] series of liquid precip. [mm/d]                          \cr
-         \emph{$CemaNeigeLayers[[iLayer]]$Psol         }   \tab [numeric] series of solid precip. [mm/d]                           \cr
-         \emph{$CemaNeigeLayers[[iLayer]]$SnowPack     }   \tab [numeric] series of snow pack [mm]                                 \cr
-         \emph{$CemaNeigeLayers[[iLayer]]$ThermalState }   \tab [numeric] series of snow pack thermal state [°C]                 \cr
-         \emph{$CemaNeigeLayers[[iLayer]]$Gratio       }   \tab [numeric] series of Gratio [0-1]                                   \cr
-         \emph{$CemaNeigeLayers[[iLayer]]$PotMelt      }   \tab [numeric] series of potential snow melt [mm/d]                     \cr
-         \emph{$CemaNeigeLayers[[iLayer]]$Melt         }   \tab [numeric] series of actual snow melt [mm/d]                        \cr
-         \emph{$CemaNeigeLayers[[iLayer]]$PliqAndMelt  }   \tab [numeric] series of liquid precip. + actual snow melt [mm/d]       \cr
-         \emph{$CemaNeigeLayers[[iLayer]]$Temp         }   \tab [numeric] series of air temperature [°C] \cr
+         \emph{$DatesR }          \tab [POSIXlt] series of dates                                                           \cr
+         \emph{$PotEvap}          \tab [numeric] series of input potential evapotranspiration [mm/d]                       \cr
+         \emph{$Precip }          \tab [numeric] series of input total precipitation [mm/d]                                \cr
+         \emph{$Prod   }          \tab [numeric] series of production store level [mm]                                     \cr
+         \emph{$Pn     }          \tab [numeric] series of net rainfall [mm/d]                         			               \cr
+         \emph{$Ps     }          \tab [numeric] series of the part of Ps filling the production store [mm/d]              \cr
+         \emph{$AE     }          \tab [numeric] series of actual evapotranspiration [mm/d]                                \cr
+         \emph{$Perc   }          \tab [numeric] series of percolation (PERC) [mm/d]                                       \cr
+         \emph{$PR     }          \tab [numeric] series of PR=PN-PS+PERC [mm/d]                                            \cr
+         \emph{$Q9     }          \tab [numeric] series of UH1 outflow (Q9) [mm/d]                                         \cr
+         \emph{$Q1     }          \tab [numeric] series of UH2 outflow (Q1) [mm/d]                                         \cr
+         \emph{$Rout   }          \tab [numeric] series of routing store level [mm]                                        \cr
+         \emph{$Exch   }          \tab [numeric] series of potential semi-exchange between catchments [mm/d]               \cr
+         \emph{$AExch1 }          \tab [numeric] series of actual exchange between catchments for branch 1 [mm/d]          \cr
+         \emph{$AExch2 }          \tab [numeric] series of actual exchange between catchments for branch 2 [mm/d]          \cr
+         \emph{$AExch  }          \tab [numeric] series of actual exchange between catchments (1+2) [mm/d]                 \cr
+         \emph{$QR     }          \tab [numeric] series of routing store outflow (QR) [mm/d]                               \cr
+         \emph{$QRExp  }          \tab [numeric] series of exponential store outflow (QRExp) [mm/d]                        \cr
+         \emph{$Exp    }          \tab [numeric] series of exponential store level (negative) [mm]                         \cr
+         \emph{$QD     }          \tab [numeric] series of direct flow from UH2 after exchange (QD) [mm/d]                 \cr
+         \emph{$Qsim   }          \tab [numeric] series of Qsim [mm/d]                                                     \cr
+         \emph{$CemaNeigeLayers}   \tab [list] list of CemaNeige outputs (1 list per layer)                                \cr
+         \emph{$CemaNeigeLayers[[iLayer]]$Pliq        }   \tab [numeric] series of liquid precip. [mm/d]                   \cr
+         \emph{$CemaNeigeLayers[[iLayer]]$Psol        }   \tab [numeric] series of solid precip. [mm/d]                    \cr
+         \emph{$CemaNeigeLayers[[iLayer]]$SnowPack    }   \tab [numeric] series of snow pack [mm]                          \cr
+         \emph{$CemaNeigeLayers[[iLayer]]$ThermalState}   \tab [numeric] series of snow pack thermal state [°C]            \cr
+         \emph{$CemaNeigeLayers[[iLayer]]$Gratio      }   \tab [numeric] series of Gratio [0-1]                            \cr
+         \emph{$CemaNeigeLayers[[iLayer]]$PotMelt     }   \tab [numeric] series of potential snow melt [mm/d]              \cr
+         \emph{$CemaNeigeLayers[[iLayer]]$Melt        }   \tab [numeric] series of actual snow melt [mm/d]                 \cr
+         \emph{$CemaNeigeLayers[[iLayer]]$PliqAndMelt }   \tab [numeric] series of liquid precip. + actual snow melt [mm/d]\cr
+         \emph{$CemaNeigeLayers[[iLayer]]$Temp        }   \tab [numeric] series of air temperature [°C]                    \cr
          \emph{$StateEnd}                                  \tab [numeric] states at the end of the run: \cr\tab store & unit hydrographs levels [mm], CemaNeige states [mm & °C], \cr\tab see \code{\link{CreateIniStates}} for more details \cr
          }                                                                                                     
          (refer to the provided references or to the package source code for further details on these model outputs)
diff --git a/man/RunModel_GR6J.Rd b/man/RunModel_GR6J.Rd
index 2afb073471ab3a15b8ab7a260e9737c3df40de67..9b357de00e37c8c2b161ff17daa8408455df8057 100644
--- a/man/RunModel_GR6J.Rd
+++ b/man/RunModel_GR6J.Rd
@@ -19,13 +19,13 @@ RunModel_GR6J(InputsModel, RunOptions, Param)
 \item{RunOptions}{[object of class \emph{RunOptions}] see \code{\link{CreateRunOptions}} for details}
 
 \item{Param}{[numeric] vector of 6 parameters
-\tabular{ll}{                                                                      
-GR6J X1      \tab production store capacity [mm]                                \cr
-GR6J X2      \tab intercatchment exchange coefficient [mm/d]                  \cr
-GR6J X3      \tab routing store capacity [mm]                                   \cr
-GR6J X4      \tab unit hydrograph time constant [d]                             \cr
-GR6J X5      \tab intercatchment exchange threshold [-]                     \cr
-GR6J X6      \tab coefficient for emptying exponential store [mm]                \cr
+\tabular{ll}{                                                            
+GR6J X1      \tab production store capacity [mm]                  \cr
+GR6J X2      \tab intercatchment exchange coefficient [mm/d]      \cr
+GR6J X3      \tab routing store capacity [mm]                     \cr
+GR6J X4      \tab unit hydrograph time constant [d]               \cr
+GR6J X5      \tab intercatchment exchange threshold [-]           \cr
+GR6J X6      \tab coefficient for emptying exponential store [mm] \cr
 }}
 }
 
@@ -36,22 +36,22 @@ GR6J X6      \tab coefficient for emptying exponential store [mm]
          \emph{$DatesR  }          \tab [POSIXlt] series of dates                                                     \cr
          \emph{$PotEvap }          \tab [numeric] series of input potential evapotranspiration [mm/d]                 \cr
          \emph{$Precip  }          \tab [numeric] series of input total precipitation [mm/d]                          \cr
-         \emph{$Prod    }          \tab [numeric] series of production store level [mm]                        \cr
-         \emph{$Pn      }          \tab [numeric] series of net rainfall [mm/d]                         			  \cr
+         \emph{$Prod    }          \tab [numeric] series of production store level [mm]                               \cr
+         \emph{$Pn      }          \tab [numeric] series of net rainfall [mm/d]                         			        \cr
          \emph{$Ps      }          \tab [numeric] series of the part of Pn filling the production store [mm/d]        \cr
          \emph{$AE      }          \tab [numeric] series of actual evapotranspiration [mm/d]                          \cr
          \emph{$Perc    }          \tab [numeric] series of percolation (PERC) [mm/d]                                 \cr
          \emph{$PR      }          \tab [numeric] series of PR=Pn-Ps+Perc [mm/d]                                      \cr
          \emph{$Q9      }          \tab [numeric] series of UH1 outflow (Q9) [mm/d]                                   \cr
          \emph{$Q1      }          \tab [numeric] series of UH2 outflow (Q1) [mm/d]                                   \cr
-         \emph{$Rout    }          \tab [numeric] series of routing store level [mm]                           \cr
+         \emph{$Rout    }          \tab [numeric] series of routing store level [mm]                                  \cr
          \emph{$Exch    }          \tab [numeric] series of potential semi-exchange between catchments [mm/d]         \cr
          \emph{$AExch1  }          \tab [numeric] series of actual exchange between catchments for branch 1 [mm/d]    \cr
          \emph{$AExch2  }          \tab [numeric] series of actual exchange between catchments for branch 2 [mm/d]    \cr
          \emph{$AExch   }          \tab [numeric] series of actual exchange between catchments (1+2) [mm/d]           \cr
          \emph{$QR      }          \tab [numeric] series of routing store outflow (QR) [mm/d]                         \cr
-         \emph{$QR1     }          \tab [numeric] series of exponential store outflow (QR1) [mm/d]                    \cr
-         \emph{$Exp     }          \tab [numeric] series of exponential store level (negative) [mm]            \cr
+         \emph{$QRExp   }          \tab [numeric] series of exponential store outflow (QRExp) [mm/d]                  \cr
+         \emph{$Exp     }          \tab [numeric] series of exponential store level (negative) [mm]                   \cr
          \emph{$QD      }          \tab [numeric] series of direct flow from UH2 after exchange (QD) [mm/d]           \cr
          \emph{$Qsim    }          \tab [numeric] series of Qsim [mm/d]                                               \cr
          \emph{$StateEnd}          \tab [numeric] states at the end of the run (res. levels, UH1 levels, UH2 levels) [mm], \cr\tab see \code{\link{CreateIniStates}} for more details \cr
diff --git a/src/frun_GR6J.f b/src/frun_GR6J.f
index 40e316d9a50be55b43f48ed7f8f915723ec5965a..0c331a03ccc49da688560bb2bd5f11d12f1653bc 100644
--- a/src/frun_GR6J.f
+++ b/src/frun_GR6J.f
@@ -153,7 +153,7 @@ C**********************************************************************
       DOUBLEPRECISION MISC(NMISC)
       DOUBLEPRECISION P1,E,Q
       DOUBLEPRECISION A,B,C,EN,ER,PN,PR,PS,WS,tanHyp,AR
-      DOUBLEPRECISION PERC,PRUH1,PRUH2,EXCH,QR,QD,QR1
+      DOUBLEPRECISION PERC,PRUH1,PRUH2,EXCH,QR,QD,QRExp
       DOUBLEPRECISION AE,AEXCH1,AEXCH2
       INTEGER K
 
@@ -257,19 +257,19 @@ C Update of exponential store
       IF(AR.LT.-33.)AR=-33.
 
       IF(AR.GT.7.)THEN
-      QR1=St(3)+Param(6)/EXP(AR)
+      QRExp=St(3)+Param(6)/EXP(AR)
       GOTO 3
       ENDIF
 
       IF(AR.LT.-7.)THEN
-      QR1=Param(6)*EXP(AR)
+      QRExp=Param(6)*EXP(AR)
       GOTO 3
       ENDIF
 
-      QR1=Param(6)*LOG(EXP(AR)+1.)
+      QRExp=Param(6)*LOG(EXP(AR)+1.)
     3 CONTINUE
 
-      St(3)=St(3)-QR1
+      St(3)=St(3)-QRExp
 
 C Runoff from direct branch QD
       AEXCH2=EXCH
@@ -277,30 +277,30 @@ C Runoff from direct branch QD
       QD=MAX(0.d0,StUH2(1)+EXCH)
 
 C Total runoff
-      Q=QR+QD+QR1
+      Q=QR+QD+QRExp
       IF(Q.LT.0.) Q=0.
 
 C 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]
-      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]
-      MISC( 9)=StUH1(1)      ! Q9     ! outflow from UH1 (Q9) [mm/day]
-      MISC(10)=StUH2(1)      ! Q1     ! outflow from UH2 (Q1) [mm/day]
-      MISC(11)=St(2)         ! Rout   ! routing store level (St(2)) [mm]
-      MISC(12)=EXCH          ! Exch   ! potential third-exchange between catchments (EXCH) [mm/day]
-      MISC(13)=AEXCH1 		 ! AExch1 ! actual exchange between catchments from routing store (AEXCH1) [mm/day]
-      MISC(14)=AEXCH2        ! AExch2 ! actual exchange between catchments from direct branch (after UH2) (AEXCH2) [mm/day]
+      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]
+      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]
+      MISC( 9)=StUH1(1)           ! Q9     ! outflow from UH1 (Q9) [mm/day]
+      MISC(10)=StUH2(1)           ! Q1     ! outflow from UH2 (Q1) [mm/day]
+      MISC(11)=St(2)              ! Rout   ! routing store level (St(2)) [mm]
+      MISC(12)=EXCH               ! Exch   ! potential third-exchange between catchments (EXCH) [mm/day]
+      MISC(13)=AEXCH1 		        ! AExch1 ! actual exchange between catchments from routing store (AEXCH1) [mm/day]
+      MISC(14)=AEXCH2             ! AExch2 ! actual exchange between catchments from direct branch (after UH2) (AEXCH2) [mm/day]
       MISC(15)=AEXCH1+AEXCH2+EXCH ! AExch  ! actual total exchange between catchments (AEXCH1+AEXCH2+EXCH) [mm/day]
-      MISC(16)=QR            ! QR     ! outflow from routing store (QR) [mm/day]
-      MISC(17)=QR1           ! QR1    ! outflow from exponential store (QR1) [mm/day]
-      MISC(18)=St(3)         ! Exp    ! exponential store level (St(3)) (negative) [mm]
-      MISC(19)=QD            ! QD     ! outflow from UH2 branch after exchange (QD) [mm/day]
-      MISC(20)=Q             ! Qsim   ! simulated outflow at catchment outlet [mm/day]
+      MISC(16)=QR                 ! QR     ! outflow from routing store (QR) [mm/day]
+      MISC(17)=QRExp              ! QRExp  ! outflow from exponential store (QRExp) [mm/day]
+      MISC(18)=St(3)              ! Exp    ! exponential store level (St(3)) (negative) [mm]
+      MISC(19)=QD                 ! QD     ! outflow from UH2 branch after exchange (QD) [mm/day]
+      MISC(20)=Q                  ! Qsim   ! simulated outflow at catchment outlet [mm/day]
 
 
       ENDSUBROUTINE