X-Git-Url: http://git.cielonegro.org/gitweb.cgi?a=blobdiff_plain;f=Network%2FHTTP%2FLucu%2FResource%2FTree.hs;h=8fbe2bf2d6b529aa1b00ad4fc4c6b17b943b64b8;hb=ea2b7838f1b3d9d4923a220a601be2e04cc559d7;hp=9af5fd54ed809d19b1f65c168748a02b7878a641;hpb=858129cb755aa09da2b7bd758efb8519f2c89103;p=Lucu.git diff --git a/Network/HTTP/Lucu/Resource/Tree.hs b/Network/HTTP/Lucu/Resource/Tree.hs index 9af5fd5..8fbe2bf 100644 --- a/Network/HTTP/Lucu/Resource/Tree.hs +++ b/Network/HTTP/Lucu/Resource/Tree.hs @@ -1,37 +1,60 @@ --- #prune +{-# LANGUAGE + DoAndIfThenElse + , OverloadedStrings + , RecordWildCards + , UnicodeSyntax + #-} -- | Repository of the resources in httpd. module Network.HTTP.Lucu.Resource.Tree ( ResourceDef(..) + , emptyResource + , ResTree - , mkResTree -- [ ([String], ResourceDef) ] -> ResTree + , FallbackHandler + + , mkResTree - , findResource -- ResTree -> URI -> Maybe ([String], ResourceDef) - , runResource -- ResourceDef -> Interaction -> IO ThreadId + , findResource + , runResource ) where - +import Control.Arrow +import Control.Applicative +import Data.Ascii (Ascii) +import qualified Data.Ascii as A import Control.Concurrent import Control.Concurrent.STM import Control.Exception -import Control.Monad.Reader -import Data.Dynamic +import Control.Monad +import Data.Text (Text) +import qualified Data.Text as T +import qualified Data.Text.Lazy.Encoding as LT import Data.List import qualified Data.Map as M import Data.Map (Map) import Data.Maybe +import Data.Monoid.Unicode import Network.HTTP.Lucu.Abortion import Network.HTTP.Lucu.Config -import Network.HTTP.Lucu.MIMEType +import Network.HTTP.Lucu.Headers (fromHeaders) import Network.HTTP.Lucu.Request import Network.HTTP.Lucu.Resource import Network.HTTP.Lucu.Response import Network.HTTP.Lucu.Interaction import Network.HTTP.Lucu.Utils -import Network.URI +import Network.URI hiding (path) import System.IO -import System.IO.Error hiding (catch) import Prelude hiding (catch) +import Prelude.Unicode + + +-- |'FallbackHandler' is an extra resource handler for resources which +-- can't be statically located anywhere in the resource tree. The Lucu +-- httpd first searches for a resource in the tree, and then calls +-- fallback handlers to ask them for a resource. If all of the +-- handlers returned 'Nothing', the httpd responds with 404 Not Found. +type FallbackHandler = [Text] → IO (Maybe ResourceDef) -- "/aaa/bbb/ccc" にアクセスされた時、もし "/aaa/bbb" に貪欲なリソース @@ -39,209 +62,236 @@ import Prelude hiding (catch) -- "/aaa/bbb" が撰ばれる。"/aaa/bbb" のリソースが貪欲でなければ、それは -- 無視される。 --- | 'ResourceDef' is basically a set of --- 'Network.HTTP.Lucu.Resource.Resource' monads for each HTTP methods. +-- | 'ResourceDef' is basically a set of 'Resource' monads for each +-- HTTP methods. data ResourceDef = ResourceDef { - -- | Whether to run a 'Network.HTTP.Lucu.Resource.Resource' on a - -- native thread (spawned using @forkOS@) or to run it on a user - -- thread (spanwed using @forkIO@). Generally you don't - resUsesNativeThread :: !Bool + -- |Whether to run a 'Resource' on a native thread (spawned by + -- 'forkOS') or to run it on a user thread (spanwed by + -- 'forkIO'). Generally you don't need to set this field to + -- 'True'. + resUsesNativeThread ∷ !Bool -- | Whether to be greedy or not. -- -- Say a client is trying to access \/aaa\/bbb\/ccc. If there is a -- greedy resource at \/aaa\/bbb, it is always chosen even if -- there is another resource at \/aaa\/bbb\/ccc. If the resource -- at \/aaa\/bbb is not greedy, it is just ignored. Greedy - -- resource is like a CGI script. - , resIsGreedy :: !Bool - -- | A 'Network.HTTP.Lucu.Resource.Resource' to be run when a GET - -- request comes for the resource path. If 'resGet' is Nothing, - -- the system responds \"405 Method Not Allowed\" for GET - -- requests. + -- resources are like CGI scripts. + , resIsGreedy ∷ !Bool + -- | A 'Resource' to be run when a GET request comes for the + -- resource path. If 'resGet' is Nothing, the system responds + -- \"405 Method Not Allowed\" for GET requests. -- -- It also runs for HEAD request if the 'resHead' is Nothing. In - -- this case 'Network.HTTP.Lucu.Resource.output' and such like - -- don't actually write a response body. - , resGet :: !(Maybe (Resource ())) - -- | A 'Network.HTTP.Lucu.Resource.Resource' to be run when a HEAD - -- request comes for the resource path. If 'resHead' is Nothing, - -- the system runs 'resGet' instead. If 'resGet' is also Nothing, - -- the system responds \"405 Method Not Allowed\" for HEAD - -- requests. - , resHead :: !(Maybe (Resource ())) - -- | A 'Network.HTTP.Lucu.Resource.Resource' to be run when a POST - -- request comes for the resource path. If 'resPost' is Nothing, - -- the system responds \"405 Method Not Allowed\" for POST - -- requests. - , resPost :: !(Maybe (Resource ())) - -- | A 'Network.HTTP.Lucu.Resource.Resource' to be run when a PUT - -- request comes for the resource path. If 'resPut' is Nothing, - -- the system responds \"405 Method Not Allowed\" for PUT - -- requests. - , resPut :: !(Maybe (Resource ())) - -- | A 'Network.HTTP.Lucu.Resource.Resource' to be run when a - -- DELETE request comes for the resource path. If 'resDelete' is - -- Nothing, the system responds \"405 Method Not Allowed\" for - -- DELETE requests. - , resDelete :: !(Maybe (Resource ())) + -- this case 'output' and such like don't actually write a + -- response body. + , resGet ∷ !(Maybe (Resource ())) + -- | A 'Resource' to be run when a HEAD request comes for the + -- resource path. If 'resHead' is Nothing, the system runs + -- 'resGet' instead. If 'resGet' is also Nothing, the system + -- responds \"405 Method Not Allowed\" for HEAD requests. + , resHead ∷ !(Maybe (Resource ())) + -- | A 'Resource' to be run when a POST request comes for the + -- resource path. If 'resPost' is Nothing, the system responds + -- \"405 Method Not Allowed\" for POST requests. + , resPost ∷ !(Maybe (Resource ())) + -- | A 'Resource' to be run when a PUT request comes for the + -- resource path. If 'resPut' is Nothing, the system responds + -- \"405 Method Not Allowed\" for PUT requests. + , resPut ∷ !(Maybe (Resource ())) + -- | A 'Resource' to be run when a DELETE request comes for the + -- resource path. If 'resDelete' is Nothing, the system responds + -- \"405 Method Not Allowed\" for DELETE requests. + , resDelete ∷ !(Maybe (Resource ())) } --- | 'ResTree' is an opaque structure which is a map from resource --- path to 'ResourceDef'. -type ResTree = ResNode -- root だから Map ではない -type ResSubtree = Map String ResNode -data ResNode = ResNode !(Maybe ResourceDef) !ResSubtree +-- |'emptyResource' is a resource definition with no actual +-- handlers. You can construct a 'ResourceDef' by selectively +-- overriding 'emptyResource'. It is defined as follows: +-- +-- @ +-- emptyResource = ResourceDef { +-- resUsesNativeThread = False +-- , resIsGreedy = False +-- , resGet = Nothing +-- , resHead = Nothing +-- , resPost = Nothing +-- , resPut = Nothing +-- , resDelete = Nothing +-- } +-- @ +emptyResource ∷ ResourceDef +emptyResource = ResourceDef { + resUsesNativeThread = False + , resIsGreedy = False + , resGet = Nothing + , resHead = Nothing + , resPost = Nothing + , resPut = Nothing + , resDelete = Nothing + } + +-- |'ResTree' is an opaque structure which is a map from resource path +-- to 'ResourceDef'. +newtype ResTree = ResTree ResNode -- root だから Map ではない +type ResSubtree = Map Text ResNode +data ResNode = ResNode (Maybe ResourceDef) ResSubtree --- | 'mkResTree' converts a list of @(path, def)@ to a 'ResTree' e.g. +-- |'mkResTree' converts a list of @(path, def)@ to a 'ResTree' e.g. -- -- @ -- mkResTree [ ([] , 'Network.HTTP.Lucu.StaticFile.staticFile' \"\/usr\/include\/stdio.h\" ) -- \/ -- , ([\"unistd\"], 'Network.HTTP.Lucu.StaticFile.staticFile' \"\/usr\/include\/unistd.h\") -- \/unistd -- ] -- @ -mkResTree :: [ ([String], ResourceDef) ] -> ResTree -mkResTree list = list `seq` processRoot list +mkResTree ∷ [ ([Text], ResourceDef) ] → ResTree +mkResTree = processRoot ∘ map (first canonicalisePath) where - processRoot :: [ ([String], ResourceDef) ] -> ResTree + canonicalisePath ∷ [Text] → [Text] + canonicalisePath = filter (≢ "") + + processRoot ∷ [ ([Text], ResourceDef) ] → ResTree processRoot list - = let (roots, nonRoots) = partition (\ (path, _) -> path == []) list + = let (roots, nonRoots) = partition (\(path, _) → null path) list children = processNonRoot nonRoots in if null roots then - -- "/" にリソースが定義されない。"/foo" とかにはあるかも。 - ResNode Nothing children + -- The root has no resources. Maybe there's one at + -- somewhere like "/foo". + ResTree (ResNode Nothing children) else - -- "/" がある。 + -- There is a root resource. let (_, def) = last roots in - ResNode (Just def) children + ResTree (ResNode (Just def) children) - processNonRoot :: [ ([String], ResourceDef) ] -> ResSubtree + processNonRoot ∷ [ ([Text], ResourceDef) ] → ResSubtree processNonRoot list = let subtree = M.fromList [(name, node name) - | name <- childNames] - childNames = [name | (name:_, _) <- list] - node name = let defs = [def | (path, def) <- list, path == [name]] + | name ← childNames] + childNames = [name | (name:_, _) ← list] + node name = let defs = [def | (path, def) ← list, path ≡ [name]] in if null defs then - -- この位置にリソースが定義されない。 - -- もっと下にはあるかも。 + -- No resources are defined + -- here. Maybe there's one at + -- somewhere below this node. ResNode Nothing children else - -- この位置にリソースがある。 + -- There is a resource here. ResNode (Just $ last defs) children children = processNonRoot [(path, def) - | (_:path, def) <- list, not (null path)] + | (_:path, def) ← list] in subtree - -findResource :: ResTree -> URI -> Maybe ([String], ResourceDef) -findResource (ResNode rootDefM subtree) uri - = let pathStr = uriPath uri - path = [x | x <- splitBy (== '/') pathStr, x /= ""] - in - if null path then - do def <- rootDefM - return (path, def) - else - walkTree subtree path [] +findResource ∷ ResTree → [FallbackHandler] → URI → IO (Maybe ([Text], ResourceDef)) +findResource (ResTree (ResNode rootDefM subtree)) fbs uri + = do let path = splitPathInfo uri + hasGreedyRoot = maybe False resIsGreedy rootDefM + foundInTree = if hasGreedyRoot ∨ null path then + do def ← rootDefM + return ([], def) + else + walkTree subtree path [] + if isJust foundInTree then + return foundInTree + else + fallback path fbs where - walkTree :: ResSubtree -> [String] -> [String] -> Maybe ([String], ResourceDef) - - walkTree subtree (name:[]) soFar - = case M.lookup name subtree of - Nothing -> Nothing - Just (ResNode defM _) -> do def <- defM - return (soFar ++ [name], def) - - walkTree subtree (x:xs) soFar - = case M.lookup x subtree of - Nothing -> Nothing - Just (ResNode defM children) -> case defM of - Just (ResourceDef { resIsGreedy = True }) - -> do def <- defM - return (soFar ++ [x], def) - _ -> walkTree children xs (soFar ++ [x]) - - -runResource :: ResourceDef -> Interaction -> IO ThreadId -runResource def itr - = def `seq` itr `seq` - fork - $! catch ( runReaderT ( do req <- getRequest - fromMaybe notAllowed $ rsrc req - driftTo Done - ) itr - ) - $ \ exc -> processException exc + walkTree ∷ ResSubtree → [Text] → [Text] → Maybe ([Text], ResourceDef) + + walkTree _ [] _ + = error "Internal error: should not reach here." + + walkTree tree (name:[]) soFar + = do ResNode defM _ ← M.lookup name tree + def ← defM + return (soFar ⧺ [name], def) + + walkTree tree (x:xs) soFar + = do ResNode defM sub ← M.lookup x tree + case defM of + Just (ResourceDef { resIsGreedy = True }) + → do def ← defM + return (soFar ⧺ [x], def) + _ → walkTree sub xs (soFar ⧺ [x]) + + fallback ∷ [Text] → [FallbackHandler] → IO (Maybe ([Text], ResourceDef)) + fallback _ [] = return Nothing + fallback path (x:xs) = do m ← x path + case m of + Just def → return $ Just ([], def) + Nothing → fallback path xs + + +runResource ∷ ResourceDef → Interaction → IO ThreadId +runResource (ResourceDef {..}) itr@(Interaction {..}) + = fork $ run `catch` processException where - fork :: IO () -> IO ThreadId - fork = if (resUsesNativeThread def) - then forkOS - else forkIO + fork ∷ IO () → IO ThreadId + fork | resUsesNativeThread = forkOS + | otherwise = forkIO + + run ∷ IO () + run = flip runRes itr $ + do req ← getRequest + fromMaybe notAllowed $ rsrc req + driftTo Done - rsrc :: Request -> Maybe (Resource ()) + rsrc ∷ Request → Maybe (Resource ()) rsrc req = case reqMethod req of - GET -> resGet def - HEAD -> case resHead def of - Just r -> Just r - Nothing -> resGet def - POST -> resPost def - PUT -> resPut def - DELETE -> resDelete def - - notAllowed :: Resource () - notAllowed = do setStatus MethodNotAllowed - setHeader "Allow" $ joinWith ", " allowedMethods - - allowedMethods :: [String] - allowedMethods = nub $ foldr (++) [] [ methods resGet ["GET"] - , methods resHead ["GET", "HEAD"] - , methods resPost ["POST"] - , methods resPut ["PUT"] - , methods resDelete ["DELETE"] - ] - - methods :: (ResourceDef -> Maybe a) -> [String] -> [String] - methods f xs = case f def of - Just _ -> xs - Nothing -> [] - - processException :: Exception -> IO () + GET → resGet + HEAD → case resHead of + Just r → Just r + Nothing → resGet + POST → resPost + PUT → resPut + DELETE → resDelete + _ → error $ "Unknown request method: " ⧺ show (reqMethod req) + + notAllowed ∷ Resource () + notAllowed + = setStatus MethodNotAllowed + *> + (setHeader "Allow" $ A.fromAsciiBuilder + $ joinWith ", " + $ map A.toAsciiBuilder allowedMethods) + + allowedMethods ∷ [Ascii] + allowedMethods = nub $ concat [ methods resGet ["GET"] + , methods resHead ["GET", "HEAD"] + , methods resPost ["POST"] + , methods resPut ["PUT"] + , methods resDelete ["DELETE"] + ] + + methods ∷ Maybe a → [Ascii] → [Ascii] + methods m xs + | isJust m = xs + | otherwise = [] + + toAbortion ∷ SomeException → Abortion + toAbortion e + = case fromException e of + Just abortion → abortion + Nothing → Abortion InternalServerError (∅) (Just $ T.pack $ show e) + + processException ∷ SomeException → IO () processException exc - = do let abo = case exc of - ErrorCall msg -> Abortion InternalServerError [] $ Just msg - IOException ioE -> Abortion InternalServerError [] $ Just $ formatIOE ioE - DynException dynE -> case fromDynamic dynE of - Just (abo :: Abortion) -> abo - Nothing - -> Abortion InternalServerError [] - $ Just $ show exc - _ -> Abortion InternalServerError [] $ Just $ show exc - conf = itrConfig itr + = do let abo = toAbortion exc -- まだ DecidingHeader 以前の状態だったら、この途中終了 -- を應答に反映させる餘地がある。さうでなければ stderr -- にでも吐くしか無い。 - state <- atomically $ readItr itr itrState id - reqM <- atomically $ readItr itr itrRequest id - res <- atomically $ readItr itr itrResponse id - if state <= DecidingHeader then - flip runReaderT itr - $ do setStatus $ aboStatus abo - -- FIXME: 同じ名前で複數の値があった時は、こ - -- れではまずいと思ふ。 - mapM_ (\ (name, value) -> setHeader name value) $ aboHeaders abo - output $ abortPage conf reqM res abo - else - when (cnfDumpTooLateAbortionToStderr $ itrConfig itr) - $ hPutStrLn stderr $ show abo - - flip runReaderT itr $ driftTo Done - - formatIOE :: IOError -> String - formatIOE ioE = if isUserError ioE then - ioeGetErrorString ioE - else - show ioE + state ← atomically $ readTVar itrState + res ← atomically $ readTVar itrResponse + if state ≤ DecidingHeader then + flip runRes itr $ + do setStatus $ aboStatus abo + mapM_ (uncurry setHeader) $ fromHeaders $ aboHeaders abo + output $ LT.encodeUtf8 $ abortPage itrConfig itrRequest res abo + else + when (cnfDumpTooLateAbortionToStderr itrConfig) + $ hPutStrLn stderr $ show abo + runRes (driftTo Done) itr