{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE StrictData        #-}

{-|
Module      : Headroom.Command.Types
Description : Data types for "Headroom.Command"
Copyright   : (c) 2019-2022 Vaclav Svejcar
License     : BSD-3-Clause
Maintainer  : vaclav.svejcar@gmail.com
Stability   : experimental
Portability : POSIX

This module contains data types for "Headroom.Command" module.
-}

module Headroom.Command.Types
  ( Command(..)
  , CommandGenOptions(..)
  , CommandInitOptions(..)
  , CommandRunOptions(..)
  )
where

import           Headroom.Config.Types               ( GenMode
                                                     , LicenseType
                                                     , RunMode
                                                     )
import           Headroom.Data.Regex                 ( Regex )
import           Headroom.FileType.Types             ( FileType )
import           Headroom.Template.TemplateRef       ( TemplateRef )
import           RIO


-- | Application command.
data Command
  = Run [FilePath] [Regex] Bool (Maybe LicenseType) [TemplateRef] [Text] (Maybe RunMode) Bool Bool -- ^ @run@ command
  | Gen Bool (Maybe (LicenseType, FileType)) -- ^ @gen@ command
  | Init LicenseType [FilePath] -- ^ @init@ command
  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)


-- | Options for the @gen@ command.
newtype CommandGenOptions = CommandGenOptions
  { CommandGenOptions -> GenMode
cgoGenMode :: GenMode -- ^ selected mode
  }
  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)

-- | Options for the @init@ command.
data CommandInitOptions = CommandInitOptions
  { CommandInitOptions -> [String]
cioSourcePaths :: [FilePath]  -- ^ paths to source code files
  , CommandInitOptions -> LicenseType
cioLicenseType :: LicenseType -- ^ license type
  }
  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

-- | Options for the @run@ command.
data CommandRunOptions = CommandRunOptions
  { CommandRunOptions -> Maybe RunMode
croRunMode             :: Maybe RunMode     -- ^ used /Run/ command mode
  , CommandRunOptions -> [String]
croSourcePaths         :: [FilePath]        -- ^ source code file paths
  , CommandRunOptions -> [Regex]
croExcludedPaths       :: [Regex]           -- ^ source paths to exclude
  , CommandRunOptions -> Bool
croExcludeIgnoredPaths :: Bool              -- ^ whether to exclude ignored paths
  , CommandRunOptions -> Maybe LicenseType
croBuiltInTemplates    :: Maybe LicenseType -- ^ whether to use built-in templates
  , CommandRunOptions -> [TemplateRef]
croTemplateRefs        :: [TemplateRef]     -- ^ template references
  , CommandRunOptions -> [Text]
croVariables           :: [Text]            -- ^ raw variables
  , CommandRunOptions -> Bool
croDebug               :: Bool              -- ^ whether to run in debug mode
  , CommandRunOptions -> Bool
croDryRun              :: Bool              -- ^ whether to perform dry run
  }
  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)