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.hs74
1 files changed, 54 insertions, 20 deletions
diff --git a/compiler/src/Compiler.hs b/compiler/src/Compiler.hs
index 749872d..1ec55c5 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,15 @@ 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 JSON.eitherDecodeFileStrict path
89 >>= either (\err -> warn err >> return Nothing) (return . Just)
90 warn = putStrLn . ("Warning:\tUnable to reuse existing index as cache: " ++)
91
76 92
77(&&&) :: (a -> Bool) -> (a -> Bool) -> a -> Bool 93(&&&) :: (a -> Bool) -> (a -> Bool) -> a -> Bool
78(&&&) = liftM2 (&&) 94(&&&) = liftM2 (&&)
@@ -81,16 +97,16 @@ writeJSON outputPath object =
81(|||) = liftM2 (||) 97(|||) = liftM2 (||)
82 98
83anyPattern :: [String] -> String -> Bool 99anyPattern :: [String] -> String -> Bool
84anyPattern patterns string = any (flip Glob.match string) (map Glob.compile patterns) 100anyPattern patterns string = any (flip Glob.match string . Glob.compile) patterns
85 101
86galleryDirFilter :: GalleryConfig -> [FilePath] -> FSNode -> Bool 102galleryDirFilter :: GalleryConfig -> [FilePath] -> FSNode -> Bool
87galleryDirFilter config excludedCanonicalDirs = 103galleryDirFilter config excludedCanonicalDirs =
88 (not . isHidden) 104 (not . isHidden)
89 &&& (not . isExcludedDir) 105 &&& (not . isExcludedDir)
90 &&& ((matchesDir $ anyPattern $ includedDirectories config) ||| 106 &&& (matchesDir (anyPattern $ includedDirectories config) |||
91 (matchesFile $ anyPattern $ includedFiles config)) 107 matchesFile (anyPattern $ includedFiles config))
92 &&& (not . ((matchesDir $ anyPattern $ excludedDirectories config) ||| 108 &&& (not . (matchesDir (anyPattern $ excludedDirectories config) |||
93 (matchesFile $ anyPattern $ excludedFiles config))) 109 matchesFile (anyPattern $ excludedFiles config)))
94 110
95 where 111 where
96 matchesDir :: (FileName -> Bool) -> FSNode -> Bool 112 matchesDir :: (FileName -> Bool) -> FSNode -> Bool
@@ -102,17 +118,17 @@ galleryDirFilter config excludedCanonicalDirs =
102 matchesFile _ Dir{} = False 118 matchesFile _ Dir{} = False
103 119
104 isExcludedDir :: FSNode -> Bool 120 isExcludedDir :: FSNode -> Bool
105 isExcludedDir Dir{canonicalPath} = any (canonicalPath ==) excludedCanonicalDirs 121 isExcludedDir Dir{canonicalPath} = canonicalPath `elem` excludedCanonicalDirs
106 isExcludedDir File{} = False 122 isExcludedDir File{} = False
107 123
108inputTreeFilter :: GalleryConfig -> InputTree -> Bool 124inputTreeFilter :: GalleryConfig -> InputTree -> Bool
109inputTreeFilter GalleryConfig{includedTags, excludedTags} = 125inputTreeFilter GalleryConfig{includedTags, excludedTags} =
110 (hasTagMatching $ anyPattern includedTags) 126 hasTagMatching (anyPattern includedTags)
111 &&& (not . (hasTagMatching $ anyPattern excludedTags)) 127 &&& (not . hasTagMatching (anyPattern excludedTags))
112 128
113 where 129 where
114 hasTagMatching :: (String -> Bool) -> InputTree -> Bool 130 hasTagMatching :: (String -> Bool) -> InputTree -> Bool
115 hasTagMatching cond = (any cond) . (fromMaybe [""] . tags) . sidecar 131 hasTagMatching cond = any cond . (fromMaybe [""] . tags) . sidecar
116 132
117 133
118compileGallery :: FilePath -> FilePath -> FilePath -> FilePath -> [FilePath] -> Bool -> Bool -> IO () 134compileGallery :: FilePath -> FilePath -> FilePath -> FilePath -> [FilePath] -> Bool -> Bool -> IO ()
@@ -127,14 +143,17 @@ compileGallery configPath inputDirPath outputDirPath outputIndexPath excludedDir
127 inputTree <- readInputTree sourceTree 143 inputTree <- readInputTree sourceTree
128 let curatedInputTree = filterInputTree (inputTreeFilter config) inputTree 144 let curatedInputTree = filterInputTree (inputTreeFilter config) inputTree
129 145
130 let cache = if rebuildAll then skipCached else withCached 146 let galleryIndexPath = outputGalleryIndex outputIndexPath
131 let itemProc = itemProcessor config cache 147 cachedIndex <- loadCachedIndex galleryIndexPath
132 let thumbnailProc = thumbnailProcessor config cache 148 let cache = mkCache cachedIndex
149
150 let itemProc = itemProcessor config (cache Resource.properties)
151 let thumbnailProc = thumbnailProcessor config (cache Resource.thumbnail)
133 let galleryBuilder = buildGalleryTree itemProc thumbnailProc (tagsFromDirectories config) 152 let galleryBuilder = buildGalleryTree itemProc thumbnailProc (tagsFromDirectories config)
134 resources <- galleryBuilder curatedInputTree 153 resources <- galleryBuilder curatedInputTree
135 154
136 when cleanOutput $ galleryCleanupResourceDir resources outputDirPath 155 when cleanOutput $ galleryCleanupResourceDir resources outputDirPath
137 writeJSON (outputGalleryIndex outputIndexPath) $ GalleryIndex (viewerConfig config) resources 156 writeJSON galleryIndexPath $ GalleryIndex (viewerConfig config) resources
138 157
139 where 158 where
140 inputGalleryConf :: FilePath -> FilePath 159 inputGalleryConf :: FilePath -> FilePath
@@ -145,10 +164,25 @@ compileGallery configPath inputDirPath outputDirPath outputIndexPath excludedDir
145 outputGalleryIndex "" = outputDirPath </> defaultIndexFile 164 outputGalleryIndex "" = outputDirPath </> defaultIndexFile
146 outputGalleryIndex file = file 165 outputGalleryIndex file = file
147 166
167 loadCachedIndex :: FilePath -> IO (Maybe GalleryIndex)
168 loadCachedIndex galleryIndexPath =
169 if rebuildAll
170 then return Nothing
171 else loadGalleryIndex galleryIndexPath
172
173 mkCache :: Maybe GalleryIndex -> (GalleryItem -> a) -> Cache a
174 mkCache refGalleryIndex =
175 if rebuildAll
176 then const noCache
177 else useCached (buildItemCache $ fmap tree refGalleryIndex)
178
179 itemProcessor :: GalleryConfig -> Cache GalleryItemProps -> ItemProcessor GalleryItemProps
148 itemProcessor config cache = 180 itemProcessor config cache =
149 itemFileProcessor 181 itemFileProcessor
150 (pictureMaxResolution config) cache 182 (pictureMaxResolution config) cache
151 inputDirPath outputDirPath itemsDir 183 inputDirPath outputDirPath itemsDir
184
185 thumbnailProcessor :: GalleryConfig -> Cache (Maybe Thumbnail) -> ItemProcessor (Maybe Thumbnail)
152 thumbnailProcessor config cache = 186 thumbnailProcessor config cache =
153 thumbnailFileProcessor 187 thumbnailFileProcessor
154 (thumbnailMaxResolution config) cache 188 (thumbnailMaxResolution config) cache