]> gitweb @ CieloNegro.org - Rakka.git/blobdiff - Rakka/Utils.hs
Rakka.Utils
[Rakka.git] / Rakka / Utils.hs
index 7673eb50230bf58fdab4c9c16ea36040b7c70444..e89fee08c381e21c66bdd498556442915a64e047 100644 (file)
@@ -10,22 +10,24 @@ module Rakka.Utils
     , deleteIfEmpty
     , chomp
     , guessMIMEType
-    , isSafeChar
     , mkQueryString
     )
     where
-import qualified Codec.Binary.Url as Url
 import Control.Arrow
 import Control.Arrow.ArrowList
+import Data.Ascii (Ascii)
+import qualified Data.Ascii as A
 import qualified Data.ByteString as BS
+import qualified Data.ByteString.Char8 as C8
 import qualified Data.ByteString.Unsafe as BS
 import qualified Data.ByteString.Lazy as LS
-import Data.List
+import Data.Char
 import qualified Data.Text as T
 import Data.Text.Encoding
 import Magic
 import Network.HTTP.Lucu
 import Network.URI
+import Numeric
 import Prelude.Unicode
 import System.IO.Unsafe
 
@@ -76,23 +78,56 @@ guessMIMEType = read
                    magicLoadDefault m
                    return m
 
+{-
 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 ∷ [(T.Text, T.Text)] → Ascii
 {-# INLINEABLE mkQueryString #-}
-mkQueryString = intercalate ";" ∘ map pairToStr
+mkQueryString = A.unsafeFromByteString
+                ∘ BS.intercalate (C8.singleton ';')
+                ∘ map encodePair
     where
-      pairToStr ∷ (T.Text, T.Text) → String
-      {-# INLINE pairToStr #-}
-      pairToStr (k, v)
-          = encode k ⧺ ('=':encode v)
+      encodePair ∷ (T.Text, T.Text) → BS.ByteString
+      {-# INLINE encodePair #-}
+      encodePair (k, v)
+          = BS.intercalate (C8.singleton '=') [encodeText k, encodeText v]
 
-      encode ∷ T.Text → String
-      {-# INLINE encode #-}
-      encode = Url.encode ∘ BS.unpack ∘ encodeUtf8
+      encodeText ∷ T.Text → BS.ByteString
+      {-# INLINE encodeText #-}
+      encodeText = toURLEncoded ∘ encodeUtf8
+
+toURLEncoded ∷ BS.ByteString → BS.ByteString
+{-# INLINEABLE toURLEncoded #-}
+toURLEncoded = C8.concatMap go
+    where
+      go ∷ Char → BS.ByteString
+      {-# INLINE go #-}
+      go c | c ≡ ' '        = C8.singleton '+'
+           | isReserved   c = urlEncode c
+           | isUnreserved c = C8.singleton c
+           | otherwise      = urlEncode c
+
+      urlEncode ∷ Char → BS.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
+
+      toChrHex ∷ Int → Char
+      {-# INLINE toChrHex #-}
+      toChrHex d
+          | d < 10    = chr (ord '0' + fromIntegral  d    )
+          | otherwise = chr (ord 'A' + fromIntegral (d-10))