{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module Data.Text.Manipulate
(
takeWord,
dropWord,
stripWord,
breakWord,
splitWords,
lowerHead,
upperHead,
mapHead,
indentLines,
prependLines,
toEllipsis,
toEllipsisWith,
toAcronym,
toOrdinal,
toTitle,
toCamel,
toPascal,
toSnake,
toSpinal,
toTrain,
isBoundary,
isWordBoundary,
)
where
import qualified Data.Char as Char
import Data.List (intersperse)
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Lazy as LText
import qualified Data.Text.Lazy.Manipulate as LMan
import Data.Text.Manipulate.Internal.Fusion (strict)
import qualified Data.Text.Manipulate.Internal.Fusion as Fusion
import Data.Text.Manipulate.Internal.Types
lowerHead :: Text -> Text
lowerHead :: Text -> Text
lowerHead = (Char -> Char) -> Text -> Text
mapHead Char -> Char
Char.toLower
upperHead :: Text -> Text
upperHead :: Text -> Text
upperHead = (Char -> Char) -> Text -> Text
mapHead Char -> Char
Char.toUpper
mapHead :: (Char -> Char) -> Text -> Text
mapHead :: (Char -> Char) -> Text -> Text
mapHead Char -> Char
f Text
x =
case Text -> Maybe (Char, Text)
Text.uncons Text
x of
Just (Char
c, Text
cs) -> Char -> Text
Text.singleton (Char -> Char
f Char
c) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
cs
Maybe (Char, Text)
Nothing -> Text
x
indentLines :: Int -> Text -> Text
indentLines :: Int -> Text -> Text
indentLines Int
n = Text -> Text -> Text
prependLines (Int -> Text -> Text
Text.replicate Int
n Text
" ")
prependLines :: Text -> Text -> Text
prependLines :: Text -> Text -> Text
prependLines Text
sep = Text -> Text -> Text
forall a. Monoid a => a -> a -> a
mappend Text
sep (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
Text.unlines ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
intersperse Text
sep ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
Text.lines
toEllipsis :: Int -> Text -> Text
toEllipsis :: Int -> Text -> Text
toEllipsis Int
n = Int -> Text -> Text -> Text
toEllipsisWith Int
n Text
"..."
toEllipsisWith ::
Int ->
Text ->
Text ->
Text
toEllipsisWith :: Int -> Text -> Text -> Text
toEllipsisWith Int
n Text
suf Text
x
| Text -> Int
Text.length Text
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n = Int -> Text -> Text
Text.take Int
n Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
suf
| Bool
otherwise = Text
x
takeWord :: Text -> Text
takeWord :: Text -> Text
takeWord = (Stream Char -> Stream Char) -> Text -> Text
strict Stream Char -> Stream Char
Fusion.takeWord
dropWord :: Text -> Text
dropWord :: Text -> Text
dropWord = (Stream Char -> Stream Char) -> Text -> Text
strict Stream Char -> Stream Char
Fusion.dropWord
breakWord :: Text -> (Text, Text)
breakWord :: Text -> (Text, Text)
breakWord Text
x = (Text -> Text
takeWord Text
x, Text -> Text
dropWord Text
x)
stripWord :: Text -> Maybe Text
stripWord :: Text -> Maybe Text
stripWord Text
x
| Text -> Int
Text.length Text
y Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Text -> Int
Text.length Text
x = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
y
| Bool
otherwise = Maybe Text
forall a. Maybe a
Nothing
where
y :: Text
y = Text -> Text
dropWord Text
x
splitWords :: Text -> [Text]
splitWords :: Text -> [Text]
splitWords = Text -> [Text]
go
where
go :: Text -> [Text]
go Text
x = case Text -> (Text, Text)
breakWord Text
x of
(Text
h, Text
t)
| Text -> Bool
Text.null Text
h -> Text -> [Text]
go Text
t
| Text -> Bool
Text.null Text
t -> [Text
h]
| Bool
otherwise -> Text
h Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: Text -> [Text]
go Text
t
toAcronym :: Text -> Maybe Text
toAcronym :: Text -> Maybe Text
toAcronym ((Char -> Bool) -> Text -> Text
Text.filter Char -> Bool
Char.isUpper -> Text
x)
| Text -> Int
Text.length Text
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
x
| Bool
otherwise = Maybe Text
forall a. Maybe a
Nothing
toOrdinal :: Integral a => a -> Text
toOrdinal :: a -> Text
toOrdinal = Text -> Text
LText.toStrict (Text -> Text) -> (a -> Text) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. Integral a => a -> Text
LMan.toOrdinal
toTitle :: Text -> Text
toTitle :: Text -> Text
toTitle = (Stream Char -> Stream Char) -> Text -> Text
strict Stream Char -> Stream Char
Fusion.toTitle
toCamel :: Text -> Text
toCamel :: Text -> Text
toCamel = (Stream Char -> Stream Char) -> Text -> Text
strict Stream Char -> Stream Char
Fusion.toCamel
toPascal :: Text -> Text
toPascal :: Text -> Text
toPascal = (Stream Char -> Stream Char) -> Text -> Text
strict Stream Char -> Stream Char
Fusion.toPascal
toSnake :: Text -> Text
toSnake :: Text -> Text
toSnake = (Stream Char -> Stream Char) -> Text -> Text
strict Stream Char -> Stream Char
Fusion.toSnake
toSpinal :: Text -> Text
toSpinal :: Text -> Text
toSpinal = (Stream Char -> Stream Char) -> Text -> Text
strict Stream Char -> Stream Char
Fusion.toSpinal
toTrain :: Text -> Text
toTrain :: Text -> Text
toTrain = (Stream Char -> Stream Char) -> Text -> Text
strict Stream Char -> Stream Char
Fusion.toTrain