{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Text.Pandoc.Chunks
( Chunk(..)
, ChunkedDoc(..)
, PathTemplate(..)
, splitIntoChunks
, toTOCTree
, tocToList
, SecInfo(..)
) where
import Text.Pandoc.Definition
import Text.Pandoc.Shared (makeSections, stringify, inlineListToIdentifier)
import Text.Pandoc.Walk (Walkable(..))
import Data.Aeson (FromJSON, ToJSON)
import Data.Text (Text)
import Text.Printf (printf)
import Data.Maybe (fromMaybe, isNothing)
import qualified Data.Map as M
import qualified Data.Text as T
import Data.String (IsString)
import GHC.Generics (Generic)
import Text.HTML.TagSoup (Tag (TagOpen), fromAttrib, parseTags)
import Data.Tree (Tree(..))
import Data.Data (Data)
import Data.Typeable (Typeable)
splitIntoChunks :: PathTemplate
-> Bool
-> Maybe Int
-> Int
-> Pandoc
-> ChunkedDoc
splitIntoChunks :: PathTemplate -> Bool -> Maybe Int -> Int -> Pandoc -> ChunkedDoc
splitIntoChunks PathTemplate
pathTemplate Bool
numberSections Maybe Int
mbBaseLevel
Int
chunklev (Pandoc Meta
meta [Block]
blocks) =
ChunkedDoc -> ChunkedDoc
addNav forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ChunkedDoc -> ChunkedDoc
fixInternalReferences forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall a b. Walkable a b => (a -> a) -> b -> b
walk Block -> Block
rmNavAttrs forall a b. (a -> b) -> a -> b
$
ChunkedDoc{ chunkedMeta :: Meta
chunkedMeta = Meta
meta
, chunkedChunks :: [Chunk]
chunkedChunks = [Chunk]
chunks
, chunkedTOC :: Tree SecInfo
chunkedTOC = Tree SecInfo
tocTree }
where
tocTree :: Tree SecInfo
tocTree = [Chunk] -> Tree SecInfo -> Tree SecInfo
fixTOCTreePaths [Chunk]
chunks forall a b. (a -> b) -> a -> b
$ [Block] -> Tree SecInfo
toTOCTree [Block]
sections
chunks :: [Chunk]
chunks = Int -> PathTemplate -> Meta -> [Block] -> [Chunk]
makeChunks Int
chunklev PathTemplate
pathTemplate Meta
meta forall a b. (a -> b) -> a -> b
$ [Block]
sections
sections :: [Block]
sections = Bool -> Maybe Int -> [Block] -> [Block]
makeSections Bool
numberSections Maybe Int
mbBaseLevel forall a b. (a -> b) -> a -> b
$ [Block]
blocks
addNav :: ChunkedDoc -> ChunkedDoc
addNav :: ChunkedDoc -> ChunkedDoc
addNav ChunkedDoc
chunkedDoc =
ChunkedDoc
chunkedDoc{ chunkedChunks :: [Chunk]
chunkedChunks =
[Chunk] -> [Chunk]
addNext forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Chunk] -> [Chunk]
addPrev forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Chunk] -> [Chunk]
addUp forall a b. (a -> b) -> a -> b
$ ChunkedDoc -> [Chunk]
chunkedChunks ChunkedDoc
chunkedDoc }
addUp :: [Chunk] -> [Chunk]
addUp :: [Chunk] -> [Chunk]
addUp (Chunk
c : Chunk
d : [Chunk]
ds)
| Chunk -> Int
chunkLevel Chunk
c forall a. Ord a => a -> a -> Bool
< Chunk -> Int
chunkLevel Chunk
d
= Chunk
c forall a. a -> [a] -> [a]
: [Chunk] -> [Chunk]
addUp (Chunk
d{ chunkUp :: Maybe Chunk
chunkUp = forall a. a -> Maybe a
Just Chunk
c } forall a. a -> [a] -> [a]
: [Chunk]
ds)
| Chunk -> Int
chunkLevel Chunk
c forall a. Eq a => a -> a -> Bool
== Chunk -> Int
chunkLevel Chunk
d
= Chunk
c forall a. a -> [a] -> [a]
: [Chunk] -> [Chunk]
addUp (Chunk
d{ chunkUp :: Maybe Chunk
chunkUp = Chunk -> Maybe Chunk
chunkUp Chunk
c} forall a. a -> [a] -> [a]
: [Chunk]
ds)
addUp (Chunk
c:[Chunk]
cs) = Chunk
c forall a. a -> [a] -> [a]
: [Chunk] -> [Chunk]
addUp [Chunk]
cs
addUp [] = []
addNext :: [Chunk] -> [Chunk]
addNext :: [Chunk] -> [Chunk]
addNext [Chunk]
cs = forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Chunk -> Maybe Chunk -> Chunk
go [Chunk]
cs (forall a b. (a -> b) -> [a] -> [b]
map forall a. a -> Maybe a
Just (forall a. [a] -> [a]
tail [Chunk]
cs) forall a. [a] -> [a] -> [a]
++ [forall a. Maybe a
Nothing])
where
go :: Chunk -> Maybe Chunk -> Chunk
go Chunk
c Maybe Chunk
nxt = Chunk
c{ chunkNext :: Maybe Chunk
chunkNext = Maybe Chunk
nxt }
addPrev :: [Chunk] -> [Chunk]
addPrev :: [Chunk] -> [Chunk]
addPrev [Chunk]
cs = forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Chunk -> Maybe Chunk -> Chunk
go [Chunk]
cs (forall a. Maybe a
Nothing forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall a. a -> Maybe a
Just [Chunk]
cs)
where
go :: Chunk -> Maybe Chunk -> Chunk
go Chunk
c Maybe Chunk
prev = Chunk
c{ chunkPrev :: Maybe Chunk
chunkPrev = Maybe Chunk
prev }
fixInternalReferences :: ChunkedDoc -> ChunkedDoc
fixInternalReferences :: ChunkedDoc -> ChunkedDoc
fixInternalReferences ChunkedDoc
chunkedDoc = forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
fixInternalRefs ChunkedDoc
chunkedDoc
where
fixInternalRefs :: Inline -> Inline
fixInternalRefs :: Inline -> Inline
fixInternalRefs il :: Inline
il@(Link Attr
attr [Inline]
ils (Text
src,Text
tit))
= case Text -> Maybe (Char, Text)
T.uncons Text
src of
Just (Char
'#', Text
ident) -> Attr -> [Inline] -> (Text, Text) -> Inline
Link Attr
attr [Inline]
ils (Text
src', Text
tit)
where src' :: Text
src' = case forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
ident Map Text Chunk
refMap of
Just Chunk
chunk -> String -> Text
T.pack (Chunk -> String
chunkPath Chunk
chunk) forall a. Semigroup a => a -> a -> a
<> Text
src
Maybe Chunk
Nothing -> Text
src
Maybe (Char, Text)
_ -> Inline
il
fixInternalRefs Inline
il = Inline
il
refMap :: Map Text Chunk
refMap = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Chunk -> Map Text Chunk -> Map Text Chunk
chunkToRefs forall a. Monoid a => a
mempty (ChunkedDoc -> [Chunk]
chunkedChunks ChunkedDoc
chunkedDoc)
chunkToRefs :: Chunk -> Map Text Chunk -> Map Text Chunk
chunkToRefs Chunk
chunk Map Text Chunk
m =
let idents :: [Text]
idents = Chunk -> Text
chunkId Chunk
chunk forall a. a -> [a] -> [a]
: forall {b}. (Walkable Block b, Walkable Inline b) => b -> [Text]
getIdents (Chunk -> [Block]
chunkContents Chunk
chunk)
in forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\Text
ident -> forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Text
ident Chunk
chunk) Map Text Chunk
m [Text]
idents
getIdents :: b -> [Text]
getIdents b
bs = forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query Block -> [Text]
getBlockIdent b
bs forall a. [a] -> [a] -> [a]
++ forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query Inline -> [Text]
getInlineIdent b
bs
getBlockIdent :: Block -> [Text]
getBlockIdent :: Block -> [Text]
getBlockIdent (Div (Text
ident, [Text]
_, [(Text, Text)]
_) [Block]
_)
| Bool -> Bool
not (Text -> Bool
T.null Text
ident) = [Text
ident]
getBlockIdent (Header Int
_ (Text
ident, [Text]
_, [(Text, Text)]
_) [Inline]
_)
| Bool -> Bool
not (Text -> Bool
T.null Text
ident) = [Text
ident]
getBlockIdent (Table (Text
ident,[Text]
_,[(Text, Text)]
_) Caption
_ [ColSpec]
_ TableHead
_ [TableBody]
_ TableFoot
_)
| Bool -> Bool
not (Text -> Bool
T.null Text
ident) = [Text
ident]
getBlockIdent (RawBlock Format
fmt Text
raw)
| Format -> Bool
isHtmlFormat Format
fmt
= forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\Tag Text
tag ->
case Tag Text
tag of
TagOpen{} ->
case forall str.
(Show str, Eq str, StringLike str) =>
str -> Tag str -> str
fromAttrib Text
"id" Tag Text
tag of
Text
"" -> forall a. a -> a
id
Text
x -> (Text
xforall a. a -> [a] -> [a]
:)
Tag Text
_ -> forall a. a -> a
id)
[] (forall str. StringLike str => str -> [Tag str]
parseTags Text
raw)
getBlockIdent Block
_ = []
getInlineIdent :: Inline -> [Text]
getInlineIdent :: Inline -> [Text]
getInlineIdent (Span (Text
ident, [Text]
_, [(Text, Text)]
_) [Inline]
_)
| Bool -> Bool
not (Text -> Bool
T.null Text
ident) = [Text
ident]
getInlineIdent (Link (Text
ident, [Text]
_, [(Text, Text)]
_) [Inline]
_ (Text, Text)
_)
| Bool -> Bool
not (Text -> Bool
T.null Text
ident) = [Text
ident]
getInlineIdent (Image (Text
ident, [Text]
_, [(Text, Text)]
_) [Inline]
_ (Text, Text)
_)
| Bool -> Bool
not (Text -> Bool
T.null Text
ident) = [Text
ident]
getInlineIdent (RawInline Format
fmt Text
raw)
| Format -> Bool
isHtmlFormat Format
fmt
= forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\Tag Text
tag ->
case Tag Text
tag of
TagOpen{} ->
case forall str.
(Show str, Eq str, StringLike str) =>
str -> Tag str -> str
fromAttrib Text
"id" Tag Text
tag of
Text
"" -> forall a. a -> a
id
Text
x -> (Text
xforall a. a -> [a] -> [a]
:)
Tag Text
_ -> forall a. a -> a
id)
[] (forall str. StringLike str => str -> [Tag str]
parseTags Text
raw)
getInlineIdent Inline
_ = []
isHtmlFormat :: Format -> Bool
isHtmlFormat :: Format -> Bool
isHtmlFormat (Format Text
"html") = Bool
True
isHtmlFormat (Format Text
"html4") = Bool
True
isHtmlFormat (Format Text
"html5") = Bool
True
isHtmlFormat Format
_ = Bool
False
makeChunks :: Int -> PathTemplate -> Meta -> [Block] -> [Chunk]
makeChunks :: Int -> PathTemplate -> Meta -> [Block] -> [Chunk]
makeChunks Int
chunklev PathTemplate
pathTemplate Meta
meta = Int -> [Block] -> [Chunk]
secsToChunks Int
1
where
isChunkHeader :: Block -> Bool
isChunkHeader :: Block -> Bool
isChunkHeader (Div (Text
_,Text
"section":[Text]
_,[(Text, Text)]
_) (Header Int
n Attr
_ [Inline]
_:[Block]
_)) = Int
n forall a. Ord a => a -> a -> Bool
<= Int
chunklev
isChunkHeader Block
_ = Bool
False
secsToChunks :: Int -> [Block] -> [Chunk]
secsToChunks :: Int -> [Block] -> [Chunk]
secsToChunks Int
chunknum [Block]
bs =
case forall a. (a -> Bool) -> [a] -> ([a], [a])
break Block -> Bool
isChunkHeader [Block]
bs of
([], []) -> []
([], (d :: Block
d@(Div attr :: Attr
attr@(Text
_,Text
"section":[Text]
_,[(Text, Text)]
_) (h :: Block
h@(Header Int
lvl Attr
_ [Inline]
_) : [Block]
bs')) : [Block]
rest))
| Int
chunklev forall a. Eq a => a -> a -> Bool
== Int
lvl ->
Int -> Block -> Chunk
toChunk Int
chunknum Block
d forall a. a -> [a] -> [a]
:
Int -> [Block] -> [Chunk]
secsToChunks (Int
chunknum forall a. Num a => a -> a -> a
+ Int
1) [Block]
rest
| Int
chunklev forall a. Ord a => a -> a -> Bool
> Int
lvl ->
case forall a. (a -> Bool) -> [a] -> ([a], [a])
break Block -> Bool
isChunkHeader [Block]
bs' of
([Block]
xs, [Block]
ys) -> Int -> Block -> Chunk
toChunk Int
chunknum (Attr -> [Block] -> Block
Div Attr
attr (Block
hforall a. a -> [a] -> [a]
:[Block]
xs)) forall a. a -> [a] -> [a]
:
Int -> [Block] -> [Chunk]
secsToChunks (Int
chunknum forall a. Num a => a -> a -> a
+ Int
1) ([Block]
ys forall a. [a] -> [a] -> [a]
++ [Block]
rest)
([Block]
xs, [Block]
ys) -> Int -> Block -> Chunk
toChunk Int
chunknum
(Attr -> [Block] -> Block
Div (Text
"",[Text
"preamble"],[]) [Block]
xs) forall a. a -> [a] -> [a]
:
Int -> [Block] -> [Chunk]
secsToChunks (Int
chunknum forall a. Num a => a -> a -> a
+ Int
1) [Block]
ys
toChunk :: Int -> Block -> Chunk
toChunk :: Int -> Block -> Chunk
toChunk Int
chunknum
(Div (Text
divid,Text
"section":[Text]
classes,[(Text, Text)]
kvs) (h :: Block
h@(Header Int
lvl Attr
_ [Inline]
ils) : [Block]
bs)) =
Chunk
{ chunkHeading :: [Inline]
chunkHeading = [Inline]
ils
, chunkId :: Text
chunkId = Text
divid
, chunkLevel :: Int
chunkLevel = Int
lvl
, chunkNumber :: Int
chunkNumber = Int
chunknum
, chunkSectionNumber :: Maybe Text
chunkSectionNumber = Maybe Text
secnum
, chunkPath :: String
chunkPath = String
chunkpath
, chunkUp :: Maybe Chunk
chunkUp = forall a. Maybe a
Nothing
, chunkNext :: Maybe Chunk
chunkNext = forall a. Maybe a
Nothing
, chunkPrev :: Maybe Chunk
chunkPrev = forall a. Maybe a
Nothing
, chunkUnlisted :: Bool
chunkUnlisted = Text
"unlisted" forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
classes
, chunkContents :: [Block]
chunkContents =
[Attr -> [Block] -> Block
Div (Text
divid,Text
"section"forall a. a -> [a] -> [a]
:[Text]
classes,[(Text, Text)]
kvs') (Block
h forall a. a -> [a] -> [a]
: [Block]
bs)]
}
where kvs' :: [(Text, Text)]
kvs' = [(Text, Text)]
kvs forall a. [a] -> [a] -> [a]
++ [(Text
"nav-path", String -> Text
T.pack String
chunkpath)]
secnum :: Maybe Text
secnum = forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"number" [(Text, Text)]
kvs
chunkpath :: String
chunkpath = PathTemplate -> Int -> Text -> Text -> Text -> String
resolvePathTemplate PathTemplate
pathTemplate Int
chunknum
(forall a. Walkable Inline a => a -> Text
stringify [Inline]
ils)
Text
divid
(forall a. a -> Maybe a -> a
fromMaybe Text
"" Maybe Text
secnum)
toChunk Int
chunknum (Div (Text
"",[Text
"preamble"],[]) [Block]
bs) =
Chunk
{ chunkHeading :: [Inline]
chunkHeading = Meta -> [Inline]
docTitle Meta
meta
, chunkId :: Text
chunkId = Extensions -> [Inline] -> Text
inlineListToIdentifier forall a. Monoid a => a
mempty forall a b. (a -> b) -> a -> b
$ Meta -> [Inline]
docTitle Meta
meta
, chunkLevel :: Int
chunkLevel = Int
0
, chunkNumber :: Int
chunkNumber = Int
chunknum
, chunkSectionNumber :: Maybe Text
chunkSectionNumber = forall a. Maybe a
Nothing
, chunkPath :: String
chunkPath = PathTemplate -> Int -> Text -> Text -> Text -> String
resolvePathTemplate PathTemplate
pathTemplate Int
chunknum
(forall a. Walkable Inline a => a -> Text
stringify (Meta -> [Inline]
docTitle Meta
meta))
(Extensions -> [Inline] -> Text
inlineListToIdentifier forall a. Monoid a => a
mempty (Meta -> [Inline]
docTitle Meta
meta))
Text
"0"
, chunkUp :: Maybe Chunk
chunkUp = forall a. Maybe a
Nothing
, chunkPrev :: Maybe Chunk
chunkPrev = forall a. Maybe a
Nothing
, chunkNext :: Maybe Chunk
chunkNext = forall a. Maybe a
Nothing
, chunkUnlisted :: Bool
chunkUnlisted = Bool
False
, chunkContents :: [Block]
chunkContents = [Block]
bs
}
toChunk Int
_ Block
b = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"toChunk called on inappropriate block " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show Block
b
rmNavAttrs :: Block -> Block
rmNavAttrs :: Block -> Block
rmNavAttrs (Div (Text
ident,[Text]
classes,[(Text, Text)]
kvs) [Block]
bs) =
Attr -> [Block] -> Block
Div (Text
ident,[Text]
classes,forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {b}. (Text, b) -> Bool
isNavAttr) [(Text, Text)]
kvs) [Block]
bs
where
isNavAttr :: (Text, b) -> Bool
isNavAttr (Text
k,b
_) = Text
"nav-" Text -> Text -> Bool
`T.isPrefixOf` Text
k
rmNavAttrs Block
b = Block
b
resolvePathTemplate :: PathTemplate
-> Int
-> Text
-> Text
-> Text
-> FilePath
resolvePathTemplate :: PathTemplate -> Int -> Text -> Text -> Text -> String
resolvePathTemplate (PathTemplate Text
templ) Int
chunknum Text
headingText Text
ident Text
secnum =
Text -> String
T.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(Char -> Bool) -> Text -> Text
T.filter (\Char
c -> Char
c forall a. Eq a => a -> a -> Bool
/= Char
'/' Bool -> Bool -> Bool
&& Char
c forall a. Eq a => a -> a -> Bool
/= Char
'\\') forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text -> Text -> Text
T.replace Text
"%n" (String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall r. PrintfType r => String -> r
printf String
"%03d" Int
chunknum) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text -> Text -> Text
T.replace Text
"%s" Text
secnum forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text -> Text -> Text
T.replace Text
"%h" Text
headingText forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text -> Text -> Text
T.replace Text
"%i" Text
ident forall a b. (a -> b) -> a -> b
$
Text
templ
newtype PathTemplate =
PathTemplate { PathTemplate -> Text
unPathTemplate :: Text }
deriving (Int -> PathTemplate -> ShowS
[PathTemplate] -> ShowS
PathTemplate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PathTemplate] -> ShowS
$cshowList :: [PathTemplate] -> ShowS
show :: PathTemplate -> String
$cshow :: PathTemplate -> String
showsPrec :: Int -> PathTemplate -> ShowS
$cshowsPrec :: Int -> PathTemplate -> ShowS
Show, String -> PathTemplate
forall a. (String -> a) -> IsString a
fromString :: String -> PathTemplate
$cfromString :: String -> PathTemplate
IsString, Typeable PathTemplate
PathTemplate -> DataType
PathTemplate -> Constr
(forall b. Data b => b -> b) -> PathTemplate -> PathTemplate
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> PathTemplate -> u
forall u. (forall d. Data d => d -> u) -> PathTemplate -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PathTemplate -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PathTemplate -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PathTemplate -> m PathTemplate
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathTemplate -> m PathTemplate
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PathTemplate
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PathTemplate -> c PathTemplate
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PathTemplate)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PathTemplate)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathTemplate -> m PathTemplate
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathTemplate -> m PathTemplate
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathTemplate -> m PathTemplate
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PathTemplate -> m PathTemplate
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PathTemplate -> m PathTemplate
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PathTemplate -> m PathTemplate
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PathTemplate -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PathTemplate -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> PathTemplate -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PathTemplate -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PathTemplate -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PathTemplate -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PathTemplate -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PathTemplate -> r
gmapT :: (forall b. Data b => b -> b) -> PathTemplate -> PathTemplate
$cgmapT :: (forall b. Data b => b -> b) -> PathTemplate -> PathTemplate
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PathTemplate)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PathTemplate)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PathTemplate)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PathTemplate)
dataTypeOf :: PathTemplate -> DataType
$cdataTypeOf :: PathTemplate -> DataType
toConstr :: PathTemplate -> Constr
$ctoConstr :: PathTemplate -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PathTemplate
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PathTemplate
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PathTemplate -> c PathTemplate
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PathTemplate -> c PathTemplate
Data, Typeable, forall x. Rep PathTemplate x -> PathTemplate
forall x. PathTemplate -> Rep PathTemplate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PathTemplate x -> PathTemplate
$cfrom :: forall x. PathTemplate -> Rep PathTemplate x
Generic, [PathTemplate] -> Encoding
[PathTemplate] -> Value
PathTemplate -> Encoding
PathTemplate -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PathTemplate] -> Encoding
$ctoEncodingList :: [PathTemplate] -> Encoding
toJSONList :: [PathTemplate] -> Value
$ctoJSONList :: [PathTemplate] -> Value
toEncoding :: PathTemplate -> Encoding
$ctoEncoding :: PathTemplate -> Encoding
toJSON :: PathTemplate -> Value
$ctoJSON :: PathTemplate -> Value
ToJSON, Value -> Parser [PathTemplate]
Value -> Parser PathTemplate
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PathTemplate]
$cparseJSONList :: Value -> Parser [PathTemplate]
parseJSON :: Value -> Parser PathTemplate
$cparseJSON :: Value -> Parser PathTemplate
FromJSON)
data Chunk =
Chunk
{ Chunk -> [Inline]
chunkHeading :: [Inline]
, Chunk -> Text
chunkId :: Text
, Chunk -> Int
chunkLevel :: Int
, Chunk -> Int
chunkNumber :: Int
, Chunk -> Maybe Text
chunkSectionNumber :: Maybe Text
, Chunk -> String
chunkPath :: FilePath
, Chunk -> Maybe Chunk
chunkUp :: Maybe Chunk
, Chunk -> Maybe Chunk
chunkPrev :: Maybe Chunk
, Chunk -> Maybe Chunk
chunkNext :: Maybe Chunk
, Chunk -> Bool
chunkUnlisted :: Bool
, Chunk -> [Block]
chunkContents :: [Block]
}
deriving (Int -> Chunk -> ShowS
[Chunk] -> ShowS
Chunk -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Chunk] -> ShowS
$cshowList :: [Chunk] -> ShowS
show :: Chunk -> String
$cshow :: Chunk -> String
showsPrec :: Int -> Chunk -> ShowS
$cshowsPrec :: Int -> Chunk -> ShowS
Show, Chunk -> Chunk -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Chunk -> Chunk -> Bool
$c/= :: Chunk -> Chunk -> Bool
== :: Chunk -> Chunk -> Bool
$c== :: Chunk -> Chunk -> Bool
Eq, forall x. Rep Chunk x -> Chunk
forall x. Chunk -> Rep Chunk x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Chunk x -> Chunk
$cfrom :: forall x. Chunk -> Rep Chunk x
Generic)
instance Walkable Inline Chunk where
query :: forall c. Monoid c => (Inline -> c) -> Chunk -> c
query Inline -> c
f Chunk
chunk = forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query Inline -> c
f (Chunk -> [Block]
chunkContents Chunk
chunk)
walk :: (Inline -> Inline) -> Chunk -> Chunk
walk Inline -> Inline
f Chunk
chunk = Chunk
chunk{ chunkContents :: [Block]
chunkContents = forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
f (Chunk -> [Block]
chunkContents Chunk
chunk) }
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Inline -> m Inline) -> Chunk -> m Chunk
walkM Inline -> m Inline
f Chunk
chunk = do
[Block]
contents <- forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
walkM Inline -> m Inline
f (Chunk -> [Block]
chunkContents Chunk
chunk)
forall (m :: * -> *) a. Monad m => a -> m a
return Chunk
chunk{ chunkContents :: [Block]
chunkContents = [Block]
contents }
instance Walkable Block Chunk where
query :: forall c. Monoid c => (Block -> c) -> Chunk -> c
query Block -> c
f Chunk
chunk = forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query Block -> c
f (Chunk -> [Block]
chunkContents Chunk
chunk)
walk :: (Block -> Block) -> Chunk -> Chunk
walk Block -> Block
f Chunk
chunk = Chunk
chunk{ chunkContents :: [Block]
chunkContents = forall a b. Walkable a b => (a -> a) -> b -> b
walk Block -> Block
f (Chunk -> [Block]
chunkContents Chunk
chunk) }
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Block -> m Block) -> Chunk -> m Chunk
walkM Block -> m Block
f Chunk
chunk = do
[Block]
contents <- forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
walkM Block -> m Block
f (Chunk -> [Block]
chunkContents Chunk
chunk)
forall (m :: * -> *) a. Monad m => a -> m a
return Chunk
chunk{ chunkContents :: [Block]
chunkContents = [Block]
contents }
data ChunkedDoc =
ChunkedDoc
{ ChunkedDoc -> Meta
chunkedMeta :: Meta
, ChunkedDoc -> Tree SecInfo
chunkedTOC :: Tree SecInfo
, ChunkedDoc -> [Chunk]
chunkedChunks :: [Chunk]
} deriving (Int -> ChunkedDoc -> ShowS
[ChunkedDoc] -> ShowS
ChunkedDoc -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChunkedDoc] -> ShowS
$cshowList :: [ChunkedDoc] -> ShowS
show :: ChunkedDoc -> String
$cshow :: ChunkedDoc -> String
showsPrec :: Int -> ChunkedDoc -> ShowS
$cshowsPrec :: Int -> ChunkedDoc -> ShowS
Show, ChunkedDoc -> ChunkedDoc -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChunkedDoc -> ChunkedDoc -> Bool
$c/= :: ChunkedDoc -> ChunkedDoc -> Bool
== :: ChunkedDoc -> ChunkedDoc -> Bool
$c== :: ChunkedDoc -> ChunkedDoc -> Bool
Eq, forall x. Rep ChunkedDoc x -> ChunkedDoc
forall x. ChunkedDoc -> Rep ChunkedDoc x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChunkedDoc x -> ChunkedDoc
$cfrom :: forall x. ChunkedDoc -> Rep ChunkedDoc x
Generic)
instance Walkable Inline ChunkedDoc where
query :: forall c. Monoid c => (Inline -> c) -> ChunkedDoc -> c
query Inline -> c
f ChunkedDoc
doc = forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query Inline -> c
f (ChunkedDoc -> [Chunk]
chunkedChunks ChunkedDoc
doc) forall a. Semigroup a => a -> a -> a
<> forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query Inline -> c
f (ChunkedDoc -> Meta
chunkedMeta ChunkedDoc
doc)
walk :: (Inline -> Inline) -> ChunkedDoc -> ChunkedDoc
walk Inline -> Inline
f ChunkedDoc
doc = ChunkedDoc
doc{ chunkedMeta :: Meta
chunkedMeta = forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
f (ChunkedDoc -> Meta
chunkedMeta ChunkedDoc
doc)
, chunkedChunks :: [Chunk]
chunkedChunks = forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
f (ChunkedDoc -> [Chunk]
chunkedChunks ChunkedDoc
doc)
}
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Inline -> m Inline) -> ChunkedDoc -> m ChunkedDoc
walkM Inline -> m Inline
f ChunkedDoc
doc = do
Meta
meta' <- forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
walkM Inline -> m Inline
f (ChunkedDoc -> Meta
chunkedMeta ChunkedDoc
doc)
[Chunk]
chunks' <- forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
walkM Inline -> m Inline
f (ChunkedDoc -> [Chunk]
chunkedChunks ChunkedDoc
doc)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ChunkedDoc
doc{ chunkedMeta :: Meta
chunkedMeta = Meta
meta'
, chunkedChunks :: [Chunk]
chunkedChunks = [Chunk]
chunks' }
instance Walkable Block ChunkedDoc where
query :: forall c. Monoid c => (Block -> c) -> ChunkedDoc -> c
query Block -> c
f ChunkedDoc
doc = forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query Block -> c
f (ChunkedDoc -> [Chunk]
chunkedChunks ChunkedDoc
doc) forall a. Semigroup a => a -> a -> a
<> forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query Block -> c
f (ChunkedDoc -> Meta
chunkedMeta ChunkedDoc
doc)
walk :: (Block -> Block) -> ChunkedDoc -> ChunkedDoc
walk Block -> Block
f ChunkedDoc
doc = ChunkedDoc
doc{ chunkedMeta :: Meta
chunkedMeta = forall a b. Walkable a b => (a -> a) -> b -> b
walk Block -> Block
f (ChunkedDoc -> Meta
chunkedMeta ChunkedDoc
doc)
, chunkedChunks :: [Chunk]
chunkedChunks = forall a b. Walkable a b => (a -> a) -> b -> b
walk Block -> Block
f (ChunkedDoc -> [Chunk]
chunkedChunks ChunkedDoc
doc)
}
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Block -> m Block) -> ChunkedDoc -> m ChunkedDoc
walkM Block -> m Block
f ChunkedDoc
doc = do
Meta
meta' <- forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
walkM Block -> m Block
f (ChunkedDoc -> Meta
chunkedMeta ChunkedDoc
doc)
[Chunk]
chunks' <- forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
walkM Block -> m Block
f (ChunkedDoc -> [Chunk]
chunkedChunks ChunkedDoc
doc)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ChunkedDoc
doc{ chunkedMeta :: Meta
chunkedMeta = Meta
meta'
, chunkedChunks :: [Chunk]
chunkedChunks = [Chunk]
chunks' }
data SecInfo =
SecInfo
{ SecInfo -> [Inline]
secTitle :: [Inline]
, SecInfo -> Maybe Text
secNumber :: Maybe Text
, SecInfo -> Text
secId :: Text
, SecInfo -> Text
secPath :: Text
, SecInfo -> Int
secLevel :: Int
} deriving (Int -> SecInfo -> ShowS
[SecInfo] -> ShowS
SecInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SecInfo] -> ShowS
$cshowList :: [SecInfo] -> ShowS
show :: SecInfo -> String
$cshow :: SecInfo -> String
showsPrec :: Int -> SecInfo -> ShowS
$cshowsPrec :: Int -> SecInfo -> ShowS
Show, SecInfo -> SecInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SecInfo -> SecInfo -> Bool
$c/= :: SecInfo -> SecInfo -> Bool
== :: SecInfo -> SecInfo -> Bool
$c== :: SecInfo -> SecInfo -> Bool
Eq, forall x. Rep SecInfo x -> SecInfo
forall x. SecInfo -> Rep SecInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SecInfo x -> SecInfo
$cfrom :: forall x. SecInfo -> Rep SecInfo x
Generic)
instance Walkable Inline SecInfo where
query :: forall c. Monoid c => (Inline -> c) -> SecInfo -> c
query Inline -> c
f SecInfo
sec = forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query Inline -> c
f (SecInfo -> [Inline]
secTitle SecInfo
sec)
walk :: (Inline -> Inline) -> SecInfo -> SecInfo
walk Inline -> Inline
f SecInfo
sec = SecInfo
sec{ secTitle :: [Inline]
secTitle = forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
f (SecInfo -> [Inline]
secTitle SecInfo
sec) }
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Inline -> m Inline) -> SecInfo -> m SecInfo
walkM Inline -> m Inline
f SecInfo
sec = do
[Inline]
st <- forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
walkM Inline -> m Inline
f (SecInfo -> [Inline]
secTitle SecInfo
sec)
forall (m :: * -> *) a. Monad m => a -> m a
return SecInfo
sec{ secTitle :: [Inline]
secTitle = [Inline]
st }
toTOCTree :: [Block] -> Tree SecInfo
toTOCTree :: [Block] -> Tree SecInfo
toTOCTree =
forall a. a -> [Tree a] -> Tree a
Node SecInfo{ secTitle :: [Inline]
secTitle = []
, secNumber :: Maybe Text
secNumber = forall a. Maybe a
Nothing
, secId :: Text
secId = Text
""
, secPath :: Text
secPath = Text
""
, secLevel :: Int
secLevel = Int
0 } forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Block -> [Tree SecInfo] -> [Tree SecInfo]
go []
where
go :: Block -> [Tree SecInfo] -> [Tree SecInfo]
go :: Block -> [Tree SecInfo] -> [Tree SecInfo]
go (Div (Text
ident,[Text]
_,[(Text, Text)]
_) (Header Int
lev (Text
_,[Text]
classes,[(Text, Text)]
kvs) [Inline]
ils : [Block]
subsecs))
| Bool -> Bool
not (forall a. Maybe a -> Bool
isNothing (forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"number" [(Text, Text)]
kvs) Bool -> Bool -> Bool
&& Text
"unlisted" forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
classes)
= ((forall a. a -> [Tree a] -> Tree a
Node SecInfo{ secTitle :: [Inline]
secTitle = [Inline]
ils
, secNumber :: Maybe Text
secNumber = forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"number" [(Text, Text)]
kvs
, secId :: Text
secId = Text
ident
, secPath :: Text
secPath = Text
""
, secLevel :: Int
secLevel = Int
lev } (forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Block -> [Tree SecInfo] -> [Tree SecInfo]
go [] [Block]
subsecs)) forall a. a -> [a] -> [a]
:)
go (Div Attr
_ [d :: Block
d@Div{}]) = Block -> [Tree SecInfo] -> [Tree SecInfo]
go Block
d
go Block
_ = forall a. a -> a
id
fixTOCTreePaths :: [Chunk] -> Tree SecInfo -> Tree SecInfo
fixTOCTreePaths :: [Chunk] -> Tree SecInfo -> Tree SecInfo
fixTOCTreePaths [Chunk]
chunks = String -> Tree SecInfo -> Tree SecInfo
go String
""
where
idMap :: Map Text String
idMap = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\Chunk
chunk -> forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert (Chunk -> Text
chunkId Chunk
chunk) (Chunk -> String
chunkPath Chunk
chunk))
forall a. Monoid a => a
mempty [Chunk]
chunks
go :: FilePath -> Tree SecInfo -> Tree SecInfo
go :: String -> Tree SecInfo -> Tree SecInfo
go String
fp (Node SecInfo
secinfo [Tree SecInfo]
subtrees) =
let newpath :: Maybe String
newpath = forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (SecInfo -> Text
secId SecInfo
secinfo) Map Text String
idMap
fp' :: String
fp' = forall a. a -> Maybe a -> a
fromMaybe String
fp Maybe String
newpath
fragment :: Text
fragment = case Maybe String
newpath of
Maybe String
Nothing -> Text
"#" forall a. Semigroup a => a -> a -> a
<> SecInfo -> Text
secId SecInfo
secinfo
Just String
_ -> Text
""
in forall a. a -> [Tree a] -> Tree a
Node SecInfo
secinfo{ secPath :: Text
secPath = String -> Text
T.pack String
fp' forall a. Semigroup a => a -> a -> a
<> Text
fragment }
(forall a b. (a -> b) -> [a] -> [b]
map (String -> Tree SecInfo -> Tree SecInfo
go String
fp') [Tree SecInfo]
subtrees)
tocEntryToLink :: Bool -> SecInfo -> [Inline]
tocEntryToLink :: Bool -> SecInfo -> [Inline]
tocEntryToLink Bool
includeNumbers SecInfo
secinfo = [Inline]
headerLink
where
addNumber :: [Inline] -> [Inline]
addNumber = case SecInfo -> Maybe Text
secNumber SecInfo
secinfo of
Just Text
num | Bool
includeNumbers
-> (Attr -> [Inline] -> Inline
Span (Text
"",[Text
"toc-section-number"],[])
[Text -> Inline
Str Text
num] forall a. a -> [a] -> [a]
:) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inline
Space forall a. a -> [a] -> [a]
:)
Maybe Text
_ -> forall a. a -> a
id
clean :: Inline -> [Inline]
clean (Link Attr
_ [Inline]
xs (Text, Text)
_) = [Inline]
xs
clean (Note [Block]
_) = []
clean Inline
x = [Inline
x]
anchor :: Text
anchor = if Text -> Bool
T.null (SecInfo -> Text
secPath SecInfo
secinfo)
then if Text -> Bool
T.null (SecInfo -> Text
secId SecInfo
secinfo)
then Text
""
else Text
"#" forall a. Semigroup a => a -> a -> a
<> SecInfo -> Text
secId SecInfo
secinfo
else SecInfo -> Text
secPath SecInfo
secinfo
headerText :: [Inline]
headerText = [Inline] -> [Inline]
addNumber forall a b. (a -> b) -> a -> b
$ forall a b. Walkable a b => (a -> a) -> b -> b
walk (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Inline -> [Inline]
clean) (SecInfo -> [Inline]
secTitle SecInfo
secinfo)
headerLink :: [Inline]
headerLink = if Text -> Bool
T.null Text
anchor
then [Inline]
headerText
else [Attr -> [Inline] -> (Text, Text) -> Inline
Link ((if Text -> Bool
T.null (SecInfo -> Text
secId SecInfo
secinfo)
then Text
""
else Text
"toc-" forall a. Semigroup a => a -> a -> a
<> SecInfo -> Text
secId SecInfo
secinfo), [], [])
[Inline]
headerText (Text
anchor, Text
"")]
tocToList :: Bool -> Int -> Tree SecInfo -> Block
tocToList :: Bool -> Int -> Tree SecInfo -> Block
tocToList Bool
includeNumbers Int
tocDepth (Node SecInfo
_ [Tree SecInfo]
subtrees) = [[Block]] -> Block
BulletList ([Tree SecInfo] -> [[Block]]
toItems [Tree SecInfo]
subtrees)
where
toItems :: [Tree SecInfo] -> [[Block]]
toItems = forall a b. (a -> b) -> [a] -> [b]
map Tree SecInfo -> [Block]
go forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter Tree SecInfo -> Bool
isBelowTocDepth
isBelowTocDepth :: Tree SecInfo -> Bool
isBelowTocDepth (Node SecInfo
sec [Tree SecInfo]
_) = SecInfo -> Int
secLevel SecInfo
sec forall a. Ord a => a -> a -> Bool
<= Int
tocDepth
go :: Tree SecInfo -> [Block]
go (Node SecInfo
secinfo [Tree SecInfo]
xs) =
[Inline] -> Block
Plain (Bool -> SecInfo -> [Inline]
tocEntryToLink Bool
includeNumbers SecInfo
secinfo) forall a. a -> [a] -> [a]
:
case [Tree SecInfo] -> [[Block]]
toItems [Tree SecInfo]
xs of
[] -> []
[[Block]]
ys -> [[[Block]] -> Block
BulletList [[Block]]
ys]