Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
High-level API for invoking the Futhark compiler.
Synopsis
- runPipelineOnProgram :: FutharkConfig -> Pipeline SOACS torep -> FilePath -> FutharkM (Prog torep)
- runCompilerOnProgram :: FutharkConfig -> Pipeline SOACS rep -> Action rep -> FilePath -> IO ()
- dumpError :: FutharkConfig -> CompilerError -> IO ()
- handleWarnings :: FutharkConfig -> FutharkM (Warnings, a) -> FutharkM a
- prettyProgErrors :: NonEmpty ProgError -> Doc AnsiStyle
- module Futhark.Compiler.Program
- module Futhark.Compiler.Config
- readProgramFile :: (MonadError CompilerError m, MonadIO m) => [Name] -> FilePath -> m (Warnings, Imports, VNameSource)
- readProgramFiles :: (MonadError CompilerError m, MonadIO m) => [Name] -> [FilePath] -> m (Warnings, Imports, VNameSource)
- readProgramOrDie :: MonadIO m => FilePath -> m (Warnings, Imports, VNameSource)
- readUntypedProgram :: (MonadError CompilerError m, MonadIO m) => FilePath -> m [(String, UncheckedProg)]
- readUntypedProgramOrDie :: MonadIO m => FilePath -> m [(String, UncheckedProg)]
Documentation
runPipelineOnProgram :: FutharkConfig -> Pipeline SOACS torep -> FilePath -> FutharkM (Prog torep) Source #
runCompilerOnProgram :: FutharkConfig -> Pipeline SOACS rep -> Action rep -> FilePath -> IO () Source #
dumpError :: FutharkConfig -> CompilerError -> IO () Source #
Print a compiler error to stdout. The FutharkConfig
controls
to which degree auxiliary information (e.g. the failing program) is
also printed.
handleWarnings :: FutharkConfig -> FutharkM (Warnings, a) -> FutharkM a Source #
Run an operation that produces warnings, and handle them appropriately, yielding the non-warning return value. "Proper handling" means e.g. to print them to the screen, as directed by the compiler configuration.
prettyProgErrors :: NonEmpty ProgError -> Doc AnsiStyle Source #
Prettyprint program errors as suitable for showing on a text console.
module Futhark.Compiler.Program
module Futhark.Compiler.Config
readProgramFile :: (MonadError CompilerError m, MonadIO m) => [Name] -> FilePath -> m (Warnings, Imports, VNameSource) Source #
Read and type-check a Futhark program, comprising a single file, including all imports.
readProgramFiles :: (MonadError CompilerError m, MonadIO m) => [Name] -> [FilePath] -> m (Warnings, Imports, VNameSource) Source #
Read and type-check a Futhark library, comprising multiple files, including all imports.
readProgramOrDie :: MonadIO m => FilePath -> m (Warnings, Imports, VNameSource) Source #
Not verbose, and terminates process on error.
readUntypedProgram :: (MonadError CompilerError m, MonadIO m) => FilePath -> m [(String, UncheckedProg)] Source #
Read and parse (but do not type-check) a Futhark program, including all imports.
readUntypedProgramOrDie :: MonadIO m => FilePath -> m [(String, UncheckedProg)] Source #
Not verbose, and terminates process on error.