summaryrefslogtreecommitdiff
path: root/lib/WriteRepo.hs
diff options
context:
space:
mode:
authorstuebinm2021-11-10 23:21:15 +0100
committerstuebinm2021-11-10 23:21:15 +0100
commit1338e4a1c9f445e5384cdee3d65cf5a46ce03105 (patch)
treea9ad34982e98a7dad4a24bc6269021283bde0d06 /lib/WriteRepo.hs
parent508f8885f6087f2c56b188cd0632a4fc39de0540 (diff)
copy map assets (and refuse if any are missing)
Diffstat (limited to '')
-rw-r--r--lib/WriteRepo.hs67
1 files changed, 47 insertions, 20 deletions
diff --git a/lib/WriteRepo.hs b/lib/WriteRepo.hs
index 5e695f5..c0bf31b 100644
--- a/lib/WriteRepo.hs
+++ b/lib/WriteRepo.hs
@@ -1,28 +1,55 @@
-
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE ScopedTypeVariables #-}
-- | Module for writing an already linted map Repository back out again.
-
module WriteRepo where
-import CheckDir (DirResult (dirresultMaps))
-import CheckMap (MapResult (mapresultAdjusted))
+import CheckDir (DirResult (dirresultMaps),
+ resultIsFatal)
+import CheckMap (MapResult (mapresultAdjusted, mapresultDepends))
+import Control.Monad (forM_)
import Data.Aeson (encodeFile)
import Data.Map.Strict (toList)
-import System.Directory.Extra (createDirectoryIfMissing)
+import Data.Maybe (mapMaybe)
+import Data.Set (Set)
+import qualified Data.Set as S
+import Paths (normalise)
+import System.Directory.Extra (copyFile, createDirectoryIfMissing)
+import System.FilePath (takeDirectory)
+import qualified System.FilePath as FP
import System.FilePath.Posix ((</>))
-
-
-
-writeAdjustedRepository :: FilePath -> DirResult -> IO ()
-writeAdjustedRepository outPath result = do
-
- -- True here just means the equivalent of mkdir -p
- createDirectoryIfMissing True outPath
-
- -- write out all maps
- mapM_
- (\(path,out) -> encodeFile (outPath </> path) $ mapresultAdjusted out)
- (toList $ dirresultMaps result)
-
- -- TODO: copy all assets
+import Types (Dep (Local))
+
+
+writeAdjustedRepository :: FilePath -> FilePath -> DirResult -> IO ()
+writeAdjustedRepository inPath outPath result
+ | resultIsFatal result = pure ()
+ | otherwise = do
+ createDirectoryIfMissing True outPath
+
+ -- write out all maps
+ mapM_
+ (\(path,out) -> encodeFile (outPath </> path) $ mapresultAdjusted out)
+ (toList $ dirresultMaps result)
+
+ -- collect asset dependencies of maps
+ -- TODO: its kinda weird doing that here, tbh
+ let localdeps :: Set FilePath =
+ S.fromList . concatMap
+ (\(mappath,mapresult) ->
+ let mapdir = takeDirectory mappath in
+ mapMaybe (\case
+ Local path -> Just . normalise mapdir $ path
+ _ -> Nothing)
+ $ mapresultDepends mapresult)
+ . toList $ dirresultMaps result
+
+ -- copy all assets
+ forM_ localdeps $ \path ->
+ let
+ assetPath = FP.normalise $ inPath </> path
+ newPath = FP.normalise $ outPath </> path
+ in do
+ putStrLn $ "copying " <> assetPath <> " → " <> newPath
+ copyFile assetPath newPath