1717{-# LANGUAGE TypeOperators #-}
1818{-# LANGUAGE UndecidableSuperClasses #-}
1919{-# LANGUAGE ViewPatterns #-}
20- {-# OPTIONS_GHC -Wno-orphans #-}
20+ {-# OPTIONS_GHC -Wno-orphans -Wno-name-shadowing #-}
2121
2222-- | `TypeSpec` definition for `[]` and functions for writing constraints over
2323-- lists
@@ -227,7 +227,8 @@ instance HasSpec a => HasSpec [a] where
227227 Just szHint -> do
228228 sz <- genFromSizeSpec (leqSpec szHint)
229229 listOfUntilLenT (genFromSpecT elemS) (fromIntegral sz) (const True )
230- pureGen $ shuffle (must ++ lst)
230+ must' <- pureGen $ shuffle must
231+ pureGen $ randomInterleaving must' lst
231232 genFromTypeSpec (ListSpec msz must szSpec elemS NoFold ) = do
232233 sz0 <- genFromSizeSpec (szSpec <> geqSpec (sizeOf must) <> maybe TrueSpec (leqSpec . max 0 ) msz)
233234 let sz = fromIntegral (sz0 - sizeOf must)
@@ -236,7 +237,8 @@ instance HasSpec a => HasSpec [a] where
236237 (genFromSpecT elemS)
237238 sz
238239 ((`conformsToSpec` szSpec) . (+ sizeOf must) . fromIntegral )
239- pureGen $ shuffle (must ++ lst)
240+ must' <- pureGen $ shuffle must
241+ pureGen $ randomInterleaving must' lst
240242 genFromTypeSpec (ListSpec msz must szSpec elemS (FoldSpec f foldS)) = do
241243 let szSpec' = szSpec <> maybe TrueSpec (leqSpec . max 0 ) msz
242244 genFromFold must szSpec' elemS f foldS
@@ -266,6 +268,21 @@ instance HasSpec a => HasSpec [a] where
266268 <> satisfies (sizeOf_ x) size
267269 <> maybe TruePred (flip genHint x) msz
268270
271+ randomInterleaving :: [a ] -> [a ] -> Gen [a ]
272+ randomInterleaving xs ys = go xs ys (length ys)
273+ where
274+ go [] ys _ = pure ys
275+ go xs [] _ = pure xs
276+ go xs ys l = do
277+ -- TODO: think about distribution here
278+ i <- choose (0 , l)
279+ go' i xs ys (l - i)
280+
281+ go' _ xs [] _ = pure xs
282+ go' _ [] ys _ = pure ys
283+ go' 0 (x: xs) ys l = (x: ) <$> go xs ys l
284+ go' i xs (y: ys) l = (y: ) <$> go' (i- 1 ) xs ys l
285+
269286instance HasSpec a => HasGenHint [a ] where
270287 type Hint [a ] = Integer
271288 giveHint szHint = typeSpec $ ListSpec (Just szHint) [] mempty mempty NoFold
0 commit comments