-- |
-- Module      : Streamly.Internal.Data.Maybe.Strict
-- Copyright   : (c) 2019 Composewell Technologies
--               (c) 2013 Gabriel Gonzalez
-- License     : BSD3
-- Maintainer  : streamly@composewell.com
-- Stability   : experimental
-- Portability : GHC
--
-- | Strict data types to be used as accumulator for strict left folds and
-- scans. For more comprehensive strict data types see
-- https://hackage.haskell.org/package/strict-base-types . The names have been
-- suffixed by a prime so that programmers can easily distinguish the strict
-- versions from the lazy ones.
--
-- One major advantage of strict data structures as accumulators in folds and
-- scans is that it helps the compiler optimize the code much better by
-- unboxing. In a big tight loop the difference could be huge.
--
module Streamly.Internal.Data.Maybe.Strict
    ( Maybe' (..)
    , toMaybe
    , isJust'
    , fromJust'
    )
where

-- | A strict 'Maybe'
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

-- | Convert strict Maybe' to lazy Maybe
{-# 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

-- | Extract the element out of a Just' and throws an error if its argument is
-- Nothing'.
{-# 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'"

-- | Returns True iff its argument is of the form "Just' _".
{-# INLINABLE isJust' #-}
isJust' :: Maybe' a -> Bool
isJust' :: Maybe' a -> Bool
isJust' (Just' a
_) = Bool
True
isJust' Maybe' a
Nothing' = Bool
False