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

Development.IDE

Synopsis

Documentation

data ParseResult a #

The result of running a parser.

Constructors

POk

The parser has consumed a (possibly empty) prefix of the input and produced a result. Use getMessages to check for accumulated warnings and non-fatal errors.

Fields

  • PState

    The resulting parsing state. Can be used to resume parsing.

  • a

    The resulting value.

PFailed

The parser has consumed a (possibly empty) prefix of the input and failed.

Fields

data Diagnostic #

Instances

Instances details
Eq Diagnostic 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

Ord Diagnostic 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

Read Diagnostic 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

Show Diagnostic 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

Generic Diagnostic 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

Associated Types

type Rep Diagnostic :: Type -> Type #

ToJSON Diagnostic 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

FromJSON Diagnostic 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

NFData Diagnostic 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

Methods

rnf :: Diagnostic -> () #

type Rep Diagnostic 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

data DiagnosticSeverity #

Constructors

DsError

Error = 1,

DsWarning

Warning = 2,

DsInfo

Info = 3,

DsHint

Hint = 4

Instances

Instances details
Eq DiagnosticSeverity 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

Ord DiagnosticSeverity 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

Read DiagnosticSeverity 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

Show DiagnosticSeverity 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

Generic DiagnosticSeverity 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

Associated Types

type Rep DiagnosticSeverity :: Type -> Type #

ToJSON DiagnosticSeverity 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

FromJSON DiagnosticSeverity 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

NFData DiagnosticSeverity 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

Methods

rnf :: DiagnosticSeverity -> () #

type Rep DiagnosticSeverity 
Instance details

Defined in Language.Haskell.LSP.Types.Diagnostic

