From f79ed27bb50411bf0704f34b555c5c348e4c7ec8 Mon Sep 17 00:00:00 2001
From: John MacFarlane <fiddlosopher@gmail.com>
Date: Fri, 20 Jul 2012 16:33:37 -0700
Subject: [PATCH] Use Parsec directly in Biblio and Templates.

---
 src/Text/Pandoc/Biblio.hs    | 12 ++++++------
 src/Text/Pandoc/Templates.hs | 20 ++++++++++----------
 2 files changed, 16 insertions(+), 16 deletions(-)

diff --git a/src/Text/Pandoc/Biblio.hs b/src/Text/Pandoc/Biblio.hs
index b4afe5117..13569a4d9 100644
--- a/src/Text/Pandoc/Biblio.hs
+++ b/src/Text/Pandoc/Biblio.hs
@@ -38,7 +38,7 @@ import qualified Text.CSL as CSL ( Cite(..) )
 import Text.Pandoc.Definition
 import Text.Pandoc.Generic
 import Text.Pandoc.Shared (stringify)
-import Text.Pandoc.Parsing
+import Text.Parsec
 import Control.Monad
 
 -- | Process a 'Pandoc' document by adding citations formatted
@@ -165,7 +165,7 @@ locatorWords inp =
          breakup (x : xs) = x : breakup xs
          splitup = groupBy (\x y -> x /= '\160' && y /= '\160')
 
-pLocatorWords :: Parser [Inline] st (String, [Inline])
+pLocatorWords :: Parsec [Inline] st (String, [Inline])
 pLocatorWords = do
   l <- pLocator
   s <- getInput -- rest is suffix
@@ -173,16 +173,16 @@ pLocatorWords = do
      then return (init l, Str "," : s)
      else return (l, s)
 
-pMatch :: (Inline -> Bool) -> Parser [Inline] st Inline
+pMatch :: (Inline -> Bool) -> Parsec [Inline] st Inline
 pMatch condition = try $ do
   t <- anyToken
   guard $ condition t
   return t
 
-pSpace :: Parser [Inline] st Inline
+pSpace :: Parsec [Inline] st Inline
 pSpace = pMatch (\t -> t == Space || t == Str "\160")
 
-pLocator :: Parser [Inline] st String
+pLocator :: Parsec [Inline] st String
 pLocator = try $ do
   optional $ pMatch (== Str ",")
   optional pSpace
@@ -190,7 +190,7 @@ pLocator = try $ do
   gs <- many1 pWordWithDigits
   return $ stringify f ++ (' ' : unwords gs)
 
-pWordWithDigits :: Parser [Inline] st String
+pWordWithDigits :: Parsec [Inline] st String
 pWordWithDigits = try $ do
   pSpace
   r <- many1 (notFollowedBy pSpace >> anyToken)
diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs
index 2be3ee2b3..bd4cdcd86 100644
--- a/src/Text/Pandoc/Templates.hs
+++ b/src/Text/Pandoc/Templates.hs
@@ -68,7 +68,7 @@ module Text.Pandoc.Templates ( renderTemplate
                              , TemplateTarget
                              , getDefaultTemplate ) where
 
-import Text.Pandoc.Parsing
+import Text.Parsec
 import Control.Monad (liftM, when, forM, mzero)
 import System.FilePath
 import Data.List (intercalate, intersperse)
@@ -98,7 +98,7 @@ getDefaultTemplate user writer = do
 
 data TemplateState = TemplateState Int [(String,String)]
 
-adjustPosition :: String -> Parser [Char] TemplateState String
+adjustPosition :: String -> Parsec [Char] TemplateState String
 adjustPosition str = do
   let lastline = takeWhile (/= '\n') $ reverse str
   updateState $ \(TemplateState pos x) ->
@@ -132,21 +132,21 @@ renderTemplate vals templ =
 reservedWords :: [String]
 reservedWords = ["else","endif","for","endfor","sep"]
 
-parseTemplate :: Parser [Char] TemplateState [String]
+parseTemplate :: Parsec [Char] TemplateState [String]
 parseTemplate =
   many $ (plaintext <|> escapedDollar <|> conditional <|> for <|> variable)
            >>= adjustPosition
 
-plaintext :: Parser [Char] TemplateState String
+plaintext :: Parsec [Char] TemplateState String
 plaintext = many1 $ noneOf "$"
 
-escapedDollar :: Parser [Char] TemplateState String
+escapedDollar :: Parsec [Char] TemplateState String
 escapedDollar = try $ string "$$" >> return "$"
 
-skipEndline :: Parser [Char] st ()
+skipEndline :: Parsec [Char] st ()
 skipEndline = try $ skipMany (oneOf " \t") >> newline >> return ()
 
-conditional :: Parser [Char] TemplateState String
+conditional :: Parsec [Char] TemplateState String
 conditional = try $ do
   TemplateState pos vars <- getState
   string "$if("
@@ -170,7 +170,7 @@ conditional = try $ do
               then ifContents
               else elseContents
 
-for :: Parser [Char] TemplateState String
+for :: Parsec [Char] TemplateState String
 for = try $ do
   TemplateState pos vars <- getState
   string "$for("
@@ -193,7 +193,7 @@ for = try $ do
   setState $ TemplateState pos vars
   return $ concat $ intersperse sep contents
 
-ident :: Parser [Char] TemplateState String
+ident :: Parsec [Char] TemplateState String
 ident = do
   first <- letter
   rest <- many (alphaNum <|> oneOf "_-")
@@ -202,7 +202,7 @@ ident = do
      then mzero
      else return id'
 
-variable :: Parser [Char] TemplateState String
+variable :: Parsec [Char] TemplateState String
 variable = try $ do
   char '$'
   id' <- ident