module Data.List.NonEmptyZipper where
import Data.List.NonEmpty (NonEmpty (..))
import Data.Semigroup
data NonEmptyZipper a = NonEmptyZipper
{ _before :: ![a]
, _current :: !a
, _after :: ![a] }
deriving (Show, Eq, Ord)
before :: Functor f => ([a] -> f [a]) -> NonEmptyZipper a -> f (NonEmptyZipper a)
before f x = (\c' -> x { _before = c' }) <$> f (_before x)
current :: Functor f => (a -> f a) -> NonEmptyZipper a -> f (NonEmptyZipper a)
current f x = (\c' -> x { _current = c' }) <$> f (_current x)
after :: Functor f => ([a] -> f [a]) -> NonEmptyZipper a -> f (NonEmptyZipper a)
after f x = (\c' -> x { _after = c' }) <$> f (_after x)
instance Functor NonEmptyZipper where
fmap f (NonEmptyZipper xs y zs) =
NonEmptyZipper (f <$> xs) (f y) (f <$> zs)
instance Applicative NonEmptyZipper where
pure x = NonEmptyZipper [x] x [x]
NonEmptyZipper fxs fy fzs <*> NonEmptyZipper xs y zs =
NonEmptyZipper (fxs <*> xs) (fy y) (fzs <*> zs)
next :: NonEmptyZipper a -> NonEmptyZipper a
next (NonEmptyZipper xs y (z:zs)) =
NonEmptyZipper (xs <> [y]) z zs
next z = z
nextMod :: NonEmptyZipper a -> NonEmptyZipper a
nextMod (NonEmptyZipper (x:xs) y []) =
NonEmptyZipper [] x (xs <> [y])
nextMod z = next z
previous :: NonEmptyZipper a -> NonEmptyZipper a
previous (NonEmptyZipper xs y zs) | not (null xs) =
NonEmptyZipper (Prelude.init xs) (Prelude.last xs) (y:zs)
previous z = z
previousMod :: NonEmptyZipper a -> NonEmptyZipper a
previousMod (NonEmptyZipper [] y zs) | not (null zs) =
NonEmptyZipper (y:Prelude.init zs) (Prelude.last zs) []
previousMod z = previous z
toList :: NonEmptyZipper a -> [a]
toList (NonEmptyZipper xs y zs) = xs <> (y:zs)
fromNonEmpty :: NonEmpty a -> NonEmptyZipper a
fromNonEmpty (x :| xs) = NonEmptyZipper [] x xs
inTheBeginning :: NonEmptyZipper a -> Bool
inTheBeginning (NonEmptyZipper [] _ _) = True
inTheBeginning _ = False
inTheEnd :: NonEmptyZipper a -> Bool
inTheEnd (NonEmptyZipper _ _ []) = True
inTheEnd _ = False
getPosition :: NonEmptyZipper a -> Int
getPosition (NonEmptyZipper xs _ _) = Prelude.length xs
length :: NonEmptyZipper a -> Int
length (NonEmptyZipper xs _ zs) = Prelude.length xs + 1 + Prelude.length zs
instance Semigroup (NonEmptyZipper a) where
NonEmptyZipper xs y zs <> z =
NonEmptyZipper xs y $ zs <> toList z
head :: NonEmptyZipper a -> a
head = \case
NonEmptyZipper [] x _ -> x
NonEmptyZipper (x:_) _ _ -> x
init :: NonEmptyZipper a -> Maybe (NonEmptyZipper a)
init = \case
NonEmptyZipper [] _ [] -> Nothing
NonEmptyZipper xs _ [] ->
Just $ NonEmptyZipper (Prelude.init xs) (Prelude.last xs) []
NonEmptyZipper xs y zs ->
Just $ NonEmptyZipper xs y (Prelude.init zs)
last :: NonEmptyZipper a -> a
last = \case
NonEmptyZipper _ x [] -> x
NonEmptyZipper _ _ xs -> Prelude.last xs
tail :: NonEmptyZipper a -> Maybe (NonEmptyZipper a)
tail = \case
NonEmptyZipper [] _ [] -> Nothing
NonEmptyZipper (_:xs) y zs -> Just $ NonEmptyZipper xs y zs
NonEmptyZipper _ _ (z:zs) -> Just $ NonEmptyZipper [] z zs
reverse :: NonEmptyZipper a -> NonEmptyZipper a
reverse (NonEmptyZipper xs y zs) =
NonEmptyZipper (Prelude.reverse zs) y (Prelude.reverse xs)
cons :: a -> NonEmptyZipper a -> NonEmptyZipper a
cons x (NonEmptyZipper xs y zs) = NonEmptyZipper (x:xs) y zs
wrap :: a -> NonEmptyZipper a
wrap x = NonEmptyZipper [] x []