From aead07929e6ed13375b86539b1679a88993c9cf5 Mon Sep 17 00:00:00 2001
From: pacien
Date: Thu, 26 Dec 2019 08:03:31 +0100
Subject: compiler: extract config and remove utils
---
compiler/src/Config.hs | 49 +++++++++++++++++++++++++++++++++++++++++++++++++
compiler/src/Gallery.hs | 6 +++++-
compiler/src/Input.hs | 3 +--
compiler/src/Lib.hs | 35 +++++++++++------------------------
compiler/src/Utils.hs | 49 -------------------------------------------------
5 files changed, 66 insertions(+), 76 deletions(-)
create mode 100644 compiler/src/Config.hs
delete mode 100644 compiler/src/Utils.hs
diff --git a/compiler/src/Config.hs b/compiler/src/Config.hs
new file mode 100644
index 0000000..6f04818
--- /dev/null
+++ b/compiler/src/Config.hs
@@ -0,0 +1,49 @@
+{-# LANGUAGE DuplicateRecordFields, DeriveGeneric, DeriveAnyClass #-}
+
+-- ldgallery - A static generator which turns a collection of tagged
+-- pictures into a searchable web gallery.
+--
+-- Copyright (C) 2019 Pacien TRAN-GIRARD
+--
+-- This program is free software: you can redistribute it and/or modify
+-- it under the terms of the GNU Affero General Public License as
+-- published by the Free Software Foundation, either version 3 of the
+-- License, or (at your option) any later version.
+--
+-- This program is distributed in the hope that it will be useful,
+-- but WITHOUT ANY WARRANTY; without even the implied warranty of
+-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
+-- GNU Affero General Public License for more details.
+--
+-- You should have received a copy of the GNU Affero General Public License
+-- along with this program. If not, see .
+
+
+module Config
+ ( GalleryConfig(..)
+ , CompilerConfig(..)
+ , readConfig
+ ) where
+
+import GHC.Generics (Generic)
+import Data.Aeson (ToJSON, FromJSON)
+import qualified Data.Aeson as JSON
+
+import Files (FileName)
+import Input (decodeYamlFile)
+
+
+data CompilerConfig = CompilerConfig
+ { dummy :: Maybe String -- TODO
+ } deriving (Generic, FromJSON, Show)
+
+data GalleryConfig = GalleryConfig
+ { compiler :: CompilerConfig
+ , viewer :: JSON.Object
+ } deriving (Generic, FromJSON, Show)
+
+-- TODO: add compiler config keys and their default values
+
+
+readConfig :: FileName -> IO GalleryConfig
+readConfig = decodeYamlFile
diff --git a/compiler/src/Gallery.hs b/compiler/src/Gallery.hs
index 3be62ad..ce52523 100644
--- a/compiler/src/Gallery.hs
+++ b/compiler/src/Gallery.hs
@@ -32,7 +32,8 @@ import Data.Maybe (fromMaybe)
import Data.Aeson (ToJSON, genericToJSON, genericToEncoding)
import qualified Data.Aeson as JSON
-importĀ Utils
+import qualified Data.Set as Set
+
import Files
import Input
import Resource
@@ -121,3 +122,6 @@ buildGalleryTree (DirResource dirItems path@(dirname:_) thumbnailPath) =
where
aggregateChildTags :: [GalleryItem] -> [Tag]
aggregateChildTags = unique . concatMap (\item -> tags (item::GalleryItem))
+
+ unique :: Ord a => [a] -> [a]
+ unique = Set.toList . Set.fromList
diff --git a/compiler/src/Input.hs b/compiler/src/Input.hs
index fa36d59..681f169 100644
--- a/compiler/src/Input.hs
+++ b/compiler/src/Input.hs
@@ -37,7 +37,6 @@ import Data.Aeson (FromJSON)
import System.FilePath (isExtensionOf, dropExtension)
import Files
-import Utils
data LoadException = LoadException String ParseException deriving Show
@@ -70,7 +69,7 @@ data Sidecar = Sidecar
readInputTree :: AnchoredFSNode -> IO InputTree
readInputTree (AnchoredFSNode anchor root@Dir{}) =
- filterDir (neg isHidden) root & mkDirNode
+ filterDir (not . isHidden) root & mkDirNode
where
mkInputNode :: FSNode -> IO (Maybe InputTree)
mkInputNode (File path@(filename:pathto)) | ".yaml" `isExtensionOf` filename =
diff --git a/compiler/src/Lib.hs b/compiler/src/Lib.hs
index 643e5f6..b2bbe15 100644
--- a/compiler/src/Lib.hs
+++ b/compiler/src/Lib.hs
@@ -24,47 +24,28 @@ module Lib
) where
-import GHC.Generics (Generic)
import Data.Function ((&))
import Data.Ord (comparing)
import Data.List (sortBy, length)
import System.Directory (createDirectoryIfMissing, removePathForcibly)
import System.FilePath (dropFileName, (>))
-import Data.Aeson (ToJSON, FromJSON)
+import Data.Aeson (ToJSON)
import qualified Data.Aeson as JSON
+import Config
import Files (FileName, readDirectory, localPath, flattenDir, root, (/>))
import Input (decodeYamlFile, readInputTree)
import Resource (ResourceTree, buildResourceTree, outputDiff)
import Gallery (buildGalleryTree)
-data CompilerConfig = CompilerConfig
- { dummy :: Maybe String -- TODO
- } deriving (Generic, FromJSON, Show)
-
-data GalleryConfig = GalleryConfig
- { compiler :: CompilerConfig
- , viewer :: JSON.Object
- } deriving (Generic, FromJSON, Show)
-
-readConfig :: FileName -> IO GalleryConfig
-readConfig = decodeYamlFile
-
-
process :: FilePath -> FilePath -> IO ()
process inputDirPath outputDirPath =
do
config <- readConfig (inputDirPath > "gallery.yaml")
-
inputDir <- readDirectory inputDirPath
- putStrLn "\nINPUT DIR"
- putStrLn (show inputDir)
-
inputTree <- readInputTree inputDir
- putStrLn "\nINPUT TREE"
- putStrLn (show inputTree)
let resourceTree = buildResourceTree inputTree
putStrLn "\nRESOURCE TREE"
@@ -77,11 +58,11 @@ process inputDirPath outputDirPath =
-- (or recompile everything if the config file has changed!)
-- execute in parallel
- cleanup resourceTree outputDirPath
-
-- TODO: execute (in parallel) the resource compilation strategy list
-- need to find a good library for that
+ cleanup resourceTree outputDirPath
+
buildGalleryTree resourceTree
& writeJSON (outputDirPath > "index.json")
@@ -95,7 +76,13 @@ process inputDirPath outputDirPath =
>>= return . outputDiff resourceTree . root
>>= return . sortBy (flip $ comparing length) -- nested files before dirs
>>= return . map (localPath . (/>) outputDir)
- >>= mapM_ removePathForcibly
+ >>= mapM_ remove
+
+ remove :: FileName -> IO ()
+ remove path =
+ do
+ putStrLn $ "Removing: " ++ path
+ removePathForcibly path
writeJSON :: ToJSON a => FileName -> a -> IO ()
writeJSON path obj =
diff --git a/compiler/src/Utils.hs b/compiler/src/Utils.hs
deleted file mode 100644
index 794382c..0000000
--- a/compiler/src/Utils.hs
+++ /dev/null
@@ -1,49 +0,0 @@
--- ldgallery - A static generator which turns a collection of tagged
--- pictures into a searchable web gallery.
---
--- Copyright (C) 2019 Pacien TRAN-GIRARD
---
--- This program is free software: you can redistribute it and/or modify
--- it under the terms of the GNU Affero General Public License as
--- published by the Free Software Foundation, either version 3 of the
--- License, or (at your option) any later version.
---
--- This program is distributed in the hope that it will be useful,
--- but WITHOUT ANY WARRANTY; without even the implied warranty of
--- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
--- GNU Affero General Public License for more details.
---
--- You should have received a copy of the GNU Affero General Public License
--- along with this program. If not, see .
-
-
-module Utils
- ( conj, neg
- , unique
- , passthrough
- ) where
-
-
-import qualified Data.List
-import qualified Data.Set
-
-
--- predicates
-
-conj :: (a -> Bool) -> (a -> Bool) -> a -> Bool
-conj p q x = (p x) && (q x)
-
-neg :: (a -> Bool) -> a -> Bool
-neg p x = not (p x)
-
-
--- lists
-
-unique :: Ord a => [a] -> [a]
-unique = Data.Set.toList . Data.Set.fromList
-
-
--- monads
-
-passthrough :: Monad m => (a -> m b) -> a -> m a
-passthrough f a = return a >>= f >>= \_ -> return a
--
cgit v1.2.3