ihaskell-0.11.0.0: A Haskell backend kernel for the Jupyter project.
Safe HaskellSafe-Inferred
LanguageHaskell2010

IHaskell.Types

Description

 
Synopsis

Documentation

data Message #

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 
Instance details

Defined in IHaskell.IPython.Types

Show Message 
Instance details

Defined in IHaskell.IPython.Types

data MessageHeader #

A message header with some metadata.

Constructors

MessageHeader 

Fields

data MessageType #

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

dupHeader :: MessageHeader -> MessageType -> IO MessageHeader Source #

Duplicate a message header, giving it a new UUID and message type.

setVersion Source #

Arguments

:: MessageHeader

The header to modify

-> String

The version to set

-> MessageHeader

The modified header

Modifies a header and appends the version of the Widget Messaging Protocol as metadata

type Username = Text #

A username for the source of a message.

data Metadata #

A metadata dictionary.

replyType :: MessageType -> Maybe MessageType #

Get the reply message type for a request message type.

data ExecutionState #

The execution state of the kernel.

Constructors

Busy 
Idle 
Starting 

Instances

Instances details
FromJSON ExecutionState 
Instance details

Defined in IHaskell.IPython.Types

ToJSON ExecutionState

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

Instance details

Defined in IHaskell.IPython.Types

Show ExecutionState 
Instance details

Defined in IHaskell.IPython.Types

data StreamType #

Input and output streams.

Constructors

Stdin 
Stdout 
Stderr 

Instances

Instances details
FromJSON StreamType 
Instance details

Defined in IHaskell.IPython.Types

ToJSON StreamType

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

Instance details

Defined in IHaskell.IPython.Types

Show StreamType 
Instance details

Defined in IHaskell.IPython.Types

data MimeType #

Instances

Instances details
Generic MimeType 
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 
Instance details

Defined in IHaskell.IPython.Types

Show MimeType 
Instance details

Defined in IHaskell.IPython.Types

Binary MimeType 
Instance details

Defined in IHaskell.IPython.Types

Methods

put :: MimeType -> Put #

get :: Get MimeType #

putList :: [MimeType] -> Put #

Eq MimeType 
Instance details

Defined in IHaskell.IPython.Types

type Rep MimeType 
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))))))

data DisplayData #

Data for display: a string with associated MIME type.

Constructors

DisplayData MimeType Text 

Instances

Instances details
Generic DisplayData 
Instance details

Defined in IHaskell.IPython.Types

Associated Types

type Rep DisplayData :: Type -> Type #

Show DisplayData 
Instance details

Defined in IHaskell.IPython.Types

Binary DisplayData 
Instance details

Defined in IHaskell.IPython.Types

Eq DisplayData 
Instance details

Defined in IHaskell.IPython.Types

IHaskellDisplay DisplayData Source # 
Instance details

Defined in IHaskell.Types

type Rep DisplayData 
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 ErrorOccurred Source #

Whether or not an error occurred.

Constructors

Success 
Failure 

Instances

Instances details
Show ErrorOccurred Source # 
Instance details

Defined in IHaskell.Types

Eq ErrorOccurred Source # 
Instance details

Defined in IHaskell.Types

data EvaluationResult Source #

Output of evaluation.

A result can either be intermediate or final. Final result has Mimebundles (DisplayData) and Comm operations (WidgetMsg) on top of Display outputs.

Constructors

IntermediateResult !Display

An intermediate result which communicates what has been printed thus far.

FinalResult !Display ![DisplayData] ![WidgetMsg] 

Instances

Instances details
Show EvaluationResult Source # 
Instance details

Defined in IHaskell.Types

data ExecuteReplyStatus #

Possible statuses in the execution reply messages.

Constructors

Ok 
Err 
Abort 

data KernelState Source #

All state stored in the kernel between executions.

Constructors

KernelState 

Fields

Instances

Instances details
Show KernelState Source # 
Instance details

Defined in IHaskell.Types

data LintStatus Source #

Current HLint status.

Constructors

LintOn 
LintOff 

Instances

Instances details
Show LintStatus Source # 
Instance details

Defined in IHaskell.Types

Eq LintStatus Source # 
Instance details

Defined in IHaskell.Types

type Width = Int #

Possible MIME types for the display data.

type Height = Int #

data Display Source #

Wrapper for ipython-kernel's DisplayData which allows sending multiple results from the same expression.

Instances

Instances details
ToJSON Display Source # 
Instance details

Defined in IHaskell.Types

Monoid Display Source # 
Instance details

Defined in IHaskell.Types

Semigroup Display Source # 
Instance details

Defined in IHaskell.Types

Generic Display Source # 
Instance details

Defined in IHaskell.Types

Associated Types

type Rep Display :: Type -> Type #

Methods

from :: Display -> Rep Display x #

to :: Rep Display x -> Display #

Show Display Source # 
Instance details

Defined in IHaskell.Types

Binary Display Source # 
Instance details

Defined in IHaskell.Types

Methods

put :: Display -> Put #

