[commit: ghc] master: Fixed missing trailing newline bug in pretty printer (995ea1c)
git at git.haskell.org
git at git.haskell.org
Thu Oct 30 16:54:25 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/995ea1c8335631d6e4db1ff4da38251b2f396edb/ghc
>---------------------------------------------------------------
commit 995ea1c8335631d6e4db1ff4da38251b2f396edb
Author: Mateusz Lenik <mlen at mlen.pl>
Date: Thu Oct 30 11:53:40 2014 -0500
Fixed missing trailing newline bug in pretty printer
Summary:
Pretty printer didn't produce trailing newline in strings in error
messages.
Reviewers: simonpj, austin
Reviewed By: austin
Subscribers: thomie, carter, simonmar, mlen
Differential Revision: https://phabricator.haskell.org/D405
GHC Trac Issues: #9681
>---------------------------------------------------------------
995ea1c8335631d6e4db1ff4da38251b2f396edb
libraries/base/GHC/Show.lhs | 1 +
libraries/base/tests/T9681.hs | 3 +++
libraries/base/tests/T9681.stderr | 5 +++++
libraries/base/tests/all.T | 1 +
4 files changed, 10 insertions(+)
diff --git a/libraries/base/GHC/Show.lhs b/libraries/base/GHC/Show.lhs
index 2834817..d5ed094 100644
--- a/libraries/base/GHC/Show.lhs
+++ b/libraries/base/GHC/Show.lhs
@@ -386,6 +386,7 @@ showMultiLineString str
where
go ch s = case break (== '\n') s of
(l, _:s'@(_:_)) -> (ch : showLitString l "\\n\\") : go '\\' s'
+ (l, "\n") -> [ch : showLitString l "\\n\""]
(l, _) -> [ch : showLitString l "\""]
isDec :: Char -> Bool
diff --git a/libraries/base/tests/T9681.hs b/libraries/base/tests/T9681.hs
new file mode 100644
index 0000000..b0fd499
--- /dev/null
+++ b/libraries/base/tests/T9681.hs
@@ -0,0 +1,3 @@
+module T9681 where
+
+foo = 1 + "\n"
diff --git a/libraries/base/tests/T9681.stderr b/libraries/base/tests/T9681.stderr
new file mode 100644
index 0000000..7945ff7
--- /dev/null
+++ b/libraries/base/tests/T9681.stderr
@@ -0,0 +1,5 @@
+
+T9681.hs:3:9:
+ No instance for (Num [Char]) arising from a use of ‘+’
+ In the expression: 1 + "\n"
+ In an equation for ‘foo’: foo = 1 + "\n"
diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T
index edb5fc3..ee0fb6b 100644
--- a/libraries/base/tests/all.T
+++ b/libraries/base/tests/all.T
@@ -173,3 +173,4 @@ test('T9111', normal, compile, [''])
test('T9395', normal, compile_and_run, [''])
test('T9532', normal, compile_and_run, [''])
test('T9586', normal, compile, [''])
+test('T9681', normal, compile_fail, [''])
More information about the ghc-commits
mailing list