X-Git-Url: http://git.cielonegro.org/gitweb.cgi?p=Rakka.git;a=blobdiff_plain;f=Rakka%2FUtils.hs;h=717a6068bddfa332b8dddb1edbcd94dc8ed39891;hp=7673eb50230bf58fdab4c9c16ea36040b7c70444;hb=HEAD;hpb=0fd09a6316e0be424e6eb454124f0cab6ade40b4 diff --git a/Rakka/Utils.hs b/Rakka/Utils.hs index 7673eb5..717a606 100644 --- a/Rakka/Utils.hs +++ b/Rakka/Utils.hs @@ -1,5 +1,7 @@ {-# LANGUAGE Arrows + , OverloadedStrings + , TypeOperators , UnicodeSyntax #-} module Rakka.Utils @@ -14,18 +16,22 @@ module Rakka.Utils , mkQueryString ) where -import qualified Codec.Binary.Url as Url import Control.Arrow import Control.Arrow.ArrowList +import Data.ByteString (ByteString) import qualified Data.ByteString as BS -import qualified Data.ByteString.Unsafe as BS +import qualified Data.ByteString.Char8 as C8 import qualified Data.ByteString.Lazy as LS -import Data.List -import qualified Data.Text as T +import qualified Data.ByteString.Unsafe as BS +import Data.Char +import Data.Monoid.Unicode +import Data.String +import Data.Text (Text) import Data.Text.Encoding import Magic import Network.HTTP.Lucu import Network.URI +import Numeric import Prelude.Unicode import System.IO.Unsafe @@ -37,12 +43,12 @@ trueOrFalse ∷ Bool → String trueOrFalse True = "true" trueOrFalse False = "false" -parseYesOrNo ∷ ArrowChoice a ⇒ a String Bool -parseYesOrNo - = proc str → do case str of - "yes" → returnA ⤙ True - "no" → returnA ⤙ False - _ → returnA ⤙ error ("Expected yes or no: " ⧺ str) +parseYesOrNo ∷ (Eq s, Show s, IsString s, ArrowChoice (⇝)) ⇒ s ⇝ Bool +parseYesOrNo = arr f + where + f "yes" = True + f "no" = False + f str = error ("Expected yes or no: " ⊕ show str) maybeA ∷ (ArrowList a, ArrowChoice a) ⇒ a b c → a b (Maybe c) maybeA a = listA a @@ -79,20 +85,49 @@ guessMIMEType = read isSafeChar ∷ Char → Bool {-# INLINEABLE isSafeChar #-} isSafeChar c - | c ≡ '/' = True - | isReserved c = False - | isUnreserved c = True - | otherwise = False + | c ≡ '/' = True + | isReserved c = False + | c > ' ' ∧ c ≤ '~' = True + | otherwise = False -mkQueryString ∷ [(T.Text, T.Text)] → String +mkQueryString ∷ [(Text, Text)] → ByteString {-# INLINEABLE mkQueryString #-} -mkQueryString = intercalate ";" ∘ map pairToStr +mkQueryString = BS.intercalate (C8.singleton ';') ∘ map encodePair where - pairToStr ∷ (T.Text, T.Text) → String - {-# INLINE pairToStr #-} - pairToStr (k, v) - = encode k ⧺ ('=':encode v) + encodePair ∷ (Text, Text) → ByteString + {-# INLINE encodePair #-} + encodePair (k, v) + = BS.intercalate (C8.singleton '=') [encodeText k, encodeText v] + + encodeText ∷ Text → ByteString + {-# INLINE encodeText #-} + encodeText = toURLEncoded ∘ encodeUtf8 + +toURLEncoded ∷ ByteString → ByteString +{-# INLINEABLE toURLEncoded #-} +toURLEncoded = C8.concatMap go + where + go ∷ Char → ByteString + {-# INLINE go #-} + go c | c ≡ ' ' = C8.singleton '+' + | isReserved c = urlEncode c + | isUnreserved c = C8.singleton c + | otherwise = urlEncode c + + urlEncode ∷ Char → ByteString + {-# INLINE urlEncode #-} + urlEncode c = C8.pack ('%':toHex (ord c)) + + toHex ∷ Int → String + {-# INLINE toHex #-} + toHex n + = case showIntAtBase 16 toChrHex n "" of + [] → "00" + [c] → ['0', c] + cs → cs - encode ∷ T.Text → String - {-# INLINE encode #-} - encode = Url.encode ∘ BS.unpack ∘ encodeUtf8 + toChrHex ∷ Int → Char + {-# INLINE toChrHex #-} + toChrHex d + | d < 10 = chr (ord '0' + fromIntegral d ) + | otherwise = chr (ord 'A' + fromIntegral (d-10))