about summary refs log tree commit diff
diff options
context:
space:
mode:
authorsternenseemann <git@lukasepple.de>2019-05-20 12:50:04 +0200
committersternenseemann <git@lukasepple.de>2019-05-20 13:20:41 +0200
commit87971e2174df14a511f5788334a27630cf0037ae (patch)
treea67e44d5ed110fae3458792516615f6f4de376fd
parent2ab0258ca291c92e4fd480c81ba9d0a279d4a747 (diff)
implement own rotation and translation of hitboxes
these functions replace our usage of the Rotate and Translate
constructors of gloss. these were fine, but only for rendering.
since we want to do proper collision detection we had to
manually implement rotation and translation.
-rw-r--r--lib/Grav2ty/Simulation.hs20
-rw-r--r--src/Main.hs14
2 files changed, 23 insertions, 11 deletions
diff --git a/lib/Grav2ty/Simulation.hs b/lib/Grav2ty/Simulation.hs
index 65ab83d..1027d3f 100644
--- a/lib/Grav2ty/Simulation.hs
+++ b/lib/Grav2ty/Simulation.hs
@@ -1,6 +1,7 @@
 module Grav2ty.Simulation where
 
 import Control.Lens
+import Data.Complex
 import Linear.Matrix
 import Linear.Metric (norm, distance)
 import Linear.V2
@@ -27,6 +28,25 @@ shipHitbox = HCombined
 centeredCircle :: Num a => a -> Hitbox a
 centeredCircle r = HCircle (V2 0 0) r
 
+translateHitbox :: Num a => V2 a -> Hitbox a -> Hitbox a
+translateHitbox t (HLine a b) = HLine (a + t) (b + t)
+translateHitbox t (HCircle c r) = HCircle (c + t) r
+translateHitbox t (HCombined hs) = HCombined . map (translateHitbox t) $ hs
+
+complexV2 :: Iso' (Complex a) (V2 a)
+complexV2 = iso (\(x :+ y) -> V2 x y) (\(V2 x y) -> x :+ y)
+
+-- TODO address inaccuracies of 'Float' and 'Double'?
+-- | Rotate a 'Hitbox' by a radial angle.
+rotateHitbox :: RealFloat a => a -> Hitbox a -> Hitbox a
+rotateHitbox angle box =
+  case box of
+    HLine a b -> HLine (rotate a) (rotate b)
+    HCircle c r -> HCircle (rotate c) r
+    HCombined l -> HCombined . map (rotateHitbox angle) $ l
+  where rotator = cos angle :+ sin angle
+        rotate = (^. complexV2) . (* rotator) . (^. from complexV2)
+
 -- | Based on <https://de.wikipedia.org/wiki/Cramersche_Regel>
 cramer2 :: (Eq a, Fractional a) => M22 a -> V2 a -> Maybe (a, a)
 cramer2 coeff res = if detA == 0
diff --git a/src/Main.hs b/src/Main.hs
index 1fe67f5..fcbf244 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -34,20 +34,12 @@ renderHitbox box =  Color white $
     HCombined boxes -> Pictures $ map renderHitbox boxes
 
 renderObject :: Object Float -> Picture
-renderObject obj = translate x y . rot . renderHitbox . objectHitbox $ obj
-  where (V2 x y)  = objectLoc obj
-        rot       =  rotate (clockwise . toDegree . objectRot $ obj)
+renderObject obj = renderHitbox . translate . rot . objectHitbox $ obj
+  where translate = translateHitbox (objectLoc obj)
+        rot       = rotateHitbox (objectRot obj)
         toDegree  = (*) (360 / (2 * pi))
         clockwise = (*) (-1)
 
-renderObjectsCenter :: World Float -> ([Picture], Maybe (Float, Float))
-renderObjectsCenter w = accum w ([], Nothing)
-  where isLocal Dynamic { objectMod = LocalMod } = True
-        isLocal _ = False
-        accum [] acc = acc
-        accum (w:ws) (l, c) = accum ws
-          (renderObject w : l, if isLocal w then Just (vectorToPoint (objectLoc w)) else c)
-
 renderUi :: (Show a, Num a) => State a GlossState -> Picture
 renderUi state = (uncurry translate) (tupleMap ((+ 50) . (* (-1)) . (/ 2) . fromIntegral)
     . glossViewPort . graphics $ state)