{-# LANGUAGE MultiParamTypeClasses
,FlexibleInstances #-}
{-# OPTIONS -fno-warn-orphans #-}
module Data.ListLike.Text.Text
where
import Prelude as P
import qualified Data.Text as T
import qualified Data.Text.IO as TI
import qualified Data.Text.Lazy as Lazy (toStrict)
import Data.Text.Encoding (decodeUtf8)
import Data.ListLike.Base as LL
import Data.ListLike.FoldableLL
import Data.ListLike.IO
import Data.ListLike.String
import qualified Data.ByteString as BS
instance FoldableLL T.Text Char where
foldl :: forall a. (a -> Char -> a) -> a -> Text -> a
foldl = (a -> Char -> a) -> a -> Text -> a
forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl
foldl' :: forall a. (a -> Char -> a) -> a -> Text -> a
foldl' = (a -> Char -> a) -> a -> Text -> a
forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl'
foldl1 :: (Char -> Char -> Char) -> Text -> Char
foldl1 = HasCallStack => (Char -> Char -> Char) -> Text -> Char
(Char -> Char -> Char) -> Text -> Char
T.foldl1
foldr :: forall b. (Char -> b -> b) -> b -> Text -> b
foldr = (Char -> b -> b) -> b -> Text -> b
forall b. (Char -> b -> b) -> b -> Text -> b
T.foldr
foldr1 :: (Char -> Char -> Char) -> Text -> Char
foldr1 = HasCallStack => (Char -> Char -> Char) -> Text -> Char
(Char -> Char -> Char) -> Text -> Char
T.foldr1
instance ListLike T.Text Char where
empty :: Text
empty = Text
T.empty
singleton :: Char -> Text
singleton = Char -> Text
T.singleton
cons :: Char -> Text -> Text
cons = Char -> Text -> Text
T.cons
snoc :: Text -> Char -> Text
snoc = Text -> Char -> Text
T.snoc
append :: Text -> Text -> Text
append = Text -> Text -> Text
T.append
head :: Text -> Char
head = HasCallStack => Text -> Char
Text -> Char
T.head
last :: Text -> Char
last = HasCallStack => Text -> Char
Text -> Char
T.last
tail :: Text -> Text
tail = HasCallStack => Text -> Text
Text -> Text
T.tail
init :: Text -> Text
init = HasCallStack => Text -> Text
Text -> Text
T.init
null :: Text -> Bool
null = Text -> Bool
T.null
length :: Text -> Int
length = Text -> Int
T.length
rigidMap :: (Char -> Char) -> Text -> Text
rigidMap = (Char -> Char) -> Text -> Text
T.map
reverse :: Text -> Text
reverse = Text -> Text
T.reverse
intersperse :: Char -> Text -> Text
intersperse = Char -> Text -> Text
T.intersperse
concat :: forall full'. ListLike full' Text => full' -> Text
concat = [Text] -> Text
T.concat ([Text] -> Text) -> (full' -> [Text]) -> full' -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. full' -> [Item full']
full' -> [Text]
forall l. IsList l => l -> [Item l]
toList
rigidConcatMap :: (Char -> Text) -> Text -> Text
rigidConcatMap = (Char -> Text) -> Text -> Text
T.concatMap
any :: (Char -> Bool) -> Text -> Bool
any = (Char -> Bool) -> Text -> Bool
T.any
all :: (Char -> Bool) -> Text -> Bool
all = (Char -> Bool) -> Text -> Bool
T.all
maximum :: Ord Char => Text -> Char
maximum = HasCallStack => Text -> Char
Text -> Char
T.maximum
minimum :: Ord Char => Text -> Char
minimum = HasCallStack => Text -> Char
Text -> Char
T.minimum
replicate :: Int -> Char -> Text
replicate Int
n = Int -> Text -> Text
T.replicate Int
n (Text -> Text) -> (Char -> Text) -> Char -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
T.singleton
take :: Int -> Text -> Text
take = Int -> Text -> Text
T.take
drop :: Int -> Text -> Text
drop = Int -> Text -> Text
T.drop
splitAt :: Int -> Text -> (Text, Text)
splitAt = Int -> Text -> (Text, Text)
T.splitAt
takeWhile :: (Char -> Bool) -> Text -> Text
takeWhile = (Char -> Bool) -> Text -> Text
T.takeWhile
dropWhile :: (Char -> Bool) -> Text -> Text
dropWhile = (Char -> Bool) -> Text -> Text
T.dropWhile
span :: (Char -> Bool) -> Text -> (Text, Text)
span = (Char -> Bool) -> Text -> (Text, Text)
T.span
break :: (Char -> Bool) -> Text -> (Text, Text)
break = (Char -> Bool) -> Text -> (Text, Text)
T.break
group :: forall full'. (ListLike full' Text, Eq Char) => Text -> full'
group = [Item full'] -> full'
[Text] -> full'
forall l. IsList l => [Item l] -> l
fromList ([Text] -> full') -> (Text -> [Text]) -> Text -> full'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.group
inits :: forall full'. ListLike full' Text => Text -> full'
inits = [Item full'] -> full'
[Text] -> full'
forall l. IsList l => [Item l] -> l
fromList ([Text] -> full') -> (Text -> [Text]) -> Text -> full'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.inits
tails :: forall full'. ListLike full' Text => Text -> full'
tails = [Item full'] -> full'
[Text] -> full'
forall l. IsList l => [Item l] -> l
fromList ([Text] -> full') -> (Text -> [Text]) -> Text -> full'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.tails
isPrefixOf :: Eq Char => Text -> Text -> Bool
isPrefixOf = Text -> Text -> Bool
T.isPrefixOf
isSuffixOf :: Eq Char => Text -> Text -> Bool
isSuffixOf = Text -> Text -> Bool
T.isSuffixOf
stripPrefix :: Eq Char => Text -> Text -> Maybe Text
stripPrefix = Text -> Text -> Maybe Text
T.stripPrefix
stripSuffix :: Eq Char => Text -> Text -> Maybe Text
stripSuffix = Text -> Text -> Maybe Text
T.stripSuffix
elem :: Eq Char => Char -> Text -> Bool
elem = Text -> Text -> Bool
T.isInfixOf (Text -> Text -> Bool) -> (Char -> Text) -> Char -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
T.singleton
find :: (Char -> Bool) -> Text -> Maybe Char
find = (Char -> Bool) -> Text -> Maybe Char
T.find
filter :: (Char -> Bool) -> Text -> Text
filter = (Char -> Bool) -> Text -> Text
T.filter
index :: Text -> Int -> Char
index = HasCallStack => Text -> Int -> Char
Text -> Int -> Char
T.index
findIndex :: (Char -> Bool) -> Text -> Maybe Int
findIndex = (Char -> Bool) -> Text -> Maybe Int
T.findIndex
groupBy :: forall full'.
(ListLike full' Text, Eq Char) =>
(Char -> Char -> Bool) -> Text -> full'
groupBy Char -> Char -> Bool
f = [Item full'] -> full'
[Text] -> full'
forall l. IsList l => [Item l] -> l
fromList ([Text] -> full') -> (Text -> [Text]) -> Text -> full'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Char -> Bool) -> Text -> [Text]
T.groupBy Char -> Char -> Bool
f
genericLength :: forall a. Num a => Text -> a
genericLength = Integer -> a
forall a. Num a => Integer -> a
fromInteger (Integer -> a) -> (Text -> Integer) -> Text -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Integer) -> (Text -> Int) -> Text -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Int
T.length
genericTake :: forall a. Integral a => a -> Text -> Text
genericTake a
i = Int -> Text -> Text
T.take (a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
i)
genericDrop :: forall a. Integral a => a -> Text -> Text
genericDrop a
i = Int -> Text -> Text
T.drop (a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
i)
genericSplitAt :: forall a. Integral a => a -> Text -> (Text, Text)
genericSplitAt a
i = Int -> Text -> (Text, Text)
T.splitAt (a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
i)
genericReplicate :: forall a. Integral a => a -> Char -> Text
genericReplicate a
i = Int -> Char -> Text
forall full item. ListLike full item => Int -> item -> full
LL.replicate (a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
i)
sequence :: forall (m :: * -> *) fullinp.
(Applicative m, ListLike fullinp (m Char)) =>
fullinp -> m Text
sequence = ([Char] -> Text) -> m [Char] -> m Text
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Char] -> Text
[Item Text] -> Text
forall l. IsList l => [Item l] -> l
fromList (m [Char] -> m Text) -> (fullinp -> m [Char]) -> fullinp -> m Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [m Char] -> m [Char]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
forall (f :: * -> *) a. Applicative f => [f a] -> f [a]
P.sequenceA ([m Char] -> m [Char])
-> (fullinp -> [m Char]) -> fullinp -> m [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. fullinp -> [m Char]
fullinp -> [Item fullinp]
forall l. IsList l => l -> [Item l]
toList
mapM :: forall (m :: * -> *) full' item'.
(Applicative m, ListLike full' item') =>
(Char -> m item') -> Text -> m full'
mapM Char -> m item'
func = ([item'] -> full') -> m [item'] -> m full'
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [item'] -> full'
[Item full'] -> full'
forall l. IsList l => [Item l] -> l
fromList (m [item'] -> m full') -> (Text -> m [item']) -> Text -> m full'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> m item') -> [Char] -> m [item']
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
P.traverse Char -> m item'
func ([Char] -> m [item']) -> (Text -> [Char]) -> Text -> m [item']
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Char]
Text -> [Item Text]
forall l. IsList l => l -> [Item l]
toList
instance ListLikeIO T.Text Char where
hGetLine :: Handle -> IO Text
hGetLine = Handle -> IO Text
TI.hGetLine
hGetContents :: Handle -> IO Text
hGetContents = Handle -> IO Text
TI.hGetContents
hGet :: Handle -> Int -> IO Text
hGet Handle
h Int
c = Handle -> Int -> IO ByteString
BS.hGet Handle
h Int
c IO ByteString -> (ByteString -> IO Text) -> IO Text
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> IO Text) -> (ByteString -> Text) -> ByteString -> IO Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
decodeUtf8
hGetNonBlocking :: Handle -> Int -> IO Text
hGetNonBlocking Handle
h Int
i = Handle -> Int -> IO ByteString
BS.hGetNonBlocking Handle
h Int
i IO ByteString -> (ByteString -> IO Text) -> IO Text
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> IO Text) -> (ByteString -> Text) -> ByteString -> IO Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
decodeUtf8
hPutStr :: Handle -> Text -> IO ()
hPutStr = Handle -> Text -> IO ()
TI.hPutStr
hPutStrLn :: Handle -> Text -> IO ()
hPutStrLn = Handle -> Text -> IO ()
TI.hPutStrLn
getLine :: IO Text
getLine = IO Text
TI.getLine
getContents :: IO Text
getContents = IO Text
TI.getContents
putStr :: Text -> IO ()
putStr = Text -> IO ()
TI.putStr
putStrLn :: Text -> IO ()
putStrLn = Text -> IO ()
TI.putStrLn
interact :: (Text -> Text) -> IO ()
interact = (Text -> Text) -> IO ()
TI.interact
readFile :: [Char] -> IO Text
readFile = [Char] -> IO Text
TI.readFile
writeFile :: [Char] -> Text -> IO ()
writeFile = [Char] -> Text -> IO ()
TI.writeFile
appendFile :: [Char] -> Text -> IO ()
appendFile = [Char] -> Text -> IO ()
TI.appendFile
instance StringLike T.Text where
toString :: Text -> [Char]
toString = Text -> [Char]
T.unpack
words :: forall full'. ListLike full' Text => Text -> full'
words = [Item full] -> full
[Text] -> full
forall l. IsList l => [Item l] -> l
fromList ([Text] -> full) -> (Text -> [Text]) -> Text -> full
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.words
lines :: forall full'. ListLike full' Text => Text -> full'
lines = [Item full] -> full
[Text] -> full
forall l. IsList l => [Item l] -> l
fromList ([Text] -> full) -> (Text -> [Text]) -> Text -> full
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.lines
unwords :: forall full'. ListLike full' Text => full' -> Text
unwords = [Text] -> Text
T.unwords ([Text] -> Text) -> (full -> [Text]) -> full -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. full -> [Item full]
full -> [Text]
forall l. IsList l => l -> [Item l]
toList
unlines :: forall full'. ListLike full' Text => full' -> Text
unlines = [Text] -> Text
T.unlines ([Text] -> Text) -> (full -> [Text]) -> full -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. full -> [Item full]
full -> [Text]
forall l. IsList l => l -> [Item l]
toList
fromText :: StringLike Text => Text -> Text
fromText = Text -> Text
forall a. a -> a
id
fromLazyText :: StringLike Text => Text -> Text
fromLazyText = Text -> Text
Lazy.toStrict