| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Helium.Main.CompileUtils
Description
- type Phase err a = IO (Either [err] a)
- type CompileOptions = ([Option], String, [String])
- (===>) :: Phase err1 a -> (a -> Phase err2 b) -> Phase (Either err1 err2) b
- doPhaseWithExit :: HasMessage err => Int -> ([err] -> String) -> CompileOptions -> Phase err a -> IO a
- sendLog :: String -> String -> [String] -> [Option] -> IO ()
- enterNewPhase :: String -> [Option] -> IO ()
- showErrorsAndExit :: HasMessage a => [a] -> Int -> IO b
- showMessages :: HasMessage a => [a] -> IO ()
- makeCoreLib :: String -> String -> IO ()
- sys :: String -> IO ()
- checkExistence :: [String] -> String -> IO ()
- resolve :: [String] -> String -> IO (Maybe String)
- data Option
- = BuildOne
- | BuildAll
- | DumpInformationForThisModule
- | DumpInformationForAllModules
- | DisableLogging
- | EnableLogging
- | Alert String
- | Overloading
- | NoOverloading
- | LvmPath String
- | Verbose
- | NoWarnings
- | MoreOptions
- | Information String
- | StopAfterParser
- | StopAfterStaticAnalysis
- | StopAfterTypeInferencing
- | StopAfterDesugar
- | DumpTokens
- | DumpUHA
- | DumpCore
- | DumpCoreToFile
- | DebugLogger
- | Host String
- | Port Int
- | DumpTypeDebug
- | AlgorithmW
- | AlgorithmM
- | DisableDirectives
- | NoRepairHeuristics
- | HFullQualification
- | ExperimentalOptions
- | KindInferencing
- | SignatureWarnings
- | RightToLeft
- | NoSpreading
- | TreeWalkTopDown
- | TreeWalkBottomUp
- | TreeWalkInorderTopFirstPre
- | TreeWalkInorderTopLastPre
- | TreeWalkInorderTopFirstPost
- | TreeWalkInorderTopLastPost
- | SolverSimple
- | SolverGreedy
- | SolverTypeGraph
- | SolverCombination
- | SolverChunks
- | UnifierHeuristics
- | SelectConstraintNumber Int
- | NoOverloadingTypeCheck
- | NoPrelude
- | UseTutor
- splitFilePath :: String -> (String, String, String)
- combinePathAndFile :: String -> String -> String
- when :: Monad m => Bool -> m () -> m ()
- unless :: Monad m => Bool -> m () -> m ()
- exitWith :: ExitCode -> IO a
- data ExitCode :: *
- exitSuccess :: IO a
- getArgs :: IO [String]
- module Helium.ModuleSystem.ImportEnvironment
- data Module = Module_Module Range MaybeName MaybeExports Body
Documentation
type CompileOptions = ([Option], String, [String]) Source
doPhaseWithExit :: HasMessage err => Int -> ([err] -> String) -> CompileOptions -> Phase err a -> IO a Source
enterNewPhase :: String -> [Option] -> IO () Source
showErrorsAndExit :: HasMessage a => [a] -> Int -> IO b Source
showMessages :: HasMessage a => [a] -> IO () Source
makeCoreLib :: String -> String -> IO () Source
checkExistence :: [String] -> String -> IO () Source
Constructors
combinePathAndFile :: String -> String -> String Source
when :: Monad m => Bool -> m () -> m ()
Conditional execution of monadic expressions. For example,
when debug (putStr "Debugging\n")
will output the string Debugging\n if the Boolean value debug is True,
and otherwise do nothing.
Computation exitWith code throws ExitCode code.
Normally this terminates the program, returning code to the
program's caller.
On program termination, the standard Handles stdout and
stderr are flushed automatically; any other buffered Handles
need to be flushed manually, otherwise the buffered data will be
discarded.
A program that fails in any other way is treated as if it had
called exitFailure.
A program that terminates successfully without calling exitWith
explicitly is treated as it it had called exitWith ExitSuccess.
As an ExitCode is not an IOError, exitWith bypasses
the error handling in the IO monad and cannot be intercepted by
catch from the Prelude. However it is a SomeException, and can
be caught using the functions of Control.Exception. This means
that cleanup computations added with bracket
(from Control.Exception) are also executed properly on exitWith.
Note: in GHC, exitWith should be called from the main program
thread in order to exit the process. When called from another
thread, exitWith will throw an ExitException as normal, but the
exception will not cause the process itself to exit.
data ExitCode :: *
Defines the exit codes that a program can return.
Constructors
| ExitSuccess | indicates successful termination; |
| ExitFailure Int | indicates program failure with an exit code. The exact interpretation of the code is operating-system dependent. In particular, some values may be prohibited (e.g. 0 on a POSIX-compliant system). |
exitSuccess :: IO a
The computation exitSuccess is equivalent to
exitWith ExitSuccess, It terminates the program
successfully.
Computation getArgs returns a list of the program's command
line arguments (not including the program name).
Constructors
| Module_Module Range MaybeName MaybeExports Body |