Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data CommandLineOptions = Options {
- optProgramName :: String
- optInputFile :: Maybe FilePath
- optIncludePaths :: [FilePath]
- optAbsoluteIncludePaths :: [AbsolutePath]
- optLibraries :: [LibName]
- optOverrideLibrariesFile :: Maybe FilePath
- optDefaultLibs :: Bool
- optUseLibs :: Bool
- optShowVersion :: Bool
- optShowHelp :: Maybe Help
- optInteractive :: Bool
- optGHCiInteraction :: Bool
- optJSONInteraction :: Bool
- optOptimSmashing :: Bool
- optCompileDir :: Maybe FilePath
- optGenerateVimFile :: Bool
- optGenerateLaTeX :: Bool
- optGenerateHTML :: Bool
- optHTMLHighlight :: HtmlHighlight
- optDependencyGraph :: Maybe FilePath
- optLaTeXDir :: FilePath
- optHTMLDir :: FilePath
- optCSSFile :: Maybe FilePath
- optIgnoreInterfaces :: Bool
- optIgnoreAllInterfaces :: Bool
- optLocalInterfaces :: Bool
- optPragmaOptions :: PragmaOptions
- optOnlyScopeChecking :: Bool
- optWithCompiler :: Maybe FilePath
- data PragmaOptions = PragmaOptions {
- optShowImplicit :: Bool
- optShowIrrelevant :: Bool
- optUseUnicode :: Bool
- optVerbose :: Verbosity
- optProp :: Bool
- optAllowUnsolved :: Bool
- optAllowIncompleteMatch :: Bool
- optDisablePositivity :: Bool
- optTerminationCheck :: Bool
- optTerminationDepth :: CutOff
- optCompletenessCheck :: Bool
- optUniverseCheck :: Bool
- optOmegaInOmega :: Bool
- optSubtyping :: WithDefault 'False
- optCumulativity :: Bool
- optSizedTypes :: WithDefault 'True
- optGuardedness :: WithDefault 'True
- optInjectiveTypeConstructors :: Bool
- optUniversePolymorphism :: Bool
- optIrrelevantProjections :: Bool
- optExperimentalIrrelevance :: Bool
- optWithoutK :: WithDefault 'False
- optCopatterns :: Bool
- optPatternMatching :: Bool
- optExactSplit :: Bool
- optEta :: Bool
- optForcing :: Bool
- optProjectionLike :: Bool
- optRewriting :: Bool
- optCubical :: Bool
- optPostfixProjections :: Bool
- optKeepPatternVariables :: Bool
- optInstanceSearchDepth :: Int
- optOverlappingInstances :: Bool
- optInversionMaxDepth :: Int
- optSafe :: Bool
- optDoubleCheck :: Bool
- optSyntacticEquality :: Bool
- optCompareSorts :: Bool
- optWarningMode :: WarningMode
- optCompileNoMain :: Bool
- optCaching :: Bool
- optCountClusters :: Bool
- optAutoInline :: Bool
- optPrintPatternSynonyms :: Bool
- optFastReduce :: Bool
- optConfluenceCheck :: Bool
- optFlatSplit :: Bool
- type OptionsPragma = [String]
- type Flag opts = opts -> OptM opts
- type OptM = ExceptT String IO
- runOptM :: OptM a -> IO (Either String a)
- data OptDescr a = Option [Char] [String] (ArgDescr a) String
- data ArgDescr a
- type Verbosity = Trie VerboseKey VerboseLevel
- type VerboseKey = String
- type VerboseLevel = Int
- data HtmlHighlight
- data WarningMode = WarningMode {}
- checkOpts :: Flag CommandLineOptions
- parsePragmaOptions :: [String] -> CommandLineOptions -> OptM PragmaOptions
- parsePluginOptions :: [String] -> [OptDescr (Flag opts)] -> Flag opts
- stripRTS :: [String] -> [String]
- defaultOptions :: CommandLineOptions
- defaultInteractionOptions :: PragmaOptions
- defaultVerbosity :: Verbosity
- defaultCutOff :: CutOff
- defaultPragmaOptions :: PragmaOptions
- standardOptions_ :: [OptDescr ()]
- unsafePragmaOptions :: PragmaOptions -> [String]
- restartOptions :: [(PragmaOptions -> RestartCodomain, String)]
- infectiveOptions :: [(PragmaOptions -> Bool, String)]
- coinfectiveOptions :: [(PragmaOptions -> Bool, String)]
- safeFlag :: Flag PragmaOptions
- mapFlag :: (String -> String) -> OptDescr a -> OptDescr a
- usage :: [OptDescr ()] -> String -> Help -> String
- defaultLibDir :: IO FilePath
- inputFlag :: FilePath -> Flag CommandLineOptions
- standardOptions :: [OptDescr (Flag CommandLineOptions)]
- deadStandardOptions :: [OptDescr (Flag CommandLineOptions)]
- getOptSimple :: [String] -> [OptDescr (Flag opts)] -> (String -> Flag opts) -> Flag opts
Documentation
data CommandLineOptions Source #
Instances
data PragmaOptions Source #
Options which can be set in a pragma.
PragmaOptions | |
|
Instances
type OptionsPragma = [String] Source #
The options from an OPTIONS
pragma.
In the future it might be nice to switch to a more structured representation. Note that, currently, there is not a one-to-one correspondence between list elements and options.
type Flag opts = opts -> OptM opts Source #
f :: Flag opts
is an action on the option record that results from
parsing an option. f opts
produces either an error message or an
updated options record
Describes whether an option takes an argument or not, and if so
how the argument is injected into a value of type a
.
type Verbosity = Trie VerboseKey VerboseLevel Source #
type VerboseKey = String Source #
type VerboseLevel = Int Source #
data HtmlHighlight Source #
Instances
Eq HtmlHighlight Source # | |
Defined in Agda.Interaction.Options (==) :: HtmlHighlight -> HtmlHighlight -> Bool # (/=) :: HtmlHighlight -> HtmlHighlight -> Bool # | |
Show HtmlHighlight Source # | |
Defined in Agda.Interaction.Options showsPrec :: Int -> HtmlHighlight -> ShowS # show :: HtmlHighlight -> String # showList :: [HtmlHighlight] -> ShowS # |
data WarningMode Source #
A WarningMode
has two components: a set of warnings to be displayed
and a flag stating whether warnings should be turned into fatal errors.
Instances
Eq WarningMode Source # | |
Defined in Agda.Interaction.Options.Warnings (==) :: WarningMode -> WarningMode -> Bool # (/=) :: WarningMode -> WarningMode -> Bool # | |
Show WarningMode Source # | |
Defined in Agda.Interaction.Options.Warnings showsPrec :: Int -> WarningMode -> ShowS # show :: WarningMode -> String # showList :: [WarningMode] -> ShowS # | |
EmbPrj WarningMode Source # | |
Defined in Agda.TypeChecking.Serialise.Instances.Errors |
checkOpts :: Flag CommandLineOptions Source #
Checks that the given options are consistent.
:: [String] | Pragma options. |
-> CommandLineOptions | Command-line options which should be updated. |
-> OptM PragmaOptions |
Parse options from an options pragma.
parsePluginOptions :: [String] -> [OptDescr (Flag opts)] -> Flag opts Source #
Parse options for a plugin.
defaultCutOff :: CutOff Source #
The default termination depth.
standardOptions_ :: [OptDescr ()] Source #
Used for printing usage info. Does not include the dead options.
unsafePragmaOptions :: PragmaOptions -> [String] Source #
Check for unsafe pragmas. Gives a list of used unsafe flags.
restartOptions :: [(PragmaOptions -> RestartCodomain, String)] Source #
If any these options have changed, then the file will be rechecked. Boolean options are negated to mention non-default options, where possible.
infectiveOptions :: [(PragmaOptions -> Bool, String)] Source #
An infective option is an option that if used in one module, must be used in all modules that depend on this module.
coinfectiveOptions :: [(PragmaOptions -> Bool, String)] Source #
A coinfective option is an option that if used in one module, must be used in all modules that this module depends on.
mapFlag :: (String -> String) -> OptDescr a -> OptDescr a Source #
Map a function over the long options. Also removes the short options. Will be used to add the plugin name to the plugin options.
usage :: [OptDescr ()] -> String -> Help -> String Source #
The usage info message. The argument is the program name (probably agda).
defaultLibDir :: IO FilePath Source #
Returns the absolute default lib dir. This directory is used to store the Primitive.agda file.
deadStandardOptions :: [OptDescr (Flag CommandLineOptions)] Source #
Command line options of previous versions of Agda. Should not be listed in the usage info, put parsed by GetOpt for good error messaging.