diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index d5add8f88..52a9e12c8 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -43,7 +43,6 @@ Implemented but discarded:
 Left to be implemented:
  - dimension sign
  - all caps
- - definition lists
  - continued blocks (ex bq..)
 
 TODO : refactor common patterns across readers :
@@ -199,7 +198,8 @@ anyList = try $ do
 -- provided correct nesting
 anyListAtDepth :: Int -> GenParser Char ParserState Block
 anyListAtDepth depth = choice [ bulletListAtDepth depth,
-                                orderedListAtDepth depth ]
+                                orderedListAtDepth depth,
+                                definitionList ]
 
 -- | Bullet List of given depth, depth being the number of leading '*'
 bulletListAtDepth :: Int -> GenParser Char ParserState Block
@@ -236,6 +236,33 @@ orderedListItemAtDepth depth = try $ do
   sublist <- option [] (anyListAtDepth (depth + 1) >>= return . (:[]))
   return (p:sublist)
 
+-- | A definition list is a set of consecutive definition items
+definitionList :: GenParser Char ParserState Block  
+definitionList = try $ do
+  items <- many1 definitionListItem
+  return $ DefinitionList items
+  
+-- | A definition list item in textile begins with '- ', followed by
+-- the term defined, then spaces and ":=". The definition follows, on
+-- the same single line, or spaned on multiple line, after a line
+-- break.
+definitionListItem :: GenParser Char ParserState ([Inline], [[Block]])
+definitionListItem = try $ do
+  string "- "
+  term <- many1Till inline (try (whitespace >> string ":="))
+  def <- inlineDef <|> multilineDef
+  return (term, def)
+  where inlineDef :: GenParser Char ParserState [[Block]]
+        inlineDef = liftM (\d -> [[Plain d]]) $ try (whitespace >> inlines)
+        multilineDef :: GenParser Char ParserState [[Block]]
+        multilineDef = try $ do
+          optional whitespace >> newline
+          s <- many1Till anyChar (try (string "=:" >> newline))
+          -- this ++ "\n\n" does not look very good
+          ds <- parseFromString parseBlocks (s ++ "\n\n")
+          return [ds]
+  
+  
 -- | This terminates a block such as a paragraph. Because of raw html
 -- blocks support, we have to lookAhead for a rawHtmlBlock.
 blockBreak :: GenParser Char ParserState ()
diff --git a/tests/textile-reader.native b/tests/textile-reader.native
index 683ebd39b..957ebeb35 100644
--- a/tests/textile-reader.native
+++ b/tests/textile-reader.native
@@ -52,6 +52,20 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
         , BulletList
           [ [ Plain [Str "ui",Space,Str "2",Str ".",Str "1",Str ".",Str "1"] ]
           , [ Plain [Str "ui",Space,Str "2",Str ".",Str "1",Str ".",Str "2"] ] ] ] ] ] ]
+, Header 2 [Str "Definition",Space,Str "List"]
+, DefinitionList
+  [ ([Str "coffee"],
+     [ [ Plain [Str "Hot",Space,Str "and",Space,Str "black"] ]
+     ])
+  , ([Str "tea"],
+     [ [ Plain [Str "Also",Space,Str "hot",Str ",",Space,Str "but",Space,Str "a",Space,Str "little",Space,Str "less",Space,Str "black"] ]
+     ])
+  , ([Str "milk"],
+     [ [ Para [Str "Nourishing",Space,Str "beverage",Space,Str "for",Space,Str "baby",Space,Str "cows",Str "."]
+       , Para [Str "Cold",Space,Str "drink",Space,Str "that",Space,Str "goes",Space,Str "great",Space,Str "with",Space,Str "cookies",Str "."] ]])
+  , ([Str "beer"],
+     [ [ Plain [Str "fresh",Space,Str "and",Space,Str "bitter"] ]
+     ]) ]
 , Header 1 [Str "Inline",Space,Str "Markup"]
 , Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str ".",LineBreak,Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str ".",LineBreak,Str "A",Space,Link [Strong [Str "strong",Space,Str "link"]] ("http://www.foobar.com",""),Str "."]
 , Para [Emph [Strong [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em",Str "."]],LineBreak,Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Space,Str "and",Space,Emph [Strong [Str "that",Space,Str "one"]],Str ".",LineBreak,Strikeout [Str "This",Space,Str "is",Space,Str "strikeout",Space,Str "and",Space,Strong [Str "strong"]]]
diff --git a/tests/textile-reader.textile b/tests/textile-reader.textile
index e2f51a4e9..64545c2c0 100644
--- a/tests/textile-reader.textile
+++ b/tests/textile-reader.textile
@@ -93,6 +93,16 @@ h2. Nested
 *** ui 2.1.1
 *** ui 2.1.2
 
+h2. Definition List
+
+- coffee := Hot and black
+- tea := Also hot, but a little less black
+- milk :=
+Nourishing beverage for baby cows.
+
+Cold drink that goes great with cookies.=:
+- beer := fresh and bitter
+
 
 h1. Inline Markup