{-# OPTIONS -Wall #-}
{-# LANGUAGE TemplateHaskell #-}
module Raylib.Core.Textures
  ( 
    loadImage,
    loadImageRaw,
    loadImageSvg,
    loadImageAnim,
    loadImageAnimFromMemory,
    loadImageFromMemory,
    loadImageFromTexture,
    loadImageFromScreen,
    isImageReady,
    exportImage,
    exportImageToMemory,
    exportImageAsCode,
    genImageColor,
    genImageGradientLinear,
    genImageGradientRadial,
    genImageGradientSquare,
    genImageChecked,
    genImageWhiteNoise,
    genImagePerlinNoise,
    genImageCellular,
    genImageText,
    imageCopy,
    imageFromImage,
    imageText,
    imageTextEx,
    imageFormat,
    imageToPOT,
    imageCrop,
    imageAlphaCrop,
    imageAlphaClear,
    imageAlphaMask,
    imageAlphaPremultiply,
    imageBlurGaussian,
    imageKernelConvolution,
    imageResize,
    imageResizeNN,
    imageResizeCanvas,
    imageMipmaps,
    imageDither,
    imageFlipVertical,
    imageFlipHorizontal,
    imageRotate,
    imageRotateCW,
    imageRotateCCW,
    imageColorTint,
    imageColorInvert,
    imageColorGrayscale,
    imageColorContrast,
    imageColorBrightness,
    imageColorReplace,
    loadImageColors,
    loadImagePalette,
    getImageAlphaBorder,
    getImageColor,
    imageClearBackground,
    imageDrawPixel,
    imageDrawPixelV,
    imageDrawLine,
    imageDrawLineV,
    imageDrawCircle,
    imageDrawCircleV,
    imageDrawCircleLines,
    imageDrawCircleLinesV,
    imageDrawRectangle,
    imageDrawRectangleV,
    imageDrawRectangleRec,
    imageDrawRectangleLines,
    imageDraw,
    imageDrawText,
    imageDrawTextEx,
    loadTexture,
    loadTextureFromImage,
    loadTextureCubemap,
    loadRenderTexture,
    isTextureReady,
    isRenderTextureReady,
    unloadTexture,
    unloadRenderTexture,
    updateTexture,
    updateTextureRec,
    genTextureMipmaps,
    setTextureFilter,
    setTextureWrap,
    drawTexture,
    drawTextureV,
    drawTextureEx,
    drawTextureRec,
    drawTexturePro,
    drawTextureNPatch,
    fade,
    colorToInt,
    colorNormalize,
    colorFromNormalized,
    colorToHSV,
    colorFromHSV,
    colorTint,
    colorBrightness,
    colorContrast,
    colorAlpha,
    colorAlphaBlend,
    getColor,
    getPixelColor,
    setPixelColor,
    getPixelDataSize,
    
    c'loadImage,
    c'loadImageRaw,
    c'loadImageSvg,
    c'loadImageAnim,
    c'loadImageAnimFromMemory,
    c'loadImageFromMemory,
    c'loadImageFromTexture,
    c'loadImageFromScreen,
    c'isImageReady,
    c'unloadImage,
    c'exportImage,
    c'exportImageToMemory,
    c'exportImageAsCode,
    c'genImageColor,
    c'genImageGradientLinear,
    c'genImageGradientRadial,
    c'genImageGradientSquare,
    c'genImageChecked,
    c'genImageWhiteNoise,
    c'genImagePerlinNoise,
    c'genImageCellular,
    c'genImageText,
    c'imageCopy,
    c'imageFromImage,
    c'imageText,
    c'imageTextEx,
    c'imageFormat,
    c'imageToPOT,
    c'imageCrop,
    c'imageAlphaCrop,
    c'imageAlphaClear,
    c'imageAlphaMask,
    c'imageAlphaPremultiply,
    c'imageBlurGaussian,
    c'imageKernelConvolution,
    c'imageResize,
    c'imageResizeNN,
    c'imageResizeCanvas,
    c'imageMipmaps,
    c'imageDither,
    c'imageFlipVertical,
    c'imageFlipHorizontal,
    c'imageRotate,
    c'imageRotateCW,
    c'imageRotateCCW,
    c'imageColorTint,
    c'imageColorInvert,
    c'imageColorGrayscale,
    c'imageColorContrast,
    c'imageColorBrightness,
    c'imageColorReplace,
    c'loadImageColors,
    c'loadImagePalette,
    c'getImageAlphaBorder,
    c'getImageColor,
    c'imageClearBackground,
    c'imageDrawPixel,
    c'imageDrawPixelV,
    c'imageDrawLine,
    c'imageDrawLineV,
    c'imageDrawCircle,
    c'imageDrawCircleV,
    c'imageDrawCircleLines,
    c'imageDrawCircleLinesV,
    c'imageDrawRectangle,
    c'imageDrawRectangleV,
    c'imageDrawRectangleRec,
    c'imageDrawRectangleLines,
    c'imageDraw,
    c'imageDrawText,
    c'imageDrawTextEx,
    c'loadTexture,
    c'loadTextureFromImage,
    c'loadTextureCubemap,
    c'loadRenderTexture,
    c'isTextureReady,
    c'unloadTexture,
    c'isRenderTextureReady,
    c'unloadRenderTexture,
    c'updateTexture,
    c'updateTextureRec,
    c'genTextureMipmaps,
    c'setTextureFilter,
    c'setTextureWrap,
    c'drawTexture,
    c'drawTextureV,
    c'drawTextureEx,
    c'drawTextureRec,
    c'drawTexturePro,
    c'drawTextureNPatch,
    c'fade,
    c'colorToInt,
    c'colorNormalize,
    c'colorFromNormalized,
    c'colorToHSV,
    c'colorFromHSV,
    c'colorTint,
    c'colorBrightness,
    c'colorContrast,
    c'colorAlpha,
    c'colorAlphaBlend,
    c'getColor,
    c'getPixelColor,
    c'setPixelColor
  )
where
import Control.Monad ((<=<))
import Data.Word (Word8)
import Foreign
  ( Ptr,
    Storable (peek, sizeOf),
    toBool,
  )
import Foreign.C
  ( CBool (..),
    CFloat (..),
    CInt (..),
    CString,
    CUChar (..),
    CUInt (..),
    withCString,
  )
import GHC.IO (unsafePerformIO)
import Raylib.Internal (WindowResources, addFrameBuffer, addTextureId, unloadSingleFrameBuffer, unloadSingleTexture)
import qualified Raylib.Internal as I
import Raylib.Internal.Foreign
  ( pop,
    popCArray,
    withFreeable,
    withFreeableArray,
    withFreeableArrayLen,
  )
import Raylib.Internal.TH (genNative)
import Raylib.Types
  ( Color,
    CubemapLayout,
    Font,
    Image (image'height, image'width),
    NPatchInfo,
    PixelFormat,
    Rectangle,
    RenderTexture (renderTexture'id, renderTexture'texture),
    Texture (texture'id),
    TextureFilter,
    TextureWrap,
    Vector2,
    Vector3,
    Vector4,
  )
$( genNative
     [ ("c'loadImage", "LoadImage_", "rl_bindings.h", [t|CString -> IO (Ptr Image)|], False),
       ("c'loadImageRaw", "LoadImageRaw_", "rl_bindings.h", [t|CString -> CInt -> CInt -> CInt -> CInt -> IO (Ptr Image)|], False),
       ("c'loadImageSvg", "LoadImageSvg_", "rl_bindings.h", [t|CString -> CInt -> CInt -> IO (Ptr Image)|], False),
       ("c'loadImageAnim", "LoadImageAnim_", "rl_bindings.h", [t|CString -> Ptr CInt -> IO (Ptr Image)|], False),
       ("c'loadImageAnimFromMemory", "LoadImageAnimFromMemory_", "rl_bindings.h", [t|CString -> Ptr CUChar -> CInt -> Ptr CInt -> IO (Ptr Image)|], False),
       ("c'loadImageFromMemory", "LoadImageFromMemory_", "rl_bindings.h", [t|CString -> Ptr CUChar -> CInt -> IO (Ptr Image)|], False),
       ("c'loadImageFromTexture", "LoadImageFromTexture_", "rl_bindings.h", [t|Ptr Texture -> IO (Ptr Image)|], False),
       ("c'loadImageFromScreen", "LoadImageFromScreen_", "rl_bindings.h", [t|IO (Ptr Image)|], False),
       ("c'isImageReady", "IsImageReady_", "rl_bindings.h", [t|Ptr Image -> IO CBool|], False),
       ("c'unloadImage", "UnloadImage_", "rl_bindings.h", [t|Ptr Image -> IO ()|], False),
       ("c'exportImage", "ExportImage_", "rl_bindings.h", [t|Ptr Image -> CString -> IO CBool|], False),
       ("c'exportImageToMemory", "ExportImageToMemory_", "rl_bindings.h", [t|Ptr Image -> CString -> Ptr CInt -> IO (Ptr CUChar)|], False),
       ("c'exportImageAsCode", "ExportImageAsCode_", "rl_bindings.h", [t|Ptr Image -> CString -> IO CBool|], False),
       ("c'genImageColor", "GenImageColor_", "rl_bindings.h", [t|CInt -> CInt -> Ptr Color -> IO (Ptr Image)|], False),
       ("c'genImageGradientLinear", "GenImageGradientLinear_", "rl_bindings.h", [t|CInt -> CInt -> CInt -> Ptr Color -> Ptr Color -> IO (Ptr Image)|], False),
       ("c'genImageGradientRadial", "GenImageGradientRadial_", "rl_bindings.h", [t|CInt -> CInt -> CFloat -> Ptr Color -> Ptr Color -> IO (Ptr Image)|], False),
       ("c'genImageGradientSquare", "GenImageGradientSquare_", "rl_bindings.h", [t|CInt -> CInt -> CFloat -> Ptr Color -> Ptr Color -> IO (Ptr Image)|], False),
       ("c'genImageChecked", "GenImageChecked_", "rl_bindings.h", [t|CInt -> CInt -> CInt -> CInt -> Ptr Color -> Ptr Color -> IO (Ptr Image)|], False),
       ("c'genImageWhiteNoise", "GenImageWhiteNoise_", "rl_bindings.h", [t|CInt -> CInt -> CFloat -> IO (Ptr Image)|], False),
       ("c'genImagePerlinNoise", "GenImagePerlinNoise_", "rl_bindings.h", [t|CInt -> CInt -> CInt -> CInt -> CFloat -> IO (Ptr Image)|], False),
       ("c'genImageCellular", "GenImageCellular_", "rl_bindings.h", [t|CInt -> CInt -> CInt -> IO (Ptr Image)|], False),
       ("c'genImageText", "GenImageText_", "rl_bindings.h", [t|CInt -> CInt -> CString -> IO (Ptr Image)|], False),
       ("c'imageCopy", "ImageCopy_", "rl_bindings.h", [t|Ptr Image -> IO (Ptr Image)|], False),
       ("c'imageFromImage", "ImageFromImage_", "rl_bindings.h", [t|Ptr Image -> Ptr Rectangle -> IO (Ptr Image)|], False),
       ("c'imageText", "ImageText_", "rl_bindings.h", [t|CString -> CInt -> Ptr Color -> IO (Ptr Image)|], False),
       ("c'imageTextEx", "ImageTextEx_", "rl_bindings.h", [t|Ptr Font -> CString -> CFloat -> CFloat -> Ptr Color -> IO (Ptr Image)|], False),
       ("c'imageFormat", "ImageFormat_", "rl_bindings.h", [t|Ptr Image -> CInt -> IO ()|], False),
       ("c'imageToPOT", "ImageToPOT_", "rl_bindings.h", [t|Ptr Image -> Ptr Color -> IO ()|], False),
       ("c'imageCrop", "ImageCrop_", "rl_bindings.h", [t|Ptr Image -> Ptr Rectangle -> IO ()|], False),
       ("c'imageAlphaCrop", "ImageAlphaCrop_", "rl_bindings.h", [t|Ptr Image -> CFloat -> IO ()|], False),
       ("c'imageAlphaClear", "ImageAlphaClear_", "rl_bindings.h", [t|Ptr Image -> Ptr Color -> CFloat -> IO ()|], False),
       ("c'imageAlphaMask", "ImageAlphaMask_", "rl_bindings.h", [t|Ptr Image -> Ptr Image -> IO ()|], False),
       ("c'imageAlphaPremultiply", "ImageAlphaPremultiply_", "rl_bindings.h", [t|Ptr Image -> IO ()|], False),
       ("c'imageBlurGaussian", "ImageBlurGaussian_", "rl_bindings.h", [t|Ptr Image -> CInt -> IO ()|], False),
       ("c'imageKernelConvolution", "ImageKernelConvolution_", "rl_bindings.h", [t|Ptr Image -> Ptr CFloat -> CInt -> IO ()|], False),
       ("c'imageResize", "ImageResize_", "rl_bindings.h", [t|Ptr Image -> CInt -> CInt -> IO ()|], False),
       ("c'imageResizeNN", "ImageResizeNN_", "rl_bindings.h", [t|Ptr Image -> CInt -> CInt -> IO ()|], False),
       ("c'imageResizeCanvas", "ImageResizeCanvas_", "rl_bindings.h", [t|Ptr Image -> CInt -> CInt -> CInt -> CInt -> Ptr Color -> IO ()|], False),
       ("c'imageMipmaps", "ImageMipmaps_", "rl_bindings.h", [t|Ptr Image -> IO ()|], False),
       ("c'imageDither", "ImageDither_", "rl_bindings.h", [t|Ptr Image -> CInt -> CInt -> CInt -> CInt -> IO ()|], False),
       ("c'imageFlipVertical", "ImageFlipVertical_", "rl_bindings.h", [t|Ptr Image -> IO ()|], False),
       ("c'imageFlipHorizontal", "ImageFlipHorizontal_", "rl_bindings.h", [t|Ptr Image -> IO ()|], False),
       ("c'imageRotate", "ImageRotate_", "rl_bindings.h", [t|Ptr Image -> CInt -> IO ()|], False),
       ("c'imageRotateCW", "ImageRotateCW_", "rl_bindings.h", [t|Ptr Image -> IO ()|], False),
       ("c'imageRotateCCW", "ImageRotateCCW_", "rl_bindings.h", [t|Ptr Image -> IO ()|], False),
       ("c'imageColorTint", "ImageColorTint_", "rl_bindings.h", [t|Ptr Image -> Ptr Color -> IO ()|], False),
       ("c'imageColorInvert", "ImageColorInvert_", "rl_bindings.h", [t|Ptr Image -> IO ()|], False),
       ("c'imageColorGrayscale", "ImageColorGrayscale_", "rl_bindings.h", [t|Ptr Image -> IO ()|], False),
       ("c'imageColorContrast", "ImageColorContrast_", "rl_bindings.h", [t|Ptr Image -> CFloat -> IO ()|], False),
       ("c'imageColorBrightness", "ImageColorBrightness_", "rl_bindings.h", [t|Ptr Image -> CInt -> IO ()|], False),
       ("c'imageColorReplace", "ImageColorReplace_", "rl_bindings.h", [t|Ptr Image -> Ptr Color -> Ptr Color -> IO ()|], False),
       ("c'loadImageColors", "LoadImageColors_", "rl_bindings.h", [t|Ptr Image -> IO (Ptr Color)|], False),
       ("c'loadImagePalette", "LoadImagePalette_", "rl_bindings.h", [t|Ptr Image -> CInt -> Ptr CInt -> IO (Ptr Color)|], False),
       ("c'getImageAlphaBorder", "GetImageAlphaBorder_", "rl_bindings.h", [t|Ptr Image -> CFloat -> IO (Ptr Rectangle)|], False),
       ("c'getImageColor", "GetImageColor_", "rl_bindings.h", [t|Ptr Image -> CInt -> CInt -> IO (Ptr Color)|], False),
       ("c'imageClearBackground", "ImageClearBackground_", "rl_bindings.h", [t|Ptr Image -> Ptr Color -> IO ()|], False),
       ("c'imageDrawPixel", "ImageDrawPixel_", "rl_bindings.h", [t|Ptr Image -> CInt -> CInt -> Ptr Color -> IO ()|], False),
       ("c'imageDrawPixelV", "ImageDrawPixelV_", "rl_bindings.h", [t|Ptr Image -> Ptr Vector2 -> Ptr Color -> IO ()|], False),
       ("c'imageDrawLine", "ImageDrawLine_", "rl_bindings.h", [t|Ptr Image -> CInt -> CInt -> CInt -> CInt -> Ptr Color -> IO ()|], False),
       ("c'imageDrawLineV", "ImageDrawLineV_", "rl_bindings.h", [t|Ptr Image -> Ptr Vector2 -> Ptr Vector2 -> Ptr Color -> IO ()|], False),
       ("c'imageDrawCircle", "ImageDrawCircle_", "rl_bindings.h", [t|Ptr Image -> CInt -> CInt -> CInt -> Ptr Color -> IO ()|], False),
       ("c'imageDrawCircleV", "ImageDrawCircleV_", "rl_bindings.h", [t|Ptr Image -> Ptr Vector2 -> CInt -> Ptr Color -> IO ()|], False),
       ("c'imageDrawCircleLines", "ImageDrawCircleLines_", "rl_bindings.h", [t|Ptr Image -> CInt -> CInt -> CInt -> Ptr Color -> IO ()|], False),
       ("c'imageDrawCircleLinesV", "ImageDrawCircleLinesV_", "rl_bindings.h", [t|Ptr Image -> Ptr Vector2 -> CInt -> Ptr Color -> IO ()|], False),
       ("c'imageDrawRectangle", "ImageDrawRectangle_", "rl_bindings.h", [t|Ptr Image -> CInt -> CInt -> CInt -> CInt -> Ptr Color -> IO ()|], False),
       ("c'imageDrawRectangleV", "ImageDrawRectangleV_", "rl_bindings.h", [t|Ptr Image -> Ptr Vector2 -> Ptr Vector2 -> Ptr Color -> IO ()|], False),
       ("c'imageDrawRectangleRec", "ImageDrawRectangleRec_", "rl_bindings.h", [t|Ptr Image -> Ptr Rectangle -> Ptr Color -> IO ()|], False),
       ("c'imageDrawRectangleLines", "ImageDrawRectangleLines_", "rl_bindings.h", [t|Ptr Image -> Ptr Rectangle -> CInt -> Ptr Color -> IO ()|], False),
       ("c'imageDraw", "ImageDraw_", "rl_bindings.h", [t|Ptr Image -> Ptr Image -> Ptr Rectangle -> Ptr Rectangle -> Ptr Color -> IO ()|], False),
       ("c'imageDrawText", "ImageDrawText_", "rl_bindings.h", [t|Ptr Image -> CString -> CInt -> CInt -> CInt -> Ptr Color -> IO ()|], False),
       ("c'imageDrawTextEx", "ImageDrawTextEx_", "rl_bindings.h", [t|Ptr Image -> Ptr Font -> CString -> Ptr Vector2 -> CFloat -> CFloat -> Ptr Color -> IO ()|], False),
       ("c'loadTexture", "LoadTexture_", "rl_bindings.h", [t|CString -> IO (Ptr Texture)|], False),
       ("c'loadTextureFromImage", "LoadTextureFromImage_", "rl_bindings.h", [t|Ptr Image -> IO (Ptr Texture)|], False),
       ("c'loadTextureCubemap", "LoadTextureCubemap_", "rl_bindings.h", [t|Ptr Image -> CInt -> IO (Ptr Texture)|], False),
       ("c'loadRenderTexture", "LoadRenderTexture_", "rl_bindings.h", [t|CInt -> CInt -> IO (Ptr RenderTexture)|], False),
       ("c'isTextureReady", "IsTextureReady_", "rl_bindings.h", [t|Ptr Texture -> IO CBool|], False),
       ("c'unloadTexture", "UnloadTexture_", "rl_bindings.h", [t|Ptr Texture -> IO ()|], False),
       ("c'isRenderTextureReady", "IsRenderTextureReady_", "rl_bindings.h", [t|Ptr RenderTexture -> IO CBool|], False),
       ("c'unloadRenderTexture", "UnloadRenderTexture_", "rl_bindings.h", [t|Ptr RenderTexture -> IO ()|], False),
       ("c'updateTexture", "UpdateTexture_", "rl_bindings.h", [t|Ptr Texture -> Ptr () -> IO ()|], False),
       ("c'updateTextureRec", "UpdateTextureRec_", "rl_bindings.h", [t|Ptr Texture -> Ptr Rectangle -> Ptr () -> IO ()|], False),
       ("c'genTextureMipmaps", "GenTextureMipmaps_", "rl_bindings.h", [t|Ptr Texture -> IO ()|], False),
       ("c'setTextureFilter", "SetTextureFilter_", "rl_bindings.h", [t|Ptr Texture -> CInt -> IO ()|], False),
       ("c'setTextureWrap", "SetTextureWrap_", "rl_bindings.h", [t|Ptr Texture -> CInt -> IO ()|], False),
       ("c'drawTexture", "DrawTexture_", "rl_bindings.h", [t|Ptr Texture -> CInt -> CInt -> Ptr Color -> IO ()|], False),
       ("c'drawTextureV", "DrawTextureV_", "rl_bindings.h", [t|Ptr Texture -> Ptr Vector2 -> Ptr Color -> IO ()|], False),
       ("c'drawTextureEx", "DrawTextureEx_", "rl_bindings.h", [t|Ptr Texture -> Ptr Vector2 -> CFloat -> CFloat -> Ptr Color -> IO ()|], False),
       ("c'drawTextureRec", "DrawTextureRec_", "rl_bindings.h", [t|Ptr Texture -> Ptr Rectangle -> Ptr Vector2 -> Ptr Color -> IO ()|], False),
       ("c'drawTexturePro", "DrawTexturePro_", "rl_bindings.h", [t|Ptr Texture -> Ptr Rectangle -> Ptr Rectangle -> Ptr Vector2 -> CFloat -> Ptr Color -> IO ()|], False),
       ("c'drawTextureNPatch", "DrawTextureNPatch_", "rl_bindings.h", [t|Ptr Texture -> Ptr NPatchInfo -> Ptr Rectangle -> Ptr Vector2 -> CFloat -> Ptr Color -> IO ()|], False),
       ("c'fade", "Fade_", "rl_bindings.h", [t|Ptr Color -> CFloat -> IO (Ptr Color)|], False),
       ("c'colorToInt", "ColorToInt_", "rl_bindings.h", [t|Ptr Color -> IO CInt|], False),
       ("c'colorNormalize", "ColorNormalize_", "rl_bindings.h", [t|Ptr Color -> IO (Ptr Vector4)|], False),
       ("c'colorFromNormalized", "ColorFromNormalized_", "rl_bindings.h", [t|Ptr Vector4 -> IO (Ptr Color)|], False),
       ("c'colorToHSV", "ColorToHSV_", "rl_bindings.h", [t|Ptr Color -> IO (Ptr Vector3)|], False),
       ("c'colorFromHSV", "ColorFromHSV_", "rl_bindings.h", [t|CFloat -> CFloat -> CFloat -> IO (Ptr Color)|], False),
       ("c'colorTint", "ColorTint_", "rl_bindings.h", [t|Ptr Color -> Ptr Color -> IO (Ptr Color)|], False),
       ("c'colorBrightness", "ColorBrightness_", "rl_bindings.h", [t|Ptr Color -> CFloat -> IO (Ptr Color)|], False),
       ("c'colorContrast", "ColorContrast_", "rl_bindings.h", [t|Ptr Color -> CFloat -> IO (Ptr Color)|], False),
       ("c'colorAlpha", "ColorAlpha_", "rl_bindings.h", [t|Ptr Color -> CFloat -> IO (Ptr Color)|], False),
       ("c'colorAlphaBlend", "ColorAlphaBlend_", "rl_bindings.h", [t|Ptr Color -> Ptr Color -> Ptr Color -> IO (Ptr Color)|], False),
       ("c'getColor", "GetColor_", "rl_bindings.h", [t|CUInt -> IO (Ptr Color)|], False),
       ("c'getPixelColor", "GetPixelColor_", "rl_bindings.h", [t|Ptr () -> CInt -> IO (Ptr Color)|], False),
       ("c'setPixelColor", "SetPixelColor_", "rl_bindings.h", [t|Ptr () -> Ptr Color -> CInt -> IO ()|], False)
     ]
 )
loadImage :: String -> IO Image
loadImage :: String -> IO Image
loadImage String
fileName = String -> (CString -> IO (Ptr Image)) -> IO (Ptr Image)
forall a. String -> (CString -> IO a) -> IO a
withCString String
fileName CString -> IO (Ptr Image)
c'loadImage IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
loadImageRaw :: String -> Int -> Int -> Int -> Int -> IO Image
loadImageRaw :: String -> Int -> Int -> Int -> Int -> IO Image
loadImageRaw String
fileName Int
width Int
height Int
format Int
headerSize =
  String -> (CString -> IO (Ptr Image)) -> IO (Ptr Image)
forall a. String -> (CString -> IO a) -> IO a
withCString String
fileName (\CString
str -> CString -> CInt -> CInt -> CInt -> CInt -> IO (Ptr Image)
c'loadImageRaw CString
str (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
width) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
height) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ Int -> Int
forall a. Enum a => a -> Int
fromEnum Int
format) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
headerSize)) IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
loadImageSvg :: String -> Int -> Int -> IO Image
loadImageSvg :: String -> Int -> Int -> IO Image
loadImageSvg String
fileNameOrString Int
width Int
height = String -> (CString -> IO (Ptr Image)) -> IO (Ptr Image)
forall a. String -> (CString -> IO a) -> IO a
withCString String
fileNameOrString (\CString
s -> CString -> CInt -> CInt -> IO (Ptr Image)
c'loadImageSvg CString
s (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
width) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
height)) IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
loadImageAnim :: String -> IO (Image, Int)
loadImageAnim :: String -> IO (Image, Int)
loadImageAnim String
fileName =
  CInt -> (Ptr CInt -> IO (Image, Int)) -> IO (Image, Int)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable
    CInt
