pandoc-3.1.2: Conversion between markup formats
CopyrightCopyright (C) 2022-2023 John MacFarlane
LicenseGNU GPL, version 2 or above
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Pandoc.Chunks

Description

Functions and types for splitting a Pandoc into subdocuments, e.g. for conversion into a set of HTML pages.

Synopsis

Documentation

data Chunk Source #

A part of a document (typically a chapter or section, or the part of a section before its subsections).

Instances

Instances details
Generic Chunk Source # 
Instance details

Defined in Text.Pandoc.Chunks

Associated Types

type Rep Chunk :: Type -> Type #

Methods

from :: Chunk -> Rep Chunk x #

to :: Rep Chunk x -> Chunk #

Show Chunk Source # 
Instance details

Defined in Text.Pandoc.Chunks

Methods

showsPrec :: Int -> Chunk -> ShowS #

show :: Chunk -> String #

showList :: [Chunk] -> ShowS #

Eq Chunk Source # 
Instance details

Defined in Text.Pandoc.Chunks

Methods

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

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

Walkable Block Chunk Source # 
Instance details

Defined in Text.Pandoc.Chunks

Methods

walk :: (Block -> Block) -> Chunk -> Chunk

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Chunk -> m Chunk

query :: Monoid c => (Block -> c) -> Chunk -> c

Walkable Inline Chunk Source # 
Instance details

Defined in Text.Pandoc.Chunks

Methods

walk :: (Inline -> Inline) -> Chunk -> Chunk

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Chunk -> m Chunk

query :: Monoid c => (Inline -> c) -> Chunk -> c

type Rep Chunk Source # 
Instance details

Defined in Text.Pandoc.Chunks

data ChunkedDoc Source #

A Pandoc broken into Chunks for writing to separate files.

Constructors

ChunkedDoc 

Instances

Instances details
Generic ChunkedDoc Source # 
Instance details

Defined in Text.Pandoc.Chunks

Associated Types

type Rep ChunkedDoc :: Type -> Type #

Show ChunkedDoc Source # 
Instance details

Defined in Text.Pandoc.Chunks

Eq ChunkedDoc Source # 
Instance details

Defined in Text.Pandoc.Chunks

Walkable Block ChunkedDoc Source # 
Instance details

Defined in Text.Pandoc.Chunks

Methods

walk :: (Block -> Block) -> ChunkedDoc -> ChunkedDoc

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> ChunkedDoc -> m ChunkedDoc

query :: Monoid c => (Block -> c) -> ChunkedDoc -> c

Walkable Inline ChunkedDoc Source # 
Instance details

Defined in Text.Pandoc.Chunks

Methods

walk :: (Inline -> Inline) -> ChunkedDoc -> ChunkedDoc

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> ChunkedDoc -> m ChunkedDoc

query :: Monoid c => (Inline -> c) -> ChunkedDoc -> c

type Rep ChunkedDoc Source # 
Instance details

Defined in Text.Pandoc.Chunks

type Rep ChunkedDoc = D1 ('MetaData "ChunkedDoc" "Text.Pandoc.Chunks" "pandoc-3.1.2-inplace" 'False) (C1 ('MetaCons "ChunkedDoc" 'PrefixI 'True) (S1 ('MetaSel ('Just "chunkedMeta") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Meta) :*: (S1 ('MetaSel ('Just "chunkedTOC") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Tree SecInfo)) :*: S1 ('MetaSel ('Just "chunkedChunks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Chunk]))))

newtype PathTemplate Source #

A PathTemplate is a FilePath in which certain codes will be substituted with information from a Chunk. %n will be replaced with the chunk number (padded with leading 0s to 3 digits), %s with the section number of the heading, %h with the (stringified) heading text, %i with the section identifier. For example, "section-%s-%i.html" might be resolved to "section-1.2-introduction.html".

Constructors

PathTemplate 

Fields

Instances

Instances details
Data PathTemplate Source # 
Instance details

Defined in Text.Pandoc.Chunks

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PathTemplate -> c PathTemplate #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PathTemplate #

toConstr :: PathTemplate -> Constr #

dataTypeOf :: PathTemplate -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PathTemplate) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PathTemplate) #

gmapT :: (forall b. Data b => b -> b) -> PathTemplate -> PathTemplate #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PathTemplate -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PathTemplate -> r #

gmapQ :: (forall d. Data d => d -> u) -> PathTemplate -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PathTemplate -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PathTemplate -> m PathTemplate #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PathTemplate -> m PathTemplate #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PathTemplate -> m PathTemplate #

IsString PathTemplate Source # 
Instance details

Defined in Text.Pandoc.Chunks

Generic PathTemplate Source # 
Instance details

Defined in Text.Pandoc.Chunks

Associated Types

type Rep PathTemplate :: Type -> Type #

Show PathTemplate Source # 
Instance details

Defined in Text.Pandoc.Chunks

FromJSON PathTemplate Source # 
Instance details

Defined in Text.Pandoc.Chunks

Methods

parseJSON :: Value -> Parser PathTemplate

parseJSONList :: Value -> Parser [PathTemplate]

ToJSON PathTemplate Source # 
Instance details

Defined in Text.Pandoc.Chunks

Methods

toJSON :: PathTemplate -> Value

toEncoding :: PathTemplate -> Encoding

toJSONList :: [PathTemplate] -> Value

toEncodingList :: [PathTemplate] -> Encoding

type Rep PathTemplate Source # 
Instance details

Defined in Text.Pandoc.Chunks

type Rep PathTemplate = D1 ('MetaData "PathTemplate" "Text.Pandoc.Chunks" "pandoc-3.1.2-inplace" 'True) (C1 ('MetaCons "PathTemplate" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPathTemplate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

splitIntoChunks Source #

Arguments

:: PathTemplate

Template for filepath

-> Bool

Number sections

-> Maybe Int

Base heading level

-> Int

Chunk level -- level of section to split at

-> Pandoc 
-> ChunkedDoc 

Split Pandoc into Chunks, e.g. for conversion into a set of HTML pages or EPUB chapters.

toTOCTree :: [Block] -> Tree SecInfo Source #

Create tree of sections with titles, links, and numbers, in a form that can be turned into a table of contents. Presupposes that the '[Block]' is the output of makeSections.

tocToList :: Bool -> Int -> Tree SecInfo -> Block Source #

Generate a table of contents of the given depth.

data SecInfo Source #

Data for a section in a hierarchical document.

Constructors

SecInfo 

Fields

Instances

Instances details
Generic SecInfo Source # 
Instance details

Defined in Text.Pandoc.Chunks

Associated Types

type Rep SecInfo :: Type -> Type #

Methods

from :: SecInfo -> Rep SecInfo x #

to :: Rep SecInfo x -> SecInfo #

Show SecInfo Source # 
Instance details

Defined in Text.Pandoc.Chunks

Eq SecInfo Source # 
Instance details

Defined in Text.Pandoc.Chunks

Methods

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

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

Walkable Inline SecInfo Source # 
Instance details

Defined in Text.Pandoc.Chunks

Methods

walk :: (Inline -> Inline) -> SecInfo -> SecInfo

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> SecInfo -> m SecInfo

query :: Monoid c => (Inline -> c) -> SecInfo -> c

type Rep SecInfo Source # 
Instance details

Defined in Text.Pandoc.Chunks