{-# LANGUAGE RecordWildCards #-} module Feedback.Test.OptParse where import Control.Monad import Data.Map (Map) import qualified Data.Map as M import Feedback.Common.OptParse import Text.Show.Pretty (pPrint) getSettings :: IO TestSettings getSettings :: IO TestSettings getSettings = do Flags flags <- IO Flags getFlags Environment env <- IO Environment getEnvironment Maybe Configuration config <- Flags -> Environment -> IO (Maybe Configuration) getConfiguration Flags flags Environment env Flags -> Environment -> Maybe Configuration -> IO TestSettings combineToTestSettings Flags flags Environment env Maybe Configuration config data TestSettings = TestSettings { TestSettings -> Map String LoopSettings testSettingLoops :: !(Map String LoopSettings) } deriving (Int -> TestSettings -> ShowS [TestSettings] -> ShowS TestSettings -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [TestSettings] -> ShowS $cshowList :: [TestSettings] -> ShowS show :: TestSettings -> String $cshow :: TestSettings -> String showsPrec :: Int -> TestSettings -> ShowS $cshowsPrec :: Int -> TestSettings -> ShowS Show, TestSettings -> TestSettings -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: TestSettings -> TestSettings -> Bool $c/= :: TestSettings -> TestSettings -> Bool == :: TestSettings -> TestSettings -> Bool $c== :: TestSettings -> TestSettings -> Bool Eq) combineToTestSettings :: Flags -> Environment -> Maybe Configuration -> IO TestSettings combineToTestSettings :: Flags -> Environment -> Maybe Configuration -> IO TestSettings combineToTestSettings flags :: Flags flags@Flags {String Maybe String OutputFlags flagOutputFlags :: Flags -> OutputFlags flagConfigFile :: Flags -> Maybe String flagCommand :: Flags -> String flagOutputFlags :: OutputFlags flagConfigFile :: Maybe String flagCommand :: String ..} Environment environment Maybe Configuration mConf = do let filterFunc :: Map String a -> Map String a filterFunc = case String flagCommand of String "" -> forall a. a -> a id String _ -> forall k a. (k -> a -> Bool) -> Map k a -> Map k a M.filterWithKey (\String k a _ -> String k forall a. Eq a => a -> a -> Bool == String flagCommand) Map String LoopSettings testSettingLoops <- forall (t :: * -> *) (f :: * -> *) a b. (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) traverse (Flags -> Environment -> Maybe OutputConfiguration -> LoopConfiguration -> IO LoopSettings combineToLoopSettings Flags flags Environment environment (Maybe Configuration mConf forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= Configuration -> Maybe OutputConfiguration configOutputConfiguration)) (forall {a}. Map String a -> Map String a filterFunc forall a b. (a -> b) -> a -> b $ forall b a. b -> (a -> b) -> Maybe a -> b maybe forall k a. Map k a M.empty Configuration -> Map String LoopConfiguration configLoops Maybe Configuration mConf) let testSets :: TestSettings testSets = TestSettings {Map String LoopSettings testSettingLoops :: Map String LoopSettings testSettingLoops :: Map String LoopSettings ..} forall (f :: * -> *). Applicative f => Bool -> f () -> f () when (OutputFlags -> Bool outputFlagDebug OutputFlags flagOutputFlags) forall a b. (a -> b) -> a -> b $ forall a. Show a => a -> IO () pPrint TestSettings testSets forall (f :: * -> *) a. Applicative f => a -> f a pure TestSettings testSets