FB2 writer: bring functions to toplevel.

This is the first of a number of changes to bring the FB2 writer a bit
closer to the idioms used elsewhere in pandoc, so it can be more easily
converted to using the pure functions from Free.
This commit is contained in:
Jesse Rosenthal 2016-11-18 06:18:12 -05:00 committed by John MacFarlane
parent 9ac1303660
commit d97fb5f3c6

View file

@ -94,53 +94,59 @@ writeFB2 opts (Pandoc meta blocks) = flip evalStateT newFB $ do
xlink = "http://www.w3.org/1999/xlink" xlink = "http://www.w3.org/1999/xlink"
in [ uattr "xmlns" xmlns in [ uattr "xmlns" xmlns
, attr ("xmlns", "l") xlink ] , attr ("xmlns", "l") xlink ]
--
frontpage :: Meta -> FBM [Content]
frontpage meta' = do frontpage :: Meta -> FBM [Content]
t <- cMapM toXml . docTitle $ meta' frontpage meta' = do
return $ t <- cMapM toXml . docTitle $ meta'
[ el "title" (el "p" t) return $
, el "annotation" (map (el "p" . cMap plain) [ el "title" (el "p" t)
(docAuthors meta' ++ [docDate meta'])) , el "annotation" (map (el "p" . cMap plain)
] (docAuthors meta' ++ [docDate meta']))
description :: Meta -> FBM Content ]
description meta' = do
bt <- booktitle meta' description :: Meta -> FBM Content
let as = authors meta' description meta' = do
dd <- docdate meta' bt <- booktitle meta'
return $ el "description" let as = authors meta'
[ el "title-info" (bt ++ as ++ dd) dd <- docdate meta'
, el "document-info" [ el "program-used" "pandoc" ] -- FIXME: +version return $ el "description"
] [ el "title-info" (bt ++ as ++ dd)
booktitle :: Meta -> FBM [Content] , el "document-info" [ el "program-used" "pandoc" ] -- FIXME: +version
booktitle meta' = do ]
t <- cMapM toXml . docTitle $ meta'
return $ if null t booktitle :: Meta -> FBM [Content]
then [] booktitle meta' = do
else [ el "book-title" t ] t <- cMapM toXml . docTitle $ meta'
authors :: Meta -> [Content] return $ if null t
authors meta' = cMap author (docAuthors meta') then []
author :: [Inline] -> [Content] else [ el "book-title" t ]
author ss =
let ws = words . cMap plain $ ss authors :: Meta -> [Content]
email = (el "email") `fmap` (take 1 $ filter ('@' `elem`) ws) authors meta' = cMap author (docAuthors meta')
ws' = filter ('@' `notElem`) ws
names = case ws' of author :: [Inline] -> [Content]
(nickname:[]) -> [ el "nickname" nickname ] author ss =
(fname:lname:[]) -> [ el "first-name" fname let ws = words . cMap plain $ ss
, el "last-name" lname ] email = (el "email") `fmap` (take 1 $ filter ('@' `elem`) ws)
(fname:rest) -> [ el "first-name" fname ws' = filter ('@' `notElem`) ws
, el "middle-name" (concat . init $ rest) names = case ws' of
, el "last-name" (last rest) ] (nickname:[]) -> [ el "nickname" nickname ]
([]) -> [] (fname:lname:[]) -> [ el "first-name" fname
in list $ el "author" (names ++ email) , el "last-name" lname ]
docdate :: Meta -> FBM [Content] (fname:rest) -> [ el "first-name" fname
docdate meta' = do , el "middle-name" (concat . init $ rest)
let ss = docDate meta' , el "last-name" (last rest) ]
d <- cMapM toXml ss ([]) -> []
return $ if null d in list $ el "author" (names ++ email)
then []
else [el "date" d] docdate :: Meta -> FBM [Content]
docdate meta' = do
let ss = docDate meta'
d <- cMapM toXml ss
return $ if null d
then []
else [el "date" d]
-- | Divide the stream of blocks into sections and convert to XML -- | Divide the stream of blocks into sections and convert to XML
-- representation. -- representation.