]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Resource/Tree.hs
Fixed breakage on GHC 6.10.1
[Lucu.git] / Network / HTTP / Lucu / Resource / Tree.hs
index be51282c910ad11c78754190b7f96b35563a7d9a..40a4150dc9fe1694cee60f55703f257c10032a0c 100644 (file)
@@ -1,6 +1,11 @@
+{-# OPTIONS_HADDOCK prune #-}
+
+-- | Repository of the resources in httpd.
 module Network.HTTP.Lucu.Resource.Tree
     ( ResourceDef(..)
     , ResTree
+    , FallbackHandler
+
     , mkResTree    -- [ ([String], ResourceDef) ] -> ResTree
 
     , findResource -- ResTree -> URI -> Maybe ([String], ResourceDef)
@@ -11,46 +16,104 @@ module Network.HTTP.Lucu.Resource.Tree
 import           Control.Concurrent
 import           Control.Concurrent.STM
 import           Control.Exception
-import           Control.Monad.Reader
-import           Data.Dynamic
+import           Control.Monad
+import qualified Data.ByteString.Char8 as C8
 import           Data.List
 import qualified Data.Map as M
 import           Data.Map (Map)
 import           Data.Maybe
 import           Network.HTTP.Lucu.Abortion
 import           Network.HTTP.Lucu.Config
-import           Network.HTTP.Lucu.MIMEType
+import           Network.HTTP.Lucu.Headers (emptyHeaders, 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)
 
 
+-- |'FallbackHandler' is an extra resource handler for resources which
+-- can't be statically located somewhere in the resource tree. The
+-- Lucu httpd first search for a resource in the tree, and then call
+-- fallback handlers to ask them for a resource. If all of the
+-- handlers returned 'Prelude.Nothing', the httpd responds with 404
+-- Not Found.
+type FallbackHandler = [String] -> IO (Maybe ResourceDef)
+
+
 -- "/aaa/bbb/ccc" にアクセスされた時、もし "/aaa/bbb" に貪欲なリソース
 -- があれば、假に "/aaa/bbb/ccc" に何らかのリソースがあったとしても必ず
 -- "/aaa/bbb" が撰ばれる。"/aaa/bbb" のリソースが貪欲でなければ、それは
 -- 無視される。
+
+-- | 'ResourceDef' is basically a set of
+-- 'Network.HTTP.Lucu.Resource.Resource' monads for each HTTP methods.
 data ResourceDef = ResourceDef {
-      resUsesNativeThread :: Bool
-    , resIsGreedy         :: Bool
-    , resGet              :: Maybe (Resource ())
-    , resHead             :: Maybe (Resource ())
-    , resPost             :: Maybe (Resource ())
-    , resPut              :: Maybe (Resource ())
-    , resDelete           :: Maybe (Resource ())
+    -- |Whether to run a 'Network.HTTP.Lucu.Resource.Resource' on a
+    -- native thread (spawned by 'Control.Concurrent.forkOS') or to
+    -- run it on a user thread (spanwed by
+    -- 'Control.Concurrent.forkIO'). Generally you don't need to set
+    -- this field to 'Prelude.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
+    -- resources are like CGI scripts.
+    , 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.
+    -- 
+    -- 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 ()))
     }
-type ResTree    = ResNode -- root だから Map ではない
-type ResSubtree = Map String ResNode
-data ResNode    = ResNode (Maybe ResourceDef) ResSubtree
 
+-- |'ResTree' is an opaque structure which is a map from resource path
+-- to 'ResourceDef'.
+newtype ResTree = ResTree ResNode -- root だから Map ではない
+type ResSubtree = Map String ResNode
+data ResNode    = ResNode !(Maybe ResourceDef) !ResSubtree
 
+-- |'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 = processRoot list
+mkResTree xs = xs `seq` processRoot xs
     where
       processRoot :: [ ([String], ResourceDef) ] -> ResTree
       processRoot list
@@ -59,12 +122,12 @@ mkResTree list = processRoot list
             in
               if null roots then
                   -- "/" にリソースが定義されない。"/foo" とかにはあるかも。
