diff options
Diffstat (limited to 'compiler/src/Lib.hs')
-rw-r--r-- | compiler/src/Lib.hs | 251 |
1 files changed, 32 insertions, 219 deletions
diff --git a/compiler/src/Lib.hs b/compiler/src/Lib.hs index 70a2cca..bab7e9c 100644 --- a/compiler/src/Lib.hs +++ b/compiler/src/Lib.hs | |||
@@ -1,11 +1,7 @@ | |||
1 | {-# LANGUAGE DuplicateRecordFields, DeriveGeneric #-} | ||
2 | |||
3 | |||
4 | -- ldgallery - A static generator which turns a collection of tagged | 1 | -- ldgallery - A static generator which turns a collection of tagged |
5 | -- pictures into a searchable web gallery. | 2 | -- pictures into a searchable web gallery. |
6 | -- | 3 | -- |
7 | -- Copyright (C) 2019 Pacien TRAN-GIRARD | 4 | -- Copyright (C) 2019 Pacien TRAN-GIRARD |
8 | -- 2019 Guillaume FOUET | ||
9 | -- | 5 | -- |
10 | -- This program is free software: you can redistribute it and/or modify | 6 | -- This program is free software: you can redistribute it and/or modify |
11 | -- it under the terms of the GNU Affero General Public License as | 7 | -- it under the terms of the GNU Affero General Public License as |
@@ -26,232 +22,49 @@ module Lib | |||
26 | ) where | 22 | ) where |
27 | 23 | ||
28 | 24 | ||
29 | import GHC.Generics | 25 | import GHC.Generics (Generic) |
30 | 26 | import Data.Function ((&)) | |
31 | import Control.Monad.IO.Class (MonadIO, liftIO) | 27 | import System.Directory (createDirectoryIfMissing) |
32 | import Control.Exception (Exception, throwIO) | 28 | import System.FilePath (dropFileName, (</>)) |
33 | 29 | import Data.Aeson (ToJSON, encodeFile) | |
34 | import Data.Function | ||
35 | import Data.Maybe (fromMaybe, listToMaybe) | ||
36 | import Data.List (map) | ||
37 | import Data.Set (fromList, toList) | ||
38 | import Data.Char (toLower) | ||
39 | import Data.Text (Text, empty, pack) | ||
40 | import Data.Yaml (ParseException, decodeFileEither) | ||
41 | import Data.Aeson | ||
42 | |||
43 | import System.FilePath ((</>), joinPath, dropFileName, dropExtension, isExtensionOf) | ||
44 | import qualified System.FilePath.Posix (joinPath) | ||
45 | import System.Directory.Tree | ||
46 | import System.Directory | ||
47 | |||
48 | |||
49 | encodingOptions :: Options | ||
50 | encodingOptions = defaultOptions | ||
51 | { fieldLabelModifier = map toLower | ||
52 | , constructorTagModifier = map toLower | ||
53 | , sumEncoding = defaultTaggedObject | ||
54 | { tagFieldName = "type" | ||
55 | , contentsFieldName = "contents" | ||
56 | } | ||
57 | } | ||
58 | |||
59 | |||
60 | -- input structure | ||
61 | |||
62 | data SidecarItemMetadata = SidecarItemMetadata | ||
63 | { title :: Maybe Text | ||
64 | , date :: Maybe Text | ||
65 | , description :: Maybe Text | ||
66 | , tags :: Maybe [Text] | ||
67 | } deriving (Generic, Show) | ||
68 | |||
69 | instance FromJSON SidecarItemMetadata where | ||
70 | parseJSON = genericParseJSON encodingOptions | ||
71 | |||
72 | |||
73 | -- output structures | ||
74 | |||
75 | type ResourcePath = Text | ||
76 | type Tag = Text | ||
77 | type FileSizeKB = Int | ||
78 | |||
79 | |||
80 | data Resolution = Resolution | ||
81 | { width :: Int | ||
82 | , height :: Int | ||
83 | } deriving (Generic, Show) | ||
84 | |||
85 | instance ToJSON Resolution where | ||
86 | toJSON = genericToJSON encodingOptions | ||
87 | toEncoding = genericToEncoding encodingOptions | ||
88 | |||
89 | |||
90 | data ItemProperties = | ||
91 | Directory { items :: [Item] } | ||
92 | | Image { resolution :: Resolution, filesize :: FileSizeKB } | ||
93 | -- | Video { filesize :: FileSizeKB } | ||
94 | | Unknown | ||
95 | deriving (Generic, Show) | ||
96 | |||
97 | instance ToJSON ItemProperties where | ||
98 | toJSON = genericToJSON encodingOptions | ||
99 | toEncoding = genericToEncoding encodingOptions | ||
100 | |||
101 | |||
102 | data Item = Item | ||
103 | { title :: Text | ||
104 | , date :: Text -- TODO: checked ISO8601 date | ||
105 | , description :: Text | ||
106 | , tags :: [Tag] | ||
107 | , path :: ResourcePath | ||
108 | , thumbnail :: Maybe ResourcePath | ||
109 | , properties :: ItemProperties | ||
110 | } deriving (Generic, Show) | ||
111 | |||
112 | instance ToJSON Item where | ||
113 | toJSON = genericToJSON encodingOptions | ||
114 | toEncoding = genericToEncoding encodingOptions | ||
115 | |||
116 | 30 | ||
117 | -- mapping | 31 | import Files (FileName, readDirectory) |
32 | import Input (readInputTree) | ||
33 | import Resource (buildResourceTree) | ||
34 | import Gallery (buildGalleryTree) | ||
118 | 35 | ||
119 | data LoadException = LoadException String ParseException deriving Show | ||
120 | instance Exception LoadException | ||
121 | 36 | ||
122 | decodeYamlFile :: (MonadIO m, FromJSON a) => FilePath -> m a | 37 | writeJSON :: ToJSON a => FileName -> a -> IO () |
123 | decodeYamlFile fpath = | 38 | writeJSON path obj = |
124 | liftIO $ Data.Yaml.decodeFileEither fpath | 39 | createDirectoryIfMissing True (dropFileName path) |
125 | >>= either (throwIO . LoadException fpath) return | 40 | >> encodeFile path obj |
126 | |||
127 | |||
128 | toMetaTree :: DirTree FilePath -> IO (DirTree SidecarItemMetadata) | ||
129 | toMetaTree tree = return (filterDir canContainMetadata tree) >>= metaNode | ||
130 | where | ||
131 | -- TODO: exclude hidden files (name starting with '.')? | ||
132 | canContainMetadata :: DirTree a -> Bool | ||
133 | canContainMetadata (File fname _) = isExtensionOf ".yaml" fname | ||
134 | canContainMetadata (Dir _ _) = True | ||
135 | |||
136 | metaNode :: DirTree FilePath -> IO (DirTree SidecarItemMetadata) | ||
137 | metaNode (Failed _ ferr) = ioError ferr | ||
138 | metaNode file@(File _ fpath) = decodeYamlFile fpath | ||
139 | >>= \metadata -> return file { file = metadata } | ||
140 | metaNode dir@(Dir _ dcontents) = mapM metaNode dcontents | ||
141 | >>= \contents -> return dir { contents = contents } | ||
142 | |||
143 | |||
144 | unique :: Ord a => [a] -> [a] | ||
145 | unique = Data.Set.toList . Data.Set.fromList | ||
146 | |||
147 | joinURLPath :: [FileName] -> Text | ||
148 | joinURLPath = pack . System.FilePath.Posix.joinPath | ||
149 | |||
150 | |||
151 | toItemTree :: FilePath -> FilePath -> DirTree SidecarItemMetadata -> IO Item | ||
152 | toItemTree itemsDir thumbnailsDir = itemNode [] | ||
153 | where | ||
154 | itemNode :: [FileName] -> DirTree SidecarItemMetadata -> IO Item | ||
155 | itemNode pathTo (Dir dname dcontents) = | ||
156 | mapM (itemNode path) dcontents | ||
157 | >>= \items -> return Item | ||
158 | { title = pack dname | ||
159 | , date = empty | ||
160 | , description = empty | ||
161 | , tags = aggregateChildTags items | ||
162 | , path = joinURLPath $ itemsDir:path | ||
163 | , thumbnail = Nothing | ||
164 | , properties = Directory items } | ||
165 | where | ||
166 | path = pathTo ++ [dname] | ||
167 | aggregateChildTags = unique . concatMap (\item -> tags (item::Item)) | ||
168 | |||
169 | itemNode pathTo (File fname metadata) = | ||
170 | return Item | ||
171 | { title = optMeta title $ pack name | ||
172 | , date = optMeta date empty -- TODO: check and normalise dates | ||
173 | , description = optMeta description empty | ||
174 | , tags = optMeta tags [] | ||
175 | , path = joinURLPath $ itemsDir:path | ||
176 | , thumbnail = Just $ joinURLPath $ thumbnailsDir:path | ||
177 | , properties = Unknown } -- TODO | ||
178 | where | ||
179 | name = dropExtension fname | ||
180 | path = pathTo ++ [name] | ||
181 | optMeta get fallback = fromMaybe fallback $ get (metadata::SidecarItemMetadata) | ||
182 | |||
183 | |||
184 | data ObjectTree = ObjectTree | ||
185 | { pathTo :: [ObjectTree] | ||
186 | , meta :: (DirTree SidecarItemMetadata) | ||
187 | , item :: Item } deriving Show | ||
188 | |||
189 | rootObjectTree :: DirTree SidecarItemMetadata -> Item -> ObjectTree | ||
190 | rootObjectTree = ObjectTree [] | ||
191 | |||
192 | toObjectTree :: (DirTree SidecarItemMetadata -> IO Item) -> DirTree SidecarItemMetadata -> IO ObjectTree | ||
193 | toObjectTree itemGen meta = itemGen meta >>= return . (rootObjectTree meta) | ||
194 | |||
195 | flatten :: ObjectTree -> [ObjectTree] | ||
196 | flatten object@(ObjectTree _ (File _ _) _) = [object] | ||
197 | flatten object@(ObjectTree pathTo (Dir _ dcontents) item) = | ||
198 | zip dcontents (items $ properties item) | ||
199 | & map (uncurry $ ObjectTree $ pathTo ++ [object]) | ||
200 | & concatMap flatten | ||
201 | & (:) object | ||
202 | |||
203 | objFileName :: ObjectTree -> FileName | ||
204 | objFileName (ObjectTree _ (Dir name _) _) = name | ||
205 | objFileName (ObjectTree _ (File name _) _) = dropExtension name -- without ".yaml" | ||
206 | |||
207 | objFilePath :: ObjectTree -> FilePath | ||
208 | objFilePath obj@(ObjectTree pathTo _ _) = | ||
209 | (map (name . meta) pathTo) ++ [objFileName obj] | ||
210 | & System.FilePath.joinPath | ||
211 | |||
212 | |||
213 | data FileTransform = FileTransform | ||
214 | { src :: FilePath | ||
215 | , dst :: FilePath } deriving Show | ||
216 | 41 | ||
217 | 42 | ||
218 | isUpToDate :: FilePath -> FilePath -> IO Bool | 43 | process :: FilePath -> FilePath -> IO () |
219 | isUpToDate ref target = | 44 | process inputDirPath outputDirPath = |
220 | do | 45 | do |
221 | refTime <- getModificationTime ref | 46 | inputDir <- readDirectory inputDirPath |
222 | targetTime <- getModificationTime target | 47 | putStrLn "\nINPUT DIR" |
223 | return (target >= ref) | 48 | putStrLn (show inputDir) |
224 | 49 | ||
50 | outputDir <- readDirectory outputDirPath | ||
51 | putStrLn "\nOUTPUT DIR" | ||
52 | putStrLn (show outputDir) | ||
225 | 53 | ||
226 | unrooted :: AnchoredDirTree a -> DirTree a | 54 | inputTree <- readInputTree inputDir |
227 | unrooted t = (dirTree t) { name = "" } | 55 | putStrLn "\nINPUT TREE" |