hhp-0.0.4: Happy Haskell Programming
Safe HaskellNone
LanguageHaskell2010

Hhp.Ghc

Description

The Happy Haskell Programming library. API for interactive processes

Synopsis

Converting the Ghc monad to the IO monad

withGHC Source #

Arguments

:: FilePath

A target file displayed in an error message.

-> Ghc a

Ghc actions created by the Ghc utilities.

-> IO a 

Converting the Ghc monad to the IO monad.

withGHC' :: Ghc a -> IO a Source #

Initializing DynFlags

initializeFlagsWithCradle :: Options -> Cradle -> Ghc () Source #

Initialize the DynFlags relating to the compilation of a single file or GHC session according to the Cradle and Options provided.

Ghc utilities

boot :: Options -> Ghc String Source #

Printing necessary information for front-end booting.

browse Source #

Arguments

:: Options 
-> ModuleString

A module name. (e.g. "Data.List")

-> Ghc String 

Getting functions, classes, etc from a module. If detailed is True, their types are also obtained. If operators is True, operators are also returned.

check Source #

Arguments

:: Options 
-> [FilePath]

The target files.

-> Ghc (Either String String) 

Checking syntax of a target file using GHC. Warnings and errors are returned.

info Source #

Arguments

:: Options 
-> FilePath

A target file.

-> Expression

A Haskell expression.

-> Ghc String 

Obtaining information of a target expression. (GHCi's info:)

types Source #

Arguments

:: Options 
-> FilePath

A target file.

-> Int

Line number.

-> Int

Column number.

-> Ghc String 

Obtaining type of a target expression. (GHCi's type:)

modules :: Options -> Ghc String Source #

Listing installed modules.

SymMdlDb

type Symbol = String Source #

Type of key for SymMdlDb.

data SymMdlDb Source #

Database from Symbol to modules.

lookupSym :: Options -> Symbol -> SymMdlDb -> String Source #

Looking up SymMdlDb with Symbol to find modules.

Misc

getSystemLibDir :: IO (Maybe FilePath) Source #

Obtaining the directory for system libraries.

liftIO :: MonadIO m => IO a -> m a #

Lift a computation from the IO monad.

runGhc #

Arguments

:: Maybe FilePath

See argument to initGhcMonad.

-> 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.

data Ghc a #

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

Instances details
Monad Ghc 
Instance details

Defined in GhcMonad

Methods

(>>=) :: Ghc a -> (a -> Ghc b) -> Ghc b #

(>>) :: Ghc a -> Ghc b -> Ghc b #

return :: a -> Ghc a #

Functor Ghc 
Instance details

Defined in GhcMonad

Methods

fmap :: (a -> b) -> Ghc a -> Ghc b #

(<$) :: a -> Ghc b -> Ghc a #

MonadFix Ghc 
Instance details

Defined in GhcMonad

Methods

mfix :: (a -> Ghc a) -> Ghc a #

Applicative Ghc 
Instance details

Defined in GhcMonad

Methods

pure :: a -> Ghc a #

(<*>) :: Ghc (a -> b) -> Ghc a -> Ghc b #

liftA2 :: (a -> b -> c) -> Ghc a -> Ghc b -> Ghc c #

(*>) :: Ghc a -> Ghc b -> Ghc b #

(<*) :: Ghc a -> Ghc b -> Ghc a #

Alternative Ghc Source # 
Instance details

Defined in Hhp.Types

Methods

empty :: Ghc a #

(<|>) :: Ghc a -> Ghc a -> Ghc a #

some :: Ghc a -> Ghc [a] #

many :: Ghc a -> Ghc [a] #

MonadIO Ghc 
Instance details

Defined in GhcMonad

Methods

liftIO :: IO a -> Ghc a #

GhcMonad Ghc 
Instance details

Defined in GhcMonad

HasDynFlags Ghc 
Instance details

Defined in GhcMonad

ExceptionMonad Ghc 
Instance details

Defined in GhcMonad

Methods

gcatch :: Exception e => Ghc a -> (e -> Ghc a) -> Ghc a #

gmask :: ((Ghc a -> Ghc a) -> Ghc b) -> Ghc b #

gbracket :: Ghc a -> (a -> Ghc b) -> (a -> Ghc c) -> Ghc c #

gfinally :: Ghc a -> Ghc b -> Ghc a #