ivory-0.1.0.8: Safe embedded C programming.

Safe HaskellNone
LanguageHaskell2010

Ivory.Language

Contents

Synopsis

Kinds

data Area k Source #

The kind of memory-area types.

Constructors

Struct Symbol 
Array Nat (Area k) 
CArray (Area k) 
Stored k

This is lifting for a *-kinded type

data Proc k Source #

The kind of procedures.

Constructors

[k] :-> k 

Types

class IvoryType t Source #

The connection between Haskell and Ivory types.

Minimal complete definition

ivoryType

Instances
IvoryType () Source #

void type

Instance details

Defined in Ivory.Language.Type

Methods

ivoryType :: Proxy () -> Type Source #

IvoryType OpaqueType Source # 
Instance details

Defined in Ivory.Language.Type

IvoryType IString Source # 
Instance details

Defined in Ivory.Language.IString

IvoryType IChar Source # 
Instance details

Defined in Ivory.Language.IChar

IvoryType Sint64 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryType Sint32 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryType Sint16 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryType Sint8 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryType Uint64 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryType Uint32 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryType Uint16 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryType Uint8 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryType IBool Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryType IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryType IFloat Source # 
Instance details

Defined in Ivory.Language.Float

ProcType proc => IvoryType (Def proc) Source # 
Instance details

Defined in Ivory.Language.Proc

Methods

ivoryType :: Proxy (Def proc) -> Type Source #

ProcType proc => IvoryType (ProcPtr proc) Source # 
Instance details

Defined in Ivory.Language.Proc

Methods

ivoryType :: Proxy (ProcPtr proc) -> Type Source #

ANat n => IvoryType (Ix n) Source # 
Instance details

Defined in Ivory.Language.Array

Methods

ivoryType :: Proxy (Ix n) -> Type Source #

