]> gitweb @ CieloNegro.org - Rakka.git/blobdiff - Rakka/Utils.hs
merge branch origin/master
[Rakka.git] / Rakka / Utils.hs
index 051685cbf8a93cfedb07258fe44a04e0ac9169d3..717a6068bddfa332b8dddb1edbcd94dc8ed39891 100644 (file)
@@ -1,5 +1,7 @@
 {-# LANGUAGE
     Arrows
+  , OverloadedStrings
+  , TypeOperators
   , UnicodeSyntax
   #-}
 module Rakka.Utils
@@ -14,21 +16,22 @@ module Rakka.Utils
     , mkQueryString
     )
     where
-import qualified Blaze.ByteString.Builder as BBB
 import Control.Arrow
 import Control.Arrow.ArrowList
-import Data.Ascii (Ascii)
-import qualified Data.Ascii as A
+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 qualified Data.ByteString.Unsafe as BS
+import Data.Char
 import Data.Monoid.Unicode
-import qualified Data.Text as T
-import qualified Data.Text.Lazy as LT
+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
 
@@ -40,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
@@ -82,28 +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)] → Ascii
-{-# INLINE mkQueryString #-}
-mkQueryString = A.unsafeFromByteString
-                ∘ BBB.toByteString
-                ∘ flip mkBBB (∅)
+mkQueryString ∷ [(Text, Text)] → ByteString
+{-# INLINEABLE mkQueryString #-}
+mkQueryString = BS.intercalate (C8.singleton ';') ∘ map encodePair
     where
-      mkBBB ∷ [(T.Text, T.Text)] → BBB.Builder → BBB.Builder
-      {-# INLINEABLE mkBBB #-}
-      mkBBB []      acc = acc
-      mkBBB (kv:[]) acc = acc ⊕ pair kv
-      mkBBB (kv:xs) acc = mkBBB xs (acc ⊕ pair kv ⊕ semicolon)
-
-      pair ∷ (T.Text, T.Text) → BBB.Builder
-      {-# INLINE pair #-}
-      pair (k, v)
-          = encodeText k ⊕ equal ⊕ encodeText v
+      encodePair ∷ (Text, Text) → ByteString
+      {-# INLINE encodePair #-}
+      encodePair (k, v)
+          = BS.intercalate (C8.singleton '=') [encodeText k, encodeText v]
 
-      encodeText ∷ T.Text → BBB.Builder
+      encodeText ∷ Text → ByteString
       {-# INLINE encodeText #-}
-      encodeText = BBB.fromByteString ∘ URI.encode ∘ encodeUtf8
+      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
+
+      toChrHex ∷ Int → Char
+      {-# INLINE toChrHex #-}
+      toChrHex d
+          | d < 10    = chr (ord '0' + fromIntegral  d    )
+          | otherwise = chr (ord 'A' + fromIntegral (d-10))