aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/Org.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2019-08-14 22:11:05 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2019-08-25 14:24:31 -0700
commit1ee6e0e0878bcd655f31deb0caf6a4766e500cc6 (patch)
tree5f11cadde103d1cb72e9b1cbf6eeb2b61a570e9b /src/Text/Pandoc/Writers/Org.hs
parent8959c44e6ae2a2f79ca55c2c173f84bf8d3abfc7 (diff)
downloadpandoc-1ee6e0e0878bcd655f31deb0caf6a4766e500cc6.tar.gz
Use new doctemplates, doclayout.
+ Remove Text.Pandoc.Pretty; use doclayout instead. [API change] + Text.Pandoc.Writers.Shared: remove metaToJSON, metaToJSON' [API change]. + Text.Pandoc.Writers.Shared: modify `addVariablesToContext`, `defField`, `setField`, `getField`, `resetField` to work with Context rather than JSON values. [API change] + Text.Pandoc.Writers.Shared: export new function `endsWithPlain` [API change]. + Use new templates and doclayout in writers. + Use Doc-based templates in all writers. + Adjust three tests for minor template rendering differences. + Added indentation to body in docbook4, docbook5 templates. The main impact of this change is better reflowing of content interpolated into templates. Previously, interpolated variables were rendered independently and intepolated as strings, which could lead to overly long lines. Now the templates interpolated as Doc values which may include breaking spaces, and reflowing occurs after template interpolation rather than before.
Diffstat (limited to 'src/Text/Pandoc/Writers/Org.hs')
-rw-r--r--src/Text/Pandoc/Writers/Org.hs69
1 files changed, 40 insertions, 29 deletions
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index 43b4c2add..3c4f1b237 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -25,7 +25,7 @@ import Text.Pandoc.Class (PandocMonad, report)
import Text.Pandoc.Definition
import Text.Pandoc.Logging
import Text.Pandoc.Options
-import Text.Pandoc.Pretty
+import Text.DocLayout
import Text.Pandoc.Shared
import Text.Pandoc.Templates (renderTemplate)
import Text.Pandoc.Writers.Shared
@@ -53,31 +53,29 @@ pandocToOrg (Pandoc meta blocks) = do
let colwidth = if writerWrapText opts == WrapAuto
then Just $ writerColumns opts
else Nothing
- let render' :: Doc -> Text
- render' = render colwidth
- metadata <- metaToJSON opts
- (fmap render' . blockListToOrg)
- (fmap render' . inlineListToOrg)
+ metadata <- metaToContext opts
+ blockListToOrg
+ (fmap chomp . inlineListToOrg)
meta
body <- blockListToOrg blocks
notes <- gets (reverse . stNotes) >>= notesToOrg
hasMath <- gets stHasMath
- let main = render colwidth . foldl ($+$) empty $ [body, notes]
+ let main = body $+$ notes
let context = defField "body" main
. defField "math" hasMath
$ metadata
- return $
+ return $ render colwidth $
case writerTemplate opts of
Nothing -> main
Just tpl -> renderTemplate tpl context
-- | Return Org representation of notes.
-notesToOrg :: PandocMonad m => [[Block]] -> Org m Doc
+notesToOrg :: PandocMonad m => [[Block]] -> Org m (Doc Text)
notesToOrg notes =
vsep <$> zipWithM noteToOrg [1..] notes
-- | Return Org representation of a note.
-noteToOrg :: PandocMonad m => Int -> [Block] -> Org m Doc
+noteToOrg :: PandocMonad m => Int -> [Block] -> Org m (Doc Text)
noteToOrg num note = do
contents <- blockListToOrg note
let marker = "[fn:" ++ show num ++ "] "
@@ -99,7 +97,7 @@ isRawFormat f =
-- | Convert Pandoc block element to Org.
blockToOrg :: PandocMonad m
=> Block -- ^ Block element
- -> Org m Doc
+ -> Org m (Doc Text)
blockToOrg Null = return empty
blockToOrg (Div (_,classes@(cls:_),kvs) bs) | "drawer" `elem` classes = do
contents <- blockListToOrg bs
@@ -198,10 +196,9 @@ blockToOrg (Table caption' _ _ headers rows) = do
map ((+2) . numChars) $ transpose (headers' : rawRows)
-- FIXME: Org doesn't allow blocks with height more than 1.
let hpipeBlocks blocks = hcat [beg, middle, end]
- where h = maximum (1 : map height blocks)
- sep' = lblock 3 $ vcat (replicate h (text " | "))
- beg = lblock 2 $ vcat (replicate h (text "| "))
- end = lblock 2 $ vcat (replicate h (text " |"))
+ where sep' = vfill " | "
+ beg = vfill "| "
+ end = vfill " |"
middle = hcat $ intersperse sep' blocks
let makeRow = hpipeBlocks . zipWith lblock widthsInChars
let head' = makeRow headers'
@@ -219,7 +216,9 @@ blockToOrg (Table caption' _ _ headers rows) = do
blockToOrg (BulletList items) = do
contents <- mapM bulletListItemToOrg items
-- ensure that sublists have preceding blank line
- return $ blankline $+$ vcat contents $$ blankline
+ return $ blankline $$
+ (if isTightList items then vcat else vsep) contents $$
+ blankline
blockToOrg (OrderedList (start, _, delim) items) = do
let delim' = case delim of
TwoParens -> OneParen
@@ -231,36 +230,48 @@ blockToOrg (OrderedList (start, _, delim) items) = do
in m ++ replicate s ' ') markers
contents <- zipWithM orderedListItemToOrg markers' items
-- ensure that sublists have preceding blank line
- return $ blankline $$ vcat contents $$ blankline
+ return $ blankline $$
+ (if isTightList items then vcat else vsep) contents $$
+ blankline
blockToOrg (DefinitionList items) = do
contents <- mapM definitionListItemToOrg items
return $ vcat contents $$ blankline
-- | Convert bullet list item (list of blocks) to Org.
-bulletListItemToOrg :: PandocMonad m => [Block] -> Org m Doc
+bulletListItemToOrg :: PandocMonad m => [Block] -> Org m (Doc Text)
bulletListItemToOrg items = do
contents <- blockListToOrg items
- return $ hang 2 "- " (contents <> cr)
+ return $ hang 2 "- " contents $$
+ if endsWithPlain items
+ then cr
+ else blankline
+
-- | Convert ordered list item (a list of blocks) to Org.
orderedListItemToOrg :: PandocMonad m
=> String -- ^ marker for list item
-> [Block] -- ^ list item (list of blocks)
- -> Org m Doc
+ -> Org m (Doc Text)
orderedListItemToOrg marker items = do
contents <- blockListToOrg items
- return $ hang (length marker + 1) (text marker <> space) (contents <> cr)
+ return $ hang (length marker + 1) (text marker <> space) contents $$
+ if endsWithPlain items
+ then cr
+ else blankline
-- | Convert definition list item (label, list of blocks) to Org.
definitionListItemToOrg :: PandocMonad m
- => ([Inline], [[Block]]) -> Org m Doc
+ => ([Inline], [[Block]]) -> Org m (Doc Text)
definitionListItemToOrg (label, defs) = do
label' <- inlineListToOrg label
contents <- vcat <$> mapM blockListToOrg defs
- return . hang 2 "- " $ label' <> " :: " <> (contents <> cr)
+ return $ hang 2 "- " (label' <> " :: " <> contents) $$
+ if isTightList defs
+ then cr
+ else blankline
-- | Convert list of key/value pairs to Org :PROPERTIES: drawer.
-propertiesDrawer :: Attr -> Doc
+propertiesDrawer :: Attr -> Doc Text
propertiesDrawer (ident, classes, kv) =
let
drawerStart = text ":PROPERTIES:"
@@ -271,11 +282,11 @@ propertiesDrawer (ident, classes, kv) =
in
drawerStart <> cr <> properties <> cr <> drawerEnd
where
- kvToOrgProperty :: (String, String) -> Doc
+ kvToOrgProperty :: (String, String) -> Doc Text
kvToOrgProperty (key, value) =
text ":" <> text key <> text ": " <> text value <> cr
-attrHtml :: Attr -> Doc
+attrHtml :: Attr -> Doc Text
attrHtml ("" , [] , []) = mempty
attrHtml (ident, classes, kvs) =
let
@@ -288,13 +299,13 @@ attrHtml (ident, classes, kvs) =
-- | Convert list of Pandoc block elements to Org.
blockListToOrg :: PandocMonad m
=> [Block] -- ^ List of block elements
- -> Org m Doc
+ -> Org m (Doc Text)
blockListToOrg blocks = vcat <$> mapM blockToOrg blocks
-- | Convert list of Pandoc inline elements to Org.
inlineListToOrg :: PandocMonad m
=> [Inline]
- -> Org m Doc
+ -> Org m (Doc Text)
inlineListToOrg lst = hcat <$> mapM inlineToOrg (fixMarkers lst)
where fixMarkers [] = [] -- prevent note refs and list markers from wrapping, see #4171
fixMarkers (Space : x : rest) | shouldFix x =
@@ -309,7 +320,7 @@ inlineListToOrg lst = hcat <$> mapM inlineToOrg (fixMarkers lst)
shouldFix _ = False
-- | Convert Pandoc inline element to Org.
-inlineToOrg :: PandocMonad m => Inline -> Org m Doc
+inlineToOrg :: PandocMonad m => Inline -> Org m (Doc Text)
inlineToOrg (Span (uid, [], []) []) =
return $ "<<" <> text uid <> ">>"
inlineToOrg (Span _ lst) =