about summary refs log tree commit diff
diff options
context:
space:
mode:
authorsternenseemann <git@lukasepple.de>2019-10-27 19:29:44 +0100
committersternenseemann <git@lukasepple.de>2019-10-27 19:29:44 +0100
commita7ac5318ad96c6d1ced72a9b169a89864b5caf4f (patch)
treec2e58f4b6fbf195a85c73076123ae11bd4b64a9e
parent18cea52049f904a175871e778b89735b3f76828b (diff)
hlint suggestions
-rw-r--r--lib/Grav2ty/Control.hs8
-rw-r--r--lib/Grav2ty/Core.hs6
-rw-r--r--lib/Grav2ty/Simulation.hs7
-rw-r--r--lib/Grav2ty/Util/RelGraph.hs4
-rw-r--r--src/Main.hs8
-rw-r--r--test/Main.hs2
6 files changed, 17 insertions, 18 deletions
diff --git a/lib/Grav2ty/Control.hs b/lib/Grav2ty/Control.hs
index a4f2928..c497d9d 100644
--- a/lib/Grav2ty/Control.hs
+++ b/lib/Grav2ty/Control.hs
@@ -28,7 +28,7 @@ modifyObject :: (Monad m, RealFloat a)
 modifyObject id obj@Static {} = pure obj
 modifyObject id obj@Dynamic {} = use tick >>= \currentTick ->
   let mod = objectMod obj in use (inputs.at mod) >>= \modOfObj ->
-    if mod == NoMod || modOfObj == Nothing
+    if mod == NoMod || isNothing modOfObj
        then pure obj
        else do
          let Just (Modification rot acc fire) = modOfObj
@@ -47,9 +47,9 @@ deletionNecessary :: Monad m
 deletionNecessary rels id obj = do
   currentTick <- use tick
   pure $
-    isDynamic obj &&                                           -- only dynamic objs are deleted
-    (fromMaybe False ((< currentTick) <$> objectLife obj) ||   -- life span expired?
-    (anyFrom _relColl id rels == Just True))                   -- collision?
+    isDynamic obj &&                                 -- only dynamic objs are deleted
+    (maybe False (< currentTick) (objectLife obj) || -- life span expired?
+    (anyFrom _relColl id rels == Just True))         -- collision?
 
 processObject :: (Monad m, RealFloat a)
               => World a -> ObjRelGraph a
diff --git a/lib/Grav2ty/Core.hs b/lib/Grav2ty/Core.hs
index 0d8f215..f4b872c 100644
--- a/lib/Grav2ty/Core.hs
+++ b/lib/Grav2ty/Core.hs
@@ -104,7 +104,7 @@ shipHitbox = HCombined
 
 -- | Generates a 'Hitbox' with a given radius centered around (0,0).
 centeredCircle :: Num a => a -> Hitbox a
-centeredCircle r = HCircle (V2 0 0) r
+centeredCircle = HCircle (V2 0 0)
 
 data Modification a
   = Modification
@@ -135,7 +135,7 @@ makeLenses ''Grav2tyState
 type Grav2ty p g m a = StateT (Grav2tyState p g) m a
 
 addObject :: Monad m => Object a -> Grav2ty a g m ()
-addObject obj = setObject Nothing obj
+addObject = setObject Nothing
 
 setObject :: Monad m => Maybe Id -> Object a -> Grav2ty a g m ()
 setObject id obj = do
@@ -144,7 +144,7 @@ setObject id obj = do
           Nothing -> do
             highestId += 1
             use highestId
-  world %= (M.insert id obj)
+  world %= M.insert id obj
 
 getObject :: Monad m => Id -> Grav2ty a g m (Maybe (Object a))
 getObject id = use (world.at id)
diff --git a/lib/Grav2ty/Simulation.hs b/lib/Grav2ty/Simulation.hs
index c6a12d6..6214a99 100644
--- a/lib/Grav2ty/Simulation.hs
+++ b/lib/Grav2ty/Simulation.hs
@@ -41,7 +41,7 @@ complexV2 = iso (\(x :+ y) -> V2 x y) (\(V2 x y) -> x :+ y)
 
 -- | Rotate a point by an radial angle around @V2 0 0@
 rotateV2 :: RealFloat a => a -> V2 a -> V2 a
-rotateV2 angle p = (^. complexV2) . (* rotator) . (^. from complexV2) $ p
+rotateV2 angle = (^. complexV2) . (* rotator) . (^. from complexV2)
   where rotator = cos angle :+ sin angle
 
 -- TODO address inaccuracies of 'Float' and 'Double'?
@@ -100,9 +100,8 @@ collision (HLine start end) (HCircle (V2 cx cy) r) =
       b = 2 * dirX * ax + 2 * dirY * ay - 2 * cx * dirX - 2 * cy * dirY
       c = ax ^ 2 + ay ^ 2 - 2 * cx * ax - 2 * cy * ay + cx ^ 2 + cy ^ 2 - r ^ 2
       discriminant = b ** 2 - 4 * a * c