0
    ( \Ptr CInt
frames ->
        String -> (CString -> IO (Image, Int)) -> IO (Image, Int)
forall a. String -> (CString -> IO a) -> IO a
withCString
          String
fileName
          ( \CString
fn -> do
              Image
img <- CString -> Ptr CInt -> IO (Ptr Image)
c'loadImageAnim CString
fn Ptr CInt
frames IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
              Int
frameNum <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
frames
              (Image, Int) -> IO (Image, Int)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Image
img, Int
frameNum)
          )
    )
loadImageAnimFromMemory :: String -> [Integer] -> IO (Image, Int)
loadImageAnimFromMemory :: String -> [Integer] -> IO (Image, Int)
loadImageAnimFromMemory String
fileType [Integer]
fileData =
  String -> (CString -> IO (Image, Int)) -> IO (Image, Int)
forall a. String -> (CString -> IO a) -> IO a
withCString
    String
fileType
    ( \CString
ft ->
        [CUChar]
-> (Int -> Ptr CUChar -> IO (Image, Int)) -> IO (Image, Int)
forall a b.
(Freeable a, Storable a) =>
[a] -> (Int -> Ptr a -> IO b) -> IO b
withFreeableArrayLen
          ((Integer -> CUChar) -> [Integer] -> [CUChar]
forall a b. (a -> b) -> [a] -> [b]
map Integer -> CUChar
forall a b. (Integral a, Num b) => a -> b
fromIntegral [Integer]
fileData)
          ( \Int
size Ptr CUChar
fd ->
              CInt -> (Ptr CInt -> IO (Image, Int)) -> IO (Image, Int)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable
                (CInt
0 :: CInt)
                ( \Ptr CInt
frames -> do
                    Image
img <- CString -> Ptr CUChar -> CInt -> Ptr CInt -> IO (Ptr Image)
c'loadImageAnimFromMemory CString
ft Ptr CUChar
fd (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ Int
size Int -> Int -> Int
forall a. Num a => a -> a -> a
* CUChar -> Int
forall a. Storable a => a -> Int
sizeOf (CUChar
0 :: CUChar)) Ptr CInt
frames IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
                    Int
frameNum <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
frames
                    (Image, Int) -> IO (Image, Int)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Image
img, Int
frameNum)
                )
          )
    )
