[commit: ghc] wip/T9858-typeable-ben2: Move CallStack type out of GHC.Types (cb79b9f)

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


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

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

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

commit cb79b9f14ac7a34beba34805fd1d995d0a2bf64b
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Sun Sep 20 10:36:00 2015 +0200

    Move CallStack type out of GHC.Types


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

cb79b9f14ac7a34beba34805fd1d995d0a2bf64b
 libraries/base/GHC/Exception.hs       |  1 +
 libraries/base/GHC/Exception.hs-boot  |  2 +-
 libraries/base/GHC/Exts.hs            |  2 +-
 libraries/base/GHC/Stack.hsc          | 48 -----------------------
 libraries/ghc-prim/GHC/Types/Stack.hs | 72 +++++++++++++++++++++++++++++++++++
 libraries/ghc-prim/ghc-prim.cabal     |  1 +
 6 files changed, 76 insertions(+), 50 deletions(-)

diff --git a/libraries/base/GHC/Exception.hs b/libraries/base/GHC/Exception.hs
index 3fbae05..38d2675 100644
--- a/libraries/base/GHC/Exception.hs
+++ b/libraries/base/GHC/Exception.hs
@@ -37,6 +37,7 @@ import Data.Typeable (Typeable, cast)
    -- loop: Data.Typeable -> GHC.Err -> GHC.Exception
 import GHC.Base
 import GHC.Show
+import GHC.Types.Stack
 
 {- |
 The @SomeException@ type is the root of the exception type hierarchy.
diff --git a/libraries/base/GHC/Exception.hs-boot b/libraries/base/GHC/Exception.hs-boot
index 594f266..0353333 100644
--- a/libraries/base/GHC/Exception.hs-boot
+++ b/libraries/base/GHC/Exception.hs-boot
@@ -28,7 +28,7 @@ module GHC.Exception ( SomeException, errorCallException,
                        errorCallWithCallStackException,
                        divZeroException, overflowException, ratioZeroDenomException
     ) where
-import GHC.Types( Char, CallStack )
+import GHC.Types.Stack( Char, CallStack )
 
 data SomeException
 divZeroException, overflowException, ratioZeroDenomException  :: SomeException
diff --git a/libraries/base/GHC/Exts.hs b/libraries/base/GHC/Exts.hs
index ffc27d1..2fb1b58 100755
--- a/libraries/base/GHC/Exts.hs
+++ b/libraries/base/GHC/Exts.hs
@@ -77,7 +77,7 @@ import GHC.Base hiding (coerce) -- implicitly comes from GHC.Prim
 import GHC.Word
 import GHC.Int
 import GHC.Ptr
-import GHC.Stack
+import GHC.Types.Stack
 
 import qualified Data.Coerce
 import Data.String
diff --git a/libraries/base/GHC/Stack.hsc b/libraries/base/GHC/Stack.hsc
index 5bff6d1..6ef1fa5 100644
--- a/libraries/base/GHC/Stack.hsc
+++ b/libraries/base/GHC/Stack.hsc
@@ -131,51 +131,3 @@ 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/Stack.hs b/libraries/ghc-prim/GHC/Types/Stack.hs
new file mode 100644
index 0000000..02f7628
--- /dev/null
+++ b/libraries/ghc-prim/GHC/Types/Stack.hs
@@ -0,0 +1,72 @@
+{-# LANGUAGE NoImplicitPrelude #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  GHC.Types.Stack
+-- Copyright   :  (c) The University of Glasgow 2015
+-- License     :  see libraries/ghc-prim/LICENSE
+--
+-- Maintainer  :  cvs-ghc at haskell.org
+-- Stability   :  internal
+-- Portability :  non-portable (GHC Extensions)
+--
+-- type definitions for call-stacks via implicit parameters.
+-- Use GHC.Exts from the base package instead of importing this
+-- module directly.
+--
+-----------------------------------------------------------------------------
+
+module GHC.Types.Stack (
+    -- * Implicit parameter call stacks
+    SrcLoc(..), CallStack(..),
+  ) where
+
+import GHC.Types
+
+----------------------------------------------------------------------
+-- 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-prim.cabal b/libraries/ghc-prim/ghc-prim.cabal
index 58b6ee0..bb3fc53 100644
--- a/libraries/ghc-prim/ghc-prim.cabal
+++ b/libraries/ghc-prim/ghc-prim.cabal
@@ -50,6 +50,7 @@ Library
         GHC.PrimopWrappers
         GHC.Tuple
         GHC.Types
+        GHC.Types.Stack
 
     if flag(include-ghc-prim)
         exposed-modules: GHC.Prim



More information about the ghc-commits mailing list