Skip to content

Commit 6483551

Browse files
committed
Fix hlint and few other warnings
1 parent df48f60 commit 6483551

File tree

4 files changed

+18
-21
lines changed

4 files changed

+18
-21
lines changed

src/Graphics/Implicit/Viewer.hs

Lines changed: 6 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
{-# LANGUAGE FlexibleContexts #-}
22
{-# LANGUAGE FlexibleInstances #-}
3-
{-# LANGUAGE PackageImports #-}
43
{-# LANGUAGE RecordWildCards #-}
54
{-# LANGUAGE ScopedTypeVariables #-}
65
{-# LANGUAGE TypeFamilies #-}
@@ -117,7 +116,7 @@ viewer config@ViewerConf{..} = do
117116

118117
fragmentStream <-
119118
do
120-
guard' (shaderEnvFlatNormals)
119+
guard' shaderEnvFlatNormals
121120
rasterize
122121
shaderEnvRasterOptions
123122
(proj Flat <$> primitiveStream)
@@ -197,8 +196,8 @@ loop win shader triangles unionBuffers@Uniforms{..} aTime eventChan renderChan v
197196

198197
projMat = perspective (pi/2) (fromIntegral windowWidth / fromIntegral windowHeight) 0.1 100
199198

200-
eye = (V3 0 (-1) 1)
201-
lookAtPoint = (V3 0 0 0)
199+
eye = V3 0 (-1) 1
200+
lookAtPoint = V3 0 0 0
202201

203202
cameraMatrix :: M44 Float
204203
cameraMatrix =
@@ -276,8 +275,8 @@ updateViewerState win chan oldState = do
276275
V2 cursorX cursorY = lastCursorPos
277276
in
278277
s { lastCursorPos = x
279-
, camPitch = ((realToFrac $ cursorY - oldCursorY) / 100 + camPitch) `mod''` (2*pi)
280-
, camYaw = ((realToFrac $ cursorX - oldCursorX) / 100 + camYaw) `mod''` (2*pi)
278+
, camPitch = (realToFrac (cursorY - oldCursorY) / 100 + camPitch) `mod''` (2*pi)
279+
, camYaw = (realToFrac (cursorX - oldCursorX) / 100 + camYaw) `mod''` (2*pi)
281280
}
282281
LeftMouse x
283282
-> s { camRotating = x }
@@ -309,7 +308,7 @@ updateViewerState win chan oldState = do
309308
else -1
310309
animTime =
311310
if animationRunning
312-
then animationTime + (faster $ animDirection * animationStep)
311+
then animationTime + faster (animDirection * animationStep)
313312
else animationTime
314313

315314
nextOutOfBounds =

src/Graphics/Implicit/Viewer/Demos.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@ module Graphics.Implicit.Viewer.Demos where
44

55
import Graphics.Implicit
66
import Graphics.Implicit.Primitives
7-
import Linear
87

98
demoLetterI :: Double -> SymbolicObj3
109
demoLetterI t =
@@ -23,8 +22,8 @@ demoRotatingAnim t =
2322
ontop :: SymbolicObj3 -> SymbolicObj3 -> SymbolicObj3
2423
ontop a b = union [ translate (V3 0 0 z) a, b ]
2524
where z = let
26-
((V3 _ _ aBottom), _) = getBox a
27-
(_, (V3 _ _ bTop)) = getBox b
25+
(V3 _ _ aBottom, _) = getBox a
26+
(_, V3 _ _ bTop) = getBox b
2827
in bTop - aBottom
2928

3029
demoTranslatedSymbolic :: SymbolicObj3

src/Graphics/Implicit/Viewer/Loaders.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,6 @@ import Graphics.Implicit.Export.GL
2121
import Graphics.Implicit.ExtOpenScad.Definitions
2222
import Graphics.Implicit.Primitives (getBox)
2323
import Graphics.Implicit.Viewer.Types
24-
import Linear (V3 (V3))
2524

2625
import qualified Language.Haskell.Interpreter as Hint
2726
import qualified System.Directory
@@ -186,7 +185,7 @@ renderObjToChan o resolution renderChan = do
186185
unless (l == 0) $ do
187186
atomically $ writeTChan renderChan (l, objScale, mesh)
188187
after <- getCurrentTime
189-
putStrLn $ "Done in " ++ (show $ diffUTCTime after now)
188+
putStrLn $ "Done in " ++ show (diffUTCTime after now)
190189

191190
when (l == 0) $ putStrLn "Mesh empty"
192191

@@ -201,6 +200,6 @@ runAnimation f initialResolution renderChan aTime = void $ async $ forever $ do
201200
isE <- atomically $ isEmptyTChan renderChan
202201
case isE of
203202
True -> do
204-
t <- atomically $ readTVar aTime
203+
t <- readTVarIO aTime
205204
renderObjToChan (f t) initialResolution renderChan
206205
False -> threadDelay 100000

src/Graphics/Implicit/Viewer/Shaders.hs

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ allShaders = Data.Map.fromList $ zip [0..]
3232

3333
asumShaderByID
3434
:: forall os
35-
. ((ShaderEnvironment os) -> Int)
35+
. (ShaderEnvironment os -> Int)
3636
-> Window os RGBAFloat Depth
3737
-> FragStream
3838
-> Shader os (ShaderEnvironment os) ()
@@ -62,16 +62,16 @@ computeLight specularIntensity eye VertexInfo{..} =
6262
halfVector = signorm viewDir
6363
specular = maxB (viNormal `dot` halfVector) 0
6464
in
65-
specularIntensity *^ (V4 1 1 1 1) ^* (specular ** 32)
65+
specularIntensity *^ V4 1 1 1 1 ^* (specular ** 32)
6666
+ (1 *^ opaque $
6767
0.1 -- global illumination
6868
+ (
6969
-- red light from front right
70-
(V3 0.8 0 0 ^* (maxB (normal `dot` dirR) 0))
70+
(V3 0.8 0 0 ^* maxB (normal `dot` dirR) 0)
7171
-- green from front left
72-
+ (V3 0 0.8 0 ^* (maxB (normal `dot` dirG) 0))
72+
+ (V3 0 0.8 0 ^* maxB (normal `dot` dirG) 0)
7373
-- blue from bottom
74-
+ (V3 0 0 0.8 ^* (maxB (normal `dot` dirB) 0))
74+
+ (V3 0 0 0.8 ^* maxB (normal `dot` dirB) 0)
7575
))
7676

7777
lightShaded
@@ -82,7 +82,7 @@ lightShaded
8282
lightShaded i win fragStream = do
8383
eye <- getUni bEye
8484
let
85-
litFrags = (computeLight i eye) <$> fragStream
85+
litFrags = computeLight i eye <$> fragStream
8686

8787
drawWindowColorDepth
8888
(const (win, def, def))
@@ -100,7 +100,7 @@ alphaWireframe win fragStream = do
100100
(V3 i j k) = w
101101
edgeFactor = minB (minB i j) k
102102
in
103-
(V4 1 0 0 ((1.0 - edgeFactor) * 0.95))
103+
V4 1 0 0 ((1.0 - edgeFactor) * 0.95)
104104

105105
drawWindowColor
106106
(const (win, blendAlpha))
@@ -125,7 +125,7 @@ edgy win fragStream = do
125125

126126
drawWindowColor
127127
(const (win, blendAlpha))
128-
(wireFrags)
128+
wireFrags
129129

130130
edges
131131
:: forall os . Window os RGBAFloat Depth

0 commit comments

Comments
 (0)