{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE UnboxedSums #-}
{-# LANGUAGE UnboxedTuples #-}
module Data.Maybe.Unpacked.Numeric.Word32
( Maybe(..)
, just
, nothing
, maybe
, isJust
, isNothing
, fromMaybe
, listToMaybe
, maybeToList
, catMaybes
, mapMaybe
, toBaseMaybe
, fromBaseMaybe
, pattern Nothing
, pattern Just
) where
import Prelude hiding (Maybe,Nothing,Just,maybe)
import GHC.Base (build)
import GHC.Exts (Word#)
import GHC.Word (Word32)
import GHC.Word.Compat (pattern W32#)
import GHC.Read (Read(readPrec))
import Text.Read (parens, Lexeme(Ident), lexP, (+++))
import Text.ParserCombinators.ReadPrec (prec, step)
import qualified Prelude as P
data Maybe = Maybe (# (# #) | Word# #)
pattern Nothing :: Maybe
pattern $bNothing :: Maybe
$mNothing :: forall {r}. Maybe -> ((# #) -> r) -> ((# #) -> r) -> r
Nothing = Maybe (# (# #) | #)
pattern Just :: Word32 -> Maybe
pattern $bJust :: Word32 -> Maybe
$mJust :: forall {r}. Maybe -> (Word32 -> r) -> ((# #) -> r) -> r
Just i <- Maybe (# | (W32# -> i) #)
where Just (W32# Word#
i) = (# (# #) | Word# #) -> Maybe
Maybe (# | Word#
i #)
{-# COMPLETE Nothing, Just #-}
instance Eq Maybe where
Maybe
ma == :: Maybe -> Maybe -> Bool
== Maybe
mb =
forall a. a -> (Word32 -> a) -> Maybe -> a
maybe (Maybe -> Bool
isNothing Maybe
mb)
(\Word32
a -> forall a. a -> (Word32 -> a) -> Maybe -> a
maybe Bool
False (\Word32
b -> Word32
a forall a. Eq a => a -> a -> Bool
== Word32
b) Maybe
mb) Maybe
ma
instance Ord Maybe where
compare :: Maybe -> Maybe -> Ordering
compare Maybe
ma Maybe
mb = forall a. a -> (Word32 -> a) -> Maybe -> a
maybe Ordering
LT (\Word32
a -> forall a. a -> (Word32 -> a) -> Maybe -> a
maybe Ordering
GT (forall a. Ord a => a -> a -> Ordering
compare Word32
a) Maybe
mb) Maybe
ma
instance Show Maybe where
showsPrec :: Int -> Maybe -> ShowS
showsPrec Int
p (Maybe (# (# #) | Word# #)
m) = case (# (# #) | Word# #)
m of
(# (# #) | #) -> String -> ShowS
showString String
"nothing"
(# | Word#
w #) -> Bool -> ShowS -> ShowS
showParen (Int
p forall a. Ord a => a -> a -> Bool
> Int
10)
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"just "
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 (Word# -> Word32
W32# Word#
w)
instance Read Maybe where
readPrec :: ReadPrec Maybe
readPrec = forall a. ReadPrec a -> ReadPrec a
parens forall a b. (a -> b) -> a -> b
$ ReadPrec Maybe
nothingP forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++ ReadPrec Maybe
justP
where
nothingP :: ReadPrec Maybe
nothingP = do
Ident String
"nothing" <- ReadPrec Lexeme
lexP
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe
nothing
justP :: ReadPrec Maybe
justP = forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10 forall a b. (a -> b) -> a -> b
$ do
Ident String
"just" <- ReadPrec Lexeme
lexP
Word32
a <- forall a. ReadPrec a -> ReadPrec a
step forall a. Read a => ReadPrec a
readPrec
forall (m :: * -> *) a. Monad m => a -> m a
return (Word32 -> Maybe
just Word32
a)
listToMaybe :: [Word32] -> Maybe
listToMaybe :: [Word32] -> Maybe
listToMaybe [] = Maybe
nothing
listToMaybe (Word32
x:[Word32]
_) = Word32 -> Maybe
just Word32
x
maybeToList :: Maybe -> [Word32]
maybeToList :: Maybe -> [Word32]
maybeToList = forall a. a -> (Word32 -> a) -> Maybe -> a
maybe [] (forall a. a -> [a] -> [a]
: [])
catMaybes :: [Maybe] -> [Word32]
catMaybes :: [Maybe] -> [Word32]
catMaybes = forall a. (a -> Maybe) -> [a] -> [Word32]
mapMaybe forall a. a -> a
id
mapMaybe :: (a -> Maybe) -> [a] -> [Word32]
mapMaybe :: forall a. (a -> Maybe) -> [a] -> [Word32]
mapMaybe a -> Maybe
_ [] = []
mapMaybe a -> Maybe
f (a
a : [a]
as) =
let ws :: [Word32]
ws = forall a. (a -> Maybe) -> [a] -> [Word32]
mapMaybe a -> Maybe
f [a]
as
in forall a. a -> (Word32 -> a) -> Maybe -> a
maybe [Word32]
ws (forall a. a -> [a] -> [a]
: [Word32]
ws) (a -> Maybe
f a
a)
{-# NOINLINE [1] mapMaybe #-}
{-# RULES
"mapMaybe" [~1] forall f xs. mapMaybe f xs
= build (\c n -> foldr (mapMaybeFB c f) n xs)
"mapMaybeList" [1] forall f. foldr (mapMaybeFB (:) f) [] = mapMaybe f
#-}
{-# NOINLINE [0] mapMaybeFB #-}
mapMaybeFB :: (Word32 -> r -> r) -> (a -> Maybe) -> a -> r -> r
mapMaybeFB :: forall r a. (Word32 -> r -> r) -> (a -> Maybe) -> a -> r -> r
mapMaybeFB Word32 -> r -> r
cons a -> Maybe
f a
x r
next = forall a. a -> (Word32 -> a) -> Maybe -> a
maybe r
next (forall a b c. (a -> b -> c) -> b -> a -> c
flip Word32 -> r -> r
cons r
next) (a -> Maybe
f a
x)
isNothing :: Maybe -> Bool
isNothing :: Maybe -> Bool
isNothing = forall a. a -> (Word32 -> a) -> Maybe -> a
maybe Bool
True (forall a b. a -> b -> a
const Bool
False)
isJust :: Maybe -> Bool
isJust :: Maybe -> Bool
isJust = forall a. a -> (Word32 -> a) -> Maybe -> a
maybe Bool
False (forall a b. a -> b -> a
const Bool
True)
nothing :: Maybe
nothing :: Maybe
nothing = (# (# #) | Word# #) -> Maybe
Maybe (# (# #) | #)
just :: Word32 -> Maybe
just :: Word32 -> Maybe
just (W32# Word#
w) = (# (# #) | Word# #) -> Maybe
Maybe (# | Word#
w #)
fromMaybe :: Word32 -> Maybe -> Word32
fromMaybe :: Word32 -> Maybe -> Word32
fromMaybe Word32
a (Maybe (# (# #) | Word# #)
m) = case (# (# #) | Word# #)
m of
(# (# #) | #) -> Word32
a
(# | Word#
w #) -> Word# -> Word32
W32# Word#
w
maybe :: a -> (Word32 -> a) -> Maybe -> a
maybe :: forall a. a -> (Word32 -> a) -> Maybe -> a
maybe a
a Word32 -> a
f (Maybe (# (# #) | Word# #)
m) = case (# (# #) | Word# #)
m of
(# (# #) | #) -> a
a
(# | Word#
w #) -> Word32 -> a
f (Word# -> Word32
W32# Word#
w)
toBaseMaybe :: Maybe -> P.Maybe Word32
toBaseMaybe :: Maybe -> Maybe Word32
toBaseMaybe = forall a. a -> (Word32 -> a) -> Maybe -> a
maybe forall a. Maybe a
P.Nothing forall a. a -> Maybe a
P.Just
fromBaseMaybe :: P.Maybe Word32 -> Maybe
fromBaseMaybe :: Maybe Word32 -> Maybe
fromBaseMaybe = forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe Maybe
nothing Word32 -> Maybe
just