Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Development.IDE
Synopsis
- data Doc ann
- data Location = Location {}
- data Position = Position {
- _line :: UInt
- _character :: UInt
- data Plugin c = Plugin {
- pluginRules :: Rules ()
- pluginHandlers :: Handlers (ServerM c)
- pluginModifyDynflags :: c -> DynFlagsModifications
- data Diagnostic = Diagnostic {}
- data ParseResult a :: TYPE ('SumRep '['TupleRep '[LiftedRep, LiftedRep], LiftedRep]) where
- pattern PFailed :: PState -> ParseResult a
- pattern POk :: PState -> a -> ParseResult a
- data Action a
- data Rules a
- type family RuleResult key
- data LoggingColumn
- newtype Recorder msg = Recorder {}
- data WithPriority a = WithPriority {
- priority :: Priority
- callStack_ :: CallStack
- payload :: a
- data Priority
- newtype LayoutOptions = LayoutOptions {}
- data PageWidth
- data SimpleDocStream ann
- = SFail
- | SEmpty
- | SChar !Char (SimpleDocStream ann)
- | SText !Int !Text (SimpleDocStream ann)
- | SLine !Int (SimpleDocStream ann)
- | SAnnPush ann (SimpleDocStream ann)
- | SAnnPop (SimpleDocStream ann)
- data FusionDepth
- class Pretty a where
- pretty :: a -> Doc ann
- prettyList :: [a] -> Doc ann
- data Range = Range {}
- type DiagnosticStore = HashMap NormalizedUri StoreItem
- data NormalizedUri
- data IdeConfiguration = IdeConfiguration {}
- data FastResult a = FastResult {}
- newtype IdeAction a = IdeAction {}
- type IdeRule k v = (RuleResult k ~ v, ShakeValue k, Show v, Typeable v, NFData v)
- data IdeState
- data RuleBody k v
- = Rule (k -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult v))
- | RuleNoDiagnostics (k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v))
- | RuleWithCustomNewnessCheck {
- newnessCheck :: ByteString -> ByteString -> Bool
- build :: k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v)
- | RuleWithOldValue (k -> NormalizedFilePath -> Value v -> Action (Maybe ByteString, IdeResult v))
- data ShakeExtras
- data VFSModified
- data GhcVersion
- data HscEnvEq
- data TcModuleResult = TcModuleResult {}
- data FileOfInterestStatus
- data NormalizedFilePath
- data GetParsedModule = GetParsedModule
- data GhcSessionIO = GhcSessionIO
- data GetClientSettings = GetClientSettings
- newtype GhcSessionDeps where
- GhcSessionDeps_ { }
- pattern GhcSessionDeps :: GhcSessionDeps
- type IdeResult v = ([FileDiagnostic], Maybe v)
- newtype GetModificationTime = GetModificationTime_ {}
- data FileVersion
- type FileDiagnostic = (NormalizedFilePath, ShowDiagnostic, Diagnostic)
- newtype Uri = Uri {}
- data GenerateCore = GenerateCore
- data GetHieAst = GetHieAst
- data TypeCheck = TypeCheck
- data IdeGhcSession = IdeGhcSession {
- loadSessionFun :: FilePath -> IO (IdeResult HscEnvEq, [FilePath])
- sessionVersion :: !Int
- data GhcSession = GhcSession
- data ShowDiagnostic
- data DiagnosticSeverity
- type IdeResultNoDiagnosticsEarlyCutoff v = (Maybe ByteString, Maybe v)
- data GetFileExists = GetFileExists
- newtype ImportMap = ImportMap {}
- data GetLocatedImports = GetLocatedImports
- data GetKnownTargets = GetKnownTargets
- data LinkableType
- data GetParsedModuleWithComments = GetParsedModuleWithComments
- data GetModuleGraph = GetModuleGraph
- 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 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 GetModificationTime :: GetModificationTime
- (<>) :: Semigroup a => a -> a -> a
- list :: [Doc ann] -> Doc ann
- comma :: Doc ann
- colon :: Doc ann
- (<+>) :: Doc ann -> Doc ann -> Doc ann
- brackets :: Doc ann -> Doc ann
- indent :: Int -> Doc ann -> Doc ann
- runParser :: DynFlags -> String -> P a -> ParseResult a
- space :: Doc ann
- group :: Doc ann -> Doc ann
- fill :: Int -> Doc ann -> Doc ann
- parens :: Doc ann -> Doc ann
- cfilter :: (a -> Bool) -> Recorder a -> Recorder a
- cmap :: (a -> b) -> Recorder b -> Recorder a
- pipe :: Doc ann
- fuse :: FusionDepth -> Doc ann -> Doc ann
- line :: Doc ann
- column :: (Int -> Doc ann) -> Doc ann
- equals :: Doc ann
- nest :: Int -> Doc ann -> Doc ann
- tupled :: [Doc ann] -> Doc ann
- semi :: Doc ann
- lparen :: Doc ann
- rparen :: Doc ann
- lbrace :: Doc ann
- rbrace :: Doc ann
- squotes :: Doc ann -> Doc ann
- braces :: Doc ann -> Doc ann
- hcat :: [Doc ann] -> Doc ann
- hsep :: [Doc ann] -> Doc ann
- vcat :: [Doc ann] -> Doc ann
- hang :: Int -> Doc ann -> Doc ann
- punctuate :: Doc ann -> [Doc ann] -> [Doc ann]
- sep :: [Doc ann] -> Doc ann
- cat :: [Doc ann] -> Doc ann
- dot :: Doc ann
- plural :: (Num amount, Eq amount) => doc -> doc -> amount -> doc
- printName :: Name -> String
- use :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe v)
- ghcVersion :: GhcVersion
- action :: Action a -> Rules ()
- renderStrict :: SimpleDocStream ann -> Text
- logWith :: (HasCallStack, MonadIO m) => Recorder (WithPriority msg) -> Priority -> msg -> m ()
- cmapWithPrio :: (a -> b) -> Recorder (WithPriority b) -> Recorder (WithPriority a)
- cmapIO :: (a -> IO b) -> Recorder b -> Recorder a
- makeDefaultStderrRecorder :: MonadIO m => Maybe [LoggingColumn] -> m (Recorder (WithPriority (Doc a)))
- withFileRecorder :: MonadUnliftIO m => FilePath -> Maybe [LoggingColumn] -> (Either IOException (Recorder (WithPriority (Doc d))) -> m a) -> m a
- makeDefaultHandleRecorder :: MonadIO m => Maybe [LoggingColumn] -> Lock -> Handle -> m (Recorder (WithPriority (Doc a)))
- defaultLoggingColumns :: [LoggingColumn]
- withBacklog :: (v -> Recorder a) -> IO (Recorder a, v -> IO ())
- lspClientMessageRecorder :: LanguageContextEnv config -> Recorder (WithPriority Text)
- lspClientLogRecorder :: LanguageContextEnv config -> Recorder (WithPriority Text)
- toCologActionWithPrio :: forall (m :: Type -> Type) msg. (MonadIO m, HasCallStack) => Recorder (WithPriority msg) -> LogAction m (WithSeverity msg)
- getClientConfig :: MonadLsp Config m => m Config
- viaShow :: Show a => a -> Doc ann
- unsafeViaShow :: Show a => a -> Doc ann
- emptyDoc :: Doc ann
- line' :: Doc ann
- softline :: Doc ann
- softline' :: Doc ann
- hardline :: Doc ann
- flatAlt :: Doc ann -> Doc ann -> Doc ann
- align :: Doc ann -> Doc ann
- encloseSep :: Doc ann -> Doc ann -> Doc ann -> [Doc ann] -> Doc ann
- concatWith :: Foldable t => (Doc ann -> Doc ann -> Doc ann) -> t (Doc ann) -> Doc ann
- vsep :: [Doc ann] -> Doc ann
- fillSep :: [Doc ann] -> Doc ann
- fillCat :: [Doc ann] -> Doc ann
- nesting :: (Int -> Doc ann) -> Doc ann
- width :: Doc ann -> (Int -> Doc ann) -> Doc ann
- pageWidth :: (PageWidth -> Doc ann) -> Doc ann
- fillBreak :: Int -> Doc ann -> Doc ann
- enclose :: Doc ann -> Doc ann -> Doc ann -> Doc ann
- surround :: Doc ann -> Doc ann -> Doc ann -> Doc ann
- annotate :: ann -> Doc ann -> Doc ann
- unAnnotate :: Doc ann -> Doc xxx
- reAnnotate :: (ann -> ann') -> Doc ann -> Doc ann'
- alterAnnotations :: (ann -> [ann']) -> Doc ann -> Doc ann'
- unAnnotateS :: SimpleDocStream ann -> SimpleDocStream xxx
- reAnnotateS :: (ann -> ann') -> SimpleDocStream ann -> SimpleDocStream ann'
- alterAnnotationsS :: (ann -> Maybe ann') -> SimpleDocStream ann -> SimpleDocStream ann'
- removeTrailingWhitespace :: SimpleDocStream ann -> SimpleDocStream ann
- defaultLayoutOptions :: LayoutOptions
- layoutPretty :: LayoutOptions -> Doc ann -> SimpleDocStream ann
- layoutSmart :: LayoutOptions -> Doc ann -> SimpleDocStream ann
- layoutCompact :: Doc ann1 -> SimpleDocStream ann2
- dquotes :: Doc ann -> Doc ann
- angles :: Doc ann -> Doc ann
- squote :: Doc ann
- dquote :: Doc ann
- langle :: Doc ann
- rangle :: Doc ann
- lbracket :: Doc ann
- rbracket :: Doc ann
- slash :: Doc ann
- backslash :: Doc ann
- readFileUtf8 :: FilePath -> IO Text
- uses :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f (Maybe v))
- getAtPoint :: NormalizedFilePath -> Position -> IdeAction (Maybe (Maybe Range, [Text]))
- getDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location])
- getTypeDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location])
- getFileExists :: NormalizedFilePath -> Action Bool
- getFileContents :: NormalizedFilePath -> Action (UTCTime, Maybe Text)
- isWorkspaceFile :: NormalizedFilePath -> Action Bool
- getFilesOfInterestUntracked :: Action (HashMap NormalizedFilePath FileOfInterestStatus)
- getClientConfigAction :: Action Config
- getParsedModule :: NormalizedFilePath -> Action (Maybe ParsedModule)
- usePropertyAction :: HasProperty s k t r => KeyNameProxy s -> PluginId -> Properties r -> Action (ToHsType t)
- runAction :: String -> IdeState -> Action a -> IO a
- actionLogger :: Action (Recorder (WithPriority Log))
- define :: IdeRule k v => Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (IdeResult v)) -> Rules ()
- defineEarlyCutoff :: IdeRule k v => Recorder (WithPriority Log) -> RuleBody k v -> Rules ()
- defineNoDiagnostics :: IdeRule k v => Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (Maybe v)) -> Rules ()
- getPluginConfigAction :: PluginId -> Action PluginConfig
- ideLogger :: IdeState -> Recorder (WithPriority Log)
- runIdeAction :: String -> ShakeExtras -> IdeAction a -> IO a
- useNoFile :: IdeRule k v => k -> Action (Maybe v)
- useNoFile_ :: IdeRule k v => k -> Action v
- useWithStale :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping))
- useWithStaleFast :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (Maybe (v, PositionMapping))
- useWithStaleFast' :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (FastResult v)
- useWithStale_ :: IdeRule k v => k -> NormalizedFilePath -> Action (v, PositionMapping)
- use_ :: IdeRule k v => k -> NormalizedFilePath -> Action v
- uses_ :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f v)
- hscEnvWithImportPaths :: HscEnvEq -> HscEnv
- modifyDynFlags :: GhcMonad m => (DynFlags -> DynFlags) -> m ()
- showDiagnostics :: [FileDiagnostic] -> Text
- fromNormalizedFilePath :: NormalizedFilePath -> FilePath
- rangeToRealSrcSpan :: NormalizedFilePath -> Range -> RealSrcSpan
- realSrcSpanToRange :: RealSrcSpan -> Range
- disableWarningsAsErrors :: DynFlags -> DynFlags
- setHieDir :: FilePath -> DynFlags -> DynFlags
- dontWriteHieFiles :: DynFlags -> DynFlags
- diagFromErrMsgs :: Text -> DynFlags -> Bag (MsgEnvelope DecoratedSDoc) -> [FileDiagnostic]
- diagFromErrMsg :: Text -> DynFlags -> MsgEnvelope DecoratedSDoc -> [FileDiagnostic]
- diagFromString :: Text -> DiagnosticSeverity -> SrcSpan -> String -> [FileDiagnostic]
- diagFromStrings :: Text -> DiagnosticSeverity -> [(SrcSpan, String)] -> [FileDiagnostic]
- diagFromGhcException :: Text -> DynFlags -> GhcException -> [FileDiagnostic]
- catchSrcErrors :: DynFlags -> Text -> IO a -> IO (Either [FileDiagnostic] a)
- srcSpanToLocation :: SrcSpan -> Maybe Location
- srcSpanToRange :: SrcSpan -> Maybe Range
- realSrcLocToPosition :: RealSrcLoc -> Position
- realSrcSpanToLocation :: RealSrcSpan -> Location
- realSrcSpanToCodePointRange :: RealSrcSpan -> CodePointRange
- realSrcLocToCodePointPosition :: RealSrcLoc -> CodePointPosition
- srcSpanToFilename :: SrcSpan -> Maybe FilePath
- rangeToSrcSpan :: NormalizedFilePath -> Range -> SrcSpan
- positionToRealSrcLoc :: NormalizedFilePath -> Position -> RealSrcLoc
- zeroSpan :: FastString -> RealSrcSpan
- realSpan :: SrcSpan -> Maybe RealSrcSpan
- isInsideSrcSpan :: Position -> SrcSpan -> Bool
- spanContainsRange :: SrcSpan -> Range -> Maybe Bool
- noSpan :: String -> SrcSpan
- toDSeverity :: Severity -> Maybe DiagnosticSeverity
- evalGhcEnv :: HscEnv -> Ghc b -> IO b
- printRdrName :: RdrName -> String
- lookupPackageConfig :: Unit -> HscEnv -> Maybe UnitInfo
- textToStringBuffer :: Text -> StringBuffer
- bytestringToStringBuffer :: ByteString -> StringBuffer
- stringBufferToByteString :: StringBuffer -> ByteString
- moduleImportPath :: NormalizedFilePath -> ModuleName -> Maybe FilePath
- cgGutsToCoreModule :: SafeHaskellMode -> CgGuts -> ModDetails -> CoreModule
- fingerprintToBS :: Fingerprint -> ByteString
- fingerprintFromByteString :: ByteString -> IO Fingerprint
- fingerprintFromStringBuffer :: StringBuffer -> IO Fingerprint
- fingerprintFromPut :: Put -> IO Fingerprint
- hDuplicateTo' :: Handle -> Handle -> IO ()
- printOutputable :: Outputable a => a -> Text
- getExtensions :: ParsedModule -> [Extension]
- toNormalizedFilePath' :: FilePath -> NormalizedFilePath
- fromUri :: NormalizedUri -> NormalizedFilePath
- ideErrorText :: NormalizedFilePath -> Text -> FileDiagnostic
- ideErrorWithSource :: Maybe Text -> Maybe DiagnosticSeverity -> a -> Text -> (a, ShowDiagnostic, Diagnostic)
- showDiagnosticsColored :: [FileDiagnostic] -> Text
- noFilePath :: FilePath
- noRange :: Range
- showPosition :: Position -> String
- toNormalizedUri :: Uri -> NormalizedUri
- fromNormalizedUri :: NormalizedUri -> Uri
- emptyFilePath :: NormalizedFilePath
- emptyPathUri :: NormalizedUri
- filePathToUri' :: NormalizedFilePath -> NormalizedUri
- uriToFilePath' :: Uri -> Maybe FilePath
- readSrcSpan :: ReadS RealSrcSpan
- 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
The abstract data type
represents pretty documents that have
been annotated with data of type Doc
annann
.
More specifically, a value of type
represents a non-empty set of
possible layouts of a document. The layout functions select one of these
possibilities, taking into account things like the width of the output
document.Doc
The annotation is an arbitrary piece of data associated with (part of) a document. Annotations may be used by the rendering backends in order to display output differently, such as
- color information (e.g. when rendering to the terminal)
- mouseover text (e.g. when rendering to rich HTML)
- whether to show something or not (to allow simple or detailed versions)
The simplest way to display a Doc
is via the Show
class.
>>>
putStrLn (show (vsep ["hello", "world"]))
hello world
Instances
Instances
Constructors
Position | |
Fields
|
Instances
Constructors
Plugin | |
Fields
|
data Diagnostic #
Constructors
Diagnostic | |
Instances
data ParseResult a :: TYPE ('SumRep '['TupleRep '[LiftedRep, LiftedRep], LiftedRep]) where #
The result of running a parser.
Bundled Patterns
pattern PFailed :: PState -> ParseResult a | The parser has consumed a (possibly empty) prefix of the input and failed. The carried parsing state can be used to resume parsing. It is the state
right before failure, including the fatal parse error. |
pattern POk :: PState -> a -> ParseResult a | The parser has consumed a (possibly empty) prefix of the input and produced
a result. Use The carried parsing state can be used to resume parsing. |
An action representing something that can be run as part of a Rule
.
Action
s can be pure functions but also have access to IO
via MonadIO
and 'MonadUnliftIO.
It should be assumed that actions throw exceptions, these can be caught with
actionCatch
. In particular, it is
permissible to use the MonadFail
instance, which will lead to an IOException
.
Instances
MonadFail Action | |
Defined in Development.IDE.Graph.Internal.Types | |
MonadIO Action | |
Defined in Development.IDE.Graph.Internal.Types | |
Applicative Action | |
Functor Action | |
Monad Action | |
MonadCatch Action | |
Defined in Development.IDE.Graph.Internal.Types | |
MonadMask Action | |
Defined in Development.IDE.Graph.Internal.Types Methods mask :: HasCallStack => ((forall a. Action a -> Action a) -> Action b) -> Action b # uninterruptibleMask :: HasCallStack => ((forall a. Action a -> Action a) -> Action b) -> Action b # generalBracket :: HasCallStack => Action a -> (a -> ExitCase b -> Action c) -> (a -> Action b) -> Action (b, c) # | |
MonadThrow Action | |
Defined in Development.IDE.Graph.Internal.Types Methods throwM :: (HasCallStack, Exception e) => e -> Action a # | |
MonadUnliftIO Action | |
Defined in Development.IDE.Graph.Internal.Types |
A computation that defines all the rules that form part of the computation graph.
Rules
has access to IO
through MonadIO
. Use of IO
is at your own risk: if
you write Rules
that throw exceptions, then you need to make sure to handle them
yourself when you run the resulting Rules
.
type family RuleResult key #
The type mapping between the key
or a rule and the resulting value
.
Instances
type RuleResult AddWatchedFile Source # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GenerateCore Source # | Convert to Core, requires TypeCheck* |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetBindings Source # | A IntervalMap telling us what is in scope at each point |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetClientSettings Source # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetDocMap Source # | |
Defined in Development.IDE.Core.RuleTypes | |
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 | |
type RuleResult GetFileExists Source # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetHieAst Source # | The uncompressed HieAST |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetImportMap Source # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetKnownTargets Source # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetLinkable Source # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetLocatedImports Source # | Resolve the imports in a module to the file path of a module in the same package |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetModIface Source # | Get a module interface details, either from an interface file or a typechecked module |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetModIfaceFromDisk Source # | Read the module interface file from disk. Throws an error for VFS files.
This is an internal rule, use |
Defined in Development.IDE.Core.RuleTypes | |
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 | |
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 | |
type RuleResult GetModSummaryWithoutTimestamps Source # | Generate a ModSummary with the timestamps and preprocessed content elided, for more successful early cutoff |
type RuleResult GetModificationTime Source # | Get the modification time of a file. |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetModuleGraph Source # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetParsedModule Source # | The parse tree for the file using GetFileContents |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GetParsedModuleWithComments Source # | The parse tree for the file using GetFileContents, all comments included using Opt_KeepRawTokenStream |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult GhcSession Source # | A GHC session that we reuse. |
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 | |
type RuleResult GhcSessionIO Source # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult IsFileOfInterest Source # | |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult NeedsCompilation Source # | Does this module need to be compiled? |
Defined in Development.IDE.Core.RuleTypes | |
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 | |
type RuleResult TypeCheck Source # | The type checked version of this file, requires TypeCheck+ |
Defined in Development.IDE.Core.RuleTypes | |
type RuleResult LocalCompletions Source # | Produce completions info for a file |
Defined in Development.IDE.Plugin.Completions.Types | |
type RuleResult NonLocalCompletions Source # | |
type RuleResult GetGlobalBindingTypeSigs Source # | |
type RuleResult (Q k) Source # | |
Defined in Development.IDE.Types.Shake |
data LoggingColumn #
Constructors
TimeColumn | |
ThreadIdColumn | |
PriorityColumn | |
DataColumn | |
SourceLocColumn |
Note that this is logging actions _of the program_, not of the user. You shouldn't call warning/error if the user has caused an error, only if our code has gone wrong and is itself erroneous (e.g. we threw an exception).
data WithPriority a #
Constructors
WithPriority | |
Fields
|
Instances
Functor WithPriority | |
Defined in Ide.Logger Methods fmap :: (a -> b) -> WithPriority a -> WithPriority b # (<$) :: a -> WithPriority b -> WithPriority a # |
Constructors
Debug | Verbose debug logging. |
Info | Useful information in case an error has to be understood. |
Warning | These error messages should not occur in a expected usage, and should be investigated. |
Error | Such log messages must never occur in expected usage. |
Instances
Bounded Priority | |
Enum Priority | |
Read Priority | |
Show Priority | |
Eq Priority | |
Ord Priority | |
Defined in Ide.Logger |
newtype LayoutOptions #
Options to influence the layout algorithms.
Constructors
LayoutOptions | |
Fields |
Instances
Show LayoutOptions | |
Defined in Prettyprinter.Internal Methods showsPrec :: Int -> LayoutOptions -> ShowS # show :: LayoutOptions -> String # showList :: [LayoutOptions] -> ShowS # | |
Eq LayoutOptions | |
Defined in Prettyprinter.Internal Methods (==) :: LayoutOptions -> LayoutOptions -> Bool # (/=) :: LayoutOptions -> LayoutOptions -> Bool # | |
Ord LayoutOptions | |
Defined in Prettyprinter.Internal Methods compare :: LayoutOptions -> LayoutOptions -> Ordering # (<) :: LayoutOptions -> LayoutOptions -> Bool # (<=) :: LayoutOptions -> LayoutOptions -> Bool # (>) :: LayoutOptions -> LayoutOptions -> Bool # (>=) :: LayoutOptions -> LayoutOptions -> Bool # max :: LayoutOptions -> LayoutOptions -> LayoutOptions # min :: LayoutOptions -> LayoutOptions -> LayoutOptions # |
Maximum number of characters that fit in one line. The layout algorithms
will try not to exceed the set limit by inserting line breaks when applicable
(e.g. via softline'
).
Constructors
AvailablePerLine !Int !Double | Layouters should not exceed the specified space per line.
|
Unbounded | Layouters should not introduce line breaks on their own. |
Instances
Show PageWidth | |
Eq PageWidth | |
Ord PageWidth | |
data SimpleDocStream ann #
The data type SimpleDocStream
represents laid out documents and is used
by the display functions.
A simplified view is that
, and the layout
functions pick one of the Doc
= [SimpleDocStream
]SimpleDocStream
s based on which one fits the
layout constraints best. This means that SimpleDocStream
has all complexity
contained in Doc
resolved, making it very easy to convert it to other
formats, such as plain text or terminal output.
To write your own
to X converter, it is therefore sufficient to
convert from Doc
. The »Render« submodules provide some
built-in converters to do so, and helpers to create own ones.SimpleDocStream
Constructors
SFail | |
SEmpty | |
SChar !Char (SimpleDocStream ann) | |
SText !Int !Text (SimpleDocStream ann) | |
SLine !Int (SimpleDocStream ann) |
|
SAnnPush ann (SimpleDocStream ann) | Add an annotation to the remaining document. |
SAnnPop (SimpleDocStream ann) | Remove a previously pushed annotation. |
Instances
data FusionDepth #
Fusion depth parameter, used by fuse
.
Constructors
Shallow | Do not dive deep into nested documents, fusing mostly concatenations of text nodes together. |
Deep | Recurse into all parts of the This value should only be used if profiling shows it is significantly
faster than using |
Instances
Show FusionDepth | |
Defined in Prettyprinter.Internal Methods showsPrec :: Int -> FusionDepth -> ShowS # show :: FusionDepth -> String # showList :: [FusionDepth] -> ShowS # | |
Eq FusionDepth | |
Defined in Prettyprinter.Internal | |
Ord FusionDepth | |
Defined in Prettyprinter.Internal Methods compare :: FusionDepth -> FusionDepth -> Ordering # (<) :: FusionDepth -> FusionDepth -> Bool # (<=) :: FusionDepth -> FusionDepth -> Bool # (>) :: FusionDepth -> FusionDepth -> Bool # (>=) :: FusionDepth -> FusionDepth -> Bool # max :: FusionDepth -> FusionDepth -> FusionDepth # min :: FusionDepth -> FusionDepth -> FusionDepth # |
Minimal complete definition
Methods
>>>
pretty 1 <+> pretty "hello" <+> pretty 1.234
1 hello 1.234
prettyList :: [a] -> Doc ann #
is only used to define the prettyList
instance
. In normal circumstances only the Pretty
a => Pretty
[a]
function is used.pretty
>>>
prettyList [1, 23, 456]
[1, 23, 456]
Instances
Pretty Void | Finding a good example for printing something that does not exist is hard, so here is an example of printing a list full of nothing.
|
Defined in Prettyprinter.Internal | |
Pretty Int16 | |
Defined in Prettyprinter.Internal | |
Pretty Int32 | |
Defined in Prettyprinter.Internal | |
Pretty Int64 | |
Defined in Prettyprinter.Internal | |
Pretty Int8 | |
Defined in Prettyprinter.Internal | |
Pretty Word16 | |
Defined in Prettyprinter.Internal | |
Pretty Word32 | |
Defined in Prettyprinter.Internal | |
Pretty Word64 | |
Defined in Prettyprinter.Internal | |
Pretty Word8 | |
Defined in Prettyprinter.Internal | |
Pretty Log Source # | |
Defined in Development.IDE.Core.FileStore | |
Pretty Log Source # | |
Defined in Development.IDE.Core.OfInterest | |
Pretty FileOfInterestStatus Source # | |
Defined in Development.IDE.Core.RuleTypes | |
Pretty Log Source # | |
Defined in Development.IDE.Core.Rules | |
Pretty Log Source # | |
Defined in Development.IDE.Core.Service | |
Pretty Log Source # | |
Defined in Development.IDE.Core.Shake | |
Pretty Log Source # | |
Defined in Development.IDE.LSP.HoverDefinition | |
Pretty Log Source # | |
Defined in Development.IDE.LSP.LanguageServer | |
Pretty Log Source # | |
Defined in Development.IDE.LSP.Notifications | |
Pretty Log Source # | |
Defined in Development.IDE.Main | |
Pretty Log Source # | |
Defined in Development.IDE.Main.HeapStats | |
Pretty Log Source # | |
Defined in Development.IDE.Plugin.Completions | |
Pretty Log Source # | |
Defined in Development.IDE.Plugin.HLS | |
Pretty Log Source # | |
Defined in Development.IDE.Plugin.HLS.GhcIde | |
Pretty Log Source # | |
Defined in Development.IDE.Plugin.TypeLenses | |
Pretty Log Source # | |
Defined in Development.IDE.Session | |
Pretty Log | |
Defined in HIE.Bios.Types | |
Pretty PluginError | |
Defined in Ide.Plugin.Error | |
Pretty HandleRequestResult | |
Defined in Ide.Plugin.HandleRequestTypes | |
Pretty RejectionReason | |
Defined in Ide.Plugin.HandleRequestTypes | |
Pretty SessionLoadingPreferenceConfig | |
Defined in Ide.Types Methods pretty :: SessionLoadingPreferenceConfig -> Doc ann # prettyList :: [SessionLoadingPreferenceConfig] -> Doc ann # | |
Pretty LspServerLog | |
Defined in Language.LSP.Server.Control | |
Pretty LspCoreLog | |
Defined in Language.LSP.Server.Core | |
Pretty VfsLog | |
Defined in Language.LSP.VFS | |
Pretty AnnotatedTextEdit | |
Pretty ApplyWorkspaceEditParams | |
Pretty ApplyWorkspaceEditResult | |
Pretty BaseSymbolInformation | |
Pretty CallHierarchyClientCapabilities | |
Pretty CallHierarchyIncomingCall | |
Pretty CallHierarchyIncomingCallsParams | |
Pretty CallHierarchyItem | |
Pretty CallHierarchyOptions | |
Pretty CallHierarchyOutgoingCall | |
Pretty CallHierarchyOutgoingCallsParams | |
Pretty CallHierarchyPrepareParams | |
Pretty CallHierarchyRegistrationOptions | |
Pretty CancelParams | |
Pretty ChangeAnnotation | |
Pretty ChangeAnnotationIdentifier | |
Pretty ChangeAnnotationsSupportOptions | |
Pretty ClientCapabilities | |
Pretty ClientCodeActionKindOptions | |
Pretty ClientCodeActionLiteralOptions | |
Pretty ClientCodeActionResolveOptions | |
Pretty ClientCompletionItemInsertTextModeOptions | |
Pretty ClientCompletionItemOptions | |
Pretty ClientCompletionItemOptionsKind | |
Pretty ClientCompletionItemResolveOptions | |
Pretty ClientDiagnosticsTagOptions | |
Pretty ClientFoldingRangeKindOptions | |
Pretty ClientFoldingRangeOptions | |
Pretty ClientInfo | |
Pretty ClientInlayHintResolveOptions | |
Pretty ClientSemanticTokensRequestFullDelta | |
Pretty ClientSemanticTokensRequestOptions | |
Pretty ClientShowMessageActionItemOptions | |
Pretty ClientSignatureInformationOptions | |
Pretty ClientSignatureParameterInformationOptions | |
Pretty ClientSymbolKindOptions | |
Pretty ClientSymbolResolveOptions | |
Pretty ClientSymbolTagOptions | |
Pretty CodeAction | |
Pretty CodeActionClientCapabilities | |
Pretty CodeActionContext | |
Pretty CodeActionDisabled | |
Pretty CodeActionKind | |
Pretty CodeActionOptions | |
Pretty CodeActionParams | |
Pretty CodeActionRegistrationOptions | |
Pretty CodeActionTriggerKind | |
Pretty CodeDescription | |
Pretty CodeLens | |
Pretty CodeLensClientCapabilities | |
Pretty CodeLensOptions | |
Pretty CodeLensParams | |
Pretty CodeLensRegistrationOptions | |
Pretty CodeLensWorkspaceClientCapabilities | |
Pretty Color | |
Defined in Language.LSP.Protocol.Internal.Types.Color | |
Pretty ColorInformation | |
Pretty ColorPresentation | |
Pretty ColorPresentationParams | |
Pretty Command | |
Defined in Language.LSP.Protocol.Internal.Types.Command | |
Pretty CompletionClientCapabilities | |
Pretty CompletionContext | |
Pretty CompletionItem | |
Pretty CompletionItemDefaults | |
Pretty CompletionItemKind | |
Pretty CompletionItemLabelDetails | |
Pretty CompletionItemTag | |
Pretty CompletionItemTagOptions | |
Pretty CompletionList | |
Pretty CompletionListCapabilities | |
Pretty CompletionOptions | |
Pretty CompletionParams | |
Pretty CompletionRegistrationOptions | |
Pretty CompletionTriggerKind | |
Pretty ConfigurationItem | |
Pretty ConfigurationParams | |
Pretty CreateFile | |
Pretty CreateFileOptions | |
Pretty CreateFilesParams | |
Pretty Declaration | |
Pretty DeclarationClientCapabilities | |
Pretty DeclarationLink | |
Pretty DeclarationOptions | |
Pretty DeclarationParams | |
Pretty DeclarationRegistrationOptions | |
Pretty Definition | |
Pretty DefinitionClientCapabilities | |
Pretty DefinitionLink | |
Pretty DefinitionOptions | |
Pretty DefinitionParams | |
Pretty DefinitionRegistrationOptions | |
Pretty DeleteFile | |
Pretty DeleteFileOptions | |
Pretty DeleteFilesParams | |
Pretty Diagnostic | |
Pretty DiagnosticClientCapabilities | |
Pretty DiagnosticOptions | |
Pretty DiagnosticRegistrationOptions | |
Pretty DiagnosticRelatedInformation | |
Pretty DiagnosticServerCancellationData | |
Pretty DiagnosticSeverity | |
Pretty DiagnosticTag | |
Pretty DiagnosticWorkspaceClientCapabilities | |
Pretty DidChangeConfigurationClientCapabilities | |
Pretty DidChangeConfigurationParams | |
Pretty DidChangeConfigurationRegistrationOptions | |
Pretty DidChangeNotebookDocumentParams | |
Pretty DidChangeTextDocumentParams | |
Pretty DidChangeWatchedFilesClientCapabilities | |
Pretty DidChangeWatchedFilesParams | |
Pretty DidChangeWatchedFilesRegistrationOptions | |
Pretty DidChangeWorkspaceFoldersParams | |
Pretty DidCloseNotebookDocumentParams | |
Pretty DidCloseTextDocumentParams | |
Pretty DidOpenNotebookDocumentParams | |
Pretty DidOpenTextDocumentParams | |
Pretty DidSaveNotebookDocumentParams | |
Pretty DidSaveTextDocumentParams | |
Pretty DocumentColorClientCapabilities | |
Pretty DocumentColorOptions | |
Pretty DocumentColorParams | |
Pretty DocumentColorRegistrationOptions | |
Pretty DocumentDiagnosticParams | |
Pretty DocumentDiagnosticReport | |
Pretty DocumentDiagnosticReportKind | |
Pretty DocumentDiagnosticReportPartialResult | |
Pretty DocumentFilter | |
Pretty DocumentFormattingClientCapabilities | |
Pretty DocumentFormattingOptions | |
Pretty DocumentFormattingParams | |
Pretty DocumentFormattingRegistrationOptions | |
Pretty DocumentHighlight | |
Pretty DocumentHighlightClientCapabilities | |
Pretty DocumentHighlightKind | |
Pretty DocumentHighlightOptions | |
Pretty DocumentHighlightParams | |
Pretty DocumentHighlightRegistrationOptions | |
Pretty DocumentLink | |
Pretty DocumentLinkClientCapabilities | |
Pretty DocumentLinkOptions | |
Pretty DocumentLinkParams | |
Pretty DocumentLinkRegistrationOptions | |
Pretty DocumentOnTypeFormattingClientCapabilities | |
Pretty DocumentOnTypeFormattingOptions | |
Pretty DocumentOnTypeFormattingParams | |
Pretty DocumentOnTypeFormattingRegistrationOptions | |
Pretty DocumentRangeFormattingClientCapabilities | |
Pretty DocumentRangeFormattingOptions | |
Pretty DocumentRangeFormattingParams | |
Pretty DocumentRangeFormattingRegistrationOptions | |
Pretty DocumentSelector | |
Pretty DocumentSymbol | |
Pretty DocumentSymbolClientCapabilities | |
Pretty DocumentSymbolOptions | |
Pretty DocumentSymbolParams | |
Pretty DocumentSymbolRegistrationOptions | |
Pretty EditRangeWithInsertReplace | |
Pretty ErrorCodes | |
Pretty ExecuteCommandClientCapabilities | |
Pretty ExecuteCommandOptions | |
Pretty ExecuteCommandParams | |
Pretty ExecuteCommandRegistrationOptions | |
Pretty ExecutionSummary | |
Pretty FailureHandlingKind | |
Pretty FileChangeType | |
Pretty FileCreate | |
Pretty FileDelete | |
Pretty FileEvent | |
Pretty FileOperationClientCapabilities | |
Pretty FileOperationFilter | |
Pretty FileOperationOptions | |
Pretty FileOperationPattern | |
Pretty FileOperationPatternKind | |
Pretty FileOperationPatternOptions | |
Pretty FileOperationRegistrationOptions | |
Pretty FileRename | |
Pretty FileSystemWatcher | |
Pretty FoldingRange | |
Pretty FoldingRangeClientCapabilities | |
Pretty FoldingRangeKind | |
Pretty FoldingRangeOptions | |
Pretty FoldingRangeParams | |
Pretty FoldingRangeRegistrationOptions | |
Pretty FormattingOptions | |
Pretty FullDocumentDiagnosticReport | |
Pretty GeneralClientCapabilities | |
Pretty GlobPattern | |
Pretty Hover | |
Defined in Language.LSP.Protocol.Internal.Types.Hover | |
Pretty HoverClientCapabilities | |
Pretty HoverOptions | |
Pretty HoverParams | |
Pretty HoverRegistrationOptions | |
Pretty ImplementationClientCapabilities | |
Pretty ImplementationOptions | |
Pretty ImplementationParams | |
Pretty ImplementationRegistrationOptions | |
Pretty InitializeError | |
Pretty InitializeParams | |
Pretty InitializeResult | |
Pretty InitializedParams | |
Pretty InlayHint | |
Pretty InlayHintClientCapabilities | |
Pretty InlayHintKind | |
Pretty InlayHintLabelPart | |
Pretty InlayHintOptions | |
Pretty InlayHintParams | |
Pretty InlayHintRegistrationOptions | |
Pretty InlayHintWorkspaceClientCapabilities | |
Pretty InlineValue | |
Pretty InlineValueClientCapabilities | |
Pretty InlineValueContext | |
Pretty InlineValueEvaluatableExpression | |
Pretty InlineValueOptions | |
Pretty InlineValueParams | |
Pretty InlineValueRegistrationOptions | |
Pretty InlineValueText | |
Pretty InlineValueVariableLookup | |
Pretty InlineValueWorkspaceClientCapabilities | |
Pretty InsertReplaceEdit | |
Pretty InsertTextFormat | |
Pretty InsertTextMode | |
Pretty LSPErrorCodes | |
Pretty LanguageKind | |
Pretty LinkedEditingRangeClientCapabilities | |
Pretty LinkedEditingRangeOptions | |
Pretty LinkedEditingRangeParams | |
Pretty LinkedEditingRangeRegistrationOptions | |
Pretty LinkedEditingRanges | |
Pretty Location | |
Pretty LocationLink | |
Pretty LocationUriOnly | |
Pretty LogMessageParams | |
Pretty LogTraceParams | |
Pretty MarkdownClientCapabilities | |
Pretty MarkedString | |
Pretty MarkedStringWithLanguage | |
Pretty MarkupContent | |
Pretty MarkupKind | |
Pretty MessageActionItem | |
Pretty MessageType | |
Pretty Moniker | |
Defined in Language.LSP.Protocol.Internal.Types.Moniker | |
Pretty MonikerClientCapabilities | |
Pretty MonikerKind | |
Pretty MonikerOptions | |
Pretty MonikerParams | |
Pretty MonikerRegistrationOptions | |
Pretty NotebookCell | |
Pretty NotebookCellArrayChange | |
Pretty NotebookCellKind | |
Pretty NotebookCellLanguage | |
Pretty NotebookCellTextDocumentFilter | |
Pretty NotebookDocument | |
Pretty NotebookDocumentCellChangeStructure | |
Pretty NotebookDocumentCellChanges | |
Pretty NotebookDocumentCellContentChanges | |
Pretty NotebookDocumentChangeEvent | |
Pretty NotebookDocumentClientCapabilities | |
Pretty NotebookDocumentFilter | |
Pretty NotebookDocumentFilterNotebookType | |
Pretty NotebookDocumentFilterPattern | |
Pretty NotebookDocumentFilterScheme | |
Pretty NotebookDocumentFilterWithCells | |
Pretty NotebookDocumentFilterWithNotebook | |
Pretty NotebookDocumentIdentifier | |
Pretty NotebookDocumentSyncClientCapabilities | |
Pretty NotebookDocumentSyncOptions | |
Pretty NotebookDocumentSyncRegistrationOptions | |
Pretty OptionalVersionedTextDocumentIdentifier | |
Pretty ParameterInformation | |
Pretty PartialResultParams | |
Pretty Pattern | |
Defined in Language.LSP.Protocol.Internal.Types.Pattern | |
Pretty Position | |
Pretty PositionEncodingKind | |
Pretty PrepareRenameDefaultBehavior | |
Pretty PrepareRenameParams | |
Pretty PrepareRenamePlaceholder | |
Pretty PrepareRenameResult | |
Pretty PrepareSupportDefaultBehavior | |
Pretty PreviousResultId | |
Pretty ProgressParams | |
Pretty ProgressToken | |
Pretty PublishDiagnosticsClientCapabilities | |
Pretty PublishDiagnosticsParams | |
Pretty Range | |
Defined in Language.LSP.Protocol.Internal.Types.Range | |
Pretty ReferenceClientCapabilities | |
Pretty ReferenceContext | |
Pretty ReferenceOptions | |
Pretty ReferenceParams | |
Pretty ReferenceRegistrationOptions | |
Pretty Registration | |
Pretty RegistrationParams | |
Pretty RegularExpressionEngineKind | |
Pretty RegularExpressionsClientCapabilities | |
Pretty RelatedFullDocumentDiagnosticReport | |
Pretty RelatedUnchangedDocumentDiagnosticReport | |
Pretty RelativePattern | |
Pretty RenameClientCapabilities | |
Pretty RenameFile | |
Pretty RenameFileOptions | |
Pretty RenameFilesParams | |
Pretty RenameOptions | |
Pretty RenameParams | |
Pretty RenameRegistrationOptions | |
Pretty ResourceOperation | |
Pretty ResourceOperationKind | |
Pretty SaveOptions | |
Pretty SelectionRange | |
Pretty SelectionRangeClientCapabilities | |
Pretty SelectionRangeOptions | |
Pretty SelectionRangeParams | |
Pretty SelectionRangeRegistrationOptions | |
Pretty SemanticTokenModifiers | |
Pretty SemanticTokenTypes | |
Pretty SemanticTokens | |
Pretty SemanticTokensClientCapabilities | |
Pretty SemanticTokensDelta | |
Pretty SemanticTokensDeltaParams | |
Pretty SemanticTokensDeltaPartialResult | |
Pretty SemanticTokensEdit | |
Pretty SemanticTokensFullDelta | |
Pretty SemanticTokensLegend | |
Pretty SemanticTokensOptions | |
Pretty SemanticTokensParams | |
Pretty SemanticTokensPartialResult | |
Pretty SemanticTokensRangeParams | |
Pretty SemanticTokensRegistrationOptions | |
Pretty SemanticTokensWorkspaceClientCapabilities | |
Pretty ServerCapabilities | |
Pretty ServerCompletionItemOptions | |
Pretty ServerInfo | |
Pretty SetTraceParams | |
Pretty ShowDocumentClientCapabilities | |
Pretty ShowDocumentParams | |
Pretty ShowDocumentResult | |
Pretty ShowMessageParams | |
Pretty ShowMessageRequestClientCapabilities | |
Pretty ShowMessageRequestParams | |
Pretty SignatureHelp | |
Pretty SignatureHelpClientCapabilities | |
Pretty SignatureHelpContext | |
Pretty SignatureHelpOptions | |
Pretty SignatureHelpParams | |
Pretty SignatureHelpRegistrationOptions | |
Pretty SignatureHelpTriggerKind | |
Pretty SignatureInformation | |
Pretty StaleRequestSupportOptions | |
Pretty StaticRegistrationOptions | |
Pretty SymbolInformation | |
Pretty SymbolKind | |
Pretty SymbolTag | |
Pretty TextDocumentChangeRegistrationOptions | |
Pretty TextDocumentClientCapabilities | |
Pretty TextDocumentContentChangeEvent | |
Pretty TextDocumentContentChangePartial | |
Pretty TextDocumentContentChangeWholeDocument | |
Pretty TextDocumentEdit | |
Pretty TextDocumentFilter | |
Pretty TextDocumentFilterLanguage | |
Pretty TextDocumentFilterPattern | |
Pretty TextDocumentFilterScheme | |
Pretty TextDocumentIdentifier | |
Pretty TextDocumentItem | |
Pretty TextDocumentPositionParams | |
Pretty TextDocumentRegistrationOptions | |
Pretty TextDocumentSaveReason | |
Pretty TextDocumentSaveRegistrationOptions | |
Pretty TextDocumentSyncClientCapabilities | |
Pretty TextDocumentSyncKind | |
Pretty TextDocumentSyncOptions | |
Pretty TextEdit | |
Pretty TokenFormat | |
Pretty TraceValue | |
Pretty TypeDefinitionClientCapabilities | |
Pretty TypeDefinitionOptions | |
Pretty TypeDefinitionParams | |
Pretty TypeDefinitionRegistrationOptions | |
Pretty TypeHierarchyClientCapabilities | |
Pretty TypeHierarchyItem | |
Pretty TypeHierarchyOptions | |
Pretty TypeHierarchyPrepareParams | |
Pretty TypeHierarchyRegistrationOptions | |
Pretty TypeHierarchySubtypesParams | |
Pretty TypeHierarchySupertypesParams | |
Pretty UInitializeParams | |
Pretty UnchangedDocumentDiagnosticReport | |
Pretty UniquenessLevel | |
Pretty Unregistration | |
Pretty UnregistrationParams | |
Pretty VersionedNotebookDocumentIdentifier | |
Pretty VersionedTextDocumentIdentifier | |
Pretty WatchKind | |
Pretty WillSaveTextDocumentParams | |
Pretty WindowClientCapabilities | |
Pretty WorkDoneProgressBegin | |
Pretty WorkDoneProgressCancelParams | |
Pretty WorkDoneProgressCreateParams | |
Pretty WorkDoneProgressEnd | |
Pretty WorkDoneProgressOptions | |
Pretty WorkDoneProgressParams | |
Pretty WorkDoneProgressReport | |
Pretty WorkspaceClientCapabilities | |
Pretty WorkspaceDiagnosticParams | |
Pretty WorkspaceDiagnosticReport | |
Pretty WorkspaceDiagnosticReportPartialResult | |
Pretty WorkspaceDocumentDiagnosticReport | |
Pretty WorkspaceEdit | |
Pretty WorkspaceEditClientCapabilities | |
Pretty WorkspaceFolder | |
Pretty WorkspaceFoldersChangeEvent | |
Pretty WorkspaceFoldersInitializeParams | |
Pretty WorkspaceFoldersServerCapabilities | |
Pretty WorkspaceFullDocumentDiagnosticReport | |
Pretty WorkspaceOptions | |
Pretty WorkspaceSymbol | |
Pretty WorkspaceSymbolClientCapabilities | |
Pretty WorkspaceSymbolOptions | |
Pretty WorkspaceSymbolParams | |
Pretty WorkspaceSymbolRegistrationOptions | |
Pretty WorkspaceUnchangedDocumentDiagnosticReport | |
Pretty SomeClientMethod | |
Defined in Language.LSP.Protocol.Message.Method | |
Pretty SomeServerMethod | |
Defined in Language.LSP.Protocol.Message.Method | |
Pretty SomeRegistration | |
Defined in Language.LSP.Protocol.Message.Registration | |
Pretty SomeUnregistration | |
Defined in Language.LSP.Protocol.Message.Registration | |
Pretty NotificationMessage | |
Defined in Language.LSP.Protocol.Message.Types | |
Pretty RequestMessage | |
Defined in Language.LSP.Protocol.Message.Types | |
Pretty ResponseError | |
Defined in Language.LSP.Protocol.Message.Types | |
Pretty ResponseMessage | |
Defined in Language.LSP.Protocol.Message.Types | |
Pretty Null | |
Defined in Language.LSP.Protocol.Types.Common | |
Pretty UInt | |
Defined in Language.LSP.Protocol.Types.Common | |
Pretty NormalizedUri | |
Defined in Language.LSP.Protocol.Types.Uri | |
Pretty Uri | |
Defined in Language.LSP.Protocol.Types.Uri | |
Pretty Text | Automatically converts all newlines to
Note that
Manually use |
Defined in Prettyprinter.Internal | |
Pretty Text | (lazy |
Defined in Prettyprinter.Internal | |
Pretty Integer |
|
Defined in Prettyprinter.Internal | |
Pretty Natural | |
Defined in Prettyprinter.Internal | |
Pretty () |
The argument is not used:
|
Defined in Prettyprinter.Internal | |
Pretty Bool |
|
Defined in Prettyprinter.Internal | |
Pretty Char | Instead of
|
Defined in Prettyprinter.Internal | |
Pretty Double |
|
Defined in Prettyprinter.Internal | |
Pretty Float |
|
Defined in Prettyprinter.Internal | |
Pretty Int |
|
Defined in Prettyprinter.Internal | |
Pretty Word | |
Defined in Prettyprinter.Internal | |
Pretty a => Pretty (Identity a) |
|
Defined in Prettyprinter.Internal | |
Pretty a => Pretty (NonEmpty a) | |
Defined in Prettyprinter.Internal | |
Pretty (AString s) | |
Defined in Language.LSP.Protocol.Types.Singletons | |
Pretty (AnInteger n) | |
Defined in Language.LSP.Protocol.Types.Singletons | |
Pretty a => Pretty (Maybe a) | Ignore
|
Defined in Prettyprinter.Internal | |
Pretty a => Pretty [a] |
|
Defined in Prettyprinter.Internal | |
Pretty (LspId m) | |
Defined in Language.LSP.Protocol.Message.LspId | |
Pretty (TRegistration m) | |
Defined in Language.LSP.Protocol.Message.Registration | |
Pretty (TUnregistration m) | |
Defined in Language.LSP.Protocol.Message.Registration | |
ToJSON (MessageParams m) => Pretty (TNotificationMessage m) | |
Defined in Language.LSP.Protocol.Message.Types | |
ToJSON (MessageParams m) => Pretty (TRequestMessage m) | |
Defined in Language.LSP.Protocol.Message.Types | |
ToJSON (ErrorData m) => Pretty (TResponseError m) | |
Defined in Language.LSP.Protocol.Message.Types | |
(ToJSON (MessageResult m), ToJSON (ErrorData m)) => Pretty (TResponseMessage m) | |
Defined in Language.LSP.Protocol.Message.Types | |
(ToJSON a, ToJSON b) => Pretty (a |? b) | |
Defined in Language.LSP.Protocol.Types.Common | |
(Pretty a1, Pretty a2) => Pretty (a1, a2) |
|
Defined in Prettyprinter.Internal | |
Pretty a => Pretty (Const a b) | |
Defined in Prettyprinter.Internal | |
KnownSymbol s => Pretty (TCustomMessage s f t) | |
Defined in Language.LSP.Protocol.Message.Types | |
(Pretty a1, Pretty a2, Pretty a3) => Pretty (a1, a2, a3) |
|
Defined in Prettyprinter.Internal |
Instances
FromJSON Range | |
Defined in Language.LSP.Protocol.Internal.Types.Range | |
ToJSON Range | |
Generic Range | |
Show Range | |
NFData Range | |
Defined in Language.LSP.Protocol.Internal.Types.Range | |
Eq Range | |
Ord Range | |
MapAge Range Source # | |
Hashable Range | |
Defined in Language.LSP.Protocol.Internal.Types.Range | |
Pretty Range | |
Defined in Language.LSP.Protocol.Internal.Types.Range | |
HasEnd Range Position | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasInsert EditRangeWithInsertReplace Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasInsert InsertReplaceEdit Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange AnnotatedTextEdit Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange CallHierarchyItem Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange CodeActionParams Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange CodeLens Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange ColorInformation Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange ColorPresentationParams Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange Diagnostic Range | |
Defined in Language.LSP.Protocol.Types.Lens Methods | |
HasRange DocumentHighlight Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange DocumentLink Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange DocumentRangeFormattingParams Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange DocumentSymbol Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange InlayHintParams Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange InlineValueEvaluatableExpression Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange InlineValueParams Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange InlineValueText Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange InlineValueVariableLookup Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange Location Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange PrepareRenamePlaceholder Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange SelectionRange Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange SemanticTokensRangeParams Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange TextDocumentContentChangePartial Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange TextEdit Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRange TypeHierarchyItem Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasReplace EditRangeWithInsertReplace Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasReplace InsertReplaceEdit Range | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasSelectionRange CallHierarchyItem Range | |
Defined in Language.LSP.Protocol.Types.Lens Methods selectionRange :: Lens' CallHierarchyItem Range | |
HasSelectionRange DocumentSymbol Range | |
Defined in Language.LSP.Protocol.Types.Lens Methods selectionRange :: Lens' DocumentSymbol Range | |
HasSelectionRange TypeHierarchyItem Range | |
Defined in Language.LSP.Protocol.Types.Lens Methods selectionRange :: Lens' TypeHierarchyItem Range | |
HasStart Range Position | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasStoppedLocation InlineValueContext Range | |
Defined in Language.LSP.Protocol.Types.Lens Methods stoppedLocation :: Lens' InlineValueContext Range | |
HasTargetRange LocationLink Range | |
Defined in Language.LSP.Protocol.Types.Lens Methods targetRange :: Lens' LocationLink Range | |
HasTargetSelectionRange LocationLink Range | |
Defined in Language.LSP.Protocol.Types.Lens Methods targetSelectionRange :: Lens' LocationLink Range | |
HasEditRange CompletionItemDefaults (Maybe (Range |? EditRangeWithInsertReplace)) | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasFromRanges CallHierarchyIncomingCall [Range] | |
Defined in Language.LSP.Protocol.Types.Lens Methods fromRanges :: Lens' CallHierarchyIncomingCall [Range] | |
HasFromRanges CallHierarchyOutgoingCall [Range] | |
Defined in Language.LSP.Protocol.Types.Lens Methods fromRanges :: Lens' CallHierarchyOutgoingCall [Range] | |
HasOriginSelectionRange LocationLink (Maybe Range) | |
Defined in Language.LSP.Protocol.Types.Lens Methods originSelectionRange :: Lens' LocationLink (Maybe Range) | |
HasRange Hover (Maybe Range) | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRanges LinkedEditingRanges [Range] | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasSelection ShowDocumentParams (Maybe Range) | |
Defined in Language.LSP.Protocol.Types.Lens | |
type Rep Range | |
Defined in Language.LSP.Protocol.Internal.Types.Range type Rep Range = D1 ('MetaData "Range" "Language.LSP.Protocol.Internal.Types.Range" "lsp-types-2.3.0.1-Dt5cmuKhDStI87OYfVmx4l" 'False) (C1 ('MetaCons "Range" 'PrefixI 'True) (S1 ('MetaSel ('Just "_start") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Position) :*: S1 ('MetaSel ('Just "_end") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Position))) |
data NormalizedUri #
Instances
data IdeConfiguration Source #
Lsp client relevant configuration details
Constructors
IdeConfiguration | |
Fields |
Instances
Show IdeConfiguration Source # | |
Defined in Development.IDE.Core.IdeConfiguration Methods showsPrec :: Int -> IdeConfiguration -> ShowS # show :: IdeConfiguration -> String # showList :: [IdeConfiguration] -> ShowS # |
data FastResult a Source #
A (maybe) stale result now, and an up to date one later
Constructors
FastResult | |
IdeActions are used when we want to return a result immediately, even if it is stale Useful for UI actions like hover, completion where we don't want to block.
Run via runIdeAction
.
Constructors
IdeAction | |
Fields |
Instances
MonadIO IdeAction Source # | |
Defined in Development.IDE.Core.Shake | |
Applicative IdeAction Source # | |
Defined in Development.IDE.Core.Shake | |
Functor IdeAction Source # | |
Monad IdeAction Source # | |
MonadReader ShakeExtras IdeAction Source # | |
Defined in Development.IDE.Core.Shake Methods ask :: IdeAction ShakeExtras # local :: (ShakeExtras -> ShakeExtras) -> IdeAction a -> IdeAction a # reader :: (ShakeExtras -> a) -> IdeAction a # | |
Semigroup a => Semigroup (IdeAction a) Source # | |
type IdeRule k v = (RuleResult k ~ v, ShakeValue k, Show v, Typeable v, NFData v) Source #
A Shake database plus persistent store. Can be thought of as storing
mappings from (FilePath, k)
to RuleResult k
.
Instances
MonadReader (ReactorChan, IdeState) (ServerM c) Source # | |
Defined in Development.IDE.LSP.Server Methods ask :: ServerM c (ReactorChan, IdeState) # local :: ((ReactorChan, IdeState) -> (ReactorChan, IdeState)) -> ServerM c a -> ServerM c a # reader :: ((ReactorChan, IdeState) -> a) -> ServerM c a # |
Constructors
Rule (k -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult v)) | |
RuleNoDiagnostics (k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v)) | |
RuleWithCustomNewnessCheck | |
Fields
| |
RuleWithOldValue (k -> NormalizedFilePath -> Value v -> Action (Maybe ByteString, IdeResult v)) |
data ShakeExtras Source #
Instances
MonadReader ShakeExtras IdeAction Source # | |
Defined in Development.IDE.Core.Shake Methods ask :: IdeAction ShakeExtras # local :: (ShakeExtras -> ShakeExtras) -> IdeAction a -> IdeAction a # reader :: (ShakeExtras -> a) -> IdeAction a # |
data VFSModified Source #
Constructors
VFSUnmodified | |
VFSModified !VFS |
data GhcVersion Source #
Instances
An HscEnv
with equality. Two values are considered equal
if they are created with the same call to newHscEnvEq
or
updateHscEnvEq
.
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 NormalizedFilePath #
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
|
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 |
type IdeResult v = ([FileDiagnostic], Maybe v) Source #
The result of an IDE operation. Warnings and errors are in the Diagnostic, and a value is in the Maybe. For operations that throw an error you expect a non-empty list of diagnostics, at least one of which is an error, and a Nothing. For operations that succeed you expect perhaps some warnings and a Just. For operations that depend on other failing operations you may get empty diagnostics and a Nothing, to indicate this phase throws no fresh errors but still failed.
A rule on a file should only return diagnostics for that given file. It should not propagate diagnostic errors through multiple phases.
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
type FileDiagnostic = (NormalizedFilePath, ShowDiagnostic, Diagnostic) Source #
Human readable diagnostics for a specific file.
This type packages a pretty printed, human readable error message along with the related source location so that we can display the error on either the console or in the IDE at the right source location.
Instances
FromJSON Uri | |
Defined in Language.LSP.Protocol.Types.Uri | |
FromJSONKey Uri | |
Defined in Language.LSP.Protocol.Types.Uri | |
ToJSON Uri | |
ToJSONKey Uri | |
Defined in Language.LSP.Protocol.Types.Uri | |
Generic Uri | |
Read Uri | |
Show Uri | |
NFData Uri | |
Defined in Language.LSP.Protocol.Types.Uri | |
Eq Uri | |
Ord Uri | |
Hashable Uri | |
Defined in Language.LSP.Protocol.Types.Uri | |
Pretty Uri | |
Defined in Language.LSP.Protocol.Types.Uri | |
HasDocument NotebookCell Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasHref CodeDescription Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasNewUri RenameFile Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasOldUri RenameFile Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasTargetUri LocationLink Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri CallHierarchyItem Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri CreateFile Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri DeleteFile Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri FileEvent Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri Location Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri LocationUriOnly Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri NotebookDocument Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri NotebookDocumentIdentifier Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri OptionalVersionedTextDocumentIdentifier Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri PreviousResultId Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri PublishDiagnosticsParams Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri ShowDocumentParams Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri TextDocumentIdentifier Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri TextDocumentItem Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri TypeHierarchyItem Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri VersionedNotebookDocumentIdentifier Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri VersionedTextDocumentIdentifier Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri WorkspaceFolder Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri WorkspaceFullDocumentDiagnosticReport Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasUri WorkspaceUnchangedDocumentDiagnosticReport Uri | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasChanges WorkspaceEdit (Maybe (Map Uri [TextEdit])) | |
HasRelatedDocuments RelatedFullDocumentDiagnosticReport (Maybe (Map Uri (FullDocumentDiagnosticReport |? UnchangedDocumentDiagnosticReport))) | |
Defined in Language.LSP.Protocol.Types.Lens Methods relatedDocuments :: Lens' RelatedFullDocumentDiagnosticReport (Maybe (Map Uri (FullDocumentDiagnosticReport |? UnchangedDocumentDiagnosticReport))) | |
HasRelatedDocuments RelatedUnchangedDocumentDiagnosticReport (Maybe (Map Uri (FullDocumentDiagnosticReport |? UnchangedDocumentDiagnosticReport))) | |
Defined in Language.LSP.Protocol.Types.Lens Methods relatedDocuments :: Lens' RelatedUnchangedDocumentDiagnosticReport (Maybe (Map Uri (FullDocumentDiagnosticReport |? UnchangedDocumentDiagnosticReport))) | |
HasScopeUri ConfigurationItem (Maybe Uri) | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasTarget DocumentLink (Maybe Uri) | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasBaseUri RelativePattern (WorkspaceFolder |? Uri) | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRelatedDocuments DocumentDiagnosticReportPartialResult (Map Uri (FullDocumentDiagnosticReport |? UnchangedDocumentDiagnosticReport)) | |
Defined in Language.LSP.Protocol.Types.Lens Methods relatedDocuments :: Lens' DocumentDiagnosticReportPartialResult (Map Uri (FullDocumentDiagnosticReport |? UnchangedDocumentDiagnosticReport)) | |
HasRootUri InitializeParams (Uri |? Null) | |
Defined in Language.LSP.Protocol.Types.Lens | |
HasRootUri UInitializeParams (Uri |? Null) | |
Defined in Language.LSP.Protocol.Types.Lens | |
type Rep Uri | |
Defined in Language.LSP.Protocol.Types.Uri |
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 ShowDiagnostic Source #
Defines whether a particular diagnostic should be reported back to the user.
One important use case is "missing signature" code lenses, for which we need to enable the corresponding warning during type checking. However, we do not want to show the warning unless the programmer asks for it (#261).
Instances
Show ShowDiagnostic Source # | |
Defined in Development.IDE.Types.Diagnostics Methods showsPrec :: Int -> ShowDiagnostic -> ShowS # show :: ShowDiagnostic -> String # showList :: [ShowDiagnostic] -> ShowS # | |
NFData ShowDiagnostic Source # | |
Defined in Development.IDE.Types.Diagnostics Methods rnf :: ShowDiagnostic -> () # | |
Eq ShowDiagnostic Source # | |
Defined in Development.IDE.Types.Diagnostics Methods (==) :: ShowDiagnostic -> ShowDiagnostic -> Bool # (/=) :: ShowDiagnostic -> ShowDiagnostic -> Bool # | |
Ord ShowDiagnostic Source # | |
Defined in Development.IDE.Types.Diagnostics Methods compare :: ShowDiagnostic -> ShowDiagnostic -> Ordering # (<) :: ShowDiagnostic -> ShowDiagnostic -> Bool # (<=) :: ShowDiagnostic -> ShowDiagnostic -> Bool # (>) :: ShowDiagnostic -> ShowDiagnostic -> Bool # (>=) :: ShowDiagnostic -> ShowDiagnostic -> Bool # max :: ShowDiagnostic -> ShowDiagnostic -> ShowDiagnostic # min :: ShowDiagnostic -> ShowDiagnostic -> ShowDiagnostic # |
data DiagnosticSeverity #
Constructors
DiagnosticSeverity_Error | |
DiagnosticSeverity_Warning | |
DiagnosticSeverity_Information | |
DiagnosticSeverity_Hint |
Instances
type IdeResultNoDiagnosticsEarlyCutoff v = (Maybe ByteString, Maybe v) Source #
an IdeResult with a fingerprint
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 GetLocatedImports Source #
Constructors
GetLocatedImports |
Instances
data GetKnownTargets Source #
Constructors
GetKnownTargets |
Instances
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 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 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 GetModificationTime :: GetModificationTime Source #
(<>) :: Semigroup a => a -> a -> a infixr 6 #
An associative operation.
>>>
[1,2,3] <> [4,5,6]
[1,2,3,4,5,6]
list :: [Doc ann] -> Doc ann #
Haskell-inspired variant of encloseSep
with braces and comma as
separator.
>>>
let doc = list (map pretty [1,20,300,4000])
>>>
putDocW 80 doc
[1, 20, 300, 4000]
>>>
putDocW 10 doc
[ 1 , 20 , 300 , 4000 ]
(
tries laying out group
x)x
into a single line by removing the
contained line breaks; if this does not fit the page, or when a hardline
within x
prevents it from being flattened, x
is laid out without any
changes.
The group
function is key to layouts that adapt to available space nicely.
See vcat
, line
, or flatAlt
for examples that are related, or make good
use of it.
(
lays out the document fill
i x)x
. It then appends space
s until
the width is equal to i
. If the width of x
is already larger, nothing is
appended.
This function is quite useful in practice to output a list of bindings:
>>>
let types = [("empty","Doc"), ("nest","Int -> Doc -> Doc"), ("fillSep","[Doc] -> Doc")]
>>>
let ptype (name, tp) = fill 5 (pretty name) <+> "::" <+> pretty tp
>>>
"let" <+> align (vcat (map ptype types))
let empty :: Doc nest :: Int -> Doc -> Doc fillSep :: [Doc] -> Doc
fuse :: FusionDepth -> Doc ann -> Doc ann #
(
combines text nodes so they can be rendered more
efficiently. A fused document is always laid out identical to its unfused
version.fuse
depth doc)
When laying a Doc
ument out to a SimpleDocStream
, every component of the
input is translated directly to the simpler output format. This sometimes
yields undesirable chunking when many pieces have been concatenated together.
For example
>>>
"a" <> "b" <> pretty 'c' <> "d"
abcd
results in a chain of four entries in a SimpleDocStream
, although this is fully
equivalent to the tightly packed
>>>
"abcd" :: Doc ann
abcd
which is only a single SimpleDocStream
entry, and can be processed faster.
It is therefore a good idea to run fuse
on concatenations of lots of small
strings that are used many times:
>>>
let oftenUsed = fuse Shallow ("a" <> "b" <> pretty 'c' <> "d")
>>>
hsep (replicate 5 oftenUsed)
abcd abcd abcd abcd abcd
column :: (Int -> Doc ann) -> Doc ann #
Layout a document depending on which column it starts at. align
is
implemented in terms of column
.
>>>
column (\l -> "Columns are" <+> pretty l <> "-based.")
Columns are 0-based.
>>>
let doc = "prefix" <+> column (\l -> "| <- column" <+> pretty l)
>>>
vsep [indent n doc | n <- [0,4,8]]
prefix | <- column 7 prefix | <- column 11 prefix | <- column 15
(
lays out the document nest
i x)x
with the current nesting level
(indentation of the following lines) increased by i
. Negative values are
allowed, and decrease the nesting level accordingly.
>>>
vsep [nest 4 (vsep ["lorem", "ipsum", "dolor"]), "sit", "amet"]
lorem ipsum dolor sit amet
See also
tupled :: [Doc ann] -> Doc ann #
Haskell-inspired variant of encloseSep
with parentheses and comma as
separator.
>>>
let doc = tupled (map pretty [1,20,300,4000])
>>>
putDocW 80 doc
(1, 20, 300, 4000)
>>>
putDocW 10 doc
( 1 , 20 , 300 , 4000 )
hsep :: [Doc ann] -> Doc ann #
(
concatenates all documents hsep
xs)xs
horizontally with
,
i.e. it puts a space between all entries.<+>
>>>
let docs = Util.words "lorem ipsum dolor sit amet"
>>>
hsep docs
lorem ipsum dolor sit amet
does not introduce line breaks on its own, even when the page is too
narrow:hsep
>>>
putDocW 5 (hsep docs)
lorem ipsum dolor sit amet
For automatic line breaks, consider using fillSep
instead.
vcat :: [Doc ann] -> Doc ann #
(
vertically concatenates the documents vcat
xs)xs
. If it is
group
ed, the line breaks are removed.
In other words
is like vcat
, with newlines removed instead of
replaced by vsep
space
s.
>>>
let docs = Util.words "lorem ipsum dolor"
>>>
vcat docs
lorem ipsum dolor>>>
group (vcat docs)
loremipsumdolor
Since group
ing a vcat
is rather common, cat
is a built-in shortcut for
it.
Arguments
:: Int | Change of nesting level, relative to the start of the first line |
-> Doc ann | |
-> Doc ann |
(
lays out the document hang
i x)x
with a nesting level set to the
current column plus i
. Negative values are allowed, and decrease the
nesting level accordingly.
>>>
let doc = reflow "Indenting these words with hang"
>>>
putDocW 24 ("prefix" <+> hang 4 doc)
prefix Indenting these words with hang
This differs from nest
, which is based on the current nesting level plus
i
. When you're not sure, try the more efficient nest
first. In our
example, this would yield
>>>
let doc = reflow "Indenting these words with nest"
>>>
putDocW 24 ("prefix" <+> nest 4 doc)
prefix Indenting these words with nest
hang
i doc =align
(nest
i doc)
(
appends punctuate
p xs)p
to all but the last document in xs
.
>>>
let docs = punctuate comma (Util.words "lorem ipsum dolor sit amet")
>>>
putDocW 80 (hsep docs)
lorem, ipsum, dolor, sit, amet
The separators are put at the end of the entries, which we can see if we position the result vertically:
>>>
putDocW 20 (vsep docs)
lorem, ipsum, dolor, sit, amet
If you want put the commas in front of their elements instead of at the end,
you should use tupled
or, in general, encloseSep
.
(
tries laying out the documents sep
xs)xs
separated with space
s,
and if this does not fit the page, separates them with newlines. This is what
differentiates it from vsep
, which always lays out its contents beneath
each other.
>>>
let doc = "prefix" <+> sep ["text", "to", "lay", "out"]
>>>
putDocW 80 doc
prefix text to lay out
With a narrower layout, the entries are separated by newlines:
>>>
putDocW 20 doc
prefix text to lay out
sep
=group
.vsep
(
tries laying out the documents cat
xs)xs
separated with nothing,
and if this does not fit the page, separates them with newlines. This is what
differentiates it from vcat
, which always lays out its contents beneath
each other.
>>>
let docs = Util.words "lorem ipsum dolor"
>>>
putDocW 80 ("Docs:" <+> cat docs)
Docs: loremipsumdolor
When there is enough space, the documents are put above one another:
>>>
putDocW 10 ("Docs:" <+> cat docs)
Docs: lorem ipsum dolor
cat
=group
.vcat
(
is plural
n one many)one
if n
is 1
, and many
otherwise. A
typical use case is adding a plural "s".
>>>
let things = [True]
>>>
let amount = length things
>>>
pretty things <+> "has" <+> pretty amount <+> plural "entry" "entries" amount
[True] has 1 entry
use :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe v) Source #
Request a Rule result if available
renderStrict :: SimpleDocStream ann -> Text #
(
takes the output renderStrict
sdoc)sdoc
from a rendering function
and transforms it to strict text.
logWith :: (HasCallStack, MonadIO m) => Recorder (WithPriority msg) -> Priority -> msg -> m () #
cmapWithPrio :: (a -> b) -> Recorder (WithPriority b) -> Recorder (WithPriority a) #
makeDefaultStderrRecorder :: MonadIO m => Maybe [LoggingColumn] -> m (Recorder (WithPriority (Doc a))) #
Arguments
:: MonadUnliftIO m | |
=> FilePath | Log file path. |
-> Maybe [LoggingColumn] | logging columns to display. |
-> (Either IOException (Recorder (WithPriority (Doc d))) -> m a) | action given a recorder, or the exception if we failed to open the file |
-> m a |
Arguments
:: MonadIO m | |
=> Maybe [LoggingColumn] | built-in logging columns to display. Nothing uses the default |
-> Lock | lock to take when outputting to handle |
-> Handle | handle to output to |
-> m (Recorder (WithPriority (Doc a))) |
lspClientMessageRecorder :: LanguageContextEnv config -> Recorder (WithPriority Text) #
Creates a recorder that sends logs to the LSP client via window/showMessage
notifications.
lspClientLogRecorder :: LanguageContextEnv config -> Recorder (WithPriority Text) #
Creates a recorder that sends logs to the LSP client via window/logMessage
notifications.
toCologActionWithPrio :: forall (m :: Type -> Type) msg. (MonadIO m, HasCallStack) => Recorder (WithPriority msg) -> LogAction m (WithSeverity msg) #
getClientConfig :: MonadLsp Config m => m Config #
Returns the current client configuration. It is not wise to permanently cache the returned value of this function, as clients can at runtime change their configuration.
viaShow :: Show a => a -> Doc ann #
Convenience function to convert a Show
able value to a Doc
. If the
String
does not contain newlines, consider using the more performant
unsafeViaShow
.
unsafeViaShow :: Show a => a -> Doc ann #
softline
behaves like
if the resulting output fits the page,
otherwise like space
.line
Here, we have enough space to put everything in one line:
>>>
let doc = "lorem ipsum" <> softline <> "dolor sit amet"
>>>
putDocW 80 doc
lorem ipsum dolor sit amet
If we narrow the page to width 10, the layouter produces a line break:
>>>
putDocW 10 doc
lorem ipsum dolor sit amet
softline
=group
line
is like softline'
, but behaves like softline
if the
resulting output does not fit on the page (instead of mempty
). In other
words, space
is to line
how line'
is to softline
.softline'
With enough space, we get direct concatenation:
>>>
let doc = "ThisWord" <> softline' <> "IsWayTooLong"
>>>
putDocW 80 doc
ThisWordIsWayTooLong
If we narrow the page to width 10, the layouter produces a line break:
>>>
putDocW 10 doc
ThisWord IsWayTooLong
softline'
=group
line'
A
is always laid out as a line break, even when hardline
group
ed or
when there is plenty of space. Note that it might still be simply discarded
if it is part of a flatAlt
inside a group
.
>>>
let doc = "lorem ipsum" <> hardline <> "dolor sit amet"
>>>
putDocW 1000 doc
lorem ipsum dolor sit amet
>>>
group doc
lorem ipsum dolor sit amet
By default, (
renders as flatAlt
x y)x
. However when group
ed,
y
will be preferred, with x
as the fallback for the case when y
doesn't fit.
>>>
let doc = flatAlt "a" "b"
>>>
putDoc doc
a>>>
putDoc (group doc)
b>>>
putDocW 0 (group doc)
a
flatAlt
is particularly useful for defining conditional separators such as
softline =group
(flatAlt
hardline
" ")
>>>
let hello = "Hello" <> softline <> "world!"
>>>
putDocW 12 hello
Hello world!>>>
putDocW 11 hello
Hello world!
Example: Haskell's do-notation
We can use this to render Haskell's do-notation nicely:
>>>
let open = flatAlt "" "{ "
>>>
let close = flatAlt "" " }"
>>>
let separator = flatAlt "" "; "
>>>
let prettyDo xs = group ("do" <+> align (encloseSep open close separator xs))
>>>
let statements = ["name:_ <- getArgs", "let greet = \"Hello, \" <> name", "putStrLn greet"]
This is put into a single line with {;}
style if it fits:
>>>
putDocW 80 (prettyDo statements)
do { name:_ <- getArgs; let greet = "Hello, " <> name; putStrLn greet }
When there is not enough space the statements are broken up into lines nicely:
>>>
putDocW 10 (prettyDo statements)
do name:_ <- getArgs let greet = "Hello, " <> name putStrLn greet
Notes
Users should be careful to choose x
to be less wide than y
.
Otherwise, if y
turns out not to fit the page, we fall back on an even
wider layout:
>>>
let ugly = group (flatAlt "even wider" "too wide")
>>>
putDocW 7 ugly
even wider
Also note that group
will flatten y
:
>>>
putDoc (group (flatAlt "x" ("y" <> line <> "y")))
y y
This also means that an "unflattenable" y
which contains a hard linebreak
will never be rendered:
>>>
putDoc (group (flatAlt "x" ("y" <> hardline <> "y")))
x
(
lays out the document align
x)x
with the nesting level set to the
current column. It is used for example to implement hang
.
As an example, we will put a document right above another one, regardless of
the current nesting level. Without align
ment, the second line is put simply
below everything we've had so far:
>>>
"lorem" <+> vsep ["ipsum", "dolor"]
lorem ipsum dolor
If we add an align
to the mix, the
's contents all start in the
same column:vsep
>>>
"lorem" <+> align (vsep ["ipsum", "dolor"])
lorem ipsum dolor
Arguments
:: Doc ann | left delimiter |
-> Doc ann | right delimiter |
-> Doc ann | separator |
-> [Doc ann] | input documents |
-> Doc ann |
(
concatenates the documents encloseSep
l r sep xs)xs
separated by
sep
, and encloses the resulting document by l
and r
.
The documents are laid out horizontally if that fits the page:
>>>
let doc = "list" <+> align (encloseSep lbracket rbracket comma (map pretty [1,20,300,4000]))
>>>
putDocW 80 doc
list [1,20,300,4000]
If there is not enough space, then the input is split into lines entry-wise therwise they are laid out vertically, with separators put in the front:
>>>
putDocW 10 doc
list [1 ,20 ,300 ,4000]
Note that doc
contains an explicit call to align
so that the list items
are aligned vertically.
For putting separators at the end of entries instead, have a look at
punctuate
.
concatWith :: Foldable t => (Doc ann -> Doc ann -> Doc ann) -> t (Doc ann) -> Doc ann #
Concatenate all documents element-wise with a binary function.
concatWith
_ [] =mempty
concatWith
(**) [x,y,z] = x ** y ** z
Multiple convenience definitions based on concatWith
are already predefined,
for example:
hsep
=concatWith
(<+>
)fillSep
=concatWith
(\x y -> x<>
softline
<>
y)
This is also useful to define customized joiners:
>>>
concatWith (surround dot) ["Prettyprinter", "Render", "Text"]
Prettyprinter.Render.Text
vsep :: [Doc ann] -> Doc ann #
(
concatenates all documents vsep
xs)xs
above each other. If a
group
undoes the line breaks inserted by vsep
, the documents are
separated with a space
instead.
Using vsep
alone yields
>>>
"prefix" <+> vsep ["text", "to", "lay", "out"]
prefix text to lay out
group
ing a vsep
separates the documents with a space
if it fits the
page (and does nothing otherwise). See the
convenience function for
this use case.sep
The align
function can be used to align the documents under their first
element:
>>>
"prefix" <+> align (vsep ["text", "to", "lay", "out"])
prefix text to lay out
Since group
ing a vsep
is rather common, sep
is a built-in for doing
that.
fillSep :: [Doc ann] -> Doc ann #
(
concatenates the documents fillSep
xs)xs
horizontally with
as long as it fits the page, then inserts a <+>
and continues doing that
for all documents in line
xs
. (
means that if line
group
ed, the documents
are separated with a space
instead of newlines. Use fillCat
if you do not
want a space
.)
Let's print some words to fill the line:
>>>
let docs = take 20 (cycle ["lorem", "ipsum", "dolor", "sit", "amet"])
>>>
putDocW 80 ("Docs:" <+> fillSep docs)
Docs: lorem ipsum dolor sit amet lorem ipsum dolor sit amet lorem ipsum dolor sit amet lorem ipsum dolor sit amet
The same document, printed at a width of only 40, yields
>>>
putDocW 40 ("Docs:" <+> fillSep docs)
Docs: lorem ipsum dolor sit amet lorem ipsum dolor sit amet lorem ipsum dolor sit amet lorem ipsum dolor sit amet
fillCat :: [Doc ann] -> Doc ann #
(
concatenates documents fillCat
xs)xs
horizontally with
as
long as it fits the page, then inserts a <>
and continues doing that
for all documents in line'
xs
. This is similar to how an ordinary word processor
lays out the text if you just keep typing after you hit the maximum line
length.
(
means that if line'
group
ed, the documents are separated with nothing
instead of newlines. See fillSep
if you want a space
instead.)
Observe the difference between fillSep
and fillCat
. fillSep
concatenates the entries space
d when group
ed:
>>>
let docs = take 20 (cycle (["lorem", "ipsum", "dolor", "sit", "amet"]))
>>>
putDocW 40 ("Grouped:" <+> group (fillSep docs))
Grouped: lorem ipsum dolor sit amet lorem ipsum dolor sit amet lorem ipsum dolor sit amet lorem ipsum dolor sit amet
On the other hand, fillCat
concatenates the entries directly when
group
ed:
>>>
putDocW 40 ("Grouped:" <+> group (fillCat docs))
Grouped: loremipsumdolorsitametlorem ipsumdolorsitametloremipsumdolorsitamet loremipsumdolorsitamet
width :: Doc ann -> (Int -> Doc ann) -> Doc ann #
(
lays out the document width
doc f)doc
, and makes the column width
of it available to a function.
>>>
let annotate doc = width (brackets doc) (\w -> " <- width:" <+> pretty w)
>>>
align (vsep (map annotate ["---", "------", indent 3 "---", vsep ["---", indent 4 "---"]]))
[---] <- width: 5 [------] <- width: 8 [ ---] <- width: 8 [--- ---] <- width: 8
pageWidth :: (PageWidth -> Doc ann) -> Doc ann #
Layout a document depending on the page width, if one has been specified.
>>>
let prettyPageWidth (AvailablePerLine l r) = "Width:" <+> pretty l <> ", ribbon fraction:" <+> pretty r
>>>
let doc = "prefix" <+> pageWidth (brackets . prettyPageWidth)
>>>
putDocW 32 (vsep [indent n doc | n <- [0,4,8]])
prefix [Width: 32, ribbon fraction: 1.0] prefix [Width: 32, ribbon fraction: 1.0] prefix [Width: 32, ribbon fraction: 1.0]
(
first lays out the document fillBreak
i x)x
. It then appends space
s
until the width is equal to i
. If the width of x
is already larger than
i
, the nesting level is increased by i
and a line
is appended. When we
redefine ptype
in the example given in fill
to use
, we get
a useful variation of the output:fillBreak
>>>
let types = [("empty","Doc"), ("nest","Int -> Doc -> Doc"), ("fillSep","[Doc] -> Doc")]
>>>
let ptype (name, tp) = fillBreak 5 (pretty name) <+> "::" <+> pretty tp
>>>
"let" <+> align (vcat (map ptype types))
let empty :: Doc nest :: Int -> Doc -> Doc fillSep :: [Doc] -> Doc
annotate :: ann -> Doc ann -> Doc ann #
Add an annotation to a
. This annotation can then be used by the
renderer to e.g. add color to certain parts of the output. For a full
tutorial example on how to use it, see the
Prettyprinter.Render.Tutorials.StackMachineTutorial or
Prettyprinter.Render.Tutorials.TreeRenderingTutorial modules.Doc
This function is only relevant for custom formats with their own annotations, and not relevant for basic prettyprinting. The predefined renderers, e.g. Prettyprinter.Render.Text, should be enough for the most common needs.
unAnnotate :: Doc ann -> Doc xxx #
Remove all annotations.
Although unAnnotate
is idempotent with respect to rendering,
unAnnotate
.unAnnotate
=unAnnotate
it should not be used without caution, for each invocation traverses the
entire contained document. If possible, it is preferrable to unannotate after
producing the layout by using unAnnotateS
.
reAnnotate :: (ann -> ann') -> Doc ann -> Doc ann' #
Change the annotation of a Doc
ument.
Useful in particular to embed documents with one form of annotation in a more generally annotated document.
Since this traverses the entire
tree, including parts that are not
rendered due to other layouts fitting better, it is preferrable to reannotate
after producing the layout by using Doc
.reAnnotateS
Since
has the right type and satisfies reAnnotate
'reAnnotate id = id'
,
it is used to define the
instance of Functor
.Doc
alterAnnotations :: (ann -> [ann']) -> Doc ann -> Doc ann' #
Change the annotations of a Doc
ument. Individual annotations can be
removed, changed, or replaced by multiple ones.
This is a general function that combines unAnnotate
and reAnnotate
, and
it is useful for mapping semantic annotations (such as »this is a keyword«)
to display annotations (such as »this is red and underlined«), because some
backends may not care about certain annotations, while others may.
Annotations earlier in the new list will be applied earlier, i.e. returning
[Bold, Green]
will result in a bold document that contains green text, and
not vice-versa.
Since this traverses the entire
tree, including parts that are not
rendered due to other layouts fitting better, it is preferrable to reannotate
after producing the layout by using Doc
.alterAnnotationsS
unAnnotateS :: SimpleDocStream ann -> SimpleDocStream xxx #
Remove all annotations. unAnnotate
for SimpleDocStream
.
reAnnotateS :: (ann -> ann') -> SimpleDocStream ann -> SimpleDocStream ann' #
Change the annotation of a document. reAnnotate
for SimpleDocStream
.
alterAnnotationsS :: (ann -> Maybe ann') -> SimpleDocStream ann -> SimpleDocStream ann' #
Change the annotation of a document to a different annotation, or none at
all. alterAnnotations
for SimpleDocStream
.
Note that the Doc
version is more flexible, since it allows changing a
single annotation to multiple ones.
(SimpleDocTree
restores
this flexibility again.)
removeTrailingWhitespace :: SimpleDocStream ann -> SimpleDocStream ann #
Remove all trailing space characters.
This has some performance impact, because it does an entire additional pass
over the SimpleDocStream
.
No trimming will be done inside annotations, which are considered to contain
no (trimmable) whitespace, since the annotation might actually be about the
whitespace, for example a renderer that colors the background of trailing
whitespace, as e.g. git diff
can be configured to do.
Historical note: Since v1.7.0, layoutPretty
and layoutSmart
avoid
producing the trailing whitespace that was the original motivation for
creating removeTrailingWhitespace
.
See https://github.com/quchen/prettyprinter/pull/139 for some background
info.
defaultLayoutOptions :: LayoutOptions #
The default layout options, suitable when you just want some output, and
don’t particularly care about the details. Used by the Show
instance, for
example.
>>>
defaultLayoutOptions
LayoutOptions {layoutPageWidth = AvailablePerLine 80 1.0}
layoutPretty :: LayoutOptions -> Doc ann -> SimpleDocStream ann #
This is the default layout algorithm, and it is used by show
, putDoc
and hPutDoc
.
commits to rendering something in a certain way if the next
element fits the layout constraints; in other words, it has one
layoutPretty
SimpleDocStream
element lookahead when rendering. Consider using the
smarter, but a bit less performant,
algorithm if the results
seem to run off to the right before having lots of line breaks.layoutSmart
layoutSmart :: LayoutOptions -> Doc ann -> SimpleDocStream ann #
A layout algorithm with more lookahead than layoutPretty
, that introduces
line breaks earlier if the content does not (or will not, rather) fit into
one line.
Consider the following python-ish document,
>>>
let fun x = hang 2 ("fun(" <> softline' <> x) <> ")"
>>>
let doc = (fun . fun . fun . fun . fun) (align (list ["abcdef", "ghijklm"]))
which we’ll be rendering using the following pipeline (where the layout algorithm has been left open):
>>>
import Data.Text.IO as T
>>>
import Prettyprinter.Render.Text
>>>
let hr = pipe <> pretty (replicate (26-2) '-') <> pipe
>>>
let go layouter x = (T.putStrLn . renderStrict . layouter (LayoutOptions (AvailablePerLine 26 1))) (vsep [hr, x, hr])
If we render this using layoutPretty
with a page width of 26 characters
per line, all the fun
calls fit into the first line so they will be put
there:
>>>
go layoutPretty doc
|------------------------| fun(fun(fun(fun(fun( [ abcdef , ghijklm ]))))) |------------------------|
Note that this exceeds the desired 26 character page width. The same
document, rendered with
, fits the layout contstraints:layoutSmart
>>>
go layoutSmart doc
|------------------------| fun( fun( fun( fun( fun( [ abcdef , ghijklm ]))))) |------------------------|
The key difference between layoutPretty
and layoutSmart
is that the
latter will check the potential document until it encounters a line with the
same indentation or less than the start of the document. Any line encountered
earlier is assumed to belong to the same syntactic structure.
layoutPretty
checks only the first line.
Consider for example the question of whether the A
s fit into the document
below:
1 A 2 A 3 A 4 B 5 B
layoutPretty
will check only line 1, ignoring whether e.g. line 2 might
already be too wide.
By contrast, layoutSmart
stops only once it reaches line 4, where the B
has the same indentation as the first A
.
layoutCompact :: Doc ann1 -> SimpleDocStream ann2 #
(layoutCompact x)
lays out the document x
without adding any
indentation and without preserving annotations.
Since no 'pretty' printing is involved, this layouter is very
fast. The resulting output contains fewer characters than a prettyprinted
version and can be used for output that is read by other programs.
>>>
let doc = hang 4 (vsep ["lorem", "ipsum", hang 4 (vsep ["dolor", "sit"])])
>>>
doc
lorem ipsum dolor sit
>>>
let putDocCompact = renderIO System.IO.stdout . layoutCompact
>>>
putDocCompact doc
lorem ipsum dolor sit
readFileUtf8 :: FilePath -> IO Text Source #
Read a UTF8 file, with lenient decoding, so it will never raise a decoding error.
uses :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f (Maybe v)) Source #
Plural version of use
getAtPoint :: NormalizedFilePath -> Position -> IdeAction (Maybe (Maybe Range, [Text])) Source #
Try to get hover text for the name under point.
getDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location]) Source #
Goto Definition.
getTypeDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location]) Source #
getFileExists :: NormalizedFilePath -> Action Bool Source #
Returns True if the file exists
getFileContents :: NormalizedFilePath -> Action (UTCTime, Maybe Text) Source #
Returns the modification time and the contents. For VFS paths, the modification time is the current time.
getClientConfigAction :: Action Config Source #
Returns the client configuration, creating a build dependency. You should always use this function when accessing client configuration from build rules.
getParsedModule :: NormalizedFilePath -> Action (Maybe ParsedModule) Source #
Parse the contents of a haskell file.
usePropertyAction :: HasProperty s k t r => KeyNameProxy s -> PluginId -> Properties r -> Action (ToHsType t) Source #
actionLogger :: Action (Recorder (WithPriority Log)) Source #
define :: IdeRule k v => Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (IdeResult v)) -> Rules () Source #
Define a new Rule without early cutoff
defineEarlyCutoff :: IdeRule k v => Recorder (WithPriority Log) -> RuleBody k v -> Rules () Source #
Define a new Rule with early cutoff
defineNoDiagnostics :: IdeRule k v => Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (Maybe v)) -> Rules () Source #
runIdeAction :: String -> ShakeExtras -> IdeAction a -> IO a Source #
useNoFile_ :: IdeRule k v => k -> Action v Source #
useWithStale :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping)) Source #
Request a Rule result, it not available return the last computed result, if any, which may be stale
useWithStaleFast :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (Maybe (v, PositionMapping)) Source #
Lookup value in the database and return with the stale value immediately Will queue an action to refresh the value. Might block the first time the rule runs, but never blocks after that.
useWithStaleFast' :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (FastResult v) Source #
Same as useWithStaleFast but lets you wait for an up to date result
useWithStale_ :: IdeRule k v => k -> NormalizedFilePath -> Action (v, PositionMapping) Source #
Request a Rule result, it not available return the last computed result which may be stale.
Throws an BadDependency
exception which is caught by the rule system if
none available.
WARNING: Not suitable for PluginHandlers. Use useWithStaleE
instead.
uses_ :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f v) Source #
Plural version of use_
Throws an BadDependency
exception which is caught by the rule system if
none available.
WARNING: Not suitable for PluginHandlers. Use usesE
instead.
hscEnvWithImportPaths :: HscEnvEq -> HscEnv Source #
Unwrap the HscEnv
with the original import paths.
Used only for locating imports
modifyDynFlags :: GhcMonad m => (DynFlags -> DynFlags) -> m () Source #
Used to modify dyn flags in preference to calling setSessionDynFlags
,
since that function also reloads packages (which is very slow).
showDiagnostics :: [FileDiagnostic] -> Text Source #
dontWriteHieFiles :: DynFlags -> DynFlags Source #
diagFromErrMsgs :: Text -> DynFlags -> Bag (MsgEnvelope DecoratedSDoc) -> [FileDiagnostic] Source #
diagFromErrMsg :: Text -> DynFlags -> MsgEnvelope DecoratedSDoc -> [FileDiagnostic] Source #
Produce a GHC-style error from a source span and a message.
diagFromString :: Text -> DiagnosticSeverity -> SrcSpan -> String -> [FileDiagnostic] Source #
Produce a GHC-style error from a source span and a message.
diagFromStrings :: Text -> DiagnosticSeverity -> [(SrcSpan, String)] -> [FileDiagnostic] Source #
Produce a bag of GHC-style errors (ErrorMessages
) from the given
(optional) locations and message strings.
diagFromGhcException :: Text -> DynFlags -> GhcException -> [FileDiagnostic] Source #
catchSrcErrors :: DynFlags -> Text -> IO a -> IO (Either [FileDiagnostic] a) Source #
Catch the errors thrown by GHC (SourceErrors and compiler-internal exceptions like Panic or InstallationError), and turn them into diagnostics
realSrcSpanToCodePointRange :: RealSrcSpan -> CodePointRange Source #
Convert a GHC SrcSpan to CodePointRange see Note [Unicode support]
realSrcLocToCodePointPosition :: RealSrcLoc -> CodePointPosition Source #
Convert a GHC RealSrcLoc to CodePointPosition see Note [Unicode support]
srcSpanToFilename :: SrcSpan -> Maybe FilePath Source #
Extract a file name from a GHC SrcSpan (use message for unhelpful ones) FIXME This may not be an _absolute_ file name, needs fixing.
rangeToSrcSpan :: NormalizedFilePath -> Range -> SrcSpan Source #
Arguments
:: FastString | file path of span |
-> RealSrcSpan |
creates a span with zero length in the filename of the argument passed
toDSeverity :: Severity -> Maybe DiagnosticSeverity Source #
Convert a GHC severity to a DAML compiler Severity. Severities below Warning level are dropped (returning Nothing).
lookupPackageConfig :: Unit -> HscEnv -> Maybe UnitInfo Source #
Given a Unit
try and find the associated PackageConfig
in the environment.
textToStringBuffer :: Text -> StringBuffer Source #
Convert from the text
package to the GHC
StringBuffer
.
Currently implemented somewhat inefficiently (if it ever comes up in a profile).
moduleImportPath :: NormalizedFilePath -> ModuleName -> Maybe FilePath Source #
Given a module location, and its parse tree, figure out what is the include directory implied by it.
For example, given the file /usr/Test/Foo/Bar.hs
with the module name Foo.Bar
the directory
/usr/Test
should be on the include path to find sibling modules.
cgGutsToCoreModule :: SafeHaskellMode -> CgGuts -> ModDetails -> CoreModule Source #
Convert from a CgGuts
to a CoreModule
.
fingerprintToBS :: Fingerprint -> ByteString Source #
Convert a Fingerprint
to a ByteString
by copying the byte across.
Will produce an 8 byte unreadable ByteString.
fingerprintFromStringBuffer :: StringBuffer -> IO Fingerprint Source #
Take the Fingerprint
of a StringBuffer
.
fingerprintFromPut :: Put -> IO Fingerprint Source #
hDuplicateTo' :: Handle -> Handle -> IO () Source #
A slightly modified version of hDuplicateTo
from GHC.
Importantly, it avoids the bug listed in https://gitlab.haskell.org/ghc/ghc/merge_requests/2318.
printOutputable :: Outputable a => a -> Text Source #
Print a GHC value in defaultUserStyle
without unique symbols.
It uses showSDocUnsafe
with unsafeGlobalDynFlags
internally.
This is the most common print utility.
It will do something additionally compared to what the Outputable
instance does.
- print with a user-friendly style:
a_a4ME
asa
. - unescape escape sequences of printable unicode characters within a pair of double quotes
getExtensions :: ParsedModule -> [Extension] Source #
ideErrorText :: NormalizedFilePath -> Text -> FileDiagnostic Source #
ideErrorWithSource :: Maybe Text -> Maybe DiagnosticSeverity -> a -> Text -> (a, ShowDiagnostic, Diagnostic) Source #
showDiagnosticsColored :: [FileDiagnostic] -> Text Source #
showPosition :: Position -> String Source #
toNormalizedUri :: Uri -> NormalizedUri #
fromNormalizedUri :: NormalizedUri -> Uri #
uriToFilePath' :: Uri -> Maybe FilePath Source #
We use an empty string as a filepath when we don’t have a file. However, haskell-lsp doesn’t support that in uriToFilePath and given that it is not a valid filepath it does not make sense to upstream a fix. So we have our own wrapper here that supports empty filepaths.
readSrcSpan :: ReadS RealSrcSpan Source #
Parser for the GHC output format
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 #