From 9602f73f2a943c21a5d1593e99cdbcbde08f6dcb Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Fri, 10 Dec 2010 17:30:32 -0800
Subject: [PATCH] Moved 'readers' and 'writers' to Text.Pandoc.

This allows library users to avoid repetitive case statements...
---
 src/Text/Pandoc.hs | 42 ++++++++++++++++++++++++++++++++++++
 src/pandoc.hs      | 54 +++++-----------------------------------------
 2 files changed, 47 insertions(+), 49 deletions(-)

diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs
index ab1e3cd03..0ac558663 100644
--- a/src/Text/Pandoc.hs
+++ b/src/Text/Pandoc.hs
@@ -57,6 +57,9 @@ module Text.Pandoc
                ( 
                -- * Definitions
                module Text.Pandoc.Definition
+               -- * Lists of readers and writers
+               , readers
+               , writers
                -- * Readers: converting /to/ Pandoc format
                , readMarkdown
                , readRST
@@ -132,3 +135,42 @@ import Paths_pandoc (version)
 -- | Version number of pandoc library.
 pandocVersion :: String
 pandocVersion = showVersion version
+
+-- | Association list of formats and readers.
+readers :: [(String, ParserState -> String -> Pandoc)]
+readers = [("native"       , \_ -> read)
+          ,("markdown"     , readMarkdown)
+          ,("markdown+lhs" , readMarkdown)
+          ,("rst"          , readRST)
+          ,("textile"      , readTextile) -- TODO : textile+lhs 
+          ,("rst+lhs"      , readRST)
+          ,("html"         , readHtml)
+          ,("latex"        , readLaTeX)
+          ,("latex+lhs"    , readLaTeX)
+          ]
+
+-- | Association list of formats and writers (omitting the
+-- binary writers, odt and epub).
+writers :: [ ( String, WriterOptions -> Pandoc -> String ) ]
+writers = [("native"       , writeNative)
+          ,("html"         , writeHtmlString)
+          ,("html+lhs"     , writeHtmlString)
+          ,("s5"           , writeHtmlString)
+          ,("slidy"        , writeHtmlString)
+          ,("docbook"      , writeDocbook)
+          ,("opendocument" , writeOpenDocument)
+          ,("latex"        , writeLaTeX)
+          ,("latex+lhs"    , writeLaTeX)
+          ,("context"      , writeConTeXt)
+          ,("texinfo"      , writeTexinfo)
+          ,("man"          , writeMan)
+          ,("markdown"     , writeMarkdown)
+          ,("markdown+lhs" , writeMarkdown)
+          ,("plain"        , writePlain)
+          ,("rst"          , writeRST)
+          ,("rst+lhs"      , writeRST)
+          ,("mediawiki"    , writeMediaWiki)
+          ,("textile"      , writeTextile)
+          ,("rtf"          , writeRTF)
+          ,("org"          , writeOrg)
+          ]
diff --git a/src/pandoc.hs b/src/pandoc.hs
index 4feaab559..52dfb731a 100644
--- a/src/pandoc.hs
+++ b/src/pandoc.hs
@@ -80,50 +80,6 @@ wrapWords c = wrap' c c where
                                                        then ",\n" ++ x ++ wrap' cols (cols - length x) xs
                                                        else ", "  ++ x ++ wrap' cols (remaining - (length x + 2)) xs
 
--- | Association list of formats and readers.
-readers :: [(String, ParserState -> String -> Pandoc)]
-readers = [("native"       , readPandoc)
-          ,("markdown"     , readMarkdown)
-          ,("markdown+lhs" , readMarkdown)
-          ,("rst"          , readRST)
-          ,("textile"      , readTextile) -- TODO : textile+lhs 
-          ,("rst+lhs"      , readRST)
-          ,("html"         , readHtml)
-          ,("latex"        , readLaTeX)
-          ,("latex+lhs"    , readLaTeX)
-          ]
-
--- | Reader for native Pandoc format.
-readPandoc :: ParserState -> String -> Pandoc
-readPandoc _ = read
-
--- | Association list of formats and writers.
-writers :: [ ( String, WriterOptions -> Pandoc -> String ) ]
-writers = [("native"       , writeNative)
-          ,("html"         , writeHtmlString)
-          ,("html+lhs"     , writeHtmlString)
-          ,("s5"           , writeHtmlString)
-          ,("slidy"        , writeHtmlString)
-          ,("docbook"      , writeDocbook)
-          ,("opendocument" , writeOpenDocument)
-          ,("odt"          , \_ _ -> "")
-          ,("epub"         , \_ _ -> "")
-          ,("latex"        , writeLaTeX)
-          ,("latex+lhs"    , writeLaTeX)
-          ,("context"      , writeConTeXt)
-          ,("texinfo"      , writeTexinfo)
-          ,("man"          , writeMan)
-          ,("markdown"     , writeMarkdown)
-          ,("markdown+lhs" , writeMarkdown)
-          ,("plain"        , writePlain)
-          ,("rst"          , writeRST)
-          ,("rst+lhs"      , writeRST)
-          ,("mediawiki"    , writeMediaWiki)
-          ,("textile"      , writeTextile)
-          ,("rtf"          , writeRTF)
-          ,("org"          , writeOrg)
-          ]
-
 isNonTextOutput :: String -> Bool
 isNonTextOutput = (`elem` ["odt","epub"])
 
@@ -210,13 +166,13 @@ options =
                  (ReqArg
                   (\arg opt -> return opt { optReader = map toLower arg })
                   "FORMAT")
-                 "" -- ("(" ++ (intercalate ", " $ map fst readers) ++ ")")
+                 ""
 
     , Option "tw" ["to","write"]
                  (ReqArg
                   (\arg opt -> return opt { optWriter = map toLower arg })
                   "FORMAT")
-                 "" -- ("(" ++ (intercalate ", " $ map fst writers) ++ ")")
+                 ""
 
     , Option "s" ["standalone"]
                  (NoArg
@@ -561,7 +517,7 @@ usageMessage :: String -> [OptDescr (Opt -> IO Opt)] -> String
 usageMessage programName = usageInfo
   (programName ++ " [OPTIONS] [FILES]" ++ "\nInput formats:  " ++
   (intercalate ", " $ map fst readers) ++ "\nOutput formats:  " ++
-  (intercalate ", " $ map fst writers) ++ "\nOptions:")
+  (intercalate ", " $ map fst writers ++ ["odt","epub"]) ++ "\nOptions:")
 
 -- Determine default reader based on source file extensions
 defaultReaderName :: String -> [FilePath] -> String
@@ -711,8 +667,8 @@ main = do
      Nothing -> error ("Unknown reader: " ++ readerName')
 
   let writer = case lookup writerName' writers of
-                Just _ | writerName' == "epub" -> writeEPUB epubStylesheet
-                Just _ | writerName' == "odt"  -> writeODT referenceODT
+                Nothing | writerName' == "epub" -> writeEPUB epubStylesheet
+                Nothing | writerName' == "odt"  -> writeODT referenceODT
                 Just r                         -> \o ->
                                                      return . fromString . r o
                 Nothing                        -> error $ "Unknown writer: " ++