| Safe Haskell | None |
|---|---|
| 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_ {}
- pattern GhcSessionDeps :: GhcSessionDeps
- newtype GetModificationTime = GetModificationTime_ {}
- pattern 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 GetLocatedImports = GetLocatedImports
- data GetKnownTargets = GetKnownTargets
- data LinkableType
- encodeLinkableType :: Maybe LinkableType -> ByteString
- data GetParsedModuleWithComments = GetParsedModuleWithComments
- data GetModuleGraph = GetModuleGraph
- data GetModuleGraphTransDepsFingerprints = GetModuleGraphTransDepsFingerprints
- data GetModuleGraphTransReverseDepsFingerprints = GetModuleGraphTransReverseDepsFingerprints
- data GetModuleGraphImmediateReverseDepsFingerprints = GetModuleGraphImmediateReverseDepsFingerprints
- 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)]
- tmrModSummary :: TcModuleResult -> ModSummary
- data HiFileResult = HiFileResult {
- hirModSummary :: !ModSummary
- hirModIface :: !ModIface
- hirModDetails :: ModDetails
- hirIfaceFp :: !ByteString
- hirRuntimeModules :: !(ModuleEnv ByteString)
- hirCoreFp :: !(Maybe (CoreFile, ByteString))
- hiFileFingerPrint :: HiFileResult -> ByteString
- mkHiFileResult :: ModSummary -> ModIface -> ModDetails -> ModuleEnv ByteString -> Maybe (CoreFile, ByteString) -> HiFileResult
- data HieAstResult = Typeable a => HAR {}
- data HieKind a where
- data GetBindings = GetBindings
- data DocAndTyThingMap = DKMap {
- getDocMap :: !DocMap
- getTyThingMap :: !TyThingMap
- getArgDocMap :: !ArgDocMap
- data GetDocMap = GetDocMap
- data ReportImportCycles = ReportImportCycles
- data GetModIfaceFromDisk = GetModIfaceFromDisk
- data GetModIfaceFromDiskAndIndex = GetModIfaceFromDiskAndIndex
- data GetModIface = GetModIface
- data GetFileContents = GetFileContents
- data GetFileHash = GetFileHash
- data AddWatchedFile = AddWatchedFile
- data GetPhysicalModificationTime = GetPhysicalModificationTime
- vfsVersion :: FileVersion -> Maybe Int32
- data IsFileOfInterestResult
- data IsFileOfInterest = IsFileOfInterest
- data ModSummaryResult = ModSummaryResult {}
- data GetModSummary = GetModSummary
- data GetModSummaryWithoutTimestamps = GetModSummaryWithoutTimestamps
- data NeedsCompilation = NeedsCompilation
- 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
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
| |||||
| 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
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 | |
pattern GhcSessionDeps :: GhcSessionDeps Source #
newtype GetModificationTime Source #
Constructors
| GetModificationTime_ | |
Fields
| |
Instances
| Generic GetModificationTime Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
Methods from :: GetModificationTime -> Rep GetModificationTime x # to :: Rep GetModificationTime x -> GetModificationTime # | |||||
| Show GetModificationTime Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetModificationTime -> ShowS # show :: GetModificationTime -> String # showList :: [GetModificationTime] -> ShowS # | |||||
| NFData GetModificationTime Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetModificationTime -> () # | |||||
| Eq GetModificationTime Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetModificationTime -> GetModificationTime -> Bool # (/=) :: GetModificationTime -> GetModificationTime -> Bool # | |||||
| Hashable GetModificationTime Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
| type Rep GetModificationTime Source # | |||||
Defined in Development.IDE.Core.RuleTypes type Rep GetModificationTime = D1 ('MetaData "GetModificationTime" "Development.IDE.Core.RuleTypes" "ghcide-2.13.0.0-3xOdL4E2K8pFtuI1JRT6Li" 'True) (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. | ||||
Defined in Development.IDE.Core.RuleTypes | |||||
pattern GetModificationTime :: GetModificationTime Source #
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
| Generic FileVersion Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
| |||||
| Show FileVersion Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> FileVersion -> ShowS # show :: FileVersion -> String # showList :: [FileVersion] -> ShowS # | |||||
| NFData FileVersion Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: FileVersion -> () # | |||||
| Eq FileVersion Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
| Ord FileVersion Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods compare :: FileVersion -> FileVersion -> Ordering # (<) :: FileVersion -> FileVersion -> Bool # (<=) :: FileVersion -> FileVersion -> Bool # (>) :: FileVersion -> FileVersion -> Bool # (>=) :: FileVersion -> FileVersion -> Bool # max :: FileVersion -> FileVersion -> FileVersion # min :: FileVersion -> FileVersion -> FileVersion # | |||||
| type Rep FileVersion Source # | |||||
Defined in Development.IDE.Core.RuleTypes type Rep FileVersion = D1 ('MetaData "FileVersion" "Development.IDE.Core.RuleTypes" "ghcide-2.13.0.0-3xOdL4E2K8pFtuI1JRT6Li" 'False) (C1 ('MetaCons "ModificationTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 POSIXTime)) :+: C1 ('MetaCons "VFSVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int32))) | |||||
data GenerateCore Source #
Constructors
| GenerateCore |
Instances
| Generic GenerateCore Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
| |||||
| 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 # | |
Defined in Development.IDE.Core.RuleTypes | |
| 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 # | |
Defined in Development.IDE.Core.RuleTypes | |
| 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
| |||||
| 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
| |||||
| 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 GetLocatedImports Source #
Constructors
| GetLocatedImports |
Instances
| Generic GetLocatedImports Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
Methods from :: GetLocatedImports -> Rep GetLocatedImports x # to :: Rep GetLocatedImports x -> GetLocatedImports # | |||||
| Show GetLocatedImports Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetLocatedImports -> ShowS # show :: GetLocatedImports -> String # showList :: [GetLocatedImports] -> ShowS # | |||||
| NFData GetLocatedImports Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetLocatedImports -> () # | |||||
| Eq GetLocatedImports Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetLocatedImports -> GetLocatedImports -> Bool # (/=) :: GetLocatedImports -> GetLocatedImports -> Bool # | |||||
| Hashable GetLocatedImports Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
| type Rep GetLocatedImports Source # | |||||
| type RuleResult GetLocatedImports Source # | Resolve the imports in a module to the file path of a module in the same package | ||||
Defined in Development.IDE.Core.RuleTypes | |||||
data GetKnownTargets Source #
Constructors
| GetKnownTargets |
Instances
| Generic GetKnownTargets Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
Methods from :: GetKnownTargets -> Rep GetKnownTargets x # to :: Rep GetKnownTargets x -> GetKnownTargets # | |||||
| Show GetKnownTargets Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetKnownTargets -> ShowS # show :: GetKnownTargets -> String # showList :: [GetKnownTargets] -> ShowS # | |||||
| NFData GetKnownTargets Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetKnownTargets -> () # | |||||
| Eq GetKnownTargets Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetKnownTargets -> GetKnownTargets -> Bool # (/=) :: GetKnownTargets -> GetKnownTargets -> Bool # | |||||
| Ord GetKnownTargets Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods compare :: GetKnownTargets -> GetKnownTargets -> Ordering # (<) :: GetKnownTargets -> GetKnownTargets -> Bool # (<=) :: GetKnownTargets -> GetKnownTargets -> Bool # (>) :: GetKnownTargets -> GetKnownTargets -> Bool # (>=) :: GetKnownTargets -> GetKnownTargets -> Bool # max :: GetKnownTargets -> GetKnownTargets -> GetKnownTargets # min :: GetKnownTargets -> GetKnownTargets -> GetKnownTargets # | |||||
| Hashable GetKnownTargets Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
| type Rep GetKnownTargets Source # | |||||
| type RuleResult GetKnownTargets Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
data LinkableType Source #
Constructors
| ObjectLinkable | |
| BCOLinkable |
Instances
| Generic LinkableType Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
| |||||
| Show LinkableType Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> LinkableType -> ShowS # show :: LinkableType -> String # showList :: [LinkableType] -> ShowS # | |||||
| NFData LinkableType Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: LinkableType -> () # | |||||
| Eq LinkableType Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
| Ord LinkableType Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods compare :: LinkableType -> LinkableType -> Ordering # (<) :: LinkableType -> LinkableType -> Bool # (<=) :: LinkableType -> LinkableType -> Bool # (>) :: LinkableType -> LinkableType -> Bool # (>=) :: LinkableType -> LinkableType -> Bool # max :: LinkableType -> LinkableType -> LinkableType # min :: LinkableType -> LinkableType -> LinkableType # | |||||
| Hashable LinkableType Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
| type Rep LinkableType Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
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.
data GetParsedModuleWithComments Source #
Constructors
| GetParsedModuleWithComments |
Instances
| Generic GetParsedModuleWithComments Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
Methods from :: GetParsedModuleWithComments -> Rep GetParsedModuleWithComments x # to :: Rep GetParsedModuleWithComments x -> GetParsedModuleWithComments # | |||||
| Show GetParsedModuleWithComments Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetParsedModuleWithComments -> ShowS # show :: GetParsedModuleWithComments -> String # showList :: [GetParsedModuleWithComments] -> ShowS # | |||||
| NFData GetParsedModuleWithComments Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetParsedModuleWithComments -> () # | |||||
| Eq GetParsedModuleWithComments Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetParsedModuleWithComments -> GetParsedModuleWithComments -> Bool # (/=) :: GetParsedModuleWithComments -> GetParsedModuleWithComments -> Bool # | |||||
| Hashable GetParsedModuleWithComments Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods hashWithSalt :: Int -> GetParsedModuleWithComments -> Int # hash :: GetParsedModuleWithComments -> Int # | |||||
| type Rep GetParsedModuleWithComments Source # | |||||
| type RuleResult GetParsedModuleWithComments Source # | The parse tree for the file using GetFileContents, all comments included using Opt_KeepRawTokenStream | ||||
Defined in Development.IDE.Core.RuleTypes | |||||
data GetModuleGraph Source #
Constructors
| GetModuleGraph |
Instances
| Generic GetModuleGraph Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
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 GetModuleGraphTransDepsFingerprints Source #
Constructors
| GetModuleGraphTransDepsFingerprints |
Instances
| Generic GetModuleGraphTransDepsFingerprints Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
| |||||
| Show GetModuleGraphTransDepsFingerprints Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetModuleGraphTransDepsFingerprints -> ShowS # show :: GetModuleGraphTransDepsFingerprints -> String # showList :: [GetModuleGraphTransDepsFingerprints] -> ShowS # | |||||
| NFData GetModuleGraphTransDepsFingerprints Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetModuleGraphTransDepsFingerprints -> () # | |||||
| Eq GetModuleGraphTransDepsFingerprints Source # | |||||
| Hashable GetModuleGraphTransDepsFingerprints Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods hashWithSalt :: Int -> GetModuleGraphTransDepsFingerprints -> Int # | |||||
| type Rep GetModuleGraphTransDepsFingerprints Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
| type RuleResult GetModuleGraphTransDepsFingerprints Source # | it only compute the fingerprint of the module graph for a file and its dependencies we need this to trigger recompilation when the sub module graph for a file changes | ||||
data GetModuleGraphTransReverseDepsFingerprints Source #
Constructors
| GetModuleGraphTransReverseDepsFingerprints |
Instances
| Generic GetModuleGraphTransReverseDepsFingerprints Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
| |||||
| Show GetModuleGraphTransReverseDepsFingerprints Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
| NFData GetModuleGraphTransReverseDepsFingerprints Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods | |||||
| Eq GetModuleGraphTransReverseDepsFingerprints Source # | |||||
| Hashable GetModuleGraphTransReverseDepsFingerprints Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods hashWithSalt :: Int -> GetModuleGraphTransReverseDepsFingerprints -> Int # | |||||
| type Rep GetModuleGraphTransReverseDepsFingerprints Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
| type RuleResult GetModuleGraphTransReverseDepsFingerprints Source # | |||||
data GetModuleGraphImmediateReverseDepsFingerprints Source #
Constructors
| GetModuleGraphImmediateReverseDepsFingerprints |
Instances
| Generic GetModuleGraphImmediateReverseDepsFingerprints Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
| |||||
| Show GetModuleGraphImmediateReverseDepsFingerprints Source # | |||||
| NFData GetModuleGraphImmediateReverseDepsFingerprints Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetModuleGraphImmediateReverseDepsFingerprints -> () # | |||||
| Eq GetModuleGraphImmediateReverseDepsFingerprints Source # | |||||
| Hashable GetModuleGraphImmediateReverseDepsFingerprints Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
| type Rep GetModuleGraphImmediateReverseDepsFingerprints Source # | |||||
Defined in Development.IDE.Core.RuleTypes type Rep GetModuleGraphImmediateReverseDepsFingerprints = D1 ('MetaData "GetModuleGraphImmediateReverseDepsFingerprints" "Development.IDE.Core.RuleTypes" "ghcide-2.13.0.0-3xOdL4E2K8pFtuI1JRT6Li" 'False) (C1 ('MetaCons "GetModuleGraphImmediateReverseDepsFingerprints" 'PrefixI 'False) (U1 :: Type -> Type)) | |||||
| type RuleResult GetModuleGraphImmediateReverseDepsFingerprints Source # | |||||
data GetLinkable Source #
Constructors
| GetLinkable |
Instances
| Generic GetLinkable Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
| |||||
| 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
| |||||
| 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 -> () # | |
mkHiFileResult :: ModSummary -> ModIface -> ModDetails -> ModuleEnv ByteString -> Maybe (CoreFile, ByteString) -> HiFileResult Source #
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
| |||||
| 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 # | |
Defined in Development.IDE.Core.RuleTypes | |
| 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 ReportImportCycles Source #
Constructors
| ReportImportCycles |
Instances
| Generic ReportImportCycles Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
Methods from :: ReportImportCycles -> Rep ReportImportCycles x # to :: Rep ReportImportCycles x -> ReportImportCycles # | |||||
| Show ReportImportCycles Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> ReportImportCycles -> ShowS # show :: ReportImportCycles -> String # showList :: [ReportImportCycles] -> ShowS # | |||||
| NFData ReportImportCycles Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: ReportImportCycles -> () # | |||||
| Eq ReportImportCycles Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods (==) :: ReportImportCycles -> ReportImportCycles -> Bool # (/=) :: ReportImportCycles -> ReportImportCycles -> Bool # | |||||
| Hashable ReportImportCycles Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
| type Rep ReportImportCycles Source # | |||||
| type RuleResult ReportImportCycles Source # | This rule is used to report import cycles. It depends on GetModuleGraph. We cannot report the cycles directly from GetModuleGraph since we can only report diagnostics for the current file. | ||||
Defined in Development.IDE.Core.RuleTypes | |||||
data GetModIfaceFromDisk Source #
Constructors
| GetModIfaceFromDisk |
Instances
| Generic GetModIfaceFromDisk Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
Methods from :: GetModIfaceFromDisk -> Rep GetModIfaceFromDisk x # to :: Rep GetModIfaceFromDisk x -> GetModIfaceFromDisk # | |||||
| Show GetModIfaceFromDisk Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetModIfaceFromDisk -> ShowS # show :: GetModIfaceFromDisk -> String # showList :: [GetModIfaceFromDisk] -> ShowS # | |||||
| NFData GetModIfaceFromDisk Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetModIfaceFromDisk -> () # | |||||
| Eq GetModIfaceFromDisk Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetModIfaceFromDisk -> GetModIfaceFromDisk -> Bool # (/=) :: GetModIfaceFromDisk -> GetModIfaceFromDisk -> Bool # | |||||
| Hashable GetModIfaceFromDisk Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
| type Rep GetModIfaceFromDisk Source # | |||||
| type RuleResult GetModIfaceFromDisk Source # | Read the module interface file from disk. Throws an error for VFS files.
This is an internal rule, use | ||||
Defined in Development.IDE.Core.RuleTypes | |||||
data GetModIfaceFromDiskAndIndex Source #
Constructors
| GetModIfaceFromDiskAndIndex |
Instances
| Generic GetModIfaceFromDiskAndIndex Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
Methods from :: GetModIfaceFromDiskAndIndex -> Rep GetModIfaceFromDiskAndIndex x # to :: Rep GetModIfaceFromDiskAndIndex x -> GetModIfaceFromDiskAndIndex # | |||||
| Show GetModIfaceFromDiskAndIndex Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetModIfaceFromDiskAndIndex -> ShowS # show :: GetModIfaceFromDiskAndIndex -> String # showList :: [GetModIfaceFromDiskAndIndex] -> ShowS # | |||||
| NFData GetModIfaceFromDiskAndIndex Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetModIfaceFromDiskAndIndex -> () # | |||||
| Eq GetModIfaceFromDiskAndIndex Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetModIfaceFromDiskAndIndex -> GetModIfaceFromDiskAndIndex -> Bool # (/=) :: GetModIfaceFromDiskAndIndex -> GetModIfaceFromDiskAndIndex -> Bool # | |||||
| Hashable GetModIfaceFromDiskAndIndex Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods hashWithSalt :: Int -> GetModIfaceFromDiskAndIndex -> Int # hash :: GetModIfaceFromDiskAndIndex -> Int # | |||||
| type Rep GetModIfaceFromDiskAndIndex Source # | |||||
| type RuleResult GetModIfaceFromDiskAndIndex Source # | GetModIfaceFromDisk and index the `.hie` file into the database.
This is an internal rule, use | ||||
Defined in Development.IDE.Core.RuleTypes | |||||
data GetModIface Source #
Constructors
| GetModIface |
Instances
| Generic GetModIface Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
| |||||
| 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
| Generic GetFileContents Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
Methods from :: GetFileContents -> Rep GetFileContents x # to :: Rep GetFileContents x -> GetFileContents # | |||||
| Show GetFileContents Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetFileContents -> ShowS # show :: GetFileContents -> String # showList :: [GetFileContents] -> ShowS # | |||||
| NFData GetFileContents Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetFileContents -> () # | |||||
| Eq GetFileContents Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetFileContents -> GetFileContents -> Bool # (/=) :: GetFileContents -> GetFileContents -> Bool # | |||||
| Hashable GetFileContents Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
| type Rep GetFileContents Source # | |||||
| type RuleResult GetFileContents Source # | Get the contents of a file, either dirty (if the buffer is modified) or Nothing to mean use from disk. | ||||
Defined in Development.IDE.Core.RuleTypes | |||||
data GetFileHash Source #
Constructors
| GetFileHash |
Instances
| Generic GetFileHash Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
| |||||
| Show GetFileHash Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetFileHash -> ShowS # show :: GetFileHash -> String # showList :: [GetFileHash] -> ShowS # | |||||
| NFData GetFileHash Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetFileHash -> () # | |||||
| Eq GetFileHash Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
| Hashable GetFileHash Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
| type Rep GetFileHash Source # | |||||
| type RuleResult GetFileHash Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
data AddWatchedFile Source #
Constructors
| AddWatchedFile |
Instances
| Generic AddWatchedFile Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
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 GetPhysicalModificationTime Source #
Constructors
| GetPhysicalModificationTime |
Instances
| Generic GetPhysicalModificationTime Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
Methods from :: GetPhysicalModificationTime -> Rep GetPhysicalModificationTime x # to :: Rep GetPhysicalModificationTime x -> GetPhysicalModificationTime # | |||||
| Show GetPhysicalModificationTime Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetPhysicalModificationTime -> ShowS # show :: GetPhysicalModificationTime -> String # showList :: [GetPhysicalModificationTime] -> ShowS # | |||||
| NFData GetPhysicalModificationTime Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetPhysicalModificationTime -> () # | |||||
| Eq GetPhysicalModificationTime Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetPhysicalModificationTime -> GetPhysicalModificationTime -> Bool # (/=) :: GetPhysicalModificationTime -> GetPhysicalModificationTime -> Bool # | |||||
| Hashable GetPhysicalModificationTime Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods hashWithSalt :: Int -> GetPhysicalModificationTime -> Int # hash :: GetPhysicalModificationTime -> Int # | |||||
| type Rep GetPhysicalModificationTime Source # | |||||
| type RuleResult GetPhysicalModificationTime Source # | Get the modification time of a file on disk, ignoring any version in the VFS. | ||||
Defined in Development.IDE.Core.RuleTypes | |||||
vfsVersion :: FileVersion -> Maybe Int32 Source #
data IsFileOfInterestResult Source #
Constructors
| NotFOI | |
| IsFOI FileOfInterestStatus |
Instances
| Generic IsFileOfInterestResult Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
Methods from :: IsFileOfInterestResult -> Rep IsFileOfInterestResult x # to :: Rep IsFileOfInterestResult x -> IsFileOfInterestResult # | |||||
| Show IsFileOfInterestResult Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> IsFileOfInterestResult -> ShowS # show :: IsFileOfInterestResult -> String # showList :: [IsFileOfInterestResult] -> ShowS # | |||||
| NFData IsFileOfInterestResult Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: IsFileOfInterestResult -> () # | |||||
| Eq IsFileOfInterestResult Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods (==) :: IsFileOfInterestResult -> IsFileOfInterestResult -> Bool # (/=) :: IsFileOfInterestResult -> IsFileOfInterestResult -> Bool # | |||||
| Hashable IsFileOfInterestResult Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods hashWithSalt :: Int -> IsFileOfInterestResult -> Int # hash :: IsFileOfInterestResult -> Int # | |||||
| type Rep IsFileOfInterestResult Source # | |||||
Defined in Development.IDE.Core.RuleTypes type Rep IsFileOfInterestResult = D1 ('MetaData "IsFileOfInterestResult" "Development.IDE.Core.RuleTypes" "ghcide-2.13.0.0-3xOdL4E2K8pFtuI1JRT6Li" '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 IsFileOfInterest Source #
Constructors
| IsFileOfInterest |
Instances
| Generic IsFileOfInterest Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
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
| |||||
| 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
| Generic GetModSummaryWithoutTimestamps Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
| |||||
| Show GetModSummaryWithoutTimestamps Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetModSummaryWithoutTimestamps -> ShowS # show :: GetModSummaryWithoutTimestamps -> String # showList :: [GetModSummaryWithoutTimestamps] -> ShowS # | |||||
| NFData GetModSummaryWithoutTimestamps Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetModSummaryWithoutTimestamps -> () # | |||||
| Eq GetModSummaryWithoutTimestamps Source # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
| Hashable GetModSummaryWithoutTimestamps Source # | |||||
Defined in Development.IDE.Core.RuleTypes Methods hashWithSalt :: Int -> GetModSummaryWithoutTimestamps -> Int # | |||||
| type Rep GetModSummaryWithoutTimestamps Source # | |||||
| type RuleResult GetModSummaryWithoutTimestamps Source # | Generate a ModSummary with the timestamps and preprocessed content elided, for more successful early cutoff | ||||
data NeedsCompilation Source #
Constructors
| NeedsCompilation |
Instances
| Generic NeedsCompilation Source # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
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 | |||||
awSplicesL :: Lens' Splices [(LHsExpr GhcTc, Serialized)] Source #