{-# LANGUAGE GHCForeignImportPrim #-}
{-# LANGUAGE UnliftedFFITypes #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE EmptyCase #-}
module GHC.Prim.Exception
( raiseOverflow
, raiseUnderflow
, raiseDivZero
)
where
import GHC.Prim
import GHC.Magic
default ()
foreign import prim "stg_raiseOverflowzh" raiseOverflow# :: State# RealWorld -> (# State# RealWorld, Void# #)
foreign import prim "stg_raiseUnderflowzh" raiseUnderflow# :: State# RealWorld -> (# State# RealWorld, Void# #)
foreign import prim "stg_raiseDivZZerozh" raiseDivZero# :: State# RealWorld -> (# State# RealWorld, Void# #)
raiseOverflow :: a
{-# NOINLINE raiseOverflow #-}
raiseOverflow :: forall a. a
raiseOverflow = (State# RealWorld -> a) -> a
forall o. (State# RealWorld -> o) -> o
runRW# (\State# RealWorld
s -> case State# RealWorld -> (# State# RealWorld, Void# #)
raiseOverflow# State# RealWorld
s of (# State# RealWorld
_, Void#
_ #) -> let x :: t
x = t
x in a
forall a. a
x)
raiseUnderflow :: a
{-# NOINLINE raiseUnderflow #-}
raiseUnderflow :: forall a. a
raiseUnderflow = (State# RealWorld -> a) -> a
forall o. (State# RealWorld -> o) -> o
runRW# (\State# RealWorld
s -> case State# RealWorld -> (# State# RealWorld, Void# #)
raiseUnderflow# State# RealWorld
s of (# State# RealWorld
_, Void#
_ #) -> let x :: t
x = t
x in a
forall a. a
x)
raiseDivZero :: a
{-# NOINLINE raiseDivZero #-}
raiseDivZero :: forall a. a
raiseDivZero = (State# RealWorld -> a) -> a
forall o. (State# RealWorld -> o) -> o
runRW# (\State# RealWorld
s -> case State# RealWorld -> (# State# RealWorld, Void# #)
raiseDivZero# State# RealWorld
s of (# State# RealWorld
_, Void#
_ #) -> let x :: t
x = t
x in a
forall a. a
x)