| Safe Haskell | Safe-Inferred | 
|---|
Data.List.PointedList
Description
An implementation of a zipper-like non-empty list structure that tracks
   an index position in the list (the focus).
- data  PointedList a = PointedList {
- _reversedPrefix :: [a]
 - _focus :: a
 - _suffix :: [a]
 
 - reversedPrefix :: Functor f => ([a] -> f [a]) -> PointedList a -> f (PointedList a)
 - focus :: Functor f => (a -> f a) -> PointedList a -> f (PointedList a)
 - suffix :: Functor f => ([a] -> f [a]) -> PointedList a -> f (PointedList a)
 - prefix :: Functor f => ([a] -> f [a]) -> PointedList a -> f (PointedList a)
 - singleton :: a -> PointedList a
 - fromList :: [a] -> Maybe (PointedList a)
 - fromListEnd :: [a] -> Maybe (PointedList a)
 - replace :: a -> PointedList a -> PointedList a
 - next :: PointedList a -> Maybe (PointedList a)
 - tryNext :: PointedList a -> PointedList a
 - previous :: PointedList a -> Maybe (PointedList a)
 - tryPrevious :: PointedList a -> PointedList a
 - insert :: a -> PointedList a -> PointedList a
 - insertLeft :: a -> PointedList a -> PointedList a
 - insertRight :: a -> PointedList a -> PointedList a
 - delete :: PointedList a -> Maybe (PointedList a)
 - deleteLeft :: PointedList a -> Maybe (PointedList a)
 - deleteRight :: PointedList a -> Maybe (PointedList a)
 - deleteOthers :: PointedList a -> PointedList a
 - length :: PointedList a -> Int
 - atStart :: PointedList a -> Bool
 - atEnd :: PointedList a -> Bool
 - positions :: PointedList a -> PointedList (PointedList a)
 - contextMap :: (PointedList a -> b) -> PointedList a -> PointedList b
 - withFocus :: PointedList a -> PointedList (a, Bool)
 - moveTo :: Int -> PointedList a -> Maybe (PointedList a)
 - moveN :: Int -> PointedList a -> Maybe (PointedList a)
 - find :: Eq a => a -> PointedList a -> Maybe (PointedList a)
 - index :: PointedList a -> Int
 
Documentation
data PointedList a Source
The implementation of the pointed list structure which tracks the current position in the list structure.
Constructors
| PointedList | |
Fields 
  | |
Instances
| Functor PointedList | |
| Foldable PointedList | |
| Traversable PointedList | |
| Eq a => Eq (PointedList a) | |
| Show a => Show (PointedList a) | |
| Binary a => Binary (PointedList a) | 
reversedPrefix :: Functor f => ([a] -> f [a]) -> PointedList a -> f (PointedList a)Source
Lens compatible with Control.Lens.
focus :: Functor f => (a -> f a) -> PointedList a -> f (PointedList a)Source
Lens compatible with Control.Lens.
suffix :: Functor f => ([a] -> f [a]) -> PointedList a -> f (PointedList a)Source
Lens compatible with Control.Lens.
prefix :: Functor f => ([a] -> f [a]) -> PointedList a -> f (PointedList a)Source
Lens compatible with Control.Lens. Internally reversing the prefix list.
singleton :: a -> PointedList aSource
Create a PointedList with a single element.
fromList :: [a] -> Maybe (PointedList a)Source
Possibly create a  if the provided list has at least
   one element; otherwise, return Nothing.
Just PointedList
The provided list's head will be the focus of the list, and the rest of list will follow on the right side.
fromListEnd :: [a] -> Maybe (PointedList a)Source
Possibly create a  if the provided list has at least
   one element; otherwise, return Nothing.
Just PointedList
The provided list's last element will be the focus of the list, following the rest of the list in order, to the left.
replace :: a -> PointedList a -> PointedList aSource
Replace the focus of the list, retaining the prefix and suffix.
next :: PointedList a -> Maybe (PointedList a)Source
Possibly move the focus to the next element in the list.
tryNext :: PointedList a -> PointedList aSource
Attempt to move the focus to the next element, or error if there are
   no more elements.
previous :: PointedList a -> Maybe (PointedList a)Source
Possibly move the focus to the previous element in the list.
tryPrevious :: PointedList a -> PointedList aSource
Attempt to move the focus to the previous element, or error if there are
   no more elements.
insert :: a -> PointedList a -> PointedList aSource
An alias for insertRight.
insertLeft :: a -> PointedList a -> PointedList aSource
Insert an element to the left of the focus, then move the focus to the new element.
insertRight :: a -> PointedList a -> PointedList aSource
Insert an element to the right of the focus, then move the focus to the new element.
delete :: PointedList a -> Maybe (PointedList a)Source
An alias of deleteRight.
deleteLeft :: PointedList a -> Maybe (PointedList a)Source
Possibly delete the element at the focus, then move the element on the
   left to the focus. If no element is on the left, focus on the element to
   the right. If the deletion will cause the list to be empty, return
   Nothing.
deleteRight :: PointedList a -> Maybe (PointedList a)Source
Possibly delete the element at the focus, then move the element on the
   right to the focus. If no element is on the right, focus on the element to
   the left. If the deletion will cause the list to be empty, return
   Nothing.
deleteOthers :: PointedList a -> PointedList aSource
Delete all elements in the list except the focus.
length :: PointedList a -> IntSource
The length of the list.
atStart :: PointedList a -> BoolSource
Whether the focus is the first element.
atEnd :: PointedList a -> BoolSource
Whether the focus is the last element.
positions :: PointedList a -> PointedList (PointedList a)Source
Create a PointedList of variations of the provided PointedList, in
   which each element is focused, with the provided PointedList as the
   focus of the sets.
contextMap :: (PointedList a -> b) -> PointedList a -> PointedList bSource
Map over the PointedLists created via positions, such that f is	
   called with each element of the list focused in the provided
   PointedList. An example makes this easier to understand:
contextMap atStart (fromJust $ fromList [1..5])
withFocus :: PointedList a -> PointedList (a, Bool)Source
Create a  of PointedList a(a, , in which the boolean values
   specify whether the current element has the focus. That is, all of the
   booleans will be Bool)False, except the focused element.
moveTo :: Int -> PointedList a -> Maybe (PointedList a)Source
Move the focus to the specified index. The first element is at index 0.
moveN :: Int -> PointedList a -> Maybe (PointedList a)Source
Move the focus by n, relative to the current index. Negative values move
   the focus backwards, positive values more forwards through the list.
find :: Eq a => a -> PointedList a -> Maybe (PointedList a)Source
Move the focus to the specified element, if it is present.
Patch with much faster algorithm provided by Runar Bjarnason for version 0.3.2. Improved again by Runar Bjarnason for version 0.3.3 to support infinite lists on both sides of the focus.
index :: PointedList a -> IntSource
The index of the focus, leftmost is 0.