module Streamly.Internal.Data.Maybe.Strict
( Maybe' (..)
, toMaybe
, isJust'
, fromJust'
)
where
data Maybe' a = Just' !a | Nothing' deriving Int -> Maybe' a -> ShowS
[Maybe' a] -> ShowS
Maybe' a -> String
(Int -> Maybe' a -> ShowS)
-> (Maybe' a -> String) -> ([Maybe' a] -> ShowS) -> Show (Maybe' a)
forall a. Show a => Int -> Maybe' a -> ShowS
forall a. Show a => [Maybe' a] -> ShowS
forall a. Show a => Maybe' a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Maybe' a] -> ShowS
$cshowList :: forall a. Show a => [Maybe' a] -> ShowS
show :: Maybe' a -> String
$cshow :: forall a. Show a => Maybe' a -> String
showsPrec :: Int -> Maybe' a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Maybe' a -> ShowS
Show
{-# INLINABLE toMaybe #-}
toMaybe :: Maybe' a -> Maybe a
toMaybe :: Maybe' a -> Maybe a
toMaybe Maybe' a
Nothing' = Maybe a
forall a. Maybe a
Nothing
toMaybe (Just' a
a) = a -> Maybe a
forall a. a -> Maybe a
Just a
a
{-# INLINABLE fromJust' #-}
fromJust' :: Maybe' a -> a
fromJust' :: Maybe' a -> a
fromJust' (Just' a
a) = a
a
fromJust' Maybe' a
Nothing' = String -> a
forall a. HasCallStack => String -> a
error String
"fromJust' cannot be run in Nothing'"
{-# INLINABLE isJust' #-}
isJust' :: Maybe' a -> Bool
isJust' :: Maybe' a -> Bool
isJust' (Just' a
_) = Bool
True
isJust' Maybe' a
Nothing' = Bool
False