#if __GLASGOW_HASKELL__ >= 706
#endif
module Agda.Utils.Maybe.Strict
  ( module Data.Strict.Maybe
  , module Agda.Utils.Maybe.Strict
  ) where
import Data.Strict.Maybe
import           Prelude             hiding (Maybe (..), maybe)
import qualified Prelude             as Lazy
import           Control.Applicative (pure, (<$>))
import           Control.DeepSeq     (NFData (..))
import           Data.Binary         (Binary (..))
#if MIN_VERSION_base(4,7,0)
import           Data.Data           (Data (..), Typeable)
#else
import           Data.Data           (Data (..), Typeable1 (..))
#endif
import           Data.Monoid         (Monoid (..))
import           Data.Foldable       (Foldable (..))
import           Data.Traversable    (Traversable (..))
import           Data.Strict.Maybe   (Maybe (Nothing, Just), fromJust,
                                      fromMaybe, isJust, isNothing, maybe)
#if __GLASGOW_HASKELL__ >= 706
import           GHC.Generics        (Generic (..))
#endif
import           Test.QuickCheck     (Arbitrary (..))
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)
#if MIN_VERSION_base(4,7,0)
deriving instance Typeable Maybe
#else
deriving instance Typeable1 Maybe
#endif
#if __GLASGOW_HASKELL__ >= 706
deriving instance Generic  (Maybe a)
#endif
instance Monoid a => Monoid (Maybe a) where
  mempty = Nothing
  Nothing `mappend` _       = Nothing
  _       `mappend` Nothing = Nothing
  Just x1 `mappend` Just x2 = Just (x1 `mappend` x2)
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
instance Arbitrary a => Arbitrary (Maybe a) where
  arbitrary = toStrict <$> arbitrary
  shrink    = map toStrict . shrink . toLazy
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)