Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Bindings for types used mainly in rtextures
Synopsis
- data PixelFormat
- = PixelFormatUnset
- | PixelFormatUncompressedGrayscale
- | PixelFormatUncompressedGrayAlpha
- | PixelFormatUncompressedR5G6B5
- | PixelFormatUncompressedR8G8B8
- | PixelFormatUncompressedR5G5B5A1
- | PixelFormatUncompressedR4G4B4A4
- | PixelFormatUncompressedR8G8B8A8
- | PixelFormatUncompressedR32
- | PixelFormatUncompressedR32G32B32
- | PixelFormatUncompressedR32G32B32A32
- | PixelFormatUncompressedR16
- | PixelFormatUncompressedR16G16B16
- | PixelFormatUncompressedR16G16B16A16
- | PixelFormatCompressedDxt1Rgb
- | PixelFormatCompressedDxt1Rgba
- | PixelFormatCompressedDxt3Rgba
- | PixelFormatCompressedDxt5Rgba
- | PixelFormatCompressedEtc1Rgb
- | PixelFormatCompressedEtc2Rgb
- | PixelFormatCompressedEtc2EacRgba
- | PixelFormatCompressedPvrtRgb
- | PixelFormatCompressedPvrtRgba
- | PixelFormatCompressedAstc4x4Rgba
- | PixelFormatCompressedAstc8x8Rgba
- data TextureFilter
- data TextureWrap
- data CubemapLayout
- data NPatchLayout
- data Image = Image {
- image'data :: [Word8]
- image'width :: Int
- image'height :: Int
- image'mipmaps :: Int
- image'format :: PixelFormat
- data Texture = Texture {}
- data RenderTexture = RenderTexture {}
- data NPatchInfo = NPatchInfo {}
- type Texture2D = Texture
- type TextureCubemap = Texture
- type RenderTexture2D = RenderTexture
- p'image'data :: Ptr Image -> Ptr (Ptr CUChar)
- p'image'width :: Ptr Image -> Ptr CInt
- p'image'height :: Ptr Image -> Ptr CInt
- p'image'mipmaps :: Ptr Image -> Ptr CInt
- p'image'format :: Ptr Image -> Ptr PixelFormat
- p'texture'id :: Ptr Texture -> Ptr CUInt
- p'texture'width :: Ptr Texture -> Ptr CInt
- p'texture'height :: Ptr Texture -> Ptr CInt
- p'texture'mipmaps :: Ptr Texture -> Ptr CInt
- p'texture'format :: Ptr Texture -> Ptr PixelFormat
- p'renderTexture'id :: Ptr RenderTexture -> Ptr CUInt
- p'renderTexture'texture :: Ptr RenderTexture -> Ptr Texture
- p'renderTexture'depth :: Ptr RenderTexture -> Ptr Texture
- p'nPatchInfo'source :: Ptr NPatchInfo -> Ptr Rectangle
- p'nPatchInfo'left :: Ptr NPatchInfo -> Ptr CInt
- p'nPatchInfo'top :: Ptr NPatchInfo -> Ptr CInt
- p'nPatchInfo'right :: Ptr NPatchInfo -> Ptr CInt
- p'nPatchInfo'bottom :: Ptr NPatchInfo -> Ptr CInt
- p'nPatchInfo'layout :: Ptr NPatchInfo -> Ptr NPatchLayout
Enumerations
data PixelFormat Source #
Instances
data TextureFilter Source #
TextureFilterPoint | |
TextureFilterBilinear | |
TextureFilterTrilinear | |
TextureFilterAnisotropic4x | |
TextureFilterAnisotropic8x | |
TextureFilterAnisotropic16x |
Instances
Enum TextureFilter Source # | |
Defined in Raylib.Types.Core.Textures succ :: TextureFilter -> TextureFilter # pred :: TextureFilter -> TextureFilter # toEnum :: Int -> TextureFilter # fromEnum :: TextureFilter -> Int # enumFrom :: TextureFilter -> [TextureFilter] # enumFromThen :: TextureFilter -> TextureFilter -> [TextureFilter] # enumFromTo :: TextureFilter -> TextureFilter -> [TextureFilter] # enumFromThenTo :: TextureFilter -> TextureFilter -> TextureFilter -> [TextureFilter] # |
data TextureWrap Source #
Instances
Enum TextureWrap Source # | |
Defined in Raylib.Types.Core.Textures succ :: TextureWrap -> TextureWrap # pred :: TextureWrap -> TextureWrap # toEnum :: Int -> TextureWrap # fromEnum :: TextureWrap -> Int # enumFrom :: TextureWrap -> [TextureWrap] # enumFromThen :: TextureWrap -> TextureWrap -> [TextureWrap] # enumFromTo :: TextureWrap -> TextureWrap -> [TextureWrap] # enumFromThenTo :: TextureWrap -> TextureWrap -> TextureWrap -> [TextureWrap] # |
data CubemapLayout Source #
CubemapLayoutAutoDetect | |
CubemapLayoutLineVertical | |
CubemapLayoutLineHorizontal | |
CubemapLayoutCrossThreeByFour | |
CubemapLayoutCrossThreeByThree | |
CubemapLayoutPanorama |
Instances
Enum CubemapLayout Source # | |
Defined in Raylib.Types.Core.Textures succ :: CubemapLayout -> CubemapLayout # pred :: CubemapLayout -> CubemapLayout # toEnum :: Int -> CubemapLayout # fromEnum :: CubemapLayout -> Int # enumFrom :: CubemapLayout -> [CubemapLayout] # enumFromThen :: CubemapLayout -> CubemapLayout -> [CubemapLayout] # enumFromTo :: CubemapLayout -> CubemapLayout -> [CubemapLayout] # enumFromThenTo :: CubemapLayout -> CubemapLayout -> CubemapLayout -> [CubemapLayout] # |
data NPatchLayout Source #
Instances
Structures
Image | |
|
Instances
Storable Image Source # | |
Show Image Source # | |
Eq Image Source # | |
Freeable Image Source # | |
Texture | |
|
Instances
Storable Texture Source # | |
Show Texture Source # | |
Eq Texture Source # | |
Closeable Texture Source # | |
Defined in Raylib.Types.Core.Textures | |
Freeable Texture Source # | |
data RenderTexture Source #
Instances
data NPatchInfo Source #
Instances
Storable NPatchInfo Source # | |
Defined in Raylib.Types.Core.Textures sizeOf :: NPatchInfo -> Int # alignment :: NPatchInfo -> Int # peekElemOff :: Ptr NPatchInfo -> Int -> IO NPatchInfo # pokeElemOff :: Ptr NPatchInfo -> Int -> NPatchInfo -> IO () # peekByteOff :: Ptr b -> Int -> IO NPatchInfo # pokeByteOff :: Ptr b -> Int -> NPatchInfo -> IO () # peek :: Ptr NPatchInfo -> IO NPatchInfo # poke :: Ptr NPatchInfo -> NPatchInfo -> IO () # | |
Show NPatchInfo Source # | |
Defined in Raylib.Types.Core.Textures showsPrec :: Int -> NPatchInfo -> ShowS # show :: NPatchInfo -> String # showList :: [NPatchInfo] -> ShowS # | |
Eq NPatchInfo Source # | |
Defined in Raylib.Types.Core.Textures (==) :: NPatchInfo -> NPatchInfo -> Bool # (/=) :: NPatchInfo -> NPatchInfo -> Bool # | |
Freeable NPatchInfo Source # | |
Defined in Raylib.Types.Core.Textures rlFreeDependents :: NPatchInfo -> Ptr NPatchInfo -> IO () Source # rlFree :: NPatchInfo -> Ptr NPatchInfo -> IO () Source # |
type TextureCubemap = Texture Source #
type RenderTexture2D = RenderTexture Source #
Pointer utilities
p'image'format :: Ptr Image -> Ptr PixelFormat Source #
p'texture'format :: Ptr Texture -> Ptr PixelFormat Source #
p'nPatchInfo'left :: Ptr NPatchInfo -> Ptr CInt Source #
p'nPatchInfo'top :: Ptr NPatchInfo -> Ptr CInt Source #
p'nPatchInfo'right :: Ptr NPatchInfo -> Ptr CInt Source #
p'nPatchInfo'bottom :: Ptr NPatchInfo -> Ptr CInt Source #