IvoryRep (BitRep n) => IvoryType (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

Methods

ivoryType :: Proxy (Bits n) -> Type Source #

(KnownNullability n, KnownConstancy c, IvoryArea a) => IvoryType (Pointer n c s a) Source # 
Instance details

Defined in Ivory.Language.Pointer

Methods

ivoryType :: Proxy (Pointer n c s a) -> Type Source #

class IvoryArea (a :: Area *) Source #

Guard the inhabitants of the Area type, as not all *s are Ivory *s.

Minimal complete definition

ivoryArea

Instances
(IvoryStruct sym, ASymbol sym) => IvoryArea (Struct sym :: Area *) Source # 
Instance details

Defined in Ivory.Language.Struct

Methods

ivoryArea :: Proxy (Struct sym) -> Type Source #

IvoryArea a => IvoryArea (CArray a) Source # 
Instance details

Defined in Ivory.Language.CArray

Methods

ivoryArea :: Proxy (CArray a) -> Type Source #

IvoryType a => IvoryArea (Stored a) Source # 
Instance details

Defined in Ivory.Language.Area

Methods

ivoryArea :: Proxy (Stored a) -> Type Source #

(ANat len, IvoryArea area) => IvoryArea (Array len area) Source # 
Instance details

Defined in Ivory.Language.Area

Methods

ivoryArea :: Proxy (Array len area) -> Type Source #

class IvoryType t => IvoryVar t Source #

Lifting a variable name.

Minimal complete definition

wrapVar, unwrapExpr

Instances
IvoryVar IString Source # 
Instance details

Defined in Ivory.Language.IString

IvoryVar IChar Source # 
Instance details

Defined in Ivory.Language.IChar

IvoryVar Sint64 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryVar Sint32 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryVar Sint16 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryVar Sint8 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryVar Uint64 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryVar Uint32 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryVar Uint16 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryVar Uint8 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryVar IBool Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryVar IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryVar IFloat Source # 
Instance details

Defined in Ivory.Language.Float

ProcType proc => IvoryVar (ProcPtr proc) Source # 
Instance details

Defined in Ivory.Language.Proc

Methods

wrapVar :: Var -> ProcPtr proc Source #

unwrapExpr :: ProcPtr proc -> Expr Source #

ANat n => IvoryVar (Ix n) Source # 
Instance details

Defined in Ivory.Language.Array

Methods

wrapVar :: Var -> Ix n Source #

unwrapExpr :: Ix n -> Expr Source #

IvoryRep (BitRep n) => IvoryVar (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

Methods

wrapVar :: Var -> Bits n Source #

unwrapExpr :: Bits n -> Expr Source #

(KnownNullability n, KnownConstancy c, IvoryArea a) => IvoryVar (Pointer n c s a) Source # 
Instance details

Defined in Ivory.Language.Pointer

Methods

wrapVar :: Var -> Pointer n c s a Source #

unwrapExpr :: Pointer n c s a -> Expr Source #

class IvoryVar t => IvoryExpr t Source #

Unwrapping for Ivory expressions.

Minimal complete definition

wrapExpr

Instances
IvoryExpr IString Source # 
Instance details

Defined in Ivory.Language.IString

IvoryExpr IChar Source # 
Instance details

Defined in Ivory.Language.IChar

Methods

wrapExpr :: Expr -> IChar Source #

IvoryExpr Sint64 Source # 
Instance details

Defined in Ivory.Language.Sint

Methods

wrapExpr :: Expr -> Sint64 Source #

IvoryExpr Sint32 Source # 
Instance details

Defined in Ivory.Language.Sint

Methods

wrapExpr :: Expr -> Sint32 Source #

IvoryExpr Sint16 Source # 
Instance details

Defined in Ivory.Language.Sint

Methods

wrapExpr :: Expr -> Sint16 Source #

IvoryExpr Sint8 Source # 
Instance details

Defined in Ivory.Language.Sint

Methods

wrapExpr :: Expr -> Sint8 Source #

IvoryExpr Uint64 Source # 
Instance details

Defined in Ivory.Language.Uint

Methods

wrapExpr :: Expr -> Uint64 Source #

IvoryExpr Uint32 Source # 
Instance details

Defined in Ivory.Language.Uint

Methods

wrapExpr :: Expr -> Uint32 Source #

IvoryExpr Uint16 Source # 
Instance details

Defined in Ivory.Language.Uint

Methods

wrapExpr :: Expr -> Uint16 Source #

IvoryExpr Uint8 Source # 
Instance details

Defined in Ivory.Language.Uint

Methods

wrapExpr :: Expr -> Uint8 Source #

IvoryExpr IBool Source # 
Instance details

Defined in Ivory.Language.IBool

Methods

wrapExpr :: Expr -> IBool Source #

IvoryExpr IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryExpr IFloat Source # 
Instance details

Defined in Ivory.Language.Float

Methods

wrapExpr :: Expr -> IFloat Source #

ANat n => IvoryExpr (Ix n) Source # 
Instance details

Defined in Ivory.Language.Array

Methods

wrapExpr :: Expr -> Ix n Source #

IvoryRep (BitRep n) => IvoryExpr (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

Methods

wrapExpr :: Expr -> Bits n Source #

(KnownNullability n, KnownConstancy c, IvoryArea a) => IvoryExpr (Pointer n c s a) Source # 
Instance details

Defined in Ivory.Language.Pointer

Methods

wrapExpr :: Expr -> Pointer n c s a Source #

data OpaqueType Source #

An opaque type that can never be implemented.

Instances
IvoryType OpaqueType Source # 
Instance details

Defined in Ivory.Language.Type

Non-null References

class IvoryRef (ref :: RefScope -> Area * -> *) Source #

TODO remove class, leave function only

Minimal complete definition

unwrapRef

Instances
IvoryRef (Pointer Valid c) Source # 
Instance details

Defined in Ivory.Language.Ref

Methods

unwrapRef :: IvoryVar a => Pointer Valid c s (Stored a) -> Expr

class IvoryVar a => IvoryStore a Source #

Things that can be safely stored in references.

Instances
IvoryStore IChar Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryStore Sint64 Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryStore Sint32 Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryStore Sint16 Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryStore Sint8 Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryStore Uint64 Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryStore Uint32 Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryStore Uint16 Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryStore Uint8 Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryStore IBool Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryStore IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryStore IFloat Source # 
Instance details

Defined in Ivory.Language.Float

ANat n => IvoryStore (Ix n) Source # 
Instance details

Defined in Ivory.Language.Array

IvoryRep (BitRep n) => IvoryStore (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

(KnownConstancy c, IvoryArea a) => IvoryStore (Pointer Nullable c Global a) Source # 
Instance details

Defined in Ivory.Language.Ref

type Ref = Pointer Valid Mutable Source #

A non-null pointer to a memory area.

refToPtr :: IvoryArea area => Ref s area -> Ptr s area Source #

Convert valid to nullable pointer. TODO deprecate in favor of pointerCastToNullable

constRef :: IvoryArea area => Ref s area -> ConstRef s area Source #

Turn a reference into a constant reference. TODO deprecate in favor of pointerCastToConst

deref :: forall eff ref s a. (IvoryStore a, IvoryVar a, IvoryVar (ref s (Stored a)), IvoryRef ref) => ref s (Stored a) -> Ivory eff a Source #

Dereferenceing.

store :: forall eff s a. IvoryStore a => Ref s (Stored a) -> a -> Ivory eff () Source #

refCopy :: forall eff sTo ref sFrom a. (IvoryRef ref, IvoryVar (Ref sTo a), IvoryVar (ref sFrom a), IvoryArea a) => Ref sTo a -> ref sFrom a -> Ivory eff () Source #

Memory copy. Emits an assertion that the two references are unequal.

refZero :: forall eff s a. (IvoryZero a, IvoryArea a) => Ref s a -> Ivory eff () Source #

Zero the memory pointed to by this reference, as long as it could have been created with a zero initializer.

Stack Allocation

class IvoryVar e => IvoryInit e where Source #

Initializers for Stored things.

Methods

ival :: e -> Init (Stored e) Source #

Instances
IvoryInit IChar Source # 
Instance details

Defined in Ivory.Language.Init

Methods

ival :: IChar -> Init (Stored IChar) Source #

IvoryInit Sint64 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit Sint32 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit Sint16 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit Sint8 Source # 
Instance details

Defined in Ivory.Language.Init

Methods

ival :: Sint8 -> Init (Stored Sint8) Source #

IvoryInit Uint64 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit Uint32 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit Uint16 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit Uint8 Source # 
Instance details

Defined in Ivory.Language.Init

Methods

ival :: Uint8 -> Init (Stored Uint8) Source #

IvoryInit IBool Source # 
Instance details

Defined in Ivory.Language.Init

Methods

ival :: IBool -> Init (Stored IBool) Source #

IvoryInit IDouble Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit IFloat Source # 
Instance details

Defined in Ivory.Language.Init

ProcType proc => IvoryInit (ProcPtr proc) Source # 
Instance details

Defined in Ivory.Language.Init

Methods

ival :: ProcPtr proc -> Init (Stored (ProcPtr proc)) Source #

ANat len => IvoryInit (Ix len) Source # 
Instance details

Defined in Ivory.Language.Init

Methods

ival :: Ix len -> Init (Stored (Ix len)) Source #

IvoryRep (BitRep n) => IvoryInit (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

Methods

ival :: Bits n -> Init (Stored (Bits n)) Source #

IvoryArea area => IvoryInit (Ptr Global area) Source # 
Instance details

Defined in Ivory.Language.Init

Methods

ival :: Ptr Global area -> Init (Stored (Ptr Global area)) Source #

data Init (area :: Area *) Source #

class IvoryVar a => IvoryZeroVal a where Source #

Minimal complete definition

izeroval

Methods

izeroval :: Init (Stored a) Source #

Instances
IvoryZeroVal IChar Source # 
Instance details

Defined in Ivory.Language.Init

IvoryZeroVal Sint64 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryZeroVal Sint32 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryZeroVal Sint16 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryZeroVal Sint8 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryZeroVal Uint64 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryZeroVal Uint32 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryZeroVal Uint16 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryZeroVal Uint8 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryZeroVal IBool Source # 
Instance details

Defined in Ivory.Language.Init

IvoryZeroVal IDouble Source # 
Instance details

Defined in Ivory.Language.Init

IvoryZeroVal IFloat Source # 
Instance details

Defined in Ivory.Language.Init

ANat n => IvoryZeroVal (Ix n) Source # 
Instance details

Defined in Ivory.Language.Init

Methods

izeroval :: Init (Stored (Ix n)) Source #

IvoryRep (BitRep n) => IvoryZeroVal (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

Methods

izeroval :: Init (Stored (Bits n)) Source #

IvoryArea area => IvoryZeroVal (Ptr Global area) Source # 
Instance details

Defined in Ivory.Language.Init

Methods

izeroval :: Init (Stored (Ptr Global area)) Source #

class IvoryZero (area :: Area *) where Source #

Zero initializers. The semantics of Ivory is that initializers must be compatible with C semantics of initializing to 0 for globals in .bss.

Minimal complete definition

izero

Methods

izero :: Init area Source #

Instances
IvoryStruct sym => IvoryZero (Struct sym :: Area *) Source # 
Instance details

Defined in Ivory.Language.Init

Methods

izero :: Init (Struct sym) Source #

IvoryZeroVal a => IvoryZero (Stored a) Source # 
Instance details

Defined in Ivory.Language.Init

Methods

izero :: Init (Stored a) Source #

(IvoryZero area, IvoryArea area, ANat len) => IvoryZero (Array len area) Source # 
Instance details

Defined in Ivory.Language.Init

Methods

izero :: Init (Array len area) Source #

iarray :: forall len area. (IvoryArea area, ANat len) => [Init area] -> Init (Array len area) Source #

data InitStruct (sym :: Symbol) Source #

Instances
IvoryStruct sym => Semigroup (InitStruct sym) Source # 
Instance details

Defined in Ivory.Language.Init

Methods

(<>) :: InitStruct sym -> InitStruct sym -> InitStruct sym #

sconcat :: NonEmpty (InitStruct sym) -> InitStruct sym #

stimes :: Integral b => b -> InitStruct sym -> InitStruct sym #

IvoryStruct sym => Monoid (InitStruct sym) Source # 
Instance details

Defined in Ivory.Language.Init

Methods

mempty :: InitStruct sym #

mappend :: InitStruct sym -> InitStruct sym -> InitStruct sym #

mconcat :: [InitStruct sym] -> InitStruct sym #

(.=) :: Label sym area -> Init area -> InitStruct sym Source #

istruct :: forall sym. IvoryStruct sym => [InitStruct sym] -> Init (Struct sym) Source #

local :: forall eff s area. (IvoryArea area, GetAlloc eff ~ Scope s) => Init area -> Ivory eff (Ref (Stack s) area) Source #

Stack allocation

SizeOf

class IvorySizeOf (t :: Area *) Source #

Instances
IvorySizeOf (Struct sym :: Area *) Source # 
Instance details

Defined in Ivory.Language.SizeOf

IvoryType area => IvorySizeOf (Stored area) Source # 
Instance details

Defined in Ivory.Language.SizeOf

(ANat len, IvorySizeOf area) => IvorySizeOf (Array len area) Source # 
Instance details

Defined in Ivory.Language.SizeOf

sizeOf :: (IvoryArea t, IvorySizeOf t, IvoryExpr a, Num a) => Proxy t -> a Source #

Get the size of an ivory type.

Nullable Pointers

type Ptr = Pointer Nullable Mutable Source #

Pointers (nullable references).

Booleans

data IBool Source #

Instances
IvoryExpr IBool Source # 
Instance details

Defined in Ivory.Language.IBool

Methods

wrapExpr :: Expr -> IBool Source #

IvoryVar IBool Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryType IBool Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd IBool Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq IBool Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryStore IBool Source # 
Instance details

Defined in Ivory.Language.Ref

Ensures IBool Source # 
Instance details

Defined in Ivory.Language.Cond

Methods

ensures :: (WrapIvory m, IvoryVar r) => (r -> IBool) -> m r -> m r Source #

ensures_ :: WrapIvory m => IBool -> m () -> m () Source #

Requires IBool Source # 
Instance details

Defined in Ivory.Language.Cond

Methods

requires :: (WrapIvory m, IvoryType r) => IBool -> m r -> m r Source #

CheckStored IBool Source # 
Instance details

Defined in Ivory.Language.Cond

Methods

checkStored :: (IvoryVar a, IvoryRef ref, IvoryVar (ref s (Stored a))) => ref s (Stored a) -> (a -> IBool) -> Cond Source #

IvoryZeroVal IBool Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit IBool Source # 
Instance details

Defined in Ivory.Language.Init

Methods

ival :: IBool -> Init (Stored IBool) Source #

SafeCast IBool IChar Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: IBool -> IChar Source #

SafeCast IBool Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Sint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Sint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: IBool -> Sint8 Source #

SafeCast IBool Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Uint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Uint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Uint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: IBool -> Uint8 Source #

SafeCast IBool IBool Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: IBool -> IBool Source #

SafeCast IBool IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

Characters

data IChar Source #

Instances
IvoryExpr IChar Source # 
Instance details

Defined in Ivory.Language.IChar

Methods

wrapExpr :: Expr -> IChar Source #

IvoryVar IChar Source # 
Instance details

Defined in Ivory.Language.IChar

IvoryType IChar Source # 
Instance details

Defined in Ivory.Language.IChar

IvoryStore IChar Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryZeroVal IChar Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit IChar Source # 
Instance details

Defined in Ivory.Language.Init

Methods

ival :: IChar -> Init (Stored IChar) Source #

SafeCast IChar IChar Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: IChar -> IChar Source #

SafeCast IBool IChar Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: IBool -> IChar Source #

Constant strings

data IString Source #

Instances
IsString IString Source # 
Instance details

Defined in Ivory.Language.IString

Methods

fromString :: String -> IString #

IvoryExpr IString Source # 
Instance details

Defined in Ivory.Language.IString

IvoryVar IString Source # 
Instance details

Defined in Ivory.Language.IString

IvoryType IString Source # 
Instance details

Defined in Ivory.Language.IString

Dynamic bounded-length strings

class (ANat (Capacity a), IvoryStruct (StructName a), IvoryArea a, a ~ Struct (StructName a)) => IvoryString a where Source #

Minimal complete definition

stringDataL, stringLengthL

Associated Types

type Capacity a :: Nat Source #

Signed Integers

data Sint8 Source #

8-bit integers.

Instances
Bounded Sint8 Source # 
Instance details

Defined in Ivory.Language.Sint

Num Sint8 Source # 
Instance details

Defined in Ivory.Language.Sint

Show Sint8 Source # 
Instance details

Defined in Ivory.Language.Sint

Methods

showsPrec :: Int -> Sint8 -> ShowS #

show :: Sint8 -> String #

showList :: [Sint8] -> ShowS #

IvoryExpr Sint8 Source # 
Instance details

Defined in Ivory.Language.Sint

Methods

wrapExpr :: Expr -> Sint8 Source #

IvoryVar Sint8 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryType Sint8 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryOrd Sint8 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Sint8 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryStore Sint8 Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryIntegral Sint8 Source # 
Instance details

Defined in Ivory.Language.IIntegral

Methods

iDiv :: Sint8 -> Sint8 -> Sint8 Source #

(.%) :: Sint8 -> Sint8 -> Sint8 Source #

Default Sint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: Sint8

IvoryZeroVal Sint8 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit Sint8 Source # 
Instance details

Defined in Ivory.Language.Init

Methods

ival :: Sint8 -> Init (Stored Sint8) Source #

SignCast Sint8 Uint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

signCast :: Sint8 -> Uint8 Source #

SignCast Uint8 Sint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

signCast :: Uint8 -> Sint8 Source #

SafeCast Sint8 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint8 Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint8 Sint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint8 Sint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: Sint8 -> Sint8 Source #

SafeCast Sint8 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint8 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Sint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: IBool -> Sint8 Source #

TwosComplementCast Uint8 Sint8 Source # 
Instance details

Defined in Ivory.Language.Bits

data Sint16 Source #

16-bit integers.

Instances
Bounded Sint16 Source # 
Instance details

Defined in Ivory.Language.Sint

Num Sint16 Source # 
Instance details

Defined in Ivory.Language.Sint

Show Sint16 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryExpr Sint16 Source # 
Instance details

Defined in Ivory.Language.Sint

Methods

wrapExpr :: Expr -> Sint16 Source #

IvoryVar Sint16 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryType Sint16 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryOrd Sint16 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Sint16 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryStore Sint16 Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryIntegral Sint16 Source # 
Instance details

Defined in Ivory.Language.IIntegral

Default Sint16 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: Sint16

IvoryZeroVal Sint16 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit Sint16 Source # 
Instance details

Defined in Ivory.Language.Init

SignCast Sint16 Uint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SignCast Uint16 Sint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint16 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint16 Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint16 Sint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint16 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint16 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint8 Sint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Sint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Sint16 Source # 
Instance details

Defined in Ivory.Language.Cast

TwosComplementCast Uint16 Sint16 Source # 
Instance details

Defined in Ivory.Language.Bits

data Sint32 Source #

32-bit integers.

Instances
Bounded Sint32 Source # 
Instance details

Defined in Ivory.Language.Sint

Num Sint32 Source # 
Instance details

Defined in Ivory.Language.Sint

Show Sint32 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryExpr Sint32 Source # 
Instance details

Defined in Ivory.Language.Sint

Methods

wrapExpr :: Expr -> Sint32 Source #

IvoryVar Sint32 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryType Sint32 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryOrd Sint32 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Sint32 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryStore Sint32 Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryIntegral Sint32 Source # 
Instance details

Defined in Ivory.Language.IIntegral

Default Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: Sint32

IvoryZeroVal Sint32 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit Sint32 Source # 
Instance details

Defined in Ivory.Language.Init

SignCast Sint32 Uint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SignCast Uint32 Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint32 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint32 Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint32 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint32 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint16 Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint8 Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

TwosComplementCast Uint32 Sint32 Source # 
Instance details

Defined in Ivory.Language.Bits

data Sint64 Source #

64-bit integers.

Instances
Bounded Sint64 Source # 
Instance details

Defined in Ivory.Language.Sint

Num Sint64 Source # 
Instance details

Defined in Ivory.Language.Sint

Show Sint64 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryExpr Sint64 Source # 
Instance details

Defined in Ivory.Language.Sint

Methods

wrapExpr :: Expr -> Sint64 Source #

IvoryVar Sint64 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryType Sint64 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryOrd Sint64 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Sint64 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryStore Sint64 Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryIntegral Sint64 Source # 
Instance details

Defined in Ivory.Language.IIntegral

Default Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: Sint64

IvoryZeroVal Sint64 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit Sint64 Source # 
Instance details

Defined in Ivory.Language.Init

SignCast Sint64 Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SignCast Uint64 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint64 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint64 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint32 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint16 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint8 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint32 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

TwosComplementCast Uint64 Sint64 Source # 
Instance details

Defined in Ivory.Language.Bits

Unsigned Integers

data Uint8 Source #

8-bit words.

Instances
Bounded Uint8 Source # 
Instance details

Defined in Ivory.Language.Uint

Num Uint8 Source # 
Instance details

Defined in Ivory.Language.Uint

Show Uint8 Source # 
Instance details

Defined in Ivory.Language.Uint

Methods

showsPrec :: Int -> Uint8 -> ShowS #

show :: Uint8 -> String #

showList :: [Uint8] -> ShowS #

IvoryExpr Uint8 Source # 
Instance details

Defined in Ivory.Language.Uint

Methods

wrapExpr :: Expr -> Uint8 Source #

IvoryVar Uint8 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryType Uint8 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryOrd Uint8 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Uint8 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryStore Uint8 Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryIntegral Uint8 Source # 
Instance details

Defined in Ivory.Language.IIntegral

Methods

iDiv :: Uint8 -> Uint8 -> Uint8 Source #

(.%) :: Uint8 -> Uint8 -> Uint8 Source #

Default Uint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: Uint8

IvoryZeroVal Uint8 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit Uint8 Source # 
Instance details

Defined in Ivory.Language.Init

Methods

ival :: Uint8 -> Init (Stored Uint8) Source #

IvoryBits Uint8 Source # 
Instance details

Defined in Ivory.Language.Bits

SignCast Sint8 Uint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

signCast :: Sint8 -> Uint8 Source #

SignCast Uint8 Sint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

signCast :: Uint8 -> Sint8 Source #

SafeCast Uint8 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Sint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Uint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Uint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Uint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: Uint8 -> Uint8 Source #

SafeCast Uint8 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Uint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: IBool -> Uint8 Source #

TwosComplementCast Uint8 Sint8 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint64 Uint8 Source # 
Instance details

Defined in Ivory.Language.Bits

Methods

bitCast :: Uint64 -> Uint8 Source #

BitCast Uint32 Uint8 Source # 
Instance details

Defined in Ivory.Language.Bits

Methods

bitCast :: Uint32 -> Uint8 Source #

BitCast Uint16 Uint8 Source # 
Instance details

Defined in Ivory.Language.Bits

Methods

bitCast :: Uint16 -> Uint8 Source #

BitCast Uint8 Uint8 Source # 
Instance details

Defined in Ivory.Language.Bits

Methods

bitCast :: Uint8 -> Uint8 Source #

BitSplit Uint16 Uint8 Source # 
Instance details

Defined in Ivory.Language.Bits

data Uint16 Source #

16-bit words.

Instances
Bounded Uint16 Source # 
Instance details

Defined in Ivory.Language.Uint

Num Uint16 Source # 
Instance details

Defined in Ivory.Language.Uint

Show Uint16 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryExpr Uint16 Source # 
Instance details

Defined in Ivory.Language.Uint

Methods

wrapExpr :: Expr -> Uint16 Source #

IvoryVar Uint16 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryType Uint16 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryOrd Uint16 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Uint16 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryStore Uint16 Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryIntegral Uint16 Source # 
Instance details

Defined in Ivory.Language.IIntegral

Default Uint16 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: Uint16

IvoryZeroVal Uint16 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit Uint16 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryBits Uint16 Source # 
Instance details

Defined in Ivory.Language.Bits

SignCast Sint16 Uint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SignCast Uint16 Sint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 Uint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 Uint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Uint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Uint16 Source # 
Instance details

Defined in Ivory.Language.Cast

TwosComplementCast Uint16 Sint16 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint64 Uint16 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint32 Uint16 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint16 Uint16 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint16 Uint8 Source # 
Instance details

Defined in Ivory.Language.Bits

Methods

bitCast :: Uint16 -> Uint8 Source #

BitSplit Uint32 Uint16 Source # 
Instance details

Defined in Ivory.Language.Bits

BitSplit Uint16 Uint8 Source # 
Instance details

Defined in Ivory.Language.Bits

data Uint32 Source #

32-bit words.

Instances
Bounded Uint32 Source # 
Instance details

Defined in Ivory.Language.Uint

Num Uint32 Source # 
Instance details

Defined in Ivory.Language.Uint

Show Uint32 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryExpr Uint32 Source # 
Instance details

Defined in Ivory.Language.Uint

Methods

wrapExpr :: Expr -> Uint32 Source #

IvoryVar Uint32 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryType Uint32 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryOrd Uint32 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Uint32 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryStore Uint32 Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryIntegral Uint32 Source # 
Instance details

Defined in Ivory.Language.IIntegral

Default Uint32 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: Uint32

IvoryZeroVal Uint32 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit Uint32 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryBits Uint32 Source # 
Instance details

Defined in Ivory.Language.Bits

SignCast Sint32 Uint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SignCast Uint32 Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint32 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint32 Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint32 Uint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint32 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint32 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 Uint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Uint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Uint32 Source # 
Instance details

Defined in Ivory.Language.Cast

TwosComplementCast Uint32 Sint32 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint64 Uint32 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint32 Uint32 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint32 Uint16 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint32 Uint8 Source # 
Instance details

Defined in Ivory.Language.Bits

Methods

bitCast :: Uint32 -> Uint8 Source #

BitSplit Uint64 Uint32 Source # 
Instance details

Defined in Ivory.Language.Bits

BitSplit Uint32 Uint16 Source # 
Instance details

Defined in Ivory.Language.Bits

data Uint64 Source #

64-bit words.

Instances
Bounded Uint64 Source # 
Instance details

Defined in Ivory.Language.Uint

Num Uint64 Source # 
Instance details

Defined in Ivory.Language.Uint

Show Uint64 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryExpr Uint64 Source # 
Instance details

Defined in Ivory.Language.Uint

Methods

wrapExpr :: Expr -> Uint64 Source #

IvoryVar Uint64 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryType Uint64 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryOrd Uint64 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Uint64 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryStore Uint64 Source # 
Instance details

Defined in Ivory.Language.Ref

IvoryIntegral Uint64 Source # 
Instance details

Defined in Ivory.Language.IIntegral

Default Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: Uint64

IvoryZeroVal Uint64 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit Uint64 Source # 
Instance details

Defined in Ivory.Language.Init

IvoryBits Uint64 Source # 
Instance details

Defined in Ivory.Language.Bits

SignCast Sint64 Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SignCast Uint64 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint64 Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint64 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint32 Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

TwosComplementCast Uint64 Sint64 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint64 Uint64 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint64 Uint32 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint64 Uint16 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint64 Uint8 Source # 
Instance details

Defined in Ivory.Language.Bits

Methods

bitCast :: Uint64 -> Uint8 Source #

BitSplit Uint64 Uint32 Source # 
Instance details

Defined in Ivory.Language.Bits

Floating-point Numbers

data IFloat Source #

Instances
Floating IFloat Source # 
Instance details

Defined in Ivory.Language.Float

Fractional IFloat Source # 
Instance details

Defined in Ivory.Language.Float

Num IFloat Source # 
Instance details

Defined in Ivory.Language.Float

IvoryExpr IFloat Source # 
Instance details

Defined in Ivory.Language.Float

Methods

wrapExpr :: Expr -> IFloat Source #

IvoryVar IFloat Source # 
Instance details

Defined in Ivory.Language.Float

IvoryType IFloat Source # 
Instance details

Defined in Ivory.Language.Float

IvoryOrd IFloat Source # 
Instance details

Defined in Ivory.Language.Float

IvoryEq IFloat Source # 
Instance details

Defined in Ivory.Language.Float

IvoryStore IFloat Source # 
Instance details

Defined in Ivory.Language.Float

IvoryFloat IFloat Source # 
Instance details

Defined in Ivory.Language.Float

Default IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: IFloat

IvoryZeroVal IFloat Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit IFloat Source # 
Instance details

Defined in Ivory.Language.Init

(Default to, Bounded to, IvoryIntegral to, SafeCast to IFloat) => RuntimeCast IFloat to Source #

Casting from a floating to a Integral type always results in truncation.

Instance details

Defined in Ivory.Language.Cast

Methods

inBounds :: to -> IFloat -> IBool

SafeCast Sint32 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint16 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint8 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint32 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IFloat IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IFloat IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

data IDouble Source #

Instances
Floating IDouble Source # 
Instance details

Defined in Ivory.Language.Float

Fractional IDouble Source # 
Instance details

Defined in Ivory.Language.Float

Num IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryExpr IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryVar IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryType IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryOrd IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryEq IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryStore IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryFloat IDouble Source # 
Instance details

Defined in Ivory.Language.Float

Default IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

IvoryZeroVal IDouble Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit IDouble Source # 
Instance details

Defined in Ivory.Language.Init

(Default to, Bounded to, IvoryIntegral to, SafeCast to IDouble) => RuntimeCast IDouble to Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

inBounds :: to -> IDouble -> IBool

SafeCast Sint64 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint32 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint16 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint8 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint64 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint32 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IDouble IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IFloat IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

isnan :: forall a. (IvoryVar a, Floating a) => a -> IBool Source #

NaN testing.

isinf :: forall a. (IvoryVar a, Floating a) => a -> IBool Source #

Infinite testing.

roundF :: IvoryFloat a => a -> a Source #

Round a floating point number.

ceilF :: IvoryFloat a => a -> a Source #

Take the ceiling of a floating point number.

floorF :: IvoryFloat a => a -> a Source #

Take the floor of a floating point number.

atan2F :: IvoryFloat a => a -> a -> a Source #

The arctangent function of two arguments.

Effects

data Effects Source #

The effect context for Ivory operations.

data BreakEff Source #

Loop break effect.

Constructors

Break 
NoBreak 

type family GetBreaks (effs :: Effects) :: BreakEff Source #

Retrieve any Breaks effect present.

Instances
type GetBreaks (Effects r b a) Source # 
Instance details

Defined in Ivory.Language.Effects

type GetBreaks (Effects r b a) = b

type family AllowBreak (effs :: Effects) :: Effects Source #

Add the Break effect into an effect context.

Instances
type AllowBreak (Effects r b a) Source # 
Instance details

Defined in Ivory.Language.Effects

type AllowBreak (Effects r b a) = Effects r Break a

type family ClearBreak (effs :: Effects) :: Effects Source #

Remove any Break effect present.

Instances
type ClearBreak (Effects r b a) Source # 
Instance details

Defined in Ivory.Language.Effects

type ClearBreak (Effects r b a) = Effects r NoBreak a

noBreak :: Ivory (ClearBreak eff) a -> Ivory eff a Source #

data ReturnEff Source #

Function return effect.

Constructors

Returns t 
NoReturn 

type family GetReturn (effs :: Effects) :: ReturnEff Source #

Retrieve any Return effect present.

Instances
type GetReturn (Effects r b a) Source # 
Instance details

Defined in Ivory.Language.Effects

type GetReturn (Effects r b a) = r

type family ClearReturn (effs :: Effects) :: Effects Source #

Remove any Return effects present.

Instances
type ClearReturn (Effects r b a) Source # 
Instance details

Defined in Ivory.Language.Effects

type ClearReturn (Effects r b a) = Effects NoReturn b a

noReturn :: Ivory (ClearReturn eff) a -> Ivory eff a Source #

data AllocEff Source #

Stack allocation effect.

Constructors

Scope s 
NoAlloc 

type family GetAlloc (effs :: Effects) :: AllocEff Source #

Retrieve the current allocation effect.

Instances
type GetAlloc (Effects r b a) Source # 
Instance details

Defined in Ivory.Language.Effects

type GetAlloc (Effects r b a) = a

type family ClearAlloc (effs :: Effects) :: Effects Source #

Remove any allocation effect currently present.

Instances
type ClearAlloc (Effects r b a) Source # 
Instance details

Defined in Ivory.Language.Effects

type ClearAlloc (Effects r b a) = Effects r b NoAlloc

noAlloc :: innerEff ~ ClearAlloc outerEff => Ivory innerEff a -> Ivory outerEff a Source #

Language

Monadic Interface

data Ivory (eff :: Effects) a Source #

Instances
Monad (Ivory eff) Source # 
Instance details

Defined in Ivory.Language.Monad

Methods

(>>=) :: Ivory eff a -> (a -> Ivory eff b) -> Ivory eff b #

(>>) :: Ivory eff a -> Ivory eff b -> Ivory eff b #

return :: a -> Ivory eff a #

fail :: String -> Ivory eff a #

Functor (Ivory eff) Source # 
Instance details

Defined in Ivory.Language.Monad

Methods

fmap :: (a -> b) -> Ivory eff a -> Ivory eff b #

(<$) :: a -> Ivory eff b -> Ivory eff a #

Applicative (Ivory eff) Source # 
Instance details

Defined in Ivory.Language.Monad

Methods

pure :: a -> Ivory eff a #

(<*>) :: Ivory eff (a -> b) -> Ivory eff a -> Ivory eff b #

liftA2 :: (a -> b -> c) -> Ivory eff a -> Ivory eff b -> Ivory eff c #

(*>) :: Ivory eff a -> Ivory eff b -> Ivory eff b #

(<*) :: Ivory eff a -> Ivory eff b -> Ivory eff a #

FreshName (Ivory eff) Source # 
Instance details

Defined in Ivory.Language.Init

Methods

freshName :: String -> Ivory eff Var Source #

IvoryType r => IvoryCall_ (([] :: [*]) :-> r) eff (Ivory eff ()) Source # 
Instance details

Defined in Ivory.Language.Proc

Methods

callAux_ :: Name -> Proxy ([] :-> r) -> [Typed Expr] -> Ivory eff () Source #

IvoryVar r => IvoryCall (([] :: [*]) :-> r) eff (Ivory eff r) Source # 
Instance details

Defined in Ivory.Language.Proc

Methods

callAux :: Name -> Proxy ([] :-> r) -> [Typed Expr] -> Ivory eff r Source #

data RefScope Source #

Definition scopes for values.

Constructors

Global

Globally allocated

Stack s

Stack allocated

Subexpression naming

assign :: forall eff a. IvoryExpr a => a -> Ivory eff a Source #

Sub-expression naming.

Constants

extern :: forall t. IvoryExpr t => Sym -> String -> t Source #

Import an externally defined constant by providing a global name.

inclSym :: IvoryExpr t => t -> ModuleDef Source #

Import an externally-defined symbol.

Arithmetic (operators from the Num class are also provided).

class (IvoryExpr a, IvoryOrd a, Num a) => IvoryIntegral a where Source #

Integral, without the baggage from Haskell (i.e., supertypes of Real and Enum). Defines Euclidian division (rather than truncated division). See http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.74.8522. Notable properties, beyond the normal div/rem properties, are that

The remainder is always non-negative. For d1 < 0, d0 iDiv (-d1) == -(d0 iDiv d1). For d1 < 0, d0 .% (-d1) == d0 .% d1.

N.B. mod and rem are equal if both args are positive, and C has no mod operator (only rem). In Haskell and C, both mod and rem may return negative values. Furthermore, before C99, the result of rem is implementation-defined.

Methods

iDiv :: a -> a -> a Source #

Euclidean division.

(.%) :: a -> a -> a Source #

Euclidean remainder.

(./) :: IvoryIntegral a => a -> a -> a Source #

Comparisons

class IvoryExpr a => IvoryEq a where Source #

Methods

(==?) :: a -> a -> IBool infix 4 Source #

(/=?) :: a -> a -> IBool infix 4 Source #

Instances
IvoryEq Sint64 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Sint32 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Sint16 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Sint8 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Uint64 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Uint32 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Uint16 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Uint8 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq IBool Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryEq IFloat Source # 
Instance details

Defined in Ivory.Language.Float

ANat n => IvoryEq (Ix n) Source # 
Instance details

Defined in Ivory.Language.Array

Methods

(==?) :: Ix n -> Ix n -> IBool Source #

(/=?) :: Ix n -> Ix n -> IBool Source #

IvoryRep (BitRep n) => IvoryEq (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

Methods

(==?) :: Bits n -> Bits n -> IBool Source #

(/=?) :: Bits n -> Bits n -> IBool Source #

(KnownNullability n, KnownConstancy c, IvoryArea a) => IvoryEq (Pointer n c s a) Source # 
Instance details

Defined in Ivory.Language.Pointer

Methods

(==?) :: Pointer n c s a -> Pointer n c s a -> IBool Source #

(/=?) :: Pointer n c s a -> Pointer n c s a -> IBool Source #

class IvoryEq a => IvoryOrd a where Source #

Methods

(>?) :: a -> a -> IBool infix 4 Source #

(>=?) :: a -> a -> IBool infix 4 Source #

(<?) :: a -> a -> IBool infix 4 Source #

(<=?) :: a -> a -> IBool infix 4 Source #

Instances
IvoryOrd Sint64 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd Sint32 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd Sint16 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd Sint8 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd Uint64 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd Uint32 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd Uint16 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd Uint8 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd IBool Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryOrd IFloat Source # 
Instance details

Defined in Ivory.Language.Float

ANat n => IvoryOrd (Ix n) Source # 
Instance details

Defined in Ivory.Language.Array

Methods

(>?) :: Ix n -> Ix n -> IBool Source #

(>=?) :: Ix n -> Ix n -> IBool Source #

(<?) :: Ix n -> Ix n -> IBool Source #

(<=?) :: Ix n -> Ix n -> IBool Source #

Boolean operators

(.&&) :: IBool -> IBool -> IBool infixr 3 Source #

(.||) :: IBool -> IBool -> IBool infixr 2 Source #

Bit operators

class (Num a, IvoryExpr a) => IvoryBits a where Source #

Minimal complete definition

iBitSize

Methods

(.&) :: a -> a -> a Source #

(.|) :: a -> a -> a Source #

(.^) :: a -> a -> a Source #

iComplement :: a -> a Source #

iBitSize :: a -> Int Source #

iShiftL :: a -> a -> a Source #

iShiftR :: a -> a -> a Source #

extractByte :: BitCast a Uint8 => a -> (Uint8, a) Source #

Extract the least significant byte from an integer. This returns the two values (x & 0xFF, x >> 8), with the first value safely casted to an 8-bit integer.

This is convenient to use with a state monad and "sets", such as:

fst $ runState x $ do
  a <- sets extractByte
  b <- sets extractByte
  return (a, b)

class (IvoryBits a, IvoryBits b) => BitSplit a b | a -> b where Source #

Extraction of the upper or lower half of a bit type into the next smallest bit type.

Minimal complete definition

ubits, lbits

Methods

ubits :: a -> b Source #

lbits :: a -> b Source #

Instances
BitSplit Uint64 Uint32 Source # 
Instance details

Defined in Ivory.Language.Bits

BitSplit Uint32 Uint16 Source # 
Instance details

Defined in Ivory.Language.Bits

BitSplit Uint16 Uint8 Source # 
Instance details

Defined in Ivory.Language.Bits

class (IvoryBits a, IvoryBits b) => BitCast a b where Source #

A narrowing cast from one bit type to another. This explicitly discards the upper bits of the input value to return a smaller type, and is only defined for unsigned integers.

Minimal complete definition

bitCast

Methods

bitCast :: a -> b Source #

Instances
BitCast Uint64 Uint64 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint64 Uint32 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint64 Uint16 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint64 Uint8 Source # 
Instance details

Defined in Ivory.Language.Bits

Methods

bitCast :: Uint64 -> Uint8 Source #

BitCast Uint32 Uint32 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint32 Uint16 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint32 Uint8 Source # 
Instance details

Defined in Ivory.Language.Bits

Methods

bitCast :: Uint32 -> Uint8 Source #

BitCast Uint16 Uint16 Source # 
Instance details

Defined in Ivory.Language.Bits

BitCast Uint16 Uint8 Source # 
Instance details

Defined in Ivory.Language.Bits

Methods

bitCast :: Uint16 -> Uint8 Source #

BitCast Uint8 Uint8 Source # 
Instance details

Defined in Ivory.Language.Bits

Methods

bitCast :: Uint8 -> Uint8 Source #

class (IvoryBits unsigned, IvoryEq unsigned, IvoryExpr signed, Num signed, IvoryIntegral unsigned, Bounded unsigned, Bounded signed, IvoryOrd signed) => TwosComplementCast unsigned signed | signed -> unsigned, unsigned -> signed where Source #

Re-interpret the bits of an unsigned integer as though they were a signed number in two's complement representation.

Methods

twosComplementCast :: unsigned -> signed Source #

twosComplementRep :: signed -> unsigned Source #

Bit data

bit types

data Bits (n :: Nat) Source #

A wrapper for an Ivory type that can hold an "n" bit unsigned integer.

Instances
IvoryRep (BitRep n) => IvoryExpr (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

Methods

wrapExpr :: Expr -> Bits n Source #

IvoryRep (BitRep n) => IvoryVar (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

Methods

wrapVar :: Var -> Bits n Source #

unwrapExpr :: Bits n -> Expr Source #

IvoryRep (BitRep n) => IvoryType (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

Methods

ivoryType :: Proxy (Bits n) -> Type Source #

IvoryRep (BitRep n) => IvoryEq (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

Methods

(==?) :: Bits n -> Bits n -> IBool Source #

(/=?) :: Bits n -> Bits n -> IBool Source #

IvoryRep (BitRep n) => IvoryStore (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

IvoryRep (BitRep n) => IvoryZeroVal (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

Methods

izeroval :: Init (Stored (Bits n)) Source #

IvoryRep (BitRep n) => IvoryInit (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

Methods

ival :: Bits n -> Init (Stored (Bits n)) Source #

(ANat n, IvoryRep (BitRep n)) => BitData (Bits n) Source #

Identity instance of BitData for the base "Bits n" type.

Instance details

Defined in Ivory.Language.BitData.BitData

Associated Types

type BitType (Bits n) :: * Source #

Methods

toBits :: Bits n -> BitType (Bits n) Source #

fromBits :: BitType (Bits n) -> Bits n Source #

type BitSize (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitSize (Bits n) = n
type BitType (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.BitData

type BitType (Bits n) = Bits n

type Bit = Bits 1 Source #

Bit is a type alias for "Bits 1".

data BitArray (n :: Nat) a Source #

An array of "n" bit data elements of type "a".

Instances
(ANat n, ANat (ArraySize n a), BitData a, IvoryRep (BitRep (ArraySize n a))) => BitData (BitArray n a) Source # 
Instance details

Defined in Ivory.Language.BitData.Array

Associated Types

type BitType (BitArray n a) :: * Source #

type BitType (BitArray n a) Source # 
Instance details

Defined in Ivory.Language.BitData.Array

type BitType (BitArray n a) = Bits (ArraySize n a)

type family BitRep (n :: Nat) :: * Source #

Type function: "BitRep (n :: Nat)" returns an Ivory type given a bit size as a type-level natural. Instances of this type family for bits [1..64] are generated using Template Haskell.

Instances
type BitRep 1 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 1 = Uint8
type BitRep 2 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 2 = Uint8
type BitRep 3 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 3 = Uint8
type BitRep 4 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 4 = Uint8
type BitRep 5 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 5 = Uint8
type BitRep 6 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 6 = Uint8
type BitRep 7 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 7 = Uint8
type BitRep 8 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 8 = Uint8
type BitRep 9 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 9 = Uint16
type BitRep 10 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 10 = Uint16
type BitRep 11 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 11 = Uint16
type BitRep 12 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 12 = Uint16
type BitRep 13 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 13 = Uint16
type BitRep 14 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 14 = Uint16
type BitRep 15 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 15 = Uint16
type BitRep 16 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 16 = Uint16
type BitRep 17 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 17 = Uint32
type BitRep 18 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 18 = Uint32
type BitRep 19 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 19 = Uint32
type BitRep 20 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 20 = Uint32
type BitRep 21 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 21 = Uint32
type BitRep 22 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 22 = Uint32
type BitRep 23 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 23 = Uint32
type BitRep 24 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 24 = Uint32
type BitRep 25 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 25 = Uint32
type BitRep 26 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 26 = Uint32
type BitRep 27 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 27 = Uint32
type BitRep 28 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 28 = Uint32
type BitRep 29 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 29 = Uint32
type BitRep 30 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 30 = Uint32
type BitRep 31 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 31 = Uint32
type BitRep 32 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 32 = Uint32
type BitRep 33 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 33 = Uint64
type BitRep 34 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 34 = Uint64
type BitRep 35 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 35 = Uint64
type BitRep 36 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 36 = Uint64
type BitRep 37 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 37 = Uint64
type BitRep 38 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 38 = Uint64
type BitRep 39 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 39 = Uint64
type BitRep 40 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 40 = Uint64
type BitRep 41 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 41 = Uint64
type BitRep 42 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 42 = Uint64
type BitRep 43 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 43 = Uint64
type BitRep 44 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 44 = Uint64
type BitRep 45 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 45 = Uint64
type BitRep 46 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 46 = Uint64
type BitRep 47 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 47 = Uint64
type BitRep 48 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 48 = Uint64
type BitRep 49 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 49 = Uint64
type BitRep 50 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 50 = Uint64
type BitRep 51 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 51 = Uint64
type BitRep 52 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 52 = Uint64
type BitRep 53 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 53 = Uint64
type BitRep 54 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 54 = Uint64
type BitRep 55 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 55 = Uint64
type BitRep 56 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 56 = Uint64
type BitRep 57 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 57 = Uint64
type BitRep 58 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 58 = Uint64
type BitRep 59 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 59 = Uint64
type BitRep 60 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 60 = Uint64
type BitRep 61 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 61 = Uint64
type BitRep 62 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 62 = Uint64
type BitRep 63 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 63 = Uint64
type BitRep 64 Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

type BitRep 64 = Uint64

repToBits :: forall n. (ANat n, IvoryRep (BitRep n)) => BitRep n -> Bits n Source #

Convert an Ivory value to a bit value. If the input value contains out of range bits, they will be ignored.

bitsToRep :: Bits n -> BitRep n Source #

Convert a bit value to an Ivory value.

zeroBits :: IvoryRep (BitRep n) => Bits n Source #

Return a bit value of all zeros of the given size.

bitLength :: forall a n. ANat n => BitArray n a -> Int Source #

Return the number of elements in a BitArray.

bitIx :: forall a n. (BitData a, ANat n, ANat (BitSize a), ANat (ArraySize n a)) => Int -> BitDataField (BitArray n a) a Source #

Return a BitDataField that accesses the "n"th element of a BitArray. This can be composed with other field accessors using "#>".

bit data

class (ANat (BitSize (BitType a)), IvoryRep (BitDataRep a), BitType a ~ Bits (BitSize (BitType a))) => BitData a Source #

Class of bit data types defined by the "bitdata" quasiquoter.

Minimal complete definition

toBits, fromBits

Instances
(ANat n, IvoryRep (BitRep n)) => BitData (Bits n) Source #

Identity instance of BitData for the base "Bits n" type.

Instance details

Defined in Ivory.Language.BitData.BitData

Associated Types

type BitType (Bits n) :: * Source #

Methods

toBits :: Bits n -> BitType (Bits n) Source #

fromBits :: BitType (Bits n) -> Bits n Source #

(ANat n, ANat (ArraySize n a), BitData a, IvoryRep (BitRep (ArraySize n a))) => BitData (BitArray n a) Source # 
Instance details

Defined in Ivory.Language.BitData.Array

Associated Types

type BitType (BitArray n a) :: * Source #

data BitDataField a b Source #

Description of a bit field defined by the "bitdata" quasiquoter. Each field defined in the record syntax will generate a top-level definition of BitDataField.

XXX do not export. This constructor must remain unexported so that only fields checked by the quasiquoter are created.

Instances
Show (BitDataField a b) Source # 
Instance details

Defined in Ivory.Language.BitData.BitData

type BitDataRep a = BitRep (BitSize (BitType a)) Source #

The Ivory type that stores the actual value for a bit data type.

This is a shorthand to simplify the constraints on functions that take arguments of the BitData class.

bit data conversions

toBits :: BitData a => a -> BitType a Source #

Convert a bit data type to its raw bit value. This is always well defined and should be exported.

fromBits :: BitData a => BitType a -> a Source #

Convert a raw bit value to a bit data type. All values may not be well defined with respect to the original set of bit data constructors. For now, we allow these "junk" values to be created, but that may change in the future (perhaps by implementing a checked, Ivory run-time conversion).

toRep :: BitData a => a -> BitDataRep a Source #

Convert a bit data value to its Ivory representation.

fromRep :: BitData a => BitDataRep a -> a Source #

Convert a raw Ivory type to a bit data type. If the input value is too large, the out of range upper bits will be masked off.

bit data field operations

setBitDataBit :: BitData a => BitDataField a Bit -> a -> a Source #

Set a single-bit field in a bit data value.

clearBitDataBit :: BitData a => BitDataField a Bit -> a -> a Source #

Clear a single-bit field in a bit data value.

getBitDataField :: (BitData a, BitData b, BitCast (BitDataRep a) (BitDataRep b)) => BitDataField a b -> a -> b Source #

Extract a field from a bit data definition. Returns the value as the type defined on the right hand side of the field definition in the "bitdata" quasiquoter.

setBitDataField :: (BitData a, BitData b, SafeCast (BitDataRep b) (BitDataRep a)) => BitDataField a b -> a -> b -> a Source #

Set a field from a bit data definition.

bit data operators

(#!) :: forall a n. (BitData a, ANat n, ANat (BitSize a), ANat (ArraySize n a), BitCast (BitRep (ArraySize n a)) (BitDataRep a), IvoryRep (BitRep (ArraySize n a))) => BitArray n a -> Int -> a Source #

Return the "n"th element of a BitArray.

(#.) :: (BitData a, BitData b, BitCast (BitDataRep a) (BitDataRep b)) => a -> BitDataField a b -> b Source #

Infix operator to read a bit data field. (like Data.Lens.^.)

(#>) :: BitDataField a b -> BitDataField b c -> BitDataField a c Source #

Bit data field composition. (like Control.Category.>>>)

bit actions

data BitDataM d a Source #

An action that modifies a bit data value of type "d" and returns a "a" in the "Ivory s r" monad. Values of this type are passed as the "body" argument to "withBits" etc.

Instances
Monad (BitDataM d) Source # 
Instance details

Defined in Ivory.Language.BitData.Monad

Methods

(>>=) :: BitDataM d a -> (a -> BitDataM d b) -> BitDataM d b #

(>>) :: BitDataM d a -> BitDataM d b -> BitDataM d b #

return :: a -> BitDataM d a #

fail :: String -> BitDataM d a #

Functor (BitDataM d) Source # 
Instance details

Defined in Ivory.Language.BitData.Monad

Methods

fmap :: (a -> b) -> BitDataM d a -> BitDataM d b #

(<$) :: a -> BitDataM d b -> BitDataM d a #

Applicative (BitDataM d) Source # 
Instance details

Defined in Ivory.Language.BitData.Monad

Methods

pure :: a -> BitDataM d a #

(<*>) :: BitDataM d (a -> b) -> BitDataM d a -> BitDataM d b #

liftA2 :: (a -> b -> c) -> BitDataM d a -> BitDataM d b -> BitDataM d c #

(*>) :: BitDataM d a -> BitDataM d b -> BitDataM d b #

(<*) :: BitDataM d a -> BitDataM d b -> BitDataM d a #

runBits :: BitData d => BitDataRep d -> BitDataM d a -> (a, BitDataRep d, [String]) Source #

Execute a bitdata action given an initial value, returning the new bitdata value and the result of the action.

withBits :: BitData d => BitDataRep d -> BitDataM d () -> BitDataRep d Source #

Execute a bitdata action given an initial value, returning the new bitdata value.

withBitsRef :: BitData d => Ref s1 (Stored (BitDataRep d)) -> BitDataM d a -> Ivory eff a Source #

Execute a bit data action given a reference to a value, writing the resulting value back to the reference upon completion and returning the result of the action.

clear :: BitData d => BitDataM d () Source #

Clear the value of the current bit data value.

setBit :: BitData d => BitDataField d Bit -> BitDataM d () Source #

Set a single bit field in the current bit data value.

clearBit :: BitData d => BitDataField d Bit -> BitDataM d () Source #

Clear a single bit.

setField :: (BitData d, BitData b, SafeCast (BitDataRep b) (BitDataRep d)) => BitDataField d b -> b -> BitDataM d () Source #

Set a field to a value.

bitToBool :: Bit -> IBool Source #

Convert a single bit bitdata to an Ivory boolean.

boolToBit :: IBool -> Bit Source #

Convert an Ivory boolean to a single bit.

External memory areas

data MemArea (area :: Area *) Source #

Externally defined memory areas.

Instances
IvoryAddrOf MemArea Ref Source # 
Instance details

Defined in Ivory.Language.MemArea

Methods

addrOf :: IvoryArea area => MemArea area -> Ref Global area Source #

Eq (MemArea area) Source # 
Instance details

Defined in Ivory.Language.MemArea

Methods

(==) :: MemArea area -> MemArea area -> Bool #

(/=) :: MemArea area -> MemArea area -> Bool #

Show (MemArea area) Source # 
Instance details

Defined in Ivory.Language.MemArea

Methods

showsPrec :: Int -> MemArea area -> ShowS #

show :: MemArea area -> String #

showList :: [MemArea area] -> ShowS #

area :: forall area. (IvoryArea area, IvoryZero area) => Sym -> Maybe (Init area) -> MemArea area Source #

Define a global constant. Requires an IvoryZero constraint to ensure the area has an initializers, but does not explicilty initialize to 0 so that the value is placed in the .bss section.

importArea :: IvoryArea area => Sym -> String -> MemArea area Source #

Import an external symbol from a header.

data ConstMemArea (area :: Area *) Source #

Instances
IvoryAddrOf ConstMemArea ConstRef Source # 
Instance details

Defined in Ivory.Language.MemArea

Methods

addrOf :: IvoryArea area => ConstMemArea area -> ConstRef Global area Source #

constArea :: forall area. IvoryArea area => Sym -> Init area -> ConstMemArea area Source #

Constant memory area definition.

importConstArea :: IvoryArea area => Sym -> String -> ConstMemArea area Source #

Import an external symbol from a header.

class IvoryAddrOf (mem :: Area * -> *) ref | mem -> ref, ref -> mem where Source #

Turn a memory area into a reference.

Minimal complete definition

addrOf

Methods

addrOf :: IvoryArea area => mem area -> ref Global area Source #

Instances
IvoryAddrOf ConstMemArea ConstRef Source # 
Instance details

Defined in Ivory.Language.MemArea

Methods

addrOf :: IvoryArea area => ConstMemArea area -> ConstRef Global area Source #

IvoryAddrOf MemArea Ref Source # 
Instance details

Defined in Ivory.Language.MemArea

Methods

addrOf :: IvoryArea area => MemArea area -> Ref Global area Source #

Procedures

data Def (proc :: Proc *) Source #

Procedure definitions.

Instances
Eq (Def proc) Source # 
Instance details

Defined in Ivory.Language.Proc

Methods

(==) :: Def proc -> Def proc -> Bool #

(/=) :: Def proc -> Def proc -> Bool #

Ord (Def proc) Source # 
Instance details

Defined in Ivory.Language.Proc

Methods

compare :: Def proc -> Def proc -> Ordering #

(<) :: Def proc -> Def proc -> Bool #

(<=) :: Def proc -> Def proc -> Bool #

(>) :: Def proc -> Def proc -> Bool #

(>=) :: Def proc -> Def proc -> Bool #

max :: Def proc -> Def proc -> Def proc #

min :: Def proc -> Def proc -> Def proc #

Show (Def proc) Source # 
Instance details

Defined in Ivory.Language.Proc

Methods

showsPrec :: Int -> Def proc -> ShowS #

show :: Def proc -> String #

showList :: [Def proc] -> ShowS #

ProcType proc => IvoryType (Def proc) Source # 
Instance details

Defined in Ivory.Language.Proc

Methods

ivoryType :: Proxy (Def proc) -> Type Source #

data ProcPtr (sig :: Proc *) Source #

Procedure pointers

Instances
ProcType proc => IvoryVar (ProcPtr proc) Source # 
Instance details

Defined in Ivory.Language.Proc

Methods

wrapVar :: Var -> ProcPtr proc Source #

unwrapExpr :: ProcPtr proc -> Expr Source #

ProcType proc => IvoryType (ProcPtr proc) Source # 
Instance details

Defined in Ivory.Language.Proc

Methods

ivoryType :: Proxy (ProcPtr proc) -> Type Source #

ProcType proc => IvoryInit (ProcPtr proc) Source # 
Instance details

Defined in Ivory.Language.Init

Methods

ival :: ProcPtr proc -> Init (Stored (ProcPtr proc)) Source #

procPtr :: ProcType sig => Def sig -> ProcPtr sig Source #

proc :: forall proc impl. IvoryProcDef proc impl => Sym -> impl -> Def proc Source #

Procedure definition.

voidProc :: IvoryProcDef (args :-> ()) impl => Sym -> impl -> Def (args :-> ()) Source #

Type inference can usually determine the argument types of an Ivory procedure, but for void procedures there's often nothing to constrain the return type. This function is a type-constrained version of proc that just forces the return type to be '()'.

importProc :: forall proc. ProcType proc => Sym -> String -> Def proc Source #

Import a function from a C header.

data Body r Source #

Instances
WrapIvory Body Source # 
Instance details

Defined in Ivory.Language.Proc

Associated Types

type Return Body :: * Source #

Methods

wrap :: (forall s. Ivory (ProcEffects s r) (Return Body)) -> Body r Source #

unwrap :: Body r -> forall s. Ivory (ProcEffects s r) (Return Body) Source #

IvoryType ret => IvoryProcDef (([] :: [*]) :-> ret) (Body ret) Source # 
Instance details

Defined in Ivory.Language.Proc

Methods

procDef :: Closure -> Proxy ([] :-> ret) -> Body ret -> ([Var], Definition) Source #

type Return Body Source # 
Instance details

Defined in Ivory.Language.Proc

type Return Body = ()

body :: IvoryType r => (forall s. Ivory (ProcEffects s r) ()) -> Body r Source #

Pre/Post-Conditions

requires :: (Requires c, WrapIvory m, IvoryType r) => c -> m r -> m r Source #

checkStored :: (CheckStored c, IvoryVar a, IvoryRef ref, IvoryVar (ref s (Stored a))) => ref s (Stored a) -> (a -> c) -> Cond Source #

ensures :: (Ensures c, WrapIvory m, IvoryVar r) => (r -> c) -> m r -> m r Source #

ensures_ :: (Ensures c, WrapIvory m) => c -> m () -> m () Source #

Assumption/Assertion statements

assert :: forall a eff. IvoryExpr a => a -> Ivory eff () Source #

assume :: forall a eff. IvoryExpr a => a -> Ivory eff () Source #

Structures

class (IvoryArea (Struct sym), ASymbol sym) => IvoryStruct (sym :: Symbol) where Source #

Minimal complete definition

structDef

Methods

structDef :: StructDef sym Source #

data StructDef (sym :: Symbol) Source #

(~>) :: forall ref s sym field. (IvoryStruct sym, IvoryRef ref, IvoryExpr (ref s (Struct sym)), IvoryExpr (ref s field)) => ref s (Struct sym) -> Label sym field -> ref s field Source #

Label indexing in a structure.

data Label (sym :: Symbol) (field :: Area *) Source #

Struct field labels.

Instances
Eq (Label sym field) Source # 
Instance details

Defined in Ivory.Language.Struct

Methods

(==) :: Label sym field -> Label sym field -> Bool #

(/=) :: Label sym field -> Label sym field -> Bool #

Arrays

(!) :: forall s len area ref. (ANat len, IvoryArea area, IvoryRef ref, IvoryExpr (ref s (Array len area)), IvoryExpr (ref s area)) => ref s (Array len area) -> Ix len -> ref s area Source #

Array indexing.

fromIx :: ANat n => Ix n -> IxRep Source #

toIx :: forall a n. (SafeCast a IxRep, ANat n) => a -> Ix n Source #

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

data Ix (n :: Nat) Source #

Values in the range 0 .. n-1.

Instances
ANat n => Bounded (Ix n) Source # 
Instance details

Defined in Ivory.Language.Array

Methods

minBound :: Ix n #

maxBound :: Ix n #

ANat n => Num (Ix n) Source # 
Instance details

Defined in Ivory.Language.Array

Methods

(+) :: Ix n -> Ix n -> Ix n #

(-) :: Ix n -> Ix n -> Ix n #

(*) :: Ix n -> Ix n -> Ix n #

negate :: Ix n -> Ix n #

abs :: Ix n -> Ix n #

signum :: Ix n -> Ix n #

fromInteger :: Integer -> Ix n #

ANat n => IvoryExpr (Ix n) Source # 
Instance details

Defined in Ivory.Language.Array

Methods

wrapExpr :: Expr -> Ix n Source #

ANat n => IvoryVar (Ix n) Source # 
Instance details

Defined in Ivory.Language.Array

Methods

wrapVar :: Var -> Ix n Source #

unwrapExpr :: Ix n -> Expr Source #

ANat n => IvoryType (Ix n) Source # 
Instance details

Defined in Ivory.Language.Array

Methods

ivoryType :: Proxy (Ix n) -> Type Source #

ANat n => IvoryOrd (Ix n) Source # 
Instance details

Defined in Ivory.Language.Array

Methods

(>?) :: Ix n -> Ix n -> IBool Source #

(>=?) :: Ix n -> Ix n -> IBool Source #

(<?) :: Ix n -> Ix n -> IBool Source #

(<=?) :: Ix n -> Ix n -> IBool Source #

ANat n => IvoryEq (Ix n) Source # 
Instance details

Defined in Ivory.Language.Array

Methods

(==?) :: Ix n -> Ix n -> IBool Source #

(/=?) :: Ix n -> Ix n -> IBool Source #

ANat n => IvoryStore (Ix n) Source # 
Instance details

Defined in Ivory.Language.Array

ANat n => IvoryZeroVal (Ix n) Source # 
Instance details

Defined in Ivory.Language.Init

Methods

izeroval :: Init (Stored (Ix n)) Source #

ANat len => IvoryInit (Ix len) Source # 
Instance details

Defined in Ivory.Language.Init

Methods

ival :: Ix len -> Init (Stored (Ix len)) Source #

(ANat n, IvoryIntegral to, Default to) => SafeCast (Ix n) to Source # 
Instance details

Defined in Ivory.Language.Array

Methods

safeCast :: Ix n -> to Source #

ixSize :: forall n. ANat n => Ix n -> Integer Source #

The number of elements that an index covers.

arrayLen :: forall s len area n ref. (Num n, ANat len, IvoryArea area, IvoryRef ref) => ref s (Array len area) -> n Source #

toCArray :: forall s len area rep ref. (ANat len, ToCArray area rep, IvoryRef ref, IvoryExpr (ref s (Array len area)), IvoryExpr (ref s (CArray rep))) => ref s (Array len area) -> ref s (CArray rep) Source #

Convert from a checked array to one that can be given to a c function.

type ANat n = KnownNat n Source #

fromTypeNat :: KnownNat i => proxy (i :: Nat) -> Integer Source #

The integer associated with a type-nat.

Looping

for :: forall eff n a. ANat n => Ix n -> (Ix n -> Ivory (AllowBreak eff) a) -> Ivory eff () Source #

Run the computation n times, where n :: Ix m, 0 <= n <= m. Indexes increment from 0 to n-1 inclusively.

Note: The definition of for may change so that no index value is provided. (Consider using upto if you need to use the index.)

times :: forall eff n a. ANat n => Ix n -> (Ix n -> Ivory (AllowBreak eff) a) -> Ivory eff () Source #

Run the computation n times, where n :: Ix m, 0 <= n <= m. Indexes decrement from n-1 to 0 inclusively.

Note: The definition of times may change so that no index value is provided. (Consider using downTo if you need to use the index.)

breakOut :: GetBreaks eff ~ Break => Ivory eff () Source #

arrayMap :: forall eff n a. ANat n => (Ix n -> Ivory (AllowBreak eff) a) -> Ivory eff () Source #

forever :: Ivory (AllowBreak eff) () -> Ivory eff () Source #

upTo :: ANat n => Ix n -> Ix n -> (Ix n -> Ivory (AllowBreak eff) a) -> Ivory eff () Source #

Loop over the range of indexes [start, start + 1 .. end]. If start > end, the loop body will never execute.

downTo :: ANat n => Ix n -> Ix n -> (Ix n -> Ivory (AllowBreak eff) a) -> Ivory eff () Source #

Loop over the range of indexes [end, end - 1 .. start]. If end > start, the loop body will never execute.

Call

call :: forall proc eff impl. IvoryCall proc eff impl => Def proc -> impl Source #

Direct calls.

indirect :: forall proc eff impl. IvoryCall proc eff impl => ProcPtr proc -> impl Source #

Indirect calls.

call_ :: forall proc eff impl. IvoryCall_ proc eff impl => Def proc -> impl Source #

Direct calls, ignoring the result.

indirect_ :: forall proc eff impl. IvoryCall_ proc eff impl => ProcPtr proc -> impl Source #

Indirect calls, ignoring the result.

Conditional Branching

ifte_ :: IBool -> Ivory eff a -> Ivory eff b -> Ivory eff () Source #

If-then-else.

(?) :: IvoryExpr a => IBool -> (a, a) -> a Source #

Conditional expressions.

withRef :: (KnownConstancy c, IvoryArea a) => Pointer Nullable c s a -> (Pointer Valid c s a -> Ivory eff t) -> Ivory eff f -> Ivory eff () Source #

Unwrap a pointer, and use it as a reference.

Return

ret :: (GetReturn eff ~ Returns r, IvoryVar r) => r -> Ivory eff () Source #

Primitive return from function.

retVoid :: GetReturn eff ~ Returns () => Ivory eff () Source #

Primitive void return from function.

Type-safe casting.

class (IvoryExpr from, IvoryExpr to) => SafeCast from to Source #

Statically safe casts.

Instances
SafeCast IChar IChar Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: IChar -> IChar Source #

SafeCast Sint64 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint64 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint32 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint32 Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint32 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint32 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint16 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint16 Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint16 Sint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint16 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint16 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint8 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint8 Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint8 Sint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint8 Sint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: Sint8 -> Sint8 Source #

SafeCast Sint8 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Sint8 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint64 Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint64 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint32 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint32 Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint32 Uint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint32 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint32 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 Uint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 Uint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint16 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Sint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Uint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Uint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 Uint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: Uint8 -> Uint8 Source #

SafeCast Uint8 IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast Uint8 IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool IChar Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: IBool -> IChar Source #

SafeCast IBool Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Sint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Sint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: IBool -> Sint8 Source #

SafeCast IBool Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Uint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Uint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Uint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: IBool -> Uint8 Source #

SafeCast IBool IBool Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: IBool -> IBool Source #

SafeCast IBool IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IDouble IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IFloat IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IFloat IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

(ANat n, IvoryIntegral to, Default to) => SafeCast (Ix n) to Source # 
Instance details

Defined in Ivory.Language.Array

Methods

safeCast :: Ix n -> to Source #

class (IvoryExpr from, IvoryExpr to, Default to) => RuntimeCast from to Source #

Casts requiring runtime checks.

Minimal complete definition

inBounds

Instances
(Bounded from, Bounded to, IvoryOrd from, IvoryOrd to, IvoryExpr from, IvoryExpr to, Default from, Default to, SafeCast to from) => RuntimeCast from to Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

inBounds :: to -> from -> IBool

(Default to, Bounded to, IvoryIntegral to, SafeCast to IDouble) => RuntimeCast IDouble to Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

inBounds :: to -> IDouble -> IBool

(Default to, Bounded to, IvoryIntegral to, SafeCast to IFloat) => RuntimeCast IFloat to Source #

Casting from a floating to a Integral type always results in truncation.

Instance details

Defined in Ivory.Language.Cast

Methods

inBounds :: to -> IFloat -> IBool

class Default a Source #

Default values for expression types.

Minimal complete definition

defaultVal

Instances
Default Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: Sint64

Default Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: Sint32

Default Sint16 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: Sint16

Default Sint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: Sint8

Default Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: Uint64

Default Uint32 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: Uint32

Default Uint16 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: Uint16

Default Uint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: Uint8

Default IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

Default IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

defaultVal :: IFloat

safeCast :: SafeCast from to => from -> to Source #

castWith :: RuntimeCast from to => to -> from -> to Source #

Cast with a default value if the casted value is too large.

castDefault :: (Default to, RuntimeCast from to) => from -> to Source #

`CastWith 0` for types for which 0 is defined.

class (IvoryExpr from, IvoryExpr to) => SignCast from to Source #

SignCast takes a unsigned number into its signed form iff safe, otherwise 0, and same with signed into unsigned

Minimal complete definition

signCast

Instances
SignCast Sint64 Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SignCast Sint32 Uint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SignCast Sint16 Uint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SignCast Sint8 Uint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

signCast :: Sint8 -> Uint8 Source #

SignCast Uint64 Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SignCast Uint32 Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SignCast Uint16 Sint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SignCast Uint8 Sint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

signCast :: Uint8 -> Sint8 Source #

signCast :: SignCast from to => from -> to Source #

Module Definitions

data Module Source #

Instances
Eq Module Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

(==) :: Module -> Module -> Bool #

(/=) :: Module -> Module -> Bool #

Ord Module Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Show Module Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Semigroup Module Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Monoid Module Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Lift Module Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Module -> Q Exp #

WriterM ModuleM Module # 
Instance details

Defined in Ivory.Language.Module

Methods

put :: Module -> ModuleM () #

package :: String -> ModuleDef -> Module Source #

Package the module up. Default visibility is public.

incl :: Def a -> ModuleDef Source #

Include a defintion in the module.

depend :: Module -> ModuleDef Source #

Add a dependency on another module.

dependByName :: String -> ModuleDef Source #

Add a dependency on another module by name. Use the same name here that you use when you call package to build the target module. This function is particularly useful when building mutually dependent module structures.

defStruct :: forall sym. (IvoryStruct sym, ASymbol sym) => Proxy sym -> ModuleDef Source #

Include the definition of a structure in the module.

defStringType :: forall str. IvoryString str => Proxy str -> ModuleDef Source #

Include the definition of a string type's structure.

defMemArea :: IvoryArea area => MemArea area -> ModuleDef Source #

Include the definition of a memory area.

defConstMemArea :: IvoryArea area => ConstMemArea area -> ModuleDef Source #

Include the definition of a constant memory area.

private :: ModuleDef -> ModuleDef Source #

Start a block of definitions that should not be put in the header.

public :: ModuleDef -> ModuleDef Source #

Start a block of definitions should be put in the header. This is the default, and this function is just included to complement private.

Quasiquoters

ivory :: QuasiQuoter Source #

Quasiquoter for defining Ivory statements in C-like syntax. No module generated.

ivoryFile :: QuasiQuoter Source #

Parse a file. Use

ivoryFile|foo.ivory|]

To parse file ```foo.ivory``` Generates a module definition by default with a module name that is constructed from the filename and path such that

"diradirbfoobar.ivory"

has a module name

diradirbfoobar

Like quoteFile except we also process the filename.

ivoryBlk :: QuasiQuoter Source #

Quasiquoter for defining blocks of Ivory statements.

Utilities

data Proxy (t :: k) :: forall k. k -> * #

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the 'undefined :: a' idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy 
Instances
Generic1 (Proxy :: k -> *) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> * #

Methods

from1 :: Proxy a -> Rep1 Proxy a #

to1 :: Rep1 Proxy a -> Proxy a #

Monad (Proxy :: * -> *)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b #

(>>) :: Proxy a -> Proxy b -> Proxy b #

return :: a -> Proxy a #

fail :: String -> Proxy a #

Functor (Proxy :: * -> *)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

fmap :: (a -> b) -> Proxy a -> Proxy b #

(<$) :: a -> Proxy b -> Proxy a #

Applicative (Proxy :: * -> *)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

pure :: a -> Proxy a #

(<*>) :: Proxy (a -> b) -> Proxy a -> Proxy b #

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c #

(*>) :: Proxy a -> Proxy b -> Proxy b #

(<*) :: Proxy a -> Proxy b -> Proxy a #

Foldable (Proxy :: * -> *)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Proxy m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy a -> m #

foldr :: (a -> b -> b) -> b -> Proxy a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy a -> b #

foldl :: (b -> a -> b) -> b -> Proxy a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy a -> b #

foldr1 :: (a -> a -> a) -> Proxy a -> a #

foldl1 :: (a -> a -> a) -> Proxy a -> a #

toList :: Proxy a -> [a] #

null :: Proxy a -> Bool #

length :: Proxy a -> Int #

elem :: Eq a => a -> Proxy a -> Bool #

maximum :: Ord a => Proxy a -> a #

minimum :: Ord a => Proxy a -> a #

sum :: Num a => Proxy a -> a #

product :: Num a => Proxy a -> a #

Traversable (Proxy :: * -> *)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Proxy a -> f (Proxy b) #

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a) #

mapM :: Monad m => (a -> m b) -> Proxy a -> m (Proxy b) #

sequence :: Monad m => Proxy (m a) -> m (Proxy a) #

Eq1 (Proxy :: * -> *)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Proxy a -> Proxy b -> Bool #

Ord1 (Proxy :: * -> *)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Proxy a -> Proxy b -> Ordering #

Read1 (Proxy :: * -> *)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a] #

Show1 (Proxy :: * -> *)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy a] -> ShowS #

Alternative (Proxy :: * -> *)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

empty :: Proxy a #

(<|>) :: Proxy a -> Proxy a -> Proxy a #

some :: Proxy a -> Proxy [a] #

many :: Proxy a -> Proxy [a] #

MonadPlus (Proxy :: * -> *)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzero :: Proxy a #

mplus :: Proxy a -> Proxy a -> Proxy a #

Bounded (Proxy t) 
Instance details

Defined in Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

succ :: Proxy s -> Proxy s #

pred :: Proxy s -> Proxy s #

toEnum :: Int -> Proxy s #

fromEnum :: Proxy s -> Int #

enumFrom :: Proxy s -> [Proxy s] #

enumFromThen :: Proxy s -> Proxy s -> [Proxy s] #

enumFromTo :: Proxy s -> Proxy s -> [Proxy s] #

enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] #

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(==) :: Proxy s -> Proxy s -> Bool #

(/=) :: Proxy s -> Proxy s -> Bool #

Ord (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering #

(<) :: Proxy s -> Proxy s -> Bool #

(<=) :: Proxy s -> Proxy s -> Bool #

(>) :: Proxy s -> Proxy s -> Bool #

(>=) :: Proxy s -> Proxy s -> Bool #

max :: Proxy s -> Proxy s -> Proxy s #

min :: Proxy s -> Proxy s -> Proxy s #

Read (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

Ix (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

range :: (Proxy s, Proxy s) -> [Proxy s] #

index :: (Proxy s, Proxy s) -> Proxy s -> Int #

unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int

inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool #

rangeSize :: (Proxy s, Proxy s) -> Int #

unsafeRangeSize :: (Proxy s, Proxy s) -> Int

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: * -> * #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s #

sconcat :: NonEmpty (Proxy s) -> Proxy s #

stimes :: Integral b => b -> Proxy s -> Proxy s #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

type Rep1 (Proxy :: k -> *) 
Instance details

Defined in GHC.Generics

type Rep1 (Proxy :: k -> *) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) (U1 :: k -> *))
type Rep (Proxy t) 
Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) (U1 :: * -> *))

comment :: String -> Ivory eff () Source #