get :: Get Display #

putList :: [Display] -> Put #

Eq Display Source # 
Instance details

Defined in IHaskell.Types

Methods

(==) :: Display -> Display -> Bool #

(/=) :: Display -> Display -> Bool #

IHaskellDisplay Display Source # 
Instance details

Defined in IHaskell.Types

type Rep Display Source # 
Instance details

Defined in IHaskell.Types

type Rep Display = D1 ('MetaData "Display" "IHaskell.Types" "ihaskell-0.11.0.0-HNOHBOiYuhqX9WBpIjYX5" 'False) (C1 ('MetaCons "Display" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DisplayData])) :+: C1 ('MetaCons "ManyDisplay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Display])))

data KernelOpt Source #

Kernel options to be set via `:set` and `:option`.

Constructors

KernelOpt 

Fields

class IHaskellDisplay a where Source #

A class for displayable Haskell types.

IHaskell's displaying of results behaves as if these two overlapping/undecidable instances also existed:

instance (Show a) => IHaskellDisplay a
instance Show a where shows _ = id

Methods

display :: a -> IO Display Source #

Instances

Instances details
IHaskellDisplay Display Source # 
Instance details

Defined in IHaskell.Types

IHaskellDisplay Widget Source # 
Instance details

Defined in IHaskell.Types

IHaskellDisplay DisplayData Source # 
Instance details

Defined in IHaskell.Types

IHaskellDisplay a => IHaskellDisplay (IO a) Source #

these instances cause the image, html etc. which look like:

Display
[Display]
IO [Display]
IO (IO Display)

be run the IO and get rendered (if the frontend allows it) in the pretty form.

Instance details

Defined in IHaskell.Types

Methods

display :: IO a -> IO Display Source #

IHaskellDisplay a => IHaskellDisplay [a] Source # 
Instance details

Defined in IHaskell.Types

Methods

display :: [a] -> IO Display Source #

class IHaskellDisplay a => IHaskellWidget a where Source #

Display as an interactive widget.

Minimal complete definition

getCommUUID

Methods

targetName :: a -> String Source #

Target name for this widget. The actual input parameter should be ignored. By default evaluate to "jupyter.widget", which is used by IPython for its backbone widgets.

targetModule :: a -> String Source #

Target module for this widget. Evaluates to an empty string by default.

getBufferPaths :: a -> [BufferPath] Source #

Buffer paths for this widget. Evaluates to an empty array by default.

getCommUUID :: a -> UUID Source #

Get the uuid for comm associated with this widget. The widget is responsible for storing the UUID during initialization.

open Source #

Arguments

:: a

Widget to open a comm port with.

-> (Value -> IO ())

A function for sending messages.

-> IO () 

Called when the comm is opened. Allows additional messages to be sent after comm open.

comm Source #

Arguments

:: a

Widget which is being communicated with.

-> Value

Data recieved from the frontend.

-> (Value -> IO ())

Way to respond to the message.

-> IO () 

Respond to a comm data message. Called when a message is recieved on the comm associated with the widget.

close Source #

Arguments

:: a

Widget to close comm port with.

-> Value

Data recieved from the frontend.

-> IO () 

Called when a comm_close is recieved from the frontend.

Instances

Instances details
IHaskellWidget Widget Source # 
Instance details

Defined in IHaskell.Types

data Widget Source #

Constructors

forall a.IHaskellWidget a => Widget a 

Instances

Instances details
Show Widget Source # 
Instance details

Defined in IHaskell.Types

Eq Widget Source # 
Instance details

Defined in IHaskell.Types

Methods

(==) :: Widget -> Widget -> Bool #

(/=) :: Widget -> Widget -> Bool #

IHaskellDisplay Widget Source # 
Instance details

Defined in IHaskell.Types

IHaskellWidget Widget Source # 
Instance details

Defined in IHaskell.Types

data WidgetMsg Source #

Send JSON objects with specific formats

Constructors

Open Widget Value

Cause the interpreter to open a new comm, and register the associated widget in the kernelState. Also sends an initial state Value with comm_open.

Update Widget Value

Cause the interpreter to send a comm_msg containing a state update for the widget. Can be used to send fragments of state for update. Also updates the value of widget stored in the kernelState

View Widget

Cause the interpreter to send a comm_msg containing a display command for the frontend.

Close Widget Value

Cause the interpreter to close the comm associated with the widget. Also sends data with comm_close.

Custom Widget Value

A [method .= custom, content = value] message

JSONValue Widget Value

A json object that is sent to the widget without modifications.

DispMsg Widget Display

A display_data message, sent as a [method .= custom] comm_msg

ClrOutput Bool

A clear_output message, sent as a clear_output message

Instances

Instances details
Show WidgetMsg Source # 
Instance details

Defined in IHaskell.Types

data KernelSpec #

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 
Instance details

Defined in IHaskell.IPython.Types

Show KernelSpec 
Instance details

Defined in IHaskell.IPython.Types

Eq KernelSpec 
Instance details

Defined in IHaskell.IPython.Types