]> gitweb @ CieloNegro.org - Rakka.git/blobdiff - Rakka/Resource.hs
Fixing build breakage...
[Rakka.git] / Rakka / Resource.hs
index 21acb4b02c16e74faea015adf5ea9743618bf8c5..a1c4d90af52b3847b7896ae5904a5690d04e09fe 100644 (file)
@@ -1,11 +1,14 @@
 module Rakka.Resource
     ( runIdempotentA
+    , runIdempotentA'
     , runXmlA
     , getEntityType
     , outputXmlPage
+    , outputXmlPage'
+    , outputXml
+    , getUserID
     )
     where
-
 import           Control.Arrow
 import           Control.Arrow.ArrowList
 import           Control.Monad
@@ -13,41 +16,48 @@ import           Control.Monad.Trans
 import           Network.HTTP.Lucu
 import           Network.HTTP.Lucu.Utils
 import           Network.URI hiding (path)
+import           Rakka.Authorization
 import           Rakka.Environment
 import           Rakka.Validation
+import           System.FilePath.Posix
+import           System.Log.Logger
 import           Text.XML.HXT.Arrow.ReadDocument
 import           Text.XML.HXT.Arrow.WriteDocument
-import           Text.XML.HXT.Arrow.XmlIOStateArrow
 import           Text.XML.HXT.DOM.TypeDefs
 import           Text.XML.HXT.DOM.XmlKeywords
 
 
+logger :: String
+logger = "Rakka.Resource"
+
+
 -- "/"         ==> "/"
 -- "/foo"      ==> "/foo.html"
 -- "/foo/"     ==> "/foo.html"
 -- "/foo.bar/" ==> "/foo.bar"
 -- "/foo.bar"  ==> "/foo.bar"
-canonicalizeURI :: Resource ()
-canonicalizeURI 
-    = do uri <- getRequestURI
-         let newURI  = uri { uriPath = "/" ++ joinWith "/" newPath }
-             newPath = case [x | x <- splitBy (== '/') (uriPath uri), x /= ""] of
-                         []   -> []
-                         path -> case break (== '.') $ last path of
-                                   (_, "") -> let basePieces = reverse $ tail $ reverse path
-                                                  lastPiece  = last path
-                                              in
-                                                basePieces ++ [lastPiece ++ ".html"]
-                                   (_, _)  -> path
-         when (uri /= newURI)
+canonicalizeURI :: URI -> Resource ()
+canonicalizeURI baseURI
+    = do rPath <- return . uriPath =<< getRequestURI
+         let newURI   = baseURI { uriPath = uriPath baseURI </> newPath }
+             newPath  = foldl (</>) "/" newPath'
+             newPath' = case [x | x <- splitBy (== '/') rPath, x /= ""] of
+                          []   -> []
+                          path -> case break (== '.') $ last path of
+                                    (_, "") -> let basePieces = reverse $ tail $ reverse path
+                                                   lastPiece  = last path
+                                               in
+                                                 basePieces ++ [lastPiece ++ ".html"]
+                                    (_, _)  -> path
+         when (rPath /= newPath)
               $ abort MovedPermanently
                 [("Location", uriToString id newURI $ "")]
                 Nothing
 
 
-runIdempotentA :: IOSArrow () (Resource c) -> Resource c
-runIdempotentA a
-    = do canonicalizeURI
+runIdempotentA :: URI -> IOSArrow () (Resource c) -> Resource c
+runIdempotentA baseURI a
+    = do canonicalizeURI baseURI
          [rsrc] <- liftIO $ runX ( setErrorMsgHandler False fail
                                    >>>
                                    constA ()
@@ -57,6 +67,17 @@ runIdempotentA a
          rsrc
 
 
+runIdempotentA' :: IOSArrow () (Resource c) -> Resource c
+runIdempotentA' a
+    = do [rsrc] <- liftIO $ runX ( setErrorMsgHandler False fail
+                                   >>>
+                                   constA ()
+                                   >>>
+                                   a
+                                 )
+         rsrc
+
+
 runXmlA :: Environment -> FilePath -> IOSArrow XmlTree (Resource c) -> Resource c
 runXmlA env schemaPath a
     = do inputA <- getInputXmlA env schemaPath
@@ -101,10 +122,11 @@ getInputReader
     where
       getXmlReader
           = do req <- input defaultLimit
+               liftIO $ debugM logger req
                return $ readString [ (a_validate         , v_0)
                                    , (a_check_namespaces , v_1)
                                    , (a_remove_whitespace, v_0)
-                                   ] req
+                                   ] (UTF8.decodeString req)
       getFailingReader code headers msg
           = return $ proc _ -> abortA -< (code, (headers, msg))
 
@@ -119,24 +141,58 @@ getEntityType
     where
       extMap :: [(String, MIMEType)]
       extMap = [ ("html", read "application/xhtml+xml")
+               , ( "rdf", read "application/rss+xml"  )
                , ( "xml", read "text/xml"             )
                ]
 
 
-outputXmlPage :: XmlTree -> IOSArrow XmlTree XmlTree -> Resource ()
-outputXmlPage tree toXHTML
+outputXmlPage :: XmlTree -> [(MIMEType, IOSArrow XmlTree XmlTree)] -> Resource ()
+outputXmlPage tree formatters
     = do mType <- getEntityType
          setContentType mType
-         let formatter = case mType of
-                           MIMEType "application" "xhtml+xml" _ -> toXHTML
-                           MIMEType "text"        "xml"       _ -> this
-                           _                                    -> undefined
+         let formatter = case lookup mType formatters of
+                           Just f  -> f
+                           Nothing -> this
          [resultStr] <- liftIO $ runX ( setErrorMsgHandler False fail
                                         >>>
                                         constA tree
                                         >>>
                                         formatter
                                         >>>
-                                        writeDocumentToString [ (a_indent, v_1) ]
+                                        writeDocumentToString [ (a_indent         , v_1 )
+                                                              , (a_output_encoding, utf8)
+                                                              , (a_no_xml_pi      , v_0 ) ]
                                       )
-         output resultStr
\ No newline at end of file
+         output resultStr
+
+
+outputXmlPage' :: XmlTree -> IOSArrow XmlTree XmlTree -> Resource ()
+outputXmlPage' tree toXHTML
+    = outputXmlPage tree [(MIMEType "application" "xhtml+xml" [], toXHTML)]
+
+
+outputXml :: XmlTree -> Resource ()
+outputXml tree
+    = do setContentType (MIMEType "text" "xml" [])
+         [xmlStr] <- liftIO $ runX ( setErrorMsgHandler False fail
+                                    >>>
+                                    constA tree
+                                    >>>
+                                    writeDocumentToString [ (a_indent         , v_1 )
+                                                           , (a_output_encoding, utf8)
+                                                           , (a_no_xml_pi      , v_0 ) ]
+                                  )
+        output xmlStr
+
+
+getUserID :: Environment -> Resource (Maybe String)
+getUserID env
+    = do auth <- getAuthorization
+         case auth of
+           Just (BasicAuthCredential userID password)
+               -> do valid <- isValidPair (envAuthDB env) userID password
+                     if valid then
+                         return (Just userID)
+                       else
+                         return Nothing
+           _   -> return Nothing