Skip to content

Commit

Permalink
fixed some point and normal bugs
Browse files Browse the repository at this point in the history
  • Loading branch information
noinia committed Apr 27, 2024
1 parent 6c478dc commit a9d662f
Show file tree
Hide file tree
Showing 3 changed files with 4 additions and 17 deletions.
4 changes: 2 additions & 2 deletions hgeometry/kernel/src/HGeometry/HyperPlane/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -260,7 +260,7 @@ class HyperPlane_ hyperPlane d r
-- | Construct a Hyperplane from a point and a normal. The normal points into the halfplane
-- for which the side-test is positive.
--
-- >>> myVerticalLine == fromPointAndNormal (Point2 5 30) (Vector2 (-1) 0)
-- >>> myVerticalLine == fromPointAndNormal (Point2 5 30) (Vector2 1 0)
-- True
fromPointAndNormal :: ( Point_ point d r, Num r)
=> point -> Vector d r -> hyperPlane
Expand All @@ -270,7 +270,7 @@ class HyperPlane_ hyperPlane d r
, Has_ Metric_ d r
)
=> point -> Vector d r -> hyperPlane
fromPointAndNormal q n = hyperPlaneFromEquation $ cons a0 n
fromPointAndNormal q n = hyperPlaneFromEquation $ cons a0 (negated n)
where
a0 = (q^.vector) `dot` n
{-# INLINE fromPointAndNormal #-}
Expand Down
14 changes: 1 addition & 13 deletions hgeometry/kernel/src/HGeometry/HyperPlane/NonVertical.hs
Original file line number Diff line number Diff line change
Expand Up @@ -119,11 +119,10 @@ instance ( MkHyperPlaneConstraints d r


instance ( MkHyperPlaneConstraints d r
, Fractional r, Eq r
, 2 <= d
) => ConstructableHyperPlane_ (NonVerticalHyperPlane d r) d r where

type HyperPlaneFromEquationConstraint (NonVerticalHyperPlane d r) d r = (Fractional r, Eq r)

-- | pre: the last component is not zero
--
--
Expand All @@ -134,17 +133,6 @@ instance ( MkHyperPlaneConstraints d r
Nothing -> error "hyperPlaneFromEquation: Hyperplane is vertical!"
{-# INLINE hyperPlaneFromEquation #-}

fromPointAndNormal _ n = NonVerticalHyperPlane n
-- see https://en.wikipedia.org/wiki/Normal_(geometry)
--
-- i.e. Alternatively, if the hyperplane is defined as the solution set of a single
-- linear equation a_1 x_1 + ⋯ + a_n x_n = c , then the vector n = ( a_1 , .. , a_n ) is
-- a normal.
--
-- FIXME: this seems fishy; don't we need the point?

--


instance ( MkHyperPlaneConstraints d r, 1 + (d-1) ~ d
, Num r
Expand Down
3 changes: 1 addition & 2 deletions hgeometry/kernel/src/HGeometry/Line/LineEQ.hs
Original file line number Diff line number Diff line change
Expand Up @@ -83,9 +83,8 @@ instance ( MkHyperPlaneConstraints 2 r
onHyperPlane = onLine

instance ( MkHyperPlaneConstraints 2 r
, Fractional r, Eq r
) => ConstructableHyperPlane_ (LineEQ r) 2 r where
type HyperPlaneFromEquationConstraint (LineEQ r) 2 r =
HyperPlaneFromEquationConstraint (NonVerticalHyperPlane 2 r) 2 r
-- | pre: the last component is not zero
hyperPlaneFromEquation = MkLineEQ
. hyperPlaneFromEquation @(NonVerticalHyperPlane 2 r)
Expand Down

0 comments on commit a9d662f

Please sign in to comment.