summaryrefslogtreecommitdiff
path: root/lib/Hakyll/Core/Util/String.hs
diff options
context:
space:
mode:
authorJasper Van der Jeugt <m@jaspervdj.be>2017-06-19 11:57:23 +0200
committerJasper Van der Jeugt <m@jaspervdj.be>2017-06-19 11:57:23 +0200
commit67ecff7ad383640bc73d64edc2506c7cc648a134 (patch)
tree6d328e43c3ab86c29a2d775fabaa23618c16fb51 /lib/Hakyll/Core/Util/String.hs
parent2df3209bafa08e6b77ee4a8598fc503269513527 (diff)
downloadhakyll-67ecff7ad383640bc73d64edc2506c7cc648a134.tar.gz
Move src/ to lib/, put Init.hs in src/
Diffstat (limited to 'lib/Hakyll/Core/Util/String.hs')
-rw-r--r--lib/Hakyll/Core/Util/String.hs78
1 files changed, 78 insertions, 0 deletions
diff --git a/lib/Hakyll/Core/Util/String.hs b/lib/Hakyll/Core/Util/String.hs
new file mode 100644
index 0000000..23bdd39
--- /dev/null
+++ b/lib/Hakyll/Core/Util/String.hs
@@ -0,0 +1,78 @@
+{-# LANGUAGE FlexibleContexts #-}
+--------------------------------------------------------------------------------
+-- | Miscellaneous string manipulation functions.
+module Hakyll.Core.Util.String
+ ( trim
+ , replaceAll
+ , splitAll
+ , needlePrefix
+ ) 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 = reverse . trim' . reverse . trim'
+ where
+ trim' = dropWhile isSpace
+
+
+--------------------------------------------------------------------------------
+-- | A simple (but inefficient) regex replace funcion
+replaceAll :: String -- ^ Pattern
+ -> (String -> String) -- ^ Replacement (called on capture)
+ -> String -- ^ Source string
+ -> String -- ^ Result
+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
+
+
+--------------------------------------------------------------------------------
+-- | A simple regex split function. The resulting list will contain no empty
+-- strings.
+splitAll :: String -- ^ Pattern
+ -> String -- ^ String to split
+ -> [String] -- ^ Result
+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)
+
+
+
+--------------------------------------------------------------------------------
+-- | 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 needle haystack = go [] haystack
+ where
+ go _ [] = Nothing
+ go acc xss@(x:xs)
+ | needle `isPrefixOf` xss = Just $ reverse acc
+ | otherwise = go (x : acc) xs