ipynb-0.1: 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 

Fields

Instances
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

FromJSON (Notebook NbV4) Source # 
Instance details

Defined in Data.Ipynb

Methods

parseJSON :: Value -> Parser (Notebook NbV4)

parseJSONList :: Value -> Parser [Notebook NbV4]

FromJSON (Notebook NbV3) Source # 
Instance details

Defined in Data.Ipynb

Methods

parseJSON :: Value -> Parser (Notebook NbV3)

parseJSONList :: Value -> Parser [Notebook NbV3]

ToJSON (Notebook NbV4) Source # 
Instance details

Defined in Data.Ipynb

Methods

toJSON :: Notebook NbV4 -> Value

toEncoding :: Notebook NbV4 -> Encoding

toJSONList :: [Notebook NbV4] -> Value

toEncodingList :: [Notebook NbV4] -> Encoding

ToJSON (Notebook NbV3) Source # 
Instance details

Defined in Data.Ipynb

Methods

toJSON :: Notebook NbV3 -> Value

toEncoding :: Notebook NbV3 -> Encoding

toJSONList :: [Notebook NbV3] -> Value

toEncodingList :: [Notebook NbV3] -> Encoding

type Rep (Notebook a) Source # 
Instance details

Defined in Data.Ipynb

type Rep (Notebook a) = D1 (MetaData "Notebook" "Data.Ipynb" "ipynb-0.1-INxpVJXMMdx14RLZkS3lLo" 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
FromJSON (Output NbV3) Source # 
Instance details

Defined in Data.Ipynb

Methods

parseJSON :: Value -> Parser (Output NbV3)

parseJSONList :: Value -> Parser [Output NbV3]

FromJSON (Cell NbV3) Source # 
Instance details

Defined in Data.Ipynb

Methods

parseJSON :: Value -> Parser (Cell NbV3)

parseJSONList :: Value -> Parser [Cell NbV3]

FromJSON (Notebook NbV3) Source # 
Instance details

Defined in Data.Ipynb

Methods

parseJSON :: Value -> Parser (Notebook NbV3)

parseJSONList :: Value -> Parser [Notebook NbV3]

ToJSON (Output NbV3) Source # 
Instance details

Defined in Data.Ipynb

Methods

toJSON :: Output NbV3 -> Value

toEncoding :: Output NbV3 -> Encoding

toJSONList :: [Output NbV3] -> Value

toEncodingList :: [Output NbV3] -> Encoding

ToJSON (Cell NbV3) Source # 
Instance details

Defined in Data.Ipynb

Methods

toJSON :: Cell NbV3 -> Value

toEncoding :: Cell NbV3 -> Encoding

toJSONList :: [Cell NbV3] -> Value

toEncodingList :: [Cell NbV3] -> Encoding

ToJSON (Notebook NbV3) Source # 
Instance details

Defined in Data.Ipynb

Methods

toJSON :: Notebook NbV3 -> Value

toEncoding :: Notebook NbV3 -> Encoding

toJSONList :: [Notebook NbV3] -> Value

toEncodingList :: [Notebook NbV3] -> Encoding

data NbV4 Source #

Indexes Notebook for serialization as nbformat version 4.

Instances
FromJSON (Output NbV4) Source # 
Instance details

Defined in Data.Ipynb

Methods

parseJSON :: Value -> Parser (Output NbV4)

parseJSONList :: Value -> Parser [Output NbV4]

FromJSON (Cell NbV4) Source # 
Instance details

Defined in Data.Ipynb

Methods

parseJSON :: Value -> Parser (Cell NbV4)

parseJSONList :: Value -> Parser [Cell NbV4]

FromJSON (Notebook NbV4) Source # 
Instance details

Defined in Data.Ipynb

Methods

parseJSON :: Value -> Parser (Notebook NbV4)

parseJSONList :: Value -> Parser [Notebook NbV4]

ToJSON (Output NbV4) Source # 
Instance details

Defined in Data.Ipynb

Methods

toJSON :: Output NbV4 -> Value

toEncoding :: Output NbV4 -> Encoding

toJSONList :: [Output NbV4] -> Value

toEncodingList :: [Output NbV4] -> Encoding

ToJSON (Cell NbV4) Source # 
Instance details

Defined in Data.Ipynb

Methods

toJSON :: Cell NbV4 -> Value

toEncoding :: Cell NbV4 -> Encoding

toJSONList :: [Cell NbV4] -> Value

toEncodingList :: [Cell NbV4] -> Encoding

ToJSON (Notebook NbV4) Source # 
Instance details

Defined in Data.Ipynb

Methods

toJSON :: Notebook NbV4 -> Value

toEncoding :: Notebook NbV4 -> Encoding

toJSONList :: [Notebook NbV4] -> Value

toEncodingList :: [Notebook NbV4] -> Encoding

type JSONMeta = Map Text Value Source #

data Cell a Source #

A Jupyter notebook cell.

Constructors

Cell 
Instances
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

FromJSON (Cell NbV4) Source # 
Instance details

Defined in Data.Ipynb

Methods

parseJSON :: Value -> Parser (Cell NbV4)

parseJSONList :: Value -> Parser [Cell NbV4]

FromJSON (Cell NbV3) Source # 
Instance details

Defined in Data.Ipynb

Methods

parseJSON :: Value -> Parser (Cell NbV3)

parseJSONList :: Value -> Parser [Cell NbV3]

ToJSON (Cell NbV4) Source # 
Instance details

Defined in Data.Ipynb

Methods

toJSON :: Cell NbV4 -> Value

toEncoding :: Cell NbV4 -> Encoding

toJSONList :: [Cell NbV4] -> Value

toEncodingList :: [Cell NbV4] -> Encoding

ToJSON (Cell NbV3) Source # 
Instance details

Defined in Data.Ipynb

Methods

toJSON :: Cell NbV3 -> Value

toEncoding :: Cell NbV3 -> Encoding

toJSONList :: [Cell NbV3] -> Value

toEncodingList :: [Cell NbV3] -> Encoding

type Rep (Cell a) Source # 
Instance details

Defined in Data.Ipynb

type Rep (Cell a) = D1 (MetaData "Cell" "Data.Ipynb" "ipynb-0.1-INxpVJXMMdx14RLZkS3lLo" False) (C1 (MetaCons "Cell" PrefixI True) ((S1 (MetaSel (Just "cellType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CellType a)) :*: S1 (MetaSel (Just "cellSource") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Source)) :*: (S1 (MetaSel (Just "cellMetadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSONMeta) :*: S1 (MetaSel (Just "cellAttachments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Map Text MimeBundle))))))

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

Methods

showsPrec :: Int -> Source -> ShowS

show :: Source -> String

showList :: [Source] -> ShowS

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

Methods

(<>) :: Source -> Source -> Source

sconcat :: NonEmpty Source -> Source

stimes :: Integral b => b -> Source -> Source

Monoid Source Source # 
Instance details

Defined in Data.Ipynb

FromJSON Source Source # 
Instance details

Defined in Data.Ipynb

Methods

parseJSON :: Value -> Parser Source

parseJSONList :: Value -> Parser [Source]

ToJSON Source Source # 
Instance details

Defined in Data.Ipynb

Methods

toJSON :: Source -> Value

toEncoding :: Source -> Encoding

toJSONList :: [Source] -> Value

toEncodingList :: [Source] -> Encoding

type Rep Source Source # 
Instance details

Defined in Data.Ipynb

type Rep Source = D1 (MetaData "Source" "Data.Ipynb" "ipynb-0.1-INxpVJXMMdx14RLZkS3lLo" 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 

Fields

Instances
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.1-INxpVJXMMdx14RLZkS3lLo" 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.

Constructors

Stream 

Fields

DisplayData 
ExecuteResult 
Err 

Fields

Instances
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

FromJSON (Output NbV4) Source # 
Instance details

Defined in Data.Ipynb

Methods

parseJSON :: Value -> Parser (Output NbV4)

parseJSONList :: Value -> Parser [Output NbV4]

FromJSON (Output NbV3) Source # 
Instance details

Defined in Data.Ipynb

Methods

parseJSON :: Value -> Parser (Output NbV3)

parseJSONList :: Value -> Parser [Output NbV3]

ToJSON (Output NbV4) Source # 
Instance details

Defined in Data.Ipynb

Methods

toJSON :: Output NbV4 -> Value

toEncoding :: Output NbV4 -> Encoding

toJSONList :: [Output NbV4] -> Value

toEncodingList :: [Output NbV4] -> Encoding

ToJSON (Output NbV3) Source # 
Instance details

Defined in Data.Ipynb

Methods

toJSON :: Output NbV3 -> Value

toEncoding :: Output NbV3 -> Encoding

toJSONList :: [Output NbV3] -> Value

toEncodingList :: [Output NbV3] -> Encoding

type Rep (Output a) Source # 
Instance details

Defined in Data.Ipynb

type Rep (Output a) = D1 (MetaData "Output" "Data.Ipynb" "ipynb-0.1-INxpVJXMMdx14RLZkS3lLo" False) ((C1 (MetaCons "Stream" PrefixI True) (S1 (MetaSel (Just "streamName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "streamText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Source)) :+: C1 (MetaCons "DisplayData" PrefixI True) (S1 (MetaSel (Just "displayData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MimeBundle) :*: S1 (MetaSel (Just "displayMetadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSONMeta))) :+: (C1 (MetaCons "ExecuteResult" PrefixI True) (S1 (MetaSel (Just "executeCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: (S1 (MetaSel (Just "executeData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MimeBundle) :*: S1 (MetaSel (Just "executeMetadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSONMeta))) :+: C1 (MetaCons "Err" PrefixI True) (S1 (MetaSel (Just "errName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Just "errValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "errTraceback") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text])))))

type MimeType = Text Source #

data MimeData Source #

Data in an execution result or display data cell.

Constructors

BinaryData ByteString 
TextualData Text 
JsonData Value 
Instances
Eq MimeData Source # 
Instance details

Defined in Data.Ipynb

Methods

(==) :: MimeData -> MimeData -> Bool

(/=) :: MimeData -> MimeData -> Bool

Show MimeData Source # 
Instance details

Defined in Data.Ipynb

Methods

showsPrec :: Int -> MimeData -> ShowS

show :: MimeData -> String

showList :: [MimeData] -> ShowS

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

type Rep MimeData Source # 
Instance details

Defined in Data.Ipynb

type Rep MimeData = D1 (MetaData "MimeData" "Data.Ipynb" "ipynb-0.1-INxpVJXMMdx14RLZkS3lLo" False) (C1 (MetaCons "BinaryData" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)) :+: (C1 (MetaCons "TextualData" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "JsonData" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Value))))

newtype MimeBundle Source #

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

Constructors

MimeBundle 
Instances
Eq MimeBundle Source # 
Instance details

Defined in Data.Ipynb

Methods

(==) :: MimeBundle -> MimeBundle -> Bool

(/=) :: MimeBundle -> MimeBundle -> Bool

Show MimeBundle Source # 
Instance details

Defined in Data.Ipynb

Methods

showsPrec :: Int -> MimeBundle -> ShowS

show :: MimeBundle -> String

showList :: [MimeBundle] -> ShowS

Generic MimeBundle Source # 
Instance details

Defined in Data.Ipynb

Associated Types

type Rep MimeBundle :: Type -> Type

Methods

from :: MimeBundle -> Rep MimeBundle x

to :: Rep MimeBundle x -> MimeBundle

Semigroup MimeBundle Source # 
Instance details

Defined in Data.Ipynb

Methods

(<>) :: MimeBundle -> MimeBundle -> MimeBundle

sconcat :: NonEmpty MimeBundle -> MimeBundle

stimes :: Integral b => b -> MimeBundle -> MimeBundle

Monoid MimeBundle Source # 
Instance details

Defined in Data.Ipynb

FromJSON MimeBundle Source # 
Instance details

Defined in Data.Ipynb

Methods

parseJSON :: Value -> Parser MimeBundle

parseJSONList :: Value -> Parser [MimeBundle]

ToJSON MimeBundle Source # 
Instance details

Defined in Data.Ipynb

Methods

toJSON :: MimeBundle -> Value

toEncoding :: MimeBundle -> Encoding

toJSONList :: [MimeBundle] -> Value

toEncodingList :: [MimeBundle] -> Encoding

type Rep MimeBundle Source # 
Instance details

Defined in Data.Ipynb

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

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).