module Prolude.Maybe
  ( module Data.Maybe
  , note
  , hush
  )
where

import Data.Maybe
    ( Maybe(Just, Nothing)
    , catMaybes
    , fromMaybe
    , isJust
    , isNothing
    , listToMaybe
    , mapMaybe
    , maybe
    , maybeToList
    )

{-# INLINE hush #-}
-- | Suppress the 'Left' value of an 'Either'
hush :: Either a b -> Maybe b
hush :: Either a b -> Maybe b
hush = (a -> Maybe b) -> (b -> Maybe b) -> Either a b -> Maybe b
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe b -> a -> Maybe b
forall a b. a -> b -> a
const Maybe b
forall a. Maybe a
Nothing) b -> Maybe b
forall a. a -> Maybe a
Just

{-# INLINE note #-}
-- | Tag the 'Nothing' value of a 'Maybe'
note :: a -> Maybe b -> Either a b
note :: a -> Maybe b -> Either a b
note a
a = Either a b -> (b -> Either a b) -> Maybe b -> Either a b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (a -> Either a b
forall a b. a -> Either a b
Left a
a) b -> Either a b
forall a b. b -> Either a b
Right