Safe Haskell | None |
---|---|
Language | Haskell2010 |
- 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 {}
- 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 {}
- defaultGhcModState :: GhcModState
- data GhcPkgDb
- type GHCOption = String
- type IncludeDir = FilePath
- newtype Expression = Expression {}
- newtype ModuleString = ModuleString {}
- data GmLogLevel
- 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]
- data LintOpts = LintOpts {
- optLintHlintOpts :: [String]
- defaultLintOpts :: LintOpts
- data BrowseOpts = BrowseOpts {}
- defaultBrowseOpts :: BrowseOpts
- 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)
- lGmCaches :: forall cat. ArrowApply cat => Lens cat GhcModState GhcModCaches
- lOptPrograms :: forall cat. ArrowApply cat => Lens cat Options Programs
- lOptOutput :: forall cat. ArrowApply cat => Lens cat Options OutputOpts
- lOptGhcUserOptions :: forall cat. ArrowApply cat => Lens cat Options [GHCOption]
- lOptFileMappings :: forall cat. ArrowApply cat => Lens cat Options [(FilePath, Maybe FilePath)]
- lOptEncoding :: forall cat. ArrowApply cat => Lens cat Options String
- 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.
newtype LineSeparator Source #
The type for line separator. Historically, a Null string is used.
type FileMappingMap = Map FilePath FileMapping Source #
Programs | |
|
data OutputOpts Source #
OutputOpts | |
|
Options | |
|
defaultOptions :: Options Source #
A default Options
.
isCabalHelperProject :: Project -> Bool Source #
StackEnv | |
|
The environment where this library is used.
Cradle | |
|
GhcModOut | |
|
GhcModLog | |
|
data GmGhcSession Source #
GmGhcSession | |
|
data GhcModCaches Source #
data GhcModState Source #
GHC package database flags.
type IncludeDir = FilePath Source #
An include directory for modules.
newtype Expression Source #
Haskell expression.
newtype ModuleString Source #
Module name.
data GmLogLevel Source #
data GmModuleGraph Source #
data GmComponent t eps Source #
GmComponent | |
|
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 # | |
Binary eps => Binary (GmComponent t eps) Source # | |
type Rep (GmComponent t eps) Source # | |
data ModulePath Source #
data GhcModError Source #
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. |
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 # | |
Options for "lintWith" function
LintOpts | |
|
defaultLintOpts :: LintOpts Source #
Default LintOpts instance
data BrowseOpts Source #
Options for "browseWith" function
BrowseOpts | |
|
defaultBrowseOpts :: BrowseOpts Source #
Default BrowseOpts instance
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 #
lGmCaches :: forall cat. ArrowApply cat => Lens cat GhcModState GhcModCaches Source #
lOptPrograms :: forall cat. ArrowApply cat => Lens cat Options Programs Source #
lOptOutput :: forall cat. ArrowApply cat => Lens cat Options OutputOpts Source #
lOptGhcUserOptions :: forall cat. ArrowApply cat => Lens cat Options [GHCOption] Source #
lOptFileMappings :: forall cat. ArrowApply cat => Lens cat Options [(FilePath, Maybe FilePath)] Source #
lOptEncoding :: forall cat. ArrowApply cat => Lens cat Options String 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 #