11{-# LANGUAGE DeriveFunctor #-}
22{-# LANGUAGE ScopedTypeVariables #-}
33
4- -- | Possibly infinite streams of @'Maybe' a@s.
4+ -- | Finite and infinite streams of @'Maybe' a@s.
55module System.FS.Sim.Stream (
66 -- * Streams
7- Stream
7+ Stream (.. )
8+ , InternalInfo (.. )
89 -- * Running
910 , runStream
11+ , runStreamN
12+ , runStreamIndefinitely
1013 -- * Construction
1114 , always
1215 , empty
13- , mkInfinite
1416 , repeating
17+ , unsafeMkInfinite
1518 , unsafeMkFinite
19+ -- * Modify
20+ , filter
1621 -- * Query
1722 , null
23+ , isFinite
24+ , isInfinite
1825 -- * Generation and shrinking
1926 , genFinite
27+ , genFiniteN
2028 , genInfinite
2129 , genMaybe
22- , genMaybe'
2330 , shrinkStream
31+ , liftShrinkStream
2432 ) where
2533
2634import Control.Monad (replicateM )
27- import Prelude hiding (null )
35+ import Prelude hiding (filter , isInfinite , null )
36+ import qualified Prelude
2837import qualified Test.QuickCheck as QC
2938import Test.QuickCheck (Gen )
3039
3140{- ------------------------------------------------------------------------------
3241 Streams
3342-------------------------------------------------------------------------------}
3443
35- -- | A 'Stream' is a stream of @'Maybe' a@s, which is /possibly/ infinite or
36- -- /definitely/ finite.
37- --
38- -- Finiteness is tracked internally and used for 'QC.shrink'ing and the 'Show'
39- -- instance.
40- data Stream a = Stream {
41- -- | Info about the size of the stream.
42- _streamInternalInfo :: InternalInfo
43- , _getStream :: [Maybe a ]
44+ -- | A stream of @'Maybe' a@s that can be infinite.
45+ data Stream a =
46+ -- | UNSAFE: when constructing, modifying, or accessing the internals of a
47+ -- 'Stream', it is the responsibility of the user to preserve the following
48+ -- invariant:
49+ --
50+ -- INVARIANT: if the stream is marked as 'Infinite', then the internal list
51+ -- should be infinite. If the stream is marked as 'Finite', then the internal
52+ -- list should finite.
53+ --
54+ -- * If the internal list is infinite but marked as 'Finite', then 'QC.shrink'
55+ -- or 'show' on the corresponding stream will diverge.
56+ --
57+ -- * If the internal list is finite but marked as 'Infinite', then 'QC.shrink'
58+ -- on the corresponding stream will degrade to an infinite list of empty
59+ -- streams.
60+ UnsafeStream {
61+ -- | UNSAFE: see 'UnsafeStream' for more information.
62+ --
63+ -- Info about the finiteness of the stream. It is used for 'QC.shrink'ing
64+ -- and the 'Show' instance.
65+ unsafeStreamInternalInfo :: InternalInfo
66+ -- | UNSAFE: see 'UnsafeStream' for more information.
67+ --
68+ -- The internal list underlying the stream.
69+ , unsafeStreamList :: [Maybe a ]
4470 }
4571 deriving Functor
4672
47- -- | Tag for 'Stream's that describes whether it is either /definitely/ a finite
48- -- stream, or /possibly/ an infinite stream.
73+ -- | Tag for 'Stream's that describes whether it is finite or infinite.
4974--
50- -- Useful for the 'Show' instance of 'Stream': when a 'Stream' is /definitely/
51- -- finite, we can safely print the full stream.
75+ -- Useful for the 'Show' instance of 'Stream': when a 'Stream' is finite, we can
76+ -- safely print the full stream.
5277data InternalInfo = Infinite | Finite
5378
54- -- | Fully shows a 'Stream' if it is /definitely/ finite, or prints a
55- -- placeholder string if it is /possibly/ infinite.
79+ -- | Fully shows a 'Stream' if it is finite, or prints a placeholder string if
80+ -- it is infinite.
5681instance Show a => Show (Stream a ) where
57- showsPrec n (Stream info xs) = case info of
82+ showsPrec n (UnsafeStream info xs) = case info of
5883 Infinite -> (" <infinite stream>" ++ )
5984 Finite -> (if n > 10 then (' (' : ) else id )
6085 . shows xs
@@ -65,104 +90,149 @@ instance Show a => Show (Stream a) where
6590 Running
6691-------------------------------------------------------------------------------}
6792
68- -- | Advance the 'Stream'. Return the @'Maybe' a@ and the remaining 'Stream'.
93+ -- | \( O(1) \): advance the 'Stream'. Return the @'Maybe' a@ and the remaining
94+ -- 'Stream'.
6995--
7096-- Returns 'Nothing' by default if the 'Stream' is empty.
7197runStream :: Stream a -> (Maybe a , Stream a )
72- runStream s@ (Stream _ [] ) = (Nothing , s)
73- runStream (Stream info (a: as)) = (a, Stream info as)
98+ runStream s@ (UnsafeStream _ [] ) = (Nothing , s)
99+ runStream (UnsafeStream info (a: as)) = (a, UnsafeStream info as)
100+
101+ -- | \( O(n) \): like 'runStream', but advancing the stream @n@ times.
102+ --
103+ -- If @n<=0@, then the stream is advanced @0@ times.
104+ runStreamN :: Int -> Stream a -> ([Maybe a ], Stream a )
105+ runStreamN n s
106+ | n <= 0 = ([] , s)
107+ | otherwise =
108+ let (x, s') = runStream s
109+ (xs, s'') = runStreamN (n- 1 ) s'
110+ in (x: xs, s'')
111+
112+ -- | \( O(\infty) \): like 'runStream', but advancing the stream indefinitely.
113+ --
114+ -- For infinite streams, this produces an infinite list. For finite streams,
115+ -- this produces a finite list.
116+ runStreamIndefinitely :: Stream a -> [Maybe a ]
117+ runStreamIndefinitely (UnsafeStream _ as) = as ++ repeat Nothing
74118
75119{- ------------------------------------------------------------------------------
76120 Construction
77121-------------------------------------------------------------------------------}
78122
79123-- | Make an empty 'Stream'.
80124empty :: Stream a
81- empty = Stream Finite []
125+ empty = UnsafeStream Finite []
82126
83127-- | Make a 'Stream' that always generates the given @a@.
84128always :: a -> Stream a
85- always x = Stream Infinite (repeat (Just x))
129+ always x = UnsafeStream Infinite (repeat (Just x))
86130
87131-- | Make a 'Stream' that infinitely repeats the given list.
88132repeating :: [Maybe a ] -> Stream a
89- repeating xs = Stream Infinite $ concat ( repeat xs)
133+ repeating xs = UnsafeStream Infinite $ cycle xs
90134
91- -- | UNSAFE: Make a 'Stream' that is marked as definitely finite.
92- --
93- -- This is unsafe since a user can pass in any list, and evaluating
94- -- 'Test.QuickCheck.shrink' or 'show' on the resulting 'Stream' will diverge. It
95- -- is the user's responsibility to only pass in a finite list.
135+ -- | UNSAFE: Make a 'Stream' that is marked as finite. It is the user's
136+ -- responsibility to only pass in finite lists. See 'UnsafeStream' for more
137+ -- information.
96138unsafeMkFinite :: [Maybe a ] -> Stream a
97- unsafeMkFinite = Stream Finite
139+ unsafeMkFinite = UnsafeStream Finite
98140
99- -- | Make a 'Stream' that is marked as possibly infinite.
100- mkInfinite :: [Maybe a ] -> Stream a
101- mkInfinite = Stream Infinite
141+ -- | UNSAFE: Make a 'Stream' that is marked as infinite. It is the user's
142+ -- responsibility to only pass in infinite lists. See 'UnsafeStream' for more
143+ -- information.
144+ unsafeMkInfinite :: [Maybe a ] -> Stream a
145+ unsafeMkInfinite = UnsafeStream Infinite
146+
147+ {- ------------------------------------------------------------------------------
148+ Modify
149+ -------------------------------------------------------------------------------}
150+
151+ -- | Filter a 'Stream', preserving finiteness.
152+ filter :: (Maybe a -> Bool ) -> Stream a -> Stream a
153+ filter p (UnsafeStream info xs) = UnsafeStream info (Prelude. filter p xs)
102154
103155{- ------------------------------------------------------------------------------
104156 Query
105157-------------------------------------------------------------------------------}
106158
107- -- | Return 'True' if the stream is empty.
159+ -- | Check that the stream is empty.
108160--
109- -- A stream consisting of only 'Nothing's (even if it is only one) is not
110- -- considered to be empty.
161+ -- In general, a stream is only empty if the stream is equivalent to 'empty'.
162+ --
163+ -- A finite\/infinite stream consisting of only 'Nothing's is not considered to
164+ -- be empty. In particular, @'null' ('always' Nothing) /= True@.
111165null :: Stream a -> Bool
112- null (Stream _ [] ) = True
113- null _ = False
166+ null (UnsafeStream Finite [] ) = True
167+ null _ = False
168+
169+ -- | Check that the stream is finite
170+ isFinite :: Stream a -> Bool
171+ isFinite (UnsafeStream Finite _) = True
172+ isFinite (UnsafeStream Infinite _) = False
173+
174+ -- | Check that the stream is infinite
175+ isInfinite :: Stream a -> Bool
176+ isInfinite (UnsafeStream Finite _) = False
177+ isInfinite (UnsafeStream Infinite _) = True
114178
115179{- ------------------------------------------------------------------------------
116180 Generation and shrinking
117181-------------------------------------------------------------------------------}
118182
119- -- | Shrink a stream like it is an 'Test.QuickCheck.InfiniteList'.
183+ -- | Shrink a stream like it is an 'QC.InfiniteList'.
184+ --
185+ -- Infinite streams are shrunk differently than lists that are finite, which is
186+ -- to ensure that we shrink infinite lists towards finite lists.
187+ --
188+ -- * Infinite streams are shrunk by taking finite prefixes of the argument
189+ -- stream. Note that there are an infinite number of finite prefixes, so even
190+ -- though the *shrink list* is infinite, the individual *list elements* are
191+ -- finite.
120192--
121- -- Possibly infinite streams are shrunk differently than lists that are
122- -- definitely finite, which is to ensure that shrinking terminates.
123- -- * Possibly infinite streams are shrunk by taking finite prefixes of the
124- -- argument stream. As such, shrinking a possibly infinite stream creates
125- -- definitely finite streams.
126- -- * Definitely finite streams are shrunk like lists are shrunk normally,
127- -- preserving that the created streams are still definitely finite.
193+ -- * Finite streams are shrunk like lists are shrunk normally, preserving
194+ -- finiteness.
128195shrinkStream :: Stream a -> [Stream a ]
129- shrinkStream (Stream info xs0) = case info of
130- Infinite -> Stream Finite <$> [take n xs0 | n <- map (2 ^ ) [0 :: Int .. ]]
131- Finite -> Stream Finite <$> QC. shrinkList (const [] ) xs0
196+ shrinkStream (UnsafeStream info xs0) = case info of
197+ Infinite -> UnsafeStream Finite <$> [take n xs0 | n <- map (2 ^ ) [0 :: Int .. ]]
198+ Finite -> UnsafeStream Finite <$> QC. shrinkList (const [] ) xs0
199+
200+ -- | Like 'shrinkStream', but with a custom shrinker for elements of the stream.
201+ liftShrinkStream :: (Maybe a -> [Maybe a ]) -> Stream a -> [Stream a ]
202+ liftShrinkStream shrinkOne (UnsafeStream info xs0) = case info of
203+ Infinite -> UnsafeStream Finite <$> [take n xs0 | n <- map (2 ^ ) [0 :: Int .. ]]
204+ Finite -> UnsafeStream Finite <$> QC. shrinkList shrinkOne xs0
132205
133206-- | Make a @'Maybe' a@ generator based on an @a@ generator.
134207--
135208-- Each element has a chance of being either 'Nothing' or an element generated
136- -- with the given @a@ generator (wrapped in a 'Just').
137- --
138- -- The first argument is the likelihood (as used by 'QC.frequency') of a
139- -- 'Just' where 'Nothing' has likelihood 2.
209+ -- with the given @a@ generator (wrapped in a 'Just'). These /likelihoods/ are
210+ -- passed to 'QC.frequency'.
140211genMaybe ::
141- Int -- ^ Likelihood of 'Nothing'
142- -> Int -- ^ Likelihood of @'Just' a@
212+ Int -- ^ Likelihood of 'Nothing'
213+ -> Int -- ^ Likelihood of @'Just' a@
143214 -> Gen a
144215 -> Gen (Maybe a )
145216genMaybe nLi jLi genA = QC. frequency
146217 [ (nLi, return Nothing )
147218 , (jLi, Just <$> genA)
148219 ]
149220
150- -- | Like 'genMaybe', but with the likelihood of 'Nothing' fixed to @2@. 'QC.frequency'
151- genMaybe' ::
152- Int -- ^ Likelihood of @'Just' a@
153- -> Gen a
221+ -- | Generate a finite 'Stream' of length @n@.
222+ genFiniteN ::
223+ Int -- ^ Requested size of finite stream.
154224 -> Gen (Maybe a )
155- genMaybe' = genMaybe 2
225+ -> Gen (Stream a )
226+ genFiniteN n gen = UnsafeStream Finite <$> replicateM n gen
156227
157- -- | Generate a finite 'Stream' of length @n@ .
228+ -- | Generate a sized, finite 'Stream'.
158229genFinite ::
159- Int -- ^ Requested size of finite stream. Tip: use 'genMaybe'.
160- -> Gen (Maybe a )
230+ Gen (Maybe a )
161231 -> Gen (Stream a )
162- genFinite n gen = Stream Finite <$> replicateM n gen
232+ genFinite gen = UnsafeStream Finite <$> QC. listOf gen
163233
164234-- | Generate an infinite 'Stream'.
165235genInfinite ::
166- Gen (Maybe a ) -- ^ Tip: use 'genMaybe'.
236+ Gen (Maybe a )
167237 -> Gen (Stream a )
168- genInfinite gen = Stream Infinite <$> QC. infiniteListOf gen
238+ genInfinite gen = UnsafeStream Infinite <$> QC. infiniteListOf gen
0 commit comments