X-Git-Url: http://git.cielonegro.org/gitweb.cgi?a=blobdiff_plain;f=Network%2FHTTP%2FLucu%2FHeaders.hs;h=163f6bcf55bb2a9e4f78ef680919be07df354246;hb=f62b6f07bbf1eefcf552163d8f7daa6e0862ed5d;hp=4ad60432b704bf16ad06853ac083c633982473d6;hpb=50e8fe7af585a8d33d93b3721be8f8f01905b891;p=Lucu.git diff --git a/Network/HTTP/Lucu/Headers.hs b/Network/HTTP/Lucu/Headers.hs index 4ad6043..163f6bc 100644 --- a/Network/HTTP/Lucu/Headers.hs +++ b/Network/HTTP/Lucu/Headers.hs @@ -14,29 +14,31 @@ module Network.HTTP.Lucu.Headers ) where -import Data.ByteString.Base (ByteString, toForeignPtr, w2c, inlinePerformIO) -import qualified Data.ByteString.Char8 as C8 +import qualified Data.ByteString as Strict (ByteString) +import Data.ByteString.Internal (toForeignPtr, w2c, inlinePerformIO) +import qualified Data.ByteString.Char8 as C8 hiding (ByteString) import Data.Char import Data.List import Data.Map (Map) import qualified Data.Map as M +import Data.Ord import Data.Word import Foreign.ForeignPtr import Foreign.Ptr import Foreign.Storable +import Network.HTTP.Lucu.HandleLike import Network.HTTP.Lucu.Parser import Network.HTTP.Lucu.Parser.Http import Network.HTTP.Lucu.Utils -import System.IO -type Headers = Map NCBS ByteString -newtype NCBS = NCBS ByteString +type Headers = Map NCBS Strict.ByteString +newtype NCBS = NCBS Strict.ByteString -toNCBS :: ByteString -> NCBS +toNCBS :: Strict.ByteString -> NCBS toNCBS = NCBS {-# INLINE toNCBS #-} -fromNCBS :: NCBS -> ByteString +fromNCBS :: NCBS -> Strict.ByteString fromNCBS (NCBS x) = x {-# INLINE fromNCBS #-} @@ -49,7 +51,7 @@ instance Ord NCBS where instance Show NCBS where show (NCBS x) = show x -noCaseCmp :: ByteString -> ByteString -> Ordering +noCaseCmp :: Strict.ByteString -> Strict.ByteString -> Ordering noCaseCmp a b = a `seq` b `seq` toForeignPtr a `cmp` toForeignPtr b where @@ -75,12 +77,12 @@ noCaseCmp' p1 l1 p2 l2 | otherwise = do c1 <- peek p1 c2 <- peek p2 - case toLower (w2c c1) `compare` toLower (w2c c2) of + case comparing (toLower . w2c) c1 c2 of EQ -> noCaseCmp' (p1 `plusPtr` 1) (l1 - 1) (p2 `plusPtr` 1) (l2 - 1) x -> return x -noCaseEq :: ByteString -> ByteString -> Bool +noCaseEq :: Strict.ByteString -> Strict.ByteString -> Bool noCaseEq a b = a `seq` b `seq` toForeignPtr a `cmp` toForeignPtr b where @@ -114,17 +116,17 @@ class HasHeaders a where getHeaders :: a -> Headers setHeaders :: a -> Headers -> a - getHeader :: ByteString -> a -> Maybe ByteString + getHeader :: Strict.ByteString -> a -> Maybe Strict.ByteString getHeader key a = key `seq` a `seq` M.lookup (toNCBS key) (getHeaders a) - deleteHeader :: ByteString -> a -> a + deleteHeader :: Strict.ByteString -> a -> a deleteHeader key a = key `seq` a `seq` setHeaders a $ M.delete (toNCBS key) (getHeaders a) - setHeader :: ByteString -> ByteString -> a -> a + setHeader :: Strict.ByteString -> Strict.ByteString -> a -> a setHeader key val a = key `seq` val `seq` a `seq` setHeaders a $ M.insert (toNCBS key) val (getHeaders a) @@ -134,18 +136,18 @@ emptyHeaders :: Headers emptyHeaders = M.empty -toHeaders :: [(ByteString, ByteString)] -> Headers +toHeaders :: [(Strict.ByteString, Strict.ByteString)] -> Headers toHeaders xs = mkHeaders xs M.empty -mkHeaders :: [(ByteString, ByteString)] -> Headers -> Headers +mkHeaders :: [(Strict.ByteString, Strict.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 + merge :: Strict.ByteString -> Strict.ByteString -> Strict.ByteString -- カンマ區切りである事を假定する。RFC ではカンマ區切りに出來ない -- ヘッダは複數個あってはならない事になってゐる。 merge a b @@ -155,7 +157,7 @@ mkHeaders ((key, val):xs) m = mkHeaders xs $ | otherwise = C8.concat [a, C8.pack ", ", b] -fromHeaders :: Headers -> [(ByteString, ByteString)] +fromHeaders :: Headers -> [(Strict.ByteString, Strict.ByteString)] fromHeaders hs = [(fromNCBS a, b) | (a, b) <- M.toList hs] @@ -175,7 +177,7 @@ headersP = do xs <- many header crlf return $! toHeaders xs where - header :: Parser (ByteString, ByteString) + header :: Parser (Strict.ByteString, Strict.ByteString) header = do name <- token char ':' -- FIXME: これは多少インチキだが、RFC 2616 のこの部分 @@ -193,7 +195,7 @@ headersP = do xs <- many header normalize :: String -> String normalize = trimBody . trim isWhiteSpace - trimBody = foldr (++) [] + trimBody = concat . map (\ s -> if head s == ' ' then " " else @@ -204,15 +206,15 @@ headersP = do xs <- many header else c) -hPutHeaders :: Handle -> Headers -> IO () +hPutHeaders :: HandleLike h => h -> Headers -> IO () hPutHeaders h hds = h `seq` hds `seq` - mapM_ putH (M.toList hds) >> C8.hPut h (C8.pack "\r\n") + mapM_ putH (M.toList hds) >> hPutBS h (C8.pack "\r\n") where - putH :: (NCBS, ByteString) -> IO () + putH :: (NCBS, Strict.ByteString) -> IO () putH (name, value) = name `seq` value `seq` - do C8.hPut h (fromNCBS name) - C8.hPut h (C8.pack ": ") - C8.hPut h value - C8.hPut h (C8.pack "\r\n") + do hPutBS h (fromNCBS name) + hPutBS h (C8.pack ": ") + hPutBS h value + hPutBS h (C8.pack "\r\n")