{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE Trustworthy #-}
module Cli.CompileOptions (
CompileOptions(..),
CompileMode(..),
ExtraSource(..),
ForceMode(..),
HelpMode(..),
LinkerMode(..),
emptyCompileOptions,
getLinkFlags,
getSourceCategories,
getSourceDeps,
getSourceFile,
isCompileBinary,
isCompileFast,
isCompileIncremental,
isCompileRecompile,
isCompileUnspecified,
isCreateTemplates,
isExecuteTests,
maybeDisableHelp,
coExtraFiles,
coExtraPaths,
coForce,
coHelp,
coMode,
coParallel,
coPaths,
coPrivateDeps,
coPublicDeps,
coSourcePrefix,
) where
import Lens.Micro.TH (makeLenses)
import Types.TypeCategory (FunctionName)
import Types.TypeInstance (CategoryName)
emptyCompileOptions :: CompileOptions
emptyCompileOptions :: CompileOptions
emptyCompileOptions =
CompileOptions {
_coHelp :: HelpMode
_coHelp = HelpMode
HelpUnspecified,
_coPublicDeps :: [FilePath]
_coPublicDeps = [],
_coPrivateDeps :: [FilePath]
_coPrivateDeps = [],
_coPaths :: [FilePath]
_coPaths = [],
_coExtraFiles :: [ExtraSource]
_coExtraFiles = [],
_coExtraPaths :: [FilePath]
_coExtraPaths = [],
_coSourcePrefix :: FilePath
_coSourcePrefix = FilePath
"",
_coMode :: CompileMode
_coMode = CompileMode
CompileUnspecified,
_coForce :: ForceMode
_coForce = ForceMode
DoNotForce,
_coParallel :: Int
_coParallel = Int
0
}
data =
CategorySource {
ExtraSource -> FilePath
csSource :: FilePath,
ExtraSource -> [CategoryName]
csCategories :: [CategoryName],
ExtraSource -> [CategoryName]
csRequires :: [CategoryName]
} |
OtherSource {
ExtraSource -> FilePath
osSource :: FilePath
}
deriving (ExtraSource -> ExtraSource -> Bool
(ExtraSource -> ExtraSource -> Bool)
-> (ExtraSource -> ExtraSource -> Bool) -> Eq ExtraSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExtraSource -> ExtraSource -> Bool
== :: ExtraSource -> ExtraSource -> Bool
$c/= :: ExtraSource -> ExtraSource -> Bool
/= :: ExtraSource -> ExtraSource -> Bool
Eq,Int -> ExtraSource -> ShowS
[ExtraSource] -> ShowS
ExtraSource -> FilePath
(Int -> ExtraSource -> ShowS)
-> (ExtraSource -> FilePath)
-> ([ExtraSource] -> ShowS)
-> Show ExtraSource
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExtraSource -> ShowS
showsPrec :: Int -> ExtraSource -> ShowS
$cshow :: ExtraSource -> FilePath
show :: ExtraSource -> FilePath
$cshowList :: [ExtraSource] -> ShowS
showList :: [ExtraSource] -> ShowS
Show)
getSourceFile :: ExtraSource -> String
getSourceFile :: ExtraSource -> FilePath
getSourceFile (CategorySource FilePath
s [CategoryName]
_ [CategoryName]
_) = FilePath
s
getSourceFile (OtherSource FilePath
s) = FilePath
s
getSourceCategories :: ExtraSource -> [CategoryName]
getSourceCategories :: ExtraSource -> [CategoryName]
getSourceCategories (CategorySource FilePath
_ [CategoryName]
cs [CategoryName]
_) = [CategoryName]
cs
getSourceCategories (OtherSource FilePath
_) = []
getSourceDeps :: ExtraSource -> [CategoryName]
getSourceDeps :: ExtraSource -> [CategoryName]
getSourceDeps (CategorySource FilePath
_ [CategoryName]
_ [CategoryName]
ds) = [CategoryName]
ds
getSourceDeps (OtherSource FilePath
_) = []
data HelpMode = HelpNeeded | HelpNotNeeded | HelpUnspecified deriving (HelpMode -> HelpMode -> Bool
(HelpMode -> HelpMode -> Bool)
-> (HelpMode -> HelpMode -> Bool) -> Eq HelpMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HelpMode -> HelpMode -> Bool
== :: HelpMode -> HelpMode -> Bool
$c/= :: HelpMode -> HelpMode -> Bool
/= :: HelpMode -> HelpMode -> Bool
Eq,Int -> HelpMode -> ShowS
[HelpMode] -> ShowS
HelpMode -> FilePath
(Int -> HelpMode -> ShowS)
-> (HelpMode -> FilePath) -> ([HelpMode] -> ShowS) -> Show HelpMode
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HelpMode -> ShowS
showsPrec :: Int -> HelpMode -> ShowS
$cshow :: HelpMode -> FilePath
show :: HelpMode -> FilePath
$cshowList :: [HelpMode] -> ShowS
showList :: [HelpMode] -> ShowS
Show)
data ForceMode = DoNotForce | ForceAll deriving (ForceMode -> ForceMode -> Bool
(ForceMode -> ForceMode -> Bool)
-> (ForceMode -> ForceMode -> Bool) -> Eq ForceMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ForceMode -> ForceMode -> Bool
== :: ForceMode -> ForceMode -> Bool
$c/= :: ForceMode -> ForceMode -> Bool
/= :: ForceMode -> ForceMode -> Bool
Eq,Eq ForceMode
Eq ForceMode =>
(ForceMode -> ForceMode -> Ordering)
-> (ForceMode -> ForceMode -> Bool)
-> (ForceMode -> ForceMode -> Bool)
-> (ForceMode -> ForceMode -> Bool)
-> (ForceMode -> ForceMode -> Bool)
-> (ForceMode -> ForceMode -> ForceMode)
-> (ForceMode -> ForceMode -> ForceMode)
-> Ord ForceMode
ForceMode -> ForceMode -> Bool
ForceMode -> ForceMode -> Ordering
ForceMode -> ForceMode -> ForceMode
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ForceMode -> ForceMode -> Ordering
compare :: ForceMode -> ForceMode -> Ordering
$c< :: ForceMode -> ForceMode -> Bool
< :: ForceMode -> ForceMode -> Bool
$c<= :: ForceMode -> ForceMode -> Bool
<= :: ForceMode -> ForceMode -> Bool
$c> :: ForceMode -> ForceMode -> Bool
> :: ForceMode -> ForceMode -> Bool
$c>= :: ForceMode -> ForceMode -> Bool
>= :: ForceMode -> ForceMode -> Bool
$cmax :: ForceMode -> ForceMode -> ForceMode
max :: ForceMode -> ForceMode -> ForceMode
$cmin :: ForceMode -> ForceMode -> ForceMode
min :: ForceMode -> ForceMode -> ForceMode
Ord,Int -> ForceMode -> ShowS
[ForceMode] -> ShowS
ForceMode -> FilePath
(Int -> ForceMode -> ShowS)
-> (ForceMode -> FilePath)
-> ([ForceMode] -> ShowS)
-> Show ForceMode
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ForceMode -> ShowS
showsPrec :: Int -> ForceMode -> ShowS
$cshow :: ForceMode -> FilePath
show :: ForceMode -> FilePath
$cshowList :: [ForceMode] -> ShowS
showList :: [ForceMode] -> ShowS
Show)
data CompileMode =
CompileBinary {
CompileMode -> CategoryName
cbCategory :: CategoryName,
CompileMode -> FunctionName
cbFunction :: FunctionName,
CompileMode -> LinkerMode
cbLinker :: LinkerMode,
CompileMode -> FilePath
cbOutputName :: FilePath,
CompileMode -> [FilePath]
cbLinkFlags :: [String]
} |
CompileFast {
CompileMode -> CategoryName
cfCategory :: CategoryName,
CompileMode -> FunctionName
cfFunction :: FunctionName,
CompileMode -> FilePath
cfSource :: FilePath
} |
ExecuteTests {
CompileMode -> [FilePath]
etInclude :: [FilePath],
CompileMode -> Maybe FilePath
etCallLog :: Maybe FilePath
} |
CompileIncremental {
CompileMode -> [FilePath]
ciLinkFlags :: [String]
} |
CompileRecompile |
CompileRecompileRecursive |
CreateTemplates |
CompileUnspecified
deriving (CompileMode -> CompileMode -> Bool
(CompileMode -> CompileMode -> Bool)
-> (CompileMode -> CompileMode -> Bool) -> Eq CompileMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CompileMode -> CompileMode -> Bool
== :: CompileMode -> CompileMode -> Bool
$c/= :: CompileMode -> CompileMode -> Bool
/= :: CompileMode -> CompileMode -> Bool
Eq,Int -> CompileMode -> ShowS
[CompileMode] -> ShowS
CompileMode -> FilePath
(Int -> CompileMode -> ShowS)
-> (CompileMode -> FilePath)
-> ([CompileMode] -> ShowS)
-> Show CompileMode
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CompileMode -> ShowS
showsPrec :: Int -> CompileMode -> ShowS
$cshow :: CompileMode -> FilePath
show :: CompileMode -> FilePath
$cshowList :: [CompileMode] -> ShowS
showList :: [CompileMode] -> ShowS
Show)
data LinkerMode = LinkStatic | LinkDynamic deriving (LinkerMode -> LinkerMode -> Bool
(LinkerMode -> LinkerMode -> Bool)
-> (LinkerMode -> LinkerMode -> Bool) -> Eq LinkerMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LinkerMode -> LinkerMode -> Bool
== :: LinkerMode -> LinkerMode -> Bool
$c/= :: LinkerMode -> LinkerMode -> Bool
/= :: LinkerMode -> LinkerMode -> Bool
Eq,Int -> LinkerMode -> ShowS
[LinkerMode] -> ShowS
LinkerMode -> FilePath
(Int -> LinkerMode -> ShowS)
-> (LinkerMode -> FilePath)
-> ([LinkerMode] -> ShowS)
-> Show LinkerMode
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LinkerMode -> ShowS
showsPrec :: Int -> LinkerMode -> ShowS
$cshow :: LinkerMode -> FilePath
show :: LinkerMode -> FilePath
$cshowList :: [LinkerMode] -> ShowS
showList :: [LinkerMode] -> ShowS
Show)
isCompileBinary :: CompileMode -> Bool
isCompileBinary :: CompileMode -> Bool
isCompileBinary (CompileBinary CategoryName
_ FunctionName
_ LinkerMode
_ FilePath
_ [FilePath]
_) = Bool
True
isCompileBinary CompileMode
_ = Bool
False
isCompileFast :: CompileMode -> Bool
isCompileFast :: CompileMode -> Bool
isCompileFast (CompileFast CategoryName
_ FunctionName
_ FilePath
_) = Bool
True
isCompileFast CompileMode
_ = Bool
False
isCompileIncremental :: CompileMode -> Bool
isCompileIncremental :: CompileMode -> Bool
isCompileIncremental (CompileIncremental [FilePath]
_) = Bool
True
isCompileIncremental CompileMode
_ = Bool
False
isCompileRecompile :: CompileMode -> Bool
isCompileRecompile :: CompileMode -> Bool
isCompileRecompile CompileMode
CompileRecompile = Bool
True
isCompileRecompile CompileMode
CompileRecompileRecursive = Bool
True
isCompileRecompile CompileMode
_ = Bool
False
isExecuteTests :: CompileMode -> Bool
isExecuteTests :: CompileMode -> Bool
isExecuteTests (ExecuteTests [FilePath]
_ Maybe FilePath
_) = Bool
True
isExecuteTests CompileMode
_ = Bool
False
isCreateTemplates :: CompileMode -> Bool
isCreateTemplates :: CompileMode -> Bool
isCreateTemplates CompileMode
CreateTemplates = Bool
True
isCreateTemplates CompileMode
_ = Bool
False
isCompileUnspecified :: CompileMode -> Bool
isCompileUnspecified :: CompileMode -> Bool
isCompileUnspecified CompileMode
CompileUnspecified = Bool
True
isCompileUnspecified CompileMode
_ = Bool
False
maybeDisableHelp :: HelpMode -> HelpMode
maybeDisableHelp :: HelpMode -> HelpMode
maybeDisableHelp HelpMode
HelpUnspecified = HelpMode
HelpNotNeeded
maybeDisableHelp HelpMode
h = HelpMode
h
getLinkFlags :: CompileMode -> [String]
getLinkFlags :: CompileMode -> [FilePath]
getLinkFlags (CompileBinary CategoryName
_ FunctionName
_ LinkerMode
_ FilePath
_ [FilePath]
lf) = [FilePath]
lf
getLinkFlags (CompileIncremental [FilePath]
lf) = [FilePath]
lf
getLinkFlags CompileMode
_ = []
data CompileOptions =
CompileOptions {
CompileOptions -> HelpMode
_coHelp :: HelpMode,
CompileOptions -> [FilePath]
_coPublicDeps :: [FilePath],
CompileOptions -> [FilePath]
_coPrivateDeps :: [FilePath],
CompileOptions -> [FilePath]
_coPaths :: [FilePath],
:: [ExtraSource],
:: [FilePath],
CompileOptions -> FilePath
_coSourcePrefix :: FilePath,
CompileOptions -> CompileMode
_coMode :: CompileMode,
CompileOptions -> ForceMode
_coForce :: ForceMode,
CompileOptions -> Int
_coParallel :: Int
}
deriving (Int -> CompileOptions -> ShowS
[CompileOptions] -> ShowS
CompileOptions -> FilePath
(Int -> CompileOptions -> ShowS)
-> (CompileOptions -> FilePath)
-> ([CompileOptions] -> ShowS)
-> Show CompileOptions
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CompileOptions -> ShowS
showsPrec :: Int -> CompileOptions -> ShowS
$cshow :: CompileOptions -> FilePath
show :: CompileOptions -> FilePath
$cshowList :: [CompileOptions] -> ShowS
showList :: [CompileOptions] -> ShowS
Show)
$