{-# LANGUAGE LambdaCase, OverloadedStrings #-}
module System.Console.Hawk.Args.Spec where
import Data.ByteString (ByteString)
data HawkSpec
= Help
| Version
| Eval ExprSpec OutputSpec
| Apply ExprSpec InputSpec OutputSpec
| Map ExprSpec InputSpec OutputSpec
deriving (Int -> HawkSpec -> ShowS
[HawkSpec] -> ShowS
HawkSpec -> String
(Int -> HawkSpec -> ShowS)
-> (HawkSpec -> String) -> ([HawkSpec] -> ShowS) -> Show HawkSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HawkSpec] -> ShowS
$cshowList :: [HawkSpec] -> ShowS
show :: HawkSpec -> String
$cshow :: HawkSpec -> String
showsPrec :: Int -> HawkSpec -> ShowS
$cshowsPrec :: Int -> HawkSpec -> ShowS
Show, HawkSpec -> HawkSpec -> Bool
(HawkSpec -> HawkSpec -> Bool)
-> (HawkSpec -> HawkSpec -> Bool) -> Eq HawkSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HawkSpec -> HawkSpec -> Bool
$c/= :: HawkSpec -> HawkSpec -> Bool
== :: HawkSpec -> HawkSpec -> Bool
$c== :: HawkSpec -> HawkSpec -> Bool
Eq)
data InputSpec = InputSpec
{ InputSpec -> InputSource
inputSource :: InputSource
, InputSpec -> InputFormat
inputFormat :: InputFormat
}
deriving (Int -> InputSpec -> ShowS
[InputSpec] -> ShowS
InputSpec -> String
(Int -> InputSpec -> ShowS)
-> (InputSpec -> String)
-> ([InputSpec] -> ShowS)
-> Show InputSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputSpec] -> ShowS
$cshowList :: [InputSpec] -> ShowS
show :: InputSpec -> String
$cshow :: InputSpec -> String
showsPrec :: Int -> InputSpec -> ShowS
$cshowsPrec :: Int -> InputSpec -> ShowS
Show, InputSpec -> InputSpec -> Bool
(InputSpec -> InputSpec -> Bool)
-> (InputSpec -> InputSpec -> Bool) -> Eq InputSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputSpec -> InputSpec -> Bool
$c/= :: InputSpec -> InputSpec -> Bool
== :: InputSpec -> InputSpec -> Bool
$c== :: InputSpec -> InputSpec -> Bool
Eq)
data OutputSpec = OutputSpec
{ OutputSpec -> OutputSink
outputSink :: OutputSink
, OutputSpec -> OutputFormat
outputFormat :: OutputFormat
}
deriving (Int -> OutputSpec -> ShowS
[OutputSpec] -> ShowS
OutputSpec -> String
(Int -> OutputSpec -> ShowS)
-> (OutputSpec -> String)
-> ([OutputSpec] -> ShowS)
-> Show OutputSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OutputSpec] -> ShowS
$cshowList :: [OutputSpec] -> ShowS
show :: OutputSpec -> String
$cshow :: OutputSpec -> String
showsPrec :: Int -> OutputSpec -> ShowS
$cshowsPrec :: Int -> OutputSpec -> ShowS
Show, OutputSpec -> OutputSpec -> Bool
(OutputSpec -> OutputSpec -> Bool)
-> (OutputSpec -> OutputSpec -> Bool) -> Eq OutputSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OutputSpec -> OutputSpec -> Bool
$c/= :: OutputSpec -> OutputSpec -> Bool
== :: OutputSpec -> OutputSpec -> Bool
$c== :: OutputSpec -> OutputSpec -> Bool
Eq)
data InputSource
= NoInput
| UseStdin
| InputFile FilePath
deriving (Int -> InputSource -> ShowS
[InputSource] -> ShowS
InputSource -> String
(Int -> InputSource -> ShowS)
-> (InputSource -> String)
-> ([InputSource] -> ShowS)
-> Show InputSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputSource] -> ShowS
$cshowList :: [InputSource] -> ShowS
show :: InputSource -> String
$cshow :: InputSource -> String
showsPrec :: Int -> InputSource -> ShowS
$cshowsPrec :: Int -> InputSource -> ShowS
Show, InputSource -> InputSource -> Bool
(InputSource -> InputSource -> Bool)
-> (InputSource -> InputSource -> Bool) -> Eq InputSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputSource -> InputSource -> Bool
$c/= :: InputSource -> InputSource -> Bool
== :: InputSource -> InputSource -> Bool
$c== :: InputSource -> InputSource -> Bool
Eq)
data OutputSink
= UseStdout
deriving (Int -> OutputSink -> ShowS
[OutputSink] -> ShowS
OutputSink -> String
(Int -> OutputSink -> ShowS)
-> (OutputSink -> String)
-> ([OutputSink] -> ShowS)
-> Show OutputSink
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OutputSink] -> ShowS
$cshowList :: [OutputSink] -> ShowS
show :: OutputSink -> String
$cshow :: OutputSink -> String
showsPrec :: Int -> OutputSink -> ShowS
$cshowsPrec :: Int -> OutputSink -> ShowS
Show, OutputSink -> OutputSink -> Bool
(OutputSink -> OutputSink -> Bool)
-> (OutputSink -> OutputSink -> Bool) -> Eq OutputSink
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OutputSink -> OutputSink -> Bool
$c/= :: OutputSink -> OutputSink -> Bool
== :: OutputSink -> OutputSink -> Bool
$c== :: OutputSink -> OutputSink -> Bool
Eq)
data InputFormat
= RawStream
| Records Separator RecordFormat
deriving (Int -> InputFormat -> ShowS
[InputFormat] -> ShowS
InputFormat -> String
(Int -> InputFormat -> ShowS)
-> (InputFormat -> String)
-> ([InputFormat] -> ShowS)
-> Show InputFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputFormat] -> ShowS
$cshowList :: [InputFormat] -> ShowS
show :: InputFormat -> String
$cshow :: InputFormat -> String
showsPrec :: Int -> InputFormat -> ShowS
$cshowsPrec :: Int -> InputFormat -> ShowS
Show, InputFormat -> InputFormat -> Bool
(InputFormat -> InputFormat -> Bool)
-> (InputFormat -> InputFormat -> Bool) -> Eq InputFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputFormat -> InputFormat -> Bool
$c/= :: InputFormat -> InputFormat -> Bool
== :: InputFormat -> InputFormat -> Bool
$c== :: InputFormat -> InputFormat -> Bool
Eq)
data RecordFormat
= RawRecord
| Fields Separator
deriving (Int -> RecordFormat -> ShowS
[RecordFormat] -> ShowS
RecordFormat -> String
(Int -> RecordFormat -> ShowS)
-> (RecordFormat -> String)
-> ([RecordFormat] -> ShowS)
-> Show RecordFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecordFormat] -> ShowS
$cshowList :: [RecordFormat] -> ShowS
show :: RecordFormat -> String
$cshow :: RecordFormat -> String
showsPrec :: Int -> RecordFormat -> ShowS
$cshowsPrec :: Int -> RecordFormat -> ShowS
Show, RecordFormat -> RecordFormat -> Bool
(RecordFormat -> RecordFormat -> Bool)
-> (RecordFormat -> RecordFormat -> Bool) -> Eq RecordFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecordFormat -> RecordFormat -> Bool
$c/= :: RecordFormat -> RecordFormat -> Bool
== :: RecordFormat -> RecordFormat -> Bool
$c== :: RecordFormat -> RecordFormat -> Bool
Eq)
data OutputFormat = OutputFormat
{ OutputFormat -> Delimiter
recordDelimiter :: Delimiter
, OutputFormat -> Delimiter
fieldDelimiter :: Delimiter
}
deriving (Int -> OutputFormat -> ShowS
[OutputFormat] -> ShowS
OutputFormat -> String
(Int -> OutputFormat -> ShowS)
-> (OutputFormat -> String)
-> ([OutputFormat] -> ShowS)
-> Show OutputFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OutputFormat] -> ShowS
$cshowList :: [OutputFormat] -> ShowS
show :: OutputFormat -> String
$cshow :: OutputFormat -> String
showsPrec :: Int -> OutputFormat -> ShowS
$cshowsPrec :: Int -> OutputFormat -> ShowS
Show, OutputFormat -> OutputFormat -> Bool
(OutputFormat -> OutputFormat -> Bool)
-> (OutputFormat -> OutputFormat -> Bool) -> Eq OutputFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OutputFormat -> OutputFormat -> Bool
$c/= :: OutputFormat -> OutputFormat -> Bool
== :: OutputFormat -> OutputFormat -> Bool
$c== :: OutputFormat -> OutputFormat -> Bool
Eq)
type Delimiter = ByteString
data Separator = Whitespace | Delimiter Delimiter
deriving (Int -> Separator -> ShowS
[Separator] -> ShowS
Separator -> String
(Int -> Separator -> ShowS)
-> (Separator -> String)
-> ([Separator] -> ShowS)
-> Show Separator
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Separator] -> ShowS
$cshowList :: [Separator] -> ShowS
show :: Separator -> String
$cshow :: Separator -> String
showsPrec :: Int -> Separator -> ShowS
$cshowsPrec :: Int -> Separator -> ShowS
Show, Separator -> Separator -> Bool
(Separator -> Separator -> Bool)
-> (Separator -> Separator -> Bool) -> Eq Separator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Separator -> Separator -> Bool
$c/= :: Separator -> Separator -> Bool
== :: Separator -> Separator -> Bool
$c== :: Separator -> Separator -> Bool
Eq)
data Processor = DoNotSeparate | SeparateOn Separator
deriving (Int -> Processor -> ShowS
[Processor] -> ShowS
Processor -> String
(Int -> Processor -> ShowS)
-> (Processor -> String)
-> ([Processor] -> ShowS)
-> Show Processor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Processor] -> ShowS
$cshowList :: [Processor] -> ShowS
show :: Processor -> String
$cshow :: Processor -> String
showsPrec :: Int -> Processor -> ShowS
$cshowsPrec :: Int -> Processor -> ShowS
Show, Processor -> Processor -> Bool
(Processor -> Processor -> Bool)
-> (Processor -> Processor -> Bool) -> Eq Processor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Processor -> Processor -> Bool
$c/= :: Processor -> Processor -> Bool
== :: Processor -> Processor -> Bool
$c== :: Processor -> Processor -> Bool
Eq)
fromSeparator :: Delimiter -> Separator -> Delimiter
fromSeparator :: Delimiter -> Separator -> Delimiter
fromSeparator Delimiter
def = \case
Separator
Whitespace -> Delimiter
def
Delimiter Delimiter
d -> Delimiter
d
fromProcessor :: Delimiter -> Processor -> Delimiter
fromProcessor :: Delimiter -> Processor -> Delimiter
fromProcessor Delimiter
def = \case
Processor
DoNotSeparate -> Delimiter
def
SeparateOn Separator
s -> Delimiter -> Separator -> Delimiter
fromSeparator Delimiter
def Separator
s
newtype ContextSpec = ContextSpec
{ ContextSpec -> String
userContextDirectory :: FilePath
}
deriving (Int -> ContextSpec -> ShowS
[ContextSpec] -> ShowS
ContextSpec -> String
(Int -> ContextSpec -> ShowS)
-> (ContextSpec -> String)
-> ([ContextSpec] -> ShowS)
-> Show ContextSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ContextSpec] -> ShowS
$cshowList :: [ContextSpec] -> ShowS
show :: ContextSpec -> String
$cshow :: ContextSpec -> String
showsPrec :: Int -> ContextSpec -> ShowS
$cshowsPrec :: Int -> ContextSpec -> ShowS
Show, ContextSpec -> ContextSpec -> Bool
(ContextSpec -> ContextSpec -> Bool)
-> (ContextSpec -> ContextSpec -> Bool) -> Eq ContextSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContextSpec -> ContextSpec -> Bool
$c/= :: ContextSpec -> ContextSpec -> Bool
== :: ContextSpec -> ContextSpec -> Bool
$c== :: ContextSpec -> ContextSpec -> Bool
Eq)
type UntypedExpr = String
data ExprSpec = ExprSpec
{ ExprSpec -> ContextSpec
contextSpec :: ContextSpec
, ExprSpec -> String
untypedExpr :: UntypedExpr
}
deriving (Int -> ExprSpec -> ShowS
[ExprSpec] -> ShowS
ExprSpec -> String
(Int -> ExprSpec -> ShowS)
-> (ExprSpec -> String) -> ([ExprSpec] -> ShowS) -> Show ExprSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExprSpec] -> ShowS
$cshowList :: [ExprSpec] -> ShowS
show :: ExprSpec -> String
$cshow :: ExprSpec -> String
showsPrec :: Int -> ExprSpec -> ShowS
$cshowsPrec :: Int -> ExprSpec -> ShowS
Show, ExprSpec -> ExprSpec -> Bool
(ExprSpec -> ExprSpec -> Bool)
-> (ExprSpec -> ExprSpec -> Bool) -> Eq ExprSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExprSpec -> ExprSpec -> Bool
$c/= :: ExprSpec -> ExprSpec -> Bool
== :: ExprSpec -> ExprSpec -> Bool
$c== :: ExprSpec -> ExprSpec -> Bool
Eq)
defaultInputSpec, noInput :: InputSpec
defaultInputSpec :: InputSpec
defaultInputSpec = InputSource -> InputFormat -> InputSpec
InputSpec InputSource
UseStdin InputFormat
defaultInputFormat
noInput :: InputSpec
noInput = InputSource -> InputFormat -> InputSpec
InputSpec InputSource
NoInput InputFormat
defaultInputFormat
defaultOutputSpec :: OutputSpec
defaultOutputSpec :: OutputSpec
defaultOutputSpec = OutputSink -> OutputFormat -> OutputSpec
OutputSpec OutputSink
UseStdout OutputFormat
defaultOutputFormat
defaultInputFormat :: InputFormat
defaultInputFormat :: InputFormat
defaultInputFormat = Separator -> RecordFormat -> InputFormat
Records Separator
defaultRecordSeparator
(RecordFormat -> InputFormat) -> RecordFormat -> InputFormat
forall a b. (a -> b) -> a -> b
$ Separator -> RecordFormat
Fields Separator
defaultFieldSeparator
defaultOutputFormat :: OutputFormat
defaultOutputFormat :: OutputFormat
defaultOutputFormat = Delimiter -> Delimiter -> OutputFormat
OutputFormat Delimiter
defaultRecordDelimiter Delimiter
defaultFieldDelimiter
defaultRecordSeparator, defaultFieldSeparator :: Separator
defaultRecordSeparator :: Separator
defaultRecordSeparator = Delimiter -> Separator
Delimiter Delimiter
defaultRecordDelimiter
defaultFieldSeparator :: Separator
defaultFieldSeparator = Separator
Whitespace
defaultRecordDelimiter, defaultFieldDelimiter :: Delimiter
defaultRecordDelimiter :: Delimiter
defaultRecordDelimiter = Delimiter
"\n"
defaultFieldDelimiter :: Delimiter
defaultFieldDelimiter = Delimiter
" "