Merge pull request #574 from shlok:seedless-unfold

This commit is contained in:
Harendra Kumar 2020-07-03 16:10:43 +05:30
commit 72b6a6db06
2 changed files with 39 additions and 4 deletions

View File

@ -57,6 +57,7 @@ module Streamly.Internal.Prelude
, unfoldr
, unfoldrM
, unfold
, unfold0
, iterate
, iterateM
, fromIndices
@ -536,6 +537,7 @@ import Data.Kind (Type)
#endif
import Data.Heap (Entry(..))
import Data.Maybe (isJust, fromJust, isNothing)
import Data.Void (Void)
import Foreign.Storable (Storable)
import Prelude
hiding (filter, drop, dropWhile, take, takeWhile, zipWith, foldr,
@ -706,6 +708,13 @@ unfoldrMZipSerial = Serial.unfoldrM
unfold :: (IsStream t, Monad m) => Unfold m a b -> a -> t m b
unfold unf x = fromStreamD $ D.unfold unf x
-- | Convert an 'Unfold' with a closed input end into a stream.
--
-- /Internal/
{-# INLINE unfold0 #-}
unfold0 :: (IsStream t, Monad m) => Unfold m Void b -> t m b
unfold0 unf = unfold unf (error "unfold0: unexpected void evaluation")
------------------------------------------------------------------------------
-- Specialized Generation
------------------------------------------------------------------------------

View File

@ -15,9 +15,13 @@ import Control.Concurrent (threadDelay)
import Control.Monad (when)
import Test.Hspec as H
import Test.Hspec.QuickCheck (prop)
import Test.QuickCheck (Property, choose)
import Test.QuickCheck.Monadic (monadicIO, pick)
import qualified Streamly.Prelude as S
import qualified Streamly.Internal.Data.Fold as FL
import qualified Streamly.Internal.Data.Unfold as UF
import qualified Streamly.Internal.Prelude as SI
import Streamly.Internal.Data.Time.Clock (Clock(Monotonic), getTime)
@ -25,6 +29,9 @@ import Streamly.Internal.Data.Time.Units
(AbsTime, NanoSecond64(..), toRelTime64, diffAbsTime64)
import Data.Int (Int64)
max_length :: Int
max_length = 1000
tenPow8 :: Int64
tenPow8 = 10^(8 :: Int)
@ -70,9 +77,28 @@ testDropByTime = do
$ S.repeatM (threadDelay 1000 >> getTime Monotonic)
checkTakeDropTime (Just t0, mt1)
unfold :: Property
unfold = monadicIO $ do
a <- pick $ choose (0, max_length `div` 2)
b <- pick $ choose (0, max_length)
let unf = UF.enumerateFromToIntegral b
ls <- S.toList $ S.unfold unf a
return $ ls == [a..b]
unfold0 :: Property
unfold0 = monadicIO $ do
a <- pick $ choose (0, max_length `div` 2)
b <- pick $ choose (0, max_length)
let unf = UF.supply (UF.enumerateFromToIntegral b) a
ls <- S.toList $ SI.unfold0 unf
return $ ls == [a..b]
main :: IO ()
main =
hspec $
describe "Filtering" $ do
it "takeByTime" (testTakeByTime `shouldReturn` True)
it "dropByTime" (testDropByTime `shouldReturn` True)
hspec $ do
describe "Filtering" $ do
it "takeByTime" (testTakeByTime `shouldReturn` True)
it "dropByTime" (testDropByTime `shouldReturn` True)
describe "From Generators" $ do
prop "unfold" unfold
prop "unfold0" unfold0