summaryrefslogtreecommitdiff
path: root/lib/WriteRepo.hs
blob: c0bf31b61b48beef2e4013644877fbf243be34d8 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
{-# LANGUAGE LambdaCase          #-}
{-# LANGUAGE ScopedTypeVariables #-}


-- | Module for writing an already linted map Repository back out again.
module WriteRepo where

import           CheckDir               (DirResult (dirresultMaps),
                                         resultIsFatal)
import           CheckMap               (MapResult (mapresultAdjusted, mapresultDepends))
import           Control.Monad          (forM_)
import           Data.Aeson             (encodeFile)
import           Data.Map.Strict        (toList)
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  ((</>))
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