module Data.Text.Zipper
    ( TextZipper
    
    , mkZipper
    , textZipper
    , stringZipper
    , clearZipper
    , vectorZipper
    , getText
    , currentLine
    , cursorPosition
    , lineLengths
    , getLineLimit
    
    , moveCursor
    , moveRight
    , moveLeft
    , moveUp
    , moveDown
    , gotoEOL
    , gotoBOL
    , gotoEOF
    , gotoBOF
    
    , currentChar
    , nextChar
    , previousChar
    
    , insertChar
    , insertMany
    , deletePrevChar
    , deleteChar
    , breakLine
    , killToEOL
    , killToBOL
    , killToEOF
    , killToBOF
    , transposeChars
    )
where
import Control.Applicative ((<$>))
import Control.DeepSeq
import Data.Char (isPrint)
import Data.Monoid
import qualified Data.Text as T
import qualified Data.Vector as V
import qualified Data.Text.Zipper.Vector as V
data TextZipper a =
    TZ { TextZipper a -> a
toLeft :: a
       , TextZipper a -> a
toRight :: a
       , TextZipper a -> [a]
above :: [a]
       , TextZipper a -> [a]
below :: [a]
       , TextZipper a -> Char -> a
fromChar :: Char -> a
       , TextZipper a -> Int -> a -> a
drop_ :: Int -> a -> a
       , TextZipper a -> Int -> a -> a
take_ :: Int -> a -> a
       , TextZipper a -> a -> Int
length_ :: a -> Int
       , TextZipper a -> a -> Char
last_ :: a -> Char
       , TextZipper a -> a -> a
init_ :: a -> a
       , TextZipper a -> a -> Bool
null_ :: a -> Bool
       , TextZipper a -> a -> [a]
lines_ :: a -> [a]
       , TextZipper a -> a -> [Char]
toList_ :: a -> [Char]
       , TextZipper a -> Maybe Int
lineLimit :: Maybe Int
       }
instance (NFData a) => NFData (TextZipper a) where
    rnf :: TextZipper a -> ()
