{-# LANGUAGE PatternGuards #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Util.Stack
-- Description :  Utility functions for manipulating @Maybe Stack@s.
-- Copyright   :  Quentin Moser <moserq@gmail.com>
-- License     :  BSD-style (see LICENSE)
--
-- Maintainer  :  orphaned
-- Stability   :  unstable
-- Portability :  unportable
--
-- Utility functions for manipulating @Maybe Stack@s.
--
-----------------------------------------------------------------------------

module XMonad.Util.Stack ( -- * Usage
                           -- | This is a developer-oriented module, intended to be used
                           -- for writing new extentions.
                           Zipper
                         , emptyZ
                         , singletonZ

                           -- * Conversions
                         , fromIndex
                         , toIndex
                         , fromTags
                         , toTags
                         , zipperFocusedAtFirstOf

                           -- * 'Zipper' manipulation functions
                           -- ** Insertion, movement
                         , insertUpZ
                         , insertDownZ
                         , swapUpZ
                         , swapDownZ
                         , swapMasterZ
                           -- ** Focus movement
                         , focusUpZ
                         , focusDownZ
                         , focusMasterZ
                         , findS
                         , findZ
                           -- ** Extraction
                         , getFocusZ
                         , getIZ
                           -- ** Sorting
                         , sortZ
                         , sortByZ
                           -- ** Maps
                         , mapZ
                         , mapZ_
                         , mapZM
                         , mapZM_
                         , onFocusedZ
                         , onFocusedZM
                         , onIndexZ
                         , onIndexZM
                           -- ** Filters
                         , filterZ
                         , filterZ_
                         , deleteFocusedZ
                         , deleteIndexZ
                           -- ** Folds
                         , foldrZ
                         , foldlZ
                         , foldrZ_
                         , foldlZ_
                         , elemZ

                           -- * Other utility functions
                         , getI
                         , tagBy
                         , fromE
                         , mapE
                         , mapE_
                         , mapEM
                         , mapEM_
                         , reverseS
                         , reverseZ
                         ) where

import qualified XMonad.StackSet as W
import XMonad.Prelude (guard, sortBy, (!?), (<|>))


type Zipper a = Maybe (W.Stack a)

emptyZ :: Zipper a
emptyZ :: forall a. Zipper a
emptyZ = forall a. Maybe a
Nothing

singletonZ :: a -> Zipper a
singletonZ :: forall a. a -> Zipper a
singletonZ a
a = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. a -> [a] -> [a] -> Stack a
W.Stack a
a [] []

-- * Conversions

-- | 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.
fromIndex :: [a] -> Int -> Zipper a
fromIndex :: forall a. [a] -> Int -> Zipper a
fromIndex [a]
as Int
i = forall a. [Either a a] -> Zipper a
fromTags forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith forall a b. (a -> b) -> a -> b
($) (forall a. Int -> a -> [a]
replicate Int
i forall a b. a -> Either a b
Left forall a. [a] -> [a] -> [a]
++ [forall a b. b -> Either a b
Right] forall a. [a] -> [a] -> [a]
++ forall a. a -> [a]
repeat forall a b. a -> Either a b
Left) [a]
as

-- | Turn a stack into a list and the index of its focused element.
toIndex :: Zipper a -> ([a], Maybe Int)
toIndex :: forall a. Zipper a -> ([a], Maybe Int)
toIndex Maybe (Stack a)
Nothing = ([], forall a. Maybe a
Nothing)
toIndex (Just Stack a
s) = (forall a. Stack a -> [a]
W.integrate Stack a
s, forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Int
length forall a b. (a -> b) -> a -> b
$ forall a. Stack a -> [a]
W.up Stack a
s)

-- | Create a stack from a list of 'Either'-tagged values. Focus will go to
-- the first 'Right' value, or if there is none, to the first 'Left' one.
fromTags :: [Either a a] -> Zipper a
fromTags :: forall a. [Either a a] -> Zipper a
fromTags = forall {a}. ([a], Maybe a, [a]) -> Maybe (Stack a)
finalize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall {a}.
Either a a -> ([a], Maybe a, [a]) -> ([a], Maybe a, [a])
step ([], forall a. Maybe a
Nothing, [])
    where step :: Either a a -> ([a], Maybe a, [a]) -> ([a], Maybe a, [a])
step (Right a
a) ([a]
u, Just a
f, [a]
d) = ([], forall a. a -> Maybe a
Just a
a, [a]
uforall a. [a] -> [a] -> [a]
++a
fforall a. a -> [a] -> [a]
:[a]
d)
          step (Right a
a) ([a]
u, Maybe a
Nothing, [a]
d) = ([a]
u, forall a. a -> Maybe a
Just a
a, [a]
d)
          step (Left a
a) ([a]
u, Just a
f, [a]
d) = (a
aforall a. a -> [a] -> [a]
:[a]
u, forall a. a -> Maybe a
Just a
f, [a]
d)
          step (Left a
a) ([a]
u, Maybe a
Nothing, [a]
d) = ([a]
u, forall a. Maybe a
Nothing, a
aforall a. a -> [a] -> [a]
:[a]
d)
          finalize :: ([a], Maybe a, [a]) -> Maybe (Stack a)
finalize ([a]
u, Just a
f, [a]
d) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. a -> [a] -> [a] -> Stack a
W.Stack a
f (forall a. [a] -> [a]
reverse [a]
u) [a]
d
          finalize ([a]
u, Maybe a
Nothing, a
a:[a]
d) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. a -> [a] -> [a] -> Stack a
W.Stack a
a (forall a. [a] -> [a]
reverse [a]
u) [a]
d
          finalize ([a]
_, Maybe a
Nothing, []) = forall a. Maybe a
Nothing

-- | Turn a stack into an 'Either'-tagged list. The focused element
-- will be tagged with 'Right', the others with 'Left'.
toTags :: Zipper a -> [Either a a]
toTags :: forall a. Zipper a -> [Either a a]
toTags Maybe (Stack a)
Nothing = []
toTags (Just Stack a
s) = forall a b. (a -> b) -> [a] -> [b]
map forall a b. a -> Either a b
Left (forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Stack a -> [a]
W.up forall a b. (a -> b) -> a -> b
$ Stack a
s) forall a. [a] -> [a] -> [a]
++ [forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Stack a -> a
W.focus forall a b. (a -> b) -> a -> b
$ Stack a
s]
                  forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall a b. a -> Either a b
Left (forall a. Stack a -> [a]
W.down Stack a
s)

-- | @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 'XMonad.StackSet.differentiate' if @zs@ and @xs@ don't intersect.
zipperFocusedAtFirstOf :: Eq q => [q] -> [q] -> Zipper q
zipperFocusedAtFirstOf :: forall q. Eq q => [q] -> [q] -> Zipper q
zipperFocusedAtFirstOf []       [q]
xs = forall a. [a] -> Maybe (Stack a)
W.differentiate [q]
xs
zipperFocusedAtFirstOf (q
z : [q]
zs) [q]
xs
  | q
z forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [q]
xs = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$
        W.Stack { focus :: q
W.focus = q
z
                , up :: [q]
W.up    = forall a. [a] -> [a]
reverse forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
takeWhile (forall a. Eq a => a -> a -> Bool
/= q
z) [q]
xs
                , down :: [q]
W.down  = forall a. Int -> [a] -> [a]
drop Int
1  forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a. Eq a => a -> a -> Bool
/= q
z) [q]
xs
                }
  | Bool
