[commit: ghc] wip/T9858-typeable-ben2: Move CallStack (e908229)

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


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

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

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

commit e9082298823e6971dd03b249bb92f2183a5ed2ce
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Sun Sep 20 08:35:01 2015 +0200

    Move CallStack


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

e9082298823e6971dd03b249bb92f2183a5ed2ce
 libraries/ghc-prim/GHC/Types.hs | 50 -----------------------------------------
 1 file changed, 50 deletions(-)

diff --git a/libraries/ghc-prim/GHC/Types.hs b/libraries/ghc-prim/GHC/Types.hs
index b186a84..202b0e0 100644
--- a/libraries/ghc-prim/GHC/Types.hs
+++ b/libraries/ghc-prim/GHC/Types.hs
@@ -30,7 +30,6 @@ module GHC.Types (
         SPEC(..),
         Nat, Symbol,
         Coercible,
-        SrcLoc(..), CallStack(..),
         TyCon(..), TrName(..), Module(..)
     ) where
 
@@ -310,55 +309,6 @@ you're reading this in 2023 then things went wrong). See #8326.
 -- loops should be aggressively specialized.
 data SPEC = SPEC | SPEC2
 
--- | 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
-  }
-
-----------------------------------------------------------------------
--- 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]
-
-
 {- *********************************************************************
 *                                                                      *
              Runtime represntation of TyCon



More information about the ghc-commits mailing list