ipython-kernel-0.11.0.0: A library for creating kernels for IPython frontends
Safe HaskellSafe-Inferred
LanguageHaskell2010

IHaskell.IPython.Types

Description

This module contains all types used to create an IPython language kernel.

Synopsis

IPython kernel profile

data Profile Source #

A kernel profile, specifying how the kernel communicates.

Constructors

Profile 

Fields

data Transport Source #

The transport mechanism used to communicate with the IPython frontend.

Constructors

TCP

Default transport mechanism via TCP.

type Port = Int Source #

A TCP port.

type IP = String Source #

An IP address.

IPython kernelspecs

data KernelSpec Source #

Constructors

KernelSpec 

Fields

  • kernelDisplayName :: String

    Name shown to users to describe this kernel (e.g. Haskell)

  • kernelLanguage :: String

    Name for the kernel; unique kernel identifier (e.g. "haskell")

  • kernelCommand :: [String]

    Command to run to start the kernel. One of the strings maybe "{connection_file}", which will be replaced by the path to a kernel profile file (see Profile) when the command is run.

Instances

Instances details
ToJSON KernelSpec Source # 
Instance details

Defined in IHaskell.IPython.Types

Show KernelSpec Source # 
Instance details

Defined in IHaskell.IPython.Types

Eq KernelSpec Source # 
Instance details

Defined in IHaskell.IPython.Types

IPython messaging protocol

data Message Source #

A message used to communicate with the IPython frontend.

See https://jupyter-client.readthedocs.io/en/stable/messaging.html

Constructors

KernelInfoRequest

A request from a frontend for information about the kernel.

Fields

KernelInfoReply

A response to a KernelInfoRequest.

Fields

CommInfoRequest

A request from a frontend for information about the comms.

Fields

CommInfoReply

A response to a CommInfoRequest.

Fields

ExecuteInput

A request from a frontend to execute some code.

Fields

ExecuteRequest

A request from a frontend to execute some code.

Fields

ExecuteReply

A reply to an execute request.

Fields

ExecuteResult

A reply to an execute request.

Fields

ExecuteError

An error reply to an execute request

Fields

PublishStatus 

Fields

PublishStream 

Fields

PublishDisplayData 

Fields

PublishUpdateDisplayData 

Fields

PublishOutput 

Fields

PublishInput 

Fields

Input 

Fields

Output 

Fields

IsCompleteRequest 

Fields

IsCompleteReply 

Fields

CompleteRequest 

Fields

CompleteReply 

Fields

InspectRequest 

Fields

  • header :: MessageHeader

    Unused field retained for backwards compatibility.

  • inspectCode :: Text

    The code context in which introspection is requested

  • inspectCursorPos :: Int

    Position of the cursor in unicode characters. json field cursor_pos

  • detailLevel :: Int

    Level of detail desired (defaults to 0). 0 is equivalent to foo?, 1 is equivalent to foo??.

InspectReply 

Fields

ShutdownRequest 

Fields

ShutdownReply 

Fields

ClearOutput 

Fields

  • header :: MessageHeader

    Unused field retained for backwards compatibility.

  • wait :: Bool

    Whether to wait to redraw until there is more output.

RequestInput 

Fields

InputReply 

Fields

CommOpen 

Fields

CommData 

Fields

CommClose 

Fields

HistoryRequest 

Fields

HistoryReply 

Fields

SendNothing 

Instances

Instances details
ToJSON Message Source # 
Instance details

Defined in IHaskell.IPython.Types

Show Message Source # 
Instance details

Defined in IHaskell.IPython.Types

data MessageHeader Source #

A message header with some metadata.

Constructors

MessageHeader 

Fields

type Username = Text Source #

A username for the source of a message.

newtype Transient Source #

Constructors

Transient 

Instances

Instances details
ToJSON Transient Source # 
Instance details

Defined in IHaskell.IPython.Types

Show Transient Source # 
Instance details

Defined in IHaskell.IPython.Types

Eq Transient Source # 
Instance details

Defined in IHaskell.IPython.Types

data MessageType Source #

The type of a message, corresponding to IPython message types.

data CodeReview Source #

Constructors

CodeComplete 
CodeIncomplete String

String to be used to indent next line of input

