{-# LANGUAGE FlexibleInstances #-}
module Data.Text.Zipper.Generic
    ( GenericTextZipper(..)
    , Data.Text.Zipper.Generic.textZipper
    )
where

import qualified Prelude
import           Prelude hiding (drop, take, length, last, init, null, lines)
import qualified Data.Text as T
import qualified Data.Text.Zipper.Vector as V
import qualified Data.Vector as V

import           Data.Monoid

import           Data.Text.Zipper

class Monoid a => GenericTextZipper a where
  singleton :: Char -> a
  drop      :: Int -> a -> a
  take      :: Int -> a -> a
  length    :: a -> Int
  last      :: a -> Char
  init      :: a -> a
  null      :: a -> Bool
  lines     :: a -> [a]
  toList    :: a -> [Char]

instance GenericTextZipper [Char] where
  singleton :: Char -> [Char]
singleton = (forall a. a -> [a] -> [a]
:[])
  drop :: Int -> [Char] -> [Char]
drop      = forall a. Int -> [a] -> [a]
Prelude.drop
  take :: Int -> [Char] -> [Char]
take      = forall a. Int -> [a] -> [a]
Prelude.take
  length :: [Char] -> Int
length    = forall (t :: * -> *) a. Foldable t => t a -> Int
Prelude.length
  last :: [Char] -> Char
last      = forall a. [a] -> a
Prelude.last
  init :: [Char] -> [Char]
init      = forall a. [a] -> [a]
Prelude.init
  null :: [Char] -> Bool
null      = forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null
  lines :: [Char] -> [[Char]]
lines     = [Char] -> [[Char]]
Prelude.lines
  toList :: [Char] -> [Char]
toList    = forall a. a -> a
id

instance GenericTextZipper T.Text where
  singleton :: Char -> Text
singleton = Char -> Text
T.singleton
  drop :: Int -> Text -> Text
drop      = Int -> Text -> Text
T.drop
  take :: Int -> Text -> Text
take      = Int -> Text -> Text
T.take
  length :: Text -> Int
length    = Text -> Int
T.length
  last :: Text -> Char
last      = Text -> Char
T.last
  init :: Text -> Text
init      = Text -> Text
T.init
  null :: Text -> Bool
null      = Text -> Bool
T.null
  lines :: Text -> [Text]
lines     = Text -> [Text]
T.lines
  toList :: Text -> [Char]
toList    = Text -> [Char]
T.unpack

instance GenericTextZipper (V.Vector Char) where
  singleton :: Char -> Vector Char
singleton = forall a. a -> Vector a
V.singleton
  drop :: Int -> Vector Char -> Vector Char
drop      = forall a. Int -> Vector a -> Vector a
V.drop
  take :: Int -> Vector Char -> Vector Char
take      = forall a. Int -> Vector a -> Vector a
V.take
  length :: Vector Char -> Int
length    = forall a. Vector a -> Int
V.length
  last :: Vector Char -> Char
last      = forall a. Vector a -> a
V.last
  init :: Vector Char -> Vector Char
init      = forall a. Vector a -> Vector a
V.init
  null :: Vector Char -> Bool
null      = forall a. Vector a -> Bool
V.null
  lines :: Vector Char -> [Vector Char]
lines     = Vector Char -> [Vector Char]
V.vecLines
  toList :: Vector Char -> [Char]
toList    = forall a. Vector a -> [a]
V.toList

textZipper :: GenericTextZipper a =>
              [a] -> Maybe Int -> TextZipper a
textZipper :: forall a. GenericTextZipper a => [a] -> Maybe Int -> TextZipper a
textZipper =
  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 forall a. GenericTextZipper a => Char -> a
singleton forall a. GenericTextZipper a => Int -> a -> a
drop forall a. GenericTextZipper a => Int -> a -> a
take forall a. GenericTextZipper a => a -> Int
length forall a. GenericTextZipper a => a -> Char
last forall a. GenericTextZipper a => a -> a
init forall a. GenericTextZipper a => a -> Bool
null forall a. GenericTextZipper a => a -> [a]
lines forall a. GenericTextZipper a => a -> [Char]
toList