Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- type Cursor = (UInt, UInt)
- cursorPosition :: Cursor -> Position
- requireDiagnostic :: (Foldable f, Show (f Diagnostic), HasCallStack) => f Diagnostic -> (DiagnosticSeverity, Cursor, Text, Maybe DiagnosticTag) -> Maybe ErrorMsg
- diagnostic :: Session (TNotificationMessage Method_TextDocumentPublishDiagnostics)
- expectDiagnostics :: HasCallStack => [(FilePath, [(DiagnosticSeverity, Cursor, Text)])] -> Session ()
- expectDiagnosticsWithTags :: HasCallStack => [(String, [(DiagnosticSeverity, Cursor, Text, Maybe DiagnosticTag)])] -> Session ()
- expectNoMoreDiagnostics :: HasCallStack => Seconds -> Session ()
- expectMessages :: SMethod m -> Seconds -> (TServerMessage m -> Session ()) -> Session ()
- expectCurrentDiagnostics :: HasCallStack => TextDocumentIdentifier -> [(DiagnosticSeverity, Cursor, Text)] -> Session ()
- checkDiagnosticsForDoc :: HasCallStack => TextDocumentIdentifier -> [(DiagnosticSeverity, Cursor, Text)] -> [Diagnostic] -> Session ()
- canonicalizeUri :: Uri -> IO Uri
- standardizeQuotes :: Text -> Text
- flushMessages :: Session ()
- waitForAction :: String -> TextDocumentIdentifier -> Session WaitForIdeRuleResult
- getInterfaceFilesDir :: TextDocumentIdentifier -> Session FilePath
- garbageCollectDirtyKeys :: CheckParents -> Int -> Session [String]
- getFilesOfInterest :: Session [FilePath]
- waitForTypecheck :: TextDocumentIdentifier -> Session Bool
- waitForBuildQueue :: Session ()
- getStoredKeys :: Session [Text]
- waitForCustomMessage :: Text -> (Value -> Maybe res) -> Session res
- waitForGC :: Session [Text]
- configureCheckProject :: Bool -> Session ()
- isReferenceReady :: FilePath -> Session ()
- referenceReady :: (FilePath -> Bool) -> Session FilePath
Documentation
cursorPosition :: Cursor -> Position Source #
requireDiagnostic :: (Foldable f, Show (f Diagnostic), HasCallStack) => f Diagnostic -> (DiagnosticSeverity, Cursor, Text, Maybe DiagnosticTag) -> Maybe ErrorMsg Source #
diagnostic :: Session (TNotificationMessage Method_TextDocumentPublishDiagnostics) Source #
expectDiagnostics :: HasCallStack => [(FilePath, [(DiagnosticSeverity, Cursor, Text)])] -> Session () Source #
It is not possible to use 'expectDiagnostics []' to assert the absence of diagnostics, only that existing diagnostics have been cleared.
Rather than trying to assert the absence of diagnostics, introduce an expected diagnostic (e.g. a redundant import) and assert the singleton diagnostic.
expectDiagnosticsWithTags :: HasCallStack => [(String, [(DiagnosticSeverity, Cursor, Text, Maybe DiagnosticTag)])] -> Session () Source #
expectNoMoreDiagnostics :: HasCallStack => Seconds -> Session () Source #
wait for timeout
seconds and report an assertion failure
if any diagnostic messages arrive in that period
expectCurrentDiagnostics :: HasCallStack => TextDocumentIdentifier -> [(DiagnosticSeverity, Cursor, Text)] -> Session () Source #
checkDiagnosticsForDoc :: HasCallStack => TextDocumentIdentifier -> [(DiagnosticSeverity, Cursor, Text)] -> [Diagnostic] -> Session () Source #
standardizeQuotes :: Text -> Text Source #
flushMessages :: Session () Source #
garbageCollectDirtyKeys :: CheckParents -> Int -> Session [String] Source #
waitForBuildQueue :: Session () Source #
getStoredKeys :: Session [Text] Source #
configureCheckProject :: Bool -> Session () Source #
isReferenceReady :: FilePath -> Session () Source #
Pattern match a message from ghcide indicating that a file has been indexed