Copyright | Copyright (C) 2022-2023 John MacFarlane |
---|---|
License | GNU GPL, version 2 or above |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Stability | alpha |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Text.Pandoc.Chunks
Description
Functions and types for splitting a Pandoc into subdocuments, e.g. for conversion into a set of HTML pages.
Synopsis
- data Chunk = Chunk {
- chunkHeading :: [Inline]
- chunkId :: Text
- chunkLevel :: Int
- chunkNumber :: Int
- chunkSectionNumber :: Maybe Text
- chunkPath :: FilePath
- chunkUp :: Maybe Chunk
- chunkPrev :: Maybe Chunk
- chunkNext :: Maybe Chunk
- chunkUnlisted :: Bool
- chunkContents :: [Block]
- data ChunkedDoc = ChunkedDoc {
- chunkedMeta :: Meta
- chunkedTOC :: Tree SecInfo
- chunkedChunks :: [Chunk]
- newtype PathTemplate = PathTemplate {}
- splitIntoChunks :: PathTemplate -> Bool -> Maybe Int -> Int -> Pandoc -> ChunkedDoc
- toTOCTree :: [Block] -> Tree SecInfo
- tocToList :: Bool -> Int -> Tree SecInfo -> Block
- data SecInfo = SecInfo {}
Documentation
A part of a document (typically a chapter or section, or the part of a section before its subsections).
Constructors
Chunk | |
Fields
|
Instances
data ChunkedDoc Source #
A Pandoc
broken into Chunk
s for writing to separate files.
Constructors
ChunkedDoc | |
Fields
|
Instances
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
Data PathTemplate Source # | |
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 # | |
Defined in Text.Pandoc.Chunks Methods fromString :: String -> PathTemplate # | |
Generic PathTemplate Source # | |
Defined in Text.Pandoc.Chunks Associated Types type Rep PathTemplate :: Type -> Type # | |
Show PathTemplate Source # | |
Defined in Text.Pandoc.Chunks Methods showsPrec :: Int -> PathTemplate -> ShowS # show :: PathTemplate -> String # showList :: [PathTemplate] -> ShowS # | |
FromJSON PathTemplate Source # | |
Defined in Text.Pandoc.Chunks | |
ToJSON PathTemplate Source # | |
Defined in Text.Pandoc.Chunks Methods toJSON :: PathTemplate -> Value toEncoding :: PathTemplate -> Encoding toJSONList :: [PathTemplate] -> Value toEncodingList :: [PathTemplate] -> Encoding | |
type Rep PathTemplate Source # | |
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))) |
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 Chunk
s, 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 for a section in a hierarchical document.
Constructors
SecInfo | |
Instances
Generic SecInfo Source # | |
Show SecInfo Source # | |
Eq SecInfo Source # | |
Walkable Inline SecInfo Source # | |
type Rep SecInfo Source # | |
Defined in Text.Pandoc.Chunks type Rep SecInfo = D1 ('MetaData "SecInfo" "Text.Pandoc.Chunks" "pandoc-3.1.2-inplace" 'False) (C1 ('MetaCons "SecInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "secTitle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Inline]) :*: S1 ('MetaSel ('Just "secNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "secId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "secPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "secLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))) |