Skip to content

Commit

Permalink
Add endnotes support
Browse files Browse the repository at this point in the history
  • Loading branch information
Alexander Krotov committed May 9, 2018
1 parent 5f33d2e commit 3cd5979
Show file tree
Hide file tree
Showing 89 changed files with 311 additions and 188 deletions.
15 changes: 15 additions & 0 deletions data/docx/word/styles.xml
Original file line number Diff line number Diff line change
Expand Up @@ -337,6 +337,14 @@
<w:unhideWhenUsed />
<w:qFormat />
</w:style>
<w:style w:type="paragraph" w:styleId="EndnoteText">
<w:name w:val="Endnote Text" />
<w:basedOn w:val="Normal" />
<w:next w:val="EndnoteText" />
<w:uiPriority w:val="9" />
<w:unhideWhenUsed />
<w:qFormat />
</w:style>
<w:style w:type="character" w:default="1" w:styleId="DefaultParagraphFont">
<w:name w:val="Default Paragraph Font" />
<w:semiHidden />
Expand Down Expand Up @@ -428,6 +436,13 @@
<w:vertAlign w:val="superscript" />
</w:rPr>
</w:style>
<w:style w:type="character" w:styleId="EndnoteReference">
<w:name w:val="Endnote Reference" />
<w:basedOn w:val="BodyTextChar" />
<w:rPr>
<w:vertAlign w:val="superscript" />
</w:rPr>
</w:style>
<w:style w:type="character" w:styleId="Hyperlink">
<w:name w:val="Hyperlink" />
<w:basedOn w:val="BodyTextChar" />
Expand Down
9 changes: 6 additions & 3 deletions data/pandoc.lua
Original file line number Diff line number Diff line change
Expand Up @@ -581,11 +581,14 @@ M.InlineMath = M.Inline:create_constructor(

--- Creates a Note inline element
-- @function Note
-- @tparam {Block,...} content footnote block content
-- @tparam "Footnote"|"Endnote" note type
-- @tparam {Block,...} content note block content
M.Note = M.Inline:create_constructor(
"Note",
function(content) return {c = ensureList(content)} end,
"content"
function(notetype, content)
return {c = {notetype, ensureList(content)}}
end,
{"notetype", "content"}
)

--- Creates a Quoted inline element given the quote type and quoted content.
Expand Down
9 changes: 7 additions & 2 deletions src/Text/Pandoc/Lua/StackInstances.hs
Original file line number Diff line number Diff line change
Expand Up @@ -142,6 +142,11 @@ instance ToLuaStack QuoteType where
instance FromLuaStack QuoteType where
peek idx = safeRead' =<< peek idx

instance ToLuaStack NoteType where
push = push . show
instance FromLuaStack NoteType where
peek idx = safeRead' =<< peek idx

instance ToLuaStack Double where
push = push . (realToFrac :: Double -> LuaNumber)
instance FromLuaStack Double where
Expand Down Expand Up @@ -254,7 +259,7 @@ pushInline = \case
Image attr alt (src,tit) -> pushViaConstructor "Image" alt src tit (LuaAttr attr)
LineBreak -> pushViaConstructor "LineBreak"
Link attr lst (src,tit) -> pushViaConstructor "Link" lst src tit (LuaAttr attr)
Note blcks -> pushViaConstructor "Note" blcks
Note t blcks -> pushViaConstructor "Note" t blcks
Math mty str -> pushViaConstructor "Math" mty str
Quoted qt inlns -> pushViaConstructor "Quoted" qt inlns
RawInline f cs -> pushViaConstructor "RawInline" f cs
Expand Down Expand Up @@ -282,7 +287,7 @@ peekInline idx = defineHowTo "get Inline value" $ do
"Link" -> (\(LuaAttr attr, lst, tgt) -> Link attr lst tgt)
<$> elementContent
"LineBreak" -> return LineBreak
"Note" -> Note <$> elementContent
"Note" -> uncurry Note <$> elementContent
"Math" -> uncurry Math <$> elementContent
"Quoted" -> uncurry Quoted <$> elementContent
"RawInline" -> uncurry RawInline <$> elementContent
Expand Down
8 changes: 4 additions & 4 deletions src/Text/Pandoc/Readers/Docx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ implemented, [-] means partially implemented):
- [X] Link (links to an arbitrary bookmark create a span with the target as
id and "anchor" class)
- [X] Image
- [X] Note (Footnotes and Endnotes are silently combined.)
- [X] Note
-}

