[commit: ghc] master: Add missing since-annotations for c024af131b9e2538 (75adc35)
git at git.haskell.org
git at git.haskell.org
Sat Apr 25 07:49:21 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/75adc352549a43d4c37bd3bdade55cecf3d75bb1/ghc
>---------------------------------------------------------------
commit 75adc352549a43d4c37bd3bdade55cecf3d75bb1
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Sat Apr 25 09:12:44 2015 +0200
Add missing since-annotations for c024af131b9e2538
See also #9049
>---------------------------------------------------------------
75adc352549a43d4c37bd3bdade55cecf3d75bb1
libraries/base/GHC/SrcLoc.hs | 7 +++++++
libraries/base/GHC/Stack.hsc | 7 ++++++-
2 files changed, 13 insertions(+), 1 deletion(-)
diff --git a/libraries/base/GHC/SrcLoc.hs b/libraries/base/GHC/SrcLoc.hs
index 16ebbab..23a109b 100644
--- a/libraries/base/GHC/SrcLoc.hs
+++ b/libraries/base/GHC/SrcLoc.hs
@@ -1,4 +1,6 @@
{-# LANGUAGE RecordWildCards #-}
+
+-- | @since 4.8.2.0
module GHC.SrcLoc
( SrcLoc
, srcLocPackage
@@ -14,6 +16,8 @@ module GHC.SrcLoc
) where
-- | A single location in the source code.
+--
+-- @since 4.8.2.0
data SrcLoc = SrcLoc
{ srcLocPackage :: String
, srcLocModule :: String
@@ -24,6 +28,9 @@ data SrcLoc = SrcLoc
, srcLocEndCol :: Int
} deriving (Show, Eq)
+-- | Pretty print 'SrcLoc'
+--
+-- @since 4.8.2.0
showSrcLoc :: SrcLoc -> String
showSrcLoc SrcLoc {..}
= concat [ srcLocFile, ":"
diff --git a/libraries/base/GHC/Stack.hsc b/libraries/base/GHC/Stack.hsc
index 8c9f0c1..40fba7d 100644
--- a/libraries/base/GHC/Stack.hsc
+++ b/libraries/base/GHC/Stack.hsc
@@ -24,6 +24,8 @@ module GHC.Stack (
errorWithStackTrace,
-- ** Explicitly created via implicit-parameters
+ --
+ -- @since 4.8.2.0
CallStack,
getCallStack,
showCallStack,
@@ -171,11 +173,14 @@ errorWithStackTrace x = unsafeDupablePerformIO $ do
-- that was called, the 'SrcLoc' is the call-site. The list is ordered with the
-- most recently called function at the head.
--
--- @since 4.9.0.0
+-- @since 4.8.2.0
data CallStack = CallStack { getCallStack :: [(String, SrcLoc)] }
-- See Note [Overview of implicit CallStacks]
deriving (Show, Eq)
+-- | Pretty print 'CallStack'
+--
+-- @since 4.8.2.0
showCallStack :: CallStack -> String
showCallStack (CallStack (root:rest))
= unlines (showCallSite root : map (indent . showCallSite) rest)
More information about the ghc-commits
mailing list