| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Hhp.Ghc
Description
The Happy Haskell Programming library. API for interactive processes
Synopsis
- withGHC :: FilePath -> Ghc a -> IO a
- withGHC' :: Ghc a -> IO a
- initializeFlagsWithCradle :: Options -> Cradle -> Ghc ()
- boot :: Options -> Ghc String
- browse :: Options -> ModuleString -> Ghc String
- check :: Options -> [FilePath] -> Ghc (Either String String)
- info :: Options -> FilePath -> Expression -> Ghc String
- types :: Options -> FilePath -> Int -> Int -> Ghc String
- modules :: Options -> Ghc String
- type Symbol = String
- data SymMdlDb
- getSymMdlDb :: Ghc SymMdlDb
- lookupSym :: Options -> Symbol -> SymMdlDb -> String
- getSystemLibDir :: IO (Maybe FilePath)
- liftIO :: MonadIO m => IO a -> m a
- runGhc :: Maybe FilePath -> Ghc a -> IO a
- getMainFileToBeDeleted :: FilePath -> Ghc (Maybe FilePath)
- data Ghc a
Converting the Ghc monad to the IO monad
Initializing DynFlags
Ghc utilities
Arguments
| :: Options | |
| -> ModuleString | A module name. (e.g. "Data.List") |
| -> Ghc String |
Checking syntax of a target file using GHC. Warnings and errors are returned.
Arguments
| :: Options | |
| -> FilePath | A target file. |
| -> Expression | A Haskell expression. |
| -> Ghc String |
Obtaining information of a target expression. (GHCi's info:)
Obtaining type of a target expression. (GHCi's type:)
SymMdlDb
Misc
Arguments
| :: Maybe FilePath | See argument to |
| -> Ghc a | The action to perform. |
| -> IO a |
Run function for the Ghc monad.
It initialises the GHC session and warnings via initGhcMonad. Each call
to this function will create a new session which should not be shared among
several threads.
Any errors not handled inside the Ghc action are propagated as IO
exceptions.
A minimal implementation of a GhcMonad. If you need a custom monad,
e.g., to maintain additional state consider wrapping this monad or using
GhcT.