Safe Haskell | Safe-Inferred |
---|---|
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
liftIO :: MonadIO m => IO a -> m a #
Lift a computation from the IO
monad.
This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations
(i.e. IO
is the base monad for the stack).
Example
import Control.Monad.Trans.State -- from the "transformers" library printState :: Show s => StateT s IO () printState = do state <- get liftIO $ print state
Had we omitted
, we would have ended up with this error:liftIO
• Couldn't match type ‘IO’ with ‘StateT s IO’ Expected type: StateT s IO () Actual type: IO ()
The important part here is the mismatch between StateT s IO ()
and
.IO
()
Luckily, we know of a function that takes an
and returns an IO
a(m a)
:
,
enabling us to run the program and see the expected results:liftIO
> evalStateT printState "hello" "hello" > evalStateT printState 3 3
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
.
Instances
MonadFail Ghc | |
Defined in GHC.Driver.Monad | |
MonadFix Ghc | |
Defined in GHC.Driver.Monad | |
MonadIO Ghc | |
Defined in GHC.Driver.Monad | |
Alternative Ghc Source # | |
Applicative Ghc | |
Functor Ghc | |
Monad Ghc | |
MonadCatch Ghc | |
Defined in GHC.Driver.Monad | |
MonadMask Ghc | |
Defined in GHC.Driver.Monad Methods mask :: HasCallStack => ((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b # uninterruptibleMask :: HasCallStack => ((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b # generalBracket :: HasCallStack => Ghc a -> (a -> ExitCase b -> Ghc c) -> (a -> Ghc b) -> Ghc (b, c) # | |
MonadThrow Ghc | |
Defined in GHC.Driver.Monad Methods throwM :: (HasCallStack, Exception e) => e -> Ghc a # | |
GhcMonad Ghc | |
Defined in GHC.Driver.Monad | |
HasDynFlags Ghc | |
Defined in GHC.Driver.Monad Methods getDynFlags :: Ghc DynFlags # | |
HasLogger Ghc | |
Defined in GHC.Driver.Monad |