module Examples.Simple.Sharing where import qualified Prelude import Feldspar import Feldspar.Wrap import Feldspar.Vector import Feldspar.Compiler -- | Examples on the optimization transformation 'sharing' (also called 'common subexpression elimination'). share1 :: Data Int32 -> Data Int32 share1 v = w + w where w = 2 * v share2 :: Data Int32 -> Data Int32 share2 v = (2*v) + (2*v) share3 :: Data Int32 -> Vector1 Int32 share3 v = indexed 10 $ const w where w = 2 * v + v share4 :: Data Int32 -> Vector1 Int32 share4 v = indexed 10 $ const w where w = 2 * q + q where q = v + 1 share4' :: Data Int32 -> Data [Int32] share4' = wrap share4 share5 :: Data Index -> Vector1 Index share5 v = indexed 10 $ \ix -> w ix where w ix = 2 * v + ix share5' :: Data Index -> Data [Index] share5' = wrap share5 share6 :: Vector1 Int32 -> Vector1 Int32 share6 v = share (map (*2) v) $ \w -> zipWith (+) w w save1 :: Vector1 Index -> Vector1 Index save1 = map (*3) . save . reverse save2 :: Data Index -> Data Index save2 = (*3) . save . (+2)