module Fold.Pure.Run where

import Fold.Pure.Type

import Data.Foldable (Foldable)
import Data.Traversable (Traversable, mapAccumL)
import Prelude (($!))

import qualified Data.Foldable as F

{-| Fold a listlike container to a single summary result

@
run 'Fold.Pure.Examples.monoid' ["a", "b", "c"] = "abc"
@ -}
run :: Foldable f => Fold a b -> f a -> b
run :: forall (f :: * -> *) a b. Foldable f => Fold a b -> f a -> b
run Fold{ x
initial :: ()
initial :: x
initial, x -> a -> x
step :: ()
step :: x -> a -> x
step, x -> b
extract :: ()
extract :: x -> b
extract } f a
as = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr forall {b}. a -> (x -> b) -> x -> b
cons x -> b
extract f a
as x
initial
  where
    cons :: a -> (x -> b) -> x -> b
cons a
a x -> b
k x
x = x -> b
k forall a b. (a -> b) -> a -> b
$! x -> a -> x
step x
x a
a

{-| Rather than only obtain a single final result, scanning gives a running
    total that shows the intermediate result at each step along the way

@
scan 'Fold.Pure.Examples.monoid' ["a", "b", "c"] = ["","a","ab","abc"]
@ -}
scan :: Foldable f => Fold a b -> f a -> [b]
scan :: forall (f :: * -> *) a b. Foldable f => Fold a b -> f a -> [b]
scan Fold{ x
initial :: x
initial :: ()
initial, x -> a -> x
step :: x -> a -> x
step :: ()
step, x -> b
extract :: x -> b
extract :: ()
extract } f a
as = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr a -> (x -> [b]) -> x -> [b]
cons x -> [b]
nil f a
as x
initial
  where
    nil :: x -> [b]
nil x
x = x -> b
extract x
x forall a. a -> [a] -> [a]
: []
    cons :: a -> (x -> [b]) -> x -> [b]
cons a
a x -> [b]
k x
x = x -> b
extract x
x forall a. a -> [a] -> [a]
: (x -> [b]
k forall a b. (a -> b) -> a -> b
$! x -> a -> x
step x
x a
a)

{-| Scan where the last input is excluded

@
prescan 'Fold.Pure.Examples.monoid' ["a", "b", "c"] = ["","a","ab"]
@ -}
prescan :: Traversable t => Fold a b -> t a -> t b
prescan :: forall (t :: * -> *) a b. Traversable t => Fold a b -> t a -> t b
prescan Fold{ x
initial :: x
initial :: ()
initial, x -> a -> x
step :: x -> a -> x
step :: ()
step, x -> b
extract :: x -> b
extract :: ()
extract } t a
as = t b
bs
  where
    step' :: x -> a -> (x, b)
step' x
x a
a = (x
x', b
b)
      where
        x' :: x
x' = x -> a -> x
step x
x a
a
        b :: b
b  = x -> b
extract x
x
    (x
_, t b
bs) = forall (t :: * -> *) s a b.
Traversable t =>
(s -> a -> (s, b)) -> s -> t a -> (s, t b)
mapAccumL x -> a -> (x, b)
step' x
initial t a
as

{-| Scan where the first input is excluded

@
postscan 'Fold.Pure.Examples.monoid' ["a", "b", "c"] = ["a","ab","abc"]
@ -}
postscan :: Traversable t => Fold a b -> t a -> t b
postscan :: forall (t :: * -> *) a b. Traversable t => Fold a b -> t a -> t b
postscan Fold{ x
initial :: x
initial :: ()
initial, x -> a -> x
step :: x -> a -> x
step :: ()
step, x -> b
extract :: x -> b
extract :: ()
extract } t a
as = t b
bs
  where
    step' :: x -> a -> (x, b)
step' x
x a
a = (x
x', b
b)
      where
        x' :: x
x' = x -> a -> x
step x
x a
a
        b :: b
b  = x -> b
extract x
x'
    (x
_, t b
bs) = forall (t :: * -> *) s a b.
Traversable t =>
(s -> a -> (s, b)) -> s -> t a -> (s, t b)
mapAccumL x -> a -> (x, b)
step' x
initial t a
as