{-# LANGUAGE OverloadedStrings #-}
-- Warning turned off for CI
{-# OPTIONS_GHC -Wwarn=unused-imports #-}
module Eventlog.Args
  (
    args
  , argsInfo
  , Args(..)
  , Sort(..)
  , defaultArgs
  ) where

import Options.Applicative
import Data.Text (Text)
-- Used for GHC 8.6.5
import Data.Semigroup ((<>))
import Control.Applicative (optional)

data Sort = Size | StdDev | Name | Gradient

data Args = Args
  {
    Args -> Sort
sorting      :: Sort
  , Args -> Bool
reversing    :: Bool
  , Args -> Int
nBands       :: Int
  , Args -> Maybe Int
detailedLimit :: Maybe Int
  , Args -> Bool
heapProfile  :: Bool
  , Args -> Bool
noIncludejs    :: Bool
  , Args -> Bool
json         :: Bool
  , Args -> Bool
noTraces     :: Bool
  , Args -> Bool
traceEvents  :: Bool -- ^ By default, only traceMarkers are included.
                         -- This option enables the inclusion of traceEvents.
  , Args -> Text
userColourScheme :: Text
  , Args -> Maybe Int
fixedYAxis :: Maybe Int
  , Args -> [Text]
includeStr :: [Text]
  , Args -> [Text]
excludeStr :: [Text]
  , Args -> Maybe String
outputFile :: Maybe String
  , Args -> [String]
files        :: [String]
  }

argParser :: Parser Args
argParser :: Parser Args
argParser = Sort
-> Bool
-> Int
-> Maybe Int
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe Int
-> [Text]
-> [Text]
-> Maybe String
-> [String]
-> Args
Args
      (Sort
 -> Bool
 -> Int
 -> Maybe Int
 -> Bool
 -> Bool
 -> Bool
 -> Bool
 -> Bool
 -> Text
 -> Maybe Int
 -> [Text]
 -> [Text]
 -> Maybe String
 -> [String]
 -> Args)
-> Parser Sort
-> Parser
     (Bool
      -> Int
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe Int
      -> [Text]
      -> [Text]
      -> Maybe String
      -> [String]
      -> Args)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM Sort -> Mod OptionFields Sort -> Parser Sort
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Sort
parseSort
          ( String -> Mod OptionFields Sort
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"sort"
         Mod OptionFields Sort
-> Mod OptionFields Sort -> Mod OptionFields Sort
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Sort
forall (f :: * -> *) a. String -> Mod f a
help String
"How to sort the bands.  One of: size (default), stddev, name, gradient."
         Mod OptionFields Sort
-> Mod OptionFields Sort -> Mod OptionFields Sort
forall a. Semigroup a => a -> a -> a
<> Sort -> Mod OptionFields Sort
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value Sort
Size
         Mod OptionFields Sort
-> Mod OptionFields Sort -> Mod OptionFields Sort
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Sort
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"FIELD" )
      Parser
  (Bool
   -> Int
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe Int
   -> [Text]
   -> [Text]
   -> Maybe String
   -> [String]
   -> Args)
-> Parser Bool
-> Parser
     (Int
      -> Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe Int
      -> [Text]
      -> [Text]
      -> Maybe String
      -> [String]
      -> Args)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
switch
          ( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"reverse"
         Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"Reverse the order of bands." )
      Parser
  (Int
   -> Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe Int
   -> [Text]
   -> [Text]
   -> Maybe String
   -> [String]
   -> Args)
-> Parser Int
-> Parser
     (Maybe Int
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe Int
      -> [Text]
      -> [Text]
      -> Maybe String
      -> [String]
      -> Args)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto
          ( String -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"bands"
         Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. String -> Mod f a
help String
"Maximum number of bands to draw (0 for unlimited)."
         Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Int -> Mod OptionFields Int
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value Int
15
         Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Int
forall a (f :: * -> *). Show a => Mod f a
showDefault
         Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"COUNT" )
      Parser
  (Maybe Int
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe Int
   -> [Text]
   -> [Text]
   -> Maybe String
   -> [String]
   -> Args)
-> Parser (Maybe Int)
-> Parser
     (Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe Int
      -> [Text]
      -> [Text]
      -> Maybe String
      -> [String]
      -> Args)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Parser Int -> Parser (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser Int -> Parser (Maybe Int))
-> Parser Int -> Parser (Maybe Int)
forall a b. (a -> b) -> a -> b
$ ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto
          (String -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"limit-detailed"
          Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. String -> Mod f a
help String
"The maximum number of bands to show in the detailed view."
          Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"N"))
      Parser
  (Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe Int
   -> [Text]
   -> [Text]
   -> Maybe String
   -> [String]
   -> Args)
-> Parser Bool
-> Parser
     (Bool
      -> Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe Int
      -> [Text]
      -> [Text]
      -> Maybe String
      -> [String]
      -> Args)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
switch
          ( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"heap-profile"
          Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'p'
          Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"Input files are .hp heap profiles.")
      Parser
  (Bool
   -> Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe Int
   -> [Text]
   -> [Text]
   -> Maybe String
   -> [String]
   -> Args)
-> Parser Bool
-> Parser
     (Bool
      -> Bool
      -> Bool
      -> Text
      -> Maybe Int
      -> [Text]
      -> [Text]
      -> Maybe String
      -> [String]
      -> Args)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
switch
          (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"no-include-js"
          Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"Fetch the javascript from a CDN rather than bundling it into the file.")
      Parser
  (Bool
   -> Bool
   -> Bool
   -> Text
   -> Maybe Int
   -> [Text]
   -> [Text]
   -> Maybe String
   -> [String]
   -> Args)
-> Parser Bool
-> Parser
     (Bool
      -> Bool
      -> Text
      -> Maybe Int
      -> [Text]
      -> [Text]
      -> Maybe String
      -> [String]
      -> Args)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
switch
          ( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"json"
          Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'j'
          Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"Output JSON")
      Parser
  (Bool
   -> Bool
   -> Text
   -> Maybe Int
   -> [Text]
   -> [Text]
   -> Maybe String
   -> [String]
   -> Args)
-> Parser Bool
-> Parser
     (Bool
      -> Text
      -> Maybe Int
      -> [Text]
      -> [Text]
      -> Maybe String
      -> [String]
      -> Args)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
switch
          ( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"no-traces"
          Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"Don't display traces on chart")
      Parser
  (Bool
   -> Text
   -> Maybe Int
   -> [Text]
   -> [Text]
   -> Maybe String
   -> [String]
   -> Args)
-> Parser Bool
-> Parser
     (Text
      -> Maybe Int
      -> [Text]
      -> [Text]
      -> Maybe String
      -> [String]
      -> Args)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
switch
          ( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"include-trace-events"
          Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help (String
"Enables the inclusion of traces emitted using `traceEvent`"
                   String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
", which should only be used for high-frequency events. "
                   String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"For low frequency events, use `traceMarker` instead.")
          Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Mod FlagFields Bool
forall a (f :: * -> *). Show a => Mod f a
showDefault)
      Parser
  (Text
   -> Maybe Int
   -> [Text]
   -> [Text]
   -> Maybe String
   -> [String]
   -> Args)
-> Parser Text
-> Parser
     (Maybe Int -> [Text] -> [Text] -> Maybe String -> [String] -> Args)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadM Text -> Mod OptionFields Text -> Parser Text
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Text
forall s. IsString s => ReadM s
str
          ( String -> Mod OptionFields Text
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"colour-scheme"
          Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<> Text -> Mod OptionFields Text
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value Text
"category20b"
          Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Text
forall (f :: * -> *) a. String -> Mod f a
help String
"The name of the colour scheme. See the vega documentation (https://vega.github.io/vega/docs/schemes/#reference) for a complete list. Examples include \"category10\" \"dark2\" \"tableau10\". ")
      Parser
  (Maybe Int -> [Text] -> [Text] -> Maybe String -> [String] -> Args)
-> Parser (Maybe Int)
-> Parser ([Text] -> [Text] -> Maybe String -> [String] -> Args)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadM (Maybe Int)
-> Mod OptionFields (Maybe Int) -> Parser (Maybe Int)
forall a. ReadM a -> Mod OptionFields a -> Parser a
option (Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> ReadM Int -> ReadM (Maybe Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM Int
forall a. Read a => ReadM a
auto)
          ( String -> Mod OptionFields (Maybe Int)
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"y-axis"
          Mod OptionFields (Maybe Int)
-> Mod OptionFields (Maybe Int) -> Mod OptionFields (Maybe Int)
forall a. Semigroup a => a -> a -> a
<> Maybe Int -> Mod OptionFields (Maybe Int)
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value Maybe Int
forall a. Maybe a
Nothing
          Mod OptionFields (Maybe Int)
-> Mod OptionFields (Maybe Int) -> Mod OptionFields (Maybe Int)
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields (Maybe Int)
forall (f :: * -> *) a. String -> Mod f a
help String
"Fixed value for the maximum extent of the y-axis in bytes. This option is useful for comparing profiles together.")
      Parser ([Text] -> [Text] -> Maybe String -> [String] -> Args)
-> Parser [Text]
-> Parser ([Text] -> Maybe String -> [String] -> Args)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Text -> Parser [Text]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (ReadM Text -> Mod OptionFields Text -> Parser Text
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Text
forall s. IsString s => ReadM s
str
          (Char -> Mod OptionFields Text
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'i'
          Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Text
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"include"
          Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Text
forall (f :: * -> *) a. String -> Mod f a
help (String
"Specify the traces which should be included in the output. Only traces which contain SUBSTRING "
                    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"in their name will be included. Multiple different traces can be included "
                    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"with \"-i foo -i bar\".")
          Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Text
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"SUBSTRING"))
      Parser ([Text] -> Maybe String -> [String] -> Args)
-> Parser [Text] -> Parser (Maybe String -> [String] -> Args)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Text -> Parser [Text]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (ReadM Text -> Mod OptionFields Text -> Parser Text
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Text
forall s. IsString s => ReadM s
str
          (Char -> Mod OptionFields Text
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'x'
          Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Text
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"exclude"
          Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Text
forall (f :: * -> *) a. String -> Mod f a
help (String
"Specify the traces which should be excluded in the output. All traces which contain SUBSTRING "
                    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"in their name will be excluded. Multiple different traces can be excluded "
                    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"with \"-x foo -x bar\".")
          Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Text
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"SUBSTRING"))
      Parser (Maybe String -> [String] -> Args)
-> Parser (Maybe String) -> Parser ([String] -> Args)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser String -> Parser (Maybe String))
-> Parser String -> Parser (Maybe String)
forall a b. (a -> b) -> a -> b
$ ReadM String -> Mod OptionFields String -> Parser String
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM String
forall s. IsString s => ReadM s
str
          (Char -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'o'
          Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"Write the output to the given filename."
          Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"OUTFILE"))
      Parser ([String] -> Args) -> Parser [String] -> Parser Args
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser [String]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
some (ReadM String -> Mod ArgumentFields String -> Parser String
forall a. ReadM a -> Mod ArgumentFields a -> Parser a
argument ReadM String
forall s. IsString s => ReadM s
str
          ( String -> Mod ArgumentFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"Eventlogs (FILE.eventlog will be converted to FILE.html)."
         Mod ArgumentFields String
-> Mod ArgumentFields String -> Mod ArgumentFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod ArgumentFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"FILES..." ))

