{-# LANGUAGE RebindableSyntax #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PatternSynonyms #-}
module Data.Array.Accelerate.Linear.Projection
where
import Data.Array.Accelerate hiding ( pattern V3, pattern V4 )
import Data.Array.Accelerate.Smart
import Data.Array.Accelerate.Linear.Epsilon
import Data.Array.Accelerate.Linear.Matrix
import Data.Array.Accelerate.Linear.Metric
import Data.Array.Accelerate.Linear.V3
import Data.Array.Accelerate.Linear.V4
import Control.Lens
import qualified Linear.Projection as L
lookAt
:: (Epsilon a, Floating a)
=> Exp (V3 a)
-> Exp (V3 a)
-> Exp (V3 a)
-> Exp (M44 a)
lookAt eye center up = V4_ (V4_ (xa ^. _x) (xa ^. _y) (xa ^. _z) xd)
(V4_ (ya ^. _x) (ya ^. _y) (ya ^. _z) yd)
(V4_ (-za ^. _x) (-za ^. _y) (-za ^. _z) zd)
(V4_ 0 0 0 1)
where
za = normalize $ center - eye
xa = normalize $ cross za up
ya = cross xa za
xd = -dot xa eye
yd = -dot ya eye
zd = dot za eye
perspective
:: Floating a
=> Exp a
-> Exp a
-> Exp a
-> Exp a
-> Exp (M44 a)
perspective = lift $$$$ L.perspective
infinitePerspective
:: Floating a
=> Exp a
-> Exp a
-> Exp a
-> Exp (M44 a)
infinitePerspective = lift $$$ L.infinitePerspective
ortho
:: Floating a
=> Exp a
-> Exp a
-> Exp a
-> Exp a
-> Exp a
-> Exp a
-> Exp (M44 a)
ortho = lift $$$$$$ L.ortho
infixr 0 $$$$$$
($$$$$$) :: (b -> a) -> (c -> d -> e -> f -> g -> h -> b) -> c -> d -> e -> f -> g -> h -> a
(f $$$$$$ g) x y z u v w = f (g x y z u v w)