{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveTraversable #-}
module Text.Casing
(
Identifier (..)
, fromHumps
, fromKebab
, fromSnake
, fromWords
, fromAny
, toCamel
, toPascal
, toSnake
, toQuietSnake
, toScreamingSnake
, toKebab
, toWords
, pascal
, camel
, snake
, quietSnake
, screamingSnake
, kebab
, wordify
, dropPrefix
)
where
import Data.Char
import Data.List (intersperse)
import Data.List.Split (wordsBy)
import Control.Applicative
newtype Identifier a = Identifier { unIdentifier :: [a] }
deriving (Monad, Functor, Applicative, Show, Foldable, Traversable, Eq)
wordCase :: String -> String
wordCase "" = ""
wordCase (x:xs) = toUpper x : map toLower xs
fromHumps :: String -> Identifier String
fromHumps = Identifier . go
where
go "" = [""]
go (x:[]) = [x:[]]
go xxs@(x:xs)
| isUpper x =
let lhs = takeWhile isUpper xxs
rhs = dropWhile isUpper xxs
in
if null rhs then
[lhs]
else
let curLen = length lhs - 1
cur = take curLen lhs
rec = go rhs
nxt = drop curLen lhs ++ concat (take 1 rec)
rem = drop 1 rec
curL = if null cur then [] else [cur]
nxtL = if null nxt then [] else [nxt]
in curL ++ nxtL ++ rem
| otherwise =
let cur = takeWhile (not . isUpper) xxs
rem = dropWhile (not . isUpper) xxs
in
if null rem then
[cur]
else
cur:go rem
fromWords :: String -> Identifier String
fromWords = Identifier . words
fromKebab :: String -> Identifier String
fromKebab = Identifier . wordsBy (== '-')
fromSnake :: String -> Identifier String
fromSnake = Identifier . wordsBy (== '_')
fromAny :: String -> Identifier String
fromAny str = fromHumps str >>= fromKebab >>= fromSnake >>= fromWords
toPascal :: Identifier String -> String
toPascal = concat . map wordCase . unIdentifier
toCamel :: Identifier String -> String
toCamel (Identifier []) = ""
toCamel (Identifier (x:xs)) = concat $ map toLower x:map wordCase xs
toKebab :: Identifier String -> String
toKebab = concat . intersperse "-" . map (map toLower) . unIdentifier
toSnake :: Identifier String -> String
toSnake = concat . intersperse "_" . unIdentifier
toQuietSnake :: Identifier String -> String
toQuietSnake = map toLower . toSnake
toScreamingSnake :: Identifier String -> String
toScreamingSnake = map toUpper . toSnake
toWords :: Identifier String -> String
toWords = unwords . unIdentifier
pascal :: String -> String
pascal = toPascal . fromAny
camel :: String -> String
camel = toCamel . fromAny
snake :: String -> String
snake = toSnake . fromAny
quietSnake :: String -> String
quietSnake = toQuietSnake . fromAny
screamingSnake :: String -> String
screamingSnake = toScreamingSnake . fromAny
kebab :: String -> String
kebab = toKebab . fromAny
wordify :: String -> String
wordify = toWords . fromAny
dropPrefix :: Identifier String -> Identifier String
dropPrefix = Identifier . drop 1 . unIdentifier