zipper-extra-0.1.3.2: Zipper utils that weren't in Control.Comonad.Store.Zipper

LicenseMIT
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell2010

Control.Comonad.Zipper.Extra

Description

Extra utilities for the Zipper comonad.

Synopsis

Documentation

data Zipper (t :: Type -> Type) a #

Instances
ComonadStore Int (Zipper t) 
Instance details

Defined in Control.Comonad.Store.Zipper

Methods

pos :: Zipper t a -> Int #

peek :: Int -> Zipper t a -> a #

peeks :: (Int -> Int) -> Zipper t a -> a #

seek :: Int -> Zipper t a -> Zipper t a #

seeks :: (Int -> Int) -> Zipper t a -> Zipper t a #

experiment :: Functor f => (Int -> f Int) -> Zipper t a -> f a #

Functor (Zipper t) 
Instance details

Defined in Control.Comonad.Store.Zipper

Methods

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

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

Foldable (Zipper t) 
Instance details

Defined in Control.Comonad.Store.Zipper

Methods

fold :: Monoid m => Zipper t m -> m #

foldMap :: Monoid m => (a -> m) -> Zipper t a -> m #

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

foldr' :: (a -> b -> b) -> b -> Zipper t a -> b #

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

foldl' :: (b -> a -> b) -> b -> Zipper t a -> b #

foldr1 :: (a -> a -> a) -> Zipper t a -> a #

foldl1 :: (a -> a -> a) -> Zipper t a -> a #

toList :: Zipper t a -> [a] #

null :: Zipper t a -> Bool #

length :: Zipper t a -> Int #

elem :: Eq a => a -> Zipper t a -> Bool #

maximum :: Ord a => Zipper t a -> a #

minimum :: Ord a => Zipper t a -> a #

sum :: Num a => Zipper t a -> a #

product :: Num a => Zipper t a -> a #

Traversable (Zipper t) 
Instance details

Defined in Control.Comonad.Store.Zipper

Methods

traverse :: Applicative f => (a -> f b) -> Zipper t a -> f (Zipper t b) #

sequenceA :: Applicative f => Zipper t (f a) -> f (Zipper t a) #

mapM :: Monad m => (a -> m b) -> Zipper t a -> m (Zipper t b) #

sequence :: Monad m => Zipper t (m a) -> m (Zipper t a) #

Comonad (Zipper t) 
Instance details

Defined in Control.Comonad.Store.Zipper

Methods

extract :: Zipper t a -> a #

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

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

Extend (Zipper t) 
Instance details

Defined in Control.Comonad.Store.Zipper

Methods

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

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

zipper :: Traversable t => t a -> Maybe (Zipper t a) #

zipper1 :: Traversable1 t => t a -> Zipper t a #

unzipper :: Zipper t a -> t a #

size :: Zipper t a -> Int #

paginate :: Int -> [a] -> Maybe (Zipper [] [a]) Source #

Turn a list into a zipper of chunks of length n

paginate' :: MonadThrow m => Int -> [a] -> m (Zipper [] [a]) Source #

Like paginate, but throw an exception if it can't create the zipper.

zipperNextMaybe :: Zipper t a -> Maybe a Source #

Return the peek of the next element if it exists.

zipperPreviousMaybe :: Zipper t a -> Maybe a Source #

Return the peek of the previous element if it exists.

zipperWithin :: Int -> Zipper t a -> [a] Source #

Return a list of elements within r hops either side of the zipper target.

zipper' :: (MonadThrow m, Traversable t) => t a -> m (Zipper t a) Source #

Like zipper but lifted to MonadThrow.

elemIndexThrow :: (MonadThrow m, Eq a, Typeable a, Show a) => a -> [a] -> m Int Source #

Lifted version of elemIndex that throws an ElemNotFoundException if the target does not exist.

seekOn :: Eq b => (a -> b) -> b -> Zipper [] a -> Maybe (Zipper [] a) Source #

Seek on a property of the elements of the zipper. Finds the index of the element to search for and moves the tape to that position.

seekOnThrow :: (MonadThrow m, Eq b, Typeable b, Show b) => (a -> b) -> b -> Zipper [] a -> m (Zipper [] a) Source #

Lifted version of seekOn which throws an ElemNotFoundException if the target does not exist.