| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | GHC2021 | 
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 TcModuleResult = TcModuleResult {}
 - data FileOfInterestStatus
 - data GetParsedModule = GetParsedModule
 - data GhcSessionIO = GhcSessionIO
 - data GetClientSettings = GetClientSettings
 - newtype GhcSessionDeps = GhcSessionDeps_ {}
 - newtype GetModificationTime = GetModificationTime_ {}
 - data FileVersion
 - data GenerateCore = GenerateCore
 - data GetHieAst = GetHieAst
 - data TypeCheck = TypeCheck
 - data IdeGhcSession = IdeGhcSession {
- loadSessionFun :: FilePath -> IO (IdeResult HscEnvEq, [FilePath])
 - sessionVersion :: !Int
 
 - data GhcSession = GhcSession
 - data GetFileExists = GetFileExists
 - newtype ImportMap = ImportMap {}
 - data LinkableType
 - data GetParsedModuleWithComments = GetParsedModuleWithComments
 - data GetModuleGraph = GetModuleGraph
 - data GetKnownTargets = GetKnownTargets
 - data GetLinkable = GetLinkable
 - data LinkableResult = LinkableResult {}
 - data GetImportMap = GetImportMap
 - 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)]
 
 - data HiFileResult = HiFileResult {
- hirModSummary :: !ModSummary
 - hirModIface :: !ModIface
 - hirModDetails :: ModDetails
 - hirIfaceFp :: !ByteString
 - hirRuntimeModules :: !(ModuleEnv ByteString)
 - hirCoreFp :: !(Maybe (CoreFile, ByteString))
 
 - data HieAstResult = forall a.Typeable a => HAR {}
 - data HieKind a where
 - data GetBindings = GetBindings
 - data DocAndTyThingMap = DKMap {
- getDocMap :: !DocMap
 - getTyThingMap :: !TyThingMap
 
 - data GetDocMap = GetDocMap
 - data GetLocatedImports = GetLocatedImports
 - data ReportImportCycles = ReportImportCycles
 - data GetModIfaceFromDisk = GetModIfaceFromDisk
 - data GetModIfaceFromDiskAndIndex = GetModIfaceFromDiskAndIndex
 - data GetModIface = GetModIface
 - data GetFileContents = GetFileContents
 - data AddWatchedFile = AddWatchedFile
 - data IsFileOfInterestResult
 - data IsFileOfInterest = IsFileOfInterest
 - data ModSummaryResult = ModSummaryResult {}
 - data GetModSummary = GetModSummary
 - data GetModSummaryWithoutTimestamps = GetModSummaryWithoutTimestamps
 - data NeedsCompilation = NeedsCompilation
 - pattern GhcSessionDeps :: GhcSessionDeps
 - pattern GetModificationTime :: GetModificationTime
 - encodeLinkableType :: Maybe LinkableType -> ByteString
 - tmrModSummary :: TcModuleResult -> ModSummary
 - hiFileFingerPrint :: HiFileResult -> ByteString
 - mkHiFileResult :: ModSummary -> ModIface -> ModDetails -> ModuleEnv ByteString -> Maybe (CoreFile, ByteString) -> HiFileResult
 - 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
| Show GhcSessionDeps Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GhcSessionDeps -> ShowS # show :: GhcSessionDeps -> String # showList :: [GhcSessionDeps] -> ShowS #  | |
| NFData GhcSessionDeps Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GhcSessionDeps -> () #  | |
| Eq GhcSessionDeps Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GhcSessionDeps -> GhcSessionDeps -> Bool # (/=) :: GhcSessionDeps -> GhcSessionDeps -> Bool #  | |
| Hashable GhcSessionDeps Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| 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 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 -> () #  | |
data FileOfInterestStatus Source #
Instances
data GetParsedModule Source #
Constructors
| GetParsedModule | 
Instances
| 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 #  | |
| Show GetParsedModule Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetParsedModule -> ShowS # show :: GetParsedModule -> String # showList :: [GetParsedModule] -> ShowS #  | |
| NFData GetParsedModule Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetParsedModule -> () #  | |
| Eq GetParsedModule Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetParsedModule -> GetParsedModule -> Bool # (/=) :: GetParsedModule -> GetParsedModule -> Bool #  | |
| Hashable GetParsedModule Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| type Rep GetParsedModule Source # | |
| type RuleResult GetParsedModule Source # | The parse tree for the file using GetFileContents  | 
Defined in Development.IDE.Core.RuleTypes  | |
data GhcSessionIO Source #
Constructors
| GhcSessionIO | 
Instances
| Generic GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GhcSessionIO :: Type -> Type #  | |
| Show GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GhcSessionIO -> ShowS # show :: GhcSessionIO -> String # showList :: [GhcSessionIO] -> ShowS #  | |
| NFData GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GhcSessionIO -> () #  | |
| Eq GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| Hashable GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| type Rep GhcSessionIO Source # | |
| type RuleResult GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
data GetClientSettings Source #
Get the client config stored in the ide state
Constructors
| GetClientSettings | 
Instances
| 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 #  | |
| Show GetClientSettings Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetClientSettings -> ShowS # show :: GetClientSettings -> String # showList :: [GetClientSettings] -> ShowS #  | |
| NFData GetClientSettings Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetClientSettings -> () #  | |
| Eq GetClientSettings Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetClientSettings -> GetClientSettings -> Bool # (/=) :: GetClientSettings -> GetClientSettings -> Bool #  | |
| Hashable GetClientSettings Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| type Rep GetClientSettings Source # | |
| type RuleResult GetClientSettings Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
newtype GhcSessionDeps Source #
Constructors
| GhcSessionDeps_ | |
Fields 
  | |
Instances
| Show GhcSessionDeps Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GhcSessionDeps -> ShowS # show :: GhcSessionDeps -> String # showList :: [GhcSessionDeps] -> ShowS #  | |
| NFData GhcSessionDeps Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GhcSessionDeps -> () #  | |
| Eq GhcSessionDeps Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GhcSessionDeps -> GhcSessionDeps -> Bool # (/=) :: GhcSessionDeps -> GhcSessionDeps -> Bool #  | |
| Hashable GhcSessionDeps Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| 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  | |
newtype GetModificationTime Source #
Constructors
| GetModificationTime_ | |
Fields 
  | |
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
data GenerateCore Source #
Constructors
| GenerateCore | 
Instances
| Generic GenerateCore Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GenerateCore :: Type -> Type #  | |
| Show GenerateCore Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GenerateCore -> ShowS # show :: GenerateCore -> String # showList :: [GenerateCore] -> ShowS #  | |
| NFData GenerateCore Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GenerateCore -> () #  | |
| Eq GenerateCore Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| Hashable GenerateCore Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| type Rep GenerateCore Source # | |
| type RuleResult GenerateCore Source # | Convert to Core, requires TypeCheck*  | 
Defined in Development.IDE.Core.RuleTypes  | |
Constructors
| GetHieAst | 
Instances
| Generic GetHieAst Source # | |
| Show GetHieAst Source # | |
| NFData GetHieAst Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| Eq GetHieAst Source # | |
| Hashable 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
| TypeCheck | 
Instances
| Generic TypeCheck Source # | |
| Show TypeCheck Source # | |
| NFData TypeCheck Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| Eq TypeCheck Source # | |
| Hashable 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 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 GhcSession Source #
Constructors
| GhcSession | 
Instances
| Generic GhcSession Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GhcSession :: Type -> Type #  | |
| Show GhcSession Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GhcSession -> ShowS # show :: GhcSession -> String # showList :: [GhcSession] -> ShowS #  | |
| NFData GhcSession Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GhcSession -> () #  | |
| Eq GhcSession Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| Hashable GhcSession Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| type Rep GhcSession Source # | |
| type RuleResult GhcSession Source # | A GHC session that we reuse.  | 
Defined in Development.IDE.Core.RuleTypes  | |
data GetFileExists Source #
Constructors
| GetFileExists | 
Instances
| Generic GetFileExists Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GetFileExists :: Type -> Type #  | |
| Show GetFileExists Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetFileExists -> ShowS # show :: GetFileExists -> String # showList :: [GetFileExists] -> ShowS #  | |
| NFData GetFileExists Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetFileExists -> () #  | |
| Eq GetFileExists Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetFileExists -> GetFileExists -> Bool # (/=) :: GetFileExists -> GetFileExists -> Bool #  | |
| Hashable GetFileExists Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| type Rep GetFileExists Source # | |
| type RuleResult GetFileExists Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
Constructors
| ImportMap | |
Fields 
  | |
data LinkableType Source #
Constructors
| ObjectLinkable | |
| BCOLinkable | 
Instances
data GetParsedModuleWithComments Source #
Constructors
| GetParsedModuleWithComments | 
Instances
data GetModuleGraph Source #
Constructors
| GetModuleGraph | 
Instances
| 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 #  | |
| Show GetModuleGraph Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetModuleGraph -> ShowS # show :: GetModuleGraph -> String # showList :: [GetModuleGraph] -> ShowS #  | |
| NFData GetModuleGraph Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetModuleGraph -> () #  | |
| Eq GetModuleGraph Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetModuleGraph -> GetModuleGraph -> Bool # (/=) :: GetModuleGraph -> GetModuleGraph -> Bool #  | |
| Hashable GetModuleGraph Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| type Rep GetModuleGraph Source # | |
| type RuleResult GetModuleGraph Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
data GetKnownTargets Source #
Constructors
| GetKnownTargets | 
Instances
data GetLinkable Source #
Constructors
| GetLinkable | 
Instances
| Generic GetLinkable Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GetLinkable :: Type -> Type #  | |
| Show GetLinkable Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetLinkable -> ShowS # show :: GetLinkable -> String # showList :: [GetLinkable] -> ShowS #  | |
| NFData GetLinkable Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetLinkable -> () #  | |
| Eq GetLinkable Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| Hashable GetLinkable Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| type Rep GetLinkable Source # | |
| type RuleResult GetLinkable Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
data LinkableResult Source #
Constructors
| LinkableResult | |
Fields 
  | |
Instances
| Show LinkableResult Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> LinkableResult -> ShowS # show :: LinkableResult -> String # showList :: [LinkableResult] -> ShowS #  | |
| NFData LinkableResult Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: LinkableResult -> () #  | |
data GetImportMap Source #
Constructors
| GetImportMap | 
Instances
| Generic GetImportMap Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GetImportMap :: Type -> Type #  | |
| Show GetImportMap Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetImportMap -> ShowS # show :: GetImportMap -> String # showList :: [GetImportMap] -> ShowS #  | |
| NFData GetImportMap Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetImportMap -> () #  | |
| Eq GetImportMap Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| Hashable GetImportMap Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| type Rep GetImportMap Source # | |
| type RuleResult GetImportMap Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
Constructors
| Splices | |
Fields 
  | |
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 HieAstResult Source #
Save the uncompressed AST here, we compress it just before writing to disk
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 GetBindings Source #
Constructors
| GetBindings | 
Instances
| Generic GetBindings Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GetBindings :: Type -> Type #  | |
| Show GetBindings Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetBindings -> ShowS # show :: GetBindings -> String # showList :: [GetBindings] -> ShowS #  | |
| NFData GetBindings Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetBindings -> () #  | |
| Eq GetBindings Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| Hashable GetBindings Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| 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  | |
data DocAndTyThingMap Source #
Constructors
| DKMap | |
Fields 
  | |
Instances
| Show DocAndTyThingMap Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> DocAndTyThingMap -> ShowS # show :: DocAndTyThingMap -> String # showList :: [DocAndTyThingMap] -> ShowS #  | |
| NFData DocAndTyThingMap Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: DocAndTyThingMap -> () #  | |
Constructors
| GetDocMap | 
Instances
| Generic GetDocMap Source # | |
| Show GetDocMap Source # | |
| NFData GetDocMap Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| Eq GetDocMap Source # | |
| Hashable GetDocMap Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| type Rep GetDocMap Source # | |
| type RuleResult GetDocMap Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
data GetLocatedImports Source #
Constructors
| GetLocatedImports | 
Instances
data ReportImportCycles Source #
Constructors
| ReportImportCycles | 
Instances
data GetModIfaceFromDisk Source #
Constructors
| GetModIfaceFromDisk | 
Instances
data GetModIfaceFromDiskAndIndex Source #
Constructors
| GetModIfaceFromDiskAndIndex | 
Instances
data GetModIface Source #
Constructors
| GetModIface | 
Instances
| Generic GetModIface Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GetModIface :: Type -> Type #  | |
| Show GetModIface Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetModIface -> ShowS # show :: GetModIface -> String # showList :: [GetModIface] -> ShowS #  | |
| NFData GetModIface Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetModIface -> () #  | |
| Eq GetModIface Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| Hashable GetModIface Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| 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 GetFileContents Source #
Constructors
| GetFileContents | 
Instances
data AddWatchedFile Source #
Constructors
| AddWatchedFile | 
Instances
| 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 #  | |
| Show AddWatchedFile Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> AddWatchedFile -> ShowS # show :: AddWatchedFile -> String # showList :: [AddWatchedFile] -> ShowS #  | |
| NFData AddWatchedFile Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: AddWatchedFile -> () #  | |
| Eq AddWatchedFile Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: AddWatchedFile -> AddWatchedFile -> Bool # (/=) :: AddWatchedFile -> AddWatchedFile -> Bool #  | |
| Hashable AddWatchedFile Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| type Rep AddWatchedFile Source # | |
| type RuleResult AddWatchedFile Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
data IsFileOfInterestResult Source #
Constructors
| NotFOI | |
| IsFOI FileOfInterestStatus | 
Instances
data IsFileOfInterest Source #
Constructors
| IsFileOfInterest | 
Instances
| 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 #  | |
| Show IsFileOfInterest Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> IsFileOfInterest -> ShowS # show :: IsFileOfInterest -> String # showList :: [IsFileOfInterest] -> ShowS #  | |
| NFData IsFileOfInterest Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: IsFileOfInterest -> () #  | |
| Eq IsFileOfInterest Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: IsFileOfInterest -> IsFileOfInterest -> Bool # (/=) :: IsFileOfInterest -> IsFileOfInterest -> Bool #  | |
| Hashable IsFileOfInterest Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| type Rep IsFileOfInterest Source # | |
| type RuleResult IsFileOfInterest Source # | |
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 GetModSummary Source #
Constructors
| GetModSummary | 
Instances
| Generic GetModSummary Source # | |
Defined in Development.IDE.Core.RuleTypes Associated Types type Rep GetModSummary :: Type -> Type #  | |
| Show GetModSummary Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetModSummary -> ShowS # show :: GetModSummary -> String # showList :: [GetModSummary] -> ShowS #  | |
| NFData GetModSummary Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetModSummary -> () #  | |
| Eq GetModSummary Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetModSummary -> GetModSummary -> Bool # (/=) :: GetModSummary -> GetModSummary -> Bool #  | |
| Hashable GetModSummary Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| 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 NeedsCompilation Source #
Constructors
| NeedsCompilation | 
Instances
| 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 #  | |
| Show NeedsCompilation Source # | |
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> NeedsCompilation -> ShowS # show :: NeedsCompilation -> String # showList :: [NeedsCompilation] -> ShowS #  | |
| NFData NeedsCompilation Source # | |
Defined in Development.IDE.Core.RuleTypes Methods rnf :: NeedsCompilation -> () #  | |
| Eq NeedsCompilation Source # | |
Defined in Development.IDE.Core.RuleTypes Methods (==) :: NeedsCompilation -> NeedsCompilation -> Bool # (/=) :: NeedsCompilation -> NeedsCompilation -> Bool #  | |
| Hashable NeedsCompilation Source # | |
Defined in Development.IDE.Core.RuleTypes  | |
| type Rep NeedsCompilation Source # | |
| type RuleResult NeedsCompilation Source # | Does this module need to be compiled?  | 
Defined in Development.IDE.Core.RuleTypes  | |
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 -> ModIface -> ModDetails -> ModuleEnv ByteString -> Maybe (CoreFile, ByteString) -> HiFileResult Source #
vfsVersion :: FileVersion -> Maybe Int32 Source #
awSplicesL :: Lens' Splices [(LHsExpr GhcTc, Serialized)] Source #