otherwise = forall q. Eq q => [q] -> [q] -> Zipper q
zipperFocusedAtFirstOf [q]
zs [q]
xs

-- * Zipper functions

-- ** Insertion, movement

-- | Insert an element before the focused one, and focus it
insertUpZ :: a -> Zipper a -> Zipper a
insertUpZ :: forall a. a -> Zipper a -> Zipper a
insertUpZ a
a Maybe (Stack a)
Nothing = forall a. [a] -> Maybe (Stack a)
W.differentiate [a
a]
insertUpZ a
a (Just Stack a
s) = forall a. a -> Maybe a
Just Stack a
s { focus :: a
W.focus = a
a , down :: [a]
W.down = forall a. Stack a -> a
W.focus Stack a
s forall a. a -> [a] -> [a]
: forall a. Stack a -> [a]
W.down Stack a
s }

-- | Insert an element after the focused one, and focus it
insertDownZ :: a -> Zipper a -> Zipper a
insertDownZ :: forall a. a -> Zipper a -> Zipper a
insertDownZ a
a Maybe (Stack a)
Nothing = forall a. [a] -> Maybe (Stack a)
W.differentiate [a
a]
insertDownZ a
a (Just Stack a
s) = forall a. a -> Maybe a
Just Stack a
s { focus :: a
W.focus = a
a, up :: [a]
W.up = forall a. Stack a -> a
W.focus Stack a
s forall a. a -> [a] -> [a]
: forall a. Stack a -> [a]
W.up Stack a
s }