module Text.Pandoc.Readers.Docx
Expand Down Expand Up @@ -333,12 +333,12 @@ runToInlines (Run rs runElems)
let ils = smushInlines (map runElemToInlines runElems)
transform <- runStyleToTransform rPr
return $ transform ils
runToInlines (Footnote bps) = do
runToInlines (RunFootnote bps) = do
blksList <- smushBlocks <$> mapM bodyPartToBlocks bps
return $ note blksList
runToInlines (Endnote bps) = do
runToInlines (RunEndnote bps) = do
blksList <- smushBlocks <$> mapM bodyPartToBlocks bps
return $ note blksList
return $ endNote blksList
runToInlines (InlineDrawing fp title alt bs ext) = do
(lift . lift) $ P.insertMedia fp Nothing bs
return $ imageWith (extentToAttr ext) fp title $ text alt
Expand Down
12 changes: 6 additions & 6 deletions src/Text/Pandoc/Readers/Docx/Parse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -285,8 +285,8 @@ data ParPart = PlainRun Run
deriving Show

data Run = Run RunStyle [RunElem]
| Footnote [BodyPart]
| Endnote [BodyPart]
| RunFootnote [BodyPart]
| RunEndnote [BodyPart]
| InlineDrawing FilePath String String B.ByteString Extent -- title, alt
| InlineChart -- placeholder
deriving Show
Expand Down Expand Up @@ -918,16 +918,16 @@ childElemToRun ns element
notes <- asks envNotes
case lookupFootnote fnId notes of
Just e -> do bps <- local (\r -> r {envLocation=InFootnote}) $ mapD (elemToBodyPart ns) (elChildren e)
return $ Footnote bps
Nothing -> return $ Footnote []
return $ RunFootnote bps
Nothing -> return $ RunFootnote []
childElemToRun ns element
| isElem ns "w" "endnoteReference" element
, Just enId <- findAttrByName ns "w" "id" element = do
notes <- asks envNotes
case lookupEndnote enId notes of
Just e -> do bps <- local (\r -> r {envLocation=InEndnote}) $ mapD (elemToBodyPart ns) (elChildren e)
return $ Endnote bps
Nothing -> return $ Endnote []
return $ RunEndnote bps
Nothing -> return $ RunEndnote []
childElemToRun _ _ = throwError WrongElem

elemToRun :: NameSpaces -> Element -> D Run
Expand Down
2 changes: 1 addition & 1 deletion src/Text/Pandoc/Readers/HTML.hs
Original file line number Diff line number Diff line change
Expand Up @@ -112,7 +112,7 @@ replaceNotes :: PandocMonad m => [Block] -> TagParser m [Block]
replaceNotes = walkM replaceNotes'

replaceNotes' :: PandocMonad m => Inline -> TagParser m Inline
replaceNotes' (RawInline (Format "noteref") ref) = maybe (Str "") (Note . B.toList) . lookup ref <$> getNotes
replaceNotes' (RawInline (Format "noteref") ref) = maybe (Str "") (Note Footnote . B.toList) . lookup ref <$> getNotes
where
getNotes = noteTable <$> getState
replaceNotes' x = return x
Expand Down
31 changes: 21 additions & 10 deletions src/Text/Pandoc/Readers/Muse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -498,10 +498,21 @@ paraUntil end = do
guard $ not $ museInPara state
first (fmap B.para) <$> paraContentsUntil end

noteMarker :: PandocMonad m => MuseParser m String
noteMarker = try $ do
char '['
(:) <$> oneOf "123456789" <*> manyTill digit (char ']')
noteBrackets :: NoteType -> (Char, Char)
noteBrackets nt =
case nt of
Endnote -> ('{', '}')
_ -> ('[', ']')

noteMarker :: PandocMonad m => NoteType -> MuseParser m (NoteType, String)
noteMarker nt = try $ do
char l
m <- (:) <$> oneOf "123456789" <*> manyTill digit (char r)
return (nt, [l] ++ m ++ [r])
where (l, r) = noteBrackets nt

