{-# LANGUAGE GHCForeignImportPrim #-}
{-# LANGUAGE UnliftedFFITypes #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE EmptyCase #-}

-- | Primitive exceptions.
module GHC.Prim.Exception
   ( raiseOverflow
   , raiseUnderflow
   , raiseDivZero
   )
where

import GHC.Prim
import GHC.Magic

default () -- Double and Integer aren't available yet

-- Note [Arithmetic exceptions]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
--
-- ghc-prim provides several functions to raise arithmetic exceptions
-- (raiseDivZero, raiseUnderflow, raiseOverflow) that are wired-in the RTS.
-- These exceptions are meant to be used by the package implementing arbitrary
-- precision numbers (Natural,Integer). It can't depend on `base` package to
-- raise exceptions in a normal way because it would create a dependency
-- cycle (base <-> bignum package). See #14664

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# #)

-- We give a bottoming demand signature to 'raiseOverflow', 'raiseUnderflow' and
-- 'raiseDivZero' in "GHC.Core.Make". NOINLINE pragmas are necessary because if
-- we ever inlined them we would lose that information.

-- | Raise 'GHC.Exception.Type.overflowException'
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)

-- | Raise 'GHC.Exception.Type.underflowException'
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)

-- | Raise 'GHC.Exception.Type.divZeroException'
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)