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

Raylib.Core.Textures

Description

Bindings to rtextures

Synopsis

High level

loadImage :: String -> IO Image Source #

loadImageRaw :: String -> Int -> Int -> Int -> Int -> IO Image Source #

loadImageAnim :: String -> IO (Image, Int) Source #

Returns the animation and the number of frames in a tuple

loadImageAnimFromMemory :: String -> [Integer] -> IO (Image, Int) Source #

loadImageFromMemory :: String -> [Integer] -> IO Image Source #

isImageReady :: Image -> IO Bool Source #

exportImage :: Image -> String -> IO Bool Source #

exportImageToMemory :: Image -> String -> IO [Word8] Source #

exportImageAsCode :: Image -> String -> IO Bool Source #

genImageGradientRadial :: Int -> Int -> Float -> Color -> Color -> IO Image Source #

genImageGradientSquare :: Int -> Int -> Float -> Color -> Color -> IO Image Source #

genImageChecked :: Int -> Int -> Int -> Int -> Color -> Color -> IO Image Source #

genImageWhiteNoise :: Int -> Int -> Float -> IO Image Source #

genImagePerlinNoise :: Int -> Int -> Int -> Int -> Float -> IO Image Source #

genImageText :: Int -> Int -> String -> IO Image Source #

imageText :: String -> Int -> Color -> IO Image Source #

imageTextEx :: Font -> String -> Float -> Float -> Color -> IO Image Source #

imageAlphaCrop :: Image -> Float -> IO Image Source #

imageAlphaClear :: Image -> Color -> Float -> IO Image Source #

imageDither :: Image -> Int -> Int -> Int -> Int -> IO Image Source #

imageDrawLine :: Image -> Int -> Int -> Int -> Int -> Color -> IO Image Source #

imageDrawText :: Image -> String -> Int -> Int -> Int -> Color -> IO Image Source #

imageDrawTextEx :: Image -> Font -> String -> Vector2 -> Float -> Float -> Color -> IO Image Source #

loadTexture :: String -> IO Texture Source #

unloadTexture :: Texture -> WindowResources -> IO () Source #

Unloads a managed texture from GPU memory (VRAM)

unloadRenderTexture :: RenderTexture -> WindowResources -> IO () Source #

Unloads a managed render texture from GPU memory (VRAM)

updateTexture :: Texture -> Ptr () -> IO () Source #

drawTexture :: Texture -> Int -> Int -> Color -> IO () Source #

drawTextureEx :: Texture -> Vector2 -> Float -> Float -> Color -> IO () Source #

drawTexturePro :: Texture -> Rectangle -> Rectangle -> Vector2 -> Float -> Color -> IO () Source #

fade :: Color -> Float -> Color Source #

colorFromHSV :: Float -> Float -> Float -> Color Source #

colorAlpha :: Color -> Float -> Color Source #

colorLerp :: Color -> Color -> Float -> Color Source #

getColor :: Integer -> Color Source #

setPixelColor :: Ptr () -> Color -> PixelFormat -> IO () Source #

Native

c'loadImage :: CString -> IO (Ptr Image) Source #

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

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

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

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

c'exportImage :: Ptr Image -> CString -> IO CBool Source #

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

c'exportImageAsCode :: Ptr Image -> CString -> IO CBool Source #

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

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

c'genImageGradientRadial :: CInt -> CInt -> CFloat -> Ptr Color -> Ptr Color -> IO (Ptr Image) Source #

c'genImageGradientSquare :: CInt -> CInt -> CFloat -> Ptr Color -> Ptr Color -> IO (Ptr Image) Source #

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

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

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

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

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

c'imageText :: CString -> CInt -> Ptr Color -> IO (Ptr Image) Source #

c'imageTextEx :: Ptr Font -> CString -> CFloat -> CFloat -> Ptr Color -> IO (Ptr Image) Source #

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

c'imageAlphaCrop :: Ptr Image -> CFloat -> IO () Source #

c'imageAlphaClear :: Ptr Image -> Ptr Color -> CFloat -> IO () Source #

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

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

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

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

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

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

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

c'imageColorContrast :: Ptr Image -> CFloat -> IO () Source #

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

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

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

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

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

c'imageDrawCircleV :: Ptr Image -> Ptr Vector2 -> CInt -> Ptr Color -> IO () Source #

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

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

c'imageDrawText :: Ptr Image -> CString -> CInt -> CInt -> CInt -> Ptr Color -> IO () Source #

c'imageDrawTextEx :: Ptr Image -> Ptr Font -> CString -> Ptr Vector2 -> CFloat -> CFloat -> Ptr Color -> IO () Source #

c'loadTexture :: CString -> IO (Ptr Texture) Source #

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

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

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

c'drawTexture :: Ptr Texture -> CInt -> CInt -> Ptr Color -> IO () Source #

c'drawTextureEx :: Ptr Texture -> Ptr Vector2 -> CFloat -> CFloat -> Ptr Color -> IO () Source #

c'fade :: Ptr Color -> CFloat -> IO (Ptr Color) Source #

c'colorToInt :: Ptr Color -> IO CInt Source #

c'colorFromHSV :: CFloat -> CFloat -> CFloat -> IO (Ptr Color) Source #

c'colorBrightness :: Ptr Color -> CFloat -> IO (Ptr Color) Source #

c'colorContrast :: Ptr Color -> CFloat -> IO (Ptr Color) Source #

c'colorAlpha :: Ptr Color -> CFloat -> IO (Ptr Color) Source #

c'colorLerp :: Ptr Color -> Ptr Color -> CFloat -> IO (Ptr Color) Source #

c'getColor :: CUInt -> IO (Ptr Color) Source #

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

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