module Data.ListLike.Utils
(and, or, sum, product, zip, zipWith, unzip, sequence_, toMonadPlus, list,
intercalate
) where
import Prelude hiding (length, head, last, null, tail, map, filter, concat,
any, lookup, init, all, foldl, foldr, foldl1, foldr1,
maximum, minimum, iterate, span, break, takeWhile,
dropWhile, reverse, zip, zipWith, sequence,
sequence_, mapM, mapM_, concatMap, and, or, sum,
product, repeat, replicate, cycle, take, drop,
splitAt, elem, notElem, unzip, lines, words,
unlines, unwords, foldMap)
import Control.Monad (MonadPlus(..))
import Data.ListLike.Base
import Data.ListLike.FoldableLL
import Data.Maybe (maybe)
import Data.Monoid
and :: ListLike full Bool => full -> Bool
and = all (== True)
or :: ListLike full Bool => full -> Bool
or = any (== True)
sum :: (Num a, ListLike full a) => full -> a
sum = getSum . foldMap Sum
product :: (Num a, ListLike full a) => full -> a
product = getProduct . foldMap Product
unzip :: (ListLike full (itema, itemb),
ListLike ra itema,
ListLike rb itemb) => full -> (ra, rb)
unzip inp = foldr convert (empty, empty) inp
where convert (a, b) (as, bs) = ((cons a as), (cons b bs))
toMonadPlus :: (MonadPlus m, ListLike full a) => full -> m (a, full)
toMonadPlus = maybe mzero return . uncons
list :: ListLike full a => b -> (a -> full -> b) -> full -> b
list d f = maybe d (uncurry f) . toMonadPlus
intercalate :: (ListLike a item, ListLike b a)
=> a -> b -> a
intercalate x = concat . intersperse x