module Network.Salvia.Handler.Directory
( hDirectory
, hDirectoryResource
)
where
import Control.Applicative
import Control.Category
import Control.Monad.State hiding (get)
import Data.List (sort)
import Data.Record.Label
import Network.Protocol.Http
import Network.Protocol.Uri (path)
import Network.Salvia.Interface
import Network.Salvia.Handler.File (hResource)
import Network.Salvia.Handler.Redirect
import Prelude hiding ((.), id, mod)
import System.Directory (doesDirectoryExist, getDirectoryContents)
hDirectoryResource
:: (MonadIO m, HttpM' m, SendM m)
=> FilePath
-> m ()
hDirectoryResource dirName =
do u <- request (getM asUri)
let p = get path u
if (null p) || last p /= '/'
then hRedirect (show $ mod path (++"/") u)
else dirHandler dirName
hDirectory :: (MonadIO m, HttpM' m, SendM m) => m ()
hDirectory = hResource hDirectoryResource
dirHandler :: (MonadIO m, HttpM' m, SendM m) => FilePath -> m ()
dirHandler dirName =
do p <- request (getM (path . asUri))
filenames <- liftIO $ getDirectoryContents dirName
processed <- liftIO $ mapM (processFilename dirName) (sort filenames)
let b = listing p processed
response $
do contentType =: Just ("text/html", Nothing)
contentLength =: Just (length b)
status =: OK
send b
processFilename :: FilePath -> FilePath -> IO FilePath
processFilename d f =
(\b -> (if b then (++"/") else id) f) <$> doesDirectoryExist (d ++ f)
listing :: FilePath -> [FilePath] -> String
listing dirName fileNames =
concat [
"<html><head><title>Index of "
, dirName
, "</title></head><body><h1>Index of "
, dirName
, "</h1><ul>"
, fileNames >>= \f -> concat ["<li><a href='", f, "'>", f, "</a></li>"]
, "</ul></body></html>"
]