Safe Haskell | None |
---|---|
Language | Haskell2010 |
A Shake implementation of the compiler service, built using the Shaker abstraction layer for in-memory use.
Synopsis
- data IdeState
- data GetParsedModule = GetParsedModule
- newtype TransitiveDependencies = TransitiveDependencies {}
- newtype Priority = Priority Double
- data GhcSessionIO = GhcSessionIO
- data GetClientSettings = GetClientSettings
- priorityTypeCheck :: Priority
- priorityGenerateCore :: Priority
- priorityFilesOfInterest :: Priority
- runAction :: String -> IdeState -> Action a -> IO a
- toIdeResult :: Either [FileDiagnostic] v -> IdeResult v
- defineNoFile :: IdeRule k v => (k -> Action v) -> Rules ()
- defineEarlyCutOffNoFile :: IdeRule k v => (k -> Action (ByteString, v)) -> Rules ()
- mainRule :: RulesConfig -> Rules ()
- data RulesConfig = RulesConfig {}
- getDependencies :: NormalizedFilePath -> Action (Maybe [NormalizedFilePath])
- getParsedModule :: NormalizedFilePath -> Action (Maybe ParsedModule)
- getParsedModuleWithComments :: NormalizedFilePath -> Action (Maybe ParsedModule)
- getClientConfigAction :: Config -> Action Config
- usePropertyAction :: HasProperty s k t r => KeyNameProxy s -> PluginId -> Properties r -> Action (ToHsType t)
- newtype CompiledLinkables = CompiledLinkables {}
- data IsHiFileStable = IsHiFileStable
- getParsedModuleRule :: Rules ()
- getParsedModuleWithCommentsRule :: Rules ()
- getLocatedImportsRule :: Rules ()
- getDependencyInformationRule :: Rules ()
- reportImportCyclesRule :: Rules ()
- typeCheckRule :: Rules ()
- getDocMapRule :: Rules ()
- loadGhcSession :: GhcSessionDepsConfig -> Rules ()
- getModIfaceFromDiskRule :: Rules ()
- getModIfaceRule :: Rules ()
- getModSummaryRule :: Rules ()
- isHiFileStableRule :: Rules ()
- getModuleGraphRule :: Rules ()
- knownFilesRule :: Rules ()
- getClientSettingsRule :: Rules ()
- getHieAstsRule :: Rules ()
- getBindingsRule :: Rules ()
- needsCompilationRule :: NormalizedFilePath -> Action (IdeResultNoDiagnosticsEarlyCutoff (Maybe LinkableType))
- computeLinkableTypeForDynFlags :: DynFlags -> LinkableType
- generateCoreRule :: Rules ()
- getImportMapRule :: Rules ()
- regenerateHiFile :: HscEnvEq -> NormalizedFilePath -> ModSummary -> Maybe LinkableType -> Action ([FileDiagnostic], Maybe HiFileResult)
- ghcSessionDepsDefinition :: Bool -> GhcSessionDepsConfig -> HscEnvEq -> NormalizedFilePath -> Action (Maybe HscEnvEq)
- getParsedModuleDefinition :: HscEnv -> IdeOptions -> NormalizedFilePath -> ModSummary -> IO ([FileDiagnostic], Maybe ParsedModule)
- typeCheckRuleDefinition :: HscEnv -> ParsedModule -> Action (IdeResult TcModuleResult)
- newtype GhcSessionDepsConfig = GhcSessionDepsConfig {}
Types
A Shake database plus persistent store. Can be thought of as storing
mappings from (FilePath, k)
to RuleResult k
.
data GetParsedModule Source #
Instances
newtype TransitiveDependencies Source #
TransitiveDependencies | |
|
Instances
data GhcSessionIO Source #
Instances
Eq GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes (==) :: GhcSessionIO -> GhcSessionIO -> Bool # (/=) :: GhcSessionIO -> GhcSessionIO -> Bool # | |
Show GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes showsPrec :: Int -> GhcSessionIO -> ShowS # show :: GhcSessionIO -> String # showList :: [GhcSessionIO] -> ShowS # | |
Generic GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes type Rep GhcSessionIO :: Type -> Type # from :: GhcSessionIO -> Rep GhcSessionIO x # to :: Rep GhcSessionIO x -> GhcSessionIO # | |
Hashable GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes hashWithSalt :: Int -> GhcSessionIO -> Int # hash :: GhcSessionIO -> Int # | |
NFData GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes rnf :: GhcSessionIO -> () # | |
type Rep GhcSessionIO Source # | |
type RuleResult GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes |
data GetClientSettings Source #
Get the vscode client settings stored in the ide state
Instances
Functions
toIdeResult :: Either [FileDiagnostic] v -> IdeResult v Source #
This is useful for rules to convert rules that can only produce errors or a result into the more general IdeResult type that supports producing warnings while also producing a result.
defineEarlyCutOffNoFile :: IdeRule k v => (k -> Action (ByteString, v)) -> Rules () Source #
mainRule :: RulesConfig -> Rules () Source #
A rule that wires per-file rules together
data RulesConfig Source #
RulesConfig | |
|
Instances
Default RulesConfig Source # | |
Defined in Development.IDE.Core.Rules def :: RulesConfig # |
getDependencies :: NormalizedFilePath -> Action (Maybe [NormalizedFilePath]) Source #
Get all transitive file dependencies of a given module. Does not include the file itself.
getParsedModule :: NormalizedFilePath -> Action (Maybe ParsedModule) Source #
Parse the contents of a haskell file.
getParsedModuleWithComments :: NormalizedFilePath -> Action (Maybe ParsedModule) Source #
Parse the contents of a haskell file, ensuring comments are preserved in annotations
getClientConfigAction Source #
Returns the client configurarion stored in the IdeState. You can use this function to access it from shake Rules
usePropertyAction :: HasProperty s k t r => KeyNameProxy s -> PluginId -> Properties r -> Action (ToHsType t) Source #
Rules
newtype CompiledLinkables Source #
Tracks which linkables are current, so we don't need to unload them
Instances
data IsHiFileStable Source #
Given the path to a module src file, this rule returns True if the corresponding `.hi` file is stable, that is, if it is newer than the src file, and all its dependencies are stable too.
Instances
Eq IsHiFileStable Source # | |
Defined in Development.IDE.Core.Rules (==) :: IsHiFileStable -> IsHiFileStable -> Bool # (/=) :: IsHiFileStable -> IsHiFileStable -> Bool # | |
Show IsHiFileStable Source # | |
Defined in Development.IDE.Core.Rules showsPrec :: Int -> IsHiFileStable -> ShowS # show :: IsHiFileStable -> String # showList :: [IsHiFileStable] -> ShowS # | |
Generic IsHiFileStable Source # | |
Defined in Development.IDE.Core.Rules type Rep IsHiFileStable :: Type -> Type # from :: IsHiFileStable -> Rep IsHiFileStable x # to :: Rep IsHiFileStable x -> IsHiFileStable # | |
Hashable IsHiFileStable Source # | |
Defined in Development.IDE.Core.Rules hashWithSalt :: Int -> IsHiFileStable -> Int # hash :: IsHiFileStable -> Int # | |
NFData IsHiFileStable Source # | |
Defined in Development.IDE.Core.Rules rnf :: IsHiFileStable -> () # | |
type Rep IsHiFileStable Source # | |
type RuleResult IsHiFileStable Source # | |
Defined in Development.IDE.Core.Rules |
getParsedModuleRule :: Rules () Source #
WARNING:
We currently parse the module both with and without Opt_Haddock, and
return the one with Haddocks if it -- succeeds. However, this may not work
for hlint or any client code that might need the parsed source with all
annotations, including comments.
For that use case you might want to use getParsedModuleWithCommentsRule
See https://github.com/haskell/ghcide/pull/350#discussion_r370878197
and https://github.com/mpickering/ghcide/pull/22#issuecomment-625070490
GHC wiki about: https://gitlab.haskell.org/ghc/ghc/-/wikis/api-annotations
getParsedModuleWithCommentsRule :: Rules () Source #
This rule provides a ParsedModule preserving all annotations, including keywords, punctuation and comments. So it is suitable for use cases where you need a perfect edit.
getLocatedImportsRule :: Rules () Source #
reportImportCyclesRule :: Rules () Source #
typeCheckRule :: Rules () Source #
Typechecks a module.
getDocMapRule :: Rules () Source #
loadGhcSession :: GhcSessionDepsConfig -> Rules () Source #
getModIfaceFromDiskRule :: Rules () Source #
Load a iface from disk, or generate it if there isn't one or it is out of date This rule also ensures that the `.hie` and `.o` (if needed) files are written out.
getModIfaceRule :: Rules () Source #
getModSummaryRule :: Rules () Source #
isHiFileStableRule :: Rules () Source #
getModuleGraphRule :: Rules () Source #
knownFilesRule :: Rules () Source #
getClientSettingsRule :: Rules () Source #
getHieAstsRule :: Rules () Source #
getBindingsRule :: Rules () Source #
needsCompilationRule :: NormalizedFilePath -> Action (IdeResultNoDiagnosticsEarlyCutoff (Maybe LinkableType)) Source #
computeLinkableTypeForDynFlags :: DynFlags -> LinkableType Source #
How should we compile this module? (assuming we do in fact need to compile it). Depends on whether it uses unboxed tuples or sums
generateCoreRule :: Rules () Source #
getImportMapRule :: Rules () Source #
regenerateHiFile :: HscEnvEq -> NormalizedFilePath -> ModSummary -> Maybe LinkableType -> Action ([FileDiagnostic], Maybe HiFileResult) Source #
Also generates and indexes the `.hie` file, along with the `.o` file if needed Invariant maintained is that if the `.hi` file was successfully written, then the `.hie` and `.o` file (if needed) were also successfully written
ghcSessionDepsDefinition Source #
:: Bool | full mod summary |
-> GhcSessionDepsConfig | |
-> HscEnvEq | |
-> NormalizedFilePath | |
-> Action (Maybe HscEnvEq) |
getParsedModuleDefinition :: HscEnv -> IdeOptions -> NormalizedFilePath -> ModSummary -> IO ([FileDiagnostic], Maybe ParsedModule) Source #
newtype GhcSessionDepsConfig Source #
Instances
Default GhcSessionDepsConfig Source # | |
Defined in Development.IDE.Core.Rules |