repa-3.4.1.3: High performance, regular, shape polymorphic parallel arrays.

Safe HaskellNone
LanguageHaskell98

Data.Array.Repa.Repr.HintSmall

Synopsis

Documentation

data S r1 Source #

Hints that evaluating this array is only a small amount of work. It will be evaluated sequentially in the main thread, instead of in parallel on the gang. This avoids the associated scheduling overhead.

Instances

Source r1 a => Source (S r1) a Source # 

Associated Types

data Array (S r1) sh a :: * Source #

Methods

extent :: Shape sh => Array (S r1) sh a -> sh Source #

index :: Shape sh => Array (S r1) sh a -> sh -> a Source #

unsafeIndex :: Shape sh => Array (S r1) sh a -> sh -> a Source #

linearIndex :: Shape sh => Array (S r1) sh a -> Int -> a Source #

unsafeLinearIndex :: Shape sh => Array (S r1) sh a -> Int -> a Source #

deepSeqArray :: Shape sh => Array (S r1) sh a -> b -> b Source #

(Shape sh, LoadRange r1 sh e) => LoadRange (S r1) sh e Source # 

Methods

loadRangeS :: Target r2 e => Array (S r1) sh e -> MVec r2 e -> sh -> sh -> IO () Source #

loadRangeP :: Target r2 e => Array (S r1) sh e -> MVec r2 e -> sh -> sh -> IO () Source #

(Shape sh, Load r1 sh e) => Load (S r1) sh e Source # 

Methods

loadS :: Target r2 e => Array (S r1) sh e -> MVec r2 e -> IO () Source #

loadP :: Target r2 e => Array (S r1) sh e -> MVec r2 e -> IO () Source #

Structured r1 a b => Structured (S r1) a b Source # 

Associated Types

type TR (S r1) :: * Source #

Methods

smap :: Shape sh => (a -> b) -> Array (S r1) sh a -> Array (TR (S r1)) sh b Source #

szipWith :: (Shape sh, Source r c) => (c -> a -> b) -> Array r sh c -> Array (S r1) sh a -> Array (TR (S r1)) sh b Source #

Read (Array r1 sh e) => Read (Array (S r1) sh e) Source # 

Methods

readsPrec :: Int -> ReadS (Array (S r1) sh e) #

readList :: ReadS [Array (S r1) sh e] #

readPrec :: ReadPrec (Array (S r1) sh e) #

readListPrec :: ReadPrec [Array (S r1) sh e] #

Show (Array r1 sh e) => Show (Array (S r1) sh e) Source # 

Methods

showsPrec :: Int -> Array (S r1) sh e -> ShowS #

show :: Array (S r1) sh e -> String #

showList :: [Array (S r1) sh e] -> ShowS #

data Array (S r1) Source # 
data Array (S r1) = ASmall !(Array r1 sh a)
type TR (S r1) Source # 
type TR (S r1) = S (TR r1)

hintSmall :: Array r1 sh e -> Array (S r1) sh e Source #

Wrap an array with a smallness hint.