From 921e2b6e67e0bcc0c6644b5455bf9d2e70f1a386 Mon Sep 17 00:00:00 2001
From: Puneeth Chaganti <punchagan@gmail.com>
Date: Sat, 4 Dec 2010 15:57:39 +0530
Subject: [PATCH 1/3] Added Org-mode writer

    + Added Text/Pandoc/Writers/Org.hs
    + Added to pandoc.cabal
    + Added to pandoc.hs and Text/Pandoc.hs exports.
---
 pandoc.cabal                   |   1 +
 src/Text/Pandoc.hs             |   2 +
 src/Text/Pandoc/Writers/Org.hs | 291 +++++++++++++++++++++++++++++++++
 src/pandoc.hs                  |   2 +
 4 files changed, 296 insertions(+)
 create mode 100644 src/Text/Pandoc/Writers/Org.hs

diff --git a/pandoc.cabal b/pandoc.cabal
index d8c281b09..465069336 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -202,6 +202,7 @@ Library
                    Text.Pandoc.Writers.Man,
                    Text.Pandoc.Writers.Markdown,
                    Text.Pandoc.Writers.RST,
+                   Text.Pandoc.Writers.Org,
                    Text.Pandoc.Writers.Textile,
                    Text.Pandoc.Writers.MediaWiki,
                    Text.Pandoc.Writers.RTF,
diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs
index d11f084a5..ab1e3cd03 100644
--- a/src/Text/Pandoc.hs
+++ b/src/Text/Pandoc.hs
@@ -89,6 +89,7 @@ module Text.Pandoc
                , writeRTF
                , writeODT
                , writeEPUB
+               , writeOrg
                -- * Writer options used in writers 
                , WriterOptions (..)
                , HTMLSlideVariant (..)
@@ -121,6 +122,7 @@ import Text.Pandoc.Writers.Man
 import Text.Pandoc.Writers.RTF 
 import Text.Pandoc.Writers.MediaWiki
 import Text.Pandoc.Writers.Textile
