diff options
author | Gregor Kleen <gkleen@yggdrasil.li> | 2018-12-18 13:51:16 +0100 |
---|---|---|
committer | Gregor Kleen <gkleen@yggdrasil.li> | 2018-12-18 13:51:16 +0100 |
commit | 46ae60eaca841b554ba20c6a2b7a15b43c12b4df (patch) | |
tree | 0bb06127a0e08e75f8be755f5a5dfb1702b627b6 /edit-lens/test | |
parent | b0b18979d5ccd109d5a56937396acdeb85c857aa (diff) | |
download | incremental-dfsts-46ae60eaca841b554ba20c6a2b7a15b43c12b4df.tar incremental-dfsts-46ae60eaca841b554ba20c6a2b7a15b43c12b4df.tar.gz incremental-dfsts-46ae60eaca841b554ba20c6a2b7a15b43c12b4df.tar.bz2 incremental-dfsts-46ae60eaca841b554ba20c6a2b7a15b43c12b4df.tar.xz incremental-dfsts-46ae60eaca841b554ba20c6a2b7a15b43c12b4df.zip |
Much ado about nothing
Diffstat (limited to 'edit-lens/test')
-rw-r--r-- | edit-lens/test/Control/DFST/LensTest.hs | 35 | ||||
-rw-r--r-- | edit-lens/test/Control/DFSTTest.hs | 101 | ||||
-rw-r--r-- | edit-lens/test/Control/FSTTest.hs | 187 | ||||
-rw-r--r-- | edit-lens/test/Driver.hs | 1 |
4 files changed, 324 insertions, 0 deletions
diff --git a/edit-lens/test/Control/DFST/LensTest.hs b/edit-lens/test/Control/DFST/LensTest.hs new file mode 100644 index 0000000..46a1896 --- /dev/null +++ b/edit-lens/test/Control/DFST/LensTest.hs | |||
@@ -0,0 +1,35 @@ | |||
1 | module Control.DFST.LensTest where | ||
2 | |||
3 | import Prelude hiding (init) | ||
4 | |||
5 | import Control.DFST | ||
6 | import Control.DFST.Lens | ||
7 | import Control.FST hiding (stInitial, stTransition, stAccept) | ||
8 | |||
9 | import Data.Set (Set) | ||
10 | import qualified Data.Set as Set | ||
11 | |||
12 | import Data.Map.Strict (Map) | ||
13 | import qualified Data.Map.Strict as Map | ||
14 | |||
15 | import Data.Sequence (Seq) | ||
16 | import qualified Data.Sequence as Seq | ||
17 | |||
18 | import Data.Maybe (maybeToList) | ||
19 | |||
20 | import Test.Tasty | ||
21 | import Test.Tasty.Hedgehog | ||
22 | import Test.Tasty.HUnit hiding (assert) | ||
23 | |||
24 | import Hedgehog | ||
25 | import qualified Hedgehog.Gen as G | ||
26 | import qualified Hedgehog.Range as R | ||
27 | |||
28 | import Numeric.Natural | ||
29 | |||
30 | import Control.DFSTTest | ||
31 | |||
32 | hprop_applyDivInit :: Property | ||
33 | hprop_applyDivInit = property $ do | ||
34 | word <- Seq.fromList <$> forAll genWord | ||
35 | init @(StringEdits Natural) `apply` (divInit word :: StringEdits Natural) === Just word | ||
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 @@ | |||
1 | module Control.DFSTTest where | ||
2 | |||
3 | import Control.DFST | ||
4 | import Control.FST hiding (stInitial, stTransition, stAccept) | ||
5 | |||
6 | import Data.Set (Set) | ||
7 | import qualified Data.Set as Set | ||
8 | |||
9 | import Data.Map.Strict (Map) | ||
10 | import qualified Data.Map.Strict as Map | ||
11 | |||
12 | import Data.Sequence (Seq) | ||
13 | import qualified Data.Sequence as Seq | ||
14 | |||
15 | import Data.Maybe (maybeToList) | ||
16 | |||
17 | import Test.Tasty | ||
18 | import Test.Tasty.Hedgehog | ||
19 | import Test.Tasty.HUnit hiding (assert) | ||
20 | |||
21 | import Hedgehog | ||
22 | import qualified Hedgehog.Gen as G | ||
23 | import qualified Hedgehog.Range as R | ||
24 | |||
25 | import Numeric.Natural | ||
26 | |||
27 | import Text.PrettyPrint.Leijen (Pretty(..)) | ||
28 | |||
29 | |||
30 | dfstId :: Ord a => Set a -> DFST () a a | ||
31 | dfstId syms = DFST | ||
32 | { stInitial = () | ||
33 | , stTransition = Map.fromList | ||
34 | [(((), sym), ((), Seq.singleton sym)) | sym <- Set.toList syms] | ||
35 | , stAccept = Set.singleton () | ||
36 | } | ||
37 | |||
38 | dfstDouble :: Ord a => Set a -> DFST () a a | ||
39 | dfstDouble syms = DFST | ||
40 | { stInitial = () | ||
41 | , stTransition = Map.fromList | ||
42 | [(((), sym), ((), Seq.fromList [sym, sym])) | sym <- Set.toList syms] | ||
43 | , stAccept = Set.singleton () | ||
44 | } | ||
45 | |||
46 | dfstRunLengthDecode :: Ord a | ||
47 | => Set a | ||
48 | -> Natural | ||
49 | -> DFST (Maybe Natural) (Either Natural a) a | ||
50 | dfstRunLengthDecode 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 | |||
59 | genWord :: Gen [Natural] | ||
60 | genWord = G.list (R.linear 0 1000) . G.integral $ R.linear 0 100 | ||
61 | |||
62 | genDFST :: (Ord input, Ord output) => Set input -> Set output -> Gen (DFST Natural input output) | ||
63 | genDFST 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 | |||
76 | testDFST :: (Show output, Ord output, Show state, Ord state) => (Set Natural -> DFST state Natural output) -> (Seq Natural -> Seq output) -> Property | ||
77 | testDFST 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 | |||
82 | hprop_runDFSTId, hprop_runDFSTDouble :: Property | ||
83 | hprop_runDFSTId = testDFST dfstId id | ||
84 | hprop_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 | |||
90 | unit_runLengthDecode :: Assertion | ||
91 | unit_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 | |||
96 | hprop_toFST :: Property | ||
97 | hprop_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) | ||
diff --git a/edit-lens/test/Control/FSTTest.hs b/edit-lens/test/Control/FSTTest.hs new file mode 100644 index 0000000..f5e02c2 --- /dev/null +++ b/edit-lens/test/Control/FSTTest.hs | |||
@@ -0,0 +1,187 @@ | |||
1 | module Control.FSTTest where | ||
2 | |||
3 | import Control.FST | ||
4 | |||
5 | import Data.Set (Set) | ||
6 | import qualified Data.Set as Set | ||
7 | |||
8 | import Data.Map.Strict (Map) | ||
9 | import qualified Data.Map.Strict as Map | ||
10 | |||
11 | import Data.Sequence (Seq) | ||
12 | import qualified Data.Sequence as Seq | ||
13 | |||
14 | import Data.Maybe (fromMaybe) | ||
15 | import Data.Foldable (Foldable(..)) | ||
16 | |||
17 | import Control.Monad (when) | ||
18 | |||
19 | import Data.Void | ||
20 | |||
21 | import Test.Tasty | ||
22 | import Test.Tasty.Hedgehog | ||
23 | import Test.Tasty.HUnit hiding (assert) | ||
24 | |||
25 | import Hedgehog | ||
26 | import qualified Hedgehog.Gen as G | ||
27 | import qualified Hedgehog.Range as R | ||
28 | |||
29 | import Numeric.Natural | ||
30 | |||
31 | import Text.PrettyPrint.Leijen (Pretty(..)) | ||
32 | |||
33 | import Control.DeepSeq (force) | ||
34 | |||
35 | |||
36 | fstId :: Ord a => Set a -> FST () a a | ||
37 | fstId syms = FST | ||
38 | { stInitial = Set.singleton () | ||
39 | , stTransition = Map.fromList [(((), Just sym), Set.singleton ((), Just sym)) | sym <- Set.toList syms] | ||
40 | , stAccept = Set.singleton () | ||
41 | } | ||
42 | |||
43 | fstDouble :: Ord a => Set a -> FST (Maybe a) a a | ||
44 | fstDouble syms = FST | ||
45 | { stInitial = Set.singleton Nothing | ||
46 | , stTransition = Map.fromListWith Set.union . concat $ | ||
47 | [ [((Nothing, Just sym), Set.singleton (Just sym, Just sym)) | sym <- Set.toList syms] | ||
48 | , [((Just sym, Nothing), Set.singleton (Nothing, Just sym)) | sym <- Set.toList syms] | ||
49 | ] | ||
50 | , stAccept = Set.singleton Nothing | ||
51 | } | ||
52 | |||
53 | fstRunLengthDecode :: Ord a | ||
54 | => Set a -- ^ Alphabet | ||
55 | -> Natural -- ^ Upper limit to run length | ||
56 | -> FST (Maybe (Natural, Maybe a)) (Either Natural a) a | ||
57 | fstRunLengthDecode syms lim = FST | ||
58 | { stInitial = Set.singleton Nothing | ||
59 | , stTransition = Map.fromListWith Set.union . concat $ | ||
60 | [ [((Nothing, Just (Left n)), Set.singleton (Just (n, Nothing), Nothing)) | n <- [0..lim]] | ||
61 | , [((Just (n, Nothing), Just (Right sym)), Set.singleton (Just (n, Just sym), Nothing)) | n <- [0..lim], sym <- Set.toList syms] | ||
62 | , [((Just (n, Just sym), Nothing), Set.singleton (Just (pred n, Just sym), Just sym)) | n <- [1..lim], sym <- Set.toList syms] | ||
63 | , [((Just (0, Just sym), Nothing), Set.singleton (Nothing, Nothing)) | sym <- Set.toList syms] | ||
64 | ] | ||
65 | , stAccept = Set.singleton Nothing | ||
66 | } | ||
67 | |||
68 | data StRunLengthEncode a = STREInitial | ||
69 | | STRECountUp a Natural | ||
70 | | STRESwitch (Maybe a) a | ||
71 | | STREFinish | ||
72 | deriving (Show, Eq, Ord) | ||
73 | |||
74 | fstRunLengthEncode :: Ord a | ||
75 | => Bool -- ^ Generate /all/ run length encodings instead of the best | ||
76 | -> Set a -- ^ Alphabet | ||
77 | -> Natural -- ^ Upper limit to run length | ||
78 | -> FST (StRunLengthEncode a) a (Either Natural a) | ||
79 | fstRunLengthEncode genAll syms lim = FST | ||
80 | { stInitial = Set.singleton STREInitial | ||
81 | , stTransition = Map.fromListWith Set.union . concat $ | ||
82 | [ [((STREInitial, Just sym), Set.singleton (STRECountUp sym 1, Nothing)) | sym <- Set.toList syms] | ||
83 | , [((STRECountUp sym n, Just sym), Set.singleton (STRECountUp sym (succ n), Nothing)) | sym <- Set.toList syms, n <- [1..pred lim]] | ||
84 | , [((STRECountUp sym n, Just sym'), Set.singleton (STRESwitch (Just sym') sym, Just $ Left n)) | n <- [1..lim], sym <- Set.toList syms, sym' <- Set.toList syms, sym /= sym'] | ||
85 | , [((STRECountUp sym lim, Just sym), Set.singleton (STRESwitch (Just sym) sym, Just $ Left lim)) | sym <- Set.toList syms] | ||
86 | , [((STRECountUp sym n, Nothing), Set.singleton (STRESwitch Nothing sym, Just $ Left n)) | sym <- Set.toList syms, n <- [1..lim]] | ||
87 | , [((STRESwitch (Just sym') sym, Nothing), Set.singleton (STRECountUp sym' 1, Just $ Right sym)) | sym <- Set.toList syms, sym' <- Set.toList syms] | ||
88 | , [((STRESwitch Nothing sym, Nothing), Set.singleton (STREFinish, Just $ Right sym)) | sym <- Set.toList syms] | ||
89 | , [((STRECountUp sym n, Just sym), Set.singleton (STRESwitch (Just sym) sym, Just $ Left n)) | n <- [1..lim], sym <- Set.toList syms, genAll] | ||
90 | ] | ||
91 | , stAccept = Set.fromList [STREInitial, STREFinish] | ||
92 | } | ||
93 | |||
94 | |||
95 | genWord :: Gen [Natural] | ||
96 | genWord = G.list (R.linear 0 1000) . G.integral $ R.linear 0 100 | ||
97 | |||
98 | |||
99 | runFSTDet :: (Show output, Ord output, Show state, Ord state) => (Set Natural -> FST state Natural output) -> (Seq Natural -> Seq output) -> Property | ||
100 | runFSTDet mkFst f = property $ do | ||
101 | input <- forAll genWord | ||
102 | let fst = mkFst $ Set.fromList input | ||
103 | annotateShow $ pretty fst | ||
104 | [f $ Seq.fromList input] === runFST fst (Seq.fromList input) | ||
105 | |||
106 | |||
107 | hprop_runFSTId, hprop_runFSTDouble :: Property | ||
108 | hprop_runFSTId = runFSTDet fstId id | ||
109 | hprop_runFSTDouble = runFSTDet fstDouble double | ||
110 | where | ||
111 | double :: Seq a -> Seq a | ||
112 | double Seq.Empty = Seq.Empty | ||
113 | double (a Seq.:<| as) = a Seq.:<| a Seq.:<| double as | ||
114 | |||
115 | hprop_runWordFST :: Property | ||
116 | hprop_runWordFST = property $ do | ||
117 | input <- forAll genWord | ||
118 | let fst = wordFST $ Seq.fromList input | ||
119 | annotateShow $ pretty fst | ||
120 | [Seq.fromList input] === runFST fst (Seq.empty :: Seq Void) | ||
121 | |||
122 | unit_runLengthDecode, unit_runLengthEncode :: Assertion | ||
123 | unit_runLengthDecode = runFST fst input @?= [Seq.fromList "aaacc"] | ||
124 | where | ||
125 | input = Seq.fromList [Left 3, Right 'a', Left 0, Right 'b', Left 2, Right 'c'] | ||
126 | fst = fstRunLengthDecode (Set.fromList "abc") 3 | ||
127 | unit_runLengthEncode = runFST fst input @?= [Seq.fromList [Left 3, Right 'a', Left 2, Right 'c']] | ||
128 | where | ||
129 | input = Seq.fromList "aaacc" | ||
130 | fst = fstRunLengthEncode False (Set.fromList "abc") 3 | ||
131 | |||
132 | hprop_runLength :: Property | ||
133 | hprop_runLength = property $ do | ||
134 | input <- forAll genWord | ||
135 | let maxRun = fromMaybe 1 $ countMaxRun input | ||
136 | alphabet = Set.fromList input | ||
137 | encode = fstRunLengthEncode False alphabet maxRun | ||
138 | decode = fstRunLengthDecode alphabet maxRun | ||
139 | annotateShow $ countMaxRun input | ||
140 | annotateShow $ pretty encode | ||
141 | annotateShow $ pretty decode | ||
142 | [encoded] <- return . runFST encode $ Seq.fromList input | ||
143 | annotateShow $ toList encoded | ||
144 | [Seq.fromList input] === runFST decode encoded | ||
145 | |||
146 | hprop_runLength' :: Property | ||
147 | hprop_runLength' = property $ do | ||
148 | input <- forAll genWord | ||
149 | |||
150 | let maxRun = fromMaybe 1 $ countMaxRun input | ||
151 | alphabet = Set.fromList input | ||
152 | encode = fstRunLengthEncode True alphabet maxRun | ||
153 | decode = fstRunLengthDecode alphabet maxRun | ||
154 | annotateShow $ countMaxRun input | ||
155 | annotateShow $ pretty encode | ||
156 | annotateShow $ pretty decode | ||
157 | |||
158 | let encoded = runFST encode $ Seq.fromList input | ||
159 | annotateShow encoded | ||
160 | when (maxRun > 1) $ | ||
161 | assert $ encoded `longerThan` 1 | ||
162 | |||
163 | encoded' <- forAll $ G.element encoded | ||
164 | [Seq.fromList input] === runFST decode encoded' | ||
165 | where | ||
166 | longerThan :: [a] -> Natural -> Bool | ||
167 | longerThan [] _ = False | ||
168 | longerThan _ 0 = True | ||
169 | longerThan (_:xs) n = longerThan xs $ pred n | ||
170 | |||
171 | countMaxRun :: (Eq a, Foldable f) => f a -> Maybe Natural | ||
172 | countMaxRun = goMaxRun Nothing Nothing . toList | ||
173 | where | ||
174 | goMaxRun :: Eq a | ||
175 | => Maybe (a, Natural) -- ^ Maximum | ||
176 | -> Maybe (a, Natural) -- ^ Current | ||
177 | -> [a] | ||
178 | -> Maybe Natural | ||
179 | goMaxRun Nothing Nothing [] = Nothing | ||
180 | goMaxRun (Just (_, n)) (Just (_, n')) [] | ||
181 | | n' > n = Just n' | ||
182 | | otherwise = Just n | ||
183 | goMaxRun Nothing Nothing (a:as) = goMaxRun (Just (a, 1)) (Just (a, 1)) as | ||
184 | goMaxRun (Just (a, n)) (Just (a', n')) (x:xs) | ||
185 | | x == a' = goMaxRun (Just (a, n)) (Just (a', succ n')) xs | ||
186 | | n' > n = goMaxRun (Just (a', n')) (Just (x, 1)) xs | ||
187 | | otherwise = goMaxRun (Just (a, n)) (Just (x, 1)) xs | ||
diff --git a/edit-lens/test/Driver.hs b/edit-lens/test/Driver.hs new file mode 100644 index 0000000..327adf4 --- /dev/null +++ b/edit-lens/test/Driver.hs | |||
@@ -0,0 +1 @@ | |||
{-# OPTIONS_GHC -F -pgmF tasty-discover -optF --tree-display #-} | |||