anyNoteMarker :: PandocMonad m => MuseParser m (NoteType, String)
anyNoteMarker = noteMarker Footnote <|> noteMarker Endnote

-- Amusewiki version of note
-- Parsing is similar to list item, except that note marker is used instead of list marker
Expand All @@ -510,7 +521,7 @@ amuseNoteBlockUntil :: PandocMonad m
-> MuseParser m (F Blocks, a)
amuseNoteBlockUntil end = try $ do
guardEnabled Ext_amuse
ref <- noteMarker <* spaceChar
(_, ref) <- anyNoteMarker <* spaceChar
pos <- getPosition
updateState (\st -> st { museInPara = False })
(content, e) <- listItemContentsUntil (sourceColumn pos - 1) (fail "x") end
Expand All @@ -526,7 +537,7 @@ emacsNoteBlock :: PandocMonad m => MuseParser m (F Blocks)
emacsNoteBlock = try $ do
guardDisabled Ext_amuse
pos <- getPosition
ref <- noteMarker <* skipSpaces
(_, ref) <- anyNoteMarker <* skipSpaces
content <- mconcat <$> blocksTillNote
oldnotes <- museNotes <$> getState
when (M.member ref oldnotes)
Expand All @@ -535,7 +546,7 @@ emacsNoteBlock = try $ do
return mempty
where
blocksTillNote =
many1Till parseBlock (eof <|> () <$ lookAhead noteMarker)
many1Till parseBlock (eof <|> () <$ lookAhead anyNoteMarker)

--
-- Verse markup
Expand Down Expand Up @@ -814,15 +825,15 @@ footnote :: PandocMonad m => MuseParser m (F Inlines)
footnote = try $ do
inLink <- museInLink <$> getState
guard $ not inLink
ref <- noteMarker
(notetype, ref) <- anyNoteMarker
return $ do
notes <- asksF museNotes
case M.lookup ref notes of
Nothing -> return $ B.str $ "[" ++ ref ++ "]"
Nothing -> return $ B.str ref
Just (_pos, contents) -> do
st <- askF
let contents' = runF contents st { museNotes = M.delete ref (museNotes st) }
return $ B.note contents'
return $ B.singleton $ Note notetype $ B.toList contents'

whitespace :: PandocMonad m => MuseParser m (F Inlines)
whitespace = try $ do
Expand Down
8 changes: 6 additions & 2 deletions src/Text/Pandoc/Readers/Odt/ContentReader.hs
Original file line number Diff line number Diff line change
Expand Up @@ -696,8 +696,12 @@ read_link = matchingElement NsText "a"

