{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Network.UI.Kafka.Interpretation (
Interpretation(..)
, AxisInterpretation(..)
, AnalogHandler
, ButtonHandler
, interpretationLoop
) where
import Control.Concurrent.MVar (MVar, newMVar, readMVar, swapMVar)
import Control.Monad (unless, void)
import Data.Aeson.Types (FromJSON, ToJSON)
import GHC.Generics (Generic)
import Linear.Conjugate (Conjugate)
import Linear.Epsilon (Epsilon)
import Linear.Quaternion (Quaternion(..), axisAngle, rotate)
import Linear.V3 (V3(..))
import Linear.Vector ((^+^), basis)
import Network.UI.Kafka (ExitAction, LoopAction, Sensor, TopicConnection, producerLoop)
import Network.UI.Kafka.Types (Button(..), Event(ButtonEvent, LocationEvent, OrientationEvent), Toggle(..))
instance FromJSON a => FromJSON (V3 a)
instance ToJSON a => ToJSON (V3 a)
instance FromJSON a => FromJSON (Quaternion a)
instance ToJSON a => ToJSON (Quaternion a)
data Interpretation a b =
TrackInterpretation
{
kafka :: TopicConnection
, sensor :: Sensor
, device :: a
, xAxis :: AxisInterpretation b
, yAxis :: AxisInterpretation b
, zAxis :: AxisInterpretation b
, phiAxis :: AxisInterpretation b
, thetaAxis :: AxisInterpretation b
, psiAxis :: AxisInterpretation b
, location :: V3 b
, orientation :: V3 b
, flying :: Bool
, resetButton :: Maybe Int
}
deriving (Eq, Generic, Read, Show)
instance (FromJSON a, FromJSON b) => FromJSON (Interpretation a b)
instance (ToJSON a, ToJSON b) => ToJSON (Interpretation a b)
data AxisInterpretation a =
AxisInterpretation
{
axisNumber :: Int
, threshold :: Maybe a
, increment :: a
, lowerBound :: Maybe a
, upperBound :: Maybe a
}
deriving (Eq, Generic, Read, Show)
instance FromJSON a => FromJSON (AxisInterpretation a)
instance ToJSON a => ToJSON (AxisInterpretation a)
translate :: (Conjugate b, Epsilon b, Num b, Ord b, RealFloat b)
=> MVar (State b)
-> AnalogHandler b c
-> ButtonHandler b c
-> Interpretation a b
-> c
-> IO [Event]
translate state analogHandler buttonHandler TrackInterpretation{..} event =
do
(location0, orientation0) <- readMVar state
let
adjust number setting AxisInterpretation{..} =
if number == axisNumber && maybe True (abs setting >) threshold
then setting * increment
else 0
clamp AxisInterpretation{..} =
maybe id ((maximum .) . (. return) . (:)) lowerBound
. maybe id ((minimum .) . (. return) . (:)) upperBound
(location1, orientation1) =
case (buttonHandler event, analogHandler event) of
(Just (number, pressed), _) -> if pressed && Just number == resetButton
then (location, fromEuler orientation)
else (location0, orientation0)
(_, Just (number, setting)) -> let
euler = adjust number setting <$> V3 phiAxis thetaAxis psiAxis
axes = V3 xAxis yAxis zAxis
delta = adjust number setting <$> axes
in
(
clamp
<$> axes
<*> location0
^+^ (if flying then (orientation0 `rotate`) else id) delta
, fromEuler euler
* orientation0
)
(_, _) -> (location0, orientation0)
unless (location0 == location1 && orientation0 == orientation1)
. void
$ swapMVar state (location1, orientation1)
return
. (if location0 /= location1 then (fromV3 location1 :) else id)
. (if orientation0 /= orientation1 then (fromQuaternion orientation1 :) else id)
$ case buttonHandler event of
Just (number, pressed) -> [ButtonEvent (IndexButton number, if pressed then Down else Up)]
Nothing -> []
fromEuler :: (Epsilon a, Num a, RealFloat a) => V3 a -> Quaternion a
fromEuler (V3 phi theta psi) =
let
[ex, ey, ez] = basis
in
ez `axisAngle` psi * ey `axisAngle` theta * ex `axisAngle` phi
fromV3 :: Real a => V3 a -> Event
fromV3 (V3 x y z) = LocationEvent (realToFrac x, realToFrac y, realToFrac z)
fromQuaternion :: Real a => Quaternion a -> Event
fromQuaternion (Quaternion w (V3 x y z)) = OrientationEvent (realToFrac w, realToFrac x, realToFrac y, realToFrac z)
fromDegrees :: (Floating a, Num a) => a -> a
fromDegrees = (* pi) . (/ 180)
type State a = (V3 a, Quaternion a)
type AnalogHandler a b = b
-> Maybe (Int, a)
type ButtonHandler a b = b
-> Maybe (Int, Bool)
interpretationLoop :: (Conjugate b, Epsilon b, Num b, Ord b, RealFloat b)
=> AnalogHandler b c
-> ButtonHandler b c
-> Interpretation a b
-> IO c
-> IO (ExitAction, LoopAction)
interpretationLoop analogHandler buttonHandler interpretation@TrackInterpretation{..} action =
do
first <- newMVar True
state <- newMVar (location, fromEuler $ fromDegrees <$> orientation)
producerLoop kafka sensor
$ do
isFirst <- readMVar first
if isFirst
then swapMVar first False >> return [fromV3 location, fromQuaternion $ fromEuler $ fromDegrees <$> orientation]
else action >>= translate state analogHandler buttonHandler interpretation