{-# OPTIONS_GHC -Wall #-}
module Physics.Learn.Visual.VisTools
( v3FromVec
, v3FromPos
, visVec
, oneVector
, displayVectorField
, curveObject
)
where
import SpatialMath
( V3(..)
, Euler(..)
)
import Vis
( VisObject(..)
, Color
)
import Physics.Learn.CarrotVec
( Vec
, xComp
, yComp
, zComp
, (^/)
)
import Physics.Learn.Position
( Position
, cartesianCoordinates
, VectorField
)
import Physics.Learn.Curve
( Curve(..)
)
v3FromVec :: Vec -> V3 Double
v3FromVec v = V3 x y z
where
x = xComp v
y = yComp v
z = zComp v
v3FromPos :: Position -> V3 Double
v3FromPos r = V3 x y z
where
(x,y,z) = cartesianCoordinates r
displayVectorField :: Color
-> Double
-> [Position]
-> VectorField
-> VisObject Double
displayVectorField col unitsPerMeter samplePts field
= VisObjects [Trans (v3FromPos r) $ visVec col (e ^/ unitsPerMeter) | r <- samplePts, let e = field r]
curveObject :: Color -> Curve -> VisObject Double
curveObject color (Curve f a b)
= Line' Nothing [(v3FromPos (f t), color) | t <- [a,a+(b-a)/1000..b]]
oneVector :: Color -> Position -> Vec -> VisObject Double
oneVector c r v = Trans (v3FromPos r) $ visVec c v
data Cart = Cart Double Double Double
deriving (Show)
data Sph = Sph Double Double Double
deriving (Show)
sphericalCoords :: Cart -> Sph
sphericalCoords (Cart x y z) = Sph r theta phi
where
r = sqrt (x*x + y*y + z*z)
s = sqrt (x*x + y*y)
theta = atan2 s z
phi = atan2 y x
visVec :: Color -> Vec -> VisObject Double
visVec c v = rotZ phi $ rotY theta $ Arrow (r,20*r) (V3 0 0 1) c
where
x = xComp v
y = yComp v
z = zComp v
Sph r theta phi = sphericalCoords (Cart x y z)
rotY :: Double
-> VisObject Double
-> VisObject Double
rotY alpha = RotEulerRad (Euler 0 alpha 0)
rotZ :: Double
-> VisObject Double
-> VisObject Double
rotZ alpha = RotEulerRad (Euler alpha 0 0)