Copyright | Quentin Moser <moserq@gmail.com> |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | orphaned |
Stability | unstable |
Portability | unportable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Utility functions for manipulating Maybe Stack
s.
Synopsis
- type Zipper a = Maybe (Stack a)
- emptyZ :: Zipper a
- singletonZ :: a -> Zipper a
- fromIndex :: [a] -> Int -> Zipper a
- toIndex :: Zipper a -> ([a], Maybe Int)
- fromTags :: [Either a a] -> Zipper a
- toTags :: Zipper a -> [Either a a]
- zipperFocusedAtFirstOf :: Eq q => [q] -> [q] -> Zipper q
- insertUpZ :: a -> Zipper a -> Zipper a
- insertDownZ :: a -> Zipper a -> Zipper a
- swapUpZ :: Zipper a -> Zipper a
- swapDownZ :: Zipper a -> Zipper a
- swapMasterZ :: Zipper a -> Zipper a
- focusUpZ :: Zipper a -> Zipper a
- focusDownZ :: Zipper a -> Zipper a
- focusMasterZ :: Zipper a -> Zipper a
- findS :: (a -> Bool) -> Stack a -> Maybe (Stack a)
- findZ :: (a -> Bool) -> Zipper a -> Zipper a
- getFocusZ :: Zipper a -> Maybe a
- getIZ :: Int -> Zipper a -> Maybe a
- sortZ :: Ord a => Zipper a -> Zipper a
- sortByZ :: (a -> a -> Ordering) -> Zipper a -> Zipper a
- mapZ :: (Bool -> a -> b) -> Zipper a -> Zipper b
- mapZ_ :: (a -> b) -> Zipper a -> Zipper b
- mapZM :: Monad m => (Bool -> a -> m b) -> Zipper a -> m (Zipper b)
- mapZM_ :: Monad m => (a -> m b) -> Zipper a -> m (Zipper b)
- onFocusedZ :: (a -> a) -> Zipper a -> Zipper a
- onFocusedZM :: Monad m => (a -> m a) -> Zipper a -> m (Zipper a)
- onIndexZ :: Int -> (a -> a) -> Zipper a -> Zipper a
- onIndexZM :: Monad m => Int -> (a -> m a) -> Zipper a -> m (Zipper a)
- filterZ :: (Bool -> a -> Bool) -> Zipper a -> Zipper a
- filterZ_ :: (a -> Bool) -> Zipper a -> Zipper a
- deleteFocusedZ :: Zipper a -> Zipper a
- deleteIndexZ :: Int -> Zipper a -> Zipper a
- foldrZ :: (Bool -> a -> b -> b) -> b -> Zipper a -> b
- foldlZ :: (Bool -> b -> a -> b) -> b -> Zipper a -> b
- foldrZ_ :: (a -> b -> b) -> b -> Zipper a -> b
- foldlZ_ :: (b -> a -> b) -> b -> Zipper a -> b
- elemZ :: Eq a => a -> Zipper a -> Bool
- getI :: Int -> [a] -> Maybe a
- tagBy :: (a -> Bool) -> a -> Either a a
- fromE :: Either a a -> a
- mapE :: (Bool -> a -> b) -> Either a a -> Either b b
- mapE_ :: (a -> b) -> Either a a -> Either b b
- mapEM :: Monad m => (Bool -> a -> m b) -> Either a a -> m (Either b b)
- mapEM_ :: Monad m => (a -> m b) -> Either a a -> m (Either b b)
- reverseS :: Stack a -> Stack a
- reverseZ :: Zipper a -> Zipper a
Usage
This is a developer-oriented module, intended to be used for writing new extentions.
singletonZ :: a -> Zipper a Source #
Conversions
fromIndex :: [a] -> Int -> Zipper a Source #
Create a stack from a list, and the 0-based index of the focused element. If the index is out of bounds, focus will go to the first element.
toIndex :: Zipper a -> ([a], Maybe Int) Source #
Turn a stack into a list and the index of its focused element.
zipperFocusedAtFirstOf :: Eq q => [q] -> [q] -> Zipper q Source #
differentiate zs xs
takes the first z
from z2 that also belongs to
xs and turns
xs into a stack with
z being the current element. Acts
as
zsdifferentiate
if and
xs@ don't intersect.
Zipper
manipulation functions
Insertion, movement
insertUpZ :: a -> Zipper a -> Zipper a Source #
Insert an element before the focused one, and focus it
insertDownZ :: a -> Zipper a -> Zipper a Source #
Insert an element after the focused one, and focus it
swapMasterZ :: Zipper a -> Zipper a Source #
Swap the focused element with the first one
Focus movement
focusDownZ :: Zipper a -> Zipper a Source #
Move the focus to the next element
focusMasterZ :: Zipper a -> Zipper a Source #
Move the focus to the first element
findS :: (a -> Bool) -> Stack a -> Maybe (Stack a) Source #
Refocus a Stack a
on an element satisfying the predicate, or fail to
Nothing
.
findZ :: (a -> Bool) -> Zipper a -> Zipper a Source #
Refocus a Zipper a
on an element satisfying the predicate, or fail to
Nothing
.
Extraction
Sorting
sortByZ :: (a -> a -> Ordering) -> Zipper a -> Zipper a Source #
Sort a stack with an arbitrary sorting function
Maps
mapZ :: (Bool -> a -> b) -> Zipper a -> Zipper b Source #
Map a function over a stack. The boolean argument indcates whether the current element is the focused one
onFocusedZ :: (a -> a) -> Zipper a -> Zipper a Source #
Apply a function to the focused element
onFocusedZM :: Monad m => (a -> m a) -> Zipper a -> m (Zipper a) Source #
Monadic version of onFocusedZ
onIndexZ :: Int -> (a -> a) -> Zipper a -> Zipper a Source #
Apply a function to the element at the given index
onIndexZM :: Monad m => Int -> (a -> m a) -> Zipper a -> m (Zipper a) Source #
Monadic version of onIndexZ
Filters
filterZ :: (Bool -> a -> Bool) -> Zipper a -> Zipper a Source #
Fiter a stack according to a predicate. The refocusing behavior mimics XMonad's usual one. The boolean argument indicates whether the current element is the focused one.
deleteFocusedZ :: Zipper a -> Zipper a Source #
Delete the focused element
Folds
Other utility functions
getI :: Int -> [a] -> Maybe a Source #
Deprecated: Use XMonad.Prelude.(!?) instead.
Safe version of !!