Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- codeActionResolveCaps :: ClientCapabilities
- codeActionNoResolveCaps :: ClientCapabilities
- codeActionSupportCaps :: ClientCapabilities
- expectCodeAction :: [Command |? CodeAction] -> [Text] -> IO ()
- ghcVersion :: GhcVersion
- data GhcVersion
- hostOS :: OS
- data OS
- matchesCurrentEnv :: EnvSpec -> Bool
- data EnvSpec
- = HostOS OS
- | GhcVer GhcVersion
- ignoreForGhcVersions :: [GhcVersion] -> String -> TestTree -> TestTree
- ignoreInEnv :: [EnvSpec] -> String -> TestTree -> TestTree
- onlyRunForGhcVersions :: [GhcVersion] -> String -> TestTree -> TestTree
- knownBrokenOnWindows :: String -> TestTree -> TestTree
- knownBrokenForGhcVersions :: [GhcVersion] -> String -> TestTree -> TestTree
- knownBrokenInEnv :: [EnvSpec] -> String -> TestTree -> TestTree
- knownBrokenInSpecificEnv :: [EnvSpec] -> String -> TestTree -> TestTree
- onlyWorkForGhcVersions :: (GhcVersion -> Bool) -> String -> TestTree -> TestTree
- fromAction :: (Command |? CodeAction) -> CodeAction
- fromCommand :: (Command |? CodeAction) -> Command
- dontExpectCodeAction :: [Command |? CodeAction] -> [Text] -> IO ()
- expectDiagnostic :: [Diagnostic] -> [Text] -> IO ()
- expectNoMoreDiagnostics :: Seconds -> TextDocumentIdentifier -> String -> Session ()
- failIfSessionTimeout :: IO a -> IO a
- getCompletionByLabel :: MonadIO m => Text -> [CompletionItem] -> m CompletionItem
- noLiteralCaps :: ClientCapabilities
- inspectCodeAction :: [Command |? CodeAction] -> [Text] -> IO CodeAction
- inspectCommand :: [Command |? CodeAction] -> [Text] -> IO Command
- inspectDiagnostic :: [Diagnostic] -> [Text] -> IO Diagnostic
- waitForDiagnosticsFrom :: TextDocumentIdentifier -> Session [Diagnostic]
- waitForDiagnosticsFromSource :: TextDocumentIdentifier -> String -> Session [Diagnostic]
- waitForDiagnosticsFromSourceWithTimeout :: Seconds -> TextDocumentIdentifier -> String -> Session [Diagnostic]
- withCurrentDirectoryInTmp :: FilePath -> IO a -> IO a
- withCurrentDirectoryInTmp' :: [FilePath] -> FilePath -> IO a -> IO a
- withCanonicalTempDir :: (FilePath -> IO a) -> IO a
- extractCursorPositions :: Text -> (Text, [PosPrefixInfo])
- mkParameterisedLabel :: PosPrefixInfo -> String
- trimming :: QuasiQuoter
Test Capabilities
expectCodeAction :: [Command |? CodeAction] -> [Text] -> IO () Source #
Environment specifications
data GhcVersion #
Instances
matchesCurrentEnv :: EnvSpec -> Bool Source #
ignoreForGhcVersions :: [GhcVersion] -> String -> TestTree -> TestTree Source #
ignoreInEnv :: [EnvSpec] -> String -> TestTree -> TestTree Source #
IgnoreTest if any of environmental spec mathces the current environment.
onlyRunForGhcVersions :: [GhcVersion] -> String -> TestTree -> TestTree Source #
Ignore the test if GHC does not match only work versions.
knownBrokenForGhcVersions :: [GhcVersion] -> String -> TestTree -> TestTree Source #
knownBrokenInEnv :: [EnvSpec] -> String -> TestTree -> TestTree Source #
Mark as broken if any of the environmental specs matches the current environment.
knownBrokenInSpecificEnv :: [EnvSpec] -> String -> TestTree -> TestTree Source #
Mark as broken if all environmental specs match the current environment.
onlyWorkForGhcVersions :: (GhcVersion -> Bool) -> String -> TestTree -> TestTree Source #
Mark as broken if GHC does not match only work versions.
Extract code actions
fromAction :: (Command |? CodeAction) -> CodeAction Source #
fromCommand :: (Command |? CodeAction) -> Command Source #
Session Assertion Helpers
dontExpectCodeAction :: [Command |? CodeAction] -> [Text] -> IO () Source #
expectDiagnostic :: [Diagnostic] -> [Text] -> IO () Source #
expectNoMoreDiagnostics :: Seconds -> TextDocumentIdentifier -> String -> Session () Source #
wait for timeout
seconds and report an assertion failure
if any diagnostic messages arrive in that period
failIfSessionTimeout :: IO a -> IO a Source #
getCompletionByLabel :: MonadIO m => Text -> [CompletionItem] -> m CompletionItem Source #
inspectCodeAction :: [Command |? CodeAction] -> [Text] -> IO CodeAction Source #
inspectCommand :: [Command |? CodeAction] -> [Text] -> IO Command Source #
inspectDiagnostic :: [Diagnostic] -> [Text] -> IO Diagnostic Source #
waitForDiagnosticsFromSourceWithTimeout :: Seconds -> TextDocumentIdentifier -> String -> Session [Diagnostic] Source #
wait for timeout
seconds and return diagnostics for the given document and
source.
If timeout is 0 it will wait until the session timeout
Temporary directories
withCurrentDirectoryInTmp :: FilePath -> IO a -> IO a Source #
Like withCurrentDirectory
, but will copy the directory over to the system
temporary directory first to avoid haskell-language-server's source tree from
interfering with the cradle.
Ignores directories containing build artefacts to avoid interference and provide reproducible test-behaviour.
withCurrentDirectoryInTmp' :: [FilePath] -> FilePath -> IO a -> IO a Source #
Like withCurrentDirectory
, but will copy the directory over to the system
temporary directory first to avoid haskell-language-server's source tree from
interfering with the cradle.
You may specify directories to ignore, but should be careful to maintain reproducibility.
Extract positions from input file.
extractCursorPositions :: Text -> (Text, [PosPrefixInfo]) Source #
Given a in-memory representation of a file, where a user can specify the
current cursor position using a ^
in the next line.
This function allows to generate multiple tests for a single input file, without the hassle of calculating by hand where there cursor is supposed to be.
Example (line number has been added for readability):
0: foo = 2 1: ^ 2: bar = 3: ^
This example input file contains two cursor positions (y, x), at
- (1, 1), and
- (3, 5).
extractCursorPositions
will search for ^
characters, and determine there are
two cursor positions in the text.
First, it will normalise the text to:
0: foo = 2 1: bar =
stripping away the ^
characters. Then, the actual cursor positions are:
- (0, 1) and
- (2, 5).
mkParameterisedLabel :: PosPrefixInfo -> String Source #
Pretty labelling for tests that use the parameterised test helpers.
trimming :: QuasiQuoter #
Trimmed quasiquoter variation.
Same as untrimming
, but also
removes the leading and trailing whitespace.