type Rep DiagnosticSeverity = D1 ('MetaData "DiagnosticSeverity" "Language.Haskell.LSP.Types.Diagnostic" "haskell-lsp-types-0.22.0.0-CptUlrdIMMV2HKQwGO1Vm6" 'False) ((C1 ('MetaCons "DsError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DsWarning" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DsInfo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DsHint" 'PrefixI 'False) (U1 :: Type -> Type)))

data Location #

Constructors

Location 

Fields

Instances

Instances details
Eq Location 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Ord Location 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Read Location 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Show Location 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Generic Location 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Associated Types

type Rep Location :: Type -> Type #

Methods

from :: Location -> Rep Location x #

to :: Rep Location x -> Location #

ToJSON Location 
Instance details

Defined in Language.Haskell.LSP.Types.Location

FromJSON Location 
Instance details

Defined in Language.Haskell.LSP.Types.Location

NFData Location 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Methods

rnf :: Location -> () #

type Rep Location 
Instance details

Defined in Language.Haskell.LSP.Types.Location

type Rep Location = D1 ('MetaData "Location" "Language.Haskell.LSP.Types.Location" "haskell-lsp-types-0.22.0.0-CptUlrdIMMV2HKQwGO1Vm6" 'False) (C1 ('MetaCons "Location" 'PrefixI 'True) (S1 ('MetaSel ('Just "_uri") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Uri) :*: S1 ('MetaSel ('Just "_range") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)))

data Range #

Constructors

Range 

Fields

Instances

Instances details
Eq Range 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Methods

(==) :: Range -> Range -> Bool #

(/=) :: Range -> Range -> Bool #

Ord Range 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Methods

compare :: Range -> Range -> Ordering #

(<) :: Range -> Range -> Bool #

(<=) :: Range -> Range -> Bool #

(>) :: Range -> Range -> Bool #

(>=) :: Range -> Range -> Bool #

max :: Range -> Range -> Range #

min :: Range -> Range -> Range #

Read Range 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Show Range 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Methods

showsPrec :: Int -> Range -> ShowS #

show :: Range -> String #

showList :: [Range] -> ShowS #

Generic Range 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Associated Types

type Rep Range :: Type -> Type #

Methods

from :: Range -> Rep Range x #

to :: Rep Range x -> Range #

ToJSON Range 
Instance details

Defined in Language.Haskell.LSP.Types.Location

FromJSON Range 
Instance details

Defined in Language.Haskell.LSP.Types.Location

NFData Range 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Methods

rnf :: Range -> () #

type Rep Range 
Instance details

Defined in Language.Haskell.LSP.Types.Location

type Rep Range = D1 ('MetaData "Range" "Language.Haskell.LSP.Types.Location" "haskell-lsp-types-0.22.0.0-CptUlrdIMMV2HKQwGO1Vm6" 'False) (C1 ('MetaCons "Range" 'PrefixI 'True) (S1 ('MetaSel ('Just "_start") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Position) :*: S1 ('MetaSel ('Just "_end") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Position)))

data Position #

Constructors

Position 

Fields

Instances

Instances details
Eq Position 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Ord Position 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Read Position 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Show Position 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Generic Position 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Associated Types

type Rep Position :: Type -> Type #

Methods

from :: Position -> Rep Position x #

to :: Rep Position x -> Position #

ToJSON Position 
Instance details

Defined in Language.Haskell.LSP.Types.Location

FromJSON Position 
Instance details

Defined in Language.Haskell.LSP.Types.Location

NFData Position 
Instance details

Defined in Language.Haskell.LSP.Types.Location

Methods

rnf :: Position -> () #

type Rep Position 
Instance details

Defined in Language.Haskell.LSP.Types.Location

type Rep Position = D1 ('MetaData "Position" "Language.Haskell.LSP.Types.Location" "haskell-lsp-types-0.22.0.0-CptUlrdIMMV2HKQwGO1Vm6" 'False) (C1 ('MetaCons "Position" 'PrefixI 'True) (S1 ('MetaSel ('Just "_line") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "_character") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

newtype Uri #

Constructors

Uri 

Fields

Instances

Instances details
Eq Uri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Methods

(==) :: Uri -> Uri -> Bool #

(/=) :: Uri -> Uri -> Bool #

Ord Uri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Methods

compare :: Uri -> Uri -> Ordering #

(<) :: Uri -> Uri -> Bool #

(<=) :: Uri -> Uri -> Bool #

(>) :: Uri -> Uri -> Bool #

(>=) :: Uri -> Uri -> Bool #

max :: Uri -> Uri -> Uri #

min :: Uri -> Uri -> Uri #

Read Uri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Show Uri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Methods

showsPrec :: Int -> Uri -> ShowS #

show :: Uri -> String #

showList :: [Uri] -> ShowS #

Generic Uri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Associated Types

type Rep Uri :: Type -> Type #

Methods

from :: Uri -> Rep Uri x #

to :: Rep Uri x -> Uri #

Hashable Uri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Methods

hashWithSalt :: Int -> Uri -> Int #

hash :: Uri -> Int #

ToJSON Uri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

ToJSONKey Uri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

FromJSON Uri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

FromJSONKey Uri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

NFData Uri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Methods

rnf :: Uri -> () #

type Rep Uri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

type Rep Uri = D1 ('MetaData "Uri" "Language.Haskell.LSP.Types.Uri" "haskell-lsp-types-0.22.0.0-CptUlrdIMMV2HKQwGO1Vm6" 'True) (C1 ('MetaCons "Uri" 'PrefixI 'True) (S1 ('MetaSel ('Just "getUri") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data NormalizedUri #

Instances

Instances details
Eq NormalizedUri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Ord NormalizedUri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Read NormalizedUri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Show NormalizedUri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Generic NormalizedUri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Associated Types

type Rep NormalizedUri :: Type -> Type #

Hashable NormalizedUri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

NFData NormalizedUri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Methods

rnf :: NormalizedUri -> () #

type Rep NormalizedUri 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

type Rep NormalizedUri = D1 ('MetaData "NormalizedUri" "Language.Haskell.LSP.Types.Uri" "haskell-lsp-types-0.22.0.0-CptUlrdIMMV2HKQwGO1Vm6" 'False) (C1 ('MetaCons "NormalizedUri" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))

data NormalizedFilePath #

Newtype wrapper around FilePath that always has normalized slashes. The NormalizedUri and hash of the FilePath are cached to avoided repeated normalisation when we need to compute them (which is a lot).

This is one of the most performance critical parts of ghcide, do not modify it without profiling.

Instances

Instances details
Eq NormalizedFilePath 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Ord NormalizedFilePath 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Show NormalizedFilePath 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

IsString NormalizedFilePath 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Generic NormalizedFilePath 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Associated Types

type Rep NormalizedFilePath :: Type -> Type #

Hashable NormalizedFilePath 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Binary NormalizedFilePath 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

NFData NormalizedFilePath 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

Methods

rnf :: NormalizedFilePath -> () #

type Rep NormalizedFilePath 
Instance details

Defined in Language.Haskell.LSP.Types.Uri

type Rep NormalizedFilePath = D1 ('MetaData "NormalizedFilePath" "Language.Haskell.LSP.Types.Uri" "haskell-lsp-types-0.22.0.0-CptUlrdIMMV2HKQwGO1Vm6" 'False) (C1 ('MetaCons "NormalizedFilePath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NormalizedUri) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FilePath)))

newtype List a #

This data type is used to host a FromJSON instance for the encoding used by elisp, where an empty list shows up as "null"

Constructors

List [a] 

Instances

Instances details
Functor List 
Instance details

Defined in Language.Haskell.LSP.Types.List

Methods

fmap :: (a -> b) -> List a -> List b #

(<$) :: a -> List b -> List a #

Foldable List 
Instance details

Defined in Language.Haskell.LSP.Types.List

Methods

fold :: Monoid m => List m -> m #

foldMap :: Monoid m => (a -> m) -> List a -> m #

foldMap' :: Monoid m => (a -> m) -> List a -> m #

foldr :: (a -> b -> b) -> b -> List a -> b #

foldr' :: (a -> b -> b) -> b -> List a -> b #

foldl :: (b -> a -> b) -> b -> List a -> b #

foldl' :: (b -> a -> b) -> b -> List a -> b #

foldr1 :: (a -> a -> a) -> List a -> a #

foldl1 :: (a -> a -> a) -> List a -> a #

toList :: List a -> [a] #

null :: List a -> Bool #

length :: List a -> Int #

elem :: Eq a => a -> List a -> Bool #

maximum :: Ord a => List a -> a #

minimum :: Ord a => List a -> a #

sum :: Num a => List a -> a #

product :: Num a => List a -> a #

Traversable List 
Instance details

Defined in Language.Haskell.LSP.Types.List

Methods

traverse :: Applicative f => (a -> f b) -> List a -> f (List b) #

sequenceA :: Applicative f => List (f a) -> f (List a) #

mapM :: Monad m => (a -> m b) -> List a -> m (List b) #

sequence :: Monad m => List (m a) -> m (List a) #

Eq a => Eq (List a) 
Instance details

Defined in Language.Haskell.LSP.Types.List

Methods

(==) :: List a -> List a -> Bool #

(/=) :: List a -> List a -> Bool #

Ord a => Ord (List a) 
Instance details

Defined in Language.Haskell.LSP.Types.List

Methods

compare :: List a -> List a -> Ordering #

(<) :: List a -> List a -> Bool #

(<=) :: List a -> List a -> Bool #

(>) :: List a -> List a -> Bool #

(>=) :: List a -> List a -> Bool #

max :: List a -> List a -> List a #

min :: List a -> List a -> List a #

Read a => Read (List a) 
Instance details

Defined in Language.Haskell.LSP.Types.List

Show a => Show (List a) 
Instance details

Defined in Language.Haskell.LSP.Types.List

Methods

showsPrec :: Int -> List a -> ShowS #

show :: List a -> String #

showList :: [List a] -> ShowS #

Generic (List a) 
Instance details

Defined in Language.Haskell.LSP.Types.List

Associated Types

type Rep (List a) :: Type -> Type #

Methods

from :: List a -> Rep (List a) x #

to :: Rep (List a) x -> List a #

Semigroup (List a) 
Instance details

Defined in Language.Haskell.LSP.Types.List

Methods

(<>) :: List a -> List a -> List a #

sconcat :: NonEmpty (List a) -> List a #

stimes :: Integral b => b -> List a -> List a #

Monoid (List a) 
Instance details

Defined in Language.Haskell.LSP.Types.List

Methods

mempty :: List a #

mappend :: List a -> List a -> List a #

mconcat :: [List a] -> List a #

ToJSON a => ToJSON (List a) 
Instance details

Defined in Language.Haskell.LSP.Types.List

FromJSON a => FromJSON (List a) 
Instance details

Defined in Language.Haskell.LSP.Types.List

NFData a => NFData (List a) 
Instance details

Defined in Language.Haskell.LSP.Types.List

Methods

rnf :: List a -> () #

type Rep (List a) 
Instance details

Defined in Language.Haskell.LSP.Types.List

type Rep (List a) = D1 ('MetaData "List" "Language.Haskell.LSP.Types.List" "haskell-lsp-types-0.22.0.0-CptUlrdIMMV2HKQwGO1Vm6" 'True) (C1 ('MetaCons "List" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a])))

action :: Partial => Action a -> Rules () #

Run an action, usually used for specifying top-level requirements.

main = shake shakeOptions $ do
   action $ do
       b <- doesFileExist "file.src"
       when b $ need ["file.out"]

This action builds file.out, but only if file.src exists. The action will be run in every build execution (unless withoutActions is used), so only cheap operations should be performed. On the flip side, consulting system information (e.g. environment variables) can be done directly as the information will not be cached. All calls to action may be run in parallel, in any order.

For the standard requirement of only needing a fixed list of files in the action, see want.

data Rules a #

Define a set of rules. Rules can be created with calls to functions such as %> or action. Rules are combined with either the Monoid instance, or (more commonly) the Monad instance and do notation. To define your own custom types of rule, see Development.Shake.Rule.

Instances

Instances details
Monad Rules 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

(>>=) :: Rules a -> (a -> Rules b) -> Rules b #

(>>) :: Rules a -> Rules b -> Rules b #

return :: a -> Rules a #

Functor Rules 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

fmap :: (a -> b) -> Rules a -> Rules b #

(<$) :: a -> Rules b -> Rules a #

MonadFix Rules 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

mfix :: (a -> Rules a) -> Rules a #

MonadFail Rules 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

fail :: String -> Rules a #

Applicative Rules 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

pure :: a -> Rules a #

(<*>) :: Rules (a -> b) -> Rules a -> Rules b #

liftA2 :: (a -> b -> c) -> Rules a -> Rules b -> Rules c #

(*>) :: Rules a -> Rules b -> Rules b #

(<*) :: Rules a -> Rules b -> Rules a #

MonadIO Rules 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

liftIO :: IO a -> Rules a #

Semigroup a => Semigroup (Rules a) 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

(<>) :: Rules a -> Rules a -> Rules a #

sconcat :: NonEmpty (Rules a) -> Rules a #

stimes :: Integral b => b -> Rules a -> Rules a #

(Semigroup a, Monoid a) => Monoid (Rules a) 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

mempty :: Rules a #

mappend :: Rules a -> Rules a -> Rules a #

mconcat :: [Rules a] -> Rules a #

type family RuleResult key #

The type mapping between the key or a rule and the resulting value. See addBuiltinRule and apply.

Instances

Instances details
type RuleResult FileQ 
Instance details

Defined in Development.Shake.Internal.Rules.File

type RuleResult FileQ = FileR
type RuleResult DoesDirectoryExistQ 
Instance details

Defined in Development.Shake.Internal.Rules.Directory

type RuleResult DoesDirectoryExistQ = DoesDirectoryExistA
type RuleResult DoesFileExistQ 
Instance details

Defined in Development.Shake.Internal.Rules.Directory

type RuleResult DoesFileExistQ = DoesFileExistA
type RuleResult GetDirectoryContentsQ 
Instance details

Defined in Development.Shake.Internal.Rules.Directory

type RuleResult GetDirectoryContentsQ = GetDirectoryA
type RuleResult GetDirectoryDirsQ 
Instance details

Defined in Development.Shake.Internal.Rules.Directory

type RuleResult GetDirectoryDirsQ = GetDirectoryA
type RuleResult GetDirectoryFilesQ 
Instance details

Defined in Development.Shake.Internal.Rules.Directory

type RuleResult GetDirectoryFilesQ = GetDirectoryA
type RuleResult GetEnvQ 
Instance details

Defined in Development.Shake.Internal.Rules.Directory

type RuleResult GetEnvQ = GetEnvA
type RuleResult FilesQ 
Instance details

Defined in Development.Shake.Internal.Rules.Files

type RuleResult FilesQ = FilesA
type RuleResult AlwaysRerunQ 
Instance details

Defined in Development.Shake.Internal.Rules.Rerun

type RuleResult AlwaysRerunQ = ()
type RuleResult GetModificationTime Source #

Get the modification time of a file.

Instance details

Defined in Development.IDE.Core.Shake

type RuleResult GetClientSettings Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GetModSummary Source #

Generate a ModSummary that has enough information to be used to get .hi and .hie files. without needing to parse the entire source

Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GetModSummaryWithoutTimestamps Source #

Generate a ModSummary with the timestamps elided, for more successful early cutoff

Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult IsFileOfInterest Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GetModIfaceWithoutLinkable Source #

Get a module interface details, without the Linkable For better early cuttoff

Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GetModIface Source #

Get a module interface details, either from an interface file or a typechecked module

Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GetModIfaceFromDisk Source #

Read the module interface file from disk. Throws an error for VFS files. This is an internal rule, use GetModIface instead.

Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GhcSessionDeps Source #

A GHC session preloaded with all the dependencies

Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GhcSession Source #

A GHC session that we reuse.

Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GetBindings Source #

A IntervalMap telling us what is in scope at each point

Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GetHieAst Source #

The uncompressed HieAST

Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GetDocMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult TypeCheck Source #

The type checked version of this file, requires TypeCheck+

Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GetDependencies Source #

Transitive module and pkg dependencies based on the information produced by GetDependencyInformation. This rule is also responsible for calling ReportImportCycles for each file in the transitive closure.

Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult ReportImportCycles Source #

This rule is used to report import cycles. It depends on GetDependencyInformation. We cannot report the cycles directly from GetDependencyInformation since we can only report diagnostics for the current file.

Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GetModuleGraph Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GetDependencyInformation Source #

The dependency information produced by following the imports recursively. This rule will succeed even if there is an error, e.g., a module could not be located, a module could not be parsed or an import cycle.

Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult NeedsCompilation Source #

Does this module need to be compiled?

Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GetLocatedImports Source #

Resolve the imports in a module to the file path of a module in the same package or the package id of another package.

Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GetParsedModule Source #

The parse tree for the file using GetFileContents

Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GetImportMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GenerateCore Source #

Convert to Core, requires TypeCheck*

Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GetKnownTargets Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type RuleResult GhcSessionIO Source # 
Instance details

Defined in Development.IDE.Core.Rules

type RuleResult (OracleQ a) 
Instance details

Defined in Development.Shake.Internal.Rules.Oracle

type RuleResult (OracleQ a) = OracleA (RuleResult a)
type RuleResult (Q k) Source # 
Instance details

Defined in Development.IDE.Core.Shake

type RuleResult (Q k)

data Action a #

The Action monad, use liftIO to raise IO actions into it, and need to execute files. Action values are used by addUserRule and action. The Action monad tracks the dependencies of a rule. To raise an exception call error, fail or liftIO . throwIO.

Instances

Instances details
Monad Action 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

(>>=) :: Action a -> (a -> Action b) -> Action b #

(>>) :: Action a -> Action b -> Action b #

return :: a -> Action a #

Functor Action 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

fmap :: (a -> b) -> Action a -> Action b #

(<$) :: a -> Action b -> Action a #

MonadFail Action 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

fail :: String -> Action a #

Applicative Action 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

pure :: a -> Action a #

(<*>) :: Action (a -> b) -> Action a -> Action b #

liftA2 :: (a -> b -> c) -> Action a -> Action b -> Action c #

(*>) :: Action a -> Action b -> Action b #

(<*) :: Action a -> Action b -> Action a #

MonadIO Action 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

liftIO :: IO a -> Action a #

MonadTempDir Action 
Instance details

Defined in Development.Shake.Command

Semigroup a => Semigroup (Action a) 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

(<>) :: Action a -> Action a -> Action a #

sconcat :: NonEmpty (Action a) -> Action a #

stimes :: Integral b => b -> Action a -> Action a #

Monoid a => Monoid (Action a) 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

mempty :: Action a #

mappend :: Action a -> Action a -> Action a #

mconcat :: [Action a] -> Action a #

CmdResult r => CmdArguments (Action r) 
Instance details

Defined in Development.Shake.Command

uriToFilePath' :: Uri -> Maybe FilePath Source #

We use an empty string as a filepath when we don’t have a file. However, haskell-lsp doesn’t support that in uriToFilePath and given that it is not a valid filepath it does not make sense to upstream a fix. So we have our own wrapper here that supports empty filepaths.

readSrcSpan :: ReadS RealSrcSpan Source #

Parser for the GHC output format

type FileDiagnostic = (NormalizedFilePath, ShowDiagnostic, Diagnostic) Source #

Human readable diagnostics for a specific file.

This type packages a pretty printed, human readable error message along with the related source location so that we can display the error on either the console or in the IDE at the right source location.

data ShowDiagnostic Source #

Defines whether a particular diagnostic should be reported back to the user.

One important use case is "missing signature" code lenses, for which we need to enable the corresponding warning during type checking. However, we do not want to show the warning unless the programmer asks for it (#261).

Constructors

ShowDiag

Report back to the user

HideDiag

Hide from user

type IdeResult v = ([FileDiagnostic], Maybe v) Source #

The result of an IDE operation. Warnings and errors are in the Diagnostic, and a value is in the Maybe. For operations that throw an error you expect a non-empty list of diagnostics, at least one of which is an error, and a Nothing. For operations that succeed you expect perhaps some warnings and a Just. For operations that depend on other failing operations you may get empty diagnostics and a Nothing, to indicate this phase throws no fresh errors but still failed.

A rule on a file should only return diagnostics for that given file. It should not propagate diagnostic errors through multiple phases.

data HscEnvEq Source #

An HscEnv with equality. Two values are considered equal if they are created with the same call to newHscEnvEq.

Instances

Instances details
Eq HscEnvEq Source # 
Instance details

Defined in Development.IDE.GHC.Util

Show HscEnvEq Source # 
Instance details

Defined in Development.IDE.GHC.Util

Hashable HscEnvEq Source # 
Instance details

Defined in Development.IDE.GHC.Util

Methods

hashWithSalt :: Int -> HscEnvEq -> Int #

hash :: HscEnvEq -> Int #

Binary HscEnvEq Source # 
Instance details

Defined in Development.IDE.GHC.Util

Methods

put :: HscEnvEq -> Put #

get :: Get HscEnvEq #

putList :: [HscEnvEq] -> Put #

NFData HscEnvEq Source # 
Instance details

Defined in Development.IDE.GHC.Util

Methods

rnf :: HscEnvEq -> () #

modifyDynFlags :: GhcMonad m => (DynFlags -> DynFlags) -> m () Source #

Used to modify dyn flags in preference to calling setSessionDynFlags, since that function also reloads packages (which is very slow).

lookupPackageConfig :: UnitId -> HscEnv -> Maybe PackageConfig Source #

Given a UnitId try and find the associated PackageConfig in the environment.

textToStringBuffer :: Text -> StringBuffer Source #

Convert from the text package to the GHC StringBuffer. Currently implemented somewhat inefficiently (if it ever comes up in a profile).

prettyPrint :: Outputable a => a -> String Source #

Pretty print a GHC value using 'unsafeGlobalDynFlags '.

printRdrName :: RdrName -> String Source #

Pretty print a RdrName wrapping operators in parens

printName :: Name -> String Source #

Pretty print a Name wrapping operators in parens

evalGhcEnv :: HscEnv -> Ghc b -> IO b Source #

Run a Ghc monad value using an existing HscEnv. Sets up and tears down all the required pieces, but designed to be more efficient than a standard runGhc.

moduleImportPath :: NormalizedFilePath -> ModuleName -> Maybe FilePath Source #

Given a module location, and its parse tree, figure out what is the include directory implied by it. For example, given the file /usr/Test/Foo/Bar.hs with the module name Foo.Bar the directory /usr/Test should be on the include path to find sibling modules.

hscEnvWithImportPaths :: HscEnvEq -> HscEnv Source #

Unwrap the HscEnv with the original import paths. Used only for locating imports

readFileUtf8 :: FilePath -> IO Text Source #

Read a UTF8 file, with lenient decoding, so it will never raise a decoding error.

fingerprintToBS :: Fingerprint -> ByteString Source #

Convert a Fingerprint to a ByteString by copying the byte across. Will produce an 8 byte unreadable ByteString.

hDuplicateTo' :: Handle -> Handle -> IO () Source #

A slightly modified version of hDuplicateTo from GHC. Importantly, it avoids the bug listed in https://gitlab.haskell.org/ghc/ghc/merge_requests/2318.

diagFromErrMsg :: Text -> DynFlags -> ErrMsg -> [FileDiagnostic] Source #

Produce a GHC-style error from a source span and a message.

srcSpanToRange :: SrcSpan -> Maybe Range Source #

Convert a GHC SrcSpan to a DAML compiler Range

srcSpanToFilename :: SrcSpan -> Maybe FilePath Source #

Extract a file name from a GHC SrcSpan (use message for unhelpful ones) FIXME This may not be an _absolute_ file name, needs fixing.

toDSeverity :: Severity -> Maybe DiagnosticSeverity Source #

Convert a GHC severity to a DAML compiler Severity. Severities below Warning level are dropped (returning Nothing).

diagFromStrings :: Text -> DiagnosticSeverity -> [(SrcSpan, String)] -> [FileDiagnostic] Source #

Produce a bag of GHC-style errors (ErrorMessages) from the given (optional) locations and message strings.

diagFromString :: Text -> DiagnosticSeverity -> SrcSpan -> String -> [FileDiagnostic] Source #

Produce a GHC-style error from a source span and a message.

noSpan :: String -> SrcSpan Source #

Produces an "unhelpful" source span with the given string.

zeroSpan Source #

Arguments

:: FastString

file path of span

-> RealSrcSpan 

creates a span with zero length in the filename of the argument passed

catchSrcErrors :: DynFlags -> Text -> IO a -> IO (Either [FileDiagnostic] a) Source #

Catch the errors thrown by GHC (SourceErrors and compiler-internal exceptions like Panic or InstallationError), and turn them into diagnostics

data Logger Source #

Note that this is logging actions _of the program_, not of the user. You shouldn't call warning/error if the user has caused an error, only if our code has gone wrong and is itself erroneous (e.g. we threw an exception).

Constructors

Logger 

Fields

data Priority Source #

Constructors

Telemetry

Events that are useful for gathering user metrics.

Debug

Verbose debug logging.

Info

Useful information in case an error has to be understood.

Warning

These error messages should not occur in a expected usage, and should be investigated.

Error

Such log messages must never occur in expected usage.

data GetModificationTime where Source #

Bundled Patterns

pattern GetModificationTime :: GetModificationTime 

Instances

Instances details
Eq GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.Shake

Show GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.Shake

Generic GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.Shake

Associated Types

type Rep GetModificationTime :: Type -> Type #

Hashable GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.Shake

Binary GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.Shake

NFData GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.Shake

Methods

rnf :: GetModificationTime -> () #

type Rep GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.Shake

type Rep GetModificationTime = D1 ('MetaData "GetModificationTime" "Development.IDE.Core.Shake" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "GetModificationTime_" 'PrefixI 'True) (S1 ('MetaSel ('Just "missingFileDiagnostics") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))
type RuleResult GetModificationTime Source #

Get the modification time of a file.

Instance details

Defined in Development.IDE.Core.Shake

data FastResult a Source #

A (maybe) stale result now, and an up to date one later

Constructors

FastResult 

Fields

newtype IdeAction a Source #

Constructors

IdeAction 

Instances

Instances details
Monad IdeAction Source # 
Instance details

Defined in Development.IDE.Core.Shake

Methods

(>>=) :: IdeAction a -> (a -> IdeAction b) -> IdeAction b #

(>>) :: IdeAction a -> IdeAction b -> IdeAction b #

return :: a -> IdeAction a #

Functor IdeAction Source # 
Instance details

Defined in Development.IDE.Core.Shake

Methods

fmap :: (a -> b) -> IdeAction a -> IdeAction b #

(<$) :: a -> IdeAction b -> IdeAction a #

Applicative IdeAction Source # 
Instance details

Defined in Development.IDE.Core.Shake

Methods

pure :: a -> IdeAction a #

(<*>) :: IdeAction (a -> b) -> IdeAction a -> IdeAction b #

liftA2 :: (a -> b -> c) -> IdeAction a -> IdeAction b -> IdeAction c #

(*>) :: IdeAction a -> IdeAction b -> IdeAction b #

(<*) :: IdeAction a -> IdeAction b -> IdeAction a #

MonadIO IdeAction Source # 
Instance details

Defined in Development.IDE.Core.Shake

Methods

liftIO :: IO a -> IdeAction a #

MonadReader ShakeExtras IdeAction Source # 
Instance details

Defined in Development.IDE.Core.Shake

data IdeState Source #

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

type IdeRule k v = (RuleResult k ~ v, ShakeValue k, Show v, Typeable v, NFData v) Source #

data ShakeExtras Source #

Instances

Instances details
MonadReader ShakeExtras IdeAction Source # 
Instance details

Defined in Development.IDE.Core.Shake

define :: IdeRule k v => (k -> NormalizedFilePath -> Action (IdeResult v)) -> Rules () Source #

Define a new Rule without early cutoff

use :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe v) Source #

Request a Rule result if available

useWithStale :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping)) Source #

Request a Rule result, it not available return the last computed result, if any, which may be stale

useWithStale_ :: IdeRule k v => k -> NormalizedFilePath -> Action (v, PositionMapping) Source #

Request a Rule result, it not available return the last computed result which may be stale. Errors out if none available.

runIdeAction :: String -> ShakeExtras -> IdeAction a -> IO a Source #

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.

useWithStaleFast :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (Maybe (v, PositionMapping)) Source #

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) Source #

Same as useWithStaleFast but lets you wait for an up to date result

useNoFile :: IdeRule k v => k -> Action (Maybe v) Source #

useNoFile_ :: IdeRule k v => k -> Action v Source #

uses_ :: IdeRule k v => k -> [NormalizedFilePath] -> Action [v] Source #

uses :: IdeRule k v => k -> [NormalizedFilePath] -> Action [Maybe v] Source #

Plural version of use

defineEarlyCutoff :: IdeRule k v => (k -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult v)) -> Rules () Source #

Define a new Rule with early cutoff

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

Binary 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-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "GetClientSettings" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult GetClientSettings Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

data GetModSummary Source #

Constructors

GetModSummary 

Instances

Instances details
Eq GetModSummary Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GetModSummary Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GetModSummary Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetModSummary :: Type -> Type #

Hashable GetModSummary Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GetModSummary Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetModSummary Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GetModSummary -> () #

type Rep GetModSummary Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetModSummary = D1 ('MetaData "GetModSummary" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "GetModSummary" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult GetModSummary Source #

Generate a ModSummary that has enough information to be used to get .hi and .hie files. without needing to parse the entire source

Instance details

Defined in Development.IDE.Core.RuleTypes

data GetModSummaryWithoutTimestamps Source #

Instances

Instances details
Eq GetModSummaryWithoutTimestamps Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GetModSummaryWithoutTimestamps Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GetModSummaryWithoutTimestamps Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetModSummaryWithoutTimestamps :: Type -> Type #

Hashable GetModSummaryWithoutTimestamps Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GetModSummaryWithoutTimestamps Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetModSummaryWithoutTimestamps Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetModSummaryWithoutTimestamps Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetModSummaryWithoutTimestamps = D1 ('MetaData "GetModSummaryWithoutTimestamps" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "GetModSummaryWithoutTimestamps" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult GetModSummaryWithoutTimestamps Source #

Generate a ModSummary with the timestamps elided, for more successful early cutoff

Instance details

Defined in Development.IDE.Core.RuleTypes

data IsFileOfInterest Source #

Constructors

IsFileOfInterest 

Instances

Instances details
Eq IsFileOfInterest Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show IsFileOfInterest Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic IsFileOfInterest Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep IsFileOfInterest :: Type -> Type #

Hashable IsFileOfInterest Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary IsFileOfInterest Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData IsFileOfInterest Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: IsFileOfInterest -> () #

type Rep IsFileOfInterest Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

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

Defined in Development.IDE.Core.RuleTypes

data GetModIfaceWithoutLinkable Source #

Instances

Instances details
Eq GetModIfaceWithoutLinkable Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GetModIfaceWithoutLinkable Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GetModIfaceWithoutLinkable Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetModIfaceWithoutLinkable :: Type -> Type #

Hashable GetModIfaceWithoutLinkable Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GetModIfaceWithoutLinkable Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetModIfaceWithoutLinkable Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetModIfaceWithoutLinkable Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetModIfaceWithoutLinkable = D1 ('MetaData "GetModIfaceWithoutLinkable" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "GetModIfaceWithoutLinkable" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult GetModIfaceWithoutLinkable Source #

Get a module interface details, without the Linkable For better early cuttoff

Instance details

Defined in Development.IDE.Core.RuleTypes

data GetModIface Source #

Constructors

GetModIface 

Instances

Instances details
Eq GetModIface Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GetModIface Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GetModIface Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetModIface :: Type -> Type #

Hashable GetModIface Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GetModIface Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetModIface Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GetModIface -> () #

type Rep GetModIface Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetModIface = D1 ('MetaData "GetModIface" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "GetModIface" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult GetModIface Source #

Get a module interface details, either from an interface file or a typechecked module

Instance details

Defined in Development.IDE.Core.RuleTypes

data GetModIfaceFromDisk Source #

Constructors

GetModIfaceFromDisk 

Instances

Instances details
Eq GetModIfaceFromDisk Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GetModIfaceFromDisk Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GetModIfaceFromDisk Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetModIfaceFromDisk :: Type -> Type #

Hashable GetModIfaceFromDisk Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GetModIfaceFromDisk Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetModIfaceFromDisk Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GetModIfaceFromDisk -> () #

type Rep GetModIfaceFromDisk Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetModIfaceFromDisk = D1 ('MetaData "GetModIfaceFromDisk" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "GetModIfaceFromDisk" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult GetModIfaceFromDisk Source #

Read the module interface file from disk. Throws an error for VFS files. This is an internal rule, use GetModIface instead.

Instance details

Defined in Development.IDE.Core.RuleTypes

data GhcSessionDeps Source #

Constructors

GhcSessionDeps 

Instances

Instances details
Eq GhcSessionDeps Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GhcSessionDeps Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GhcSessionDeps Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GhcSessionDeps :: Type -> Type #

Hashable GhcSessionDeps Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GhcSessionDeps Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GhcSessionDeps Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GhcSessionDeps -> () #

type Rep GhcSessionDeps Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GhcSessionDeps = D1 ('MetaData "GhcSessionDeps" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "GhcSessionDeps" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult GhcSessionDeps Source #

A GHC session preloaded with all the dependencies

Instance details

Defined in Development.IDE.Core.RuleTypes

data GhcSession Source #

Constructors

GhcSession 

Instances

Instances details
Eq GhcSession Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GhcSession Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GhcSession Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GhcSession :: Type -> Type #

Hashable GhcSession Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GhcSession Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GhcSession Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GhcSession -> () #

type Rep GhcSession Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GhcSession = D1 ('MetaData "GhcSession" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "GhcSession" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult GhcSession Source #

A GHC session that we reuse.

Instance details

Defined in Development.IDE.Core.RuleTypes

data GetBindings Source #

Constructors

GetBindings 

Instances

Instances details
Eq GetBindings Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GetBindings Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GetBindings Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetBindings :: Type -> Type #

Hashable GetBindings Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GetBindings Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetBindings Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GetBindings -> () #

type Rep GetBindings Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetBindings = D1 ('MetaData "GetBindings" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "GetBindings" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult GetBindings Source #

A IntervalMap telling us what is in scope at each point

Instance details

Defined in Development.IDE.Core.RuleTypes

data GetHieAst Source #

Constructors

GetHieAst 

Instances

Instances details
Eq GetHieAst Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GetHieAst Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GetHieAst Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetHieAst :: Type -> Type #

Hashable GetHieAst Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GetHieAst Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetHieAst Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GetHieAst -> () #

type Rep GetHieAst Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetHieAst = D1 ('MetaData "GetHieAst" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "GetHieAst" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult GetHieAst Source #

The uncompressed HieAST

Instance details

Defined in Development.IDE.Core.RuleTypes

data GetDocMap Source #

Constructors

GetDocMap 

Instances

Instances details
Eq GetDocMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GetDocMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GetDocMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetDocMap :: Type -> Type #

Hashable GetDocMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GetDocMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetDocMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GetDocMap -> () #

type Rep GetDocMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

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

Defined in Development.IDE.Core.RuleTypes

data TypeCheck Source #

Constructors

TypeCheck 

Instances

Instances details
Eq TypeCheck Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show TypeCheck Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic TypeCheck Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep TypeCheck :: Type -> Type #

Hashable TypeCheck Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary TypeCheck Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData TypeCheck Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: TypeCheck -> () #

type Rep TypeCheck Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep TypeCheck = D1 ('MetaData "TypeCheck" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "TypeCheck" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult TypeCheck Source #

The type checked version of this file, requires TypeCheck+

Instance details

Defined in Development.IDE.Core.RuleTypes

data GetDependencies Source #

Constructors

GetDependencies 

Instances

Instances details
Eq GetDependencies Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GetDependencies Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GetDependencies Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetDependencies :: Type -> Type #

Hashable GetDependencies Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GetDependencies Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetDependencies Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GetDependencies -> () #

type Rep GetDependencies Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetDependencies = D1 ('MetaData "GetDependencies" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "GetDependencies" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult GetDependencies Source #

Transitive module and pkg dependencies based on the information produced by GetDependencyInformation. This rule is also responsible for calling ReportImportCycles for each file in the transitive closure.

Instance details

Defined in Development.IDE.Core.RuleTypes

data ReportImportCycles Source #

Constructors

ReportImportCycles 

Instances

Instances details
Eq ReportImportCycles Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show ReportImportCycles Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic ReportImportCycles Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep ReportImportCycles :: Type -> Type #

Hashable ReportImportCycles Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary ReportImportCycles Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData ReportImportCycles Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: ReportImportCycles -> () #

type Rep ReportImportCycles Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep ReportImportCycles = D1 ('MetaData "ReportImportCycles" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "ReportImportCycles" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult ReportImportCycles Source #

This rule is used to report import cycles. It depends on GetDependencyInformation. We cannot report the cycles directly from GetDependencyInformation since we can only report diagnostics for the current file.

Instance details

Defined in Development.IDE.Core.RuleTypes

data GetModuleGraph Source #

Constructors

GetModuleGraph 

Instances

Instances details
Eq GetModuleGraph Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GetModuleGraph Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GetModuleGraph Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetModuleGraph :: Type -> Type #

Hashable GetModuleGraph Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GetModuleGraph Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetModuleGraph Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GetModuleGraph -> () #

type Rep GetModuleGraph Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

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

Defined in Development.IDE.Core.RuleTypes

data GetDependencyInformation Source #

Instances

Instances details
Eq GetDependencyInformation Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GetDependencyInformation Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GetDependencyInformation Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetDependencyInformation :: Type -> Type #

Hashable GetDependencyInformation Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GetDependencyInformation Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetDependencyInformation Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetDependencyInformation Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetDependencyInformation = D1 ('MetaData "GetDependencyInformation" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "GetDependencyInformation" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult GetDependencyInformation Source #

The dependency information produced by following the imports recursively. This rule will succeed even if there is an error, e.g., a module could not be located, a module could not be parsed or an import cycle.

Instance details

Defined in Development.IDE.Core.RuleTypes

data NeedsCompilation Source #

Constructors

NeedsCompilation 

Instances

Instances details
Eq NeedsCompilation Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show NeedsCompilation Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic NeedsCompilation Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep NeedsCompilation :: Type -> Type #

Hashable NeedsCompilation Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary NeedsCompilation Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData NeedsCompilation Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: NeedsCompilation -> () #

type Rep NeedsCompilation Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep NeedsCompilation = D1 ('MetaData "NeedsCompilation" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "NeedsCompilation" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult NeedsCompilation Source #

Does this module need to be compiled?

Instance details

Defined in Development.IDE.Core.RuleTypes

data GetLocatedImports Source #

Constructors

GetLocatedImports 

Instances

Instances details
Eq GetLocatedImports Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GetLocatedImports Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GetLocatedImports Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetLocatedImports :: Type -> Type #

Hashable GetLocatedImports Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GetLocatedImports Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetLocatedImports Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GetLocatedImports -> () #

type Rep GetLocatedImports Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetLocatedImports = D1 ('MetaData "GetLocatedImports" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "GetLocatedImports" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult GetLocatedImports Source #

Resolve the imports in a module to the file path of a module in the same package or the package id of another package.

Instance details

Defined in Development.IDE.Core.RuleTypes

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

Binary 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-0.5.0-44qfEMOy50OD1DtXc48AUP" '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

data IsFileOfInterestResult Source #

Instances

Instances details
Eq IsFileOfInterestResult Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show IsFileOfInterestResult Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic IsFileOfInterestResult Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep IsFileOfInterestResult :: Type -> Type #

Hashable IsFileOfInterestResult Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary IsFileOfInterestResult Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData IsFileOfInterestResult Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: IsFileOfInterestResult -> () #

type Rep IsFileOfInterestResult Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep IsFileOfInterestResult = D1 ('MetaData "IsFileOfInterestResult" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "NotFOI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IsFOI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FileOfInterestStatus)))

data FileOfInterestStatus Source #

Constructors

OnDisk 
Modified 

Instances

Instances details
Eq FileOfInterestStatus Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show FileOfInterestStatus Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic FileOfInterestStatus Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep FileOfInterestStatus :: Type -> Type #

Hashable FileOfInterestStatus Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary FileOfInterestStatus Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData FileOfInterestStatus Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: FileOfInterestStatus -> () #

type Rep FileOfInterestStatus Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep FileOfInterestStatus = D1 ('MetaData "FileOfInterestStatus" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "OnDisk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Modified" 'PrefixI 'False) (U1 :: Type -> Type))

data DocAndKindMap Source #

Constructors

DKMap 

Instances

Instances details
Show DocAndKindMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData DocAndKindMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: DocAndKindMap -> () #

data HieAstResult Source #

Save the uncompressed AST here, we compress it just before writing to disk

Constructors

HAR 

Fields

Instances

Instances details
Show HieAstResult Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData HieAstResult Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: HieAstResult -> () #

data HiFileResult Source #

Constructors

HiFileResult 

Fields

Instances

Instances details
Show HiFileResult Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData HiFileResult Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: HiFileResult -> () #

data TcModuleResult Source #

Contains the typechecked module and the OrigNameCache entry for that module.

Constructors

TcModuleResult 

Fields

Instances

Instances details
Show TcModuleResult Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData TcModuleResult Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: TcModuleResult -> () #

newtype ImportMap Source #

Constructors

ImportMap 

Fields

Instances

Instances details
Show ImportMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData ImportMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: ImportMap -> () #

data GetImportMap Source #

Constructors

GetImportMap 

Instances

Instances details
Eq GetImportMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GetImportMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GetImportMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetImportMap :: Type -> Type #

Hashable GetImportMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GetImportMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetImportMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GetImportMap -> () #

type Rep GetImportMap Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

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

Defined in Development.IDE.Core.RuleTypes

data GenerateCore Source #

Constructors

GenerateCore 

Instances

Instances details
Eq GenerateCore Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GenerateCore Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GenerateCore Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GenerateCore :: Type -> Type #

Hashable GenerateCore Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GenerateCore Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GenerateCore Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GenerateCore -> () #

type Rep GenerateCore Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GenerateCore = D1 ('MetaData "GenerateCore" "Development.IDE.Core.RuleTypes" "ghcide-0.5.0-44qfEMOy50OD1DtXc48AUP" 'False) (C1 ('MetaCons "GenerateCore" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult GenerateCore Source #

Convert to Core, requires TypeCheck*

Instance details

Defined in Development.IDE.Core.RuleTypes

data GetKnownTargets Source #

Constructors

GetKnownTargets 

Instances

Instances details
Eq GetKnownTargets Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Ord GetKnownTargets Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GetKnownTargets Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GetKnownTargets Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetKnownTargets :: Type -> Type #

Hashable GetKnownTargets Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GetKnownTargets Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetKnownTargets Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GetKnownTargets -> () #

type Rep GetKnownTargets Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

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

Defined in Development.IDE.Core.RuleTypes

data IdeConfiguration Source #

Lsp client relevant configuration details

getFileContents :: NormalizedFilePath -> Action (UTCTime, Maybe Text) Source #

Returns the modification time and the contents. For VFS paths, the modification time is the current time.

getFileExists :: NormalizedFilePath -> Action Bool Source #

Returns True if the file exists Note that a file is not considered to exist unless it is saved to disk. In particular, VFS existence is not enough. Consider the following example: 1. The file A.hs containing the line import B is added to the files of interest Since B.hs is neither open nor exists, GetLocatedImports finds Nothing 2. The editor creates a new buffer B.hs Unless the editor also sends a DidChangeWatchedFile event, ghcide will not pick it up Most editors, e.g. VSCode, only send the event when the file is saved to disk.

data GhcSessionIO Source #

Constructors

GhcSessionIO 

Instances

Instances details
Eq GhcSessionIO Source # 
Instance details

Defined in Development.IDE.Core.Rules

Show GhcSessionIO Source # 
Instance details

Defined in Development.IDE.Core.Rules

Generic GhcSessionIO Source # 
Instance details

Defined in Development.IDE.Core.Rules

Associated Types

type Rep GhcSessionIO :: Type -> Type #

Hashable GhcSessionIO Source # 
Instance details

Defined in Development.IDE.Core.Rules

Binary GhcSessionIO Source # 
Instance details

Defined in Development.IDE.Core.Rules

NFData GhcSessionIO Source # 
Instance details

Defined in Development.IDE.Core.Rules

Methods

rnf :: GhcSessionIO -> () #

type Rep GhcSessionIO Source # 
Instance details

Defined in Development.IDE.Core.Rules

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

Defined in Development.IDE.Core.Rules

getAtPoint :: NormalizedFilePath -> Position -> IdeAction (Maybe (Maybe Range, [Text])) Source #

Try to get hover text for the name under point.

getParsedModule :: NormalizedFilePath -> Action (Maybe ParsedModule) Source #

Parse the contents of a daml file.

data Plugin c Source #

Constructors

Plugin 

Instances

Instances details
Semigroup (Plugin c) Source # 
Instance details

Defined in Development.IDE.Plugin

Methods

(<>) :: Plugin c -> Plugin c -> Plugin c #

sconcat :: NonEmpty (Plugin c) -> Plugin c #

stimes :: Integral b => b -> Plugin c -> Plugin c #

Monoid (Plugin c) Source # 
Instance details

Defined in Development.IDE.Plugin

Methods

mempty :: Plugin c #

mappend :: Plugin c -> Plugin c -> Plugin c #

mconcat :: [Plugin c] -> Plugin c #

Default (Plugin c) Source # 
Instance details

Defined in Development.IDE.Plugin

Methods

def :: Plugin c #

makeLspCommandId :: Text -> IO Text Source #

Prefix to uniquely identify commands sent to the client. This has two parts

  • A representation of the process id to make sure that a client has unique commands if it is running multiple servers, since some clients have a global command table and get confused otherwise.
  • A string to identify ghcide, to ease integration into haskell-language-server, which routes commands to plugins based on that.

getPid :: IO Text Source #

Get the operating system process id for the running server instance. This should be the same for the lifetime of the instance, and different from that of any other currently running instance.