X-Git-Url: http://git.cielonegro.org/gitweb.cgi?a=blobdiff_plain;f=Network%2FHTTP%2FLucu%2FUtils.hs;h=7dbb1162cbda616ae5eb57ce989bc481f813a9ac;hb=ece223c;hp=d2541691ced99dd41ac579d146224fa7657a8f7a;hpb=e34910f85f459f049b9e6e6b79db9ef95dfccc13;p=Lucu.git diff --git a/Network/HTTP/Lucu/Utils.hs b/Network/HTTP/Lucu/Utils.hs index d254169..7dbb116 100644 --- a/Network/HTTP/Lucu/Utils.hs +++ b/Network/HTTP/Lucu/Utils.hs @@ -1,20 +1,23 @@ {-# LANGUAGE - BangPatterns - , OverloadedStrings + 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 - , joinWith , 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 @@ -25,22 +28,11 @@ 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 - --- |> joinWith ":" ["ab", "c", "def"] --- > ==> "ab:c:def" -joinWith ∷ Ascii → [AsciiBuilder] → AsciiBuilder -{-# INLINEABLE joinWith #-} -joinWith sep = flip go (∅) - where - go ∷ [AsciiBuilder] → AsciiBuilder → AsciiBuilder - {-# INLINE go #-} - go [] ab = ab - go (x:[]) ab = ab ⊕ x - go (x:xs) ab = go xs (ab ⊕ A.toAsciiBuilder sep ⊕ x) + = case break isSep src of + (last , [] ) → [last] + (first, _sep:rest) → first : splitBy isSep rest -- |> quoteStr "abc" -- > ==> "\"abc\"" @@ -65,10 +57,12 @@ quoteStr str = A.toAsciiBuilder "\"" ⊕ -- |> parseWWWFormURLEncoded "aaa=bbb&ccc=ddd" -- > ==> [("aaa", "bbb"), ("ccc", "ddd")] -parseWWWFormURLEncoded ∷ String → [(String, String)] +parseWWWFormURLEncoded ∷ Ascii → [(ByteString, ByteString)] parseWWWFormURLEncoded src - | null src = [] - | otherwise = do pairStr ← splitBy (\ c → c ≡ ';' ∨ c ≡ '&') 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 @@ -76,9 +70,29 @@ parseWWWFormURLEncoded src val → val ) where - unescape ∷ String → String - unescape = unEscapeString ∘ map plusToSpace + 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)