Txt2Tags Reader: Added recognition of macros

This commit is contained in:
Matthew Pickering 2014-07-20 17:00:38 +01:00
parent ab3589ff0b
commit 43304d6bd6
3 changed files with 34 additions and 11 deletions

View file

@ -65,6 +65,9 @@ import qualified Data.Map as M
import Data.Yaml (decode)
import qualified Data.Yaml as Yaml
import qualified Data.Text as T
import Control.Applicative ((<$>))
import Text.Pandoc.Readers.Txt2Tags (getT2TMeta)
import Data.List (intersperse)
copyrightMessage :: String
copyrightMessage = "\nCopyright (C) 2006-2014 John MacFarlane\n" ++
@ -180,7 +183,7 @@ data Opt = Opt
, optTeXLigatures :: Bool -- ^ Use TeX ligatures for quotes/dashes
, optDefaultImageExtension :: String -- ^ Default image extension
, optTrace :: Bool -- ^ Print debug information
, optTrackChanges :: TrackChanges -- ^ Accept or reject MS Word track-changes.
, optTrackChanges :: TrackChanges -- ^ Accept or reject MS Word track-changes.
}
-- | Defaults for command-line options.
@ -1055,9 +1058,14 @@ main = do
else e
Right w -> return w
reader <- case getReader readerName' of
Right r -> return r
Left e -> err 7 e
let concatInput = concat (intersperse ", " sources)
reader <- if "t2t" == readerName'
then (mkStringReader .
readTxt2Tags) <$>
(getT2TMeta concatInput outputFile)
else case getReader readerName' of
Right r -> return r
Left e -> err 7 e
let standalone' = standalone || not (isTextFormat writerName') || pdfOutput
@ -1189,11 +1197,11 @@ main = do
else return
doc <- case reader of
StringReader r->
StringReader r->
readSources sources >>=
handleIncludes' . convertTabs . intercalate "\n" >>=
r readerOpts
ByteStringReader r -> readFiles sources >>= r readerOpts
ByteStringReader r -> readFiles sources >>= r readerOpts
let doc0 = M.foldWithKey setMeta doc metadata

View file

@ -63,6 +63,7 @@ module Text.Pandoc
, writers
-- * Readers: converting /to/ Pandoc format
, Reader (..)
, mkStringReader
, readDocx
, readMarkdown
, readMediaWiki
@ -230,7 +231,7 @@ readers = [ ("native" , StringReader $ \_ s -> return $ readNative s)
,("latex" , mkStringReader readLaTeX)
,("haddock" , mkStringReader readHaddock)
,("docx" , mkBSReader readDocx)
,("t2t" , mkStringReader readTxt2Tags)
,("t2t" , mkStringReader readTxt2TagsNoMacros)
]
data Writer = PureStringWriter (WriterOptions -> Pandoc -> String)

View file

@ -12,7 +12,7 @@ import Text.Pandoc.Builder ( Inlines, Blocks, (<>)
import Text.Pandoc.Definition
import Text.Pandoc.Options
import Text.Pandoc.Shared (escapeURI,compactify', compactify'DL)
import Text.Pandoc.Parsing hiding (space, spaces, uri)
import Text.Pandoc.Parsing hiding (space, spaces, uri, macro)
import Control.Applicative ((<$>), (<$), (<*>), (<*), (*>))
import Data.Char (toLower)
import Data.List (transpose, intersperse, intercalate)
@ -23,12 +23,14 @@ import Control.Monad (void, guard, when)
import Data.Default
import Control.Monad.Reader (Reader, runReader, asks)
type T2T = Parser String ParserState
import Data.Time.LocalTime (getZonedTime)
import System.Directory (getModificationTime)
import Data.Time.Format (formatTime)
import System.Locale (defaultTimeLocale)
import System.IO.Error (catchIOError)
type T2T = ParserT String ParserState (Reader T2TMeta)
-- | An object for the T2T macros meta information
-- the contents of each field is simply substituted verbatim into the file
data T2TMeta = T2TMeta {
@ -295,6 +297,7 @@ blockMarkupLine p f s = try (f <$> (string s *> space *> p))
comment :: Monoid a => T2T a
comment = try $ do
atStart
notFollowedBy macro
mempty <$ (char '%' *> anyLine)
-- Inline
@ -306,6 +309,7 @@ inline :: T2T Inlines
inline = do
choice
[ endline
, macro
, commentLine
, whitespace
, url
@ -405,6 +409,16 @@ imageLink = try $ do
l <- manyTill (noneOf "\n\r ") (char ']')
return (B.link l "" body)
macro :: T2T Inlines
macro = try $ do
name <- string "%%" *> oneOfStringsCI (map fst commands)
optional (try $ enclosed (char '(') (char ')') anyChar)
lookAhead (spaceChar <|> oneOf specialChars <|> newline)
maybe (return mempty) (\f -> B.str <$> asks f) (lookup name commands)
where
commands = [ ("date", date), ("mtime", mtime)
, ("infile", infile), ("outfile", outfile)]
-- raw URLs in text are automatically linked
url :: T2T Inlines
url = try $ do