gpu-vulkan-0.1.0.140: Vulkan library
Safe HaskellNone
LanguageHaskell2010

Gpu.Vulkan.Object.Base

Synopsis

OBJECT

data O Source #

Constructors

O Alignment (Maybe Symbol) ObjectType Type 

class (Storable (ImagePixel img), FormatToValue (ImageFormat img)) => IsImage img where Source #

Associated Types

type ImagePixel img Source #

type ImageFormat img :: Format Source #

Methods

imageRow :: img -> Size Source #

imageWidth :: img -> Size Source #

imageHeight :: img -> Size Source #

imageDepth :: img -> Size Source #

imageBody :: img -> [[ImagePixel img]] Source #

imageMake :: Size -> Size -> Size -> [[ImagePixel img]] -> img Source #

Synonyms

type Atom (algn :: Alignment) t (mnm :: Maybe Symbol) = AtomMaybeName algn t mnm Source #

type AtomNew (algn :: Alignment) t (nm :: Symbol) = AtomMaybeName algn t ('Just nm) Source #

type List (algn :: Alignment) t (nm :: Symbol) = ListMaybeName algn t ('Just nm) Source #

type Image (algn :: Alignment) t (nm :: Symbol) = ImageMaybeName algn t ('Just nm) Source #

type AtomNoName (al :: Alignment) t = AtomMaybeName al t ('Nothing :: Maybe Symbol) Source #

type ListNoName (al :: Alignment) t = ListMaybeName al t ('Nothing :: Maybe Symbol) Source #

type ImageNoName (al :: Alignment) t = ImageMaybeName al t ('Nothing :: Maybe Symbol) Source #

type AtomMaybeName (al :: Alignment) t (mnm :: Maybe Symbol) = 'O al mnm 'AtomT t Source #

type ListMaybeName (al :: Alignment) t (mnm :: Maybe Symbol) = 'O al mnm 'ListT t Source #

type ImageMaybeName (al :: Alignment) t (mnm :: Maybe Symbol) = 'O al mnm 'ImageT t Source #

Type Of Object

type family TypeOf (obj :: O) where ... Source #

Equations

TypeOf (Atom _algn t _nm) = t 
TypeOf (List _algn t _nm) = t 

OBJECT LENGTH

data Length (obj :: O) where Source #

Constructors

LengthAtom :: forall (algn :: Alignment) t (nm :: Maybe Symbol). Length ('O algn nm 'AtomT t) 
LengthList :: forall (algn :: Alignment) (mnm :: Maybe Symbol) t. Size -> Length ('O algn mnm 'ListT t) 
LengthImage 

Fields

Instances

Instances details
Show (Length obj) Source # 
Instance details

Defined in Gpu.Vulkan.Object.Base

Methods

showsPrec :: Int -> Length obj -> ShowS #

show :: Length obj -> String #

showList :: [Length obj] -> ShowS #

Default (Length (Atom algn t mnm)) Source # 
Instance details

Defined in Gpu.Vulkan.Object.Base

Methods

def :: Length (Atom algn t mnm) #

Default (Length (Image algn t nm)) Source # 
Instance details

Defined in Gpu.Vulkan.Object.Base

Methods

def :: Length (Image algn t nm) #

Default (Length (List algn t nm)) Source # 
Instance details

Defined in Gpu.Vulkan.Object.Base

Methods

def :: Length (List algn t nm) #

Eq (Length obj) Source # 
Instance details

Defined in Gpu.Vulkan.Object.Base

Methods

(==) :: Length obj -> Length obj -> Bool #

(/=) :: Length obj -> Length obj -> Bool #

renameLength :: forall (algn :: Alignment) (mnm :: Maybe Symbol) (ot :: ObjectType) t (mnm' :: Maybe Symbol). Length ('O algn mnm ot t) -> Length ('O algn mnm' ot t) Source #

STORE OBJECT

class SizeAlignment obj => Store v (obj :: O) where Source #

Methods

store :: Ptr (TypeOf obj) -> Length obj -> v -> IO () Source #

load :: Ptr (TypeOf obj) -> Length obj -> IO v Source #

length :: v -> Length obj Source #

Instances

Instances details
(KnownNat algn, IsImage img) => Store img (Image algn img nm) Source # 
Instance details

Defined in Gpu.Vulkan.Object.Base

Methods

store :: Ptr (TypeOf (Image algn img nm)) -> Length (Image algn img nm) -> img -> IO () Source #

load :: Ptr (TypeOf (Image algn img nm)) -> Length (Image algn img nm) -> IO img Source #

length :: img -> Length (Image algn img nm) Source #

(Storable t, KnownNat algn) => Store t (Atom algn t _nm) Source # 
Instance details

Defined in Gpu.Vulkan.Object.Base

Methods

store :: Ptr (TypeOf (Atom algn t _nm)) -> Length (Atom algn t _nm) -> t -> IO () Source #

load :: Ptr (TypeOf (Atom algn t _nm)) -> Length (Atom algn t _nm) -> IO t Source #

length :: t -> Length (Atom algn t _nm) Source #

(KnownNat algn, IsSequence v, Storable t, Element v ~ t) => Store v (List algn t _nm) Source # 
Instance details

Defined in Gpu.Vulkan.Object.Base

Methods

store :: Ptr (TypeOf (List algn t _nm)) -> Length (List algn t _nm) -> v -> IO () Source #

load :: Ptr (TypeOf (List algn t _nm)) -> Length (List algn t _nm) -> IO v Source #

length :: v -> Length (List algn t _nm) Source #

SIZE AND ALIGNMENT

class SizeAlignment (obj :: O) where Source #

Instances

Instances details
(KnownNat algn, Storable t) => SizeAlignment (AtomMaybeName algn t _nm) Source # 
Instance details

Defined in Gpu.Vulkan.Object.Base

Methods

size :: Length (AtomMaybeName algn t _nm) -> Size Source #

alignment :: Size Source #

(KnownNat algn, Storable (ImagePixel img)) => SizeAlignment (ImageMaybeName algn img nm) Source # 
Instance details

Defined in Gpu.Vulkan.Object.Base

Methods

size :: Length (ImageMaybeName algn img nm) -> Size Source #

alignment :: Size Source #

(KnownNat algn, Storable t) => SizeAlignment (ListMaybeName algn t _nm) Source # 
Instance details

Defined in Gpu.Vulkan.Object.Base

Methods

size :: Length (ListMaybeName algn t _nm) -> Size Source #

alignment :: Size Source #