Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data CList a
- empty :: CList a
- fromList :: [a] -> CList a
- singleton :: a -> CList a
- update :: a -> CList a -> CList a
- reverseDirection :: CList a -> CList a
- leftElements :: CList a -> [a]
- rightElements :: CList a -> [a]
- toList :: CList a -> [a]
- toInfList :: CList a -> [a]
- focus :: CList a -> Maybe a
- insertR :: a -> CList a -> CList a
- insertL :: a -> CList a -> CList a
- removeL :: CList a -> CList a
- removeR :: CList a -> CList a
- allRotations :: CList a -> CList (CList a)
- rotL :: CList a -> CList a
- mRotL :: CList a -> Maybe (CList a)
- rotR :: CList a -> CList a
- mRotR :: CList a -> Maybe (CList a)
- rotN :: Int -> CList a -> CList a
- rotNR :: Int -> CList a -> CList a
- rotNL :: Int -> CList a -> CList a
- rotateTo :: Eq a => a -> CList a -> Maybe (CList a)
- findRotateTo :: (a -> Bool) -> CList a -> Maybe (CList a)
- filterR :: (a -> Bool) -> CList a -> CList a
- filterL :: (a -> Bool) -> CList a -> CList a
- filterCL :: (CList a -> CList a) -> (a -> Bool) -> CList a -> CList a
- foldrR :: (a -> b -> b) -> b -> CList a -> b
- foldrL :: (a -> b -> b) -> b -> CList a -> b
- foldrCL :: (CList a -> [a]) -> (a -> b -> b) -> b -> CList a -> b
- foldlR :: (a -> b -> a) -> a -> CList b -> a
- foldlL :: (a -> b -> a) -> a -> CList b -> a
- foldlCL :: (CList b -> [b]) -> (a -> b -> a) -> a -> CList b -> a
- balance :: CList a -> CList a
- packL :: CList a -> CList a
- packR :: CList a -> CList a
- isEmpty :: CList a -> Bool
- size :: CList a -> Int
Documentation
A functional ring type.
Instances
Functor CList Source # | |
Foldable CList Source # | |
Defined in Data.CircularList.Internal fold :: Monoid m => CList m -> m # foldMap :: Monoid m => (a -> m) -> CList a -> m # foldMap' :: Monoid m => (a -> m) -> CList a -> m # foldr :: (a -> b -> b) -> b -> CList a -> b # foldr' :: (a -> b -> b) -> b -> CList a -> b # foldl :: (b -> a -> b) -> b -> CList a -> b # foldl' :: (b -> a -> b) -> b -> CList a -> b # foldr1 :: (a -> a -> a) -> CList a -> a # foldl1 :: (a -> a -> a) -> CList a -> a # elem :: Eq a => a -> CList a -> Bool # maximum :: Ord a => CList a -> a # minimum :: Ord a => CList a -> a # | |
Traversable CList Source # | |
Eq a => Eq (CList a) Source # | |
Read a => Read (CList a) Source # | |
Show a => Show (CList a) Source # | |
NFData a => NFData (CList a) Source # | |
Defined in Data.CircularList.Internal |
reverseDirection :: CList a -> CList a Source #
Reverse the direction of rotation.
leftElements :: CList a -> [a] Source #
Starting with the focus, go left and accumulate all elements of the CList in a list.
rightElements :: CList a -> [a] Source #
Starting with the focus, go right and accumulate all elements of the CList in a list.
insertR :: a -> CList a -> CList a Source #
Insert an element into the CList as the new focus. The old focus is now the next element to the right.
insertL :: a -> CList a -> CList a Source #
Insert an element into the CList as the new focus. The old focus is now the next element to the left.
removeL :: CList a -> CList a Source #
Remove the focus from the CList. The new focus is the next element to the left.
mRotL :: CList a -> Maybe (CList a) Source #
A non-cyclic version of rotL
; that is, only rotate the focus if
there is a previous (left) element to rotate to.
mRotR :: CList a -> Maybe (CList a) Source #
A non-cyclic version of rotL
; that is, only rotate the focus if
there is a previous (left) element to rotate to.
rotN :: Int -> CList a -> CList a Source #
Rotate the focus the specified number of times; if the index is positive then it is rotated to the right; otherwise it is rotated to the left.
rotNR :: Int -> CList a -> CList a Source #
A wrapper around rotN
that doesn't rotate the CList if n <= 0
.
rotNL :: Int -> CList a -> CList a Source #
Rotate the focus the specified number of times to the left (but
don't rotate if n <= 0
).
rotateTo :: Eq a => a -> CList a -> Maybe (CList a) Source #
Rotate the CList
such that the specified element (if it exists)
is focused.
findRotateTo :: (a -> Bool) -> CList a -> Maybe (CList a) Source #
Attempt to rotate the CList
such that focused element matches
the supplied predicate.
filterR :: (a -> Bool) -> CList a -> CList a Source #
Remove those elements that do not satisfy the supplied predicate, rotating to the right if the focus does not satisfy the predicate.
filterL :: (a -> Bool) -> CList a -> CList a Source #
As with filterR
, but rotates to the left if the focus does not
satisfy the predicate.
filterCL :: (CList a -> CList a) -> (a -> Bool) -> CList a -> CList a Source #
Abstract away what to do with the focused element if it doesn't match the predicate when filtering.
foldrR :: (a -> b -> b) -> b -> CList a -> b Source #
A right-fold, rotating to the right through the CList.
foldrL :: (a -> b -> b) -> b -> CList a -> b Source #
A right-fold, rotating to the left through the CList.
foldrCL :: (CList a -> [a]) -> (a -> b -> b) -> b -> CList a -> b Source #
Abstract away direction for a foldr.
foldlR :: (a -> b -> a) -> a -> CList b -> a Source #
A (strict) left-fold, rotating to the right through the CList.
foldlL :: (a -> b -> a) -> a -> CList b -> a Source #
A (strict) left-fold, rotating to the left through the CList.