diff --git a/README b/README
index b4f7fa245..f24b4efe3 100644
--- a/README
+++ b/README
@@ -7,8 +7,8 @@ another, and a command-line tool that uses this library. It can read
 [markdown] and (subsets of) [reStructuredText], [HTML], and [LaTeX]; and
 it can write plain text, [markdown], [reStructuredText], [HTML], [LaTeX],
 [ConTeXt], [RTF], [DocBook XML], [OpenDocument XML], [ODT], [GNU Texinfo],
-[MediaWiki markup], [EPUB], [groff man] pages, and [Slidy] or [S5]
-HTML slide shows.
+[MediaWiki markup], [EPUB], [Textile], [groff man] pages, and [Slidy]
+or [S5] HTML slide shows.
 
 Pandoc's enhanced version of markdown includes syntax for footnotes,
 tables, flexible ordered lists, definition lists, delimited code blocks,
@@ -75,9 +75,9 @@ Supported output formats include `markdown`, `latex`, `context`
 (ConTeXt), `html`, `rtf` (rich text format), `rst`
 (reStructuredText), `docbook` (DocBook XML), `opendocument`
 (OpenDocument XML), `odt` (OpenOffice text document), `texinfo`, (GNU
-Texinfo), `mediawiki` (MediaWiki markup), `epub` (EPUB ebook),
-`man` (groff man), `slidy` (slidy HTML and javascript slide show), or
-`s5` (S5 HTML and javascript slide show).
+Texinfo), `mediawiki` (MediaWiki markup), `textile` (Textile),
+`epub` (EPUB ebook), `man` (groff man), `slidy` (slidy HTML and
+javascript slide show), or `s5` (S5 HTML and javascript slide show).
 
 Supported input formats include `markdown`, `html`, `latex`, and `rst`.
 Note that the `rst` reader only parses a subset of reStructuredText
@@ -1202,6 +1202,8 @@ In groff man output, it will be rendered verbatim without $'s.
 
 In MediaWiki output, it will be rendered inside `<math>` tags.
 
+In Textile output, it will be rendered inside `<span class="math">` tags.
+
 In RTF, Docbook, and OpenDocument output, it will be rendered, as far as
 possible, using unicode characters, and will otherwise appear verbatim.
 Unknown commands and symbols, and commands that cannot be dealt with
@@ -1412,6 +1414,7 @@ and pasted as literate Haskell source.
 [DocBook XML]:  http://www.docbook.org/
 [OpenDocument XML]: http://opendocument.xml.org/ 
 [ODT]: http://en.wikipedia.org/wiki/OpenDocument
+[Textile]: http://redcloth.org/textile
 [MediaWiki markup]: http://www.mediawiki.org/wiki/Help:Formatting
 [groff man]: http://developer.apple.com/DOCUMENTATION/Darwin/Reference/ManPages/man7/groff_man.7.html
 [Haskell]:  http://www.haskell.org/
diff --git a/man/man1/pandoc.1.md b/man/man1/pandoc.1.md
index 28a085b68..d6f188276 100644
--- a/man/man1/pandoc.1.md
+++ b/man/man1/pandoc.1.md
@@ -15,8 +15,9 @@ pandoc [*options*] [*input-file*]...
 Pandoc converts files from one markup format to another. It can
 read markdown and (subsets of) reStructuredText, HTML, and LaTeX, and
 it can write plain text, markdown, reStructuredText, HTML, LaTeX,
