{-# OPTIONS_GHC -fno-warn-orphans #-} {-# LANGUAGE TypeSynonymInstances #-} -- provides Arbitrary instance for Pandoc types module Tests.Arbitrary () where import Test.QuickCheck.Gen import Test.QuickCheck.Arbitrary import Control.Monad (liftM, liftM2) import Text.Pandoc import Text.Pandoc.Shared import Text.Pandoc.Builder realString :: Gen String realString = resize 8 arbitrary -- elements wordlist wordlist :: [String] wordlist = ["foo","Bar","baz","\\","/",":","\"","'","féé"] instance Arbitrary Inlines where arbitrary = liftM fromList arbitrary instance Arbitrary Blocks where arbitrary = liftM fromList arbitrary instance Arbitrary Inline where arbitrary = resize 3 $ arbInline 3 -- restrict to 3 levels of nesting max; otherwise we get -- bogged down in indefinitely large structures arbInline :: Int -> Gen Inline arbInline n = frequency $ [ (60, liftM Str realString) , (60, return Space) , (10, liftM Code realString) , (5, return EmDash) , (5, return EnDash) , (5, return Apostrophe) , (5, return Ellipses) , (5, elements [ RawInline "html" "*&*" , RawInline "latex" "\\my{command}" ]) ] ++ [ x | x <- nesters, n > 1] where nesters = [ (10, liftM Emph $ listOf $ arbInline (n-1)) , (10, liftM Strong $ listOf $ arbInline (n-1)) , (10, liftM Strikeout $ listOf $ arbInline (n-1)) , (10, liftM Superscript $ listOf $ arbInline (n-1)) , (10, liftM Subscript $ listOf $ arbInline (n-1)) , (10, liftM SmallCaps $ listOf $ arbInline (n-1)) , (10, do x1 <- arbitrary x2 <- listOf $ arbInline (n-1) return $ Quoted x1 x2) , (10, do x1 <- arbitrary x2 <- realString return $ Math x1 x2) , (10, do x1 <- listOf $ arbInline (n-1) x3 <- realString x2 <- realString return $ Link x1 (x2,x3)) , (10, do x1 <- listOf $ arbInline (n-1) x3 <- realString x2 <- realString return $ Image x1 (x2,x3)) , (2, liftM Note $ resize 3 $ listOf1 arbitrary) ] instance Arbitrary Block where arbitrary = resize 3 $ arbBlock 3 arbBlock :: Int -> Gen Block arbBlock n = frequency $ [ (10, liftM Plain arbitrary) , (15, liftM Para arbitrary) , (5, liftM2 CodeBlock arbitrary realString) , (2, elements [ RawBlock "html" "