{-# LANGUAGE TemplateHaskell #-}
module Graphics.Camera( Camera(Camera)
, cameraPosition, rawCameraNormal, rawViewUp
, viewPlaneDepth, nearDist, farDist, screenDimensions
, cameraNormal, viewUp
, cameraTransform, worldToView
, toViewPort, perspectiveProjection, rotateCoordSystem
, flipAxes
) where
import Control.Lens
import Data.Geometry.Matrix
import Data.Geometry.Point
import Data.Geometry.Transformation
import Data.Geometry.Vector
data Camera r = Camera { _cameraPosition :: !(Point 3 r)
, _rawCameraNormal :: !(Vector 3 r)
, _rawViewUp :: !(Vector 3 r)
, _viewPlaneDepth :: !r
, _nearDist :: !r
, _farDist :: !r
, _screenDimensions :: !(Vector 2 r)
} deriving (Show,Eq,Ord)
makeLenses ''Camera
cameraNormal :: Floating r => Lens' (Camera r) (Vector 3 r)
cameraNormal = lens _rawCameraNormal (\c n -> c { _rawCameraNormal = signorm n} )
viewUp :: Floating r => Lens' (Camera r) (Vector 3 r)
viewUp = lens _rawViewUp (\c n -> c { _rawViewUp = signorm n})
cameraTransform :: Fractional r => Camera r -> Transformation 3 r
cameraTransform c = toViewPort c
|.| perspectiveProjection c
|.| worldToView c
worldToView :: Fractional r => Camera r -> Transformation 3 r
worldToView c = rotateCoordSystem c
|.| (translation $ (-1) *^ c^.cameraPosition.vector)
toViewPort :: Fractional r => Camera r -> Transformation 3 r
toViewPort c = Transformation . Matrix
$ Vector4 (Vector4 (w/2) 0 0 0)
(Vector4 0 (h/2) 0 0)
(Vector4 0 0 (1/2) (1/2))
(Vector4 0 0 0 1)
where
Vector2 w h = c^.screenDimensions
perspectiveProjection :: Fractional r => Camera r -> Transformation 3 r
perspectiveProjection c = Transformation . Matrix $
Vector4 (Vector4 (-n/rx) 0 0 0)
(Vector4 0 (-n/ry) 0 0)
(Vector4 0 0 (-(n+f)/(n-f)) (-2*n*f/(n-f)))
(Vector4 0 0 1 0)
where
n = c^.nearDist
f = c^.farDist
Vector2 rx ry = (/2) <$> c^.screenDimensions
rotateCoordSystem :: Num r => Camera r -> Transformation 3 r
rotateCoordSystem c = rotateTo $ Vector3 u v n
where
u = (c^.rawViewUp) `cross` n
v = n `cross` u
n = (-1) *^ c^.rawCameraNormal
flipAxes :: Num r => Transformation 3 r
flipAxes = Transformation . Matrix
$ Vector4 (Vector4 1 0 0 0)
(Vector4 0 0 1 0)
(Vector4 0 1 0 0)
(Vector4 0 0 0 1)