module Examples.Simple.Streams where import Prelude () import Feldspar import Feldspar.Vector import Feldspar.Stream import Feldspar.Compiler -- | Generic (not compilable) function to introduce usage of scan function for Streams. -- 'scan f a str' produces a stream by successively applying 'f' to -- each element of the input stream 'str' and the previous element of -- the output stream. stream1 :: (Num a, Syntactic a) => Stream a -> Stream a stream1 = scan (+) 0 -- | Wrapper to turn the parameters of 'stream1' into vectors. stream1_1 :: (Numeric a) => DVector a -> DVector a stream1_1 = streamAsVector stream1 -- | Wrappers to fix the type and size of the streams in 'stream1_1'. stream1_1' :: Data [Int32] -> Data [Int32] stream1_1' xs = freezeVector $ stream1_1 $ unfreezeVector' 64 xs stream1_1_wrapped:: Data' D64 [Int32] -> Data [Int32] stream1_1_wrapped = wrap (stream1_1 :: DVector Int32 -> DVector Int32)