{-# LANGUAGE BangPatterns , UnicodeSyntax #-} -- |Utility functions used internally in the Lucu httpd. These -- functions may be useful too for something else. module Network.HTTP.Lucu.Utils ( splitBy , joinWith , trim , isWhiteSpace , quoteStr , parseWWWFormURLEncoded ) where import Control.Monad import Data.List hiding (last) import Network.URI import Prelude hiding (last) import Prelude.Unicode -- |> splitBy (== ':') "ab:c:def" -- > ==> ["ab", "c", "def"] splitBy :: (a -> Bool) -> [a] -> [[a]] splitBy isSep src = case break isSep src of (last , [] ) -> [last] (first, _sep:rest) -> first : splitBy isSep rest -- |> joinWith ":" ["ab", "c", "def"] -- > ==> "ab:c:def" joinWith :: [a] -> [[a]] -> [a] joinWith = (join .) . intersperse -- |> trim (== '_') "__ab_c__def___" -- > ==> "ab_c__def" trim :: (a -> Bool) -> [a] -> [a] trim !p = trimTail . trimHead where trimHead = dropWhile p trimTail = reverse . trimHead . reverse -- |@'isWhiteSpace' c@ is 'Prelude.True' iff c is one of SP, HT, CR -- and LF. isWhiteSpace :: Char -> Bool isWhiteSpace ' ' = True isWhiteSpace '\t' = True isWhiteSpace '\r' = True isWhiteSpace '\n' = True isWhiteSpace _ = False {-# INLINE isWhiteSpace #-} -- |> quoteStr "abc" -- > ==> "\"abc\"" -- -- > quoteStr "ab\"c" -- > ==> "\"ab\\\"c\"" quoteStr :: String -> String quoteStr !str = concat (["\""] ++ map quote str ++ ["\""]) where quote :: Char -> String quote '"' = "\\\"" quote c = [c] -- |> parseWWWFormURLEncoded "aaa=bbb&ccc=ddd" -- > ==> [("aaa", "bbb"), ("ccc", "ddd")] parseWWWFormURLEncoded ∷ String → [(String, String)] parseWWWFormURLEncoded src | null src = [] | otherwise = do pairStr ← splitBy (\ c → c ≡ ';' ∨ c ≡ '&') src let (key, value) = break (≡ '=') pairStr return ( unescape key , unescape $ case value of ('=':val) → val val → val ) where unescape ∷ String → String unescape = unEscapeString ∘ map plusToSpace plusToSpace ∷ Char → Char plusToSpace '+' = ' ' plusToSpace c = c