X-Git-Url: http://git.cielonegro.org/gitweb.cgi?a=blobdiff_plain;f=Network%2FHTTP%2FLucu%2FHeaders.hs;h=c97c93cb652156c618d92bab8977fa2627fda117;hb=15aa04a569fb13fb0793389f78f52b0255083cef;hp=65a4940026d5b626d4a11bbec50449d101745256;hpb=d05d8c883eaca12ee621975a2b95c5ebdc2357d2;p=Lucu.git diff --git a/Network/HTTP/Lucu/Headers.hs b/Network/HTTP/Lucu/Headers.hs index 65a4940..c97c93c 100644 --- a/Network/HTTP/Lucu/Headers.hs +++ b/Network/HTTP/Lucu/Headers.hs @@ -1,51 +1,139 @@ module Network.HTTP.Lucu.Headers ( Headers , HasHeaders(..) + + , noCaseCmp + , noCaseEq + , emptyHeaders + , toHeaders + , fromHeaders + , headersP , hPutHeaders ) where +import Data.ByteString.Base (ByteString, toForeignPtr, w2c, inlinePerformIO) +import qualified Data.ByteString.Char8 as C8 import Data.Char import Data.List +import Data.Map (Map) +import qualified Data.Map as M +import Data.Word +import Foreign.ForeignPtr +import Foreign.Ptr +import Foreign.Storable import Network.HTTP.Lucu.Parser import Network.HTTP.Lucu.Parser.Http import Network.HTTP.Lucu.Utils import System.IO -type Headers = [ (String, String) ] +type Headers = Map NCBS ByteString +newtype NCBS = NCBS ByteString + +toNCBS :: ByteString -> NCBS +toNCBS = NCBS +{-# INLINE toNCBS #-} + +fromNCBS :: NCBS -> ByteString +fromNCBS (NCBS x) = x +{-# INLINE fromNCBS #-} + +instance Eq NCBS where + (NCBS a) == (NCBS b) = a == b + +instance Ord NCBS where + (NCBS a) `compare` (NCBS b) = a `noCaseCmp` b + +instance Show NCBS where + show (NCBS x) = show x + +noCaseCmp :: ByteString -> ByteString -> Ordering +noCaseCmp a b = toForeignPtr a `cmp` toForeignPtr b + where + cmp :: (ForeignPtr Word8, Int, Int) -> (ForeignPtr Word8, Int, Int) -> Ordering + cmp (x1, s1, l1) (x2, s2, l2) + | l1 == 0 && l2 == 0 = EQ + | x1 == x2 && s1 == s2 && l1 == l2 = EQ + | otherwise + = inlinePerformIO $ + 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 + | l1 == 0 && l2 == 0 = return EQ + | l1 == 0 && l1 /= 0 = return LT + | l1 /= 0 && l2 == 0 = return GT + | otherwise + = do c1 <- peek p1 + c2 <- peek p2 + case toLower (w2c c1) `compare` toLower (w2c c2) of + EQ -> noCaseCmp' (p1 `plusPtr` 1) (l1 - 1) (p2 `plusPtr` 1) (l2 - 1) + x -> return x + + +noCaseEq :: ByteString -> ByteString -> Bool +noCaseEq a b = toForeignPtr a `cmp` toForeignPtr b + where + cmp :: (ForeignPtr Word8, Int, Int) -> (ForeignPtr Word8, Int, Int) -> Bool + cmp (x1, s1, l1) (x2, s2, l2) + | l1 /= l2 = False + | l1 == 0 && l2 == 0 = True + | x1 == x2 && s1 == s2 && l1 == l2 = True + | otherwise + = inlinePerformIO $ + withForeignPtr x1 $ \ p1 -> + withForeignPtr x2 $ \ p2 -> + noCaseEq' (p1 `plusPtr` s1) (p2 `plusPtr` s2) l1 + + +noCaseEq' :: Ptr Word8 -> Ptr Word8 -> Int -> IO Bool +noCaseEq' p1 p2 l + | l == 0 = return True + | otherwise + = do c1 <- peek p1 + c2 <- peek p2 + if toLower (w2c c1) == toLower (w2c c2) then + noCaseEq' (p1 `plusPtr` 1) (p2 `plusPtr` 1) (l - 1) + else + return False + class HasHeaders a where getHeaders :: a -> Headers setHeaders :: a -> Headers -> a - getHeader :: String -> a -> Maybe String + getHeader :: ByteString -> a -> Maybe ByteString getHeader key a = key `seq` a `seq` - fmap snd $ find (noCaseEq' key . fst) (getHeaders a) + M.lookup (toNCBS key) (getHeaders a) - deleteHeader :: String -> a -> a + deleteHeader :: ByteString -> a -> a deleteHeader key a = key `seq` a `seq` - setHeaders a $ filter (not . noCaseEq' key . fst) (getHeaders a) - - addHeader :: String -> String -> a -> a - addHeader key val a - = key `seq` val `seq` a `seq` - setHeaders a $ (getHeaders a) ++ [(key, val)] + setHeaders a $ M.delete (toNCBS key) (getHeaders a) - setHeader :: String -> String -> a -> a + setHeader :: ByteString -> ByteString -> a -> a setHeader key val a = key `seq` val `seq` a `seq` - let list = getHeaders a - deleted = filter (not . noCaseEq' key . fst) list - added = deleted ++ [(key, val)] - in - setHeaders a added + setHeaders a $ M.insert (toNCBS key) val (getHeaders a) + emptyHeaders :: Headers -emptyHeaders = [] +emptyHeaders = M.empty + + +toHeaders :: [(ByteString, ByteString)] -> Headers +toHeaders xs = M.fromList [(toNCBS a, b) | (a, b) <- xs] + + +fromHeaders :: Headers -> [(ByteString, ByteString)] +fromHeaders hs = [(fromNCBS a, b) | (a, b) <- M.toList hs] {- @@ -62,9 +150,9 @@ emptyHeaders = [] headersP :: Parser Headers headersP = do xs <- many header crlf - return xs + return (M.fromList xs) where - header :: Parser (String, String) + header :: Parser (NCBS, ByteString) header = do name <- token char ':' -- FIXME: これは多少インチキだが、RFC 2616 のこの部分 @@ -76,7 +164,8 @@ headersP = do xs <- many header contents <- many (lws <|> many1 text) crlf let value = foldr (++) "" contents - return (name, normalize value) + norm = normalize value + return (toNCBS $ C8.pack name, C8.pack norm) normalize :: String -> String normalize = trimBody . trim isWhiteSpace @@ -95,12 +184,12 @@ headersP = do xs <- many header hPutHeaders :: Handle -> Headers -> IO () hPutHeaders h hds = h `seq` hds `seq` - mapM_ putH hds >> hPutStr h "\r\n" + mapM_ putH (M.toList hds) >> hPutStr h "\r\n" where - putH :: (String, String) -> IO () + putH :: (NCBS, ByteString) -> IO () putH (name, value) = name `seq` value `seq` - do hPutStr h name - hPutStr h ": " - hPutStr h value - hPutStr h "\r\n" + do C8.hPutStr h (fromNCBS name) + C8.hPutStr h (C8.pack ": ") + C8.hPutStr h value + C8.hPutStr h (C8.pack "\r\n")