-- | Swap the focused element with the previous one
swapUpZ :: Zipper a -> Zipper a
swapUpZ :: forall a. Zipper a -> Zipper a
swapUpZ Maybe (Stack a)
Nothing = forall a. Maybe a
Nothing
swapUpZ (Just Stack a
s) | a
u:[a]
up <- forall a. Stack a -> [a]
W.up Stack a
s = forall a. a -> Maybe a
Just Stack a
s { up :: [a]
W.up = [a]
up, down :: [a]
W.down = a
uforall a. a -> [a] -> [a]
:forall a. Stack a -> [a]
W.down Stack a
s}
swapUpZ (Just Stack a
s) = forall a. a -> Maybe a
Just Stack a
s { up :: [a]
W.up = forall a. [a] -> [a]
reverse (forall a. Stack a -> [a]
W.down Stack a
s), down :: [a]
W.down = [] }

-- | Swap the focused element with the next one
swapDownZ :: Zipper a -> Zipper a
swapDownZ :: forall a. Zipper a -> Zipper a
swapDownZ Maybe (Stack a)
Nothing = forall a. Maybe a
Nothing
swapDownZ (Just Stack a
s) | a
d:[a]
down <- forall a. Stack a -> [a]
W.down Stack a
s = forall a. a -> Maybe a
Just Stack a
s { down :: [a]
W.down = [a]
down, up :: [a]
W.up = a
dforall a. a -> [a] -> [a]
:forall a. Stack a -> [a]
W.up Stack a
s }
swapDownZ (Just Stack a
s) = forall a. a -> Maybe a
Just Stack a
s { up :: [a]
W.up = [], down :: [a]
W.down = forall a. [a] -> [a]
reverse (forall a. Stack a -> [a]
W.up Stack a
s) }

-- | Swap the focused element with the first one
swapMasterZ :: Zipper a -> Zipper a
swapMasterZ :: forall a. Zipper a -> Zipper a
swapMasterZ Maybe (Stack a)
Nothing = forall a. Maybe a
Nothing
swapMasterZ (Just (W.Stack a
f [a]
up [a]
down)) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. a -> [a] -> [a] -> Stack a
W.Stack a
f [] (forall a. [a] -> [a]
reverse [a]
up forall a. [a] -> [a] -> [a]
++ [a]
down)

-- ** Focus movement

-- | Move the focus to the previous element
focusUpZ :: Zipper a -> Zipper a
focusUpZ :: forall a. Zipper a -> Zipper a
focusUpZ Maybe (Stack a)
Nothing = forall a. Maybe a
Nothing
focusUpZ (Just Stack a
s) | a
u:[a]
up <- forall a. Stack a -> [a]
W.up Stack a
s = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. a -> [a] -> [a] -> Stack a
W.Stack a
u [a]
up (forall a. Stack a -> a
W.focus Stack a
sforall a. a -> [a] -> [a]
:forall a. Stack a -> [a]
W.down Stack a
s)
focusUpZ (Just Stack a
s) | forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall a b. (a -> b) -> a -> b
$ forall a. Stack a -> [a]
W.down Stack a
s = forall a. a -> Maybe a
Just Stack a
s
focusUpZ (Just (W.Stack a
f [a]
_ [a]
down)) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. a -> [a] -> [a] -> Stack a
W.Stack (forall a. [a] -> a
last [a]
down) (forall a. Int -> [a] -> [a]
drop Int
1 (forall a. [a] -> [a]
reverse [a]
down) forall a. [a] -> [a] -> [a]
++ [a
f]) []

