h-raylib-5.5.1.0: Raylib bindings for Haskell
Safe HaskellNone
LanguageHaskell2010

Raylib.Types.Core

Description

Bindings for types used in all raylib modules

Synopsis

Enumerations

data KeyboardKey Source #

Instances

Instances details
Enum KeyboardKey Source # 
Instance details

Defined in Raylib.Types.Core

Show KeyboardKey Source # 
Instance details

Defined in Raylib.Types.Core

Methods

showsPrec :: Int -> KeyboardKey -> ShowS

show :: KeyboardKey -> String

showList :: [KeyboardKey] -> ShowS

Eq KeyboardKey Source # 
Instance details

Defined in Raylib.Types.Core

Methods

(==) :: KeyboardKey -> KeyboardKey -> Bool

(/=) :: KeyboardKey -> KeyboardKey -> Bool

data GamepadButton Source #

data Gesture Source #

Instances

Instances details
Enum Gesture Source # 
Instance details

Defined in Raylib.Types.Core

Show Gesture Source # 
Instance details

Defined in Raylib.Types.Core

Methods

showsPrec :: Int -> Gesture -> ShowS

show :: Gesture -> String

showList :: [Gesture] -> ShowS

Eq Gesture Source # 
Instance details

Defined in Raylib.Types.Core

Methods

(==) :: Gesture -> Gesture -> Bool

(/=) :: Gesture -> Gesture -> Bool

Structures

type Vector2 = V2 Float Source #

type Vector3 = V3 Float Source #

type Vector4 = V4 Float Source #

pattern Vector2 :: Float -> Float -> Vector2 Source #

pattern Vector3 :: Float -> Float -> Float -> Vector3 Source #

pattern Vector4 :: a -> a -> a -> a -> V4 a Source #

vector4'x :: V4 a -> a Source #

vector4'y :: V4 a -> a Source #

vector4'z :: V4 a -> a Source #

vector4'w :: V4 a -> a Source #

data Matrix Source #

Constructors

Matrix 

Fields

Instances

Instances details
Storable Matrix Source # 
Instance details

Defined in Raylib.Types.Core

Methods

sizeOf :: Matrix -> Int

alignment :: Matrix -> Int

peekElemOff :: Ptr Matrix -> Int -> IO Matrix

pokeElemOff :: Ptr Matrix -> Int -> Matrix -> IO ()

peekByteOff :: Ptr b -> Int -> IO Matrix

pokeByteOff :: Ptr b -> Int -> Matrix -> IO ()

peek :: Ptr Matrix -> IO Matrix

poke :: Ptr Matrix -> Matrix -> IO ()

Show Matrix Source # 
Instance details

Defined in Raylib.Types.Core

Methods

showsPrec :: Int -> Matrix -> ShowS

show :: Matrix -> String

showList :: [Matrix] -> ShowS

Eq Matrix Source # 
Instance details

Defined in Raylib.Types.Core

Methods

(==) :: Matrix -> Matrix -> Bool

(/=) :: Matrix -> Matrix -> Bool

Freeable Matrix Source # 
Instance details

Defined in Raylib.Types.Core

Methods

rlFreeDependents :: Matrix -> Ptr Matrix -> IO () Source #

rlFree :: Matrix -> Ptr Matrix -> IO () Source #

data Color Source #

Constructors

Color 

Instances

Instances details
Storable Color Source # 
Instance details

Defined in Raylib.Types.Core

Methods

sizeOf :: Color -> Int

alignment :: Color -> Int

peekElemOff :: Ptr Color -> Int -> IO Color

pokeElemOff :: Ptr Color -> Int -> Color -> IO ()

peekByteOff :: Ptr b -> Int -> IO Color

pokeByteOff :: Ptr b -> Int -> Color -> IO ()

peek :: Ptr Color -> IO Color

poke :: Ptr Color -> Color -> IO ()

Show Color Source # 
Instance details

Defined in Raylib.Types.Core

Methods

showsPrec :: Int -> Color -> ShowS

show :: Color -> String

showList :: [Color] -> ShowS

Eq Color Source # 
Instance details

Defined in Raylib.Types.Core

Methods

(==) :: Color -> Color -> Bool

(/=) :: Color -> Color -> Bool

Freeable Color Source # 
Instance details

Defined in Raylib.Types.Core

Methods

rlFreeDependents :: Color -> Ptr Color -> IO () Source #

rlFree :: Color -> Ptr Color -> IO () Source #

data Rectangle Source #

Constructors

Rectangle 

Fields

Instances

Instances details
Storable Rectangle Source # 
Instance details

Defined in Raylib.Types.Core

Show Rectangle Source # 
Instance details

Defined in Raylib.Types.Core

Methods

showsPrec :: Int -> Rectangle -> ShowS

show :: Rectangle -> String

showList :: [Rectangle] -> ShowS

Eq Rectangle Source # 
Instance details

Defined in Raylib.Types.Core

Methods

(==) :: Rectangle -> Rectangle -> Bool

(/=) :: Rectangle -> Rectangle -> Bool

Freeable Rectangle Source # 
Instance details

Defined in Raylib.Types.Core

data FilePathList Source #

Constructors

FilePathList 

Fields

Instances

Instances details
Storable FilePathList Source # 
Instance details

Defined in Raylib.Types.Core

Show FilePathList Source # 
Instance details

Defined in Raylib.Types.Core

Methods

showsPrec :: Int -> FilePathList -> ShowS

show :: FilePathList -> String

showList :: [FilePathList] -> ShowS

Eq FilePathList Source # 
Instance details

Defined in Raylib.Types.Core

Methods

(==) :: FilePathList -> FilePathList -> Bool

(/=) :: FilePathList -> FilePathList -> Bool

Freeable FilePathList Source # 
Instance details

Defined in Raylib.Types.Core

data AutomationEventList Source #

Pointer utilities

p'color'r :: Ptr Color -> Ptr CUChar Source #

p'color'g :: Ptr Color -> Ptr CUChar Source #

p'color'b :: Ptr Color -> Ptr CUChar Source #

p'color'a :: Ptr Color -> Ptr CUChar Source #

Callbacks

type TraceLogCallback = TraceLogLevel -> String -> IO () Source #

type LoadFileDataCallback = String -> IO [Integer] Source #

type SaveFileDataCallback a = String -> Ptr a -> Integer -> IO Bool Source #

type LoadFileTextCallback = String -> IO String Source #

type SaveFileTextCallback = String -> String -> IO Bool Source #

type C'TraceLogCallback = FunPtr (CInt -> CString -> IO ()) Source #

type C'LoadFileDataCallback = FunPtr (CString -> Ptr CUInt -> IO (Ptr CUChar)) Source #

type C'SaveFileDataCallback = FunPtr (CString -> Ptr () -> CUInt -> IO CInt) Source #

type C'LoadFileTextCallback = FunPtr (CString -> IO CString) Source #

type C'SaveFileTextCallback = FunPtr (CString -> CString -> IO CInt) Source #