Removed tests for Walk; these now live in pandoc-types.
This commit is contained in:
parent
e02e3aa10c
commit
2bc0cbc239
3 changed files with 0 additions and 49 deletions
|
@ -525,7 +525,6 @@ Test-Suite test-pandoc
|
||||||
Other-Modules: Tests.Old
|
Other-Modules: Tests.Old
|
||||||
Tests.Helpers
|
Tests.Helpers
|
||||||
Tests.Shared
|
Tests.Shared
|
||||||
Tests.Walk
|
|
||||||
Tests.Readers.LaTeX
|
Tests.Readers.LaTeX
|
||||||
Tests.Readers.HTML
|
Tests.Readers.HTML
|
||||||
Tests.Readers.Markdown
|
Tests.Readers.Markdown
|
||||||
|
|
|
@ -1,46 +0,0 @@
|
||||||
{-# LANGUAGE ScopedTypeVariables, FlexibleContexts #-}
|
|
||||||
module Tests.Walk (tests) where
|
|
||||||
|
|
||||||
import Text.Pandoc.Definition
|
|
||||||
import Text.Pandoc.Walk
|
|
||||||
import Test.Framework
|
|
||||||
import Tests.Helpers
|
|
||||||
import Data.Char (toUpper)
|
|
||||||
import Text.Pandoc.Arbitrary()
|
|
||||||
import Data.Generics
|
|
||||||
|
|
||||||
tests :: [Test]
|
|
||||||
tests = [ testGroup "Walk"
|
|
||||||
[ property "p_walk inlineTrans" (p_walk inlineTrans)
|
|
||||||
, property "p_walk blockTrans" (p_walk blockTrans)
|
|
||||||
, property "p_query inlineQuery" (p_query inlineQuery)
|
|
||||||
, property "p_query blockQuery" (p_query blockQuery)
|
|
||||||
]
|
|
||||||
]
|
|
||||||
|
|
||||||
p_walk :: (Typeable a, Walkable a Pandoc)
|
|
||||||
=> (a -> a) -> Pandoc -> Bool
|
|
||||||
p_walk f d = everywhere (mkT f) d == walk f d
|
|
||||||
|
|
||||||
p_query :: (Eq a, Typeable a1, Monoid a, Walkable a1 Pandoc)
|
|
||||||
=> (a1 -> a) -> Pandoc -> Bool
|
|
||||||
p_query f d = everything mappend (mempty `mkQ` f) d == query f d
|
|
||||||
|
|
||||||
inlineTrans :: Inline -> Inline
|
|
||||||
inlineTrans (Str xs) = Str $ map toUpper xs
|
|
||||||
inlineTrans (Emph xs) = Strong xs
|
|
||||||
inlineTrans x = x
|
|
||||||
|
|
||||||
blockTrans :: Block -> Block
|
|
||||||
blockTrans (Plain xs) = Para xs
|
|
||||||
blockTrans (BlockQuote xs) = Div ("",["special"],[]) xs
|
|
||||||
blockTrans x = x
|
|
||||||
|
|
||||||
inlineQuery :: Inline -> String
|
|
||||||
inlineQuery (Str xs) = xs
|
|
||||||
inlineQuery _ = ""
|
|
||||||
|
|
||||||
blockQuery :: Block -> [Int]
|
|
||||||
blockQuery (Header lev _ _) = [lev]
|
|
||||||
blockQuery _ = []
|
|
||||||
|
|
|
@ -26,14 +26,12 @@ import qualified Tests.Writers.Docx
|
||||||
import qualified Tests.Writers.RST
|
import qualified Tests.Writers.RST
|
||||||
import qualified Tests.Writers.TEI
|
import qualified Tests.Writers.TEI
|
||||||
import qualified Tests.Shared
|
import qualified Tests.Shared
|
||||||
import qualified Tests.Walk
|
|
||||||
import Text.Pandoc.Shared (inDirectory)
|
import Text.Pandoc.Shared (inDirectory)
|
||||||
import System.Environment (getArgs)
|
import System.Environment (getArgs)
|
||||||
|
|
||||||
tests :: [Test]
|
tests :: [Test]
|
||||||
tests = [ testGroup "Old" Tests.Old.tests
|
tests = [ testGroup "Old" Tests.Old.tests
|
||||||
, testGroup "Shared" Tests.Shared.tests
|
, testGroup "Shared" Tests.Shared.tests
|
||||||
, testGroup "Walk" Tests.Walk.tests
|
|
||||||
, testGroup "Writers"
|
, testGroup "Writers"
|
||||||
[ testGroup "Native" Tests.Writers.Native.tests
|
[ testGroup "Native" Tests.Writers.Native.tests
|
||||||
, testGroup "ConTeXt" Tests.Writers.ConTeXt.tests
|
, testGroup "ConTeXt" Tests.Writers.ConTeXt.tests
|
||||||
|
|
Loading…
Reference in a new issue