]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Resource/Tree.hs
Changes from 0.4 to 0.4.1
[Lucu.git] / Network / HTTP / Lucu / Resource / Tree.hs
index 149fa9d92d3b5101a27f5ba6c334133a3921fe34..660d8ff735bdc3f2fab18f7d42ab8a1f8951a091 100644 (file)
@@ -1,9 +1,13 @@
--- #prune
+{-# OPTIONS_HADDOCK prune #-}
 
 -- | Repository of the resources in httpd.
 module Network.HTTP.Lucu.Resource.Tree
     ( ResourceDef(..)
+    , emptyResource
+
     , ResTree
+    , FallbackHandler
+
     , mkResTree    -- [ ([String], ResourceDef) ] -> ResTree
 
     , findResource -- ResTree -> URI -> Maybe ([String], ResourceDef)
@@ -15,24 +19,33 @@ import           Control.Concurrent
 import           Control.Concurrent.STM
 import           Control.Exception
 import           Control.Monad
-import           Data.Dynamic
+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.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" のリソースが貪欲でなければ、それは
@@ -53,7 +66,7 @@ data ResourceDef = ResourceDef {
     -- 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.
+    -- 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,
@@ -87,13 +100,39 @@ data ResourceDef = ResourceDef {
     , resDelete           :: !(Maybe (Resource ()))
     }
 
--- | 'ResTree' is an opaque structure which is a map from resource
--- path to 'ResourceDef'.
-type ResTree    = ResNode -- root だから Map ではない
+-- |'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 String ResNode
-data ResNode    = ResNode !(Maybe ResourceDef) !ResSubtree
+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\" ) -- \/
@@ -101,21 +140,28 @@ data ResNode    = ResNode !(Maybe ResourceDef) !ResSubtree
 --             ]
 -- @
 mkResTree :: [ ([String], ResourceDef) ] -> ResTree
-mkResTree list = list `seq` processRoot list
+mkResTree = processRoot . mapFirst canonicalisePath
     where
+      mapFirst :: (a -> a') -> [(a, b)] -> [(a', b)]
+      mapFirst f = map (\ (a, b) -> (f a, b))
+
+      canonicalisePath :: [String] -> [String]
+      canonicalisePath = filter (\ x -> x /= "")
+
       processRoot :: [ ([String], ResourceDef) ] -> ResTree
       processRoot list
           = let (roots, nonRoots) = partition (\ (path, _) -> 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 list
@@ -125,39 +171,49 @@ mkResTree list = list `seq` processRoot 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 ([String], ResourceDef))
+findResource (ResTree (ResNode rootDefM subtree)) fbs uri
+    = do let pathStr        = uriPath uri
+             path           = [unEscapeString x | x <- splitBy (== '/') pathStr, x /= ""]
+             haveGreedyRoot = case rootDefM of
+                                Just def -> resIsGreedy def
+                                Nothing  -> False
+             foundInTree    = if haveGreedyRoot || 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
+      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 })
@@ -165,6 +221,13 @@ 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
@@ -175,10 +238,10 @@ runResource def itr
                              driftTo Done
                         ) itr
                )
-             $ \ exc -> processException exc
+               processException
     where
       fork :: IO () -> IO ThreadId
-      fork = if (resUsesNativeThread def)
+      fork = if resUsesNativeThread def
              then forkOS
              else forkIO
       
@@ -192,35 +255,33 @@ runResource def itr
               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"]
-                                           , methods resHead   ["GET", "HEAD"]
-                                           , methods resPost   ["POST"]
-                                           , methods resPut    ["PUT"]
-                                           , methods resDelete ["DELETE"]
-                                           ]
+      allowedMethods = nub $ concat [ 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 ()
+      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
                -- まだ DecidingHeader 以前の状態だったら、この途中終了
                -- を應答に反映させる餘地がある。さうでなければ stderr
@@ -231,18 +292,10 @@ runResource def itr
                if state <= DecidingHeader then
                    flip runRes itr
                       $ do setStatus $ aboStatus abo
-                           -- FIXME: 同じ名前で複數の値があった時は、こ
-                           -- れではまずいと思ふ。
-                           mapM_ (\ (name, value) -> setHeader name value) $ aboHeaders abo
+                           mapM_ (uncurry setHeader) $ fromHeaders $ aboHeaders abo
                            output $ abortPage conf reqM res abo
                  else
                    when (cnfDumpTooLateAbortionToStderr $ itrConfig itr)
                             $ hPutStrLn stderr $ show abo
 
                flip runRes itr $ driftTo Done
-
-      formatIOE :: IOError -> String
-      formatIOE ioE = if isUserError ioE then
-                          ioeGetErrorString ioE
-                      else
-                          show ioE