{-# LANGUAGE FlexibleContexts #-}
--------------------------------------------------------------------------------
-- | Miscellaneous string manipulation functions.
module Hakyll.Core.Util.String
    ( trim
    , replaceAll
    , splitAll
    , needlePrefix
    , removeWinPathSeparator
    ) where


--------------------------------------------------------------------------------
import Data.Char (isSpace)
import Data.List (isPrefixOf)
import Data.Maybe (listToMaybe)
import Text.Regex.TDFA ((=~~))


--------------------------------------------------------------------------------
-- | Trim a string (drop spaces, tabs and newlines at both sides).
trim :: String -> String
trim :: [Char] -> [Char]
trim = forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
trim' 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
. [Char] -> [Char]
trim'
  where
    trim' :: [Char] -> [Char]
trim' = forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isSpace


--------------------------------------------------------------------------------
-- | A simple (but inefficient) regex replace funcion
replaceAll :: String              -- ^ Pattern
           -> (String -> String)  -- ^ Replacement (called on match)
           -> String              -- ^ Source string
           -> String              -- ^ Result
replaceAll :: [Char] -> ([Char] -> [Char]) -> [Char] -> [Char]
replaceAll [Char]
pattern [Char] -> [Char]
f [Char]
source = [Char] -> [Char]
replaceAll' [Char]
source
  where
    replaceAll' :: [Char] -> [Char]
replaceAll' [Char]
src = case forall a. [a] -> Maybe a
listToMaybe ([Char]
src forall source source1 target (m :: * -> *).
(RegexMaker Regex CompOption ExecOption source,
 RegexContext Regex source1 target, MonadFail m) =>
source1 -> source -> m target
=~~ [Char]
pattern) of
        Maybe (Int, Int)
Nothing     -> [Char]
src
        Just (Int
o, Int
l) ->
            let ([Char]
before, [Char]
tmp) = forall a. Int -> [a] -> ([a], [a])
splitAt Int
o [Char]
src
                ([Char]
capture, [Char]
after) = forall a. Int -> [a] -> ([a], [a])
splitAt Int
l [Char]
tmp
            in [Char]
before forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
f [Char]
capture forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
replaceAll' [Char]
after


--------------------------------------------------------------------------------
-- | A simple regex split function. The resulting list will contain no empty
-- strings.
splitAll :: String    -- ^ Pattern
         -> String    -- ^ String to split
         -> [String]  -- ^ Result
splitAll :: [Char] -> [Char] -> [[Char]]
splitAll [Char]
pattern = forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. RegexLike Regex [a] => [a] -> [[a]]
splitAll'
  where
    splitAll' :: [a] -> [[a]]
splitAll' [a]
src = case forall a. [a] -> Maybe a
listToMaybe ([a]
src forall source source1 target (m :: * -> *).
(RegexMaker Regex CompOption ExecOption source,
 RegexContext Regex source1 target, MonadFail m) =>
source1 -> source -> m target
=~~ [Char]
pattern) of
        Maybe (Int, Int)
Nothing     -> [[a]
src]
        Just (Int
o, Int
l) ->
            let ([a]
before, [a]
tmp) = forall a. Int -> [a] -> ([a], [a])
splitAt Int
o [a]
src
            in [a]
before forall a. a -> [a] -> [a]
: [a] -> [[a]]
splitAll' (forall a. Int -> [a] -> [a]
drop Int
l [a]
tmp)



--------------------------------------------------------------------------------
-- | Find the first instance of needle (must be non-empty) in haystack. We
-- return the prefix of haystack before needle is matched.
--
-- Examples:
--
-- > needlePrefix "cd" "abcde" = "ab"
--
-- > needlePrefix "ab" "abc" = ""
--
-- > needlePrefix "ab" "xxab" = "xx"
--
-- > needlePrefix "a" "xx" = "xx"
needlePrefix :: String -> String -> Maybe String
needlePrefix :: [Char] -> [Char] -> Maybe [Char]
needlePrefix [Char]
needle [Char]
haystack = [Char] -> [Char] -> Maybe [Char]
go [] [Char]
haystack
  where
    go :: [Char] -> [Char] -> Maybe [Char]
go [Char]
_   []                     = forall a. Maybe a
Nothing
    go [Char]
acc xss :: [Char]
xss@(Char
x:[Char]
xs)
        | [Char]
needle forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` [Char]
xss = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse [Char]
acc
        | Bool
otherwise               = [Char] -> [Char] -> Maybe [Char]
go (Char
x forall a. a -> [a] -> [a]
: [Char]
acc) [Char]
xs


--------------------------------------------------------------------------------
-- | Translate native Windows path separators '\\' to '/' if present.
removeWinPathSeparator :: String -> String
removeWinPathSeparator :: [Char] -> [Char]
removeWinPathSeparator = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\Char
c -> if Char
c forall a. Eq a => a -> a -> Bool
== Char
'\\' then [Char
'/'] else [Char
c])