-- | Copyright: (c) 2021-2022 berberman
-- SPDX-License-Identifier: MIT
-- Maintainer: berberman <berberman@yandex.com>
-- Stability: experimental
-- Portability: portable
module NvFetcher.Config where

import Data.Default
import Development.Shake

-- | Nvfetcher configuration
data Config = Config
  { Config -> ShakeOptions
shakeConfig :: ShakeOptions,
    Config -> FilePath
buildDir :: FilePath,
    Config -> Rules ()
customRules :: Rules (),
    Config -> Action ()
actionAfterBuild :: Action (),
    Config -> Action ()
actionAfterClean :: Action (),
    Config -> Int
retry :: Int,
    Config -> Maybe FilePath
filterRegex :: Maybe String,
    Config -> Bool
cacheNvchecker :: Bool
  }

instance Default Config where
  def :: Config
def =
    Config :: ShakeOptions
-> FilePath
-> Rules ()
-> Action ()
-> Action ()
-> Int
-> Maybe FilePath
-> Bool
-> Config
Config
      { shakeConfig :: ShakeOptions
shakeConfig =
          ShakeOptions
shakeOptions
            { shakeProgress :: IO Progress -> IO ()
shakeProgress = IO Progress -> IO ()
progressSimple,
              shakeThreads :: Int
shakeThreads = Int
0
            },
        buildDir :: FilePath
buildDir = FilePath
"_sources",
        customRules :: Rules ()
customRules = () -> Rules ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (),
        actionAfterBuild :: Action ()
actionAfterBuild = () -> Action ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (),
        actionAfterClean :: Action ()
actionAfterClean = () -> Action ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (),
        retry :: Int
retry = Int
3,
        filterRegex :: Maybe FilePath
filterRegex = Maybe FilePath
forall a. Maybe a
Nothing,
        cacheNvchecker :: Bool
cacheNvchecker = Bool
True
      }