aboutsummaryrefslogtreecommitdiff
path: root/compiler/src/Compiler.hs
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/src/Compiler.hs')
-rw-r--r--compiler/src/Compiler.hs78
1 files changed, 58 insertions, 20 deletions
diff --git a/compiler/src/Compiler.hs b/compiler/src/Compiler.hs
index 749872d..d92d8e9 100644
--- a/compiler/src/Compiler.hs
+++ b/compiler/src/Compiler.hs
@@ -24,17 +24,25 @@ module Compiler
24 24
25import GHC.Generics (Generic) 25import GHC.Generics (Generic)
26import Control.Monad (liftM2, when) 26import Control.Monad (liftM2, when)
27import Data.Bool (bool)
27import Data.Maybe (fromMaybe) 28import Data.Maybe (fromMaybe)
28import System.FilePath ((</>)) 29import System.FilePath ((</>))
29import qualified System.FilePath.Glob as Glob 30import qualified System.FilePath.Glob as Glob
30import System.Directory (canonicalizePath) 31import System.Directory (canonicalizePath, doesFileExist)
31 32
32import Data.Aeson (ToJSON) 33import Data.Aeson (ToJSON, FromJSON)
33import qualified Data.Aeson as JSON 34import qualified Data.Aeson as JSON
34 35
35import Config 36import Config
36import Input (InputTree, readInputTree, filterInputTree, sidecar, tags) 37import Input (InputTree, readInputTree, filterInputTree, sidecar, tags)
37import Resource (GalleryItem, buildGalleryTree, galleryCleanupResourceDir) 38import Resource
39 ( GalleryItem
40 , GalleryItemProps
41 , Thumbnail
42 , buildGalleryTree
43 , galleryCleanupResourceDir
44 , properties
45 , thumbnail)
38import Files 46import Files
39 ( FileName 47 ( FileName
40 , FSNode(..) 48 , FSNode(..)
@@ -43,9 +51,8 @@ import Files
43 , nodeName 51 , nodeName
44 , filterDir 52 , filterDir
45 , ensureParentDir ) 53 , ensureParentDir )
46import Processors 54import ItemProcessors (ItemProcessor, itemFileProcessor, thumbnailFileProcessor)
47 ( itemFileProcessor, thumbnailFileProcessor 55import Caching (Cache, noCache, buildItemCache, useCached)
48 , skipCached, withCached )
49 56
50 57
51defaultGalleryConf :: String 58defaultGalleryConf :: String
@@ -64,7 +71,7 @@ thumbnailsDir = "thumbnails"
64data GalleryIndex = GalleryIndex 71data GalleryIndex = GalleryIndex
65 { properties :: ViewerConfig 72 { properties :: ViewerConfig
66 , tree :: GalleryItem 73 , tree :: GalleryItem
67 } deriving (Generic, Show, ToJSON) 74 } deriving (Generic, Show, ToJSON, FromJSON)
68 75
69 76
70writeJSON :: ToJSON a => FileName -> a -> IO () 77writeJSON :: ToJSON a => FileName -> a -> IO ()
@@ -73,6 +80,16 @@ writeJSON outputPath object =
73 putStrLn $ "Generating:\t" ++ outputPath 80 putStrLn $ "Generating:\t" ++ outputPath
74 ensureParentDir JSON.encodeFile outputPath object 81 ensureParentDir JSON.encodeFile outputPath object
75 82
83loadGalleryIndex :: FilePath -> IO (Maybe GalleryIndex)
84loadGalleryIndex path =
85 doesFileExist path >>= bool (return Nothing) decodeIndex
86 where
87 decodeIndex =
88 putStrLn ("Loading previous index:\t" ++ path)
89 >> JSON.eitherDecodeFileStrict path
90 >>= either (\err -> warn err >> return Nothing) (return . Just)
91 warn = putStrLn . ("Warning:\tUnable to reuse existing index as cache: " ++)
92
76 93
77(&&&) :: (a -> Bool) -> (a -> Bool) -> a -> Bool 94(&&&) :: (a -> Bool) -> (a -> Bool) -> a -> Bool
78(&&&) = liftM2 (&&) 95(&&&) = liftM2 (&&)
@@ -81,16 +98,16 @@ writeJSON outputPath object =
81(|||) = liftM2 (||) 98(|||) = liftM2 (||)
82 99
83anyPattern :: [String] -> String -> Bool 100anyPattern :: [String] -> String -> Bool
84anyPattern patterns string = any (flip Glob.match string) (map Glob.compile patterns) 101anyPattern patterns string = any (flip Glob.match string . Glob.compile) patterns
85 102
86galleryDirFilter :: GalleryConfig -> [FilePath] -> FSNode -> Bool 103galleryDirFilter :: GalleryConfig -> [FilePath] -> FSNode -> Bool
87galleryDirFilter config excludedCanonicalDirs = 104galleryDirFilter config excludedCanonicalDirs =
88 (not . isHidden) 105 (not . isHidden)
89 &&& (not . isExcludedDir) 106 &&& (not . isExcludedDir)
90 &&& ((matchesDir $ anyPattern $ includedDirectories config) ||| 107 &&& (matchesDir (anyPattern $ includedDirectories config) |||
91 (matchesFile $ anyPattern $ includedFiles config)) 108 matchesFile (anyPattern $ includedFiles config))
92 &&& (not . ((matchesDir $ anyPattern $ excludedDirectories config) ||| 109 &&& (not . (matchesDir (anyPattern $ excludedDirectories config) |||
93 (matchesFile $ anyPattern $ excludedFiles config))) 110 matchesFile (anyPattern $ excludedFiles config)))
94 111
95 where 112 where
96 matchesDir :: (FileName -> Bool) -> FSNode -> Bool 113 matchesDir :: (FileName -> Bool) -> FSNode -> Bool
@@ -102,17 +119,17 @@ galleryDirFilter config excludedCanonicalDirs =
102 matchesFile _ Dir{} = False 119 matchesFile _ Dir{} = False
103 120
104 isExcludedDir :: FSNode -> Bool 121 isExcludedDir :: FSNode -> Bool
105 isExcludedDir Dir{canonicalPath} = any (canonicalPath ==) excludedCanonicalDirs 122 isExcludedDir Dir{canonicalPath} = canonicalPath `elem` excludedCanonicalDirs
106 isExcludedDir File{} = False 123 isExcludedDir File{} = False
107 124
108inputTreeFilter :: GalleryConfig -> InputTree -> Bool 125inputTreeFilter :: GalleryConfig -> InputTree -> Bool
109inputTreeFilter GalleryConfig{includedTags, excludedTags} = 126inputTreeFilter GalleryConfig{includedTags, excludedTags} =
110 (hasTagMatching $ anyPattern includedTags) 127 hasTagMatching (anyPattern includedTags)
111 &&& (not . (hasTagMatching $ anyPattern excludedTags)) 128 &&& (not . hasTagMatching (anyPattern excludedTags))
112 129
113 where 130 where
114 hasTagMatching :: (String -> Bool) -> InputTree -> Bool 131 hasTagMatching :: (String -> Bool) -> InputTree -> Bool
115 hasTagMatching cond = (any cond) . (fromMaybe [""] . tags) . sidecar 132 hasTagMatching cond = any cond . (fromMaybe [""] . tags) . sidecar
116 133
117 134
118compileGallery :: FilePath -> FilePath -> FilePath -> FilePath -> [FilePath] -> Bool -> Bool -> IO () 135compileGallery :: FilePath -> FilePath -> FilePath -> FilePath -> [FilePath] -> Bool -> Bool -> IO ()
@@ -120,21 +137,27 @@ compileGallery configPath inputDirPath outputDirPath outputIndexPath excludedDir
120 do 137 do
121 config <- readConfig $ inputGalleryConf configPath 138 config <- readConfig $ inputGalleryConf configPath
122 139
140 putStrLn "Inventorying input files"
123 inputDir <- readDirectory inputDirPath 141 inputDir <- readDirectory inputDirPath
124 excludedCanonicalDirs <- mapM canonicalizePath excludedDirs 142 excludedCanonicalDirs <- mapM canonicalizePath excludedDirs
143
125 let sourceFilter = galleryDirFilter config excludedCanonicalDirs 144 let sourceFilter = galleryDirFilter config excludedCanonicalDirs
126 let sourceTree = filterDir sourceFilter inputDir 145 let sourceTree = filterDir sourceFilter inputDir
146 putStrLn "Reading input metadata"
127 inputTree <- readInputTree sourceTree 147 inputTree <- readInputTree sourceTree
128 let curatedInputTree = filterInputTree (inputTreeFilter config) inputTree 148 let curatedInputTree = filterInputTree (inputTreeFilter config) inputTree
129 149
130 let cache = if rebuildAll then skipCached else withCached 150 let galleryIndexPath = outputGalleryIndex outputIndexPath
131 let itemProc = itemProcessor config cache 151 cachedIndex <- loadCachedIndex galleryIndexPath
132 let thumbnailProc = thumbnailProcessor config cache 152 let cache = mkCache cachedIndex
153
154 let itemProc = itemProcessor config (cache $ return . Resource.properties)
155 let thumbnailProc = thumbnailProcessor config (cache $ fmap return . Resource.thumbnail)
133 let galleryBuilder = buildGalleryTree itemProc thumbnailProc (tagsFromDirectories config) 156 let galleryBuilder = buildGalleryTree itemProc thumbnailProc (tagsFromDirectories config)
134 resources <- galleryBuilder curatedInputTree 157 resources <- galleryBuilder curatedInputTree
135 158
136 when cleanOutput $ galleryCleanupResourceDir resources outputDirPath 159 when cleanOutput $ galleryCleanupResourceDir resources outputDirPath
137 writeJSON (outputGalleryIndex outputIndexPath) $ GalleryIndex (viewerConfig config) resources 160 writeJSON galleryIndexPath $ GalleryIndex (viewerConfig config) resources
138 161
139 where 162 where
140 inputGalleryConf :: FilePath -> FilePath 163 inputGalleryConf :: FilePath -> FilePath
@@ -145,10 +168,25 @@ compileGallery configPath inputDirPath outputDirPath outputIndexPath excludedDir
145 outputGalleryIndex "" = outputDirPath </> defaultIndexFile 168 outputGalleryIndex "" = outputDirPath </> defaultIndexFile
146 outputGalleryIndex file = file 169 outputGalleryIndex file = file
147 170
171 loadCachedIndex :: FilePath -> IO (Maybe GalleryIndex)
172 loadCachedIndex galleryIndexPath =
173 if rebuildAll
174 then return Nothing
175 else loadGalleryIndex galleryIndexPath
176
177 mkCache :: Maybe GalleryIndex -> (GalleryItem -> Maybe a) -> Cache a
178 mkCache refGalleryIndex =
179 if rebuildAll
180 then const noCache
181 else useCached (buildItemCache $ fmap tree refGalleryIndex)
182
183 itemProcessor :: GalleryConfig -> Cache GalleryItemProps -> ItemProcessor GalleryItemProps
148 itemProcessor config cache = 184 itemProcessor config cache =
149 itemFileProcessor 185 itemFileProcessor
150 (pictureMaxResolution config) cache 186 (pictureMaxResolution config) cache
151 inputDirPath outputDirPath itemsDir 187 inputDirPath outputDirPath itemsDir
188
189 thumbnailProcessor :: GalleryConfig -> Cache (Maybe Thumbnail) -> ItemProcessor (Maybe Thumbnail)
152 thumbnailProcessor config cache = 190 thumbnailProcessor config cache =
153 thumbnailFileProcessor 191 thumbnailFileProcessor
154 (thumbnailMaxResolution config) cache 192 (thumbnailMaxResolution config) cache