{-# LANGUAGE Safe #-}
module Config.Programs (
CompilerBackend(..),
CxxCommand(..),
TestCommand(..),
TestCommandResult(..),
VersionHash(..),
) where
class CompilerBackend b where
runCxxCommand :: b -> CxxCommand -> IO String
runTestCommand :: b -> TestCommand -> IO TestCommandResult
getCompilerHash :: b -> VersionHash
newtype VersionHash = VersionHash String deriving (Eq)
instance Show VersionHash where
show (VersionHash h) = h
data CxxCommand =
CompileToObject {
ctoSource :: String,
ctoPath :: String,
ctoNamespaceMacro :: String,
ctoNamespace :: String,
ctoPaths :: [String],
ctoExtra :: Bool
} |
CompileToBinary {
ctbMain :: String,
ctbSources :: [String],
ctbOutput :: String,
ctbPaths :: [String],
ctbLinkFlags :: [String]
}
deriving (Show)
data TestCommand =
TestCommand {
tcBinary :: String,
tcPath :: String
}
deriving (Show)
data TestCommandResult =
TestCommandResult {
tcrSuccess :: Bool,
tcrOutput :: [String],
tcrError :: [String]
}
deriving (Show)