[commit: ghc] master: utils: Provide CallStack to expectJust (10c6df0)

git at git.haskell.org git at git.haskell.org
Fri Apr 15 14:22:06 UTC 2016


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/10c6df007cd85f3ad1c0ab67c177c23781b579bb/ghc

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

commit 10c6df007cd85f3ad1c0ab67c177c23781b579bb
Author: Ben Gamari <bgamari.foss at gmail.com>
Date:   Fri Apr 15 11:41:00 2016 +0200

    utils: Provide CallStack to expectJust
    
    Test Plan: Validate
    
    Reviewers: gridaphobe, austin
    
    Reviewed By: austin
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D2106


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

10c6df007cd85f3ad1c0ab67c177c23781b579bb
 compiler/utils/Maybes.hs | 12 +++++++++++-
 1 file changed, 11 insertions(+), 1 deletion(-)

diff --git a/compiler/utils/Maybes.hs b/compiler/utils/Maybes.hs
index a736e3d..b400fa6 100644
--- a/compiler/utils/Maybes.hs
+++ b/compiler/utils/Maybes.hs
@@ -1,3 +1,7 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE KindSignatures #-}
+
 {-
 (c) The University of Glasgow 2006
 (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
@@ -22,6 +26,12 @@ import Control.Monad
 import Control.Monad.Trans.Maybe
 import Control.Exception (catch, SomeException(..))
 import Data.Maybe
+#if __GLASGOW_HASKELL__ >= 800
+import GHC.Stack
+#else
+import GHC.Exts (Constraint)
+type HasCallStack = (() :: Constraint)
+#endif
 
 infixr 4 `orElse`
 
@@ -41,7 +51,7 @@ firstJust a b = firstJusts [a, b]
 firstJusts :: [Maybe a] -> Maybe a
 firstJusts = msum
 
-expectJust :: String -> Maybe a -> a
+expectJust :: HasCallStack => String -> Maybe a -> a
 {-# INLINE expectJust #-}
 expectJust _   (Just x) = x
 expectJust err Nothing  = error ("expectJust " ++ err)



More information about the ghc-commits mailing list