-                  ResNode Nothing children
+                  ResTree (ResNode Nothing children)
               else
                   -- "/" がある。
                   let (_, def) = last roots
                   in 
-                    ResNode (Just def) children
+                    ResTree (ResNode (Just def) children)
 
       processNonRoot :: [ ([String], ResourceDef) ] -> ResSubtree
       processNonRoot list
@@ -86,27 +149,33 @@ mkResTree list = processRoot list
               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 ([String], ResourceDef))
+findResource (ResTree (ResNode rootDefM subtree)) fbs uri
+    = do let pathStr     = uriPath uri
+             path        = [x | x <- splitBy (== '/') pathStr, x /= ""]
+             foundInTree = if null path then
+                               do def <- rootDefM
+                                  return (path, 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
+      walkTree _ [] _
+          = error "Internal error: should not reach here."
+
+      walkTree tree (name:[]) soFar
+          = case M.lookup name tree of
               Nothing               -> Nothing
               Just (ResNode defM _) -> do def <- defM
                                           return (soFar ++ [name], def)
 
-      walkTree subtree (x:xs) soFar
-          = case M.lookup x subtree of
+      walkTree tree (x:xs) soFar
+          = case M.lookup x tree of
               Nothing                      -> Nothing
               Just (ResNode defM children) -> case defM of
                                                 Just (ResourceDef { resIsGreedy = True })
@@ -114,34 +183,45 @@ findResource (ResNode rootDefM subtree) uri
                                                           return (soFar ++ [x], def)
                                                 _   -> walkTree children xs (soFar ++ [x])
 
+      fallback :: [String] -> [FallbackHandler] -> IO (Maybe ([String], 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 def itr
-    = fork
-      $ catch ( runReaderT ( do fromMaybe notAllowed rsrc 
-                                driftTo Done
-                           ) itr
-              )
-      $ \ exc -> processException exc
+    = def `seq` itr `seq`
+      fork
+      $! catch ( runRes ( do req <- getRequest
+                             fromMaybe notAllowed $ rsrc req
+                             driftTo Done
+                        ) itr
+               )
+             $ \ exc -> processException exc
     where
       fork :: IO () -> IO ThreadId
       fork = if (resUsesNativeThread def)
              then forkOS
              else forkIO
       
-      rsrc :: Maybe (Resource ())
-      rsrc = case reqMethod $ fromJust $ itrRequest itr 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
+      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
+              _      -> undefined
 
       notAllowed :: Resource ()
       notAllowed = do setStatus MethodNotAllowed
-                      setHeader "Allow" $ joinWith ", " allowedMethods
+                      setHeader (C8.pack "Allow") (C8.pack $ joinWith ", " allowedMethods)
 
       allowedMethods :: [String]
       allowedMethods = nub $ foldr (++) [] [ methods resGet    ["GET"]
@@ -156,35 +236,31 @@ runResource def itr
                        Just _  -> xs
                        Nothing -> []
 
-      processException :: Exception -> IO ()
+      toAbortion :: SomeException -> Abortion
+      toAbortion e = case fromException e of
+                       Just abortion -> abortion
+                       Nothing       -> Abortion InternalServerError emptyHeaders (Just (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
+          = do let abo = toAbortion exc
                    conf = itrConfig itr
-                   reqM = itrRequest itr
                -- まだ 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
+                   flip runRes itr
                       $ do setStatus $ aboStatus abo
-                           -- FIXME: 同じ名前で複數の値があった時は、こ
-                           -- れではまずいと思ふ。
-                           mapM_ (\ (name, value) -> setHeader name value) $ aboHeaders abo
+                           mapM_ (\ (name, value) -> setHeader name value) $ fromHeaders $ aboHeaders abo
                            output $ abortPage conf reqM res abo
                  else
-                   hPutStrLn stderr $ show abo
+                   when (cnfDumpTooLateAbortionToStderr $ itrConfig itr)
+                            $ hPutStrLn stderr $ show abo
 
-               flip runReaderT itr $ driftTo Done
+               flip runRes itr $ driftTo Done
 
       formatIOE :: IOError -> String
       formatIOE ioE = if isUserError ioE then