[commit: ghc] wip/T9858-typeable-ben2: Move CallStack back to base (05a36ad)

git at git.haskell.org git at git.haskell.org
Tue Sep 22 14:47:36 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/T9858-typeable-ben2
Link       : http://ghc.haskell.org/trac/ghc/changeset/05a36addd363bd40099f587d17b7ed96a700b959/ghc

>---------------------------------------------------------------

commit 05a36addd363bd40099f587d17b7ed96a700b959
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Sun Sep 20 08:27:34 2015 +0200

    Move CallStack back to base
    
    CallStack requires tuples, instances of which are defined in GHC.Tuple.
    Unfortunately the D757 change to Typeable deriving means that
    GHC.Tuple must import GHC.Types for the type representation types,
    resulting in a cycle.


>---------------------------------------------------------------

05a36addd363bd40099f587d17b7ed96a700b959
 libraries/base/GHC/Stack.hsc    | 51 +++++++++++++++++++++++++++++++++++++++++
 libraries/ghc-prim/GHC/Types.hs |  1 -
 2 files changed, 51 insertions(+), 1 deletion(-)

diff --git a/libraries/base/GHC/Stack.hsc b/libraries/base/GHC/Stack.hsc
index a2283ff..5bff6d1 100644
--- a/libraries/base/GHC/Stack.hsc
+++ b/libraries/base/GHC/Stack.hsc
@@ -22,6 +22,9 @@ module GHC.Stack (
     whoCreated,
     errorWithStackTrace,
 
+    -- * Implicit parameter call stacks
+    SrcLoc(..), CallStack(..),
+
     -- * Internals
     CostCentreStack,
     CostCentre,
@@ -128,3 +131,51 @@ errorWithStackTrace x = unsafeDupablePerformIO $ do
    if null stack
       then throwIO (ErrorCall x)
       else throwIO (ErrorCallWithLocation x (renderStack stack))
+
+----------------------------------------------------------------------
+-- Explicit call-stacks built via ImplicitParams
+----------------------------------------------------------------------
+
+-- | @CallStack at s are an alternate method of obtaining the call stack at a given
+-- point in the program.
+--
+-- When an implicit-parameter of type @CallStack@ occurs in a program, GHC will
+-- solve it with the current location. If another @CallStack@ implicit-parameter
+-- is in-scope (e.g. as a function argument), the new location will be appended
+-- to the one in-scope, creating an explicit call-stack. For example,
+--
+-- @
+-- myerror :: (?loc :: CallStack) => String -> a
+-- myerror msg = error (msg ++ "\n" ++ showCallStack ?loc)
+-- @
+-- ghci> myerror "die"
+-- *** Exception: die
+-- CallStack:
+--   ?loc, called at MyError.hs:7:51 in main:MyError
+--   myerror, called at <interactive>:2:1 in interactive:Ghci1
+--
+-- @CallStack at s do not interact with the RTS and do not require compilation with
+-- @-prof at . On the other hand, as they are built up explicitly using
+-- implicit-parameters, they will generally not contain as much information as
+-- the simulated call-stacks maintained by the RTS.
+--
+-- A @CallStack@ is a @[(String, SrcLoc)]@. The @String@ is the name of
+-- function that was called, the 'SrcLoc' is the call-site. The list is
+-- ordered with the most recently called function at the head.
+--
+-- @since 4.8.2.0
+data CallStack = CallStack { getCallStack :: [([Char], SrcLoc)] }
+  -- See Note [Overview of implicit CallStacks]
+
+-- | A single location in the source code.
+--
+-- @since 4.8.2.0
+data SrcLoc = SrcLoc
+  { srcLocPackage   :: [Char]
+  , srcLocModule    :: [Char]
+  , srcLocFile      :: [Char]
+  , srcLocStartLine :: Int
+  , srcLocStartCol  :: Int
+  , srcLocEndLine   :: Int
+  , srcLocEndCol    :: Int
+  }
diff --git a/libraries/ghc-prim/GHC/Types.hs b/libraries/ghc-prim/GHC/Types.hs
index fe76819..a9e6a47 100644
--- a/libraries/ghc-prim/GHC/Types.hs
+++ b/libraries/ghc-prim/GHC/Types.hs
@@ -35,7 +35,6 @@ module GHC.Types (
     ) where
 
 import GHC.Prim
-import GHC.Tuple ()
 
 infixr 5 :
 



More information about the ghc-commits mailing list