aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2012-08-09 20:19:06 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2012-08-09 20:24:05 -0700
commit0cb7362f62410f58e2356381bbf2c1fe85abe2a5 (patch)
treeb6158a288fde45e430fe1afb094306ec442575b1 /src/Text
parent71e0c206c169c12e30bec4869dd04e166ef7ed5d (diff)
downloadpandoc-0cb7362f62410f58e2356381bbf2c1fe85abe2a5.tar.gz
Removed `--strict`, added extensions to writer/reader names.
* The `--strict` option has been removed. * Instead of using `--strict`, one can now use `strict` instead of `markdown` as an input or output format name. * The `--enable` and `--disable` optinos have been removed. * It is now possible to enable or disable specific extensions by appending them (with '+' or '-') to the writer or reader name. For example `pandoc -f markdown-footnotes+hard_line_breaks`. * The lhs extensions are now implemented this way, too; you can use either `+lhs` or `+literate_haskell`.
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc.hs19
-rw-r--r--src/Text/Pandoc/Shared.hs5
-rw-r--r--src/Text/Pandoc/Templates.hs17
3 files changed, 26 insertions, 15 deletions
diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs
index 06bfd128f..61e461b35 100644
--- a/src/Text/Pandoc.hs
+++ b/src/Text/Pandoc.hs
@@ -139,11 +139,13 @@ import Text.Pandoc.Templates
import Text.Pandoc.Options
import Text.Pandoc.Shared (safeRead)
import Data.ByteString.Lazy (ByteString)
+import Data.List (intercalate)
import Data.Version (showVersion)
import Text.JSON.Generic
import Data.Set (Set)
import qualified Data.Set as Set
import Text.Parsec
+import Text.Parsec.Error
import Paths_pandoc (version)
-- | Version number of pandoc library.
@@ -160,10 +162,12 @@ parseFormatSpec = parse formatSpec ""
formatName = many1 $ noneOf "-+"
extMod = do
polarity <- oneOf "-+"
- name <- many1 $ noneOf "-+"
- ext <- case safeRead name of
+ name <- many $ noneOf "-+"
+ ext <- case safeRead ("Ext_" ++ name) of
Just n -> return n
- Nothing -> unexpected $ "Unknown extension: " ++ name
+ Nothing
+ | name == "lhs" -> return Ext_literate_haskell
+ | otherwise -> fail $ "Unknown extension: " ++ name
return $ case polarity of
'-' -> Set.delete ext
_ -> Set.insert ext
@@ -172,6 +176,8 @@ parseFormatSpec = parse formatSpec ""
readers :: [(String, ReaderOptions -> String -> Pandoc)]
readers = [("native" , \_ -> readNative)
,("json" , \_ -> decodeJSON)
+ ,("strict" , \o -> readMarkdown
+ o{ readerExtensions = strictExtensions } )
,("markdown" , readMarkdown)
,("rst" , readRST)
,("docbook" , readDocBook)
@@ -215,6 +221,8 @@ writers = [
,("texinfo" , PureStringWriter writeTexinfo)
,("man" , PureStringWriter writeMan)
,("markdown" , PureStringWriter writeMarkdown)
+ ,("strict" , PureStringWriter $ \o ->
+ writeMarkdown o{ writerExtensions = strictExtensions } )
,("plain" , PureStringWriter writePlain)
,("rst" , PureStringWriter writeRST)
,("mediawiki" , PureStringWriter writeMediaWiki)
@@ -224,10 +232,11 @@ writers = [
,("asciidoc" , PureStringWriter writeAsciiDoc)
]
+-- | Retrieve reader based on formatSpec (format+extensions).
getReader :: String -> Either String (ReaderOptions -> String -> Pandoc)
getReader s =
case parseFormatSpec s of
- Left e -> Left $ show e
+ Left e -> Left $ intercalate "\n" $ [m | Message m <- errorMessages e]
Right (readerName, setExts) ->
case lookup readerName readers of
Nothing -> Left $ "Unknown reader: " ++ readerName
@@ -239,7 +248,7 @@ getReader s =
getWriter :: String -> Either String Writer
getWriter s =
case parseFormatSpec s of
- Left e -> Left $ show e
+ Left e -> Left $ intercalate "\n" $ [m | Message m <- errorMessages e]
Right (writerName, setExts) ->
case lookup writerName writers of
Nothing -> Left $ "Unknown writer: " ++ writerName
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 9f615867c..ad28b7c23 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -498,5 +498,6 @@ warn msg = do
safeRead :: (Monad m, Read a) => String -> m a
safeRead s = case reads s of
- (d,[]):_ -> return d
- _ -> fail $ "Could not read `" ++ s ++ "'"
+ (d,x):_
+ | all isSpace x -> return d
+ _ -> fail $ "Could not read `" ++ s ++ "'"
diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs
index 061be29aa..899f6510a 100644
--- a/src/Text/Pandoc/Templates.hs
+++ b/src/Text/Pandoc/Templates.hs
@@ -86,15 +86,16 @@ import qualified Control.Exception.Extensible as E (try, IOException)
getDefaultTemplate :: (Maybe FilePath) -- ^ User data directory to search first
-> String -- ^ Name of writer
-> IO (Either E.IOException String)
-getDefaultTemplate _ "native" = return $ Right ""
-getDefaultTemplate _ "json" = return $ Right ""
-getDefaultTemplate _ "docx" = return $ Right ""
-getDefaultTemplate user "odt" = getDefaultTemplate user "opendocument"
-getDefaultTemplate user "epub" = getDefaultTemplate user "html"
getDefaultTemplate user writer = do
- let format = takeWhile (/='+') writer -- strip off "+lhs" if present
- let fname = "templates" </> "default" <.> format
- E.try $ readDataFile user fname
+ let format = takeWhile (`notElem` "+-") writer -- strip off extensions
+ case format of
+ "native" -> return $ Right ""
+ "json" -> return $ Right ""
+ "docx" -> return $ Right ""
+ "odt" -> getDefaultTemplate user "opendocument"
+ "epub" -> return $ Right ""
+ _ -> let fname = "templates" </> "default" <.> format
+ in E.try $ readDataFile user fname
data TemplateState = TemplateState Int [(String,String)]