Refactor to put more work (checking files existance, making path absolutes) into the Files module and simplify Arguments a bit

This commit is contained in:
Tissevert 2019-02-19 21:48:55 +01:00
parent c0b7285b2f
commit 04fe7b8f31
7 changed files with 63 additions and 66 deletions

View file

@ -9,9 +9,7 @@ import Control.Applicative ((<|>), (<**>), optional)
import Options.Applicative (Parser, ReadM, argument, auto, eitherReader, execParser, flag', fullDesc, header, help, helper, info, long, metavar, short, str, value) import Options.Applicative (Parser, ReadM, argument, auto, eitherReader, execParser, flag', fullDesc, header, help, helper, info, long, metavar, short, str, value)
import qualified Options.Applicative as Optparse (option) import qualified Options.Applicative as Optparse (option)
import qualified Paths_hablo as Hablo (version) import qualified Paths_hablo as Hablo (version)
import System.Directory (doesDirectoryExist, doesFileExist, makeAbsolute) import System.FilePath (dropTrailingPathSeparator, isValid)
import System.Exit (die)
import System.FilePath ((</>), dropTrailingPathSeparator, isValid)
data Arguments = BlogConfig { data Arguments = BlogConfig {
sourceDir :: FilePath sourceDir :: FilePath
@ -89,37 +87,9 @@ filePath = eitherReader $ \path ->
then Right $ dropTrailingPathSeparator path then Right $ dropTrailingPathSeparator path
else Left "This string doesn't represent a valid path" else Left "This string doesn't represent a valid path"
ifNotDie :: (a -> IO Bool) -> (a -> String) -> a -> IO ()
ifNotDie check messageBuilder input = do
bool <- check input
if bool
then return ()
else die $ messageBuilder input
checkAndMakeAbsolute :: Arguments -> IO Arguments
checkAndMakeAbsolute Version = return Version
checkAndMakeAbsolute aBlogConfig = do
doesDirectoryExist `ifNotDie` noSuchDirectory $ sourceDir aBlogConfig
doesDirectoryExist `ifNotDie` noSuchDirectory $
sourceDir aBlogConfig </> articlesPath aBlogConfig
absoluteSourceDir <- makeAbsolute $ sourceDir aBlogConfig
mapM_ (doesFileExist `ifNotDie` noSuchFile) $ bannerPath aBlogConfig
absoluteBannerPath <- mapM makeAbsolute $ bannerPath aBlogConfig
mapM_ (doesFileExist `ifNotDie` noSuchFile) $ headPath aBlogConfig
absoluteHeadPath <- mapM makeAbsolute $ headPath aBlogConfig
return $ aBlogConfig {
sourceDir = absoluteSourceDir
, bannerPath = absoluteBannerPath
, headPath = absoluteHeadPath
}
where
noSuchDirectory = (++ ": no such directory")
noSuchFile = (++ ": no such file")
get :: IO Arguments get :: IO Arguments
get = do get = do
checkAndMakeAbsolute =<< (execParser $ execParser $
info info
(arguments <**> helper) (arguments <**> helper)
(fullDesc <> header ("Hablo v" ++ showVersion Hablo.version)) (fullDesc <> header ("Hablo v" ++ showVersion Hablo.version))
)

View file

@ -13,6 +13,7 @@ import Control.Monad.Reader (MonadReader)
import Data.Text (Text, pack) import Data.Text (Text, pack)
import Data.Text.Lazy (toStrict) import Data.Text.Lazy (toStrict)
import Data.Text.Template (render) import Data.Text.Template (render)
import Files (absoluteLink)
import Pretty ((.$)) import Pretty ((.$))
import System.FilePath.Posix ((</>)) import System.FilePath.Posix ((</>))
@ -23,12 +24,8 @@ data ArticlesList = ArticlesList {
} }
otherUrl :: ArticlesList -> String otherUrl :: ArticlesList -> String
otherUrl (ArticlesList {full, tagged}) = otherUrl (ArticlesList {full, tagged}) = absoluteLink $
if full (if full then id else (</> "all.html")) $ maybe "" id tagged
then url tagged
else url tagged </> "all.html"
where
url = maybe "/" ("/" </>)
pageTitle :: (MonadReader Blog m) => ArticlesList -> m Text pageTitle :: (MonadReader Blog m) => ArticlesList -> m Text
pageTitle (ArticlesList {full, tagged}) = do pageTitle (ArticlesList {full, tagged}) = do

View file

@ -67,15 +67,19 @@ tagged collection path = do
else Set.empty else Set.empty
return (takeFileName path, foldl Set.union Set.empty keys) return (takeFileName path, foldl Set.union Set.empty keys)
build :: Arguments -> IO Blog discover :: Path -> IO (Collection, Map String (Set String))
build arguments = withCurrentDirectory (root path) $ do discover path = withCurrentDirectory (root path) $ do
skin <- Skin.build name arguments
wording <- Wording.build arguments
articles <- findArticles $ articlesPath path articles <- findArticles $ articlesPath path
tags <- Map.fromList . filter (not . Set.null . snd) tags <- Map.fromList . filter (not . Set.null . snd)
<$> (Files.find (articlesPath path </> "tags") >>= mapM (articles `tagged`)) <$> (Files.find (articlesPath path </> "tags") >>= mapM (articles `tagged`))
return $ Blog {articles, name, path, skin, tags, wording} return (articles, tags)
where
path = Path.build arguments build :: Arguments -> IO Blog
name = maybe (takeFileName . dropTrailingPathSeparator $ root path) id build arguments = do
path <- Path.build arguments
let name = maybe (takeFileName . dropTrailingPathSeparator $ root path) id
$ Arguments.name arguments $ Arguments.name arguments
skin <- Skin.build name arguments
wording <- Wording.build arguments
(articles, tags) <- discover path
return $ Blog {articles, name, path, skin, tags, wording}

View file

@ -1,3 +1,4 @@
{-# LANGUAGE NamedFieldPuns #-}
module Blog.Path ( module Blog.Path (
Path(..) Path(..)
, build , build
@ -5,6 +6,7 @@ module Blog.Path (
import Arguments (Arguments) import Arguments (Arguments)
import qualified Arguments as Arguments (Arguments(..)) import qualified Arguments as Arguments (Arguments(..))
import Files (File(..), absolute, filePath)
data Path = Path { data Path = Path {
articlesPath :: FilePath articlesPath :: FilePath
@ -13,10 +15,11 @@ data Path = Path {
, root :: FilePath , root :: FilePath
} }
build :: Arguments -> Path build :: Arguments -> IO Path
build arguments = Path { build arguments = do
articlesPath = Arguments.articlesPath arguments articlesPath <- filePath . Dir $ Arguments.articlesPath arguments
, commentsAt = Arguments.commentsAt arguments pagesPath <- mapM (filePath . Dir) $ Arguments.pagesPath arguments
, pagesPath = Arguments.pagesPath arguments root <- absolute . Dir $ Arguments.sourceDir arguments
, root = Arguments.sourceDir arguments return $ Path {
} articlesPath, commentsAt = Arguments.commentsAt arguments, pagesPath, root
}

View file

@ -8,6 +8,7 @@ import Arguments (Arguments)
import qualified Arguments (bannerPath, favicon, cardImage, headPath, previewArticlesCount, previewLinesCount) import qualified Arguments (bannerPath, favicon, cardImage, headPath, previewArticlesCount, previewLinesCount)
import Control.Monad (filterM) import Control.Monad (filterM)
import Data.Maybe (listToMaybe) import Data.Maybe (listToMaybe)
import Files (absoluteLink)
import Prelude hiding (head) import Prelude hiding (head)
import System.Directory (doesFileExist) import System.Directory (doesFileExist)
import System.FilePath ((</>), (<.>)) import System.FilePath ((</>), (<.>))
@ -21,14 +22,10 @@ data Skin = Skin {
, previewLinesCount :: Int , previewLinesCount :: Int
} }
absolute :: FilePath -> FilePath
absolute ('.':path) = path
absolute path = "/" </> path
findImage :: String -> Maybe FilePath -> IO (Maybe FilePath) findImage :: String -> Maybe FilePath -> IO (Maybe FilePath)
findImage _ (Just path) = return . Just $ absolute path findImage _ (Just path) = return . Just $ absoluteLink path
findImage name Nothing = findImage name Nothing =
fmap absolute . listToMaybe <$> filterM doesFileExist pathsToCheck fmap absoluteLink . listToMaybe <$> filterM doesFileExist pathsToCheck
where where
directories = [".", "image", "images", "pictures", "skin", "static"] directories = [".", "image", "images", "pictures", "skin", "static"]
extensions = ["ico", "gif", "jpeg", "jpg", "png", "svg"] extensions = ["ico", "gif", "jpeg", "jpg", "png", "svg"]

View file

@ -14,6 +14,7 @@ import Control.Monad.Reader (ReaderT)
import qualified Data.Map as Map (keys, lookup) import qualified Data.Map as Map (keys, lookup)
import Data.Monoid ((<>)) import Data.Monoid ((<>))
import Data.Text (Text, pack, empty) import Data.Text (Text, pack, empty)
import Files (absoluteLink)
import Lucid import Lucid
import Lucid.Base (makeAttribute) import Lucid.Base (makeAttribute)
import Prelude hiding (head, lookup) import Prelude hiding (head, lookup)
@ -55,7 +56,7 @@ instance Page ArticlesList where
article :: Bool -> Article -> HtmlGenerator () article :: Bool -> Article -> HtmlGenerator ()
article raw (Article {key, body, title}) = do article raw (Article {key, body, title}) = do
url <- ("/" </>) . (</> key <.> extension) <$> (Blog.get $path.$articlesPath) url <- absoluteLink . (</> key <.> extension) <$> (Blog.get $path.$articlesPath)
article_ (do article_ (do
header_ (do header_ (do
aElem [href_ . pack $ url] . h1_ $ toHtml title aElem [href_ . pack $ url] . h1_ $ toHtml title
@ -79,7 +80,7 @@ navigationA :: Term arg result => arg -> result
navigationA = "a" `termWith` [class_ "navigation"] navigationA = "a" `termWith` [class_ "navigation"]
tag :: String -> HtmlGenerator () tag :: String -> HtmlGenerator ()
tag tagName = li_ (navigationA [href_ $ pack ("/" </> tagName)] $ toHtml tagName) tag tagName = li_ (navigationA [href_ . pack $ absoluteLink tagName] $ toHtml tagName)
defaultBanner :: HtmlGenerator () defaultBanner :: HtmlGenerator ()
defaultBanner = do defaultBanner = do

View file

@ -1,9 +1,34 @@
module Files ( module Files (
find File(..)
, absolute
, absoluteLink
, filePath
, find
) where ) where
import System.Exit (die)
import System.Directory (doesDirectoryExist, doesFileExist, listDirectory, makeAbsolute)
import System.FilePath ((</>)) import System.FilePath ((</>))
import System.Directory (listDirectory)
data File = File FilePath | Dir FilePath
absolute :: File -> IO (FilePath)
absolute file = filePath file >>= makeAbsolute
absoluteLink :: FilePath -> FilePath
absoluteLink ('.':path) = path
absoluteLink path = "/" </> path
filePath :: File -> IO FilePath
filePath file = do
let (thePath, test, errorMessage) =
case file of
File path -> (path, doesFileExist, (++ ": no such file"))
Dir path -> (path, doesDirectoryExist, (++ ": no such directory"))
bool <- test thePath
if bool
then return thePath
else die $ errorMessage thePath
find :: FilePath -> IO [FilePath] find :: FilePath -> IO [FilePath]
find path = find path =