jupyter-0.9.0: A library for creating and using Jupyter kernels.

Copyright(c) Andrew Gibiansky, 2016
LicenseMIT
Maintainerandrew.gibiansky@gmail.com
Stabilitystable
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Jupyter.Client

Contents

Description

This module provides an easy API for writing Jupyter clients. Jupyter clients (also commonly called frontends) are programs which communicate with Jupyter kernels, possibly starting them and then sending them requests over the ZeroMQ-based messaging protocol. Examples of Jupyter clients include the Jupyter console, the QtConsole, and the http://jupyter.org/.

Communication with clients is done in the Client monad, which is a thin wrapper over IO which maintains a small bit of required state to identify a running kernel and the sockets on which to communicate with it. The initial state and connection information is supplied when you use runClient, which requires connection information and the Client action to run.

The runClient function also requires a set of ClientHandlers, which are callbacks that get called when the kernel sends any sort of message to the client (KernelRequests, KernelOutputs, and Comms).

These functions can be used quite succinctly to communicate with external clients. For example, the following code connects to an installed Python kernel (the ipykernel package must be installed):

import Control.Monad.IO.Class (MonadIO(liftIO))
import System.Process (spawnProcess)

import Jupyter.Client
import Jupyter.Messages

main :: IO ()
main = 
  runClient Nothing Nothing handlers $ profile -> do
    -- The profile provided is a generated KernelProfile
    -- that the client will connect to. Start an IPython kernel
    -- that listens on that profile.
    liftIO $ do
      writeProfile profile "profile.json"
      spawnProcess "python" ["-m", "ipykernel", "-f", "profile.json"]

    -- Find out info about the kernel by sending it a kernel info request.
    connection <- connectKernel
    reply <- sendClientRequest connection KernelInfoRequest
    liftIO $ print reply

handlers :: ClientHandlers
handlers = ClientHandlers {
    -- Do nothing on comm messages
    commHandler = defaultClientCommHandler,

    -- Return a fake stdin string if asked for stdin
    kernelRequestHandler = _ req ->
        case req of
          InputRequest{} -> return $ InputReply "Fake Stdin",

    -- Do nothing on kernel outputs
    kernelOutputHandler = _ _ -> return ()
  }

A more detailed example is provided in the examples/client-kernel-info directory, and more information about the client and kernel interfaces can be found on the jupyter README.

Synopsis

Communicating with Clients

data Client a Source

A client action, representing a computation in which communication happens with a Jupyter client.

Use sendClientRequest and sendClientComm to construct Client values, the Monad interface to manipulate them, and runClient to supply all needed connection info and run the action.

runClient Source

Arguments

:: Maybe KernelProfile

Optionally, a KernelProfile to connect to. If no KernelProfile is provided, one is generated on the fly. However, if a KernelProfile is provided, and connecting to the specified ports fails, an exception is thrown.

-> Maybe Username

Optionally, a username to use when sending messages to the client. If no username is provided, a default one is used.

-> ClientHandlers

A record containing handlers for messages the kernel sends to the client.

-> (KernelProfile -> Client a)

Provided with the KernelProfile that was being used (either a freshly generated one or the one passed in by the user), generate a Client action. This action is then run, handling all the ZeroMQ communication in the background.

-> IO a 

Run a Client action in IO.

This function sets up ZeroMQ sockets on which it can connect to a kernel; if no KernelProfile is provided, it generates a fresh KernelProfile which contains information about the ports and transport protocols which it expects the kernel to connect with. It guarantees that the ports it chooses are open – that is, that no kernel is currently connected to those ports.

The generated KernelProfile is passed to the user-provided KernelProfile -> Client a callback, which may use functions such as sendClientRequest to communicate with the kernel. If the kernel sends messages to the client, they are handled with the callbacks provided in the ClientHandlers record.

Most clients follow a simple pattern:

  1. Invoke runClient, passing Nothing for the KernelProfile. This allows runClient to set up and choose its own ports.
  2. Write the connection file containing the chosen ports to a JSON file using writeProfile. Make sure to write it to a temporary directory, to avoid clobbering user directories with connection files.
  3. If you do not know the command used to invoke the target kernel, use findKernel to find the Kernelspec for the kernel you wish to launch. Then, use the kernelspecCommand field to generate the kernel command invocation.
  4. Launch the kernel using spawnProcess or a similar function, providing the connection file you wrote out as a command-line parameter.
  5. Wait for the kernel to connect to the client using connectKernel.
  6. Use the output KernelConnection from connectClient to communicate with the kernel using sendClientRequest (and maybe sendClientComm).

