Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.Haskell.GhcMod.Types
- type IOish m = (Functor m, MonadIO m, MonadBaseControl IO m, ExceptionMonad m)
- type MonadIOC m = MonadIO m
- class MonadIOC m => MonadIO m where
- data OutputStyle
- newtype LineSeparator = LineSeparator String
- data FileMapping = FileMapping {}
- type FileMappingMap = Map FilePath FileMapping
- data ProgramSource
- data Programs = Programs {}
- data OutputOpts = OutputOpts {}
- data Options = Options {
- optOutput :: OutputOpts
- optPrograms :: Programs
- optGhcUserOptions :: [GHCOption]
- optOperators :: Bool
- optDetailed :: Bool
- optQualified :: Bool
- optHlintOpts :: [String]
- optFileMappings :: [(FilePath, Maybe FilePath)]
- defaultOptions :: Options
- data Project
- isCabalHelperProject :: Project -> Bool
- data StackEnv = StackEnv {}
- data Cradle = Cradle {}
- data GmStream
- data GhcModEnv = GhcModEnv {}
- data GhcModOut = GhcModOut {
- gmoOptions :: OutputOpts
- gmoChan :: Chan (Either (MVar ()) (GmStream, String))
- data GhcModLog = GhcModLog {
- gmLogLevel :: Maybe GmLogLevel
- gmLogVomitDump :: Last Bool
- gmLogMessages :: [(GmLogLevel, String, Doc)]
- data GmGhcSession = GmGhcSession {
- gmgsOptions :: ![GHCOption]
- gmgsSession :: !(IORef HscEnv)
- data GhcModCaches = GhcModCaches {
- gmcPackageDbStack :: CacheContents ChCacheData [GhcPkgDb]
- gmcMergedPkgOptions :: CacheContents ChCacheData [GHCOption]
- gmcComponents :: CacheContents ChCacheData [GmComponent GMCRaw ChEntrypoint]
- gmcResolvedComponents :: CacheContents [GmComponent GMCRaw (Set ModulePath)] (Map ChComponentName (GmComponent GMCResolved (Set ModulePath)))
- data GhcModState = GhcModState {}
- data CompilerMode
- defaultGhcModState :: GhcModState
- data GhcPkgDb
- type GHCOption = String
- type IncludeDir = FilePath
- type PackageBaseName = String
- type PackageVersion = String
- type PackageId = String
- type Package = (PackageBaseName, PackageVersion, PackageId)
- pkgName :: Package -> PackageBaseName
- pkgVer :: Package -> PackageVersion
- pkgId :: Package -> PackageId
- showPkg :: Package -> String
- showPkgId :: Package -> String
- newtype Expression = Expression {}
- newtype ModuleString = ModuleString {}
- data GmLogLevel
- type PkgDb = Map Package PackageConfig
- data GmModuleGraph = GmModuleGraph {
- gmgGraph :: Map ModulePath (Set ModulePath)
- data GmComponentType
- data GmComponent t eps = GmComponent {}
- data ModulePath = ModulePath {
- mpModule :: ModuleName
- mpPath :: FilePath
- data GhcModError
- = GMENoMsg
- | GMEString String
- | GMECabalConfigure GhcModError
- | GMEStackConfigure GhcModError
- | GMEStackBootstrap GhcModError
- | GMECabalCompAssignment [(Either FilePath ModuleName, Set ChComponentName)]
- | GMEProcess String String [String] (Either Int GhcModError)
- | GMENoCabalFile
- | GMETooManyCabalFiles [FilePath]
- | GMEWrongWorkingDirectory FilePath FilePath
- lGmcResolvedComponents :: forall cat. ArrowApply cat => Lens cat GhcModCaches (CacheContents [GmComponent GMCRaw (Set ModulePath)] (Map ChComponentName (GmComponent GMCResolved (Set ModulePath))))
- lGmcPackageDbStack :: forall cat. ArrowApply cat => Lens cat GhcModCaches (CacheContents ChCacheData [GhcPkgDb])
- lGmcMergedPkgOptions :: forall cat. ArrowApply cat => Lens cat GhcModCaches (CacheContents ChCacheData [GHCOption])
- lGmcComponents :: forall cat. ArrowApply cat => Lens cat GhcModCaches (CacheContents ChCacheData [GmComponent GMCRaw ChEntrypoint])
- lGmMMappedFiles :: forall cat. ArrowApply cat => Lens cat GhcModState FileMappingMap
- lGmGhcSession :: forall cat. ArrowApply cat => Lens cat GhcModState (Maybe GmGhcSession)
- lGmComponents :: forall cat. ArrowApply cat => Lens cat GhcModState (Map ChComponentName (GmComponent GMCResolved (Set ModulePath)))
- lGmCompilerMode :: forall cat. ArrowApply cat => Lens cat GhcModState CompilerMode
- lGmCaches :: forall cat. ArrowApply cat => Lens cat GhcModState GhcModCaches
- lOptQualified :: forall cat. ArrowApply cat => Lens cat Options Bool
- lOptPrograms :: forall cat. ArrowApply cat => Lens cat Options Programs
- lOptOutput :: forall cat. ArrowApply cat => Lens cat Options OutputOpts
- lOptOperators :: forall cat. ArrowApply cat => Lens cat Options Bool
- lOptHlintOpts :: forall cat. ArrowApply cat => Lens cat Options [String]
- lOptGhcUserOptions :: forall cat. ArrowApply cat => Lens cat Options [GHCOption]
- lOptFileMappings :: forall cat. ArrowApply cat => Lens cat Options [(FilePath, Maybe FilePath)]
- lOptDetailed :: forall cat. ArrowApply cat => Lens cat Options Bool
- lOoptStyle :: forall cat. ArrowApply cat => Lens cat OutputOpts OutputStyle
- lOoptLogLevel :: forall cat. ArrowApply cat => Lens cat OutputOpts GmLogLevel
- lOoptLineSeparator :: forall cat. ArrowApply cat => Lens cat OutputOpts LineSeparator
- lOoptLinePrefix :: forall cat. ArrowApply cat => Lens cat OutputOpts (Maybe (String, String))
- lStackProgram :: forall cat. ArrowApply cat => Lens cat Programs FilePath
- lGhcProgram :: forall cat. ArrowApply cat => Lens cat Programs FilePath
- lGhcPkgProgram :: forall cat. ArrowApply cat => Lens cat Programs FilePath
- lCabalProgram :: forall cat. ArrowApply cat => Lens cat Programs FilePath
- data ModuleName :: *
- mkModuleName :: String -> ModuleName
- moduleNameString :: ModuleName -> String
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.
data OutputStyle Source
Output style.
Constructors
LispStyle | S expression style. |
PlainStyle | Plain textstyle. |
Instances
newtype LineSeparator Source
The type for line separator. Historically, a Null string is used.
Constructors
LineSeparator String |
Instances
type FileMappingMap = Map FilePath FileMapping Source
data ProgramSource Source
Constructors
ProgramSourceUser | |
ProgramSourceStack |
Constructors
Programs | |
Fields
|
data OutputOpts Source
Constructors
OutputOpts | |
Fields
|
Instances
Constructors
Options | |
Fields
|
defaultOptions :: Options Source
A default Options
.
Constructors
CabalProject | |
SandboxProject | |
PlainProject | |
StackProject StackEnv |
Constructors
StackEnv | |
Fields
|
The environment where this library is used.
Constructors
Cradle | |
Fields
|
Constructors
GhcModOut | |
Fields
|
Constructors
GhcModLog | |
Fields
|
data GmGhcSession Source
Constructors
GmGhcSession | |
Fields
|
data GhcModCaches Source
Constructors
data GhcModState Source
Constructors
GhcModState | |
Fields
|
Instances
Monad m => GmState (StateT GhcModState m) Source |
GHC package database flags.
type IncludeDir = FilePath Source
An include directory for modules.
type PackageBaseName = String Source
A package name.
type PackageVersion = String Source
A package version.
type Package = (PackageBaseName, PackageVersion, PackageId) Source
A package's name, verson and id.
pkgName :: Package -> PackageBaseName Source
pkgVer :: Package -> PackageVersion Source
data GmLogLevel Source
type PkgDb = Map Package PackageConfig Source
Collection of packages
data GmModuleGraph Source
Constructors
GmModuleGraph | |
Fields
|
data GmComponentType Source
Constructors
GMCRaw | |
GMCResolved |
data GmComponent t eps Source
Constructors
GmComponent | |
Fields
|
Instances
Functor (GmComponent t) Source | |
Eq eps => Eq (GmComponent t eps) Source | |
Ord eps => Ord (GmComponent t eps) Source | |
Read eps => Read (GmComponent t eps) Source | |
Show eps => Show (GmComponent t eps) Source | |
Generic (GmComponent t eps) Source | |
Serialize eps => Serialize (GmComponent t eps) Source | |
type Rep (GmComponent t eps) Source |
data ModulePath Source
Constructors
ModulePath | |
Fields
|
data GhcModError Source
Constructors
GMENoMsg | Unknown error |
GMEString String | Some Error with a message. These are produced mostly by
|
GMECabalConfigure GhcModError | Configuring a cabal project failed. |
GMEStackConfigure GhcModError | Configuring a stack project failed. |
GMEStackBootstrap GhcModError | Bootstrapping |
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. |
GMEWrongWorkingDirectory FilePath FilePath |
Instances
Eq GhcModError Source | |
Show GhcModError Source | |
Exception GhcModError Source | |
Error GhcModError Source | |
Monad m => MonadError GhcModError (GmlT m) | |
Monad m => MonadError GhcModError (GmT m) | |
GmEnv m => GmEnv (ErrorT GhcModError m) Source |
lGmcResolvedComponents :: forall cat. ArrowApply cat => Lens cat GhcModCaches (CacheContents [GmComponent GMCRaw (Set ModulePath)] (Map ChComponentName (GmComponent GMCResolved (Set ModulePath)))) Source
lGmcPackageDbStack :: forall cat. ArrowApply cat => Lens cat GhcModCaches (CacheContents ChCacheData [GhcPkgDb]) Source
lGmcMergedPkgOptions :: forall cat. ArrowApply cat => Lens cat GhcModCaches (CacheContents ChCacheData [GHCOption]) Source
lGmcComponents :: forall cat. ArrowApply cat => Lens cat GhcModCaches (CacheContents ChCacheData [GmComponent GMCRaw ChEntrypoint]) Source
lGmMMappedFiles :: forall cat. ArrowApply cat => Lens cat GhcModState FileMappingMap Source
lGmGhcSession :: forall cat. ArrowApply cat => Lens cat GhcModState (Maybe GmGhcSession) Source
lGmComponents :: forall cat. ArrowApply cat => Lens cat GhcModState (Map ChComponentName (GmComponent GMCResolved (Set ModulePath))) Source
lGmCompilerMode :: forall cat. ArrowApply cat => Lens cat GhcModState CompilerMode Source
lGmCaches :: forall cat. ArrowApply cat => Lens cat GhcModState GhcModCaches Source
lOptQualified :: forall cat. ArrowApply cat => Lens cat Options Bool Source
lOptPrograms :: forall cat. ArrowApply cat => Lens cat Options Programs Source
lOptOutput :: forall cat. ArrowApply cat => Lens cat Options OutputOpts Source
lOptOperators :: forall cat. ArrowApply cat => Lens cat Options Bool Source
lOptHlintOpts :: forall cat. ArrowApply cat => Lens cat Options [String] Source
lOptGhcUserOptions :: forall cat. ArrowApply cat => Lens cat Options [GHCOption] Source
lOptFileMappings :: forall cat. ArrowApply cat => Lens cat Options [(FilePath, Maybe FilePath)] Source
lOptDetailed :: forall cat. ArrowApply cat => Lens cat Options Bool Source
lOoptStyle :: forall cat. ArrowApply cat => Lens cat OutputOpts OutputStyle Source
lOoptLogLevel :: forall cat. ArrowApply cat => Lens cat OutputOpts GmLogLevel Source
lOoptLineSeparator :: forall cat. ArrowApply cat => Lens cat OutputOpts LineSeparator Source
lOoptLinePrefix :: forall cat. ArrowApply cat => Lens cat OutputOpts (Maybe (String, String)) Source
lStackProgram :: forall cat. ArrowApply cat => Lens cat Programs FilePath Source
lGhcProgram :: forall cat. ArrowApply cat => Lens cat Programs FilePath Source
lGhcPkgProgram :: forall cat. ArrowApply cat => Lens cat Programs FilePath Source
lCabalProgram :: forall cat. ArrowApply cat => Lens cat Programs FilePath Source
data ModuleName :: *
A ModuleName is essentially a simple string, e.g. Data.List
.
mkModuleName :: String -> ModuleName
moduleNameString :: ModuleName -> String