-- | Move the focus to the next element
focusDownZ :: Zipper a -> Zipper a
focusDownZ :: forall a. Zipper a -> Zipper a
focusDownZ Maybe (Stack a)
Nothing = forall a. Maybe a
Nothing
focusDownZ (Just Stack a
s) | a
d:[a]
down <- forall a. Stack a -> [a]
W.down Stack a
s = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. a -> [a] -> [a] -> Stack a
W.Stack a
d (forall a. Stack a -> a
W.focus Stack a
sforall a. a -> [a] -> [a]
:forall a. Stack a -> [a]
W.up Stack a
s) [a]
down
focusDownZ (Just Stack a
s) | forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall a b. (a -> b) -> a -> b
$ forall a. Stack a -> [a]
W.up Stack a
s = forall a. a -> Maybe a
Just Stack a
s
focusDownZ (Just (W.Stack a
f [a]
up [a]
_)) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. a -> [a] -> [a] -> Stack a
W.Stack (forall a. [a] -> a
last [a]
up) [] (forall a. Int -> [a] -> [a]
drop Int
1 (forall a. [a] -> [a]
reverse [a]
up) forall a. [a] -> [a] -> [a]
++ [a
f])

-- | Move the focus to the first element
focusMasterZ :: Zipper a -> Zipper a
focusMasterZ :: forall a. Zipper a -> Zipper a
focusMasterZ Maybe (Stack a)
Nothing = forall a. Maybe a
Nothing
focusMasterZ (Just (W.Stack a
f [a]
up [a]
down)) | Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
up
    = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. a -> [a] -> [a] -> Stack a
W.Stack (forall a. [a] -> a
last [a]
up) [] (forall a. Int -> [a] -> [a]
drop Int
1 (forall a. [a] -> [a]
reverse [a]
up) forall a. [a] -> [a] -> [a]
++ [a
f] forall a. [a] -> [a] -> [a]
++ [a]
down)
focusMasterZ (Just Stack a
s) = forall a. a -> Maybe a
Just Stack a
s

-- | Refocus a @Stack a@ on an element satisfying the predicate, or fail to
--   @Nothing@.
findS :: (a -> Bool) -> W.Stack a -> Maybe (W.Stack a)
findS :: forall a. (a -> Bool) -> Stack a -> Maybe (Stack a)
findS a -> Bool
p Stack a
st = Stack a
st forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Bool
p forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Stack a -> a
W.focus) Stack a
st forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Stack a -> Maybe (Stack a)
findUp Stack a
st forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Stack a -> Maybe (Stack a)
findDown Stack a
st
  where findDown :: Stack a -> Maybe (Stack a)
findDown = forall a. Zipper a -> Zipper a
reverseZ forall b c a. (b -> c) -> (a -> b) -> a -> c
. Stack a -> Maybe (Stack a)
findUp forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Stack a -> Stack a
reverseS
        findUp :: Stack a -> Maybe (Stack a)
findUp Stack a
s | a
u:[a]
ups <- forall a. Stack a -> [a]
W.up Stack a
s = (if a -> Bool
p a
u then forall a. a -> Maybe a
Just else Stack a -> Maybe (Stack a)
findUp)
                                   forall a b. (a -> b) -> a -> b
$ forall a. a -> [a] -> [a] -> Stack a
W.Stack a
u [a]
ups (forall a. Stack a -> a
W.focus Stack a
s forall a. a -> [a] -> [a]
: forall a. Stack a -> [a]
W.down Stack a
s)
                 | Bool
otherwise       = forall a. Maybe a
Nothing

-- | Refocus a @Zipper a@ on an element satisfying the predicate, or fail to
--   @Nothing@.
findZ :: (a -> Bool) -> Zipper a -> Zipper a
findZ :: forall a. (a -> Bool) -> Zipper a -> Zipper a
findZ a -> Bool
_ Maybe (Stack a)
Nothing   = forall a. Maybe a
Nothing
findZ a -> Bool
p (Just Stack a
st) = forall a. (a -> Bool) -> Stack a -> Maybe (Stack a)
findS a -> Bool
p Stack a
st

-- ** Extraction

-- | Get the focused element
getFocusZ :: Zipper a -> Maybe a
getFocusZ :: forall a. Zipper a -> Maybe a
getFocusZ = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Stack a -> a
W.focus