read_note :: InlineMatcher
read_note = matchingElement NsText "note"
$ liftA note
$ matchChildContent' [ read_note_body ]
$ liftA2 (\nt -> singleton . Note nt . toList)
(liftA makeNoteType (findAttrWithDefault NsText "note-class" "footnote"))
(matchChildContent' [ read_note_body ])
where
makeNoteType :: String -> NoteType
makeNoteType x = if x == "endnote" then Endnote else Footnote

read_note_body :: BlockMatcher
read_note_body = matchingElement NsText "note-body"
Expand Down
4 changes: 2 additions & 2 deletions src/Text/Pandoc/Shared.hs
Original file line number Diff line number Diff line change
Expand Up @@ -348,8 +348,8 @@ removeFormatting = query go . walk (deNote . deQuote)
go _ = []

deNote :: Inline -> Inline
deNote (Note _) = Str ""
deNote x = x
deNote (Note _ _) = Str ""
deNote x = x

deQuote :: Inline -> Inline
deQuote (Quoted SingleQuote xs) =
Expand Down
8 changes: 4 additions & 4 deletions src/Text/Pandoc/Writers/AsciiDoc.hs
Original file line number Diff line number Diff line change
Expand Up @@ -479,13 +479,13 @@ inlineToAsciiDoc opts (Image attr alternate (src, tit)) = do
then empty
else "," <> cat (intersperse "," dimList)
return $ "image:" <> text src <> "[" <> linktext <> linktitle <> dims <> "]"
inlineToAsciiDoc opts (Note [Para inlines]) =
inlineToAsciiDoc opts (Note [Plain inlines])
inlineToAsciiDoc opts (Note [Plain inlines]) = do
inlineToAsciiDoc opts (Note t [Para inlines]) =
inlineToAsciiDoc opts (Note t [Plain inlines])
inlineToAsciiDoc opts (Note _ [Plain inlines]) = do
contents <- inlineListToAsciiDoc opts inlines
return $ text "footnote:[" <> contents <> "]"
-- asciidoc can't handle blank lines in notes
inlineToAsciiDoc _ (Note _) = return "[multiblock footnote omitted]"
inlineToAsciiDoc _ (Note _ _) = return "[multiblock footnote omitted]"
inlineToAsciiDoc opts (Span (ident,_,_) ils) = do
let identifier = if null ident then empty else ("[[" <> text ident <> "]]")
contents <- inlineListToAsciiDoc opts ils
Expand Down
4 changes: 2 additions & 2 deletions src/Text/Pandoc/Writers/CommonMark.hs
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,7 @@ softBreakToSpace SoftBreak = Space
softBreakToSpace x = x

processNotes :: Inline -> State [[Block]] Inline
processNotes (Note bs) = do
processNotes (Note _ bs) = do
modify (bs :)
notes <- get
return $ Str $ "[" ++ show (length notes) ++ "]"
Expand Down Expand Up @@ -312,5 +312,5 @@ inlineToNodes opts (Span attr ils) =
[node (HTML_INLINE (T.pack "</span>")) []]) ++)
else (nodes ++)
inlineToNodes opts (Cite _ ils) = (inlinesToNodes opts ils ++)
inlineToNodes _ (Note _) = id -- should not occur
inlineToNodes _ (Note{}) = id -- should not occur
-- we remove Note elements in preprocessing
2 changes: 1 addition & 1 deletion src/Text/Pandoc/Writers/ConTeXt.hs
Original file line number Diff line number Diff line change
Expand Up @@ -461,7 +461,7 @@ inlineToConTeXt (Image attr@(_,cls,_) _ (src, _)) = do
then src
else unEscapeString src
return $ braces $ "\\externalfigure" <> brackets (text src') <> dims <> clas
inlineToConTeXt (Note contents) = do
inlineToConTeXt (Note _ contents) = do
contents' <- blockListToConTeXt contents
let codeBlock x@(CodeBlock _ _) = [x]
codeBlock _ = []
Expand Down
2 changes: 1 addition & 1 deletion src/Text/Pandoc/Writers/Custom.hs
Original file line number Diff line number Diff line change
Expand Up @@ -244,7 +244,7 @@ inlineToCustom (Link attr txt (src,tit)) =
inlineToCustom (Image attr alt (src,tit)) =
callFunc "Image" (Stringify alt) src tit (attrToMap attr)

inlineToCustom (Note contents) = callFunc "Note" (Stringify contents)
inlineToCustom (Note noteType contents) = callFunc "Note" (Stringify contents) noteType

inlineToCustom (Span attr items) =
callFunc "Span" (Stringify items) (attrToMap attr)
4 changes: 2 additions & 2 deletions src/Text/Pandoc/Writers/Docbook.hs
Original file line number Diff line number Diff line change
Expand Up @@ -317,7 +317,7 @@ hasLineBreaks :: [Inline] -> Bool
hasLineBreaks = getAny . query isLineBreak . walk removeNote
where
removeNote :: Inline -> Inline
removeNote (Note _) = Str ""
removeNote (Note{}) = Str ""
removeNote x = x
isLineBreak :: Inline -> Any
isLineBreak LineBreak = Any True
Expand Down Expand Up @@ -429,7 +429,7 @@ inlineToDocbook opts (Image attr _ (src, tit)) = return $
inTagsIndented "title" (text $ escapeStringForXML tit)
in inTagsIndented "inlinemediaobject" $ inTagsIndented "imageobject" $
titleDoc $$ imageToDocbook opts attr src
inlineToDocbook opts (Note contents) =
inlineToDocbook opts (Note _ contents) =
inTagsIndented "footnote" <$> blocksToDocbook opts contents

isMathML :: HTMLMathMethod -> Bool
Expand Down
Loading

0 comments on commit 3cd5979

Please sign in to comment.