Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
If you are interested in the IHaskell library for the purpose of augmenting the IHaskell notebook or writing your own display mechanisms and widgets, this module contains all functions you need.
In order to create a display mechanism for a particular data type, write a module named (for
example) IHaskell.Display.YourThing
in a package named ihaskell-yourThing
. (Note the
capitalization - it's important!) Then, in that module, add an instance of IHaskellDisplay
for
your data type. Similarly, to create a widget, add an instance of IHaskellWidget
.
An example of creating a display is provided in the demo notebook.
Synopsis
- class IHaskellDisplay a where
- data Display
- = Display [DisplayData]
- | ManyDisplay [Display]
- data DisplayData = DisplayData MimeType Text
- class IHaskellDisplay a => IHaskellWidget a where
- targetName :: a -> String
- targetModule :: a -> String
- getBufferPaths :: a -> [BufferPath]
- getCommUUID :: a -> UUID
- open :: a -> (Value -> IO ()) -> IO ()
- comm :: a -> Value -> (Value -> IO ()) -> IO ()
- close :: a -> Value -> IO ()
- printDisplay :: IHaskellDisplay a => a -> IO ()
- plain :: String -> DisplayData
- html :: String -> DisplayData
- bmp :: Width -> Height -> Base64 -> DisplayData
- png :: Width -> Height -> Base64 -> DisplayData
- jpg :: Width -> Height -> Base64 -> DisplayData
- gif :: Width -> Height -> Base64 -> DisplayData
- svg :: String -> DisplayData
- latex :: String -> DisplayData
- markdown :: String -> DisplayData
- javascript :: String -> DisplayData
- json :: String -> DisplayData
- vega :: String -> DisplayData
- vegalite :: String -> DisplayData
- vdom :: String -> DisplayData
- widgetdisplay :: String -> DisplayData
- custom :: Text -> String -> DisplayData
- many :: [Display] -> Display
- type Width = Int
- type Height = Int
- type Base64 = Text
- encode64 :: String -> Base64
- base64 :: ByteString -> Base64
- displayFromChanEncoded :: IO ByteString
- serializeDisplay :: Display -> ByteString
- data Widget = forall a.IHaskellWidget a => Widget a
Rich display and interactive display typeclasses and types
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
Instances
IHaskellDisplay Display Source # | |
IHaskellDisplay Widget Source # | |
IHaskellDisplay DisplayData Source # | |
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. |
IHaskellDisplay a => IHaskellDisplay [a] Source # | |
Wrapper for ipython-kernel's DisplayData which allows sending multiple results from the same expression.
Instances
ToJSON Display Source # | |
Defined in IHaskell.Types | |
Monoid Display Source # | |
Semigroup Display Source # | |
Generic Display Source # | |
Show Display Source # | |
Binary Display Source # | |
IHaskellDisplay Display Source # | |
type Rep Display Source # | |
Defined in IHaskell.Types type Rep Display = D1 ('MetaData "Display" "IHaskell.Types" "ihaskell-0.10.3.0-1Y1GeklUisK1aFT1NNWHeo" '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 DisplayData #
Data for display: a string with associated MIME type.
Instances
Generic DisplayData | |
Defined in IHaskell.IPython.Types type Rep DisplayData :: Type -> Type # from :: DisplayData -> Rep DisplayData x # to :: Rep DisplayData x -> DisplayData # | |
Show DisplayData | |
Defined in IHaskell.IPython.Types showsPrec :: Int -> DisplayData -> ShowS # show :: DisplayData -> String # showList :: [DisplayData] -> ShowS # | |
Binary DisplayData | |
Defined in IHaskell.IPython.Types | |
IHaskellDisplay DisplayData Source # | |
Defined in IHaskell.Types | |
type Rep DisplayData | |
Defined in IHaskell.IPython.Types type Rep DisplayData = D1 ('MetaData "DisplayData" "IHaskell.IPython.Types" "ipython-kernel-0.10.3.0-7rXj2chaGhf4ymDgbYiVwI" '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))) |
class IHaskellDisplay a => IHaskellWidget a where Source #
Display as an interactive widget.
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.
Called when the comm is opened. Allows additional messages to be sent after comm open.
:: 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.
Called when a comm_close is recieved from the frontend.
Instances
IHaskellWidget Widget Source # | |
Defined in IHaskell.Types |
Interactive use functions
printDisplay :: IHaskellDisplay a => a -> IO () Source #
Write to the display channel. The contents will be displayed in the notebook once the current execution call ends.
Constructors for displays
plain :: String -> DisplayData Source #
Generate a plain text display.
html :: String -> DisplayData Source #
Generate an HTML display.
bmp :: Width -> Height -> Base64 -> DisplayData Source #
Generate a BMP display of the given width and height. Data must be provided in a Base64 encoded
manner, suitable for embedding into HTML. The base64
function may be used to encode data into
this format.
png :: Width -> Height -> Base64 -> DisplayData Source #
Generate a PNG display of the given width and height. Data must be provided in a Base64 encoded
manner, suitable for embedding into HTML. The base64
function may be used to encode data into
this format.
jpg :: Width -> Height -> Base64 -> DisplayData Source #
Generate a JPG display of the given width and height. Data must be provided in a Base64 encoded
manner, suitable for embedding into HTML. The base64
function may be used to encode data into
this format.
gif :: Width -> Height -> Base64 -> DisplayData Source #
Generate a GIF display of the given width and height. Data must be provided in a Base64 encoded
manner, suitable for embedding into HTML. The base64
function may be used to encode data into
this format.
svg :: String -> DisplayData Source #
Generate an SVG display.
latex :: String -> DisplayData Source #
Generate a LaTeX display.
markdown :: String -> DisplayData Source #
Generate a Markdown display.
javascript :: String -> DisplayData Source #
Generate a Javascript display.
json :: String -> DisplayData Source #
Generate a Json display.
vega :: String -> DisplayData Source #
Generate a Vega display.
vegalite :: String -> DisplayData Source #
Generate a Vegalite display.
vdom :: String -> DisplayData Source #
Generate a Vdom display.
widgetdisplay :: String -> DisplayData Source #
Generate a Widget display given the uuid and the view version
custom :: Text -> String -> DisplayData Source #
Generate a custom display. The first argument is the mimetype and the second argument is the payload.
Image and data encoding functions
base64 :: ByteString -> Base64 Source #
Convert from a ByteString into base 64 encoded data.
Internal only use
displayFromChanEncoded :: IO ByteString Source #
Take everything that was put into the displayChan
at that point out, and make a Display
out
of it.
serializeDisplay :: Display -> ByteString Source #
For internal use within IHaskell. Serialize displays to a ByteString.
forall a.IHaskellWidget a => Widget a |
Instances
Show Widget Source # | |
Eq Widget Source # | |
IHaskellDisplay Widget Source # | |
IHaskellWidget Widget Source # | |
Defined in IHaskell.Types |