{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module Data.Text.Lazy.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.Int
import Data.List (intersperse)
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as LText
import Data.Text.Lazy.Builder (toLazyText)
import Data.Text.Manipulate.Internal.Fusion (lazy)
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)
LText.uncons Text
x of
Just (Char
c, Text
cs) -> Char -> Text
LText.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 (Int64 -> Text -> Text
LText.replicate (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral 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
LText.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]
LText.lines
toEllipsis :: Int64 -> Text -> Text
toEllipsis :: Int64 -> Text -> Text
toEllipsis Int64
n = Int64 -> Text -> Text -> Text
toEllipsisWith Int64
n Text
"..."
toEllipsisWith ::
Int64 ->
Text ->
Text ->
Text
toEllipsisWith :: Int64 -> Text -> Text -> Text
toEllipsisWith Int64
n Text
suf Text
x
| Text -> Int64
LText.length Text
x Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
> Int64
n = Int64 -> Text -> Text
LText.take Int64
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
lazy Stream Char -> Stream Char
Fusion.takeWord
dropWord :: Text -> Text
dropWord :: Text -> Text
dropWord = (Stream Char -> Stream Char) -> Text -> Text
lazy 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 -> Int64
LText.length Text
y Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Text -> Int64
LText.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
LText.null Text
h -> Text -> [Text]
go Text
t
| Text -> Bool
LText.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
LText.filter Char -> Bool
Char.isUpper -> Text
x)
| Text -> Int64
LText.length Text
x Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
> Int64
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 = Builder -> Text
toLazyText (Builder -> Text) -> (a -> Builder) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Builder
forall a. Integral a => a -> Builder
ordinal
toTitle :: Text -> Text
toTitle :: Text -> Text
toTitle = (Stream Char -> Stream Char) -> Text -> Text
lazy Stream Char -> Stream Char
Fusion.toTitle
toCamel :: Text -> Text
toCamel :: Text -> Text
toCamel = (Stream Char -> Stream Char) -> Text -> Text
lazy Stream Char -> Stream Char
Fusion.toCamel
toPascal :: Text -> Text
toPascal :: Text -> Text
toPascal = (Stream Char -> Stream Char) -> Text -> Text
lazy Stream Char -> Stream Char
Fusion.toPascal
toSnake :: Text -> Text
toSnake :: Text -> Text
toSnake = (Stream Char -> Stream Char) -> Text -> Text
lazy Stream Char -> Stream Char
Fusion.toSnake
toSpinal :: Text -> Text
toSpinal :: Text -> Text
toSpinal = (Stream Char -> Stream Char) -> Text -> Text
lazy Stream Char -> Stream Char
Fusion.toSpinal
toTrain :: Text -> Text
toTrain :: Text -> Text
toTrain = (Stream Char -> Stream Char) -> Text -> Text
lazy Stream Char -> Stream Char
Fusion.toTrain