Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Raylib.Core.Models
Contents
Description
Bindings to rmodels
Synopsis
- drawLine3D :: Vector3 -> Vector3 -> Color -> IO ()
- drawPoint3D :: Vector3 -> Color -> IO ()
- drawCircle3D :: Vector3 -> Float -> Vector3 -> Float -> Color -> IO ()
- drawTriangle3D :: Vector3 -> Vector3 -> Vector3 -> Color -> IO ()
- drawTriangleStrip3D :: [Vector3] -> Int -> Color -> IO ()
- drawCube :: Vector3 -> Float -> Float -> Float -> Color -> IO ()
- drawCubeV :: Vector3 -> Vector3 -> Color -> IO ()
- drawCubeWires :: Vector3 -> Float -> Float -> Float -> Color -> IO ()
- drawCubeWiresV :: Vector3 -> Vector3 -> Color -> IO ()
- drawSphere :: Vector3 -> Float -> Color -> IO ()
- drawSphereEx :: Vector3 -> Float -> Int -> Int -> Color -> IO ()
- drawSphereWires :: Vector3 -> Float -> Int -> Int -> Color -> IO ()
- drawCylinder :: Vector3 -> Float -> Float -> Float -> Int -> Color -> IO ()
- drawCylinderEx :: Vector3 -> Vector3 -> Float -> Float -> Int -> Color -> IO ()
- drawCylinderWires :: Vector3 -> Float -> Float -> Float -> Int -> Color -> IO ()
- drawCylinderWiresEx :: Vector3 -> Vector3 -> Float -> Float -> Int -> Color -> IO ()
- drawCapsule :: Vector3 -> Vector3 -> Float -> Int -> Int -> Color -> IO ()
- drawCapsuleWires :: Vector3 -> Vector3 -> Float -> Int -> Int -> Color -> IO ()
- drawPlane :: Vector3 -> Vector2 -> Color -> IO ()
- drawRay :: Ray -> Color -> IO ()
- drawGrid :: Int -> Float -> IO ()
- loadModel :: String -> IO Model
- loadModelFromMesh :: Mesh -> IO Model
- loadModelFromMeshManaged :: Mesh -> WindowResources -> IO Model
- unloadModel :: Model -> WindowResources -> IO ()
- isModelValid :: Model -> IO Bool
- getModelBoundingBox :: Model -> IO BoundingBox
- drawModel :: Model -> Vector3 -> Float -> Color -> IO ()
- drawModelEx :: Model -> Vector3 -> Vector3 -> Float -> Vector3 -> Color -> IO ()
- drawModelWires :: Model -> Vector3 -> Float -> Color -> IO ()
- drawModelWiresEx :: Model -> Vector3 -> Vector3 -> Float -> Vector3 -> Color -> IO ()
- drawModelPoints :: Model -> Vector3 -> Float -> Color -> IO ()
- drawModelPointsEx :: Model -> Vector3 -> Vector3 -> Float -> Vector3 -> Color -> IO ()
- drawBoundingBox :: BoundingBox -> Color -> IO ()
- drawBillboard :: Camera3D -> Texture -> Vector3 -> Float -> Color -> IO ()
- drawBillboardRec :: Camera3D -> Texture -> Rectangle -> Vector3 -> Vector2 -> Color -> IO ()
- drawBillboardPro :: Camera3D -> Texture -> Rectangle -> Vector3 -> Vector3 -> Vector2 -> Vector2 -> Float -> Color -> IO ()
- uploadMesh :: Mesh -> Bool -> IO Mesh
- updateMeshBuffer :: Mesh -> Int -> Ptr () -> Int -> Int -> IO ()
- unloadMesh :: Mesh -> WindowResources -> IO ()
- drawMesh :: Mesh -> Material -> Matrix -> IO ()
- drawMeshInstanced :: Mesh -> Material -> [Matrix] -> IO ()
- exportMesh :: Mesh -> String -> IO Bool
- exportMeshAsCode :: Mesh -> String -> IO Bool
- getMeshBoundingBox :: Mesh -> IO BoundingBox
- genMeshTangents :: Mesh -> IO Mesh
- genMeshPoly :: Int -> Float -> IO Mesh
- genMeshPlane :: Float -> Float -> Int -> Int -> IO Mesh
- genMeshCube :: Float -> Float -> Float -> IO Mesh
- genMeshSphere :: Float -> Int -> Int -> IO Mesh
- genMeshHemiSphere :: Float -> Int -> Int -> IO Mesh
- genMeshCylinder :: Float -> Float -> Int -> IO Mesh
- genMeshCone :: Float -> Float -> Int -> IO Mesh
- genMeshTorus :: Float -> Float -> Int -> Int -> IO Mesh
- genMeshKnot :: Float -> Float -> Int -> Int -> IO Mesh
- genMeshHeightmap :: Image -> Vector3 -> IO Mesh
- genMeshCubicmap :: Image -> Vector3 -> IO Mesh
- loadMaterials :: String -> IO [Material]
- unloadMaterial :: Material -> WindowResources -> IO ()
- loadMaterialDefault :: IO Material
- isMaterialValid :: Material -> IO Bool
- setMaterialTexture :: Material -> MaterialMapIndex -> Texture -> IO Material
- setModelMeshMaterial :: Model -> Int -> Int -> IO Model
- loadModelAnimations :: String -> IO [ModelAnimation]
- updateModelAnimation :: Model -> ModelAnimation -> Int -> IO ()
- isModelAnimationValid :: Model -> ModelAnimation -> IO Bool
- updateModelAnimationBoneMatrices :: Model -> ModelAnimation -> Int -> IO ()
- checkCollisionSpheres :: Vector3 -> Float -> Vector3 -> Float -> Bool
- checkCollisionBoxes :: BoundingBox -> BoundingBox -> Bool
- checkCollisionBoxSphere :: BoundingBox -> Vector3 -> Float -> Bool
- getRayCollisionSphere :: Ray -> Vector3 -> Float -> RayCollision
- getRayCollisionBox :: Ray -> BoundingBox -> RayCollision
- getRayCollisionMesh :: Ray -> Mesh -> Matrix -> RayCollision
- getRayCollisionTriangle :: Ray -> Vector3 -> Vector3 -> Vector3 -> RayCollision
- getRayCollisionQuad :: Ray -> Vector3 -> Vector3 -> Vector3 -> Vector3 -> RayCollision
- c'drawLine3D :: Ptr Vector3 -> Ptr Vector3 -> Ptr Color -> IO ()
- c'drawPoint3D :: Ptr Vector3 -> Ptr Color -> IO ()
- c'drawCircle3D :: Ptr Vector3 -> CFloat -> Ptr Vector3 -> CFloat -> Ptr Color -> IO ()
- c'drawTriangle3D :: Ptr Vector3 -> Ptr Vector3 -> Ptr Vector3 -> Ptr Color -> IO ()
- c'drawTriangleStrip3D :: Ptr Vector3 -> CInt -> Ptr Color -> IO ()
- c'drawCube :: Ptr Vector3 -> CFloat -> CFloat -> CFloat -> Ptr Color -> IO ()
- c'drawCubeV :: Ptr Vector3 -> Ptr Vector3 -> Ptr Color -> IO ()
- c'drawCubeWires :: Ptr Vector3 -> CFloat -> CFloat -> CFloat -> Ptr Color -> IO ()
- c'drawCubeWiresV :: Ptr Vector3 -> Ptr Vector3 -> Ptr Color -> IO ()
- c'drawSphere :: Ptr Vector3 -> CFloat -> Ptr Color -> IO ()
- c'drawSphereEx :: Ptr Vector3 -> CFloat -> CInt -> CInt -> Ptr Color -> IO ()
- c'drawSphereWires :: Ptr Vector3 -> CFloat -> CInt -> CInt -> Ptr Color -> IO ()
- c'drawCylinder :: Ptr Vector3 -> CFloat -> CFloat -> CFloat -> CInt -> Ptr Color -> IO ()
- c'drawCylinderEx :: Ptr Vector3 -> Ptr Vector3 -> CFloat -> CFloat -> CInt -> Ptr Color -> IO ()
- c'drawCylinderWires :: Ptr Vector3 -> CFloat -> CFloat -> CFloat -> CInt -> Ptr Color -> IO ()
- c'drawCylinderWiresEx :: Ptr Vector3 -> Ptr Vector3 -> CFloat -> CFloat -> CInt -> Ptr Color -> IO ()
- c'drawCapsule :: Ptr Vector3 -> Ptr Vector3 -> CFloat -> CInt -> CInt -> Ptr Color -> IO ()
- c'drawCapsuleWires :: Ptr Vector3 -> Ptr Vector3 -> CFloat -> CInt -> CInt -> Ptr Color -> IO ()
- c'drawPlane :: Ptr Vector3 -> Ptr Vector2 -> Ptr Color -> IO ()
- c'drawRay :: Ptr Ray -> Ptr Color -> IO ()
- c'drawGrid :: CInt -> CFloat -> IO ()
- c'loadModel :: CString -> IO (Ptr Model)
- c'loadModelFromMesh :: Ptr Mesh -> IO (Ptr Model)
- c'isModelValid :: Ptr Model -> IO CBool
- c'unloadModel :: Ptr Model -> IO ()
- c'getModelBoundingBox :: Ptr Model -> IO (Ptr BoundingBox)
- c'drawModel :: Ptr Model -> Ptr Vector3 -> CFloat -> Ptr Color -> IO ()
- c'drawModelEx :: Ptr Model -> Ptr Vector3 -> Ptr Vector3 -> CFloat -> Ptr Vector3 -> Ptr Color -> IO ()
- c'drawModelWires :: Ptr Model -> Ptr Vector3 -> CFloat -> Ptr Color -> IO ()
- c'drawModelWiresEx :: Ptr Model -> Ptr Vector3 -> Ptr Vector3 -> CFloat -> Ptr Vector3 -> Ptr Color -> IO ()
- c'drawModelPoints :: Ptr Model -> Ptr Vector3 -> CFloat -> Ptr Color -> IO ()
- c'drawModelPointsEx :: Ptr Model -> Ptr Vector3 -> Ptr Vector3 -> CFloat -> Ptr Vector3 -> Ptr Color -> IO ()
- c'drawBoundingBox :: Ptr BoundingBox -> Ptr Color -> IO ()
- c'drawBillboard :: Ptr Camera3D -> Ptr Texture -> Ptr Vector3 -> CFloat -> Ptr Color -> IO ()
- c'drawBillboardRec :: Ptr Camera3D -> Ptr Texture -> Ptr Rectangle -> Ptr Vector3 -> Ptr Vector2 -> Ptr Color -> IO ()
- c'drawBillboardPro :: Ptr Camera3D -> Ptr Texture -> Ptr Rectangle -> Ptr Vector3 -> Ptr Vector3 -> Ptr Vector2 -> Ptr Vector2 -> CFloat -> Ptr Color -> IO ()
- c'uploadMesh :: Ptr Mesh -> CInt -> IO ()
- c'updateMeshBuffer :: Ptr Mesh -> CInt -> Ptr () -> CInt -> CInt -> IO ()
- c'unloadMesh :: Ptr Mesh -> IO ()
- c'drawMesh :: Ptr Mesh -> Ptr Material -> Ptr Matrix -> IO ()
- c'drawMeshInstanced :: Ptr Mesh -> Ptr Material -> Ptr Matrix -> CInt -> IO ()
- c'exportMesh :: Ptr Mesh -> CString -> IO CBool
- c'exportMeshAsCode :: Ptr Mesh -> CString -> IO CBool
- c'getMeshBoundingBox :: Ptr Mesh -> IO (Ptr BoundingBox)
- c'genMeshTangents :: Ptr Mesh -> IO ()
- c'genMeshPoly :: CInt -> CFloat -> IO (Ptr Mesh)
- c'genMeshPlane :: CFloat -> CFloat -> CInt -> CInt -> IO (Ptr Mesh)
- c'genMeshCube :: CFloat -> CFloat -> CFloat -> IO (Ptr Mesh)
- c'genMeshSphere :: CFloat -> CInt -> CInt -> IO (Ptr Mesh)
- c'genMeshHemiSphere :: CFloat -> CInt -> CInt -> IO (Ptr Mesh)
- c'genMeshCylinder :: CFloat -> CFloat -> CInt -> IO (Ptr Mesh)
- c'genMeshCone :: CFloat -> CFloat -> CInt -> IO (Ptr Mesh)
- c'genMeshTorus :: CFloat -> CFloat -> CInt -> CInt -> IO (Ptr Mesh)
- c'genMeshKnot :: CFloat -> CFloat -> CInt -> CInt -> IO (Ptr Mesh)
- c'genMeshHeightmap :: Ptr Image -> Ptr Vector3 -> IO (Ptr Mesh)
- c'genMeshCubicmap :: Ptr Image -> Ptr Vector3 -> IO (Ptr Mesh)
- c'loadMaterials :: CString -> Ptr CInt -> IO (Ptr Material)
- c'loadMaterialDefault :: IO (Ptr Material)
- c'isMaterialValid :: Ptr Material -> IO CBool
- c'unloadMaterial :: Ptr Material -> IO ()
- c'setMaterialTexture :: Ptr Material -> CInt -> Ptr Texture -> IO ()
- c'setModelMeshMaterial :: Ptr Model -> CInt -> CInt -> IO ()
- c'loadModelAnimations :: CString -> Ptr CInt -> IO (Ptr ModelAnimation)
- c'updateModelAnimation :: Ptr Model -> Ptr ModelAnimation -> CInt -> IO ()
- c'unloadModelAnimation :: Ptr ModelAnimation -> IO ()
- c'unloadModelAnimations :: Ptr ModelAnimation -> CInt -> IO ()
- c'isModelAnimationValid :: Ptr Model -> Ptr ModelAnimation -> IO CBool
- c'updateModelAnimationBoneMatrices :: Ptr Model -> Ptr ModelAnimation -> CInt -> IO ()
- c'checkCollisionSpheres :: Ptr Vector3 -> CFloat -> Ptr Vector3 -> CFloat -> IO CBool
- c'checkCollisionBoxes :: Ptr BoundingBox -> Ptr BoundingBox -> IO CBool
- c'checkCollisionBoxSphere :: Ptr BoundingBox -> Ptr Vector3 -> CFloat -> IO CBool
- c'getRayCollisionSphere :: Ptr Ray -> Ptr Vector3 -> CFloat -> IO (Ptr RayCollision)
- c'getRayCollisionBox :: Ptr Ray -> Ptr BoundingBox -> IO (Ptr RayCollision)
- c'getRayCollisionMesh :: Ptr Ray -> Ptr Mesh -> Ptr Matrix -> IO (Ptr RayCollision)
- c'getRayCollisionTriangle :: Ptr Ray -> Ptr Vector3 -> Ptr Vector3 -> Ptr Vector3 -> IO (Ptr RayCollision)
- c'getRayCollisionQuad :: Ptr Ray -> Ptr Vector3 -> Ptr Vector3 -> Ptr Vector3 -> Ptr Vector3 -> IO (Ptr RayCollision)
High level
loadModelFromMesh :: Mesh -> IO Model Source #
Use loadModelFromMeshManaged
for a resource-managed version
loadModelFromMeshManaged :: Mesh -> WindowResources -> IO Model Source #
unloadModel :: Model -> WindowResources -> IO () Source #
Unloads a managed
model from GPU memory (VRAM)
getModelBoundingBox :: Model -> IO BoundingBox Source #
drawBoundingBox :: BoundingBox -> Color -> IO () Source #
drawBillboardRec :: Camera3D -> Texture -> Rectangle -> Vector3 -> Vector2 -> Color -> IO () Source #
drawBillboardPro :: Camera3D -> Texture -> Rectangle -> Vector3 -> Vector3 -> Vector2 -> Vector2 -> Float -> Color -> IO () Source #
unloadMesh :: Mesh -> WindowResources -> IO () Source #
Unloads a managed
mesh from GPU memory (VRAM)
getMeshBoundingBox :: Mesh -> IO BoundingBox Source #
unloadMaterial :: Material -> WindowResources -> IO () Source #
Unloads a managed
material from GPU memory (VRAM)
setMaterialTexture :: Material -> MaterialMapIndex -> Texture -> IO Material Source #
loadModelAnimations :: String -> IO [ModelAnimation] Source #
updateModelAnimation :: Model -> ModelAnimation -> Int -> IO () Source #
isModelAnimationValid :: Model -> ModelAnimation -> IO Bool Source #
updateModelAnimationBoneMatrices :: Model -> ModelAnimation -> Int -> IO () Source #
checkCollisionBoxes :: BoundingBox -> BoundingBox -> Bool Source #
checkCollisionBoxSphere :: BoundingBox -> Vector3 -> Float -> Bool Source #
getRayCollisionSphere :: Ray -> Vector3 -> Float -> RayCollision Source #
getRayCollisionBox :: Ray -> BoundingBox -> RayCollision Source #
getRayCollisionMesh :: Ray -> Mesh -> Matrix -> RayCollision Source #
getRayCollisionTriangle :: Ray -> Vector3 -> Vector3 -> Vector3 -> RayCollision Source #
getRayCollisionQuad :: Ray -> Vector3 -> Vector3 -> Vector3 -> Vector3 -> RayCollision Source #
Native
c'drawCylinderEx :: Ptr Vector3 -> Ptr Vector3 -> CFloat -> CFloat -> CInt -> Ptr Color -> IO () Source #
c'drawCylinderWires :: Ptr Vector3 -> CFloat -> CFloat -> CFloat -> CInt -> Ptr Color -> IO () Source #
c'drawCylinderWiresEx :: Ptr Vector3 -> Ptr Vector3 -> CFloat -> CFloat -> CInt -> Ptr Color -> IO () Source #
c'drawCapsule :: Ptr Vector3 -> Ptr Vector3 -> CFloat -> CInt -> CInt -> Ptr Color -> IO () Source #
c'drawCapsuleWires :: Ptr Vector3 -> Ptr Vector3 -> CFloat -> CInt -> CInt -> Ptr Color -> IO () Source #
c'getModelBoundingBox :: Ptr Model -> IO (Ptr BoundingBox) Source #
c'drawModelEx :: Ptr Model -> Ptr Vector3 -> Ptr Vector3 -> CFloat -> Ptr Vector3 -> Ptr Color -> IO () Source #
c'drawModelWiresEx :: Ptr Model -> Ptr Vector3 -> Ptr Vector3 -> CFloat -> Ptr Vector3 -> Ptr Color -> IO () Source #
c'drawModelPointsEx :: Ptr Model -> Ptr Vector3 -> Ptr Vector3 -> CFloat -> Ptr Vector3 -> Ptr Color -> IO () Source #
c'drawBoundingBox :: Ptr BoundingBox -> Ptr Color -> IO () Source #
c'drawBillboard :: Ptr Camera3D -> Ptr Texture -> Ptr Vector3 -> CFloat -> Ptr Color -> IO () Source #
c'drawBillboardRec :: Ptr Camera3D -> Ptr Texture -> Ptr Rectangle -> Ptr Vector3 -> Ptr Vector2 -> Ptr Color -> IO () Source #
c'drawBillboardPro :: Ptr Camera3D -> Ptr Texture -> Ptr Rectangle -> Ptr Vector3 -> Ptr Vector3 -> Ptr Vector2 -> Ptr Vector2 -> CFloat -> Ptr Color -> IO () Source #
c'getMeshBoundingBox :: Ptr Mesh -> IO (Ptr BoundingBox) Source #
c'loadModelAnimations :: CString -> Ptr CInt -> IO (Ptr ModelAnimation) Source #
c'updateModelAnimation :: Ptr Model -> Ptr ModelAnimation -> CInt -> IO () Source #
c'unloadModelAnimation :: Ptr ModelAnimation -> IO () Source #
c'unloadModelAnimations :: Ptr ModelAnimation -> CInt -> IO () Source #
c'isModelAnimationValid :: Ptr Model -> Ptr ModelAnimation -> IO CBool Source #
c'updateModelAnimationBoneMatrices :: Ptr Model -> Ptr ModelAnimation -> CInt -> IO () Source #
c'checkCollisionBoxes :: Ptr BoundingBox -> Ptr BoundingBox -> IO CBool Source #
c'checkCollisionBoxSphere :: Ptr BoundingBox -> Ptr Vector3 -> CFloat -> IO CBool Source #
c'getRayCollisionBox :: Ptr Ray -> Ptr BoundingBox -> IO (Ptr RayCollision) Source #