Safe Haskell | None |
---|---|
Language | Haskell2010 |
A Shake implementation of the compiler service, built using the Shaker abstraction layer for in-memory use.
Synopsis
- data IdeState
- data GetDependencies = GetDependencies
- data GetParsedModule = GetParsedModule
- data TransitiveDependencies = TransitiveDependencies {}
- newtype Priority = Priority Double
- data GhcSessionIO = GhcSessionIO
- priorityTypeCheck :: Priority
- priorityGenerateCore :: Priority
- priorityFilesOfInterest :: Priority
- runAction :: String -> IdeState -> Action a -> IO a
- useE :: IdeRule k v => k -> NormalizedFilePath -> MaybeT IdeAction (v, PositionMapping)
- useNoFileE :: IdeRule k v => IdeState -> k -> MaybeT IdeAction v
- usesE :: IdeRule k v => k -> [NormalizedFilePath] -> MaybeT IdeAction [(v, PositionMapping)]
- toIdeResult :: Either [FileDiagnostic] v -> IdeResult v
- defineNoFile :: IdeRule k v => (k -> Action v) -> Rules ()
- defineEarlyCutOffNoFile :: IdeRule k v => (k -> Action (ByteString, v)) -> Rules ()
- mainRule :: Rules ()
- getAtPoint :: NormalizedFilePath -> Position -> IdeAction (Maybe (Maybe Range, [Text]))
- getDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe Location)
- getTypeDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location])
- getDependencies :: NormalizedFilePath -> Action (Maybe [NormalizedFilePath])
- getParsedModule :: NormalizedFilePath -> Action (Maybe ParsedModule)
- generateCore :: RunSimplifier -> NormalizedFilePath -> Action (IdeResult (SafeHaskellMode, CgGuts, ModDetails))
Documentation
A Shake database plus persistent store. Can be thought of as storing
mappings from (FilePath, k)
to RuleResult k
.
data GetDependencies Source #
Instances
data GetParsedModule Source #
Instances
data TransitiveDependencies Source #
TransitiveDependencies | |
|
Instances
data GhcSessionIO Source #
Instances
Eq GhcSessionIO Source # | |
Defined in Development.IDE.Core.Rules (==) :: GhcSessionIO -> GhcSessionIO -> Bool # (/=) :: GhcSessionIO -> GhcSessionIO -> Bool # | |
Show GhcSessionIO Source # | |
Defined in Development.IDE.Core.Rules showsPrec :: Int -> GhcSessionIO -> ShowS # show :: GhcSessionIO -> String # showList :: [GhcSessionIO] -> ShowS # | |
Generic GhcSessionIO Source # | |
Defined in Development.IDE.Core.Rules type Rep GhcSessionIO :: Type -> Type # from :: GhcSessionIO -> Rep GhcSessionIO x # to :: Rep GhcSessionIO x -> GhcSessionIO # | |
Hashable GhcSessionIO Source # | |
Defined in Development.IDE.Core.Rules hashWithSalt :: Int -> GhcSessionIO -> Int # hash :: GhcSessionIO -> Int # | |
Binary GhcSessionIO Source # | |
Defined in Development.IDE.Core.Rules | |
NFData GhcSessionIO Source # | |
Defined in Development.IDE.Core.Rules rnf :: GhcSessionIO -> () # | |
type Rep GhcSessionIO Source # | |
type RuleResult GhcSessionIO Source # | |
Defined in Development.IDE.Core.Rules |
useE :: IdeRule k v => k -> NormalizedFilePath -> MaybeT IdeAction (v, PositionMapping) Source #
useE is useful to implement functions that aren’t rules but need shortcircuiting e.g. getDefinition.
usesE :: IdeRule k v => k -> [NormalizedFilePath] -> MaybeT IdeAction [(v, PositionMapping)] Source #
toIdeResult :: Either [FileDiagnostic] v -> IdeResult v Source #
This is useful for rules to convert rules that can only produce errors or a result into the more general IdeResult type that supports producing warnings while also producing a result.
defineEarlyCutOffNoFile :: IdeRule k v => (k -> Action (ByteString, v)) -> Rules () Source #
getAtPoint :: NormalizedFilePath -> Position -> IdeAction (Maybe (Maybe Range, [Text])) Source #
Try to get hover text for the name under point.
getDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe Location) Source #
Goto Definition.
getTypeDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location]) Source #
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 daml file.
generateCore :: RunSimplifier -> NormalizedFilePath -> Action (IdeResult (SafeHaskellMode, CgGuts, ModDetails)) Source #