streams-3.3.2: Various Haskell 2010 stream comonads
Copyright(C) 2011-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Stream.Infinite.Functional.Zipper

Description

This is an infinite bidirectional zipper

Synopsis

The type of streams

data Zipper a Source #

Constructors

!Integer :~ !(Integer -> a) infixr 0 

Instances

Instances details
Applicative Zipper Source # 
Instance details

Defined in Data.Stream.Infinite.Functional.Zipper

Methods

pure :: a -> Zipper a #

(<*>) :: Zipper (a -> b) -> Zipper a -> Zipper b #

liftA2 :: (a -> b -> c) -> Zipper a -> Zipper b -> Zipper c #

(*>) :: Zipper a -> Zipper b -> Zipper b #

(<*) :: Zipper a -> Zipper b -> Zipper a #

Functor Zipper Source # 
Instance details

Defined in Data.Stream.Infinite.Functional.Zipper

Methods

fmap :: (a -> b) -> Zipper a -> Zipper b #

(<$) :: a -> Zipper b -> Zipper a #

Monad Zipper Source # 
Instance details

Defined in Data.Stream.Infinite.Functional.Zipper

Methods

(>>=) :: Zipper a -> (a -> Zipper b) -> Zipper b #

(>>) :: Zipper a -> Zipper b -> Zipper b #

return :: a -> Zipper a #

Comonad Zipper Source # 
Instance details

Defined in Data.Stream.Infinite.Functional.Zipper

Methods

extract :: Zipper a -> a #

duplicate :: Zipper a -> Zipper (Zipper a) #

extend :: (Zipper a -> b) -> Zipper a -> Zipper b #

ComonadApply Zipper Source # 
Instance details

Defined in Data.Stream.Infinite.Functional.Zipper

Methods

(<@>) :: Zipper (a -> b) -> Zipper a -> Zipper b #

(@>) :: Zipper a -> Zipper b -> Zipper b #

(<@) :: Zipper a -> Zipper b -> Zipper a #

Apply Zipper Source # 
Instance details

Defined in Data.Stream.Infinite.Functional.Zipper

Methods

(<.>) :: Zipper (a -> b) -> Zipper a -> Zipper b #

(.>) :: Zipper a -> Zipper b -> Zipper b #

(<.) :: Zipper a -> Zipper b -> Zipper a #

liftF2 :: (a -> b -> c) -> Zipper a -> Zipper b -> Zipper c #

Extend Zipper Source # 
Instance details

Defined in Data.Stream.Infinite.Functional.Zipper

Methods

duplicated :: Zipper a -> Zipper (Zipper a) #

extended :: (Zipper a -> b) -> Zipper a -> Zipper b #

Semigroup (Zipper a) Source # 
Instance details

Defined in Data.Stream.Infinite.Functional.Zipper

Methods

(<>) :: Zipper a -> Zipper a -> Zipper a #

sconcat :: NonEmpty (Zipper a) -> Zipper a #

stimes :: Integral b => b -> Zipper a -> Zipper a #

tail :: Zipper a -> Zipper a Source #

Move the head of the zipper to the right

untail :: Zipper a -> Zipper a Source #

Move the head of the zipper to the left

intersperse :: a -> Zipper a -> Zipper a Source #

intersperse y xs creates an alternating stream of elements from xs and y.

interleave :: Zipper a -> Zipper a -> Zipper a Source #

Interleave two Zippers xs and ys, alternating elements from each list.

[x1,x2,...] `interleave` [y1,y2,...] == [x1,y1,x2,y2,...]
interleave = (<>)

transpose :: Zipper (Zipper a) -> Zipper (Zipper a) Source #

transpose computes the transposition of a stream of streams.

take :: Integer -> Zipper a -> [a] Source #

drop :: Integer -> Zipper a -> Zipper a Source #

drop n xs drops the first n elements off the front of the sequence xs.

splitAt :: Integer -> Zipper a -> ([a], Zipper a) Source #

splitAt n xs returns a pair consisting of the prefix of xs of length n and the remaining stream immediately following this prefix.

Beware: passing a negative integer as the first argument will cause an error if you access the taken portion

(!!) :: Zipper a -> Integer -> a Source #

xs !! n returns the element of the stream xs at index n. Note that the head of the stream has index 0.

unzip :: Zipper (a, b) -> (Zipper a, Zipper b) Source #

The unzip function is the inverse of the zip function.

head :: Zipper a -> a Source #

Extract the focused element

(<|) :: a -> Zipper a -> Zipper a Source #

Cons before the head of the zipper. The head now points to the new element

uncons :: Zipper a -> (a, Zipper a) Source #

Move the head of the zipper one step to the right, returning the value we move over.

takeWhile :: (a -> Bool) -> Zipper a -> [a] Source #

takeWhile p xs returns the longest prefix of the stream xs for which the predicate p holds.

dropWhile :: (a -> Bool) -> Zipper a -> Zipper a Source #

dropWhile p xs returns the suffix remaining after takeWhile p xs.

Beware: this function may diverge if every element of xs satisfies p, e.g. dropWhile even (repeat 0) will loop.

span :: (a -> Bool) -> Zipper a -> ([a], Zipper a) Source #

span p xs returns the longest prefix of xs that satisfies p, together with the remainder of the stream.

break :: (a -> Bool) -> Zipper a -> ([a], Zipper a) Source #

The break p function is equivalent to span not . p.

isPrefixOf :: Eq a => [a] -> Zipper a -> Bool Source #

The isPrefix function returns True if the first argument is a prefix of the second.

findIndex :: (a -> Bool) -> Zipper a -> Integer Source #

The findIndex function takes a predicate and a stream and returns the index of the first element in the stream that satisfies the predicate,

Beware: findIndex p xs will diverge if none of the elements of xs satisfy p.

elemIndex :: Eq a => a -> Zipper a -> Integer Source #

The elemIndex function returns the index of the first element in the given stream which is equal (by ==) to the query element,

Beware: elemIndex x xs will diverge if none of the elements of xs equal x.

zip :: Zipper a -> Zipper b -> Zipper (a, b) Source #

The zip function takes two streams and returns a list of corresponding pairs.

zip = liftA2 (,)

zipWith :: (a -> b -> c) -> Zipper a -> Zipper b -> Zipper c Source #

The zipWith function generalizes zip. Rather than tupling the functions, the elements are combined using the function passed as the first argument to zipWith.

zipWith = liftA2