ipynb-0.2: Data structure for working with Jupyter notebooks (ipynb).
CopyrightCopyright (C) 2019 John MacFarlane
LicenseBSD3
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.Ipynb

Description

Data structure and JSON serializers for ipynb (Jupyter notebook) format. Version 4 of the format is documented here: https://nbformat.readthedocs.io/en/latest/format_description.html.

The library supports both version 4 ('Notebook NbV4') and version 3 ('Notebook NbV3') of nbformat. Note that this is a phantom type: the NbV3 or NbV4 parameter only affects JSON serialization, not the data structure itself. So code that manipulates notebooks can be polymorphic, operating on `Notebook a`.

Synopsis

Documentation

data Notebook a Source #

A Jupyter notebook.

Constructors

Notebook 

Instances

Instances details
Eq (Notebook a) Source # 
Instance details

Defined in Data.Ipynb

Methods

(==) :: Notebook a -> Notebook a -> Bool #

(/=) :: Notebook a -> Notebook a -> Bool #

Show (Notebook a) Source # 
Instance details

Defined in Data.Ipynb

Methods

showsPrec :: Int -> Notebook a -> ShowS #

show :: Notebook a -> String #

showList :: [Notebook a] -> ShowS #

Generic (Notebook a) Source # 
Instance details

Defined in Data.Ipynb

Associated Types

type Rep (Notebook a) :: Type -> Type #

Methods

from :: Notebook a -> Rep (Notebook a) x #

to :: Rep (Notebook a) x -> Notebook a #

Semigroup (Notebook a) Source # 
Instance details

Defined in Data.Ipynb

Methods

(<>) :: Notebook a -> Notebook a -> Notebook a #

sconcat :: NonEmpty (Notebook a) -> Notebook a #

stimes :: Integral b => b -> Notebook a -> Notebook a #

Monoid (Notebook a) Source # 
Instance details

Defined in Data.Ipynb

Methods

mempty :: Notebook a #

mappend :: Notebook a -> Notebook a -> Notebook a #

mconcat :: [Notebook a] -> Notebook a #

ToJSON (Notebook NbV4) Source # 
Instance details

Defined in Data.Ipynb

ToJSON (Notebook NbV3) Source # 
Instance details

Defined in Data.Ipynb

FromJSON (Notebook NbV4) Source # 
Instance details

Defined in Data.Ipynb

FromJSON (Notebook NbV3) Source # 
Instance details

Defined in Data.Ipynb

type Rep (Notebook a) Source # 
Instance details

Defined in Data.Ipynb

