Skip to content
Snippets Groups Projects
Commit 0e5951ee authored by stuebinm's avatar stuebinm
Browse files

config option: don't copy asset files

parent 52b73711
No related branches found
No related tags found
No related merge requests found
......@@ -33,6 +33,7 @@ data LintConfig f = LintConfig
{ configScriptInject :: HKD f (Maybe Text)
, configAssemblyTag :: HKD f Text
, configMaxWarnLevel :: HKD f Level
, configDontCopyAssets :: HKD f Bool
} deriving (Generic)
type LintConfig' = LintConfig Identity
......@@ -43,6 +44,7 @@ deriving instance
, Show (HKD a Text)
, Show (HKD a Level)
, Show (HKD a [Text])
, Show (HKD a Bool)
)
=> Show (LintConfig a)
......@@ -58,6 +60,7 @@ instance
, FromJSON (HKD a [Text])
, FromJSON (HKD a Text)
, FromJSON (HKD a Level)
, FromJSON (HKD a Bool)
)
=> FromJSON (LintConfig a)
where
......
......@@ -8,12 +8,14 @@ module WriteRepo where
import CheckDir (DirResult (dirresultMaps),
resultIsFatal)
import CheckMap (MapResult (mapresultAdjusted, mapresultDepends))
import Control.Monad (forM_)
import Control.Monad (forM_, unless)
import Data.Aeson (encodeFile)
import Data.Map.Strict (toList)
import Data.Maybe (mapMaybe)
import Data.Set (Set)
import qualified Data.Set as S
import LintConfig (LintConfig (configDontCopyAssets),
LintConfig')
import Paths (normalise)
import System.Directory.Extra (copyFile, createDirectoryIfMissing)
import System.Exit (ExitCode (..))
......@@ -23,9 +25,9 @@ import System.FilePath.Posix ((</>))
import Types (Dep (Local))
writeAdjustedRepository :: FilePath -> FilePath -> DirResult -> IO ExitCode
writeAdjustedRepository inPath outPath result
| resultIsFatal result = do
writeAdjustedRepository :: LintConfig' -> FilePath -> FilePath -> DirResult -> IO ExitCode
writeAdjustedRepository config inPath outPath result
| resultIsFatal result && not (configDontCopyAssets config) = do
putStrLn "FATAL: Repository has missing assets; cannot write to outPath"
pure (ExitFailure 1)
| otherwise = do
......@@ -36,6 +38,7 @@ writeAdjustedRepository inPath outPath result
(\(path,out) -> encodeFile (outPath </> path) $ mapresultAdjusted out)
(toList $ dirresultMaps result)
unless (configDontCopyAssets config) $ do
-- collect asset dependencies of maps
-- TODO: its kinda weird doing that here, tbh
let localdeps :: Set FilePath =
......
......@@ -67,7 +67,7 @@ run options = do
else printPretty (level, lints)
case out options of
Just outpath -> writeAdjustedRepository repo outpath lints
Just outpath -> writeAdjustedRepository lintconfig repo outpath lints
>>= exitWith
Nothing -> pure ()
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment