{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
module Data.Maybe.Strict (
StrictMaybe (SNothing, SJust),
strictMaybeToMaybe,
maybeToStrictMaybe,
fromSMaybe,
isSNothing,
isSJust,
strictMaybe,
)
where
import Cardano.Binary (
FromCBOR (fromCBOR),
ToCBOR (toCBOR),
decodeBreakOr,
decodeListLenOrIndef,
encodeListLen,
)
import Control.Applicative (Alternative (..))
import Control.DeepSeq (NFData)
import Data.Aeson (FromJSON (..), ToJSON (..))
import Data.Default.Class (Default (..))
import Data.Functor (($>))
import Data.Functor.Classes (
Eq1 (..),
Ord1 (..),
Read1 (..),
Show1 (..),
liftReadListDefault,
liftReadListPrecDefault,
readData,
readUnaryWith,
showsUnaryWith,
)
import GHC.Generics (Generic)
import GHC.Read (expectP)
import NoThunks.Class (NoThunks (..))
import Text.Read (Lexeme (..), parens)
data StrictMaybe a
= SNothing
| SJust !a
deriving
( StrictMaybe a -> StrictMaybe a -> Bool
(StrictMaybe a -> StrictMaybe a -> Bool)
-> (StrictMaybe a -> StrictMaybe a -> Bool) -> Eq (StrictMaybe a)
forall a. Eq a => StrictMaybe a -> StrictMaybe a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => StrictMaybe a -> StrictMaybe a -> Bool
== :: StrictMaybe a -> StrictMaybe a -> Bool
$c/= :: forall a. Eq a => StrictMaybe a -> StrictMaybe a -> Bool
/= :: StrictMaybe a -> StrictMaybe a -> Bool
Eq
, Eq (StrictMaybe a)
Eq (StrictMaybe a) =>
(StrictMaybe a -> StrictMaybe a -> Ordering)
-> (StrictMaybe a -> StrictMaybe a -> Bool)
-> (StrictMaybe a -> StrictMaybe a -> Bool)
-> (StrictMaybe a -> StrictMaybe a -> Bool)
-> (StrictMaybe a -> StrictMaybe a -> Bool)
-> (StrictMaybe a -> StrictMaybe a -> StrictMaybe a)
-> (StrictMaybe a -> StrictMaybe a -> StrictMaybe a)
-> Ord (StrictMaybe a)
StrictMaybe a -> StrictMaybe a -> Bool
StrictMaybe a -> StrictMaybe a -> Ordering
StrictMaybe a -> StrictMaybe a -> StrictMaybe a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (StrictMaybe a)
forall a. Ord a => StrictMaybe a -> StrictMaybe a -> Bool
forall a. Ord a => StrictMaybe a -> StrictMaybe a -> Ordering
forall a. Ord a => StrictMaybe a -> StrictMaybe a -> StrictMaybe a
$ccompare :: forall a. Ord a => StrictMaybe a -> StrictMaybe a -> Ordering
compare :: StrictMaybe a -> StrictMaybe a -> Ordering
$c< :: forall a. Ord a => StrictMaybe a -> StrictMaybe a -> Bool
< :: StrictMaybe a -> StrictMaybe a -> Bool
$c<= :: forall a. Ord a => StrictMaybe a -> StrictMaybe a -> Bool
<= :: StrictMaybe a -> StrictMaybe a -> Bool
$c> :: forall a. Ord a => StrictMaybe a -> StrictMaybe a -> Bool
> :: StrictMaybe a -> StrictMaybe a -> Bool
$c>= :: forall a. Ord a => StrictMaybe a -> StrictMaybe a -> Bool
>= :: StrictMaybe a -> StrictMaybe a -> Bool
$cmax :: forall a. Ord a => StrictMaybe a -> StrictMaybe a -> StrictMaybe a
max :: StrictMaybe a -> StrictMaybe a -> StrictMaybe a
$cmin :: forall a. Ord a => StrictMaybe a -> StrictMaybe a -> StrictMaybe a
min :: StrictMaybe a -> StrictMaybe a -> StrictMaybe a
Ord
, Int -> StrictMaybe a -> ShowS
[StrictMaybe a] -> ShowS
StrictMaybe a -> String
(Int -> StrictMaybe a -> ShowS)
-> (StrictMaybe a -> String)
-> ([StrictMaybe a] -> ShowS)
-> Show (StrictMaybe a)
forall a. Show a => Int -> StrictMaybe a -> ShowS
forall a. Show a => [StrictMaybe a] -> ShowS
forall a. Show a => StrictMaybe a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> StrictMaybe a -> ShowS
showsPrec :: Int -> StrictMaybe a -> ShowS
$cshow :: forall a. Show a => StrictMaybe a -> String
show :: StrictMaybe a -> String
$cshowList :: forall a. Show a => [StrictMaybe a] -> ShowS
showList :: [StrictMaybe a] -> ShowS
Show
, ReadPrec [StrictMaybe a]
ReadPrec (StrictMaybe a)
Int -> ReadS (StrictMaybe a)
ReadS [StrictMaybe a]
(Int -> ReadS (StrictMaybe a))
-> ReadS [StrictMaybe a]
-> ReadPrec (StrictMaybe a)
-> ReadPrec [StrictMaybe a]
-> Read (StrictMaybe a)
forall a. Read a => ReadPrec [StrictMaybe a]
forall a. Read a => ReadPrec (StrictMaybe a)
forall a. Read a => Int -> ReadS (StrictMaybe a)
forall a. Read a => ReadS [StrictMaybe a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall a. Read a => Int -> ReadS (StrictMaybe a)
readsPrec :: Int -> ReadS (StrictMaybe a)
$creadList :: forall a. Read a => ReadS [StrictMaybe a]
readList :: ReadS [StrictMaybe a]
$creadPrec :: forall a. Read a => ReadPrec (StrictMaybe a)
readPrec :: ReadPrec (StrictMaybe a)
$creadListPrec :: forall a. Read a => ReadPrec [StrictMaybe a]
readListPrec :: ReadPrec [StrictMaybe a]
Read
, (forall x. StrictMaybe a -> Rep (StrictMaybe a) x)
-> (forall x. Rep (StrictMaybe a) x -> StrictMaybe a)
-> Generic (StrictMaybe a)
forall x. Rep (StrictMaybe a) x -> StrictMaybe a
forall x. StrictMaybe a -> Rep (StrictMaybe a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (StrictMaybe a) x -> StrictMaybe a
forall a x. StrictMaybe a -> Rep (StrictMaybe a) x
$cfrom :: forall a x. StrictMaybe a -> Rep (StrictMaybe a) x
from :: forall x. StrictMaybe a -> Rep (StrictMaybe a) x
$cto :: forall a x. Rep (StrictMaybe a) x -> StrictMaybe a
to :: forall x. Rep (StrictMaybe a) x -> StrictMaybe a
Generic
, (forall a b. (a -> b) -> StrictMaybe a -> StrictMaybe b)
-> (forall a b. a -> StrictMaybe b -> StrictMaybe a)
-> Functor StrictMaybe
forall a b. a -> StrictMaybe b -> StrictMaybe a
forall a b. (a -> b) -> StrictMaybe a -> StrictMaybe b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> StrictMaybe a -> StrictMaybe b
fmap :: forall a b. (a -> b) -> StrictMaybe a -> StrictMaybe b
$c<$ :: forall a b. a -> StrictMaybe b -> StrictMaybe a
<$ :: forall a b. a -> StrictMaybe b -> StrictMaybe a
Functor
, (forall m. Monoid m => StrictMaybe m -> m)
-> (forall m a. Monoid m => (a -> m) -> StrictMaybe a -> m)
-> (forall m a. Monoid m => (a -> m) -> StrictMaybe a -> m)
-> (forall a b. (a -> b -> b) -> b -> StrictMaybe a -> b)
-> (forall a b. (a -> b -> b) -> b -> StrictMaybe a -> b)
-> (forall b a. (b -> a -> b) -> b -> StrictMaybe a -> b)
-> (forall b a. (b -> a -> b) -> b -> StrictMaybe a -> b)
-> (forall a. (a -> a -> a) -> StrictMaybe a -> a)
-> (forall a. (a -> a -> a) -> StrictMaybe a -> a)
-> (forall a. StrictMaybe a -> [a])
-> (forall a. StrictMaybe a -> Bool)
-> (forall a. StrictMaybe a -> Int)
-> (forall a. Eq a => a -> StrictMaybe a -> Bool)
-> (forall a. Ord a => StrictMaybe a -> a)
-> (forall a. Ord a => StrictMaybe a -> a)
-> (forall a. Num a => StrictMaybe a -> a)
-> (forall a. Num a => StrictMaybe a -> a)
-> Foldable StrictMaybe
forall a. Eq a => a -> StrictMaybe a -> Bool
forall a. Num a => StrictMaybe a -> a
forall a. Ord a => StrictMaybe a -> a
forall m. Monoid m => StrictMaybe m -> m
forall a. StrictMaybe a -> Bool
forall a. StrictMaybe a -> Int
forall a. StrictMaybe a -> [a]
forall a. (a -> a -> a) -> StrictMaybe a -> a
forall m a. Monoid m => (a -> m) -> StrictMaybe a -> m
forall b a. (b -> a -> b) -> b -> StrictMaybe a -> b
forall a b. (a -> b -> b) -> b -> StrictMaybe a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => StrictMaybe m -> m
fold :: forall m. Monoid m => StrictMaybe m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> StrictMaybe a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> StrictMaybe a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> StrictMaybe a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> StrictMaybe a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> StrictMaybe a -> b
foldr :: forall a b. (a -> b -> b) -> b -> StrictMaybe a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> StrictMaybe a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> StrictMaybe a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> StrictMaybe a -> b
foldl :: forall b a. (b -> a -> b) -> b -> StrictMaybe a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> StrictMaybe a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> StrictMaybe a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> StrictMaybe a -> a
foldr1 :: forall a. (a -> a -> a) -> StrictMaybe a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> StrictMaybe a -> a
foldl1 :: forall a. (a -> a -> a) -> StrictMaybe a -> a
$ctoList :: forall a. StrictMaybe a -> [a]
toList :: forall a. StrictMaybe a -> [a]
$cnull :: forall a. StrictMaybe a -> Bool
null :: forall a. StrictMaybe a -> Bool
$clength :: forall a. StrictMaybe a -> Int
length :: forall a. StrictMaybe a -> Int
$celem :: forall a. Eq a => a -> StrictMaybe a -> Bool
elem :: forall a. Eq a => a -> StrictMaybe a -> Bool
$cmaximum :: forall a. Ord a => StrictMaybe a -> a
maximum :: forall a. Ord a => StrictMaybe a -> a
$cminimum :: forall a. Ord a => StrictMaybe a -> a
minimum :: forall a. Ord a => StrictMaybe a -> a
$csum :: forall a. Num a => StrictMaybe a -> a
sum :: forall a. Num a => StrictMaybe a -> a
$cproduct :: forall a. Num a => StrictMaybe a -> a
product :: forall a. Num a => StrictMaybe a -> a
Foldable
, Functor StrictMaybe
Foldable StrictMaybe
(Functor StrictMaybe, Foldable StrictMaybe) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> StrictMaybe a -> f (StrictMaybe b))
-> (forall (f :: * -> *) a.
Applicative f =>
StrictMaybe (f a) -> f (StrictMaybe a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> StrictMaybe a -> m (StrictMaybe b))
-> (forall (m :: * -> *) a.
Monad m =>
StrictMaybe (m a) -> m (StrictMaybe a))
-> Traversable StrictMaybe
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
StrictMaybe (m a) -> m (StrictMaybe a)
forall (f :: * -> *) a.
Applicative f =>
StrictMaybe (f a) -> f (StrictMaybe a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> StrictMaybe a -> m (StrictMaybe b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> StrictMaybe a -> f (StrictMaybe b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> StrictMaybe a -> f (StrictMaybe b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> StrictMaybe a -> f (StrictMaybe b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
StrictMaybe (f a) -> f (StrictMaybe a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
StrictMaybe (f a) -> f (StrictMaybe a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> StrictMaybe a -> m (StrictMaybe b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> StrictMaybe a -> m (StrictMaybe b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
StrictMaybe (m a) -> m (StrictMaybe a)
sequence :: forall (m :: * -> *) a.
Monad m =>
StrictMaybe (m a) -> m (StrictMaybe a)
Traversable
, Context -> StrictMaybe a -> IO (Maybe ThunkInfo)
Proxy (StrictMaybe a) -> String
(Context -> StrictMaybe a -> IO (Maybe ThunkInfo))
-> (Context -> StrictMaybe a -> IO (Maybe ThunkInfo))
-> (Proxy (StrictMaybe a) -> String)
-> NoThunks (StrictMaybe a)
forall a.
NoThunks a =>
Context -> StrictMaybe a -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Proxy (StrictMaybe a) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: forall a.
NoThunks a =>
Context -> StrictMaybe a -> IO (Maybe ThunkInfo)
noThunks :: Context -> StrictMaybe a -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall a.
NoThunks a =>
Context -> StrictMaybe a -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> StrictMaybe a -> IO (Maybe ThunkInfo)
$cshowTypeOf :: forall a. NoThunks a => Proxy (StrictMaybe a) -> String
showTypeOf :: Proxy (StrictMaybe a) -> String
NoThunks
, StrictMaybe a -> ()
(StrictMaybe a -> ()) -> NFData (StrictMaybe a)
forall a. NFData a => StrictMaybe a -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall a. NFData a => StrictMaybe a -> ()
rnf :: StrictMaybe a -> ()
NFData
)
instance Applicative StrictMaybe where
pure :: forall a. a -> StrictMaybe a
pure = a -> StrictMaybe a
forall a. a -> StrictMaybe a
SJust
SJust a -> b
f <*> :: forall a b. StrictMaybe (a -> b) -> StrictMaybe a -> StrictMaybe b
<*> StrictMaybe a
m = (a -> b) -> StrictMaybe a -> StrictMaybe b
forall a b. (a -> b) -> StrictMaybe a -> StrictMaybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f StrictMaybe a
m
StrictMaybe (a -> b)
SNothing <*> StrictMaybe a
_m = StrictMaybe b
forall a. StrictMaybe a
SNothing
SJust a
_m1 *> :: forall a b. StrictMaybe a -> StrictMaybe b -> StrictMaybe b
*> StrictMaybe b
m2 = StrictMaybe b
m2
StrictMaybe a
SNothing *> StrictMaybe b
_m2 = StrictMaybe b
forall a. StrictMaybe a
SNothing
instance Monad StrictMaybe where
SJust a
x >>= :: forall a b. StrictMaybe a -> (a -> StrictMaybe b) -> StrictMaybe b
>>= a -> StrictMaybe b
k = a -> StrictMaybe b
k a
x
StrictMaybe a
SNothing >>= a -> StrictMaybe b
_ = StrictMaybe b
forall a. StrictMaybe a
SNothing
>> :: forall a b. StrictMaybe a -> StrictMaybe b -> StrictMaybe b
(>>) = StrictMaybe a -> StrictMaybe b -> StrictMaybe b
forall a b. StrictMaybe a -> StrictMaybe b -> StrictMaybe b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>)
return :: forall a. a -> StrictMaybe a
return = a -> StrictMaybe a
forall a. a -> StrictMaybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
instance MonadFail StrictMaybe where
fail :: forall a. String -> StrictMaybe a
fail String
_ = StrictMaybe a
forall a. StrictMaybe a
SNothing
instance ToCBOR a => ToCBOR (StrictMaybe a) where
toCBOR :: StrictMaybe a -> Encoding
toCBOR StrictMaybe a
SNothing = Word -> Encoding
encodeListLen Word
0
toCBOR (SJust a
x) = Word -> Encoding
encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> a -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR a
x
instance FromCBOR a => FromCBOR (StrictMaybe a) where
fromCBOR :: forall s. Decoder s (StrictMaybe a)
fromCBOR = do
Maybe Int
maybeN <- Decoder s (Maybe Int)
forall s. Decoder s (Maybe Int)
decodeListLenOrIndef
case Maybe Int
maybeN of
Just Int
0 -> StrictMaybe a -> Decoder s (StrictMaybe a)
forall a. a -> Decoder s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure StrictMaybe a
forall a. StrictMaybe a
SNothing
Just Int
1 -> a -> StrictMaybe a
forall a. a -> StrictMaybe a
SJust (a -> StrictMaybe a) -> Decoder s a -> Decoder s (StrictMaybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s a
forall s. Decoder s a
forall a s. FromCBOR a => Decoder s a
fromCBOR
Just Int
_ -> String -> Decoder s (StrictMaybe a)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"too many elements in length-style decoding of StrictMaybe."
Maybe Int
Nothing -> do
Bool
isBreak <- Decoder s Bool
forall s. Decoder s Bool
decodeBreakOr
if Bool
isBreak
then StrictMaybe a -> Decoder s (StrictMaybe a)
forall a. a -> Decoder s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure StrictMaybe a
forall a. StrictMaybe a
SNothing
else do
a
x <- Decoder s a
forall s. Decoder s a
forall a s. FromCBOR a => Decoder s a
fromCBOR
Bool
isBreak2 <- Decoder s Bool
forall s. Decoder s Bool
decodeBreakOr
if Bool
isBreak2
then StrictMaybe a -> Decoder s (StrictMaybe a)
forall a. a -> Decoder s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> StrictMaybe a
forall a. a -> StrictMaybe a
SJust a
x)
else String -> Decoder s (StrictMaybe a)
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"too many elements in break-style decoding of StrictMaybe."
instance ToJSON a => ToJSON (StrictMaybe a) where
toJSON :: StrictMaybe a -> Value
toJSON = Maybe a -> Value
forall a. ToJSON a => a -> Value
toJSON (Maybe a -> Value)
-> (StrictMaybe a -> Maybe a) -> StrictMaybe a -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictMaybe a -> Maybe a
forall a. StrictMaybe a -> Maybe a
strictMaybeToMaybe
toEncoding :: StrictMaybe a -> Encoding
toEncoding = Maybe a -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding (Maybe a -> Encoding)
-> (StrictMaybe a -> Maybe a) -> StrictMaybe a -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictMaybe a -> Maybe a
forall a. StrictMaybe a -> Maybe a
strictMaybeToMaybe
instance FromJSON a => FromJSON (StrictMaybe a) where
parseJSON :: Value -> Parser (StrictMaybe a)
parseJSON Value
v = Maybe a -> StrictMaybe a
forall a. Maybe a -> StrictMaybe a
maybeToStrictMaybe (Maybe a -> StrictMaybe a)
-> Parser (Maybe a) -> Parser (StrictMaybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser (Maybe a)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
strictMaybeToMaybe :: StrictMaybe a -> Maybe a
strictMaybeToMaybe :: forall a. StrictMaybe a -> Maybe a
strictMaybeToMaybe StrictMaybe a
SNothing = Maybe a
forall a. Maybe a
Nothing
strictMaybeToMaybe (SJust a
x) = a -> Maybe a
forall a. a -> Maybe a
Just a
x
maybeToStrictMaybe :: Maybe a -> StrictMaybe a
maybeToStrictMaybe :: forall a. Maybe a -> StrictMaybe a
maybeToStrictMaybe Maybe a
Nothing = StrictMaybe a
forall a. StrictMaybe a
SNothing
maybeToStrictMaybe (Just a
x) = a -> StrictMaybe a
forall a. a -> StrictMaybe a
SJust a
x
fromSMaybe :: a -> StrictMaybe a -> a
fromSMaybe :: forall a. a -> StrictMaybe a -> a
fromSMaybe a
d StrictMaybe a
SNothing = a
d
fromSMaybe a
_ (SJust a
x) = a
x
isSNothing :: StrictMaybe a -> Bool
isSNothing :: forall a. StrictMaybe a -> Bool
isSNothing StrictMaybe a
SNothing = Bool
True
isSNothing StrictMaybe a
_ = Bool
False
isSJust :: StrictMaybe a -> Bool
isSJust :: forall a. StrictMaybe a -> Bool
isSJust = Bool -> Bool
not (Bool -> Bool) -> (StrictMaybe a -> Bool) -> StrictMaybe a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictMaybe a -> Bool
forall a. StrictMaybe a -> Bool
isSNothing
strictMaybe :: a -> (b -> a) -> StrictMaybe b -> a
strictMaybe :: forall a b. a -> (b -> a) -> StrictMaybe b -> a
strictMaybe a
x b -> a
_ StrictMaybe b
SNothing = a
x
strictMaybe a
_ b -> a
f (SJust b
y) = b -> a
f b
y
instance Default (StrictMaybe t) where
def :: StrictMaybe t
def = StrictMaybe t
forall a. StrictMaybe a
SNothing
instance Semigroup a => Semigroup (StrictMaybe a) where
StrictMaybe a
SNothing <> :: StrictMaybe a -> StrictMaybe a -> StrictMaybe a
<> StrictMaybe a
x = StrictMaybe a
x
StrictMaybe a
x <> StrictMaybe a
SNothing = StrictMaybe a
x
SJust a
x <> SJust a
y = a -> StrictMaybe a
forall a. a -> StrictMaybe a
SJust (a
x a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
y)
instance Semigroup a => Monoid (StrictMaybe a) where
mempty :: StrictMaybe a
mempty = StrictMaybe a
forall a. StrictMaybe a
SNothing
instance Alternative StrictMaybe where
empty :: forall a. StrictMaybe a
empty = StrictMaybe a
forall a. StrictMaybe a
SNothing
StrictMaybe a
SNothing <|> :: forall a. StrictMaybe a -> StrictMaybe a -> StrictMaybe a
<|> StrictMaybe a
r = StrictMaybe a
r
StrictMaybe a
l <|> StrictMaybe a
_ = StrictMaybe a
l
instance Eq1 StrictMaybe where
liftEq :: forall a b.
(a -> b -> Bool) -> StrictMaybe a -> StrictMaybe b -> Bool
liftEq a -> b -> Bool
f (SJust a
a) (SJust b
b) = a -> b -> Bool
f a
a b
b
liftEq a -> b -> Bool
_ StrictMaybe a
SNothing StrictMaybe b
SNothing = Bool
True
liftEq a -> b -> Bool
_ StrictMaybe a
_ StrictMaybe b
_ = Bool
False
instance Ord1 StrictMaybe where
liftCompare :: forall a b.
(a -> b -> Ordering) -> StrictMaybe a -> StrictMaybe b -> Ordering
liftCompare a -> b -> Ordering
_ StrictMaybe a
SNothing StrictMaybe b
SNothing = Ordering
EQ
liftCompare a -> b -> Ordering
_ StrictMaybe a
SNothing (SJust b
_) = Ordering
LT
liftCompare a -> b -> Ordering
_ (SJust a
_) StrictMaybe b
SNothing = Ordering
GT
liftCompare a -> b -> Ordering
comp (SJust a
x) (SJust b
y) = a -> b -> Ordering
comp a
x b
y
instance Show1 StrictMaybe where
liftShowsPrec :: forall a.
(Int -> a -> ShowS)
-> ([a] -> ShowS) -> Int -> StrictMaybe a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
_ Int
d (SJust a
x) = (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith Int -> a -> ShowS
sp String
"SJust" Int
d a
x
liftShowsPrec Int -> a -> ShowS
_ [a] -> ShowS
_ Int
_ StrictMaybe a
SNothing = String -> ShowS
showString String
"SNothing"
instance Read1 StrictMaybe where
liftReadPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec (StrictMaybe a)
liftReadPrec ReadPrec a
rp ReadPrec [a]
_ =
ReadPrec (StrictMaybe a) -> ReadPrec (StrictMaybe a)
forall a. ReadPrec a -> ReadPrec a
parens (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"SNothing") ReadPrec () -> StrictMaybe a -> ReadPrec (StrictMaybe a)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> StrictMaybe a
forall a. StrictMaybe a
SNothing)
ReadPrec (StrictMaybe a)
-> ReadPrec (StrictMaybe a) -> ReadPrec (StrictMaybe a)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ReadPrec (StrictMaybe a) -> ReadPrec (StrictMaybe a)
forall a. ReadPrec a -> ReadPrec a
readData (ReadPrec a
-> String -> (a -> StrictMaybe a) -> ReadPrec (StrictMaybe a)
forall a t. ReadPrec a -> String -> (a -> t) -> ReadPrec t
readUnaryWith ReadPrec a
rp String
"SJust" a -> StrictMaybe a
forall a. a -> StrictMaybe a
SJust)
liftReadListPrec :: forall a. ReadPrec a -> ReadPrec [a] -> ReadPrec [StrictMaybe a]
liftReadListPrec = ReadPrec a -> ReadPrec [a] -> ReadPrec [StrictMaybe a]
forall (f :: * -> *) a.
Read1 f =>
ReadPrec a -> ReadPrec [a] -> ReadPrec [f a]
liftReadListPrecDefault
liftReadList :: forall a. (Int -> ReadS a) -> ReadS [a] -> ReadS [StrictMaybe a]
liftReadList = (Int -> ReadS a) -> ReadS [a] -> ReadS [StrictMaybe a]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadListDefault