aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
authorJesse Rosenthal <jrosenthal@jhu.edu>2016-11-16 20:49:17 -0500
committerJohn MacFarlane <jgm@berkeley.edu>2017-01-25 17:07:39 +0100
commite24d5a56a7d0b26b9f15185bb570836878927d16 (patch)
treeb044a42d0a467fc47660ced96efef01347aba84b /src/Text/Pandoc/Writers
parent072107d1a2300afc7fb99263cc464048291d16d1 (diff)
downloadpandoc-e24d5a56a7d0b26b9f15185bb570836878927d16.tar.gz
Implement runTest functions.
These work with a State monad and a Reader monad to produce deterministic results. It can probably be simplified somewhat.
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs19
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs8
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs8
-rw-r--r--src/Text/Pandoc/Writers/ODT.hs6
4 files changed, 16 insertions, 25 deletions
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index cecee7e9e..3f380a3ee 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -55,7 +55,6 @@ import Text.Pandoc.Readers.Docx.Util (elemName)
import Control.Monad.Reader
import Control.Monad.State
import Skylighting
-import Data.Unique (hashUnique, newUnique)
import System.Random (randomR)
import Text.Printf (printf)
import qualified Control.Exception as E
@@ -69,8 +68,6 @@ import Data.Char (ord, isSpace, toLower)
import Text.Pandoc.Free (PandocAction, runIO)
import qualified Text.Pandoc.Free as P
-type DocxAction = PandocAction ()
-
data ListMarker = NoMarker
| BulletMarker
| NumberMarker ListNumberStyle ListNumberDelim Int
@@ -149,7 +146,7 @@ defaultWriterState = WriterState{
, stDynamicTextProps = []
}
-type WS = ReaderT WriterEnv (StateT WriterState (DocxAction))
+type WS = ReaderT WriterEnv (StateT WriterState (PandocAction))
mknode :: Node t => String -> [(String,String)] -> t -> Element
mknode s attrs =
@@ -227,7 +224,7 @@ writeDocx opts doc = runIO $ writeDocxPure opts doc
-- | Produce an Docx file from a Pandoc document.
writeDocxPure :: WriterOptions -- ^ Writer options
-> Pandoc -- ^ Document to convert
- -> DocxAction BL.ByteString
+ -> PandocAction BL.ByteString
writeDocxPure opts doc@(Pandoc meta _) = do
let datadir = writerUserDataDir opts
let doc' = walk fixDisplayMath $ doc
@@ -614,7 +611,7 @@ styleToOpenXml sm style =
$ backgroundColor style )
]
-copyChildren :: Archive -> Archive -> String -> Integer -> [String] -> DocxAction Entry
+copyChildren :: Archive -> Archive -> String -> Integer -> [String] -> PandocAction Entry
copyChildren refArchive distArchive path timestamp elNames = do
ref <- parseXml refArchive distArchive path
dist <- parseXml distArchive distArchive path
@@ -633,7 +630,7 @@ copyChildren refArchive distArchive path timestamp elNames = do
baseListId :: Int
baseListId = 1000
-mkNumbering :: [ListMarker] -> DocxAction [Element]
+mkNumbering :: [ListMarker] -> PandocAction [Element]
mkNumbering lists = do
elts <- mapM mkAbstractNum (ordNub lists)
return $ elts ++ zipWith mkNum lists [baseListId..(baseListId + length lists - 1)]
@@ -649,7 +646,7 @@ mkNum marker numid =
map (\lvl -> mknode "w:lvlOverride" [("w:ilvl",show (lvl :: Int))]
$ mknode "w:startOverride" [("w:val",show start)] ()) [0..6]
-mkAbstractNum :: ListMarker -> DocxAction Element
+mkAbstractNum :: ListMarker -> PandocAction Element
mkAbstractNum marker = do
gen <- P.newStdGen
let (nsid, _) = randomR (0x10000000 :: Integer, 0xFFFFFFFF :: Integer) gen
@@ -794,10 +791,10 @@ rStyleM styleName = do
let sty' = getStyleId styleName $ sCharStyleMap styleMaps
return $ mknode "w:rStyle" [("w:val",sty')] ()
-getUniqueId :: DocxAction String
+getUniqueId :: PandocAction String
-- the + 20 is to ensure that there are no clashes with the rIds
-- already in word/document.xml.rel
-getUniqueId = (show . (+ 20) . hashUnique) <$> P.newUnique
+getUniqueId = (show . (+ 20)) <$> P.newUniqueHash
-- | Key for specifying user-defined docx styles.
dynamicStyleKey :: String
@@ -1284,7 +1281,7 @@ defaultFootnotes = [ mknode "w:footnote"
[ mknode "w:r" [] $
[ mknode "w:continuationSeparator" [] ()]]]]
-parseXml :: Archive -> Archive -> String -> DocxAction Element
+parseXml :: Archive -> Archive -> String -> PandocAction Element
parseXml refArchive distArchive relpath =
case findEntryByPath relpath refArchive `mplus`
findEntryByPath relpath distArchive of
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 8e283a66a..435893443 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -66,8 +66,6 @@ import Text.HTML.TagSoup (Tag(TagOpen), fromAttrib, parseTags)
import Text.Pandoc.Free (PandocAction, runIO)
import qualified Text.Pandoc.Free as P
-type EPUBAction = PandocAction [(FilePath, (FilePath, Maybe Entry))]
-
-- A Chapter includes a list of blocks and maybe a section
-- number offset. Note, some chapters are unnumbered. The section
-- number is different from the index number, which will be used
@@ -77,7 +75,7 @@ data Chapter = Chapter (Maybe [Int]) [Block]
data EPUBState = EPUBState { stMediaPaths :: [(FilePath, (FilePath, Maybe Entry))]
}
-type E = StateT EPUBState EPUBAction
+type E = StateT EPUBState PandocAction
data EPUBMetadata = EPUBMetadata{
epubIdentifier :: [Identifier]
@@ -343,7 +341,7 @@ writeEPUB opts doc = runIO $ writeEPUBPure opts doc
writeEPUBPure :: WriterOptions -- ^ Writer options
-> Pandoc -- ^ Document to convert
- -> EPUBAction B.ByteString
+ -> PandocAction B.ByteString
writeEPUBPure opts doc =
let initState = EPUBState { stMediaPaths = []
}
@@ -398,7 +396,7 @@ pandocToEPUB opts doc@(Pandoc meta _) = do
picEntries <- (catMaybes . map (snd . snd)) <$> (gets stMediaPaths)
-- handle fonts
let matchingGlob f = do
- xs <- lift $ P.namesMatching f
+ xs <- lift $ P.glob f
when (null xs) $
lift $ P.warn $ f ++ " did not match any font files."
return xs
diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs
index 3a1e772ce..186bf0c8d 100644
--- a/src/Text/Pandoc/Writers/ICML.hs
+++ b/src/Text/Pandoc/Writers/ICML.hs
@@ -28,11 +28,9 @@ import Data.Text as Text (breakOnAll, pack)
import Control.Monad.State
import Network.URI (isURI)
import qualified Data.Set as Set
-import Text.Pandoc.Free (runIO)
+import Text.Pandoc.Free (runIO, PandocAction)
import qualified Text.Pandoc.Free as P
-type ICMLAction = P.PandocAction ()
-
type Style = [String]
type Hyperlink = [(Int, String)]
@@ -44,7 +42,7 @@ data WriterState = WriterState{
, maxListDepth :: Int
}
-type WS a = StateT WriterState ICMLAction a
+type WS a = StateT WriterState PandocAction a
defaultWriterState :: WriterState
defaultWriterState = WriterState{
@@ -130,7 +128,7 @@ writeICML :: WriterOptions -> Pandoc -> IO String
writeICML opts doc = runIO $ writeICMLPure opts doc
-- | Convert Pandoc document to string in ICML format.
-writeICMLPure :: WriterOptions -> Pandoc -> ICMLAction String
+writeICMLPure :: WriterOptions -> Pandoc -> PandocAction String
writeICMLPure opts (Pandoc meta blocks) = do
let colwidth = if writerWrapText opts == WrapAuto
then Just $ writerColumns opts
diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs
index b139695db..561230b15 100644
--- a/src/Text/Pandoc/Writers/ODT.hs
+++ b/src/Text/Pandoc/Writers/ODT.hs
@@ -53,12 +53,10 @@ import System.FilePath ( takeExtension, takeDirectory, (<.>))
import Text.Pandoc.Free ( PandocAction, runIO )
import qualified Text.Pandoc.Free as P
-type ODTAction = PandocAction [Entry]
-
data ODTState = ODTState { stEntries :: [Entry]
}
-type O = StateT ODTState ODTAction
+type O = StateT ODTState PandocAction
-- | Produce an ODT file from a Pandoc document.
writeODT :: WriterOptions -- ^ Writer options
@@ -68,7 +66,7 @@ writeODT opts doc = runIO $ writeODTPure opts doc
writeODTPure :: WriterOptions
-> Pandoc
- -> ODTAction B.ByteString
+ -> PandocAction B.ByteString
writeODTPure opts doc =
let initState = ODTState{ stEntries = []
}