{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedSums #-}
{-# LANGUAGE UnboxedTuples #-}

module Data.Maybe.Unpacked.Numeric.Int
  ( Maybe(..)
  , just
  , nothing

  , maybe

  , isJust
  , isNothing
  , fromMaybe
  , listToMaybe
  , maybeToList
  , catMaybes
  , mapMaybe

  , toBaseMaybe
  , fromBaseMaybe
  ) where 

import Prelude hiding (Maybe,maybe)

import GHC.Base (build)
import GHC.Exts (Int#)
import GHC.Int (Int(I#))

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

instance Eq Maybe where
  Maybe
ma == :: Maybe -> Maybe -> Bool
== Maybe
mb =
    Bool -> (Int -> Bool) -> Maybe -> Bool
forall a. a -> (Int -> a) -> Maybe -> a
maybe (Maybe -> Bool
isNothing Maybe
mb)
          (\Int
a -> Bool -> (Int -> Bool) -> Maybe -> Bool
forall a. a -> (Int -> a) -> Maybe -> a
maybe Bool
False (\Int
b -> Int
a Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
b) Maybe
mb) Maybe
ma
    
instance Ord Maybe where
  compare :: Maybe -> Maybe -> Ordering
compare Maybe
ma Maybe
mb = Ordering -> (Int -> Ordering) -> Maybe -> Ordering
forall a. a -> (Int -> a) -> Maybe -> a
maybe Ordering
LT (\Int
a -> Ordering -> (Int -> Ordering) -> Maybe -> Ordering
forall a. a -> (Int -> a) -> Maybe -> a
maybe Ordering
GT (Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
a) Maybe
mb) Maybe
ma  

instance Show Maybe where
  showsPrec :: Int -> Maybe -> ShowS
showsPrec Int
p (Maybe (# (# #) | Int# #)
m) = case (# (# #) | Int# #)
m of
    (# (# #) | #) -> String -> ShowS
showString String
"nothing"
    (# | Int#
i #) -> 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 -> Int -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 (Int# -> Int
I# Int#
i)

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 (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
        Int
a <- ReadPrec Int -> ReadPrec Int
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int
forall a. Read a => ReadPrec a
readPrec
        Maybe -> ReadPrec Maybe
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Maybe
just Int
a)

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

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

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

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

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

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

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

just :: Int -> Maybe
just :: Int -> Maybe
just (I# Int#
i) = (# (# #) | Int# #) -> Maybe
Maybe (# | Int#
i #)

fromMaybe :: Int -> Maybe -> Int
fromMaybe :: Int -> Maybe -> Int
fromMaybe Int
a (Maybe (# (# #) | Int# #)
m) = case (# (# #) | Int# #)
m of
  (# (# #) | #) -> Int
a
  (# | Int#
i #) -> Int# -> Int
I# Int#
i

maybe :: a -> (Int -> a) -> Maybe -> a
maybe :: a -> (Int -> a) -> Maybe -> a
maybe a
a Int -> a
f (Maybe (# (# #) | Int# #)
m) = case (# (# #) | Int# #)
m of
  (# (# #) | #) -> a
a
  (# | Int#
i #) -> Int -> a
f (Int# -> Int
I# Int#
i)

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

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