import Data.Vector.Generic (Vector, (!)) import qualified Data.Vector.Generic as V conv_1, conv_2, conv_3 :: (Num a, Vector v a) => v a -> v a -> v a {-# INLINE conv_1 #-} conv_1 h x = V.generate (l+m) f where m = V.length h - 1 l = V.length x {-# INLINE f #-} f n = g 0 n (max 0 (n-l+1)) (min n m) g y n m k = if m <= k then let y' = y + (h ! m) * (x ! (n-m)) in y' `seq` g y' n (m+1) k else y {-# INLINE conv_2 #-} conv_2 h x = V.generate (l+m) f where l = V.length x m = V.length h - 1 {-# INLINE f #-} f n = let j = max 0 (n-l+1) k = (min n m) - j + 1 in V.sum (V.zipWith (*) (V.slice j k h) (V.reverse (V.slice (n - j - k + 1) k x))) {-# INLINE conv_3 #-} conv_3 h x = V.generate (l+m-1) f where m = V.length h l = V.length x p = V.replicate (m-1) 0 x' = p ++ x ++ p {-# INLINE f #-} f i = V.sum (V.zipWith (*) (V.reverse h) (V.slice i m x'))