module Fold.Pure.Conversion where
import Fold.Pure.Type
import Data.Function (($))
import Data.Functor ((<$>), (<&>))
import Data.Functor.Identity (Identity, runIdentity)
import Data.Maybe (Maybe)
import Fold.Effectful.Type (EffectfulFold (EffectfulFold))
import Fold.Nonempty.Type (NonemptyFold (NonemptyFold))
import Fold.Shortcut.Type (ShortcutFold (ShortcutFold))
import Fold.ShortcutNonempty.Type (ShortcutNonemptyFold (ShortcutNonemptyFold))
import Strict (Vitality (Dead, Alive))
import qualified Fold.Effectful.Type as Effectful
import qualified Fold.Nonempty.Type as Nonempty
import qualified Fold.ShortcutNonempty.Type as ShortcutNonempty
import qualified Fold.Shortcut.Type as Shortcut
import qualified Strict
effectfulFold :: EffectfulFold Identity a b -> Fold a b
effectfulFold :: forall a b. EffectfulFold Identity a b -> Fold a b
effectfulFold
EffectfulFold{ Identity x
initial :: ()
initial :: Identity x
Effectful.initial, x -> a -> Identity x
step :: ()
step :: x -> a -> Identity x
Effectful.step, x -> Identity b
extract :: ()
extract :: x -> Identity b
Effectful.extract } =
Fold
{ initial :: x
initial = forall a. Identity a -> a
runIdentity ( Identity x
initial )
, step :: x -> a -> x
step = \x
x a
a -> forall a. Identity a -> a
runIdentity ( x -> a -> Identity x
step x
x a
a )
, extract :: x -> b
extract = \x
x -> forall a. Identity a -> a
runIdentity ( x -> Identity b
extract x
x )
}
nonemptyFold :: NonemptyFold a b -> Fold a (Maybe b)
nonemptyFold :: forall a b. NonemptyFold a b -> Fold a (Maybe b)
nonemptyFold
NonemptyFold{ a -> x
initial :: ()
initial :: a -> x
Nonempty.initial, x -> a -> x
step :: ()
step :: x -> a -> x
Nonempty.step, x -> b
extract :: ()
extract :: x -> b
Nonempty.extract } =
Fold
{ initial :: Maybe x
initial = forall a. Maybe a
Strict.Nothing
, step :: Maybe x -> a -> Maybe x
step = \Maybe x
xm a
a -> forall a. a -> Maybe a
Strict.Just forall a b. (a -> b) -> a -> b
$ case Maybe x
xm of
Maybe x
Strict.Nothing -> a -> x
initial a
a
Strict.Just x
x -> x -> a -> x
step x
x a
a
, extract :: Maybe x -> Maybe b
extract = \Maybe x
xm -> x -> b
extract forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Maybe a -> Maybe a
Strict.lazy Maybe x
xm
}
shortcutFold :: ShortcutFold a b -> Fold a b
shortcutFold :: forall a b. ShortcutFold a b -> Fold a b
shortcutFold ShortcutFold{
Vitality x y
initial :: ()
initial :: Vitality x y
Shortcut.initial, y -> a -> Vitality x y
step :: ()
step :: y -> a -> Vitality x y
Shortcut.step, y -> b
extractLive :: ()
extractLive :: y -> b
Shortcut.extractLive, x -> b
extractDead :: ()
extractDead :: x -> b
Shortcut.extractDead } =
Fold
{ initial :: Vitality x y
initial = Vitality x y
initial
, step :: Vitality x y -> a -> Vitality x y
step = \Vitality x y
s -> case Vitality x y
s of { Dead x
_ -> \a
_ -> Vitality x y
s; Alive Will
_ y
x -> y -> a -> Vitality x y
step y
x }
, extract :: Vitality x y -> b
extract = \Vitality x y
s -> case Vitality x y
s of
Dead x
x -> x -> b
extractDead x
x
Alive Will
_ y
x -> y -> b
extractLive y
x
}
shortcutNonemptyFold :: ShortcutNonemptyFold a b -> Fold a (Maybe b)
shortcutNonemptyFold :: forall a b. ShortcutNonemptyFold a b -> Fold a (Maybe b)
shortcutNonemptyFold ShortcutNonemptyFold{ a -> Vitality x y
initial :: ()
initial :: a -> Vitality x y
ShortcutNonempty.initial,
y -> a -> Vitality x y
step :: ()
step :: y -> a -> Vitality x y
ShortcutNonempty.step, y -> b
extractLive :: ()
extractLive :: y -> b
ShortcutNonempty.extractLive, x -> b
extractDead :: ()
extractDead :: x -> b
ShortcutNonempty.extractDead } =
Fold
{ initial :: Maybe (Vitality x y)
initial = forall a. Maybe a
Strict.Nothing
, step :: Maybe (Vitality x y) -> a -> Maybe (Vitality x y)
step = \Maybe (Vitality x y)
xm a
a -> case Maybe (Vitality x y)
xm of
Maybe (Vitality x y)
Strict.Nothing -> forall a. a -> Maybe a
Strict.Just (a -> Vitality x y
initial a
a)
Strict.Just (Alive Will
_ y
x) -> forall a. a -> Maybe a
Strict.Just (y -> a -> Vitality x y
step y
x a
a)
Strict.Just (Dead x
_) -> Maybe (Vitality x y)
xm
, extract :: Maybe (Vitality x y) -> Maybe b
extract = \Maybe (Vitality x y)
xm -> forall a. Maybe a -> Maybe a
Strict.lazy Maybe (Vitality x y)
xm forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \Vitality x y
s -> case Vitality x y
s of
Dead x
x -> x -> b
extractDead x
x
Alive Will
_ y
x -> y -> b
extractLive y
x
}