module Hakyll.Web.Util.String
( trim
, replaceAll
, splitAll
, toUrl
, toSiteRoot
) where
import Data.Char (isSpace)
import Data.Maybe (listToMaybe)
import System.FilePath (splitPath, takeDirectory, joinPath)
import Text.Regex.PCRE ((=~~))
trim :: String -> String
trim = reverse . trim' . reverse . trim'
where
trim' = dropWhile isSpace
replaceAll :: String
-> (String -> String)
-> String
-> String
replaceAll pattern f source = replaceAll' source
where
replaceAll' src = case listToMaybe (src =~~ pattern) of
Nothing -> src
Just (o, l) ->
let (before, tmp) = splitAt o src
(capture, after) = splitAt l tmp
in before ++ f capture ++ replaceAll' after
splitAll :: String
-> String
-> [String]
splitAll pattern = filter (not . null) . splitAll'
where
splitAll' src = case listToMaybe (src =~~ pattern) of
Nothing -> [src]
Just (o, l) ->
let (before, tmp) = splitAt o src
in before : splitAll' (drop l tmp)
toUrl :: FilePath -> String
toUrl = ('/' :)
toSiteRoot :: String -> String
toSiteRoot = emptyException . joinPath . map parent . splitPath . takeDirectory
where
parent = const ".."
emptyException [] = "."
emptyException x = x