{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE TupleSections #-}
module Brassica.SoundChange.Apply.Internal.MultiZipper
( MultiZipper
, fromListStart
, fromListPos
, toList
, curPos
, atStart
, atEnd
, atBoundary
, value
, valueN
, locationOf
, yank
, move
, fwd
, bwd
, consume
, seek
, toBeginning
, toEnd
, insert
, insertMany
, reverseMZ
, zap
, tag
, tagAt
, query
, untag
, untagWhen
, delete
, extend
, extend'
) where
import Control.Applicative (Alternative((<|>)))
import Data.Foldable (Foldable(foldl'))
import Data.Vector ((!?), (!))
import Data.Vector.Mutable (write)
import qualified Data.Vector as V
import qualified Data.Map.Strict as M
data MultiZipper t a = MultiZipper (V.Vector a) Int (M.Map t Int)
deriving (Int -> MultiZipper t a -> ShowS
[MultiZipper t a] -> ShowS
MultiZipper t a -> String
(Int -> MultiZipper t a -> ShowS)
-> (MultiZipper t a -> String)
-> ([MultiZipper t a] -> ShowS)
-> Show (MultiZipper t a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall t a. (Show a, Show t) => Int -> MultiZipper t a -> ShowS
forall t a. (Show a, Show t) => [MultiZipper t a] -> ShowS
forall t a. (Show a, Show t) => MultiZipper t a -> String
$cshowsPrec :: forall t a. (Show a, Show t) => Int -> MultiZipper t a -> ShowS
showsPrec :: Int -> MultiZipper t a -> ShowS
$cshow :: forall t a. (Show a, Show t) => MultiZipper t a -> String
show :: MultiZipper t a -> String
$cshowList :: forall t a. (Show a, Show t) => [MultiZipper t a] -> ShowS
showList :: [MultiZipper t a] -> ShowS
Show, (forall a b. (a -> b) -> MultiZipper t a -> MultiZipper t b)
-> (forall a b. a -> MultiZipper t b -> MultiZipper t a)
-> Functor (MultiZipper t)
forall a b. a -> MultiZipper t b -> MultiZipper t a
forall a b. (a -> b) -> MultiZipper t a -> MultiZipper t b
forall t a b. a -> MultiZipper t b -> MultiZipper t a
forall t a b. (a -> b) -> MultiZipper t a -> MultiZipper t b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall t a b. (a -> b) -> MultiZipper t a -> MultiZipper t b
fmap :: forall a b. (a -> b) -> MultiZipper t a -> MultiZipper t b
$c<$ :: forall t a b. a -> MultiZipper t b -> MultiZipper t a
<$ :: forall a b. a -> MultiZipper t b -> MultiZipper t a
Functor, (forall m. Monoid m => MultiZipper t m -> m)
-> (forall m a. Monoid m => (a -> m) -> MultiZipper t a -> m)
-> (forall m a. Monoid m => (a -> m) -> MultiZipper t a -> m)
-> (forall a b. (a -> b -> b) -> b -> MultiZipper t a -> b)
-> (forall a b. (a -> b -> b) -> b -> MultiZipper t a -> b)
-> (forall b a. (b -> a -> b) -> b -> MultiZipper t a -> b)
-> (forall b a. (b -> a -> b) -> b -> MultiZipper t a -> b)
-> (forall a. (a -> a -> a) -> MultiZipper t a -> a)
-> (forall a. (a -> a -> a) -> MultiZipper t a -> a)
-> (forall a. MultiZipper t a -> [a])
-> (forall a. MultiZipper t a -> Bool)
-> (forall a. MultiZipper t a -> Int)
-> (forall a. Eq a => a -> MultiZipper t a -> Bool)
-> (forall a. Ord a => MultiZipper t a -> a)
-> (forall a. Ord a => MultiZipper t a -> a)
-> (forall a. Num a => MultiZipper t a -> a)
-> (forall a. Num a => MultiZipper t a -> a)
-> Foldable (MultiZipper t)
forall a. Eq a => a -> MultiZipper t a -> Bool
forall a. Num a => MultiZipper t a -> a
forall a. Ord a => MultiZipper t a -> a
forall m. Monoid m => MultiZipper t m -> m
forall a. MultiZipper t a -> Bool
forall a. MultiZipper t a -> Int
forall a. MultiZipper t a -> [a]
forall a. (a -> a -> a) -> MultiZipper t a -> a
forall t a. Eq a => a -> MultiZipper t a -> Bool
forall t a. Num a => MultiZipper t a -> a
forall t a. Ord a => MultiZipper t a -> a
forall m a. Monoid m => (a -> m) -> MultiZipper t a -> m
forall t m. Monoid m => MultiZipper t m -> m
forall t a. MultiZipper t a -> Bool
forall t a. MultiZipper t a -> Int
forall t a. MultiZipper t a -> [a]
forall b a. (b -> a -> b) -> b -> MultiZipper t a -> b
forall a b. (a -> b -> b) -> b -> MultiZipper t a -> b
forall t a. (a -> a -> a) -> MultiZipper t a -> a
forall t m a. Monoid m => (a -> m) -> MultiZipper t a -> m
forall t b a. (b -> a -> b) -> b -> MultiZipper t a -> b
forall t a b. (a -> b -> b) -> b -> MultiZipper t a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall t m. Monoid m => MultiZipper t m -> m
fold :: forall m. Monoid m => MultiZipper t m -> m
$cfoldMap :: forall t m a. Monoid m => (a -> m) -> MultiZipper t a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> MultiZipper t a -> m
$cfoldMap' :: forall t m a. Monoid m => (a -> m) -> MultiZipper t a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> MultiZipper t a -> m
$cfoldr :: forall t a b. (a -> b -> b) -> b -> MultiZipper t a -> b
foldr :: forall a b. (a -> b -> b) -> b -> MultiZipper t a -> b
$cfoldr' :: forall t a b. (a -> b -> b) -> b -> MultiZipper t a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> MultiZipper t a -> b
$cfoldl :: forall t b a. (b -> a -> b) -> b -> MultiZipper t a -> b
foldl :: forall b a. (b -> a -> b) -> b -> MultiZipper t a -> b
$cfoldl' :: forall t b a. (b -> a -> b) -> b -> MultiZipper t a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> MultiZipper t a -> b
$cfoldr1 :: forall t a. (a -> a -> a) -> MultiZipper t a -> a
foldr1 :: forall a. (a -> a -> a) -> MultiZipper t a -> a
$cfoldl1 :: forall t a. (a -> a -> a) -> MultiZipper t a -> a
foldl1 :: forall a. (a -> a -> a) -> MultiZipper t a -> a
$ctoList :: forall t a. MultiZipper t a -> [a]
toList :: forall a. MultiZipper t a -> [a]
$cnull :: forall t a. MultiZipper t a -> Bool
null :: forall a. MultiZipper t a -> Bool
$clength :: forall t a. MultiZipper t a -> Int
length :: forall a. MultiZipper t a -> Int
$celem :: forall t a. Eq a => a -> MultiZipper t a -> Bool
elem :: forall a. Eq a => a -> MultiZipper t a -> Bool
$cmaximum :: forall t a. Ord a => MultiZipper t a -> a
maximum :: forall a. Ord a => MultiZipper t a -> a
$cminimum :: forall t a. Ord a => MultiZipper t a -> a
minimum :: forall a. Ord a => MultiZipper t a -> a
$csum :: forall t a. Num a => MultiZipper t a -> a
sum :: forall a. Num a => MultiZipper t a -> a
$cproduct :: forall t a. Num a => MultiZipper t a -> a
product :: forall a. Num a => MultiZipper t a -> a
Foldable, Functor (MultiZipper t)
Foldable (MultiZipper t)
(Functor (MultiZipper t), Foldable (MultiZipper t)) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> MultiZipper t a -> f (MultiZipper t b))
-> (forall (f :: * -> *) a.
Applicative f =>
MultiZipper t (f a) -> f (MultiZipper t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> MultiZipper t a -> m (MultiZipper t b))
-> (forall (m :: * -> *) a.
Monad m =>
MultiZipper t (m a) -> m (MultiZipper t a))
-> Traversable (MultiZipper t)
forall t. Functor (MultiZipper t)
forall t. Foldable (MultiZipper t)
forall t (m :: * -> *) a.
Monad m =>
MultiZipper t (m a) -> m (MultiZipper t a)
forall t (f :: * -> *) a.
Applicative f =>
MultiZipper t (f a) -> f (MultiZipper t a)
forall t (m :: * -> *) a b.
Monad m =>
(a -> m b) -> MultiZipper t a -> m (MultiZipper t b)
forall t (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> MultiZipper t a -> f (MultiZipper t b)
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
MultiZipper t (m a) -> m (MultiZipper t a)
forall (f :: * -> *) a.
Applicative f =>
MultiZipper t (f a) -> f (MultiZipper t a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> MultiZipper t a -> m (MultiZipper t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> MultiZipper t a -> f (MultiZipper t b)
$ctraverse :: forall t (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> MultiZipper t a -> f (MultiZipper t b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> MultiZipper t a -> f (MultiZipper t b)
$csequenceA :: forall t (f :: * -> *) a.
Applicative f =>
MultiZipper t (f a) -> f (MultiZipper t a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
MultiZipper t (f a) -> f (MultiZipper t a)
$cmapM :: forall t (m :: * -> *) a b.
Monad m =>
(a -> m b) -> MultiZipper t a -> m (MultiZipper t b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> MultiZipper t a -> m (MultiZipper t b)
$csequence :: forall t (m :: * -> *) a.
Monad m =>
MultiZipper t (m a) -> m (MultiZipper t a)
sequence :: forall (m :: * -> *) a.
Monad m =>
MultiZipper t (m a) -> m (MultiZipper t a)
Traversable)
fromListStart :: [a] -> MultiZipper t a
fromListStart :: forall a t. [a] -> MultiZipper t a
fromListStart [a]
as = Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper ([a] -> Vector a
forall a. [a] -> Vector a
V.fromList [a]
as) Int
0 Map t Int
forall k a. Map k a
M.empty
fromListPos :: [a] -> Int -> Maybe (MultiZipper t a)
fromListPos :: forall a t. [a] -> Int -> Maybe (MultiZipper t a)
fromListPos [a]
as Int
pos =
if Int -> Int -> Bool
invalid Int
pos ([a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
as)
then Maybe (MultiZipper t a)
forall a. Maybe a
Nothing
else MultiZipper t a -> Maybe (MultiZipper t a)
forall a. a -> Maybe a
Just (MultiZipper t a -> Maybe (MultiZipper t a))
-> MultiZipper t a -> Maybe (MultiZipper t a)
forall a b. (a -> b) -> a -> b
$ Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper ([a] -> Vector a
forall a. [a] -> Vector a
V.fromList [a]
as) Int
pos Map t Int
forall k a. Map k a
M.empty
toList :: MultiZipper t a -> [a]
toList :: forall t a. MultiZipper t a -> [a]
toList (MultiZipper Vector a
as Int
_ Map t Int
_) = Vector a -> [a]
forall a. Vector a -> [a]
V.toList Vector a
as
reverseMZ :: MultiZipper t a -> MultiZipper t a
reverseMZ :: forall t a. MultiZipper t a -> MultiZipper t a
reverseMZ (MultiZipper Vector a
as Int
pos Map t Int
ts) =
let l :: Int
l = Vector a -> Int
forall a. Vector a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Vector a
as
in Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper
(Vector a -> Vector a
forall a. Vector a -> Vector a
V.reverse Vector a
as)
(Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
pos)
((Int -> Int) -> Map t Int -> Map t Int
forall a b k. (a -> b) -> Map k a -> Map k b
M.map (Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
-) Map t Int
ts)
curPos :: MultiZipper t a -> Int
curPos :: forall t a. MultiZipper t a -> Int
curPos (MultiZipper Vector a
_ Int
pos Map t Int
_) = Int
pos
atStart :: MultiZipper t a -> Bool
atStart :: forall t a. MultiZipper t a -> Bool
atStart (MultiZipper Vector a
_ Int
pos Map t Int
_) = Int
pos Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0
atEnd :: MultiZipper t a -> Bool
atEnd :: forall t a. MultiZipper t a -> Bool
atEnd (MultiZipper Vector a
as Int
pos Map t Int
_) = Int
pos Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Vector a -> Int
forall a. Vector a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Vector a
as
atBoundary :: MultiZipper t a -> Bool
atBoundary :: forall t a. MultiZipper t a -> Bool
atBoundary = Bool -> Bool -> Bool
(||) (Bool -> Bool -> Bool)
-> (MultiZipper t a -> Bool) -> MultiZipper t a -> Bool -> Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MultiZipper t a -> Bool
forall t a. MultiZipper t a -> Bool
atStart (MultiZipper t a -> Bool -> Bool)
-> (MultiZipper t a -> Bool) -> MultiZipper t a -> Bool
forall a b.
(MultiZipper t a -> a -> b)
-> (MultiZipper t a -> a) -> MultiZipper t a -> b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MultiZipper t a -> Bool
forall t a. MultiZipper t a -> Bool
atEnd
value :: MultiZipper t a -> Maybe a
value :: forall t a. MultiZipper t a -> Maybe a
value (MultiZipper Vector a
as Int
pos Map t Int
_) = Vector a
as Vector a -> Int -> Maybe a
forall a. Vector a -> Int -> Maybe a
!? Int
pos
valueN :: Int -> MultiZipper t a -> Maybe ([a], MultiZipper t a)
valueN :: forall t a. Int -> MultiZipper t a -> Maybe ([a], MultiZipper t a)
valueN Int
i (MultiZipper Vector a
as Int
pos Map t Int
ts) =
let pos' :: Int
pos' = Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i in
if Int -> Int -> Bool
invalid Int
pos' (Vector a -> Int
forall a. Vector a -> Int
V.length Vector a
as) Bool -> Bool -> Bool
|| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0
then Maybe ([a], MultiZipper t a)
forall a. Maybe a
Nothing
else ([a], MultiZipper t a) -> Maybe ([a], MultiZipper t a)
forall a. a -> Maybe a
Just (Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take Int
i ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
drop Int
pos ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ Vector a -> [a]
forall a. Vector a -> [a]
V.toList Vector a
as, Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper Vector a
as Int
pos' Map t Int
ts)
locationOf :: Ord t => t -> MultiZipper t a -> Maybe Int
locationOf :: forall t a. Ord t => t -> MultiZipper t a -> Maybe Int
locationOf t
t (MultiZipper Vector a
_ Int
_ Map t Int
ts) = t -> Map t Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup t
t Map t Int
ts
query :: Ord t => MultiZipper t a -> [t]
query :: forall t a. Ord t => MultiZipper t a -> [t]
query (MultiZipper Vector a
_ Int
pos Map t Int
ts) = Map t Int -> [t]
forall k a. Map k a -> [k]
M.keys (Map t Int -> [t]) -> Map t Int -> [t]
forall a b. (a -> b) -> a -> b
$ (Int -> Bool) -> Map t Int -> Map t Int
forall a k. (a -> Bool) -> Map k a -> Map k a
M.filter (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
pos) Map t Int
ts
seekIx :: Int -> MultiZipper t a -> Maybe (MultiZipper t a)
seekIx :: forall t a. Int -> MultiZipper t a -> Maybe (MultiZipper t a)
seekIx Int
i (MultiZipper Vector a
as Int
_ Map t Int
ts) =
if Int -> Int -> Bool
invalid Int
i (Vector a -> Int
forall a. Vector a -> Int
V.length Vector a
as)
then Maybe (MultiZipper t a)
forall a. Maybe a
Nothing
else MultiZipper t a -> Maybe (MultiZipper t a)
forall a. a -> Maybe a
Just (Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper Vector a
as Int
i Map t Int
ts)
move :: Int -> MultiZipper t a -> Maybe (MultiZipper t a)
move :: forall t a. Int -> MultiZipper t a -> Maybe (MultiZipper t a)
move Int
s mz :: MultiZipper t a
mz@(MultiZipper Vector a
_ Int
pos Map t Int
_) = Int -> MultiZipper t a -> Maybe (MultiZipper t a)
forall t a. Int -> MultiZipper t a -> Maybe (MultiZipper t a)
seekIx (Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
s) MultiZipper t a
mz
fwd :: MultiZipper t a -> Maybe (MultiZipper t a)
fwd :: forall t a. MultiZipper t a -> Maybe (MultiZipper t a)
fwd = Int -> MultiZipper t a -> Maybe (MultiZipper t a)
forall t a. Int -> MultiZipper t a -> Maybe (MultiZipper t a)
move Int
1
bwd :: MultiZipper t a -> Maybe (MultiZipper t a)
bwd :: forall t a. MultiZipper t a -> Maybe (MultiZipper t a)
bwd = Int -> MultiZipper t a -> Maybe (MultiZipper t a)
forall t a. Int -> MultiZipper t a -> Maybe (MultiZipper t a)
move (-Int
1)
consume :: MultiZipper t a -> Maybe (a, MultiZipper t a)
consume :: forall t a. MultiZipper t a -> Maybe (a, MultiZipper t a)
consume (MultiZipper Vector a
as Int
pos Map t Int
ts) =
(a -> (a, MultiZipper t a))
-> Maybe a -> Maybe (a, MultiZipper t a)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (,Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper Vector a
as (Int
posInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Map t Int
ts) (Vector a
asVector a -> Int -> Maybe a
forall a. Vector a -> Int -> Maybe a
!?Int
pos)
seek :: Ord t => t -> MultiZipper t a -> Maybe (MultiZipper t a)
seek :: forall t a.
Ord t =>
t -> MultiZipper t a -> Maybe (MultiZipper t a)
seek t
t (MultiZipper Vector a
as Int
_ Map t Int
ts) = case t -> Map t Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup t
t Map t Int
ts of
Maybe Int
Nothing -> Maybe (MultiZipper t a)
forall a. Maybe a
Nothing
Just Int
pos -> MultiZipper t a -> Maybe (MultiZipper t a)
forall a. a -> Maybe a
Just (MultiZipper t a -> Maybe (MultiZipper t a))
-> MultiZipper t a -> Maybe (MultiZipper t a)
forall a b. (a -> b) -> a -> b
$ Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper Vector a
as Int
pos Map t Int
ts
toBeginning :: MultiZipper t a -> MultiZipper t a
toBeginning :: forall t a. MultiZipper t a -> MultiZipper t a
toBeginning (MultiZipper Vector a
as Int
_ Map t Int
ts) = Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper Vector a
as Int
0 Map t Int
ts
toEnd :: MultiZipper t a -> MultiZipper t a
toEnd :: forall t a. MultiZipper t a -> MultiZipper t a
toEnd (MultiZipper Vector a
as Int
_ Map t Int
ts) = Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper Vector a
as (Vector a -> Int
forall a. Vector a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Vector a
as) Map t Int
ts
yank :: (a -> Maybe b) -> MultiZipper t a -> Maybe b
yank :: forall a b t. (a -> Maybe b) -> MultiZipper t a -> Maybe b
yank a -> Maybe b
p MultiZipper t a
mz = MultiZipper t a -> Maybe (MultiZipper t a)
forall t a. MultiZipper t a -> Maybe (MultiZipper t a)
bwd MultiZipper t a
mz Maybe (MultiZipper t a) -> (MultiZipper t a -> Maybe b) -> Maybe b
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \MultiZipper t a
mz' -> (MultiZipper t a -> Maybe a
forall t a. MultiZipper t a -> Maybe a
value MultiZipper t a
mz' Maybe a -> (a -> Maybe b) -> Maybe b
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> Maybe b
p) Maybe b -> Maybe b -> Maybe b
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (a -> Maybe b) -> MultiZipper t a -> Maybe b
forall a b t. (a -> Maybe b) -> MultiZipper t a -> Maybe b
yank a -> Maybe b
p MultiZipper t a
mz'
insert :: a -> MultiZipper t a -> MultiZipper t a
insert :: forall a t. a -> MultiZipper t a -> MultiZipper t a
insert a
a (MultiZipper Vector a
as Int
pos Map t Int
ts) =
case Int -> Vector a -> (Vector a, Vector a)
forall a. Int -> Vector a -> (Vector a, Vector a)
V.splitAt Int
pos Vector a
as of
(Vector a
as1, Vector a
as2) -> Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper
(Vector a
as1 Vector a -> Vector a -> Vector a
forall a. Vector a -> Vector a -> Vector a
V.++ a -> Vector a -> Vector a
forall a. a -> Vector a -> Vector a
V.cons a
a Vector a
as2)
(Int
posInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
(Int -> (Int -> Int) -> Map t Int -> Map t Int
forall t. Int -> (Int -> Int) -> Map t Int -> Map t Int
correctIxsFrom Int
pos (Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Map t Int
ts)
insertMany :: [a] -> MultiZipper t a -> MultiZipper t a
insertMany :: forall a t. [a] -> MultiZipper t a -> MultiZipper t a
insertMany = (MultiZipper t a -> [a] -> MultiZipper t a)
-> [a] -> MultiZipper t a -> MultiZipper t a
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((MultiZipper t a -> [a] -> MultiZipper t a)
-> [a] -> MultiZipper t a -> MultiZipper t a)
-> (MultiZipper t a -> [a] -> MultiZipper t a)
-> [a]
-> MultiZipper t a
-> MultiZipper t a
forall a b. (a -> b) -> a -> b
$ (MultiZipper t a -> a -> MultiZipper t a)
-> MultiZipper t a -> [a] -> MultiZipper t a
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ((MultiZipper t a -> a -> MultiZipper t a)
-> MultiZipper t a -> [a] -> MultiZipper t a)
-> (MultiZipper t a -> a -> MultiZipper t a)
-> MultiZipper t a
-> [a]
-> MultiZipper t a
forall a b. (a -> b) -> a -> b
$ (a -> MultiZipper t a -> MultiZipper t a)
-> MultiZipper t a -> a -> MultiZipper t a
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> MultiZipper t a -> MultiZipper t a
forall a t. a -> MultiZipper t a -> MultiZipper t a
insert
zap :: (a -> Maybe a) -> MultiZipper t a -> MultiZipper t a
zap :: forall a t. (a -> Maybe a) -> MultiZipper t a -> MultiZipper t a
zap a -> Maybe a
p = \mz :: MultiZipper t a
mz@(MultiZipper Vector a
as Int
pos Map t Int
ts) -> case Vector a -> Int -> Maybe (Vector a)
go Vector a
as (Int
posInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) of
Maybe (Vector a)
Nothing -> MultiZipper t a
mz
Just Vector a
as' -> Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper Vector a
as' Int
pos Map t Int
ts
where
go :: Vector a -> Int -> Maybe (Vector a)
go Vector a
_ (-1) = Maybe (Vector a)
forall a. Maybe a
Nothing
go Vector a
as Int
pos
| Int
pos Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Vector a -> Int
forall a. Vector a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Vector a
as = Vector a -> Int -> Maybe (Vector a)
go Vector a
as (Int
posInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
| Bool
otherwise = case a -> Maybe a
p (Vector a
as Vector a -> Int -> a
forall a. Vector a -> Int -> a
! Int
pos) of
Maybe a
Nothing -> Vector a -> Int -> Maybe (Vector a)
go Vector a
as (Int
posInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
Just a
a' -> Vector a -> Maybe (Vector a)
forall a. a -> Maybe a
Just (Vector a -> Maybe (Vector a)) -> Vector a -> Maybe (Vector a)
forall a b. (a -> b) -> a -> b
$ (forall s. MVector s a -> ST s ()) -> Vector a -> Vector a
forall a.
(forall s. MVector s a -> ST s ()) -> Vector a -> Vector a
V.modify (\MVector s a
v -> MVector (PrimState (ST s)) a -> Int -> a -> ST s ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> a -> m ()
write MVector s a
MVector (PrimState (ST s)) a
v Int
pos a
a') Vector a
as
tag :: Ord t => t -> MultiZipper t a -> MultiZipper t a
tag :: forall t a. Ord t => t -> MultiZipper t a -> MultiZipper t a
tag t
t (MultiZipper Vector a
as Int
pos Map t Int
ts) = Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper Vector a
as Int
pos (Map t Int -> MultiZipper t a) -> Map t Int -> MultiZipper t a
forall a b. (a -> b) -> a -> b
$ t -> Int -> Map t Int -> Map t Int
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert t
t Int
pos Map t Int
ts
tagAt :: Ord t => t -> Int -> MultiZipper t a -> Maybe (MultiZipper t a)
tagAt :: forall t a.
Ord t =>
t -> Int -> MultiZipper t a -> Maybe (MultiZipper t a)
tagAt t
t Int
i (MultiZipper Vector a
as Int
pos Map t Int
ts) =
if Int -> Int -> Bool
invalid Int
i (Vector a -> Int
forall a. Vector a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Vector a
as)
then Maybe (MultiZipper t a)
forall a. Maybe a
Nothing
else MultiZipper t a -> Maybe (MultiZipper t a)
forall a. a -> Maybe a
Just (MultiZipper t a -> Maybe (MultiZipper t a))
-> MultiZipper t a -> Maybe (MultiZipper t a)
forall a b. (a -> b) -> a -> b
$ Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper Vector a
as Int
pos (Map t Int -> MultiZipper t a) -> Map t Int -> MultiZipper t a
forall a b. (a -> b) -> a -> b
$ t -> Int -> Map t Int -> Map t Int
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert t
t Int
i Map t Int
ts
untagWhen :: (t -> Bool) -> MultiZipper t a -> MultiZipper t a
untagWhen :: forall t a. (t -> Bool) -> MultiZipper t a -> MultiZipper t a
untagWhen t -> Bool
p (MultiZipper Vector a
as Int
pos Map t Int
ts) = Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper Vector a
as Int
pos (Map t Int -> MultiZipper t a) -> Map t Int -> MultiZipper t a
forall a b. (a -> b) -> a -> b
$ (Map t Int, Map t Int) -> Map t Int
forall a b. (a, b) -> b
snd ((Map t Int, Map t Int) -> Map t Int)
-> (Map t Int, Map t Int) -> Map t Int
forall a b. (a -> b) -> a -> b
$ (t -> Int -> Bool) -> Map t Int -> (Map t Int, Map t Int)
forall k a. (k -> a -> Bool) -> Map k a -> (Map k a, Map k a)
M.partitionWithKey ((Int -> t -> Bool) -> t -> Int -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((Int -> t -> Bool) -> t -> Int -> Bool)
-> (Int -> t -> Bool) -> t -> Int -> Bool
forall a b. (a -> b) -> a -> b
$ (t -> Bool) -> Int -> t -> Bool
forall a b. a -> b -> a
const t -> Bool
p) Map t Int
ts
untag :: MultiZipper t a -> MultiZipper t a
untag :: forall t a. MultiZipper t a -> MultiZipper t a
untag (MultiZipper Vector a
as Int
pos Map t Int
_) = Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper Vector a
as Int
pos Map t Int
forall k a. Map k a
M.empty
delete
:: Ord t
=> (t, t)
-> MultiZipper t a
-> Maybe (MultiZipper t a)
delete :: forall t a.
Ord t =>
(t, t) -> MultiZipper t a -> Maybe (MultiZipper t a)
delete (t
t1, t
t2) mz :: MultiZipper t a
mz@(MultiZipper Vector a
as Int
pos Map t Int
ts) = do
(Int
i1, Int
i2) <- ((Int, Int) -> (Int, Int)) -> Maybe (Int, Int) -> Maybe (Int, Int)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int, Int) -> (Int, Int)
forall {b}. Ord b => (b, b) -> (b, b)
correctOrder (Maybe (Int, Int) -> Maybe (Int, Int))
-> Maybe (Int, Int) -> Maybe (Int, Int)
forall a b. (a -> b) -> a -> b
$ (,) (Int -> Int -> (Int, Int))
-> Maybe Int -> Maybe (Int -> (Int, Int))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> t -> MultiZipper t a -> Maybe Int
forall t a. Ord t => t -> MultiZipper t a -> Maybe Int
locationOf t
t1 MultiZipper t a
mz Maybe (Int -> (Int, Int)) -> Maybe Int -> Maybe (Int, Int)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> t -> MultiZipper t a -> Maybe Int
forall t a. Ord t => t -> MultiZipper t a -> Maybe Int
locationOf t
t2 MultiZipper t a
mz
let (Vector a
before_t1, Vector a
after_t1) = Int -> Vector a -> (Vector a, Vector a)
forall a. Int -> Vector a -> (Vector a, Vector a)
V.splitAt Int
i1 Vector a
as
(Vector a
cut_part, Vector a
after_t2) = Int -> Vector a -> (Vector a, Vector a)
forall a. Int -> Vector a -> (Vector a, Vector a)
V.splitAt (Int
i2Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i1) Vector a
after_t1
removed :: Int
removed = Vector a -> Int
forall a. Vector a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Vector a
cut_part
pos' :: Int
pos' = Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
removed
MultiZipper t a -> Maybe (MultiZipper t a)
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (MultiZipper t a -> Maybe (MultiZipper t a))
-> MultiZipper t a -> Maybe (MultiZipper t a)
forall a b. (a -> b) -> a -> b
$ Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper (Vector a
before_t1 Vector a -> Vector a -> Vector a
forall a. Vector a -> Vector a -> Vector a
V.++ Vector a
after_t2) Int
pos' (Int -> (Int -> Int) -> Map t Int -> Map t Int
forall t. Int -> (Int -> Int) -> Map t Int -> Map t Int
correctIxsFrom Int
i2 (Int -> Int -> Int
forall a. Num a => a -> a -> a
subtract Int
removed) Map t Int
ts)
where
correctOrder :: (b, b) -> (b, b)
correctOrder (b
m, b
n) = if b
m b -> b -> Bool
forall a. Ord a => a -> a -> Bool
<= b
n then (b
m, b
n) else (b
n, b
m)
extend :: (MultiZipper t a -> b) -> MultiZipper t a -> MultiZipper t b
extend :: forall t a b.
(MultiZipper t a -> b) -> MultiZipper t a -> MultiZipper t b
extend MultiZipper t a -> b
f (MultiZipper Vector a
as Int
pos Map t Int
ts) = Vector b -> Int -> Map t Int -> MultiZipper t b
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper Vector b
as' Int
pos Map t Int
ts
where
as' :: Vector b
as' = (Int -> b) -> Vector Int -> Vector b
forall a b. (a -> b) -> Vector a -> Vector b
V.map (\Int
i -> MultiZipper t a -> b
f (MultiZipper t a -> b) -> MultiZipper t a -> b
forall a b. (a -> b) -> a -> b
$ Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper Vector a
as Int
i Map t Int
ts) (Vector Int -> Vector b) -> Vector Int -> Vector b
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector Int
forall a. Num a => a -> Int -> Vector a
V.enumFromN Int
0 (Vector a -> Int
forall a. Vector a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Vector a
as)
extend' :: (MultiZipper t a -> b) -> MultiZipper t a -> MultiZipper t b
extend' :: forall t a b.
(MultiZipper t a -> b) -> MultiZipper t a -> MultiZipper t b
extend' MultiZipper t a -> b
f (MultiZipper Vector a
as Int
pos Map t Int
ts) = Vector b -> Int -> Map t Int -> MultiZipper t b
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper Vector b
as' Int
pos Map t Int
ts
where
as' :: Vector b
as' = (Int -> b) -> Vector Int -> Vector b
forall a b. (a -> b) -> Vector a -> Vector b
V.map (\Int
i -> MultiZipper t a -> b
f (MultiZipper t a -> b) -> MultiZipper t a -> b
forall a b. (a -> b) -> a -> b
$ Vector a -> Int -> Map t Int -> MultiZipper t a
forall t a. Vector a -> Int -> Map t Int -> MultiZipper t a
MultiZipper Vector a
as Int
i Map t Int
ts) (Vector Int -> Vector b) -> Vector Int -> Vector b
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector Int
forall a. Num a => a -> Int -> Vector a
V.enumFromN Int
0 (Vector a -> Int
forall a. Vector a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Vector a
as Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
invalid :: Int -> Int -> Bool
invalid :: Int -> Int -> Bool
invalid Int
pos Int
len = (Int
pos Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0) Bool -> Bool -> Bool
|| (Int
pos Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
len)
correctIxsFrom :: Int -> (Int -> Int) -> M.Map t Int -> M.Map t Int
correctIxsFrom :: forall t. Int -> (Int -> Int) -> Map t Int -> Map t Int
correctIxsFrom Int
i Int -> Int
f = (Int -> Int) -> Map t Int -> Map t Int
forall a b k. (a -> b) -> Map k a -> Map k b
M.map ((Int -> Int) -> Map t Int -> Map t Int)
-> (Int -> Int) -> Map t Int -> Map t Int
forall a b. (a -> b) -> a -> b
$ \Int
pos -> if Int
pos Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
i then Int -> Int
f Int
pos else Int
pos