ribosome-test-0.9.9.9: Test tools for Ribosome
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ribosome.Test.Embed

Synopsis

Embedded Neovim testing

The function testPluginEmbed starts an embedded Neovim subprocess and a Ribosome main loop, then executes the supplied Sem.

This can be interpreted into a Hedgehog TestT by using the functions runEmbedTest and runTest.

The functions testPluginConf and testPlugin run a full Ribosome plugin with RPC handlers and extra effects in addition to the above. This can be used to test calling RPC handlers from Neovim, which usually shouldn't be necessary but may be helpful for some edge cases.

The functions testEmbedConf and testEmbed run tests with extra effects, but no handlers. This is the most advisable way to test plugins, running handlers directly as Haskell functions instead of routing them through Neovim, in particular for those that don't have any parameters.

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.

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.

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.

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.

testEmbedDebug_ :: HasCallStack => Sem EmbedStack () -> UnitTest Source #

Run a plugin test without extra effects and RPC handlers at the Debug log level.

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.