2010-12-12 20:09:14 -08:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2010-12-04 15:57:39 +05:30
|
|
|
{-
|
2014-05-08 21:50:20 +02:00
|
|
|
Copyright (C) 2010-2014 Puneeth Chaganti <punchagan@gmail.com>
|
|
|
|
and John MacFarlane <jgm@berkeley.edu>
|
2010-12-04 15:57:39 +05:30
|
|
|
|
|
|
|
This program is free software; you can redistribute it and/or modify
|
|
|
|
it under the terms of the GNU General Public License as published by
|
|
|
|
the Free Software Foundation; either version 2 of the License, or
|
|
|
|
(at your option) any later version.
|
|
|
|
|
|
|
|
This program is distributed in the hope that it will be useful,
|
|
|
|
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
GNU General Public License for more details.
|
|
|
|
|
|
|
|
You should have received a copy of the GNU General Public License
|
|
|
|
along with this program; if not, write to the Free Software
|
|
|
|
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|
|
|
-}
|
|
|
|
|
|
|
|
{- |
|
|
|
|
Module : Text.Pandoc.Writers.Org
|
2014-05-08 21:50:20 +02:00
|
|
|
Copyright : Copyright (C) 2010-2014 Puneeth Chaganti and John MacFarlane
|
2012-07-26 22:32:53 -07:00
|
|
|
License : GNU GPL, version 2 or above
|
2010-12-04 15:57:39 +05:30
|
|
|
|
|
|
|
Maintainer : Puneeth Chaganti <punchagan@gmail.com>
|
|
|
|
Stability : alpha
|
|
|
|
Portability : portable
|
|
|
|
|
2010-12-05 09:48:54 -08:00
|
|
|
Conversion of 'Pandoc' documents to Emacs Org-Mode.
|
2010-12-04 15:57:39 +05:30
|
|
|
|
2010-12-05 09:48:54 -08:00
|
|
|
Org-Mode: <http://orgmode.org>
|
2010-12-04 15:57:39 +05:30
|
|
|
-}
|
|
|
|
module Text.Pandoc.Writers.Org ( writeOrg) where
|
|
|
|
import Text.Pandoc.Definition
|
2012-07-26 22:59:56 -07:00
|
|
|
import Text.Pandoc.Options
|
2012-07-26 22:32:53 -07:00
|
|
|
import Text.Pandoc.Shared
|
2013-07-01 20:47:26 -07:00
|
|
|
import Text.Pandoc.Writers.Shared
|
2010-12-12 20:09:14 -08:00
|
|
|
import Text.Pandoc.Pretty
|
2013-05-10 22:53:35 -07:00
|
|
|
import Text.Pandoc.Templates (renderTemplate')
|
2010-12-04 15:57:39 +05:30
|
|
|
import Data.List ( intersect, intersperse, transpose )
|
|
|
|
import Control.Monad.State
|
|
|
|
import Control.Applicative ( (<$>) )
|
|
|
|
|
2012-07-26 22:32:53 -07:00
|
|
|
data WriterState =
|
2010-12-04 15:57:39 +05:30
|
|
|
WriterState { stNotes :: [[Block]]
|
|
|
|
, stLinks :: Bool
|
|
|
|
, stImages :: Bool
|
|
|
|
, stHasMath :: Bool
|
|
|
|
, stOptions :: WriterOptions
|
|
|
|
}
|
|
|
|
|
|
|
|
-- | Convert Pandoc to Org.
|
|
|
|
writeOrg :: WriterOptions -> Pandoc -> String
|
2012-07-26 22:32:53 -07:00
|
|
|
writeOrg opts document =
|
2010-12-04 15:57:39 +05:30
|
|
|
let st = WriterState { stNotes = [], stLinks = False,
|
|
|
|
stImages = False, stHasMath = False,
|
|
|
|
stOptions = opts }
|
|
|
|
in evalState (pandocToOrg document) st
|
|
|
|
|
|
|
|
-- | Return Org representation of document.
|
|
|
|
pandocToOrg :: Pandoc -> State WriterState String
|
2013-05-10 22:53:35 -07:00
|
|
|
pandocToOrg (Pandoc meta blocks) = do
|
2010-12-04 15:57:39 +05:30
|
|
|
opts <- liftM stOptions get
|
2013-05-10 22:53:35 -07:00
|
|
|
let colwidth = if writerWrapText opts
|
|
|
|
then Just $ writerColumns opts
|
|
|
|
else Nothing
|
2013-07-01 20:47:26 -07:00
|
|
|
metadata <- metaToJSON opts
|
2013-05-10 22:53:35 -07:00
|
|
|
(fmap (render colwidth) . blockListToOrg)
|
|
|
|
(fmap (render colwidth) . inlineListToOrg)
|
|
|
|
meta
|
2010-12-04 15:57:39 +05:30
|
|
|
body <- blockListToOrg blocks
|
|
|
|
notes <- liftM (reverse . stNotes) get >>= notesToOrg
|
|
|
|
-- note that the notes may contain refs, so we do them first
|
|
|
|
hasMath <- liftM stHasMath get
|
2010-12-12 20:09:14 -08:00
|
|
|
let main = render colwidth $ foldl ($+$) empty $ [body, notes]
|
2013-06-27 22:42:55 -07:00
|
|
|
let context = defField "body" main
|
|
|
|
$ defField "math" hasMath
|
2013-06-29 22:14:01 -07:00
|
|
|
$ metadata
|
2010-12-04 15:57:39 +05:30
|
|
|
if writerStandalone opts
|
2013-05-10 22:53:35 -07:00
|
|
|
then return $ renderTemplate' (writerTemplate opts) context
|
2010-12-04 15:57:39 +05:30
|
|
|
else return main
|
|
|
|
|
|
|
|
-- | Return Org representation of notes.
|
|
|
|
notesToOrg :: [[Block]] -> State WriterState Doc
|
2012-07-26 22:32:53 -07:00
|
|
|
notesToOrg notes =
|
|
|
|
mapM (\(num, note) -> noteToOrg num note) (zip [1..] notes) >>=
|
2010-12-12 20:09:14 -08:00
|
|
|
return . vsep
|
2010-12-04 15:57:39 +05:30
|
|
|
|
|
|
|
-- | Return Org representation of a note.
|
|
|
|
noteToOrg :: Int -> [Block] -> State WriterState Doc
|
|
|
|
noteToOrg num note = do
|
|
|
|
contents <- blockListToOrg note
|
2010-12-12 20:09:14 -08:00
|
|
|
let marker = "[" ++ show num ++ "] "
|
|
|
|
return $ hang (length marker) (text marker) contents
|
2010-12-04 15:57:39 +05:30
|
|
|
|
|
|
|
-- | Escape special characters for Org.
|
|
|
|
escapeString :: String -> String
|
2011-12-27 15:45:34 -08:00
|
|
|
escapeString = escapeStringUsing $
|
|
|
|
[ ('\x2014',"---")
|
|
|
|
, ('\x2013',"--")
|
|
|
|
, ('\x2019',"'")
|
|
|
|
, ('\x2026',"...")
|
|
|
|
] ++ backslashEscapes "^_"
|
2010-12-04 15:57:39 +05:30
|
|
|
|
2012-07-26 22:32:53 -07:00
|
|
|
-- | Convert Pandoc block element to Org.
|
2010-12-04 15:57:39 +05:30
|
|
|
blockToOrg :: Block -- ^ Block element
|
2012-07-26 22:32:53 -07:00
|
|
|
-> State WriterState Doc
|
2010-12-04 15:57:39 +05:30
|
|
|
blockToOrg Null = return empty
|
2013-08-18 14:36:40 -07:00
|
|
|
blockToOrg (Div attrs bs) = do
|
|
|
|
contents <- blockListToOrg bs
|
|
|
|
let startTag = tagWithAttrs "div" attrs
|
|
|
|
let endTag = text "</div>"
|
|
|
|
return $ blankline $$ "#+BEGIN_HTML" $$
|
|
|
|
nest 2 startTag $$ "#+END_HTML" $$ blankline $$
|
|
|
|
contents $$ blankline $$ "#+BEGIN_HTML" $$
|
|
|
|
nest 2 endTag $$ "#+END_HTML" $$ blankline
|
2010-12-12 20:09:14 -08:00
|
|
|
blockToOrg (Plain inlines) = inlineListToOrg inlines
|
2013-01-15 08:45:46 -08:00
|
|
|
-- title beginning with fig: indicates that the image is a figure
|
|
|
|
blockToOrg (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
|
2012-08-04 11:34:01 -07:00
|
|
|
capt <- if null txt
|
|
|
|
then return empty
|
|
|
|
else (\c -> "#+CAPTION: " <> c <> blankline) `fmap`
|
|
|
|
inlineListToOrg txt
|
2010-12-04 15:57:39 +05:30
|
|
|
img <- inlineToOrg (Image txt (src,tit))
|
2012-08-04 11:34:01 -07:00
|
|
|
return $ capt <> img
|
2010-12-04 15:57:39 +05:30
|
|
|
blockToOrg (Para inlines) = do
|
2010-12-12 20:09:14 -08:00
|
|
|
contents <- inlineListToOrg inlines
|
|
|
|
return $ contents <> blankline
|
2012-07-26 22:32:53 -07:00
|
|
|
blockToOrg (RawBlock "html" str) =
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ blankline $$ "#+BEGIN_HTML" $$
|
|
|
|
nest 2 (text str) $$ "#+END_HTML" $$ blankline
|
2013-12-19 20:19:24 -05:00
|
|
|
blockToOrg (RawBlock f str) | f `elem` ["org", "latex", "tex"] =
|
2011-01-24 22:13:27 -08:00
|
|
|
return $ text str
|
2011-01-23 10:55:56 -08:00
|
|
|
blockToOrg (RawBlock _ _) = return empty
|
2010-12-12 20:09:14 -08:00
|
|
|
blockToOrg HorizontalRule = return $ blankline $$ "--------------" $$ blankline
|
2012-10-29 22:45:52 -07:00
|
|
|
blockToOrg (Header level _ inlines) = do
|
2010-12-04 15:57:39 +05:30
|
|
|
contents <- inlineListToOrg inlines
|
|
|
|
let headerStr = text $ if level > 999 then " " else replicate level '*'
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ headerStr <> " " <> contents <> blankline
|
2010-12-04 15:57:39 +05:30
|
|
|
blockToOrg (CodeBlock (_,classes,_) str) = do
|
|
|
|
opts <- stOptions <$> get
|
|
|
|
let tabstop = writerTabStop opts
|
2012-07-26 22:32:53 -07:00
|
|
|
let at = classes `intersect` ["asymptote", "C", "clojure", "css", "ditaa",
|
|
|
|
"dot", "emacs-lisp", "gnuplot", "haskell", "js", "latex",
|
|
|
|
"ledger", "lisp", "matlab", "mscgen", "ocaml", "octave",
|
|
|
|
"oz", "perl", "plantuml", "python", "R", "ruby", "sass",
|
2010-12-04 15:57:39 +05:30
|
|
|
"scheme", "screen", "sh", "sql", "sqlite"]
|
2012-05-29 16:27:19 -07:00
|
|
|
let (beg, end) = case at of
|
|
|
|
[] -> ("#+BEGIN_EXAMPLE", "#+END_EXAMPLE")
|
|
|
|
(x:_) -> ("#+BEGIN_SRC " ++ x, "#+END_SRC")
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ text beg $$ nest tabstop (text str) $$ text end $$ blankline
|
2010-12-04 15:57:39 +05:30
|
|
|
blockToOrg (BlockQuote blocks) = do
|
2012-07-26 22:32:53 -07:00
|
|
|
contents <- blockListToOrg blocks
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ blankline $$ "#+BEGIN_QUOTE" $$
|
|
|
|
nest 2 contents $$ "#+END_QUOTE" $$ blankline
|
2010-12-04 15:57:39 +05:30
|
|
|
blockToOrg (Table caption' _ _ headers rows) = do
|
|
|
|
caption'' <- inlineListToOrg caption'
|
|
|
|
let caption = if null caption'
|
|
|
|
then empty
|
2010-12-12 20:09:14 -08:00
|
|
|
else ("#+CAPTION: " <> caption'')
|
2010-12-04 15:57:39 +05:30
|
|
|
headers' <- mapM blockListToOrg headers
|
|
|
|
rawRows <- mapM (mapM blockListToOrg) rows
|
2010-12-12 20:09:14 -08:00
|
|
|
let numChars = maximum . map offset
|
2012-07-26 22:32:53 -07:00
|
|
|
-- FIXME: width is not being used.
|
2010-12-04 15:57:39 +05:30
|
|
|
let widthsInChars =
|
|
|
|
map ((+2) . numChars) $ transpose (headers' : rawRows)
|
2012-07-26 22:32:53 -07:00
|
|
|
-- FIXME: Org doesn't allow blocks with height more than 1.
|
|
|
|
let hpipeBlocks blocks = hcat [beg, middle, end]
|
2010-12-12 20:09:14 -08:00
|
|
|
where h = maximum (map height blocks)
|
|
|
|
sep' = lblock 3 $ vcat (map text $ replicate h " | ")
|
|
|
|
beg = lblock 2 $ vcat (map text $ replicate h "| ")
|
|
|
|
end = lblock 2 $ vcat (map text $ replicate h " |")
|
|
|
|
middle = hcat $ intersperse sep' blocks
|
|
|
|
let makeRow = hpipeBlocks . zipWith lblock widthsInChars
|
2010-12-04 15:57:39 +05:30
|
|
|
let head' = makeRow headers'
|
|
|
|
rows' <- mapM (\row -> do cols <- mapM blockListToOrg row
|
|
|
|
return $ makeRow cols) rows
|
|
|
|
let border ch = char '|' <> char ch <>
|
2012-07-26 22:32:53 -07:00
|
|
|
(hcat $ intersperse (char ch <> char '+' <> char ch) $
|
2010-12-04 15:57:39 +05:30
|
|
|
map (\l -> text $ replicate l ch) widthsInChars) <>
|
|
|
|
char ch <> char '|'
|
2010-12-12 20:09:14 -08:00
|
|
|
let body = vcat rows'
|
2010-12-04 15:57:39 +05:30
|
|
|
let head'' = if all null headers
|
|
|
|
then empty
|
2010-12-12 20:09:14 -08:00
|
|
|
else head' $$ border '-'
|
|
|
|
return $ head'' $$ body $$ caption $$ blankline
|
2010-12-04 15:57:39 +05:30
|
|
|
blockToOrg (BulletList items) = do
|
|
|
|
contents <- mapM bulletListItemToOrg items
|
|
|
|
-- ensure that sublists have preceding blank line
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ blankline $+$ vcat contents $$ blankline
|
|
|
|
blockToOrg (OrderedList (start, _, delim) items) = do
|
|
|
|
let delim' = case delim of
|
|
|
|
TwoParens -> OneParen
|
|
|
|
x -> x
|
2012-07-26 22:32:53 -07:00
|
|
|
let markers = take (length items) $ orderedListMarkers
|
2010-12-12 20:09:14 -08:00
|
|
|
(start, Decimal, delim')
|
2010-12-04 15:57:39 +05:30
|
|
|
let maxMarkerLength = maximum $ map length markers
|
|
|
|
let markers' = map (\m -> let s = maxMarkerLength - length m
|
|
|
|
in m ++ replicate s ' ') markers
|
|
|
|
contents <- mapM (\(item, num) -> orderedListItemToOrg item num) $
|
2010-12-12 20:09:14 -08:00
|
|
|
zip markers' items
|
2010-12-04 15:57:39 +05:30
|
|
|
-- ensure that sublists have preceding blank line
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ blankline $$ vcat contents $$ blankline
|
2010-12-04 15:57:39 +05:30
|
|
|
blockToOrg (DefinitionList items) = do
|
|
|
|
contents <- mapM definitionListItemToOrg items
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ vcat contents $$ blankline
|
2010-12-04 15:57:39 +05:30
|
|
|
|
|
|
|
-- | Convert bullet list item (list of blocks) to Org.
|
|
|
|
bulletListItemToOrg :: [Block] -> State WriterState Doc
|
|
|
|
bulletListItemToOrg items = do
|
|
|
|
contents <- blockListToOrg items
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ hang 3 "- " (contents <> cr)
|
2010-12-04 15:57:39 +05:30
|
|
|
|
|
|
|
-- | Convert ordered list item (a list of blocks) to Org.
|
|
|
|
orderedListItemToOrg :: String -- ^ marker for list item
|
|
|
|
-> [Block] -- ^ list item (list of blocks)
|
|
|
|
-> State WriterState Doc
|
|
|
|
orderedListItemToOrg marker items = do
|
|
|
|
contents <- blockListToOrg items
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ hang (length marker + 1) (text marker <> space) (contents <> cr)
|
2010-12-04 15:57:39 +05:30
|
|
|
|
|
|
|
-- | Convert defintion list item (label, list of blocks) to Org.
|
|
|
|
definitionListItemToOrg :: ([Inline], [[Block]]) -> State WriterState Doc
|
|
|
|
definitionListItemToOrg (label, defs) = do
|
|
|
|
label' <- inlineListToOrg label
|
|
|
|
contents <- liftM vcat $ mapM blockListToOrg defs
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ hang 3 "- " $ label' <> " :: " <> (contents <> cr)
|
2010-12-04 15:57:39 +05:30
|
|
|
|
|
|
|
-- | Convert list of Pandoc block elements to Org.
|
|
|
|
blockListToOrg :: [Block] -- ^ List of block elements
|
2012-07-26 22:32:53 -07:00
|
|
|
-> State WriterState Doc
|
2010-12-04 15:57:39 +05:30
|
|
|
blockListToOrg blocks = mapM blockToOrg blocks >>= return . vcat
|
|
|
|
|
|
|
|
-- | Convert list of Pandoc inline elements to Org.
|
|
|
|
inlineListToOrg :: [Inline] -> State WriterState Doc
|
|
|
|
inlineListToOrg lst = mapM inlineToOrg lst >>= return . hcat
|
|
|
|
|
|
|
|
-- | Convert Pandoc inline element to Org.
|
|
|
|
inlineToOrg :: Inline -> State WriterState Doc
|
2014-08-08 00:11:02 +01:00
|
|
|
inlineToOrg (Span (uid, [], []) []) =
|
|
|
|
return $ "<<" <> text uid <> ">>"
|
2013-08-08 23:14:12 -07:00
|
|
|
inlineToOrg (Span _ lst) =
|
|
|
|
inlineListToOrg lst
|
2012-07-26 22:32:53 -07:00
|
|
|
inlineToOrg (Emph lst) = do
|
2010-12-04 15:57:39 +05:30
|
|
|
contents <- inlineListToOrg lst
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ "/" <> contents <> "/"
|
2010-12-04 15:57:39 +05:30
|
|
|
inlineToOrg (Strong lst) = do
|
|
|
|
contents <- inlineListToOrg lst
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ "*" <> contents <> "*"
|
2012-07-26 22:32:53 -07:00
|
|
|
inlineToOrg (Strikeout lst) = do
|
2010-12-04 15:57:39 +05:30
|
|
|
contents <- inlineListToOrg lst
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ "+" <> contents <> "+"
|
2012-07-26 22:32:53 -07:00
|
|
|
inlineToOrg (Superscript lst) = do
|
2010-12-04 15:57:39 +05:30
|
|
|
contents <- inlineListToOrg lst
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ "^{" <> contents <> "}"
|
2012-07-26 22:32:53 -07:00
|
|
|
inlineToOrg (Subscript lst) = do
|
2010-12-04 15:57:39 +05:30
|
|
|
contents <- inlineListToOrg lst
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ "_{" <> contents <> "}"
|
2010-12-04 15:57:39 +05:30
|
|
|
inlineToOrg (SmallCaps lst) = inlineListToOrg lst
|
|
|
|
inlineToOrg (Quoted SingleQuote lst) = do
|
|
|
|
contents <- inlineListToOrg lst
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ "'" <> contents <> "'"
|
2010-12-04 15:57:39 +05:30
|
|
|
inlineToOrg (Quoted DoubleQuote lst) = do
|
|
|
|
contents <- inlineListToOrg lst
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ "\"" <> contents <> "\""
|
|
|
|
inlineToOrg (Cite _ lst) = inlineListToOrg lst
|
2011-01-26 20:44:25 -08:00
|
|
|
inlineToOrg (Code _ str) = return $ "=" <> text str <> "="
|
2010-12-04 15:57:39 +05:30
|
|
|
inlineToOrg (Str str) = return $ text $ escapeString str
|
|
|
|
inlineToOrg (Math t str) = do
|
|
|
|
modify $ \st -> st{ stHasMath = True }
|
|
|
|
return $ if t == InlineMath
|
2010-12-12 20:09:14 -08:00
|
|
|
then "$" <> text str <> "$"
|
|
|
|
else "$$" <> text str <> "$$"
|
2011-01-24 22:13:27 -08:00
|
|
|
inlineToOrg (RawInline f str) | f == "tex" || f == "latex" = return $ text str
|
2011-01-23 10:55:56 -08:00
|
|
|
inlineToOrg (RawInline _ _) = return empty
|
2014-04-12 00:22:49 +02:00
|
|
|
inlineToOrg (LineBreak) = return (text "\\\\" <> cr)
|
2010-12-12 20:09:14 -08:00
|
|
|
inlineToOrg Space = return space
|
2010-12-04 15:57:39 +05:30
|
|
|
inlineToOrg (Link txt (src, _)) = do
|
|
|
|
case txt of
|
2013-01-06 20:51:51 -08:00
|
|
|
[Str x] | escapeURI x == src -> -- autolink
|
2010-12-04 15:57:39 +05:30
|
|
|
do modify $ \s -> s{ stLinks = True }
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ "[[" <> text x <> "]]"
|
2010-12-04 15:57:39 +05:30
|
|
|
_ -> do contents <- inlineListToOrg txt
|
|
|
|
modify $ \s -> s{ stLinks = True }
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ "[[" <> text src <> "][" <> contents <> "]]"
|
2011-12-02 19:39:30 -08:00
|
|
|
inlineToOrg (Image _ (source, _)) = do
|
2010-12-04 15:57:39 +05:30
|
|
|
modify $ \s -> s{ stImages = True }
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ "[[" <> text source <> "]]"
|
2012-07-26 22:32:53 -07:00
|
|
|
inlineToOrg (Note contents) = do
|
2010-12-04 15:57:39 +05:30
|
|
|
-- add to notes in state
|
|
|
|
notes <- get >>= (return . stNotes)
|
|
|
|
modify $ \st -> st { stNotes = contents:notes }
|
|
|
|
let ref = show $ (length notes) + 1
|
2010-12-12 20:09:14 -08:00
|
|
|
return $ " [" <> text ref <> "]"
|