| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Raylib.Types
Documentation
Instances
| Storable Vector2 Source # | |
| Show Vector2 Source # | |
| Eq Vector2 Source # | |
Instances
| Storable Vector3 Source # | |
| Show Vector3 Source # | |
| Eq Vector3 Source # | |
Constructors
| Vector4 | |
Instances
| Storable Vector4 Source # | |
| Show Vector4 Source # | |
| Eq Vector4 Source # | |
type Quaternion = Vector4 Source #
Constructors
| Matrix | |
Fields
| |
Instances
| Storable Matrix Source # | |
| Show Matrix Source # | |
| Eq Matrix Source # | |
Instances
| Storable Color Source # | |
| Show Color Source # | |
| Eq Color Source # | |
Constructors
| Rectangle | |
Fields | |
Instances
| Storable Rectangle Source # | |
Defined in Raylib.Types | |
| Show Rectangle Source # | |
| Eq Rectangle Source # | |
Constructors
| Image | |
Fields
| |
Instances
| Storable Image Source # | |
| Show Image Source # | |
| Eq Image Source # | |
Constructors
| Texture | |
Fields
| |
Instances
| Storable Texture Source # | |
| Show Texture Source # | |
| Eq Texture Source # | |
type TextureCubemap = Texture Source #
data RenderTexture Source #
Constructors
| RenderTexture | |
Fields | |
Instances
| Storable RenderTexture Source # | |
Defined in Raylib.Types Methods sizeOf :: RenderTexture -> Int # alignment :: RenderTexture -> Int # peekElemOff :: Ptr RenderTexture -> Int -> IO RenderTexture # pokeElemOff :: Ptr RenderTexture -> Int -> RenderTexture -> IO () # peekByteOff :: Ptr b -> Int -> IO RenderTexture # pokeByteOff :: Ptr b -> Int -> RenderTexture -> IO () # peek :: Ptr RenderTexture -> IO RenderTexture # poke :: Ptr RenderTexture -> RenderTexture -> IO () # | |
| Show RenderTexture Source # | |
Defined in Raylib.Types Methods showsPrec :: Int -> RenderTexture -> ShowS # show :: RenderTexture -> String # showList :: [RenderTexture] -> ShowS # | |
| Eq RenderTexture Source # | |
Defined in Raylib.Types Methods (==) :: RenderTexture -> RenderTexture -> Bool # (/=) :: RenderTexture -> RenderTexture -> Bool # | |
type RenderTexture2D = RenderTexture Source #
data NPatchInfo Source #
Constructors
| NPatchInfo | |
Fields | |
Instances
| Storable NPatchInfo Source # | |
Defined in Raylib.Types Methods 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 Methods showsPrec :: Int -> NPatchInfo -> ShowS # show :: NPatchInfo -> String # showList :: [NPatchInfo] -> ShowS # | |
| Eq NPatchInfo Source # | |
Defined in Raylib.Types | |
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 #
p'NPatchInfo'layout :: Ptr NPatchInfo -> Ptr CInt Source #
Constructors
| GlyphInfo | |
Fields | |
Instances
| Storable GlyphInfo Source # | |
Defined in Raylib.Types | |
| Show GlyphInfo Source # | |
| Eq GlyphInfo Source # | |
Constructors
| Font | |
Fields
| |
Constructors
| Camera3D | |
Fields | |
Instances
| Storable Camera3D Source # | |
Defined in Raylib.Types | |
| Show Camera3D Source # | |
| Eq Camera3D Source # | |
Constructors
| Camera2D | |
Fields | |
Instances
| Storable Camera2D Source # | |
Defined in Raylib.Types | |
| Show Camera2D Source # | |
| Eq Camera2D Source # | |
Constructors
| Mesh | |
Fields
| |
Instances
| Storable Shader Source # | |
| Show Shader Source # | |
| Eq Shader Source # | |
data MaterialMap Source #
Constructors
| MaterialMap | |
Fields | |
Instances
| Storable MaterialMap Source # | |
Defined in Raylib.Types Methods sizeOf :: MaterialMap -> Int # alignment :: MaterialMap -> Int # peekElemOff :: Ptr MaterialMap -> Int -> IO MaterialMap # pokeElemOff :: Ptr MaterialMap -> Int -> MaterialMap -> IO () # peekByteOff :: Ptr b -> Int -> IO MaterialMap # pokeByteOff :: Ptr b -> Int -> MaterialMap -> IO () # peek :: Ptr MaterialMap -> IO MaterialMap # poke :: Ptr MaterialMap -> MaterialMap -> IO () # | |
| Show MaterialMap Source # | |
Defined in Raylib.Types Methods showsPrec :: Int -> MaterialMap -> ShowS # show :: MaterialMap -> String # showList :: [MaterialMap] -> ShowS # | |
| Eq MaterialMap Source # | |
Defined in Raylib.Types | |
p'MaterialMap'color :: Ptr MaterialMap -> Ptr Color Source #
Constructors
| Material | |
Fields | |
Instances
| Storable Material Source # | |
Defined in Raylib.Types | |
| Show Material Source # | |
| Eq Material Source # | |
p'Material'maps :: Ptr Material -> Ptr (Ptr MaterialMap) Source #
Constructors
| Transform | |
Fields | |
Instances
| Storable Transform Source # | |
Defined in Raylib.Types | |
| Show Transform Source # | |
| Eq Transform Source # | |
Constructors
| BoneInfo | |
Fields
| |
Instances
| Storable BoneInfo Source # | |
Defined in Raylib.Types | |
| Show BoneInfo Source # | |
| Eq BoneInfo Source # | |
Constructors
| Model | |
Fields | |
Instances
| Storable Model Source # | |
| Show Model Source # | |
| Eq Model Source # | |
data ModelAnimation Source #
Constructors
| ModelAnimation | |
Instances
| Storable ModelAnimation Source # | |
Defined in Raylib.Types Methods sizeOf :: ModelAnimation -> Int # alignment :: ModelAnimation -> Int # peekElemOff :: Ptr ModelAnimation -> Int -> IO ModelAnimation # pokeElemOff :: Ptr ModelAnimation -> Int -> ModelAnimation -> IO () # peekByteOff :: Ptr b -> Int -> IO ModelAnimation # pokeByteOff :: Ptr b -> Int -> ModelAnimation -> IO () # peek :: Ptr ModelAnimation -> IO ModelAnimation # poke :: Ptr ModelAnimation -> ModelAnimation -> IO () # | |
| Show ModelAnimation Source # | |
Defined in Raylib.Types Methods showsPrec :: Int -> ModelAnimation -> ShowS # show :: ModelAnimation -> String # showList :: [ModelAnimation] -> ShowS # | |
| Eq ModelAnimation Source # | |
Defined in Raylib.Types Methods (==) :: ModelAnimation -> ModelAnimation -> Bool # (/=) :: ModelAnimation -> ModelAnimation -> Bool # | |
p'ModelAnimation'bones :: Ptr ModelAnimation -> Ptr (Ptr BoneInfo) Source #
p'ModelAnimation'framePoses :: Ptr ModelAnimation -> Ptr (Ptr (Ptr Transform)) Source #
Constructors
| Ray | |
Fields | |
data RayCollision Source #
Constructors
| RayCollision | |
Fields | |
Instances
| Storable RayCollision Source # | |
Defined in Raylib.Types Methods sizeOf :: RayCollision -> Int # alignment :: RayCollision -> Int # peekElemOff :: Ptr RayCollision -> Int -> IO RayCollision # pokeElemOff :: Ptr RayCollision -> Int -> RayCollision -> IO () # peekByteOff :: Ptr b -> Int -> IO RayCollision # pokeByteOff :: Ptr b -> Int -> RayCollision -> IO () # peek :: Ptr RayCollision -> IO RayCollision # poke :: Ptr RayCollision -> RayCollision -> IO () # | |
| Show RayCollision Source # | |
Defined in Raylib.Types Methods showsPrec :: Int -> RayCollision -> ShowS # show :: RayCollision -> String # showList :: [RayCollision] -> ShowS # | |
| Eq RayCollision Source # | |
Defined in Raylib.Types | |
p'RayCollision'hit :: Ptr RayCollision -> Ptr CInt Source #
data BoundingBox Source #
Constructors
| BoundingBox | |
Fields | |
Instances
| Storable BoundingBox Source # | |
Defined in Raylib.Types Methods sizeOf :: BoundingBox -> Int # alignment :: BoundingBox -> Int # peekElemOff :: Ptr BoundingBox -> Int -> IO BoundingBox # pokeElemOff :: Ptr BoundingBox -> Int -> BoundingBox -> IO () # peekByteOff :: Ptr b -> Int -> IO BoundingBox # pokeByteOff :: Ptr b -> Int -> BoundingBox -> IO () # peek :: Ptr BoundingBox -> IO BoundingBox # poke :: Ptr BoundingBox -> BoundingBox -> IO () # | |
| Show BoundingBox Source # | |
Defined in Raylib.Types Methods showsPrec :: Int -> BoundingBox -> ShowS # show :: BoundingBox -> String # showList :: [BoundingBox] -> ShowS # | |
| Eq BoundingBox Source # | |
Defined in Raylib.Types | |
p'BoundingBox'min :: Ptr BoundingBox -> Ptr Vector3 Source #
p'BoundingBox'max :: Ptr BoundingBox -> Ptr Vector3 Source #
Constructors
| Wave | |
Fields
| |
data RAudioBuffer Source #
Constructors
| RAudioBuffer |
data RAudioProcessor Source #
Constructors
| RAudioProcessor |
data AudioStream Source #
Constructors
| AudioStream | |
Instances
| Storable AudioStream Source # | |
Defined in Raylib.Types Methods sizeOf :: AudioStream -> Int # alignment :: AudioStream -> Int # peekElemOff :: Ptr AudioStream -> Int -> IO AudioStream # pokeElemOff :: Ptr AudioStream -> Int -> AudioStream -> IO () # peekByteOff :: Ptr b -> Int -> IO AudioStream # pokeByteOff :: Ptr b -> Int -> AudioStream -> IO () # peek :: Ptr AudioStream -> IO AudioStream # poke :: Ptr AudioStream -> AudioStream -> IO () # | |
| Show AudioStream Source # | |
Defined in Raylib.Types Methods showsPrec :: Int -> AudioStream -> ShowS # show :: AudioStream -> String # showList :: [AudioStream] -> ShowS # | |
| Eq AudioStream Source # | |
Defined in Raylib.Types | |
p'AudioStream'buffer :: Ptr AudioStream -> Ptr (Ptr RAudioBuffer) Source #
p'AudioStream'processor :: Ptr AudioStream -> Ptr (Ptr rAudioProcessor) Source #
Constructors
| Sound | |
Fields | |
Instances
| Storable Sound Source # | |
| Show Sound Source # | |
| Eq Sound Source # | |
p'Sound'stream :: Ptr Sound -> Ptr AudioStream Source #
Constructors
| Music | |
Fields
| |
Instances
| Storable Music Source # | |
| Show Music Source # | |
| Eq Music Source # | |
p'Musistream :: Ptr Music -> Ptr AudioStream Source #
data VrDeviceInfo Source #
Constructors
Instances
| Storable VrDeviceInfo Source # | |
Defined in Raylib.Types Methods sizeOf :: VrDeviceInfo -> Int # alignment :: VrDeviceInfo -> Int # peekElemOff :: Ptr VrDeviceInfo -> Int -> IO VrDeviceInfo # pokeElemOff :: Ptr VrDeviceInfo -> Int -> VrDeviceInfo -> IO () # peekByteOff :: Ptr b -> Int -> IO VrDeviceInfo # pokeByteOff :: Ptr b -> Int -> VrDeviceInfo -> IO () # peek :: Ptr VrDeviceInfo -> IO VrDeviceInfo # poke :: Ptr VrDeviceInfo -> VrDeviceInfo -> IO () # | |
| Show VrDeviceInfo Source # | |
Defined in Raylib.Types Methods showsPrec :: Int -> VrDeviceInfo -> ShowS # show :: VrDeviceInfo -> String # showList :: [VrDeviceInfo] -> ShowS # | |
| Eq VrDeviceInfo Source # | |
Defined in Raylib.Types | |
data VrStereoConfig Source #
Constructors
Instances
| Storable VrStereoConfig Source # | |
Defined in Raylib.Types Methods sizeOf :: VrStereoConfig -> Int # alignment :: VrStereoConfig -> Int # peekElemOff :: Ptr VrStereoConfig -> Int -> IO VrStereoConfig # pokeElemOff :: Ptr VrStereoConfig -> Int -> VrStereoConfig -> IO () # peekByteOff :: Ptr b -> Int -> IO VrStereoConfig # pokeByteOff :: Ptr b -> Int -> VrStereoConfig -> IO () # peek :: Ptr VrStereoConfig -> IO VrStereoConfig # poke :: Ptr VrStereoConfig -> VrStereoConfig -> IO () # | |
| Show VrStereoConfig Source # | |
Defined in Raylib.Types Methods showsPrec :: Int -> VrStereoConfig -> ShowS # show :: VrStereoConfig -> String # showList :: [VrStereoConfig] -> ShowS # | |
| Eq VrStereoConfig Source # | |
Defined in Raylib.Types Methods (==) :: VrStereoConfig -> VrStereoConfig -> Bool # (/=) :: VrStereoConfig -> VrStereoConfig -> Bool # | |
data FilePathList Source #
Constructors
| FilePathList | |
Fields | |
Instances
| Storable FilePathList Source # | |
Defined in Raylib.Types Methods sizeOf :: FilePathList -> Int # alignment :: FilePathList -> Int # peekElemOff :: Ptr FilePathList -> Int -> IO FilePathList # pokeElemOff :: Ptr FilePathList -> Int -> FilePathList -> IO () # peekByteOff :: Ptr b -> Int -> IO FilePathList # pokeByteOff :: Ptr b -> Int -> FilePathList -> IO () # peek :: Ptr FilePathList -> IO FilePathList # poke :: Ptr FilePathList -> FilePathList -> IO () # | |
| Show FilePathList Source # | |
Defined in Raylib.Types Methods showsPrec :: Int -> FilePathList -> ShowS # show :: FilePathList -> String # showList :: [FilePathList] -> ShowS # | |
| Eq FilePathList Source # | |
Defined in Raylib.Types | |
p'FilePathList'paths :: Ptr FilePathList -> Ptr (Ptr CString) Source #