{-# LANGUAGE LinearTypes #-}
{-# LANGUAGE NoImplicitPrelude #-}

-- | This module provides linear functions on the standard 'Maybe' type.
module Data.Maybe.Linear
  ( Maybe (..)
  , maybe
  , fromMaybe
  , maybeToList
  , catMaybes
  , mapMaybe
  )
  where

import qualified Data.Functor.Linear as Linear
import Prelude (Maybe(..))

-- | @maybe b f m@ returns @(f a)@ where @a@ is in
-- @m@ if it exists and @b@ otherwise
maybe :: b -> (a %1-> b) -> Maybe a %1-> b
maybe :: forall b a. b -> (a %1 -> b) -> Maybe a %1 -> b
maybe b
x a %1 -> b
_ Maybe a
Nothing = b
x
maybe b
_ a %1 -> b
f (Just a
y) = a %1 -> b
f a
y

-- | @fromMaybe default m@ is the @a@ in
-- @m@ if it exists and the @default@ otherwise
fromMaybe :: a -> Maybe a %1-> a
fromMaybe :: forall a. a -> Maybe a %1 -> a
fromMaybe a
a Maybe a
Nothing = a
a
fromMaybe a
_ (Just a
a') = a
a'

-- | @maybeToList m@ creates a singleton or an empty list
-- based on the @Maybe a@.
maybeToList :: Maybe a %1-> [a]
maybeToList :: forall a. Maybe a %1 -> [a]
maybeToList Maybe a
Nothing = []
maybeToList (Just a
a) = [a
a]

-- | @catMaybes xs@ discards the @Nothing@s in @xs@
-- and extracts the @a@s
catMaybes :: [Maybe a] %1-> [a]
catMaybes :: forall a. [Maybe a] %1 -> [a]
catMaybes [] = []
catMaybes (Maybe a
Nothing : [Maybe a]
xs) = [Maybe a] %1 -> [a]
forall a. [Maybe a] %1 -> [a]
catMaybes [Maybe a]
xs
catMaybes (Just a
a : [Maybe a]
xs) = a
a a %1 -> [a] %1 -> [a]
forall a. a -> [a] -> [a]
: [Maybe a] %1 -> [a]
forall a. [Maybe a] %1 -> [a]
catMaybes [Maybe a]
xs

-- | @mapMaybe f xs = catMaybes (map f xs)@
mapMaybe :: (a %1-> Maybe b) -> [a] %1-> [b]
mapMaybe :: forall a b. (a %1 -> Maybe b) -> [a] %1 -> [b]
mapMaybe a %1 -> Maybe b
f [a]
xs = [Maybe b] %1 -> [b]
forall a. [Maybe a] %1 -> [a]
catMaybes ((a %1 -> Maybe b) -> [a] %1 -> [Maybe b]
forall (f :: * -> *) a b. Functor f => (a %1 -> b) -> f a %1 -> f b
Linear.fmap a %1 -> Maybe b
f [a]
xs)