{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-unticked-promoted-constructors #-}
module Relude.Foldable.Fold
( flipfoldl'
, foldMapA
, foldMapM
, safeHead
, sum
, product
, elem
, notElem
, allM
, anyM
, andM
, orM
) where
import GHC.TypeLits (ErrorMessage (..), TypeError)
import Relude.Applicative (Applicative (..), pure)
import Relude.Base (Constraint, Eq, IO, Num (..), Type, ($!))
import Relude.Bool (Bool (..))
import Relude.Container.Reexport (HashSet, Set)
import Relude.Foldable.Reexport (Foldable (..))
import Relude.Function (flip, (.))
import Relude.Functor ((<$>))
import Relude.Monad.Reexport (Maybe (..), Monad (..))
import Relude.Monoid (Monoid (..))
import qualified Data.Foldable as F
safeHead :: Foldable f => f a -> Maybe a
safeHead = foldr (\x _ -> Just x) Nothing
{-# INLINE safeHead #-}
flipfoldl' :: Foldable f => (a -> b -> b) -> b -> f a -> b
flipfoldl' f = foldl' (flip f)
{-# INLINE flipfoldl' #-}
foldMapA :: (Monoid b, Applicative m, Foldable f) => (a -> m b) -> f a -> m b
foldMapA f = foldr step (pure mempty)
where
step a mb = mappend <$> f a <*> mb
{-# INLINE foldMapA #-}
foldMapM :: (Monoid b, Monad m, Foldable f) => (a -> m b) -> f a -> m b
foldMapM f xs = foldr step return xs mempty
where
step x r z = f x >>= \y -> r $! z `mappend` y
{-# INLINE foldMapM #-}
sum :: forall a f . (Foldable f, Num a) => f a -> a
sum = foldl' (+) 0
{-# INLINE sum #-}
product :: forall a f . (Foldable f, Num a) => f a -> a
product = foldl' (*) 1
{-# INLINE product #-}
elem :: (Foldable f, DisallowElem f, Eq a) => a -> f a -> Bool
elem = F.elem
{-# INLINE elem #-}
notElem :: (Foldable f, DisallowElem f, Eq a) => a -> f a -> Bool
notElem = F.notElem
{-# INLINE notElem #-}
andM :: (Foldable f, Monad m) => f (m Bool) -> m Bool
andM = go . toList
where
go [] = pure True
go (p:ps) = do
q <- p
if q then go ps else pure False
orM :: (Foldable f, Monad m) => f (m Bool) -> m Bool
orM = go . toList
where
go [] = pure False
go (p:ps) = do
q <- p
if q then pure True else go ps
allM :: (Foldable f, Monad m) => (a -> m Bool) -> f a -> m Bool
allM p = go . toList
where
go [] = pure True
go (x:xs) = do
q <- p x
if q then go xs else pure False
anyM :: (Foldable f, Monad m) => (a -> m Bool) -> f a -> m Bool
anyM p = go . toList
where
go [] = pure False
go (x:xs) = do
q <- p x
if q then pure True else go xs
{-# SPECIALIZE andM :: [IO Bool] -> IO Bool #-}
{-# SPECIALIZE orM :: [IO Bool] -> IO Bool #-}
{-# SPECIALIZE anyM :: (a -> IO Bool) -> [a] -> IO Bool #-}
{-# SPECIALIZE allM :: (a -> IO Bool) -> [a] -> IO Bool #-}
type family DisallowElem (f :: Type -> Type) :: Constraint where
DisallowElem Set = TypeError (ElemErrorMessage Set)
DisallowElem HashSet = TypeError (ElemErrorMessage HashSet)
DisallowElem f = ()
type family ElemErrorMessage (t :: k) :: ErrorMessage where
ElemErrorMessage t =
Text "Do not use 'elem' and 'notElem' methods from 'Foldable' on " :<>: ShowType t
:$$: Text "Suggestions:"
:$$: Text " Instead of"
:$$: Text " elem :: (Foldable t, Eq a) => a -> t a -> Bool"
:$$: Text " use"
:$$: Text " member :: ??? -- TODO"
:$$: Text ""
:$$: Text " Instead of"
:$$: Text " notElem :: (Foldable t, Eq a) => a -> t a -> Bool"
:$$: Text " use"
:$$: Text " notMember :: ??? -- TODO"
:$$: Text ""