CodeInvalid 
CodeUnknown 

Instances

Instances details
Show CodeReview Source # 
Instance details

Defined in IHaskell.IPython.Types

type Width = Int Source #

Possible MIME types for the display data.

data StreamType Source #

Input and output streams.

Constructors

Stdin 
Stdout 
Stderr 

Instances

Instances details
FromJSON StreamType Source # 
Instance details

Defined in IHaskell.IPython.Types

ToJSON StreamType Source #

Print a stream as "stdin" or "stdout" strings.

Instance details

Defined in IHaskell.IPython.Types

Show StreamType Source # 
Instance details

Defined in IHaskell.IPython.Types

data ExecutionState Source #

The execution state of the kernel.

Constructors

Busy 
Idle 
Starting 

Instances

Instances details
FromJSON ExecutionState Source # 
Instance details

Defined in IHaskell.IPython.Types

ToJSON ExecutionState Source #

Print an execution state as "busy", "idle", or "starting".

Instance details

Defined in IHaskell.IPython.Types

Show ExecutionState Source # 
Instance details

Defined in IHaskell.IPython.Types

data ExecuteReplyStatus Source #

Possible statuses in the execution reply messages.

Constructors

Ok 
Err 
Abort 

data HistoryAccessType Source #

Ways in which the frontend can request history. TODO: Implement fields as described in messaging spec.

newtype Metadata Source #

A metadata dictionary.

Constructors

Metadata Object 

replyType :: MessageType -> Maybe MessageType Source #

Get the reply message type for a request message type.

IPython display data message

data DisplayData Source #

Data for display: a string with associated MIME type.

Constructors

DisplayData MimeType Text 

Instances

Instances details
Generic DisplayData Source # 
Instance details

Defined in IHaskell.IPython.Types

Associated Types

type Rep DisplayData :: Type -> Type #

Show DisplayData Source # 
Instance details

Defined in IHaskell.IPython.Types

Binary DisplayData Source # 
Instance details

Defined in IHaskell.IPython.Types

Eq DisplayData Source # 
Instance details

Defined in IHaskell.IPython.Types

type Rep DisplayData Source # 
Instance details

Defined in IHaskell.IPython.Types

type Rep DisplayData = D1 ('MetaData "DisplayData" "IHaskell.IPython.Types" "ipython-kernel-0.11.0.0-GlmZ6swXw3x3fGdtSywazY" 'False) (C1 ('MetaCons "DisplayData" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MimeType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data MimeType Source #

Instances

Instances details
Generic MimeType Source # 
Instance details

Defined in IHaskell.IPython.Types

Associated Types

type Rep MimeType :: Type -> Type #

Methods

from :: MimeType -> Rep MimeType x #

to :: Rep MimeType x -> MimeType #

Read MimeType Source # 
Instance details

Defined in IHaskell.IPython.Types

Show MimeType Source # 
Instance details

Defined in IHaskell.IPython.Types

Binary MimeType Source # 
Instance details

Defined in IHaskell.IPython.Types

Methods

put :: MimeType -> Put #

get :: Get MimeType #

putList :: [MimeType] -> Put #

Eq MimeType Source # 
Instance details

Defined in IHaskell.IPython.Types

type Rep MimeType Source # 
Instance details

Defined in IHaskell.IPython.Types

type Rep MimeType = D1 ('MetaData "MimeType" "IHaskell.IPython.Types" "ipython-kernel-0.11.0.0-GlmZ6swXw3x3fGdtSywazY" 'False) ((((C1 ('MetaCons "PlainText" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MimeHtml" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MimeBmp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Width) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Height)) :+: C1 ('MetaCons "MimePng" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Width) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Height)))) :+: ((C1 ('MetaCons "MimeJpg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Width) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Height)) :+: C1 ('MetaCons "MimeGif" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Width) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Height))) :+: (C1 ('MetaCons "MimeSvg" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MimeLatex" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "MimeMarkdown" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MimeJavascript" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MimeJson" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MimeVega" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MimeVegalite" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MimeVdom" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MimeWidget" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MimeCustom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))))

displayDataToJson :: DisplayData -> (Key, Value) Source #

Convert a MIME type and value into a JSON dictionary pair.