Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Zipper a
- lefts :: Zipper a -> [a]
- rights :: Zipper a -> [a]
- current :: Zipper a -> a
- left :: Zipper a -> Maybe (Zipper a)
- right :: Zipper a -> Maybe (Zipper a)
- findLeft :: Eq a => a -> Zipper a -> Maybe (Zipper a)
- findRight :: Eq a => a -> Zipper a -> Maybe (Zipper a)
- start :: Zipper a -> Zipper a
- end :: Zipper a -> Zipper a
- fromNonEmpty :: NonEmpty a -> Zipper a
- fromNonEmptyEnd :: NonEmpty a -> Zipper a
- replace :: a -> Zipper a -> Zipper a
- delete :: Zipper a -> Maybe (Zipper a)
- push :: a -> Zipper a -> Zipper a
- pop :: Zipper a -> (Zipper a, Maybe a)
- shift :: Zipper a -> (Zipper a, Maybe a)
- unshift :: a -> Zipper a -> Zipper a
- reverse :: Zipper a -> Zipper a
- isStart :: Zipper a -> Bool
- isEnd :: Zipper a -> Bool
Documentation
Instances
Functor Zipper Source # | |
Foldable Zipper Source # | |
Defined in Data.List.NonEmpty.Zipper fold :: Monoid m => Zipper m -> m # foldMap :: Monoid m => (a -> m) -> Zipper a -> m # foldMap' :: Monoid m => (a -> m) -> Zipper a -> m # foldr :: (a -> b -> b) -> b -> Zipper a -> b # foldr' :: (a -> b -> b) -> b -> Zipper a -> b # foldl :: (b -> a -> b) -> b -> Zipper a -> b # foldl' :: (b -> a -> b) -> b -> Zipper a -> b # foldr1 :: (a -> a -> a) -> Zipper a -> a # foldl1 :: (a -> a -> a) -> Zipper a -> a # elem :: Eq a => a -> Zipper a -> Bool # maximum :: Ord a => Zipper a -> a # minimum :: Ord a => Zipper a -> a # | |
Traversable Zipper Source # | |
Comonad Zipper Source # | The list zipper is a basic comonad This instance allows us to create a zipper of all possible states of
traversing the zipper with
|
Eq a => Eq (Zipper a) Source # | |
Show a => Show (Zipper a) Source # | |
Generic (Zipper a) Source # | |
NFData a => NFData (Zipper a) Source # | |
Defined in Data.List.NonEmpty.Zipper | |
type Rep (Zipper a) Source # | |
Defined in Data.List.NonEmpty.Zipper type Rep (Zipper a) = D1 ('MetaData "Zipper" "Data.List.NonEmpty.Zipper" "nonempty-zipper-1.0.0.4-Akhc94dkNFlGOjsZPnEJvM" 'False) (C1 ('MetaCons "Zipper" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a])))) |
Accessors
lefts :: Zipper a -> [a] Source #
Get all values on the left of the cursor
>>>
lefts . fromNonEmptyEnd $ NE.fromList [1, 2, 3]
[1,2]
rights :: Zipper a -> [a] Source #
Get all values on the right of the cursor
>>>
rights . fromNonEmpty $ NE.fromList [1, 2, 3]
[2,3]
Traversal
left :: Zipper a -> Maybe (Zipper a) Source #
Move the current focus of the cursor to the left
>>>
left . fromNonEmptyEnd $ NE.fromList [1, 2, 3]
Just (Zipper [1] 2 [3])
right :: Zipper a -> Maybe (Zipper a) Source #
Move the current focus of the cursor to the right
>>>
right . fromNonEmpty $ NE.fromList [1, 2, 3]
Just (Zipper [1] 2 [3])
findLeft :: Eq a => a -> Zipper a -> Maybe (Zipper a) Source #
Move the current focus of the cursor to the first occurence of a value on the left
>>>
findLeft 2 . fromNonEmptyEnd $ NE.fromList [2, 1, 2, 1, 1, 3]
Just (Zipper [1,2] 2 [1,1,3])
findRight :: Eq a => a -> Zipper a -> Maybe (Zipper a) Source #
Move the current focus of the cursor to the first occurence of a value on the right
>>>
findRight 3 . fromNonEmpty $ NE.fromList [2, 1, 3, 1, 1, 3]
Just (Zipper [1,2] 3 [1,1,3])
start :: Zipper a -> Zipper a Source #
Move the current focus of the cursor to the start of the Zipper
>>>
start . fromNonEmptyEnd $ NE.fromList [1, 2, 3]
Zipper [] 1 [2,3]
end :: Zipper a -> Zipper a Source #
Move the current focus of the cursor to the end of the Zipper
>>>
end . fromNonEmpty $ NE.fromList [1, 2, 3]
Zipper [2,1] 3 []
Construction
fromNonEmpty :: NonEmpty a -> Zipper a Source #
fromNonEmptyEnd :: NonEmpty a -> Zipper a Source #
Update
replace :: a -> Zipper a -> Zipper a Source #
Replace the current item under the curosr
>>>
replace 4 . fromNonEmpty $ NE.fromList [1, 2, 3]
Zipper [] 4 [2,3]
delete :: Zipper a -> Maybe (Zipper a) Source #
Delete the item currently under the cursor
The item currently under the cursor is removed. The cursors focus will move
right. If at the end of the
the cursor will move left.Zipper
>>>
delete . fromNonEmpty $ NE.fromList [1, 2, 3]
Just (Zipper [] 2 [3])
>>>
delete . fromNonEmptyEnd $ NE.fromList [1, 2, 3]
Just (Zipper [1] 2 [])
push :: a -> Zipper a -> Zipper a Source #
Insert a value to the left of the cursor
>>>
push 0 . fromNonEmpty $ NE.fromList [1, 2, 3]
Zipper [0] 1 [2,3]
pop :: Zipper a -> (Zipper a, Maybe a) Source #
Remove a value to the left of the cursor
>>>
pop . fromNonEmpty $ NE.fromList [1, 2, 3]
(Zipper [] 1 [2,3],Nothing)
>>>
pop . fromNonEmptyEnd $ NE.fromList [1, 2, 3]
(Zipper [1] 3 [],Just 2)
shift :: Zipper a -> (Zipper a, Maybe a) Source #
Remove a value to the right of the cursor
>>>
shift . fromNonEmptyEnd $ NE.fromList [1, 2, 3]
(Zipper [2,1] 3 [],Nothing)
>>>
shift . fromNonEmpty $ NE.fromList [1, 2, 3]
(Zipper [] 1 [3],Just 2)
unshift :: a -> Zipper a -> Zipper a Source #
Insert a value to the right of the cursor
>>>
unshift 4 . fromNonEmpty $ NE.fromList [1, 2, 3]
Zipper [] 1 [4,2,3]
reverse :: Zipper a -> Zipper a Source #
Reverse the zipper keeping the cursor focus intact
>>>
reverse . fromNonEmpty $ NE.fromList [1, 2, 3]
Zipper [2,3] 1 []