{-# OPTIONS -Wall #-}
module Raylib.Util.Camera
  ( getCameraForward,
    getCameraUp,
    getCameraRight,
    cameraMove,
    cameraMoveForward,
    cameraMoveUp,
    cameraMoveRight,
    cameraRotate,
    cameraYaw,
    cameraPitch,
    cameraRoll,
    getCameraViewMatrix,
    getCameraProjectionMatrix,
  )
where
import Raylib.Types (Camera, Camera3D (..), CameraProjection (CameraOrthographic, CameraPerspective), Matrix, Vector3 (..))
import Raylib.Util.Math (Vector (..), clamp, deg2Rad, matrixLookAt, matrixOrtho, matrixPerspective, vector3Angle, vector3CrossProduct, vector3RotateByAxisAngle)
getCameraForward :: Camera -> Vector3
getCameraForward :: Camera -> Vector3
getCameraForward Camera
cam = Vector3 -> Vector3
forall a. Vector a => a -> a
vectorNormalize (Vector3 -> Vector3) -> Vector3 -> Vector3
forall a b. (a -> b) -> a -> b
$ Camera -> Vector3
camera3D'target Camera
cam Vector3 -> Vector3 -> Vector3
forall a. Vector a => a -> a -> a
|-| Camera -> Vector3
camera3D'position Camera
cam
getCameraUp :: Camera -> Vector3
getCameraUp :: Camera -> Vector3
getCameraUp Camera
cam = Vector3 -> Vector3
forall a. Vector a => a -> a
vectorNormalize (Vector3 -> Vector3) -> Vector3 -> Vector3
forall a b. (a -> b) -> a -> b
$ Camera -> Vector3
camera3D'up Camera
cam
getCameraRight :: Camera -> Vector3
getCameraRight :: Camera -> Vector3
getCameraRight Camera
cam = Vector3 -> Vector3
forall a. Vector a => a -> a
vectorNormalize (Vector3 -> Vector3) -> Vector3 -> Vector3
forall a b. (a -> b) -> a -> b
$ Vector3 -> Vector3 -> Vector3
vector3CrossProduct (Camera -> Vector3
getCameraForward Camera
cam) (Camera -> Vector3
getCameraUp Camera
cam)
cameraMove :: Camera -> Vector3 -> Camera
cameraMove :: Camera -> Vector3 -> Camera
cameraMove Camera
cam Vector3
dir =
  Camera
cam {camera3D'position = camera3D'position cam |+| dir, camera3D'target = camera3D'target cam |+| dir}
cameraMoveForward ::
  Camera ->
  
  Float ->
  
  Bool ->
  Camera
cameraMoveForward :: Camera -> Float -> Bool -> Camera
cameraMoveForward Camera
cam Float
distance Bool
moveInWorldPlane =
  Camera -> Vector3 -> Camera
cameraMove Camera
cam (Vector3
forward Vector3 -> Float -> Vector3
forall a. Vector a => a -> Float -> a
|* Float
distance)
  where
    forward :: Vector3
forward = if Bool
moveInWorldPlane then Vector3
camForward {vector3'y = 0} else Vector3
camForward
    camForward :: Vector3
camForward = Camera -> Vector3
getCameraForward Camera
cam
cameraMoveUp ::
  Camera ->
  
  Float ->
  Camera
cameraMoveUp :: Camera -> Float -> Camera
cameraMoveUp Camera
cam Float
distance =
  Camera -> Vector3 -> Camera
cameraMove Camera
cam (Vector3
up Vector3 -> Float -> Vector3
forall a. Vector a => a -> Float -> a
|* Float
distance)
  where
    up :: Vector3
up = Camera -> Vector3
getCameraUp Camera
cam
cameraMoveRight ::
  Camera ->
  
  Float ->
  
  Bool ->
  Camera
cameraMoveRight :: Camera -> Float -> Bool -> Camera
cameraMoveRight Camera
cam Float
distance Bool
moveInWorldPlane =
  Camera -> Vector3 -> Camera
cameraMove Camera
cam (Vector3
right Vector3 -> Float -> Vector3
forall a. Vector a => a -> Float -> a
|* Float
distance)
  where
    right :: Vector3
right = if Bool
moveInWorldPlane then Vector3
camRight {vector3'y = 0} else Vector3
camRight
    camRight :: Vector3
camRight = Camera -> Vector3
getCameraRight Camera
cam
cameraRotate ::
  Camera ->
  
  Vector3 ->
  
  Float ->
  
  Bool ->
  Camera
cameraRotate :: Camera -> Vector3 -> Float -> Bool -> Camera
cameraRotate Camera
cam Vector3
axis Float
angle Bool
rotateAroundTarget =
  Camera
cam
    { camera3D'position = if rotateAroundTarget then target |-| viewRot else pos,
      camera3D'target = if rotateAroundTarget then target else pos |+| viewRot
    }
  where
    viewVec :: Vector3
viewVec = Vector3
target Vector3 -> Vector3 -> Vector3
forall a. Vector a => a -> a -> a
|-| Vector3
pos
    viewRot :: Vector3
viewRot = Vector3 -> Vector3 -> Float -> Vector3
vector3RotateByAxisAngle Vector3
viewVec Vector3
axis Float
angle
    pos :: Vector3
pos = Camera -> Vector3
camera3D'position Camera
cam
    target :: Vector3
target = Camera -> Vector3
camera3D'target Camera
cam
cameraYaw ::
  Camera ->
  
  Float ->
  
  Bool ->
  Camera
cameraYaw :: Camera -> Float -> Bool -> Camera
cameraYaw Camera
cam Float
angle Bool
rotateAroundTarget =
  Camera
cam
    { camera3D'position = if rotateAroundTarget then target |-| viewRot else pos,
      camera3D'target = if rotateAroundTarget then target else pos |+| viewRot
    }
  where
    viewVec :: Vector3
viewVec = Vector3
target Vector3 -> Vector3 -> Vector3
forall a. Vector a => a -> a -> a
|-| Vector3
pos
    viewRot :: Vector3
viewRot = Vector3 -> Vector3 -> Float -> Vector3
vector3RotateByAxisAngle Vector3
viewVec (Camera -> Vector3
getCameraUp Camera
cam) Float
angle
    pos :: Vector3
pos = Camera -> Vector3
camera3D'position Camera
cam
    target :: Vector3
target = Camera -> Vector3
camera3D'target Camera
cam
cameraPitch ::
  Camera ->
  
  Float ->
  
  Bool ->
  
  Bool ->
  
  Bool ->
  Camera
cameraPitch :: Camera -> Float -> Bool -> Bool -> Bool -> Camera
cameraPitch Camera
cam Float
angle Bool
lockView Bool
rotateAroundTarget Bool
rotateUp =
  Camera
cam
    { camera3D'position = if rotateAroundTarget then target |-| viewRot else pos,
      camera3D'target = if rotateAroundTarget then target else pos |+| viewRot,
      camera3D'up = if not rotateUp then up else vector3RotateByAxisAngle up right angle'
    }
  where
    angle' :: Float
angle' = if Bool -> Bool
not Bool
lockView then Float
angle else Float -> Float -> Float -> Float
clamp Float
angle Float
maxAngleDown Float
maxAngleUp
    maxAngleUp :: Float
maxAngleUp = Vector3 -> Vector3 -> Float
vector3Angle Vector3
up Vector3
viewVec Float -> Float -> Float
forall a. Num a => a -> a -> a
- Float
0.001
    maxAngleDown :: Float
maxAngleDown = (-Vector3 -> Vector3 -> Float
vector3Angle (Vector3 -> Vector3
forall a. Vector a => a -> a
additiveInverse Vector3
up) Vector3
viewVec) Float -> Float -> Float
forall a. Num a => a -> a -> a
+ Float
0.001
    viewVec :: Vector3
viewVec = Vector3
target Vector3 -> Vector3 -> Vector3
forall a. Vector a => a -> a -> a
|-| Vector3
pos
    viewRot :: Vector3
viewRot = Vector3 -> Vector3 -> Float -> Vector3
vector3RotateByAxisAngle Vector3
viewVec Vector3
right Float
angle'
    pos :: Vector3
pos = Camera -> Vector3
camera3D'position Camera
cam
    target :: Vector3
target = Camera -> Vector3
camera3D'target Camera
cam
    up :: Vector3
up = Camera -> Vector3
getCameraUp Camera
cam
    right :: Vector3
right = Camera -> Vector3
getCameraRight Camera
cam
cameraRoll ::
  Camera ->
  
  Float ->
  Camera
cameraRoll :: Camera -> Float -> Camera
cameraRoll Camera
cam Float
angle =
  Camera
cam
    { camera3D'up = vector3RotateByAxisAngle up forward angle
    }
  where
    forward :: Vector3
forward = Camera -> Vector3
getCameraForward Camera
cam
    up :: Vector3
up = Camera -> Vector3
getCameraUp Camera
cam
getCameraViewMatrix :: Camera -> Matrix
getCameraViewMatrix :: Camera -> Matrix
getCameraViewMatrix Camera
cam = Vector3 -> Vector3 -> Vector3 -> Matrix
matrixLookAt (Camera -> Vector3
camera3D'position Camera
cam) (Camera -> Vector3
camera3D'target Camera
cam) (Camera -> Vector3
camera3D'up Camera
cam)
getCameraProjectionMatrix ::
  Camera ->
  
  Float ->
  
  Float ->
  
  Float ->
  Matrix
getCameraProjectionMatrix :: Camera -> Float -> Float -> Float -> Matrix
getCameraProjectionMatrix Camera
cam Float
aspect Float
near Float
far =
  case Camera -> CameraProjection
camera3D'projection Camera
cam of
    CameraProjection
CameraPerspective -> Float -> Float -> Float -> Float -> Matrix
matrixPerspective (Camera -> Float
camera3D'fovy Camera
cam Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
deg2Rad) Float
aspect Float
near Float
far
    CameraProjection
CameraOrthographic -> Float -> Float -> Float -> Float -> Float -> Float -> Matrix
matrixOrtho (-Float
right) Float
right (-Float
top) Float
top Float
near Float
far
      where
        top :: Float
top = Camera -> Float
camera3D'fovy Camera
cam Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
2
        right :: Float
right = Float
top Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
aspect