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

Raylib.Core

Description

Bindings to rcore

Synopsis

High level

initWindow Source #

Arguments

:: Int 
-> Int 
-> String 
-> IO WindowResources

This value can be used with managed when loading resources for automatic memory management.

initWindowUnmanaged :: Int -> Int -> String -> IO () Source #

setWindowTitle :: String -> IO () Source #

setWindowSize :: Int -> Int -> IO () Source #

setWindowOpacity :: Float -> IO () Source #

getMonitorName :: Int -> IO String Source #

setClipboardText :: String -> IO () Source #

waitTime :: Double -> IO () Source #

endMode2D :: IO () Source #

endMode3D :: IO () Source #

beginScissorMode :: Int -> Int -> Int -> Int -> IO () Source #

loadShader :: Maybe String -> Maybe String -> IO Shader Source #

loadShaderFromMemory :: Maybe String -> Maybe String -> IO Shader Source #

unloadShader :: Shader -> WindowResources -> IO () Source #

Unloads a managed shader from GPU memory (VRAM)

getScreenToWorldRayEx :: Vector2 -> Camera3D -> Float -> Float -> Ray Source #

setTargetFPS :: Int -> IO () Source #

getFrameTime :: IO Float Source #

getTime :: IO Double Source #

setRandomSeed :: Integer -> IO () Source #

loadRandomSequence :: Integer -> Int -> Int -> IO [Int] Source #

takeScreenshot :: String -> IO () Source #

traceLog :: TraceLogLevel -> String -> IO () Source #

openURL :: String -> IO () Source #

loadFileData :: String -> IO [Integer] Source #

saveFileData :: Storable a => String -> Ptr a -> Integer -> IO Bool Source #

exportDataAsCode :: [Integer] -> Integer -> String -> IO Bool Source #

loadFileText :: String -> IO String Source #

saveFileText :: String -> String -> IO Bool Source #

fileExists :: String -> IO Bool Source #

directoryExists :: String -> IO Bool Source #

isFileExtension :: String -> String -> IO Bool Source #

getFileLength :: String -> IO Bool Source #

getFileExtension :: String -> IO String Source #

getFileName :: String -> IO String Source #

getFileNameWithoutExt :: String -> IO String Source #

getDirectoryPath :: String -> IO String Source #

getPrevDirectoryPath :: String -> IO String Source #

makeDirectory :: String -> IO Bool Source #

changeDirectory :: String -> IO Bool Source #

isPathFile :: String -> IO Bool Source #

isFileNameValid :: String -> IO Bool Source #

loadDirectoryFilesEx :: String -> String -> Bool -> IO FilePathList Source #

getFileModTime :: String -> IO Integer Source #

compressData :: [Integer] -> IO [Integer] Source #

decompressData :: [Integer] -> IO [Integer] Source #

encodeDataBase64 :: [Integer] -> IO [Integer] Source #

decodeDataBase64 :: [Integer] -> IO [Integer] Source #

unloadAutomationEventList :: AutomationEventListRef -> WindowResources -> IO () Source #

Unloads a managed automation event list from CPU memory (RAM)

isKeyUp :: KeyboardKey -> IO Bool Source #

getGamepadName :: Int -> IO String Source #

setGamepadMappings :: String -> IO Int Source #

setGamepadVibration :: Int -> Float -> Float -> IO () Source #

setMouseOffset :: Int -> Int -> IO () Source #

setMouseScale :: Float -> Float -> IO () Source #

Native

c'initWindow :: CInt -> CInt -> CString -> IO () Source #

c'isWindowState :: CUInt -> IO CBool Source #

c'setWindowState :: CUInt -> IO () Source #

c'clearWindowState :: CUInt -> IO () Source #

c'setWindowIcons :: Ptr Image -> CInt -> IO () Source #

c'setWindowTitle :: CString -> IO () Source #

c'setWindowPosition :: CInt -> CInt -> IO () Source #

c'setWindowMonitor :: CInt -> IO () Source #

c'setWindowMinSize :: CInt -> CInt -> IO () Source #

c'setWindowMaxSize :: CInt -> CInt -> IO () Source #

c'setWindowSize :: CInt -> CInt -> IO () Source #

c'setWindowOpacity :: CFloat -> IO () Source #

c'getMonitorWidth :: CInt -> IO CInt Source #

c'getMonitorHeight :: CInt -> IO CInt Source #

c'getMonitorRefreshRate :: CInt -> IO CInt Source #

c'getMonitorName :: CInt -> IO CString Source #

c'setClipboardText :: CString -> IO () Source #

c'waitTime :: CDouble -> IO () Source #

c'beginBlendMode :: CInt -> IO () Source #

c'beginScissorMode :: CInt -> CInt -> CInt -> CInt -> IO () Source #

c'loadShader :: CString -> CString -> IO (Ptr Shader) Source #

c'loadShaderFromMemory :: CString -> CString -> IO (Ptr Shader) Source #

c'getShaderLocation :: Ptr Shader -> CString -> IO CInt Source #

c'getShaderLocationAttrib :: Ptr Shader -> CString -> IO CInt Source #

c'setShaderValue :: Ptr Shader -> CInt -> Ptr () -> CInt -> IO () Source #

c'setShaderValueV :: Ptr Shader -> CInt -> Ptr () -> CInt -> CInt -> IO () Source #

c'getScreenToWorldRayEx :: Ptr Vector2 -> Ptr Camera3D -> CFloat -> CFloat -> IO (Ptr Ray) Source #

c'setTargetFPS :: CInt -> IO () Source #

c'getFPS :: IO CInt Source #

c'getFrameTime :: IO CFloat Source #

c'getTime :: IO CDouble Source #

c'setRandomSeed :: CUInt -> IO () Source #

c'getRandomValue :: CInt -> CInt -> IO CInt Source #

c'loadRandomSequence :: CUInt -> CInt -> CInt -> IO (Ptr CInt) Source #

c'takeScreenshot :: CString -> IO () Source #

c'setConfigFlags :: CUInt -> IO () Source #

c'traceLog :: CInt -> CString -> IO () Source #

c'setTraceLogLevel :: CInt -> IO () Source #

c'memAlloc :: CInt -> IO (Ptr ()) Source #

c'memRealloc :: Ptr () -> CInt -> IO (Ptr ()) Source #

c'memFree :: Ptr () -> IO () Source #

c'openURL :: CString -> IO () Source #

c'loadFileData :: CString -> Ptr CInt -> IO (Ptr CUChar) Source #

c'unloadFileData :: Ptr CUChar -> IO () Source #

c'saveFileData :: CString -> Ptr () -> CInt -> IO CBool Source #

c'exportDataAsCode :: Ptr CUChar -> CInt -> CString -> IO CBool Source #

c'loadFileText :: CString -> IO CString Source #

c'unloadFileText :: CString -> IO () Source #

c'saveFileText :: CString -> CString -> IO CBool Source #

c'fileExists :: CString -> IO CBool Source #

c'directoryExists :: CString -> IO CBool Source #

c'isFileExtension :: CString -> CString -> IO CBool Source #

c'getFileLength :: CString -> IO CBool Source #

c'getFileExtension :: CString -> IO CString Source #

c'getFileName :: CString -> IO CString Source #

c'getFileNameWithoutExt :: CString -> IO CString Source #

c'getDirectoryPath :: CString -> IO CString Source #

c'getPrevDirectoryPath :: CString -> IO CString Source #

c'makeDirectory :: CString -> IO CInt Source #

c'changeDirectory :: CString -> IO CBool Source #

c'isPathFile :: CString -> IO CBool Source #

c'isFileNameValid :: CString -> IO CBool Source #

c'loadDirectoryFilesEx :: CString -> CString -> CInt -> IO (Ptr FilePathList) Source #

c'getFileModTime :: CString -> IO CLong Source #

c'compressData :: Ptr CUChar -> CInt -> Ptr CInt -> IO (Ptr CUChar) Source #

c'decompressData :: Ptr CUChar -> CInt -> Ptr CInt -> IO (Ptr CUChar) Source #

c'encodeDataBase64 :: Ptr CUChar -> CInt -> Ptr CInt -> IO CString Source #

c'decodeDataBase64 :: Ptr CUChar -> Ptr CInt -> IO (Ptr CUChar) Source #

c'isKeyPressed :: CInt -> IO CBool Source #

c'isKeyPressedRepeat :: CInt -> IO CBool Source #

c'isKeyDown :: CInt -> IO CBool Source #

c'isKeyReleased :: CInt -> IO CBool Source #

c'isKeyUp :: CInt -> IO CBool Source #

c'setExitKey :: CInt -> IO () Source #

c'isGamepadAvailable :: CInt -> IO CBool Source #

c'getGamepadName :: CInt -> IO CString Source #

c'isGamepadButtonPressed :: CInt -> CInt -> IO CBool Source #

c'isGamepadButtonDown :: CInt -> CInt -> IO CBool Source #

c'isGamepadButtonReleased :: CInt -> CInt -> IO CBool Source #

c'isGamepadButtonUp :: CInt -> CInt -> IO CBool Source #

c'getGamepadAxisCount :: CInt -> IO CInt Source #

c'getGamepadAxisMovement :: CInt -> CInt -> IO CFloat Source #

c'setGamepadMappings :: CString -> IO CInt Source #

c'setGamepadVibration :: CInt -> CFloat -> CFloat -> IO () Source #

c'isMouseButtonPressed :: CInt -> IO CBool Source #

c'isMouseButtonDown :: CInt -> IO CBool Source #

c'isMouseButtonReleased :: CInt -> IO CBool Source #

c'isMouseButtonUp :: CInt -> IO CBool Source #

c'getMouseX :: IO CInt Source #

c'getMouseY :: IO CInt Source #

c'setMousePosition :: CInt -> CInt -> IO () Source #

c'setMouseOffset :: CInt -> CInt -> IO () Source #

c'setMouseScale :: CFloat -> CFloat -> IO () Source #

c'setMouseCursor :: CInt -> IO () Source #

c'getTouchX :: IO CInt Source #

c'getTouchY :: IO CInt Source #

c'getTouchPointId :: CInt -> IO CInt Source #

c'setGesturesEnabled :: CUInt -> IO () Source #

c'isGestureDetected :: CUInt -> IO CBool Source #

Callbacks

mk'loadFileDataCallback :: (CString -> Ptr CUInt -> IO (Ptr CUChar)) -> IO C'LoadFileDataCallback Source #

mk'saveFileDataCallback :: (CString -> Ptr () -> CUInt -> IO CInt) -> IO C'SaveFileDataCallback Source #

mk'loadFileTextCallback :: (CString -> IO CString) -> IO C'LoadFileTextCallback Source #

mk'saveFileTextCallback :: (CString -> CString -> IO CInt) -> IO C'SaveFileTextCallback Source #