rnf TextZipper a
z = (TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
z) a -> a -> a
forall a b. NFData a => a -> b -> b
`deepseq`
            (TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
z) a -> [a] -> [a]
forall a b. NFData a => a -> b -> b
`deepseq`
            (TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
z) [a] -> [a] -> [a]
forall a b. NFData a => a -> b -> b
`deepseq`
            (TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
z) [a] -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq`
            ()
getLineLimit :: TextZipper a -> Maybe Int
getLineLimit :: TextZipper a -> Maybe Int
getLineLimit = TextZipper a -> Maybe Int
forall a. TextZipper a -> Maybe Int
lineLimit
instance (Eq a) => Eq (TextZipper a) where
    TextZipper a
a == :: TextZipper a -> TextZipper a -> Bool
== TextZipper a
b = [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and [ TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
a a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
b
                 , TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
a a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
b
                 , TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
a [a] -> [a] -> Bool
forall a. Eq a => a -> a -> Bool
== TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
b
                 , TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
a [a] -> [a] -> Bool
forall a. Eq a => a -> a -> Bool
== TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
b
                 ]
instance (Show a) => Show (TextZipper a) where
    show :: TextZipper a -> [Char]
show TextZipper a
tz = [[Char]] -> [Char]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [Char]
"TextZipper { "
                     , [Char]
"above = "
                     , [a] -> [Char]
forall a. Show a => a -> [Char]
show ([a] -> [Char]) -> [a] -> [Char]
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz
                     , [Char]
", below = "
                     , [a] -> [Char]
forall a. Show a => a -> [Char]
show ([a] -> [Char]) -> [a] -> [Char]
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
tz
                     , [Char]
", toLeft = "
                     , a -> [Char]
forall a. Show a => a -> [Char]
show (a -> [Char]) -> a -> [Char]
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz
                     , [Char]
", toRight = "
                     , a -> [Char]
forall a. Show a => a -> [Char]
show (a -> [Char]) -> a -> [Char]
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
tz
                     , [Char]
" }"
                     ]
mkZipper :: (Monoid a) =>
            (Char -> a)
         
         -> (Int -> a -> a)
         
         -> (Int -> a -> a)
         
         -> (a -> Int)
         
         -> (a -> Char)
         
         -> (a -> a)
         
         -> (a -> Bool)
         
         -> (a -> [a])
         
         -> (a -> [Char])
         
         -> [a]
         
         -> Maybe Int
         
         -> TextZipper a
mkZipper :: (Char -> a)
-> (Int -> a -> a)
-> (Int -> a -> a)
-> (a -> Int)
-> (a -> Char)
-> (a -> a)
-> (a -> Bool)
-> (a -> [a])
-> (a -> [Char])
-> [a]
-> Maybe Int
-> TextZipper a
mkZipper Char -> a
fromCh Int -> a -> a
drp Int -> a -> a
tk a -> Int
lngth a -> Char
lst a -> a
int a -> Bool
nl a -> [a]
linesFunc a -> [Char]
toListF [a]
ls Maybe Int
lmt =
    let limitedLs :: [a]
limitedLs = case Maybe Int
lmt of
          Maybe Int
Nothing -> [a]
ls
          Just Int
n -> Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take Int
n [a]
ls
        (a
first, [a]
rest) = if [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
limitedLs
                        then (a
forall a. Monoid a => a
mempty, [a]
forall a. Monoid a => a
mempty)
                        else ([a] -> a
forall a. [a] -> a
head [a]
limitedLs, [a] -> [a]
forall a. [a] -> [a]
tail [a]
limitedLs)
    in a
-> a
-> [a]
-> [a]
-> (Char -> a)
-> (Int -> a -> a)
-> (Int -> a -> a)
-> (a -> Int)
-> (a -> Char)
-> (a -> a)
-> (a -> Bool)
-> (a -> [a])
-> (a -> [Char])
-> Maybe Int
-> TextZipper a
forall a.
a
-> a
-> [a]
-> [a]
-> (Char -> a)
-> (Int -> a -> a)
-> (Int -> a -> a)
-> (a -> Int)
-> (a -> Char)
-> (a -> a)
-> (a -> Bool)
-> (a -> [a])
-> (a -> [Char])
-> Maybe Int
-> TextZipper a
TZ a
forall a. Monoid a => a
mempty a
first [] [a]
rest Char -> a
fromCh Int -> a -> a
drp Int -> a -> a
tk a -> Int
lngth a -> Char
lst a -> a
int a -> Bool
nl a -> [a]
linesFunc a -> [Char]
toListF Maybe Int
lmt
getText :: (Monoid a) => TextZipper a -> [a]
getText :: TextZipper a -> [a]
getText TextZipper a
tz = [[a]] -> [a]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz
                    , [TextZipper a -> a
forall a. Monoid a => TextZipper a -> a
currentLine TextZipper a
tz]
                    , TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
tz
                    ]
lineLengths :: (Monoid a) => TextZipper a -> [Int]
lineLengths :: TextZipper a -> [Int]
lineLengths TextZipper a
tz = (TextZipper a -> a -> Int
forall a. TextZipper a -> a -> Int
length_ TextZipper a
tz) (a -> Int) -> [a] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[a]] -> [a]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz
                                         , [TextZipper a -> a
forall a. Monoid a => TextZipper a -> a
currentLine TextZipper a
tz]
                                         , TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
tz
                                         ]
cursorPosition :: TextZipper a -> (Int, Int)
cursorPosition :: TextZipper a -> (Int, Int)
cursorPosition TextZipper a
tz = ([a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([a] -> Int) -> [a] -> Int
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz, TextZipper a -> a -> Int
forall a. TextZipper a -> a -> Int
length_ TextZipper a
tz (a -> Int) -> a -> Int
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz)
moveCursor :: (Monoid a) => (Int, Int) -> TextZipper a -> TextZipper a
moveCursor :: (Int, Int) -> TextZipper a -> TextZipper a
moveCursor (Int
row, Int
col) TextZipper a
tz =
    let t :: [a]
t = TextZipper a -> [a]
forall a. Monoid a => TextZipper a -> [a]
getText TextZipper a
tz
    in if Int
row Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0
           Bool -> Bool -> Bool
|| Int
row Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
t
           Bool -> Bool -> Bool
|| Int
col Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0
           Bool -> Bool -> Bool
|| Int
col Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> TextZipper a -> a -> Int
forall a. TextZipper a -> a -> Int
length_ TextZipper a
tz ([a]
t [a] -> Int -> a
forall a. [a] -> Int -> a
!! Int
row)
       then TextZipper a
tz
       else TextZipper a
tz { above :: [a]
above = Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take Int
row [a]
t
               , below :: [a]
below = Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
drop (Int
row Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) [a]
t
               , toLeft :: a
toLeft = TextZipper a -> Int -> a -> a
forall a. TextZipper a -> Int -> a -> a
take_ TextZipper a
tz Int
col ([a]
t [a] -> Int -> a
forall a. [a] -> Int -> a
!! Int
row)
               , toRight :: a
toRight = TextZipper a -> Int -> a -> a
forall a. TextZipper a -> Int -> a -> a
drop_ TextZipper a
tz Int
col ([a]
t [a] -> Int -> a
forall a. [a] -> Int -> a
!! Int
row)
               }
isFirstLine :: TextZipper a -> Bool
isFirstLine :: TextZipper a -> Bool
isFirstLine = [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([a] -> Bool) -> (TextZipper a -> [a]) -> TextZipper a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextZipper a -> [a]
forall a. TextZipper a -> [a]
above
isLastLine :: TextZipper a -> Bool
isLastLine :: TextZipper a -> Bool
isLastLine = (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) (Int -> Bool) -> (TextZipper a -> Int) -> TextZipper a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([a] -> Int) -> (TextZipper a -> [a]) -> TextZipper a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextZipper a -> [a]
forall a. TextZipper a -> [a]
below
nextLine :: TextZipper a -> a
nextLine :: TextZipper a -> a
nextLine = [a] -> a
forall a. [a] -> a
head ([a] -> a) -> (TextZipper a -> [a]) -> TextZipper a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextZipper a -> [a]
forall a. TextZipper a -> [a]
below
currentLine :: (Monoid a) => TextZipper a -> a
currentLine :: TextZipper a -> a
currentLine TextZipper a
tz = (TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz) a -> a -> a
forall a. Monoid a => a -> a -> a
`mappend` (TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
tz)
insertChar :: (Monoid a) => Char -> TextZipper a -> TextZipper a
insertChar :: Char -> TextZipper a -> TextZipper a
insertChar Char
ch TextZipper a
tz = TextZipper a
-> (TextZipper a -> TextZipper a)
-> Maybe (TextZipper a)
-> TextZipper a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe TextZipper a
tz TextZipper a -> TextZipper a
forall a. a -> a
id (Maybe (TextZipper a) -> TextZipper a)
-> Maybe (TextZipper a) -> TextZipper a
forall a b. (a -> b) -> a -> b
$ Char -> TextZipper a -> Maybe (TextZipper a)
forall a. Monoid a => Char -> TextZipper a -> Maybe (TextZipper a)
insertChar_ Char
ch TextZipper a
tz
insertChar_ :: (Monoid a) => Char -> TextZipper a -> Maybe (TextZipper a)
insertChar_ :: Char -> TextZipper a -> Maybe (TextZipper a)
insertChar_ Char
ch TextZipper a
tz
    | Char
ch Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n' = TextZipper a -> Maybe (TextZipper a)
forall a. Monoid a => TextZipper a -> Maybe (TextZipper a)
breakLine_ TextZipper a
tz
    | Char -> Bool
isPrint Char
ch = TextZipper a -> Maybe (TextZipper a)
forall a. a -> Maybe a
Just (TextZipper a -> Maybe (TextZipper a))
-> TextZipper a -> Maybe (TextZipper a)
forall a b. (a -> b) -> a -> b
$ TextZipper a
tz { toLeft :: a
toLeft = TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz a -> a -> a
forall a. Monoid a => a -> a -> a
`mappend` (TextZipper a -> Char -> a
forall a. TextZipper a -> Char -> a
fromChar TextZipper a
tz Char
ch) }
    | Bool
otherwise  = Maybe (TextZipper a)
forall a. Maybe a
Nothing
insertMany :: (Monoid a) => a -> TextZipper a -> TextZipper a
insertMany :: a -> TextZipper a -> TextZipper a
insertMany a
str TextZipper a
tz =
    let go :: [Char] -> TextZipper a -> TextZipper a
go [] TextZipper a
z = TextZipper a
z
        go (Char
c:[Char]
cs) TextZipper a
z = TextZipper a
-> (TextZipper a -> TextZipper a)
-> Maybe (TextZipper a)
-> TextZipper a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe TextZipper a
z ([Char] -> TextZipper a -> TextZipper a
go [Char]
cs) (Maybe (TextZipper a) -> TextZipper a)
-> Maybe (TextZipper a) -> TextZipper a
forall a b. (a -> b) -> a -> b
$ Char -> TextZipper a -> Maybe (TextZipper a)
forall a. Monoid a => Char -> TextZipper a -> Maybe (TextZipper a)
insertChar_ Char
c TextZipper a
z
    in [Char] -> TextZipper a -> TextZipper a
forall a. Monoid a => [Char] -> TextZipper a -> TextZipper a
go (TextZipper a -> a -> [Char]
forall a. TextZipper a -> a -> [Char]
toList_ TextZipper a
tz a
str) TextZipper a
tz
breakLine :: (Monoid a) => TextZipper a -> TextZipper a
breakLine :: TextZipper a -> TextZipper a
breakLine TextZipper a
tz = TextZipper a
-> (TextZipper a -> TextZipper a)
-> Maybe (TextZipper a)
-> TextZipper a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe TextZipper a
tz TextZipper a -> TextZipper a
forall a. a -> a
id (Maybe (TextZipper a) -> TextZipper a)
-> Maybe (TextZipper a) -> TextZipper a
forall a b. (a -> b) -> a -> b
$ TextZipper a -> Maybe (TextZipper a)
forall a. Monoid a => TextZipper a -> Maybe (TextZipper a)
breakLine_ TextZipper a
tz
breakLine_ :: (Monoid a) => TextZipper a -> Maybe (TextZipper a)
breakLine_ :: TextZipper a -> Maybe (TextZipper a)
breakLine_ TextZipper a
tz =
    
    
    
    let modified :: TextZipper a
modified = TextZipper a
tz { above :: [a]
above = TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz]
                      , toLeft :: a
toLeft = a
forall a. Monoid a => a
mempty
                      }
    in case TextZipper a -> Maybe Int
forall a. TextZipper a -> Maybe Int
lineLimit TextZipper a
tz of
          Just Int
lim -> if [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
tz) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
lim
                      then Maybe (TextZipper a)
forall a. Maybe a
Nothing
                      else TextZipper a -> Maybe (TextZipper a)
forall a. a -> Maybe a
Just TextZipper a
modified
          Maybe Int
Nothing -> TextZipper a -> Maybe (TextZipper a)
forall a. a -> Maybe a
Just TextZipper a
modified
gotoEOL :: (Monoid a) => TextZipper a -> TextZipper a
gotoEOL :: TextZipper a -> TextZipper a
gotoEOL TextZipper a
tz = TextZipper a
tz { toLeft :: a
toLeft = TextZipper a -> a
forall a. Monoid a => TextZipper a -> a
currentLine TextZipper a
tz
                , toRight :: a
toRight = a
forall a. Monoid a => a
mempty
                }
gotoEOF :: (Monoid a) => TextZipper a -> TextZipper a
gotoEOF :: TextZipper a -> TextZipper a
gotoEOF TextZipper a
tz =
    TextZipper a
tz { toLeft :: a
toLeft = a
end
       , toRight :: a
toRight = a
forall a. Monoid a => a
mempty
       , above :: [a]
above = [a]
top
       , below :: [a]
below = [a]
forall a. Monoid a => a
mempty
       }
   where
       tx :: [a]
tx = TextZipper a -> [a]
forall a. Monoid a => TextZipper a -> [a]
getText TextZipper a
tz
       ([a]
top, a
end) = if [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
tx
                    then ([a]
forall a. Monoid a => a
mempty, a
forall a. Monoid a => a
mempty)
                    else ([a] -> [a]
forall a. [a] -> [a]
init [a]
tx, [a] -> a
forall a. [a] -> a
last [a]
tx)
killToEOL :: (Monoid a) => TextZipper a -> TextZipper a
killToEOL :: TextZipper a -> TextZipper a
killToEOL TextZipper a
tz
    | (TextZipper a -> a -> Bool
forall a. TextZipper a -> a -> Bool
null_ TextZipper a
tz (a -> Bool) -> a -> Bool
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz) Bool -> Bool -> Bool
&& (TextZipper a -> a -> Bool
forall a. TextZipper a -> a -> Bool
null_ TextZipper a
tz (a -> Bool) -> a -> Bool
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
tz) Bool -> Bool -> Bool
&&
      (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([a] -> Bool) -> [a] -> Bool
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
tz) =
          TextZipper a
tz { toRight :: a
toRight = [a] -> a
forall a. [a] -> a
head ([a] -> a) -> [a] -> a
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
tz
             , below :: [a]
below = [a] -> [a]
forall a. [a] -> [a]
tail ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
tz
             }
    | Bool
otherwise = TextZipper a
tz { toRight :: a
toRight = a
forall a. Monoid a => a
mempty
                     }
killToBOL :: Monoid a => TextZipper a -> TextZipper a
killToBOL :: TextZipper a -> TextZipper a
killToBOL TextZipper a
tz = TextZipper a
tz { toLeft :: a
toLeft = a
forall a. Monoid a => a
mempty
                  }
killToEOF :: (Monoid a) => TextZipper a -> TextZipper a
killToEOF :: TextZipper a -> TextZipper a
killToEOF TextZipper a
tz =
    TextZipper a
tz { toRight :: a
toRight = a
forall a. Monoid a => a
mempty
       , below :: [a]
below = [a]
forall a. Monoid a => a
mempty
       }
killToBOF :: Monoid a => TextZipper a -> TextZipper a
killToBOF :: TextZipper a -> TextZipper a
killToBOF TextZipper a
tz =
    TextZipper a
tz { toLeft :: a
toLeft = a
forall a. Monoid a => a
mempty
       , above :: [a]
above = [a]
forall a. Monoid a => a
mempty
       }
deletePrevChar :: (Eq a, Monoid a) => TextZipper a -> TextZipper a
deletePrevChar :: TextZipper a -> TextZipper a
deletePrevChar TextZipper a
tz
    | TextZipper a -> TextZipper a
forall a. Monoid a => TextZipper a -> TextZipper a
moveLeft TextZipper a
tz TextZipper a -> TextZipper a -> Bool
forall a. Eq a => a -> a -> Bool
== TextZipper a
tz = TextZipper a
tz
    | Bool
otherwise = TextZipper a -> TextZipper a
forall a. Monoid a => TextZipper a -> TextZipper a
deleteChar (TextZipper a -> TextZipper a) -> TextZipper a -> TextZipper a
forall a b. (a -> b) -> a -> b
$ TextZipper a -> TextZipper a
forall a. Monoid a => TextZipper a -> TextZipper a
moveLeft TextZipper a
tz
deleteChar :: (Monoid a) => TextZipper a -> TextZipper a
deleteChar :: TextZipper a -> TextZipper a
deleteChar TextZipper a
tz
    
    | (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a -> Bool
forall a. TextZipper a -> a -> Bool
null_ TextZipper a
tz (TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
tz)) =
        TextZipper a
tz { toRight :: a
toRight = TextZipper a -> Int -> a -> a
forall a. TextZipper a -> Int -> a -> a
drop_ TextZipper a
tz Int
1 (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
tz
           }
    
    | TextZipper a -> a -> Bool
forall a. TextZipper a -> a -> Bool
null_ TextZipper a
tz (TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
tz) Bool -> Bool -> Bool
&& (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([a] -> Bool) -> [a] -> Bool
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
tz) =
        TextZipper a
tz { toRight :: a
toRight = [a] -> a
forall a. [a] -> a
head ([a] -> a) -> [a] -> a
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
tz
           , below :: [a]
below = [a] -> [a]
forall a. [a] -> [a]
tail ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
tz
           }
    | Bool
otherwise = TextZipper a
tz
currentChar :: TextZipper a -> Maybe Char
currentChar :: TextZipper a -> Maybe Char
currentChar TextZipper a
tz
  | Bool -> Bool
not (TextZipper a -> a -> Bool
forall a. TextZipper a -> a -> Bool
null_ TextZipper a
tz (TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
tz)) =
    Char -> Maybe Char
forall a. a -> Maybe a
Just (TextZipper a -> a -> Char
forall a. TextZipper a -> a -> Char
last_ TextZipper a
tz (TextZipper a -> Int -> a -> a
forall a. TextZipper a -> Int -> a -> a
take_ TextZipper a
tz Int
1 (TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
tz)))
  | Bool
otherwise = Maybe Char
forall a. Maybe a
Nothing
nextChar :: (Monoid a) => TextZipper a -> Maybe Char
nextChar :: TextZipper a -> Maybe Char
nextChar TextZipper a
tz = TextZipper a -> Maybe Char
forall a. TextZipper a -> Maybe Char
currentChar (TextZipper a -> TextZipper a
forall a. Monoid a => TextZipper a -> TextZipper a
moveRight TextZipper a
tz)
previousChar :: (Monoid a) => TextZipper a -> Maybe Char
previousChar :: TextZipper a -> Maybe Char
previousChar TextZipper a
tz
  
  
  | (Int, Int) -> Int
forall a b. (a, b) -> b
snd (TextZipper a -> (Int, Int)
forall a. TextZipper a -> (Int, Int)
cursorPosition TextZipper a
tz) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
&& (a -> Bool) -> [a] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (TextZipper a -> a -> Bool
forall a. TextZipper a -> a -> Bool
null_ TextZipper a
tz) (TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz) =
    Maybe Char
forall a. Maybe a
Nothing
  | Bool
otherwise =
    TextZipper a -> Maybe Char
forall a. TextZipper a -> Maybe Char
currentChar (TextZipper a -> TextZipper a
forall a. Monoid a => TextZipper a -> TextZipper a
moveLeft TextZipper a
tz)
gotoBOL :: (Monoid a) => TextZipper a -> TextZipper a
gotoBOL :: TextZipper a -> TextZipper a
gotoBOL TextZipper a
tz = TextZipper a
tz { toLeft :: a
toLeft = a
forall a. Monoid a => a
mempty
                , toRight :: a
toRight = TextZipper a -> a
forall a. Monoid a => TextZipper a -> a
currentLine TextZipper a
tz
                }
gotoBOF :: (Monoid a) => TextZipper a -> TextZipper a
gotoBOF :: TextZipper a -> TextZipper a
gotoBOF TextZipper a
tz =
    TextZipper a
tz { toLeft :: a
toLeft = a
forall a. Monoid a => a
mempty
       , toRight :: a
toRight = a
first
       , above :: [a]
above = [a]
forall a. Monoid a => a
mempty
       , below :: [a]
below = [a]
rest
       }
    where
        tx :: [a]
tx = TextZipper a -> [a]
forall a. Monoid a => TextZipper a -> [a]
getText TextZipper a
tz
        (a
first, [a]
rest) = if [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
tx
                        then (a
forall a. Monoid a => a
mempty, [a]
forall a. Monoid a => a
mempty)
                        else ([a] -> a
forall a. [a] -> a
head [a]
tx, [a] -> [a]
forall a. [a] -> [a]
tail [a]
tx)
moveRight :: (Monoid a) => TextZipper a -> TextZipper a
moveRight :: TextZipper a -> TextZipper a
moveRight TextZipper a
tz
    
    | Bool -> Bool
not (TextZipper a -> a -> Bool
forall a. TextZipper a -> a -> Bool
null_ TextZipper a
tz (TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
tz)) =
        TextZipper a
tz { toLeft :: a
toLeft = TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz
                      a -> a -> a
forall a. Monoid a => a -> a -> a
`mappend` (TextZipper a -> Int -> a -> a
forall a. TextZipper a -> Int -> a -> a
take_ TextZipper a
tz Int
1 (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
tz)
           , toRight :: a
toRight = TextZipper a -> Int -> a -> a
forall a. TextZipper a -> Int -> a -> a
drop_ TextZipper a
tz Int
1 (TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
tz)
           }
    
    
    | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
tz) =
        TextZipper a
tz { above :: [a]
above = TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz]
           , below :: [a]
below = [a] -> [a]
forall a. [a] -> [a]
tail ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
tz
           , toLeft :: a
toLeft = a
forall a. Monoid a => a
mempty
           , toRight :: a
toRight = TextZipper a -> a
forall a. TextZipper a -> a
nextLine TextZipper a
tz
           }
    | Bool
otherwise = TextZipper a
tz
moveLeft :: (Monoid a) => TextZipper a -> TextZipper a
moveLeft :: TextZipper a -> TextZipper a
moveLeft TextZipper a
tz
    
    | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a -> Bool
forall a. TextZipper a -> a -> Bool
null_ TextZipper a
tz (TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz) =
        TextZipper a
tz { toLeft :: a
toLeft = TextZipper a -> a -> a
forall a. TextZipper a -> a -> a
init_ TextZipper a
tz (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz
           , toRight :: a
toRight = TextZipper a -> Char -> a
forall a. TextZipper a -> Char -> a
fromChar TextZipper a
tz (TextZipper a -> a -> Char
forall a. TextZipper a -> a -> Char
last_ TextZipper a
tz (TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz))
                       a -> a -> a
forall a. Monoid a => a -> a -> a
`mappend` TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
tz
           }
    
    
    | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz) =
        TextZipper a
tz { above :: [a]
above = [a] -> [a]
forall a. [a] -> [a]
init ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz
           , below :: [a]
below = TextZipper a -> a
forall a. Monoid a => TextZipper a -> a
currentLine TextZipper a
tz a -> [a] -> [a]
forall a. a -> [a] -> [a]
: TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
tz
           , toLeft :: a
toLeft = [a] -> a
forall a. [a] -> a
last ([a] -> a) -> [a] -> a
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz
           , toRight :: a
toRight = a
forall a. Monoid a => a
mempty
           }
    | Bool
otherwise = TextZipper a
tz
moveUp :: (Monoid a) => TextZipper a -> TextZipper a
moveUp :: TextZipper a -> TextZipper a
moveUp TextZipper a
tz
    
    | (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ TextZipper a -> Bool
forall a. TextZipper a -> Bool
isFirstLine TextZipper a
tz) Bool -> Bool -> Bool
&&
      (TextZipper a -> a -> Int
forall a. TextZipper a -> a -> Int
length_ TextZipper a
tz (a -> Int) -> a -> Int
forall a b. (a -> b) -> a -> b
$ [a] -> a
forall a. [a] -> a
last ([a] -> a) -> [a] -> a
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= TextZipper a -> a -> Int
forall a. TextZipper a -> a -> Int
length_ TextZipper a
tz (TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz) =
        TextZipper a
tz { below :: [a]
below = TextZipper a -> a
forall a. Monoid a => TextZipper a -> a
currentLine TextZipper a
tz a -> [a] -> [a]
forall a. a -> [a] -> [a]
: TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
tz
           , above :: [a]
above = [a] -> [a]
forall a. [a] -> [a]
init ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz
           , toLeft :: a
toLeft = TextZipper a -> Int -> a -> a
forall a. TextZipper a -> Int -> a -> a
take_ TextZipper a
tz (TextZipper a -> a -> Int
forall a. TextZipper a -> a -> Int
length_ TextZipper a
tz (a -> Int) -> a -> Int
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz) ([a] -> a
forall a. [a] -> a
last ([a] -> a) -> [a] -> a
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz)
           , toRight :: a
toRight = TextZipper a -> Int -> a -> a
forall a. TextZipper a -> Int -> a -> a
drop_ TextZipper a
tz (TextZipper a -> a -> Int
forall a. TextZipper a -> a -> Int
length_ TextZipper a
tz (a -> Int) -> a -> Int
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz) ([a] -> a
forall a. [a] -> a
last ([a] -> a) -> [a] -> a
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz)
           }
    
    | (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ TextZipper a -> Bool
forall a. TextZipper a -> Bool
isFirstLine TextZipper a
tz) =
        TextZipper a
tz { above :: [a]
above = [a] -> [a]
forall a. [a] -> [a]
init ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz
           , below :: [a]
below = TextZipper a -> a
forall a. Monoid a => TextZipper a -> a
currentLine TextZipper a
tz a -> [a] -> [a]
forall a. a -> [a] -> [a]
: TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
tz
           , toLeft :: a
toLeft = [a] -> a
forall a. [a] -> a
last ([a] -> a) -> [a] -> a
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz
           , toRight :: a
toRight = a
forall a. Monoid a => a
mempty
           }
    
    | Bool
otherwise = TextZipper a -> TextZipper a
forall a. Monoid a => TextZipper a -> TextZipper a
gotoBOL TextZipper a
tz
moveDown :: (Monoid a) => TextZipper a -> TextZipper a
moveDown :: TextZipper a -> TextZipper a
moveDown TextZipper a
tz
    
    | (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ TextZipper a -> Bool
forall a. TextZipper a -> Bool
isLastLine TextZipper a
tz) Bool -> Bool -> Bool
&&
      (TextZipper a -> a -> Int
forall a. TextZipper a -> a -> Int
length_ TextZipper a
tz (a -> Int) -> a -> Int
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a
forall a. TextZipper a -> a
nextLine TextZipper a
tz) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= TextZipper a -> a -> Int
forall a. TextZipper a -> a -> Int
length_ TextZipper a
tz (TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz) =
        TextZipper a
tz { below :: [a]
below = [a] -> [a]
forall a. [a] -> [a]
tail ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
tz
           , above :: [a]
above = TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [TextZipper a -> a
forall a. Monoid a => TextZipper a -> a
currentLine TextZipper a
tz]
           , toLeft :: a
toLeft = TextZipper a -> Int -> a -> a
forall a. TextZipper a -> Int -> a -> a
take_ TextZipper a
tz (TextZipper a -> a -> Int
forall a. TextZipper a -> a -> Int
length_ TextZipper a
tz (a -> Int) -> a -> Int
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz) (TextZipper a -> a
forall a. TextZipper a -> a
nextLine TextZipper a
tz)
           , toRight :: a
toRight = TextZipper a -> Int -> a -> a
forall a. TextZipper a -> Int -> a -> a
drop_ TextZipper a
tz (TextZipper a -> a -> Int
forall a. TextZipper a -> a -> Int
length_ TextZipper a
tz (a -> Int) -> a -> Int
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz) (TextZipper a -> a
forall a. TextZipper a -> a
nextLine TextZipper a
tz)
           }
    
    | (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ TextZipper a -> Bool
forall a. TextZipper a -> Bool
isLastLine TextZipper a
tz) =
        TextZipper a
tz { above :: [a]
above = TextZipper a -> [a]
forall a. TextZipper a -> [a]
above TextZipper a
tz [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [TextZipper a -> a
forall a. Monoid a => TextZipper a -> a
currentLine TextZipper a
tz]
           , below :: [a]
below = [a] -> [a]
forall a. [a] -> [a]
tail ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ TextZipper a -> [a]
forall a. TextZipper a -> [a]
below TextZipper a
tz
           , toLeft :: a
toLeft = TextZipper a -> a
forall a. TextZipper a -> a
nextLine TextZipper a
tz
           , toRight :: a
toRight = a
forall a. Monoid a => a
mempty
           }
    
    | Bool
otherwise = TextZipper a -> TextZipper a
forall a. Monoid a => TextZipper a -> TextZipper a
gotoEOL TextZipper a
tz
transposeChars :: (Monoid a) => TextZipper a -> TextZipper a
transposeChars :: TextZipper a -> TextZipper a
transposeChars TextZipper a
tz
    | TextZipper a -> a -> Bool
forall a. TextZipper a -> a -> Bool
null_ TextZipper a
tz (TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz) = TextZipper a
tz
    | TextZipper a -> a -> Bool
forall a. TextZipper a -> a -> Bool
null_ TextZipper a
tz (TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
tz) =
        if TextZipper a -> a -> Int
forall a. TextZipper a -> a -> Int
length_ TextZipper a
tz (TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
2
        then TextZipper a
tz
        else let prefixLen :: Int
prefixLen = TextZipper a -> a -> Int
forall a. TextZipper a -> a -> Int
length_ TextZipper a
tz (TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2
                 prefix :: a
prefix = TextZipper a -> Int -> a -> a
forall a. TextZipper a -> Int -> a -> a
take_ TextZipper a
tz Int
prefixLen (TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz)
                 lastTwo :: a
lastTwo = TextZipper a -> Int -> a -> a
forall a. TextZipper a -> Int -> a -> a
drop_ TextZipper a
tz Int
prefixLen (TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz)
                 a :: a
a = TextZipper a -> Int -> a -> a
forall a. TextZipper a -> Int -> a -> a
take_ TextZipper a
tz Int
1 a
lastTwo
                 b :: a
b = TextZipper a -> Int -> a -> a
forall a. TextZipper a -> Int -> a -> a
drop_ TextZipper a
tz Int
1 a
lastTwo
             in TextZipper a
tz { toLeft :: a
toLeft = a
prefix a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
b a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
a
                   }
    | Bool
otherwise = TextZipper a
tz { toLeft :: a
toLeft = (TextZipper a -> a -> a
forall a. TextZipper a -> a -> a
init_ TextZipper a
tz (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz) a -> a -> a
forall a. Semigroup a => a -> a -> a
<>
                                (TextZipper a -> Int -> a -> a
forall a. TextZipper a -> Int -> a -> a
take_ TextZipper a
tz Int
1 (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
tz) a -> a -> a
forall a. Semigroup a => a -> a -> a
<>
                                (TextZipper a -> Char -> a
forall a. TextZipper a -> Char -> a
fromChar TextZipper a
tz (Char -> a) -> Char -> a
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a -> Char
forall a. TextZipper a -> a -> Char
last_ TextZipper a
tz (a -> Char) -> a -> Char
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a
forall a. TextZipper a -> a
toLeft TextZipper a
tz)
                     , toRight :: a
toRight = (TextZipper a -> Int -> a -> a
forall a. TextZipper a -> Int -> a -> a
drop_ TextZipper a
tz Int
1 (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ TextZipper a -> a
forall a. TextZipper a -> a
toRight TextZipper a
tz)
                     }
stringZipper :: [String] -> Maybe Int -> TextZipper String
stringZipper :: [[Char]] -> Maybe Int -> TextZipper [Char]
stringZipper =
    (Char -> [Char])
-> (Int -> ShowS)
-> (Int -> ShowS)
-> ([Char] -> Int)
-> ([Char] -> Char)
-> ShowS
-> ([Char] -> Bool)
-> ([Char] -> [[Char]])
-> ShowS
-> [[Char]]
-> Maybe Int
-> TextZipper [Char]
forall a.
Monoid a =>
(Char -> a)
-> (Int -> a -> a)
-> (Int -> a -> a)
-> (a -> Int)
-> (a -> Char)
-> (a -> a)
-> (a -> Bool)
-> (a -> [a])
-> (a -> [Char])
-> [a]
-> Maybe Int
-> TextZipper a
mkZipper (Char -> ShowS
forall a. a -> [a] -> [a]
:[]) Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int -> ShowS
forall a. Int -> [a] -> [a]
take [Char] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Char] -> Char
forall a. [a] -> a
last ShowS
forall a. [a] -> [a]
init [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char] -> [[Char]]
lines ShowS
forall a. a -> a
id
vectorZipper :: [V.Vector Char] -> Maybe Int -> TextZipper (V.Vector Char)
vectorZipper :: [Vector Char] -> Maybe Int -> TextZipper (Vector Char)
vectorZipper =
    (Char -> Vector Char)
-> (Int -> Vector Char -> Vector Char)
-> (Int -> Vector Char -> Vector Char)
-> (Vector Char -> Int)
-> (Vector Char -> Char)
-> (Vector Char -> Vector Char)
-> (Vector Char -> Bool)
-> (Vector Char -> [Vector Char])
-> (Vector Char -> [Char])
-> [Vector Char]
-> Maybe Int
-> TextZipper (Vector Char)
forall a.
Monoid a =>
(Char -> a)
-> (Int -> a -> a)
-> (Int -> a -> a)
-> (a -> Int)
-> (a -> Char)
-> (a -> a)
-> (a -> Bool)
-> (a -> [a])
-> (a -> [Char])
-> [a]
-> Maybe Int
-> TextZipper a
mkZipper Char -> Vector Char
forall a. a -> Vector a
V.singleton Int -> Vector Char -> Vector Char
forall a. Int -> Vector a -> Vector a
V.drop Int -> Vector Char -> Vector Char
forall a. Int -> Vector a -> Vector a
V.take Vector Char -> Int
forall a. Vector a -> Int
V.length Vector Char -> Char
forall a. Vector a -> a
V.last Vector Char -> Vector Char
forall a. Vector a -> Vector a
V.init Vector Char -> Bool
forall a. Vector a -> Bool
V.null Vector Char -> [Vector Char]
V.vecLines Vector Char -> [Char]
forall a. Vector a -> [a]
V.toList
clearZipper :: (Monoid a) => TextZipper a -> TextZipper a
clearZipper :: TextZipper a -> TextZipper a
clearZipper TextZipper a
tz =
    TextZipper a
tz { toLeft :: a
toLeft = a
forall a. Monoid a => a
mempty
       , toRight :: a
toRight = a
forall a. Monoid a => a
mempty
       , above :: [a]
above = []
       , below :: [a]
below = []
       }
textZipper :: [T.Text] -> Maybe Int -> TextZipper T.Text
textZipper :: [Text] -> Maybe Int -> TextZipper Text
textZipper =
    (Char -> Text)
-> (Int -> Text -> Text)
-> (Int -> Text -> Text)
-> (Text -> Int)
-> (Text -> Char)
-> (Text -> Text)
-> (Text -> Bool)
-> (Text -> [Text])
-> (Text -> [Char])
-> [Text]
-> Maybe Int
-> TextZipper Text
forall a.
Monoid a =>
(Char -> a)
-> (Int -> a -> a)
-> (Int -> a -> a)
-> (a -> Int)
-> (a -> Char)
-> (a -> a)
-> (a -> Bool)
-> (a -> [a])
-> (a -> [Char])
-> [a]
-> Maybe Int
-> TextZipper a
mkZipper Char -> Text
T.singleton Int -> Text -> Text
T.drop Int -> Text -> Text
T.take Text -> Int
T.length Text -> Char
T.last Text -> Text
T.init Text -> Bool
T.null Text -> [Text]
T.lines Text -> [Char]
T.unpack