module Data.Array.Repa.Repr.HintSmall
        (S, Array (..), hintSmall)
where
import Data.Array.Repa.Eval.Load
import Data.Array.Repa.Base
import Data.Array.Repa.Shape
data S r1
instance Source r1 a => Source (S r1) a where
 data Array (S r1) sh a
        = ASmall !(Array r1 sh a)
 extent (ASmall arr) 
        = extent arr
 
 index  (ASmall arr) ix
        = index arr ix
 
 unsafeIndex (ASmall arr) ix
        = unsafeIndex arr ix
 
 linearIndex (ASmall arr) ix
        = linearIndex arr ix
 
 unsafeLinearIndex (ASmall arr) ix
        = unsafeLinearIndex arr ix
 
 deepSeqArray (ASmall arr) x
        = deepSeqArray arr x
 
hintSmall :: Array r1 sh e -> Array (S r1) sh e
hintSmall = ASmall
deriving instance Show (Array r1 sh e) 
        => Show (Array (S r1) sh e)
deriving instance Read (Array r1 sh e) 
        => Read (Array (S r1) sh e)
instance ( Shape sh, Load r1 sh e) 
        => Load (S r1) sh e where
 loadP (ASmall arr) marr
  = loadS arr marr
 
 loadS (ASmall arr) marr
  = loadS arr marr
 
instance ( Shape sh, LoadRange r1 sh e)
        => LoadRange (S r1) sh e where
 loadRangeP (ASmall arr) marr ix1 ix2
  = loadRangeS arr marr ix1 ix2
 
 loadRangeS (ASmall arr) marr ix1 ix2
  = loadRangeS arr marr ix1 ix2