{-# LANGUAGE Safe #-}
module Cli.CompileOptions (
CompileOptions(..),
CompileMode(..),
ExtraSource(..),
ForceMode(..),
HelpMode(..),
emptyCompileOptions,
getLinkFlags,
getSourceCategories,
getSourceDeps,
getSourceFile,
isCompileBinary,
isCompileFast,
isCompileIncremental,
isCompileRecompile,
isCreateTemplates,
isExecuteTests,
maybeDisableHelp,
) where
import Types.TypeCategory (FunctionName)
import Types.TypeInstance (CategoryName)
data CompileOptions =
CompileOptions {
coHelp :: HelpMode,
coPublicDeps :: [FilePath],
coPrivateDeps :: [FilePath],
coPaths :: [FilePath],
coExtraFiles :: [ExtraSource],
coExtraPaths :: [FilePath],
coSourcePrefix :: FilePath,
coMode :: CompileMode,
coForce :: ForceMode
}
deriving (Show)
emptyCompileOptions :: CompileOptions
emptyCompileOptions =
CompileOptions {
coHelp = HelpUnspecified,
coPublicDeps = [],
coPrivateDeps = [],
coPaths = [],
coExtraFiles = [],
coExtraPaths = [],
coSourcePrefix = "",
coMode = CompileUnspecified,
coForce = DoNotForce
}
data ExtraSource =
CategorySource {
csSource :: FilePath,
csCategories :: [CategoryName],
csDepCategories :: [CategoryName]
} |
OtherSource {
osSource :: FilePath
}
deriving (Eq,Show)
getSourceFile :: ExtraSource -> String
getSourceFile (CategorySource s _ _) = s
getSourceFile (OtherSource s) = s
getSourceCategories :: ExtraSource -> [CategoryName]
getSourceCategories (CategorySource _ cs _) = cs
getSourceCategories (OtherSource _) = []
getSourceDeps :: ExtraSource -> [CategoryName]
getSourceDeps (CategorySource _ _ ds) = ds
getSourceDeps (OtherSource _) = []
data HelpMode = HelpNeeded | HelpNotNeeded | HelpUnspecified deriving (Eq,Show)
data ForceMode = DoNotForce | ForceAll deriving (Eq,Ord,Show)
data CompileMode =
CompileBinary {
cbCategory :: CategoryName,
cbFunction :: FunctionName,
cbOutputName :: FilePath,
cbLinkFlags :: [String]
} |
CompileFast {
cfCategory :: CategoryName,
cfFunction :: FunctionName,
cfSource :: FilePath
} |
ExecuteTests {
etInclude :: [FilePath]
} |
CompileIncremental {
ciLinkFlags :: [String]
} |
CompileRecompile |
CompileRecompileRecursive |
CreateTemplates |
CompileUnspecified
deriving (Eq,Show)
isCompileBinary :: CompileMode -> Bool
isCompileBinary (CompileBinary _ _ _ _) = True
isCompileBinary _ = False
isCompileFast :: CompileMode -> Bool
isCompileFast (CompileFast _ _ _) = True
isCompileFast _ = False
isCompileIncremental :: CompileMode -> Bool
isCompileIncremental (CompileIncremental _) = True
isCompileIncremental _ = False
isCompileRecompile :: CompileMode -> Bool
isCompileRecompile CompileRecompile = True
isCompileRecompile CompileRecompileRecursive = True
isCompileRecompile _ = False
isExecuteTests :: CompileMode -> Bool
isExecuteTests (ExecuteTests _) = True
isExecuteTests _ = False
isCreateTemplates :: CompileMode -> Bool
isCreateTemplates CreateTemplates = True
isCreateTemplates _ = False
maybeDisableHelp :: HelpMode -> HelpMode
maybeDisableHelp HelpUnspecified = HelpNotNeeded
maybeDisableHelp h = h
getLinkFlags :: CompileMode -> [String]
getLinkFlags (CompileBinary _ _ _ lf) = lf
getLinkFlags (CompileIncremental lf) = lf
getLinkFlags _ = []