Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data O = O Alignment (Maybe Symbol) ObjectType Type
- class (Storable (ImagePixel img), FormatToValue (ImageFormat img)) => IsImage img where
- type ImagePixel img
- type ImageFormat img :: Format
- imageRow :: img -> Size
- imageWidth :: img -> Size
- imageHeight :: img -> Size
- imageDepth :: img -> Size
- imageBody :: img -> [[ImagePixel img]]
- imageMake :: Size -> Size -> Size -> [[ImagePixel img]] -> img
- type Atom (algn :: Alignment) t (mnm :: Maybe Symbol) = AtomMaybeName algn t mnm
- type AtomNew (algn :: Alignment) t (nm :: Symbol) = AtomMaybeName algn t ('Just nm)
- type List (algn :: Alignment) t (nm :: Symbol) = ListMaybeName algn t ('Just nm)
- type Image (algn :: Alignment) t (nm :: Symbol) = ImageMaybeName algn t ('Just nm)
- type AtomNoName (al :: Alignment) t = AtomMaybeName al t ('Nothing :: Maybe Symbol)
- type ListNoName (al :: Alignment) t = ListMaybeName al t ('Nothing :: Maybe Symbol)
- type ImageNoName (al :: Alignment) t = ImageMaybeName al t ('Nothing :: Maybe Symbol)
- type AtomMaybeName (al :: Alignment) t (mnm :: Maybe Symbol) = 'O al mnm 'AtomT t
- type ListMaybeName (al :: Alignment) t (mnm :: Maybe Symbol) = 'O al mnm 'ListT t
- type ImageMaybeName (al :: Alignment) t (mnm :: Maybe Symbol) = 'O al mnm 'ImageT t
- type family TypeOf (obj :: O) where ...
- data Length (obj :: O) where
- 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 :: forall (algn :: Alignment) (mnm :: Maybe Symbol) t. {..} -> Length ('O algn mnm 'ImageT t)
- 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)
- class SizeAlignment obj => Store v (obj :: O) where
- class SizeAlignment (obj :: O) where
OBJECT
class (Storable (ImagePixel img), FormatToValue (ImageFormat img)) => IsImage img where Source #
type ImagePixel img Source #
type ImageFormat img :: Format Source #
Synonyms
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 Of Object
OBJECT LENGTH
data Length (obj :: O) where Source #
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 | |
|
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 #
store :: Ptr (TypeOf obj) -> Length obj -> v -> IO () Source #
SIZE AND ALIGNMENT
class SizeAlignment (obj :: O) where Source #
Instances
(KnownNat algn, Storable t) => SizeAlignment (AtomMaybeName algn t _nm) Source # | |
(KnownNat algn, Storable (ImagePixel img)) => SizeAlignment (ImageMaybeName algn img nm) Source # | |
(KnownNat algn, Storable t) => SizeAlignment (ListMaybeName algn t _nm) Source # | |