module Examples.Simple.Vectors where import qualified Prelude import Feldspar import Feldspar.Wrap import Feldspar.Vector import Feldspar.Compiler -- * Examples on working with vectors. -- | Generates a vector: [1, 2, 3, ... , 16], -- adds 3 to every element and -- reverses the vector then -- multiplies every element by 10. vector1 :: Vector1 Index vector1 = map (*10) $ reverse $ map (+3) $ enumFromTo 1 16 -- | The same computation, but storing each intermediate result into temporal buffers vector1' :: Vector1 Index vector1' = map (*10) $ force $ reverse $ force $ map (+3) $ force $ enumFromTo 1 16 -- | Drops the first 3 elements of a vector vector2 :: Vector1 Int32 -> Vector1 Int32 vector2 = drop 3 -- | Wrappers to `vector2` to provide static information on the input vector size vector2' :: Data' D10 [Int32] -> Data [Int32] vector2' = wrap vector2 vector2'' :: Data [Int32] -> Data [Int32] vector2'' = desugar . vector2 . thawVector' 10 -- | Generates a parallel vector of size 10 vector3 :: Data Index -> Vector1 Index vector3 a = indexed 10 ((+a) . (*10)) -- | Vector summation. vector4 :: (Numeric a, Type a) => Vector1 a -> Data a vector4 xs = fold (+) 0 xs -- | Wrappers to provide the necessary type information vector4' :: Vector1 Int32 -> Data Int32 vector4' = vector4 vector4'' :: Vector1 Word8 -> Data Word8 vector4'' = vector4 -- | Generic function to increment vector elements vector5 :: (Type a, Numeric a) => Vector1 a -> Vector1 a vector5 = map (+1) -- | Wrappers to provide necessary type information and input size vector5' :: Vector1 Int32 -> Vector1 Int32 vector5' = vector5 vector5'' :: Data' D64 [Int32] -> Data [Int32] vector5'' = wrap (vector5 :: Vector1 Int32 -> Vector1 Int32) -- | Concatenation vector6 :: Vector1 Int32 -> Vector1 Int32 vector6 xs = map (+1) xs ++ map (*2) xs