{-# LANGUAGE CPP #-}

module SDL.Raw.Video (
  -- * Display and Window Management
  createWindow,
  createWindowAndRenderer,
  createWindowFrom,
  destroyWindow,
  disableScreenSaver,
  enableScreenSaver,
  glBindTexture,
  glCreateContext,
  glDeleteContext,
  glExtensionSupported,
  glGetAttribute,
  glGetCurrentContext,
  glGetCurrentWindow,
  glGetDrawableSize,
  glGetProcAddress,
  glGetSwapInterval,
  glLoadLibrary,
  glMakeCurrent,
  glResetAttributes,
  glSetAttribute,
  glSetSwapInterval,
  glSwapWindow,
  glUnbindTexture,
  glUnloadLibrary,
  getClosestDisplayMode,
  getCurrentDisplayMode,
  getCurrentVideoDriver,
  getDesktopDisplayMode,
  getDisplayBounds,
  getDisplayDPI,
  getDisplayMode,
  getDisplayName,
  getDisplayUsableBounds,
  getGrabbedWindow,
  getNumDisplayModes,
  getNumVideoDisplays,
  getNumVideoDrivers,
  getVideoDriver,
  getWindowBordersSize,
  getWindowBrightness,
  getWindowData,
  getWindowDisplayIndex,
  getWindowDisplayMode,
  getWindowFlags,
  getWindowFromID,
  getWindowGammaRamp,
  getWindowGrab,
  getWindowID,
  getWindowMaximumSize,
  getWindowMinimumSize,
  getWindowPixelFormat,
  getWindowPosition,
  getWindowSize,
  getWindowSurface,
  getWindowTitle,
  hideWindow,
  isScreenSaverEnabled,
  maximizeWindow,
  minimizeWindow,
  raiseWindow,
  restoreWindow,
  setWindowBordered,
  setWindowBrightness,
  setWindowData,
  setWindowDisplayMode,
  setWindowFullscreen,
  setWindowGammaRamp,
  setWindowGrab,
  setWindowIcon,
  setWindowMaximumSize,
  setWindowMinimumSize,
  setWindowPosition,
  setWindowSize,
  setWindowTitle,
  showMessageBox,
  showSimpleMessageBox,
  showWindow,
  updateWindowSurface,
  updateWindowSurfaceRects,
  videoInit,
  videoQuit,

  -- * 2D Accelerated Rendering
  composeCustomBlendMode,
  createRenderer,
  createSoftwareRenderer,
  createTexture,
  createTextureFromSurface,
  destroyRenderer,
  destroyTexture,
  getNumRenderDrivers,
  getRenderDrawBlendMode,
  getRenderDrawColor,
  getRenderDriverInfo,
  getRenderTarget,
  getRenderer,
  getRendererInfo,
  getRendererOutputSize,
  getTextureAlphaMod,
  getTextureBlendMode,
  getTextureColorMod,
  lockTexture,
  queryTexture,
  renderClear,
  renderCopy,
  renderCopyEx,
#ifdef RECENT_ISH
  renderCopyExF,
#endif
  renderDrawLine,
  renderDrawLines,
  renderDrawPoint,
  renderDrawPoints,
  renderDrawRect,
  renderDrawRects,
  renderFillRect,
  renderFillRectEx,
  renderFillRects,
  renderGetClipRect,
  renderGetLogicalSize,
  renderGetScale,
  renderGetViewport,
  renderIsClipEnabled,
  renderPresent,
  renderReadPixels,
  renderSetClipRect,
  renderSetLogicalSize,
  renderSetScale,
  renderSetViewport,
  renderTargetSupported,
  setRenderDrawBlendMode,
  setRenderDrawColor,
  setRenderTarget,
  setTextureAlphaMod,
  setTextureBlendMode,
  setTextureColorMod,
  unlockTexture,
  updateTexture,
  updateYUVTexture,

  -- * Pixel Formats and Conversion Routines
  allocFormat,
  allocPalette,
  calculateGammaRamp,
  freeFormat,
  freePalette,
  getPixelFormatName,
  getRGB,
  getRGBA,
  mapRGB,
  mapRGBA,
  masksToPixelFormatEnum,
  pixelFormatEnumToMasks,
  setPaletteColors,
  setPixelFormatPalette,

  -- * Rectangle Functions
  enclosePoints,
  hasIntersection,
  intersectRect,
  intersectRectAndLine,
  unionRect,

  -- * Surface Creation and Simple Drawing
  blitScaled,
  blitSurface,
  convertPixels,
  convertSurface,
  convertSurfaceFormat,
  createRGBSurface,
  createRGBSurfaceFrom,
  fillRect,
  fillRects,
  freeSurface,
  getClipRect,
  getColorKey,
  getSurfaceAlphaMod,
  getSurfaceBlendMode,
  getSurfaceColorMod,
  loadBMP,
  loadBMP_RW,
  lockSurface,
  lowerBlit,
  lowerBlitScaled,
  saveBMP,
  saveBMP_RW,
  setClipRect,
  setColorKey,
  setSurfaceAlphaMod,
  setSurfaceBlendMode,
  setSurfaceColorMod,
  setSurfacePalette,
  setSurfaceRLE,
  unlockSurface,

  -- * Platform-specific Window Management
  getWindowWMInfo,

  -- * Clipboard Handling
  getClipboardText,
  hasClipboardText,
  setClipboardText,

  -- * Vulkan support functions
  vkLoadLibrary,
  vkGetVkGetInstanceProcAddr,
  vkUnloadLibrary,
  vkGetInstanceExtensions,
  vkCreateSurface,
  vkGetDrawableSize
) where

import Control.Monad.IO.Class
import Data.Word
import Foreign.C.String
import Foreign.C.Types
import Foreign.Ptr
import SDL.Raw.Enum
import SDL.Raw.Filesystem
import SDL.Raw.Types

foreign import ccall "SDL.h SDL_CreateWindow" createWindowFFI :: CString -> CInt -> CInt -> CInt -> CInt -> Word32 -> IO Window
foreign import ccall "SDL.h SDL_CreateWindowAndRenderer" createWindowAndRendererFFI :: CInt -> CInt -> Word32 -> Ptr Window -> Ptr Renderer -> IO CInt
foreign import ccall "SDL.h SDL_CreateWindowFrom" createWindowFromFFI :: Ptr () -> IO Window
foreign import ccall "SDL.h SDL_DestroyWindow" destroyWindowFFI :: Window -> IO ()
foreign import ccall "SDL.h SDL_DisableScreenSaver" disableScreenSaverFFI :: IO ()
foreign import ccall "SDL.h SDL_EnableScreenSaver" enableScreenSaverFFI :: IO ()
foreign import ccall "SDL.h SDL_GL_BindTexture" glBindTextureFFI :: Texture -> Ptr CFloat -> Ptr CFloat -> IO CInt
foreign import ccall "SDL.h SDL_GL_CreateContext" glCreateContextFFI :: Window -> IO GLContext
foreign import ccall "SDL.h SDL_GL_DeleteContext" glDeleteContextFFI :: GLContext -> IO ()
foreign import ccall "SDL.h SDL_GL_ExtensionSupported" glExtensionSupportedFFI :: CString -> IO Bool
foreign import ccall "SDL.h SDL_GL_GetAttribute" glGetAttributeFFI :: GLattr -> Ptr CInt -> IO CInt
foreign import ccall "SDL.h SDL_GL_GetCurrentContext" glGetCurrentContextFFI :: IO GLContext
foreign import ccall "SDL.h SDL_GL_GetCurrentWindow" glGetCurrentWindowFFI :: IO Window
foreign import ccall "SDL.h SDL_GL_GetDrawableSize" glGetDrawableSizeFFI :: Window -> Ptr CInt -> Ptr CInt -> IO ()
foreign import ccall "SDL.h SDL_GL_GetProcAddress" glGetProcAddressFFI :: CString -> IO (Ptr ())
foreign import ccall "SDL.h SDL_GL_GetSwapInterval" glGetSwapIntervalFFI :: IO CInt
foreign import ccall "SDL.h SDL_GL_LoadLibrary" glLoadLibraryFFI :: CString -> IO CInt
foreign import ccall "SDL.h SDL_GL_MakeCurrent" glMakeCurrentFFI :: Window -> GLContext -> IO CInt
foreign import ccall "SDL.h SDL_GL_ResetAttributes" glResetAttributesFFI :: IO ()
foreign import ccall "SDL.h SDL_GL_SetAttribute" glSetAttributeFFI :: GLattr -> CInt -> IO CInt
foreign import ccall "SDL.h SDL_GL_SetSwapInterval" glSetSwapIntervalFFI :: CInt -> IO CInt
foreign import ccall "SDL.h SDL_GL_SwapWindow" glSwapWindowFFI :: Window -> IO ()
foreign import ccall "SDL.h SDL_GL_UnbindTexture" glUnbindTextureFFI :: Texture -> IO CInt
foreign import ccall "SDL.h SDL_GL_UnloadLibrary" glUnloadLibraryFFI :: IO ()
foreign import ccall "SDL.h SDL_GetClosestDisplayMode" getClosestDisplayModeFFI :: CInt -> Ptr DisplayMode -> Ptr DisplayMode -> IO (Ptr DisplayMode)
foreign import ccall "SDL.h SDL_GetCurrentDisplayMode" getCurrentDisplayModeFFI :: CInt -> Ptr DisplayMode -> IO CInt
foreign import ccall "SDL.h SDL_GetCurrentVideoDriver" getCurrentVideoDriverFFI :: IO CString
foreign import ccall "SDL.h SDL_GetDesktopDisplayMode" getDesktopDisplayModeFFI :: CInt -> Ptr DisplayMode -> IO CInt
foreign import ccall "SDL.h SDL_GetDisplayBounds" getDisplayBoundsFFI :: CInt -> Ptr Rect -> IO CInt
foreign import ccall "SDL.h SDL_GetDisplayDPI" getDisplayDPIFFI :: CInt -> Ptr CFloat -> Ptr CFloat -> Ptr CFloat -> IO CInt
foreign import ccall "SDL.h SDL_GetDisplayMode" getDisplayModeFFI :: CInt -> CInt -> Ptr DisplayMode -> IO CInt
foreign import ccall "SDL.h SDL_GetDisplayName" getDisplayNameFFI :: CInt -> IO CString
foreign import ccall "SDL.h SDL_GetDisplayUsableBounds" getDisplayUsableBoundsFFI :: CInt -> Ptr Rect -> IO CInt
foreign import ccall "SDL.h SDL_GetGrabbedWindow" getGrabbedWindowFFI :: IO Window
foreign import ccall "SDL.h SDL_GetNumDisplayModes" getNumDisplayModesFFI :: CInt -> IO CInt
foreign import ccall "SDL.h SDL_GetNumVideoDisplays" getNumVideoDisplaysFFI :: IO CInt
foreign import ccall "SDL.h SDL_GetNumVideoDrivers" getNumVideoDriversFFI :: IO CInt
foreign import ccall "SDL.h SDL_GetVideoDriver" getVideoDriverFFI :: CInt -> IO CString
foreign import ccall "SDL.h SDL_GetWindowBordersSize" getWindowBordersSizeFFI :: Window -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO CInt
foreign import ccall "SDL.h SDL_GetWindowBrightness" getWindowBrightnessFFI :: Window -> IO CFloat
foreign import ccall "SDL.h SDL_GetWindowData" getWindowDataFFI :: Window -> CString -> IO (Ptr ())
foreign import ccall "SDL.h SDL_GetWindowDisplayIndex" getWindowDisplayIndexFFI :: Window -> IO CInt
foreign import ccall "SDL.h SDL_GetWindowDisplayMode" getWindowDisplayModeFFI :: Window -> Ptr DisplayMode -> IO CInt
foreign import ccall "SDL.h SDL_GetWindowFlags" getWindowFlagsFFI :: Window -> IO Word32
foreign import ccall "SDL.h SDL_GetWindowFromID" getWindowFromIDFFI :: Word32 -> IO Window
foreign import ccall "SDL.h SDL_GetWindowGammaRamp" getWindowGammaRampFFI :: Window -> Ptr Word16 -> Ptr Word16 -> Ptr Word16 -> IO CInt
foreign import ccall "SDL.h SDL_GetWindowGrab" getWindowGrabFFI :: Window -> IO Bool
foreign import ccall "SDL.h SDL_GetWindowID" getWindowIDFFI :: Window -> IO Word32
foreign import ccall "SDL.h SDL_GetWindowMaximumSize" getWindowMaximumSizeFFI :: Window -> Ptr CInt -> Ptr CInt -> IO ()
foreign import ccall "SDL.h SDL_GetWindowMinimumSize" getWindowMinimumSizeFFI :: Window -> Ptr CInt -> Ptr CInt -> IO ()
foreign import ccall "SDL.h SDL_GetWindowPixelFormat" getWindowPixelFormatFFI :: Window -> IO Word32
foreign import ccall "SDL.h SDL_GetWindowPosition" getWindowPositionFFI :: Window -> Ptr CInt -> Ptr CInt -> IO ()
foreign import ccall "SDL.h SDL_GetWindowSize" getWindowSizeFFI :: Window -> Ptr CInt -> Ptr CInt -> IO ()
foreign import ccall "SDL.h SDL_GetWindowSurface" getWindowSurfaceFFI :: Window -> IO (Ptr Surface)
foreign import ccall "SDL.h SDL_GetWindowTitle" getWindowTitleFFI :: Window -> IO CString
foreign import ccall "SDL.h SDL_HideWindow" hideWindowFFI :: Window -> IO ()
foreign import ccall "SDL.h SDL_IsScreenSaverEnabled" isScreenSaverEnabledFFI :: IO Bool
foreign import ccall "SDL.h SDL_MaximizeWindow" maximizeWindowFFI :: Window -> IO ()
foreign import ccall "SDL.h SDL_MinimizeWindow" minimizeWindowFFI :: Window -> IO ()
foreign import ccall "SDL.h SDL_RaiseWindow" raiseWindowFFI :: Window -> IO ()
foreign import ccall "SDL.h SDL_RestoreWindow" restoreWindowFFI :: Window -> IO ()
foreign import ccall "SDL.h SDL_SetWindowBordered" setWindowBorderedFFI :: Window -> Bool -> IO ()
foreign import ccall "SDL.h SDL_SetWindowBrightness" setWindowBrightnessFFI :: Window -> CFloat -> IO CInt
foreign import ccall "SDL.h SDL_SetWindowData" setWindowDataFFI :: Window -> CString -> Ptr () -> IO (Ptr ())
foreign import ccall "SDL.h SDL_SetWindowDisplayMode" setWindowDisplayModeFFI :: Window -> Ptr DisplayMode -> IO CInt
foreign import ccall "SDL.h SDL_SetWindowFullscreen" setWindowFullscreenFFI :: Window -> Word32 -> IO CInt
foreign import ccall "SDL.h SDL_SetWindowGammaRamp" setWindowGammaRampFFI :: Window -> Ptr Word16 -> Ptr Word16 -> Ptr Word16 -> IO CInt
foreign import ccall "SDL.h SDL_SetWindowGrab" setWindowGrabFFI :: Window -> Bool -> IO ()
foreign import ccall "SDL.h SDL_SetWindowIcon" setWindowIconFFI :: Window -> Ptr Surface -> IO ()
foreign import ccall "SDL.h SDL_SetWindowMaximumSize" setWindowMaximumSizeFFI :: Window -> CInt -> CInt -> IO ()
foreign import ccall "SDL.h SDL_SetWindowMinimumSize" setWindowMinimumSizeFFI :: Window -> CInt -> CInt -> IO ()
foreign import ccall "SDL.h SDL_SetWindowPosition" setWindowPositionFFI :: Window -> CInt -> CInt -> IO ()
foreign import ccall "SDL.h SDL_SetWindowSize" setWindowSizeFFI :: Window -> CInt -> CInt -> IO ()
foreign import ccall "SDL.h SDL_SetWindowTitle" setWindowTitleFFI :: Window -> CString -> IO ()
foreign import ccall "SDL.h SDL_ShowMessageBox" showMessageBoxFFI :: Ptr MessageBoxData -> Ptr CInt -> IO CInt
foreign import ccall "SDL.h SDL_ShowSimpleMessageBox" showSimpleMessageBoxFFI :: Word32 -> CString -> CString -> Window -> IO CInt
foreign import ccall "SDL.h SDL_ShowWindow" showWindowFFI :: Window -> IO ()
foreign import ccall "SDL.h SDL_UpdateWindowSurface" updateWindowSurfaceFFI :: Window -> IO CInt
foreign import ccall "SDL.h SDL_UpdateWindowSurfaceRects" updateWindowSurfaceRectsFFI :: Window -> Ptr Rect -> CInt -> IO CInt
foreign import ccall "SDL.h SDL_VideoInit" videoInitFFI :: CString -> IO CInt
foreign import ccall "SDL.h SDL_VideoQuit" videoQuitFFI :: IO ()

foreign import ccall "SDL.h SDL_ComposeCustomBlendMode" composeCustomBlendModeFFI :: BlendFactor -> BlendFactor -> BlendOperation -> BlendFactor -> BlendFactor -> BlendOperation -> IO BlendMode
foreign import ccall "SDL.h SDL_CreateRenderer" createRendererFFI :: Window -> CInt -> Word32 -> IO Renderer
foreign import ccall "SDL.h SDL_CreateSoftwareRenderer" createSoftwareRendererFFI :: Ptr Surface -> IO Renderer
foreign import ccall "SDL.h SDL_CreateTexture" createTextureFFI :: Renderer -> Word32 -> CInt -> CInt -> CInt -> IO Texture
foreign import ccall "SDL.h SDL_CreateTextureFromSurface" createTextureFromSurfaceFFI :: Renderer -> Ptr Surface -> IO Texture
foreign import ccall "SDL.h SDL_DestroyRenderer" destroyRendererFFI :: Renderer -> IO ()
foreign import ccall "SDL.h SDL_DestroyTexture" destroyTextureFFI :: Texture -> IO ()
foreign import ccall "SDL.h SDL_GetNumRenderDrivers" getNumRenderDriversFFI :: IO CInt
foreign import ccall "SDL.h SDL_GetRenderDrawBlendMode" getRenderDrawBlendModeFFI :: Renderer -> Ptr BlendMode -> IO Int
foreign import ccall "SDL.h SDL_GetRenderDrawColor" getRenderDrawColorFFI :: Renderer -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO CInt
foreign import ccall "SDL.h SDL_GetRenderDriverInfo" getRenderDriverInfoFFI :: CInt -> Ptr RendererInfo -> IO CInt
foreign import ccall "SDL.h SDL_GetRenderTarget" getRenderTargetFFI :: Renderer -> IO Texture
foreign import ccall "SDL.h SDL_GetRenderer" getRendererFFI :: Window -> IO Renderer
foreign import ccall "SDL.h SDL_GetRendererInfo" getRendererInfoFFI :: Renderer -> Ptr RendererInfo -> IO CInt
foreign import ccall "SDL.h SDL_GetRendererOutputSize" getRendererOutputSizeFFI :: Renderer -> Ptr CInt -> Ptr CInt -> IO CInt
foreign import ccall "SDL.h SDL_GetTextureAlphaMod" getTextureAlphaModFFI :: Texture -> Ptr Word8 -> IO CInt
foreign import ccall "SDL.h SDL_GetTextureBlendMode" getTextureBlendModeFFI :: Texture -> Ptr BlendMode -> IO CInt
foreign import ccall "SDL.h SDL_GetTextureColorMod" getTextureColorModFFI :: Texture -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO CInt
foreign import ccall "SDL.h SDL_LockTexture" lockTextureFFI :: Texture -> Ptr Rect -> Ptr (Ptr ()) -> Ptr CInt -> IO CInt
foreign import ccall "SDL.h SDL_QueryTexture" queryTextureFFI :: Texture -> Ptr Word32 -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO CInt
foreign import ccall "SDL.h SDL_RenderClear" renderClearFFI :: Renderer -> IO CInt
foreign import ccall "SDL.h SDL_RenderCopy" renderCopyFFI :: Renderer -> Texture -> Ptr Rect -> Ptr Rect -> IO CInt
foreign import ccall "SDL.h SDL_RenderCopyEx" renderCopyExFFI :: Renderer -> Texture -> Ptr Rect -> Ptr Rect -> CDouble -> Ptr Point -> RendererFlip -> IO CInt
#ifdef RECENT_ISH
foreign import ccall "SDL.h SDL_RenderCopyExF" renderCopyExFFFI :: Renderer -> Texture -> Ptr Rect -> Ptr FRect -> CDouble -> Ptr FPoint -> RendererFlip -> IO CInt
#endif
foreign import ccall "SDL.h SDL_RenderDrawLine" renderDrawLineFFI :: Renderer -> CInt -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "SDL.h SDL_RenderDrawLines" renderDrawLinesFFI :: Renderer -> Ptr Point -> CInt -> IO CInt
foreign import ccall "SDL.h SDL_RenderDrawPoint" renderDrawPointFFI :: Renderer -> CInt -> CInt -> IO CInt
foreign import ccall "SDL.h SDL_RenderDrawPoints" renderDrawPointsFFI :: Renderer -> Ptr Point -> CInt -> IO CInt
foreign import ccall "SDL.h SDL_RenderDrawRect" renderDrawRectFFI :: Renderer -> Ptr Rect -> IO CInt
foreign import ccall "SDL.h SDL_RenderDrawRects" renderDrawRectsFFI :: Renderer -> Ptr Rect -> CInt -> IO CInt
foreign import ccall "SDL.h SDL_RenderFillRect" renderFillRectFFI :: Renderer -> Ptr Rect -> IO CInt
foreign import ccall "sqlhelper.c SDLHelper_RenderFillRectEx" renderFillRectExFFI :: Renderer -> CInt -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "SDL.h SDL_RenderFillRects" renderFillRectsFFI :: Renderer -> Ptr Rect -> CInt -> IO CInt
foreign import ccall "SDL.h SDL_RenderGetClipRect" renderGetClipRectFFI :: Renderer -> Ptr Rect -> IO ()
foreign import ccall "SDL.h SDL_RenderGetLogicalSize" renderGetLogicalSizeFFI :: Renderer -> Ptr CInt -> Ptr CInt -> IO ()
foreign import ccall "SDL.h SDL_RenderGetScale" renderGetScaleFFI :: Renderer -> Ptr CFloat -> Ptr CFloat -> IO ()
foreign import ccall "SDL.h SDL_RenderGetViewport" renderGetViewportFFI :: Renderer -> Ptr Rect -> IO ()
foreign import ccall "SDL.h SDL_RenderIsClipEnabled" renderIsClipEnabledFFI :: Renderer -> IO Bool
foreign import ccall "SDL.h SDL_RenderPresent" renderPresentFFI :: Renderer -> IO ()
foreign import ccall "SDL.h SDL_RenderReadPixels" renderReadPixelsFFI :: Renderer -> Ptr Rect -> Word32 -> Ptr () -> CInt -> IO CInt
foreign import ccall "SDL.h SDL_RenderSetClipRect" renderSetClipRectFFI :: Renderer -> Ptr Rect -> IO CInt
foreign import ccall "SDL.h SDL_RenderSetLogicalSize" renderSetLogicalSizeFFI :: Renderer -> CInt -> CInt -> IO CInt
foreign import ccall "SDL.h SDL_RenderSetScale" renderSetScaleFFI :: Renderer -> CFloat -> CFloat -> IO CInt
foreign import ccall "SDL.h SDL_RenderSetViewport" renderSetViewportFFI :: Renderer -> Ptr Rect -> IO CInt
foreign import ccall "SDL.h SDL_RenderTargetSupported" renderTargetSupportedFFI :: Renderer -> IO Bool
foreign import ccall "SDL.h SDL_SetRenderDrawBlendMode" setRenderDrawBlendModeFFI :: Renderer -> BlendMode -> IO CInt
foreign import ccall "SDL.h SDL_SetRenderDrawColor" setRenderDrawColorFFI :: Renderer -> Word8 -> Word8 -> Word8 -> Word8 -> IO CInt
foreign import ccall "SDL.h SDL_SetRenderTarget" setRenderTargetFFI :: Renderer -> Texture -> IO CInt
foreign import ccall "SDL.h SDL_SetTextureAlphaMod" setTextureAlphaModFFI :: Texture -> Word8 -> IO CInt
foreign import ccall "SDL.h SDL_SetTextureBlendMode" setTextureBlendModeFFI :: Texture -> BlendMode -> IO CInt
foreign import ccall "SDL.h SDL_SetTextureColorMod" setTextureColorModFFI :: Texture -> Word8 -> Word8 -> Word8 -> IO CInt
foreign import ccall "SDL.h SDL_UnlockTexture" unlockTextureFFI :: Texture -> IO ()
foreign import ccall "SDL.h SDL_UpdateTexture" updateTextureFFI :: Texture -> Ptr Rect -> Ptr () -> CInt -> IO CInt
foreign import ccall "SDL.h SDL_UpdateYUVTexture" updateYUVTextureFFI :: Texture -> Ptr Rect -> Ptr Word8 -> CInt -> Ptr Word8 -> CInt -> Ptr Word8 -> CInt -> IO CInt

foreign import ccall "SDL.h SDL_AllocFormat" allocFormatFFI :: Word32 -> IO (Ptr PixelFormat)
foreign import ccall "SDL.h SDL_AllocPalette" allocPaletteFFI :: CInt -> IO (Ptr Palette)
foreign import ccall "SDL.h SDL_CalculateGammaRamp" calculateGammaRampFFI :: CFloat -> Ptr Word16 -> IO ()
foreign import ccall "SDL.h SDL_FreeFormat" freeFormatFFI :: Ptr PixelFormat -> IO ()
foreign import ccall "SDL.h SDL_FreePalette" freePaletteFFI :: Ptr Palette -> IO ()
foreign import ccall "SDL.h SDL_GetPixelFormatName" getPixelFormatNameFFI :: Word32 -> IO CString
foreign import ccall "SDL.h SDL_GetRGB" getRGBFFI :: Word32 -> Ptr PixelFormat -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO ()
foreign import ccall "SDL.h SDL_GetRGBA" getRGBAFFI :: Word32 -> Ptr PixelFormat -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO ()
foreign import ccall "SDL.h SDL_MapRGB" mapRGBFFI :: Ptr PixelFormat -> Word8 -> Word8 -> Word8 -> IO Word32
foreign import ccall "SDL.h SDL_MapRGBA" mapRGBAFFI :: Ptr PixelFormat -> Word8 -> Word8 -> Word8 -> Word8 -> IO Word32
foreign import ccall "SDL.h SDL_MasksToPixelFormatEnum" masksToPixelFormatEnumFFI :: CInt -> Word32 -> Word32 -> Word32 -> Word32 -> IO Word32
foreign import ccall "SDL.h SDL_PixelFormatEnumToMasks" pixelFormatEnumToMasksFFI :: Word32 -> Ptr CInt -> Ptr Word32 -> Ptr Word32 -> Ptr Word32 -> Ptr Word32 -> IO Bool
foreign import ccall "SDL.h SDL_SetPaletteColors" setPaletteColorsFFI :: Ptr Palette -> Ptr Color -> CInt -> CInt -> IO CInt
foreign import ccall "SDL.h SDL_SetPixelFormatPalette" setPixelFormatPaletteFFI :: Ptr PixelFormat -> Ptr Palette -> IO CInt

foreign import ccall "SDL.h SDL_EnclosePoints" enclosePointsFFI :: Ptr Point -> CInt -> Ptr Rect -> Ptr Rect -> IO Bool
foreign import ccall "SDL.h SDL_HasIntersection" hasIntersectionFFI :: Ptr Rect -> Ptr Rect -> IO Bool
foreign import ccall "SDL.h SDL_IntersectRect" intersectRectFFI :: Ptr Rect -> Ptr Rect -> Ptr Rect -> IO Bool
foreign import ccall "SDL.h SDL_IntersectRectAndLine" intersectRectAndLineFFI :: Ptr Rect -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO Bool
foreign import ccall "SDL.h SDL_UnionRect" unionRectFFI :: Ptr Rect -> Ptr Rect -> Ptr Rect -> IO ()

foreign import ccall "SDL.h SDL_UpperBlitScaled" blitScaledFFI :: Ptr Surface -> Ptr Rect -> Ptr Surface -> Ptr Rect -> IO CInt
foreign import ccall "SDL.h SDL_UpperBlit" blitSurfaceFFI :: Ptr Surface -> Ptr Rect -> Ptr Surface -> Ptr Rect -> IO CInt
foreign import ccall "SDL.h SDL_ConvertPixels" convertPixelsFFI :: CInt -> CInt -> Word32 -> Ptr () -> CInt -> Word32 -> Ptr () -> CInt -> IO CInt
foreign import ccall "SDL.h SDL_ConvertSurface" convertSurfaceFFI :: Ptr Surface -> Ptr PixelFormat -> Word32 -> IO (Ptr Surface)
foreign import ccall "SDL.h SDL_ConvertSurfaceFormat" convertSurfaceFormatFFI :: Ptr Surface -> Word32 -> Word32 -> IO (Ptr Surface)
foreign import ccall "SDL.h SDL_CreateRGBSurface" createRGBSurfaceFFI :: Word32 -> CInt -> CInt -> CInt -> Word32 -> Word32 -> Word32 -> Word32 -> IO (Ptr Surface)
foreign import ccall "SDL.h SDL_CreateRGBSurfaceFrom" createRGBSurfaceFromFFI :: Ptr () -> CInt -> CInt -> CInt -> CInt -> Word32 -> Word32 -> Word32 -> Word32 -> IO (Ptr Surface)
foreign import ccall "SDL.h SDL_FillRect" fillRectFFI :: Ptr Surface -> Ptr Rect -> Word32 -> IO CInt
foreign import ccall "SDL.h SDL_FillRects" fillRectsFFI :: Ptr Surface -> Ptr Rect -> CInt -> Word32 -> IO CInt
foreign import ccall "SDL.h SDL_FreeSurface" freeSurfaceFFI :: Ptr Surface -> IO ()
foreign import ccall "SDL.h SDL_GetClipRect" getClipRectFFI :: Ptr Surface -> Ptr Rect -> IO ()
foreign import ccall "SDL.h SDL_GetColorKey" getColorKeyFFI :: Ptr Surface -> Ptr Word32 -> IO CInt
foreign import ccall "SDL.h SDL_GetSurfaceAlphaMod" getSurfaceAlphaModFFI :: Ptr Surface -> Ptr Word8 -> IO CInt
foreign import ccall "SDL.h SDL_GetSurfaceBlendMode" getSurfaceBlendModeFFI :: Ptr Surface -> Ptr BlendMode -> IO CInt
foreign import ccall "SDL.h SDL_GetSurfaceColorMod" getSurfaceColorModFFI :: Ptr Surface -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO CInt
foreign import ccall "SDL.h SDL_LoadBMP_RW" loadBMP_RWFFI :: Ptr RWops -> CInt -> IO (Ptr Surface)
foreign import ccall "SDL.h SDL_LockSurface" lockSurfaceFFI :: Ptr Surface -> IO CInt
foreign import ccall "SDL.h SDL_LowerBlit" lowerBlitFFI :: Ptr Surface -> Ptr Rect -> Ptr Surface -> Ptr Rect -> IO CInt
foreign import ccall "SDL.h SDL_LowerBlitScaled" lowerBlitScaledFFI :: Ptr Surface -> Ptr Rect -> Ptr Surface -> Ptr Rect -> IO CInt
foreign import ccall "SDL.h SDL_SaveBMP_RW" saveBMP_RWFFI :: Ptr Surface -> Ptr RWops -> CInt -> IO CInt
foreign import ccall "SDL.h SDL_SetClipRect" setClipRectFFI :: Ptr Surface -> Ptr Rect -> IO Bool
foreign import ccall "SDL.h SDL_SetColorKey" setColorKeyFFI :: Ptr Surface -> CInt -> Word32 -> IO CInt
foreign import ccall "SDL.h SDL_SetSurfaceAlphaMod" setSurfaceAlphaModFFI :: Ptr Surface -> Word8 -> IO CInt
foreign import ccall "SDL.h SDL_SetSurfaceBlendMode" setSurfaceBlendModeFFI :: Ptr Surface -> BlendMode -> IO CInt
foreign import ccall "SDL.h SDL_SetSurfaceColorMod" setSurfaceColorModFFI :: Ptr Surface -> Word8 -> Word8 -> Word8 -> IO CInt
foreign import ccall "SDL.h SDL_SetSurfacePalette" setSurfacePaletteFFI :: Ptr Surface -> Ptr Palette -> IO CInt
foreign import ccall "SDL.h SDL_SetSurfaceRLE" setSurfaceRLEFFI :: Ptr Surface -> CInt -> IO CInt
foreign import ccall "SDL.h SDL_UnlockSurface" unlockSurfaceFFI :: Ptr Surface -> IO ()

foreign import ccall "SDL.h SDL_GetWindowWMInfo" getWindowWMInfoFFI :: Window -> SysWMinfo -> IO Bool

foreign import ccall "SDL.h SDL_GetClipboardText" getClipboardTextFFI :: IO CString
foreign import ccall "SDL.h SDL_HasClipboardText" hasClipboardTextFFI :: IO Bool
foreign import ccall "SDL.h SDL_SetClipboardText" setClipboardTextFFI :: CString -> IO CInt

foreign import ccall "SDL_vulkan.h SDL_Vulkan_LoadLibrary" vkLoadLibraryFFI :: CString -> IO CInt
foreign import ccall "SDL_vulkan.h SDL_Vulkan_GetVkGetInstanceProcAddr" vkGetVkGetInstanceProcAddrFFI :: IO (FunPtr VkGetInstanceProcAddrFunc)
foreign import ccall "SDL_vulkan.h SDL_Vulkan_UnloadLibrary" vkUnloadLibraryFFI :: IO ()
foreign import ccall "SDL_vulkan.h SDL_Vulkan_GetInstanceExtensions" vkGetInstanceExtensionsFFI :: Window -> Ptr CUInt -> Ptr CString -> IO Bool
foreign import ccall "SDL_vulkan.h SDL_Vulkan_CreateSurface" vkCreateSurfaceFFI :: Window -> VkInstance -> Ptr VkSurfaceKHR -> IO Bool
foreign import ccall "SDL_vulkan.h SDL_Vulkan_GetDrawableSize" vkGetDrawableSizeFFI :: Window -> Ptr CInt -> Ptr CInt -> IO ()

createWindow :: MonadIO m => CString -> CInt -> CInt -> CInt -> CInt -> Word32 -> m Window
createWindow :: CString -> CInt -> CInt -> CInt -> CInt -> Word32 -> m Window
createWindow CString
v1 CInt
v2 CInt
v3 CInt
v4 CInt
v5 Word32
v6 = IO Window -> m Window
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ CString -> CInt -> CInt -> CInt -> CInt -> Word32 -> IO Window
createWindowFFI CString
v1 CInt
v2 CInt
v3 CInt
v4 CInt
v5 Word32
v6
{-# INLINE createWindow #-}

createWindowAndRenderer :: MonadIO m => CInt -> CInt -> Word32 -> Ptr Window -> Ptr Renderer -> m CInt
createWindowAndRenderer :: CInt -> CInt -> Word32 -> Ptr Window -> Ptr Window -> m CInt
createWindowAndRenderer CInt
v1 CInt
v2 Word32
v3 Ptr Window
v4 Ptr Window
v5 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ CInt -> CInt -> Word32 -> Ptr Window -> Ptr Window -> IO CInt
createWindowAndRendererFFI CInt
v1 CInt
v2 Word32
v3 Ptr Window
v4 Ptr Window
v5
{-# INLINE createWindowAndRenderer #-}

createWindowFrom :: MonadIO m => Ptr () -> m Window
createWindowFrom :: Window -> m Window
createWindowFrom Window
v1 = IO Window -> m Window
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ Window -> IO Window
createWindowFromFFI Window
v1
{-# INLINE createWindowFrom #-}

destroyWindow :: MonadIO m => Window -> m ()
destroyWindow :: Window -> m ()
destroyWindow Window
v1 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> IO ()
destroyWindowFFI Window
v1
{-# INLINE destroyWindow #-}

disableScreenSaver :: MonadIO m => m ()
disableScreenSaver :: m ()
disableScreenSaver = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO ()
disableScreenSaverFFI
{-# INLINE disableScreenSaver #-}

enableScreenSaver :: MonadIO m => m ()
enableScreenSaver :: m ()
enableScreenSaver = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO ()
enableScreenSaverFFI
{-# INLINE enableScreenSaver #-}

glBindTexture :: MonadIO m => Texture -> Ptr CFloat -> Ptr CFloat -> m CInt
glBindTexture :: Window -> Ptr CFloat -> Ptr CFloat -> m CInt
glBindTexture Window
v1 Ptr CFloat
v2 Ptr CFloat
v3 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr CFloat -> Ptr CFloat -> IO CInt
glBindTextureFFI Window
v1 Ptr CFloat
v2 Ptr CFloat
v3
{-# INLINE glBindTexture #-}

glCreateContext :: MonadIO m => Window -> m GLContext
glCreateContext :: Window -> m Window
glCreateContext Window
v1 = IO Window -> m Window
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ Window -> IO Window
glCreateContextFFI Window
v1
{-# INLINE glCreateContext #-}

glDeleteContext :: MonadIO m => GLContext -> m ()
glDeleteContext :: Window -> m ()
glDeleteContext Window
v1 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> IO ()
glDeleteContextFFI Window
v1
{-# INLINE glDeleteContext #-}

glExtensionSupported :: MonadIO m => CString -> m Bool
glExtensionSupported :: CString -> m Bool
glExtensionSupported CString
v1 = IO Bool -> m Bool
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ CString -> IO Bool
glExtensionSupportedFFI CString
v1
{-# INLINE glExtensionSupported #-}

glGetAttribute :: MonadIO m => GLattr -> Ptr CInt -> m CInt
glGetAttribute :: Word32 -> Ptr CInt -> m CInt
glGetAttribute Word32
v1 Ptr CInt
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Word32 -> Ptr CInt -> IO CInt
glGetAttributeFFI Word32
v1 Ptr CInt
v2
{-# INLINE glGetAttribute #-}

glGetCurrentContext :: MonadIO m => m GLContext
glGetCurrentContext :: m Window
glGetCurrentContext = IO Window -> m Window
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO Window
glGetCurrentContextFFI
{-# INLINE glGetCurrentContext #-}

glGetCurrentWindow :: MonadIO m => m Window
glGetCurrentWindow :: m Window
glGetCurrentWindow = IO Window -> m Window
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO Window
glGetCurrentWindowFFI
{-# INLINE glGetCurrentWindow #-}

glGetDrawableSize :: MonadIO m => Window -> Ptr CInt -> Ptr CInt -> m ()
glGetDrawableSize :: Window -> Ptr CInt -> Ptr CInt -> m ()
glGetDrawableSize Window
v1 Ptr CInt
v2 Ptr CInt
v3 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> Ptr CInt -> Ptr CInt -> IO ()
glGetDrawableSizeFFI Window
v1 Ptr CInt
v2 Ptr CInt
v3
{-# INLINE glGetDrawableSize #-}

glGetProcAddress :: MonadIO m => CString -> m (Ptr ())
glGetProcAddress :: CString -> m Window
glGetProcAddress CString
v1 = IO Window -> m Window
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ CString -> IO Window
glGetProcAddressFFI CString
v1
{-# INLINE glGetProcAddress #-}

glGetSwapInterval :: MonadIO m => m CInt
glGetSwapInterval :: m CInt
glGetSwapInterval = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO CInt
glGetSwapIntervalFFI
{-# INLINE glGetSwapInterval #-}

glLoadLibrary :: MonadIO m => CString -> m CInt
glLoadLibrary :: CString -> m CInt
glLoadLibrary CString
v1 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ CString -> IO CInt
glLoadLibraryFFI CString
v1
{-# INLINE glLoadLibrary #-}

glMakeCurrent :: MonadIO m => Window -> GLContext -> m CInt
glMakeCurrent :: Window -> Window -> m CInt
glMakeCurrent Window
v1 Window
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Window -> IO CInt
glMakeCurrentFFI Window
v1 Window
v2
{-# INLINE glMakeCurrent #-}

glResetAttributes :: MonadIO m => m ()
glResetAttributes :: m ()
glResetAttributes = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO ()
glResetAttributesFFI
{-# INLINE glResetAttributes #-}

glSetAttribute :: MonadIO m => GLattr -> CInt -> m CInt
glSetAttribute :: Word32 -> CInt -> m CInt
glSetAttribute Word32
v1 CInt
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Word32 -> CInt -> IO CInt
glSetAttributeFFI Word32
v1 CInt
v2
{-# INLINE glSetAttribute #-}

glSetSwapInterval :: MonadIO m => CInt -> m CInt
glSetSwapInterval :: CInt -> m CInt
glSetSwapInterval CInt
v1 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ CInt -> IO CInt
glSetSwapIntervalFFI CInt
v1
{-# INLINE glSetSwapInterval #-}

glSwapWindow :: MonadIO m => Window -> m ()
glSwapWindow :: Window -> m ()
glSwapWindow Window
v1 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> IO ()
glSwapWindowFFI Window
v1
{-# INLINE glSwapWindow #-}

glUnbindTexture :: MonadIO m => Texture -> m CInt
glUnbindTexture :: Window -> m CInt
glUnbindTexture Window
v1 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> IO CInt
glUnbindTextureFFI Window
v1
{-# INLINE glUnbindTexture #-}

glUnloadLibrary :: MonadIO m => m ()
glUnloadLibrary :: m ()
glUnloadLibrary = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO ()
glUnloadLibraryFFI
{-# INLINE glUnloadLibrary #-}

getClosestDisplayMode :: MonadIO m => CInt -> Ptr DisplayMode -> Ptr DisplayMode -> m (Ptr DisplayMode)
getClosestDisplayMode :: CInt -> Ptr DisplayMode -> Ptr DisplayMode -> m (Ptr DisplayMode)
getClosestDisplayMode CInt
v1 Ptr DisplayMode
v2 Ptr DisplayMode
v3 = IO (Ptr DisplayMode) -> m (Ptr DisplayMode)
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr DisplayMode) -> m (Ptr DisplayMode))
-> IO (Ptr DisplayMode) -> m (Ptr DisplayMode)
forall a b. (a -> b) -> a -> b
$ CInt -> Ptr DisplayMode -> Ptr DisplayMode -> IO (Ptr DisplayMode)
getClosestDisplayModeFFI CInt
v1 Ptr DisplayMode
v2 Ptr DisplayMode
v3
{-# INLINE getClosestDisplayMode #-}

getCurrentDisplayMode :: MonadIO m => CInt -> Ptr DisplayMode -> m CInt
getCurrentDisplayMode :: CInt -> Ptr DisplayMode -> m CInt
getCurrentDisplayMode CInt
v1 Ptr DisplayMode
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ CInt -> Ptr DisplayMode -> IO CInt
getCurrentDisplayModeFFI CInt
v1 Ptr DisplayMode
v2
{-# INLINE getCurrentDisplayMode #-}

getCurrentVideoDriver :: MonadIO m => m CString
getCurrentVideoDriver :: m CString
getCurrentVideoDriver = IO CString -> m CString
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO CString
getCurrentVideoDriverFFI
{-# INLINE getCurrentVideoDriver #-}

getDesktopDisplayMode :: MonadIO m => CInt -> Ptr DisplayMode -> m CInt
getDesktopDisplayMode :: CInt -> Ptr DisplayMode -> m CInt
getDesktopDisplayMode CInt
v1 Ptr DisplayMode
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ CInt -> Ptr DisplayMode -> IO CInt
getDesktopDisplayModeFFI CInt
v1 Ptr DisplayMode
v2
{-# INLINE getDesktopDisplayMode #-}

getDisplayBounds :: MonadIO m => CInt -> Ptr Rect -> m CInt
getDisplayBounds :: CInt -> Ptr Rect -> m CInt
getDisplayBounds CInt
v1 Ptr Rect
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ CInt -> Ptr Rect -> IO CInt
getDisplayBoundsFFI CInt
v1 Ptr Rect
v2
{-# INLINE getDisplayBounds #-}

getDisplayDPI :: MonadIO m => CInt -> Ptr CFloat -> Ptr CFloat -> Ptr CFloat -> m CInt
getDisplayDPI :: CInt -> Ptr CFloat -> Ptr CFloat -> Ptr CFloat -> m CInt
getDisplayDPI CInt
v1 Ptr CFloat
v2 Ptr CFloat
v3 Ptr CFloat
v4 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ CInt -> Ptr CFloat -> Ptr CFloat -> Ptr CFloat -> IO CInt
getDisplayDPIFFI CInt
v1 Ptr CFloat
v2 Ptr CFloat
v3 Ptr CFloat
v4
{-# INLINE getDisplayDPI #-}

getDisplayMode :: MonadIO m => CInt -> CInt -> Ptr DisplayMode -> m CInt
getDisplayMode :: CInt -> CInt -> Ptr DisplayMode -> m CInt
getDisplayMode CInt
v1 CInt
v2 Ptr DisplayMode
v3 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ CInt -> CInt -> Ptr DisplayMode -> IO CInt
getDisplayModeFFI CInt
v1 CInt
v2 Ptr DisplayMode
v3
{-# INLINE getDisplayMode #-}

getDisplayName :: MonadIO m => CInt -> m CString
getDisplayName :: CInt -> m CString
getDisplayName CInt
v1 = IO CString -> m CString
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CString -> m CString) -> IO CString -> m CString
forall a b. (a -> b) -> a -> b
$ CInt -> IO CString
getDisplayNameFFI CInt
v1
{-# INLINE getDisplayName #-}

getDisplayUsableBounds :: MonadIO m => CInt -> Ptr Rect -> m CInt
getDisplayUsableBounds :: CInt -> Ptr Rect -> m CInt
getDisplayUsableBounds CInt
v1 Ptr Rect
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ CInt -> Ptr Rect -> IO CInt
getDisplayUsableBoundsFFI CInt
v1 Ptr Rect
v2
{-# INLINE getDisplayUsableBounds #-}

getGrabbedWindow :: MonadIO m => m Window
getGrabbedWindow :: m Window
getGrabbedWindow = IO Window -> m Window
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO Window
getGrabbedWindowFFI
{-# INLINE getGrabbedWindow #-}

getNumDisplayModes :: MonadIO m => CInt -> m CInt
getNumDisplayModes :: CInt -> m CInt
getNumDisplayModes CInt
v1 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ CInt -> IO CInt
getNumDisplayModesFFI CInt
v1
{-# INLINE getNumDisplayModes #-}

getNumVideoDisplays :: MonadIO m => m CInt
getNumVideoDisplays :: m CInt
getNumVideoDisplays = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO CInt
getNumVideoDisplaysFFI
{-# INLINE getNumVideoDisplays #-}

getNumVideoDrivers :: MonadIO m => m CInt
getNumVideoDrivers :: m CInt
getNumVideoDrivers = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO CInt
getNumVideoDriversFFI
{-# INLINE getNumVideoDrivers #-}

getVideoDriver :: MonadIO m => CInt -> m CString
getVideoDriver :: CInt -> m CString
getVideoDriver CInt
v1 = IO CString -> m CString
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CString -> m CString) -> IO CString -> m CString
forall a b. (a -> b) -> a -> b
$ CInt -> IO CString
getVideoDriverFFI CInt
v1
{-# INLINE getVideoDriver #-}

getWindowBordersSize :: MonadIO m => Window -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> m CInt
getWindowBordersSize :: Window -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> m CInt
getWindowBordersSize Window
v1 Ptr CInt
v2 Ptr CInt
v3 Ptr CInt
v4 Ptr CInt
v5 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO CInt
getWindowBordersSizeFFI Window
v1 Ptr CInt
v2 Ptr CInt
v3 Ptr CInt
v4 Ptr CInt
v5
{-# INLINE getWindowBordersSize #-}

getWindowBrightness :: MonadIO m => Window -> m CFloat
getWindowBrightness :: Window -> m CFloat
getWindowBrightness Window
v1 = IO CFloat -> m CFloat
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CFloat -> m CFloat) -> IO CFloat -> m CFloat
forall a b. (a -> b) -> a -> b
$ Window -> IO CFloat
getWindowBrightnessFFI Window
v1
{-# INLINE getWindowBrightness #-}

getWindowData :: MonadIO m => Window -> CString -> m (Ptr ())
getWindowData :: Window -> CString -> m Window
getWindowData Window
v1 CString
v2 = IO Window -> m Window
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ Window -> CString -> IO Window
getWindowDataFFI Window
v1 CString
v2
{-# INLINE getWindowData #-}

getWindowDisplayIndex :: MonadIO m => Window -> m CInt
getWindowDisplayIndex :: Window -> m CInt
getWindowDisplayIndex Window
v1 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> IO CInt
getWindowDisplayIndexFFI Window
v1
{-# INLINE getWindowDisplayIndex #-}

getWindowDisplayMode :: MonadIO m => Window -> Ptr DisplayMode -> m CInt
getWindowDisplayMode :: Window -> Ptr DisplayMode -> m CInt
getWindowDisplayMode Window
v1 Ptr DisplayMode
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr DisplayMode -> IO CInt
getWindowDisplayModeFFI Window
v1 Ptr DisplayMode
v2
{-# INLINE getWindowDisplayMode #-}

getWindowFlags :: MonadIO m => Window -> m Word32
getWindowFlags :: Window -> m Word32
getWindowFlags Window
v1 = IO Word32 -> m Word32
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ Window -> IO Word32
getWindowFlagsFFI Window
v1
{-# INLINE getWindowFlags #-}

getWindowFromID :: MonadIO m => Word32 -> m Window
getWindowFromID :: Word32 -> m Window
getWindowFromID Word32
v1 = IO Window -> m Window
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ Word32 -> IO Window
getWindowFromIDFFI Word32
v1
{-# INLINE getWindowFromID #-}

getWindowGammaRamp :: MonadIO m => Window -> Ptr Word16 -> Ptr Word16 -> Ptr Word16 -> m CInt
getWindowGammaRamp :: Window -> Ptr Word16 -> Ptr Word16 -> Ptr Word16 -> m CInt
getWindowGammaRamp Window
v1 Ptr Word16
v2 Ptr Word16
v3 Ptr Word16
v4 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Word16 -> Ptr Word16 -> Ptr Word16 -> IO CInt
getWindowGammaRampFFI Window
v1 Ptr Word16
v2 Ptr Word16
v3 Ptr Word16
v4
{-# INLINE getWindowGammaRamp #-}

getWindowGrab :: MonadIO m => Window -> m Bool
getWindowGrab :: Window -> m Bool
getWindowGrab Window
v1 = IO Bool -> m Bool
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Window -> IO Bool
getWindowGrabFFI Window
v1
{-# INLINE getWindowGrab #-}

getWindowID :: MonadIO m => Window -> m Word32
getWindowID :: Window -> m Word32
getWindowID Window
v1 = IO Word32 -> m Word32
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ Window -> IO Word32
getWindowIDFFI Window
v1
{-# INLINE getWindowID #-}

getWindowMaximumSize :: MonadIO m => Window -> Ptr CInt -> Ptr CInt -> m ()
getWindowMaximumSize :: Window -> Ptr CInt -> Ptr CInt -> m ()
getWindowMaximumSize Window
v1 Ptr CInt
v2 Ptr CInt
v3 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> Ptr CInt -> Ptr CInt -> IO ()
getWindowMaximumSizeFFI Window
v1 Ptr CInt
v2 Ptr CInt
v3
{-# INLINE getWindowMaximumSize #-}

getWindowMinimumSize :: MonadIO m => Window -> Ptr CInt -> Ptr CInt -> m ()
getWindowMinimumSize :: Window -> Ptr CInt -> Ptr CInt -> m ()
getWindowMinimumSize Window
v1 Ptr CInt
v2 Ptr CInt
v3 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> Ptr CInt -> Ptr CInt -> IO ()
getWindowMinimumSizeFFI Window
v1 Ptr CInt
v2 Ptr CInt
v3
{-# INLINE getWindowMinimumSize #-}

getWindowPixelFormat :: MonadIO m => Window -> m Word32
getWindowPixelFormat :: Window -> m Word32
getWindowPixelFormat Window
v1 = IO Word32 -> m Word32
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ Window -> IO Word32
getWindowPixelFormatFFI Window
v1
{-# INLINE getWindowPixelFormat #-}

getWindowPosition :: MonadIO m => Window -> Ptr CInt -> Ptr CInt -> m ()
getWindowPosition :: Window -> Ptr CInt -> Ptr CInt -> m ()
getWindowPosition Window
v1 Ptr CInt
v2 Ptr CInt
v3 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> Ptr CInt -> Ptr CInt -> IO ()
getWindowPositionFFI Window
v1 Ptr CInt
v2 Ptr CInt
v3
{-# INLINE getWindowPosition #-}

getWindowSize :: MonadIO m => Window -> Ptr CInt -> Ptr CInt -> m ()
getWindowSize :: Window -> Ptr CInt -> Ptr CInt -> m ()
getWindowSize Window
v1 Ptr CInt
v2 Ptr CInt
v3 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> Ptr CInt -> Ptr CInt -> IO ()
getWindowSizeFFI Window
v1 Ptr CInt
v2 Ptr CInt
v3
{-# INLINE getWindowSize #-}

getWindowSurface :: MonadIO m => Window -> m (Ptr Surface)
getWindowSurface :: Window -> m (Ptr Surface)
getWindowSurface Window
v1 = IO (Ptr Surface) -> m (Ptr Surface)
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr Surface) -> m (Ptr Surface))
-> IO (Ptr Surface) -> m (Ptr Surface)
forall a b. (a -> b) -> a -> b
$ Window -> IO (Ptr Surface)
getWindowSurfaceFFI Window
v1
{-# INLINE getWindowSurface #-}

getWindowTitle :: MonadIO m => Window -> m CString
getWindowTitle :: Window -> m CString
getWindowTitle Window
v1 = IO CString -> m CString
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CString -> m CString) -> IO CString -> m CString
forall a b. (a -> b) -> a -> b
$ Window -> IO CString
getWindowTitleFFI Window
v1
{-# INLINE getWindowTitle #-}

hideWindow :: MonadIO m => Window -> m ()
hideWindow :: Window -> m ()
hideWindow Window
v1 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> IO ()
hideWindowFFI Window
v1
{-# INLINE hideWindow #-}

isScreenSaverEnabled :: MonadIO m => m Bool
isScreenSaverEnabled :: m Bool
isScreenSaverEnabled = IO Bool -> m Bool
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO Bool
isScreenSaverEnabledFFI
{-# INLINE isScreenSaverEnabled #-}

maximizeWindow :: MonadIO m => Window -> m ()
maximizeWindow :: Window -> m ()
maximizeWindow Window
v1 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> IO ()
maximizeWindowFFI Window
v1
{-# INLINE maximizeWindow #-}

minimizeWindow :: MonadIO m => Window -> m ()
minimizeWindow :: Window -> m ()
minimizeWindow Window
v1 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> IO ()
minimizeWindowFFI Window
v1
{-# INLINE minimizeWindow #-}

raiseWindow :: MonadIO m => Window -> m ()
raiseWindow :: Window -> m ()
raiseWindow Window
v1 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> IO ()
raiseWindowFFI Window
v1
{-# INLINE raiseWindow #-}

restoreWindow :: MonadIO m => Window -> m ()
restoreWindow :: Window -> m ()
restoreWindow Window
v1 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> IO ()
restoreWindowFFI Window
v1
{-# INLINE restoreWindow #-}

setWindowBordered :: MonadIO m => Window -> Bool -> m ()
setWindowBordered :: Window -> Bool -> m ()
setWindowBordered Window
v1 Bool
v2 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> Bool -> IO ()
setWindowBorderedFFI Window
v1 Bool
v2
{-# INLINE setWindowBordered #-}

setWindowBrightness :: MonadIO m => Window -> CFloat -> m CInt
setWindowBrightness :: Window -> CFloat -> m CInt
setWindowBrightness Window
v1 CFloat
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> CFloat -> IO CInt
setWindowBrightnessFFI Window
v1 CFloat
v2
{-# INLINE setWindowBrightness #-}

setWindowData :: MonadIO m => Window -> CString -> Ptr () -> m (Ptr ())
setWindowData :: Window -> CString -> Window -> m Window
setWindowData Window
v1 CString
v2 Window
v3 = IO Window -> m Window
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ Window -> CString -> Window -> IO Window
setWindowDataFFI Window
v1 CString
v2 Window
v3
{-# INLINE setWindowData #-}

setWindowDisplayMode :: MonadIO m => Window -> Ptr DisplayMode -> m CInt
setWindowDisplayMode :: Window -> Ptr DisplayMode -> m CInt
setWindowDisplayMode Window
v1 Ptr DisplayMode
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr DisplayMode -> IO CInt
setWindowDisplayModeFFI Window
v1 Ptr DisplayMode
v2
{-# INLINE setWindowDisplayMode #-}

setWindowFullscreen :: MonadIO m => Window -> Word32 -> m CInt
setWindowFullscreen :: Window -> Word32 -> m CInt
setWindowFullscreen Window
v1 Word32
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Word32 -> IO CInt
setWindowFullscreenFFI Window
v1 Word32
v2
{-# INLINE setWindowFullscreen #-}

setWindowGammaRamp :: MonadIO m => Window -> Ptr Word16 -> Ptr Word16 -> Ptr Word16 -> m CInt
setWindowGammaRamp :: Window -> Ptr Word16 -> Ptr Word16 -> Ptr Word16 -> m CInt
setWindowGammaRamp Window
v1 Ptr Word16
v2 Ptr Word16
v3 Ptr Word16
v4 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Word16 -> Ptr Word16 -> Ptr Word16 -> IO CInt
setWindowGammaRampFFI Window
v1 Ptr Word16
v2 Ptr Word16
v3 Ptr Word16
v4
{-# INLINE setWindowGammaRamp #-}

setWindowGrab :: MonadIO m => Window -> Bool -> m ()
setWindowGrab :: Window -> Bool -> m ()
setWindowGrab Window
v1 Bool
v2 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> Bool -> IO ()
setWindowGrabFFI Window
v1 Bool
v2
{-# INLINE setWindowGrab #-}

setWindowIcon :: MonadIO m => Window -> Ptr Surface -> m ()
setWindowIcon :: Window -> Ptr Surface -> m ()
setWindowIcon Window
v1 Ptr Surface
v2 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Surface -> IO ()
setWindowIconFFI Window
v1 Ptr Surface
v2
{-# INLINE setWindowIcon #-}

setWindowMaximumSize :: MonadIO m => Window -> CInt -> CInt -> m ()
setWindowMaximumSize :: Window -> CInt -> CInt -> m ()
setWindowMaximumSize Window
v1 CInt
v2 CInt
v3 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> CInt -> CInt -> IO ()
setWindowMaximumSizeFFI Window
v1 CInt
v2 CInt
v3
{-# INLINE setWindowMaximumSize #-}

setWindowMinimumSize :: MonadIO m => Window -> CInt -> CInt -> m ()
setWindowMinimumSize :: Window -> CInt -> CInt -> m ()
setWindowMinimumSize Window
v1 CInt
v2 CInt
v3 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> CInt -> CInt -> IO ()
setWindowMinimumSizeFFI Window
v1 CInt
v2 CInt
v3
{-# INLINE setWindowMinimumSize #-}

setWindowPosition :: MonadIO m => Window -> CInt -> CInt -> m ()
setWindowPosition :: Window -> CInt -> CInt -> m ()
setWindowPosition Window
v1 CInt
v2 CInt
v3 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> CInt -> CInt -> IO ()
setWindowPositionFFI Window
v1 CInt
v2 CInt
v3
{-# INLINE setWindowPosition #-}

setWindowSize :: MonadIO m => Window -> CInt -> CInt -> m ()
setWindowSize :: Window -> CInt -> CInt -> m ()
setWindowSize Window
v1 CInt
v2 CInt
v3 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> CInt -> CInt -> IO ()
setWindowSizeFFI Window
v1 CInt
v2 CInt
v3
{-# INLINE setWindowSize #-}

setWindowTitle :: MonadIO m => Window -> CString -> m ()
setWindowTitle :: Window -> CString -> m ()
setWindowTitle Window
v1 CString
v2 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> CString -> IO ()
setWindowTitleFFI Window
v1 CString
v2
{-# INLINE setWindowTitle #-}

showMessageBox :: MonadIO m => Ptr MessageBoxData -> Ptr CInt -> m CInt
showMessageBox :: Ptr MessageBoxData -> Ptr CInt -> m CInt
showMessageBox Ptr MessageBoxData
v1 Ptr CInt
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr MessageBoxData -> Ptr CInt -> IO CInt
showMessageBoxFFI Ptr MessageBoxData
v1 Ptr CInt
v2
{-# INLINE showMessageBox #-}

showSimpleMessageBox :: MonadIO m => Word32 -> CString -> CString -> Window -> m CInt
showSimpleMessageBox :: Word32 -> CString -> CString -> Window -> m CInt
showSimpleMessageBox Word32
v1 CString
v2 CString
v3 Window
v4 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Word32 -> CString -> CString -> Window -> IO CInt
showSimpleMessageBoxFFI Word32
v1 CString
v2 CString
v3 Window
v4
{-# INLINE showSimpleMessageBox #-}

showWindow :: MonadIO m => Window -> m ()
showWindow :: Window -> m ()
showWindow Window
v1 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> IO ()
showWindowFFI Window
v1
{-# INLINE showWindow #-}

updateWindowSurface :: MonadIO m => Window -> m CInt
updateWindowSurface :: Window -> m CInt
updateWindowSurface Window
v1 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> IO CInt
updateWindowSurfaceFFI Window
v1
{-# INLINE updateWindowSurface #-}

updateWindowSurfaceRects :: MonadIO m => Window -> Ptr Rect -> CInt -> m CInt
updateWindowSurfaceRects :: Window -> Ptr Rect -> CInt -> m CInt
updateWindowSurfaceRects Window
v1 Ptr Rect
v2 CInt
v3 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Rect -> CInt -> IO CInt
updateWindowSurfaceRectsFFI Window
v1 Ptr Rect
v2 CInt
v3
{-# INLINE updateWindowSurfaceRects #-}

videoInit :: MonadIO m => CString -> m CInt
videoInit :: CString -> m CInt
videoInit CString
v1 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ CString -> IO CInt
videoInitFFI CString
v1
{-# INLINE videoInit #-}

videoQuit :: MonadIO m => m ()
videoQuit :: m ()
videoQuit = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO ()
videoQuitFFI
{-# INLINE videoQuit #-}

composeCustomBlendMode :: MonadIO m => BlendFactor -> BlendFactor -> BlendOperation -> BlendFactor -> BlendFactor -> BlendOperation -> m BlendMode
composeCustomBlendMode :: Word32
-> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> m Word32
composeCustomBlendMode Word32
v1 Word32
v2 Word32
v3 Word32
v4 Word32
v5 Word32
v6 = IO Word32 -> m Word32
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ Word32
-> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> IO Word32
composeCustomBlendModeFFI Word32
v1 Word32
v2 Word32
v3 Word32
v4 Word32
v5 Word32
v6
{-# INLINE composeCustomBlendMode #-}

createRenderer :: MonadIO m => Window -> CInt -> Word32 -> m Renderer
createRenderer :: Window -> CInt -> Word32 -> m Window
createRenderer Window
v1 CInt
v2 Word32
v3 = IO Window -> m Window
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ Window -> CInt -> Word32 -> IO Window
createRendererFFI Window
v1 CInt
v2 Word32
v3
{-# INLINE createRenderer #-}

createSoftwareRenderer :: MonadIO m => Ptr Surface -> m Renderer
createSoftwareRenderer :: Ptr Surface -> m Window
createSoftwareRenderer Ptr Surface
v1 = IO Window -> m Window
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> IO Window
createSoftwareRendererFFI Ptr Surface
v1
{-# INLINE createSoftwareRenderer #-}

createTexture :: MonadIO m => Renderer -> Word32 -> CInt -> CInt -> CInt -> m Texture
createTexture :: Window -> Word32 -> CInt -> CInt -> CInt -> m Window
createTexture Window
v1 Word32
v2 CInt
v3 CInt
v4 CInt
v5 = IO Window -> m Window
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ Window -> Word32 -> CInt -> CInt -> CInt -> IO Window
createTextureFFI Window
v1 Word32
v2 CInt
v3 CInt
v4 CInt
v5
{-# INLINE createTexture #-}

createTextureFromSurface :: MonadIO m => Renderer -> Ptr Surface -> m Texture
createTextureFromSurface :: Window -> Ptr Surface -> m Window
createTextureFromSurface Window
v1 Ptr Surface
v2 = IO Window -> m Window
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Surface -> IO Window
createTextureFromSurfaceFFI Window
v1 Ptr Surface
v2
{-# INLINE createTextureFromSurface #-}

destroyRenderer :: MonadIO m => Renderer -> m ()
destroyRenderer :: Window -> m ()
destroyRenderer Window
v1 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> IO ()
destroyRendererFFI Window
v1
{-# INLINE destroyRenderer #-}

destroyTexture :: MonadIO m => Texture -> m ()
destroyTexture :: Window -> m ()
destroyTexture Window
v1 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> IO ()
destroyTextureFFI Window
v1
{-# INLINE destroyTexture #-}

getNumRenderDrivers :: MonadIO m => m CInt
getNumRenderDrivers :: m CInt
getNumRenderDrivers = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO CInt
getNumRenderDriversFFI
{-# INLINE getNumRenderDrivers #-}

getRenderDrawBlendMode :: MonadIO m => Renderer -> Ptr BlendMode -> m Int
getRenderDrawBlendMode :: Window -> Ptr Word32 -> m Int
getRenderDrawBlendMode Window
v1 Ptr Word32
v2 = IO Int -> m Int
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Int -> m Int) -> IO Int -> m Int
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Word32 -> IO Int
getRenderDrawBlendModeFFI Window
v1 Ptr Word32
v2
{-# INLINE getRenderDrawBlendMode #-}

getRenderDrawColor :: MonadIO m => Renderer -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> m CInt
getRenderDrawColor :: Window
-> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> m CInt
getRenderDrawColor Window
v1 Ptr Word8
v2 Ptr Word8
v3 Ptr Word8
v4 Ptr Word8
v5 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window
-> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO CInt
getRenderDrawColorFFI Window
v1 Ptr Word8
v2 Ptr Word8
v3 Ptr Word8
v4 Ptr Word8
v5
{-# INLINE getRenderDrawColor #-}

getRenderDriverInfo :: MonadIO m => CInt -> Ptr RendererInfo -> m CInt
getRenderDriverInfo :: CInt -> Ptr RendererInfo -> m CInt
getRenderDriverInfo CInt
v1 Ptr RendererInfo
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ CInt -> Ptr RendererInfo -> IO CInt
getRenderDriverInfoFFI CInt
v1 Ptr RendererInfo
v2
{-# INLINE getRenderDriverInfo #-}

getRenderTarget :: MonadIO m => Renderer -> m Texture
getRenderTarget :: Window -> m Window
getRenderTarget Window
v1 = IO Window -> m Window
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ Window -> IO Window
getRenderTargetFFI Window
v1
{-# INLINE getRenderTarget #-}

getRenderer :: MonadIO m => Window -> m Renderer
getRenderer :: Window -> m Window
getRenderer Window
v1 = IO Window -> m Window
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ Window -> IO Window
getRendererFFI Window
v1
{-# INLINE getRenderer #-}

getRendererInfo :: MonadIO m => Renderer -> Ptr RendererInfo -> m CInt
getRendererInfo :: Window -> Ptr RendererInfo -> m CInt
getRendererInfo Window
v1 Ptr RendererInfo
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr RendererInfo -> IO CInt
getRendererInfoFFI Window
v1 Ptr RendererInfo
v2
{-# INLINE getRendererInfo #-}

getRendererOutputSize :: MonadIO m => Renderer -> Ptr CInt -> Ptr CInt -> m CInt
getRendererOutputSize :: Window -> Ptr CInt -> Ptr CInt -> m CInt
getRendererOutputSize Window
v1 Ptr CInt
v2 Ptr CInt
v3 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr CInt -> Ptr CInt -> IO CInt
getRendererOutputSizeFFI Window
v1 Ptr CInt
v2 Ptr CInt
v3
{-# INLINE getRendererOutputSize #-}

getTextureAlphaMod :: MonadIO m => Texture -> Ptr Word8 -> m CInt
getTextureAlphaMod :: Window -> Ptr Word8 -> m CInt
getTextureAlphaMod Window
v1 Ptr Word8
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Word8 -> IO CInt
getTextureAlphaModFFI Window
v1 Ptr Word8
v2
{-# INLINE getTextureAlphaMod #-}

getTextureBlendMode :: MonadIO m => Texture -> Ptr BlendMode -> m CInt
getTextureBlendMode :: Window -> Ptr Word32 -> m CInt
getTextureBlendMode Window
v1 Ptr Word32
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Word32 -> IO CInt
getTextureBlendModeFFI Window
v1 Ptr Word32
v2
{-# INLINE getTextureBlendMode #-}

getTextureColorMod :: MonadIO m => Texture -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> m CInt
getTextureColorMod :: Window -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> m CInt
getTextureColorMod Window
v1 Ptr Word8
v2 Ptr Word8
v3 Ptr Word8
v4 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO CInt
getTextureColorModFFI Window
v1 Ptr Word8
v2 Ptr Word8
v3 Ptr Word8
v4
{-# INLINE getTextureColorMod #-}

lockTexture :: MonadIO m => Texture -> Ptr Rect -> Ptr (Ptr ()) -> Ptr CInt -> m CInt
lockTexture :: Window -> Ptr Rect -> Ptr Window -> Ptr CInt -> m CInt
lockTexture Window
v1 Ptr Rect
v2 Ptr Window
v3 Ptr CInt
v4 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Rect -> Ptr Window -> Ptr CInt -> IO CInt
lockTextureFFI Window
v1 Ptr Rect
v2 Ptr Window
v3 Ptr CInt
v4
{-# INLINE lockTexture #-}

queryTexture :: MonadIO m => Texture -> Ptr Word32 -> Ptr CInt -> Ptr CInt -> Ptr CInt -> m CInt
queryTexture :: Window -> Ptr Word32 -> Ptr CInt -> Ptr CInt -> Ptr CInt -> m CInt
queryTexture Window
v1 Ptr Word32
v2 Ptr CInt
v3 Ptr CInt
v4 Ptr CInt
v5 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Word32 -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO CInt
queryTextureFFI Window
v1 Ptr Word32
v2 Ptr CInt
v3 Ptr CInt
v4 Ptr CInt
v5
{-# INLINE queryTexture #-}

renderClear :: MonadIO m => Renderer -> m CInt
renderClear :: Window -> m CInt
renderClear Window
v1 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> IO CInt
renderClearFFI Window
v1
{-# INLINE renderClear #-}

renderCopy :: MonadIO m => Renderer -> Texture -> Ptr Rect -> Ptr Rect -> m CInt
renderCopy :: Window -> Window -> Ptr Rect -> Ptr Rect -> m CInt
renderCopy Window
v1 Window
v2 Ptr Rect
v3 Ptr Rect
v4 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Window -> Ptr Rect -> Ptr Rect -> IO CInt
renderCopyFFI Window
v1 Window
v2 Ptr Rect
v3 Ptr Rect
v4
{-# INLINE renderCopy #-}

renderCopyEx :: MonadIO m => Renderer -> Texture -> Ptr Rect -> Ptr Rect -> CDouble -> Ptr Point -> RendererFlip -> m CInt
renderCopyEx :: Window
-> Window
-> Ptr Rect
-> Ptr Rect
-> CDouble
-> Ptr Point
-> Word32
-> m CInt
renderCopyEx Window
v1 Window
v2 Ptr Rect
v3 Ptr Rect
v4 CDouble
v5 Ptr Point
v6 Word32
v7 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window
-> Window
-> Ptr Rect
-> Ptr Rect
-> CDouble
-> Ptr Point
-> Word32
-> IO CInt
renderCopyExFFI Window
v1 Window
v2 Ptr Rect
v3 Ptr Rect
v4 CDouble
v5 Ptr Point
v6 Word32
v7
{-# INLINE renderCopyEx #-}

#ifdef RECENT_ISH
renderCopyExF :: MonadIO m => Renderer -> Texture -> Ptr Rect -> Ptr FRect -> CDouble -> Ptr FPoint -> RendererFlip -> m CInt
renderCopyExF v1 v2 v3 v4 v5 v6 v7 = liftIO $ renderCopyExFFFI v1 v2 v3 v4 v5 v6 v7
{-# INLINE renderCopyExF #-}
#endif

renderDrawLine :: MonadIO m => Renderer -> CInt -> CInt -> CInt -> CInt -> m CInt
renderDrawLine :: Window -> CInt -> CInt -> CInt -> CInt -> m CInt
renderDrawLine Window
v1 CInt
v2 CInt
v3 CInt
v4 CInt
v5 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> CInt -> CInt -> CInt -> CInt -> IO CInt
renderDrawLineFFI Window
v1 CInt
v2 CInt
v3 CInt
v4 CInt
v5
{-# INLINE renderDrawLine #-}

renderDrawLines :: MonadIO m => Renderer -> Ptr Point -> CInt -> m CInt
renderDrawLines :: Window -> Ptr Point -> CInt -> m CInt
renderDrawLines Window
v1 Ptr Point
v2 CInt
v3 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Point -> CInt -> IO CInt
renderDrawLinesFFI Window
v1 Ptr Point
v2 CInt
v3
{-# INLINE renderDrawLines #-}

renderDrawPoint :: MonadIO m => Renderer -> CInt -> CInt -> m CInt
renderDrawPoint :: Window -> CInt -> CInt -> m CInt
renderDrawPoint Window
v1 CInt
v2 CInt
v3 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> CInt -> CInt -> IO CInt
renderDrawPointFFI Window
v1 CInt
v2 CInt
v3
{-# INLINE renderDrawPoint #-}

renderDrawPoints :: MonadIO m => Renderer -> Ptr Point -> CInt -> m CInt
renderDrawPoints :: Window -> Ptr Point -> CInt -> m CInt
renderDrawPoints Window
v1 Ptr Point
v2 CInt
v3 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Point -> CInt -> IO CInt
renderDrawPointsFFI Window
v1 Ptr Point
v2 CInt
v3
{-# INLINE renderDrawPoints #-}

renderDrawRect :: MonadIO m => Renderer -> Ptr Rect -> m CInt
renderDrawRect :: Window -> Ptr Rect -> m CInt
renderDrawRect Window
v1 Ptr Rect
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Rect -> IO CInt
renderDrawRectFFI Window
v1 Ptr Rect
v2
{-# INLINE renderDrawRect #-}

renderDrawRects :: MonadIO m => Renderer -> Ptr Rect -> CInt -> m CInt
renderDrawRects :: Window -> Ptr Rect -> CInt -> m CInt
renderDrawRects Window
v1 Ptr Rect
v2 CInt
v3 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Rect -> CInt -> IO CInt
renderDrawRectsFFI Window
v1 Ptr Rect
v2 CInt
v3
{-# INLINE renderDrawRects #-}

renderFillRectEx :: MonadIO m => Renderer -> CInt -> CInt -> CInt -> CInt -> m CInt
renderFillRectEx :: Window -> CInt -> CInt -> CInt -> CInt -> m CInt
renderFillRectEx Window
v1 CInt
x CInt
y CInt
w CInt
h = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> CInt -> CInt -> CInt -> CInt -> IO CInt
renderFillRectExFFI Window
v1 CInt
x CInt
y CInt
w CInt
h
{-# INLINE renderFillRectEx #-}

renderFillRect :: MonadIO m => Renderer -> Ptr Rect -> m CInt
renderFillRect :: Window -> Ptr Rect -> m CInt
renderFillRect Window
v1 Ptr Rect
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Rect -> IO CInt
renderFillRectFFI Window
v1 Ptr Rect
v2
{-# INLINE renderFillRect #-}

renderFillRects :: MonadIO m => Renderer -> Ptr Rect -> CInt -> m CInt
renderFillRects :: Window -> Ptr Rect -> CInt -> m CInt
renderFillRects Window
v1 Ptr Rect
v2 CInt
v3 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Rect -> CInt -> IO CInt
renderFillRectsFFI Window
v1 Ptr Rect
v2 CInt
v3
{-# INLINE renderFillRects #-}

renderGetClipRect :: MonadIO m => Renderer -> Ptr Rect -> m ()
renderGetClipRect :: Window -> Ptr Rect -> m ()
renderGetClipRect Window
v1 Ptr Rect
v2 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Rect -> IO ()
renderGetClipRectFFI Window
v1 Ptr Rect
v2
{-# INLINE renderGetClipRect #-}

renderGetLogicalSize :: MonadIO m => Renderer -> Ptr CInt -> Ptr CInt -> m ()
renderGetLogicalSize :: Window -> Ptr CInt -> Ptr CInt -> m ()
renderGetLogicalSize Window
v1 Ptr CInt
v2 Ptr CInt
v3 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> Ptr CInt -> Ptr CInt -> IO ()
renderGetLogicalSizeFFI Window
v1 Ptr CInt
v2 Ptr CInt
v3
{-# INLINE renderGetLogicalSize #-}

renderGetScale :: MonadIO m => Renderer -> Ptr CFloat -> Ptr CFloat -> m ()
renderGetScale :: Window -> Ptr CFloat -> Ptr CFloat -> m ()
renderGetScale Window
v1 Ptr CFloat
v2 Ptr CFloat
v3 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> Ptr CFloat -> Ptr CFloat -> IO ()
renderGetScaleFFI Window
v1 Ptr CFloat
v2 Ptr CFloat
v3
{-# INLINE renderGetScale #-}

renderGetViewport :: MonadIO m => Renderer -> Ptr Rect -> m ()
renderGetViewport :: Window -> Ptr Rect -> m ()
renderGetViewport Window
v1 Ptr Rect
v2 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Rect -> IO ()
renderGetViewportFFI Window
v1 Ptr Rect
v2
{-# INLINE renderGetViewport #-}

renderIsClipEnabled :: MonadIO m => Renderer -> m Bool
renderIsClipEnabled :: Window -> m Bool
renderIsClipEnabled Window
v1 = IO Bool -> m Bool
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Window -> IO Bool
renderIsClipEnabledFFI Window
v1
{-# INLINE renderIsClipEnabled #-}

renderPresent :: MonadIO m => Renderer -> m ()
renderPresent :: Window -> m ()
renderPresent Window
v1 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> IO ()
renderPresentFFI Window
v1
{-# INLINE renderPresent #-}

renderReadPixels :: MonadIO m => Renderer -> Ptr Rect -> Word32 -> Ptr () -> CInt -> m CInt
renderReadPixels :: Window -> Ptr Rect -> Word32 -> Window -> CInt -> m CInt
renderReadPixels Window
v1 Ptr Rect
v2 Word32
v3 Window
v4 CInt
v5 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Rect -> Word32 -> Window -> CInt -> IO CInt
renderReadPixelsFFI Window
v1 Ptr Rect
v2 Word32
v3 Window
v4 CInt
v5
{-# INLINE renderReadPixels #-}

renderSetClipRect :: MonadIO m => Renderer -> Ptr Rect -> m CInt
renderSetClipRect :: Window -> Ptr Rect -> m CInt
renderSetClipRect Window
v1 Ptr Rect
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Rect -> IO CInt
renderSetClipRectFFI Window
v1 Ptr Rect
v2
{-# INLINE renderSetClipRect #-}

renderSetLogicalSize :: MonadIO m => Renderer -> CInt -> CInt -> m CInt
renderSetLogicalSize :: Window -> CInt -> CInt -> m CInt
renderSetLogicalSize Window
v1 CInt
v2 CInt
v3 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> CInt -> CInt -> IO CInt
renderSetLogicalSizeFFI Window
v1 CInt
v2 CInt
v3
{-# INLINE renderSetLogicalSize #-}

renderSetScale :: MonadIO m => Renderer -> CFloat -> CFloat -> m CInt
renderSetScale :: Window -> CFloat -> CFloat -> m CInt
renderSetScale Window
v1 CFloat
v2 CFloat
v3 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> CFloat -> CFloat -> IO CInt
renderSetScaleFFI Window
v1 CFloat
v2 CFloat
v3
{-# INLINE renderSetScale #-}

renderSetViewport :: MonadIO m => Renderer -> Ptr Rect -> m CInt
renderSetViewport :: Window -> Ptr Rect -> m CInt
renderSetViewport Window
v1 Ptr Rect
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Rect -> IO CInt
renderSetViewportFFI Window
v1 Ptr Rect
v2
{-# INLINE renderSetViewport #-}

renderTargetSupported :: MonadIO m => Renderer -> m Bool
renderTargetSupported :: Window -> m Bool
renderTargetSupported Window
v1 = IO Bool -> m Bool
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Window -> IO Bool
renderTargetSupportedFFI Window
v1
{-# INLINE renderTargetSupported #-}

setRenderDrawBlendMode :: MonadIO m => Renderer -> BlendMode -> m CInt
setRenderDrawBlendMode :: Window -> Word32 -> m CInt
setRenderDrawBlendMode Window
v1 Word32
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Word32 -> IO CInt
setRenderDrawBlendModeFFI Window
v1 Word32
v2
{-# INLINE setRenderDrawBlendMode #-}

setRenderDrawColor :: MonadIO m => Renderer -> Word8 -> Word8 -> Word8 -> Word8 -> m CInt
setRenderDrawColor :: Window -> Word8 -> Word8 -> Word8 -> Word8 -> m CInt
setRenderDrawColor Window
v1 Word8
v2 Word8
v3 Word8
v4 Word8
v5 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Word8 -> Word8 -> Word8 -> Word8 -> IO CInt
setRenderDrawColorFFI Window
v1 Word8
v2 Word8
v3 Word8
v4 Word8
v5
{-# INLINE setRenderDrawColor #-}

setRenderTarget :: MonadIO m => Renderer -> Texture -> m CInt
setRenderTarget :: Window -> Window -> m CInt
setRenderTarget Window
v1 Window
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Window -> IO CInt
setRenderTargetFFI Window
v1 Window
v2
{-# INLINE setRenderTarget #-}

setTextureAlphaMod :: MonadIO m => Texture -> Word8 -> m CInt
setTextureAlphaMod :: Window -> Word8 -> m CInt
setTextureAlphaMod Window
v1 Word8
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Word8 -> IO CInt
setTextureAlphaModFFI Window
v1 Word8
v2
{-# INLINE setTextureAlphaMod #-}

setTextureBlendMode :: MonadIO m => Texture -> BlendMode -> m CInt
setTextureBlendMode :: Window -> Word32 -> m CInt
setTextureBlendMode Window
v1 Word32
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Word32 -> IO CInt
setTextureBlendModeFFI Window
v1 Word32
v2
{-# INLINE setTextureBlendMode #-}

setTextureColorMod :: MonadIO m => Texture -> Word8 -> Word8 -> Word8 -> m CInt
setTextureColorMod :: Window -> Word8 -> Word8 -> Word8 -> m CInt
setTextureColorMod Window
v1 Word8
v2 Word8
v3 Word8
v4 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Word8 -> Word8 -> Word8 -> IO CInt
setTextureColorModFFI Window
v1 Word8
v2 Word8
v3 Word8
v4
{-# INLINE setTextureColorMod #-}

unlockTexture :: MonadIO m => Texture -> m ()
unlockTexture :: Window -> m ()
unlockTexture Window
v1 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> IO ()
unlockTextureFFI Window
v1
{-# INLINE unlockTexture #-}

updateTexture :: MonadIO m => Texture -> Ptr Rect -> Ptr () -> CInt -> m CInt
updateTexture :: Window -> Ptr Rect -> Window -> CInt -> m CInt
updateTexture Window
v1 Ptr Rect
v2 Window
v3 CInt
v4 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window -> Ptr Rect -> Window -> CInt -> IO CInt
updateTextureFFI Window
v1 Ptr Rect
v2 Window
v3 CInt
v4
{-# INLINE updateTexture #-}

updateYUVTexture :: MonadIO m => Texture -> Ptr Rect -> Ptr Word8 -> CInt -> Ptr Word8 -> CInt -> Ptr Word8 -> CInt -> m CInt
updateYUVTexture :: Window
-> Ptr Rect
-> Ptr Word8
-> CInt
-> Ptr Word8
-> CInt
-> Ptr Word8
-> CInt
-> m CInt
updateYUVTexture Window
v1 Ptr Rect
v2 Ptr Word8
v3 CInt
v4 Ptr Word8
v5 CInt
v6 Ptr Word8
v7 CInt
v8 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Window
-> Ptr Rect
-> Ptr Word8
-> CInt
-> Ptr Word8
-> CInt
-> Ptr Word8
-> CInt
-> IO CInt
updateYUVTextureFFI Window
v1 Ptr Rect
v2 Ptr Word8
v3 CInt
v4 Ptr Word8
v5 CInt
v6 Ptr Word8
v7 CInt
v8
{-# INLINE updateYUVTexture #-}

allocFormat :: MonadIO m => Word32 -> m (Ptr PixelFormat)
allocFormat :: Word32 -> m (Ptr PixelFormat)
allocFormat Word32
v1 = IO (Ptr PixelFormat) -> m (Ptr PixelFormat)
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr PixelFormat) -> m (Ptr PixelFormat))
-> IO (Ptr PixelFormat) -> m (Ptr PixelFormat)
forall a b. (a -> b) -> a -> b
$ Word32 -> IO (Ptr PixelFormat)
allocFormatFFI Word32
v1
{-# INLINE allocFormat #-}

allocPalette :: MonadIO m => CInt -> m (Ptr Palette)
allocPalette :: CInt -> m (Ptr Palette)
allocPalette CInt
v1 = IO (Ptr Palette) -> m (Ptr Palette)
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr Palette) -> m (Ptr Palette))
-> IO (Ptr Palette) -> m (Ptr Palette)
forall a b. (a -> b) -> a -> b
$ CInt -> IO (Ptr Palette)
allocPaletteFFI CInt
v1
{-# INLINE allocPalette #-}

calculateGammaRamp :: MonadIO m => CFloat -> Ptr Word16 -> m ()
calculateGammaRamp :: CFloat -> Ptr Word16 -> m ()
calculateGammaRamp CFloat
v1 Ptr Word16
v2 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ CFloat -> Ptr Word16 -> IO ()
calculateGammaRampFFI CFloat
v1 Ptr Word16
v2
{-# INLINE calculateGammaRamp #-}

freeFormat :: MonadIO m => Ptr PixelFormat -> m ()
freeFormat :: Ptr PixelFormat -> m ()
freeFormat Ptr PixelFormat
v1 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Ptr PixelFormat -> IO ()
freeFormatFFI Ptr PixelFormat
v1
{-# INLINE freeFormat #-}

freePalette :: MonadIO m => Ptr Palette -> m ()
freePalette :: Ptr Palette -> m ()
freePalette Ptr Palette
v1 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Ptr Palette -> IO ()
freePaletteFFI Ptr Palette
v1
{-# INLINE freePalette #-}

getPixelFormatName :: MonadIO m => Word32 -> m CString
getPixelFormatName :: Word32 -> m CString
getPixelFormatName Word32
v1 = IO CString -> m CString
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CString -> m CString) -> IO CString -> m CString
forall a b. (a -> b) -> a -> b
$ Word32 -> IO CString
getPixelFormatNameFFI Word32
v1
{-# INLINE getPixelFormatName #-}

getRGB :: MonadIO m => Word32 -> Ptr PixelFormat -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> m ()
getRGB :: Word32
-> Ptr PixelFormat -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> m ()
getRGB Word32
v1 Ptr PixelFormat
v2 Ptr Word8
v3 Ptr Word8
v4 Ptr Word8
v5 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Word32
-> Ptr PixelFormat -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO ()
getRGBFFI Word32
v1 Ptr PixelFormat
v2 Ptr Word8
v3 Ptr Word8
v4 Ptr Word8
v5
{-# INLINE getRGB #-}

getRGBA :: MonadIO m => Word32 -> Ptr PixelFormat -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> m ()
getRGBA :: Word32
-> Ptr PixelFormat
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> m ()
getRGBA Word32
v1 Ptr PixelFormat
v2 Ptr Word8
v3 Ptr Word8
v4 Ptr Word8
v5 Ptr Word8
v6 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Word32
-> Ptr PixelFormat
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> Ptr Word8
-> IO ()
getRGBAFFI Word32
v1 Ptr PixelFormat
v2 Ptr Word8
v3 Ptr Word8
v4 Ptr Word8
v5 Ptr Word8
v6
{-# INLINE getRGBA #-}

mapRGB :: MonadIO m => Ptr PixelFormat -> Word8 -> Word8 -> Word8 -> m Word32
mapRGB :: Ptr PixelFormat -> Word8 -> Word8 -> Word8 -> m Word32
mapRGB Ptr PixelFormat
v1 Word8
v2 Word8
v3 Word8
v4 = IO Word32 -> m Word32
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ Ptr PixelFormat -> Word8 -> Word8 -> Word8 -> IO Word32
mapRGBFFI Ptr PixelFormat
v1 Word8
v2 Word8
v3 Word8
v4
{-# INLINE mapRGB #-}

mapRGBA :: MonadIO m => Ptr PixelFormat -> Word8 -> Word8 -> Word8 -> Word8 -> m Word32
mapRGBA :: Ptr PixelFormat -> Word8 -> Word8 -> Word8 -> Word8 -> m Word32
mapRGBA Ptr PixelFormat
v1 Word8
v2 Word8
v3 Word8
v4 Word8
v5 = IO Word32 -> m Word32
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ Ptr PixelFormat -> Word8 -> Word8 -> Word8 -> Word8 -> IO Word32
mapRGBAFFI Ptr PixelFormat
v1 Word8
v2 Word8
v3 Word8
v4 Word8
v5
{-# INLINE mapRGBA #-}

masksToPixelFormatEnum :: MonadIO m => CInt -> Word32 -> Word32 -> Word32 -> Word32 -> m Word32
masksToPixelFormatEnum :: CInt -> Word32 -> Word32 -> Word32 -> Word32 -> m Word32
masksToPixelFormatEnum CInt
v1 Word32
v2 Word32
v3 Word32
v4 Word32
v5 = IO Word32 -> m Word32
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ CInt -> Word32 -> Word32 -> Word32 -> Word32 -> IO Word32
masksToPixelFormatEnumFFI CInt
v1 Word32
v2 Word32
v3 Word32
v4 Word32
v5
{-# INLINE masksToPixelFormatEnum #-}

pixelFormatEnumToMasks :: MonadIO m => Word32 -> Ptr CInt -> Ptr Word32 -> Ptr Word32 -> Ptr Word32 -> Ptr Word32 -> m Bool
pixelFormatEnumToMasks :: Word32
-> Ptr CInt
-> Ptr Word32
-> Ptr Word32
-> Ptr Word32
-> Ptr Word32
-> m Bool
pixelFormatEnumToMasks Word32
v1 Ptr CInt
v2 Ptr Word32
v3 Ptr Word32
v4 Ptr Word32
v5 Ptr Word32
v6 = IO Bool -> m Bool
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Word32
-> Ptr CInt
-> Ptr Word32
-> Ptr Word32
-> Ptr Word32
-> Ptr Word32
-> IO Bool
pixelFormatEnumToMasksFFI Word32
v1 Ptr CInt
v2 Ptr Word32
v3 Ptr Word32
v4 Ptr Word32
v5 Ptr Word32
v6
{-# INLINE pixelFormatEnumToMasks #-}

setPaletteColors :: MonadIO m => Ptr Palette -> Ptr Color -> CInt -> CInt -> m CInt
setPaletteColors :: Ptr Palette -> Ptr Color -> CInt -> CInt -> m CInt
setPaletteColors Ptr Palette
v1 Ptr Color
v2 CInt
v3 CInt
v4 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Palette -> Ptr Color -> CInt -> CInt -> IO CInt
setPaletteColorsFFI Ptr Palette
v1 Ptr Color
v2 CInt
v3 CInt
v4
{-# INLINE setPaletteColors #-}

setPixelFormatPalette :: MonadIO m => Ptr PixelFormat -> Ptr Palette -> m CInt
setPixelFormatPalette :: Ptr PixelFormat -> Ptr Palette -> m CInt
setPixelFormatPalette Ptr PixelFormat
v1 Ptr Palette
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr PixelFormat -> Ptr Palette -> IO CInt
setPixelFormatPaletteFFI Ptr PixelFormat
v1 Ptr Palette
v2
{-# INLINE setPixelFormatPalette #-}

enclosePoints :: MonadIO m => Ptr Point -> CInt -> Ptr Rect -> Ptr Rect -> m Bool
enclosePoints :: Ptr Point -> CInt -> Ptr Rect -> Ptr Rect -> m Bool
enclosePoints Ptr Point
v1 CInt
v2 Ptr Rect
v3 Ptr Rect
v4 = IO Bool -> m Bool
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Ptr Point -> CInt -> Ptr Rect -> Ptr Rect -> IO Bool
enclosePointsFFI Ptr Point
v1 CInt
v2 Ptr Rect
v3 Ptr Rect
v4
{-# INLINE enclosePoints #-}

hasIntersection :: MonadIO m => Ptr Rect -> Ptr Rect -> m Bool
hasIntersection :: Ptr Rect -> Ptr Rect -> m Bool
hasIntersection Ptr Rect
v1 Ptr Rect
v2 = IO Bool -> m Bool
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Ptr Rect -> Ptr Rect -> IO Bool
hasIntersectionFFI Ptr Rect
v1 Ptr Rect
v2
{-# INLINE hasIntersection #-}

intersectRect :: MonadIO m => Ptr Rect -> Ptr Rect -> Ptr Rect -> m Bool
intersectRect :: Ptr Rect -> Ptr Rect -> Ptr Rect -> m Bool
intersectRect Ptr Rect
v1 Ptr Rect
v2 Ptr Rect
v3 = IO Bool -> m Bool
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Ptr Rect -> Ptr Rect -> Ptr Rect -> IO Bool
intersectRectFFI Ptr Rect
v1 Ptr Rect
v2 Ptr Rect
v3
{-# INLINE intersectRect #-}

intersectRectAndLine :: MonadIO m => Ptr Rect -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> m Bool
intersectRectAndLine :: Ptr Rect -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> m Bool
intersectRectAndLine Ptr Rect
v1 Ptr CInt
v2 Ptr CInt
v3 Ptr CInt
v4 Ptr CInt
v5 = IO Bool -> m Bool
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Ptr Rect -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO Bool
intersectRectAndLineFFI Ptr Rect
v1 Ptr CInt
v2 Ptr CInt
v3 Ptr CInt
v4 Ptr CInt
v5
{-# INLINE intersectRectAndLine #-}

unionRect :: MonadIO m => Ptr Rect -> Ptr Rect -> Ptr Rect -> m ()
unionRect :: Ptr Rect -> Ptr Rect -> Ptr Rect -> m ()
unionRect Ptr Rect
v1 Ptr Rect
v2 Ptr Rect
v3 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Ptr Rect -> Ptr Rect -> Ptr Rect -> IO ()
unionRectFFI Ptr Rect
v1 Ptr Rect
v2 Ptr Rect
v3
{-# INLINE unionRect #-}

blitScaled :: MonadIO m => Ptr Surface -> Ptr Rect -> Ptr Surface -> Ptr Rect -> m CInt
blitScaled :: Ptr Surface -> Ptr Rect -> Ptr Surface -> Ptr Rect -> m CInt
blitScaled Ptr Surface
v1 Ptr Rect
v2 Ptr Surface
v3 Ptr Rect
v4 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Ptr Rect -> Ptr Surface -> Ptr Rect -> IO CInt
blitScaledFFI Ptr Surface
v1 Ptr Rect
v2 Ptr Surface
v3 Ptr Rect
v4
{-# INLINE blitScaled #-}

blitSurface :: MonadIO m => Ptr Surface -> Ptr Rect -> Ptr Surface -> Ptr Rect -> m CInt
blitSurface :: Ptr Surface -> Ptr Rect -> Ptr Surface -> Ptr Rect -> m CInt
blitSurface Ptr Surface
v1 Ptr Rect
v2 Ptr Surface
v3 Ptr Rect
v4 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Ptr Rect -> Ptr Surface -> Ptr Rect -> IO CInt
blitSurfaceFFI Ptr Surface
v1 Ptr Rect
v2 Ptr Surface
v3 Ptr Rect
v4
{-# INLINE blitSurface #-}

convertPixels :: MonadIO m => CInt -> CInt -> Word32 -> Ptr () -> CInt -> Word32 -> Ptr () -> CInt -> m CInt
convertPixels :: CInt
-> CInt
-> Word32
-> Window
-> CInt
-> Word32
-> Window
-> CInt
-> m CInt
convertPixels CInt
v1 CInt
v2 Word32
v3 Window
v4 CInt
v5 Word32
v6 Window
v7 CInt
v8 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ CInt
-> CInt
-> Word32
-> Window
-> CInt
-> Word32
-> Window
-> CInt
-> IO CInt
convertPixelsFFI CInt
v1 CInt
v2 Word32
v3 Window
v4 CInt
v5 Word32
v6 Window
v7 CInt
v8
{-# INLINE convertPixels #-}

convertSurface :: MonadIO m => Ptr Surface -> Ptr PixelFormat -> Word32 -> m (Ptr Surface)
convertSurface :: Ptr Surface -> Ptr PixelFormat -> Word32 -> m (Ptr Surface)
convertSurface Ptr Surface
v1 Ptr PixelFormat
v2 Word32
v3 = IO (Ptr Surface) -> m (Ptr Surface)
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr Surface) -> m (Ptr Surface))
-> IO (Ptr Surface) -> m (Ptr Surface)
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Ptr PixelFormat -> Word32 -> IO (Ptr Surface)
convertSurfaceFFI Ptr Surface
v1 Ptr PixelFormat
v2 Word32
v3
{-# INLINE convertSurface #-}

convertSurfaceFormat :: MonadIO m => Ptr Surface -> Word32 -> Word32 -> m (Ptr Surface)
convertSurfaceFormat :: Ptr Surface -> Word32 -> Word32 -> m (Ptr Surface)
convertSurfaceFormat Ptr Surface
v1 Word32
v2 Word32
v3 = IO (Ptr Surface) -> m (Ptr Surface)
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr Surface) -> m (Ptr Surface))
-> IO (Ptr Surface) -> m (Ptr Surface)
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Word32 -> Word32 -> IO (Ptr Surface)
convertSurfaceFormatFFI Ptr Surface
v1 Word32
v2 Word32
v3
{-# INLINE convertSurfaceFormat #-}

createRGBSurface :: MonadIO m => Word32 -> CInt -> CInt -> CInt -> Word32 -> Word32 -> Word32 -> Word32 -> m (Ptr Surface)
createRGBSurface :: Word32
-> CInt
-> CInt
-> CInt
-> Word32
-> Word32
-> Word32
-> Word32
-> m (Ptr Surface)
createRGBSurface Word32
v1 CInt
v2 CInt
v3 CInt
v4 Word32
v5 Word32
v6 Word32
v7 Word32
v8 = IO (Ptr Surface) -> m (Ptr Surface)
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr Surface) -> m (Ptr Surface))
-> IO (Ptr Surface) -> m (Ptr Surface)
forall a b. (a -> b) -> a -> b
$ Word32
-> CInt
-> CInt
-> CInt
-> Word32
-> Word32
-> Word32
-> Word32
-> IO (Ptr Surface)
createRGBSurfaceFFI Word32
v1 CInt
v2 CInt
v3 CInt
v4 Word32
v5 Word32
v6 Word32
v7 Word32
v8
{-# INLINE createRGBSurface #-}

createRGBSurfaceFrom :: MonadIO m => Ptr () -> CInt -> CInt -> CInt -> CInt -> Word32 -> Word32 -> Word32 -> Word32 -> m (Ptr Surface)
createRGBSurfaceFrom :: Window
-> CInt
-> CInt
-> CInt
-> CInt
-> Word32
-> Word32
-> Word32
-> Word32
-> m (Ptr Surface)
createRGBSurfaceFrom Window
v1 CInt
v2 CInt
v3 CInt
v4 CInt
v5 Word32
v6 Word32
v7 Word32
v8 Word32
v9 = IO (Ptr Surface) -> m (Ptr Surface)
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr Surface) -> m (Ptr Surface))
-> IO (Ptr Surface) -> m (Ptr Surface)
forall a b. (a -> b) -> a -> b
$ Window
-> CInt
-> CInt
-> CInt
-> CInt
-> Word32
-> Word32
-> Word32
-> Word32
-> IO (Ptr Surface)
createRGBSurfaceFromFFI Window
v1 CInt
v2 CInt
v3 CInt
v4 CInt
v5 Word32
v6 Word32
v7 Word32
v8 Word32
v9
{-# INLINE createRGBSurfaceFrom #-}

fillRect :: MonadIO m => Ptr Surface -> Ptr Rect -> Word32 -> m CInt
fillRect :: Ptr Surface -> Ptr Rect -> Word32 -> m CInt
fillRect Ptr Surface
v1 Ptr Rect
v2 Word32
v3 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Ptr Rect -> Word32 -> IO CInt
fillRectFFI Ptr Surface
v1 Ptr Rect
v2 Word32
v3
{-# INLINE fillRect #-}

fillRects :: MonadIO m => Ptr Surface -> Ptr Rect -> CInt -> Word32 -> m CInt
fillRects :: Ptr Surface -> Ptr Rect -> CInt -> Word32 -> m CInt
fillRects Ptr Surface
v1 Ptr Rect
v2 CInt
v3 Word32
v4 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Ptr Rect -> CInt -> Word32 -> IO CInt
fillRectsFFI Ptr Surface
v1 Ptr Rect
v2 CInt
v3 Word32
v4
{-# INLINE fillRects #-}

freeSurface :: MonadIO m => Ptr Surface -> m ()
freeSurface :: Ptr Surface -> m ()
freeSurface Ptr Surface
v1 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> IO ()
freeSurfaceFFI Ptr Surface
v1
{-# INLINE freeSurface #-}

getClipRect :: MonadIO m => Ptr Surface -> Ptr Rect -> m ()
getClipRect :: Ptr Surface -> Ptr Rect -> m ()
getClipRect Ptr Surface
v1 Ptr Rect
v2 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Ptr Rect -> IO ()
getClipRectFFI Ptr Surface
v1 Ptr Rect
v2
{-# INLINE getClipRect #-}

getColorKey :: MonadIO m => Ptr Surface -> Ptr Word32 -> m CInt
getColorKey :: Ptr Surface -> Ptr Word32 -> m CInt
getColorKey Ptr Surface
v1 Ptr Word32
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Ptr Word32 -> IO CInt
getColorKeyFFI Ptr Surface
v1 Ptr Word32
v2
{-# INLINE getColorKey #-}

getSurfaceAlphaMod :: MonadIO m => Ptr Surface -> Ptr Word8 -> m CInt
getSurfaceAlphaMod :: Ptr Surface -> Ptr Word8 -> m CInt
getSurfaceAlphaMod Ptr Surface
v1 Ptr Word8
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Ptr Word8 -> IO CInt
getSurfaceAlphaModFFI Ptr Surface
v1 Ptr Word8
v2
{-# INLINE getSurfaceAlphaMod #-}

getSurfaceBlendMode :: MonadIO m => Ptr Surface -> Ptr BlendMode -> m CInt
getSurfaceBlendMode :: Ptr Surface -> Ptr Word32 -> m CInt
getSurfaceBlendMode Ptr Surface
v1 Ptr Word32
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Ptr Word32 -> IO CInt
getSurfaceBlendModeFFI Ptr Surface
v1 Ptr Word32
v2
{-# INLINE getSurfaceBlendMode #-}

getSurfaceColorMod :: MonadIO m => Ptr Surface -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> m CInt
getSurfaceColorMod :: Ptr Surface -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> m CInt
getSurfaceColorMod Ptr Surface
v1 Ptr Word8
v2 Ptr Word8
v3 Ptr Word8
v4 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO CInt
getSurfaceColorModFFI Ptr Surface
v1 Ptr Word8
v2 Ptr Word8
v3 Ptr Word8
v4
{-# INLINE getSurfaceColorMod #-}

loadBMP :: MonadIO m => CString -> m (Ptr Surface)
loadBMP :: CString -> m (Ptr Surface)
loadBMP CString
file = IO (Ptr Surface) -> m (Ptr Surface)
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr Surface) -> m (Ptr Surface))
-> IO (Ptr Surface) -> m (Ptr Surface)
forall a b. (a -> b) -> a -> b
$ do
  Ptr RWops
rw <- String -> (CString -> IO (Ptr RWops)) -> IO (Ptr RWops)
forall a. String -> (CString -> IO a) -> IO a
withCString String
"rb" ((CString -> IO (Ptr RWops)) -> IO (Ptr RWops))
-> (CString -> IO (Ptr RWops)) -> IO (Ptr RWops)
forall a b. (a -> b) -> a -> b
$ CString -> CString -> IO (Ptr RWops)
forall (m :: Type -> Type).
MonadIO m =>
CString -> CString -> m (Ptr RWops)
rwFromFile CString
file
  Ptr RWops -> CInt -> IO (Ptr Surface)
forall (m :: Type -> Type).
MonadIO m =>
Ptr RWops -> CInt -> m (Ptr Surface)
loadBMP_RW Ptr RWops
rw CInt
1
{-# INLINE loadBMP #-}

loadBMP_RW :: MonadIO m => Ptr RWops -> CInt -> m (Ptr Surface)
loadBMP_RW :: Ptr RWops -> CInt -> m (Ptr Surface)
loadBMP_RW Ptr RWops
v1 CInt
v2 = IO (Ptr Surface) -> m (Ptr Surface)
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr Surface) -> m (Ptr Surface))
-> IO (Ptr Surface) -> m (Ptr Surface)
forall a b. (a -> b) -> a -> b
$ Ptr RWops -> CInt -> IO (Ptr Surface)
loadBMP_RWFFI Ptr RWops
v1 CInt
v2
{-# INLINE loadBMP_RW #-}

lockSurface :: MonadIO m => Ptr Surface -> m CInt
lockSurface :: Ptr Surface -> m CInt
lockSurface Ptr Surface
v1 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> IO CInt
lockSurfaceFFI Ptr Surface
v1
{-# INLINE lockSurface #-}

lowerBlit :: MonadIO m => Ptr Surface -> Ptr Rect -> Ptr Surface -> Ptr Rect -> m CInt
lowerBlit :: Ptr Surface -> Ptr Rect -> Ptr Surface -> Ptr Rect -> m CInt
lowerBlit Ptr Surface
v1 Ptr Rect
v2 Ptr Surface
v3 Ptr Rect
v4 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Ptr Rect -> Ptr Surface -> Ptr Rect -> IO CInt
lowerBlitFFI Ptr Surface
v1 Ptr Rect
v2 Ptr Surface
v3 Ptr Rect
v4
{-# INLINE lowerBlit #-}

lowerBlitScaled :: MonadIO m => Ptr Surface -> Ptr Rect -> Ptr Surface -> Ptr Rect -> m CInt
lowerBlitScaled :: Ptr Surface -> Ptr Rect -> Ptr Surface -> Ptr Rect -> m CInt
lowerBlitScaled Ptr Surface
v1 Ptr Rect
v2 Ptr Surface
v3 Ptr Rect
v4 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Ptr Rect -> Ptr Surface -> Ptr Rect -> IO CInt
lowerBlitScaledFFI Ptr Surface
v1 Ptr Rect
v2 Ptr Surface
v3 Ptr Rect
v4
{-# INLINE lowerBlitScaled #-}

saveBMP :: MonadIO m => Ptr Surface -> CString -> m CInt
saveBMP :: Ptr Surface -> CString -> m CInt
saveBMP Ptr Surface
surface CString
file = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ do
  Ptr RWops
rw <- String -> (CString -> IO (Ptr RWops)) -> IO (Ptr RWops)
forall a. String -> (CString -> IO a) -> IO a
withCString String
"wb" ((CString -> IO (Ptr RWops)) -> IO (Ptr RWops))
-> (CString -> IO (Ptr RWops)) -> IO (Ptr RWops)
forall a b. (a -> b) -> a -> b
$ CString -> CString -> IO (Ptr RWops)
forall (m :: Type -> Type).
MonadIO m =>
CString -> CString -> m (Ptr RWops)
rwFromFile CString
file
  Ptr Surface -> Ptr RWops -> CInt -> IO CInt
forall (m :: Type -> Type).
MonadIO m =>
Ptr Surface -> Ptr RWops -> CInt -> m CInt
saveBMP_RW Ptr Surface
surface Ptr RWops
rw CInt
1
{-# INLINE saveBMP #-}

saveBMP_RW :: MonadIO m => Ptr Surface -> Ptr RWops -> CInt -> m CInt
saveBMP_RW :: Ptr Surface -> Ptr RWops -> CInt -> m CInt
saveBMP_RW Ptr Surface
v1 Ptr RWops
v2 CInt
v3 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Ptr RWops -> CInt -> IO CInt
saveBMP_RWFFI Ptr Surface
v1 Ptr RWops
v2 CInt
v3
{-# INLINE saveBMP_RW #-}

setClipRect :: MonadIO m => Ptr Surface -> Ptr Rect -> m Bool
setClipRect :: Ptr Surface -> Ptr Rect -> m Bool
setClipRect Ptr Surface
v1 Ptr Rect
v2 = IO Bool -> m Bool
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Ptr Rect -> IO Bool
setClipRectFFI Ptr Surface
v1 Ptr Rect
v2
{-# INLINE setClipRect #-}

setColorKey :: MonadIO m => Ptr Surface -> CInt -> Word32 -> m CInt
setColorKey :: Ptr Surface -> CInt -> Word32 -> m CInt
setColorKey Ptr Surface
v1 CInt
v2 Word32
v3 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> CInt -> Word32 -> IO CInt
setColorKeyFFI Ptr Surface
v1 CInt
v2 Word32
v3
{-# INLINE setColorKey #-}

setSurfaceAlphaMod :: MonadIO m => Ptr Surface -> Word8 -> m CInt
setSurfaceAlphaMod :: Ptr Surface -> Word8 -> m CInt
setSurfaceAlphaMod Ptr Surface
v1 Word8
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Word8 -> IO CInt
setSurfaceAlphaModFFI Ptr Surface
v1 Word8
v2
{-# INLINE setSurfaceAlphaMod #-}

setSurfaceBlendMode :: MonadIO m => Ptr Surface -> BlendMode -> m CInt
setSurfaceBlendMode :: Ptr Surface -> Word32 -> m CInt
setSurfaceBlendMode Ptr Surface
v1 Word32
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Word32 -> IO CInt
setSurfaceBlendModeFFI Ptr Surface
v1 Word32
v2
{-# INLINE setSurfaceBlendMode #-}

setSurfaceColorMod :: MonadIO m => Ptr Surface -> Word8 -> Word8 -> Word8 -> m CInt
setSurfaceColorMod :: Ptr Surface -> Word8 -> Word8 -> Word8 -> m CInt
setSurfaceColorMod Ptr Surface
v1 Word8
v2 Word8
v3 Word8
v4 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Word8 -> Word8 -> Word8 -> IO CInt
setSurfaceColorModFFI Ptr Surface
v1 Word8
v2 Word8
v3 Word8
v4
{-# INLINE setSurfaceColorMod #-}

setSurfacePalette :: MonadIO m => Ptr Surface -> Ptr Palette -> m CInt
setSurfacePalette :: Ptr Surface -> Ptr Palette -> m CInt
setSurfacePalette Ptr Surface
v1 Ptr Palette
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Ptr Palette -> IO CInt
setSurfacePaletteFFI Ptr Surface
v1 Ptr Palette
v2
{-# INLINE setSurfacePalette #-}

setSurfaceRLE :: MonadIO m => Ptr Surface -> CInt -> m CInt
setSurfaceRLE :: Ptr Surface -> CInt -> m CInt
setSurfaceRLE Ptr Surface
v1 CInt
v2 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> CInt -> IO CInt
setSurfaceRLEFFI Ptr Surface
v1 CInt
v2
{-# INLINE setSurfaceRLE #-}

unlockSurface :: MonadIO m => Ptr Surface -> m ()
unlockSurface :: Ptr Surface -> m ()
unlockSurface Ptr Surface
v1 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> IO ()
unlockSurfaceFFI Ptr Surface
v1
{-# INLINE unlockSurface #-}

getWindowWMInfo :: MonadIO m => Window -> SysWMinfo -> m Bool
getWindowWMInfo :: Window -> Window -> m Bool
getWindowWMInfo Window
v1 Window
v2 = IO Bool -> m Bool
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Window -> Window -> IO Bool
getWindowWMInfoFFI Window
v1 Window
v2
{-# INLINE getWindowWMInfo #-}

getClipboardText :: MonadIO m => m CString
getClipboardText :: m CString
getClipboardText = IO CString -> m CString
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO CString
getClipboardTextFFI
{-# INLINE getClipboardText #-}

hasClipboardText :: MonadIO m => m Bool
hasClipboardText :: m Bool
hasClipboardText = IO Bool -> m Bool
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO Bool
hasClipboardTextFFI
{-# INLINE hasClipboardText #-}

setClipboardText :: MonadIO m => CString -> m CInt
setClipboardText :: CString -> m CInt
setClipboardText CString
v1 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ CString -> IO CInt
setClipboardTextFFI CString
v1
{-# INLINE setClipboardText #-}

vkLoadLibrary :: MonadIO m => CString -> m CInt
vkLoadLibrary :: CString -> m CInt
vkLoadLibrary CString
v1 = IO CInt -> m CInt
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO CInt -> m CInt) -> IO CInt -> m CInt
forall a b. (a -> b) -> a -> b
$ CString -> IO CInt
vkLoadLibraryFFI CString
v1
{-# INLINE vkLoadLibrary #-}

vkGetVkGetInstanceProcAddr :: MonadIO m => m (FunPtr VkGetInstanceProcAddrFunc)
vkGetVkGetInstanceProcAddr :: m (FunPtr VkGetInstanceProcAddrFunc)
vkGetVkGetInstanceProcAddr = IO (FunPtr VkGetInstanceProcAddrFunc)
-> m (FunPtr VkGetInstanceProcAddrFunc)
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO (FunPtr VkGetInstanceProcAddrFunc)
vkGetVkGetInstanceProcAddrFFI
{-# INLINE vkGetVkGetInstanceProcAddr #-}

vkUnloadLibrary :: MonadIO m => m ()
vkUnloadLibrary :: m ()
vkUnloadLibrary = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO IO ()
vkUnloadLibraryFFI
{-# INLINE vkUnloadLibrary #-}

vkGetInstanceExtensions :: MonadIO m => Window -> Ptr CUInt -> Ptr CString -> m Bool
vkGetInstanceExtensions :: Window -> Ptr CUInt -> Ptr CString -> m Bool
vkGetInstanceExtensions Window
v1 Ptr CUInt
v2 Ptr CString
v3 = IO Bool -> m Bool
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Window -> Ptr CUInt -> Ptr CString -> IO Bool
vkGetInstanceExtensionsFFI Window
v1 Ptr CUInt
v2 Ptr CString
v3
{-# INLINE vkGetInstanceExtensions #-}

vkCreateSurface :: MonadIO m => Window -> VkInstance -> Ptr VkSurfaceKHR -> m Bool
vkCreateSurface :: Window -> Window -> Ptr VkSurfaceKHR -> m Bool
vkCreateSurface Window
v1 Window
v2 Ptr VkSurfaceKHR
v3 = IO Bool -> m Bool
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Window -> Window -> Ptr VkSurfaceKHR -> IO Bool
vkCreateSurfaceFFI Window
v1 Window
v2 Ptr VkSurfaceKHR
v3
{-# INLINE vkCreateSurface #-}

vkGetDrawableSize :: MonadIO m => Window -> Ptr CInt -> Ptr CInt -> m ()
vkGetDrawableSize :: Window -> Ptr CInt -> Ptr CInt -> m ()
vkGetDrawableSize Window
v1 Ptr CInt
v2 Ptr CInt
v3 = IO () -> m ()
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Window -> Ptr CInt -> Ptr CInt -> IO ()
vkGetDrawableSizeFFI Window
v1 Ptr CInt
v2 Ptr CInt
v3
{-# INLINE vkGetDrawableSize #-}