module Hcompta.Lib.Foldable where
-import Data.Monoid
-import Data.Maybe (listToMaybe, maybeToList)
-import Data.Foldable (Foldable, foldMap, foldr)
+import Data.Either (Either(..), either)
+import Data.Foldable (Foldable(..))
+import Data.Function ((.))
+import Data.Maybe (Maybe(..), listToMaybe, maybeToList)
+import Data.Monoid (Monoid(..))
-- | Return the first non-'Nothing' returned by the given function
-- applied on the elements of a 'Foldable'.
find :: Foldable t => (a -> Maybe b) -> t a -> Maybe b
-find f = listToMaybe . Data.Foldable.foldMap (maybeToList . f)
+find f = listToMaybe . foldMap (maybeToList . f)
-- | Like 'Data.Either.partitionEithers' but generalized
-- to work on a 'Foldable' containing 'Monoid's.
partitionEithers
:: (Foldable t, Monoid r, Monoid l)
=> t (Either l r) -> (l, r)
-partitionEithers m =
- Data.Foldable.foldr (either left right) (mempty, mempty) m
+partitionEithers =
+ foldr (either left right) (mempty, mempty)
where
left a ~(l, r) = (a`mappend`l, r)
right a ~(l, r) = (l, a`mappend`r)
-- | Return a tuple of accumulated 'Left's and folded 'Right's
-- in the given 'Foldable'.
--
--- NOTE: any lazyness on resulting 'Left's’ 'Monoid' is preserved.
+-- * NOTE: any lazyness on resulting 'Monoid's is preserved.
+-- * WARNING: beware that given an infinite 'Foldable',
+-- the initial 'Right' accumulator will never be appended
+-- to the final 'Right' accumulator.
accumLeftsAndFoldrRights
:: (Foldable t, Monoid l)
=> (r -> ra -> ra) -> ra -> t (Either l r) -> (l, ra)
-accumLeftsAndFoldrRights f rempty m =
- Data.Foldable.foldr (either left right) (mempty, rempty) m
+accumLeftsAndFoldrRights f rempty =
+ foldr (either left right) (mempty, rempty)
where
left a ~(l, r) = (a`mappend`l, r)
right a ~(l, r) = (l, f a r)