loadImageFromMemory :: String -> [Integer] -> IO Image
loadImageFromMemory :: String -> [Integer] -> IO Image
loadImageFromMemory String
fileType [Integer]
fileData =
  String -> (CString -> IO (Ptr Image)) -> IO (Ptr Image)
forall a. String -> (CString -> IO a) -> IO a
withCString String
fileType (\CString
ft -> [CUChar] -> (Int -> Ptr CUChar -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b.
(Freeable a, Storable a) =>
[a] -> (Int -> Ptr a -> IO b) -> IO b
withFreeableArrayLen ((Integer -> CUChar) -> [Integer] -> [CUChar]
forall a b. (a -> b) -> [a] -> [b]
map Integer -> CUChar
forall a b. (Integral a, Num b) => a -> b
fromIntegral [Integer]
fileData) (\Int
size Ptr CUChar
fd -> CString -> Ptr CUChar -> CInt -> IO (Ptr Image)
c'loadImageFromMemory CString
ft Ptr CUChar
fd (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ Int
size Int -> Int -> Int
forall a. Num a => a -> a -> a
* CUChar -> Int
forall a. Storable a => a -> Int
sizeOf (CUChar
0 :: CUChar)))) IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
loadImageFromTexture :: Texture -> IO Image
loadImageFromTexture :: Texture -> IO Image
loadImageFromTexture Texture
tex = Texture -> (Ptr Texture -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Texture
tex Ptr Texture -> IO (Ptr Image)
c'loadImageFromTexture IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
loadImageFromScreen :: IO Image
loadImageFromScreen :: IO Image
loadImageFromScreen = IO (Ptr Image)
c'loadImageFromScreen IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
isImageReady :: Image -> IO Bool
isImageReady :: Image -> IO Bool
isImageReady Image
image = CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Image -> (Ptr Image -> IO CBool) -> IO CBool
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image Ptr Image -> IO CBool
c'isImageReady
exportImage :: Image -> String -> IO Bool
exportImage :: Image -> String -> IO Bool
exportImage Image
image String
fileName = CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Image -> (Ptr Image -> IO CBool) -> IO CBool
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (String -> (CString -> IO CBool) -> IO CBool
forall a. String -> (CString -> IO a) -> IO a
withCString String
fileName ((CString -> IO CBool) -> IO CBool)
-> (Ptr Image -> CString -> IO CBool) -> Ptr Image -> IO CBool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Image -> CString -> IO CBool
c'exportImage)
exportImageToMemory :: Image -> String -> IO [Word8]
exportImageToMemory :: Image -> String -> IO [Word8]
exportImageToMemory Image
image String
fileType =
  Image -> (Ptr Image -> IO [Word8]) -> IO [Word8]
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable
    Image
image
    ( \Ptr Image
i ->
        String -> (CString -> IO [Word8]) -> IO [Word8]
forall a. String -> (CString -> IO a) -> IO a
withCString
          String
fileType
          ( \CString
t ->
              CInt -> (Ptr CInt -> IO [Word8]) -> IO [Word8]
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable
                CInt
0
                ( \Ptr CInt
s -> do
                    Ptr CUChar
bytes <- Ptr Image -> CString -> Ptr CInt -> IO (Ptr CUChar)
c'exportImageToMemory Ptr Image
i CString
t Ptr CInt
s
                    Int
size <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
s
                    (CUChar -> Word8) -> [CUChar] -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
map (\(CUChar Word8
x) -> Word8
x) ([CUChar] -> [Word8]) -> IO [CUChar] -> IO [Word8]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Ptr CUChar -> IO [CUChar]
forall a. (Freeable a, Storable a) => Int -> Ptr a -> IO [a]
popCArray Int
size Ptr CUChar
bytes
                )
          )
    )
exportImageAsCode :: Image -> String -> IO Bool
exportImageAsCode :: Image -> String -> IO Bool
exportImageAsCode Image
image String
fileName =
  CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Image -> (Ptr Image -> IO CBool) -> IO CBool
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (String -> (CString -> IO CBool) -> IO CBool
forall a. String -> (CString -> IO a) -> IO a
withCString String
fileName ((CString -> IO CBool) -> IO CBool)
-> (Ptr Image -> CString -> IO CBool) -> Ptr Image -> IO CBool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Image -> CString -> IO CBool
c'exportImageAsCode)
genImageColor :: Int -> Int -> Color -> IO Image
genImageColor :: Int -> Int -> Color -> IO Image
genImageColor Int
width Int
height Color
color =
  Color -> (Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (CInt -> CInt -> Ptr Color -> IO (Ptr Image)
c'genImageColor (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
width) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
height)) IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
genImageGradientLinear :: Int -> Int -> Int -> Color -> Color -> IO Image
genImageGradientLinear :: Int -> Int -> Int -> Color -> Color -> IO Image
genImageGradientLinear Int
width Int
height Int
direction Color
start Color
end =
  Color -> (Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
start (Color -> (Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
end ((Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image))
-> (Ptr Color -> Ptr Color -> IO (Ptr Image))
-> Ptr Color
-> IO (Ptr Image)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> CInt -> CInt -> Ptr Color -> Ptr Color -> IO (Ptr Image)
c'genImageGradientLinear (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
width) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
height) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
direction)) IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
genImageGradientRadial :: Int -> Int -> Float -> Color -> Color -> IO Image
genImageGradientRadial :: Int -> Int -> Float -> Color -> Color -> IO Image
genImageGradientRadial Int
width Int
height Float
density Color
inner Color
outer =
  Color -> (Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
inner (Color -> (Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
outer ((Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image))
-> (Ptr Color -> Ptr Color -> IO (Ptr Image))
-> Ptr Color
-> IO (Ptr Image)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> CInt -> CFloat -> Ptr Color -> Ptr Color -> IO (Ptr Image)
c'genImageGradientRadial (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
width) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
height) (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
density)) IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
genImageGradientSquare :: Int -> Int -> Float -> Color -> Color -> IO Image
genImageGradientSquare :: Int -> Int -> Float -> Color -> Color -> IO Image
genImageGradientSquare Int
width Int
height Float
density Color
inner Color
outer =
  Color -> (Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
inner (Color -> (Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
outer ((Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image))
-> (Ptr Color -> Ptr Color -> IO (Ptr Image))
-> Ptr Color
-> IO (Ptr Image)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> CInt -> CFloat -> Ptr Color -> Ptr Color -> IO (Ptr Image)
c'genImageGradientSquare (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
width) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
height) (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
density)) IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
genImageChecked :: Int -> Int -> Int -> Int -> Color -> Color -> IO Image
genImageChecked :: Int -> Int -> Int -> Int -> Color -> Color -> IO Image
genImageChecked Int
width Int
height Int
checksX Int
checksY Color
col1 Color
col2 =
  Color -> (Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
col1 (Color -> (Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
col2 ((Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image))
-> (Ptr Color -> Ptr Color -> IO (Ptr Image))
-> Ptr Color
-> IO (Ptr Image)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt
-> CInt -> CInt -> CInt -> Ptr Color -> Ptr Color -> IO (Ptr Image)
c'genImageChecked (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
width) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
height) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
checksX) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
checksY)) IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
genImageWhiteNoise :: Int -> Int -> Float -> IO Image
genImageWhiteNoise :: Int -> Int -> Float -> IO Image
genImageWhiteNoise Int
width Int
height Float
factor =
  CInt -> CInt -> CFloat -> IO (Ptr Image)
