{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE TypeFamilies #-}
module Data.ListZipper(
ListZipper(..)
, ListZipperOp(..)
, ListZipperOp'
, AsListZipper(..)
, HasListZipper(..)
, HasListZipperOp(..)
, AsListZipperOp(..)
, leftz'
, rightz'
, leftzrightz
, rightzleftz
, zipper
, zipper0L
, zipper0L'
, zipper0R
, zipper0R'
, list
, zipperIndices
, moveLeft
, moveRight
, moveStart
, moveEnd
, moveLeftLoop
, moveRightLoop
, opWith
, moveLeftWith
, moveRightWith
, moveLeftRightWith
, moveRightLeftWith
, opWithThen
, moveLeftWithThen
, moveRightWithThen
, moveLeftRightWithThen
, moveRightLeftWithThen
, opUntil
, moveLeftUntil
, moveRightUntil
, moveLeftRightUntil
, moveRightLeftUntil
, opUntilThen
, moveLeftUntilThen
, moveRightUntilThen
, moveLeftRightUntilThen
, moveRightLeftUntilThen
, insertMoveLeft
, insertMoveRight
, deleteStepLeft
, deleteStepRight
, modifyFocus
, setFocus
, atStart
, atEnd
, getFocus
, getLeft
, getRight
, getRightz
, getLeftz
, getList
, liftListZipperOp
, mkListZipperOp
, (<$~)
, (*>>)
, (<<*)
, mkListZipperOp'
, (.>>)
, (<<.)
, runListZipperOp
, execListZipperOp
, execListZipperOpOr
, (##>)
, (<##)
, evalListZipperOp
, (&&>)
, (<&&)
, execOpList
, (%%>)
, (<%%)
, execOpList'
, ($$>)
, (<$$)
, opWhileJust
, shuffleLeft
, shuffleRight
, shuffleListZipper
) where
import System.Random.Shuffle
import Control.Monad.Random.Class
import Control.Applicative(Applicative(pure, (<*>)), Alternative((<|>), empty), (<*))
import Control.Category((.), id)
import Control.Comonad(Comonad(duplicate, extract))
import Control.Lens(Each(each), Reversing(reversing), Ixed(ix), Rewrapped, Wrapped(Unwrapped, _Wrapped'), IxValue, Index, Prism', Lens', Traversal', _Wrapped, (^.), iso, (&), _1, _2)
import Control.Monad
import Control.Monad.Error.Class(MonadError(throwError, catchError))
import Control.Monad.Fail(MonadFail(fail))
import Control.Monad.Fix(MonadFix(mfix))
import Control.Monad.Reader(MonadReader(ask, local, reader))
import Control.Monad.State(MonadState(get, put, state))
import qualified Control.Monad.Fail as Fail(fail)
import Data.Foldable
import Data.Traversable(Traversable(traverse))
import Data.Semigroup.Traversable(Traversable1(traverse1))
import Control.Monad(Monad((>>=), return), MonadPlus(mplus, mzero), (=<<))
import Data.Bool(Bool)
import Data.Eq(Eq((==)))
import Data.Eq.Deriving(deriveEq1)
import Data.Foldable(Foldable(toList, foldMap))
import Data.Function(flip)
import Data.Functor(Functor(fmap), (<$>), (<$))
import Data.Functor.Alt(Alt((<!>)))
import Data.Functor.Apply(Apply((<.>)))
import Data.Functor.Bind(Bind((>>-)))
import Data.Functor.Extend(Extend(duplicated))
import Data.Int(Int)
import Data.List(unfoldr, zipWith, repeat, reverse, null, zip)
import Data.List.NonEmpty(NonEmpty((:|)))
import Data.Maybe(Maybe(Nothing, Just), fromMaybe)
import Data.Monoid(Monoid(mappend, mempty))
import Data.Ord(Ord((<)))
import Data.Semigroup(Semigroup((<>)))
import Data.Semigroup.Foldable(Foldable1(foldMap1))
import Prelude(Show, (+), (-))
import Text.Show.Deriving(deriveShow1)
data ListZipper a =
ListZipper
[a]
a
[a]
deriving (ListZipper a -> ListZipper a -> Bool
(ListZipper a -> ListZipper a -> Bool)
-> (ListZipper a -> ListZipper a -> Bool) -> Eq (ListZipper a)
forall a. Eq a => ListZipper a -> ListZipper a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListZipper a -> ListZipper a -> Bool
$c/= :: forall a. Eq a => ListZipper a -> ListZipper a -> Bool
== :: ListZipper a -> ListZipper a -> Bool
$c== :: forall a. Eq a => ListZipper a -> ListZipper a -> Bool
Eq, Eq (ListZipper a)
Eq (ListZipper a)
-> (ListZipper a -> ListZipper a -> Ordering)
-> (ListZipper a -> ListZipper a -> Bool)
-> (ListZipper a -> ListZipper a -> Bool)
-> (ListZipper a -> ListZipper a -> Bool)
-> (ListZipper a -> ListZipper a -> Bool)
-> (ListZipper a -> ListZipper a -> ListZipper a)
-> (ListZipper a -> ListZipper a -> ListZipper a)
-> Ord (ListZipper a)
ListZipper a -> ListZipper a -> Bool
ListZipper a -> ListZipper a -> Ordering
ListZipper a -> ListZipper a -> ListZipper a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (ListZipper a)
forall a. Ord a => ListZipper a -> ListZipper a -> Bool
forall a. Ord a => ListZipper a -> ListZipper a -> Ordering
forall a. Ord a => ListZipper a -> ListZipper a -> ListZipper a
min :: ListZipper a -> ListZipper a -> ListZipper a
$cmin :: forall a. Ord a => ListZipper a -> ListZipper a -> ListZipper a
max :: ListZipper a -> ListZipper a -> ListZipper a
$cmax :: forall a. Ord a => ListZipper a -> ListZipper a -> ListZipper a
>= :: ListZipper a -> ListZipper a -> Bool
$c>= :: forall a. Ord a => ListZipper a -> ListZipper a -> Bool
> :: ListZipper a -> ListZipper a -> Bool
$c> :: forall a. Ord a => ListZipper a -> ListZipper a -> Bool
<= :: ListZipper a -> ListZipper a -> Bool
$c<= :: forall a. Ord a => ListZipper a -> ListZipper a -> Bool
< :: ListZipper a -> ListZipper a -> Bool
$c< :: forall a. Ord a => ListZipper a -> ListZipper a -> Bool
compare :: ListZipper a -> ListZipper a -> Ordering
$ccompare :: forall a. Ord a => ListZipper a -> ListZipper a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (ListZipper a)
Ord, Int -> ListZipper a -> ShowS
[ListZipper a] -> ShowS
ListZipper a -> String
(Int -> ListZipper a -> ShowS)
-> (ListZipper a -> String)
-> ([ListZipper a] -> ShowS)
-> Show (ListZipper a)
forall a. Show a => Int -> ListZipper a -> ShowS
forall a. Show a => [ListZipper a] -> ShowS
forall a. Show a => ListZipper a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListZipper a] -> ShowS
$cshowList :: forall a. Show a => [ListZipper a] -> ShowS
show :: ListZipper a -> String
$cshow :: forall a. Show a => ListZipper a -> String
showsPrec :: Int -> ListZipper a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> ListZipper a -> ShowS
Show)
instance Functor ListZipper where
fmap :: (a -> b) -> ListZipper a -> ListZipper b
fmap a -> b
f (ListZipper [a]
l a
x [a]
r) =
[b] -> b -> [b] -> ListZipper b
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper ((a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f [a]
l) (a -> b
f a
x) ((a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f [a]
r)
instance Apply ListZipper where
ListZipper [a -> b]
l1 a -> b
x1 [a -> b]
r1 <.> :: ListZipper (a -> b) -> ListZipper a -> ListZipper b
<.> ListZipper [a]
l2 a
x2 [a]
r2 =
[b] -> b -> [b] -> ListZipper b
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper (((a -> b) -> a -> b) -> [a -> b] -> [a] -> [b]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (a -> b) -> a -> b
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id [a -> b]
l1 [a]
l2) (a -> b
x1 a
x2) (((a -> b) -> a -> b) -> [a -> b] -> [a] -> [b]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (a -> b) -> a -> b
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id [a -> b]
r1 [a]
r2)
instance Applicative ListZipper where
pure :: a -> ListZipper a
pure a
a =
[a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper (a -> [a]
forall a. a -> [a]
repeat a
a) a
a (a -> [a]
forall a. a -> [a]
repeat a
a)
<*> :: ListZipper (a -> b) -> ListZipper a -> ListZipper b
(<*>) =
ListZipper (a -> b) -> ListZipper a -> ListZipper b
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
(<.>)
instance Foldable ListZipper where
foldMap :: (a -> m) -> ListZipper a -> m
foldMap a -> m
f (ListZipper [a]
l a
x [a]
r) =
(a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f [a]
l m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` a -> m
f a
x m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f [a]
r
instance Foldable1 ListZipper where
foldMap1 :: (a -> m) -> ListZipper a -> m
foldMap1 a -> m
f (ListZipper [] a
x []) =
a -> m
f a
x
foldMap1 a -> m
f (ListZipper [] a
x (a
rh:[a]
rt)) =
a -> m
f a
x m -> m -> m
forall a. Semigroup a => a -> a -> a
<> (a -> m) -> NonEmpty a -> m
forall (t :: * -> *) m a.
(Foldable1 t, Semigroup m) =>
(a -> m) -> t a -> m
foldMap1 a -> m
f (a
rh a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
rt)
foldMap1 a -> m
f (ListZipper (a
lh:[a]
lt) a
x []) =
(a -> m) -> NonEmpty a -> m
forall (t :: * -> *) m a.
(Foldable1 t, Semigroup m) =>
(a -> m) -> t a -> m
foldMap1 a -> m
f (a
lh a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
lt) m -> m -> m
forall a. Semigroup a => a -> a -> a
<> a -> m
f a
x
foldMap1 a -> m
f (ListZipper (a
lh:[a]
lt) a
x (a
rh:[a]
rt)) =
(a -> m) -> NonEmpty a -> m
forall (t :: * -> *) m a.
(Foldable1 t, Semigroup m) =>
(a -> m) -> t a -> m
foldMap1 a -> m
f (a
lh a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
lt) m -> m -> m
forall a. Semigroup a => a -> a -> a
<> a -> m
f a
x m -> m -> m
forall a. Semigroup a => a -> a -> a
<> (a -> m) -> NonEmpty a -> m
forall (t :: * -> *) m a.
(Foldable1 t, Semigroup m) =>
(a -> m) -> t a -> m
foldMap1 a -> m
f (a
rh a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
rt)
instance Traversable ListZipper where
traverse :: (a -> f b) -> ListZipper a -> f (ListZipper b)
traverse a -> f b
f (ListZipper [a]
l a
x [a]
r) =
[b] -> b -> [b] -> ListZipper b
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper ([b] -> b -> [b] -> ListZipper b)
-> f [b] -> f (b -> [b] -> ListZipper b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f b) -> [a] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f b
f [a]
l f (b -> [b] -> ListZipper b) -> f b -> f ([b] -> ListZipper b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
x f ([b] -> ListZipper b) -> f [b] -> f (ListZipper b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (a -> f b) -> [a] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f b
f [a]
r
instance Traversable1 ListZipper where
traverse1 :: (a -> f b) -> ListZipper a -> f (ListZipper b)
traverse1 a -> f b
f (ListZipper [] a
x []) =
(\b
x' -> [b] -> b -> [b] -> ListZipper b
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper [] b
x' []) (b -> ListZipper b) -> f b -> f (ListZipper b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
x
traverse1 a -> f b
f (ListZipper (a
lh:[a]
lt) a
x []) =
(\NonEmpty b
l' b
x' -> [b] -> b -> [b] -> ListZipper b
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper (NonEmpty b -> [b]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty b
l') b
x' []) (NonEmpty b -> b -> ListZipper b)
-> f (NonEmpty b) -> f (b -> ListZipper b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f b) -> NonEmpty a -> f (NonEmpty b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable1 t, Apply f) =>
(a -> f b) -> t a -> f (t b)
traverse1 a -> f b
f (a
lh a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
lt) f (b -> ListZipper b) -> f b -> f (ListZipper b)
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> a -> f b
f a
x
traverse1 a -> f b
f (ListZipper [] a
x (a
rh:[a]
rt)) =
(\b
x' NonEmpty b
r' -> [b] -> b -> [b] -> ListZipper b
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper [] b
x' (NonEmpty b -> [b]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty b
r')) (b -> NonEmpty b -> ListZipper b)
-> f b -> f (NonEmpty b -> ListZipper b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
x f (NonEmpty b -> ListZipper b)
-> f (NonEmpty b) -> f (ListZipper b)
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> (a -> f b) -> NonEmpty a -> f (NonEmpty b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable1 t, Apply f) =>
(a -> f b) -> t a -> f (t b)
traverse1 a -> f b
f (a
rh a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
rt)
traverse1 a -> f b
f (ListZipper (a
lh:[a]
lt) a
x (a
rh:[a]
rt)) =
(\NonEmpty b
l' b
x' NonEmpty b
r' -> [b] -> b -> [b] -> ListZipper b
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper (NonEmpty b -> [b]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty b
l') b
x' (NonEmpty b -> [b]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty b
r')) (NonEmpty b -> b -> NonEmpty b -> ListZipper b)
-> f (NonEmpty b) -> f (b -> NonEmpty b -> ListZipper b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f b) -> NonEmpty a -> f (NonEmpty b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable1 t, Apply f) =>
(a -> f b) -> t a -> f (t b)
traverse1 a -> f b
f (a
lh a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
lt) f (b -> NonEmpty b -> ListZipper b)
-> f b -> f (NonEmpty b -> ListZipper b)
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> a -> f b
f a
x f (NonEmpty b -> ListZipper b)
-> f (NonEmpty b) -> f (ListZipper b)
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> (a -> f b) -> NonEmpty a -> f (NonEmpty b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable1 t, Apply f) =>
(a -> f b) -> t a -> f (t b)
traverse1 a -> f b
f (a
rh a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
rt)
instance Semigroup a => Semigroup (ListZipper a) where
ListZipper [a]
l1 a
x1 [a]
r1 <> :: ListZipper a -> ListZipper a -> ListZipper a
<> ListZipper [a]
l2 a
x2 [a]
r2 =
[a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper ((a -> a -> a) -> [a] -> [a] -> [a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith a -> a -> a
forall a. Semigroup a => a -> a -> a
(<>) [a]
l1 [a]
l2) (a
x1 a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
x2) ((a -> a -> a) -> [a] -> [a] -> [a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith a -> a -> a
forall a. Semigroup a => a -> a -> a
(<>) [a]
r1 [a]
r2)
instance Each (ListZipper a) (ListZipper a) a a where
each :: (a -> f a) -> ListZipper a -> f (ListZipper a)
each =
(a -> f a) -> ListZipper a -> f (ListZipper a)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse
instance Reversing (ListZipper a) where
reversing :: ListZipper a -> ListZipper a
reversing (ListZipper [a]
l a
x [a]
r) =
[a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper [a]
r a
x [a]
l
type instance IxValue (ListZipper a) = a
type instance Index (ListZipper a) = Int
instance Ixed (ListZipper a) where
ix :: Index (ListZipper a)
-> Traversal' (ListZipper a) (IxValue (ListZipper a))
ix Index (ListZipper a)
i IxValue (ListZipper a) -> f (IxValue (ListZipper a))
f ListZipper a
z =
if Int
Index (ListZipper a)
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0
then
ListZipper a -> f (ListZipper a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ListZipper a
z
else
let ListZipper [(Int, a)]
l (Int, a)
x [(Int, a)]
r =
ListZipper a -> ListZipper (Int, a)
forall a. ListZipper a -> ListZipper (Int, a)
zipperIndices ListZipper a
z
applyn :: (Int, a) -> f a
applyn (Int
n, a
a) =
if Int
Index (ListZipper a)
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
n
then
IxValue (ListZipper a) -> f (IxValue (ListZipper a))
f a
IxValue (ListZipper a)
a
else
a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a
in [a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper ([a] -> a -> [a] -> ListZipper a)
-> f [a] -> f (a -> [a] -> ListZipper a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Int, a) -> f a) -> [(Int, a)] -> f [a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (Int, a) -> f a
applyn [(Int, a)]
l f (a -> [a] -> ListZipper a) -> f a -> f ([a] -> ListZipper a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Int, a) -> f a
applyn (Int, a)
x f ([a] -> ListZipper a) -> f [a] -> f (ListZipper a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Int, a) -> f a) -> [(Int, a)] -> f [a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (Int, a) -> f a
applyn [(Int, a)]
r
instance Extend ListZipper where
duplicated :: ListZipper a -> ListZipper (ListZipper a)
duplicated ListZipper a
z =
let dup :: b -> (b, b)
dup b
x =
(b
x, b
x)
unf :: ListZipperOp a () -> [ListZipper a]
unf ListZipperOp a ()
m =
(ListZipper a -> Maybe (ListZipper a, ListZipper a))
-> ListZipper a -> [ListZipper a]
forall b a. (b -> Maybe (a, b)) -> b -> [a]
unfoldr ((ListZipper a -> (ListZipper a, ListZipper a))
-> Maybe (ListZipper a) -> Maybe (ListZipper a, ListZipper a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ListZipper a -> (ListZipper a, ListZipper a)
forall b. b -> (b, b)
dup (Maybe (ListZipper a) -> Maybe (ListZipper a, ListZipper a))
-> (ListZipper a -> Maybe (ListZipper a))
-> ListZipper a
-> Maybe (ListZipper a, ListZipper a)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ListZipperOp a () -> ListZipper a -> Maybe (ListZipper a)
forall a x.
ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a)
execListZipperOp ListZipperOp a ()
m)) ListZipper a
z
in [ListZipper a]
-> ListZipper a -> [ListZipper a] -> ListZipper (ListZipper a)
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper (ListZipperOp a () -> [ListZipper a]
unf ListZipperOp a ()
forall a. ListZipperOp' a
moveLeft) ListZipper a
z (ListZipperOp a () -> [ListZipper a]
unf ListZipperOp a ()
forall a. ListZipperOp' a
moveRight)
instance Comonad ListZipper where
duplicate :: ListZipper a -> ListZipper (ListZipper a)
duplicate =
ListZipper a -> ListZipper (ListZipper a)
forall (w :: * -> *) a. Extend w => w a -> w (w a)
duplicated
extract :: ListZipper a -> a
extract (ListZipper [a]
_ a
x [a]
_) =
a
x
class AsListZipper z a | z -> a where
_ListZipper ::
Prism' z (ListZipper a)
instance AsListZipper (ListZipper a) a where
_ListZipper :: p (ListZipper a) (f (ListZipper a))
-> p (ListZipper a) (f (ListZipper a))
_ListZipper =
p (ListZipper a) (f (ListZipper a))
-> p (ListZipper a) (f (ListZipper a))
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
class HasListZipper z a | z -> a where
listZipper ::
Lens' z (ListZipper a)
focus ::
Lens' z a
{-# INLINE focus #-}
leftz ::
Lens' z [a]
{-# INLINE leftz #-}
rightz ::
Lens' z [a]
{-# INLINE rightz #-}
leftz =
(ListZipper a -> f (ListZipper a)) -> z -> f z
forall z a. HasListZipper z a => Lens' z (ListZipper a)
listZipper ((ListZipper a -> f (ListZipper a)) -> z -> f z)
-> (([a] -> f [a]) -> ListZipper a -> f (ListZipper a))
-> ([a] -> f [a])
-> z
-> f z
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ([a] -> f [a]) -> ListZipper a -> f (ListZipper a)
forall z a. HasListZipper z a => Lens' z [a]
leftz
focus =
(ListZipper a -> f (ListZipper a)) -> z -> f z
forall z a. HasListZipper z a => Lens' z (ListZipper a)
listZipper ((ListZipper a -> f (ListZipper a)) -> z -> f z)
-> ((a -> f a) -> ListZipper a -> f (ListZipper a))
-> (a -> f a)
-> z
-> f z
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (a -> f a) -> ListZipper a -> f (ListZipper a)
forall z a. HasListZipper z a => Lens' z a
focus
rightz =
(ListZipper a -> f (ListZipper a)) -> z -> f z
forall z a. HasListZipper z a => Lens' z (ListZipper a)
listZipper ((ListZipper a -> f (ListZipper a)) -> z -> f z)
-> (([a] -> f [a]) -> ListZipper a -> f (ListZipper a))
-> ([a] -> f [a])
-> z
-> f z
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ([a] -> f [a]) -> ListZipper a -> f (ListZipper a)
forall z a. HasListZipper z a => Lens' z [a]
rightz
instance HasListZipper (ListZipper a) a where
{-# INLINE focus #-}
{-# INLINE leftz #-}
{-# INLINE rightz #-}
listZipper :: (ListZipper a -> f (ListZipper a))
-> ListZipper a -> f (ListZipper a)
listZipper =
(ListZipper a -> f (ListZipper a))
-> ListZipper a -> f (ListZipper a)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
leftz :: ([a] -> f [a]) -> ListZipper a -> f (ListZipper a)
leftz [a] -> f [a]
f (ListZipper [a]
l a
x [a]
r) =
([a] -> ListZipper a) -> f [a] -> f (ListZipper a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[a]
l' -> [a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper [a]
l' a
x [a]
r) ([a] -> f [a]
f [a]
l)
focus :: (a -> f a) -> ListZipper a -> f (ListZipper a)
focus a -> f a
f (ListZipper [a]
l a
x [a]
r) =
(a -> ListZipper a) -> f a -> f (ListZipper a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\a
x' -> [a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper [a]
l a
x' [a]
r) (a -> f a
f a
x)
rightz :: ([a] -> f [a]) -> ListZipper a -> f (ListZipper a)
rightz [a] -> f [a]
f (ListZipper [a]
l a
x [a]
r) =
([a] -> ListZipper a) -> f [a] -> f (ListZipper a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[a]
r' -> [a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper [a]
l a
x [a]
r') ([a] -> f [a]
f [a]
r)
leftz' ::
HasListZipper z a =>
Traversal' z a
leftz' :: Traversal' z a
leftz' =
([a] -> f [a]) -> z -> f z
forall z a. HasListZipper z a => Lens' z [a]
leftz (([a] -> f [a]) -> z -> f z)
-> ((a -> f a) -> [a] -> f [a]) -> (a -> f a) -> z -> f z
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (a -> f a) -> [a] -> f [a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse
rightz' ::
HasListZipper z a =>
Traversal' z a
rightz' :: Traversal' z a
rightz' =
([a] -> f [a]) -> z -> f z
forall z a. HasListZipper z a => Lens' z [a]
rightz (([a] -> f [a]) -> z -> f z)
-> ((a -> f a) -> [a] -> f [a]) -> (a -> f a) -> z -> f z
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (a -> f a) -> [a] -> f [a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse
leftzrightz ::
Traversal' (ListZipper a) a
leftzrightz :: (a -> f a) -> ListZipper a -> f (ListZipper a)
leftzrightz a -> f a
f (ListZipper [a]
l a
x [a]
r) =
(\[a]
l' [a]
r' -> [a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper [a]
l' a
x [a]
r') ([a] -> [a] -> ListZipper a) -> f [a] -> f ([a] -> ListZipper a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f a) -> [a] -> f [a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f a
f [a]
l f ([a] -> ListZipper a) -> f [a] -> f (ListZipper a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (a -> f a) -> [a] -> f [a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f a
f [a]
r
rightzleftz ::
Traversal' (ListZipper a) a
rightzleftz :: (a -> f a) -> ListZipper a -> f (ListZipper a)
rightzleftz a -> f a
f (ListZipper [a]
l a
x [a]
r) =
(\[a]
r' [a]
l' -> [a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper [a]
l' a
x [a]
r') ([a] -> [a] -> ListZipper a) -> f [a] -> f ([a] -> ListZipper a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f a) -> [a] -> f [a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f a
f [a]
r f ([a] -> ListZipper a) -> f [a] -> f (ListZipper a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (a -> f a) -> [a] -> f [a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f a
f [a]
l
zipper ::
[a]
-> Maybe (ListZipper a)
zipper :: [a] -> Maybe (ListZipper a)
zipper [] =
Maybe (ListZipper a)
forall a. Maybe a
Nothing
zipper (a
h:[a]
t) =
ListZipper a -> Maybe (ListZipper a)
forall a. a -> Maybe a
Just ([a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper [] a
h [a]
t)
zipper0L ::
a
-> [a]
-> ListZipper a
zipper0L :: a -> [a] -> ListZipper a
zipper0L =
[a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper []
zipper0L' ::
NonEmpty a
-> ListZipper a
zipper0L' :: NonEmpty a -> ListZipper a
zipper0L' (a
h :| [a]
t) =
a -> [a] -> ListZipper a
forall a. a -> [a] -> ListZipper a
zipper0L a
h [a]
t
zipper0R ::
[a]
-> a
-> ListZipper a
zipper0R :: [a] -> a -> ListZipper a
zipper0R [a]
l a
x =
[a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper [a]
l a
x []
zipper0R' ::
NonEmpty a
-> ListZipper a
zipper0R' :: NonEmpty a -> ListZipper a
zipper0R' (a
h :| []) =
[a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper [] a
h []
zipper0R' (a
h :| a
i : [a]
t) =
let ListZipper [a]
l a
x [a]
r = NonEmpty a -> ListZipper a
forall a. NonEmpty a -> ListZipper a
zipper0R' (a
i a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
t)
in [a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper (a
ha -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
l) a
x [a]
r
list ::
ListZipper a
-> [a]
list :: ListZipper a -> [a]
list (ListZipper [a]
l a
x [a]
r) =
[a] -> [a]
forall a. [a] -> [a]
reverse [a]
l [a] -> [a] -> [a]
forall a. Semigroup a => a -> a -> a
<> (a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
r)
zipperIndices ::
ListZipper a
-> ListZipper (Int, a)
zipperIndices :: ListZipper a -> ListZipper (Int, a)
zipperIndices (ListZipper [a]
l a
x [a]
r) =
let zipl ::
[a]
-> [b]
-> ([a], [(a, b)])
zipl :: [a] -> [b] -> ([a], [(a, b)])
zipl [a]
y [] =
([a]
y, [])
zipl [] (b
_:[b]
_) =
([], [])
zipl (a
a:[a]
b) (b
c:[b]
d) =
([(a, b)] -> [(a, b)]) -> ([a], [(a, b)]) -> ([a], [(a, b)])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a
a, b
c) (a, b) -> [(a, b)] -> [(a, b)]
forall a. a -> [a] -> [a]
:) ([a] -> [b] -> ([a], [(a, b)])
forall a b. [a] -> [b] -> ([a], [(a, b)])
zipl [a]
b [b]
d)
rl :: [a]
rl =
[a] -> [a]
forall a. [a] -> [a]
reverse [a]
l
([Int]
z, [(Int, a)]
l') =
[Int] -> [a] -> ([Int], [(Int, a)])
forall a b. [a] -> [b] -> ([a], [(a, b)])
zipl [Int
0..] [a]
rl
ln :: Int
ln =
case [Int]
z of
Int
n:[Int]
_ ->
Int
n
[] ->
Int
0
in [(Int, a)] -> (Int, a) -> [(Int, a)] -> ListZipper (Int, a)
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper
([(Int, a)] -> [(Int, a)]
forall a. [a] -> [a]
reverse [(Int, a)]
l')
(Int
ln, a
x)
([Int] -> [a] -> [(Int, a)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
ln Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1..] [a]
r)
moveStart ::
ListZipper a
-> ListZipper a
moveStart :: ListZipper a -> ListZipper a
moveStart =
ListZipperOp' a -> ListZipper a -> ListZipper a
forall a. ListZipperOp' a -> ListZipper a -> ListZipper a
opWhileJust ListZipperOp' a
forall a. ListZipperOp' a
moveLeft
moveEnd ::
ListZipper a
-> ListZipper a
moveEnd :: ListZipper a -> ListZipper a
moveEnd ListZipper a
z =
ListZipperOp' a -> ListZipper a -> ListZipper a
forall a. ListZipperOp' a -> ListZipper a -> ListZipper a
opWhileJust ListZipperOp' a
forall a. ListZipperOp' a
moveRight ListZipper a
z
atStart ::
HasListZipper z a =>
z
-> Bool
atStart :: z -> Bool
atStart z
z =
[a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (z
z z -> Getting [a] z [a] -> [a]
forall s a. s -> Getting a s a -> a
^. Getting [a] z [a]
forall z a. HasListZipper z a => Lens' z [a]
leftz)
atEnd ::
HasListZipper z a =>
z
-> Bool
atEnd :: z -> Bool
atEnd z
z =
[a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (z
z z -> Getting [a] z [a] -> [a]
forall s a. s -> Getting a s a -> a
^. Getting [a] z [a]
forall z a. HasListZipper z a => Lens' z [a]
rightz)
moveLeftLoop ::
ListZipper a
-> ListZipper a
moveLeftLoop :: ListZipper a -> ListZipper a
moveLeftLoop ListZipper a
z =
ListZipper a -> Maybe (ListZipper a) -> ListZipper a
forall a. a -> Maybe a -> a
fromMaybe (ListZipper a -> ListZipper a
forall a. ListZipper a -> ListZipper a
moveEnd ListZipper a
z) (ListZipperOp a () -> ListZipper a -> Maybe (ListZipper a)
forall a x.
ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a)
execListZipperOp ListZipperOp a ()
forall a. ListZipperOp' a
moveLeft ListZipper a
z)
moveRightLoop ::
ListZipper a
-> ListZipper a
moveRightLoop :: ListZipper a -> ListZipper a
moveRightLoop ListZipper a
z =
ListZipper a -> Maybe (ListZipper a) -> ListZipper a
forall a. a -> Maybe a -> a
fromMaybe (ListZipper a -> ListZipper a
forall a. ListZipper a -> ListZipper a
moveStart ListZipper a
z) (ListZipperOp a () -> ListZipper a -> Maybe (ListZipper a)
forall a x.
ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a)
execListZipperOp ListZipperOp a ()
forall a. ListZipperOp' a
moveRight ListZipper a
z)
insertMoveLeft ::
a
-> ListZipper a
-> ListZipper a
insertMoveLeft :: a -> ListZipper a -> ListZipper a
insertMoveLeft a
a (ListZipper [a]
l a
x [a]
r) =
[a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
l) a
a [a]
r
insertMoveRight ::
a
-> ListZipper a
-> ListZipper a
insertMoveRight :: a -> ListZipper a -> ListZipper a
insertMoveRight a
a (ListZipper [a]
l a
x [a]
r) =
[a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper [a]
l a
a (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
r)
newtype ListZipperOp a b =
ListZipperOp (ListZipper a -> Maybe (ListZipper a, b))
type ListZipperOp' a =
ListZipperOp a ()
instance ListZipperOp a x ~ t =>
Rewrapped (ListZipperOp b' a') t
instance Wrapped (ListZipperOp a' x') where
type Unwrapped (ListZipperOp a' x') =
ListZipper a'
-> Maybe (ListZipper a', x')
_Wrapped' :: p (Unwrapped (ListZipperOp a' x'))
(f (Unwrapped (ListZipperOp a' x')))
-> p (ListZipperOp a' x') (f (ListZipperOp a' x'))
_Wrapped' =
(ListZipperOp a' x' -> ListZipper a' -> Maybe (ListZipper a', x'))
-> ((ListZipper a' -> Maybe (ListZipper a', x'))
-> ListZipperOp a' x')
-> Iso
(ListZipperOp a' x')
(ListZipperOp a' x')
(ListZipper a' -> Maybe (ListZipper a', x'))
(ListZipper a' -> Maybe (ListZipper a', x'))
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\(ListZipperOp ListZipper a' -> Maybe (ListZipper a', x')
k) -> ListZipper a' -> Maybe (ListZipper a', x')
k) (ListZipper a' -> Maybe (ListZipper a', x')) -> ListZipperOp a' x'
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp
class HasListZipperOp lo x y | lo -> x y where
lo ::
Lens' lo (ListZipperOp x y)
instance HasListZipperOp (ListZipperOp x y) x y where
lo :: (ListZipperOp x y -> f (ListZipperOp x y))
-> ListZipperOp x y -> f (ListZipperOp x y)
lo =
(ListZipperOp x y -> f (ListZipperOp x y))
-> ListZipperOp x y -> f (ListZipperOp x y)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
class AsListZipperOp t x y | t -> x y where
_ListZipperOp :: Prism' t (ListZipperOp x y)
instance AsListZipperOp (ListZipperOp x y) x y where
_ListZipperOp :: p (ListZipperOp x y) (f (ListZipperOp x y))
-> p (ListZipperOp x y) (f (ListZipperOp x y))
_ListZipperOp =
p (ListZipperOp x y) (f (ListZipperOp x y))
-> p (ListZipperOp x y) (f (ListZipperOp x y))
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance Functor (ListZipperOp a) where
fmap :: (a -> b) -> ListZipperOp a a -> ListZipperOp a b
fmap a -> b
f (ListZipperOp ListZipper a -> Maybe (ListZipper a, a)
k) =
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (((ListZipper a, a) -> (ListZipper a, b))
-> Maybe (ListZipper a, a) -> Maybe (ListZipper a, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> (ListZipper a, a) -> (ListZipper a, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) (Maybe (ListZipper a, a) -> Maybe (ListZipper a, b))
-> (ListZipper a -> Maybe (ListZipper a, a))
-> ListZipper a
-> Maybe (ListZipper a, b)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ListZipper a -> Maybe (ListZipper a, a)
k)
instance Apply (ListZipperOp a) where
ListZipperOp ListZipper a -> Maybe (ListZipper a, a -> b)
j <.> :: ListZipperOp a (a -> b) -> ListZipperOp a a -> ListZipperOp a b
<.> ListZipperOp ListZipper a -> Maybe (ListZipper a, a)
k =
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
z ->
ListZipper a -> Maybe (ListZipper a, a -> b)
j ListZipper a
z Maybe (ListZipper a, a -> b)
-> ((ListZipper a, a -> b) -> Maybe (ListZipper a, b))
-> Maybe (ListZipper a, b)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \(ListZipper a
z', a -> b
f) ->
ListZipper a -> Maybe (ListZipper a, a)
k ListZipper a
z' Maybe (ListZipper a, a)
-> ((ListZipper a, a) -> Maybe (ListZipper a, b))
-> Maybe (ListZipper a, b)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \(ListZipper a
z'', a
a) ->
(ListZipper a, b) -> Maybe (ListZipper a, b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ListZipper a
z'', a -> b
f a
a)
)
instance Applicative (ListZipperOp a) where
<*> :: ListZipperOp a (a -> b) -> ListZipperOp a a -> ListZipperOp a b
(<*>) =
ListZipperOp a (a -> b) -> ListZipperOp a a -> ListZipperOp a b
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
(<.>)
pure :: a -> ListZipperOp a a
pure a
a =
(ListZipper a -> Maybe (ListZipper a, a)) -> ListZipperOp a a
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
z -> (ListZipper a, a) -> Maybe (ListZipper a, a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ListZipper a
z, a
a))
instance Bind (ListZipperOp a) where
ListZipperOp ListZipper a -> Maybe (ListZipper a, a)
j >>- :: ListZipperOp a a -> (a -> ListZipperOp a b) -> ListZipperOp a b
>>- a -> ListZipperOp a b
f =
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
z ->
ListZipper a -> Maybe (ListZipper a, a)
j ListZipper a
z Maybe (ListZipper a, a)
-> ((ListZipper a, a) -> Maybe (ListZipper a, b))
-> Maybe (ListZipper a, b)
forall (m :: * -> *) a b. Bind m => m a -> (a -> m b) -> m b
>>- \(ListZipper a
z', a
a) ->
ListZipper a
z' ListZipper a
-> (ListZipper a -> Maybe (ListZipper a, b))
-> Maybe (ListZipper a, b)
forall a b. a -> (a -> b) -> b
& a -> ListZipperOp a b
f a
a ListZipperOp a b
-> Getting
(ListZipper a -> Maybe (ListZipper a, b))
(ListZipperOp a b)
(ListZipper a -> Maybe (ListZipper a, b))
-> ListZipper a
-> Maybe (ListZipper a, b)
forall s a. s -> Getting a s a -> a
^. Getting
(ListZipper a -> Maybe (ListZipper a, b))
(ListZipperOp a b)
(ListZipper a -> Maybe (ListZipper a, b))
forall s t. Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t)
_Wrapped
)
instance Alt (ListZipperOp a) where
ListZipperOp ListZipper a -> Maybe (ListZipper a, a)
j <!> :: ListZipperOp a a -> ListZipperOp a a -> ListZipperOp a a
<!> ListZipperOp ListZipper a -> Maybe (ListZipper a, a)
k =
(ListZipper a -> Maybe (ListZipper a, a)) -> ListZipperOp a a
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
z -> ListZipper a -> Maybe (ListZipper a, a)
j ListZipper a
z Maybe (ListZipper a, a)
-> Maybe (ListZipper a, a) -> Maybe (ListZipper a, a)
forall (f :: * -> *) a. Alt f => f a -> f a -> f a
<!> ListZipper a -> Maybe (ListZipper a, a)
k ListZipper a
z)
instance Alternative (ListZipperOp x) where
<|> :: ListZipperOp x a -> ListZipperOp x a -> ListZipperOp x a
(<|>) =
ListZipperOp x a -> ListZipperOp x a -> ListZipperOp x a
forall (f :: * -> *) a. Alt f => f a -> f a -> f a
(<!>)
empty :: ListZipperOp x a
empty =
(ListZipper x -> Maybe (ListZipper x, a)) -> ListZipperOp x a
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (Maybe (ListZipper x, a) -> ListZipper x -> Maybe (ListZipper x, a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (ListZipper x, a)
forall (f :: * -> *) a. Alternative f => f a
empty)
instance Monad (ListZipperOp a) where
>>= :: ListZipperOp a a -> (a -> ListZipperOp a b) -> ListZipperOp a b
(>>=) =
ListZipperOp a a -> (a -> ListZipperOp a b) -> ListZipperOp a b
forall (m :: * -> *) a b. Bind m => m a -> (a -> m b) -> m b
(>>-)
return :: a -> ListZipperOp a a
return =
a -> ListZipperOp a a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
instance MonadPlus (ListZipperOp a) where
ListZipperOp ListZipper a -> Maybe (ListZipper a, a)
j mplus :: ListZipperOp a a -> ListZipperOp a a -> ListZipperOp a a
`mplus` ListZipperOp ListZipper a -> Maybe (ListZipper a, a)
k =
(ListZipper a -> Maybe (ListZipper a, a)) -> ListZipperOp a a
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
z -> ListZipper a -> Maybe (ListZipper a, a)
j ListZipper a
z Maybe (ListZipper a, a)
-> Maybe (ListZipper a, a) -> Maybe (ListZipper a, a)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` ListZipper a -> Maybe (ListZipper a, a)
k ListZipper a
z)
mzero :: ListZipperOp a a
mzero =
(ListZipper a -> Maybe (ListZipper a, a)) -> ListZipperOp a a
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (Maybe (ListZipper a, a) -> ListZipper a -> Maybe (ListZipper a, a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (ListZipper a, a)
forall (m :: * -> *) a. MonadPlus m => m a
mzero)
instance Semigroup (ListZipperOp a b) where
ListZipperOp ListZipper a -> Maybe (ListZipper a, b)
j <> :: ListZipperOp a b -> ListZipperOp a b -> ListZipperOp a b
<> ListZipperOp ListZipper a -> Maybe (ListZipper a, b)
k =
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
z -> ListZipper a -> Maybe (ListZipper a, b)
j ListZipper a
z Maybe (ListZipper a, b)
-> Maybe (ListZipper a, b) -> Maybe (ListZipper a, b)
forall (f :: * -> *) a. Alt f => f a -> f a -> f a
<!> ListZipper a -> Maybe (ListZipper a, b)
k ListZipper a
z)
instance Monoid (ListZipperOp a b) where
mappend :: ListZipperOp a b -> ListZipperOp a b -> ListZipperOp a b
mappend =
ListZipperOp a b -> ListZipperOp a b -> ListZipperOp a b
forall a. Semigroup a => a -> a -> a
(<>)
mempty :: ListZipperOp a b
mempty =
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (Maybe (ListZipper a, b) -> ListZipper a -> Maybe (ListZipper a, b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (ListZipper a, b)
forall a. Maybe a
Nothing)
instance MonadState (ListZipper a) (ListZipperOp a) where
get :: ListZipperOp a (ListZipper a)
get =
(ListZipper a -> Maybe (ListZipper a, ListZipper a))
-> ListZipperOp a (ListZipper a)
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
z -> (ListZipper a, ListZipper a) -> Maybe (ListZipper a, ListZipper a)
forall a. a -> Maybe a
Just (ListZipper a
z, ListZipper a
z))
put :: ListZipper a -> ListZipperOp a ()
put ListZipper a
z =
(ListZipper a -> Maybe (ListZipper a, ())) -> ListZipperOp a ()
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
_ -> (ListZipper a, ()) -> Maybe (ListZipper a, ())
forall a. a -> Maybe a
Just (ListZipper a
z, ()))
state :: (ListZipper a -> (a, ListZipper a)) -> ListZipperOp a a
state ListZipper a -> (a, ListZipper a)
k =
(ListZipper a -> Maybe (ListZipper a, a)) -> ListZipperOp a a
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
z -> let (a
z', ListZipper a
a) = ListZipper a -> (a, ListZipper a)
k ListZipper a
z in (ListZipper a, a) -> Maybe (ListZipper a, a)
forall a. a -> Maybe a
Just (ListZipper a
a, a
z'))
instance MonadReader (ListZipper a) (ListZipperOp a) where
ask :: ListZipperOp a (ListZipper a)
ask =
(ListZipper a -> Maybe (ListZipper a, ListZipper a))
-> ListZipperOp a (ListZipper a)
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
z -> (ListZipper a, ListZipper a) -> Maybe (ListZipper a, ListZipper a)
forall a. a -> Maybe a
Just (ListZipper a
z, ListZipper a
z))
local :: (ListZipper a -> ListZipper a)
-> ListZipperOp a a -> ListZipperOp a a
local ListZipper a -> ListZipper a
k (ListZipperOp ListZipper a -> Maybe (ListZipper a, a)
o) =
(ListZipper a -> Maybe (ListZipper a, a)) -> ListZipperOp a a
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
z -> (\(ListZipper a
z', a
a) -> (ListZipper a -> ListZipper a
k ListZipper a
z', a
a)) ((ListZipper a, a) -> (ListZipper a, a))
-> Maybe (ListZipper a, a) -> Maybe (ListZipper a, a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ListZipper a -> Maybe (ListZipper a, a)
o ListZipper a
z)
reader :: (ListZipper a -> a) -> ListZipperOp a a
reader ListZipper a -> a
k =
(ListZipper a -> Maybe (ListZipper a, a)) -> ListZipperOp a a
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
z -> (ListZipper a, a) -> Maybe (ListZipper a, a)
forall a. a -> Maybe a
Just (ListZipper a
z, ListZipper a -> a
k ListZipper a
z))
instance MonadFix (ListZipperOp a) where
mfix :: (a -> ListZipperOp a a) -> ListZipperOp a a
mfix a -> ListZipperOp a a
f =
(ListZipper a -> Maybe (ListZipper a, a)) -> ListZipperOp a a
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
z ->
((ListZipper a, a) -> Maybe (ListZipper a, a))
-> Maybe (ListZipper a, a)
forall (m :: * -> *) a. MonadFix m => (a -> m a) -> m a
mfix (\ ~(ListZipper a
_, a
a) -> ListZipper a
z ListZipper a
-> (ListZipper a -> Maybe (ListZipper a, a))
-> Maybe (ListZipper a, a)
forall a b. a -> (a -> b) -> b
& a -> ListZipperOp a a
f a
a ListZipperOp a a
-> Getting
(ListZipper a -> Maybe (ListZipper a, a))
(ListZipperOp a a)
(ListZipper a -> Maybe (ListZipper a, a))
-> ListZipper a
-> Maybe (ListZipper a, a)
forall s a. s -> Getting a s a -> a
^. Getting
(ListZipper a -> Maybe (ListZipper a, a))
(ListZipperOp a a)
(ListZipper a -> Maybe (ListZipper a, a))
forall s t. Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t)
_Wrapped)
)
instance MonadFail (ListZipperOp a) where
fail :: String -> ListZipperOp a a
fail String
s =
(ListZipper a -> Maybe (ListZipper a, a)) -> ListZipperOp a a
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
_ ->
String -> Maybe (ListZipper a, a)
forall (m :: * -> *) a. MonadFail m => String -> m a
Fail.fail String
s
)
instance MonadError () (ListZipperOp a) where
throwError :: () -> ListZipperOp a a
throwError () =
(ListZipper a -> Maybe (ListZipper a, a)) -> ListZipperOp a a
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
_ -> Maybe (ListZipper a, a)
forall a. Maybe a
Nothing)
catchError :: ListZipperOp a a -> (() -> ListZipperOp a a) -> ListZipperOp a a
catchError (ListZipperOp ListZipper a -> Maybe (ListZipper a, a)
k) () -> ListZipperOp a a
f =
(ListZipper a -> Maybe (ListZipper a, a)) -> ListZipperOp a a
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
z ->
ListZipper a -> Maybe (ListZipper a, a)
k ListZipper a
z Maybe (ListZipper a, a)
-> Maybe (ListZipper a, a) -> Maybe (ListZipper a, a)
forall (f :: * -> *) a. Alt f => f a -> f a -> f a
<!> (ListZipper a
z ListZipper a
-> (ListZipper a -> Maybe (ListZipper a, a))
-> Maybe (ListZipper a, a)
forall a b. a -> (a -> b) -> b
& () -> ListZipperOp a a
f () ListZipperOp a a
-> Getting
(ListZipper a -> Maybe (ListZipper a, a))
(ListZipperOp a a)
(ListZipper a -> Maybe (ListZipper a, a))
-> ListZipper a
-> Maybe (ListZipper a, a)
forall s a. s -> Getting a s a -> a
^. Getting
(ListZipper a -> Maybe (ListZipper a, a))
(ListZipperOp a a)
(ListZipper a -> Maybe (ListZipper a, a))
forall s t. Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t)
_Wrapped)
)
liftListZipperOp ::
Maybe b
-> ListZipperOp a b
liftListZipperOp :: Maybe b -> ListZipperOp a b
liftListZipperOp Maybe b
m =
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
z ->
(\b
b -> (ListZipper a
z, b
b)) (b -> (ListZipper a, b)) -> Maybe b -> Maybe (ListZipper a, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe b
m
)
getFocus ::
ListZipperOp a a
getFocus :: ListZipperOp a a
getFocus =
(ListZipper a -> a) -> ListZipperOp a a
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
reader (ListZipper a -> Getting a (ListZipper a) a -> a
forall s a. s -> Getting a s a -> a
^. Getting a (ListZipper a) a
forall z a. HasListZipper z a => Lens' z a
focus)
getLeft ::
ListZipperOp a a
getLeft :: ListZipperOp a a
getLeft =
do ListZipper a
z <- ListZipperOp a (ListZipper a)
forall s (m :: * -> *). MonadState s m => m s
get
case ListZipper a
z of
ListZipper (a
l:[a]
_) a
_ [a]
_ ->
a -> ListZipperOp a a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
l
ListZipper [] a
_ [a]
_ ->
ListZipperOp a a
forall a. Monoid a => a
mempty
getRight ::
ListZipperOp a a
getRight :: ListZipperOp a a
getRight =
do ListZipper a
z <- ListZipperOp a (ListZipper a)
forall s (m :: * -> *). MonadState s m => m s
get
case ListZipper a
z of
ListZipper [a]
_ a
_ (a
r:[a]
_) ->
a -> ListZipperOp a a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
r
ListZipper [a]
_ a
_ [] ->
ListZipperOp a a
forall a. Monoid a => a
mempty
getRightz ::
ListZipperOp a [a]
getRightz :: ListZipperOp a [a]
getRightz =
(ListZipper a -> [a]) -> ListZipperOp a [a]
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
reader (ListZipper a -> Getting [a] (ListZipper a) [a] -> [a]
forall s a. s -> Getting a s a -> a
^. Getting [a] (ListZipper a) [a]
forall z a. HasListZipper z a => Lens' z [a]
rightz)
getLeftz ::
ListZipperOp a [a]
getLeftz :: ListZipperOp a [a]
getLeftz =
(ListZipper a -> [a]) -> ListZipperOp a [a]
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
reader (ListZipper a -> Getting [a] (ListZipper a) [a] -> [a]
forall s a. s -> Getting a s a -> a
^. Getting [a] (ListZipper a) [a]
forall z a. HasListZipper z a => Lens' z [a]
leftz)
getList ::
ListZipperOp a [a]
getList :: ListZipperOp a [a]
getList =
(ListZipper a -> [a]) -> ListZipperOp a [a]
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
reader ListZipper a -> [a]
forall a. ListZipper a -> [a]
list
mkListZipperOp ::
(ListZipper a -> Maybe b)
-> ListZipperOp a b
mkListZipperOp :: (ListZipper a -> Maybe b) -> ListZipperOp a b
mkListZipperOp ListZipper a -> Maybe b
f =
ListZipperOp a (ListZipper a)
forall s (m :: * -> *). MonadState s m => m s
get ListZipperOp a (ListZipper a)
-> (ListZipper a -> ListZipperOp a b) -> ListZipperOp a b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Maybe b -> ListZipperOp a b
forall b a. Maybe b -> ListZipperOp a b
liftListZipperOp (Maybe b -> ListZipperOp a b)
-> (ListZipper a -> Maybe b) -> ListZipper a -> ListZipperOp a b
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ListZipper a -> Maybe b
f
(<$~) ::
ListZipperOp a b
-> ListZipperOp a c
-> ListZipperOp a b
ListZipperOp ListZipper a -> Maybe (ListZipper a, b)
x <$~ :: ListZipperOp a b -> ListZipperOp a c -> ListZipperOp a b
<$~ ListZipperOp ListZipper a -> Maybe (ListZipper a, c)
y =
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp
(\ListZipper a
z ->
case ListZipper a -> Maybe (ListZipper a, b)
x ListZipper a
z of
Maybe (ListZipper a, b)
Nothing ->
Maybe (ListZipper a, b)
forall a. Maybe a
Nothing
Just (ListZipper a
z', b
r) ->
((ListZipper a, c) -> (ListZipper a, b))
-> Maybe (ListZipper a, c) -> Maybe (ListZipper a, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (b
r b -> (ListZipper a, c) -> (ListZipper a, b)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$) (ListZipper a -> Maybe (ListZipper a, c)
y ListZipper a
z')
)
infixl 5 <$~
(*>>) ::
(ListZipper a -> Maybe b)
-> ListZipperOp a c
-> ListZipperOp a b
ListZipper a -> Maybe b
f *>> :: (ListZipper a -> Maybe b) -> ListZipperOp a c -> ListZipperOp a b
*>> ListZipperOp a c
k =
(ListZipper a -> Maybe b) -> ListZipperOp a b
forall a b. (ListZipper a -> Maybe b) -> ListZipperOp a b
mkListZipperOp ListZipper a -> Maybe b
f ListZipperOp a b -> ListZipperOp a c -> ListZipperOp a b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ListZipperOp a c
k
infixl 5 *>>
(<<*) ::
ListZipperOp a c
-> (ListZipper a -> Maybe b)
-> ListZipperOp a b
<<* :: ListZipperOp a c -> (ListZipper a -> Maybe b) -> ListZipperOp a b
(<<*) =
((ListZipper a -> Maybe b) -> ListZipperOp a c -> ListZipperOp a b)
-> ListZipperOp a c
-> (ListZipper a -> Maybe b)
-> ListZipperOp a b
forall a b c. (a -> b -> c) -> b -> a -> c
flip (ListZipper a -> Maybe b) -> ListZipperOp a c -> ListZipperOp a b
forall a b c.
(ListZipper a -> Maybe b) -> ListZipperOp a c -> ListZipperOp a b
(*>>)
infixl 5 <<*
mkListZipperOp' ::
(ListZipper a -> Maybe (ListZipper a))
-> ListZipperOp' a
mkListZipperOp' :: (ListZipper a -> Maybe (ListZipper a)) -> ListZipperOp' a
mkListZipperOp' ListZipper a -> Maybe (ListZipper a)
f =
(ListZipper a -> Maybe (ListZipper a, ())) -> ListZipperOp' a
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
s -> (\ListZipper a
s' -> (ListZipper a
s', ())) (ListZipper a -> (ListZipper a, ()))
-> Maybe (ListZipper a) -> Maybe (ListZipper a, ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ListZipper a -> Maybe (ListZipper a)
f ListZipper a
s)
(.>>) ::
(ListZipper a -> Maybe (ListZipper a))
-> ListZipperOp a b
-> ListZipperOp' a
ListZipper a -> Maybe (ListZipper a)
f .>> :: (ListZipper a -> Maybe (ListZipper a))
-> ListZipperOp a b -> ListZipperOp' a
.>> ListZipperOp a b
k =
(ListZipper a -> Maybe (ListZipper a)) -> ListZipperOp' a
forall a. (ListZipper a -> Maybe (ListZipper a)) -> ListZipperOp' a
mkListZipperOp' ListZipper a -> Maybe (ListZipper a)
f ListZipperOp' a -> ListZipperOp a b -> ListZipperOp' a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ListZipperOp a b
k
infixl 5 .>>
(<<.) ::
ListZipperOp a b
-> (ListZipper a -> Maybe (ListZipper a))
-> ListZipperOp' a
<<. :: ListZipperOp a b
-> (ListZipper a -> Maybe (ListZipper a)) -> ListZipperOp' a
(<<.) =
((ListZipper a -> Maybe (ListZipper a))
-> ListZipperOp a b -> ListZipperOp' a)
-> ListZipperOp a b
-> (ListZipper a -> Maybe (ListZipper a))
-> ListZipperOp' a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (ListZipper a -> Maybe (ListZipper a))
-> ListZipperOp a b -> ListZipperOp' a
forall a b.
(ListZipper a -> Maybe (ListZipper a))
-> ListZipperOp a b -> ListZipperOp' a
(.>>)
infixl 5 <<.
runListZipperOp ::
ListZipperOp a x
-> ListZipper a
-> Maybe (ListZipper a, x)
runListZipperOp :: ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a, x)
runListZipperOp (ListZipperOp ListZipper a -> Maybe (ListZipper a, x)
o) ListZipper a
z =
ListZipper a -> Maybe (ListZipper a, x)
o ListZipper a
z
execListZipperOp ::
ListZipperOp a x
-> ListZipper a
-> Maybe (ListZipper a)
execListZipperOp :: ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a)
execListZipperOp ListZipperOp a x
o =
((ListZipper a, x) -> ListZipper a)
-> Maybe (ListZipper a, x) -> Maybe (ListZipper a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((ListZipper a, x)
-> Getting (ListZipper a) (ListZipper a, x) (ListZipper a)
-> ListZipper a
forall s a. s -> Getting a s a -> a
^. Getting (ListZipper a) (ListZipper a, x) (ListZipper a)
forall s t a b. Field1 s t a b => Lens s t a b
_1) (Maybe (ListZipper a, x) -> Maybe (ListZipper a))
-> (ListZipper a -> Maybe (ListZipper a, x))
-> ListZipper a
-> Maybe (ListZipper a)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a, x)
forall a x.
ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a, x)
runListZipperOp ListZipperOp a x
o
execListZipperOpOr ::
ListZipperOp a x
-> ListZipper a
-> ListZipper a
execListZipperOpOr :: ListZipperOp a x -> ListZipper a -> ListZipper a
execListZipperOpOr ListZipperOp a x
o =
ListZipper a -> Maybe (ListZipper a) -> ListZipper a
forall a. a -> Maybe a -> a
fromMaybe (ListZipper a -> Maybe (ListZipper a) -> ListZipper a)
-> (ListZipper a -> Maybe (ListZipper a))
-> ListZipper a
-> ListZipper a
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a)
forall a x.
ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a)
execListZipperOp ListZipperOp a x
o
(##>) ::
ListZipperOp a x
-> ListZipper a
-> Maybe (ListZipper a)
##> :: ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a)
(##>) =
ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a)
forall a x.
ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a)
execListZipperOp
infixl 6 ##>
(<##) ::
ListZipper a
-> ListZipperOp a x
-> Maybe (ListZipper a)
<## :: ListZipper a -> ListZipperOp a x -> Maybe (ListZipper a)
(<##) =
(ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a))
-> ListZipper a -> ListZipperOp a x -> Maybe (ListZipper a)
forall a b c. (a -> b -> c) -> b -> a -> c
flip ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a)
forall a x.
ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a)
(##>)
infixl 6 <##
evalListZipperOp ::
ListZipperOp a x
-> ListZipper a
-> Maybe x
evalListZipperOp :: ListZipperOp a x -> ListZipper a -> Maybe x
evalListZipperOp ListZipperOp a x
o =
((ListZipper a, x) -> x) -> Maybe (ListZipper a, x) -> Maybe x
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((ListZipper a, x) -> Getting x (ListZipper a, x) x -> x
forall s a. s -> Getting a s a -> a
^. Getting x (ListZipper a, x) x
forall s t a b. Field2 s t a b => Lens s t a b
_2) (Maybe (ListZipper a, x) -> Maybe x)
-> (ListZipper a -> Maybe (ListZipper a, x))
-> ListZipper a
-> Maybe x
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a, x)
forall a x.
ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a, x)
runListZipperOp ListZipperOp a x
o
(&&>) ::
ListZipperOp a x
-> ListZipper a
-> Maybe x
&&> :: ListZipperOp a x -> ListZipper a -> Maybe x
(&&>) =
ListZipperOp a x -> ListZipper a -> Maybe x
forall a x. ListZipperOp a x -> ListZipper a -> Maybe x
evalListZipperOp
infixl 6 &&>
(<&&) ::
ListZipper a
-> ListZipperOp a x
-> Maybe x
<&& :: ListZipper a -> ListZipperOp a x -> Maybe x
(<&&) =
(ListZipperOp a x -> ListZipper a -> Maybe x)
-> ListZipper a -> ListZipperOp a x -> Maybe x
forall a b c. (a -> b -> c) -> b -> a -> c
flip ListZipperOp a x -> ListZipper a -> Maybe x
forall a x. ListZipperOp a x -> ListZipper a -> Maybe x
(&&>)
infixl 6 <&&
execOpList ::
ListZipperOp a x
-> ListZipper a
-> Maybe [a]
execOpList :: ListZipperOp a x -> ListZipper a -> Maybe [a]
execOpList ListZipperOp a x
o =
(ListZipper a -> [a]) -> Maybe (ListZipper a) -> Maybe [a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ListZipper a -> [a]
forall a. ListZipper a -> [a]
list (Maybe (ListZipper a) -> Maybe [a])
-> (ListZipper a -> Maybe (ListZipper a))
-> ListZipper a
-> Maybe [a]
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a)
forall a x.
ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a)
execListZipperOp ListZipperOp a x
o
(%%>) ::
ListZipperOp a x
-> ListZipper a
-> Maybe [a]
%%> :: ListZipperOp a x -> ListZipper a -> Maybe [a]
(%%>) =
ListZipperOp a x -> ListZipper a -> Maybe [a]
forall a x. ListZipperOp a x -> ListZipper a -> Maybe [a]
execOpList
infixl 5 %%>
(<%%) ::
ListZipper a
-> ListZipperOp a x
-> Maybe [a]
<%% :: ListZipper a -> ListZipperOp a x -> Maybe [a]
(<%%) =
(ListZipperOp a x -> ListZipper a -> Maybe [a])
-> ListZipper a -> ListZipperOp a x -> Maybe [a]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ListZipperOp a x -> ListZipper a -> Maybe [a]
forall a x. ListZipperOp a x -> ListZipper a -> Maybe [a]
(%%>)
infixl 5 <%%
execOpList' ::
ListZipperOp a x
-> ListZipper a
-> [a]
execOpList' :: ListZipperOp a x -> ListZipper a -> [a]
execOpList' ListZipperOp a x
o =
[a] -> Maybe [a] -> [a]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [a] -> [a])
-> (ListZipper a -> Maybe [a]) -> ListZipper a -> [a]
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ListZipperOp a x -> ListZipper a -> Maybe [a]
forall a x. ListZipperOp a x -> ListZipper a -> Maybe [a]
execOpList ListZipperOp a x
o
($$>) ::
ListZipperOp a x
-> ListZipper a
-> [a]
$$> :: ListZipperOp a x -> ListZipper a -> [a]
($$>) =
ListZipperOp a x -> ListZipper a -> [a]
forall a x. ListZipperOp a x -> ListZipper a -> [a]
execOpList'
infixl 5 $$>
(<$$) ::
ListZipper a
-> ListZipperOp a x
-> [a]
<$$ :: ListZipper a -> ListZipperOp a x -> [a]
(<$$) =
(ListZipperOp a x -> ListZipper a -> [a])
-> ListZipper a -> ListZipperOp a x -> [a]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ListZipperOp a x -> ListZipper a -> [a]
forall a x. ListZipperOp a x -> ListZipper a -> [a]
($$>)
infixl 5 <$$
moveLeft ::
ListZipperOp' a
moveLeft :: ListZipperOp' a
moveLeft =
(ListZipper a -> Maybe (ListZipper a)) -> ListZipperOp' a
forall a. (ListZipper a -> Maybe (ListZipper a)) -> ListZipperOp' a
mkListZipperOp' (\ListZipper a
z ->
case ListZipper a
z of
ListZipper [] a
_ [a]
_ ->
Maybe (ListZipper a)
forall a. Maybe a
Nothing
ListZipper (a
h:[a]
t) a
x [a]
r ->
ListZipper a -> Maybe (ListZipper a)
forall a. a -> Maybe a
Just ([a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper [a]
t a
h (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
r))
)
moveRight ::
ListZipperOp' a
moveRight :: ListZipperOp' a
moveRight =
(ListZipper a -> Maybe (ListZipper a)) -> ListZipperOp' a
forall a. (ListZipper a -> Maybe (ListZipper a)) -> ListZipperOp' a
mkListZipperOp' (\ListZipper a
z ->
case ListZipper a
z of
ListZipper [a]
_ a
_ [] ->
Maybe (ListZipper a)
forall a. Maybe a
Nothing
ListZipper [a]
l a
x (a
h:[a]
t) ->
ListZipper a -> Maybe (ListZipper a)
forall a. a -> Maybe a
Just ([a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
l) a
h [a]
t)
)
opWith ::
ListZipperOp a b
-> (a -> Maybe c)
-> ListZipperOp a c
opWith :: ListZipperOp a b -> (a -> Maybe c) -> ListZipperOp a c
opWith ListZipperOp a b
o a -> Maybe c
p =
(ListZipper a -> Maybe (ListZipper a, c)) -> ListZipperOp a c
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\ListZipper a
z ->
let go :: ListZipper a -> Maybe (ListZipper a, c)
go ListZipper a
z' =
let x :: a
x = ListZipper a
z' ListZipper a -> Getting a (ListZipper a) a -> a
forall s a. s -> Getting a s a -> a
^. Getting a (ListZipper a) a
forall z a. HasListZipper z a => Lens' z a
focus
in case a -> Maybe c
p a
x of
Maybe c
Nothing ->
ListZipper a -> Maybe (ListZipper a, c)
go (ListZipper a -> Maybe (ListZipper a, c))
-> Maybe (ListZipper a) -> Maybe (ListZipper a, c)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ListZipperOp a b -> ListZipper a -> Maybe (ListZipper a)
forall a x.
ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a)
execListZipperOp ListZipperOp a b
o ListZipper a
z'
Just c
w ->
(ListZipper a, c) -> Maybe (ListZipper a, c)
forall a. a -> Maybe a
Just (ListZipper a
z', c
w)
in ListZipper a -> Maybe (ListZipper a, c)
go ListZipper a
z
)
moveLeftWith ::
(a -> Maybe c)
-> ListZipperOp a c
moveLeftWith :: (a -> Maybe c) -> ListZipperOp a c
moveLeftWith =
ListZipperOp a () -> (a -> Maybe c) -> ListZipperOp a c
forall a b c.
ListZipperOp a b -> (a -> Maybe c) -> ListZipperOp a c
opWith ListZipperOp a ()
forall a. ListZipperOp' a
moveLeft
moveRightWith ::
(a -> Maybe c)
-> ListZipperOp a c
moveRightWith :: (a -> Maybe c) -> ListZipperOp a c
moveRightWith =
ListZipperOp a () -> (a -> Maybe c) -> ListZipperOp a c
forall a b c.
ListZipperOp a b -> (a -> Maybe c) -> ListZipperOp a c
opWith ListZipperOp a ()
forall a. ListZipperOp' a
moveRight
moveLeftRightWith ::
(a -> Maybe c)
-> ListZipperOp a c
moveLeftRightWith :: (a -> Maybe c) -> ListZipperOp a c
moveLeftRightWith a -> Maybe c
p =
(a -> Maybe c) -> ListZipperOp a c
forall a c. (a -> Maybe c) -> ListZipperOp a c
moveLeftWith a -> Maybe c
p ListZipperOp a c -> ListZipperOp a c -> ListZipperOp a c
forall (f :: * -> *) a. Alt f => f a -> f a -> f a
<!> (a -> Maybe c) -> ListZipperOp a c
forall a c. (a -> Maybe c) -> ListZipperOp a c
moveRightWith a -> Maybe c
p
moveRightLeftWith ::
(a -> Maybe c)
-> ListZipperOp a c
moveRightLeftWith :: (a -> Maybe c) -> ListZipperOp a c
moveRightLeftWith a -> Maybe c
p =
(a -> Maybe c) -> ListZipperOp a c
forall a c. (a -> Maybe c) -> ListZipperOp a c
moveRightWith a -> Maybe c
p ListZipperOp a c -> ListZipperOp a c -> ListZipperOp a c
forall (f :: * -> *) a. Alt f => f a -> f a -> f a
<!> (a -> Maybe c) -> ListZipperOp a c
forall a c. (a -> Maybe c) -> ListZipperOp a c
moveLeftWith a -> Maybe c
p
opWithThen ::
ListZipperOp a b
-> (a -> Maybe c)
-> ListZipperOp a c
opWithThen :: ListZipperOp a b -> (a -> Maybe c) -> ListZipperOp a c
opWithThen ListZipperOp a b
o a -> Maybe c
p =
ListZipperOp a b -> (a -> Maybe c) -> ListZipperOp a c
forall a b c.
ListZipperOp a b -> (a -> Maybe c) -> ListZipperOp a c
opWith ListZipperOp a b
o a -> Maybe c
p ListZipperOp a c -> ListZipperOp a b -> ListZipperOp a c
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ListZipperOp a b
o
moveLeftWithThen ::
(a -> Maybe c)
-> ListZipperOp a c
moveLeftWithThen :: (a -> Maybe c) -> ListZipperOp a c
moveLeftWithThen =
ListZipperOp a () -> (a -> Maybe c) -> ListZipperOp a c
forall a b c.
ListZipperOp a b -> (a -> Maybe c) -> ListZipperOp a c
opWithThen ListZipperOp a ()
forall a. ListZipperOp' a
moveLeft
moveRightWithThen ::
(a -> Maybe c)
-> ListZipperOp a c
moveRightWithThen :: (a -> Maybe c) -> ListZipperOp a c
moveRightWithThen =
ListZipperOp a () -> (a -> Maybe c) -> ListZipperOp a c
forall a b c.
ListZipperOp a b -> (a -> Maybe c) -> ListZipperOp a c
opWithThen ListZipperOp a ()
forall a. ListZipperOp' a
moveRight
moveLeftRightWithThen ::
(a -> Maybe c)
-> ListZipperOp a c
moveLeftRightWithThen :: (a -> Maybe c) -> ListZipperOp a c
moveLeftRightWithThen a -> Maybe c
p =
(a -> Maybe c) -> ListZipperOp a c
forall a c. (a -> Maybe c) -> ListZipperOp a c
moveLeftWithThen a -> Maybe c
p ListZipperOp a c -> ListZipperOp a c -> ListZipperOp a c
forall (f :: * -> *) a. Alt f => f a -> f a -> f a
<!> (a -> Maybe c) -> ListZipperOp a c
forall a c. (a -> Maybe c) -> ListZipperOp a c
moveRightWithThen a -> Maybe c
p
moveRightLeftWithThen ::
(a -> Maybe c)
-> ListZipperOp a c
moveRightLeftWithThen :: (a -> Maybe c) -> ListZipperOp a c
moveRightLeftWithThen a -> Maybe c
p =
(a -> Maybe c) -> ListZipperOp a c
forall a c. (a -> Maybe c) -> ListZipperOp a c
moveRightWithThen a -> Maybe c
p ListZipperOp a c -> ListZipperOp a c -> ListZipperOp a c
forall (f :: * -> *) a. Alt f => f a -> f a -> f a
<!> (a -> Maybe c) -> ListZipperOp a c
forall a c. (a -> Maybe c) -> ListZipperOp a c
moveLeftWithThen a -> Maybe c
p
opUntil ::
ListZipperOp a x
-> (a -> Bool)
-> ListZipperOp' a
opUntil :: ListZipperOp a x -> (a -> Bool) -> ListZipperOp' a
opUntil ListZipperOp a x
o a -> Bool
p =
ListZipperOp a x -> (a -> Maybe ()) -> ListZipperOp' a
forall a b c.
ListZipperOp a b -> (a -> Maybe c) -> ListZipperOp a c
opWith ListZipperOp a x
o (\a
a -> if a -> Bool
p a
a then () -> Maybe ()
forall a. a -> Maybe a
Just () else Maybe ()
forall a. Maybe a
Nothing)
moveLeftUntil ::
(a -> Bool)
-> ListZipperOp' a
moveLeftUntil :: (a -> Bool) -> ListZipperOp' a
moveLeftUntil =
ListZipperOp' a -> (a -> Bool) -> ListZipperOp' a
forall a x. ListZipperOp a x -> (a -> Bool) -> ListZipperOp' a
opUntil ListZipperOp' a
forall a. ListZipperOp' a
moveLeft
moveRightUntil ::
(a -> Bool)
-> ListZipperOp' a
moveRightUntil :: (a -> Bool) -> ListZipperOp' a
moveRightUntil =
ListZipperOp' a -> (a -> Bool) -> ListZipperOp' a
forall a x. ListZipperOp a x -> (a -> Bool) -> ListZipperOp' a
opUntil ListZipperOp' a
forall a. ListZipperOp' a
moveRight
moveLeftRightUntil ::
(a -> Bool)
-> ListZipperOp' a
moveLeftRightUntil :: (a -> Bool) -> ListZipperOp' a
moveLeftRightUntil a -> Bool
p =
(a -> Bool) -> ListZipperOp' a
forall a. (a -> Bool) -> ListZipperOp' a
moveLeftUntil a -> Bool
p ListZipperOp' a -> ListZipperOp' a -> ListZipperOp' a
forall (f :: * -> *) a. Alt f => f a -> f a -> f a
<!> (a -> Bool) -> ListZipperOp' a
forall a. (a -> Bool) -> ListZipperOp' a
moveRightUntil a -> Bool
p
moveRightLeftUntil ::
(a -> Bool)
-> ListZipperOp' a
moveRightLeftUntil :: (a -> Bool) -> ListZipperOp' a
moveRightLeftUntil a -> Bool
p =
(a -> Bool) -> ListZipperOp' a
forall a. (a -> Bool) -> ListZipperOp' a
moveRightUntil a -> Bool
p ListZipperOp' a -> ListZipperOp' a -> ListZipperOp' a
forall (f :: * -> *) a. Alt f => f a -> f a -> f a
<!> (a -> Bool) -> ListZipperOp' a
forall a. (a -> Bool) -> ListZipperOp' a
moveLeftUntil a -> Bool
p
opUntilThen ::
ListZipperOp a x
-> (a -> Bool)
-> ListZipperOp' a
opUntilThen :: ListZipperOp a x -> (a -> Bool) -> ListZipperOp' a
opUntilThen ListZipperOp a x
o a -> Bool
p =
ListZipperOp a x -> (a -> Bool) -> ListZipperOp' a
forall a x. ListZipperOp a x -> (a -> Bool) -> ListZipperOp' a
opUntil ListZipperOp a x
o a -> Bool
p ListZipperOp' a -> ListZipperOp a x -> ListZipperOp' a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ListZipperOp a x
o
moveLeftUntilThen ::
(a -> Bool)
-> ListZipperOp' a
moveLeftUntilThen :: (a -> Bool) -> ListZipperOp' a
moveLeftUntilThen =
ListZipperOp' a -> (a -> Bool) -> ListZipperOp' a
forall a x. ListZipperOp a x -> (a -> Bool) -> ListZipperOp' a
opUntilThen ListZipperOp' a
forall a. ListZipperOp' a
moveLeft
moveRightUntilThen ::
(a -> Bool)
-> ListZipperOp' a
moveRightUntilThen :: (a -> Bool) -> ListZipperOp' a
moveRightUntilThen =
ListZipperOp' a -> (a -> Bool) -> ListZipperOp' a
forall a x. ListZipperOp a x -> (a -> Bool) -> ListZipperOp' a
opUntilThen ListZipperOp' a
forall a. ListZipperOp' a
moveRight
moveLeftRightUntilThen ::
(a -> Bool)
-> ListZipperOp' a
moveLeftRightUntilThen :: (a -> Bool) -> ListZipperOp' a
moveLeftRightUntilThen a -> Bool
p =
(a -> Bool) -> ListZipperOp' a
forall a. (a -> Bool) -> ListZipperOp' a
moveLeftUntilThen a -> Bool
p ListZipperOp' a -> ListZipperOp' a -> ListZipperOp' a
forall (f :: * -> *) a. Alt f => f a -> f a -> f a
<!> (a -> Bool) -> ListZipperOp' a
forall a. (a -> Bool) -> ListZipperOp' a
moveRightUntilThen a -> Bool
p
moveRightLeftUntilThen ::
(a -> Bool)
-> ListZipperOp' a
moveRightLeftUntilThen :: (a -> Bool) -> ListZipperOp' a
moveRightLeftUntilThen a -> Bool
p =
(a -> Bool) -> ListZipperOp' a
forall a. (a -> Bool) -> ListZipperOp' a
moveRightUntilThen a -> Bool
p ListZipperOp' a -> ListZipperOp' a -> ListZipperOp' a
forall (f :: * -> *) a. Alt f => f a -> f a -> f a
<!> (a -> Bool) -> ListZipperOp' a
forall a. (a -> Bool) -> ListZipperOp' a
moveLeftUntilThen a -> Bool
p
opWhileJust ::
ListZipperOp' a
-> ListZipper a
-> ListZipper a
opWhileJust :: ListZipperOp' a -> ListZipper a -> ListZipper a
opWhileJust ListZipperOp' a
o ListZipper a
z =
case ListZipperOp' a -> ListZipper a -> Maybe (ListZipper a)
forall a x.
ListZipperOp a x -> ListZipper a -> Maybe (ListZipper a)
execListZipperOp ListZipperOp' a
o ListZipper a
z of
Maybe (ListZipper a)
Nothing ->
ListZipper a
z
Just ListZipper a
z' ->
ListZipperOp' a -> ListZipper a -> ListZipper a
forall a. ListZipperOp' a -> ListZipper a -> ListZipper a
opWhileJust ListZipperOp' a
o ListZipper a
z'
deleteStepLeft ::
ListZipperOp a a
deleteStepLeft :: ListZipperOp a a
deleteStepLeft =
(ListZipper a -> Maybe (ListZipper a, a)) -> ListZipperOp a a
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\(ListZipper [a]
l a
x [a]
r) ->
case [a]
l of
[] ->
Maybe (ListZipper a, a)
forall a. Maybe a
Nothing
a
h:[a]
t ->
(ListZipper a, a) -> Maybe (ListZipper a, a)
forall a. a -> Maybe a
Just ([a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper [a]
t a
h [a]
r, a
x)
)
deleteStepRight ::
ListZipperOp a a
deleteStepRight :: ListZipperOp a a
deleteStepRight =
(ListZipper a -> Maybe (ListZipper a, a)) -> ListZipperOp a a
forall a b.
(ListZipper a -> Maybe (ListZipper a, b)) -> ListZipperOp a b
ListZipperOp (\(ListZipper [a]
l a
x [a]
r) ->
case [a]
r of
[] ->
Maybe (ListZipper a, a)
forall a. Maybe a
Nothing
a
h:[a]
t ->
(ListZipper a, a) -> Maybe (ListZipper a, a)
forall a. a -> Maybe a
Just ([a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper [a]
l a
h [a]
t, a
x)
)
modifyFocus ::
(a -> a)
-> ListZipperOp a a
modifyFocus :: (a -> a) -> ListZipperOp a a
modifyFocus a -> a
f =
(ListZipper a -> (a, ListZipper a)) -> ListZipperOp a a
forall s (m :: * -> *) a. MonadState s m => (s -> (a, s)) -> m a
state (\(ListZipper [a]
l a
x [a]
r) -> (a
x, [a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper [a]
l (a -> a
f a
x) [a]
r))
setFocus ::
a
-> ListZipperOp a a
setFocus :: a -> ListZipperOp a a
setFocus =
(a -> a) -> ListZipperOp a a
forall a. (a -> a) -> ListZipperOp a a
modifyFocus ((a -> a) -> ListZipperOp a a)
-> (a -> a -> a) -> a -> ListZipperOp a a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> a -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
shuffleLeft ::
ListZipperOp' a
shuffleLeft :: ListZipperOp' a
shuffleLeft =
(ListZipper a -> Maybe (ListZipper a)) -> ListZipperOp' a
forall a. (ListZipper a -> Maybe (ListZipper a)) -> ListZipperOp' a
mkListZipperOp' (\ListZipper a
z ->
case ListZipper a
z of
ListZipper [] a
_ [a]
_ ->
Maybe (ListZipper a)
forall a. Maybe a
Nothing
ListZipper (a
h:[a]
t) a
x [a]
r ->
ListZipper a -> Maybe (ListZipper a)
forall a. a -> Maybe a
Just ([a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper [a]
t a
x (a
ha -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
r))
)
shuffleRight ::
ListZipperOp' a
shuffleRight :: ListZipperOp' a
shuffleRight =
(ListZipper a -> Maybe (ListZipper a)) -> ListZipperOp' a
forall a. (ListZipper a -> Maybe (ListZipper a)) -> ListZipperOp' a
mkListZipperOp' (\ListZipper a
z ->
case ListZipper a
z of
ListZipper [a]
_ a
_ [] ->
Maybe (ListZipper a)
forall a. Maybe a
Nothing
ListZipper [a]
l a
x (a
h:[a]
t) ->
ListZipper a -> Maybe (ListZipper a)
forall a. a -> Maybe a
Just ([a] -> a -> [a] -> ListZipper a
forall a. [a] -> a -> [a] -> ListZipper a
ListZipper (a
ha -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
l) a
x [a]
t)
)
shuffleListZipper ::
MonadRandom f =>
ListZipper a
-> f (ListZipper a)
shuffleListZipper :: ListZipper a -> f (ListZipper a)
shuffleListZipper ListZipper a
z =
let z' :: ListZipper a
z' =
ListZipperOp' a -> ListZipper a -> ListZipper a
forall a. ListZipperOp' a -> ListZipper a -> ListZipper a
opWhileJust ListZipperOp' a
forall a. ListZipperOp' a
shuffleLeft ListZipper a
z
in do Int
i <- (Int, Int) -> f Int
forall (m :: * -> *) a. (MonadRandom m, Random a) => (a, a) -> m a
getRandomR (Int
0, ListZipper a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ListZipper a
z Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
ListZipper a
z'' <- ([a] -> f [a]) -> ListZipper a -> f (ListZipper a)
forall z a. HasListZipper z a => Lens' z [a]
rightz [a] -> f [a]
forall (m :: * -> *) a. MonadRandom m => [a] -> m [a]
shuffleM ListZipper a
z'
ListZipper a -> f (ListZipper a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ListZipperOp a [()] -> ListZipper a -> ListZipper a
forall a x. ListZipperOp a x -> ListZipper a -> ListZipper a
execListZipperOpOr (Int -> ListZipperOp' a -> ListZipperOp a [()]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
i ListZipperOp' a
forall a. ListZipperOp' a
shuffleRight) ListZipper a
z'')
deriveEq1 ''ListZipper
deriveShow1 ''ListZipper