[Git][ghc/ghc][master] Correct off by one error in ghci +c
Marge Bot
gitlab at gitlab.haskell.org
Mon Apr 22 18:44:02 UTC 2019
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
1a7a329b by Matthew Pickering at 2019-04-22T18:37:30Z
Correct off by one error in ghci +c
Fixes #16569
- - - - -
7 changed files:
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Info.hs
- + testsuite/tests/ghci/scripts/T16569.hs
- + testsuite/tests/ghci/scripts/T16569.script
- + testsuite/tests/ghci/scripts/T16569.stdout
- testsuite/tests/ghci/scripts/all.T
- testsuite/tests/ghci/should_run/T15369.stdout
Changes:
=====================================
ghc/GHCi/UI.hs
=====================================
@@ -2146,7 +2146,9 @@ parseSpanArg s = do
let fs = mkFastString fp
span' = mkRealSrcSpan (mkRealSrcLoc fs sl sc)
- (mkRealSrcLoc fs el ec)
+ -- End column of RealSrcSpan is the column
+ -- after the end of the span.
+ (mkRealSrcLoc fs el (ec + 1))
return (span',trailer)
where
@@ -2192,7 +2194,9 @@ showRealSrcSpan spn = concat [ fp, ":(", show sl, ",", show sc
sl = srcSpanStartLine spn
sc = srcSpanStartCol spn
el = srcSpanEndLine spn
- ec = srcSpanEndCol spn
+ -- The end column is the column after the end of the span see the
+ -- RealSrcSpan module
+ ec = let ec' = srcSpanEndCol spn in if ec' == 0 then 0 else ec' - 1
-----------------------------------------------------------------------------
-- | @:kind@ command
=====================================
ghc/GHCi/UI/Info.hs
=====================================
@@ -75,6 +75,9 @@ data SpanInfo = SpanInfo
-- locality, definition location, etc.
}
+instance Outputable SpanInfo where
+ ppr (SpanInfo s t i) = ppr s <+> ppr t <+> ppr i
+
-- | Test whether second span is contained in (or equal to) first span.
-- This is basically 'containsSpan' for 'SpanInfo'
containsSpanInfo :: SpanInfo -> SpanInfo -> Bool
=====================================
testsuite/tests/ghci/scripts/T16569.hs
=====================================
@@ -0,0 +1,4 @@
+module T16569 where
+
+main :: IO ()
+main = putStrLn (case (undefined :: Int) of _ -> undefined)
=====================================
testsuite/tests/ghci/scripts/T16569.script
=====================================
@@ -0,0 +1,3 @@
+:set +c
+:l T16569.hs
+::type-at T16569.hs 4 8 4 59
=====================================
testsuite/tests/ghci/scripts/T16569.stdout
=====================================
@@ -0,0 +1,2 @@
+Collecting type info for 1 module(s) ...
+ :: IO ()
=====================================
testsuite/tests/ghci/scripts/all.T
=====================================
@@ -295,3 +295,4 @@ test('T16089', normal, ghci_script, ['T16089.script'])
test('T14828', normal, ghci_script, ['T14828.script'])
test('T16376', normal, ghci_script, ['T16376.script'])
test('T16527', normal, ghci_script, ['T16527.script'])
+test('T16569', normal, ghci_script, ['T16569.script'])
=====================================
testsuite/tests/ghci/should_run/T15369.stdout
=====================================
@@ -1,8 +1,8 @@
Collecting type info for 1 module(s) ...
-T15369.hs:(3,1)-(3,2): GHC.Types.Int
-T15369.hs:(3,5)-(3,6): GHC.Types.Int
-T15369.hs:(3,1)-(3,2): GHC.Types.Int
-T15369.hs:(3,5)-(3,6): GHC.Types.Int
+T15369.hs:(3,1)-(3,1): GHC.Types.Int
+T15369.hs:(3,5)-(3,5): GHC.Types.Int
+T15369.hs:(3,1)-(3,1): GHC.Types.Int
+T15369.hs:(3,5)-(3,5): GHC.Types.Int
Collecting type info for 1 module(s) ...
-T15369.hs:(3,1)-(3,2): GHC.Types.Double
-T15369.hs:(3,5)-(3,6): GHC.Types.Double
+T15369.hs:(3,1)-(3,1): GHC.Types.Double
+T15369.hs:(3,5)-(3,5): GHC.Types.Double
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/1a7a329b983fa03f4115b769ede5c2e148abaad0
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/1a7a329b983fa03f4115b769ede5c2e148abaad0
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190422/b5317d6f/attachment-0001.html>
More information about the ghc-commits
mailing list