ghcide-1.7.0.0: The core of an IDE
Safe HaskellNone
LanguageHaskell2010

Development.IDE.Core.Rules

Description

A Shake implementation of the compiler service, built using the Shaker abstraction layer for in-memory use.

Synopsis

Types

data IdeState Source #

A Shake database plus persistent store. Can be thought of as storing mappings from (FilePath, k) to RuleResult k.

data GetParsedModule Source #

Constructors

GetParsedModule 

Instances

Instances details
Eq GetParsedModule Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GetParsedModule Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GetParsedModule Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetParsedModule :: Type -> Type #

Hashable GetParsedModule Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetParsedModule Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GetParsedModule -> () #

type Rep GetParsedModule Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetParsedModule = D1 ('MetaData "GetParsedModule" "Development.IDE.Core.RuleTypes" "ghcide-1.7.0.0-Et6Gp1ZnqTjGFkpVtgQ7GA" 'False) (C1 ('MetaCons "GetParsedModule" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult GetParsedModule Source #

The parse tree for the file using GetFileContents

Instance details

Defined in Development.IDE.Core.RuleTypes

newtype TransitiveDependencies Source #

Constructors

TransitiveDependencies 

Fields

newtype Priority Source #

Constructors

Priority Double 

data GhcSessionIO Source #

Constructors

GhcSessionIO 

Instances

Instances details
Eq GhcSessionIO Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GhcSessionIO Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GhcSessionIO Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GhcSessionIO :: Type -> Type #

Hashable GhcSessionIO Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GhcSessionIO Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GhcSessionIO -> () #

type Rep GhcSessionIO Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GhcSessionIO = D1 ('MetaData "GhcSessionIO" "Development.IDE.Core.RuleTypes" "ghcide-1.7.0.0-Et6Gp1ZnqTjGFkpVtgQ7GA" 'False) (C1 ('MetaCons "GhcSessionIO" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult GhcSessionIO Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

data GetClientSettings Source #

Get the vscode client settings stored in the ide state

Constructors

GetClientSettings 

Instances

Instances details
Eq GetClientSettings Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GetClientSettings Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GetClientSettings Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetClientSettings :: Type -> Type #

Hashable GetClientSettings Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetClientSettings Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GetClientSettings -> () #

type Rep GetClientSettings Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetClientSettings = D1 ('MetaData "GetClientSettings" "Development.IDE.Core.RuleTypes" "ghcide-1.7.0.0-Et6Gp1ZnqTjGFkpVtgQ7GA" 'False) (C1 ('MetaCons "GetClientSettings" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult GetClientSettings Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

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.

mainRule :: Recorder (WithPriority Log) -> RulesConfig -> Rules () Source #

A rule that wires per-file rules together

data RulesConfig Source #

Constructors

RulesConfig 

Fields

Instances

Instances details
Default RulesConfig Source # 
Instance details

Defined in Development.IDE.Core.Rules

Methods

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 #

Arguments

:: Config

default value

-> Action Config 

Returns the client configurarion stored in the IdeState. You can use this function to access it from shake Rules

Rules

newtype CompiledLinkables Source #

Tracks which linkables are current, so we don't need to unload them

Instances

Instances details
IsIdeGlobal CompiledLinkables Source # 
Instance details

Defined in Development.IDE.Core.Rules

getParsedModuleRule :: Recorder (WithPriority Log) -> 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 :: Recorder (WithPriority Log) -> 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.

typeCheckRule :: Recorder (WithPriority Log) -> Rules () Source #

Typechecks a module.

getModIfaceFromDiskRule :: Recorder (WithPriority Log) -> 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.

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

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

newtype GhcSessionDepsConfig Source #

Instances

Instances details
Default GhcSessionDepsConfig Source # 
Instance details

Defined in Development.IDE.Core.Rules

newtype DisplayTHWarning Source #

Constructors

DisplayTHWarning (IO ()) 

Instances

Instances details
IsIdeGlobal DisplayTHWarning Source # 
Instance details

Defined in Development.IDE.Core.Rules