{-# LANGUAGE FlexibleInstances #-}
module ShortcutLinks.Utils
( replaceSpaces
, titleFirst
, tryStripPrefixCI
, stripPrefixCI
, orElse
, format
, formatSlash
) where
import Data.Char (isSpace, toUpper)
import Data.Semigroup ((<>))
import Data.Text (Text)
import qualified Data.Text as T
replaceSpaces :: Char -> Text -> Text
replaceSpaces r = T.map (\c -> if isSpace c then r else c)
titleFirst :: Text -> Text
titleFirst = T.intercalate "#" . map title . T.splitOn "#"
where
title :: Text -> Text
title s = case T.uncons s of
Nothing -> ""
Just (c, rest) -> toUpper c `T.cons` rest
tryStripPrefixCI :: Text -> Text -> Text
tryStripPrefixCI pref str =
let pref' = T.toCaseFold pref
(str_pref, rest) = T.splitAt (T.length pref') str
in if T.toCaseFold str_pref == pref' then rest else str
stripPrefixCI :: Text -> Text -> Maybe Text
stripPrefixCI pref str =
let pref' = T.toCaseFold pref
(str_pref, rest) = T.splitAt (T.length pref') str
in if T.toCaseFold str_pref == pref' then Just rest else Nothing
orElse :: (Eq a, Monoid a) => a -> a -> a
orElse a b = if a == mempty then b else a
class FormatArg a where
formatArg :: a -> Text
instance FormatArg Text where formatArg = id
instance FormatArg String where formatArg = T.pack
instance FormatArg Int where formatArg = T.pack . show
instance FormatArg Integer where formatArg = T.pack . show
class FormatType r where
format' :: Text -> [Text] -> r
instance FormatType String where
format' str params = T.unpack $ format' str params
instance FormatType Text where
format' str params = go fragments (reverse params)
where
fragments = T.splitOn "{}" str
go (f:fs) (y:ys) = f <> y <> go fs ys
go [f] [] = f
go _ _ = error $ format
"ShortcutLinks.Utils.format: {} placeholders, but {} parameters"
(length fragments - 1)
(length params)
instance (FormatArg a, FormatType r) => FormatType (a -> r) where
format' :: Text -> [Text] -> (a -> r)
format' str params a = format' str (formatArg a : params)
format :: FormatType r => Text -> r
format str = format' str []
formatSlash :: FormatType r => r
formatSlash = format "{}/{}"