{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Relude.Foldable.Fold
( flipfoldl'
, asumMap
, foldMapA
, foldMapM
, sum
, product
, elem
, notElem
, allM
, anyM
, andM
, orM
, DisallowElem
, ElemErrorMessage
) where
import GHC.TypeLits (ErrorMessage (..), Symbol, TypeError)
import Relude.Applicative (Alternative, Applicative (..), pure)
import Relude.Base (Constraint, Eq, IO, Type, ($!))
import Relude.Bool (Bool (..))
import Relude.Container.Reexport (HashSet, Set)
import Relude.Foldable.Reexport (Foldable (..))
import Relude.Function (flip, (.))
import Relude.Monad.Reexport (Monad (..))
import Relude.Monoid (Alt (..), Ap (..), Monoid (..), Semigroup)
import Relude.Numeric (Num (..))
import qualified Data.Foldable as F
flipfoldl' :: Foldable f => (a -> b -> b) -> b -> f a -> b
flipfoldl' f = foldl' (flip f)
{-# INLINE flipfoldl' #-}
asumMap :: (Foldable f, Alternative m) => (a -> m b) -> f a -> m b
asumMap f = getAlt . foldMap (Alt . f)
{-# INLINE asumMap #-}
foldMapA :: forall b m f a . (Semigroup b, Monoid b, Applicative m, Foldable f) => (a -> m b) -> f a -> m b
foldMapA f = getAp . foldMap (Ap . f)
{-# INLINE foldMapA #-}
foldMapM :: forall b m f a . (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 SetMemberType)
DisallowElem HashSet = TypeError (ElemErrorMessage HashSet HashSetMemberType)
DisallowElem f = ()
type family ElemErrorMessage (t :: k) (msg :: Symbol) :: ErrorMessage where
ElemErrorMessage t msg =
'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 :: " ':<>: 'Text msg
':$$: 'Text ""
':$$: 'Text " Instead of"
':$$: 'Text " notElem :: (Foldable t, Eq a) => a -> t a -> Bool"
':$$: 'Text " use"
':$$: 'Text " not . member"
':$$: 'Text ""
type SetMemberType = "Ord a => a -> Set a -> Bool"
type HashSetMemberType = "(Eq a, Hashable a) => a -> HashSet a -> Bool"