-      solution m = (-b `m` (sqrt discriminant)) / (2 * a)
-      solutions = solution (+) :
-        (if discriminant > 0 then [solution (-)] else [])
+      solution m = (-b `m` sqrt discriminant) / (2 * a)
+      solutions = solution (+) : [solution (-) | discriminant > 0]
    in discriminant >= 0 -- there is a possible intersection
    && a /= 0 -- HLine is proper line (i.e. has distinct start and end points)
    && any (inRange (0, 1)) solutions
diff --git a/lib/Grav2ty/Util/RelGraph.hs b/lib/Grav2ty/Util/RelGraph.hs
index bf529b4..8cdb7a9 100644
--- a/lib/Grav2ty/Util/RelGraph.hs
+++ b/lib/Grav2ty/Util/RelGraph.hs
@@ -87,7 +87,7 @@ insertMapKey f g map = M.foldlWithKey' ins g map
 
 -- | Lookup the Relation between two given Vertices.
 lookupRel :: Ord a => a -> a -> RelGraph a v -> Maybe v
-lookupRel x y = (>>= (M.lookup y)) . M.lookup x . unRelGraph
+lookupRel x y = (>>= M.lookup y) . M.lookup x . unRelGraph
 
 -- | Wether any of the Edges from a given Vertex satisfy
 --   the given condition.
@@ -100,7 +100,7 @@ foldlFrom' f res x =
   foldl' f res . fromMaybe M.empty . M.lookup x . unRelGraph
 
 prop_relCorrectness :: Seq Integer -> Bool
-prop_relCorrectness seq = and . map cond $ allCombinations g
+prop_relCorrectness seq = all cond $ allCombinations g
   where g = insertSeq (\x y -> let r = x * y in (r, negate r)) emptyRel seq
         cond (x, y) = lookupRel x y g == fmap negate (lookupRel y x g)
 
diff --git a/src/Main.hs b/src/Main.hs
index 09f6d6d..cfd4923 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -46,10 +46,10 @@ renderHitbox box =  Color white $
     HCombined boxes -> Pictures $ map renderHitbox boxes
 
 renderObject :: Object Float -> Picture
-renderObject obj = renderHitbox . realHitbox $ obj
+renderObject = renderHitbox . realHitbox
 
 renderUi :: (PrintfArg a, Num a) => Grav2tyState a GlossState -> Picture
-renderUi state = (uncurry translate) (homBimap ((+ 50) . (* (-1)) . (/ 2) . fromIntegral)
+renderUi state = uncurry translate (homBimap ((+ 50) . (* (-1)) . (/ 2) . fromIntegral)
   . (^. graphics.glossViewPort) $ state)
   . scale 0.2 0.2 . Color green . Text $ uiText
   where uiText = printf "Acceleration: %.0f Time/Tick: %f Tick: %d" acc tpt t
@@ -84,7 +84,7 @@ eventHandler :: (Show a, Ord a, Real a, Floating a) => Event
 eventHandler (EventKey key Down _ _) state = action state
   where updateLocalMod :: Lens' (Modification a) b -> (b -> b)
                        -> Grav2tyState a GlossState -> Grav2tyState a GlossState
-        updateLocalMod l f = over (inputs.at LocalMod ._Just.l) f
+        updateLocalMod l = over (inputs.at LocalMod ._Just.l)
         accStep = 1
         rotStep = pi / 10
         scaleStep = 1.1
@@ -95,7 +95,7 @@ eventHandler (EventKey key Down _ _) state = action state
             SpecialKey KeyUp -> updateLocalMod modAcc (+ accStep)
             SpecialKey KeyDown -> updateLocalMod modAcc (boundSub 0 accStep)
             SpecialKey KeyLeft -> updateLocalMod modRot (mod2pi . (+ rotStep))
-            SpecialKey KeyRight -> updateLocalMod modRot (mod2pi . (subtract rotStep))
+            SpecialKey KeyRight -> updateLocalMod modRot (mod2pi . subtract rotStep)
             SpecialKey KeySpace -> updateLocalMod modFire (const $ state^.tick + 10)
             Char 'c' -> over (graphics.glossCenterView) not
             Char '+' -> over (graphics.glossViewPortScale) (* scaleStep)
diff --git a/test/Main.hs b/test/Main.hs
index 2d52c51..49d5027 100644
--- a/test/Main.hs
+++ b/test/Main.hs
@@ -14,7 +14,7 @@ instance (Ord a, Arbitrary a, Arbitrary v) => Arbitrary (RelGraph a v) where
   arbitrary = do
     let g = emptyRel
     c <- arbitrary `suchThat` (>= 0)
-    times c g $ (\g -> do
+    times c g (\g -> do
       x <- arbitrary
       y <- arbitrary
       v <- arbitrary