{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TemplateHaskell #-} module Config ( Config(..) , configParserInfo , checkConfig ) where import Data.Functor.Identity (Identity(..)) import Data.Version (showVersion) import Options.Applicative import qualified Paths_nix_freeze_tree as NixFreezeTree import Text.RawString.QQ (r) data Config f = Config { _force :: f Bool , _verbose :: f Bool , _outputRoot :: f FilePath , _inDir :: f FilePath } deriving instance Eq (Config Identity) deriving instance Eq (Config Maybe) deriving instance Show (Config Identity) deriving instance Show (Config Maybe) version :: Parser (a -> a) version = abortOption (InfoMsg message) $ mconcat [ long "version" , help "Display version information and exit." ] where message = "nix-freeze-tree " <> showVersion NixFreezeTree.version <> "\n" <> [r|Copyright (C) 2020 Jack Kelly License AGPLv3+: GNU Affero General Public License version 3 or later This is free software: you are free to change and redistribute it. There is NO WARRANTY, to the extent permitted by law. |] configParser :: Parser (Config Maybe) configParser = Config <$> do fmap Just . switch $ mconcat [ long "force" , short 'f' , help $ "If any default.nix exist in the output directory, " <> "remove them and generate anyway" ] <*> do fmap Just . switch $ mconcat [ long "verbose" , short 'v' , help "Display messages while working." ] <*> do option (Just <$> str) $ mconcat [ long "out-root" , short 'o' , metavar "OUT_ROOT" , help "Where to write the nix files" , showDefaultWith $ const "IN_DIR" , value Nothing ] <*> do argument (Just <$> str) $ mconcat [ metavar "IN_DIR" , help "Directory to freeze" , showDefaultWith $ const "." , value (Just ".") ] configParserInfo :: ParserInfo (Config Maybe) configParserInfo = info (version <*> helper <*> configParser) $ mconcat [ header $ "nix-freeze-tree - " <> "Create fixed-output derivations for each file in a tree" , progDesc $ "Write a tree of nix expressions to OUT_ROOT that build a " <> "derivation, symlinking every file in IN_DIR as a separate " <> "fixed-output derivation." , fullDesc ] checkConfig :: Config Maybe -> Maybe (Config Identity) checkConfig = collectMaybes . applyDefaults where collectMaybes (Config f v o i) = Config <$> (Identity <$> f) <*> (Identity <$> v) <*> (Identity <$> o) <*> (Identity <$> i) applyDefaults c = Config (_force c) (_verbose c <|> Just False) (_outputRoot c <|> _inDir c) (_inDir c)