{-# LANGUAGE MagicHash #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE ViewPatterns #-}

module Data.Maybe.Unpacked.Numeric.Word8
  ( Maybe (..)
  , just
  , nothing
  , maybe
  , isJust
  , isNothing
  , fromMaybe
  , listToMaybe
  , maybeToList
  , catMaybes
  , mapMaybe
  , toBaseMaybe
  , fromBaseMaybe
    -- * Patterns
  , pattern Nothing
  , pattern Just
  ) where

import Prelude hiding (Just, Maybe, Nothing, maybe)

import GHC.Base (build)
import GHC.Exts (Word#)
import GHC.Word (Word8)
import GHC.Word.Compat (pattern W8#)

import GHC.Read (Read (readPrec))
import Text.ParserCombinators.ReadPrec (prec, step)
import Text.Read (Lexeme (Ident), lexP, parens, (+++))

import qualified Prelude as P

data Maybe = Maybe (# (# #) | Word# #)

instance Eq Maybe where
  Maybe
ma == :: Maybe -> Maybe -> Bool
== Maybe
mb =
    Bool -> (Word8 -> Bool) -> Maybe -> Bool
forall a. a -> (Word8 -> a) -> Maybe -> a
maybe
      (Maybe -> Bool
isNothing Maybe
mb)
      (\Word8
a -> Bool -> (Word8 -> Bool) -> Maybe -> Bool
forall a. a -> (Word8 -> a) -> Maybe -> a
maybe Bool
False (\Word8
b -> Word8
a Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
b) Maybe
mb)
      Maybe
ma

instance Ord Maybe where
  compare :: Maybe -> Maybe -> Ordering
compare Maybe
ma Maybe
mb = case Maybe
ma of
    Just Word8
a -> case Maybe
mb of
      Just Word8
b -> Word8 -> Word8 -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Word8
a Word8
b
      Maybe
_ -> Ordering
GT
    Maybe
_ -> case Maybe
mb of
      Just{} -> Ordering
LT
      Maybe
_ -> Ordering
EQ

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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
        String -> ShowS
showString String
"just "
          ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word8 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 (Word# -> Word8
W8# Word#
w)

instance Read Maybe where
  readPrec :: ReadPrec Maybe
readPrec = ReadPrec Maybe -> ReadPrec Maybe
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec Maybe -> ReadPrec Maybe)
-> ReadPrec Maybe -> ReadPrec Maybe
forall a b. (a -> b) -> a -> b
$ ReadPrec Maybe
nothingP ReadPrec Maybe -> ReadPrec Maybe -> ReadPrec Maybe
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++ ReadPrec Maybe
justP
   where
    nothingP :: ReadPrec Maybe
nothingP = do
      Ident String
"nothing" <- ReadPrec Lexeme
lexP
      Maybe -> ReadPrec Maybe
forall a. a -> ReadPrec a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe
nothing
    justP :: ReadPrec Maybe
justP = Int -> ReadPrec Maybe -> ReadPrec Maybe
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10 (ReadPrec Maybe -> ReadPrec Maybe)
-> ReadPrec Maybe -> ReadPrec Maybe
forall a b. (a -> b) -> a -> b
$ do
      Ident String
"just" <- ReadPrec Lexeme
lexP
      Word8
a <- ReadPrec Word8 -> ReadPrec Word8
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Word8
forall a. Read a => ReadPrec a
readPrec
      Maybe -> ReadPrec Maybe
forall a. a -> ReadPrec a
forall (m :: * -> *) a. Monad m => a -> m a
return (Word8 -> Maybe
just Word8
a)

listToMaybe :: [Word8] -> Maybe
listToMaybe :: [Word8] -> Maybe
listToMaybe [] = Maybe
nothing
listToMaybe (Word8
x : [Word8]
_) = Word8 -> Maybe
just Word8
x

maybeToList :: Maybe -> [Word8]
maybeToList :: Maybe -> [Word8]
maybeToList = [Word8] -> (Word8 -> [Word8]) -> Maybe -> [Word8]
forall a. a -> (Word8 -> a) -> Maybe -> a
maybe [] (Word8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
: [])

catMaybes :: [Maybe] -> [Word8]
catMaybes :: [Maybe] -> [Word8]
catMaybes = (Maybe -> Maybe) -> [Maybe] -> [Word8]
forall a. (a -> Maybe) -> [a] -> [Word8]
mapMaybe Maybe -> Maybe
forall a. a -> a
id

mapMaybe :: (a -> Maybe) -> [a] -> [Word8]
mapMaybe :: forall a. (a -> Maybe) -> [a] -> [Word8]
mapMaybe a -> Maybe
_ [] = []
mapMaybe a -> Maybe
f (a
a : [a]
as) =
  let ws :: [Word8]
ws = (a -> Maybe) -> [a] -> [Word8]
forall a. (a -> Maybe) -> [a] -> [Word8]
mapMaybe a -> Maybe
f [a]
as
   in [Word8] -> (Word8 -> [Word8]) -> Maybe -> [Word8]
forall a. a -> (Word8 -> a) -> Maybe -> a
maybe [Word8]
ws (Word8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
: [Word8]
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 :: (Word8 -> r -> r) -> (a -> Maybe) -> a -> r -> r
mapMaybeFB :: forall r a. (Word8 -> r -> r) -> (a -> Maybe) -> a -> r -> r
mapMaybeFB Word8 -> r -> r
cons a -> Maybe
f a
x r
next = r -> (Word8 -> r) -> Maybe -> r
forall a. a -> (Word8 -> a) -> Maybe -> a
maybe r
next ((Word8 -> r -> r) -> r -> Word8 -> r
forall a b c. (a -> b -> c) -> b -> a -> c
flip Word8 -> r -> r
cons r
next) (a -> Maybe
f a
x)

isNothing :: Maybe -> Bool
isNothing :: Maybe -> Bool
isNothing = Bool -> (Word8 -> Bool) -> Maybe -> Bool
forall a. a -> (Word8 -> a) -> Maybe -> a
maybe Bool
True (Bool -> Word8 -> Bool
forall a b. a -> b -> a
const Bool
False)

isJust :: Maybe -> Bool
isJust :: Maybe -> Bool
isJust = Bool -> (Word8 -> Bool) -> Maybe -> Bool
forall a. a -> (Word8 -> a) -> Maybe -> a
maybe Bool
False (Bool -> Word8 -> Bool
forall a b. a -> b -> a
const Bool
True)

nothing :: Maybe
nothing :: Maybe
nothing = (# (# #) | Word# #) -> Maybe
Maybe (# (# #) | #)

just :: Word8 -> Maybe
just :: Word8 -> Maybe
just (W8# Word#
w) = (# (# #) | Word# #) -> Maybe
Maybe (# | Word#
w #)

fromMaybe :: Word8 -> Maybe -> Word8
fromMaybe :: Word8 -> Maybe -> Word8
fromMaybe Word8
a (Maybe (# (# #) | Word# #)
m) = case (# (# #) | Word# #)
m of
  (# (# #) | #) -> Word8
a
  (# | Word#
w #) -> Word# -> Word8
W8# Word#
w

maybe :: a -> (Word8 -> a) -> Maybe -> a
maybe :: forall a. a -> (Word8 -> a) -> Maybe -> a
maybe a
a Word8 -> a
f (Maybe (# (# #) | Word# #)
m) = case (# (# #) | Word# #)
m of
  (# (# #) | #) -> a
a
  (# | Word#
w #) -> Word8 -> a
f (Word# -> Word8
W8# Word#
w)

toBaseMaybe :: Maybe -> P.Maybe Word8
toBaseMaybe :: Maybe -> Maybe Word8
toBaseMaybe = Maybe Word8 -> (Word8 -> Maybe Word8) -> Maybe -> Maybe Word8
forall a. a -> (Word8 -> a) -> Maybe -> a
maybe Maybe Word8
forall a. Maybe a
P.Nothing Word8 -> Maybe Word8
forall a. a -> Maybe a
P.Just

fromBaseMaybe :: P.Maybe Word8 -> Maybe
fromBaseMaybe :: Maybe Word8 -> Maybe
fromBaseMaybe = Maybe -> (Word8 -> Maybe) -> Maybe Word8 -> Maybe
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe Maybe
nothing Word8 -> Maybe
just

pattern Nothing :: Maybe
pattern $mNothing :: forall {r}. Maybe -> ((# #) -> r) -> ((# #) -> r) -> r
$bNothing :: Maybe
Nothing = Maybe (# (# #) | #)

pattern Just :: Word8 -> Maybe
pattern $mJust :: forall {r}. Maybe -> (Word8 -> r) -> ((# #) -> r) -> r
$bJust :: Word8 -> Maybe
Just i <- Maybe (# | (W8# -> i) #)
  where
    Just (W8# Word#
i) = (# (# #) | Word# #) -> Maybe
Maybe (# | Word#
i #)

{-# COMPLETE Nothing, Just #-}