{-# LANGUAGE OverloadedStrings , UnicodeSyntax #-} -- |Utility functions used internally in the Lucu httpd. These -- functions may be useful too for something else. module Network.HTTP.Lucu.Utils ( splitBy , quoteStr , parseWWWFormURLEncoded , splitPathInfo , show3 ) where import Blaze.ByteString.Builder.ByteString as B import Blaze.Text.Int as BT import Control.Monad import Data.Ascii (Ascii, AsciiBuilder) import qualified Data.Ascii as A import Data.ByteString (ByteString) import qualified Data.ByteString.Char8 as BS import Data.List hiding (last) import Data.Monoid.Unicode import Network.URI import Prelude hiding (last) import Prelude.Unicode -- |> splitBy (== ':') "ab:c:def" -- > ==> ["ab", "c", "def"] splitBy ∷ (a → Bool) → [a] → [[a]] {-# INLINEABLE splitBy #-} splitBy isSep src = case break isSep src of (last , [] ) → [last] (first, _sep:rest) → first : splitBy isSep rest -- |> quoteStr "abc" -- > ==> "\"abc\"" -- -- > quoteStr "ab\"c" -- > ==> "\"ab\\\"c\"" quoteStr ∷ Ascii → AsciiBuilder quoteStr str = A.toAsciiBuilder "\"" ⊕ go (A.toByteString str) (∅) ⊕ A.toAsciiBuilder "\"" where go ∷ BS.ByteString → AsciiBuilder → AsciiBuilder go bs ab = case BS.break (≡ '"') bs of (x, y) | BS.null y → ab ⊕ b2ab x | otherwise → go (BS.tail y) (ab ⊕ b2ab x ⊕ A.toAsciiBuilder "\\\"") b2ab ∷ BS.ByteString → AsciiBuilder b2ab = A.toAsciiBuilder ∘ A.unsafeFromByteString -- |> parseWWWFormURLEncoded "aaa=bbb&ccc=ddd" -- > ==> [("aaa", "bbb"), ("ccc", "ddd")] parseWWWFormURLEncoded ∷ Ascii → [(ByteString, ByteString)] parseWWWFormURLEncoded src -- THINKME: We could gain some performance by using attoparsec -- here. | src ≡ "" = [] | otherwise = do pairStr ← splitBy (\ c → c ≡ ';' ∨ c ≡ '&') (A.toString src) let (key, value) = break (≡ '=') pairStr return ( unescape key , unescape $ case value of ('=':val) → val val → val ) where unescape ∷ String → ByteString unescape = BS.pack ∘ unEscapeString ∘ map plusToSpace plusToSpace ∷ Char → Char plusToSpace '+' = ' ' plusToSpace c = c -- |> splitPathInfo "http://example.com/foo/bar" -- > ==> ["foo", "bar"] splitPathInfo ∷ URI → [ByteString] splitPathInfo uri = let reqPathStr = uriPath uri reqPath = [unEscapeString x | x ← splitBy (≡ '/') reqPathStr, (¬) (null x)] in map BS.pack reqPath -- |> show3 5 -- > ==> "005" show3 ∷ Integral n ⇒ n → AsciiBuilder {-# INLINEABLE show3 #-} show3 = A.unsafeFromBuilder ∘ go where go i | i ≥ 0 ∧ i < 10 = B.fromByteString "00" ⊕ BT.digit i | i ≥ 0 ∧ i < 100 = B.fromByteString "0" ⊕ BT.integral i | i ≥ 0 ∧ i < 1000 = BT.integral i | otherwise = error ("show3: the integer i must satisfy 0 <= i < 1000: " ⧺ show i)