Skip to content

Commit

Permalink
more cleaning up + fixed ball spec
Browse files Browse the repository at this point in the history
  • Loading branch information
noinia committed Jan 19, 2025
1 parent 9967eb1 commit 1f86694
Show file tree
Hide file tree
Showing 2 changed files with 13 additions and 18 deletions.
13 changes: 1 addition & 12 deletions hgeometry/src/HGeometry/Polygon/WithHoles.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,30 +22,19 @@ module HGeometry.Polygon.WithHoles

import Control.DeepSeq (NFData)
import Control.Lens hiding (holes)
import qualified Data.Foldable as F
import Data.Foldable1
import Data.Functor.Apply (Apply, (<.*>), MaybeApply(..))
import Data.Functor.Classes
import Data.Functor.Apply ((<.*>), MaybeApply(..))
import Data.Kind (Type)
import qualified Data.List.NonEmpty as NonEmpty
import qualified Data.Map as Map
import Data.Semigroup.Foldable
import Data.Semigroup.Traversable
import Data.Vector (Vector)
import qualified Data.Vector as Vector
import Data.Vector.NonEmpty.Internal (NonEmptyVector(..))
import GHC.Generics (Generic)
import HGeometry.Boundary
import HGeometry.Box
import HGeometry.Cyclic
import HGeometry.Foldable.Util
import HGeometry.Intersection
import HGeometry.LineSegment.Intersection.BentleyOttmann
import HGeometry.Point
import HGeometry.Polygon.Class
import HGeometry.Polygon.Simple
import HGeometry.Polygon.Simple.Implementation
import HGeometry.Polygon.Simple.InPolygon
import HGeometry.Properties
import HGeometry.Transformation
import HGeometry.Vector.NonEmpty.Util ()
Expand Down
18 changes: 12 additions & 6 deletions hgeometry/test-with-ipe/test/BallSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,11 @@
{-# LANGUAGE OverloadedStrings #-}
module BallSpec where

import Control.Lens
import Data.Maybe
import Golden
import HGeometry.Ball
import HGeometry.Ext
import HGeometry.HalfLine
import HGeometry.Intersection
import HGeometry.Line
Expand Down Expand Up @@ -34,14 +36,18 @@ spec = describe "ball intersection with line" $ do
, map (\b -> iO'' b $ attr SLayer "balls"
) balls
, map (\case
Line_x_Ball_Point q -> iO'' q $ attr SLayer "LineXBall"
Line_x_Ball_Segment seg -> iO'' seg $ attr SPen (IpePen "fat")
<> attr SLayer "LineXBall"
Line_x_Ball_Point q -> iO'' (q^.core)
$ attr SLayer "LineXBall"
Line_x_Ball_Segment seg -> iO'' (view core <$> seg)
$ attr SPen (IpePen "fat")
<> attr SLayer "LineXBall"
) intersections
, map (\case
Line_x_Ball_Point q -> iO'' q $ attr SLayer "HalfLineXBall"
Line_x_Ball_Segment seg -> iO'' seg $ attr SPen (IpePen "fat")
<> attr SLayer "HalfLineXBall"
Line_x_Ball_Point q -> iO'' (q^.core)
$ attr SLayer "HalfLineXBall"
Line_x_Ball_Segment seg -> iO'' (view core <$> seg)
$ attr SPen (IpePen "fat")
<> attr SLayer "HalfLineXBall"
) hlIntersections
])

Expand Down

0 comments on commit 1f86694

Please sign in to comment.