{-# LANGUAGE TupleSections #-} module Clean.Foldable where import Clean.Core import Clean.Classes import Clean.Functor import Data.Tree class Functor t => Foldable t where fold :: Monoid m => t m -> m instance Foldable Id where fold = getId instance Foldable (Either a) where fold = pure zero <|> id instance Foldable [] where fold [] = zero fold (x:t) = x+fold t deriving instance Foldable Interleave instance Foldable Tree where fold (Node m subs) = m + fold (map fold subs) foldMap f e = fold (map f e) concat = fold sum = fold split ch = foldMap (\a -> ((,zero)<|>(zero,)) (ch a)) partition p = split (\a -> (if p a then Left else Right) (pure a)) filter p = fst . partition p count = sum . map (const 1) length :: (Num n,Monoid n) => [a] -> n length = count foldl f e t = runEndo (foldMap (\b -> Endo (\a -> f a b)) t) e foldr f e t = runEndo (foldMap (\b -> Endo (f b)) t) e