{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric      #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Agda.Utils.Maybe.Strict
  ( module Data.Strict.Maybe
  , module Agda.Utils.Maybe.Strict
  ) where
import           Prelude             hiding (Maybe (..), maybe, null)
import qualified Prelude             as Lazy
import           Control.DeepSeq     (NFData (..))
import           Data.Binary         (Binary (..))
import           Data.Data           (Data (..))
import           Data.Semigroup      (Semigroup, (<>))
import           Data.Strict.Maybe   (Maybe (Nothing, Just), fromJust,
                                      fromMaybe, isJust, isNothing, maybe)
import           GHC.Generics        (Generic (..))
import Agda.Utils.Null
toStrict :: Lazy.Maybe a -> Maybe a
toStrict Lazy.Nothing  = Nothing
toStrict (Lazy.Just x) = Just x
toLazy :: Maybe a -> Lazy.Maybe a
toLazy Nothing  = Lazy.Nothing
toLazy (Just x) = Lazy.Just x
deriving instance Data a => Data (Maybe a)
deriving instance Generic  (Maybe a)
instance Null (Maybe a) where
  empty = Nothing
  null = isNothing
instance Semigroup a => Semigroup (Maybe a) where
  (<>) = unionMaybeWith (<>)
instance Semigroup a => Monoid (Maybe a) where
  mempty  = Nothing
  mappend = (<>)
instance Applicative Maybe where
  pure              = Just
  Just f <*> Just x = Just $ f x
  _      <*> _      = Nothing
instance Foldable Maybe where
    foldMap _ Nothing  = mempty
    foldMap f (Just x) = f x
instance Traversable Maybe where
    traverse _ Nothing  = pure Nothing
    traverse f (Just x) = Just <$> f x
instance NFData a => NFData (Maybe a) where
  rnf = rnf . toLazy
instance Binary a => Binary (Maybe a) where
  put = put . toLazy
  get = toStrict <$> get
listToMaybe :: [a] -> Maybe a
listToMaybe []        =  Nothing
listToMaybe (a:_)     =  Just a
maybeToList :: Maybe a -> [a]
maybeToList  Nothing   = []
maybeToList  (Just x)  = [x]
catMaybes :: [Maybe a] -> [a]
catMaybes ls = [x | Just x <- ls]
mapMaybe :: (a -> Maybe b) -> [a] -> [b]
mapMaybe _ []     = []
mapMaybe f (x:xs) = case f x of
    Nothing -> rs
    Just r  -> r:rs
  where
    rs = mapMaybe f xs
unionMaybeWith :: (a -> a -> a) -> Maybe a -> Maybe a -> Maybe a
unionMaybeWith f Nothing mb      = mb
unionMaybeWith f ma      Nothing = ma
unionMaybeWith f (Just a) (Just b) = Just $ f a b
unzipMaybe :: Maybe (a,b) -> (Maybe a, Maybe b)
unzipMaybe Nothing      = (Nothing, Nothing)
unzipMaybe (Just (a,b)) = (Just a, Just b)
filterMaybe :: (a -> Bool) -> a -> Maybe a
filterMaybe p a
  | p a       = Just a
  | otherwise = Nothing
forMaybe :: [a] -> (a -> Maybe b) -> [b]
forMaybe = flip mapMaybe
caseMaybe :: Maybe a -> b -> (a -> b) -> b
caseMaybe m err f = maybe err f m
maybeM :: Monad m => m b -> (a -> m b) -> m (Maybe a) -> m b
maybeM n j mm = maybe n j =<< mm
fromMaybeM :: Monad m => m a -> m (Maybe a) -> m a
fromMaybeM m mm = maybeM m return mm
caseMaybeM :: Monad m => m (Maybe a) -> m b -> (a -> m b) -> m b
caseMaybeM mm err f = maybeM  err f mm
ifJustM :: Monad m => m (Maybe a) -> (a -> m b) -> m b -> m b
ifJustM mm = flip (caseMaybeM mm)
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust m k = caseMaybe m (return ()) k
whenJustM :: Monad m => m (Maybe a) -> (a -> m ()) -> m ()
whenJustM c m = c >>= (`whenJust` m)