diff --git a/hledger/Hledger/Cli/Commands/Balance.hs b/hledger/Hledger/Cli/Commands/Balance.hs
index fd50fbd62..ed4fec0d5 100644
--- a/hledger/Hledger/Cli/Commands/Balance.hs
+++ b/hledger/Hledger/Cli/Commands/Balance.hs
@@ -232,12 +232,13 @@ Currently, empty cells show 0.
 
 -}
 
-{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE CPP                  #-}
 {-# LANGUAGE ExtendedDefaultRules #-}
-{-# LANGUAGE RecordWildCards #-}
-{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE TemplateHaskell #-}
-{-# LANGUAGE NamedFieldPuns #-}
+{-# LANGUAGE NamedFieldPuns       #-}
+{-# LANGUAGE OverloadedStrings    #-}
+{-# LANGUAGE RecordWildCards      #-}
+{-# LANGUAGE ScopedTypeVariables  #-}
+{-# LANGUAGE TemplateHaskell      #-}
 
 module Hledger.Cli.Commands.Balance (
   balancemode
@@ -257,12 +258,14 @@ import Data.Default (def)
 import Data.List (intercalate, transpose)
 import Data.Maybe (fromMaybe, maybeToList)
 --import qualified Data.Map as Map
+#if !(MIN_VERSION_base(4,11,0))
+import Data.Semigroup ((<>))
+#endif
 import qualified Data.Text as T
 import qualified Data.Text.Lazy as TL
 import Data.Time (fromGregorian)
 import System.Console.CmdArgs.Explicit as C
 import Lucid as L
-import Text.Printf (printf)
 import Text.Tabular as T
 import Text.Tabular.AsciiWide as T
 
@@ -555,23 +558,31 @@ multiBalanceReportAsText :: ReportOpts -> MultiBalanceReport -> String
 multiBalanceReportAsText ropts@ReportOpts{..} r =
     title ++ "\n\n" ++ (balanceReportTableAsText ropts $ balanceReportAsTable ropts r)
   where
-    multiperiod = interval_ /= NoInterval
-    title = printf "%s in %s%s:"
-      (case balancetype_ of
-        PeriodChange       -> "Balance changes"
-        CumulativeChange   -> "Ending balances (cumulative)"
-        HistoricalBalance  -> "Ending balances (historical)")
-      (showDateSpan $ periodicReportSpan r)
-      (case value_ of
-        Just (AtCost _mc)   -> ", valued at cost"
-        Just (AtThen _mc)   -> error' unsupportedValueThenError  -- TODO -- ", valued at period ends"  -- handled like AtEnd for now  -- PARTIAL:
-        Just (AtEnd _mc)    -> ", valued at period ends"
-        Just (AtNow _mc)    -> ", current value"
+    title = mtitle <> " in " <> showDateSpan (periodicReportSpan r) <> valuationdesc <> ":"
+
+    mtitle = case balancetype_ of
+        PeriodChange     | changingValuation -> "Period-end value changes"
+        PeriodChange                         -> "Balance changes"
+        CumulativeChange                     -> "Ending balances (cumulative)"
+        HistoricalBalance                    -> "Ending balances (historical)"
+    valuationdesc = case value_ of
+        Just (AtCost _mc)    -> ", valued at cost"
+        Just (AtThen _mc)    -> error' unsupportedValueThenError  -- TODO -- ", valued at period ends"  -- handled like AtEnd for now  -- PARTIAL:
+        Just (AtEnd _mc) | changingValuation -> ""
+        Just (AtEnd _mc)     -> ", valued at period ends"
+        Just (AtNow _mc)     -> ", current value"
         -- XXX duplicates the above
-        Just (AtDefault _mc) | multiperiod -> ", valued at period ends"
+        Just (AtDefault _mc) | changingValuation -> ""
+        Just (AtDefault _mc) | multiperiod       -> ", valued at period ends"
         Just (AtDefault _mc) -> ", current value"
-        Just (AtDate d _mc) -> ", valued at "++showDate d
-        Nothing             -> "")
+        Just (AtDate d _mc)  -> ", valued at "++showDate d
+        Nothing              -> ""
+
+    multiperiod = interval_ /= NoInterval
+    changingValuation
+      | PeriodChange <- balancetype_, Just (AtEnd _mc)     <- value_ = multiperiod
+      | PeriodChange <- balancetype_, Just (AtDefault _mc) <- value_ = multiperiod
+      | otherwise                                                    = False
 
 -- | Build a 'Table' from a multi-column balance report.
 balanceReportAsTable :: ReportOpts -> MultiBalanceReport -> Table String String MixedAmount
diff --git a/hledger/Hledger/Cli/CompoundBalanceCommand.hs b/hledger/Hledger/Cli/CompoundBalanceCommand.hs
index 1fab250ed..f6cada00f 100644
--- a/hledger/Hledger/Cli/CompoundBalanceCommand.hs
+++ b/hledger/Hledger/Cli/CompoundBalanceCommand.hs
@@ -125,22 +125,29 @@ compoundBalanceCommand CompoundBalanceCommandSpec{..} opts@CliOpts{reportspec_=r
                                   `spanDefaultsFrom` journalDateSpan date2_ j
 
           -- when user overrides, add an indication to the report title
-          mtitleclarification = flip fmap mBalanceTypeOverride $ \t ->
-            case t of
-              PeriodChange      -> "(Balance Changes)"
-              CumulativeChange  -> "(Cumulative Ending Balances)"
-              HistoricalBalance -> "(Historical Ending Balances)"
+          mtitleclarification = flip fmap mBalanceTypeOverride $ \case
+              PeriodChange | changingValuation -> "(Period-End Value Changes)"
+              PeriodChange                     -> "(Balance Changes)"
+              CumulativeChange                 -> "(Cumulative Ending Balances)"
+              HistoricalBalance                -> "(Historical Ending Balances)"
 
           valuationdesc = case value_ of
             Just (AtCost _mc)       -> ", valued at cost"
             Just (AtThen _mc)       -> error' unsupportedValueThenError  -- TODO
+            Just (AtEnd _mc) | changingValuation -> ""
             Just (AtEnd _mc)        -> ", valued at period ends"
             Just (AtNow _mc)        -> ", current value"
-            Just (AtDefault _mc) | multiperiod   -> ", valued at period ends"
+            Just (AtDefault _mc) | changingValuation -> ""
+            Just (AtDefault _mc) | multiperiod       -> ", valued at period ends"
             Just (AtDefault _mc)    -> ", current value"
             Just (AtDate today _mc) -> ", valued at "++showDate today
             Nothing                 -> ""
-            where multiperiod = interval_ /= NoInterval
+
+          multiperiod = interval_ /= NoInterval
+          changingValuation
+            | PeriodChange <- balancetype_, Just (AtEnd _mc)     <- value_ = multiperiod
+            | PeriodChange <- balancetype_, Just (AtDefault _mc) <- value_ = multiperiod
+            | otherwise                                                    = False
 
       -- make a CompoundBalanceReport.
       cbr' = compoundBalanceReport rspec{rsOpts=ropts'} j cbcqueries
diff --git a/hledger/hledger.m4.md b/hledger/hledger.m4.md
index 6ad8940e9..7c45f8219 100644
--- a/hledger/hledger.m4.md
+++ b/hledger/hledger.m4.md
@@ -1488,28 +1488,29 @@ Related:
 [#329](https://github.com/simonmichael/hledger/issues/329),
 [#1083](https://github.com/simonmichael/hledger/issues/1083).
 
-| Report type                                     | `-B`, `--value=cost`                          | `-V`, `-X`                                       | `--value=then`                                        | `--value=end`                                      | `--value=DATE`, `--value=now`           |
-|-------------------------------------------------|-----------------------------------------------|--------------------------------------------------|-------------------------------------------------------|----------------------------------------------------|-----------------------------------------|
-| **print**                                       |                                               |                                                  |                                                       |                                                    |                                         |
-| posting amounts                                 | cost                                          | value at report end or today                     | value at posting date                                 | value at report or journal end                     | value at DATE/today                     |
-| balance assertions / assignments                | unchanged                                     | unchanged                                        | unchanged                                             | unchanged                                          | unchanged                               |
-| 
                                            |                                               |                                                  |                                                       |                                                    |                                         |
-| **register**                                    |                                               |                                                  |                                                       |                                                    |                                         |
-| starting balance (with -H)                      | cost                                          | value at day before report or journal start      | not supported                                         | value at day before report or journal start        | value at DATE/today                     |
-| posting amounts (no report interval)            | cost                                          | value at report end or today                     | value at posting date                                 | value at report or journal end                     | value at DATE/today                     |
-| summary posting amounts (with report interval)  | summarised cost                               | value at period ends                             | sum of postings in interval, valued at interval start | value at period ends                               | value at DATE/today                     |
-| running total/average                           | sum/average of displayed values               | sum/average of displayed values                  | sum/average of displayed values                       | sum/average of displayed values                    | sum/average of displayed values         |
-| 
                                            |                                               |                                                  |                                                       |                                                    |                                         |
-| **balance (bs, bse, cf, is..)**                 |                                               |                                                  |                                                       |                                                    |                                         |
-| balances (no report interval)                   | sums of costs                                 | value at report end or today of sums of postings | not supported                                         | value at report or journal end of sums of postings | value at DATE/today of sums of postings |
-| balances (with report interval)                 | sums of costs                                 | value at period ends of sums of postings         | not supported                                         | value at period ends of sums of postings           | value at DATE/today of sums of postings |
-| starting balances (with report interval and -H) | sums of costs of postings before report start | sums of postings before report start             | not supported                                         | sums of postings before report start               | sums of postings before report start    |
-| budget amounts with --budget                    | like balances                                 | like balances                                    | not supported                                         | like balances                                      | like balances                           |
-| grand total (no report interval)                | sum of displayed values                       | sum of displayed values                          | not supported                                         | sum of displayed values                            | sum of displayed values                 |
-| row totals/averages (with report interval)      | sums/averages of displayed values             | sums/averages of displayed values                | not supported                                         | sums/averages of displayed values                  | sums/averages of displayed values       |
-| column totals                                   | sums of displayed values                      | sums of displayed values                         | not supported                                         | sums of displayed values                           | sums of displayed values                |
-| grand total/average                             | sum/average of column totals                  | sum/average of column totals                     | not supported                                         | sum/average of column totals                       | sum/average of column totals            |
-| 
                                            |                                               |                                                  |                                                       |                                                    |                                         |
+| Report type                                                | `-B`, `--value=cost`                                                                          | `-V`, `-X`                                                                                                                                                    | `--value=then`                                        | `--value=end`                                                                                                                                                 | `--value=DATE`, `--value=now`           |
+|------------------------------------------------------------|-----------------------------------------------------------------------------------------------|---------------------------------------------------------------------------------------------------------------------------------------------------------------|-------------------------------------------------------|---------------------------------------------------------------------------------------------------------------------------------------------------------------|-----------------------------------------|
+| **print**                                                  |                                                                                               |                                                                                                                                                               |                                                       |                                                                                                                                                               |                                         |
+| posting amounts                                            | cost                                                                                          | value at report end or today                                                                                                                                  | value at posting date                                 | value at report or journal end                                                                                                                                | value at DATE/today                     |
+| balance assertions / assignments                           | unchanged                                                                                     | unchanged                                                                                                                                                     | unchanged                                             | unchanged                                                                                                                                                     | unchanged                               |
+| 
                                                       |                                                                                               |                                                                                                                                                               |                                                       |                                                                                                                                                               |                                         |
+| **register**                                               |                                                                                               |                                                                                                                                                               |                                                       |                                                                                                                                                               |                                         |
+| starting balance (with -H)                                 | cost                                                                                          | value at day before report or journal start                                                                                                                   | not supported                                         | value at day before report or journal start                                                                                                                   | value at DATE/today                     |
+| posting amounts (no report interval)                       | cost                                                                                          | value at report end or today                                                                                                                                  | value at posting date                                 | value at report or journal end                                                                                                                                | value at DATE/today                     |
+| summary posting amounts (with report interval)             | summarised cost                                                                               | value at period ends                                                                                                                                          | sum of postings in interval, valued at interval start | value at period ends                                                                                                                                          | value at DATE/today                     |
+| running total/average                                      | sum/average of displayed values                                                               | sum/average of displayed values                                                                                                                               | sum/average of displayed values                       | sum/average of displayed values                                                                                                                               | sum/average of displayed values         |
+| 
                                                       |                                                                                               |                                                                                                                                                               |                                                       |                                                                                                                                                               |                                         |
+| **balance (bs, bse, cf, is..)**                            |                                                                                               |                                                                                                                                                               |                                                       |                                                                                                                                                               |                                         |
+| balances (no report interval)                              | sums of costs                                                                                 | value at report end or today of sums of postings                                                                                                              | not supported                                         | value at report or journal end of sums of postings                                                                                                            | value at DATE/today of sums of postings |
+| balances changes (with report interval)                    | sums of costs of postings in interval                                                         | value at period ends of sums of postings before period end minus value at period starts of sums of all postings before period start                           | not supported                                         | value at period ends of sums of postings before period end minus value at period starts of sums of all postings before period start                           | value at DATE/today of sums of postings |
+| end balances (with report interval and --cumulative or -H) | sums of costs of postings from report start (or before report start with -H) and interval end | value at period ends of sums of all postings before period end (minus value at report start of of sums of all postings before report start with --cumulative) | not supported                                         | value at period ends of sums of all postings before period end (minus value at report start of of sums of all postings before report start with --cumulative) | value at DATE/today of sums of postings |
+| starting balances (with report interval and -H)            | sums of costs of postings before report start                                                 | value at report start of sums of all postings before report start                                                                                             | not supported                                         | value at report start of sums of all postings before report start                                                                                             | sums of postings before report start    |
+| budget amounts with --budget                               | like balances                                                                                 | like balances                                                                                                                                                 | not supported                                         | like balances                                                                                                                                                 | like balances                           |
+| grand total (no report interval)                           | sum of displayed values                                                                       | sum of displayed values                                                                                                                                       | not supported                                         | sum of displayed values                                                                                                                                       | sum of displayed values                 |
+| row totals/averages (with report interval)                 | sums/averages of displayed values                                                             | sums/averages of displayed values                                                                                                                             | not supported                                         | sums/averages of displayed values                                                                                                                             | sums/averages of displayed values       |
+| column totals                                              | sums of displayed values                                                                      | sums of displayed values                                                                                                                                      | not supported                                         | sums of displayed values                                                                                                                                      | sums of displayed values                |
+| grand total/average                                        | sum/average of column totals                                                                  | sum/average of column totals                                                                                                                                  | not supported                                         | sum/average of column totals                                                                                                                                  | sum/average of column totals            |
+| 
                                                       |                                                                                               |                                                                                                                                                               |                                                       |                                                                                                                                                               |                                         |
 
 **Glossary:**
 
diff --git a/tests/journal/valuation.test b/tests/journal/valuation.test
index 3e0248cca..fa9ddc126 100644
--- a/tests/journal/valuation.test
+++ b/tests/journal/valuation.test
@@ -374,10 +374,10 @@ Balance changes in 2000Q1, valued at cost:
  a || 6 B  7 B  8 B     21 B      7 B 
 ---++---------------------------------
    || 6 B  7 B  8 B     21 B      7 B 
- 
-# 35. multicolumn balance report valued at period end
+
+# 35. multicolumn balance report showing changes in period-end values
 $ hledger -f- bal -M --value=end
-Balance changes in 2000Q1, valued at period ends:
+Period-end value changes in 2000Q1:
 
    || Jan   Feb  Mar 
 ===++================
@@ -385,9 +385,9 @@ Balance changes in 2000Q1, valued at period ends:
 ---++----------------
    || 5 B  -1 B  5 B 
 
-# 36. multicolumn balance report valued at period end with -T or -A
+# 36. multicolumn balance report showing changes in period-end values with -T or -A
 $ hledger -f- bal -MTA --value=end
-Balance changes in 2000Q1, valued at period ends:
+Period-end value changes in 2000Q1:
 
    || Jan   Feb  Mar    Total  Average 
 ===++==================================
@@ -415,9 +415,9 @@ Balance changes in 2000Q1, current value:
 ---++---------------
    || 4 B  4 B  4 B 
 
-# 39. multicolumn balance report valued at default date (same as --value=end)
+# 39. multicolumn balance report showing changes in period-end values (same as --value=end)
 $ hledger -f- bal -M -V
-Balance changes in 2000Q1, valued at period ends:
+Period-end value changes in 2000Q1:
 
    || Jan   Feb  Mar 
 ===++================
@@ -547,7 +547,7 @@ Budget performance in 2000Q1, valued at cost:
 ---++------------------------------------------------------------------------------------------------
    || 6 B [300% of 2 B]  7 B [350% of 2 B]  8 B [400% of 2 B]  21 B [350% of 6 B]  7 B [350% of 2 B] 
 
-# 48. budget report, valued at period ends.
+# 48. budget report, showing changes in period-end values.
 $ hledger -f- bal -MTA --budget --value=e
 Budget performance in 2000Q1, valued at period ends: