ghc-mod-5.6.0.0: Happy Haskell Programming

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.GhcMod.Types

Contents

Synopsis

Documentation

type IOish m = (Functor m, MonadIO m, MonadBaseControl IO m, ExceptionMonad m) Source #

A constraint alias (-XConstraintKinds) to make functions dealing with GhcModT somewhat cleaner.

Basicially an IOish m => m is a Monad supporting arbitrary IO and exception handling. Usually this will simply be IO but we parametrise it in the exported API so users have the option to use a custom inner monad.

class MonadIOC m => MonadIO m where Source #

Minimal complete definition

liftIO

Methods

liftIO :: IO a -> m a Source #

data OutputStyle Source #

Output style.

Constructors

LispStyle

S expression style.

PlainStyle

Plain textstyle.

newtype LineSeparator Source #

The type for line separator. Historically, a Null string is used.

Constructors

LineSeparator String 

data Programs Source #

Constructors

Programs 

Fields

data OutputOpts Source #

Constructors

OutputOpts 

Fields

data Options Source #

Constructors

Options 

Fields

Instances

data Cradle Source #

The environment where this library is used.

Constructors

Cradle 

Fields

data GhcModEnv Source #

Constructors

GhcModEnv 

data GhcPkgDb Source #

GHC package database flags.

Instances

Eq GhcPkgDb Source # 
Show GhcPkgDb Source # 
Generic GhcPkgDb Source # 

Associated Types

type Rep GhcPkgDb :: * -> * #

Methods

from :: GhcPkgDb -> Rep GhcPkgDb x #

to :: Rep GhcPkgDb x -> GhcPkgDb #

Binary GhcPkgDb Source # 

Methods

put :: GhcPkgDb -> Put #

get :: Get GhcPkgDb #

putList :: [GhcPkgDb] -> Put #

type Rep GhcPkgDb Source # 
type Rep GhcPkgDb = D1 (MetaData "GhcPkgDb" "Language.Haskell.GhcMod.Types" "ghc-mod-5.6.0.0-DrWbB7VrwRGAyCXFhpJdY" False) ((:+:) (C1 (MetaCons "GlobalDb" PrefixI False) U1) ((:+:) (C1 (MetaCons "UserDb" PrefixI False) U1) (C1 (MetaCons "PackageDb" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))

type GHCOption = String Source #

A single GHC command line option.

type IncludeDir = FilePath Source #

An include directory for modules.

data GmModuleGraph Source #

Instances

Eq GmModuleGraph Source # 
Ord GmModuleGraph Source # 
Read GmModuleGraph Source # 
Show GmModuleGraph Source # 
Generic GmModuleGraph Source # 

Associated Types

type Rep GmModuleGraph :: * -> * #

Monoid GmModuleGraph Source # 
Binary GmModuleGraph Source # 
type Rep GmModuleGraph Source # 
type Rep GmModuleGraph = D1 (MetaData "GmModuleGraph" "Language.Haskell.GhcMod.Types" "ghc-mod-5.6.0.0-DrWbB7VrwRGAyCXFhpJdY" False) (C1 (MetaCons "GmModuleGraph" PrefixI True) (S1 (MetaSel (Just Symbol "gmgGraph") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map ModulePath (Set ModulePath)))))

data GmComponent t eps Source #

Instances

Functor (GmComponent t) Source # 

Methods

fmap :: (a -> b) -> GmComponent t a -> GmComponent t b #

(<$) :: a -> GmComponent t b -> GmComponent t a #

Eq eps => Eq (GmComponent t eps) Source # 

Methods

(==) :: GmComponent t eps -> GmComponent t eps -> Bool #

(/=) :: GmComponent t eps -> GmComponent t eps -> Bool #

Ord eps => Ord (GmComponent t eps) Source # 

Methods

compare :: GmComponent t eps -> GmComponent t eps -> Ordering #

(<) :: GmComponent t eps -> GmComponent t eps -> Bool #

(<=) :: GmComponent t eps -> GmComponent t eps -> Bool #

(>) :: GmComponent t eps -> GmComponent t eps -> Bool #

(>=) :: GmComponent t eps -> GmComponent t eps -> Bool #

max :: GmComponent t eps -> GmComponent t eps -> GmComponent t eps #

min :: GmComponent t eps -> GmComponent t eps -> GmComponent t eps #

Read eps => Read (GmComponent t eps) Source # 
Show eps => Show (GmComponent t eps) Source # 

Methods

showsPrec :: Int -> GmComponent t eps -> ShowS #

show :: GmComponent t eps -> String #

showList :: [GmComponent t eps] -> ShowS #

Generic (GmComponent t eps) Source # 

Associated Types

type Rep (GmComponent t eps) :: * -> * #

Methods

from :: GmComponent t eps -> Rep (GmComponent t eps) x #

to :: Rep (GmComponent t eps) x -> GmComponent t eps #

Binary eps => Binary (GmComponent t eps) Source # 

Methods

put :: GmComponent t eps -> Put #

get :: Get (GmComponent t eps) #

putList :: [GmComponent t eps] -> Put #

type Rep (GmComponent t eps) Source # 

data ModulePath Source #

Constructors

ModulePath 

data GhcModError Source #

Constructors

GMENoMsg

Unknown error

GMEString String

Some Error with a message. These are produced mostly by fail calls on GhcModT.

GMECabalConfigure GhcModError

Configuring a cabal project failed.

GMEStackConfigure GhcModError

Configuring a stack project failed.

GMEStackBootstrap GhcModError

Bootstrapping stack environment failed (process exited with failure)

GMECabalCompAssignment [(Either FilePath ModuleName, Set ChComponentName)]

Could not find a consistent component assignment for modules

GMEProcess String String [String] (Either Int GhcModError)

Launching an operating system process failed. Fields in order: function, command, arguments, (stdout, stderr, exitcode)

GMENoCabalFile

No cabal file found.

GMETooManyCabalFiles [FilePath]

Too many cabal files found.

data LintOpts Source #

Options for "lintWith" function

Constructors

LintOpts 

Fields

data BrowseOpts Source #

Options for "browseWith" function

Constructors

BrowseOpts 

Fields

lOptPrograms :: forall cat. ArrowApply cat => Lens cat Options Programs Source #

lOptOutput :: forall cat. ArrowApply cat => Lens cat Options OutputOpts Source #

lOptEncoding :: forall cat. ArrowApply cat => Lens cat Options String Source #

lGhcProgram :: forall cat. ArrowApply cat => Lens cat Programs FilePath Source #

data ModuleName :: * #

A ModuleName is essentially a simple string, e.g. Data.List.

Instances

Eq ModuleName 
Data ModuleName 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleName -> c ModuleName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleName #

toConstr :: ModuleName -> Constr #

dataTypeOf :: ModuleName -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ModuleName) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleName) #

gmapT :: (forall b. Data b => b -> b) -> ModuleName -> ModuleName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r #

gmapQ :: (forall d. Data d => d -> u) -> ModuleName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName #

Ord ModuleName 
Binary ModuleName 
Uniquable ModuleName 
Outputable ModuleName 
BinaryStringRep ModuleName 

Orphan instances