A full example is provided in the examples/client-kernel-info directory.

If any of the client handlers in the provided ClientHandlers throw an exception, the client is gracefully shutdown and the exception is reraised on the main runClient thread.

connectKernel :: Client KernelConnection Source

Wait for a kernel to connect to this client, and return a KernelConnection once the kernel has connected.

This KernelConnection must be passed to sendClientRequest and sendClientComm to communicate with the connected kernel.

sendClientRequest Source

Arguments

:: KernelConnection

A kernel connection, produced by connectKernel.

-> ClientRequest

The request to send to the connected kernel.

-> Client KernelReply 

Send a ClientRequest to the kernel. Wait for the kernel to reply with a KernelReply, blocking until it does so.

sendClientComm Source

Arguments

:: KernelConnection

A kernel connection, produced by connectKernel.

-> Comm

The Comm message to send.

-> Client () 

Send a Comm message to the kernel. The kernel is not obligated to respond in any way, so do not block, but return immediately upon sending the message.

data ClientHandlers Source

A set of callbacks for the client. These callbacks get called when the client receives any message from the kernel.

One callback exists per message type that the clients can receive. Each callbacks can also send Comm messages to kernel, and receive a function of type Comm -> IO () that sends a single Comm message to the kernel.

Constructors

ClientHandlers 

Fields

kernelRequestHandler :: (Comm -> IO ()) -> KernelRequest -> IO ClientReply

A callback for handling KernelRequests. A KernelRequest is sent from a kernel to just one client, and that client must generate a ClientReply with the corresponding constructor.

The handler is passed a function Comm -> IO () which may be used to send Comm messages back to the client that sent the message.

commHandler :: (Comm -> IO ()) -> Comm -> IO ()

A callback for handling Comm messages from the kernel. Comm messages may be handled in any way, and defaultClientCommHandler may be used as a Comm handler that simply does nothing.

The handler is passed a function Comm -> IO () which may be used to send Comm messages back to the client that sent the message.

kernelOutputHandler :: (Comm -> IO ()) -> KernelOutput -> IO ()

A callback for handling KernelOutputs. KernelOutput messages are the primary way for a kernel to publish outputs, and are sent to all connected frontends.

The handler is passed a function Comm -> IO () which may be used to send Comm messages back to the client that sent the message.

defaultClientCommHandler :: (Comm -> IO ()) -> Comm -> IO () Source

A default client Comm handlers, which, upon receiving a Comm message, does nothing.

For use with the ClientHandlers commHandler field.

data KernelConnection Source

A connection to a kernel from a client.

A connection can be obtained with connectKernel, and must be provided to sendClientRequest and sendClientComm to communicate with a kernel.

Writing Connection Files

writeProfile :: KernelProfile -> FilePath -> IO () Source

Write a KernelProfile to a JSON file, which can be passed as the connection file to a starting kernel.

Locating kernels

data Kernelspec Source

A kernelspec is a description of a kernel which tells the Jupyter command-line application how to install the kernel and tells the frontends how to invoke the kernel (command line flags, environment, etc).

More documentation about kernelspecs is located in the official documentation.

Constructors

Kernelspec 

Fields

kernelspecDisplayName :: Text

Name for the kernel to be shown in frontends, e.g. "Haskell".

kernelspecLanguage :: Text

Language name for the kernel, used to refer to this kernel (in command-line arguments, URLs, etc), e.g. "haskell".

kernelspecCommand :: FilePath -> FilePath -> [String]

How to invoke the kernel. Given the path to the currently running executable and connection file, this function should return the full command to invoke the kernel. For example:

\exe connectionFile -> [exe, "kernel", "--debug", "--connection-file", connectionFile]
kernelspecJsFile :: Maybe FilePath

(optional) path to a Javascript file (kernel.js) to provide to the Jupyter notebook. This file is loaded upon notebook startup.

kernelspecLogoFile :: Maybe FilePath

(optional) path to a 64x64 PNG file to display as the kernel logo in the notebook.

kernelspecEnv :: Map Text Text

Additional environment variables to set when invoking the kernel. If no additional environment variables are required, pass fromList [] or mempty.

findKernel :: Text -> IO (Maybe Kernelspec) Source

Find the kernelspec for a kernel with a given language name.

If no such kernel exists, then Nothing is returned. If an error occurs while searching for Jupyter kernels, a JupyterKernelspecException is thrown.

findKernels :: IO [Kernelspec] Source

Find all kernelspecs that the Jupyter installation is aware of, using the jupyter kernelspec list command.

If an error occurs while searching for Jupyter kernels, a JupyterKernelspecException is thrown.