aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/FB2.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/FB2.hs')
-rw-r--r--src/Text/Pandoc/Writers/FB2.hs26
1 files changed, 6 insertions, 20 deletions
diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs
index 7fcb50b05..a46011a8f 100644
--- a/src/Text/Pandoc/Writers/FB2.hs
+++ b/src/Text/Pandoc/Writers/FB2.hs
@@ -118,6 +118,9 @@ description meta' = do
bt <- booktitle meta'
let as = authors meta'
dd <- docdate meta'
+ annotation <- case lookupMeta "abstract" meta' of
+ Just (MetaBlocks bs) -> (list . el "annotation") <$> cMapM blockToXml bs
+ _ -> pure mempty
let lang = case lookupMeta "lang" meta' of
Just (MetaInlines [Str s]) -> [el "lang" $ iso639 s]
Just (MetaString s) -> [el "lang" $ iso639 s]
@@ -132,7 +135,7 @@ description meta' = do
Just (MetaString s) -> coverimage s
_ -> return []
return $ el "description"
- [ el "title-info" (genre : (bt ++ as ++ dd ++ lang))
+ [ el "title-info" (genre : (bt ++ annotation ++ as ++ dd ++ lang))
, el "document-info" (el "program-used" "pandoc" : coverpage)
]
@@ -311,9 +314,6 @@ isMimeType s =
footnoteID :: Int -> String
footnoteID i = "n" ++ show i
-linkID :: Int -> String
-linkID i = "l" ++ show i
-
-- | Convert a block-level Pandoc's element to FictionBook XML representation.
blockToXml :: PandocMonad m => Block -> FBM m [Content]
blockToXml (Plain ss) = cMapM toXml ss -- FIXME: can lead to malformed FB2
@@ -452,23 +452,9 @@ toXml (Math _ formula) = insertMath InlineImage formula
toXml il@(RawInline _ _) = do
report $ InlineNotRendered il
return [] -- raw TeX and raw HTML are suppressed
-toXml (Link _ text (url,ttl)) = do
- fns <- footnotes `liftM` get
- let n = 1 + length fns
- let ln_id = linkID n
- let ln_ref = list . el "sup" . txt $ "[" ++ show n ++ "]"
+toXml (Link _ text (url,_)) = do
ln_text <- cMapM toXml text
- let ln_desc =
- let ttl' = dropWhile isSpace ttl
- in if null ttl'
- then list . el "p" $ el "code" url
- else list . el "p" $ [ txt (ttl' ++ ": "), el "code" url ]
- modify (\s -> s { footnotes = (n, ln_id, ln_desc) : fns })
- return $ ln_text ++
- [ el "a"
- ( [ attr ("l","href") ('#':ln_id)
- , uattr "type" "note" ]
- , ln_ref) ]
+ return [ el "a" ( [ attr ("l","href") url ], ln_text) ]
toXml img@Image{} = insertImage InlineImage img
toXml (Note bs) = do
fns <- footnotes `liftM` get