{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE StrictData #-}
module Headroom.Command.Types
( Command(..)
, CommandGenOptions(..)
, CommandInitOptions(..)
, CommandRunOptions(..)
)
where
import Headroom.Configuration.Types ( GenMode
, LicenseType
, RunMode
, TemplateSource
)
import Headroom.Data.Regex ( Regex )
import Headroom.FileType.Types ( FileType )
import RIO
data Command
= Run [FilePath] [Regex] (Maybe TemplateSource) [Text] (Maybe RunMode) Bool Bool
| Gen Bool (Maybe (LicenseType, FileType))
| Init LicenseType [FilePath]
deriving (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
showList :: [Command] -> ShowS
$cshowList :: [Command] -> ShowS
show :: Command -> String
$cshow :: Command -> String
showsPrec :: Int -> Command -> ShowS
$cshowsPrec :: Int -> Command -> ShowS
Show)
newtype CommandGenOptions = CommandGenOptions
{ CommandGenOptions -> GenMode
cgoGenMode :: GenMode
}
deriving (Int -> CommandGenOptions -> ShowS
[CommandGenOptions] -> ShowS
CommandGenOptions -> String
(Int -> CommandGenOptions -> ShowS)
-> (CommandGenOptions -> String)
-> ([CommandGenOptions] -> ShowS)
-> Show CommandGenOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandGenOptions] -> ShowS
$cshowList :: [CommandGenOptions] -> ShowS
show :: CommandGenOptions -> String
$cshow :: CommandGenOptions -> String
showsPrec :: Int -> CommandGenOptions -> ShowS
$cshowsPrec :: Int -> CommandGenOptions -> ShowS
Show)
data CommandInitOptions = CommandInitOptions
{ CommandInitOptions -> [String]
cioSourcePaths :: [FilePath]
, CommandInitOptions -> LicenseType
cioLicenseType :: LicenseType
}
deriving Int -> CommandInitOptions -> ShowS
[CommandInitOptions] -> ShowS
CommandInitOptions -> String
(Int -> CommandInitOptions -> ShowS)
-> (CommandInitOptions -> String)
-> ([CommandInitOptions] -> ShowS)
-> Show CommandInitOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandInitOptions] -> ShowS
$cshowList :: [CommandInitOptions] -> ShowS
show :: CommandInitOptions -> String
$cshow :: CommandInitOptions -> String
showsPrec :: Int -> CommandInitOptions -> ShowS
$cshowsPrec :: Int -> CommandInitOptions -> ShowS
Show
data CommandRunOptions = CommandRunOptions
{ CommandRunOptions -> Maybe RunMode
croRunMode :: Maybe RunMode
, CommandRunOptions -> [String]
croSourcePaths :: [FilePath]
, CommandRunOptions -> [Regex]
croExcludedPaths :: [Regex]
, CommandRunOptions -> Maybe TemplateSource
croTemplateSource :: Maybe TemplateSource
, CommandRunOptions -> [Text]
croVariables :: [Text]
, CommandRunOptions -> Bool
croDebug :: Bool
, CommandRunOptions -> Bool
croDryRun :: Bool
}
deriving (CommandRunOptions -> CommandRunOptions -> Bool
(CommandRunOptions -> CommandRunOptions -> Bool)
-> (CommandRunOptions -> CommandRunOptions -> Bool)
-> Eq CommandRunOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandRunOptions -> CommandRunOptions -> Bool
$c/= :: CommandRunOptions -> CommandRunOptions -> Bool
== :: CommandRunOptions -> CommandRunOptions -> Bool
$c== :: CommandRunOptions -> CommandRunOptions -> Bool
Eq, Int -> CommandRunOptions -> ShowS
[CommandRunOptions] -> ShowS
CommandRunOptions -> String
(Int -> CommandRunOptions -> ShowS)
-> (CommandRunOptions -> String)
-> ([CommandRunOptions] -> ShowS)
-> Show CommandRunOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandRunOptions] -> ShowS
$cshowList :: [CommandRunOptions] -> ShowS
show :: CommandRunOptions -> String
$cshow :: CommandRunOptions -> String
showsPrec :: Int -> CommandRunOptions -> ShowS
$cshowsPrec :: Int -> CommandRunOptions -> ShowS
Show)