Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Stream f m r
- yields :: ( Monad m, Functor f) => f r -> Stream f m r
- effect :: ( Monad m, Functor f) => m ( Stream f m r) -> Stream f m r
- wrap :: ( Monad m, Functor f) => f ( Stream f m r) -> Stream f m r
- replicates :: ( Monad m, Functor f) => Int -> f () -> Stream f m ()
- repeats :: ( Monad m, Functor f) => f () -> Stream f m r
- repeatsM :: ( Monad m, Functor f) => m (f ()) -> Stream f m r
- unfold :: ( Monad m, Functor f) => (s -> m ( Either r (f s))) -> s -> Stream f m r
- never :: ( Monad m, Applicative f) => Stream f m r
- untilJust :: ( Monad m, Applicative f) => m ( Maybe r) -> Stream f m r
- streamBuild :: ( forall b. (r -> b) -> (m b -> b) -> (f b -> b) -> b) -> Stream f m r
- delays :: ( MonadIO m, Applicative f) => Double -> Stream f m r
- maps :: ( Monad m, Functor f) => ( forall x. f x -> g x) -> Stream f m r -> Stream g m r
- mapsPost :: forall m f g r. ( Monad m, Functor g) => ( forall x. f x -> g x) -> Stream f m r -> Stream g m r
- mapsM :: ( Monad m, Functor f) => ( forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r
- mapsMPost :: forall m f g r. ( Monad m, Functor g) => ( forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r
- mapped :: ( Monad m, Functor f) => ( forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r
- mappedPost :: ( Monad m, Functor g) => ( forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r
- hoistUnexposed :: ( Monad m, Functor f) => ( forall a. m a -> n a) -> Stream f m r -> Stream f n r
- distribute :: ( Monad m, Functor f, MonadTrans t, MFunctor t, Monad (t ( Stream f m))) => Stream f (t m) r -> t ( Stream f m) r
- groups :: ( Monad m, Functor f, Functor g) => Stream ( Sum f g) m r -> Stream ( Sum ( Stream f m) ( Stream g m)) m r
- inspect :: Monad m => Stream f m r -> m ( Either r (f ( Stream f m r)))
- splitsAt :: ( Monad m, Functor f) => Int -> Stream f m r -> Stream f m ( Stream f m r)
- takes :: ( Monad m, Functor f) => Int -> Stream f m r -> Stream f m ()
- chunksOf :: ( Monad m, Functor f) => Int -> Stream f m r -> Stream ( Stream f m) m r
- concats :: ( Monad m, Functor f) => Stream ( Stream f m) m r -> Stream f m r
- intercalates :: ( Monad m, Monad (t m), MonadTrans t) => t m x -> Stream (t m) m r -> t m r
- cutoff :: ( Monad m, Functor f) => Int -> Stream f m r -> Stream f m ( Maybe r)
- zipsWith :: forall f g h m r. ( Monad m, Functor h) => ( forall x y. f x -> g y -> h (x, y)) -> Stream f m r -> Stream g m r -> Stream h m r
- zipsWith' :: forall f g h m r. Monad m => ( forall x y p. (x -> y -> p) -> f x -> g y -> h p) -> Stream f m r -> Stream g m r -> Stream h m r
- zips :: ( Monad m, Functor f, Functor g) => Stream f m r -> Stream g m r -> Stream ( Compose f g) m r
- unzips :: ( Monad m, Functor f, Functor g) => Stream ( Compose f g) m r -> Stream f ( Stream g m) r
- interleaves :: ( Monad m, Applicative h) => Stream h m r -> Stream h m r -> Stream h m r
- separate :: ( Monad m, Functor f, Functor g) => Stream ( Sum f g) m r -> Stream f ( Stream g m) r
- unseparate :: ( Monad m, Functor f, Functor g) => Stream f ( Stream g m) r -> Stream ( Sum f g) m r
- decompose :: ( Monad m, Functor f) => Stream ( Compose m f) m r -> Stream f m r
- expand :: ( Monad m, Functor f) => ( forall a b. (g a -> b) -> f a -> h b) -> Stream f m r -> Stream g ( Stream h m) r
- expandPost :: ( Monad m, Functor g) => ( forall a b. (g a -> b) -> f a -> h b) -> Stream f m r -> Stream g ( Stream h m) r
- mapsM_ :: ( Functor f, Monad m) => ( forall x. f x -> m x) -> Stream f m r -> m r
- run :: Monad m => Stream m m r -> m r
- streamFold :: ( Functor f, Monad m) => (r -> b) -> (m b -> b) -> (f b -> b) -> Stream f m r -> b
- iterTM :: ( Functor f, Monad m, MonadTrans t, Monad (t m)) => (f (t m a) -> t m a) -> Stream f m a -> t m a
- iterT :: ( Functor f, Monad m) => (f (m a) -> m a) -> Stream f m a -> m a
- destroy :: ( Functor f, Monad m) => Stream f m r -> (f b -> b) -> (m b -> b) -> (r -> b) -> b
- data Of a b = !a :> b
- lazily :: Of a b -> (a, b)
- strictly :: (a, b) -> Of a b
- class MFunctor (t :: ( Type -> Type ) -> k -> Type ) where
- class ( MFunctor t, MonadTrans t) => MMonad (t :: ( Type -> Type ) -> Type -> Type ) where
- class MonadTrans (t :: ( Type -> Type ) -> Type -> Type ) where
- class Monad m => MonadIO (m :: Type -> Type ) where
-
newtype
Compose
(f :: k ->
Type
) (g :: k1 -> k) (a :: k1) =
Compose
{
- getCompose :: f (g a)
- data Sum (f :: k -> Type ) (g :: k -> Type ) (a :: k)
-
newtype
Identity
a =
Identity
{
- runIdentity :: a
-
class
Applicative
f =>
Alternative
(f ::
Type
->
Type
)
where
- (<|>) :: f a -> f a -> f a
- class Bifunctor (p :: Type -> Type -> Type ) where
- join :: Monad m => m (m a) -> m a
- liftM :: Monad m => (a1 -> r) -> m a1 -> m r
- liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
- liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
- liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
- void :: Functor f => f a -> f ()
- (<>) :: Semigroup a => a -> a -> a
An iterable streaming monad transformer
The
Stream
data type can be used to represent any effectful
succession of steps arising in some monad.
The form of the steps is specified by the first ("functor")
parameter in
Stream f m r
. The monad of the underlying effects
is expressed by the second parameter.
This module exports combinators that pertain to that general case. Some of these are quite abstract and pervade any use of the library, e.g.
maps :: (forall x . f x -> g x) -> Stream f m r -> Stream g m r mapped :: (forall x . f x -> m (g x)) -> Stream f m r -> Stream g m r hoist :: (forall x . m x -> n x) -> Stream f m r -> Stream f n r -- from the MFunctor instance concats :: Stream (Stream f m) m r -> Stream f m r
(assuming here and thoughout that
m
or
n
satisfies a
Monad
constraint, and
f
or
g
a
Functor
constraint.)
Others are surprisingly determinate in content:
chunksOf :: Int -> Stream f m r -> Stream (Stream f m) m r splitsAt :: Int -> Stream f m r -> Stream f m (Stream f m r) zipsWith :: (forall x y. f x -> g y -> h (x, y)) -> Stream f m r -> Stream g m r -> Stream h m r zipsWith' :: (forall x y p. (x -> y -> p) -> f x -> g y -> h p) -> Stream f m r -> Stream g m r -> Stream h m r intercalates :: Stream f m () -> Stream (Stream f m) m r -> Stream f m r unzips :: Stream (Compose f g) m r -> Stream f (Stream g m) r separate :: Stream (Sum f g) m r -> Stream f (Stream g m) r -- cp. partitionEithers unseparate :: Stream f (Stream g) m r -> Stream (Sum f g) m r groups :: Stream (Sum f g) m r -> Stream (Sum (Stream f m) (Stream g m)) m r
One way to see that
any
streaming library needs some such general type is
that it is required to represent the segmentation of a stream, and to
express the equivalents of
Prelude/Data.List
combinators that involve
'lists of lists' and the like. See for example this
post
on the correct expression of a streaming 'lines' function.
The module
Streaming.Prelude
exports combinators relating to
Stream (Of a) m r
where
Of a r = !a :> r
is a left-strict pair.
This expresses the concept of a
Producer
or
Source
or
Generator
and
easily inter-operates with types with such names in e.g.
conduit
,
iostreams
and
pipes
.
Instances
( Functor f, MonadState s m) => MonadState s ( Stream f m) Source # | |
( Functor f, MonadReader r m) => MonadReader r ( Stream f m) Source # | |
( Functor f, MonadError e m) => MonadError e ( Stream f m) Source # | |
Defined in Streaming.Internal throwError :: e -> Stream f m a Source # catchError :: Stream f m a -> (e -> Stream f m a) -> Stream f m a Source # |
|
Functor f => MMonad ( Stream f) Source # | |
Functor f => MonadTrans ( Stream f) Source # | |
Functor f => MFunctor ( Stream f :: ( Type -> Type ) -> Type -> Type ) Source # | |
( Functor f, Monad m) => Monad ( Stream f m) Source # | |
( Functor f, Monad m) => Functor ( Stream f m) Source # |
Operates covariantly on the stream result, not on its elements: Stream (Of a) m r ^ ^ | `--- This is what |
( Functor f, MonadFail m) => MonadFail ( Stream f m) Source # | |
( Functor f, Monad m) => Applicative ( Stream f m) Source # | |
Defined in Streaming.Internal pure :: a -> Stream f m a Source # (<*>) :: Stream f m (a -> b) -> Stream f m a -> Stream f m b Source # liftA2 :: (a -> b -> c) -> Stream f m a -> Stream f m b -> Stream f m c Source # (*>) :: Stream f m a -> Stream f m b -> Stream f m b Source # (<*) :: Stream f m a -> Stream f m b -> Stream f m a Source # |
|
( Monad m, Functor f, Eq1 m, Eq1 f) => Eq1 ( Stream f m) Source # | |
( Monad m, Functor f, Ord1 m, Ord1 f) => Ord1 ( Stream f m) Source # | |
Defined in Streaming.Internal |
|
( Monad m, Functor f, Show (m ShowSWrapper), Show (f ShowSWrapper)) => Show1 ( Stream f m) Source # | |
( MonadIO m, Functor f) => MonadIO ( Stream f m) Source # | |
( Applicative f, Monad m) => Alternative ( Stream f m) Source # |
The
empty = never (<|>) = zipsWith (liftA2 (,)) |
( Applicative f, Monad m) => MonadPlus ( Stream f m) Source # | |
( Monad m, Eq (m ( Either r (f ( Stream f m r))))) => Eq ( Stream f m r) Source # | |
( Monad m, Ord (m ( Either r (f ( Stream f m r))))) => Ord ( Stream f m r) Source # | |
Defined in Streaming.Internal compare :: Stream f m r -> Stream f m r -> Ordering Source # (<) :: Stream f m r -> Stream f m r -> Bool Source # (<=) :: Stream f m r -> Stream f m r -> Bool Source # (>) :: Stream f m r -> Stream f m r -> Bool Source # (>=) :: Stream f m r -> Stream f m r -> Bool Source # max :: Stream f m r -> Stream f m r -> Stream f m r Source # min :: Stream f m r -> Stream f m r -> Stream f m r Source # |
|
( Monad m, Show r, Show (m ShowSWrapper), Show (f ( Stream f m r))) => Show ( Stream f m r) Source # | |
( Functor f, Monad m, Semigroup w) => Semigroup ( Stream f m w) Source # | |
( Functor f, Monad m, Monoid w) => Monoid ( Stream f m w) Source # | |
Constructing a
Stream
on a given functor
yields :: ( Monad m, Functor f) => f r -> Stream f m r Source #
yields
is like
lift
for items in the streamed functor.
It makes a singleton or one-layer succession.
lift :: (Monad m, Functor f) => m r -> Stream f m r yields :: (Monad m, Functor f) => f r -> Stream f m r
Viewed in another light, it is like a functor-general version of
yield
:
S.yield a = yields (a :> ())
effect :: ( Monad m, Functor f) => m ( Stream f m r) -> Stream f m r Source #
Wrap an effect that returns a stream
effect = join . lift
wrap :: ( Monad m, Functor f) => f ( Stream f m r) -> Stream f m r Source #
Wrap a new layer of a stream. So, e.g.
S.cons :: Monad m => a -> Stream (Of a) m r -> Stream (Of a) m r S.cons a str = wrap (a :> str)
and, recursively:
S.each :: (Monad m, Foldable t) => t a -> Stream (Of a) m () S.each = foldr (\a b -> wrap (a :> b)) (return ())
The two operations
wrap :: (Monad m, Functor f ) => f (Stream f m r) -> Stream f m r effect :: (Monad m, Functor f ) => m (Stream f m r) -> Stream f m r
are fundamental. We can define the parallel operations
yields
and
lift
in
terms of them
yields :: (Monad m, Functor f ) => f r -> Stream f m r yields = wrap . fmap return lift :: (Monad m, Functor f ) => m r -> Stream f m r lift = effect . fmap return
replicates :: ( Monad m, Functor f) => Int -> f () -> Stream f m () Source #
Repeat a functorial layer, command or instruction a fixed number of times.
replicates n = takes n . repeats
repeats :: ( Monad m, Functor f) => f () -> Stream f m r Source #
Repeat a functorial layer (a "command" or "instruction") forever.
repeatsM :: ( Monad m, Functor f) => m (f ()) -> Stream f m r Source #
Repeat an effect containing a functorial layer, command or instruction forever.
unfold :: ( Monad m, Functor f) => (s -> m ( Either r (f s))) -> s -> Stream f m r Source #
Build a
Stream
by unfolding steps starting from a seed. See also
the specialized
unfoldr
in the prelude.
unfold inspect = id -- modulo the quotient we work with unfold Pipes.next :: Monad m => Producer a m r -> Stream ((,) a) m r unfold (curry (:>) . Pipes.next) :: Monad m => Producer a m r -> Stream (Of a) m r
never :: ( Monad m, Applicative f) => Stream f m r Source #
never
interleaves the pure applicative action with the return of the monad forever.
It is the
empty
of the
Alternative
instance, thus
never <|> a = a a <|> never = a
and so on. If w is a monoid then
never :: Stream (Of w) m r
is
the infinite sequence of
mempty
, and
str1 <|> str2
appends the elements monoidally until one of streams ends.
Thus we have, e.g.
>>>
S.stdoutLn $ S.take 2 $ S.stdinLn <|> S.repeat " " <|> S.stdinLn <|> S.repeat " " <|> S.stdinLn
1<Enter> 2<Enter> 3<Enter> 1 2 3 4<Enter> 5<Enter> 6<Enter> 4 5 6
This is equivalent to
>>>
S.stdoutLn $ S.take 2 $ foldr (<|>) never [S.stdinLn, S.repeat " ", S.stdinLn, S.repeat " ", S.stdinLn ]
Where
f
is a monad,
(<|>)
sequences the conjoined streams stepwise. See the
definition of
paste
here
,
where the separate steps are bytestreams corresponding to the lines of a file.
Given, say,
data Branch r = Branch r r deriving Functor -- add obvious applicative instance
then
never :: Stream Branch Identity r
is the pure infinite binary tree with
(inaccessible)
r
s in its leaves. Given two binary trees,
tree1 <|> tree2
intersects them, preserving the leaves that came first,
so
tree1 <|> never = tree1
Stream Identity m r
is an action in
m
that is indefinitely delayed. Such an
action can be constructed with e.g.
untilJust
.
untilJust :: (Monad m, Applicative f) => m (Maybe r) -> Stream f m r
Given two such items,
<|>
instance races them.
It is thus the iterative monad transformer specially defined in
Control.Monad.Trans.Iter
So, for example, we might write
>>>
let justFour str = if length str == 4 then Just str else Nothing
>>>
let four = untilJust (fmap justFour getLine)
>>>
run four
one<Enter> two<Enter> three<Enter> four<Enter> "four"
The
Alternative
instance in
Control.Monad.Trans.Free
is avowedly wrong, though no explanation is given for this.
streamBuild :: ( forall b. (r -> b) -> (m b -> b) -> (f b -> b) -> b) -> Stream f m r Source #
Reflect a church-encoded stream; cp.
GHC.Exts.build
streamFold return_ effect_ step_ (streamBuild psi) = psi return_ effect_ step_
Transforming streams
maps :: ( Monad m, Functor f) => ( forall x. f x -> g x) -> Stream f m r -> Stream g m r Source #
Map layers of one functor to another with a transformation. Compare
hoist, which has a similar effect on the
monadic
parameter.
maps id = id maps f . maps g = maps (f . g)
mapsPost :: forall m f g r. ( Monad m, Functor g) => ( forall x. f x -> g x) -> Stream f m r -> Stream g m r Source #
Map layers of one functor to another with a transformation. Compare
hoist, which has a similar effect on the
monadic
parameter.
mapsPost id = id mapsPost f . mapsPost g = mapsPost (f . g) mapsPost f = maps f
mapsPost
is essentially the same as
maps
, but it imposes a
Functor
constraint on
its target functor rather than its source functor. It should be preferred if
fmap
is cheaper for the target functor than for the source functor.
mapsM :: ( Monad m, Functor f) => ( forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r Source #
Map layers of one functor to another with a transformation involving the base monad.
maps
is more fundamental than
mapsM
, which is best understood as a convenience
for effecting this frequent composition:
mapsM phi = decompose . maps (Compose . phi)
The streaming prelude exports the same function under the better name
mapped
,
which overlaps with the lens libraries.
mapsMPost :: forall m f g r. ( Monad m, Functor g) => ( forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r Source #
Map layers of one functor to another with a transformation involving the base monad.
mapsMPost
is essentially the same as
mapsM
, but it imposes a
Functor
constraint on
its target functor rather than its source functor. It should be preferred if
fmap
is cheaper for the target functor than for the source functor.
mapsPost
is more fundamental than
mapsMPost
, which is best understood as a convenience
for effecting this frequent composition:
mapsMPost phi = decompose . mapsPost (Compose . phi)
The streaming prelude exports the same function under the better name
mappedPost
,
which overlaps with the lens libraries.
mapped :: ( Monad m, Functor f) => ( forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r Source #
Map layers of one functor to another with a transformation involving the base monad.
This function is completely functor-general. It is often useful with the more concrete type
mapped :: (forall x. Stream (Of a) IO x -> IO (Of b x)) -> Stream (Stream (Of a) IO) IO r -> Stream (Of b) IO r
to process groups which have been demarcated in an effectful,
IO
-based
stream by grouping functions like
group
,
split
or
breaks
. Summary functions
like
fold
,
foldM
,
mconcat
or
toList
are often used
to define the transformation argument. For example:
>>>
S.toList_ $ S.mapped S.toList $ S.split 'c' (S.each "abcde")
["ab","de"]
maps
and
mapped
obey these rules:
maps id = id mapped return = id maps f . maps g = maps (f . g) mapped f . mapped g = mapped (f <=< g) maps f . mapped g = mapped (fmap f . g) mapped f . maps g = mapped (f <=< fmap g)
maps
is more fundamental than
mapped
, which is best understood as a convenience for
effecting this frequent composition:
mapped phi = decompose . maps (Compose . phi)
mappedPost :: ( Monad m, Functor g) => ( forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r Source #
hoistUnexposed :: ( Monad m, Functor f) => ( forall a. m a -> n a) -> Stream f m r -> Stream f n r Source #
A less-efficient version of
hoist
that works properly even when its
argument is not a monad morphism.
hoistUnexposed = hoist . unexposed
distribute :: ( Monad m, Functor f, MonadTrans t, MFunctor t, Monad (t ( Stream f m))) => Stream f (t m) r -> t ( Stream f m) r Source #
Make it possible to 'run' the underlying transformed monad.
groups :: ( Monad m, Functor f, Functor g) => Stream ( Sum f g) m r -> Stream ( Sum ( Stream f m) ( Stream g m)) m r Source #
Group layers in an alternating stream into adjoining sub-streams of one type or another.
Inspecting a stream
inspect :: Monad m => Stream f m r -> m ( Either r (f ( Stream f m r))) Source #
Inspect the first stage of a freely layered sequence.
Compare
Pipes.next
and the replica
Streaming.Prelude.next
.
This is the
uncons
for the general
unfold
.
unfold inspect = id Streaming.Prelude.unfoldr StreamingPrelude.next = id
Splitting and joining
Stream
s
splitsAt :: ( Monad m, Functor f) => Int -> Stream f m r -> Stream f m ( Stream f m r) Source #
Split a succession of layers after some number, returning a streaming or effectful pair.
>>>
rest <- S.print $ S.splitAt 1 $ each [1..3]
1>>>
S.print rest
2 3
splitAt 0 = return splitAt n >=> splitAt m = splitAt (m+n)
Thus, e.g.
>>>
rest <- S.print $ splitsAt 2 >=> splitsAt 2 $ each [1..5]
1 2 3 4>>>
S.print rest
5
chunksOf :: ( Monad m, Functor f) => Int -> Stream f m r -> Stream ( Stream f m) m r Source #
Break a stream into substreams each with n functorial layers.
>>>
S.print $ mapped S.sum $ chunksOf 2 $ each [1,1,1,1,1]
2 2 1
concats :: ( Monad m, Functor f) => Stream ( Stream f m) m r -> Stream f m r Source #
Dissolves the segmentation into layers of
Stream f m
layers.
intercalates :: ( Monad m, Monad (t m), MonadTrans t) => t m x -> Stream (t m) m r -> t m r Source #
Interpolate a layer at each segment. This specializes to e.g.
intercalates :: (Monad m, Functor f) => Stream f m () -> Stream (Stream f m) m r -> Stream f m r
Zipping, unzipping, separating and unseparating streams
zipsWith :: forall f g h m r. ( Monad m, Functor h) => ( forall x y. f x -> g y -> h (x, y)) -> Stream f m r -> Stream g m r -> Stream h m r Source #
Zip two streams together. The
zipsWith'
function should generally
be preferred for efficiency.
zipsWith' :: forall f g h m r. Monad m => ( forall x y p. (x -> y -> p) -> f x -> g y -> h p) -> Stream f m r -> Stream g m r -> Stream h m r Source #
Zip two streams together.
zips :: ( Monad m, Functor f, Functor g) => Stream f m r -> Stream g m r -> Stream ( Compose f g) m r Source #
unzips :: ( Monad m, Functor f, Functor g) => Stream ( Compose f g) m r -> Stream f ( Stream g m) r Source #
interleaves :: ( Monad m, Applicative h) => Stream h m r -> Stream h m r -> Stream h m r Source #
Interleave functor layers, with the effects of the first preceding the effects of the second. When the first stream runs out, any remaining effects in the second are ignored.
interleaves = zipsWith (liftA2 (,))
>>>
let paste = \a b -> interleaves (Q.lines a) (maps (Q.cons' '\t') (Q.lines b))
>>>
Q.stdout $ Q.unlines $ paste "hello\nworld\n" "goodbye\nworld\n"
hello goodbye world world
separate :: ( Monad m, Functor f, Functor g) => Stream ( Sum f g) m r -> Stream f ( Stream g m) r Source #
Given a stream on a sum of functors, make it a stream on the left functor,
with the streaming on the other functor as the governing monad. This is
useful for acting on one or the other functor with a fold, leaving the
other material for another treatment. It generalizes
partitionEithers
, but actually streams properly.
>>>
let odd_even = S.maps (S.distinguish even) $ S.each [1..10::Int]
>>>
:t separate odd_even
separate odd_even :: Monad m => Stream (Of Int) (Stream (Of Int) m) ()
Now, for example, it is convenient to fold on the left and right values separately:
>>>
S.toList $ S.toList $ separate odd_even
[2,4,6,8,10] :> ([1,3,5,7,9] :> ())
Or we can write them to separate files or whatever:
>>>
S.writeFile "even.txt" . S.show $ S.writeFile "odd.txt" . S.show $ S.separate odd_even
>>>
:! cat even.txt
2 4 6 8 10>>>
:! cat odd.txt
1 3 5 7 9
Of course, in the special case of
Stream (Of a) m r
, we can achieve the above
effects more simply by using
copy
>>>
S.toList . S.filter even $ S.toList . S.filter odd $ S.copy $ each [1..10::Int]
[2,4,6,8,10] :> ([1,3,5,7,9] :> ())
But
separate
and
unseparate
are functor-general.
unseparate :: ( Monad m, Functor f, Functor g) => Stream f ( Stream g m) r -> Stream ( Sum f g) m r Source #
decompose :: ( Monad m, Functor f) => Stream ( Compose m f) m r -> Stream f m r Source #
Rearrange a succession of layers of the form
Compose m (f x)
.
we could as well define
decompose
by
mapsM
:
decompose = mapped getCompose
but
mapped
is best understood as:
mapped phi = decompose . maps (Compose . phi)
since
maps
and
hoist
are the really fundamental operations that preserve the
shape of the stream:
maps :: (Monad m, Functor f) => (forall x. f x -> g x) -> Stream f m r -> Stream g m r hoist :: (Monad m, Functor f) => (forall a. m a -> n a) -> Stream f m r -> Stream f n r
expand :: ( Monad m, Functor f) => ( forall a b. (g a -> b) -> f a -> h b) -> Stream f m r -> Stream g ( Stream h m) r Source #
If
Of
had a
Comonad
instance, then we'd have
copy = expand extend
See
expandPost
for a version that requires a
Functor g
instance instead.
expandPost :: ( Monad m, Functor g) => ( forall a b. (g a -> b) -> f a -> h b) -> Stream f m r -> Stream g ( Stream h m) r Source #
If
Of
had a
Comonad
instance, then we'd have
copy = expandPost extend
See
expand
for a version that requires a
Functor f
instance
instead.
Eliminating a
Stream
mapsM_ :: ( Functor f, Monad m) => ( forall x. f x -> m x) -> Stream f m r -> m r Source #
Map each layer to an effect, and run them all.
run :: Monad m => Stream m m r -> m r Source #
Run the effects in a stream that merely layers effects.
streamFold :: ( Functor f, Monad m) => (r -> b) -> (m b -> b) -> (f b -> b) -> Stream f m r -> b Source #
streamFold
reorders the arguments of
destroy
to be more akin
to
foldr
It is more convenient to query in ghci to figure out
what kind of 'algebra' you need to write.
>>>
:t streamFold return join
(Monad m, Functor f) => (f (m a) -> m a) -> Stream f m a -> m a -- iterT
>>>
:t streamFold return (join . lift)
(Monad m, Monad (t m), Functor f, MonadTrans t) => (f (t m a) -> t m a) -> Stream f m a -> t m a -- iterTM
>>>
:t streamFold return effect
(Monad m, Functor f, Functor g) => (f (Stream g m r) -> Stream g m r) -> Stream f m r -> Stream g m r
>>>
:t \f -> streamFold return effect (wrap . f)
(Monad m, Functor f, Functor g) => (f (Stream g m a) -> g (Stream g m a)) -> Stream f m a -> Stream g m a -- maps
>>>
:t \f -> streamFold return effect (effect . fmap wrap . f)
(Monad m, Functor f, Functor g) => (f (Stream g m a) -> m (g (Stream g m a))) -> Stream f m a -> Stream g m a -- mapped
streamFold done eff construct = eff . iterT (return . construct . fmap eff) . fmap done
iterTM :: ( Functor f, Monad m, MonadTrans t, Monad (t m)) => (f (t m a) -> t m a) -> Stream f m a -> t m a Source #
Specialized fold following the usage of
Control.Monad.Trans.Free
iterTM alg = streamFold return (join . lift) iterTM alg = iterT alg . hoist lift
iterT :: ( Functor f, Monad m) => (f (m a) -> m a) -> Stream f m a -> m a Source #
Specialized fold following the usage of
Control.Monad.Trans.Free
iterT alg = streamFold return join alg iterT alg = runIdentityT . iterTM (IdentityT . alg . fmap runIdentityT)
destroy :: ( Functor f, Monad m) => Stream f m r -> (f b -> b) -> (m b -> b) -> (r -> b) -> b Source #
Map a stream to its church encoding; compare
Data.List.foldr
.
destroyExposed
may be more efficient in some cases when
applicable, but it is less safe.
destroy s construct eff done = eff . iterT (return . construct . fmap eff) . fmap done $ s
Base functor for streams of individual items
A left-strict pair; the base functor for streams of individual elements.
!a :> b infixr 5 |
Instances
Bitraversable Of Source # |
Since: 0.2.4.0 |
Defined in Data.Functor.Of bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Of a b -> f ( Of c d) Source # |
|
Bifoldable Of Source # |
Since: 0.2.4.0 |
Bifunctor Of Source # | |
Eq2 Of Source # | |
Ord2 Of Source # | |
Defined in Data.Functor.Of |
|
Show2 Of Source # | |
Monoid a => Monad ( Of a) Source # | |
Functor ( Of a) Source # | |
Monoid a => Applicative ( Of a) Source # | |
Foldable ( Of a) Source # | |
Defined in Data.Functor.Of fold :: Monoid m => Of a m -> m Source # foldMap :: Monoid m => (a0 -> m) -> Of a a0 -> m Source # foldMap' :: Monoid m => (a0 -> m) -> Of a a0 -> m Source # foldr :: (a0 -> b -> b) -> b -> Of a a0 -> b Source # foldr' :: (a0 -> b -> b) -> b -> Of a a0 -> b Source # foldl :: (b -> a0 -> b) -> b -> Of a a0 -> b Source # foldl' :: (b -> a0 -> b) -> b -> Of a a0 -> b Source # foldr1 :: (a0 -> a0 -> a0) -> Of a a0 -> a0 Source # foldl1 :: (a0 -> a0 -> a0) -> Of a a0 -> a0 Source # toList :: Of a a0 -> [a0] Source # null :: Of a a0 -> Bool Source # length :: Of a a0 -> Int Source # elem :: Eq a0 => a0 -> Of a a0 -> Bool Source # maximum :: Ord a0 => Of a a0 -> a0 Source # minimum :: Ord a0 => Of a a0 -> a0 Source # |
|
Traversable ( Of a) Source # | |
Eq a => Eq1 ( Of a) Source # | |
Ord a => Ord1 ( Of a) Source # | |
Defined in Data.Functor.Of |
|
Show a => Show1 ( Of a) Source # | |
Generic1 ( Of a :: Type -> Type ) Source # | |
( Eq a, Eq b) => Eq ( Of a b) Source # | |
( Data a, Data b) => Data ( Of a b) Source # | |
Defined in Data.Functor.Of gfoldl :: ( forall d b0. Data d => c (d -> b0) -> d -> c b0) -> ( forall g. g -> c g) -> Of a b -> c ( Of a b) Source # gunfold :: ( forall b0 r. Data b0 => c (b0 -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Of a b) Source # toConstr :: Of a b -> Constr Source # dataTypeOf :: Of a b -> DataType Source # dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Of a b)) Source # dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Of a b)) Source # gmapT :: ( forall b0. Data b0 => b0 -> b0) -> Of a b -> Of a b Source # gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Of a b -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Of a b -> r Source # gmapQ :: ( forall d. Data d => d -> u) -> Of a b -> [u] Source # gmapQi :: Int -> ( forall d. Data d => d -> u) -> Of a b -> u Source # gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Of a b -> m ( Of a b) Source # gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Of a b -> m ( Of a b) Source # gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Of a b -> m ( Of a b) Source # |
|
( Ord a, Ord b) => Ord ( Of a b) Source # | |
( Read a, Read b) => Read ( Of a b) Source # | |
( Show a, Show b) => Show ( Of a b) Source # | |
Generic ( Of a b) Source # | |
( Semigroup a, Semigroup b) => Semigroup ( Of a b) Source # | |
( Monoid a, Monoid b) => Monoid ( Of a b) Source # | |
type Rep1 ( Of a :: Type -> Type ) Source # | |
Defined in Data.Functor.Of
type
Rep1
(
Of
a ::
Type
->
Type
) =
D1
('
MetaData
"Of" "Data.Functor.Of" "streaming-0.2.3.1-3gWNnnaywYgIAjY6UdiTPf" '
False
) (
C1
('
MetaCons
":>" ('
InfixI
'
RightAssociative
5) '
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
SourceStrict
'
DecidedStrict
) (
Rec0
a)
:*:
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
)
Par1
))
|
|
type Rep ( Of a b) Source # | |
Defined in Data.Functor.Of
type
Rep
(
Of
a b) =
D1
('
MetaData
"Of" "Data.Functor.Of" "streaming-0.2.3.1-3gWNnnaywYgIAjY6UdiTPf" '
False
) (
C1
('
MetaCons
":>" ('
InfixI
'
RightAssociative
5) '
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
SourceStrict
'
DecidedStrict
) (
Rec0
a)
:*:
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
b)))
|
lazily :: Of a b -> (a, b) Source #
Note that
lazily
,
strictly
,
fst'
, and
mapOf
are all so-called
natural transformations
on the primitive
Of a
functor.
If we write
type f ~~> g = forall x . f x -> g x
then we can restate some types as follows:
mapOf :: (a -> b) -> Of a ~~> Of b -- Bifunctor first lazily :: Of a ~~> (,) a Identity . fst' :: Of a ~~> Identity a
Manipulation of a
Stream f m r
by mapping often turns on recognizing natural transformations of
f
.
Thus
maps
is far more general the the
map
of the
Streaming.Prelude
, which can be
defined thus:
S.map :: (a -> b) -> Stream (Of a) m r -> Stream (Of b) m r S.map f = maps (mapOf f)
i.e.
S.map f = maps (\(a :> x) -> (f a :> x))
This rests on recognizing that
mapOf
is a natural transformation; note though
that it results in such a transformation as well:
S.map :: (a -> b) -> Stream (Of a) m ~~> Stream (Of b) m
Thus we can
maps
it in turn.
re-exports
class MFunctor (t :: ( Type -> Type ) -> k -> Type ) where Source #
A functor in the category of monads, using
hoist
as the analog of
fmap
:
hoist (f . g) = hoist f . hoist g hoist id = id
hoist :: forall m n (b :: k). Monad m => ( forall a. m a -> n a) -> t m b -> t n b Source #
Lift a monad morphism from
m
to
n
into a monad morphism from
(t m)
to
(t n)
The first argument to
hoist
must be a monad morphism, even though the
type system does not enforce this
Instances
MFunctor Lift | |
MFunctor MaybeT | |
MFunctor ( IdentityT :: ( Type -> Type ) -> Type -> Type ) | |
MFunctor ( ExceptT e :: ( Type -> Type ) -> Type -> Type ) | |
MFunctor ( ReaderT r :: ( Type -> Type ) -> Type -> Type ) | |
MFunctor ( StateT s :: ( Type -> Type ) -> Type -> Type ) | |
MFunctor ( StateT s :: ( Type -> Type ) -> Type -> Type ) | |
MFunctor ( WriterT w :: ( Type -> Type ) -> Type -> Type ) | |
MFunctor ( WriterT w :: ( Type -> Type ) -> Type -> Type ) | |
MFunctor ( Backwards :: ( Type -> Type ) -> Type -> Type ) | |
Functor f => MFunctor ( Stream f :: ( Type -> Type ) -> Type -> Type ) Source # | |
MFunctor ( Product f :: ( Type -> Type ) -> Type -> Type ) | |
Functor f => MFunctor ( Compose f :: ( Type -> Type ) -> Type -> Type ) | |
MFunctor ( RWST r w s :: ( Type -> Type ) -> Type -> Type ) | |
MFunctor ( RWST r w s :: ( Type -> Type ) -> Type -> Type ) | |
class ( MFunctor t, MonadTrans t) => MMonad (t :: ( Type -> Type ) -> Type -> Type ) where Source #
A monad in the category of monads, using
lift
from
MonadTrans
as the
analog of
return
and
embed
as the analog of (
=<<
):
embed lift = id embed f (lift m) = f m embed g (embed f t) = embed (\m -> embed g (f m)) t
embed :: forall (n :: Type -> Type ) m b. Monad n => ( forall a. m a -> t n a) -> t m b -> t n b Source #
class MonadTrans (t :: ( Type -> Type ) -> Type -> Type ) where Source #
The class of monad transformers. Instances should satisfy the
following laws, which state that
lift
is a monad transformation:
lift :: Monad m => m a -> t m a Source #
Lift a computation from the argument monad to the constructed monad.
Instances
MonadTrans ListT | |
MonadTrans MaybeT | |
MonadTrans ( IdentityT :: ( Type -> Type ) -> Type -> Type ) | |
MonadTrans ( ErrorT e) | |
MonadTrans ( ExceptT e) | |
MonadTrans ( ReaderT r) | |
MonadTrans ( StateT s) | |
MonadTrans ( StateT s) | |
Monoid w => MonadTrans ( WriterT w) | |
Monoid w => MonadTrans ( WriterT w) | |
Functor f => MonadTrans ( Stream f) Source # | |
MonadTrans ( ContT r) | |
Monoid w => MonadTrans ( RWST r w s) | |
Monoid w => MonadTrans ( RWST r w s) | |
class Monad m => MonadIO (m :: Type -> Type ) where Source #
Monads in which
IO
computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO
monad will be an instance of this class.
Instances should satisfy the following laws, which state that
liftIO
is a transformer of monads:
Instances
MonadIO IO |
Since: base-4.9.0.0 |
MonadIO m => MonadIO ( ListT m) | |
MonadIO m => MonadIO ( MaybeT m) | |
MonadIO m => MonadIO ( IdentityT m) | |
( Error e, MonadIO m) => MonadIO ( ErrorT e m) | |
MonadIO m => MonadIO ( ExceptT e m) | |
MonadIO m => MonadIO ( ReaderT r m) | |
MonadIO m => MonadIO ( StateT s m) | |
MonadIO m => MonadIO ( StateT s m) | |
( Monoid w, MonadIO m) => MonadIO ( WriterT w m) | |
( Monoid w, MonadIO m) => MonadIO ( WriterT w m) | |
( MonadIO m, Functor f) => MonadIO ( Stream f m) Source # | |
MonadIO m => MonadIO ( ContT r m) | |
( Monoid w, MonadIO m) => MonadIO ( RWST r w s m) | |
( Monoid w, MonadIO m) => MonadIO ( RWST r w s m) | |
newtype Compose (f :: k -> Type ) (g :: k1 -> k) (a :: k1) infixr 9 Source #
Right-to-left composition of functors. The composition of applicative functors is always applicative, but the composition of monads is not always a monad.
Compose infixr 9 | |
|
Instances
Functor f => Generic1 ( Compose f g :: k -> Type ) |
Since: base-4.9.0.0 |
TestEquality f => TestEquality ( Compose f g :: k2 -> Type ) |
The deduction (via generativity) that if
Since: base-4.14.0.0 |
Defined in Data.Functor.Compose |
|
Functor f => MFunctor ( Compose f :: ( Type -> Type ) -> Type -> Type ) | |
( Functor f, Functor g) => Functor ( Compose f g) |
Since: base-4.9.0.0 |
( Applicative f, Applicative g) => Applicative ( Compose f g) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Compose pure :: a -> Compose f g a Source # (<*>) :: Compose f g (a -> b) -> Compose f g a -> Compose f g b Source # liftA2 :: (a -> b -> c) -> Compose f g a -> Compose f g b -> Compose f g c Source # (*>) :: Compose f g a -> Compose f g b -> Compose f g b Source # (<*) :: Compose f g a -> Compose f g b -> Compose f g a Source # |
|
( Foldable f, Foldable g) => Foldable ( Compose f g) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Compose fold :: Monoid m => Compose f g m -> m Source # foldMap :: Monoid m => (a -> m) -> Compose f g a -> m Source # foldMap' :: Monoid m => (a -> m) -> Compose f g a -> m Source # foldr :: (a -> b -> b) -> b -> Compose f g a -> b Source # foldr' :: (a -> b -> b) -> b -> Compose f g a -> b Source # foldl :: (b -> a -> b) -> b -> Compose f g a -> b Source # foldl' :: (b -> a -> b) -> b -> Compose f g a -> b Source # foldr1 :: (a -> a -> a) -> Compose f g a -> a Source # foldl1 :: (a -> a -> a) -> Compose f g a -> a Source # toList :: Compose f g a -> [a] Source # null :: Compose f g a -> Bool Source # length :: Compose f g a -> Int Source # elem :: Eq a => a -> Compose f g a -> Bool Source # maximum :: Ord a => Compose f g a -> a Source # minimum :: Ord a => Compose f g a -> a Source # |
|
( Traversable f, Traversable g) => Traversable ( Compose f g) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Compose traverse :: Applicative f0 => (a -> f0 b) -> Compose f g a -> f0 ( Compose f g b) Source # sequenceA :: Applicative f0 => Compose f g (f0 a) -> f0 ( Compose f g a) Source # mapM :: Monad m => (a -> m b) -> Compose f g a -> m ( Compose f g b) Source # sequence :: Monad m => Compose f g (m a) -> m ( Compose f g a) Source # |
|
( Eq1 f, Eq1 g) => Eq1 ( Compose f g) |
Since: base-4.9.0.0 |
( Ord1 f, Ord1 g) => Ord1 ( Compose f g) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Compose |
|
( Read1 f, Read1 g) => Read1 ( Compose f g) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Compose liftReadsPrec :: ( Int -> ReadS a) -> ReadS [a] -> Int -> ReadS ( Compose f g a) Source # liftReadList :: ( Int -> ReadS a) -> ReadS [a] -> ReadS [ Compose f g a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec ( Compose f g a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [ Compose f g a] Source # |
|
( Show1 f, Show1 g) => Show1 ( Compose f g) |
Since: base-4.9.0.0 |
( Alternative f, Applicative g) => Alternative ( Compose f g) |
Since: base-4.9.0.0 |
( Eq1 f, Eq1 g, Eq a) => Eq ( Compose f g a) |
Since: base-4.9.0.0 |
( Typeable a, Typeable f, Typeable g, Typeable k1, Typeable k2, Data (f (g a))) => Data ( Compose f g a) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Compose gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g0. g0 -> c g0) -> Compose f g a -> c ( Compose f g a) Source # gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Compose f g a) Source # toConstr :: Compose f g a -> Constr Source # dataTypeOf :: Compose f g a -> DataType Source # dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Compose f g a)) Source # dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Compose f g a)) Source # gmapT :: ( forall b. Data b => b -> b) -> Compose f g a -> Compose f g a Source # gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Compose f g a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Compose f g a -> r Source # gmapQ :: ( forall d. Data d => d -> u) -> Compose f g a -> [u] Source # gmapQi :: Int -> ( forall d. Data d => d -> u) -> Compose f g a -> u Source # gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Compose f g a -> m ( Compose f g a) Source # gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Compose f g a -> m ( Compose f g a) Source # gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Compose f g a -> m ( Compose f g a) Source # |
|
( Ord1 f, Ord1 g, Ord a) => Ord ( Compose f g a) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Compose compare :: Compose f g a -> Compose f g a -> Ordering Source # (<) :: Compose f g a -> Compose f g a -> Bool Source # (<=) :: Compose f g a -> Compose f g a -> Bool Source # (>) :: Compose f g a -> Compose f g a -> Bool Source # (>=) :: Compose f g a -> Compose f g a -> Bool Source # max :: Compose f g a -> Compose f g a -> Compose f g a Source # min :: Compose f g a -> Compose f g a -> Compose f g a Source # |
|
( Read1 f, Read1 g, Read a) => Read ( Compose f g a) |
Since: base-4.9.0.0 |
( Show1 f, Show1 g, Show a) => Show ( Compose f g a) |
Since: base-4.9.0.0 |
Generic ( Compose f g a) |
Since: base-4.9.0.0 |
type Rep1 ( Compose f g :: k -> Type ) | |
Defined in Data.Functor.Compose |
|
type Rep ( Compose f g a) | |
Defined in Data.Functor.Compose |
data Sum (f :: k -> Type ) (g :: k -> Type ) (a :: k) Source #
Lifted sum of functors.
Instances
Generic1 ( Sum f g :: k -> Type ) |
Since: base-4.9.0.0 |
( Functor f, Functor g) => Functor ( Sum f g) |
Since: base-4.9.0.0 |
( Foldable f, Foldable g) => Foldable ( Sum f g) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Sum fold :: Monoid m => Sum f g m -> m Source # foldMap :: Monoid m => (a -> m) -> Sum f g a -> m Source # foldMap' :: Monoid m => (a -> m) -> Sum f g a -> m Source # foldr :: (a -> b -> b) -> b -> Sum f g a -> b Source # foldr' :: (a -> b -> b) -> b -> Sum f g a -> b Source # foldl :: (b -> a -> b) -> b -> Sum f g a -> b Source # foldl' :: (b -> a -> b) -> b -> Sum f g a -> b Source # foldr1 :: (a -> a -> a) -> Sum f g a -> a Source # foldl1 :: (a -> a -> a) -> Sum f g a -> a Source # toList :: Sum f g a -> [a] Source # null :: Sum f g a -> Bool Source # length :: Sum f g a -> Int Source # elem :: Eq a => a -> Sum f g a -> Bool Source # maximum :: Ord a => Sum f g a -> a Source # minimum :: Ord a => Sum f g a -> a Source # |
|
( Traversable f, Traversable g) => Traversable ( Sum f g) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Sum |
|
( Eq1 f, Eq1 g) => Eq1 ( Sum f g) |
Since: base-4.9.0.0 |
( Ord1 f, Ord1 g) => Ord1 ( Sum f g) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Sum |
|
( Read1 f, Read1 g) => Read1 ( Sum f g) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Sum liftReadsPrec :: ( Int -> ReadS a) -> ReadS [a] -> Int -> ReadS ( Sum f g a) Source # liftReadList :: ( Int -> ReadS a) -> ReadS [a] -> ReadS [ Sum f g a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec ( Sum f g a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [ Sum f g a] Source # |
|
( Show1 f, Show1 g) => Show1 ( Sum f g) |
Since: base-4.9.0.0 |
( Eq1 f, Eq1 g, Eq a) => Eq ( Sum f g a) |
Since: base-4.9.0.0 |
( Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => Data ( Sum f g a) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Sum gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g0. g0 -> c g0) -> Sum f g a -> c ( Sum f g a) Source # gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Sum f g a) Source # toConstr :: Sum f g a -> Constr Source # dataTypeOf :: Sum f g a -> DataType Source # dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Sum f g a)) Source # dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Sum f g a)) Source # gmapT :: ( forall b. Data b => b -> b) -> Sum f g a -> Sum f g a Source # gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Sum f g a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Sum f g a -> r Source # gmapQ :: ( forall d. Data d => d -> u) -> Sum f g a -> [u] Source # gmapQi :: Int -> ( forall d. Data d => d -> u) -> Sum f g a -> u Source # gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Sum f g a -> m ( Sum f g a) Source # gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Sum f g a -> m ( Sum f g a) Source # gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Sum f g a -> m ( Sum f g a) Source # |
|
( Ord1 f, Ord1 g, Ord a) => Ord ( Sum f g a) |
Since: base-4.9.0.0 |
Defined in Data.Functor.Sum |
|
( Read1 f, Read1 g, Read a) => Read ( Sum f g a) |
Since: base-4.9.0.0 |
( Show1 f, Show1 g, Show a) => Show ( Sum f g a) |
Since: base-4.9.0.0 |
Generic ( Sum f g a) |
Since: base-4.9.0.0 |
type Rep1 ( Sum f g :: k -> Type ) | |
Defined in Data.Functor.Sum
type
Rep1
(
Sum
f g :: k ->
Type
) =
D1
('
MetaData
"Sum" "Data.Functor.Sum" "base" '
False
) (
C1
('
MetaCons
"InL" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec1
f))
:+:
C1
('
MetaCons
"InR" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec1
g)))
|
|
type Rep ( Sum f g a) | |
Defined in Data.Functor.Sum
type
Rep
(
Sum
f g a) =
D1
('
MetaData
"Sum" "Data.Functor.Sum" "base" '
False
) (
C1
('
MetaCons
"InL" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
(f a)))
:+:
C1
('
MetaCons
"InR" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
(g a))))
|
Identity functor and monad. (a non-strict monad)
Since: base-4.8.0.0
Identity | |
|
Instances
class Applicative f => Alternative (f :: Type -> Type ) where Source #
A monoid on applicative functors.
If defined,
some
and
many
should be the least solutions
of the equations:
Instances
class Bifunctor (p :: Type -> Type -> Type ) where Source #
A bifunctor is a type constructor that takes
two type arguments and is a functor in
both
arguments. That
is, unlike with
Functor
, a type constructor such as
Either
does not need to be partially applied for a
Bifunctor
instance, and the methods in this class permit mapping
functions over the
Left
value or the
Right
value,
or both at the same time.
Formally, the class
Bifunctor
represents a bifunctor
from
Hask
->
Hask
.
Intuitively it is a bifunctor where both the first and second arguments are covariant.
You can define a
Bifunctor
by either defining
bimap
or by
defining both
first
and
second
.
If you supply
bimap
, you should ensure that:
bimap
id
id
≡id
If you supply
first
and
second
, ensure:
first
id
≡id
second
id
≡id
If you supply both, you should also ensure:
bimap
f g ≡first
f.
second
g
These ensure by parametricity:
bimap
(f.
g) (h.
i) ≡bimap
f h.
bimap
g ifirst
(f.
g) ≡first
f.
first
gsecond
(f.
g) ≡second
f.
second
g
Since: base-4.8.0.0
bimap :: (a -> b) -> (c -> d) -> p a c -> p b d Source #
Map over both arguments at the same time.
bimap
f g ≡first
f.
second
g
Examples
>>>
bimap toUpper (+1) ('j', 3)
('J',4)
>>>
bimap toUpper (+1) (Left 'j')
Left 'J'
>>>
bimap toUpper (+1) (Right 3)
Right 4
Instances
Bifunctor Either |
Since: base-4.8.0.0 |
Bifunctor (,) |
Since: base-4.8.0.0 |
Bifunctor Arg |
Since: base-4.9.0.0 |
Bifunctor Of Source # | |
Bifunctor ( (,,) x1) |
Since: base-4.8.0.0 |
Bifunctor ( Const :: Type -> Type -> Type ) |
Since: base-4.8.0.0 |
Bifunctor ( K1 i :: Type -> Type -> Type ) |
Since: base-4.9.0.0 |
Bifunctor ( (,,,) x1 x2) |
Since: base-4.8.0.0 |
Bifunctor ( (,,,,) x1 x2 x3) |
Since: base-4.8.0.0 |
Bifunctor ( (,,,,,) x1 x2 x3 x4) |
Since: base-4.8.0.0 |
Bifunctor ( (,,,,,,) x1 x2 x3 x4 x5) |
Since: base-4.8.0.0 |
join :: Monad m => m (m a) -> m a Source #
The
join
function is the conventional monad join operator. It
is used to remove one level of monadic structure, projecting its
bound argument into the outer level.
'
' can be understood as the
join
bss
do
expression
do bs <- bss bs
Examples
A common use of
join
is to run an
IO
computation returned from
an
STM
transaction, since
STM
transactions
can't perform
IO
directly. Recall that
atomically
:: STM a -> IO a
is used to run
STM
transactions atomically. So, by
specializing the types of
atomically
and
join
to
atomically
:: STM (IO b) -> IO (IO b)join
:: IO (IO b) -> IO b
we can compose them as
join
.atomically
:: STM (IO b) -> IO b
liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r Source #
Promote a function to a monad, scanning the monadic arguments from left to right. For example,
liftM2 (+) [0,1] [0,2] = [0,2,1,3] liftM2 (+) (Just 1) Nothing = Nothing
liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c Source #
Lift a binary function to actions.
Some functors support an implementation of
liftA2
that is more
efficient than the default one. In particular, if
fmap
is an
expensive operation, it is likely better to use
liftA2
than to
fmap
over the structure and then use
<*>
.
This became a typeclass method in 4.10.0.0. Prior to that, it was
a function defined in terms of
<*>
and
fmap
.
Using
ApplicativeDo
: '
' can be understood
as the
liftA2
f as bs
do
expression
do a <- as b <- bs pure (f a b)
liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d Source #
Lift a ternary function to actions.
Using
ApplicativeDo
: '
' can be understood
as the
liftA3
f as bs cs
do
expression
do a <- as b <- bs c <- cs pure (f a b c)
void :: Functor f => f a -> f () Source #
discards or ignores the result of evaluation, such
as the return value of an
void
value
IO
action.
Using
ApplicativeDo
: '
' can be understood as the
void
as
do
expression
do as pure ()
with an inferred
Functor
constraint.
Examples
Replace the contents of a
with unit:
Maybe
Int
>>>
void Nothing
Nothing>>>
void (Just 3)
Just ()
Replace the contents of an
with unit, resulting in an
Either
Int
Int
:
Either
Int
()
>>>
void (Left 8675309)
Left 8675309>>>
void (Right 8675309)
Right ()
Replace every element of a list with unit:
>>>
void [1,2,3]
[(),(),()]
Replace the second element of a pair with unit:
>>>
void (1,2)
(1,())
Discard the result of an
IO
action:
>>>
mapM print [1,2]
1 2 [(),()]>>>
void $ mapM print [1,2]
1 2