Safe Haskell | None |
---|---|
Language | GHC2021 |
Development.IDE
Synopsis
- module Development.IDE.Core.RuleTypes
- module Development.IDE.GHC.Error
- module Development.IDE.GHC.Util
- module Development.IDE.Plugin
- module Development.IDE.Types.Diagnostics
- module Development.IDE.Types.Location
- module Ide.Logger
- data RuleBody k v
- = Rule (k -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult v))
- | RuleNoDiagnostics (k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v))
- | RuleWithCustomNewnessCheck {
- newnessCheck :: ByteString -> ByteString -> Bool
- build :: k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v)
- | RuleWithOldValue (k -> NormalizedFilePath -> Value v -> Action (Maybe ByteString, IdeResult v))
- data IdeConfiguration = IdeConfiguration {}
- use :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe v)
- ghcVersion :: GhcVersion
- data Action a
- data Rules a
- type family RuleResult key
- action :: Action a -> Rules ()
- getClientConfig :: MonadLsp Config m => m Config
- uses :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f (Maybe v))
- getAtPoint :: NormalizedFilePath -> Position -> IdeAction (Maybe (Maybe Range, [Text]))
- getDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location])
- getTypeDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location])
- getFileExists :: NormalizedFilePath -> Action Bool
- getFileContents :: NormalizedFilePath -> Action (UTCTime, Maybe Text)
- isWorkspaceFile :: NormalizedFilePath -> Action Bool
- getFilesOfInterestUntracked :: Action (HashMap NormalizedFilePath FileOfInterestStatus)
- getClientConfigAction :: Action Config
- getParsedModule :: NormalizedFilePath -> Action (Maybe ParsedModule)
- usePropertyAction :: forall (s :: Symbol) (k :: PropertyKey) (t :: PropertyType) (r :: [PropertyKey]). HasProperty s k t r => KeyNameProxy s -> PluginId -> Properties r -> Action (ToHsType t)
- runAction :: String -> IdeState -> Action a -> IO a
- data FastResult a = FastResult {}
- newtype IdeAction a = IdeAction {}
- type IdeRule k v = (RuleResult k ~ v, ShakeValue k, Show v, Typeable v, NFData v)
- data IdeState
- data ShakeExtras
- data VFSModified
- actionLogger :: Action Logger
- define :: IdeRule k v => Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (IdeResult v)) -> Rules ()
- defineEarlyCutoff :: IdeRule k v => Recorder (WithPriority Log) -> RuleBody k v -> Rules ()
- defineNoDiagnostics :: IdeRule k v => Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (Maybe v)) -> Rules ()
- getPluginConfigAction :: PluginId -> Action PluginConfig
- ideLogger :: IdeState -> Logger
- runIdeAction :: String -> ShakeExtras -> IdeAction a -> IO a
- useNoFile :: IdeRule k v => k -> Action (Maybe v)
- useNoFile_ :: IdeRule k v => k -> Action v
- useWithStale :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping))
- useWithStaleFast :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (Maybe (v, PositionMapping))
- useWithStaleFast' :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (FastResult v)
- useWithStale_ :: IdeRule k v => k -> NormalizedFilePath -> Action (v, PositionMapping)
- use_ :: IdeRule k v => k -> NormalizedFilePath -> Action v
- uses_ :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f v)
- data GhcVersion
- data HscEnvEq
- hscEnvWithImportPaths :: HscEnvEq -> HscEnv
Documentation
module Development.IDE.GHC.Error
module Development.IDE.GHC.Util
module Development.IDE.Plugin
module Ide.Logger
Constructors
Rule (k -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult v)) | |
RuleNoDiagnostics (k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v)) | |
RuleWithCustomNewnessCheck | |
Fields
| |
RuleWithOldValue (k -> NormalizedFilePath -> Value v -> Action (Maybe ByteString, IdeResult v)) |
data IdeConfiguration #
Lsp client relevant configuration details
Constructors
IdeConfiguration | |
Fields |
Instances
Show IdeConfiguration # | |
Defined in Development.IDE.Core.IdeConfiguration Methods showsPrec :: Int -> IdeConfiguration -> ShowS # show :: IdeConfiguration -> String # showList :: [IdeConfiguration] -> ShowS # |
use :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe v) #
Request a Rule result if available
An action representing something that can be run as part of a Rule
.
Action
s can be pure functions but also have access to IO
via MonadIO
and 'MonadUnliftIO.
It should be assumed that actions throw exceptions, these can be caught with
actionCatch
. In particular, it is
permissible to use the MonadFail
instance, which will lead to an IOException
.
Instances
MonadFail Action | |
Defined in Development.IDE.Graph.Internal.Types | |
MonadIO Action | |
Defined in Development.IDE.Graph.Internal.Types | |
Applicative Action | |
Functor Action | |
Monad Action | |
MonadCatch Action | |
Defined in Development.IDE.Graph.Internal.Types | |
MonadMask Action | |
Defined in Development.IDE.Graph.Internal.Types Methods mask :: HasCallStack => ((forall a. Action a -> Action a) -> Action b) -> Action b # uninterruptibleMask :: HasCallStack => ((forall a. Action a -> Action a) -> Action b) -> Action b # generalBracket :: HasCallStack => Action a -> (a -> ExitCase b -> Action c) -> (a -> Action b) -> Action (b, c) # | |
MonadThrow Action | |
Defined in Development.IDE.Graph.Internal.Types Methods throwM :: (HasCallStack, Exception e) => e -> Action a # | |
MonadUnliftIO Action | |
Defined in Development.IDE.Graph.Internal.Types |
A computation that defines all the rules that form part of the computation graph.
Rules
has access to IO
through MonadIO
. Use of IO
is at your own risk: if
you write Rules
that throw exceptions, then you need to make sure to handle them
yourself when you run the resulting Rules
.
type family RuleResult key #
The type mapping between the key
or a rule and the resulting value
.
Instances
type RuleResult AddWatchedFile # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GenerateCore # | Convert to Core, requires TypeCheck* |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetBindings # | A IntervalMap telling us what is in scope at each point |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetClientSettings # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetDocMap # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetFileContents # | Get the contents of a file, either dirty (if the buffer is modified) or Nothing to mean use from disk. |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetFileExists # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetHieAst # | The uncompressed HieAST |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetImportMap # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetKnownTargets # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetLinkable # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetLocatedImports # | Resolve the imports in a module to the file path of a module in the same package |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetModIface # | Get a module interface details, either from an interface file or a typechecked module |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetModIfaceFromDisk # | Read the module interface file from disk. Throws an error for VFS files.
This is an internal rule, use |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetModIfaceFromDiskAndIndex # | GetModIfaceFromDisk and index the `.hie` file into the database.
This is an internal rule, use |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetModSummary # | Generate a ModSummary that has enough information to be used to get .hi and .hie files. without needing to parse the entire source |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetModSummaryWithoutTimestamps # | Generate a ModSummary with the timestamps and preprocessed content elided, for more successful early cutoff |
type RuleResult GetModificationTime # | Get the modification time of a file. |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetModuleGraph # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetParsedModule # | The parse tree for the file using GetFileContents |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetParsedModuleWithComments # | The parse tree for the file using GetFileContents, all comments included using Opt_KeepRawTokenStream |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GhcSession # | A GHC session that we reuse. |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GhcSessionDeps # | A GHC session preloaded with all the dependencies This rule is also responsible for calling ReportImportCycles for the direct dependencies |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GhcSessionIO # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult IsFileOfInterest # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult NeedsCompilation # | Does this module need to be compiled? |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult ReportImportCycles # | This rule is used to report import cycles. It depends on GetModuleGraph. We cannot report the cycles directly from GetModuleGraph since we can only report diagnostics for the current file. |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult TypeCheck # | The type checked version of this file, requires TypeCheck+ |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult LocalCompletions # | Produce completions info for a file |
Defined in Development.IDE.Plugin.Completions.Types | |
type RuleResult NonLocalCompletions # | |
type RuleResult GetGlobalBindingTypeSigs # | |
type RuleResult (Q k) # | |
Defined in Development.IDE.Types.Shake |
getClientConfig :: MonadLsp Config m => m Config #
Returns the current client configuration. It is not wise to permanently cache the returned value of this function, as clients can at runtime change their configuration.
uses :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f (Maybe v)) #
Plural version of use
getAtPoint :: NormalizedFilePath -> Position -> IdeAction (Maybe (Maybe Range, [Text])) #
Try to get hover text for the name under point.
getDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location]) #
Goto Definition.
getTypeDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location]) #
getFileExists :: NormalizedFilePath -> Action Bool #
Returns True if the file exists
getFileContents :: NormalizedFilePath -> Action (UTCTime, Maybe Text) #
Returns the modification time and the contents. For VFS paths, the modification time is the current time.
getClientConfigAction :: Action Config #
Returns the client configuration, creating a build dependency. You should always use this function when accessing client configuration from build rules.
getParsedModule :: NormalizedFilePath -> Action (Maybe ParsedModule) #
Parse the contents of a haskell file.
usePropertyAction :: forall (s :: Symbol) (k :: PropertyKey) (t :: PropertyType) (r :: [PropertyKey]). HasProperty s k t r => KeyNameProxy s -> PluginId -> Properties r -> Action (ToHsType t) #
IdeActions are used when we want to return a result immediately, even if it is stale Useful for UI actions like hover, completion where we don't want to block.
Run via runIdeAction
.
Constructors
IdeAction | |
Fields |
Instances
MonadIO IdeAction # | |
Defined in Development.IDE.Core.Shake | |
Applicative IdeAction # | |
Defined in Development.IDE.Core.Shake | |
Functor IdeAction # | |
Monad IdeAction # | |
MonadReader ShakeExtras IdeAction # | |
Defined in Development.IDE.Core.Shake Methods ask :: IdeAction ShakeExtras # local :: (ShakeExtras -> ShakeExtras) -> IdeAction a -> IdeAction a # reader :: (ShakeExtras -> a) -> IdeAction a # | |
Semigroup a => Semigroup (IdeAction a) # | |
type IdeRule k v = (RuleResult k ~ v, ShakeValue k, Show v, Typeable v, NFData v) #
A Shake database plus persistent store. Can be thought of as storing
mappings from (FilePath, k)
to RuleResult k
.
Instances
MonadReader (ReactorChan, IdeState) (ServerM c) # | |
Defined in Development.IDE.LSP.Server Methods ask :: ServerM c (ReactorChan, IdeState) # local :: ((ReactorChan, IdeState) -> (ReactorChan, IdeState)) -> ServerM c a -> ServerM c a # reader :: ((ReactorChan, IdeState) -> a) -> ServerM c a # |
data ShakeExtras #
Instances
MonadReader ShakeExtras IdeAction # | |
Defined in Development.IDE.Core.Shake Methods ask :: IdeAction ShakeExtras # local :: (ShakeExtras -> ShakeExtras) -> IdeAction a -> IdeAction a # reader :: (ShakeExtras -> a) -> IdeAction a # |
data VFSModified #
Constructors
VFSUnmodified | |
VFSModified !VFS |
define :: IdeRule k v => Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (IdeResult v)) -> Rules () #
Define a new Rule without early cutoff
defineEarlyCutoff :: IdeRule k v => Recorder (WithPriority Log) -> RuleBody k v -> Rules () #
Define a new Rule with early cutoff
defineNoDiagnostics :: IdeRule k v => Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (Maybe v)) -> Rules () #
runIdeAction :: String -> ShakeExtras -> IdeAction a -> IO a #
useNoFile_ :: IdeRule k v => k -> Action v #
useWithStale :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping)) #
Request a Rule result, it not available return the last computed result, if any, which may be stale
useWithStaleFast :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (Maybe (v, PositionMapping)) #
Lookup value in the database and return with the stale value immediately Will queue an action to refresh the value. Might block the first time the rule runs, but never blocks after that.
useWithStaleFast' :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (FastResult v) #
Same as useWithStaleFast but lets you wait for an up to date result
useWithStale_ :: IdeRule k v => k -> NormalizedFilePath -> Action (v, PositionMapping) #
Request a Rule result, it not available return the last computed result which may be stale.
Throws an BadDependency
exception which is caught by the rule system if
none available.
WARNING: Not suitable for PluginHandlers. Use useWithStaleE
instead.
use_ :: IdeRule k v => k -> NormalizedFilePath -> Action v #
uses_ :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f v) #
Plural version of use_
Throws an BadDependency
exception which is caught by the rule system if
none available.
WARNING: Not suitable for PluginHandlers. Use usesE
instead.
data GhcVersion #
Instances
Show GhcVersion # | |
Defined in Development.IDE.GHC.Compat Methods showsPrec :: Int -> GhcVersion -> ShowS # show :: GhcVersion -> String # showList :: [GhcVersion] -> ShowS # | |
Eq GhcVersion # | |
Defined in Development.IDE.GHC.Compat | |
Ord GhcVersion # | |
Defined in Development.IDE.GHC.Compat Methods compare :: GhcVersion -> GhcVersion -> Ordering # (<) :: GhcVersion -> GhcVersion -> Bool # (<=) :: GhcVersion -> GhcVersion -> Bool # (>) :: GhcVersion -> GhcVersion -> Bool # (>=) :: GhcVersion -> GhcVersion -> Bool # max :: GhcVersion -> GhcVersion -> GhcVersion # min :: GhcVersion -> GhcVersion -> GhcVersion # |
An HscEnv
with equality. Two values are considered equal
if they are created with the same call to newHscEnvEq
or
updateHscEnvEq
.
hscEnvWithImportPaths :: HscEnvEq -> HscEnv #
Unwrap the HscEnv
with the original import paths.
Used only for locating imports