Skip to content

Commit

Permalink
feat: add pointer utilities
Browse files Browse the repository at this point in the history
  • Loading branch information
Anut-py committed Feb 21, 2024
1 parent 1beaf7a commit 0494c88
Show file tree
Hide file tree
Showing 10 changed files with 1,471 additions and 583 deletions.
22 changes: 11 additions & 11 deletions examples/bunnymark/src/Main.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# OPTIONS -Wall #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE TemplateHaskell #-}

-- Writing performant h-raylib code requires the use of pointers and other
-- un-Haskelly functionality. Unfortunately, this cannot be avoided.
Expand Down Expand Up @@ -41,7 +41,7 @@ import Raylib.Core
import Raylib.Core.Shapes (drawRectangle)
import Raylib.Core.Text (drawFPS, drawText)
import Raylib.Core.Textures (c'drawTexture, c'loadTexture, c'unloadTexture)
import Raylib.Types (Color (Color), MouseButton (MouseButtonLeft), Texture (texture'height, texture'width))
import Raylib.Types (Color (Color), MouseButton (MouseButtonLeft), Texture, p'texture'height, p'texture'width)
import Raylib.Util (inGHCi, raylibApplication)
import Raylib.Util.Colors (black, green, maroon, rayWhite)

Expand Down Expand Up @@ -120,20 +120,20 @@ startup = do
texPtr <- withCString texPath c'loadTexture
-- Use `peek` when you need to access the underlying fields

-- If you have to do this often (e.g. every frame), use `plusPtr`
-- to get a pointer to the exact field that you need

-- For example, this could be rewritten as
-- tWidth <- fromIntegral (peekByteOff texPtr 4 :: IO CInt)
-- but since we are only doing this on startup, there is no need to optimize it
tex <- peek texPtr
-- This could be rewritten as
-- tex <- peek texPtr
-- let tWidth = texture'width tex
-- ...
-- but the code below is faster as it doesn't have to load the entire structure into Haskell
tWidth <- peek (p'texture'width texPtr)
tHeight <- peek (p'texture'height texPtr)
bunniesPtr <- callocArray maxBunnies
return
( AppState
{ texBunny = texPtr,
bunnies = bunniesPtr,
halfTexWidth = fromIntegral (texture'width tex) / 2,
halfTexHeight = fromIntegral (texture'height tex) / 2,
halfTexWidth = fromIntegral tWidth / 2,
halfTexHeight = fromIntegral tHeight / 2,
bunniesCount = 0
}
)
Expand Down
74 changes: 38 additions & 36 deletions src/Raylib/Types.hs
Original file line number Diff line number Diff line change
@@ -1,38 +1,41 @@
{-# OPTIONS -Wall #-}

{-|
Each @Types@ module has up to 3 sections: one for enumerations, one for
structures, and one for callbacks. Any one of these may be omitted if not
needed (for example, most of the @Types@ modules do not have a callback
section). Most of these types are instances of `Foreign.Storable` so they can
be converted to raw bytes and passed to a C function.
The enumerations section contains Haskell sum types that are instances of
@Enum@. Each of these types corresponds to a raylib (C) @enum@ or a set of
@define@ directives. The `Prelude.fromEnum` and `Prelude.toEnum` functions for
these types use the numbers associated with these values in C. /NOTE: Some of/
/these types correspond to C @enum@s that are defined in C source files, rather/
/than header files./
The structures section contains Haskell types that each correspond to a raylib
@struct@. Each field in these types is named @typeName'fieldName@ (e.g.
@Vector2.x@ in C is `vector2'x` in Haskell). These structs also all derive the
typeclass t`Raylib.Util.Freeable`. This typeclass allows types to describe how
to properly free all the data associated with a pointer to that type. For
example, `Image`'s implementation of @Freeable@ also frees the pointer stored
in the @Image.data@ field in C.
The callbacks section contains `Foreign.FunPtr` types, along with higher-level
Haskell wrappers. When you pass one of these wrappers (e.g.
`LoadFileDataCallback`) to a function that takes one as an argument (e.g.
`Raylib.Core.setLoadFileDataCallback`), the function will return a @FunPtr@
type (e.g. `C'LoadFileDataCallback`). You will have to manually free this with
`Foreign.freeHaskellFunPtr` at the end of your program to avoid memory leaks
(TODO: implement automatic memory management for `FunPtr`s).
-}

-- |
--
-- Each @Types@ module has up to 4 sections: one for enumerations, one for
-- structures, one for pointer utilities, and one for callbacks. Any one of
-- these may be omitted if not needed (for example, most of the @Types@ modules
-- do not have a callback section). Most of these types are instances of
-- `Foreign.Storable` so they can be converted to raw bytes and passed to a C
-- function.
--
-- The enumerations section contains Haskell sum types that are instances of
-- @Enum@. Each of these types corresponds to a raylib (C) @enum@ or a set of
-- @define@ directives. The `Prelude.fromEnum` and `Prelude.toEnum` functions for
-- these types use the numbers associated with these values in C. /NOTE: Some of/
-- /these types correspond to C @enum@s that are defined in C source files, rather/
-- /than header files./
--
-- The structures section contains Haskell types that each correspond to a raylib
-- @struct@. Each field in these types is named @typeName'fieldName@ (e.g.
-- @Vector2.x@ in C is `vector2'x` in Haskell). These structs also all derive the
-- typeclass t`Raylib.Util.Freeable`. This typeclass allows types to describe how
-- to properly free all the data associated with a pointer to that type. For
-- example, `Image`'s implementation of @Freeable@ also frees the pointer stored
-- in the @Image.data@ field in C.
--
-- The pointer utilities section contains functions starting with @p'@. These
-- functions advance a pointer by some amount to allow for efficient memory
-- access. These are only necessary when writing high-performance applications
-- where memory access has to be fast.
--
-- The callbacks section contains `Foreign.FunPtr` types, along with higher-level
-- Haskell wrappers. When you pass one of these wrappers (e.g.
-- `LoadFileDataCallback`) to a function that takes one as an argument (e.g.
-- `Raylib.Core.setLoadFileDataCallback`), the function will return a @FunPtr@
-- type (e.g. `C'LoadFileDataCallback`). You will have to manually free this with
-- `Foreign.freeHaskellFunPtr` at the end of your program to avoid memory leaks
-- (TODO: implement automatic memory management for `FunPtr`s).
module Raylib.Types
( module Raylib.Types.Core,
module Raylib.Types.Core.Audio,
Expand All @@ -42,7 +45,8 @@ module Raylib.Types
module Raylib.Types.Core.Textures,
module Raylib.Types.Util.GUI,
module Raylib.Types.Util.RLGL,
) where
)
where

import Raylib.Types.Core
import Raylib.Types.Core.Audio
Expand All @@ -52,5 +56,3 @@ import Raylib.Types.Core.Text
import Raylib.Types.Core.Textures
import Raylib.Types.Util.GUI
import Raylib.Types.Util.RLGL

-- TODO: Add pointer advancing functions (p'field) for all records
Loading

0 comments on commit 0494c88

Please sign in to comment.