{-# LANGUAGE NamedFieldPuns, QuasiQuotes #-} import Hack.Handler.Happstack import System (getArgs) import MPS.Env hiding (div, log) import MPS.TH import MPS.Extra (u2b, b2u, strip, purify) import MPSUTF8 (ls) import Prelude () import Data.Default (def) import Hack.Contrib.Middleware.Config import Hack.Contrib.Middleware.ContentLength import Hack.Contrib.Middleware.Static import Hack.Contrib.Middleware.SimpleAccessLogger import Hack.Contrib.Middleware.UserMime -- import Hack.Contrib.Mime -- import Data.Map (toAscList) import Hack.Contrib.Utils (use, unescape_uri) import Hack.Contrib.Response (set_content_type) import Hack.Contrib.Request (path) import Hack import Data.ByteString.Lazy.Char8 (pack) import System.Posix.Files import Data.List (isInfixOf, sort) import Text.HTML.Moe hiding ((/), body, head, select) import Control.Monad ((>=>)) import System.Process import System.Directory (doesFileExist) import Control.Concurrent import Control.Arrow ((&&&)) main :: IO () main = do args <- getArgs let { port = if length args == 0 then 3000 else read - head args } let { app = dir_serve - \env -> do let static_app = static (Just ".") [""] (const - return not_found) r <- static_app env if r.status == 200 then do _content_type <- readProcess "file" ["-b", "--mime", "." + env.pathInfo.unescape_uri] "" -- putStrLn _content_type return - r.set_content_type (_content_type.strip) else return r } maid_mime_exist <- doesFileExist "mime.types" mime_types <- if maid_mime_exist then readFile "mime.types" else return default_mime_types putStrLn "" putStrLn - " ❂ Maid serving on port: " ++ show port putStrLn "" runWithConfig def {port} - use (middleware_stack mime_types) app -- run port - use middleware_stack app where dir_serve app = cascade [ app , config (\env -> env {pathInfo = pathInfo env / "index.htm"}) app , config (\env -> env {pathInfo = pathInfo env / "index.html"}) app , list_dir ] log :: String -> IO () log x = jailed - putStrLn - b2u - x where sync_lock :: MVar () sync_lock = purify - newMVar () jailed :: IO a -> IO a jailed io = do withMVar sync_lock (const io) middleware_stack :: String -> [Middleware] middleware_stack mime_types = [ no_favicon , content_length , simple_access_logger - Just log , user_mime - parse_user_mines mime_types -- , user_mime - mime_types.toAscList.map_fst (drop 1) -- , \app env -> do -- r <- app env -- print - r.headers -- return r ] where parse_user_mines :: String -> [(String, String)] parse_user_mines = lines > reject null > map (words > head &&& words > tail > unwords) cascade :: [Application] -> Application cascade [] = const - return not_found cascade (x:xs) = \env -> do r <- x env if r.status == 404 then cascade xs env else return r no_favicon :: Middleware no_favicon app = \env -> do -- putStrLn - "pathInfo is: " + env.pathInfo if env.pathInfo.is "/favicon.ico" then return not_found else app env not_found :: Response not_found = def { status = 404 } is_directory :: String -> IO Bool is_directory = u2b > getFileStatus >=> isDirectory > return list_dir :: Application list_dir env = do let _path = "." + env.pathInfo .unescape_uri .b2u -- print _path -- no hack please if ".." `isInfixOf` _path then return not_found else do is_dir <- is_directory _path if not is_dir then return not_found else do _paths <- ls _path -- print _paths let _full_paths = _paths.map (_path.drop 2 /) dir_tags <- _full_paths.mapM is_directory let tagged = zip _paths dir_tags dirs = tagged.select snd.sort .map_fst (+ "/") files = tagged.reject snd.sort sorted = dirs + files maid_css_exist <- doesFileExist "maid.css" css <- if maid_css_exist then readFile "maid.css" else return default_css_style return - def { status = 200 , body = pack - dir_template sorted css (env.path.unescape_uri.b2u) } .set_content_type "text/html; charset=utf-8" dir_template :: [(String, Bool)] -> String -> String -> String dir_template xs css current_path = render - html' - do head' - do meta [http_equiv "Content-Type", content "text/html; charset=utf-8"] style' - str css body' - do div [_class "container"] - do ul' - do xs.mapM_ (\(path, dir_tag) -> li' - do let path_dom = a [href - "/" / current_path / path] - str - path if dir_tag then div [_class "directory"] - path_dom else path_dom ) default_css_style :: String default_css_style = [$here| body { line-height: 1.5em; font-size: 1.3em; } .directory a , .directory a:visited { color: grey; } a , a:visited { text-decoration: none; color: #222; display: block; background: #eee; padding: 3px; padding-left: 20px; } a:hover { background: #ccc; } li { list-style-type: none; width: 80%; margin: 5px; } |] default_mime_types :: String default_mime_types = [$here| hs text/plain; charset=utf-8 lhs text/plain; charset=utf-8 |]