Skip to content

Commit

Permalink
supress the remaining warnings in the codebase
Browse files Browse the repository at this point in the history
  • Loading branch information
mmachenry committed Sep 25, 2015
1 parent 2258fa7 commit c300078
Show file tree
Hide file tree
Showing 5 changed files with 35 additions and 32 deletions.
26 changes: 13 additions & 13 deletions Graphics/Implicit/ExtOpenScad.hs
Expand Up @@ -22,19 +22,19 @@ import qualified System.Directory as Dir
-- Small wrapper to handle parse errors, etc
runOpenscad :: [Char] -> Either Parsec.ParseError (IO (VarLookup, [SymbolicObj2], [SymbolicObj3]))
runOpenscad s =
let
initial = defaultObjects
rearrange (_, (varlookup, ovals, _ , _ , _)) = (varlookup, obj2s, obj3s) where
(obj2s, obj3s, _ ) = divideObjs ovals
in case parseProgram "" s of
Left e -> Left e
Right sts -> Right
$ fmap rearrange
$ (\sts -> do
path <- Dir.getCurrentDirectory
State.runStateT sts (initial, [], path, (), () )
)
$ Monad.mapM_ runStatementI sts
let
initial = defaultObjects
rearrange (_, (varlookup, ovals, _ , _ , _)) = (varlookup, obj2s, obj3s) where
(obj2s, obj3s, _ ) = divideObjs ovals
in case parseProgram "" s of
Left e -> Left e
Right sts -> Right
$ fmap rearrange
$ (\sts -> do
path <- Dir.getCurrentDirectory
State.runStateT sts (initial, [], path, (), () )
)
$ Monad.mapM_ runStatementI sts



6 changes: 5 additions & 1 deletion Graphics/Implicit/ExtOpenScad/Util/OVal.hs
@@ -1,4 +1,8 @@
{-# LANGUAGE OverlappingInstances, ViewPatterns, RankNTypes, ScopedTypeVariables, TypeSynonymInstances, FlexibleInstances #-}
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ < 710
{-# LANGUAGE OverlappingInstances -#}
#endif
{-# LANGUAGE ViewPatterns, RankNTypes, ScopedTypeVariables, TypeSynonymInstances, FlexibleInstances #-}

module Graphics.Implicit.ExtOpenScad.Util.OVal where

Expand Down
6 changes: 3 additions & 3 deletions Graphics/Implicit/ObjectUtil/GetBox2.hs
Expand Up @@ -114,12 +114,12 @@ getDist2 p (Translate2 v obj) = getDist2 (p ^+^ v) obj

getDist2 p (Circle r) = magnitude p + r

getDist2 p (PolygonR r points) =
r + maximum [magnitude (p ^-^ p') | p' <- points]

getDist2 (x,y) symbObj =
let
((x1,y1), (x2,y2)) = getBox2 symbObj
in
sqrt ((max (abs (x1 - x)) (abs (x2 - x)))**2 + (max (abs (y1 - y)) (abs (y2 - y)))**2)

getDist2 p (PolygonR r points) =
r + maximum [magnitude (p ^-^ p') | p' <- points]

28 changes: 14 additions & 14 deletions Graphics/Implicit/Primitives.hs
Expand Up @@ -193,14 +193,14 @@ rotate3V = Rotate3V

pack3 :: ℝ2 -> -> [SymbolicObj3] -> Maybe SymbolicObj3
pack3 (dx, dy) sep objs =
let
boxDropZ ((a,b,_),(d,e,_)) = ((a,b),(d,e))
withBoxes :: [(Box2, SymbolicObj3)]
withBoxes = map (\obj -> ( boxDropZ $ getBox3 obj, obj)) objs
in case pack ((0,0),(dx,dy)) sep withBoxes of
(a, []) -> Just $ union $ map (\((x,y),obj) -> translate (x,y,0) obj) a
_ -> Nothing
let
boxDropZ ((a,b,_),(d,e,_)) = ((a,b),(d,e))
withBoxes :: [(Box2, SymbolicObj3)]
withBoxes = map (\obj -> ( boxDropZ $ getBox3 obj, obj)) objs
in case pack ((0,0),(dx,dy)) sep withBoxes of
(a, []) -> Just $ union $ map (\((x,y),obj) -> translate (x,y,0) obj) a
_ -> Nothing

-- 2D operations

Expand All @@ -210,10 +210,10 @@ rotate = Rotate2

pack2 :: ℝ2 -> -> [SymbolicObj2] -> Maybe SymbolicObj2
pack2 (dx, dy) sep objs =
let
withBoxes :: [(Box2, SymbolicObj2)]
withBoxes = map (\obj -> ( getBox2 obj, obj)) objs
in case pack ((0,0),(dx,dy)) sep withBoxes of
(a, []) -> Just $ union $ map (\((x,y),obj) -> translate (x,y) obj) a
_ -> Nothing
let
withBoxes :: [(Box2, SymbolicObj2)]
withBoxes = map (\obj -> ( getBox2 obj, obj)) objs
in case pack ((0,0),(dx,dy)) sep withBoxes of
(a, []) -> Just $ union $ map (\((x,y),obj) -> translate (x,y) obj) a
_ -> Nothing

1 change: 0 additions & 1 deletion implicit.cabal
Expand Up @@ -39,7 +39,6 @@ Library

ghc-options:
-O2 -optc-O3
-threaded
-rtsopts
-funfolding-use-threshold=16
-fspec-constr-count=10
Expand Down

0 comments on commit c300078

Please sign in to comment.