module Network.HTTP.RedHandler.FileUtils where import System.Posix (FileStatus, getFileStatus, fileSize, fileAccess, modificationTime, isDirectory, isRegularFile) import Control.Exception as Exception (tryJust, ioErrors) import Foreign.C.Error (getErrno, eNOENT) sendFileResponse :: String -> IO (Maybe (Integer, String)) sendFileResponse path = do check <- findRealFilename path case check of { Nothing -> return Nothing; Just (filename,stat) -> do -- check we can actually read this file access <- fileAccess filename True{-read-} False False case access of { False -> return Nothing; -- not "permission denied", we're being paranoid -- about security. True -> do {- let content_type = case mimeTypeOf filename of Nothing -> contentTypeHeader (show defaultType) Just t -> contentTypeHeader (show t) let last_modified = lastModifiedHeader (epochTimeToClockTime (modificationTime stat)) -} let size = toInteger (fileSize stat) return (Just (size, filename) ) }} statFile :: String -> IO (Maybe FileStatus) statFile filename = do maybe_stat <- tryJust ioErrors (getFileStatus filename) case maybe_stat of Left e -> do errno <- getErrno if errno == eNOENT then return Nothing else ioError e Right stat -> return (Just stat) findRealFilename :: String -> IO (Maybe (String,FileStatus)) findRealFilename filename = do stat <- statFile filename case stat of Nothing -> return Nothing Just stat | isDirectory stat -> do let index_filename = filename ++ '/': "index.html" stat <- statFile index_filename case stat of Nothing -> return Nothing Just stat -> return (Just (index_filename,stat)) | isRegularFile stat -> return (Just (filename,stat)) | otherwise -> return Nothing