module Fixedpoint where import qualified Prelude import Feldspar import Feldspar.FixedPoint import Feldspar.Compiler import Feldspar.Vector generic :: (Fractional a) => Vector a -> Vector a generic = map (\x -> x+3.14) floating :: DVector Float -> DVector Float floating = generic fixed :: DVector Int32 -> DVector Int32 fixed = map (freezeFix' (-6)) . generic . map (unfreezeFix' (-4)) emulation :: Vector (Fix Int16) -> Vector (Fix Int16) emulation = generic branch1 :: Data Bool -> Data Int32 -> Data Int32 -> Data Int32 branch1 c x y = freezeFix' (-16) $ c ? (x', y') where x' = unfreezeFix' (-20) x y' = unfreezeFix' (-10) y branch2 :: Data Bool -> Data Int32 -> Data Int32 -> Data Int32 branch2 c x y = freezeFix' (-16) $ c ?! (x', y') where x' = unfreezeFix' (-20) x y' = unfreezeFix' (-10) y scalarProduct :: (Num a, Syntactic a, Fixable a) => Data DefaultInt -> Vector a -> Vector a -> a scalarProduct e xs ys = fixFold (+) (fix e 0) $ zipWith (*) xs ys floatScalarProduct :: DVector Float -> DVector Float -> Data Float floatScalarProduct = scalarProduct undefined fixScalarProduct :: DVector Int32 -> DVector Int32 -> Data Int32 fixScalarProduct xs ys = freezeFix' (-18) $ scalarProduct (-16) xs' ys' where xs' = map (unfreezeFix' (-8)) xs ys' = map (unfreezeFix' (-6)) ys