summaryrefslogtreecommitdiff
path: root/edit-lens/test/Control/DFSTTest.hs
diff options
context:
space:
mode:
Diffstat (limited to 'edit-lens/test/Control/DFSTTest.hs')
-rw-r--r--edit-lens/test/Control/DFSTTest.hs101
1 files changed, 101 insertions, 0 deletions
diff --git a/edit-lens/test/Control/DFSTTest.hs b/edit-lens/test/Control/DFSTTest.hs
new file mode 100644
index 0000000..4d91a03
--- /dev/null
+++ b/edit-lens/test/Control/DFSTTest.hs
@@ -0,0 +1,101 @@
1module Control.DFSTTest where
2
3import Control.DFST
4import Control.FST hiding (stInitial, stTransition, stAccept)
5
6import Data.Set (Set)
7import qualified Data.Set as Set
8
9import Data.Map.Strict (Map)
10import qualified Data.Map.Strict as Map
11
12import Data.Sequence (Seq)
13import qualified Data.Sequence as Seq
14
15import Data.Maybe (maybeToList)
16
17import Test.Tasty
18import Test.Tasty.Hedgehog
19import Test.Tasty.HUnit hiding (assert)
20
21import Hedgehog
22import qualified Hedgehog.Gen as G
23import qualified Hedgehog.Range as R
24
25import Numeric.Natural
26
27import Text.PrettyPrint.Leijen (Pretty(..))
28
29
30dfstId :: Ord a => Set a -> DFST () a a
31dfstId syms = DFST
32 { stInitial = ()
33 , stTransition = Map.fromList
34 [(((), sym), ((), Seq.singleton sym)) | sym <- Set.toList syms]
35 , stAccept = Set.singleton ()
36 }
37
38dfstDouble :: Ord a => Set a -> DFST () a a
39dfstDouble syms = DFST
40 { stInitial = ()
41 , stTransition = Map.fromList
42 [(((), sym), ((), Seq.fromList [sym, sym])) | sym <- Set.toList syms]
43 , stAccept = Set.singleton ()
44 }
45
46dfstRunLengthDecode :: Ord a
47 => Set a
48 -> Natural
49 -> DFST (Maybe Natural) (Either Natural a) a
50dfstRunLengthDecode syms lim = DFST
51 { stInitial = Nothing
52 , stTransition = Map.fromList . concat $
53 [ [((Nothing, Left n), (Just n, Seq.empty)) | n <- [0..lim]]
54 , [((Just n, Right sym), (Nothing, Seq.replicate (fromIntegral n) sym)) | n <- [0..lim], sym <- Set.toList syms]
55 ]
56 , stAccept = Set.singleton Nothing
57 }
58
59genWord :: Gen [Natural]
60genWord = G.list (R.linear 0 1000) . G.integral $ R.linear 0 100
61
62genDFST :: (Ord input, Ord output) => Set input -> Set output -> Gen (DFST Natural input output)
63genDFST inA outA = do
64 states <- G.set (R.linear 1 1000) . G.integral $ R.linear 0 100
65 stInitial <- G.element $ Set.toList states
66 stAccept <- Set.fromList <$> G.subsequence (Set.toList states)
67 stTransition <- fmap Map.fromList . G.list (R.linear 0 1000) . G.small $ do
68 st <- G.element $ Set.toList states
69 input <- G.element $ Set.toList inA
70 st' <- G.element $ Set.toList states
71 output <- fmap Seq.fromList . G.list (R.linear 0 20) . G.element $ Set.toList outA
72 return ((st, input), (st', output))
73 return DFST{..}
74
75
76testDFST :: (Show output, Ord output, Show state, Ord state) => (Set Natural -> DFST state Natural output) -> (Seq Natural -> Seq output) -> Property
77testDFST mkDfst f = property $ do
78 input <- forAll genWord
79 let fst = mkDfst $ Set.fromList input
80 Just (f $ Seq.fromList input) === runDFST fst (Seq.fromList input)
81
82hprop_runDFSTId, hprop_runDFSTDouble :: Property
83hprop_runDFSTId = testDFST dfstId id
84hprop_runDFSTDouble = testDFST dfstDouble double
85 where
86 double :: Seq a -> Seq a
87 double Seq.Empty = Seq.Empty
88 double (a Seq.:<| as) = a Seq.:<| a Seq.:<| double as
89
90unit_runLengthDecode :: Assertion
91unit_runLengthDecode = runDFST dfst input @?= Just (Seq.fromList "aaacc")
92 where
93 input = Seq.fromList [Left 3, Right 'a', Left 0, Right 'b', Left 2, Right 'c']
94 dfst = dfstRunLengthDecode (Set.fromList "abc") 3
95
96hprop_toFST :: Property
97hprop_toFST = property $ do
98 input <- forAll genWord
99 dfst <- forAllWith (show . pretty . toFST) $ genDFST (Set.fromList $ input ++ [0..20]) (Set.fromList [0..20] :: Set Natural)
100
101 runFST (toFST dfst) (Seq.fromList input) === maybeToList (runDFST dfst $ Seq.fromList input)