module Data.List.Zipper where import Control.Monad (liftM2) import Test.QuickCheck (Arbitrary(..)) data Zipper a = Zip ![a] ![a] deriving (Eq,Show) instance Arbitrary a => Arbitrary (Zipper a) where arbitrary = liftM2 Zip arbitrary arbitrary coarbitrary (Zip ls rs) = coarbitrary rs . coarbitrary ls empty :: Zipper a empty = Zip [] [] fromList :: [a] -> Zipper a fromList as = Zip [] as fromListEnd :: [a] -> Zipper a fromListEnd as = Zip (reverse as) [] toList :: Zipper a -> [a] toList (Zip ls rs) = reverse ls ++ rs beginp, endp, emptyp :: Zipper a -> Bool beginp (Zip [] _ ) = True beginp _ = False endp (Zip _ []) = True endp _ = False emptyp (Zip [] []) = True emptyp _ = False -- | @cursor z@ returns the targeted element in @z@. -- -- This function is not total, but the invariant is that -- @endp z == False@ means that you can safely call -- @cursor z@. cursor :: Zipper a -> a cursor (Zip _ (a:_)) = a left, right :: Zipper a -> Zipper a left (Zip (a:ls) rs) = Zip ls (a:rs) left z = z right (Zip ls (a:rs)) = Zip (a:ls) rs right z = z insert, push :: a -> Zipper a -> Zipper a insert a (Zip ls rs) = Zip ls (a:rs) push a (Zip ls rs) = Zip (a:ls) rs delete, pop :: Zipper a -> Zipper a delete (Zip ls (_:rs)) = Zip ls rs delete z = z pop (Zip (_:ls) rs) = Zip ls rs pop z = z -- | @replace a z@ changes the current element in the zipper -- to the passed in value. If there is no current element, -- the zipper is unchanged. If you want to add the element -- in that case instead, use @insert a (delete z)@. replace :: a -> Zipper a -> Zipper a replace a (Zip ls (_:rs)) = Zip ls (a:rs) replace _ z = z