{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Diagrams.ThreeD.Transform
( T3
, aboutX, aboutY, aboutZ
, rotationAbout, rotateAbout
, pointAt, pointAt'
, scalingX, scalingY, scalingZ
, scaleX, scaleY, scaleZ
, scaling, scale
, translationX, translateX
, translationY, translateY
, translationZ, translateZ
, translation, translate
, reflectionX, reflectX
, reflectionY, reflectY
, reflectionZ, reflectZ
, reflectionAcross, reflectAcross
) where
import Diagrams.Core
import Diagrams.Core.Transform
import Diagrams.Angle
import Diagrams.Direction
import Diagrams.Points
import Diagrams.ThreeD.Types
import Diagrams.Transform
import Control.Lens (view, (&), (*~), (.~), (//~))
import Data.Semigroup
import Diagrams.TwoD.Transform
import Linear.Affine
import Linear.Metric
import Linear.V3 (cross)
import Linear.Vector
aboutZ :: Floating n => Angle n -> Transformation V3 n
aboutZ (view rad -> a) = fromOrthogonal r where
r = rot a <-> rot (-a)
rot θ (V3 x y z) = V3 (cos θ * x - sin θ * y)
(sin θ * x + cos θ * y)
z
aboutX :: Floating n => Angle n -> Transformation V3 n
aboutX (view rad -> a) = fromOrthogonal r where
r = rot a <-> rot (-a)
rot θ (V3 x y z) = V3 x
(cos θ * y - sin θ * z)
(sin θ * y + cos θ * z)
aboutY :: Floating n => Angle n -> Transformation V3 n
aboutY (view rad -> a) = fromOrthogonal r where
r = rot a <-> rot (-a)
rot θ (V3 x y z) = V3 (cos θ * x + sin θ * z)
y
(-sin θ * x + cos θ * z)
rotationAbout
:: Floating n
=> Point V3 n
-> Direction V3 n
-> Angle n
-> Transformation V3 n
rotationAbout (P t) d (view rad -> a)
= mconcat [translation (negated t),
fromOrthogonal r,
translation t] where
r = rot a <-> rot (-a)
w = fromDirection d
rot θ v = v ^* cos θ
^+^ cross w v ^* sin θ
^+^ w ^* ((w `dot` v) * (1 - cos θ))
rotateAbout
:: (InSpace V3 n t, Floating n, Transformable t)
=> Point V3 n
-> Direction V3 n
-> Angle n
-> t -> t
rotateAbout p d theta = transform (rotationAbout p d theta)
pointAt :: (Floating n, Ord n)
=> Direction V3 n -> Direction V3 n -> Direction V3 n
-> Transformation V3 n
pointAt a i f = pointAt' (fromDirection a) (fromDirection i) (fromDirection f)
pointAt' :: (Floating n, Ord n) => V3 n -> V3 n -> V3 n -> Transformation V3 n
pointAt' about initial final = pointAtUnit (signorm about) (signorm initial) (signorm final)
pointAtUnit :: (Floating n, Ord n) => V3 n -> V3 n -> V3 n -> Transformation V3 n
pointAtUnit about initial final = tilt <> pan where
signedAngle rel u v = signum (cross u v `dot` rel) *^ angleBetween u v
inPanPlaneF = final ^-^ project about final
inPanPlaneI = initial ^-^ project about initial
panAngle = signedAngle about inPanPlaneI inPanPlaneF
pan = rotationAbout origin (direction about) panAngle
tiltAngle = signedAngle tiltAxis (transform pan initial) final
tiltAxis = cross final about
tilt = rotationAbout origin (direction tiltAxis) tiltAngle
scalingZ :: (Additive v, R3 v, Fractional n) => n -> Transformation v n
scalingZ c = fromSymmetric $ (_z *~ c) <-> (_z //~ c)
scaleZ :: (InSpace v n t, R3 v, Fractional n, Transformable t) => n -> t -> t
scaleZ = transform . scalingZ
translationZ :: (Additive v, R3 v, Num n) => n -> Transformation v n
translationZ z = translation (zero & _z .~ z)
translateZ :: (InSpace v n t, R3 v, Transformable t) => n -> t -> t
translateZ = transform . translationZ
reflectionZ :: (Additive v, R3 v, Num n) => Transformation v n
reflectionZ = fromSymmetric $ (_z *~ (-1)) <-> (_z *~ (-1))
reflectZ :: (InSpace v n t, R3 v, Transformable t) => t -> t
reflectZ = transform reflectionZ
reflectionAcross :: (Metric v, Fractional n)
=> Point v n -> v n -> Transformation v n
reflectionAcross p v =
conjugate (translation (origin .-. p)) reflect
where
reflect = fromLinear t (linv t)
t = f v <-> f (negated v)
f u w = w ^-^ 2 *^ project u w
reflectAcross :: (InSpace v n t, Metric v, Fractional n, Transformable t)
=> Point v n -> v n -> t -> t
reflectAcross p v = transform (reflectionAcross p v)