module Hix.Data.Options where
import Path (Abs, Dir, File, Path, SomeBase)
import Hix.Data.BootstrapProjectConfig (BootstrapProjectConfig)
import Hix.Data.ComponentConfig (ComponentName, ModuleName, SourceDir)
import Hix.Data.EnvName (EnvName)
import Hix.Data.GhciConfig (ChangeDir, EnvConfig, GhciConfig, RunnerName)
import Hix.Data.GlobalOptions (GlobalOptions)
import Hix.Data.NewProjectConfig (NewProjectConfig)
import Hix.Data.PackageName (PackageName)
import Hix.Data.PreprocConfig (PreprocConfig)
import Hix.Managed.Cabal.Data.Config (CabalConfig)
import Hix.Managed.Data.BuildConfig (BuildConfig)
import Hix.Managed.Data.ProjectContextProto (ProjectContextProto)
import Hix.Managed.Data.Query (RawQuery)
import Hix.Managed.Data.StateFileConfig (StateFileConfig)
import Hix.Managed.Handlers.Build (SpecialBuildHandlers)
import Hix.Optparse (JsonConfig)
data PreprocOptions =
PreprocOptions {
PreprocOptions -> Maybe (Either PreprocConfig JsonConfig)
config :: Maybe (Either PreprocConfig JsonConfig),
PreprocOptions -> Maybe (Path Abs Dir)
root :: Maybe (Path Abs Dir),
PreprocOptions -> Path Abs File
source :: Path Abs File,
PreprocOptions -> Path Abs File
inFile :: Path Abs File,
PreprocOptions -> Path Abs File
outFile :: Path Abs File
}
deriving stock (Int -> PreprocOptions -> ShowS
[PreprocOptions] -> ShowS
PreprocOptions -> String
(Int -> PreprocOptions -> ShowS)
-> (PreprocOptions -> String)
-> ([PreprocOptions] -> ShowS)
-> Show PreprocOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PreprocOptions -> ShowS
showsPrec :: Int -> PreprocOptions -> ShowS
$cshow :: PreprocOptions -> String
show :: PreprocOptions -> String
$cshowList :: [PreprocOptions] -> ShowS
showList :: [PreprocOptions] -> ShowS
Show, (forall x. PreprocOptions -> Rep PreprocOptions x)
-> (forall x. Rep PreprocOptions x -> PreprocOptions)
-> Generic PreprocOptions
forall x. Rep PreprocOptions x -> PreprocOptions
forall x. PreprocOptions -> Rep PreprocOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PreprocOptions -> Rep PreprocOptions x
from :: forall x. PreprocOptions -> Rep PreprocOptions x
$cto :: forall x. Rep PreprocOptions x -> PreprocOptions
to :: forall x. Rep PreprocOptions x -> PreprocOptions
Generic)
data PackageSpec =
PackageSpec {
PackageSpec -> PackageName
name :: PackageName,
PackageSpec -> Maybe (SomeBase Dir)
dir :: Maybe (SomeBase Dir)
}
deriving stock (PackageSpec -> PackageSpec -> Bool
(PackageSpec -> PackageSpec -> Bool)
-> (PackageSpec -> PackageSpec -> Bool) -> Eq PackageSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PackageSpec -> PackageSpec -> Bool
== :: PackageSpec -> PackageSpec -> Bool
$c/= :: PackageSpec -> PackageSpec -> Bool
/= :: PackageSpec -> PackageSpec -> Bool
Eq, Int -> PackageSpec -> ShowS
[PackageSpec] -> ShowS
PackageSpec -> String
(Int -> PackageSpec -> ShowS)
-> (PackageSpec -> String)
-> ([PackageSpec] -> ShowS)
-> Show PackageSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PackageSpec -> ShowS
showsPrec :: Int -> PackageSpec -> ShowS
$cshow :: PackageSpec -> String
show :: PackageSpec -> String
$cshowList :: [PackageSpec] -> ShowS
showList :: [PackageSpec] -> ShowS
Show, (forall x. PackageSpec -> Rep PackageSpec x)
-> (forall x. Rep PackageSpec x -> PackageSpec)
-> Generic PackageSpec
forall x. Rep PackageSpec x -> PackageSpec
forall x. PackageSpec -> Rep PackageSpec x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PackageSpec -> Rep PackageSpec x
from :: forall x. PackageSpec -> Rep PackageSpec x
$cto :: forall x. Rep PackageSpec x -> PackageSpec
to :: forall x. Rep PackageSpec x -> PackageSpec
Generic)
data ComponentSpec =
ComponentSpec {
ComponentSpec -> ComponentName
name :: ComponentName,
ComponentSpec -> Maybe SourceDir
dir :: Maybe SourceDir
}
deriving stock (ComponentSpec -> ComponentSpec -> Bool
(ComponentSpec -> ComponentSpec -> Bool)
-> (ComponentSpec -> ComponentSpec -> Bool) -> Eq ComponentSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ComponentSpec -> ComponentSpec -> Bool
== :: ComponentSpec -> ComponentSpec -> Bool
$c/= :: ComponentSpec -> ComponentSpec -> Bool
/= :: ComponentSpec -> ComponentSpec -> Bool
Eq, Int -> ComponentSpec -> ShowS
[ComponentSpec] -> ShowS
ComponentSpec -> String
(Int -> ComponentSpec -> ShowS)
-> (ComponentSpec -> String)
-> ([ComponentSpec] -> ShowS)
-> Show ComponentSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ComponentSpec -> ShowS
showsPrec :: Int -> ComponentSpec -> ShowS
$cshow :: ComponentSpec -> String
show :: ComponentSpec -> String
$cshowList :: [ComponentSpec] -> ShowS
showList :: [ComponentSpec] -> ShowS
Show, (forall x. ComponentSpec -> Rep ComponentSpec x)
-> (forall x. Rep ComponentSpec x -> ComponentSpec)
-> Generic ComponentSpec
forall x. Rep ComponentSpec x -> ComponentSpec
forall x. ComponentSpec -> Rep ComponentSpec x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ComponentSpec -> Rep ComponentSpec x
from :: forall x. ComponentSpec -> Rep ComponentSpec x
$cto :: forall x. Rep ComponentSpec x -> ComponentSpec
to :: forall x. Rep ComponentSpec x -> ComponentSpec
Generic)
data ComponentCoords =
ComponentCoords {
ComponentCoords -> Maybe PackageSpec
package :: Maybe PackageSpec,
ComponentCoords -> Maybe ComponentSpec
component :: Maybe ComponentSpec
}
deriving stock (ComponentCoords -> ComponentCoords -> Bool
(ComponentCoords -> ComponentCoords -> Bool)
-> (ComponentCoords -> ComponentCoords -> Bool)
-> Eq ComponentCoords
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ComponentCoords -> ComponentCoords -> Bool
== :: ComponentCoords -> ComponentCoords -> Bool
$c/= :: ComponentCoords -> ComponentCoords -> Bool
/= :: ComponentCoords -> ComponentCoords -> Bool
Eq, Int -> ComponentCoords -> ShowS
[ComponentCoords] -> ShowS
ComponentCoords -> String
(Int -> ComponentCoords -> ShowS)
-> (ComponentCoords -> String)
-> ([ComponentCoords] -> ShowS)
-> Show ComponentCoords
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ComponentCoords -> ShowS
showsPrec :: Int -> ComponentCoords -> ShowS
$cshow :: ComponentCoords -> String
show :: ComponentCoords -> String
$cshowList :: [ComponentCoords] -> ShowS
showList :: [ComponentCoords] -> ShowS
Show, (forall x. ComponentCoords -> Rep ComponentCoords x)
-> (forall x. Rep ComponentCoords x -> ComponentCoords)
-> Generic ComponentCoords
forall x. Rep ComponentCoords x -> ComponentCoords
forall x. ComponentCoords -> Rep ComponentCoords x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ComponentCoords -> Rep ComponentCoords x
from :: forall x. ComponentCoords -> Rep ComponentCoords x
$cto :: forall x. Rep ComponentCoords x -> ComponentCoords
to :: forall x. Rep ComponentCoords x -> ComponentCoords
Generic)
data TargetSpec =
TargetForFile (Path Abs File)
|
TargetForComponent ComponentCoords
deriving stock (TargetSpec -> TargetSpec -> Bool
(TargetSpec -> TargetSpec -> Bool)
-> (TargetSpec -> TargetSpec -> Bool) -> Eq TargetSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TargetSpec -> TargetSpec -> Bool
== :: TargetSpec -> TargetSpec -> Bool
$c/= :: TargetSpec -> TargetSpec -> Bool
/= :: TargetSpec -> TargetSpec -> Bool
Eq, Int -> TargetSpec -> ShowS
[TargetSpec] -> ShowS
TargetSpec -> String
(Int -> TargetSpec -> ShowS)
-> (TargetSpec -> String)
-> ([TargetSpec] -> ShowS)
-> Show TargetSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TargetSpec -> ShowS
showsPrec :: Int -> TargetSpec -> ShowS
$cshow :: TargetSpec -> String
show :: TargetSpec -> String
$cshowList :: [TargetSpec] -> ShowS
showList :: [TargetSpec] -> ShowS
Show, (forall x. TargetSpec -> Rep TargetSpec x)
-> (forall x. Rep TargetSpec x -> TargetSpec) -> Generic TargetSpec
forall x. Rep TargetSpec x -> TargetSpec
forall x. TargetSpec -> Rep TargetSpec x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TargetSpec -> Rep TargetSpec x
from :: forall x. TargetSpec -> Rep TargetSpec x
$cto :: forall x. Rep TargetSpec x -> TargetSpec
to :: forall x. Rep TargetSpec x -> TargetSpec
Generic)
data TestOptions =
TestOptions {
TestOptions -> ModuleName
mod :: ModuleName,
TestOptions -> Maybe Text
test :: Maybe Text,
TestOptions -> Maybe RunnerName
runner :: Maybe RunnerName,
TestOptions -> ChangeDir
cd :: ChangeDir
}
deriving stock (TestOptions -> TestOptions -> Bool
(TestOptions -> TestOptions -> Bool)
-> (TestOptions -> TestOptions -> Bool) -> Eq TestOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TestOptions -> TestOptions -> Bool
== :: TestOptions -> TestOptions -> Bool
$c/= :: TestOptions -> TestOptions -> Bool
/= :: TestOptions -> TestOptions -> Bool
Eq, Int -> TestOptions -> ShowS
[TestOptions] -> ShowS
TestOptions -> String
(Int -> TestOptions -> ShowS)
-> (TestOptions -> String)
-> ([TestOptions] -> ShowS)
-> Show TestOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TestOptions -> ShowS
showsPrec :: Int -> TestOptions -> ShowS
$cshow :: TestOptions -> String
show :: TestOptions -> String
$cshowList :: [TestOptions] -> ShowS
showList :: [TestOptions] -> ShowS
Show, (forall x. TestOptions -> Rep TestOptions x)
-> (forall x. Rep TestOptions x -> TestOptions)
-> Generic TestOptions
forall x. Rep TestOptions x -> TestOptions
forall x. TestOptions -> Rep TestOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TestOptions -> Rep TestOptions x
from :: forall x. TestOptions -> Rep TestOptions x
$cto :: forall x. Rep TestOptions x -> TestOptions
to :: forall x. Rep TestOptions x -> TestOptions
Generic)
data EnvRunnerOptions =
EnvRunnerOptions {
EnvRunnerOptions -> Either EnvConfig JsonConfig
config :: Either EnvConfig JsonConfig,
EnvRunnerOptions -> Maybe (Path Abs Dir)
root :: Maybe (Path Abs Dir),
EnvRunnerOptions -> Maybe TargetSpec
component :: Maybe TargetSpec
}
deriving stock (Int -> EnvRunnerOptions -> ShowS
[EnvRunnerOptions] -> ShowS
EnvRunnerOptions -> String
(Int -> EnvRunnerOptions -> ShowS)
-> (EnvRunnerOptions -> String)
-> ([EnvRunnerOptions] -> ShowS)
-> Show EnvRunnerOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EnvRunnerOptions -> ShowS
showsPrec :: Int -> EnvRunnerOptions -> ShowS
$cshow :: EnvRunnerOptions -> String
show :: EnvRunnerOptions -> String
$cshowList :: [EnvRunnerOptions] -> ShowS
showList :: [EnvRunnerOptions] -> ShowS
Show, (forall x. EnvRunnerOptions -> Rep EnvRunnerOptions x)
-> (forall x. Rep EnvRunnerOptions x -> EnvRunnerOptions)
-> Generic EnvRunnerOptions
forall x. Rep EnvRunnerOptions x -> EnvRunnerOptions
forall x. EnvRunnerOptions -> Rep EnvRunnerOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EnvRunnerOptions -> Rep EnvRunnerOptions x
from :: forall x. EnvRunnerOptions -> Rep EnvRunnerOptions x
$cto :: forall x. Rep EnvRunnerOptions x -> EnvRunnerOptions
to :: forall x. Rep EnvRunnerOptions x -> EnvRunnerOptions
Generic)
newtype =
Text
deriving stock (ExtraGhciOptions -> ExtraGhciOptions -> Bool
(ExtraGhciOptions -> ExtraGhciOptions -> Bool)
-> (ExtraGhciOptions -> ExtraGhciOptions -> Bool)
-> Eq ExtraGhciOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExtraGhciOptions -> ExtraGhciOptions -> Bool
== :: ExtraGhciOptions -> ExtraGhciOptions -> Bool
$c/= :: ExtraGhciOptions -> ExtraGhciOptions -> Bool
/= :: ExtraGhciOptions -> ExtraGhciOptions -> Bool
Eq, Int -> ExtraGhciOptions -> ShowS
[ExtraGhciOptions] -> ShowS
ExtraGhciOptions -> String
(Int -> ExtraGhciOptions -> ShowS)
-> (ExtraGhciOptions -> String)
-> ([ExtraGhciOptions] -> ShowS)
-> Show ExtraGhciOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExtraGhciOptions -> ShowS
showsPrec :: Int -> ExtraGhciOptions -> ShowS
$cshow :: ExtraGhciOptions -> String
show :: ExtraGhciOptions -> String
$cshowList :: [ExtraGhciOptions] -> ShowS
showList :: [ExtraGhciOptions] -> ShowS
Show, (forall x. ExtraGhciOptions -> Rep ExtraGhciOptions x)
-> (forall x. Rep ExtraGhciOptions x -> ExtraGhciOptions)
-> Generic ExtraGhciOptions
forall x. Rep ExtraGhciOptions x -> ExtraGhciOptions
forall x. ExtraGhciOptions -> Rep ExtraGhciOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExtraGhciOptions -> Rep ExtraGhciOptions x
from :: forall x. ExtraGhciOptions -> Rep ExtraGhciOptions x
$cto :: forall x. Rep ExtraGhciOptions x -> ExtraGhciOptions
to :: forall x. Rep ExtraGhciOptions x -> ExtraGhciOptions
Generic)
deriving newtype (String -> ExtraGhciOptions
(String -> ExtraGhciOptions) -> IsString ExtraGhciOptions
forall a. (String -> a) -> IsString a
$cfromString :: String -> ExtraGhciOptions
fromString :: String -> ExtraGhciOptions
IsString)
newtype =
Text
deriving stock (ExtraGhcidOptions -> ExtraGhcidOptions -> Bool
(ExtraGhcidOptions -> ExtraGhcidOptions -> Bool)
-> (ExtraGhcidOptions -> ExtraGhcidOptions -> Bool)
-> Eq ExtraGhcidOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExtraGhcidOptions -> ExtraGhcidOptions -> Bool
== :: ExtraGhcidOptions -> ExtraGhcidOptions -> Bool
$c/= :: ExtraGhcidOptions -> ExtraGhcidOptions -> Bool
/= :: ExtraGhcidOptions -> ExtraGhcidOptions -> Bool
Eq, Int -> ExtraGhcidOptions -> ShowS
[ExtraGhcidOptions] -> ShowS
ExtraGhcidOptions -> String
(Int -> ExtraGhcidOptions -> ShowS)
-> (ExtraGhcidOptions -> String)
-> ([ExtraGhcidOptions] -> ShowS)
-> Show ExtraGhcidOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExtraGhcidOptions -> ShowS
showsPrec :: Int -> ExtraGhcidOptions -> ShowS
$cshow :: ExtraGhcidOptions -> String
show :: ExtraGhcidOptions -> String
$cshowList :: [ExtraGhcidOptions] -> ShowS
showList :: [ExtraGhcidOptions] -> ShowS
Show, (forall x. ExtraGhcidOptions -> Rep ExtraGhcidOptions x)
-> (forall x. Rep ExtraGhcidOptions x -> ExtraGhcidOptions)
-> Generic ExtraGhcidOptions
forall x. Rep ExtraGhcidOptions x -> ExtraGhcidOptions
forall x. ExtraGhcidOptions -> Rep ExtraGhcidOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExtraGhcidOptions -> Rep ExtraGhcidOptions x
from :: forall x. ExtraGhcidOptions -> Rep ExtraGhcidOptions x
$cto :: forall x. Rep ExtraGhcidOptions x -> ExtraGhcidOptions
to :: forall x. Rep ExtraGhcidOptions x -> ExtraGhcidOptions
Generic)
deriving newtype (String -> ExtraGhcidOptions
(String -> ExtraGhcidOptions) -> IsString ExtraGhcidOptions
forall a. (String -> a) -> IsString a
$cfromString :: String -> ExtraGhcidOptions
fromString :: String -> ExtraGhcidOptions
IsString)
data GhciOptions =
GhciOptions {
GhciOptions -> Either GhciConfig JsonConfig
config :: Either GhciConfig JsonConfig,
GhciOptions -> Maybe (Path Abs Dir)
root :: Maybe (Path Abs Dir),
GhciOptions -> TargetSpec
component :: TargetSpec,
GhciOptions -> TestOptions
test :: TestOptions,
:: Maybe ExtraGhciOptions
}
deriving stock (Int -> GhciOptions -> ShowS
[GhciOptions] -> ShowS
GhciOptions -> String
(Int -> GhciOptions -> ShowS)
-> (GhciOptions -> String)
-> ([GhciOptions] -> ShowS)
-> Show GhciOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GhciOptions -> ShowS
showsPrec :: Int -> GhciOptions -> ShowS
$cshow :: GhciOptions -> String
show :: GhciOptions -> String
$cshowList :: [GhciOptions] -> ShowS
showList :: [GhciOptions] -> ShowS
Show, (forall x. GhciOptions -> Rep GhciOptions x)
-> (forall x. Rep GhciOptions x -> GhciOptions)
-> Generic GhciOptions
forall x. Rep GhciOptions x -> GhciOptions
forall x. GhciOptions -> Rep GhciOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GhciOptions -> Rep GhciOptions x
from :: forall x. GhciOptions -> Rep GhciOptions x
$cto :: forall x. Rep GhciOptions x -> GhciOptions
to :: forall x. Rep GhciOptions x -> GhciOptions
Generic)
data GhcidOptions =
GhcidOptions {
GhcidOptions -> GhciOptions
ghci :: GhciOptions,
:: Maybe ExtraGhcidOptions
}
deriving stock (Int -> GhcidOptions -> ShowS
[GhcidOptions] -> ShowS
GhcidOptions -> String
(Int -> GhcidOptions -> ShowS)
-> (GhcidOptions -> String)
-> ([GhcidOptions] -> ShowS)
-> Show GhcidOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GhcidOptions -> ShowS
showsPrec :: Int -> GhcidOptions -> ShowS
$cshow :: GhcidOptions -> String
show :: GhcidOptions -> String
$cshowList :: [GhcidOptions] -> ShowS
showList :: [GhcidOptions] -> ShowS
Show, (forall x. GhcidOptions -> Rep GhcidOptions x)
-> (forall x. Rep GhcidOptions x -> GhcidOptions)
-> Generic GhcidOptions
forall x. Rep GhcidOptions x -> GhcidOptions
forall x. GhcidOptions -> Rep GhcidOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GhcidOptions -> Rep GhcidOptions x
from :: forall x. GhcidOptions -> Rep GhcidOptions x
$cto :: forall x. Rep GhcidOptions x -> GhcidOptions
to :: forall x. Rep GhcidOptions x -> GhcidOptions
Generic)
data NewOptions =
NewOptions {
NewOptions -> NewProjectConfig
config :: NewProjectConfig
}
deriving stock (NewOptions -> NewOptions -> Bool
(NewOptions -> NewOptions -> Bool)
-> (NewOptions -> NewOptions -> Bool) -> Eq NewOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NewOptions -> NewOptions -> Bool
== :: NewOptions -> NewOptions -> Bool
$c/= :: NewOptions -> NewOptions -> Bool
/= :: NewOptions -> NewOptions -> Bool
Eq, Int -> NewOptions -> ShowS
[NewOptions] -> ShowS
NewOptions -> String
(Int -> NewOptions -> ShowS)
-> (NewOptions -> String)
-> ([NewOptions] -> ShowS)
-> Show NewOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NewOptions -> ShowS
showsPrec :: Int -> NewOptions -> ShowS
$cshow :: NewOptions -> String
show :: NewOptions -> String
$cshowList :: [NewOptions] -> ShowS
showList :: [NewOptions] -> ShowS
Show, (forall x. NewOptions -> Rep NewOptions x)
-> (forall x. Rep NewOptions x -> NewOptions) -> Generic NewOptions
forall x. Rep NewOptions x -> NewOptions
forall x. NewOptions -> Rep NewOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. NewOptions -> Rep NewOptions x
from :: forall x. NewOptions -> Rep NewOptions x
$cto :: forall x. Rep NewOptions x -> NewOptions
to :: forall x. Rep NewOptions x -> NewOptions
Generic)
data BootstrapOptions =
BootstrapOptions {
BootstrapOptions -> BootstrapProjectConfig
config :: BootstrapProjectConfig
}
deriving stock (BootstrapOptions -> BootstrapOptions -> Bool
(BootstrapOptions -> BootstrapOptions -> Bool)
-> (BootstrapOptions -> BootstrapOptions -> Bool)
-> Eq BootstrapOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BootstrapOptions -> BootstrapOptions -> Bool
== :: BootstrapOptions -> BootstrapOptions -> Bool
$c/= :: BootstrapOptions -> BootstrapOptions -> Bool
/= :: BootstrapOptions -> BootstrapOptions -> Bool
Eq, Int -> BootstrapOptions -> ShowS
[BootstrapOptions] -> ShowS
BootstrapOptions -> String
(Int -> BootstrapOptions -> ShowS)
-> (BootstrapOptions -> String)
-> ([BootstrapOptions] -> ShowS)
-> Show BootstrapOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BootstrapOptions -> ShowS
showsPrec :: Int -> BootstrapOptions -> ShowS
$cshow :: BootstrapOptions -> String
show :: BootstrapOptions -> String
$cshowList :: [BootstrapOptions] -> ShowS
showList :: [BootstrapOptions] -> ShowS
Show, (forall x. BootstrapOptions -> Rep BootstrapOptions x)
-> (forall x. Rep BootstrapOptions x -> BootstrapOptions)
-> Generic BootstrapOptions
forall x. Rep BootstrapOptions x -> BootstrapOptions
forall x. BootstrapOptions -> Rep BootstrapOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BootstrapOptions -> Rep BootstrapOptions x
from :: forall x. BootstrapOptions -> Rep BootstrapOptions x
$cto :: forall x. Rep BootstrapOptions x -> BootstrapOptions
to :: forall x. Rep BootstrapOptions x -> BootstrapOptions
Generic)
data EnvRunnerCommandOptions =
EnvRunnerCommandOptions {
EnvRunnerCommandOptions -> EnvRunnerOptions
options :: EnvRunnerOptions,
EnvRunnerCommandOptions -> TestOptions
test :: TestOptions,
:: Maybe ExtraGhciOptions,
:: Maybe ExtraGhcidOptions
}
deriving stock (Int -> EnvRunnerCommandOptions -> ShowS
[EnvRunnerCommandOptions] -> ShowS
EnvRunnerCommandOptions -> String
(Int -> EnvRunnerCommandOptions -> ShowS)
-> (EnvRunnerCommandOptions -> String)
-> ([EnvRunnerCommandOptions] -> ShowS)
-> Show EnvRunnerCommandOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EnvRunnerCommandOptions -> ShowS
showsPrec :: Int -> EnvRunnerCommandOptions -> ShowS
$cshow :: EnvRunnerCommandOptions -> String
show :: EnvRunnerCommandOptions -> String
$cshowList :: [EnvRunnerCommandOptions] -> ShowS
showList :: [EnvRunnerCommandOptions] -> ShowS
Show, (forall x.
EnvRunnerCommandOptions -> Rep EnvRunnerCommandOptions x)
-> (forall x.
Rep EnvRunnerCommandOptions x -> EnvRunnerCommandOptions)
-> Generic EnvRunnerCommandOptions
forall x. Rep EnvRunnerCommandOptions x -> EnvRunnerCommandOptions
forall x. EnvRunnerCommandOptions -> Rep EnvRunnerCommandOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EnvRunnerCommandOptions -> Rep EnvRunnerCommandOptions x
from :: forall x. EnvRunnerCommandOptions -> Rep EnvRunnerCommandOptions x
$cto :: forall x. Rep EnvRunnerCommandOptions x -> EnvRunnerCommandOptions
to :: forall x. Rep EnvRunnerCommandOptions x -> EnvRunnerCommandOptions
Generic)
data ProjectOptions =
ProjectOptions {
ProjectOptions -> BuildConfig
build :: BuildConfig,
ProjectOptions -> [EnvName]
envs :: [EnvName],
ProjectOptions -> RawQuery
query :: RawQuery,
ProjectOptions -> Bool
readUpperBounds :: Bool,
ProjectOptions -> Bool
mergeBounds :: Bool
}
deriving stock (ProjectOptions -> ProjectOptions -> Bool
(ProjectOptions -> ProjectOptions -> Bool)
-> (ProjectOptions -> ProjectOptions -> Bool) -> Eq ProjectOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProjectOptions -> ProjectOptions -> Bool
== :: ProjectOptions -> ProjectOptions -> Bool
$c/= :: ProjectOptions -> ProjectOptions -> Bool
/= :: ProjectOptions -> ProjectOptions -> Bool
Eq, Int -> ProjectOptions -> ShowS
[ProjectOptions] -> ShowS
ProjectOptions -> String
(Int -> ProjectOptions -> ShowS)
-> (ProjectOptions -> String)
-> ([ProjectOptions] -> ShowS)
-> Show ProjectOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProjectOptions -> ShowS
showsPrec :: Int -> ProjectOptions -> ShowS
$cshow :: ProjectOptions -> String
show :: ProjectOptions -> String
$cshowList :: [ProjectOptions] -> ShowS
showList :: [ProjectOptions] -> ShowS
Show, (forall x. ProjectOptions -> Rep ProjectOptions x)
-> (forall x. Rep ProjectOptions x -> ProjectOptions)
-> Generic ProjectOptions
forall x. Rep ProjectOptions x -> ProjectOptions
forall x. ProjectOptions -> Rep ProjectOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProjectOptions -> Rep ProjectOptions x
from :: forall x. ProjectOptions -> Rep ProjectOptions x
$cto :: forall x. Rep ProjectOptions x -> ProjectOptions
to :: forall x. Rep ProjectOptions x -> ProjectOptions
Generic)
instance Default ProjectOptions where
def :: ProjectOptions
def = ProjectOptions {
build :: BuildConfig
build = BuildConfig
forall a. Default a => a
def,
envs :: [EnvName]
envs = [],
query :: RawQuery
query = [],
readUpperBounds :: Bool
readUpperBounds = Bool
False,
mergeBounds :: Bool
mergeBounds = Bool
False
}
projectOptions :: [EnvName] -> ProjectOptions
projectOptions :: [EnvName] -> ProjectOptions
projectOptions [EnvName]
envs = ProjectOptions
forall a. Default a => a
def {envs}
data ManagedOptions =
ManagedOptions {
ManagedOptions -> Either ProjectContextProto JsonConfig
context :: Either ProjectContextProto JsonConfig,
ManagedOptions -> ProjectOptions
project :: ProjectOptions,
ManagedOptions -> StateFileConfig
stateFile :: StateFileConfig,
ManagedOptions -> CabalConfig
cabal :: CabalConfig,
ManagedOptions -> Maybe SpecialBuildHandlers
handlers :: Maybe SpecialBuildHandlers
}
deriving stock (Int -> ManagedOptions -> ShowS
[ManagedOptions] -> ShowS
ManagedOptions -> String
(Int -> ManagedOptions -> ShowS)
-> (ManagedOptions -> String)
-> ([ManagedOptions] -> ShowS)
-> Show ManagedOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ManagedOptions -> ShowS
showsPrec :: Int -> ManagedOptions -> ShowS
$cshow :: ManagedOptions -> String
show :: ManagedOptions -> String
$cshowList :: [ManagedOptions] -> ShowS
showList :: [ManagedOptions] -> ShowS
Show, (forall x. ManagedOptions -> Rep ManagedOptions x)
-> (forall x. Rep ManagedOptions x -> ManagedOptions)
-> Generic ManagedOptions
forall x. Rep ManagedOptions x -> ManagedOptions
forall x. ManagedOptions -> Rep ManagedOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ManagedOptions -> Rep ManagedOptions x
from :: forall x. ManagedOptions -> Rep ManagedOptions x
$cto :: forall x. Rep ManagedOptions x -> ManagedOptions
to :: forall x. Rep ManagedOptions x -> ManagedOptions
Generic)
data BumpOptions =
BumpOptions {
BumpOptions -> ManagedOptions
common :: ManagedOptions
}
deriving stock (Int -> BumpOptions -> ShowS
[BumpOptions] -> ShowS
BumpOptions -> String
(Int -> BumpOptions -> ShowS)
-> (BumpOptions -> String)
-> ([BumpOptions] -> ShowS)
-> Show BumpOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BumpOptions -> ShowS
showsPrec :: Int -> BumpOptions -> ShowS
$cshow :: BumpOptions -> String
show :: BumpOptions -> String
$cshowList :: [BumpOptions] -> ShowS
showList :: [BumpOptions] -> ShowS
Show, (forall x. BumpOptions -> Rep BumpOptions x)
-> (forall x. Rep BumpOptions x -> BumpOptions)
-> Generic BumpOptions
forall x. Rep BumpOptions x -> BumpOptions
forall x. BumpOptions -> Rep BumpOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BumpOptions -> Rep BumpOptions x
from :: forall x. BumpOptions -> Rep BumpOptions x
$cto :: forall x. Rep BumpOptions x -> BumpOptions
to :: forall x. Rep BumpOptions x -> BumpOptions
Generic)
data LowerOptions =
LowerOptions {
LowerOptions -> ManagedOptions
common :: ManagedOptions,
LowerOptions -> Bool
initOnly :: Bool,
LowerOptions -> Bool
reset :: Bool,
LowerOptions -> Bool
stabilize :: Bool
}
deriving stock (Int -> LowerOptions -> ShowS
[LowerOptions] -> ShowS
LowerOptions -> String
(Int -> LowerOptions -> ShowS)
-> (LowerOptions -> String)
-> ([LowerOptions] -> ShowS)
-> Show LowerOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LowerOptions -> ShowS
showsPrec :: Int -> LowerOptions -> ShowS
$cshow :: LowerOptions -> String
show :: LowerOptions -> String
$cshowList :: [LowerOptions] -> ShowS
showList :: [LowerOptions] -> ShowS
Show)
data LowerCommand =
LowerInitCmd LowerOptions
|
LowerOptimizeCmd LowerOptions
|
LowerStabilizeCmd LowerOptions
|
LowerAutoCmd LowerOptions
deriving stock (Int -> LowerCommand -> ShowS
[LowerCommand] -> ShowS
LowerCommand -> String
(Int -> LowerCommand -> ShowS)
-> (LowerCommand -> String)
-> ([LowerCommand] -> ShowS)
-> Show LowerCommand
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LowerCommand -> ShowS
showsPrec :: Int -> LowerCommand -> ShowS
$cshow :: LowerCommand -> String
show :: LowerCommand -> String
$cshowList :: [LowerCommand] -> ShowS
showList :: [LowerCommand] -> ShowS
Show)
data Command =
Preproc PreprocOptions
|
EnvRunner EnvRunnerCommandOptions
|
GhcidCmd GhcidOptions
|
GhciCmd GhciOptions
|
NewCmd NewOptions
|
BootstrapCmd BootstrapOptions
|
BumpCmd BumpOptions
|
LowerCmd LowerCommand
deriving stock (Int -> Command -> ShowS
[Command] -> ShowS
Command -> String
(Int -> Command -> ShowS)
-> (Command -> String) -> ([Command] -> ShowS) -> Show Command
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Command -> ShowS
showsPrec :: Int -> Command -> ShowS
$cshow :: Command -> String
show :: Command -> String
$cshowList :: [Command] -> ShowS
showList :: [Command] -> ShowS
Show)
data Options =
Options {
Options -> GlobalOptions
global :: GlobalOptions,
Options -> Command
cmd :: Command
}
deriving stock (Int -> Options -> ShowS
[Options] -> ShowS
Options -> String
(Int -> Options -> ShowS)
-> (Options -> String) -> ([Options] -> ShowS) -> Show Options
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Options -> ShowS
showsPrec :: Int -> Options -> ShowS
$cshow :: Options -> String
show :: Options -> String
$cshowList :: [Options] -> ShowS
showList :: [Options] -> ShowS
Show)