| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Ivory.Language.Init
Synopsis
- data XInit
- initType :: XInit -> Type
- newtype Init (area :: Area *) = Init {}
- class IvoryZero (area :: Area *) where
- refZero :: forall eff s a. (IvoryZero a, IvoryArea a) => Ref s a -> Ivory eff ()
- class Monad m => FreshName m where
- data Binding = Binding {
- bindingVar :: Var
- bindingType :: Type
- bindingInit :: Init
- bindingSym :: Binding -> Sym
- runInit :: FreshName m => XInit -> m (Init, [Binding])
- class IvoryVar e => IvoryInit e where
- class IvoryVar a => IvoryZeroVal a where
- iarray :: forall len area. (IvoryArea area, ANat len) => [Init area] -> Init (Array len area)
- newtype InitStruct (sym :: Symbol) = InitStruct {
- getInitStruct :: [(String, XInit)]
- istruct :: forall sym. IvoryStruct sym => [InitStruct sym] -> Init (Struct sym)
- (.=) :: Label sym area -> Init area -> InitStruct sym
- local :: forall eff s area. (IvoryArea area, GetAlloc eff ~ Scope s) => Init area -> Ivory eff (Ref (Stack s) area)
Documentation
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.
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.
A variable binding (on the stack or in a memory area).
Constructors
| Binding | |
Fields
| |
bindingSym :: Binding -> Sym Source #
runInit :: FreshName m => XInit -> m (Init, [Binding]) Source #
Return the initializer and auxillary bindings for an initializer in a context that can allocate fresh names.
class IvoryVar e => IvoryInit e where Source #
Initializers for Stored things.
Minimal complete definition
Nothing
Instances
| IvoryInit IChar Source # | |
| IvoryInit Sint64 Source # | |
| IvoryInit Sint32 Source # | |
| IvoryInit Sint16 Source # | |
| IvoryInit Sint8 Source # | |
| IvoryInit Uint64 Source # | |
| IvoryInit Uint32 Source # | |
| IvoryInit Uint16 Source # | |
| IvoryInit Uint8 Source # | |
| IvoryInit IBool Source # | |
| IvoryInit IDouble Source # | |
| IvoryInit IFloat Source # | |
| ProcType proc => IvoryInit (ProcPtr proc) Source # | |
| ANat len => IvoryInit (Ix len) Source # | |
| IvoryRep (BitRep n) => IvoryInit (Bits n) Source # | |
| IvoryArea area => IvoryInit (Ptr Global area) Source # | |
class IvoryVar a => IvoryZeroVal a where Source #
Instances
| IvoryZeroVal IChar Source # | |
| IvoryZeroVal Sint64 Source # | |
| IvoryZeroVal Sint32 Source # | |
| IvoryZeroVal Sint16 Source # | |
| IvoryZeroVal Sint8 Source # | |
| IvoryZeroVal Uint64 Source # | |
| IvoryZeroVal Uint32 Source # | |
| IvoryZeroVal Uint16 Source # | |
| IvoryZeroVal Uint8 Source # | |
| IvoryZeroVal IBool Source # | |
| IvoryZeroVal IDouble Source # | |
| IvoryZeroVal IFloat Source # | |
| ANat n => IvoryZeroVal (Ix n) Source # | |
| IvoryRep (BitRep n) => IvoryZeroVal (Bits n) Source # | |
| IvoryArea area => IvoryZeroVal (Ptr Global area) Source # | |
iarray :: forall len area. (IvoryArea area, ANat len) => [Init area] -> Init (Array len area) Source #
newtype InitStruct (sym :: Symbol) Source #
Constructors
| InitStruct | |
Fields
| |
Instances
| IvoryStruct sym => Semigroup (InitStruct sym) Source # | |
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 # | |
Defined in Ivory.Language.Init Methods mempty :: InitStruct sym # mappend :: InitStruct sym -> InitStruct sym -> InitStruct sym # mconcat :: [InitStruct sym] -> InitStruct sym # | |
istruct :: forall sym. IvoryStruct sym => [InitStruct sym] -> Init (Struct sym) Source #