module Data.Registry.Options.Text where
import qualified Data.Char as C
import qualified Data.List as L
import qualified Data.Text as T
import Protolude
camelCaseToHyphenated :: Text -> Text
camelCaseToHyphenated :: Text -> Text
camelCaseToHyphenated = Text -> [Text] -> Text
T.intercalate Text
"-" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
T.toLower forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
splitCamelCase
hyphenatedToCamelCase :: Text -> Text
hyphenatedToCamelCase :: Text -> Text
hyphenatedToCamelCase Text
t =
case Text -> Text -> [Text]
T.splitOn Text
"-" Text
t of
[] -> Text
""
Text
t1:[Text]
ts -> [Text] -> Text
T.concat (Text
t1forall a. a -> [a] -> [a]
: (Text -> Text
T.toTitle forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Text]
ts))
dropQualifier :: Text -> Text
dropQualifier :: Text -> Text
dropQualifier Text
t = forall a. a -> Maybe a -> a
fromMaybe Text
t forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Maybe a
lastMay forall a b. (a -> b) -> a -> b
$ Text -> Text -> [Text]
T.splitOn Text
"." Text
t
dropPrefix :: Text -> Text
dropPrefix :: Text -> Text
dropPrefix Text
t =
case forall a b. ConvertText a b => a -> b
toS forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> [Text]
splitCamelCase Text
t of
[] -> Text
t
[Text
t1] -> Text
t1
(Text
t1 : Text
t2 : [Text]
ts) ->
[Text] -> Text
T.concat forall a b. (a -> b) -> a -> b
$ if Text -> Bool
isCapitalized Text
t1 then Text
t2 forall a. a -> [a] -> [a]
: [Text]
ts else Text -> Text
T.toLower Text
t2 forall a. a -> [a] -> [a]
: [Text]
ts
splitCamelCase :: Text -> [Text]
splitCamelCase :: Text -> [Text]
splitCamelCase = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. ConvertText a b => a -> b
toS forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [[Char]]
splitCamelCaseString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. ConvertText a b => a -> b
toS
where
splitCamelCaseString :: [Char] -> [[Char]]
splitCamelCaseString [] = []
splitCamelCaseString (Char
c : [Char]
cs) = do
let ([Char]
lower, [Char]
rest) = forall a. (a -> Bool) -> [a] -> ([a], [a])
L.break Char -> Bool
C.isUpper [Char]
cs
[Char
c forall a. a -> [a] -> [a]
: [Char]
lower] forall a. Semigroup a => a -> a -> a
<> [Char] -> [[Char]]
splitCamelCaseString [Char]
rest
isCapitalized :: Text -> Bool
isCapitalized :: Text -> Bool
isCapitalized Text
t = Text -> Bool
T.null Text
t Bool -> Bool -> Bool
|| Char -> Bool
C.isUpper (Text -> Char
T.head Text
t)
displayColumns :: [Text] -> [Text] -> [Text]
displayColumns :: [Text] -> [Text] -> [Text]
displayColumns [Text]
cs1 [Text]
cs2 = do
let maxSize :: Int
maxSize = forall a. a -> Maybe a -> a
fromMaybe Int
0 forall a b. (a -> b) -> a -> b
$ forall a. Ord a => [a] -> Maybe a
maximumMay (Text -> Int
T.length forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Text]
cs1)
(\(Text
c1, Text
c2) -> Text
c1 forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.replicate (Int
maxSize forall a. Num a => a -> a -> a
- Text -> Int
T.length Text
c1) Text
" " forall a. Semigroup a => a -> a -> a
<> Text
" " forall a. Semigroup a => a -> a -> a
<> Text
c2) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b. [a] -> [b] -> [(a, b)]
zip [Text]
cs1 [Text]
cs2
bracketText :: Text -> Text
bracketText :: Text -> Text
bracketText = Bool -> Text -> Text
bracketTextWhen Bool
True
bracketTextWhen :: Bool -> Text -> Text
bracketTextWhen :: Bool -> Text -> Text
bracketTextWhen Bool
False Text
t = Text
t
bracketTextWhen Bool
True Text
t = Text
"[" forall a. Semigroup a => a -> a -> a
<> Text
t forall a. Semigroup a => a -> a -> a
<> Text
"]"
parenthesizeText :: Text -> Text
parenthesizeText :: Text -> Text
parenthesizeText = Bool -> Text -> Text
parenthesizeTextWhen Bool
True
parenthesizeTextWhen :: Bool -> Text -> Text
parenthesizeTextWhen :: Bool -> Text -> Text
parenthesizeTextWhen Bool
False Text
t = Text
t
parenthesizeTextWhen Bool
True Text
t = Text
"(" forall a. Semigroup a => a -> a -> a
<> Text
t forall a. Semigroup a => a -> a -> a
<> Text
")"
indent :: Text -> Text -> Text
indent :: Text -> Text -> Text
indent Text
i Text
t = Text -> [Text] -> Text
T.intercalate Text
"\n" forall a b. (a -> b) -> a -> b
$ (Text
i <> ) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> [Text]
T.lines Text
t
trimRight :: Text -> Text
trimRight :: Text -> Text
trimRight = [Char] -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isSpace forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
reverseforall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Char]
T.unpack
underscoreToCamelCase :: Text -> Text
underscoreToCamelCase :: Text -> Text
underscoreToCamelCase Text
t =
case Text -> Text -> [Text]
T.splitOn Text
"_" Text
t of
[] -> Text
""
Text
h:[Text]
ts -> Text
h forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
T.concat (Text -> Text
T.toTitle forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Text]
ts)
camelCaseToUnderscore :: Text -> Text
camelCaseToUnderscore :: Text -> Text
camelCaseToUnderscore Text
t = Text -> [Text] -> Text
T.intercalate Text
"_" (Text -> Text
T.toLower forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> [Text]
splitCamelCase Text
t)
underscoreToHyphenated :: Text -> Text
underscoreToHyphenated :: Text -> Text
underscoreToHyphenated = Text -> [Text] -> Text
T.intercalate Text
"-" forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> [Text]
T.splitOn Text
"_"
hyphenatedToUnderscore :: Text -> Text
hyphenatedToUnderscore :: Text -> Text
hyphenatedToUnderscore = Text -> [Text] -> Text
T.intercalate Text
"_" forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> [Text]
T.splitOn Text
"-"