Skip to content

Instantly share code, notes, and snippets.

@aavogt
Created May 7, 2024 01:32
Show Gist options
  • Save aavogt/081740a0e5984afc49f9fc1f7b68670f to your computer and use it in GitHub Desktop.
Save aavogt/081740a0e5984afc49f9fc1f7b68670f to your computer and use it in GitHub Desktop.
subset of h-raylib using linear for vectors
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
-- use linear V2 Float, V3 Float instead of raylib Vector2 Vector3
module RaylibLinear
(module Raylib.Core,
module Raylib.Types,
module Raylib.Util,
module RaylibLinear) where
import Raylib.Core hiding (getMonitorPosition, getWindowPosition, getWindowScaleDPI, getMousePosition, getMouseDelta, getMouseWheelMoveV, getTouchPosition, getScreenToWorldRay)
import Raylib.Types hiding (Quaternion, Camera3D)
import qualified Raylib.Types as Raylib
import qualified Raylib.Util as Raylib
import qualified Raylib.Core.Models as Raylib
import qualified Raylib.Core as Raylib
import Raylib.Util hiding (mode3D)
import Linear
import Foreign.Storable
import Foreign
import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Catch
import Linear.Plucker
data Camera3D = Camera3D
{ cameraPosition :: V3 Float
, cameraTarget :: V3 Float
, cameraUp :: V3 Float
, cameraFovy :: Float
, cameraProjection :: CameraProjection
} deriving (Show, Eq)
class To a b | a -> b, b -> a where
toVector :: a Float -> b
fromVector :: b -> a Float
instance To V2 Vector2 where
toVector (V2 a b) = Vector2 a b
fromVector (Vector2 a b) = V2 a b
instance To V3 Vector3 where
toVector (V3 a b c) = Vector3 a b c
fromVector (Vector3 a b c) = V3 a b c
getScreenToWorldRay :: V2 Float -> Camera3D -> IO (V3 Float, V3 Float)
getScreenToWorldRay a (Camera3D b c d e f) = do
Ray p d <- Raylib.getScreenToWorldRay (toVector a) (Raylib.Camera3D (toVector b) (toVector c) (toVector d) e f)
return $ (fromVector p, fromVector d)
drawLine3D :: V3 Float -> V3 Float -> Color -> IO ()
drawLine3D a b c = Raylib.drawLine3D (toVector a) (toVector b) c
drawCubeV :: V3 Float -> V3 Float -> Color -> IO ()
drawCubeV a b c = Raylib.drawCubeV (toVector a) (toVector b) c
mode3D :: (MonadIO m, MonadMask m) => Camera3D -> m b -> m b
mode3D (Camera3D a b c d e) = Raylib.mode3D (Raylib.Camera3D (toVector a) (toVector b) (toVector c) d e)
peek2 :: Ptr Vector2 -> IO (V2 Float)
peek2 = peek . castPtr
getMonitorPosition :: Int -> IO (V2 Float)
getMonitorPosition = peek2 <=< c'getMonitorPosition . fromIntegral
getWindowPosition :: IO (V2 Float)
getWindowPosition = peek2 =<< c'getWindowPosition
getWindowScaleDPI :: IO (V2 Float)
getWindowScaleDPI = peek2 =<< c'getWindowScaleDPI
getMousePosition :: IO (V2 Float)
getMousePosition = peek2 =<< c'getMousePosition
getMouseDelta :: IO (V2 Float)
getMouseDelta = peek2 =<< c'getMouseDelta
getMouseWheelMoveV :: IO (V2 Float)
getMouseWheelMoveV = peek2 =<< c'getMouseWheelMoveV
getTouchPosition :: Int -> IO (V2 Float)
getTouchPosition = peek2 <=< c'getTouchPosition . fromIntegral
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment