-- Unboxed counterparts to data structures

{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE UnliftedNewtypes #-}

module GHC.Data.Unboxed (
  MaybeUB(JustUB, NothingUB),
  fmapMaybeUB, fromMaybeUB, apMaybeUB, maybeUB
  ) where

import GHC.Prelude hiding (Maybe(..), Either(..))

-- | Like Maybe, but using unboxed sums.
--
-- Use with care. Using a unboxed maybe is not always a win
-- in execution *time* even when allocations go down. So make
-- sure to benchmark for execution time as well. If the difference
-- in *runtime* for the compiler is too small to measure it's likely
-- better to use a regular Maybe instead.
--
-- This is since it causes more function arguments to be passed, and
-- potentially more variables to be captured by closures increasing
-- closure size.
newtype MaybeUB a = MaybeUB (# (# #) | a #)

pattern JustUB :: a -> MaybeUB a
pattern $mJustUB :: forall {r} {a}. MaybeUB a -> (a -> r) -> ((# #) -> r) -> r
$bJustUB :: forall a. a -> MaybeUB a
JustUB x = MaybeUB (# | x #)

pattern NothingUB :: MaybeUB a
pattern $mNothingUB :: forall {r} {a}. MaybeUB a -> ((# #) -> r) -> ((# #) -> r) -> r
$bNothingUB :: (# #) -> forall a. MaybeUB a
NothingUB = MaybeUB (# (# #) | #)

{-# COMPLETE NothingUB, JustUB #-}

fromMaybeUB :: a -> MaybeUB a -> a
fromMaybeUB :: forall a. a -> MaybeUB a -> a
fromMaybeUB a
d MaybeUB a
NothingUB = a
d
fromMaybeUB a
_ (JustUB a
x) = a
x

apMaybeUB :: MaybeUB (a -> b) -> MaybeUB a -> MaybeUB b
apMaybeUB :: forall a b. MaybeUB (a -> b) -> MaybeUB a -> MaybeUB b
apMaybeUB (JustUB a -> b
f) (JustUB a
x) = b -> MaybeUB b
forall a. a -> MaybeUB a
JustUB (a -> b
f a
x)
apMaybeUB MaybeUB (a -> b)
_ MaybeUB a
_ = (# #) -> forall a. MaybeUB a
forall a. MaybeUB a
NothingUB

fmapMaybeUB :: (a -> b) -> MaybeUB a -> MaybeUB b
fmapMaybeUB :: forall a b. (a -> b) -> MaybeUB a -> MaybeUB b
fmapMaybeUB a -> b
_f MaybeUB a
NothingUB = (# #) -> forall a. MaybeUB a
forall a. MaybeUB a
NothingUB
fmapMaybeUB a -> b
f (JustUB a
x) = b -> MaybeUB b
forall a. a -> MaybeUB a
JustUB (b -> MaybeUB b) -> b -> MaybeUB b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
x

maybeUB :: b -> (a -> b) -> MaybeUB a -> b
maybeUB :: forall b a. b -> (a -> b) -> MaybeUB a -> b
maybeUB b
_def a -> b
f (JustUB a
x) = a -> b
f a
x
maybeUB b
def a -> b
_f MaybeUB a
NothingUB = b
def