]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Headers.hs
multipart/form-data and more
[Lucu.git] / Network / HTTP / Lucu / Headers.hs
index c97c93cb652156c618d92bab8977fa2627fda117..28723bc206512f92adb178126629a89c9a15a926 100644 (file)
@@ -50,10 +50,12 @@ instance Show NCBS where
     show (NCBS x) = show x
 
 noCaseCmp :: ByteString -> ByteString -> Ordering
-noCaseCmp a b = toForeignPtr a `cmp` toForeignPtr b
+noCaseCmp a b = a `seq` b `seq`
+                toForeignPtr a `cmp` toForeignPtr b
     where
       cmp :: (ForeignPtr Word8, Int, Int) -> (ForeignPtr Word8, Int, Int) -> Ordering
       cmp (x1, s1, l1) (x2, s2, l2)
+          | x1 `seq` s1 `seq` l1 `seq` x2 `seq` s2 `seq` l2 `seq` False = undefined
           | l1 == 0  && l2 == 0               = EQ
           | x1 == x2 && s1 == s2 && l1 == l2  = EQ
           | otherwise
@@ -61,14 +63,15 @@ noCaseCmp a b = toForeignPtr a `cmp` toForeignPtr b
                 withForeignPtr x1 $ \ p1 ->
                 withForeignPtr x2 $ \ p2 ->
                 noCaseCmp' (p1 `plusPtr` s1) l1 (p2 `plusPtr` s2) l2
-{-# INLINE noCaseCmp #-}
+
 
 -- もし先頭の文字列が等しければ、短い方が小さい。
 noCaseCmp' :: Ptr Word8 -> Int -> Ptr Word8 -> Int -> IO Ordering
 noCaseCmp' p1 l1 p2 l2
+    | p1 `seq` l1 `seq` p2 `seq` l2 `seq` False = undefined
     | l1 == 0 && l2 == 0 = return EQ
-    | l1 == 0 && l1 /= 0 = return LT
-    | l1 /= 0 && l2 == 0 = return GT
+    | l1 == 0            = return LT
+    |            l2 == 0 = return GT
     | otherwise
         = do c1 <- peek p1
              c2 <- peek p2
@@ -78,10 +81,12 @@ noCaseCmp' p1 l1 p2 l2
 
 
 noCaseEq :: ByteString -> ByteString -> Bool
-noCaseEq a b = toForeignPtr a `cmp` toForeignPtr b
+noCaseEq a b = a `seq` b `seq`
+               toForeignPtr a `cmp` toForeignPtr b
     where
       cmp :: (ForeignPtr Word8, Int, Int) -> (ForeignPtr Word8, Int, Int) -> Bool
       cmp (x1, s1, l1) (x2, s2, l2)
+          | x1 `seq` s1 `seq` l1 `seq` x2 `seq` s2 `seq` l2 `seq` False = undefined
           | l1 /= l2                          = False
           | l1 == 0  && l2 == 0               = True
           | x1 == x2 && s1 == s2 && l1 == l2  = True
@@ -94,6 +99,7 @@ noCaseEq a b = toForeignPtr a `cmp` toForeignPtr b
 
 noCaseEq' :: Ptr Word8 -> Ptr Word8 -> Int -> IO Bool
 noCaseEq' p1 p2 l
+    | p1 `seq` p2 `seq` l `seq` False = undefined
     | l == 0    = return True
     | otherwise
         = do c1 <- peek p1
@@ -129,7 +135,24 @@ emptyHeaders = M.empty
 
 
 toHeaders :: [(ByteString, ByteString)] -> Headers
-toHeaders xs = M.fromList [(toNCBS a, b) | (a, b) <- xs]
+toHeaders xs = mkHeaders xs M.empty
+
+
+mkHeaders :: [(ByteString, ByteString)] -> Headers -> Headers
+mkHeaders []              m = m
+mkHeaders ((key, val):xs) m = mkHeaders xs $
+                              case M.lookup (toNCBS key) m of
+                                Nothing  -> M.insert (toNCBS key) val m
+                                Just old -> M.insert (toNCBS key) (merge old val) m
+    where
+      merge :: ByteString -> ByteString -> ByteString
+      -- カンマ區切りである事を假定する。RFC ではカンマ區切りに出來ない
+      -- ヘッダは複數個あってはならない事になってゐる。
+      merge a b
+          | C8.null a && C8.null b = C8.empty
+          | C8.null a              = b
+          |              C8.null b = a
+          | otherwise              = C8.concat [a, C8.pack ", ", b]
 
 
 fromHeaders :: Headers -> [(ByteString, ByteString)]
@@ -150,9 +173,9 @@ fromHeaders hs = [(fromNCBS a, b) | (a, b) <- M.toList hs]
 headersP :: Parser Headers
 headersP = do xs <- many header
               crlf
-              return (M.fromList xs)
+              return $! toHeaders xs
     where
-      header :: Parser (NCBS, ByteString)
+      header :: Parser (ByteString, ByteString)
       header = do name <- token
                   char ':'
                   -- FIXME: これは多少インチキだが、RFC 2616 のこの部分
@@ -165,7 +188,7 @@ headersP = do xs <- many header
                   crlf
                   let value = foldr (++) "" contents
                       norm  = normalize value
-                  return (toNCBS $ C8.pack name, C8.pack norm)
+                  return (C8.pack name, C8.pack norm)
 
       normalize :: String -> String
       normalize = trimBody . trim isWhiteSpace