module Graphics.GLUtil.VertexArrayObjects 
  (makeVAO, withVAO, deleteVAO, deleteVAOs, VAO) where
import Graphics.Rendering.OpenGL
import Graphics.Rendering.OpenGL.Raw.Core31 (glDeleteVertexArrays)
import Foreign.Marshal.Array (withArrayLen)
import Foreign.Marshal.Utils (with)
import Unsafe.Coerce (unsafeCoerce)
type VAO = VertexArrayObject
makeVAO :: IO () -> IO VertexArrayObject
makeVAO setup = do [vao] <- genObjectNames 1
                   bindVertexArrayObject $= Just vao
                   setup
                   bindVertexArrayObject $= Nothing
                   return vao
withVAO :: VertexArrayObject -> IO r -> IO r
withVAO vao useIt = do bindVertexArrayObject $= Just vao
                       r <- useIt
                       bindVertexArrayObject $= Nothing
                       return r
deleteVAO :: VertexArrayObject -> IO ()
deleteVAO vao = with (vaoID vao) $ glDeleteVertexArrays 1
  where vaoID = unsafeCoerce :: VertexArrayObject -> GLuint
deleteVAOs :: [VertexArrayObject] -> IO ()
deleteVAOs vaos = withArrayLen (map vaoID vaos) $ 
                    glDeleteVertexArrays . fromIntegral
  where vaoID = unsafeCoerce :: VertexArrayObject -> GLuint