Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- testPlugin :: forall r. HasCallStack => HigherOrder r EmbedHandlerStack => InterpretersFor r EmbedHandlerStack -> [RpcHandler (r ++ EmbedHandlerStack)] -> Sem (EmbedStackWith r) () -> UnitTest
- testEmbed :: forall r. HasCallStack => HigherOrder r EmbedHandlerStack => InterpretersFor r EmbedHandlerStack -> Sem (EmbedStackWith r) () -> UnitTest
- testPluginEmbed :: Members (HostDeps er) r => Members BuiltinHandlersDeps r => Members [Settings !! SettingError, Error TestError] r => InterpretersFor TestEffects r
- runEmbedTest :: HasCallStack => TestConfig -> Sem EmbedHandlerStack () -> UnitTest
- runTest :: HasCallStack => Sem EmbedHandlerStack () -> UnitTest
- testPluginConf :: forall r. HasCallStack => HigherOrder r EmbedHandlerStack => TestConfig -> InterpretersFor r EmbedHandlerStack -> [RpcHandler (r ++ EmbedHandlerStack)] -> Sem (EmbedStackWith r) () -> UnitTest
- testPlugin_ :: HasCallStack => [RpcHandler EmbedHandlerStack] -> Sem EmbedStack () -> UnitTest
- testEmbedConf :: forall r. HasCallStack => HigherOrder r EmbedHandlerStack => TestConfig -> InterpretersFor r EmbedHandlerStack -> Sem (EmbedStackWith r) () -> UnitTest
- testEmbed_ :: HasCallStack => Sem EmbedStack () -> UnitTest
- testEmbedLevel :: forall r. HasCallStack => HigherOrder r EmbedHandlerStack => Severity -> InterpretersFor r EmbedHandlerStack -> Sem (EmbedStackWith r) () -> UnitTest
- testEmbedLevel_ :: HasCallStack => Severity -> Sem EmbedStack () -> UnitTest
- testEmbedDebug :: forall r. HasCallStack => HigherOrder r EmbedHandlerStack => InterpretersFor r EmbedHandlerStack -> Sem (EmbedStackWith r) () -> UnitTest
- testEmbedDebug_ :: HasCallStack => Sem EmbedStack () -> UnitTest
- testEmbedTrace :: forall r. HasCallStack => HigherOrder r EmbedHandlerStack => InterpretersFor r EmbedHandlerStack -> Sem (EmbedStackWith r) () -> UnitTest
- testEmbedTrace_ :: HasCallStack => Sem EmbedStack () -> UnitTest
- runTestConf :: HasCallStack => TestConfig -> Sem (Reader PluginName ': TestStack) () -> UnitTest
- runTestLogConf :: Members [Error BootError, Resource, Race, Async, Embed IO] r => TestConfig -> InterpretersFor (Reader PluginName ': TestConfStack) r
- type EmbedStackWith r = TestEffects ++ (r ++ EmbedHandlerStack)
- type EmbedStack = EmbedStackWith '[]
- type EmbedHandlerStack = HandlerEffects ++ (Reader PluginName ': TestStack)
- type TestEffects = [Stop Report, Stop RpcError, Scratch, Settings, Rpc]
- data TestConfig = TestConfig Bool (PluginConfig ())
- data TmuxTestConfig = TmuxTestConfig TestConfig TmuxTestConfig
- module Ribosome.Test.Error
- resumeReportFail :: forall (eff :: (Type -> Type) -> Type -> Type) err (r :: EffectRow). (Members '[Fail :: (Type -> Type) -> Type -> Type, eff !! err] r, Reportable err) => InterpreterFor eff r
- stopReportToFail :: forall e (r :: EffectRow). (Member (Fail :: (Type -> Type) -> Type -> Type) r, Reportable e) => InterpreterFor (Stop e) r
- windowCountIs :: Monad m => Members [Rpc, Hedgehog m] r => Int -> Sem r ()
- cursorIs :: Monad m => Members [Rpc, Hedgehog m] r => Int -> Int -> Window -> Sem r ()
- currentCursorIs :: Monad m => Members [Rpc, Hedgehog m] r => Int -> Int -> Sem r ()
- awaitScreenshot :: HasCallStack => Members [NativeTmux, NativeCommandCodecE, Stop CodecError] r => Members [Hedgehog IO, Test, Error TestError, Error Failure, ChronosTime, StderrLog, Race, Embed IO] r => Bool -> Text -> Int -> Sem r ()
- assertWait :: Monad m => HasCallStack => Members [Hedgehog m, Time t d, Race, Error Failure, Embed IO] r => Sem r a -> (a -> Sem r b) -> Sem r b
- assertWaitFor :: Monad m => HasCallStack => Members [Hedgehog m, Time t d, Race, Error Failure, Embed IO] r => TimeUnit t1 => TimeUnit t2 => t1 -> t2 -> Sem r a -> (a -> Sem r b) -> Sem r b
Introduction
This is the test library for the Ribosome Neoivm plugin framework.
Three different test environments are available:
- Ribosome.Test.Embed runs Neovim as a subprocess and connects over stdio
- Ribosome.Test.EmbedTmux is like Ribosome.Test.Embed, but provides a tmux server
- Ribosome.Test.SocketTmux runs Neovim in a window in a fresh tmux server, either headless in a pseudo terminal
or in an
xterm
instance
This module reexports Ribosome.Test.Embed.
Embedded testing
Running a test against an embedded Neovim process is the simplest approach that is suited for unit testing plugin logic where the integration with Neovim startup isn't important.
Handlers can be registered in Neovim and triggered via RPC API functions like nvimCallFunction
and nvimCommand
.
Most of the time this is only interesting if a handler has complex parameters and you want to test that they are
decoded correctly, or that the handler is triggered properly by an autocmd.
In more basic cases, where only the interaction with Neovim from within the handler is relevant, it can simply be run
directly.
import Polysemy.Test import Ribosome import Ribosome.Api import Ribosome.Test store :: Member (Rpc !! RpcError) r => Args -> Handler r () store (Args msg) = ignoreRpcError do nvimSetVar "message" msg test_direct :: UnitTest test_direct = testEmbed_ do store "test directly" assertEq "test directly" =<< nvimGetVar @Text "message" test_rpc :: UnitTest test_rpc = testPlugin_ [rpcCommand "Store" Sync store] do nvimCommand "Store test RPC" assertEq "test RPC" =<< nvimGetVar @Text "message"
See Ribosome.Test.Embed for more options.
tmux testing
It is possible to run a standalone Neovim instance to test against. This is useful to observe the UI's behaviour for debugging purposes, but might also be desired to test a feature in the full environment that is used in production.
Ribosome provides a testing mode that starts a terminal with a tmux server, in which Neovim is executed as a regular shell process. Variants of this that run tmux in a pseudo terminal that is not rendered, or simply run a tmux server for use in an embedded test, are also available.
In the terminal case, the test connects the plugin over a socket.
It is possible to take "screenshots" (capturing the tmux pane running Neovim) that are automatically stored in the
fixtures
directory of the test suite and compared to previous recordings on subsequent runs, as in this example
that runs tmux in a terminal and tests some syntax rules:
import Polysemy.Test import Ribosome.Api import Ribosome.Syntax import Ribosome.Test import Ribosome.Test.SocketTmux syntax :: Syntax syntax = Syntax [syntaxMatch "TestColons" "::"] [ syntaxHighlight "TestColons" [("cterm", "reverse"), ("ctermfg", "1"), ("gui", "reverse"), ("guifg", "#dc322f")] ] [] test_syntax :: UnitTest test_syntax = testSocketTmuxGui do setCurrentBufferContent ["function :: String -> Int", "function _ = 5"] _ <- executeSyntax syntax awaitScreenshot False "syntax" 0 See [Ribosome.Test.SocketTmux]("Ribosome.Test.SocketTmux") and [Ribosome.Test.EmbedTmux]("Ribosome.Test.EmbedTmux") for more options.
Embedded test API
testPlugin :: forall r. HasCallStack => HigherOrder r EmbedHandlerStack => InterpretersFor r EmbedHandlerStack -> [RpcHandler (r ++ EmbedHandlerStack)] -> Sem (EmbedStackWith r) () -> UnitTest Source #
Run a full plugin test, using extra effects and RPC handlers.
testEmbed :: forall r. HasCallStack => HigherOrder r EmbedHandlerStack => InterpretersFor r EmbedHandlerStack -> Sem (EmbedStackWith r) () -> UnitTest Source #
Run a plugin test with extra effects but no RPC handlers.
testPluginEmbed :: Members (HostDeps er) r => Members BuiltinHandlersDeps r => Members [Settings !! SettingError, Error TestError] r => InterpretersFor TestEffects r Source #
Run the test plugin effects, TestEffects
, and start an embedded Neovim subprocess.
runEmbedTest :: HasCallStack => TestConfig -> Sem EmbedHandlerStack () -> UnitTest Source #
Run the plugin stack and the test stack, using the supplied config.
runTest :: HasCallStack => Sem EmbedHandlerStack () -> UnitTest Source #
Run the plugin stack and the test stack, using the default config.
testPluginConf :: forall r. HasCallStack => HigherOrder r EmbedHandlerStack => TestConfig -> InterpretersFor r EmbedHandlerStack -> [RpcHandler (r ++ EmbedHandlerStack)] -> Sem (EmbedStackWith r) () -> UnitTest Source #
Run a full plugin test, using extra effects and RPC handlers.
testPlugin_ :: HasCallStack => [RpcHandler EmbedHandlerStack] -> Sem EmbedStack () -> UnitTest Source #
Run a plugin test with RPC handlers.
testEmbedConf :: forall r. HasCallStack => HigherOrder r EmbedHandlerStack => TestConfig -> InterpretersFor r EmbedHandlerStack -> Sem (EmbedStackWith r) () -> UnitTest Source #
Run a plugin test with extra effects but no RPC handlers.
testEmbed_ :: HasCallStack => Sem EmbedStack () -> UnitTest Source #
Run a plugin test without extra effects and RPC handlers.
testEmbedLevel :: forall r. HasCallStack => HigherOrder r EmbedHandlerStack => Severity -> InterpretersFor r EmbedHandlerStack -> Sem (EmbedStackWith r) () -> UnitTest Source #
Run a plugin test with extra effects but no RPC handlers.
Takes a log level, for which the default is to only print critical errors.
testEmbedLevel_ :: HasCallStack => Severity -> Sem EmbedStack () -> UnitTest Source #
Run a plugin test without extra effects and RPC handlers.
Takes a log level, for which the default is to only print critical errors.
testEmbedDebug :: forall r. HasCallStack => HigherOrder r EmbedHandlerStack => InterpretersFor r EmbedHandlerStack -> Sem (EmbedStackWith r) () -> UnitTest Source #
Run a plugin test with extra effects but no RPC handlers at the Debug
log level.
testEmbedDebug_ :: HasCallStack => Sem EmbedStack () -> UnitTest Source #
Run a plugin test without extra effects and RPC handlers at the Debug
log level.
testEmbedTrace :: forall r. HasCallStack => HigherOrder r EmbedHandlerStack => InterpretersFor r EmbedHandlerStack -> Sem (EmbedStackWith r) () -> UnitTest Source #
Run a plugin test with extra effects but no RPC handlers at the Trace
log level for debugging RPC traffic.
testEmbedTrace_ :: HasCallStack => Sem EmbedStack () -> UnitTest Source #
Run a plugin test without extra effects and RPC handlers at the Trace
log level for debugging RPC traffic.
runTestConf :: HasCallStack => TestConfig -> Sem (Reader PluginName ': TestStack) () -> UnitTest Source #
Run the basic test effects as a Hedgehog test.
runTestLogConf :: Members [Error BootError, Resource, Race, Async, Embed IO] r => TestConfig -> InterpretersFor (Reader PluginName ': TestConfStack) r Source #
Interpret the basic test effects without IO
related effects.
type EmbedStackWith r = TestEffects ++ (r ++ EmbedHandlerStack) Source #
The full test stack with additional effects.
type EmbedStack = EmbedStackWith '[] Source #
The full test stack with no additional effects.
type EmbedHandlerStack = HandlerEffects ++ (Reader PluginName ': TestStack) Source #
The full test stack below test effects and extra effects.
type TestEffects = [Stop Report, Stop RpcError, Scratch, Settings, Rpc] Source #
The extra effects that tests are expected to use, related to errors.
The plugin effects Scratch
, Settings
and Rpc
are allowed without Resume
, causing tests to terminate
immediately if one of these effects is used and throws an error.
Additionally, the two core errors, LogReport
and RpcError
are executed directly via Stop
.
data TestConfig Source #
TestConfig Bool (PluginConfig ()) |
Instances
data TmuxTestConfig Source #
Instances
Error handling
module Ribosome.Test.Error
resumeReportFail :: forall (eff :: (Type -> Type) -> Type -> Type) err (r :: EffectRow). (Members '[Fail :: (Type -> Type) -> Type -> Type, eff !! err] r, Reportable err) => InterpreterFor eff r #
Resume an effect with an error that's an instance of Reportable
by reinterpreting to Fail
, for use in tests.
stopReportToFail :: forall e (r :: EffectRow). (Member (Fail :: (Type -> Type) -> Type -> Type) r, Reportable e) => InterpreterFor (Stop e) r #
Convert an error that's an instance of Reportable
to Fail
, for use in tests.
Assertions for Neovim UI elements
windowCountIs :: Monad m => Members [Rpc, Hedgehog m] r => Int -> Sem r () Source #
Assert the number of windows.
cursorIs :: Monad m => Members [Rpc, Hedgehog m] r => Int -> Int -> Window -> Sem r () Source #
Assert the cursor position in a window.
currentCursorIs :: Monad m => Members [Rpc, Hedgehog m] r => Int -> Int -> Sem r () Source #
Assert the cursor position in the current window.
awaitScreenshot :: HasCallStack => Members [NativeTmux, NativeCommandCodecE, Stop CodecError] r => Members [Hedgehog IO, Test, Error TestError, Error Failure, ChronosTime, StderrLog, Race, Embed IO] r => Bool -> Text -> Int -> Sem r () Source #