module Diagrams.ThreeD.Deform
( parallelX0, perspectiveX1, facingX
, parallelY0, perspectiveY1, facingY
, parallelZ0, perspectiveZ1, facingZ
) where
import Control.Lens
import Diagrams.Deform
import Diagrams.TwoD.Deform
import Linear.V3
import Linear.Vector
parallelZ0 :: (R3 v, Num n) => Deformation v v n
parallelZ0 :: forall (v :: * -> *) n. (R3 v, Num n) => Deformation v v n
parallelZ0 = forall (v :: * -> *) (u :: * -> *) n.
(Point v n -> Point u n) -> Deformation v u n
Deformation (forall (t :: * -> *) a. R3 t => Lens' (t a) a
_z forall s t a b. ASetter s t a b -> b -> s -> t
.~ n
0)
perspectiveZ1 :: (R3 v, Functor v, Fractional n) => Deformation v v n
perspectiveZ1 :: forall (v :: * -> *) n.
(R3 v, Functor v, Fractional n) =>
Deformation v v n
perspectiveZ1 = forall (v :: * -> *) (u :: * -> *) n.
(Point v n -> Point u n) -> Deformation v u n
Deformation forall a b. (a -> b) -> a -> b
$ \Point v n
p -> Point v n
p forall (f :: * -> *) a.
(Functor f, Fractional a) =>
f a -> a -> f a
^/ (Point v n
p forall s a. s -> Getting a s a -> a
^. forall (t :: * -> *) a. R3 t => Lens' (t a) a
_z)
facingZ :: (R3 v, Functor v, Fractional n) => Deformation v v n
facingZ :: forall (v :: * -> *) n.
(R3 v, Functor v, Fractional n) =>
Deformation v v n
facingZ = forall (v :: * -> *) (u :: * -> *) n.
(Point v n -> Point u n) -> Deformation v u n
Deformation forall a b. (a -> b) -> a -> b
$
\Point v n
p -> let z :: n
z = Point v n
p forall s a. s -> Getting a s a -> a
^. forall (t :: * -> *) a. R3 t => Lens' (t a) a
_z
in Point v n
p forall (f :: * -> *) a.
(Functor f, Fractional a) =>
f a -> a -> f a
^/ n
z forall a b. a -> (a -> b) -> b
& forall (t :: * -> *) a. R3 t => Lens' (t a) a
_z forall s t a b. ASetter s t a b -> b -> s -> t
.~ n
z