-- | Get the element at a given index
getIZ :: Int -> Zipper a -> Maybe a
getIZ :: forall a. Int -> Zipper a -> Maybe a
getIZ Int
i = forall a. Int -> [a] -> Maybe a
getI Int
i forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Maybe (Stack a) -> [a]
W.integrate'

-- ** Sorting

-- | Sort a stack of elements supporting 'Ord'
sortZ :: Ord a => Zipper a -> Zipper a
sortZ :: forall a. Ord a => Zipper a -> Zipper a
sortZ = forall a. (a -> a -> Ordering) -> Zipper a -> Zipper a
sortByZ forall a. Ord a => a -> a -> Ordering
compare

-- | Sort a stack with an arbitrary sorting function
sortByZ :: (a -> a -> Ordering) -> Zipper a -> Zipper a
sortByZ :: forall a. (a -> a -> Ordering) -> Zipper a -> Zipper a
sortByZ a -> a -> Ordering
f = forall a. [Either a a] -> Zipper a
fromTags forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (forall {t} {t} {t}. (t -> t -> t) -> Either t t -> Either t t -> t
adapt a -> a -> Ordering
f) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Zipper a -> [Either a a]
toTags
    where adapt :: (t -> t -> t) -> Either t t -> Either t t -> t
adapt t -> t -> t
g Either t t
e1 Either t t
e2 = t -> t -> t
g (forall a. Either a a -> a
fromE Either t t
e1) (forall a. Either a a -> a
fromE Either t t
e2)

-- ** Maps

-- | Map a function over a stack. The boolean argument indcates whether
-- the current element is the focused one
mapZ :: (Bool -> a -> b) -> Zipper a -> Zipper b
mapZ :: forall a b. (Bool -> a -> b) -> Zipper a -> Zipper b
mapZ Bool -> a -> b
f = forall a. [Either a a] -> Zipper a
fromTags forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (forall a b. (Bool -> a -> b) -> Either a a -> Either b b
mapE Bool -> a -> b
f) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Zipper a -> [Either a a]
toTags

-- | 'mapZ' without the 'Bool' argument
mapZ_ :: (a -> b) -> Zipper a -> Zipper b
mapZ_ :: forall a b. (a -> b) -> Zipper a -> Zipper b
mapZ_ = forall a b. (Bool -> a -> b) -> Zipper a -> Zipper b
mapZ forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const

-- | Monadic version of 'mapZ'
mapZM :: Monad m => (Bool -> a -> m b) -> Zipper a -> m (Zipper b)
mapZM :: forall (m :: * -> *) a b.
Monad m =>
(Bool -> a -> m b) -> Zipper a -> m (Zipper b)
mapZM Bool -> a -> m b
f Zipper a
as = forall a. [Either a a] -> Zipper a
fromTags forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (m :: * -> *) a b.
Monad m =>
(Bool -> a -> m b) -> Either a a -> m (Either b b)
mapEM Bool -> a -> m b
f) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Zipper a -> [Either a a]
toTags) Zipper a
as


-- | Monadic version of 'mapZ_'
mapZM_ :: Monad m => (a -> m b) -> Zipper a -> m (Zipper b)
mapZM_ :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Zipper a -> m (Zipper b)
mapZM_ = forall (m :: * -> *) a b.
Monad m =>
(Bool -> a -> m b) -> Zipper a -> m (Zipper b)
mapZM forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const

-- | Apply a function to the focused element
onFocusedZ :: (a -> a) -> Zipper a -> Zipper a
onFocusedZ :: forall a. (a -> a) -> Zipper a -> Zipper a
onFocusedZ a -> a
f = forall a b. (Bool -> a -> b) -> Zipper a -> Zipper b
mapZ forall a b. (a -> b) -> a -> b
$ \Bool
b a
a -> if Bool
b then a -> a
f a
a else a
a

