Safe Haskell | None |
---|---|
Language | Haskell2010 |
Development.IDE.Core.RuleTypes
Description
A Shake implementation of the compiler service, built using the Shaker abstraction layer for in-memory use.
Synopsis
- newtype GhcSessionDeps where
- GhcSessionDeps_ { }
- pattern GhcSessionDeps :: GhcSessionDeps
- data GhcSessionIO = GhcSessionIO
- data IdeGhcSession = IdeGhcSession {
- loadSessionFun :: FilePath -> IO (IdeResult HscEnvEq, [FilePath])
- sessionVersion :: !Int
- data AddWatchedFile = AddWatchedFile
- data GetClientSettings = GetClientSettings
- data GetModSummary = GetModSummary
- data GetModSummaryWithoutTimestamps = GetModSummaryWithoutTimestamps
- data IsFileOfInterest = IsFileOfInterest
- data GetModIface = GetModIface
- data GetModIfaceFromDiskAndIndex = GetModIfaceFromDiskAndIndex
- data GetModIfaceFromDisk = GetModIfaceFromDisk
- newtype GhcSessionDeps = GhcSessionDeps_ {}
- data GhcSession = GhcSession
- data GetBindings = GetBindings
- data GetHieAst = GetHieAst
- data GetDocMap = GetDocMap
- data TypeCheck = TypeCheck
- data ReportImportCycles = ReportImportCycles
- data GetModuleGraph = GetModuleGraph
- data GetDependencyInformation = GetDependencyInformation
- data NeedsCompilation = NeedsCompilation
- data GetLocatedImports = GetLocatedImports
- data GetParsedModuleWithComments = GetParsedModuleWithComments
- data GetParsedModule = GetParsedModule
- data ModSummaryResult = ModSummaryResult {}
- data IsFileOfInterestResult
- data FileOfInterestStatus
- data GetFileExists = GetFileExists
- data GetFileContents = GetFileContents
- data FileVersion
- newtype GetModificationTime = GetModificationTime_ {}
- data DocAndKindMap = DKMap {
- getDocMap :: !DocMap
- getKindMap :: !KindMap
- data HieKind a where
- data HieAstResult = forall a. HAR {}
- data HiFileResult = HiFileResult {}
- data TcModuleResult = TcModuleResult {}
- data Splices = Splices {
- exprSplices :: [(LHsExpr GhcTc, LHsExpr GhcPs)]
- patSplices :: [(LHsExpr GhcTc, LPat GhcPs)]
- typeSplices :: [(LHsExpr GhcTc, LHsType GhcPs)]
- declSplices :: [(LHsExpr GhcTc, [LHsDecl GhcPs])]
- awSplices :: [(LHsExpr GhcTc, Serialized)]
- newtype ImportMap = ImportMap {}
- data GetImportMap = GetImportMap
- data GenerateCore = GenerateCore
- data GetKnownTargets = GetKnownTargets
- data LinkableType
- pattern GhcSessionDeps :: GhcSessionDeps
- pattern GetModificationTime :: GetModificationTime
- encodeLinkableType :: Maybe LinkableType -> ByteString
- tmrModSummary :: TcModuleResult -> ModSummary
- hiFileFingerPrint :: HiFileResult -> ByteString
- mkHiFileResult :: ModSummary -> HomeModInfo -> ModuleEnv UTCTime -> HiFileResult
- hirModIface :: HiFileResult -> ModIface
- vfsVersion :: FileVersion -> Maybe Int32
- awSplicesL :: Lens' Splices [(LHsExpr GhcTc, Serialized)]
- declSplicesL :: Lens' Splices [(LHsExpr GhcTc, [LHsDecl GhcPs])]
- exprSplicesL :: Lens' Splices [(LHsExpr GhcTc, LHsExpr GhcPs)]
- patSplicesL :: Lens' Splices [(LHsExpr GhcTc, LPat GhcPs)]
- typeSplicesL :: Lens' Splices [(LHsExpr GhcTc, LHsType GhcPs)]
Documentation
newtype GhcSessionDeps Source #
Constructors
GhcSessionDeps_ | |
Fields
|
Bundled Patterns
pattern GhcSessionDeps :: GhcSessionDeps |
Instances
Eq GhcSessionDeps Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GhcSessionDeps -> GhcSessionDeps -> Bool # (/=) :: GhcSessionDeps -> GhcSessionDeps -> Bool # | |
Show GhcSessionDeps Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GhcSessionDeps -> ShowS # show :: GhcSessionDeps -> String # showList :: [GhcSessionDeps] -> ShowS # | |
Hashable GhcSessionDeps Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData GhcSessionDeps Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GhcSessionDeps -> () # | |
type RuleResult GhcSessionDeps Source # | 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 |
data GhcSessionIO Source #
Constructors
GhcSessionIO |
Instances
Eq GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes | |
Show GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GhcSessionIO -> ShowS # show :: GhcSessionIO -> String # showList :: [GhcSessionIO] -> ShowS # | |
Generic GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GhcSessionIO :: Type -> Type # | |
Hashable GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GhcSessionIO -> () # | |
type Rep GhcSessionIO Source # | |
type RuleResult GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes |
data IdeGhcSession Source #
Constructors
IdeGhcSession | |
Fields
|
Instances
Show IdeGhcSession Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> IdeGhcSession -> ShowS # show :: IdeGhcSession -> String # showList :: [IdeGhcSession] -> ShowS # | |
NFData IdeGhcSession Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: IdeGhcSession -> () # |
data AddWatchedFile Source #
Constructors
AddWatchedFile |
Instances
Eq AddWatchedFile Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: AddWatchedFile -> AddWatchedFile -> Bool # (/=) :: AddWatchedFile -> AddWatchedFile -> Bool # | |
Show AddWatchedFile Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> AddWatchedFile -> ShowS # show :: AddWatchedFile -> String # showList :: [AddWatchedFile] -> ShowS # | |
Generic AddWatchedFile Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep AddWatchedFile :: Type -> Type # Methods from :: AddWatchedFile -> Rep AddWatchedFile x # to :: Rep AddWatchedFile x -> AddWatchedFile # | |
Hashable AddWatchedFile Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData AddWatchedFile Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: AddWatchedFile -> () # | |
type Rep AddWatchedFile Source # | |
type RuleResult AddWatchedFile Source # | |
Defined in Development.IDE.Core.RuleTypes |
data GetClientSettings Source #
Get the vscode client settings stored in the ide state
Constructors
GetClientSettings |
Instances
Eq GetClientSettings Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetClientSettings -> GetClientSettings -> Bool # (/=) :: GetClientSettings -> GetClientSettings -> Bool # | |
Show GetClientSettings Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetClientSettings -> ShowS # show :: GetClientSettings -> String # showList :: [GetClientSettings] -> ShowS # | |
Generic GetClientSettings Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GetClientSettings :: Type -> Type # Methods from :: GetClientSettings -> Rep GetClientSettings x # to :: Rep GetClientSettings x -> GetClientSettings # | |
Hashable GetClientSettings Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData GetClientSettings Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetClientSettings -> () # | |
type Rep GetClientSettings Source # | |
type RuleResult GetClientSettings Source # | |
Defined in Development.IDE.Core.RuleTypes |
data GetModSummary Source #
Constructors
GetModSummary |
Instances
Eq GetModSummary Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetModSummary -> GetModSummary -> Bool # (/=) :: GetModSummary -> GetModSummary -> Bool # | |
Show GetModSummary Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetModSummary -> ShowS # show :: GetModSummary -> String # showList :: [GetModSummary] -> ShowS # | |
Generic GetModSummary Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GetModSummary :: Type -> Type # | |
Hashable GetModSummary Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData GetModSummary Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetModSummary -> () # | |
type Rep GetModSummary Source # | |
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 |
Defined in Development.IDE.Core.RuleTypes |
data GetModSummaryWithoutTimestamps Source #
Constructors
GetModSummaryWithoutTimestamps |
Instances
data IsFileOfInterest Source #
Constructors
IsFileOfInterest |
Instances
Eq IsFileOfInterest Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: IsFileOfInterest -> IsFileOfInterest -> Bool # (/=) :: IsFileOfInterest -> IsFileOfInterest -> Bool # | |
Show IsFileOfInterest Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> IsFileOfInterest -> ShowS # show :: IsFileOfInterest -> String # showList :: [IsFileOfInterest] -> ShowS # | |
Generic IsFileOfInterest Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep IsFileOfInterest :: Type -> Type # Methods from :: IsFileOfInterest -> Rep IsFileOfInterest x # to :: Rep IsFileOfInterest x -> IsFileOfInterest # | |
Hashable IsFileOfInterest Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData IsFileOfInterest Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: IsFileOfInterest -> () # | |
type Rep IsFileOfInterest Source # | |
type RuleResult IsFileOfInterest Source # | |
Defined in Development.IDE.Core.RuleTypes |
data GetModIface Source #
Constructors
GetModIface |
Instances
Eq GetModIface Source # | |
Defined in Development.IDE.Core.RuleTypes | |
Show GetModIface Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetModIface -> ShowS # show :: GetModIface -> String # showList :: [GetModIface] -> ShowS # | |
Generic GetModIface Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GetModIface :: Type -> Type # | |
Hashable GetModIface Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData GetModIface Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetModIface -> () # | |
type Rep GetModIface Source # | |
type RuleResult GetModIface Source # | Get a module interface details, either from an interface file or a typechecked module |
Defined in Development.IDE.Core.RuleTypes |
data GetModIfaceFromDiskAndIndex Source #
Constructors
GetModIfaceFromDiskAndIndex |
Instances
data GetModIfaceFromDisk Source #
Constructors
GetModIfaceFromDisk |
Instances
newtype GhcSessionDeps Source #
Constructors
GhcSessionDeps_ | |
Fields
|
Instances
Eq GhcSessionDeps Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GhcSessionDeps -> GhcSessionDeps -> Bool # (/=) :: GhcSessionDeps -> GhcSessionDeps -> Bool # | |
Show GhcSessionDeps Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GhcSessionDeps -> ShowS # show :: GhcSessionDeps -> String # showList :: [GhcSessionDeps] -> ShowS # | |
Hashable GhcSessionDeps Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData GhcSessionDeps Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GhcSessionDeps -> () # | |
type RuleResult GhcSessionDeps Source # | 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 |
data GhcSession Source #
Constructors
GhcSession |
Instances
Eq GhcSession Source # | |
Defined in Development.IDE.Core.RuleTypes | |
Show GhcSession Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GhcSession -> ShowS # show :: GhcSession -> String # showList :: [GhcSession] -> ShowS # | |
Generic GhcSession Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GhcSession :: Type -> Type # | |
Hashable GhcSession Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData GhcSession Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GhcSession -> () # | |
type Rep GhcSession Source # | |
type RuleResult GhcSession Source # | A GHC session that we reuse. |
Defined in Development.IDE.Core.RuleTypes |
data GetBindings Source #
Constructors
GetBindings |
Instances
Eq GetBindings Source # | |
Defined in Development.IDE.Core.RuleTypes | |
Show GetBindings Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetBindings -> ShowS # show :: GetBindings -> String # showList :: [GetBindings] -> ShowS # | |
Generic GetBindings Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GetBindings :: Type -> Type # | |
Hashable GetBindings Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData GetBindings Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetBindings -> () # | |
type Rep GetBindings Source # | |
type RuleResult GetBindings Source # | A IntervalMap telling us what is in scope at each point |
Defined in Development.IDE.Core.RuleTypes |
Constructors
GetHieAst |
Instances
Eq GetHieAst Source # | |
Show GetHieAst Source # | |
Generic GetHieAst Source # | |
Hashable GetHieAst Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData GetHieAst Source # | |
Defined in Development.IDE.Core.RuleTypes | |
type Rep GetHieAst Source # | |
type RuleResult GetHieAst Source # | The uncompressed HieAST |
Defined in Development.IDE.Core.RuleTypes |
Constructors
GetDocMap |
Instances
Eq GetDocMap Source # | |
Show GetDocMap Source # | |
Generic GetDocMap Source # | |
Hashable GetDocMap Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData GetDocMap Source # | |
Defined in Development.IDE.Core.RuleTypes | |
type Rep GetDocMap Source # | |
type RuleResult GetDocMap Source # | |
Defined in Development.IDE.Core.RuleTypes |
Constructors
TypeCheck |
Instances
Eq TypeCheck Source # | |
Show TypeCheck Source # | |
Generic TypeCheck Source # | |
Hashable TypeCheck Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData TypeCheck Source # | |
Defined in Development.IDE.Core.RuleTypes | |
type Rep TypeCheck Source # | |
type RuleResult TypeCheck Source # | The type checked version of this file, requires TypeCheck+ |
Defined in Development.IDE.Core.RuleTypes |
data ReportImportCycles Source #
Constructors
ReportImportCycles |
Instances
data GetModuleGraph Source #
Constructors
GetModuleGraph |
Instances
Eq GetModuleGraph Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetModuleGraph -> GetModuleGraph -> Bool # (/=) :: GetModuleGraph -> GetModuleGraph -> Bool # | |
Show GetModuleGraph Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetModuleGraph -> ShowS # show :: GetModuleGraph -> String # showList :: [GetModuleGraph] -> ShowS # | |
Generic GetModuleGraph Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GetModuleGraph :: Type -> Type # Methods from :: GetModuleGraph -> Rep GetModuleGraph x # to :: Rep GetModuleGraph x -> GetModuleGraph # | |
Hashable GetModuleGraph Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData GetModuleGraph Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetModuleGraph -> () # | |
type Rep GetModuleGraph Source # | |
type RuleResult GetModuleGraph Source # | |
Defined in Development.IDE.Core.RuleTypes |
data GetDependencyInformation Source #
Constructors
GetDependencyInformation |
Instances
data NeedsCompilation Source #
Constructors
NeedsCompilation |
Instances
Eq NeedsCompilation Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: NeedsCompilation -> NeedsCompilation -> Bool # (/=) :: NeedsCompilation -> NeedsCompilation -> Bool # | |
Show NeedsCompilation Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> NeedsCompilation -> ShowS # show :: NeedsCompilation -> String # showList :: [NeedsCompilation] -> ShowS # | |
Generic NeedsCompilation Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep NeedsCompilation :: Type -> Type # Methods from :: NeedsCompilation -> Rep NeedsCompilation x # to :: Rep NeedsCompilation x -> NeedsCompilation # | |
Hashable NeedsCompilation Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData NeedsCompilation Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: NeedsCompilation -> () # | |
type Rep NeedsCompilation Source # | |
type RuleResult NeedsCompilation Source # | Does this module need to be compiled? |
Defined in Development.IDE.Core.RuleTypes |
data GetLocatedImports Source #
Constructors
GetLocatedImports |
Instances
data GetParsedModuleWithComments Source #
Constructors
GetParsedModuleWithComments |
Instances
data GetParsedModule Source #
Constructors
GetParsedModule |
Instances
Eq GetParsedModule Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetParsedModule -> GetParsedModule -> Bool # (/=) :: GetParsedModule -> GetParsedModule -> Bool # | |
Show GetParsedModule Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetParsedModule -> ShowS # show :: GetParsedModule -> String # showList :: [GetParsedModule] -> ShowS # | |
Generic GetParsedModule Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GetParsedModule :: Type -> Type # Methods from :: GetParsedModule -> Rep GetParsedModule x # to :: Rep GetParsedModule x -> GetParsedModule # | |
Hashable GetParsedModule Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData GetParsedModule Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetParsedModule -> () # | |
type Rep GetParsedModule Source # | |
type RuleResult GetParsedModule Source # | The parse tree for the file using GetFileContents |
Defined in Development.IDE.Core.RuleTypes |
data ModSummaryResult Source #
Constructors
ModSummaryResult | |
Fields
|
Instances
Show ModSummaryResult Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> ModSummaryResult -> ShowS # show :: ModSummaryResult -> String # showList :: [ModSummaryResult] -> ShowS # | |
NFData ModSummaryResult Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: ModSummaryResult -> () # |
data IsFileOfInterestResult Source #
Constructors
NotFOI | |
IsFOI FileOfInterestStatus |
Instances
data FileOfInterestStatus Source #
Instances
data GetFileExists Source #
Constructors
GetFileExists |
Instances
Eq GetFileExists Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetFileExists -> GetFileExists -> Bool # (/=) :: GetFileExists -> GetFileExists -> Bool # | |
Show GetFileExists Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetFileExists -> ShowS # show :: GetFileExists -> String # showList :: [GetFileExists] -> ShowS # | |
Generic GetFileExists Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GetFileExists :: Type -> Type # | |
Hashable GetFileExists Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData GetFileExists Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetFileExists -> () # | |
type Rep GetFileExists Source # | |
type RuleResult GetFileExists Source # | |
Defined in Development.IDE.Core.RuleTypes |
data GetFileContents Source #
Constructors
GetFileContents |
Instances
data FileVersion Source #
Either the mtime from disk or an LSP version LSP versions always compare as greater than on disk versions
Constructors
ModificationTime !POSIXTime | |
VFSVersion !Int32 |
Instances
newtype GetModificationTime Source #
Constructors
GetModificationTime_ | |
Fields
|
Instances
data DocAndKindMap Source #
Constructors
DKMap | |
Fields
|
Instances
Show DocAndKindMap Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> DocAndKindMap -> ShowS # show :: DocAndKindMap -> String # showList :: [DocAndKindMap] -> ShowS # | |
NFData DocAndKindMap Source # | |
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
forall a. HAR | |
Fields |
Instances
Show HieAstResult Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> HieAstResult -> ShowS # show :: HieAstResult -> String # showList :: [HieAstResult] -> ShowS # | |
NFData HieAstResult Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: HieAstResult -> () # |
data HiFileResult Source #
Constructors
HiFileResult | |
Fields
|
Instances
Show HiFileResult Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> HiFileResult -> ShowS # show :: HiFileResult -> String # showList :: [HiFileResult] -> ShowS # | |
NFData HiFileResult Source # | |
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
Show TcModuleResult Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> TcModuleResult -> ShowS # show :: TcModuleResult -> String # showList :: [TcModuleResult] -> ShowS # | |
NFData TcModuleResult Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: TcModuleResult -> () # |
Constructors
Splices | |
Fields
|
Constructors
ImportMap | |
Fields
|
data GetImportMap Source #
Constructors
GetImportMap |
Instances
Eq GetImportMap Source # | |
Defined in Development.IDE.Core.RuleTypes | |
Show GetImportMap Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetImportMap -> ShowS # show :: GetImportMap -> String # showList :: [GetImportMap] -> ShowS # | |
Generic GetImportMap Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GetImportMap :: Type -> Type # | |
Hashable GetImportMap Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData GetImportMap Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetImportMap -> () # | |
type Rep GetImportMap Source # | |
type RuleResult GetImportMap Source # | |
Defined in Development.IDE.Core.RuleTypes |
data GenerateCore Source #
Constructors
GenerateCore |
Instances
Eq GenerateCore Source # | |
Defined in Development.IDE.Core.RuleTypes | |
Show GenerateCore Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GenerateCore -> ShowS # show :: GenerateCore -> String # showList :: [GenerateCore] -> ShowS # | |
Generic GenerateCore Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GenerateCore :: Type -> Type # | |
Hashable GenerateCore Source # | |
Defined in Development.IDE.Core.RuleTypes | |
NFData GenerateCore Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GenerateCore -> () # | |
type Rep GenerateCore Source # | |
type RuleResult GenerateCore Source # | Convert to Core, requires TypeCheck* |
Defined in Development.IDE.Core.RuleTypes |
data GetKnownTargets Source #
Constructors
GetKnownTargets |
Instances
data LinkableType Source #
Constructors
ObjectLinkable | |
BCOLinkable |
Instances
pattern GhcSessionDeps :: GhcSessionDeps Source #
pattern GetModificationTime :: GetModificationTime Source #
encodeLinkableType :: Maybe LinkableType -> ByteString Source #
Encode the linkable into an ordered bytestring.
This is used to drive an ordered "newness" predicate in the
NeedsCompilation
build rule.
mkHiFileResult :: ModSummary -> HomeModInfo -> ModuleEnv UTCTime -> HiFileResult Source #
hirModIface :: HiFileResult -> ModIface Source #
vfsVersion :: FileVersion -> Maybe Int32 Source #
awSplicesL :: Lens' Splices [(LHsExpr GhcTc, Serialized)] Source #