parseSort :: ReadM Sort
parseSort :: ReadM Sort
parseSort = (String -> Either String Sort) -> ReadM Sort
forall a. (String -> Either String a) -> ReadM a
eitherReader ((String -> Either String Sort) -> ReadM Sort)
-> (String -> Either String Sort) -> ReadM Sort
forall a b. (a -> b) -> a -> b
$ \String
s -> case String
s of
  String
"size" -> Sort -> Either String Sort
forall a b. b -> Either a b
Right Sort
Size
  String
"stddev" -> Sort -> Either String Sort
forall a b. b -> Either a b
Right Sort
StdDev
  String
"name" -> Sort -> Either String Sort
forall a b. b -> Either a b
Right Sort
Name
  String
"gradient" -> Sort -> Either String Sort
forall a b. b -> Either a b
Right Sort
Gradient
  String
_ -> String -> Either String Sort
forall a b. a -> Either a b
Left String
"expected one of: size, stddev, name"

args :: IO Args
args :: IO Args
args = ParserInfo Args -> IO Args
forall a. ParserInfo a -> IO a
execParser ParserInfo Args
argsInfo


defaultArgs :: FilePath -> IO Args
defaultArgs :: String -> IO Args
defaultArgs String
fp = ParserResult Args -> IO Args
forall a. ParserResult a -> IO a
handleParseResult (ParserPrefs -> ParserInfo Args -> [String] -> ParserResult Args
forall a. ParserPrefs -> ParserInfo a -> [String] -> ParserResult a
execParserPure ParserPrefs
defaultPrefs ParserInfo Args
argsInfo [String
fp])


argsInfo :: ParserInfo Args
argsInfo :: ParserInfo Args
argsInfo = ParserInfo Args
opts
  where
    opts :: ParserInfo Args
opts = Parser Args -> InfoMod Args -> ParserInfo Args
forall a. Parser a -> InfoMod a -> ParserInfo a
info (Parser Args
argParser Parser Args -> Parser (Args -> Args) -> Parser Args
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Args -> Args)
forall a. Parser (a -> a)
helper)
      ( InfoMod Args
forall a. InfoMod a
fullDesc
     InfoMod Args -> InfoMod Args -> InfoMod Args
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod Args
forall a. String -> InfoMod a
progDesc String
"Convert eventlogs FILES.eventlog to interactive FILES.html"
     InfoMod Args -> InfoMod Args -> InfoMod Args
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod Args
forall a. String -> InfoMod a
header String
"eventlog2html - generate interactive html from eventlogs" )