c'genImageWhiteNoise (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
width) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
height) (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factor) IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
genImagePerlinNoise :: Int -> Int -> Int -> Int -> Float -> IO Image
genImagePerlinNoise :: Int -> Int -> Int -> Int -> Float -> IO Image
genImagePerlinNoise Int
width Int
height Int
offsetX Int
offsetY Float
scale = CInt -> CInt -> CInt -> CInt -> CFloat -> IO (Ptr Image)
c'genImagePerlinNoise (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
width) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
height) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
offsetX) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
offsetY) (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
scale) IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
genImageCellular :: Int -> Int -> Int -> IO Image
genImageCellular :: Int -> Int -> Int -> IO Image
genImageCellular Int
width Int
height Int
tileSize =
  CInt -> CInt -> CInt -> IO (Ptr Image)
c'genImageCellular (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
width) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
height) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
tileSize) IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
genImageText :: Int -> Int -> String -> IO Image
genImageText :: Int -> Int -> String -> IO Image
genImageText Int
width Int
height String
text =
  String -> (CString -> IO (Ptr Image)) -> IO (Ptr Image)
forall a. String -> (CString -> IO a) -> IO a
withCString String
text (CInt -> CInt -> CString -> IO (Ptr Image)
c'genImageText (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
width) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
height)) IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
imageCopy :: Image -> IO Image
imageCopy :: Image -> IO Image
imageCopy Image
image = Image -> (Ptr Image -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image Ptr Image -> IO (Ptr Image)
c'imageCopy IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
imageFromImage :: Image -> Rectangle -> IO Image
imageFromImage :: Image -> Rectangle -> IO Image
imageFromImage Image
image Rectangle
rect = Image -> (Ptr Image -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (Rectangle -> (Ptr Rectangle -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Rectangle
rect ((Ptr Rectangle -> IO (Ptr Image)) -> IO (Ptr Image))
-> (Ptr Image -> Ptr Rectangle -> IO (Ptr Image))
-> Ptr Image
-> IO (Ptr Image)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Image -> Ptr Rectangle -> IO (Ptr Image)
c'imageFromImage) IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
imageText :: String -> Int -> Color -> IO Image
imageText :: String -> Int -> Color -> IO Image
imageText String
text Int
fontSize Color
color =
  String -> (CString -> IO (Ptr Image)) -> IO (Ptr Image)
forall a. String -> (CString -> IO a) -> IO a
withCString String
text (\CString
t -> Color -> (Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color ((Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image))
-> (Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b. (a -> b) -> a -> b
$ CString -> CInt -> Ptr Color -> IO (Ptr Image)
c'imageText CString
t (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
fontSize)) IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
imageTextEx :: Font -> String -> Float -> Float -> Color -> IO Image
imageTextEx :: Font -> String -> Float -> Float -> Color -> IO Image
imageTextEx Font
font String
text Float
fontSize Float
spacing Color
tint =
  Font -> (Ptr Font -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Font
font (\Ptr Font
f -> String -> (CString -> IO (Ptr Image)) -> IO (Ptr Image)
forall a. String -> (CString -> IO a) -> IO a
withCString String
text (\CString
t -> Color -> (Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
tint ((Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image))
-> (Ptr Color -> IO (Ptr Image)) -> IO (Ptr Image)
forall a b. (a -> b) -> a -> b
$ Ptr Font
-> CString -> CFloat -> CFloat -> Ptr Color -> IO (Ptr Image)
c'imageTextEx Ptr Font
f CString
t (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
fontSize) (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
spacing))) IO (Ptr Image) -> (Ptr Image -> IO Image) -> IO Image
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Image -> IO Image
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
imageFormat :: Image -> PixelFormat -> IO Image
imageFormat :: Image -> PixelFormat -> IO Image
imageFormat Image
image PixelFormat
newFormat =
  Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> CInt -> IO ()
c'imageFormat Ptr Image
i (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ PixelFormat -> Int
forall a. Enum a => a -> Int
fromEnum PixelFormat
newFormat) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageToPOT :: Image -> Color -> IO Image
imageToPOT :: Image -> Color -> IO Image
imageToPOT Image
image Color
color = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (Ptr Image -> Ptr Color -> IO ()
c'imageToPOT Ptr Image
i) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageCrop :: Image -> Rectangle -> IO Image
imageCrop :: Image -> Rectangle -> IO Image
imageCrop Image
image Rectangle
crop = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Rectangle
crop (Ptr Image -> Ptr Rectangle -> IO ()
c'imageCrop Ptr Image
i) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageAlphaCrop :: Image -> Float -> IO Image
imageAlphaCrop :: Image -> Float -> IO Image
imageAlphaCrop Image
image Float
threshold = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> CFloat -> IO ()
c'imageAlphaCrop Ptr Image
i (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
threshold) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageAlphaClear :: Image -> Color -> Float -> IO Image
imageAlphaClear :: Image -> Color -> Float -> IO Image
imageAlphaClear Image
image Color
color Float
threshold = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Color -> (Ptr Color -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (\Ptr Color
c -> Ptr Image -> Ptr Color -> CFloat -> IO ()
c'imageAlphaClear Ptr Image
i Ptr Color
c (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
threshold) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i))
imageAlphaMask :: Image -> Image -> IO Image
imageAlphaMask :: Image -> Image -> IO Image
imageAlphaMask Image
image Image
alphaMask = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Image -> (Ptr Image -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
alphaMask (Ptr Image -> Ptr Image -> IO ()
c'imageAlphaMask Ptr Image
i) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageAlphaPremultiply :: Image -> IO Image
imageAlphaPremultiply :: Image -> IO Image
imageAlphaPremultiply Image
image = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> IO ()
c'imageAlphaPremultiply Ptr Image
i IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageBlurGaussian :: Image -> Int -> IO Image
imageBlurGaussian :: Image -> Int -> IO Image
imageBlurGaussian Image
image Int
blurSize = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> CInt -> IO ()
c'imageBlurGaussian Ptr Image
i (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
blurSize) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageKernelConvolution :: Image -> [Float] -> IO Image
imageKernelConvolution :: Image -> [Float] -> IO Image
imageKernelConvolution Image
image [Float]
kernel = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> [CFloat] -> (Ptr CFloat -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
[a] -> (Ptr a -> IO b) -> IO b
withFreeableArray ((Float -> CFloat) -> [Float] -> [CFloat]
forall a b. (a -> b) -> [a] -> [b]
map Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac [Float]
kernel :: [CFloat]) (\Ptr CFloat
k -> Ptr Image -> Ptr CFloat -> CInt -> IO ()
c'imageKernelConvolution Ptr Image
i Ptr CFloat
k (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ [Float] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Float]
kernel) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i))
imageResize :: Image -> Int -> Int -> IO Image
imageResize :: Image -> Int -> Int -> IO Image
imageResize Image
image Int
newWidth Int
newHeight = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> CInt -> CInt -> IO ()
c'imageResize Ptr Image
i (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
newWidth) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
newHeight) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageResizeNN :: Image -> Int -> Int -> IO Image
imageResizeNN :: Image -> Int -> Int -> IO Image
imageResizeNN Image
image Int
newWidth Int
newHeight = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> CInt -> CInt -> IO ()
c'imageResizeNN Ptr Image
i (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
newWidth) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
newHeight) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageResizeCanvas :: Image -> Int -> Int -> Int -> Int -> Color -> IO Image
imageResizeCanvas :: Image -> Int -> Int -> Int -> Int -> Color -> IO Image
imageResizeCanvas Image
image Int
newWidth Int
newHeight Int
offsetX Int
offsetY Color
fill = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
fill (Ptr Image -> CInt -> CInt -> CInt -> CInt -> Ptr Color -> IO ()
c'imageResizeCanvas Ptr Image
i (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
newWidth) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
newHeight) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
offsetX) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
offsetY)) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageMipmaps :: Image -> IO Image
imageMipmaps :: Image -> IO Image
imageMipmaps Image
image = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> IO ()
c'imageMipmaps Ptr Image
i IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageDither :: Image -> Int -> Int -> Int -> Int -> IO Image
imageDither :: Image -> Int -> Int -> Int -> Int -> IO Image
imageDither Image
image Int
rBpp Int
gBpp Int
bBpp Int
aBpp = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> CInt -> CInt -> CInt -> CInt -> IO ()
c'imageDither Ptr Image
i (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
rBpp) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
gBpp) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
bBpp) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
aBpp) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageFlipVertical :: Image -> IO Image
imageFlipVertical :: Image -> IO Image
imageFlipVertical Image
image = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> IO ()
c'imageFlipVertical Ptr Image
i IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageFlipHorizontal :: Image -> IO Image
imageFlipHorizontal :: Image -> IO Image
imageFlipHorizontal Image
image = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> IO ()
c'imageFlipHorizontal Ptr Image
i IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageRotate :: Image -> Int -> IO Image
imageRotate :: Image -> Int -> IO Image
imageRotate Image
image Int
degrees = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> CInt -> IO ()
c'imageRotate Ptr Image
i (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
degrees) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageRotateCW :: Image -> IO Image
imageRotateCW :: Image -> IO Image
imageRotateCW Image
image = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> IO ()
c'imageRotateCW Ptr Image
i IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageRotateCCW :: Image -> IO Image
imageRotateCCW :: Image -> IO Image
imageRotateCCW Image
image = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> IO ()
c'imageRotateCCW Ptr Image
i IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageColorTint :: Image -> Color -> IO Image
imageColorTint :: Image -> Color -> IO Image
imageColorTint Image
image Color
color = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (Ptr Image -> Ptr Color -> IO ()
c'imageColorTint Ptr Image
i) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageColorInvert :: Image -> IO Image
imageColorInvert :: Image -> IO Image
imageColorInvert Image
image = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> IO ()
c'imageColorInvert Ptr Image
i IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageColorGrayscale :: Image -> IO Image
imageColorGrayscale :: Image -> IO Image
imageColorGrayscale Image
image = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> IO ()
c'imageColorGrayscale Ptr Image
i IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageColorContrast :: Image -> Float -> IO Image
imageColorContrast :: Image -> Float -> IO Image
imageColorContrast Image
image Float
contrast = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> CFloat -> IO ()
c'imageColorContrast Ptr Image
i (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
contrast) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageColorBrightness :: Image -> Int -> IO Image
imageColorBrightness :: Image -> Int -> IO Image
imageColorBrightness Image
image Int
brightness = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> CInt -> IO ()
c'imageColorBrightness Ptr Image
i (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
brightness) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageColorReplace :: Image -> Color -> Color -> IO Image
imageColorReplace :: Image -> Color -> Color -> IO Image
imageColorReplace Image
image Color
color Color
replace = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
replace ((Ptr Color -> IO ()) -> IO ())
-> (Ptr Color -> Ptr Color -> IO ()) -> Ptr Color -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Image -> Ptr Color -> Ptr Color -> IO ()
c'imageColorReplace Ptr Image
i) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
loadImageColors :: Image -> IO [Color]
loadImageColors :: Image -> IO [Color]
loadImageColors Image
image =
  Image -> (Ptr Image -> IO [Color]) -> IO [Color]
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable
    Image
image
    (Int -> Ptr Color -> IO [Color]
forall a. (Freeable a, Storable a) => Int -> Ptr a -> IO [a]
popCArray (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Image -> Int
image'width Image
image Int -> Int -> Int
forall a. Num a => a -> a -> a
* Image -> Int
image'height Image
image) (Ptr Color -> IO [Color])
-> (Ptr Image -> IO (Ptr Color)) -> Ptr Image -> IO [Color]
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Ptr Image -> IO (Ptr Color)
c'loadImageColors)
loadImagePalette :: Image -> Int -> IO [Color]
loadImagePalette :: Image -> Int -> IO [Color]
loadImagePalette Image
image Int
maxPaletteSize =
  Image -> (Ptr Image -> IO [Color]) -> IO [Color]
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable
    Image
image
    ( \Ptr Image
i -> do
        (Ptr Color
palette, CInt
num) <-
          CInt -> (Ptr CInt -> IO (Ptr Color, CInt)) -> IO (Ptr Color, CInt)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable
            CInt
0
            ( \Ptr CInt
size -> do
                Ptr Color
cols <- Ptr Image -> CInt -> Ptr CInt -> IO (Ptr Color)
c'loadImagePalette Ptr Image
i (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
maxPaletteSize) Ptr CInt
size
                CInt
s <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
size
                (Ptr Color, CInt) -> IO (Ptr Color, CInt)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Color
cols, CInt
s)
            )
        Int -> Ptr Color -> IO [Color]
forall a. (Freeable a, Storable a) => Int -> Ptr a -> IO [a]
popCArray (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
num) Ptr Color
palette
    )
getImageAlphaBorder :: Image -> Float -> IO Rectangle
getImageAlphaBorder :: Image -> Float -> IO Rectangle
getImageAlphaBorder Image
image Float
threshold = Image -> (Ptr Image -> IO (Ptr Rectangle)) -> IO (Ptr Rectangle)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> CFloat -> IO (Ptr Rectangle)
c'getImageAlphaBorder Ptr Image
i (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
threshold)) IO (Ptr Rectangle)
-> (Ptr Rectangle -> IO Rectangle) -> IO Rectangle
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Rectangle -> IO Rectangle
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
getImageColor :: Image -> Int -> Int -> IO Color
getImageColor :: Image -> Int -> Int -> IO Color
getImageColor Image
image Int
x Int
y = Image -> (Ptr Image -> IO (Ptr Color)) -> IO (Ptr Color)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> CInt -> CInt -> IO (Ptr Color)
c'getImageColor Ptr Image
i (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
y)) IO (Ptr Color) -> (Ptr Color -> IO Color) -> IO Color
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Color -> IO Color
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
imageClearBackground :: Image -> Color -> IO Image
imageClearBackground :: Image -> Color -> IO Image
imageClearBackground Image
image Color
color = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (Ptr Image -> Ptr Color -> IO ()
c'imageClearBackground Ptr Image
i) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageDrawPixel :: Image -> Int -> Int -> Color -> IO Image
imageDrawPixel :: Image -> Int -> Int -> Color -> IO Image
imageDrawPixel Image
image Int
x Int
y Color
color = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (Ptr Image -> CInt -> CInt -> Ptr Color -> IO ()
c'imageDrawPixel Ptr Image
i (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
y)) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageDrawPixelV :: Image -> Vector2 -> Color -> IO Image
imageDrawPixelV :: Image -> Vector2 -> Color -> IO Image
imageDrawPixelV Image
image Vector2
position Color
color = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Vector2 -> (Ptr Vector2 -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Vector2
position (Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color ((Ptr Color -> IO ()) -> IO ())
-> (Ptr Vector2 -> Ptr Color -> IO ()) -> Ptr Vector2 -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Image -> Ptr Vector2 -> Ptr Color -> IO ()
c'imageDrawPixelV Ptr Image
i) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageDrawLine :: Image -> Int -> Int -> Int -> Int -> Color -> IO Image
imageDrawLine :: Image -> Int -> Int -> Int -> Int -> Color -> IO Image
imageDrawLine Image
image Int
startPosX Int
startPosY Int
endPosX Int
endPosY Color
color = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (Ptr Image -> CInt -> CInt -> CInt -> CInt -> Ptr Color -> IO ()
c'imageDrawLine Ptr Image
i (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
startPosX) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
startPosY) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
endPosX) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
endPosY)) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageDrawLineV :: Image -> Vector2 -> Vector2 -> Color -> IO Image
imageDrawLineV :: Image -> Vector2 -> Vector2 -> Color -> IO Image
imageDrawLineV Image
image Vector2
start Vector2
end Color
color = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Vector2 -> (Ptr Vector2 -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Vector2
start (\Ptr Vector2
s -> Vector2 -> (Ptr Vector2 -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Vector2
end (Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color ((Ptr Color -> IO ()) -> IO ())
-> (Ptr Vector2 -> Ptr Color -> IO ()) -> Ptr Vector2 -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Image -> Ptr Vector2 -> Ptr Vector2 -> Ptr Color -> IO ()
c'imageDrawLineV Ptr Image
i Ptr Vector2
s)) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageDrawCircle :: Image -> Int -> Int -> Int -> Color -> IO Image
imageDrawCircle :: Image -> Int -> Int -> Int -> Color -> IO Image
imageDrawCircle Image
image Int
centerX Int
centerY Int
radius Color
color = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (Ptr Image -> CInt -> CInt -> CInt -> Ptr Color -> IO ()
c'imageDrawCircle Ptr Image
i (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
centerX) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
centerY) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
radius)) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageDrawCircleV :: Image -> Vector2 -> Int -> Color -> IO Image
imageDrawCircleV :: Image -> Vector2 -> Int -> Color -> IO Image
imageDrawCircleV Image
image Vector2
center Int
radius Color
color = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Vector2 -> (Ptr Vector2 -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Vector2
center (\Ptr Vector2
c -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (Ptr Image -> Ptr Vector2 -> CInt -> Ptr Color -> IO ()
c'imageDrawCircleV Ptr Image
i Ptr Vector2
c (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
radius))) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageDrawCircleLines :: Image -> Int -> Int -> Int -> Color -> IO Image
imageDrawCircleLines :: Image -> Int -> Int -> Int -> Color -> IO Image
imageDrawCircleLines Image
image Int
centerX Int
centerY Int
radius Color
color = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (Ptr Image -> CInt -> CInt -> CInt -> Ptr Color -> IO ()
c'imageDrawCircleLines Ptr Image
i (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
centerX) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
centerY) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
radius)) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageDrawCircleLinesV :: Image -> Vector2 -> Int -> Color -> IO Image
imageDrawCircleLinesV :: Image -> Vector2 -> Int -> Color -> IO Image
imageDrawCircleLinesV Image
image Vector2
center Int
radius Color
color = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Vector2 -> (Ptr Vector2 -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Vector2
center (\Ptr Vector2
c -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (Ptr Image -> Ptr Vector2 -> CInt -> Ptr Color -> IO ()
c'imageDrawCircleLinesV Ptr Image
i Ptr Vector2
c (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
radius))) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageDrawRectangle :: Image -> Int -> Int -> Int -> Int -> Color -> IO Image
imageDrawRectangle :: Image -> Int -> Int -> Int -> Int -> Color -> IO Image
imageDrawRectangle Image
image Int
posX Int
posY Int
width Int
height Color
color = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (Ptr Image -> CInt -> CInt -> CInt -> CInt -> Ptr Color -> IO ()
c'imageDrawRectangle Ptr Image
i (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
posX) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
posY) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
width) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
height)) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageDrawRectangleV :: Image -> Vector2 -> Vector2 -> Color -> IO Image
imageDrawRectangleV :: Image -> Vector2 -> Vector2 -> Color -> IO Image
imageDrawRectangleV Image
image Vector2
position Vector2
size Color
color = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Vector2 -> (Ptr Vector2 -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Vector2
position (\Ptr Vector2
p -> Vector2 -> (Ptr Vector2 -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Vector2
size (Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color ((Ptr Color -> IO ()) -> IO ())
-> (Ptr Vector2 -> Ptr Color -> IO ()) -> Ptr Vector2 -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Image -> Ptr Vector2 -> Ptr Vector2 -> Ptr Color -> IO ()
c'imageDrawRectangleV Ptr Image
i Ptr Vector2
p)) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageDrawRectangleRec :: Image -> Rectangle -> Color -> IO Image
imageDrawRectangleRec :: Image -> Rectangle -> Color -> IO Image
imageDrawRectangleRec Image
image Rectangle
rectangle Color
color = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Rectangle
rectangle (Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color ((Ptr Color -> IO ()) -> IO ())
-> (Ptr Rectangle -> Ptr Color -> IO ()) -> Ptr Rectangle -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Image -> Ptr Rectangle -> Ptr Color -> IO ()
c'imageDrawRectangleRec Ptr Image
i) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageDrawRectangleLines :: Image -> Rectangle -> Int -> Color -> IO Image
imageDrawRectangleLines :: Image -> Rectangle -> Int -> Color -> IO Image
imageDrawRectangleLines Image
image Rectangle
rectangle Int
thickness Color
color = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Rectangle
rectangle (\Ptr Rectangle
r -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (Ptr Image -> Ptr Rectangle -> CInt -> Ptr Color -> IO ()
c'imageDrawRectangleLines Ptr Image
i Ptr Rectangle
r (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
thickness))) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageDraw :: Image -> Image -> Rectangle -> Rectangle -> Color -> IO Image
imageDraw :: Image -> Image -> Rectangle -> Rectangle -> Color -> IO Image
imageDraw Image
image Image
source Rectangle
srcRec Rectangle
dstRec Color
tint = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Image -> (Ptr Image -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
source (\Ptr Image
s -> Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Rectangle
srcRec (\Ptr Rectangle
sr -> Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Rectangle
dstRec (Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
tint ((Ptr Color -> IO ()) -> IO ())
-> (Ptr Rectangle -> Ptr Color -> IO ()) -> Ptr Rectangle -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Image
-> Ptr Image
-> Ptr Rectangle
-> Ptr Rectangle
-> Ptr Color
-> IO ()
c'imageDraw Ptr Image
i Ptr Image
s Ptr Rectangle
sr))) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageDrawText :: Image -> String -> Int -> Int -> Int -> Color -> IO Image
imageDrawText :: Image -> String -> Int -> Int -> Int -> Color -> IO Image
imageDrawText Image
image String
text Int
x Int
y Int
fontSize Color
color = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withCString String
text (\CString
t -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (Ptr Image -> CString -> CInt -> CInt -> CInt -> Ptr Color -> IO ()
c'imageDrawText Ptr Image
i CString
t (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
y) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
fontSize))) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
imageDrawTextEx :: Image -> Font -> String -> Vector2 -> Float -> Float -> Color -> IO Image
imageDrawTextEx :: Image
-> Font -> String -> Vector2 -> Float -> Float -> Color -> IO Image
imageDrawTextEx Image
image Font
font String
text Vector2
position Float
fontSize Float
spacing Color
tint = Image -> (Ptr Image -> IO Image) -> IO Image
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Font -> (Ptr Font -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Font
font (\Ptr Font
f -> String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withCString String
text (\CString
t -> Vector2 -> (Ptr Vector2 -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Vector2
position (\Ptr Vector2
p -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
tint (Ptr Image
-> Ptr Font
-> CString
-> Ptr Vector2
-> CFloat
-> CFloat
-> Ptr Color
-> IO ()
c'imageDrawTextEx Ptr Image
i Ptr Font
f CString
t Ptr Vector2
p (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
fontSize) (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
spacing))))) IO () -> IO Image -> IO Image
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek Ptr Image
i)
loadTexture :: String -> WindowResources -> IO Texture
loadTexture :: String -> WindowResources -> IO Texture
loadTexture String
fileName WindowResources
wr = do
  Texture
texture <- String -> (CString -> IO (Ptr Texture)) -> IO (Ptr Texture)
forall a. String -> (CString -> IO a) -> IO a
withCString String
fileName CString -> IO (Ptr Texture)
c'loadTexture IO (Ptr Texture) -> (Ptr Texture -> IO Texture) -> IO Texture
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Texture -> IO Texture
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
  Integer -> WindowResources -> IO ()
forall a. Integral a => a -> WindowResources -> IO ()
addTextureId (Texture -> Integer
texture'id Texture
texture) WindowResources
wr
  Texture -> IO Texture
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Texture
texture
loadTextureFromImage :: Image -> WindowResources -> IO Texture
loadTextureFromImage :: Image -> WindowResources -> IO Texture
loadTextureFromImage Image
image WindowResources
wr = do
  Texture
texture <- Image -> (Ptr Image -> IO (Ptr Texture)) -> IO (Ptr Texture)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image Ptr Image -> IO (Ptr Texture)
c'loadTextureFromImage IO (Ptr Texture) -> (Ptr Texture -> IO Texture) -> IO Texture
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Texture -> IO Texture
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
  Integer -> WindowResources -> IO ()
forall a. Integral a => a -> WindowResources -> IO ()
addTextureId (Texture -> Integer
texture'id Texture
texture) WindowResources
wr
  Texture -> IO Texture
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Texture
texture
loadTextureCubemap :: Image -> CubemapLayout -> WindowResources -> IO Texture
loadTextureCubemap :: Image -> CubemapLayout -> WindowResources -> IO Texture
loadTextureCubemap Image
image CubemapLayout
layout WindowResources
wr = do
  Texture
texture <- Image -> (Ptr Image -> IO (Ptr Texture)) -> IO (Ptr Texture)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Image
image (\Ptr Image
i -> Ptr Image -> CInt -> IO (Ptr Texture)
c'loadTextureCubemap Ptr Image
i (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ CubemapLayout -> Int
forall a. Enum a => a -> Int
fromEnum CubemapLayout
layout)) IO (Ptr Texture) -> (Ptr Texture -> IO Texture) -> IO Texture
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Texture -> IO Texture
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
  Integer -> WindowResources -> IO ()
forall a. Integral a => a -> WindowResources -> IO ()
addTextureId (Texture -> Integer
texture'id Texture
texture) WindowResources
wr
  Texture -> IO Texture
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Texture
texture
loadRenderTexture :: Int -> Int -> WindowResources -> IO RenderTexture
loadRenderTexture :: Int -> Int -> WindowResources -> IO RenderTexture
loadRenderTexture Int
width Int
height WindowResources
wr = do
  RenderTexture
renderTexture <- CInt -> CInt -> IO (Ptr RenderTexture)
c'loadRenderTexture (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
width) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
height) IO (Ptr RenderTexture)
-> (Ptr RenderTexture -> IO RenderTexture) -> IO RenderTexture
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr RenderTexture -> IO RenderTexture
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
  Integer -> WindowResources -> IO ()
forall a. Integral a => a -> WindowResources -> IO ()
addFrameBuffer (RenderTexture -> Integer
renderTexture'id RenderTexture
renderTexture) WindowResources
wr
  Integer -> WindowResources -> IO ()
forall a. Integral a => a -> WindowResources -> IO ()
addTextureId (Texture -> Integer
texture'id (Texture -> Integer) -> Texture -> Integer
forall a b. (a -> b) -> a -> b
$ RenderTexture -> Texture
renderTexture'texture RenderTexture
renderTexture) WindowResources
wr
  RenderTexture -> IO RenderTexture
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return RenderTexture
renderTexture
isTextureReady :: Texture -> IO Bool
isTextureReady :: Texture -> IO Bool
isTextureReady Texture
texture = CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Texture -> (Ptr Texture -> IO CBool) -> IO CBool
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Texture
texture Ptr Texture -> IO CBool
c'isTextureReady
isRenderTextureReady :: RenderTexture -> IO Bool
isRenderTextureReady :: RenderTexture -> IO Bool
isRenderTextureReady RenderTexture
renderTexture = CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RenderTexture -> (Ptr RenderTexture -> IO CBool) -> IO CBool
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable RenderTexture
renderTexture Ptr RenderTexture -> IO CBool
c'isRenderTextureReady
unloadTexture :: Texture -> WindowResources -> IO ()
unloadTexture :: Texture -> WindowResources -> IO ()
unloadTexture Texture
texture = Integer -> WindowResources -> IO ()
forall a. Integral a => a -> WindowResources -> IO ()
unloadSingleTexture (Texture -> Integer
texture'id Texture
texture)
unloadRenderTexture :: RenderTexture -> WindowResources -> IO ()
unloadRenderTexture :: RenderTexture -> WindowResources -> IO ()
unloadRenderTexture RenderTexture
renderTexture WindowResources
wr = do
  Integer -> WindowResources -> IO ()
forall a. Integral a => a -> WindowResources -> IO ()
unloadSingleTexture (Texture -> Integer
texture'id (Texture -> Integer) -> Texture -> Integer
forall a b. (a -> b) -> a -> b
$ RenderTexture -> Texture
renderTexture'texture RenderTexture
renderTexture) WindowResources
wr
  Integer -> WindowResources -> IO ()
forall a. Integral a => a -> WindowResources -> IO ()
unloadSingleFrameBuffer (RenderTexture -> Integer
renderTexture'id RenderTexture
renderTexture) WindowResources
wr
updateTexture :: Texture -> Ptr () -> IO Texture
updateTexture :: Texture -> Ptr () -> IO Texture
updateTexture Texture
texture Ptr ()
pixels = Texture -> (Ptr Texture -> IO Texture) -> IO Texture
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Texture
texture (\Ptr Texture
t -> Ptr Texture -> Ptr () -> IO ()
c'updateTexture Ptr Texture
t Ptr ()
pixels IO () -> IO Texture -> IO Texture
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Texture -> IO Texture
forall a. Storable a => Ptr a -> IO a
peek Ptr Texture
t)
updateTextureRec :: Texture -> Rectangle -> Ptr () -> IO Texture
updateTextureRec :: Texture -> Rectangle -> Ptr () -> IO Texture
updateTextureRec Texture
texture Rectangle
rect Ptr ()
pixels = Texture -> (Ptr Texture -> IO Texture) -> IO Texture
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Texture
texture (\Ptr Texture
t -> Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Rectangle
rect (\Ptr Rectangle
r -> Ptr Texture -> Ptr Rectangle -> Ptr () -> IO ()
c'updateTextureRec Ptr Texture
t Ptr Rectangle
r Ptr ()
pixels) IO () -> IO Texture -> IO Texture
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Texture -> IO Texture
forall a. Storable a => Ptr a -> IO a
peek Ptr Texture
t)
genTextureMipmaps :: Texture -> IO Texture
genTextureMipmaps :: Texture -> IO Texture
genTextureMipmaps Texture
texture = Texture -> (Ptr Texture -> IO Texture) -> IO Texture
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Texture
texture (\Ptr Texture
t -> Ptr Texture -> IO ()
c'genTextureMipmaps Ptr Texture
t IO () -> IO Texture -> IO Texture
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Texture -> IO Texture
forall a. Storable a => Ptr a -> IO a
peek Ptr Texture
t)
setTextureFilter :: Texture -> TextureFilter -> IO Texture
setTextureFilter :: Texture -> TextureFilter -> IO Texture
setTextureFilter Texture
texture TextureFilter
filterType = Texture -> (Ptr Texture -> IO Texture) -> IO Texture
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Texture
texture (\Ptr Texture
t -> Ptr Texture -> CInt -> IO ()
c'setTextureFilter Ptr Texture
t (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ TextureFilter -> Int
forall a. Enum a => a -> Int
fromEnum TextureFilter
filterType) IO () -> IO Texture -> IO Texture
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Texture -> IO Texture
forall a. Storable a => Ptr a -> IO a
peek Ptr Texture
t)
setTextureWrap :: Texture -> TextureWrap -> IO Texture
setTextureWrap :: Texture -> TextureWrap -> IO Texture
setTextureWrap Texture
texture TextureWrap
wrap = Texture -> (Ptr Texture -> IO Texture) -> IO Texture
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Texture
texture (\Ptr Texture
t -> Ptr Texture -> CInt -> IO ()
c'setTextureWrap Ptr Texture
t (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ TextureWrap -> Int
forall a. Enum a => a -> Int
fromEnum TextureWrap
wrap) IO () -> IO Texture -> IO Texture
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Texture -> IO Texture
forall a. Storable a => Ptr a -> IO a
peek Ptr Texture
t)
drawTexture :: Texture -> Int -> Int -> Color -> IO ()
drawTexture :: Texture -> Int -> Int -> Color -> IO ()
drawTexture Texture
texture Int
x Int
y Color
tint = Texture -> (Ptr Texture -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Texture
texture (\Ptr Texture
t -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
tint (Ptr Texture -> CInt -> CInt -> Ptr Color -> IO ()
c'drawTexture Ptr Texture
t (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
y)))
drawTextureV :: Texture -> Vector2 -> Color -> IO ()
drawTextureV :: Texture -> Vector2 -> Color -> IO ()
drawTextureV Texture
texture Vector2
position Color
color = Texture -> (Ptr Texture -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Texture
texture (\Ptr Texture
t -> Vector2 -> (Ptr Vector2 -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Vector2
position (Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color ((Ptr Color -> IO ()) -> IO ())
-> (Ptr Vector2 -> Ptr Color -> IO ()) -> Ptr Vector2 -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Texture -> Ptr Vector2 -> Ptr Color -> IO ()
c'drawTextureV Ptr Texture
t))
drawTextureEx :: Texture -> Vector2 -> Float -> Float -> Color -> IO ()
drawTextureEx :: Texture -> Vector2 -> Float -> Float -> Color -> IO ()
drawTextureEx Texture
texture Vector2
position Float
rotation Float
scale Color
tint = Texture -> (Ptr Texture -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Texture
texture (\Ptr Texture
t -> Vector2 -> (Ptr Vector2 -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Vector2
position (\Ptr Vector2
p -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
tint (Ptr Texture
-> Ptr Vector2 -> CFloat -> CFloat -> Ptr Color -> IO ()
c'drawTextureEx Ptr Texture
t Ptr Vector2
p (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
rotation) (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
scale))))
drawTextureRec :: Texture -> Rectangle -> Vector2 -> Color -> IO ()
drawTextureRec :: Texture -> Rectangle -> Vector2 -> Color -> IO ()
drawTextureRec Texture
texture Rectangle
source Vector2
position Color
tint = Texture -> (Ptr Texture -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Texture
texture (\Ptr Texture
t -> Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Rectangle
source (\Ptr Rectangle
s -> Vector2 -> (Ptr Vector2 -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Vector2
position (Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
tint ((Ptr Color -> IO ()) -> IO ())
-> (Ptr Vector2 -> Ptr Color -> IO ()) -> Ptr Vector2 -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Texture -> Ptr Rectangle -> Ptr Vector2 -> Ptr Color -> IO ()
c'drawTextureRec Ptr Texture
t Ptr Rectangle
s)))
drawTexturePro :: Texture -> Rectangle -> Rectangle -> Vector2 -> Float -> Color -> IO ()
drawTexturePro :: Texture
-> Rectangle -> Rectangle -> Vector2 -> Float -> Color -> IO ()
drawTexturePro Texture
texture Rectangle
source Rectangle
dest Vector2
origin Float
rotation Color
tint = Texture -> (Ptr Texture -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Texture
texture (\Ptr Texture
t -> Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Rectangle
source (\Ptr Rectangle
s -> Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Rectangle
dest (\Ptr Rectangle
d -> Vector2 -> (Ptr Vector2 -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Vector2
origin (\Ptr Vector2
o -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
tint (Ptr Texture
-> Ptr Rectangle
-> Ptr Rectangle
-> Ptr Vector2
-> CFloat
-> Ptr Color
-> IO ()
c'drawTexturePro Ptr Texture
t Ptr Rectangle
s Ptr Rectangle
d Ptr Vector2
o (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
rotation))))))
drawTextureNPatch :: Texture -> NPatchInfo -> Rectangle -> Vector2 -> Float -> Color -> IO ()
drawTextureNPatch :: Texture
-> NPatchInfo -> Rectangle -> Vector2 -> Float -> Color -> IO ()
drawTextureNPatch Texture
texture NPatchInfo
nPatchInfo Rectangle
dest Vector2
origin Float
rotation Color
tint = Texture -> (Ptr Texture -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Texture
texture (\Ptr Texture
t -> NPatchInfo -> (Ptr NPatchInfo -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable NPatchInfo
nPatchInfo (\Ptr NPatchInfo
n -> Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Rectangle
dest (\Ptr Rectangle
d -> Vector2 -> (Ptr Vector2 -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Vector2
origin (\Ptr Vector2
o -> Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
tint (Ptr Texture
-> Ptr NPatchInfo
-> Ptr Rectangle
-> Ptr Vector2
-> CFloat
-> Ptr Color
-> IO ()
c'drawTextureNPatch Ptr Texture
t Ptr NPatchInfo
n Ptr Rectangle
d Ptr Vector2
o (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
rotation))))))
fade :: Color -> Float -> Color
fade :: Color -> Float -> Color
fade Color
color Float
alpha = IO Color -> Color
forall a. IO a -> a
unsafePerformIO (IO Color -> Color) -> IO Color -> Color
forall a b. (a -> b) -> a -> b
$ Color -> (Ptr Color -> IO (Ptr Color)) -> IO (Ptr Color)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (\Ptr Color
c -> Ptr Color -> CFloat -> IO (Ptr Color)
c'fade Ptr Color
c (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
alpha)) IO (Ptr Color) -> (Ptr Color -> IO Color) -> IO Color
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Color -> IO Color
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
colorToInt :: Color -> Int
colorToInt :: Color -> Int
colorToInt Color
color = IO Int -> Int
forall a. IO a -> a
unsafePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Color -> (Ptr Color -> IO CInt) -> IO CInt
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color Ptr Color -> IO CInt
c'colorToInt
colorNormalize :: Color -> Vector4
colorNormalize :: Color -> Vector4
colorNormalize Color
color = IO Vector4 -> Vector4
forall a. IO a -> a
unsafePerformIO (IO Vector4 -> Vector4) -> IO Vector4 -> Vector4
forall a b. (a -> b) -> a -> b
$ Color -> (Ptr Color -> IO (Ptr Vector4)) -> IO (Ptr Vector4)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color Ptr Color -> IO (Ptr Vector4)
c'colorNormalize IO (Ptr Vector4) -> (Ptr Vector4 -> IO Vector4) -> IO Vector4
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Vector4 -> IO Vector4
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
colorFromNormalized :: Vector4 -> Color
colorFromNormalized :: Vector4 -> Color
colorFromNormalized Vector4
normalized = IO Color -> Color
forall a. IO a -> a
unsafePerformIO (IO Color -> Color) -> IO Color -> Color
forall a b. (a -> b) -> a -> b
$ Vector4 -> (Ptr Vector4 -> IO (Ptr Color)) -> IO (Ptr Color)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Vector4
normalized Ptr Vector4 -> IO (Ptr Color)
c'colorFromNormalized IO (Ptr Color) -> (Ptr Color -> IO Color) -> IO Color
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Color -> IO Color
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
colorToHSV :: Color -> Vector3
colorToHSV :: Color -> Vector3
colorToHSV Color
color = IO Vector3 -> Vector3
forall a. IO a -> a
unsafePerformIO (IO Vector3 -> Vector3) -> IO Vector3 -> Vector3
forall a b. (a -> b) -> a -> b
$ Color -> (Ptr Color -> IO (Ptr Vector3)) -> IO (Ptr Vector3)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color Ptr Color -> IO (Ptr Vector3)
c'colorToHSV IO (Ptr Vector3) -> (Ptr Vector3 -> IO Vector3) -> IO Vector3
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Vector3 -> IO Vector3
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
colorFromHSV :: Float -> Float -> Float -> Color
colorFromHSV :: Float -> Float -> Float -> Color
colorFromHSV Float
hue Float
saturation Float
value = IO Color -> Color
forall a. IO a -> a
unsafePerformIO (IO Color -> Color) -> IO Color -> Color
forall a b. (a -> b) -> a -> b
$ CFloat -> CFloat -> CFloat -> IO (Ptr Color)
c'colorFromHSV (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
hue) (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
saturation) (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
value) IO (Ptr Color) -> (Ptr Color -> IO Color) -> IO Color
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Color -> IO Color
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
colorTint :: Color -> Color -> Color
colorTint :: Color -> Color -> Color
colorTint Color
color Color
tint = IO Color -> Color
forall a. IO a -> a
unsafePerformIO (IO Color -> Color) -> IO Color -> Color
forall a b. (a -> b) -> a -> b
$ Color -> (Ptr Color -> IO (Ptr Color)) -> IO (Ptr Color)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (Color -> (Ptr Color -> IO (Ptr Color)) -> IO (Ptr Color)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
tint ((Ptr Color -> IO (Ptr Color)) -> IO (Ptr Color))
-> (Ptr Color -> Ptr Color -> IO (Ptr Color))
-> Ptr Color
-> IO (Ptr Color)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Color -> Ptr Color -> IO (Ptr Color)
c'colorTint) IO (Ptr Color) -> (Ptr Color -> IO Color) -> IO Color
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Color -> IO Color
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
colorBrightness :: Color -> Float -> Color
colorBrightness :: Color -> Float -> Color
colorBrightness Color
color Float
brightness = IO Color -> Color
forall a. IO a -> a
unsafePerformIO (IO Color -> Color) -> IO Color -> Color
forall a b. (a -> b) -> a -> b
$ Color -> (Ptr Color -> IO (Ptr Color)) -> IO (Ptr Color)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (\Ptr Color
c -> Ptr Color -> CFloat -> IO (Ptr Color)
c'colorBrightness Ptr Color
c (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
brightness)) IO (Ptr Color) -> (Ptr Color -> IO Color) -> IO Color
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Color -> IO Color
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
colorContrast :: Color -> Float -> Color
colorContrast :: Color -> Float -> Color
colorContrast Color
color Float
contrast = IO Color -> Color
forall a. IO a -> a
unsafePerformIO (IO Color -> Color) -> IO Color -> Color
forall a b. (a -> b) -> a -> b
$ Color -> (Ptr Color -> IO (Ptr Color)) -> IO (Ptr Color)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (\Ptr Color
c -> Ptr Color -> CFloat -> IO (Ptr Color)
c'colorContrast Ptr Color
c (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
contrast)) IO (Ptr Color) -> (Ptr Color -> IO Color) -> IO Color
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Color -> IO Color
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
colorAlpha :: Color -> Float -> Color
colorAlpha :: Color -> Float -> Color
colorAlpha Color
color Float
alpha = IO Color -> Color
forall a. IO a -> a
unsafePerformIO (IO Color -> Color) -> IO Color -> Color
forall a b. (a -> b) -> a -> b
$ Color -> (Ptr Color -> IO (Ptr Color)) -> IO (Ptr Color)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (\Ptr Color
c -> Ptr Color -> CFloat -> IO (Ptr Color)
c'colorAlpha Ptr Color
c (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
alpha)) IO (Ptr Color) -> (Ptr Color -> IO Color) -> IO Color
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Color -> IO Color
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
colorAlphaBlend :: Color -> Color -> Color -> Color
colorAlphaBlend :: Color -> Color -> Color -> Color
colorAlphaBlend Color
dst Color
src Color
tint = IO Color -> Color
forall a. IO a -> a
unsafePerformIO (IO Color -> Color) -> IO Color -> Color
forall a b. (a -> b) -> a -> b
$ Color -> (Ptr Color -> IO (Ptr Color)) -> IO (Ptr Color)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
dst (\Ptr Color
d -> Color -> (Ptr Color -> IO (Ptr Color)) -> IO (Ptr Color)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
src (Color -> (Ptr Color -> IO (Ptr Color)) -> IO (Ptr Color)
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
tint ((Ptr Color -> IO (Ptr Color)) -> IO (Ptr Color))
-> (Ptr Color -> Ptr Color -> IO (Ptr Color))
-> Ptr Color
-> IO (Ptr Color)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Color -> Ptr Color -> Ptr Color -> IO (Ptr Color)
c'colorAlphaBlend Ptr Color
d)) IO (Ptr Color) -> (Ptr Color -> IO Color) -> IO Color
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Color -> IO Color
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
getColor :: Integer -> Color
getColor :: Integer -> Color
getColor Integer
hexValue = IO Color -> Color
forall a. IO a -> a
unsafePerformIO (IO Color -> Color) -> IO Color -> Color
forall a b. (a -> b) -> a -> b
$ CUInt -> IO (Ptr Color)
c'getColor (Integer -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
hexValue) IO (Ptr Color) -> (Ptr Color -> IO Color) -> IO Color
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Color -> IO Color
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
getPixelColor :: Ptr () -> PixelFormat -> IO Color
getPixelColor :: Ptr () -> PixelFormat -> IO Color
getPixelColor Ptr ()
srcPtr PixelFormat
format = Ptr () -> CInt -> IO (Ptr Color)
c'getPixelColor Ptr ()
srcPtr (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ PixelFormat -> Int
forall a. Enum a => a -> Int
fromEnum PixelFormat
format) IO (Ptr Color) -> (Ptr Color -> IO Color) -> IO Color
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr Color -> IO Color
forall a. (Freeable a, Storable a) => Ptr a -> IO a
pop
setPixelColor :: Ptr () -> Color -> PixelFormat -> IO ()
setPixelColor :: Ptr () -> Color -> PixelFormat -> IO ()
setPixelColor Ptr ()
dstPtr Color
color PixelFormat
format = Color -> (Ptr Color -> IO ()) -> IO ()
forall a b.
(Freeable a, Storable a) =>
a -> (Ptr a -> IO b) -> IO b
withFreeable Color
color (\Ptr Color
c -> Ptr () -> Ptr Color -> CInt -> IO ()
c'setPixelColor Ptr ()
dstPtr Ptr Color
c (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ PixelFormat -> Int
forall a. Enum a => a -> Int
fromEnum PixelFormat
format))
getPixelDataSize :: Int -> Int -> PixelFormat -> Int
getPixelDataSize :: Int -> Int -> PixelFormat -> Int
getPixelDataSize Int
width Int
height PixelFormat
format = Int -> Int -> Int -> Int
I.getPixelDataSize Int
width Int
height (PixelFormat -> Int
forall a. Enum a => a -> Int
fromEnum PixelFormat
format)