ivory-0.1.0.0: Safe embedded C programming.

Safe HaskellNone

Ivory.Language.Array

Synopsis

Documentation

newtype Ix n Source

Values in the range 0 .. n-1.

Constructors

Ix 

Fields

getIx :: Expr
 

Instances

SingI Nat n => Num (Ix n) 
SingI Nat n => IvoryExpr (Ix n) 
SingI Nat n => IvoryVar (Ix n) 
SingI Nat n => IvoryType (Ix n) 
SingI Nat n => IvoryOrd (Ix n) 
SingI Nat n => IvoryEq (Ix n) 
SingI Nat n => IvoryStore (Ix n) 
SingI Nat len => IvoryInit (Ix len) 
(SingI Nat n, IvoryIntegral to, Default to) => SafeCast (Ix n) to 

fromIx :: SingI n => Ix n -> IxRepSource

toIx :: (IvoryExpr a, Bounded a, SingI n) => a -> Ix nSource

Casting from a bounded Ivory expression to an index. This is safe, although the value may be truncated. Furthermore, indexes are always positive.

ixSize :: forall n. SingI n => Ix n -> IntegerSource

The number of elements that an index covers.

arrayLen :: forall s len area n ref. (Num n, SingI len, IvoryArea area, IvoryRef ref) => ref s (Array len area) -> nSource

(!) :: forall s len area ref. (SingI len, IvoryArea area, IvoryRef ref, IvoryExpr (ref s (Array len area)), IvoryExpr (ref s area)) => ref s (Array len area) -> Ix len -> ref s areaSource

Array indexing.

mkIx :: forall n. SingI n => Expr -> Ix nSource

ixBinop :: SingI n => (Expr -> Expr -> Expr) -> Ix n -> Ix n -> Ix nSource

ixUnary :: SingI n => (Expr -> Expr) -> Ix n -> Ix nSource