| Copyright | (c) 2005 Martin Engelke 2007 Sebastian Fischer 2011 - 2016 Björn Peemöller 2016 - 2017 Finn Teegen 2018 Kai-Oliver Prott |
|---|---|
| License | BSD-3-clause |
| Maintainer | fte@informatik.uni-kiel.de |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | Safe |
| Language | Haskell2010 |
CompilerOpts
Description
This module defines data structures holding options for the compilation of Curry programs, and utility functions for printing help information as well as parsing the command line arguments.
Synopsis
- data Options = Options {
- optMode :: CymakeMode
- optVerbosity :: Verbosity
- optForce :: Bool
- optLibraryPaths :: [FilePath]
- optImportPaths :: [FilePath]
- optHtmlDir :: Maybe FilePath
- optUseSubdir :: Bool
- optInterface :: Bool
- optPrepOpts :: PrepOpts
- optWarnOpts :: WarnOpts
- optTargetTypes :: [TargetType]
- optExtensions :: [KnownExtension]
- optDebugOpts :: DebugOpts
- optCaseMode :: CaseMode
- optCppOpts :: CppOpts
- data CppOpts = CppOpts {}
- data PrepOpts = PrepOpts {}
- data WarnOpts = WarnOpts {
- wnWarn :: Bool
- wnWarnFlags :: [WarnFlag]
- wnWarnAsError :: Bool
- data DebugOpts = DebugOpts {
- dbDumpLevels :: [DumpLevel]
- dbDumpEnv :: Bool
- dbDumpRaw :: Bool
- dbDumpAllBindings :: Bool
- dbDumpSimple :: Bool
- data CaseMode
- data CymakeMode
- data Verbosity
- data TargetType
- data WarnFlag
- data KnownExtension
- data DumpLevel
- = DumpCondCompiled
- | DumpParsed
- | DumpExtensionChecked
- | DumpTypeSyntaxChecked
- | DumpKindChecked
- | DumpSyntaxChecked
- | DumpPrecChecked
- | DumpDeriveChecked
- | DumpInstanceChecked
- | DumpTypeChecked
- | DumpExportChecked
- | DumpQualified
- | DumpDerived
- | DumpDesugared
- | DumpDictionaries
- | DumpNewtypes
- | DumpSimplified
- | DumpLifted
- | DumpTranslated
- | DumpCaseCompleted
- | DumpTypedFlatCurry
- | DumpFlatCurry
- dumpLevel :: [(DumpLevel, String, String)]
- defaultOptions :: Options
- defaultPrepOpts :: PrepOpts
- defaultWarnOpts :: WarnOpts
- defaultDebugOpts :: DebugOpts
- getCompilerOpts :: IO (String, Options, [String], [String])
- updateOpts :: Options -> [String] -> (Options, [String], [String])
- usage :: String -> String
Documentation
Compiler options
Constructors
| Options | |
Fields
| |
C preprocessor options
Constructors
| CppOpts | |
Preprocessor options
Constructors
| PrepOpts | |
Warning options
Constructors
| WarnOpts | |
Fields
| |
Debug options
Constructors
| DebugOpts | |
Fields
| |
Constructors
| CaseModeFree | |
| CaseModeHaskell | |
| CaseModeProlog | |
| CaseModeGoedel |
data CymakeMode Source #
Modus operandi of the program
Constructors
| ModeHelp | Show help information and exit |
| ModeVersion | Show version and exit |
| ModeNumericVersion | Show numeric version, suitable for later processing |
| ModeMake | Compile with dependencies |
Instances
| Eq CymakeMode Source # | |
Defined in CompilerOpts | |
| Show CymakeMode Source # | |
Defined in CompilerOpts Methods showsPrec :: Int -> CymakeMode -> ShowS # show :: CymakeMode -> String # showList :: [CymakeMode] -> ShowS # | |
Verbosity level
Constructors
| VerbQuiet | be quiet |
| VerbStatus | show status of compilation |
Instances
| Eq Verbosity Source # | |
| Ord Verbosity Source # | |
| Show Verbosity Source # | |
data TargetType Source #
Type of the target file
Constructors
| Tokens | Source code tokens |
| Comments | Source code comments |
| Parsed | Parsed source code |
| FlatCurry | FlatCurry |
| TypedFlatCurry | Typed FlatCurry |
| TypeAnnotatedFlatCurry | Type-annotated FlatCurry |
| AbstractCurry | AbstractCurry |
| UntypedAbstractCurry | Untyped AbstractCurry |
| Html | HTML documentation |
| AST | Abstract-Syntax-Tree after checks |
| ShortAST | Abstract-Syntax-Tree with shortened decls |
Instances
| Eq TargetType Source # | |
Defined in CompilerOpts | |
| Show TargetType Source # | |
Defined in CompilerOpts Methods showsPrec :: Int -> TargetType -> ShowS # show :: TargetType -> String # showList :: [TargetType] -> ShowS # | |
Warnings flags
Constructors
| WarnMultipleImports | Warn for multiple imports |
| WarnDisjoinedRules | Warn for disjoined function rules |
| WarnUnusedGlobalBindings | Warn for unused global bindings |
| WarnUnusedBindings | Warn for unused local bindings |
| WarnNameShadowing | Warn for name shadowing |
| WarnOverlapping | Warn for overlapping rules/alternatives |
| WarnIncompletePatterns | Warn for incomplete pattern matching |
| WarnMissingSignatures | Warn for missing type signatures |
| WarnMissingMethods | Warn for missing method implementations |
| WarnOrphanInstances | Warn for orphan instances |
| WarnIrregularCaseMode |
Instances
| Bounded WarnFlag Source # | |
| Enum WarnFlag Source # | |
| Eq WarnFlag Source # | |
| Show WarnFlag Source # | |
data KnownExtension #
Known language extensions of Curry.
Constructors
| AnonFreeVars | anonymous free variables |
| CPP | C preprocessor |
| FunctionalPatterns | functional patterns |
| NegativeLiterals | negative literals |
| NoImplicitPrelude | no implicit import of the prelude |
Instances
Dump level
Constructors
| DumpCondCompiled | dump source code after conditional compiling |
| DumpParsed | dump source code after parsing |
| DumpExtensionChecked | dump source code after extension checking |
| DumpTypeSyntaxChecked | dump source code after type syntax checking |
| DumpKindChecked | dump source code after kind checking |
| DumpSyntaxChecked | dump source code after syntax checking |
| DumpPrecChecked | dump source code after precedence checking |
| DumpDeriveChecked | dump source code after derive checking |
| DumpInstanceChecked | dump source code after instance checking |
| DumpTypeChecked | dump source code after type checking |
| DumpExportChecked | dump source code after export checking |
| DumpQualified | dump source code after qualification |
| DumpDerived | dump source code after deriving |
| DumpDesugared | dump source code after desugaring |
| DumpDictionaries | dump source code after dictionary transformation |
| DumpNewtypes | dump source code after removing newtype constructors |
| DumpSimplified | dump source code after simplification |
| DumpLifted | dump source code after lambda-lifting |
| DumpTranslated | dump IL code after translation |
| DumpCaseCompleted | dump IL code after case completion |
| DumpTypedFlatCurry | dump typed FlatCurry code |
| DumpFlatCurry | dump FlatCurry code |
Instances
| Bounded DumpLevel Source # | |
| Enum DumpLevel Source # | |
Defined in CompilerOpts Methods succ :: DumpLevel -> DumpLevel # pred :: DumpLevel -> DumpLevel # fromEnum :: DumpLevel -> Int # enumFrom :: DumpLevel -> [DumpLevel] # enumFromThen :: DumpLevel -> DumpLevel -> [DumpLevel] # enumFromTo :: DumpLevel -> DumpLevel -> [DumpLevel] # enumFromThenTo :: DumpLevel -> DumpLevel -> DumpLevel -> [DumpLevel] # | |
| Eq DumpLevel Source # | |
| Show DumpLevel Source # | |
defaultOptions :: Options Source #
Default compiler options
defaultPrepOpts :: PrepOpts Source #
Default preprocessor options
defaultWarnOpts :: WarnOpts Source #
Default warning options
defaultDebugOpts :: DebugOpts Source #
Default dump options