type Rep (Notebook a) = D1 ('MetaData "Notebook" "Data.Ipynb" "ipynb-0.2-J1hPjnFwlGuIK3vIBmAEF4" 'False) (C1 ('MetaCons "Notebook" 'PrefixI 'True) (S1 ('MetaSel ('Just "notebookMetadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSONMeta) :*: (S1 ('MetaSel ('Just "notebookFormat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Int)) :*: S1 ('MetaSel ('Just "notebookCells") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Cell a]))))

data NbV3 Source #

Indexes Notebook for serialization as nbformat version 3.

Instances

Instances details
ToJSON (Output NbV3) Source # 
Instance details

Defined in Data.Ipynb

ToJSON (Cell NbV3) Source # 
Instance details

Defined in Data.Ipynb

ToJSON (Notebook NbV3) Source # 
Instance details

Defined in Data.Ipynb

FromJSON (Output NbV3) Source # 
Instance details

Defined in Data.Ipynb

FromJSON (Cell NbV3) Source # 
Instance details

Defined in Data.Ipynb

FromJSON (Notebook NbV3) Source # 
Instance details

Defined in Data.Ipynb

data NbV4 Source #

Indexes Notebook for serialization as nbformat version 4.

Instances

Instances details
ToJSON (Output NbV4) Source # 
Instance details

Defined in Data.Ipynb

ToJSON (Cell NbV4) Source # 
Instance details

Defined in Data.Ipynb

ToJSON (Notebook NbV4) Source # 
Instance details

Defined in Data.Ipynb

FromJSON (Output NbV4) Source # 
Instance details

Defined in Data.Ipynb

FromJSON (Cell NbV4) Source # 
Instance details

Defined in Data.Ipynb

FromJSON (Notebook NbV4) Source # 
Instance details

Defined in Data.Ipynb

newtype JSONMeta Source #

Constructors

JSONMeta (Map Text Value) 

Instances

Instances details
Eq JSONMeta Source # 
Instance details

Defined in Data.Ipynb

Ord JSONMeta Source # 
Instance details

Defined in Data.Ipynb

Show JSONMeta Source # 
Instance details

Defined in Data.Ipynb

Generic JSONMeta Source # 
Instance details

Defined in Data.Ipynb

Associated Types

type Rep JSONMeta :: Type -> Type #

Methods

from :: JSONMeta -> Rep JSONMeta x #

to :: Rep JSONMeta x -> JSONMeta #

Semigroup JSONMeta Source # 
Instance details

Defined in Data.Ipynb

Monoid JSONMeta Source # 
Instance details

Defined in Data.Ipynb

ToJSON JSONMeta Source # 
Instance details

Defined in Data.Ipynb

FromJSON JSONMeta Source # 
Instance details

Defined in Data.Ipynb

type Rep JSONMeta Source # 
Instance details

Defined in Data.Ipynb

type Rep JSONMeta = D1 ('MetaData "JSONMeta" "Data.Ipynb" "ipynb-0.2-J1hPjnFwlGuIK3vIBmAEF4" 'True) (C1 ('MetaCons "JSONMeta" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text Value))))

data Cell a Source #

A Jupyter notebook cell.

Instances

Instances details
Eq (Cell a) Source # 
Instance details

Defined in Data.Ipynb

Methods

(==) :: Cell a -> Cell a -> Bool #

(/=) :: Cell a -> Cell a -> Bool #

Show (Cell a) Source # 
Instance details

Defined in Data.Ipynb

Methods

showsPrec :: Int -> Cell a -> ShowS #

show :: Cell a -> String #

showList :: [Cell a] -> ShowS #

Generic (Cell a) Source # 
Instance details

Defined in Data.Ipynb

Associated Types

type Rep (Cell a) :: Type -> Type #

Methods

from :: Cell a -> Rep (Cell a) x #

to :: Rep (Cell a) x -> Cell a #

ToJSON (Cell NbV4) Source # 
Instance details

Defined in Data.Ipynb

ToJSON (Cell NbV3) Source # 
Instance details

Defined in Data.Ipynb

FromJSON (Cell NbV4) Source # 
Instance details

Defined in Data.Ipynb

FromJSON (Cell NbV3) Source # 
Instance details

Defined in Data.Ipynb

type Rep (Cell a) Source # 
Instance details

Defined in Data.Ipynb

newtype Source Source #

A Source is a textual content which may be represented in JSON either as a single string or as a list of strings (which are concatenated).

Constructors

Source 

Fields

Instances

Instances details
Eq Source Source # 
Instance details

Defined in Data.Ipynb

Methods

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

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

Show Source Source # 
Instance details

Defined in Data.Ipynb

Generic Source Source # 
Instance details

Defined in Data.Ipynb

Associated Types

type Rep Source :: Type -> Type #

Methods

from :: Source -> Rep Source x #

to :: Rep Source x -> Source #

Semigroup Source Source # 
Instance details

Defined in Data.Ipynb

Monoid Source Source # 
Instance details

Defined in Data.Ipynb

ToJSON Source Source # 
Instance details

Defined in Data.Ipynb

FromJSON Source Source # 
Instance details

Defined in Data.Ipynb

type Rep Source Source # 
Instance details

Defined in Data.Ipynb

type Rep Source = D1 ('MetaData "Source" "Data.Ipynb" "ipynb-0.2-J1hPjnFwlGuIK3vIBmAEF4" 'True) (C1 ('MetaCons "Source" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])))

data CellType a Source #

Information about the type of a notebook cell, plus data specific to that type. note that Heading is for v3 only; a Heading will be rendered as Markdown in v4.

Constructors

Markdown 
Heading 

Fields

Raw 
Code 

Instances

Instances details
Eq (CellType a) Source # 
Instance details

Defined in Data.Ipynb

Methods

(==) :: CellType a -> CellType a -> Bool #

(/=) :: CellType a -> CellType a -> Bool #

Show (CellType a) Source # 
Instance details

Defined in Data.Ipynb

Methods

showsPrec :: Int -> CellType a -> ShowS #

show :: CellType a -> String #

showList :: [CellType a] -> ShowS #

Generic (CellType a) Source # 
Instance details

Defined in Data.Ipynb

Associated Types

type Rep (CellType a) :: Type -> Type #

Methods

from :: CellType a -> Rep (CellType a) x #

to :: Rep (CellType a) x -> CellType a #

type Rep (CellType a) Source # 
Instance details

Defined in Data.Ipynb

type Rep (CellType a) = D1 ('MetaData "CellType" "Data.Ipynb" "ipynb-0.2-J1hPjnFwlGuIK3vIBmAEF4" 'False) ((C1 ('MetaCons "Markdown" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Heading" 'PrefixI 'True) (S1 ('MetaSel ('Just "headingLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "Raw" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Code" 'PrefixI 'True) (S1 ('MetaSel ('Just "codeExecutionCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "codeOutputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Output a]))))

data Output a Source #

Output from a Code cell.

Instances

Instances details
Eq (Output a) Source # 
Instance details

Defined in Data.Ipynb

Methods

(==) :: Output a -> Output a -> Bool #

(/=) :: Output a -> Output a -> Bool #

Show (Output a) Source # 
Instance details

Defined in Data.Ipynb

Methods

showsPrec :: Int -> Output a -> ShowS #

show :: Output a -> String #

showList :: [Output a] -> ShowS #

Generic (Output a) Source # 
Instance details

Defined in Data.Ipynb

Associated Types

type Rep (Output a) :: Type -> Type #

Methods

from :: Output a -> Rep (Output a) x #

to :: Rep (Output a) x -> Output a #

ToJSON (Output NbV4) Source # 
Instance details

Defined in Data.Ipynb

ToJSON (Output NbV3) Source # 
Instance details

Defined in Data.Ipynb

FromJSON (Output NbV4) Source # 
Instance details

Defined in Data.Ipynb

FromJSON (Output NbV3) Source # 
Instance details

Defined in Data.Ipynb

type Rep (Output a) Source # 
Instance details

Defined in Data.Ipynb

data MimeData Source #

Data in an execution result or display data cell.

Instances

Instances details
Eq MimeData Source # 
Instance details

Defined in Data.Ipynb

Ord MimeData Source # 
Instance details

Defined in Data.Ipynb

Show MimeData Source # 
Instance details

Defined in Data.Ipynb

Generic MimeData Source # 
Instance details

Defined in Data.Ipynb

Associated Types

type Rep MimeData :: Type -> Type #

Methods

from :: MimeData -> Rep MimeData x #

to :: Rep MimeData x -> MimeData #

ToJSON MimeData Source # 
Instance details

Defined in Data.Ipynb

type Rep MimeData Source # 
Instance details

Defined in Data.Ipynb

newtype MimeBundle Source #

A MimeBundle wraps a map from mime types to mime data.

Constructors

MimeBundle 

Instances

Instances details
Eq MimeBundle Source # 
Instance details

Defined in Data.Ipynb

Ord MimeBundle Source # 
Instance details

Defined in Data.Ipynb

Show MimeBundle Source # 
Instance details

Defined in Data.Ipynb

Generic MimeBundle Source # 
Instance details

Defined in Data.Ipynb

Associated Types

type Rep MimeBundle :: Type -> Type #

Semigroup MimeBundle Source # 
Instance details

Defined in Data.Ipynb

Monoid MimeBundle Source # 
Instance details

Defined in Data.Ipynb

ToJSON MimeBundle Source # 
Instance details

Defined in Data.Ipynb

FromJSON MimeBundle Source # 
Instance details

Defined in Data.Ipynb

type Rep MimeBundle Source # 
Instance details

Defined in Data.Ipynb

type Rep MimeBundle = D1 ('MetaData "MimeBundle" "Data.Ipynb" "ipynb-0.2-J1hPjnFwlGuIK3vIBmAEF4" 'True) (C1 ('MetaCons "MimeBundle" 'PrefixI 'True) (S1 ('MetaSel ('Just "unMimeBundle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map MimeType MimeData))))

newtype MimeAttachments Source #

Instances

Instances details
Eq MimeAttachments Source # 
Instance details

Defined in Data.Ipynb

Ord MimeAttachments Source # 
Instance details

Defined in Data.Ipynb

Show MimeAttachments Source # 
Instance details

Defined in Data.Ipynb

Generic MimeAttachments Source # 
Instance details

Defined in Data.Ipynb

Associated Types

type Rep MimeAttachments :: Type -> Type #

Semigroup MimeAttachments Source # 
Instance details

Defined in Data.Ipynb

Monoid MimeAttachments Source # 
Instance details

Defined in Data.Ipynb

ToJSON MimeAttachments Source # 
Instance details

Defined in Data.Ipynb

FromJSON MimeAttachments Source # 
Instance details

Defined in Data.Ipynb

type Rep MimeAttachments Source # 
Instance details

Defined in Data.Ipynb

type Rep MimeAttachments = D1 ('MetaData "MimeAttachments" "Data.Ipynb" "ipynb-0.2-J1hPjnFwlGuIK3vIBmAEF4" 'True) (C1 ('MetaCons "MimeAttachments" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text MimeBundle))))

breakLines :: Text -> [Text] Source #

Break up a string into a list of strings, each representing one line of the string (including trailing newline if any).