{-# LANGUAGE TypeFamilies, TypeSynonymInstances, TypeOperators, PackageImports, CPP #-} module NoSlow.Backend.DPH.Prim.Seq ( module U, enumFromTo_Int, pair, fst, snd #if __GLASGOW_HASKELL__ < 612 , filter #endif ) where import NoSlow.Util.Computation import "dph-prim-seq" Data.Array.Parallel.Unlifted as U import Data.Array.Parallel.Unlifted.Sequential import Data.Array.Parallel.Base ( (:*:)(..), fstS, sndS ) import qualified Prelude import Prelude ( Int, Num, Bool ) instance DeepSeq (U.Array a) instance (TestData a, U.Elt a) => TestData (U.Array a) where testData n = U.fromList (testData n) instance Computation (U.Array a) where type Arg (U.Array a) = Nil type Res (U.Array a) = U.Array a apply x _ = x #if __GLASGOW_HASKELL__ < 612 filter :: Elt a => (a -> Bool) -> Array a -> Array a {-# INLINE filter #-} filter = filterU #endif enumFromTo_Int :: Int -> Int -> Array Int {-# INLINE enumFromTo_Int #-} enumFromTo_Int = U.enumFromTo pair :: a -> b -> a :*: b {-# INLINE pair #-} pair = (:*:) fst :: a :*: b -> a {-# INLINE fst #-} fst = fstS snd :: a :*: b -> b {-# INLINE snd #-} snd = sndS