( Parser(..)
, ParserResult(..)
- , parse -- Parser a -> ByteString -> ParserResult a
+ , parse -- Parser a -> ByteString -> (ParserResult a, ByteString)
+ , parseStr -- Parser a -> String -> (ParserResult a, ByteString)
, anyChar -- Parser Char
+ , eof -- Parser ()
+ , allowEOF -- Parser a -> Parser a
, satisfy -- (Char -> Bool) -> Parser Char
, char -- Char -> Parser Char
, string -- String -> Parser String
, manyTill -- Parser a -> Parser end -> Parser [a]
, many1Till -- Parser a -> Parser end -> Parser [a]
, option -- a -> Parser a -> Parser a
+ , sepBy -- Parser a -> Parser sep -> Parser [a]
+ , sepBy1 -- Parser a -> Parser sep -> Parser [a]
+
, sp -- Parser Char
, ht -- Parser Char
, crlf -- Parser String
import Data.ByteString.Lazy.Char8 (ByteString)
data Parser a = Parser {
- runParser :: State ByteString (ParserResult a)
+ runParser :: State ParserState (ParserResult a)
}
+type ParserState = (ByteString, IsEOFFatal)
+
+type IsEOFFatal = Bool
+
data ParserResult a = Success a
| IllegalInput -- 受理出來ない入力があった
| ReachedEOF -- 限界を越えて讀まうとした
-- (>>=) :: Parser a -> (a -> Parser b) -> Parser b
instance Monad Parser where
- p >>= f = Parser $ do saved <- get -- 失敗した時の爲に状態を保存
+ p >>= f = Parser $ do saved@(_, isEOFFatal) <- get -- 失敗した時の爲に状態を保存
result <- runParser p
case result of
Success a -> runParser (f a)
IllegalInput -> do put saved -- 状態を復歸
return IllegalInput
- ReachedEOF -> return ReachedEOF
+ ReachedEOF -> if isEOFFatal then
+ return ReachedEOF
+ else
+ do put saved
+ return IllegalInput
return = Parser . return . Success
fail _ = Parser $ return IllegalInput
parse :: Parser a -> ByteString -> (ParserResult a, ByteString)
-parse p input = runState (runParser p) input
+parse p input = let (result, (input', _)) = runState (runParser p) (input, True)
+ in
+ (result, input')
+
+
+parseStr :: Parser a -> String -> (ParserResult a, ByteString)
+parseStr p input = parse p $ B.pack input
anyChar :: Parser Char
-anyChar = Parser $ do input <- get
+anyChar = Parser $ do (input, isEOFFatal) <- get
if B.null input then
return ReachedEOF
else
do let c = B.head input
- put (B.tail input)
+ put (B.tail input, isEOFFatal)
return (Success c)
+eof :: Parser ()
+eof = Parser $ do (input, _) <- get
+ if B.null input then
+ return $ Success ()
+ else
+ return IllegalInput
+
+
+allowEOF :: Parser a -> Parser a
+allowEOF f = Parser $ do (input, isEOFFatal) <- get
+ put (input, False)
+
+ result <- runParser f
+
+ (input', _) <- get
+ put (input', isEOFFatal)
+
+ return result
+
+
satisfy :: (Char -> Bool) -> Parser Char
satisfy f = do c <- anyChar
unless (f c) (fail "")
infixr 0 <|>
(<|>) :: Parser a -> Parser a -> Parser a
-f <|> g = Parser $ do saved <- get -- 状態を保存
+f <|> g = Parser $ do saved@(_, isEOFFatal) <- get -- 状態を保存
result <- runParser f
case result of
Success a -> return $ Success a
IllegalInput -> do put saved -- 状態を復歸
runParser g
- ReachedEOF -> return ReachedEOF
+ ReachedEOF -> if isEOFFatal then
+ return ReachedEOF
+ else
+ do put saved
+ runParser g
oneOf :: [Char] -> Parser Char
option def p = p <|> return def
+sepBy :: Parser a -> Parser sep -> Parser [a]
+sepBy p sep = sepBy1 p sep <|> return []
+
+
+sepBy1 :: Parser a -> Parser sep -> Parser [a]
+sepBy1 p sep = do x <- p
+ xs <- many $ sep >> p
+ return (x:xs)
+
+
sp :: Parser Char
sp = char ' '
, findResource -- ResTree -> URI -> Maybe ResourceDef
, runResource -- ResourceDef -> Interaction -> IO ThreadId
+ , getMethod -- Resource Method
+ , getHeader -- String -> Resource (Maybe String)
+
+ , foundEntity -- Bool -> String -> ClockTime -> Resource ()
+ , foundETag -- Bool -> String -> Resource ()
+ , foundTimeStamp -- ClockTime -> Resource ()
+ , foundNoEntity -- Maybe String -> Resource ()
+
, input -- Int -> Resource String
, inputChunk -- Int -> Resource String
, inputBS -- Int -> Resource ByteString
, setStatus -- StatusCode -> Resource ()
, setHeader -- String -> String -> Resource ()
-
, redirect -- StatusCode -> URI -> Resource ()
+ , setETag -- Bool -> String -> Resource ()
+ , setLastModified -- ClockTime -> Resource ()
, output -- String -> Resource ()
, outputChunk -- String -> Resource ()
import Network.HTTP.Lucu.Abortion
import Network.HTTP.Lucu.Config
import Network.HTTP.Lucu.DefaultPage
+import Network.HTTP.Lucu.ETag
import qualified Network.HTTP.Lucu.Headers as H
import Network.HTTP.Lucu.HttpVersion
import Network.HTTP.Lucu.Interaction
+import Network.HTTP.Lucu.Parser
import Network.HTTP.Lucu.Postprocess
+import Network.HTTP.Lucu.RFC1123DateTime
import Network.HTTP.Lucu.Request
import Network.HTTP.Lucu.Response
import Network.HTTP.Lucu.Utils
import Prelude hiding (catch)
import System.IO
import System.IO.Error hiding (catch)
+import System.Time
type Resource a = ReaderT Interaction IO a
show ioE
-{- Resource モナド -}
+getMethod :: Resource Method
+getMethod = do itr <- ask
+ return $ reqMethod $ fromJust $ itrRequest itr
+
+
+getHeader :: String -> Resource (Maybe String)
+getHeader name = do itr <- ask
+ return $ H.getHeader name $ fromJust $ itrRequest itr
+
+
+{- ExaminingRequest 時に使用するアクション群 -}
+
+foundEntity :: Bool -> String -> ClockTime -> Resource ()
+foundEntity isWeak token timeStamp
+ = do driftTo ExaminingRequest
+
+ method <- getMethod
+ when (method == GET || method == HEAD)
+ $ setHeader' "Last-Modified" $ formatHTTPDateTime timeStamp
+ foundETag isWeak token
+
+ driftTo GettingBody
+
+
+foundETag :: Bool -> String -> Resource ()
+foundETag isWeak token
+ = do driftTo ExaminingRequest
+
+ let tag = mkETag isWeak token
+
+ method <- getMethod
+ when (method == GET || method == HEAD)
+ $ setHeader' "ETag" $ show tag
+
+ -- If-Match があればそれを見る。
+ ifMatch <- getHeader "If-Match"
+ case ifMatch of
+ Nothing -> return ()
+ Just "*" -> return ()
+ Just list -> case parseStr eTagListP list of
+ (Success tags, _)
+ -- tags の中に一致するものが無ければ
+ -- PreconditionFailed で終了。
+ -> when (not $ any (== tag) tags)
+ $ abort PreconditionFailed [] ("The entity tag doesn't match: " ++ list)
+ _ -> abort BadRequest [] ("Unparsable If-Match: " ++ fromJust ifMatch)
+
+ let statusForNoneMatch = if method == GET || method == HEAD then
+ NotModified
+ else
+ PreconditionFailed
+
+ -- If-None-Match があればそれを見る。
+ ifNoneMatch <- getHeader "If-None-Match"
+ case ifNoneMatch of
+ Nothing -> return ()
+ Just "*" -> abort statusForNoneMatch [] ("The entity tag matches: *")
+ Just list -> case parseStr eTagListP list of
+ (Success tags, _)
+ -> when (any (== tag) tags)
+ $ abort statusForNoneMatch [] ("The entity tag matches: " ++ list)
+ _ -> abort BadRequest [] ("Unparsable If-None-Match: " ++ list)
+
+ driftTo GettingBody
+
+
+foundTimeStamp :: ClockTime -> Resource ()
+foundTimeStamp timeStamp
+ = do driftTo ExaminingRequest
+
+ method <- getMethod
+ when (method == GET || method == HEAD)
+ $ setHeader' "Last-Modified" $ formatHTTPDateTime timeStamp
+
+ let statusForIfModSince = if method == GET || method == HEAD then
+ NotModified
+ else
+ PreconditionFailed
+
+ -- If-Modified-Since があればそれを見る。
+ ifModSince <- getHeader "If-Modified-Since"
+ case ifModSince of
+ Just str -> case parseHTTPDateTime str of
+ Just lastTime
+ -> when (timeStamp <= lastTime)
+ $ abort statusForIfModSince [] ("The entity has not been modified since " ++ str)
+ Nothing
+ -> return () -- 不正な時刻は無視
+ Nothing -> return ()
+
+ -- If-Unmodified-Since があればそれを見る。
+ ifUnmodSince <- getHeader "If-Unmodified-Since"
+ case ifUnmodSince of
+ Just str -> case parseHTTPDateTime str of
+ Just lastTime
+ -> when (timeStamp > lastTime)
+ $ abort PreconditionFailed [] ("The entity has not been modified since " ++ str)
+ Nothing
+ -> return () -- 不正な時刻は無視
+ Nothing -> return ()
+
+ driftTo GettingBody
+
+
+foundNoEntity :: Maybe String -> Resource ()
+foundNoEntity msgM
+ = do driftTo ExaminingRequest
+
+ let msg = fromMaybe "The requested entity was not found in this server." msgM
+
+ method <- getMethod
+ when (method /= PUT)
+ $ abort NotFound [] msg
+
+ -- エンティティが存在しないと云ふ事は、"*" も含めたどのやうな
+ -- If-Match: 條件も滿たさない。
+ ifMatch <- getHeader "If-Match"
+ when (ifMatch /= Nothing)
+ $ abort PreconditionFailed [] msg
+
+ driftTo GettingBody
+
+
+{- GettingBody 時に使用するアクション群 -}
input :: Int -> Resource String
input limit = inputBS limit >>= return . B.unpack
inputBS :: Int -> Resource ByteString
inputBS limit
= do driftTo GettingBody
- itr <- ask
- let defaultLimit = cnfMaxEntityLength $ itrConfig itr
- actualLimit = if limit <= 0 then
- defaultLimit
- else
- limit
- when (actualLimit <= 0)
- $ fail ("inputBS: limit must be positive: " ++ show actualLimit)
- -- Reader にリクエスト
- liftIO $ atomically
- $ do chunkLen <- readItr itr itrReqChunkLength id
- writeItr itr itrWillReceiveBody True
- if fmap (> actualLimit) chunkLen == Just True then
- -- 受信前から多過ぎる事が分かってゐる
- tooLarge actualLimit
- else
- writeItr itr itrReqBodyWanted $ Just actualLimit
- -- 應答を待つ。トランザクションを分けなければ當然デッドロック。
- chunk <- liftIO $ atomically
- $ do chunk <- readItr itr itrReceivedBody id
- chunkIsOver <- readItr itr itrReqChunkIsOver id
- if B.length chunk < fromIntegral actualLimit then
- -- 要求された量に滿たなくて、まだ殘りがある
- -- なら再試行。
- unless chunkIsOver
- $ retry
- else
- -- 制限値一杯まで讀むやうに指示したのにまだ殘っ
- -- てゐるなら、それは多過ぎる。
- unless chunkIsOver
- $ tooLarge actualLimit
- -- 成功。itr 内にチャンクを置いたままにするとメ
- -- モリの無駄になるので除去。
- writeItr itr itrReceivedBody B.empty
- return chunk
- driftTo DecidingHeader
+ itr <- ask
+ hasBody <- liftIO $ atomically $ readItr itr itrRequestHasBody id
+ chunk <- if hasBody then
+ askForInput itr
+ else
+ do driftTo DecidingHeader
+ return B.empty
return chunk
where
+ askForInput :: Interaction -> Resource ByteString
+ askForInput itr
+ = do let defaultLimit = cnfMaxEntityLength $ itrConfig itr
+ actualLimit = if limit <= 0 then
+ defaultLimit
+ else
+ limit
+ when (actualLimit <= 0)
+ $ fail ("inputBS: limit must be positive: " ++ show actualLimit)
+ -- Reader にリクエスト
+ liftIO $ atomically
+ $ do chunkLen <- readItr itr itrReqChunkLength id
+ writeItr itr itrWillReceiveBody True
+ if fmap (> actualLimit) chunkLen == Just True then
+ -- 受信前から多過ぎる事が分かってゐる
+ tooLarge actualLimit
+ else
+ writeItr itr itrReqBodyWanted $ Just actualLimit
+ -- 應答を待つ。トランザクションを分けなければ當然デッドロック。
+ chunk <- liftIO $ atomically
+ $ do chunk <- readItr itr itrReceivedBody id
+ chunkIsOver <- readItr itr itrReqChunkIsOver id
+ if B.length chunk < fromIntegral actualLimit then
+ -- 要求された量に滿たなくて、まだ殘り
+ -- があるなら再試行。
+ unless chunkIsOver
+ $ retry
+ else
+ -- 制限値一杯まで讀むやうに指示したの
+ -- にまだ殘ってゐるなら、それは多過ぎ
+ -- る。
+ unless chunkIsOver
+ $ tooLarge actualLimit
+ -- 成功。itr 内にチャンクを置いたままにす
+ -- るとメモリの無駄になるので除去。
+ writeItr itr itrReceivedBody B.empty
+ return chunk
+ driftTo DecidingHeader
+ return chunk
+
tooLarge :: Int -> STM ()
tooLarge lim = abortSTM RequestEntityTooLarge []
("Request body must be smaller than "
inputChunkBS limit
= do driftTo GettingBody
itr <- ask
- let defaultLimit = cnfMaxEntityLength $ itrConfig itr
- actualLimit = if limit < 0 then
- defaultLimit
- else
- limit
- when (actualLimit <= 0)
- $ fail ("inputChunkBS: limit must be positive: " ++ show actualLimit)
- -- Reader にリクエスト
- liftIO $ atomically
- $ do writeItr itr itrReqBodyWanted $ Just actualLimit
- writeItr itr itrWillReceiveBody True
- -- 應答を待つ。トランザクションを分けなければ當然デッドロック。
- chunk <- liftIO $ atomically
- $ do chunk <- readItr itr itrReceivedBody id
- -- 要求された量に滿たなくて、まだ殘りがあるなら
- -- 再試行。
- when (B.length chunk < fromIntegral actualLimit)
- $ do chunkIsOver <- readItr itr itrReqChunkIsOver id
- unless chunkIsOver
- $ retry
- -- 成功
- writeItr itr itrReceivedBody B.empty
- return chunk
- when (B.null chunk)
- $ driftTo DecidingHeader
+ hasBody <- liftIO $ atomically $ readItr itr itrRequestHasBody id
+ chunk <- if hasBody then
+ askForInput itr
+ else
+ do driftTo DecidingHeader
+ return B.empty
return chunk
+ where
+ askForInput :: Interaction -> Resource ByteString
+ askForInput itr
+ = do let defaultLimit = cnfMaxEntityLength $ itrConfig itr
+ actualLimit = if limit < 0 then
+ defaultLimit
+ else
+ limit
+ when (actualLimit <= 0)
+ $ fail ("inputChunkBS: limit must be positive: " ++ show actualLimit)
+ -- Reader にリクエスト
+ liftIO $ atomically
+ $ do writeItr itr itrReqBodyWanted $ Just actualLimit
+ writeItr itr itrWillReceiveBody True
+ -- 應答を待つ。トランザクションを分けなければ當然デッドロック。
+ chunk <- liftIO $ atomically
+ $ do chunk <- readItr itr itrReceivedBody id
+ -- 要求された量に滿たなくて、まだ殘りがあ
+ -- るなら再試行。
+ when (B.length chunk < fromIntegral actualLimit)
+ $ do chunkIsOver <- readItr itr itrReqChunkIsOver id
+ unless chunkIsOver
+ $ retry
+ -- 成功
+ writeItr itr itrReceivedBody B.empty
+ return chunk
+ when (B.null chunk)
+ $ driftTo DecidingHeader
+ return chunk
defaultLimit :: Int
defaultLimit = (-1)
+
+{- DecidingHeader 時に使用するアクション群 -}
+
setStatus :: StatusCode -> Resource ()
setStatus code
= do driftTo DecidingHeader
setHeader :: String -> String -> Resource ()
setHeader name value
- = do driftTo DecidingHeader
- itr <- ask
+ = driftTo DecidingHeader >> setHeader' name value
+
+
+setHeader' :: String -> String -> Resource()
+setHeader' name value
+ = do itr <- ask
liftIO $ atomically $ updateItr itr itrResponse
$ \ resM -> case resM of
Nothing -> Just $ Response {
setHeader "Location" (uriToString id uri $ "")
+setETag :: Bool -> String -> Resource ()
+setETag isWeak token
+ = setHeader "ETag" $ show $ mkETag isWeak token
+
+
+setLastModified :: ClockTime -> Resource ()
+setLastModified lastmod
+ = setHeader "Last-Modified" $ formatHTTPDateTime lastmod
+
+
+{- DecidingBody 時に使用するアクション群 -}
+
output :: String -> Resource ()
output = outputBS . B.pack