+import Text.Pandoc.Writers.Org
 import Text.Pandoc.Templates
 import Text.Pandoc.Parsing
 import Text.Pandoc.Shared
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
new file mode 100644
index 000000000..32ae254cf
--- /dev/null
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -0,0 +1,291 @@
+{-
+Copyright (C) 2006-2010 Puneeth Chaganti <punchagan@gmail.com>
+
+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
+   Copyright   : Copyright (C) 2006-2010 Puneeth Chaganti
+   License     : GNU GPL, version 2 or above 
+
+   Maintainer  : Puneeth Chaganti <punchagan@gmail.com>
+   Stability   : alpha
+   Portability : portable
+
+Conversion of 'Pandoc' documents to reStructuredText.
+
+reStructuredText:  <http://docutils.sourceforge.net/rst.html>
+-}
+module Text.Pandoc.Writers.Org ( writeOrg) where
+import Text.Pandoc.Definition
+import Text.Pandoc.Shared 
+import Text.Pandoc.Blocks
+import Text.Pandoc.Templates (renderTemplate)
+import Data.List ( intersect, intersperse, transpose )
+import Text.PrettyPrint.HughesPJ hiding ( Str )
+import Control.Monad.State
+import Control.Applicative ( (<$>) )
+
+data WriterState = 
+  WriterState { stNotes     :: [[Block]]
+              , stLinks     :: Bool
+              , stImages    :: Bool
+              , stHasMath   :: Bool
+              , stOptions   :: WriterOptions
+              }
+
+-- | Convert Pandoc to Org.
+writeOrg :: WriterOptions -> Pandoc -> String
+writeOrg opts document = 
+  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
+pandocToOrg (Pandoc (Meta tit auth dat) blocks) = do
+  opts <- liftM stOptions get
+  title <- titleToOrg tit
+  authors <- mapM inlineListToOrg auth
+  date <- inlineListToOrg dat
+  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
+  let main = render $ foldl ($+$) empty $ [body, notes]
+  let context = writerVariables opts ++
+                [ ("body", main)
+                , ("title", render title)
+                , ("date", render date) ] ++
+                [ ("math", "yes") | hasMath ] ++
+                [ ("author", render a) | a <- authors ]
+  if writerStandalone opts
+     then return $ renderTemplate context $ writerTemplate opts
+     else return main
+
+-- | Return Org representation of notes.
+notesToOrg :: [[Block]] -> State WriterState Doc
+notesToOrg notes = 
+  mapM (\(num, note) -> noteToOrg num note) (zip [1..] notes) >>= 
+  return . vcat
+
+-- | Return Org representation of a note.
+noteToOrg :: Int -> [Block] -> State WriterState Doc
+noteToOrg num note = do
+  contents <- blockListToOrg note
+  let marker = text "[" <> text (show num) <> text "] "
+  return $ marker <> contents
+
+-- | Take list of inline elements and return wrapped doc.
+wrappedOrg :: WriterOptions -> [Inline] -> State WriterState Doc
+wrappedOrg opts inlines = do
+  lineBreakDoc <- inlineToOrg LineBreak  
+  chunks <- mapM (wrapIfNeeded opts inlineListToOrg)
+                 (splitBy LineBreak inlines)
+  return $ vcat $ intersperse lineBreakDoc chunks
+
+-- | Escape special characters for Org.
+escapeString :: String -> String
+escapeString = escapeStringUsing (backslashEscapes "^_")
+
+titleToOrg :: [Inline] -> State WriterState Doc
+titleToOrg [] = return empty
+titleToOrg lst = do
+  contents <- inlineListToOrg lst
+  let titleName = text "#+TITLE: "
+  return $ titleName $+$ contents 
+
+-- | Convert Pandoc block element to Org. 
+blockToOrg :: Block         -- ^ Block element
+           -> State WriterState Doc 
+blockToOrg Null = return empty
+blockToOrg (Plain inlines) = do
+  opts <- get >>= (return . stOptions)
+  wrappedOrg opts inlines
+blockToOrg (Para [Image txt (src,tit)]) = do
+  capt <- inlineListToOrg txt
+  img <- inlineToOrg (Image txt (src,tit))
+  return $ text "#+CAPTION: " <> capt <> text "\n" $$ img 
+blockToOrg (Para inlines) = do
+  opts <- get >>= (return . stOptions)
+  contents <- wrappedOrg opts inlines
+  return $ contents <> text "\n"
+blockToOrg (RawHtml str) = 
+  return $ (text "\n#+BEGIN_HTML\n") $$ (nest 2 $ vcat $ map text (lines str)) 
+         $$ (text "\n#+END_HTML\n")
+blockToOrg HorizontalRule = return $ text "--------------\n"
+blockToOrg (Header level inlines) = do
+  contents <- inlineListToOrg inlines
+  let headerStr = text $ if level > 999 then " " else replicate level '*'
+  return $ headerStr <> text " " <> contents <> text "\n"
+blockToOrg (CodeBlock (_,classes,_) str) = do
+  opts <- stOptions <$> get
+  let tabstop = writerTabStop opts
+  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", 
+                    "scheme", "screen", "sh", "sql", "sqlite"]
+  let (beg, end) = if null at
+                      then ("#+BEGIN_EXAMPLE", "#+END_EXAMPLE")
+                      else ("#+BEGIN_SRC" ++ head at, "#+END_SRC")
+  return $ text beg $+$ (nest tabstop $ vcat $ map text (lines str)) 
+         $+$ text end
+blockToOrg (BlockQuote blocks) = do
+  contents <- blockListToOrg blocks 
+  return $ (text "\n#+BEGIN_QUOTE\n") $$ (nest 2 contents) 
+         $$ (text "\n#+END_QUOTE\n")
+blockToOrg (Table caption' _ _ headers rows) =  do
+  caption'' <- inlineListToOrg caption'
+  let caption = if null caption'
+                   then empty
+                   else (text "#+CAPTION: " <> caption'')
+  headers' <- mapM blockListToOrg headers
+  rawRows <- mapM (mapM blockListToOrg) rows
+  let numChars = maximum . map (length . render)
+  -- FIXME: width is not being used. 
+  let widthsInChars =
+       map ((+2) . numChars) $ transpose (headers' : rawRows)
+  -- FIXME: Org doesn't allow blocks with height more than 1. 
+  let hpipeBlocks blocks = hcatBlocks [beg, middle, end] 
+        where height = maximum (map heightOfBlock blocks)
+              sep'   = TextBlock 3 height (replicate height " | ")
+              beg    = TextBlock 2 height (replicate height "| ")
+              end    = TextBlock 2 height (replicate height " |")
+              middle = hcatBlocks $ intersperse sep' blocks
+  let makeRow = hpipeBlocks . zipWith docToBlock widthsInChars
+  let head' = makeRow headers'
+  rows' <- mapM (\row -> do cols <- mapM blockListToOrg row
+                            return $ makeRow cols) rows
+  let border ch = char '|' <> char ch <>
+                  (hcat $ intersperse (char ch <> char '+' <> char ch) $ 
+                          map (\l -> text $ replicate l ch) widthsInChars) <>
+                  char ch <> char '|'
+  let body = vcat $ map blockToDoc rows'
+  let head'' = if all null headers
+                  then empty
+                  else blockToDoc head' $+$ border '-'
+  return $ head'' $+$ body $$ caption $$ text ""
+blockToOrg (BulletList items) = do
+  contents <- mapM bulletListItemToOrg items
+  -- ensure that sublists have preceding blank line
+  return $ text "" $+$ vcat contents <> text "\n"
+blockToOrg (OrderedList (start, style', delim) items) = do
+  let markers = take (length items) $ orderedListMarkers 
+                                      (start, style', delim)
+  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) $
+              zip markers' items  
+  -- ensure that sublists have preceding blank line
+  return $ text "" $+$ vcat contents <> text "\n"
+blockToOrg (DefinitionList items) = do
+  contents <- mapM definitionListItemToOrg items
+  return $ (vcat contents) <> text "\n"
+
+-- | Convert bullet list item (list of blocks) to Org.
+bulletListItemToOrg :: [Block] -> State WriterState Doc
+bulletListItemToOrg items = do
+  contents <- blockListToOrg items
+  return $ (text "-  ") <> contents
+
+-- | 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
+  return $ (text marker <> char ' ') <> contents 
+
+-- | 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
+  return $ (text "-  ") <> label' <> (text " :: ") <> contents
+
+-- | Convert list of Pandoc block elements to Org.
+blockListToOrg :: [Block]       -- ^ List of block elements
+               -> State WriterState Doc 
+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
+inlineToOrg (Emph lst) = do 
+  contents <- inlineListToOrg lst
+  return $ char '/' <> contents <> char '/'
+inlineToOrg (Strong lst) = do
+  contents <- inlineListToOrg lst
+  return $ text "*" <> contents <> text "*"
+inlineToOrg (Strikeout lst) = do 
+  contents <- inlineListToOrg lst
+  return $ text "+" <> contents <> char '+'
+inlineToOrg (Superscript lst) = do 
+  contents <- inlineListToOrg lst
+  return $ text "^{" <> contents <> text "}"
+inlineToOrg (Subscript lst) = do 
+  contents <- inlineListToOrg lst
+  return $ text "_{" <> contents <> text "}"
+inlineToOrg (SmallCaps lst) = inlineListToOrg lst
+inlineToOrg (Quoted SingleQuote lst) = do
+  contents <- inlineListToOrg lst
+  return $ char '\'' <> contents <> char '\''
+inlineToOrg (Quoted DoubleQuote lst) = do
+  contents <- inlineListToOrg lst
+  return $ char '\"' <> contents <> char '\"'
+inlineToOrg (Cite _  lst) =
+  inlineListToOrg lst
+inlineToOrg EmDash = return $ text "---"
+inlineToOrg EnDash = return $ text "--"
+inlineToOrg Apostrophe = return $ char '\''
+inlineToOrg Ellipses = return $ text "..."
+inlineToOrg (Code str) = return $ text $ "=" ++ str ++ "="
+inlineToOrg (Str str) = return $ text $ escapeString str
+inlineToOrg (Math t str) = do
+  modify $ \st -> st{ stHasMath = True }
+  return $ if t == InlineMath
+              then text $ "$" ++ str ++ "$"
+              else text $ "$$" ++ str ++ "$$"
+inlineToOrg (TeX str) = return $ text str
+inlineToOrg (HtmlInline _) = return empty
+inlineToOrg (LineBreak) = do
+  return $ empty -- there's no line break in Org
+inlineToOrg Space = return $ char ' '
+inlineToOrg (Link txt (src, _)) = do
+  case txt of
+        [Code x] | x == src ->  -- autolink
+             do modify $ \s -> s{ stLinks = True }
+                return $ text $ "[[" ++ x ++ "]]"
+        _ -> do contents <- inlineListToOrg txt
+                modify $ \s -> s{ stLinks = True }
+                return $ text ("[[" ++ src ++ "][") <> contents <> 
+                         (text "]]")
+inlineToOrg (Image _ (source', _)) = do
+  let source = unescapeURI source'
+  modify $ \s -> s{ stImages = True }
+  return $ text $ "[[" ++ source ++ "]]"
+inlineToOrg (Note contents) = do 
+  -- add to notes in state
+  notes <- get >>= (return . stNotes)
+  modify $ \st -> st { stNotes = contents:notes }
+  let ref = show $ (length notes) + 1
+  return $ text " [" <> text ref <> text "]"
diff --git a/src/pandoc.hs b/src/pandoc.hs
index 0cf694873..3aa9a4ba8 100644
--- a/src/pandoc.hs
+++ b/src/pandoc.hs
@@ -121,6 +121,7 @@ writers = [("native"       , writeNative)
           ,("mediawiki"    , writeMediaWiki)
           ,("textile"      , writeTextile)
           ,("rtf"          , writeRTF)
+          ,("org"          , writeOrg)
           ]
 
 isNonTextOutput :: String -> Bool
@@ -616,6 +617,7 @@ defaultWriterName x =
     ".db"       -> "docbook"
     ".odt"      -> "odt"
     ".epub"     -> "epub"
+    ".org"      -> "org"
     ['.',y] | y `elem` ['1'..'9'] -> "man"
     _          -> "html"
 

From 4d48abcb12f11e05091669c462c2ac8248f4c7aa Mon Sep 17 00:00:00 2001
From: Puneeth Chaganti <punchagan@gmail.com>
Date: Sat, 4 Dec 2010 23:49:53 +0530
Subject: [PATCH 2/3] Added tests.

    + Added tables.org and writer.org to tests.
    + Added org.template to templates.
    + Changed RunTests.hs as required.
    + Minor changes to Org writer.
---
 src/Text/Pandoc/Writers/Org.hs |   2 +-
 templates/org.template         |  22 +
 tests/RunTests.hs              |   1 +
 tests/tables.org               |  51 ++
 tests/writer.org               | 886 +++++++++++++++++++++++++++++++++
 5 files changed, 961 insertions(+), 1 deletion(-)
 create mode 100644 templates/org.template
 create mode 100644 tests/tables.org
 create mode 100644 tests/writer.org

diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index 32ae254cf..9285e9c55 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -107,7 +107,7 @@ titleToOrg [] = return empty
 titleToOrg lst = do
   contents <- inlineListToOrg lst
   let titleName = text "#+TITLE: "
-  return $ titleName $+$ contents 
+  return $ titleName <> contents 
 
 -- | Convert Pandoc block element to Org. 
 blockToOrg :: Block         -- ^ Block element
diff --git a/templates/org.template b/templates/org.template
new file mode 100644
index 000000000..303e1aad0
--- /dev/null
+++ b/templates/org.template
@@ -0,0 +1,22 @@
+$if(title)$
+$title$
+
+$endif$
+#+AUTHOR: $for(author)$$author$$sep$; $endfor$
+$if(date)$
+#+DATE: $date$
+
+$endif$
+$for(header-includes)$
+$header-includes$
+
+$endfor$
+$for(include-before)$
+$include-before$
+
+$endfor$
+$body$
+$for(include-after)$
+
+$include-after$
+$endfor$
diff --git a/tests/RunTests.hs b/tests/RunTests.hs
index b56b492ae..94b56d04d 100644
--- a/tests/RunTests.hs
+++ b/tests/RunTests.hs
@@ -62,6 +62,7 @@ writerFormats = [ "native"
                 , "mediawiki"
                 , "textile"
                 , "rtf"
+                , "org"
                 ]
 
 lhsWriterFormats :: [String]
diff --git a/tests/tables.org b/tests/tables.org
new file mode 100644
index 000000000..9eaf5e706
--- /dev/null
+++ b/tests/tables.org
@@ -0,0 +1,51 @@
+Simple table with caption:
+
+| Right   | Left   | Center   | Default   |
+|---------+--------+----------+-----------|
+| 12      | 12     | 12       | 12        |
+| 123     | 123    | 123      | 123       |
+| 1       | 1      | 1        | 1         |
+#+CAPTION: Demonstration of simple table syntax.
+
+Simple table without caption:
+
+| Right   | Left   | Center   | Default   |
+|---------+--------+----------+-----------|
+| 12      | 12     | 12       | 12        |
+| 123     | 123    | 123      | 123       |
+| 1       | 1      | 1        | 1         |
+
+Simple table indented two spaces:
+
+| Right   | Left   | Center   | Default   |
+|---------+--------+----------+-----------|
+| 12      | 12     | 12       | 12        |
+| 123     | 123    | 123      | 123       |
+| 1       | 1      | 1        | 1         |
+#+CAPTION: Demonstration of simple table syntax.
+
+Multiline table with caption:
+
+| Centered Header   | Left Aligned   | Right Aligned   | Default aligned                                         |
+|-------------------+----------------+-----------------+---------------------------------------------------------|
+| First             | row            | 12.0            | Example of a row that spans multiple lines.             |
+| Second            | row            | 5.0             | Here's another one. Note the blank line between rows.   |
+#+CAPTION: Here's the caption. It may span multiple lines.
+
+Multiline table without caption:
+
+| Centered Header   | Left Aligned   | Right Aligned   | Default aligned                                         |
+|-------------------+----------------+-----------------+---------------------------------------------------------|
+| First             | row            | 12.0            | Example of a row that spans multiple lines.             |
+| Second            | row            | 5.0             | Here's another one. Note the blank line between rows.   |
+
+Table without column headers:
+
+| 12    | 12    | 12    | 12    |
+| 123   | 123   | 123   | 123   |
+| 1     | 1     | 1     | 1     |
+
+Multiline table without column headers:
+
+| First    | row   | 12.0   | Example of a row that spans multiple lines.             |
+| Second   | row   | 5.0    | Here's another one. Note the blank line between rows.   |
diff --git a/tests/writer.org b/tests/writer.org
new file mode 100644
index 000000000..59f27acfc
--- /dev/null
+++ b/tests/writer.org
@@ -0,0 +1,886 @@
+#+TITLE: Pandoc Test Suite
+
+#+AUTHOR: John MacFarlane; Anonymous
+#+DATE: July 17, 2006
+
+This is a set of tests for pandoc. Most of them are adapted from
+John Gruber's markdown test suite.
+
+--------------
+
+* Headers
+
+** Level 2 with an [[/url][embedded link]]
+
+*** Level 3 with /emphasis/
+
+**** Level 4
+
+***** Level 5
+
+* Level 1
+
+** Level 2 with /emphasis/
+
+*** Level 3
+
+with no blank line
+
+** Level 2
+
+with no blank line
+
+--------------
+
+* Paragraphs
+
+Here's a regular paragraph.
+
+In Markdown 1.0.0 and earlier. Version 8. This line turns into a
+list item. Because a hard-wrapped line in the middle of a paragraph
+looked like a list item.
+
+Here's one with a bullet. * criminey.
+
+There should be a hard line break
+here.
+
+--------------
+
+* Block Quotes
+
+E-mail style:
+
+
+#+BEGIN_QUOTE
+
+  This is a block quote. It is pretty short.
+
+
+#+END_QUOTE
+
+
+#+BEGIN_QUOTE
+
+  Code in a block quote:
+
+  #+BEGIN_EXAMPLE
+      sub status {
+          print "working";
+      }
+  #+END_EXAMPLE
+  A list:
+
+  
+  1. item one
+  2. item two
+
+  Nested block quotes:
+
+  
+#+BEGIN_QUOTE
+
+    nested
+
+  
+#+END_QUOTE
+
+  
+#+BEGIN_QUOTE
+
+    nested
+
+  
+#+END_QUOTE
+
+
+#+END_QUOTE
+
+This should not be a block quote: 2 > 1.
+
+And a following paragraph.
+
+--------------
+
+* Code Blocks
+
+Code:
+
+#+BEGIN_EXAMPLE
+    ---- (should be four hyphens)
+    
+    sub status {
+        print "working";
+    }
+    
+    this code block is indented by one tab
+#+END_EXAMPLE
+And:
+
+#+BEGIN_EXAMPLE
+        this code block is indented by two tabs
+    
+    These should not be escaped:  \$ \\ \> \[ \{
+#+END_EXAMPLE
+--------------
+
+* Lists
+
+** Unordered
+
+Asterisks tight:
+
+
+-  asterisk 1
+-  asterisk 2
+-  asterisk 3
+
+Asterisks loose:
+
+
+-  asterisk 1
+
+-  asterisk 2
+
+-  asterisk 3
+
+
+Pluses tight:
+
+
+-  Plus 1
+-  Plus 2
+-  Plus 3
+
+Pluses loose:
+
+
+-  Plus 1
+
+-  Plus 2
+
+-  Plus 3
+
+
+Minuses tight:
+
+
+-  Minus 1
+-  Minus 2
+-  Minus 3
+
+Minuses loose:
+
+
+-  Minus 1
+
+-  Minus 2
+
+-  Minus 3
+
+
+** Ordered
+
+Tight:
+
+
+1. First
+2. Second
+3. Third
+
+and:
+
+
+1. One
+2. Two
+3. Three
+
+Loose using tabs:
+
+
+1. First
+
+2. Second
+
+3. Third
+
+
+and using spaces:
+
+
+1. One
+
+2. Two
+
+3. Three
+
+
+Multiple paragraphs:
+
+
+1. Item 1, graf one.
+
+   Item 1. graf two. The quick brown fox jumped over the lazy dog's
+   back.
+
+2. Item 2.
+
+3. Item 3.
+
+
+** Nested
+
+
+-  Tab
+   
+   -  Tab
+      
+      -  Tab
+
+
+
+Here's another:
+
+
+1. First
+2. Second:
+   
+   -  Fee
+   -  Fie
+   -  Foe
+
+3. Third
+
+Same thing but with paragraphs:
+
+
+1. First
+
+2. Second:
+
+   
+   -  Fee
+   -  Fie
+   -  Foe
+
+3. Third
+
+
+** Tabs and spaces
+
+
+-  this is a list item indented with tabs
+
+-  this is a list item indented with spaces
+
+   
+   -  this is an example list item indented with tabs
+
+   -  this is an example list item indented with spaces
+
+
+
+** Fancy list markers
+
+
+(2) begins with 2
+(3) and now 3
+
+    with a continuation
+
+    
+    iv. sublist with roman numerals, starting with 4
+    v.  more items
+        
+        (A) a subsublist
+        (B) a subsublist
+
+
+
+Nesting:
+
+
+A. Upper Alpha
+   
+   I. Upper Roman.
+      
+      (6) Decimal start with 6
+          
+          c) Lower alpha with paren
+
+
+
+
+Autonumbering:
+
+
+1. Autonumber.
+2. More.
+   
+   1. Nested.
+
+
+Should not be a list item:
+
+M.A. 2007
+
+B. Williams
+
+--------------
+
+* Definition Lists
+
+Tight using spaces:
+
+-  apple :: red fruit
+-  orange :: orange fruit
+-  banana :: yellow fruit
+
+Tight using tabs:
+
+-  apple :: red fruit
+-  orange :: orange fruit
+-  banana :: yellow fruit
+
+Loose:
+
+-  apple :: red fruit
+
+-  orange :: orange fruit
+
+-  banana :: yellow fruit
+
+
+Multiple blocks with italics:
+
+-  /apple/ :: red fruit
+
+              contains seeds, crisp, pleasant to taste
+
+-  /orange/ :: orange fruit
+
+               #+BEGIN_EXAMPLE
+                   { orange code block }
+               #+END_EXAMPLE
+               
+#+BEGIN_QUOTE
+
+                 orange block quote
+
+               
+#+END_QUOTE
+
+
+Multiple definitions, tight:
+
+-  apple :: red fruit
+            computer
+-  orange :: orange fruit
+             bank
+
+Multiple definitions, loose:
+
+-  apple :: red fruit
+
+            computer
+
+-  orange :: orange fruit
+
+             bank
+
+
+Blank line after term, indented marker, alternate markers:
+
+-  apple :: red fruit
+
+            computer
+
+-  orange :: orange fruit
+
+             
+             1. sublist
+             2. sublist
+
+
+* HTML Blocks
+
+Simple block on one line:
+
+
+#+BEGIN_HTML
+
+  <div>
+
+#+END_HTML
+
+foo
+
+#+BEGIN_HTML
+
+  </div>
+
+#+END_HTML
+
+And nested without indentation:
+
+
+#+BEGIN_HTML
+
+  <div>
+  <div>
+  <div>
+
+#+END_HTML
+
+foo
+
+#+BEGIN_HTML
+
+  </div>
+  </div>
+  <div>
+
+#+END_HTML
+
+bar
+
+#+BEGIN_HTML
+
+  </div>
+  </div>
+
+#+END_HTML
+
+Interpreted markdown in a table:
+
+
+#+BEGIN_HTML
+
+  <table>
+  <tr>
+  <td>
+
+#+END_HTML
+
+This is /emphasized/
+
+#+BEGIN_HTML
+
+  </td>
+  <td>
+
+#+END_HTML
+
+And this is *strong*
+
+#+BEGIN_HTML
+
+  </td>
+  </tr>
+  </table>
+  
+  <script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script>
+
+#+END_HTML
+
+Here's a simple block:
+
+
+#+BEGIN_HTML
+
+  <div>
+      
+
+#+END_HTML
+
+foo
+
+#+BEGIN_HTML
+
+  </div>
+
+#+END_HTML
+
+This should be a code block, though:
+
+#+BEGIN_EXAMPLE
+    <div>
+        foo
+    </div>
+#+END_EXAMPLE
+As should this:
+
+#+BEGIN_EXAMPLE
+    <div>foo</div>
+#+END_EXAMPLE
+Now, nested:
+
+
+#+BEGIN_HTML
+
+  <div>
+      <div>
+          <div>
+              
+
+#+END_HTML
+
+foo
+
+#+BEGIN_HTML
+
+  </div>
+      </div>
+  </div>
+
+#+END_HTML
+
+This should just be an HTML comment:
+
+
+#+BEGIN_HTML
+
+  <!-- Comment -->
+
+#+END_HTML
+
+Multiline:
+
+
+#+BEGIN_HTML
+
+  <!--
+  Blah
+  Blah
+  -->
+  
+  <!--
+      This is another comment.
+  -->
+
+#+END_HTML
+
+Code block:
+
+#+BEGIN_EXAMPLE
+    <!-- Comment -->
+#+END_EXAMPLE
+Just plain comment, with trailing spaces on the line:
+
+
+#+BEGIN_HTML
+
+  <!-- foo -->   
+
+#+END_HTML
+
+Code:
+
+#+BEGIN_EXAMPLE
+    <hr />
+#+END_EXAMPLE
+Hr's:
+
+
+#+BEGIN_HTML
+
+  <hr>
+  
+  <hr />
+  
+  <hr />
+  
+  <hr>   
+  
+  <hr />  
+  
+  <hr /> 
+  
+  <hr class="foo" id="bar" />
+  
+  <hr class="foo" id="bar" />
+  
+  <hr class="foo" id="bar">
+
+#+END_HTML
+
+--------------
+
+* Inline Markup
+
+This is /emphasized/, and so /is this/.
+
+This is *strong*, and so *is this*.
+
+An /[[/url][emphasized link]]/.
+
+*/This is strong and em./*
+
+So is */this/* word.
+
+*/This is strong and em./*
+
+So is */this/* word.
+
+This is code: =>=, =$=, =\=, =\$=, =<html>=.
+
++This is /strikeout/.+
+
+Superscripts: a^{bc}d a^{/hello/} a^{hello there}.
+
+Subscripts: H_{2}O, H_{23}O, H_{many of them}O.
+
+These should not be superscripts or subscripts, because of the
+unescaped spaces: a\^b c\^d, a~b c~d.
+
+--------------
+
+* Smart quotes, ellipses, dashes
+
+"Hello," said the spider. "'Shelob' is my name."
+
+'A', 'B', and 'C' are letters.
+
+'Oak,' 'elm,' and 'beech' are names of trees. So is 'pine.'
+
+'He said, "I want to go."' Were you alive in the 70's?
+
+Here is some quoted '=code=' and a
+"[[http://example.com/?foo=1&bar=2][quoted link]]".
+
+Some dashes: one---two --- three---four --- five.
+
+Dashes between numbers: 5--7, 255--66, 1987--1999.
+
+Ellipses...and...and....
+
+--------------
+
+* LaTeX
+
+
+-  \cite[22-23]{smith.1899}
+-  $2+2=4$
+-  $x \in y$
+-  $\alpha \wedge \omega$
+-  $223$
+-  $p$-Tree
+-  Here's some display math:
+   $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$
+-  Here's one that has a line break in it:
+   $\alpha + \omega \times x^2$.
+
+These shouldn't be math:
+
+
+-  To get the famous equation, write =$e = mc^2$=.
+-  $22,000 is a /lot/ of money. So is $34,000. (It worked if "lot"
+   is emphasized.)
+-  Shoes ($20) and socks ($5).
+-  Escaped =$=: $73 /this should be emphasized/ 23$.
+
+Here's a LaTeX table:
+
+\begin{tabular}{|l|l|}\hline
+Animal & Number \\ \hline
+Dog    & 2      \\
+Cat    & 1      \\ \hline
+\end{tabular}
+
+--------------
+
+* Special Characters
+
+Here is some unicode:
+
+
+-  I hat: Î
+-  o umlaut: ö
+-  section: §
+-  set membership: ∈
+-  copyright: ©
+
+AT&T has an ampersand in their name.
+
+AT&T is another way to write it.
+
+This & that.
+
+4 < 5.
+
+6 > 5.
+
+Backslash: \
+
+Backtick: `
+
+Asterisk: *
+
+Underscore: \_
+
+Left brace: {
+
+Right brace: }
+
+Left bracket: [
+
+Right bracket: ]
+
+Left paren: (
+
+Right paren: )
+
+Greater-than: >
+
+Hash: #
+
+Period: .
+
+Bang: !
+
+Plus: +
+
+Minus: -
+
+--------------
+
+* Links
+
+** Explicit
+
+Just a [[/url/][URL]].
+
+[[/url/][URL and title]].
+
+[[/url/][URL and title]].
+
+[[/url/][URL and title]].
+
+[[/url/][URL and title]]
+
+[[/url/][URL and title]]
+
+[[/url/with_underscore][with\_underscore]]
+
+[[mailto:nobody@nowhere.net][Email link]]
+
+[[][Empty]].
+
+** Reference
+
+Foo [[/url/][bar]].
+
+Foo [[/url/][bar]].
+
+Foo [[/url/][bar]].
+
+With [[/url/][embedded [brackets]]].
+
+[[/url/][b]] by itself should be a link.
+
+Indented [[/url][once]].
+
+Indented [[/url][twice]].
+
+Indented [[/url][thrice]].
+
+This should [not][] be a link.
+
+#+BEGIN_EXAMPLE
+    [not]: /url
+#+END_EXAMPLE
+Foo [[/url/][bar]].
+
+Foo [[/url/][biz]].
+
+** With ampersands
+
+Here's a
+[[http://example.com/?foo=1&bar=2][link with an ampersand in the URL]].
+
+Here's a link with an amersand in the link text:
+[[http://att.com/][AT&T]].
+
+Here's an [[/script?foo=1&bar=2][inline link]].
+
+Here's an [[/script?foo=1&bar=2][inline link in pointy braces]].
+
+** Autolinks
+
+With an ampersand: [[http://example.com/?foo=1&bar=2]]
+
+
+-  In a list?
+-  [[http://example.com/]]
+-  It should.
+
+An e-mail address:
+[[mailto:nobody@nowhere.net][=nobody@nowhere.net=]]
+
+
+#+BEGIN_QUOTE
+
+  Blockquoted: [[http://example.com/]]
+
+
+#+END_QUOTE
+
+Auto-links should not occur here: =<http://example.com/>=
+
+#+BEGIN_EXAMPLE
+    or here: <http://example.com/>
+#+END_EXAMPLE
+--------------
+
+* Images
+
+From "Voyage dans la Lune" by Georges Melies (1902):
+
+#+CAPTION: lalune
+
+[[lalune.jpg]]
+Here is a movie [[movie.jpg]] icon.
+
+--------------
+
+* Footnotes
+
+Here is a footnote reference, [1] and another. [2] This should
+/not/ be a footnote reference, because it contains a space.[\^my
+note] Here is an inline note. [3]
+
+
+#+BEGIN_QUOTE
+
+  Notes can go in quotes. [4]
+
+
+#+END_QUOTE
+
+
+1. And in list items. [5]
+
+This paragraph should not be part of the note, as it is not
+indented.
+
+[1] Here is the footnote. It can go anywhere after the footnote
+    reference. It need not be placed at the end of the document.
+
+[2] Here's the long note. This one contains multiple blocks.
+
+    Subsequent blocks are indented to show that they belong to the
+    footnote (as with list items).
+
+    #+BEGIN_EXAMPLE
+          { <code> }
+    #+END_EXAMPLE
+    If you want, you can indent every line, but you can also be lazy
+    and just indent the first line of each block.
+
+[3] This is /easier/ to type. Inline notes may contain
+    [[http://google.com][links]] and =]= verbatim characters, as well
+    as [bracketed text].
+
+[4] In quote.
+
+[5] In list.

From 85263ecda9ba33d3ff8c71e35ee6fe6aa89cf5bc Mon Sep 17 00:00:00 2001
From: Puneeth Chaganti <punchagan@gmail.com>
Date: Sun, 5 Dec 2010 11:18:02 +0530
Subject: [PATCH 3/3] Added templates/org.template to pandoc.cabal.

---
 pandoc.cabal | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/pandoc.cabal b/pandoc.cabal
index 465069336..56843a5e6 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -43,7 +43,7 @@ Data-Files:
                  templates/rst.template, templates/plain.template,
                  templates/mediawiki.template, templates/rtf.template,
                  templates/s5.template, templates/slidy.template,
-                 templates/textile.template
+                 templates/textile.template, templates/org.template
                  -- data for ODT writer
                  reference.odt,
                  -- stylesheet for EPUB writer