diff --git a/R/get_result.R b/R/get_result.R
index f4f358262ce9935ae82922d4aadb80000c5810ae..b73a0eeb9e55e90343e3b71beb586656d3265424 100644
--- a/R/get_result.R
+++ b/R/get_result.R
@@ -4,7 +4,15 @@
 #' @param filters [character] conditions to select columns in result table, see details
 #' @param m [matrix] of results produced by [read_bin_result_matrix]
 #'
-#' @return [matrix] of results with columns selected by `filters`.
+#' @return [matrix] of results with a first column "t" with the simulation time
+#' in seconds followed by columns selected by `filters`.
+#'
+#' Column names are a concatenation of nested SIC model elements separated by
+#' the character "|" and numbered after the character ":". The variable is
+#' represented by the item "var".
+#' For example, water elevation in the first section of the first reach is:
+#' "bf:1|sn:1|var:Z".
+#'
 #' @export
 #' @import magrittr
 #'
@@ -26,6 +34,24 @@ get_result <- function(cfg,
     df_col %<>% tidyquery::query(paste("SELECT * WHERE", filters))
   }
   m <- m[, df_col$col, drop = FALSE]
+
+  # Compute time column
+  x <- read_xml(cfg$project$path)
+  xpath <-
+    sprintf("/Reseau/Flu[@nScenario=%d]/ListeRes/Res[@nVar=%d]",
+            scenario,
+            variant)
+  x_res <- xml_find_first(x, xpath)
+  attrs <- paste0("Tps", c("Debut", "Pas", "Sauv", "Fin"))
+  names(attrs) <- attrs
+  time_prms <- sapply(attrs, function(attr) {
+    as.numeric(xml_attr(x_res, attr))
+  })
+  tms <- seq(from = time_prms["TpsDebut"],
+             to = time_prms["TpsFin"],
+             by = time_prms["TpsPas"] * time_prms["TpsSauv"])
+
+  # set column names
   column_names <- sapply(seq_len(nrow(df_col)),
                    function(i) {
                      df_col$col <- NULL
@@ -40,7 +66,10 @@ get_result <- function(cfg,
                      cols[sapply(cols, is.null)] <- NULL
                      paste(cols, collapse = "|")
                    })
-  colnames(m) <- column_names
+
+  m <- cbind(tms, m)
+  colnames(m) <- c("t", column_names)
+
   return(m)
 }
 
diff --git a/man/get_result.Rd b/man/get_result.Rd
index 2d4dd7b38fe517eb89d0efa1e49323d0e6b36282..5d02c20a0134fdf3578d47b4f884f0412ad6f5b1 100644
--- a/man/get_result.Rd
+++ b/man/get_result.Rd
@@ -24,7 +24,14 @@ get_result(
 \item{m}{\link{matrix} of results produced by \link{read_bin_result_matrix}}
 }
 \value{
-\link{matrix} of results with columns selected by \code{filters}.
+\link{matrix} of results with a first column "t" with the simulation time
+in seconds followed by columns selected by \code{filters}.
+
+Column names are a concatenation of nested SIC model elements separated by
+the character "|" and numbered after the character ":". The variable is
+represented by the item "var".
+For example, water elevation in the first section of the first reach is:
+"bf:1|sn:1|var:Z".
 }
 \description{
 Get a selection of variables from a simulation result
diff --git a/tests/testthat/test-get_result.R b/tests/testthat/test-get_result.R
index 36407e676f42910ab2a7a4e03a5cf8fd895542a2..63b3010fbf58b136dfd86c1db83a9e9ea6ad5df2 100644
--- a/tests/testthat/test-get_result.R
+++ b/tests/testthat/test-get_result.R
@@ -7,5 +7,5 @@ test_that("get_result returns a matrix with correct colnames", {
   result <- get_result(cfg, 1, filters = c("bf=4", "var='Z'"))
   expect_true(is.matrix(result))
   expect_type(result, "double")
-  expect_equal(colnames(result), sprintf("bf:4|sn:%d|var:Z", 1:4))
+  expect_equal(colnames(result), c("t", sprintf("bf:4|sn:%d|var:Z", 1:4)))
 })