Skip to content

Instantly share code, notes, and snippets.

@monadplus
Created January 27, 2020 22:17
Show Gist options
  • Save monadplus/0ec8e2102445c9e07936f087323b370d to your computer and use it in GitHub Desktop.
Save monadplus/0ec8e2102445c9e07936f087323b370d to your computer and use it in GitHub Desktop.
foldl: Composable, streaming, and efficient left folds (https://hackage.haskell.org/package/foldl)
module Foldl where
import qualified Control.Foldl as L
import Control.Applicative
import Data.Functor
import Data.Monoid
import Control.Monad.State
import Data.Functor.Identity
-- More on https://hackage.haskell.org/package/foldl
-- I recommend taking a look at the sources :-)
-- Actions:
--
-- fold :: Foldable f => Fold a b -> f a -> b
-- foldM :: (Foldable f, Monad m) => FoldM m a b -> f a -> m b
-- scan :: Fold a b -> [a] -> [b]
-- Folds:
--
-- foldMap :: Monoid w => (a -> w) -> (w -> b) -> Fold a b
-- head :: Fold a (Maybe a)
-- last :: Fold a (Maybe a)
-- length :: Fold a Int
-- mean :: Fractional a => Fold a a
-- variance :: Fractional a => Fold a a
-- random :: FoldM IO a (Maybe a)
-- mapM_ :: Monad m => (a -> m ()) -> FoldM m a ()
-- sink :: (Monoid w, Monad m) => (a -> m w) -> FoldM m a w
-- ...
-- Containers:
--
-- revList :: Fold a [a]
-- set :: Ord a => Fold a (Set a)
-- map :: Ord a => Fold (a, b) (Map a b)
-- Utilities
--
-- purely and impurely allow you to write folds compatible with the foldl library without incurring a foldl dependency.
--
-- Pipes implements the following fold/foldM operations:
--
-- Pipes.Prelude.fold
-- :: Monad m
-- -> (x -> a -> x) -> x -> (x -> b) -> Producer a m () -> m b
--
-- Pipes.Prelude.foldM
-- :: Monad m
-- => (x -> a -> m x) -> m x -> (x -> m b) -> Producer a m () -> m b
-- They can be translate into Fold/FoldM:
-- purely Pipes.Prelude.fold
-- :: Monad m => Fold a b -> Producer a m () -> m b
--
-- impurely Pipes.Prelude.foldM
-- :: Monad m => FoldM m a b -> Producer a m () -> m b
-- hoists :: (forall x. m x -> n x) -> FoldM m a b -> FoldM n a b
-- _Fold1 :: (a -> a -> a) -> Fold a (Maybe a)
-- premap :: (a -> b) -> Fold b r -> Fold a r
-- prefilter :: (a -> Bool) -> Fold a r -> Fold a r
-- drop :: Natural -> Fold a b -> Fold a b
-- There are also some utilities that work with `lens` library!
---------------------------------------------------
-- Examples
-- nb.avg is already implemented
avg :: Fractional a => L.Fold a a
avg = (/) <$> L.sum <*> L.genericLength
-- >>> L.fold avg [1..10000000]
minAndMax = L.fold ((,) <$> L.minimum <*> L.maximum) [1..10000000]
sum' = L.foldMap Sum getSum
-- >>> L.fold (liftA2 (,) L.head L.last) [1..100]
-- >>> L.fold (L.mconcat) (coerce [1..100] :: [Sum Integer])
-- >>> L.fold ((,) <$> (L.foldMap Sum getSum) <*> L.maximum) [1..1000]
-- >>> L.foldM (L.mapM_ (putStrLn . show)) [1..10]
-- note this example is pointless in a real problem
sumM' :: L.FoldM (StateT Int Identity) Int ()
sumM' = L.sink $ \a -> do s <- get; put (s + a)
-- >>> flip execStateT 0 $ L.foldM sumM' [1..10]
-- 55
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment