-- This file was automatically generated.
{-# LANGUAGE ScopedTypeVariables, PatternSynonyms #-}
module Graphics.GL.Raw.Extension.OES.PointSizeArray (
  -- * Extension Support
    gl_OES_point_size_array

  -- * GL_OES_point_size_array
  , glPointSizePointerOES
  , pattern GL_POINT_SIZE_ARRAY_BUFFER_BINDING_OES
  , pattern GL_POINT_SIZE_ARRAY_OES
  , pattern GL_POINT_SIZE_ARRAY_POINTER_OES
  , pattern GL_POINT_SIZE_ARRAY_STRIDE_OES
  , pattern GL_POINT_SIZE_ARRAY_TYPE_OES
) where

import Control.Monad.IO.Class
import Data.Set
import Foreign.Ptr
import Graphics.GL.Raw.Internal.FFI
import Graphics.GL.Raw.Internal.Proc
import Graphics.GL.Raw.Types
import System.IO.Unsafe

-- | Checks that the GL_OES_point_size_array extension is available.

gl_OES_point_size_array :: Bool
gl_OES_point_size_array = member "GL_OES_point_size_array" extensions
{-# NOINLINE gl_OES_point_size_array #-}

-- | Usage: @'glPointSizePointerOES' type stride pointer@
--
-- The length of @pointer@ should be @COMPSIZE(type,stride)@.


glPointSizePointerOES :: MonadIO m => GLenum -> GLsizei -> Ptr () -> m ()
glPointSizePointerOES = ffienumsizeiPtrVIOV glPointSizePointerOESFunPtr

glPointSizePointerOESFunPtr :: FunPtr (GLenum -> GLsizei -> Ptr () -> IO ())
glPointSizePointerOESFunPtr = unsafePerformIO (getProcAddress "glPointSizePointerOES")

{-# NOINLINE glPointSizePointerOESFunPtr #-}

pattern GL_POINT_SIZE_ARRAY_BUFFER_BINDING_OES = 0x8B9F

pattern GL_POINT_SIZE_ARRAY_OES = 0x8B9C

pattern GL_POINT_SIZE_ARRAY_POINTER_OES = 0x898C

pattern GL_POINT_SIZE_ARRAY_STRIDE_OES = 0x898B

pattern GL_POINT_SIZE_ARRAY_TYPE_OES = 0x898A