-ConTeXt, Texinfo, groff man, MediaWiki markup, RTF, OpenDocument XML,
-ODT, DocBook XML, EPUB, and Slidy or S5 HTML slide shows.
+ConTeXt, Texinfo, groff man, MediaWiki markup, Textile, RTF,
+OpenDocument XML, ODT, DocBook XML, EPUB, and Slidy or S5 HTML slide
+shows.
 
 If no *input-file* is specified, input is read from *stdin*.
 Otherwise, the *input-files* are concatenated (with a blank
@@ -72,10 +73,10 @@ should pipe input and output through `iconv`:
 :   Specify output format.  *FORMAT* can be `native` (native Haskell),
     `plain` (plain text), `markdown` (markdown), `rst` (reStructuredText),
     `html` (HTML), `latex` (LaTeX), `context` (ConTeXt), `man` (groff man), 
-    `mediawiki` (MediaWiki markup), `texinfo` (GNU Texinfo),
-    `docbook` (DocBook XML), `opendocument` (OpenDocument XML),
-    `odt` (OpenOffice text document), `epub` (EPUB book),
-    `slidy` (Slidy HTML and javascript slide show),
+    `mediawiki` (MediaWiki markup), `textile` (Textile),
+    `texinfo` (GNU Texinfo), `docbook` (DocBook XML),
+    `opendocument` (OpenDocument XML), `odt` (OpenOffice text document),
+    `epub` (EPUB book), `slidy` (Slidy HTML and javascript slide show),
     `s5` (S5 HTML and javascript slide show), or `rtf` (rich text
     format). Note that `odt` and `epub` output will not be directed to
     *stdout*; an output filename must be specified using the `-o/--output`
diff --git a/pandoc.cabal b/pandoc.cabal
index c760df2be..ddcb94ee0 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -18,8 +18,8 @@ Description:     Pandoc is a Haskell library for converting from one markup
                  this library. It can read markdown and (subsets of)
                  reStructuredText, HTML, and LaTeX, and it can write
                  markdown, reStructuredText, HTML, LaTeX, ConTeXt, Docbook,
-                 OpenDocument, ODT, RTF, MediaWiki, groff man pages, EPUB,
-                 and S5 and Slidy HTML slide shows.
+                 OpenDocument, ODT, RTF, MediaWiki, Textile, groff man pages,
+                 EPUB, and S5 and Slidy HTML slide shows.
                  .
                  Pandoc extends standard markdown syntax with footnotes,
                  embedded LaTeX, definition lists, tables, and other
@@ -43,6 +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
                  -- data for ODT writer
                  reference.odt,
                  -- stylesheet for EPUB writer
@@ -93,6 +94,7 @@ Extra-Source-Files:
                  tests/tables.plain,
                  tests/tables.markdown,
                  tests/tables.mediawiki,
+                 tests/tables.textile,
                  tests/tables.native,
                  tests/tables.opendocument,
                  tests/tables.texinfo,
@@ -110,6 +112,7 @@ Extra-Source-Files:
                  tests/writer.markdown,
                  tests/writer.plain,
                  tests/writer.mediawiki,
+                 tests/writer.textile,
                  tests/writer.native,
                  tests/writer.opendocument,
                  tests/writer.rst,
@@ -200,6 +203,7 @@ Library
                    Text.Pandoc.Writers.Man,
                    Text.Pandoc.Writers.Markdown,
                    Text.Pandoc.Writers.RST,
+                   Text.Pandoc.Writers.Textile,
                    Text.Pandoc.Writers.MediaWiki,
                    Text.Pandoc.Writers.RTF,
                    Text.Pandoc.Writers.ODT,
diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs
index ad429bc93..6cb8130a4 100644
--- a/src/Text/Pandoc.hs
+++ b/src/Text/Pandoc.hs
@@ -84,6 +84,7 @@ module Text.Pandoc
                , writeOpenDocument
                , writeMan
                , writeMediaWiki
+               , writeTextile
                , writeRTF
                , writeODT
                , writeEPUB
@@ -117,6 +118,7 @@ import Text.Pandoc.Writers.OpenDocument
 import Text.Pandoc.Writers.Man
 import Text.Pandoc.Writers.RTF 
 import Text.Pandoc.Writers.MediaWiki
+import Text.Pandoc.Writers.Textile
 import Text.Pandoc.Templates
 import Text.Pandoc.Parsing
 import Text.Pandoc.Shared
diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs
new file mode 100644
index 000000000..cb8f20a0a
--- /dev/null
+++ b/src/Text/Pandoc/Writers/Textile.hs
@@ -0,0 +1,415 @@
+{-
+Copyright (C) 2010 John MacFarlane <jgm@berkeley.edu>
+
+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.Textile
+   Copyright   : Copyright (C) 2010 John MacFarlane
+   License     : GNU GPL, version 2 or above 
+
+   Maintainer  : John MacFarlane <jgm@berkeley.edu>
+   Stability   : alpha
+   Portability : portable
+
+Conversion of 'Pandoc' documents to Textile markup.
+
+Textile:  <http://thresholdstate.com/articles/4312/the-textile-reference-manual>
+-}
+module Text.Pandoc.Writers.Textile ( writeTextile ) where
+import Text.Pandoc.Definition
+import Text.Pandoc.Shared 
+import Text.Pandoc.Templates (renderTemplate)
+import Text.Pandoc.XML ( escapeStringForXML )
+import Data.List ( intercalate )
+import Control.Monad.State
+import Data.Char ( isSpace )
+
+data WriterState = WriterState {
+    stNotes     :: [String]        -- Footnotes
+  , stListLevel :: [Char]          -- String at beginning of list items, e.g. "**"
+  , stUseTags   :: Bool            -- True if we should use HTML tags because we're in a complex list
+  }
+
+-- | Convert Pandoc to Textile.
+writeTextile :: WriterOptions -> Pandoc -> String
+writeTextile opts document = 
+  evalState (pandocToTextile opts document) 
+            (WriterState { stNotes = [], stListLevel = [], stUseTags = False }) 
+
+-- | Return Textile representation of document.
+pandocToTextile :: WriterOptions -> Pandoc -> State WriterState String
+pandocToTextile opts (Pandoc _ blocks) = do
+  body <- blockListToTextile opts blocks
+  notes <- liftM (unlines . reverse . stNotes) get
+  let main = body ++ if null notes then "" else ("\n\n" ++ notes)
+  let context = writerVariables opts ++ [ ("body", main) ]
+  if writerStandalone opts
+     then return $ renderTemplate context $ writerTemplate opts
+     else return main
+
+withUseTags :: State WriterState a -> State WriterState a
+withUseTags action = do
+  oldUseTags <- liftM stUseTags get
+  modify $ \s -> s { stUseTags = True }
+  result <- action
+  modify $ \s -> s { stUseTags = oldUseTags }
+  return result
+
+-- | Escape one character as needed for Textile.
+escapeCharForTextile :: Char -> String
+escapeCharForTextile x = case x of
+                         '&'    -> "&amp;"
+                         '<'    -> "&lt;"
+                         '>'    -> "&gt;"
+                         '"'    -> "&quot;"
+                         '*'    -> "&#42;"
+                         '_'    -> "&#95;"
+                         '@'    -> "&#64;"
+                         '|'    -> "&#124;"
+                         c      -> [c]
+
+-- | Escape string as needed for Textile.
+escapeStringForTextile :: String -> String
+escapeStringForTextile = concatMap escapeCharForTextile
+
+-- | Convert Pandoc block element to Textile. 
+blockToTextile :: WriterOptions -- ^ Options
+                -> Block         -- ^ Block element
+                -> State WriterState String 
+
+blockToTextile _ Null = return ""
+
+blockToTextile opts (Plain inlines) = 
+  inlineListToTextile opts inlines
+
+blockToTextile opts (Para [Image txt (src,tit)]) = do
+  capt <- blockToTextile opts (Para txt)
+  im <- inlineToTextile opts (Image txt (src,tit))
+  return $ im ++ "\n" ++ capt
+
+blockToTextile opts (Para inlines) = do
+  useTags <- liftM stUseTags get
+  listLevel <- liftM stListLevel get
+  contents <- inlineListToTextile opts inlines
+  return $ if useTags
+              then " <p>" ++ contents ++ "</p>"
+              else contents ++ if null listLevel then "\n" else ""
+
+blockToTextile _ (RawHtml str) = return str
+
+blockToTextile _ HorizontalRule = return "<hr />\n"
+
+blockToTextile opts (Header level inlines) = do
+  contents <- inlineListToTextile opts inlines
+  let prefix = 'h' : (show level ++ ". ")
+  return $ prefix ++ contents ++ "\n"
+
+blockToTextile _ (CodeBlock (_,classes,_) str) =
+  return $ "bc" ++ classes' ++ dots ++ escapeStringForXML str ++ "\n"
+    where classes' = if null classes
+                        then ""
+                        else "(" ++ unwords classes ++ ")"
+          dots = if any isBlank (lines str)
+                    then ".. "
+                    else ". "
+          isBlank = all isSpace
+
+blockToTextile opts (BlockQuote bs@[Para _]) = do
+  contents <- blockListToTextile opts bs
+  return $ "bq. " ++ contents
+
+blockToTextile opts (BlockQuote blocks) = do
+  contents <- blockListToTextile opts blocks
+  return $ "<blockquote>\n\n" ++ contents ++ "\n</blockquote>\n"
+
+blockToTextile opts (Table [] aligns widths headers rows') |
+         all (==0) widths && all (`elem` [AlignLeft,AlignDefault]) aligns = do
+  hs <- mapM (liftM (("_. " ++) . stripTrailingNewlines) . blockListToTextile opts) headers
+  let cellsToRow cells = "|" ++ intercalate "|" cells ++ "|"
+  let header = if all null headers then "" else cellsToRow hs
+  let rowToCells = mapM (liftM stripTrailingNewlines . blockListToTextile opts)
+  bs <- mapM rowToCells rows'
+  let body = unlines $ map cellsToRow bs
+  return $ header ++ "\n" ++ body ++ "\n"
+
+blockToTextile opts (Table capt aligns widths headers rows') = do
+  let alignStrings = map alignmentToString aligns
+  captionDoc <- if null capt
+                   then return ""
+                   else do
+                      c <- inlineListToTextile opts capt
+                      return $ " <caption>" ++ c ++ "</caption>\n"
+  let percent w = show (truncate (100*w) :: Integer) ++ "%"
+  let coltags = if all (== 0.0) widths
+                   then ""
+                   else unlines $ map
+                         (\w -> " <col width=\"" ++ percent w ++ "\" />") widths
+  head' <- if all null headers
+              then return ""
+              else do
+                 hs <- tableRowToTextile opts alignStrings 0 headers
+                 return $ " <thead>\n" ++ hs ++ "\n </thead>\n"
+  body' <- zipWithM (tableRowToTextile opts alignStrings) [1..] rows'
+  return $ " <table>\n" ++ captionDoc ++ coltags ++ head' ++
+            " <tbody>\n" ++ unlines body' ++ " </tbody>\n </table>\n"
+
+blockToTextile opts x@(BulletList items) = do
+  oldUseTags <- liftM stUseTags get
+  let useTags = oldUseTags || not (isSimpleList x)
+  if useTags
+     then do
+        contents <- withUseTags $ mapM (listItemToTextile opts) items
+        return $ " <ul>\n" ++ vcat contents ++ " </ul>\n"
+     else do
+        modify $ \s -> s { stListLevel = stListLevel s ++ "*" }
+        level <- get >>= return . length . stListLevel
+        contents <- mapM (listItemToTextile opts) items
+        modify $ \s -> s { stListLevel = init (stListLevel s) }
+        return $ vcat contents ++ (if level > 1 then "" else "\n")
+
+blockToTextile opts x@(OrderedList attribs items) = do
+  oldUseTags <- liftM stUseTags get
+  let useTags = oldUseTags || not (isSimpleList x)
+  if useTags
+     then do
+        contents <- withUseTags $ mapM (listItemToTextile opts) items
+        return $ " <ol" ++ listAttribsToString attribs ++ ">\n" ++ vcat contents ++
+                   " </ol>\n"
+     else do
+        modify $ \s -> s { stListLevel = stListLevel s ++ "#" }
+        level <- get >>= return . length . stListLevel
+        contents <- mapM (listItemToTextile opts) items
+        modify $ \s -> s { stListLevel = init (stListLevel s) }
+        return $ vcat contents ++ (if level > 1 then "" else "\n")
+
+blockToTextile opts (DefinitionList items) = do
+  contents <- withUseTags $ mapM (definitionListItemToTextile opts) items
+  return $ " <dl>\n" ++ vcat contents ++ " </dl>\n"
+
+-- Auxiliary functions for lists:
+
+-- | Convert ordered list attributes to HTML attribute string
+listAttribsToString :: ListAttributes -> String
+listAttribsToString (startnum, numstyle, _) =
+  let numstyle' = camelCaseToHyphenated $ show numstyle
+  in  (if startnum /= 1
+          then " start=\"" ++ show startnum ++ "\""
+          else "") ++
+      (if numstyle /= DefaultStyle
+          then " style=\"list-style-type: " ++ numstyle' ++ ";\""
+          else "")
+
+-- | Convert bullet or ordered list item (list of blocks) to Textile.
+listItemToTextile :: WriterOptions -> [Block] -> State WriterState String
+listItemToTextile opts items = do
+  contents <- blockListToTextile opts items
+  useTags <- get >>= return . stUseTags
+  if useTags
+     then return $ " <li>" ++ contents ++ "</li>"
+     else do
+       marker <- get >>= return . stListLevel
+       return $ marker ++ " " ++ contents
+
+-- | Convert definition list item (label, list of blocks) to Textile.
+definitionListItemToTextile :: WriterOptions
+                             -> ([Inline],[[Block]]) 
+                             -> State WriterState String
+definitionListItemToTextile opts (label, items) = do
+  labelText <- inlineListToTextile opts label
+  contents <- mapM (blockListToTextile opts) items
+  return $ " <dt>" ++ labelText ++ "</dt>\n" ++
+          (intercalate "\n" $ map (\d -> " <dd>" ++ d ++ "</dd>") contents)
+
+-- | True if the list can be handled by simple wiki markup, False if HTML tags will be needed.
+isSimpleList :: Block -> Bool
+isSimpleList x =
+  case x of
+       BulletList items                 -> all isSimpleListItem items
+       OrderedList (num, sty, _) items  -> all isSimpleListItem items &&
+                                            num == 1 && sty `elem` [DefaultStyle, Decimal]
+       _                                -> False
+
+-- | True if list item can be handled with the simple wiki syntax.  False if
+--   HTML tags will be needed.
+isSimpleListItem :: [Block] -> Bool
+isSimpleListItem []  = True
+isSimpleListItem [x] =
+  case x of
+       Plain _           -> True
+       Para  _           -> True
+       BulletList _      -> isSimpleList x
+       OrderedList _ _   -> isSimpleList x
+       _                 -> False
+isSimpleListItem [x, y] | isPlainOrPara x =
+  case y of
+       BulletList _      -> isSimpleList y
+       OrderedList _ _   -> isSimpleList y
+       _                 -> False
+isSimpleListItem _ = False
+
+isPlainOrPara :: Block -> Bool
+isPlainOrPara (Plain _) = True
+isPlainOrPara (Para  _) = True
+isPlainOrPara _         = False
+
+-- | Concatenates strings with line breaks between them.
+vcat :: [String] -> String
+vcat = intercalate "\n"
+
+-- Auxiliary functions for tables. (TODO: these are common to HTML, MediaWiki,
+-- and Textile writers, and should be abstracted out.)
+
+tableRowToTextile :: WriterOptions
+                    -> [String]
+                    -> Int
+                    -> [[Block]]
+                    -> State WriterState String
+tableRowToTextile opts alignStrings rownum cols' = do
+  let celltype = if rownum == 0 then "th" else "td"
+  let rowclass = case rownum of
+                      0                  -> "header"
+                      x | x `rem` 2 == 1 -> "odd"
+                      _                  -> "even"
+  cols'' <- sequence $ zipWith 
+            (\alignment item -> tableItemToTextile opts celltype alignment item) 
+            alignStrings cols'
+  return $ "<tr class=\"" ++ rowclass ++ "\">\n" ++ unlines cols'' ++ "</tr>"
+
+alignmentToString :: Alignment -> [Char]
+alignmentToString alignment = case alignment of
+                                 AlignLeft    -> "left"
+                                 AlignRight   -> "right"
+                                 AlignCenter  -> "center"
+                                 AlignDefault -> "left"
+
+tableItemToTextile :: WriterOptions
+                     -> String
+                     -> String
+                     -> [Block]
+                     -> State WriterState String
+tableItemToTextile opts celltype align' item = do
+  let mkcell x = "<" ++ celltype ++ " align=\"" ++ align' ++ "\">" ++
+                    x ++ "</" ++ celltype ++ ">"
+  contents <- blockListToTextile opts item
+  return $ mkcell contents
+
+-- | Convert list of Pandoc block elements to Textile.
+blockListToTextile :: WriterOptions -- ^ Options
+                    -> [Block]       -- ^ List of block elements
+                    -> State WriterState String 
+blockListToTextile opts blocks =
+  mapM (blockToTextile opts) blocks >>= return . vcat
+
+-- | Convert list of Pandoc inline elements to Textile.
+inlineListToTextile :: WriterOptions -> [Inline] -> State WriterState String
+inlineListToTextile opts lst =
+  mapM (inlineToTextile opts) lst >>= return . concat
+
+-- | Convert Pandoc inline element to Textile.
+inlineToTextile :: WriterOptions -> Inline -> State WriterState String
+
+inlineToTextile opts (Emph lst) = do 
+  contents <- inlineListToTextile opts lst
+  return $ if '_' `elem` contents
+              then "<em>" ++ contents ++ "</em>"
+              else "_" ++ contents ++ "_" 
+
+inlineToTextile opts (Strong lst) = do
+  contents <- inlineListToTextile opts lst
+  return $ if '*' `elem` contents
+              then "<strong>" ++ contents ++ "</strong>"
+              else "*" ++ contents ++ "*"
+
+inlineToTextile opts (Strikeout lst) = do
+  contents <- inlineListToTextile opts lst
+  return $ if '-' `elem` contents
+              then "<del>" ++ contents ++ "</del>"
+              else "-" ++ contents ++ "-"
+
+inlineToTextile opts (Superscript lst) = do
+  contents <- inlineListToTextile opts lst
+  return $ if '^' `elem` contents
+              then "<sup>" ++ contents ++ "</sup>"
+              else "[^" ++ contents ++ "^]"
+
+inlineToTextile opts (Subscript lst) = do
+  contents <- inlineListToTextile opts lst
+  return $ if '~' `elem` contents
+              then "<sub>" ++ contents ++ "</sub>"
+              else "[~" ++ contents ++ "~]"
+
+inlineToTextile opts (SmallCaps lst) = inlineListToTextile opts lst
+
+inlineToTextile opts (Quoted SingleQuote lst) = do
+  contents <- inlineListToTextile opts lst
+  return $ "'" ++ contents ++ "'"
+
+inlineToTextile opts (Quoted DoubleQuote lst) = do
+  contents <- inlineListToTextile opts lst
+  return $ "\"" ++ contents ++ "\""
+
+inlineToTextile opts (Cite _  lst) = inlineListToTextile opts lst
+
+inlineToTextile _ EmDash = return " -- "
+
+inlineToTextile _ EnDash = return " - "
+
+inlineToTextile _ Apostrophe = return "'"
+
+inlineToTextile _ Ellipses = return "..."
+
+inlineToTextile _ (Code str) =
+  return $ if '@' `elem` str
+           then "<tt>" ++ escapeStringForXML str ++ "</tt>"
+           else "@" ++ escapeStringForXML str ++ "@" 
+
+inlineToTextile _ (Str str) = return $ escapeStringForTextile str
+
+inlineToTextile _ (Math _ str) =
+  return $ "<span class=\"math\">" ++ escapeStringForXML str ++ "</math>"
+
+inlineToTextile _ (TeX _) = return ""
+
+inlineToTextile _ (HtmlInline str) = return str 
+
+inlineToTextile _ (LineBreak) = return "\n"
+
+inlineToTextile _ Space = return " "
+
+inlineToTextile opts (Link txt (src, _)) = do
+  label <- case txt of
+                [Code s]  -> return s
+                _         -> inlineListToTextile opts txt
+  return $ "\"" ++ label ++ "\":" ++ src
+
+inlineToTextile opts (Image alt (source, tit)) = do
+  alt' <- inlineListToTextile opts alt
+  let txt = if null tit
+               then if null alt'
+                       then ""
+                       else "(" ++ alt' ++ ")"
+               else "(" ++ tit ++ ")"
+  return $ "!" ++ source ++ txt ++ "!"
+
+inlineToTextile opts (Note contents) = do
+  curNotes <- liftM stNotes get
+  let newnum = length curNotes + 1
+  contents' <- blockListToTextile opts contents
+  let thisnote = "fn" ++ show newnum ++ ". " ++ contents' ++ "\n"
+  modify $ \s -> s { stNotes = thisnote : curNotes }
+  return $ "[" ++ show newnum ++ "]"
+  -- note - may not work for notes with multiple blocks
diff --git a/src/pandoc.hs b/src/pandoc.hs
index 4caabdd29..4f5a1c32a 100644
--- a/src/pandoc.hs
+++ b/src/pandoc.hs
@@ -122,6 +122,7 @@ writers = [("native"       , writeNative)
           ,("rst"          , writeRST)
           ,("rst+lhs"      , writeRST)
           ,("mediawiki"    , writeMediaWiki)
+          ,("textile"      , writeTextile)
           ,("rtf"          , writeRTF)
           ]
 
diff --git a/templates/textile.template b/templates/textile.template
new file mode 100644
index 000000000..1862360a8
--- /dev/null
+++ b/templates/textile.template
@@ -0,0 +1,12 @@
+$if(legacy-header)$
+$legacy-header$
+$endif$
+$for(include-before)$
+$include-before$
+
+$endfor$
+$body$
+$for(include-after)$
+
+$include-after$
+$endfor$
diff --git a/tests/RunTests.hs b/tests/RunTests.hs
index 1715400fd..cf2997a06 100644
--- a/tests/RunTests.hs
+++ b/tests/RunTests.hs
@@ -60,6 +60,7 @@ writerFormats = [ "native"
                 , "markdown"
                 , "rst"
                 , "mediawiki"
+                , "textile"
                 , "rtf"
                 ]
 
diff --git a/tests/tables.textile b/tests/tables.textile
new file mode 100644
index 000000000..ccb34cf58
--- /dev/null
+++ b/tests/tables.textile
@@ -0,0 +1,212 @@
+Simple table with caption:
+
+ <table>
+ <caption>Demonstration of simple table syntax.</caption>
+ <thead>
+<tr class="header">
+<th align="right">Right</th>
+<th align="left">Left</th>
+<th align="center">Center</th>
+<th align="left">Default</th>
+</tr>
+ </thead>
+ <tbody>
+<tr class="odd">
+<td align="right">12</td>
+<td align="left">12</td>
+<td align="center">12</td>
+<td align="left">12</td>
+</tr>
+<tr class="even">
+<td align="right">123</td>
+<td align="left">123</td>
+<td align="center">123</td>
+<td align="left">123</td>
+</tr>
+<tr class="odd">
+<td align="right">1</td>
+<td align="left">1</td>
+<td align="center">1</td>
+<td align="left">1</td>
+</tr>
+ </tbody>
+ </table>
+
+Simple table without caption:
+
+ <table>
+ <thead>
+<tr class="header">
+<th align="right">Right</th>
+<th align="left">Left</th>
+<th align="center">Center</th>
+<th align="left">Default</th>
+</tr>
+ </thead>
+ <tbody>
+<tr class="odd">
+<td align="right">12</td>
+<td align="left">12</td>
+<td align="center">12</td>
+<td align="left">12</td>
+</tr>
+<tr class="even">
+<td align="right">123</td>
+<td align="left">123</td>
+<td align="center">123</td>
+<td align="left">123</td>
+</tr>
+<tr class="odd">
+<td align="right">1</td>
+<td align="left">1</td>
+<td align="center">1</td>
+<td align="left">1</td>
+</tr>
+ </tbody>
+ </table>
+
+Simple table indented two spaces:
+
+ <table>
+ <caption>Demonstration of simple table syntax.</caption>
+ <thead>
+<tr class="header">
+<th align="right">Right</th>
+<th align="left">Left</th>
+<th align="center">Center</th>
+<th align="left">Default</th>
+</tr>
+ </thead>
+ <tbody>
+<tr class="odd">
+<td align="right">12</td>
+<td align="left">12</td>
+<td align="center">12</td>
+<td align="left">12</td>
+</tr>
+<tr class="even">
+<td align="right">123</td>
+<td align="left">123</td>
+<td align="center">123</td>
+<td align="left">123</td>
+</tr>
+<tr class="odd">
+<td align="right">1</td>
+<td align="left">1</td>
+<td align="center">1</td>
+<td align="left">1</td>
+</tr>
+ </tbody>
+ </table>
+
+Multiline table with caption:
+
+ <table>
+ <caption>Here's the caption. It may span multiple lines.</caption>
+ <col width="15%" />
+ <col width="13%" />
+ <col width="16%" />
+ <col width="33%" />
+ <thead>
+<tr class="header">
+<th align="center">Centered Header</th>
+<th align="left">Left Aligned</th>
+<th align="right">Right Aligned</th>
+<th align="left">Default aligned</th>
+</tr>
+ </thead>
+ <tbody>
+<tr class="odd">
+<td align="center">First</td>
+<td align="left">row</td>
+<td align="right">12.0</td>
+<td align="left">Example of a row that spans multiple lines.</td>
+</tr>
+<tr class="even">
+<td align="center">Second</td>
+<td align="left">row</td>
+<td align="right">5.0</td>
+<td align="left">Here's another one. Note the blank line between rows.</td>
+</tr>
+ </tbody>
+ </table>
+
+Multiline table without caption:
+
+ <table>
+ <col width="15%" />
+ <col width="13%" />
+ <col width="16%" />
+ <col width="33%" />
+ <thead>
+<tr class="header">
+<th align="center">Centered Header</th>
+<th align="left">Left Aligned</th>
+<th align="right">Right Aligned</th>
+<th align="left">Default aligned</th>
+</tr>
+ </thead>
+ <tbody>
+<tr class="odd">
+<td align="center">First</td>
+<td align="left">row</td>
+<td align="right">12.0</td>
+<td align="left">Example of a row that spans multiple lines.</td>
+</tr>
+<tr class="even">
+<td align="center">Second</td>
+<td align="left">row</td>
+<td align="right">5.0</td>
+<td align="left">Here's another one. Note the blank line between rows.</td>
+</tr>
+ </tbody>
+ </table>
+
+Table without column headers:
+
+ <table>
+ <tbody>
+<tr class="odd">
+<td align="right">12</td>
+<td align="left">12</td>
+<td align="center">12</td>
+<td align="right">12</td>
+</tr>
+<tr class="even">
+<td align="right">123</td>
+<td align="left">123</td>
+<td align="center">123</td>
+<td align="right">123</td>
+</tr>
+<tr class="odd">
+<td align="right">1</td>
+<td align="left">1</td>
+<td align="center">1</td>
+<td align="right">1</td>
+</tr>
+ </tbody>
+ </table>
+
+Multiline table without column headers:
+
+ <table>
+ <col width="15%" />
+ <col width="13%" />
+ <col width="16%" />
+ <col width="33%" />
+ <tbody>
+<tr class="odd">
+<td align="center">First</td>
+<td align="left">row</td>
+<td align="right">12.0</td>
+<td align="left">Example of a row that spans multiple lines.</td>
+</tr>
+<tr class="even">
+<td align="center">Second</td>
+<td align="left">row</td>
+<td align="right">5.0</td>
+<td align="left">Here's another one. Note the blank line between rows.</td>
+</tr>
+ </tbody>
+ </table>
+
diff --git a/tests/writer.textile b/tests/writer.textile
new file mode 100644
index 000000000..b3e2e545b
--- /dev/null
+++ b/tests/writer.textile
@@ -0,0 +1,677 @@
+This is a set of tests for pandoc. Most of them are adapted from John Gruber's markdown test suite.
+
+<hr />
+
+h1. Headers
+
+h2. Level 2 with an "embedded link":/url
+
+h3. Level 3 with _emphasis_
+
+h4. Level 4
+
+h5. Level 5
+
+h1. Level 1
+
+h2. Level 2 with _emphasis_
+
+h3. Level 3
+
+with no blank line
+
+h2. Level 2
+
+with no blank line
+
+<hr />
+
+h1. 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. &#42; criminey.
+
+There should be a hard line break
+here.
+
+<hr />
+
+h1. Block Quotes
+
+E-mail style:
+
+bq. This is a block quote. It is pretty short.
+
+<blockquote>
+
+Code in a block quote:
+
+bc. sub status {
+    print &quot;working&quot;;
+}
+
+A list:
+
+# item one
+# item two
+
+Nested block quotes:
+
+bq. nested
+
+bq. nested
+
+</blockquote>
+
+This should not be a block quote: 2 &gt; 1.
+
+And a following paragraph.
+
+<hr />
+
+h1. Code Blocks
+
+Code:
+
+bc.. ---- (should be four hyphens)
+
+sub status {
+    print &quot;working&quot;;
+}
+
+this code block is indented by one tab
+
+And:
+
+bc..     this code block is indented by two tabs
+
+These should not be escaped:  \$ \\ \&gt; \[ \{
+
+<hr />
+
+h1. Lists
+
+h2. 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
+
+h2. Ordered
+
+Tight:
+
+# First
+# Second
+# Third
+
+and:
+
+# One
+# Two
+# Three
+
+Loose using tabs:
+
+# First
+# Second
+# Third
+
+and using spaces:
+
+# One
+# Two
+# Three
+
+Multiple paragraphs:
+
+ <ol style="list-style-type: decimal;">
+ <li> <p>Item 1, graf one.</p>
+ <p>Item 1. graf two. The quick brown fox jumped over the lazy dog's back.</p></li>
+ <li> <p>Item 2.</p></li>
+ <li> <p>Item 3.</p></li> </ol>
+
+h2. Nested
+
+* Tab
+** Tab
+*** Tab
+
+Here's another:
+
+# First
+# Second:
+#* Fee
+#* Fie
+#* Foe
+# Third
+
+Same thing but with paragraphs:
+
+# First
+# Second:
+#* Fee
+#* Fie
+#* Foe
+# Third
+
+h2. 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
+
+h2. Fancy list markers
+
+ <ol start="2" style="list-style-type: decimal;">
+ <li>begins with 2</li>
+ <li> <p>and now 3</p>
+ <p>with a continuation</p>
+ <ol start="4" style="list-style-type: lower-roman;">
+ <li>sublist with roman numerals, starting with 4</li>
+ <li>more items
+ <ol style="list-style-type: upper-alpha;">
+ <li>a subsublist</li>
+ <li>a subsublist</li> </ol>
+</li> </ol>
+</li> </ol>
+
+Nesting:
+
+ <ol style="list-style-type: upper-alpha;">
+ <li>Upper Alpha
+ <ol style="list-style-type: upper-roman;">
+ <li>Upper Roman.
+ <ol start="6" style="list-style-type: decimal;">
+ <li>Decimal start with 6
+ <ol start="3" style="list-style-type: lower-alpha;">
+ <li>Lower alpha with paren</li> </ol>
+</li> </ol>
+</li> </ol>
+</li> </ol>
+
+Autonumbering:
+
+# Autonumber.
+# More.
+## Nested.
+
+Should not be a list item:
+
+M.A. 2007
+
+B. Williams
+
+<hr />
+
+h1. Definition Lists
+
+Tight using spaces:
+
+ <dl>
+ <dt>apple</dt>
+ <dd>red fruit</dd>
+ <dt>orange</dt>
+ <dd>orange fruit</dd>
+ <dt>banana</dt>
+ <dd>yellow fruit</dd> </dl>
+
+Tight using tabs:
+
+ <dl>
+ <dt>apple</dt>
+ <dd>red fruit</dd>
+ <dt>orange</dt>
+ <dd>orange fruit</dd>
+ <dt>banana</dt>
+ <dd>yellow fruit</dd> </dl>
+
+Loose:
+
+ <dl>
+ <dt>apple</dt>
+ <dd> <p>red fruit</p></dd>
+ <dt>orange</dt>
+ <dd> <p>orange fruit</p></dd>
+ <dt>banana</dt>
+ <dd> <p>yellow fruit</p></dd> </dl>
+
+Multiple blocks with italics:
+
+ <dl>
+ <dt>_apple_</dt>
+ <dd> <p>red fruit</p>
+ <p>contains seeds, crisp, pleasant to taste</p></dd>
+ <dt>_orange_</dt>
+ <dd> <p>orange fruit</p>
+bc. { orange code block }
+
+bq.  <p>orange block quote</p></dd> </dl>
+
+Multiple definitions, tight:
+
+ <dl>
+ <dt>apple</dt>
+ <dd>red fruit</dd>
+ <dd>computer</dd>
+ <dt>orange</dt>
+ <dd>orange fruit</dd>
+ <dd>bank</dd> </dl>
+
+Multiple definitions, loose:
+
+ <dl>
+ <dt>apple</dt>
+ <dd> <p>red fruit</p></dd>
+ <dd> <p>computer</p></dd>
+ <dt>orange</dt>
+ <dd> <p>orange fruit</p></dd>
+ <dd> <p>bank</p></dd> </dl>
+
+Blank line after term, indented marker, alternate markers:
+
+ <dl>
+ <dt>apple</dt>
+ <dd> <p>red fruit</p></dd>
+ <dd> <p>computer</p></dd>
+ <dt>orange</dt>
+ <dd> <p>orange fruit</p>
+ <ol style="list-style-type: decimal;">
+ <li>sublist</li>
+ <li>sublist</li> </ol>
+</dd> </dl>
+
+h1. HTML Blocks
+
+Simple block on one line:
+
+<div>
+foo
+</div>
+
+And nested without indentation:
+
+<div>
+<div>
+<div>
+foo
+</div>
+</div>
+<div>
+bar
+</div>
+</div>
+
+Interpreted markdown in a table:
+
+<table>
+<tr>
+<td>
+This is _emphasized_
+</td>
+<td>
+And this is *strong*
+</td>
+</tr>
+</table>
+
+<script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script>
+
+Here's a simple block:
+
+<div>
+    
+foo
+</div>
+
+This should be a code block, though:
+
+bc. &lt;div&gt;
+    foo
+&lt;/div&gt;
+
+As should this:
+
+bc. &lt;div&gt;foo&lt;/div&gt;
+
+Now, nested:
+
+<div>
+    <div>
+        <div>
+            
+foo
+</div>
+    </div>
+</div>
+
+This should just be an HTML comment:
+
+<!-- Comment -->
+
+Multiline:
+
+<!--
+Blah
+Blah
+-->
+
+<!--
+    This is another comment.
+-->
+
+Code block:
+
+bc. &lt;!-- Comment --&gt;
+
+Just plain comment, with trailing spaces on the line:
+
+<!-- foo -->   
+
+Code:
+
+bc. &lt;hr /&gt;
+
+Hr's:
+
+<hr>
+
+<hr />
+
+<hr />
+
+<hr>   
+
+<hr />  
+
+<hr /> 
+
+<hr class="foo" id="bar" />
+
+<hr class="foo" id="bar" />
+
+<hr class="foo" id="bar">
+
+<hr />
+
+h1. Inline Markup
+
+This is _emphasized_, and so _is this_.
+
+This is *strong*, and so *is this*.
+
+An _"emphasized link":/url_.
+
+*_This is strong and em._*
+
+So is *_this_* word.
+
+*_This is strong and em._*
+
+So is *_this_* word.
+
+This is code: @&gt;@, @$@, @\@, @\$@, @&lt;html&gt;@.
+
+-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.
+
+<hr />
+
+h1. 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 ""quoted link":http://example.com/?foo=1&bar=2".
+
+Some dashes: one -- two  --  three -- four  --  five.
+
+Dashes between numbers: 5 - 7, 255 - 66, 1987 - 1999.
+
+Ellipses...and...and....
+
+<hr />
+
+h1. LaTeX
+
+* 
+* <span class="math">2+2=4</math>
+* <span class="math">x \in y</math>
+* <span class="math">\alpha \wedge \omega</math>
+* <span class="math">223</math>
+* <span class="math">p</math>-Tree
+* Here's some display math: <span class="math">\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}</math>
+* Here's one that has a line break in it: <span class="math">\alpha + \omega \times x^2</math>.
+
+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:
+
+
+
+<hr />
+
+h1. Special Characters
+
+Here is some unicode:
+
+* I hat: Î
+* o umlaut: ö
+* section: §
+* set membership: ∈
+* copyright: ©
+
+AT&amp;T has an ampersand in their name.
+
+AT&amp;T is another way to write it.
+
+This &amp; that.
+
+4 &lt; 5.
+
+6 &gt; 5.
+
+Backslash: \
+
+Backtick: `
+
+Asterisk: &#42;
+
+Underscore: &#95;
+
+Left brace: {
+
+Right brace: }
+
+Left bracket: [
+
+Right bracket: ]
+
+Left paren: (
+
+Right paren: )
+
+Greater-than: &gt;
+
+Hash: #
+
+Period: .
+
+Bang: !
+
+Plus: +
+
+Minus: -
+
+<hr />
+
+h1. Links
+
+h2. Explicit
+
+Just a "URL":/url/.
+
+"URL and title":/url/.
+
+"URL and title":/url/.
+
+"URL and title":/url/.
+
+"URL and title":/url/
+
+"URL and title":/url/
+
+"with&#95;underscore":/url/with_underscore
+
+"Email link":mailto:nobody@nowhere.net
+
+"Empty":.
+
+h2. Reference
+
+Foo "bar":/url/.
+
+Foo "bar":/url/.
+
+Foo "bar":/url/.
+
+With "embedded [brackets]":/url/.
+
+"b":/url/ by itself should be a link.
+
+Indented "once":/url.
+
+Indented "twice":/url.
+
+Indented "thrice":/url.
+
+This should [not][] be a link.
+
+bc. [not]: /url
+
+Foo "bar":/url/.
+
+Foo "biz":/url/.
+
+h2. With ampersands
+
+Here's a "link with an ampersand in the URL":http://example.com/?foo=1&bar=2.
+
+Here's a link with an amersand in the link text: "AT&amp;T":http://att.com/.
+
+Here's an "inline link":/script?foo=1&bar=2.
+
+Here's an "inline link in pointy braces":/script?foo=1&bar=2.
+
+h2. Autolinks
+
+With an ampersand: "http://example.com/?foo=1&bar=2":http://example.com/?foo=1&bar=2
+
+* In a list?
+* "http://example.com/":http://example.com/
+* It should.
+
+An e-mail address: "nobody@nowhere.net":mailto:nobody@nowhere.net
+
+bq. Blockquoted: "http://example.com/":http://example.com/
+
+Auto-links should not occur here: @&lt;http://example.com/&gt;@
+
+bc. or here: &lt;http://example.com/&gt;
+
+<hr />
+
+h1. Images
+
+From "Voyage dans la Lune" by Georges Melies (1902):
+
+!lalune.jpg(Voyage dans la Lune)!
+lalune
+
+Here is a movie !movie.jpg(movie)! icon.
+
+<hr />
+
+h1. 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]
+
+bq. Notes can go in quotes.[4]
+
+# And in list items.[5]
+
+This paragraph should not be part of the note, as it is not indented.
+
+
+fn1. Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.
+
+
+fn2. 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).
+
+bc.   { &lt;code&gt; }
+
+If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.
+
+
+fn3. This is _easier_ to type. Inline notes may contain "links":http://google.com and @]@ verbatim characters, as well as [bracketed text].
+
+
+fn4. In quote.
+
+
+fn5. In list.
+
+