{-# 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 (Int -> TestSettings -> ShowS) -> (TestSettings -> String) -> ([TestSettings] -> ShowS) -> Show TestSettings forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> TestSettings -> ShowS showsPrec :: Int -> TestSettings -> ShowS $cshow :: TestSettings -> String show :: TestSettings -> String $cshowList :: [TestSettings] -> ShowS showList :: [TestSettings] -> ShowS Show, TestSettings -> TestSettings -> Bool (TestSettings -> TestSettings -> Bool) -> (TestSettings -> TestSettings -> Bool) -> Eq TestSettings forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: TestSettings -> TestSettings -> Bool == :: TestSettings -> TestSettings -> Bool $c/= :: TestSettings -> TestSettings -> Bool /= :: 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 flagCommand :: String flagConfigFile :: Maybe String flagOutputFlags :: OutputFlags flagCommand :: Flags -> String flagConfigFile :: Flags -> Maybe String flagOutputFlags :: Flags -> OutputFlags ..} Environment environment Maybe Configuration mConf = do let filterFunc :: Map String a -> Map String a filterFunc = case String flagCommand of String "" -> Map String a -> Map String a forall a. a -> a id String _ -> (String -> a -> Bool) -> Map String a -> Map String a forall k a. (k -> a -> Bool) -> Map k a -> Map k a M.filterWithKey (\String k a _ -> String k String -> String -> Bool forall a. Eq a => a -> a -> Bool == String flagCommand) Map String LoopSettings testSettingLoops <- (LoopConfiguration -> IO LoopSettings) -> Map String LoopConfiguration -> IO (Map String LoopSettings) forall (t :: * -> *) (f :: * -> *) a b. (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) forall (f :: * -> *) a b. Applicative f => (a -> f b) -> Map String a -> f (Map String b) traverse (Flags -> Environment -> Maybe OutputConfiguration -> LoopConfiguration -> IO LoopSettings combineToLoopSettings Flags flags Environment environment (Maybe Configuration mConf Maybe Configuration -> (Configuration -> Maybe OutputConfiguration) -> Maybe OutputConfiguration forall a b. Maybe a -> (a -> Maybe b) -> Maybe b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= Configuration -> Maybe OutputConfiguration configOutputConfiguration)) (Map String LoopConfiguration -> Map String LoopConfiguration forall {a}. Map String a -> Map String a filterFunc (Map String LoopConfiguration -> Map String LoopConfiguration) -> Map String LoopConfiguration -> Map String LoopConfiguration forall a b. (a -> b) -> a -> b $ Map String LoopConfiguration -> (Configuration -> Map String LoopConfiguration) -> Maybe Configuration -> Map String LoopConfiguration forall b a. b -> (a -> b) -> Maybe a -> b maybe Map String LoopConfiguration 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 ..} Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () when (OutputFlags -> Bool outputFlagDebug OutputFlags flagOutputFlags) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ TestSettings -> IO () forall a. Show a => a -> IO () pPrint TestSettings testSets TestSettings -> IO TestSettings forall a. a -> IO a forall (f :: * -> *) a. Applicative f => a -> f a pure TestSettings testSets