module Text
(
Text,
isEmpty,
length,
reverse,
repeat,
replace,
append,
concat,
split,
join,
words,
lines,
slice,
left,
right,
dropLeft,
dropRight,
contains,
startsWith,
endsWith,
indexes,
indices,
toInt,
fromInt,
toFloat,
fromFloat,
fromChar,
cons,
uncons,
toList,
fromList,
toUpper,
toLower,
pad,
padLeft,
padRight,
trim,
trimLeft,
trimRight,
map,
filter,
foldl,
foldr,
any,
all,
)
where
import Basics
( (+),
(-),
(<),
(<<),
(<=),
(>>),
Bool,
Float,
Int,
clamp,
(|>),
)
import Char (Char)
import qualified Data.Text
import qualified List
import List (List)
import Maybe (Maybe)
import qualified Text.Read
import Prelude (otherwise)
import qualified Prelude
type Text = Data.Text.Text
isEmpty :: Text -> Bool
isEmpty :: Text -> Bool
isEmpty = Text -> Bool
Data.Text.null
length :: Text -> Int
length :: Text -> Int
length =
Text -> Int
Data.Text.length (Text -> Int) -> (Int -> Int) -> Text -> Int
forall a b c. (a -> b) -> (b -> c) -> a -> c
>> Int -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
reverse :: Text -> Text
reverse :: Text -> Text
reverse = Text -> Text
Data.Text.reverse
repeat :: Int -> Text -> Text
repeat :: Int -> Text -> Text
repeat =
Int -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (Int -> Int) -> (Int -> Text -> Text) -> Int -> Text -> Text
forall a b c. (a -> b) -> (b -> c) -> a -> c
>> Int -> Text -> Text
Data.Text.replicate
replace :: Text -> Text -> Text -> Text
replace :: Text -> Text -> Text -> Text
replace = Text -> Text -> Text -> Text
Data.Text.replace
append :: Text -> Text -> Text
append :: Text -> Text -> Text
append = Text -> Text -> Text
Data.Text.append
concat :: List Text -> Text
concat :: List Text -> Text
concat = List Text -> Text
Data.Text.concat
split :: Text -> Text -> List Text
split :: Text -> Text -> List Text
split = Text -> Text -> List Text
Data.Text.splitOn
join :: Text -> List Text -> Text
join :: Text -> List Text -> Text
join = Text -> List Text -> Text
Data.Text.intercalate
words :: Text -> List Text
words :: Text -> List Text
words = Text -> List Text
Data.Text.words
lines :: Text -> List Text
lines :: Text -> List Text
lines = Text -> List Text
Data.Text.lines
slice :: Int -> Int -> Text -> Text
slice :: Int -> Int -> Text -> Text
slice Int
from Int
to Text
text
| Int
to' Int -> Int -> Int
forall number. Num number => number -> number -> number
- Int
from' Int -> Int -> Bool
forall comparable.
Ord comparable =>
comparable -> comparable -> Bool
<= Int
0 = Text
Data.Text.empty
| Bool
otherwise =
Int -> Text -> Text
Data.Text.drop Int
from' (Int -> Text -> Text
Data.Text.take Int
to' Text
text)
where
len :: Int
len = Text -> Int
Data.Text.length Text
text
handleNegative :: Int -> Int
handleNegative Int
value
| Int
value Int -> Int -> Bool
forall comparable.
Ord comparable =>
comparable -> comparable -> Bool
< Int
0 = Int
len Int -> Int -> Int
forall number. Num number => number -> number -> number
+ Int
value
| Bool
otherwise = Int
value
normalize :: Int -> Int
normalize =
Int -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
(Int -> Int) -> (Int -> Int) -> Int -> Int
forall a b c. (a -> b) -> (b -> c) -> a -> c
>> Int -> Int
handleNegative
(Int -> Int) -> (Int -> Int) -> Int -> Int
forall a b c. (a -> b) -> (b -> c) -> a -> c
>> Int -> Int -> Int -> Int
forall number. Ord number => number -> number -> number -> number
clamp Int
0 Int
len
from' :: Int
from' = Int -> Int
normalize Int
from
to' :: Int
to' = Int -> Int
normalize Int
to
left :: Int -> Text -> Text
left :: Int -> Text -> Text
left =
Int -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (Int -> Int) -> (Int -> Text -> Text) -> Int -> Text -> Text
forall a b c. (a -> b) -> (b -> c) -> a -> c
>> Int -> Text -> Text
Data.Text.take
right :: Int -> Text -> Text
right :: Int -> Text -> Text
right =
Int -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (Int -> Int) -> (Int -> Text -> Text) -> Int -> Text -> Text
forall a b c. (a -> b) -> (b -> c) -> a -> c
>> Int -> Text -> Text
Data.Text.takeEnd
dropLeft :: Int -> Text -> Text
dropLeft :: Int -> Text -> Text
dropLeft =
Int -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (Int -> Int) -> (Int -> Text -> Text) -> Int -> Text -> Text
forall a b c. (a -> b) -> (b -> c) -> a -> c
>> Int -> Text -> Text
Data.Text.drop
dropRight :: Int -> Text -> Text
dropRight :: Int -> Text -> Text
dropRight =
Int -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (Int -> Int) -> (Int -> Text -> Text) -> Int -> Text -> Text
forall a b c. (a -> b) -> (b -> c) -> a -> c
>> Int -> Text -> Text
Data.Text.dropEnd
contains :: Text -> Text -> Bool
contains :: Text -> Text -> Bool
contains = Text -> Text -> Bool
Data.Text.isInfixOf
startsWith :: Text -> Text -> Bool
startsWith :: Text -> Text -> Bool
startsWith = Text -> Text -> Bool
Data.Text.isPrefixOf
endsWith :: Text -> Text -> Bool
endsWith :: Text -> Text -> Bool
endsWith = Text -> Text -> Bool
Data.Text.isSuffixOf
indexes :: Text -> Text -> List Int
indexes :: Text -> Text -> List Int
indexes Text
n Text
h
| Text -> Bool
isEmpty Text
n = []
| Bool
otherwise = Text -> Text -> List Int
forall b. Num b => Text -> Text -> List b
indexes' Text
n Text
h
where
indexes' :: Text -> Text -> List b
indexes' Text
needle Text
haystack =
Text -> Text -> [(Text, Text)]
Data.Text.breakOnAll Text
needle Text
haystack
[(Text, Text)] -> ([(Text, Text)] -> List b) -> List b
forall a b. a -> (a -> b) -> b
|> ((Text, Text) -> b) -> [(Text, Text)] -> List b
forall a b. (a -> b) -> List a -> List b
List.map
( \(Text
lhs, Text
_) ->
Text -> Int
Data.Text.length Text
lhs
Int -> (Int -> b) -> b
forall a b. a -> (a -> b) -> b
|> Int -> b
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
)
indices :: Text -> Text -> List Int
indices :: Text -> Text -> List Int
indices = Text -> Text -> List Int
indexes
toUpper :: Text -> Text
toUpper :: Text -> Text
toUpper = Text -> Text
Data.Text.toUpper
toLower :: Text -> Text
toLower :: Text -> Text
toLower = Text -> Text
Data.Text.toLower
pad :: Int -> Char -> Text -> Text
pad :: Int -> Char -> Text -> Text
pad =
Int -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (Int -> Int)
-> (Int -> Char -> Text -> Text) -> Int -> Char -> Text -> Text
forall a b c. (a -> b) -> (b -> c) -> a -> c
>> Int -> Char -> Text -> Text
Data.Text.center
padLeft :: Int -> Char -> Text -> Text
padLeft :: Int -> Char -> Text -> Text
padLeft =
Int -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (Int -> Int)
-> (Int -> Char -> Text -> Text) -> Int -> Char -> Text -> Text
forall a b c. (a -> b) -> (b -> c) -> a -> c
>> Int -> Char -> Text -> Text
Data.Text.justifyRight
padRight :: Int -> Char -> Text -> Text
padRight :: Int -> Char -> Text -> Text
padRight =
Int -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (Int -> Int)
-> (Int -> Char -> Text -> Text) -> Int -> Char -> Text -> Text
forall a b c. (a -> b) -> (b -> c) -> a -> c
>> Int -> Char -> Text -> Text
Data.Text.justifyLeft
trim :: Text -> Text
trim :: Text -> Text
trim = Text -> Text
Data.Text.strip
trimLeft :: Text -> Text
trimLeft :: Text -> Text
trimLeft = Text -> Text
Data.Text.stripStart
trimRight :: Text -> Text
trimRight :: Text -> Text
trimRight = Text -> Text
Data.Text.stripEnd
toInt :: Text -> Maybe Int
toInt :: Text -> Maybe Int
toInt Text
text =
String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
str'
where
str :: String
str = Text -> String
Data.Text.unpack Text
text
str' :: String
str' = case String
str of
Char
'+' : String
rest -> String
rest
String
other -> String
other
fromInt :: Int -> Text
fromInt :: Int -> Text
fromInt = String -> Text
Data.Text.pack (String -> Text) -> (Int -> String) -> Int -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
<< Int -> String
forall a. Show a => a -> String
Prelude.show
toFloat :: Text -> Maybe Float
toFloat :: Text -> Maybe Float
toFloat Text
text =
String -> Maybe Float
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
str'
where
str :: String
str = Text -> String
Data.Text.unpack Text
text
str' :: String
str' = case String
str of
Char
'+' : String
rest -> String
rest
Char
'.' : String
rest -> Char
'0' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
'.' Char -> String -> String
forall a. a -> [a] -> [a]
: String
rest
String
other -> String
other
fromFloat :: Float -> Text
fromFloat :: Float -> Text
fromFloat = String -> Text
Data.Text.pack (String -> Text) -> (Float -> String) -> Float -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
<< Float -> String
forall a. Show a => a -> String
Prelude.show
toList :: Text -> List Char
toList :: Text -> String
toList = Text -> String
Data.Text.unpack
fromList :: List Char -> Text
fromList :: String -> Text
fromList = String -> Text
Data.Text.pack
fromChar :: Char -> Text
fromChar :: Char -> Text
fromChar = Char -> Text
Data.Text.singleton
cons :: Char -> Text -> Text
cons :: Char -> Text -> Text
cons = Char -> Text -> Text
Data.Text.cons
uncons :: Text -> Maybe (Char, Text)
uncons :: Text -> Maybe (Char, Text)
uncons = Text -> Maybe (Char, Text)
Data.Text.uncons
map :: (Char -> Char) -> Text -> Text
map :: (Char -> Char) -> Text -> Text
map = (Char -> Char) -> Text -> Text
Data.Text.map
filter :: (Char -> Bool) -> Text -> Text
filter :: (Char -> Bool) -> Text -> Text
filter = (Char -> Bool) -> Text -> Text
Data.Text.filter
foldl :: (Char -> b -> b) -> b -> Text -> b
foldl :: (Char -> b -> b) -> b -> Text -> b
foldl Char -> b -> b
f = (b -> Char -> b) -> b -> Text -> b
forall a. (a -> Char -> a) -> a -> Text -> a
Data.Text.foldl' (\b
a Char
b -> Char -> b -> b
f Char
b b
a)
foldr :: (Char -> b -> b) -> b -> Text -> b
foldr :: (Char -> b -> b) -> b -> Text -> b
foldr = (Char -> b -> b) -> b -> Text -> b
forall a. (Char -> a -> a) -> a -> Text -> a
Data.Text.foldr
any :: (Char -> Bool) -> Text -> Bool
any :: (Char -> Bool) -> Text -> Bool
any = (Char -> Bool) -> Text -> Bool
Data.Text.any
all :: (Char -> Bool) -> Text -> Bool
all :: (Char -> Bool) -> Text -> Bool
all = (Char -> Bool) -> Text -> Bool
Data.Text.all