1 {-# OPTIONS_HADDOCK prune #-}
3 -- | Repository of the resources in httpd.
4 module Network.HTTP.Lucu.Resource.Tree
9 , mkResTree -- [ ([String], ResourceDef) ] -> ResTree
11 , findResource -- ResTree -> URI -> Maybe ([String], ResourceDef)
12 , runResource -- ResourceDef -> Interaction -> IO ThreadId
16 import Control.Concurrent
17 import Control.Concurrent.STM
18 import Control.Exception
20 import qualified Data.ByteString.Char8 as C8
22 import qualified Data.Map as M
25 import Network.HTTP.Lucu.Abortion
26 import Network.HTTP.Lucu.Config
27 import Network.HTTP.Lucu.Headers (emptyHeaders, fromHeaders)
28 import Network.HTTP.Lucu.Request
29 import Network.HTTP.Lucu.Resource
30 import Network.HTTP.Lucu.Response
31 import Network.HTTP.Lucu.Interaction
32 import Network.HTTP.Lucu.Utils
33 import Network.URI hiding (path)
35 import Prelude hiding (catch)
38 -- |'FallbackHandler' is an extra resource handler for resources which
39 -- can't be statically located somewhere in the resource tree. The
40 -- Lucu httpd first search for a resource in the tree, and then call
41 -- fallback handlers to ask them for a resource. If all of the
42 -- handlers returned 'Prelude.Nothing', the httpd responds with 404
44 type FallbackHandler = [String] -> IO (Maybe ResourceDef)
47 -- "/aaa/bbb/ccc" にアクセスされた時、もし "/aaa/bbb" に貪欲なリソース
48 -- があれば、假に "/aaa/bbb/ccc" に何らかのリソースがあったとしても必ず
49 -- "/aaa/bbb" が撰ばれる。"/aaa/bbb" のリソースが貪欲でなければ、それは
52 -- | 'ResourceDef' is basically a set of
53 -- 'Network.HTTP.Lucu.Resource.Resource' monads for each HTTP methods.
54 data ResourceDef = ResourceDef {
55 -- |Whether to run a 'Network.HTTP.Lucu.Resource.Resource' on a
56 -- native thread (spawned by 'Control.Concurrent.forkOS') or to
57 -- run it on a user thread (spanwed by
58 -- 'Control.Concurrent.forkIO'). Generally you don't need to set
59 -- this field to 'Prelude.True'.
60 resUsesNativeThread :: !Bool
61 -- | Whether to be greedy or not.
63 -- Say a client is trying to access \/aaa\/bbb\/ccc. If there is a
64 -- greedy resource at \/aaa\/bbb, it is always chosen even if
65 -- there is another resource at \/aaa\/bbb\/ccc. If the resource
66 -- at \/aaa\/bbb is not greedy, it is just ignored. Greedy
67 -- resources are like CGI scripts.
68 , resIsGreedy :: !Bool
69 -- | A 'Network.HTTP.Lucu.Resource.Resource' to be run when a GET
70 -- request comes for the resource path. If 'resGet' is Nothing,
71 -- the system responds \"405 Method Not Allowed\" for GET
74 -- It also runs for HEAD request if the 'resHead' is Nothing. In
75 -- this case 'Network.HTTP.Lucu.Resource.output' and such like
76 -- don't actually write a response body.
77 , resGet :: !(Maybe (Resource ()))
78 -- | A 'Network.HTTP.Lucu.Resource.Resource' to be run when a HEAD
79 -- request comes for the resource path. If 'resHead' is Nothing,
80 -- the system runs 'resGet' instead. If 'resGet' is also Nothing,
81 -- the system responds \"405 Method Not Allowed\" for HEAD
83 , resHead :: !(Maybe (Resource ()))
84 -- | A 'Network.HTTP.Lucu.Resource.Resource' to be run when a POST
85 -- request comes for the resource path. If 'resPost' is Nothing,
86 -- the system responds \"405 Method Not Allowed\" for POST
88 , resPost :: !(Maybe (Resource ()))
89 -- | A 'Network.HTTP.Lucu.Resource.Resource' to be run when a PUT
90 -- request comes for the resource path. If 'resPut' is Nothing,
91 -- the system responds \"405 Method Not Allowed\" for PUT
93 , resPut :: !(Maybe (Resource ()))
94 -- | A 'Network.HTTP.Lucu.Resource.Resource' to be run when a
95 -- DELETE request comes for the resource path. If 'resDelete' is
96 -- Nothing, the system responds \"405 Method Not Allowed\" for
98 , resDelete :: !(Maybe (Resource ()))
101 -- |'ResTree' is an opaque structure which is a map from resource path
103 newtype ResTree = ResTree ResNode -- root だから Map ではない
104 type ResSubtree = Map String ResNode
105 data ResNode = ResNode !(Maybe ResourceDef) !ResSubtree
107 -- |'mkResTree' converts a list of @(path, def)@ to a 'ResTree' e.g.
110 -- mkResTree [ ([] , 'Network.HTTP.Lucu.StaticFile.staticFile' \"\/usr\/include\/stdio.h\" ) -- \/
111 -- , ([\"unistd\"], 'Network.HTTP.Lucu.StaticFile.staticFile' \"\/usr\/include\/unistd.h\") -- \/unistd
114 mkResTree :: [ ([String], ResourceDef) ] -> ResTree
115 mkResTree xs = xs `seq` processRoot xs
117 processRoot :: [ ([String], ResourceDef) ] -> ResTree
119 = let (roots, nonRoots) = partition (\ (path, _) -> path == []) list
120 children = processNonRoot nonRoots
123 -- "/" にリソースが定義されない。"/foo" とかにはあるかも。
124 ResTree (ResNode Nothing children)
127 let (_, def) = last roots
129 ResTree (ResNode (Just def) children)
131 processNonRoot :: [ ([String], ResourceDef) ] -> ResSubtree
133 = let subtree = M.fromList [(name, node name)
134 | name <- childNames]
135 childNames = [name | (name:_, _) <- list]
136 node name = let defs = [def | (path, def) <- list, path == [name]]
141 ResNode Nothing children
144 ResNode (Just $ last defs) children
145 children = processNonRoot [(path, def)
146 | (_:path, def) <- list, not (null path)]
151 findResource :: ResTree -> [FallbackHandler] -> URI -> IO (Maybe ([String], ResourceDef))
152 findResource (ResTree (ResNode rootDefM subtree)) fbs uri
153 = do let pathStr = uriPath uri
154 path = [x | x <- splitBy (== '/') pathStr, x /= ""]
155 foundInTree = if null path then
159 walkTree subtree path []
160 if isJust foundInTree then
165 walkTree :: ResSubtree -> [String] -> [String] -> Maybe ([String], ResourceDef)
168 = error "Internal error: should not reach here."
170 walkTree tree (name:[]) soFar
171 = case M.lookup name tree of
173 Just (ResNode defM _) -> do def <- defM
174 return (soFar ++ [name], def)
176 walkTree tree (x:xs) soFar
177 = case M.lookup x tree of
179 Just (ResNode defM children) -> case defM of
180 Just (ResourceDef { resIsGreedy = True })
182 return (soFar ++ [x], def)
183 _ -> walkTree children xs (soFar ++ [x])
185 fallback :: [String] -> [FallbackHandler] -> IO (Maybe ([String], ResourceDef))
186 fallback _ [] = return Nothing
187 fallback path (x:xs) = do m <- x path
189 Just def -> return $! Just ([], def)
190 Nothing -> fallback path xs
193 runResource :: ResourceDef -> Interaction -> IO ThreadId
195 = def `seq` itr `seq`
197 $! catch ( runRes ( do req <- getRequest
198 fromMaybe notAllowed $ rsrc req
202 $ \ exc -> processException exc
204 fork :: IO () -> IO ThreadId
205 fork = if (resUsesNativeThread def)
209 rsrc :: Request -> Maybe (Resource ())
211 = case reqMethod req of
213 HEAD -> case resHead def of
215 Nothing -> resGet def
218 DELETE -> resDelete def
221 notAllowed :: Resource ()
222 notAllowed = do setStatus MethodNotAllowed
223 setHeader (C8.pack "Allow") (C8.pack $ joinWith ", " allowedMethods)
225 allowedMethods :: [String]
226 allowedMethods = nub $ foldr (++) [] [ methods resGet ["GET"]
227 , methods resHead ["GET", "HEAD"]
228 , methods resPost ["POST"]
229 , methods resPut ["PUT"]
230 , methods resDelete ["DELETE"]
233 methods :: (ResourceDef -> Maybe a) -> [String] -> [String]
234 methods f xs = case f def of
238 toAbortion :: SomeException -> Abortion
239 toAbortion e = case fromException e of
240 Just abortion -> abortion
241 Nothing -> Abortion InternalServerError emptyHeaders (Just (show e))
243 processException :: SomeException -> IO ()
245 = do let abo = toAbortion exc
247 -- まだ DecidingHeader 以前の状態だったら、この途中終了
248 -- を應答に反映させる餘地がある。さうでなければ stderr
250 state <- atomically $ readItr itr itrState id
251 reqM <- atomically $ readItr itr itrRequest id
252 res <- atomically $ readItr itr itrResponse id
253 if state <= DecidingHeader then
255 $ do setStatus $ aboStatus abo
256 mapM_ (\ (name, value) -> setHeader name value) $ fromHeaders $ aboHeaders abo
257 output $ abortPage conf reqM res abo
259 when (cnfDumpTooLateAbortionToStderr $ itrConfig itr)
260 $ hPutStrLn stderr $ show abo
262 flip runRes itr $ driftTo Done