-- | Monadic version of 'onFocusedZ'
onFocusedZM :: Monad m => (a -> m a) -> Zipper a -> m (Zipper a)
onFocusedZM :: forall (m :: * -> *) a.
Monad m =>
(a -> m a) -> Zipper a -> m (Zipper a)
onFocusedZM a -> m a
f = forall (m :: * -> *) a b.
Monad m =>
(Bool -> a -> m b) -> Zipper a -> m (Zipper b)
mapZM forall a b. (a -> b) -> a -> b
$ \Bool
b a
a -> if Bool
b then a -> m a
f a
a else forall (m :: * -> *) a. Monad m => a -> m a
return a
a

-- | Apply a function to the element at the given index
onIndexZ :: Int -> (a -> a) -> Zipper a -> Zipper a
onIndexZ :: forall a. Int -> (a -> a) -> Zipper a -> Zipper a
onIndexZ Int
i a -> a
_ Zipper a
as | Int
i forall a. Ord a => a -> a -> Bool
< Int
0 = Zipper a
as
onIndexZ Int
i a -> a
f Zipper a
as = case forall a. Int -> [a] -> ([a], [a])
splitAt Int
i forall a b. (a -> b) -> a -> b
$ forall a. Zipper a -> [Either a a]
toTags Zipper a
as of
                    ([Either a a]
before, []) -> forall a. [Either a a] -> Zipper a
fromTags [Either a a]
before
                    ([Either a a]
before, Either a a
a:[Either a a]
after) -> forall a. [Either a a] -> Zipper a
fromTags forall a b. (a -> b) -> a -> b
$ [Either a a]
before forall a. [a] -> [a] -> [a]
++ forall a b. (Bool -> a -> b) -> Either a a -> Either b b
mapE (forall a b. a -> b -> a
const a -> a
f) Either a a
a forall a. a -> [a] -> [a]
: [Either a a]
after

-- | Monadic version of 'onIndexZ'
onIndexZM :: Monad m => Int -> (a -> m a) -> Zipper a -> m (Zipper a)
onIndexZM :: forall (m :: * -> *) a.
Monad m =>
Int -> (a -> m a) -> Zipper a -> m (Zipper a)
onIndexZM Int
i a -> m a
f Zipper a
as = case forall a. Int -> [a] -> ([a], [a])
splitAt Int
i forall a b. (a -> b) -> a -> b
$ forall a. Zipper a -> [Either a a]
toTags Zipper a
as of
                     ([Either a a]
before, []) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. [Either a a] -> Zipper a
fromTags [Either a a]
before
                     ([Either a a]
before, Either a a
a:[Either a a]
after) -> do Either a a
a' <- forall (m :: * -> *) a b.
Monad m =>
(Bool -> a -> m b) -> Either a a -> m (Either b b)
mapEM (forall a b. a -> b -> a
const a -> m a
f) Either a a
a
                                             forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. [Either a a] -> Zipper a
fromTags forall a b. (a -> b) -> a -> b
$ [Either a a]
before forall a. [a] -> [a] -> [a]
++ Either a a
a' forall a. a -> [a] -> [a]
: [Either a a]
after

-- ** Filters

-- | 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.
filterZ :: (Bool -> a -> Bool) -> Zipper a -> Zipper a
filterZ :: forall a. (Bool -> a -> Bool) -> Zipper a -> Zipper a
filterZ Bool -> a -> Bool
_ Maybe (Stack a)
Nothing = forall a. Maybe a
Nothing
filterZ Bool -> a -> Bool
p (Just Stack a
s) = case ( Bool -> a -> Bool
p Bool
True (forall a. Stack a -> a
W.focus Stack a
s)
                          , forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> a -> Bool
p Bool
False) (forall a. Stack a -> [a]
W.up Stack a
s)
                          , forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> a -> Bool
