License | MIT |
---|---|
Stability | experimental |
Safe Haskell | Safe |
Language | Haskell2010 |
Control.Comonad.Zipper.Extra
Description
Extra utilities for the Zipper
comonad.
Synopsis
- data Zipper (t :: Type -> Type) a
- 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])
- paginate' :: MonadThrow m => Int -> [a] -> m (Zipper [] [a])
- data PaginationException
- zipperNextMaybe :: Zipper t a -> Maybe a
- zipperPreviousMaybe :: Zipper t a -> Maybe a
- zipperWithin :: Int -> Zipper t a -> [a]
- zipper' :: (MonadThrow m, Traversable t) => t a -> m (Zipper t a)
- data ZipperException = EmptyZipper
- elemIndexThrow :: (MonadThrow m, Eq a, Typeable a, Show a) => a -> [a] -> m Int
- data ElemNotFoundException a = ElemNotFoundException a [a]
- seekOn :: Eq b => (a -> b) -> b -> Zipper [] a -> Maybe (Zipper [] a)
- seekOnThrow :: (MonadThrow m, Eq b, Typeable b, Show b) => (a -> b) -> b -> Zipper [] a -> m (Zipper [] a)
Documentation
data Zipper (t :: Type -> Type) a #
Instances
ComonadStore Int (Zipper t) | |
Defined in Control.Comonad.Store.Zipper | |
Functor (Zipper t) | |
Foldable (Zipper t) | |
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 # elem :: Eq a => a -> Zipper t a -> Bool # maximum :: Ord a => Zipper t a -> a # minimum :: Ord a => Zipper t a -> a # | |
Traversable (Zipper t) | |
Defined in Control.Comonad.Store.Zipper | |
Comonad (Zipper t) | |
Extend (Zipper t) | |
zipper :: Traversable t => t a -> Maybe (Zipper t a) #
zipper1 :: Traversable1 t => t a -> Zipper t a #
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.
data PaginationException Source #
An exception type for when pagination fails to break up a list because either the length of the list or the page size is zero.
Constructors
EmptyContentsError | |
ZeroPageSize | |
UnknownPaginationException |
Instances
Eq PaginationException Source # | |
Defined in Control.Comonad.Zipper.Extra Methods (==) :: PaginationException -> PaginationException -> Bool # (/=) :: PaginationException -> PaginationException -> Bool # | |
Show PaginationException Source # | |
Defined in Control.Comonad.Zipper.Extra Methods showsPrec :: Int -> PaginationException -> ShowS # show :: PaginationException -> String # showList :: [PaginationException] -> ShowS # | |
Exception PaginationException Source # | |
Defined in Control.Comonad.Zipper.Extra Methods toException :: PaginationException -> SomeException # fromException :: SomeException -> Maybe PaginationException # |
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
.
data ZipperException Source #
Exception thrown when trying to make an empty zipper.
Constructors
EmptyZipper |
Instances
Eq ZipperException Source # | |
Defined in Control.Comonad.Zipper.Extra Methods (==) :: ZipperException -> ZipperException -> Bool # (/=) :: ZipperException -> ZipperException -> Bool # | |
Show ZipperException Source # | |
Defined in Control.Comonad.Zipper.Extra Methods showsPrec :: Int -> ZipperException -> ShowS # show :: ZipperException -> String # showList :: [ZipperException] -> ShowS # | |
Exception ZipperException Source # | |
Defined in Control.Comonad.Zipper.Extra Methods toException :: ZipperException -> SomeException # |
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.
data ElemNotFoundException a Source #
Exception thrown when an element can not be found in a list or a zipper.
Constructors
ElemNotFoundException a [a] |
Instances
Eq a => Eq (ElemNotFoundException a) Source # | |
Defined in Control.Comonad.Zipper.Extra Methods (==) :: ElemNotFoundException a -> ElemNotFoundException a -> Bool # (/=) :: ElemNotFoundException a -> ElemNotFoundException a -> Bool # | |
Show a => Show (ElemNotFoundException a) Source # | |
Defined in Control.Comonad.Zipper.Extra Methods showsPrec :: Int -> ElemNotFoundException a -> ShowS # show :: ElemNotFoundException a -> String # showList :: [ElemNotFoundException a] -> ShowS # | |
(Typeable a, Show a) => Exception (ElemNotFoundException a) Source # | |
Defined in Control.Comonad.Zipper.Extra Methods toException :: ElemNotFoundException a -> SomeException # fromException :: SomeException -> Maybe (ElemNotFoundException a) # displayException :: ElemNotFoundException a -> String # |
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.