p Bool
False) (forall a. Stack a -> [a]
W.down Stack a
s) ) of
                       (Bool
True, [a]
up', [a]
down') -> forall a. a -> Maybe a
Just Stack a
s { up :: [a]
W.up = [a]
up', down :: [a]
W.down = [a]
down' }
                       (Bool
False, [], []) -> forall a. Maybe a
Nothing
                       (Bool
False, a
f:[a]
up', []) -> forall a. a -> Maybe a
Just Stack a
s { focus :: a
W.focus = a
f, up :: [a]
W.up = [a]
up', down :: [a]
W.down = [] }
                       (Bool
False, [a]
up', a
f:[a]
down') ->  forall a. a -> Maybe a
Just Stack a
s { focus :: a
W.focus = a
f
                                                        , up :: [a]
W.up = [a]
up'
                                                        , down :: [a]
W.down = [a]
down' }

-- | 'filterZ' without the 'Bool' argument
filterZ_ :: (a -> Bool) -> Zipper a -> Zipper a
filterZ_ :: forall a. (a -> Bool) -> Zipper a -> Zipper a
filterZ_ = forall a. (Bool -> a -> Bool) -> Zipper a -> Zipper a
filterZ forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const

-- | Delete the focused element
deleteFocusedZ :: Zipper a -> Zipper a
deleteFocusedZ :: forall a. Zipper a -> Zipper a
deleteFocusedZ = forall a. (Bool -> a -> Bool) -> Zipper a -> Zipper a
filterZ (\Bool
b a
_ -> Bool -> Bool
not Bool
b)

-- | Delete the ith element
deleteIndexZ :: Int -> Zipper a -> Zipper a
deleteIndexZ :: forall a. Int -> Zipper a -> Zipper a
deleteIndexZ Int
i Zipper a
z = let numbered :: Zipper (Int, a)
numbered = (forall a. [Either a a] -> Zipper a
fromTags forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith forall {a} {b}. a -> Either b b -> Either (a, b) (a, b)
number [Int
0..] forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Zipper a -> [Either a a]
toTags) Zipper a
z
                       number :: a -> Either b b -> Either (a, b) (a, b)
number a
j = forall a b. (Bool -> a -> b) -> Either a a -> Either b b
mapE (\Bool
_ b
a -> (a
j,b
a))
                   in forall a b. (a -> b) -> Zipper a -> Zipper b
mapZ_ forall a b. (a, b) -> b
snd forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> Zipper a -> Zipper a
filterZ_ ((forall a. Eq a => a -> a -> Bool
/=Int
i) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) Zipper (Int, a)
numbered

-- ** Folds

-- | Analogous to 'foldr'. The 'Bool' argument to the step functions indicates
-- whether the current element is the focused one
foldrZ :: (Bool -> a -> b -> b) -> b -> Zipper a -> b
foldrZ :: forall a b. (Bool -> a -> b -> b) -> b -> Zipper a -> b
foldrZ Bool -> a -> b -> b
_ b
b Maybe (Stack a)
Nothing = b
b
foldrZ Bool -> a -> b -> b
f b
b (Just Stack a
s) = let b1 :: b
b1 = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Bool -> a -> b -> b
f Bool
False) b
b (forall a. Stack a -> [a]
W.down Stack a
s)
                          b2 :: b
b2 = Bool -> a -> b -> b
f Bool
True (forall a. Stack a -> a
W.focus Stack a
s) b
b1
                          b3 :: b
b3 = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> a -> b
$ Bool -> a -> b -> b
f Bool
False) b
b2 (forall a. Stack a -> [a]
W.up Stack a
s)
                      in b
b3

-- | Analogous to 'foldl'. The 'Bool' argument to the step functions indicates
-- whether the current element is the focused one
foldlZ :: (Bool -> b -> a -> b) -> b -> Zipper a -> b
foldlZ :: forall b a. (Bool -> b -> a -> b) -> b -> Zipper a -> b
foldlZ Bool -> b -> a -> b
_ b
b Maybe (Stack a)
Nothing = b
b
foldlZ Bool -> b -> a -> b
f b
b (Just Stack a
s) = let b1 :: b
b1 = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> a -> b
$ Bool -> b -> a -> b
f Bool
False) b
b (forall a. Stack a -> [a]
W.up Stack a
s)
                          b2 :: b
b2 = Bool -> b -> a -> b
f Bool
True b
b1 (forall a. Stack a -> a
W.focus Stack a
s)
                          b3 :: b
b3 = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (Bool -> b -> a -> b
f Bool
False) b
b2 (forall a. Stack a -> [a]
W.down Stack a
s)
                      in b
b3

-- | 'foldrZ' without the 'Bool' argument.
foldrZ_ :: (a -> b -> b) -> b -> Zipper a -> b
foldrZ_ :: forall a b. (a -> b -> b) -> b -> Zipper a -> b
foldrZ_ = forall a b. (Bool -> a -> b -> b) -> b -> Zipper a -> b
foldrZ forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const

-- | 'foldlZ' without the 'Bool' argument.
foldlZ_ :: (b -> a -> b) -> b -> Zipper a -> b
foldlZ_ :: forall b a. (b -> a -> b) -> b -> Zipper a -> b
foldlZ_ = forall b a. (Bool -> b -> a -> b) -> b -> Zipper a -> b
foldlZ forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const

-- | Find whether an element is present in a stack.
elemZ :: Eq a => a -> Zipper a -> Bool
elemZ :: forall a. Eq a => a -> Zipper a -> Bool
elemZ a
a = forall b a. (b -> a -> b) -> b -> Zipper a -> b
foldlZ_ Bool -> a -> Bool
step Bool
False
    where step :: Bool -> a -> Bool
step Bool
True a
_ = Bool
True
          step Bool
False a
a' = a
a' forall a. Eq a => a -> a -> Bool
== a
a


-- * Other utility functions

-- | Safe version of '!!'
getI :: Int -> [a] -> Maybe a
getI :: forall a. Int -> [a] -> Maybe a
getI Int
i [a]
xs = [a]
xs forall a. [a] -> Int -> Maybe a
!? Int
i
{-# DEPRECATED getI "Use XMonad.Prelude.(!?) instead." #-}

-- | Map a function across both 'Left's and 'Right's.
-- The 'Bool' argument is 'True' in a 'Right', 'False'
-- in a 'Left'.
mapE :: (Bool -> a -> b) -> Either a a -> Either b b
mapE :: forall a b. (Bool -> a -> b) -> Either a a -> Either b b
mapE Bool -> a -> b
f (Left a
a) = forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ Bool -> a -> b
f Bool
False a
a
mapE Bool -> a -> b
f (Right a
a) = forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ Bool -> a -> b
f Bool
True a
a

mapE_ :: (a -> b) -> Either a a -> Either b b
mapE_ :: forall a b. (a -> b) -> Either a a -> Either b b
mapE_ = forall a b. (Bool -> a -> b) -> Either a a -> Either b b
mapE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const

-- | Monadic version of 'mapE'
mapEM :: Monad m => (Bool -> a -> m b) -> Either a a -> m (Either b b)
mapEM :: forall (m :: * -> *) a b.
Monad m =>
(Bool -> a -> m b) -> Either a a -> m (Either b b)
mapEM Bool -> a -> m b
f (Left a
a) = forall a b. a -> Either a b
Left forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool -> a -> m b
f Bool
False a
a
mapEM Bool -> a -> m b
f (Right a
a) = forall a b. b -> Either a b
Right forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool -> a -> m b
f Bool
True a
a

mapEM_ :: Monad m => (a -> m b) -> Either a a -> m (Either b b)
mapEM_ :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Either a a -> m (Either b b)
mapEM_ = forall (m :: * -> *) a b.
Monad m =>
(Bool -> a -> m b) -> Either a a -> m (Either b b)
mapEM forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const

-- | Get the @a@ from an @Either a a@
fromE :: Either a a -> a
fromE :: forall a. Either a a -> a
fromE (Right a
a) = a
a
fromE (Left a
a) = a
a

-- | Tag the element with 'Right' if the property is true, 'Left' otherwise
tagBy :: (a -> Bool) -> a -> Either a a
tagBy :: forall a. (a -> Bool) -> a -> Either a a
tagBy a -> Bool
p a
a = if a -> Bool
p a
a then forall a b. b -> Either a b
Right a
a else forall a b. a -> Either a b
Left a
a

-- | Reverse a @Stack a@; O(1).
reverseS :: W.Stack a -> W.Stack a
reverseS :: forall a. Stack a -> Stack a
reverseS (W.Stack a
foc [a]
ups [a]
downs) = forall a. a -> [a] -> [a] -> Stack a
W.Stack a
foc [a]
downs [a]
ups

-- | Reverse a @Zipper a@; O(1).
reverseZ :: Zipper a -> Zipper a
reverseZ :: forall a. Zipper a -> Zipper a
reverseZ = (forall a. Stack a -> Stack a
reverseS forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>)