hgeometry-0.13: Geometric Algorithms, Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Algorithms.Geometry.SoS

Description

Implementation of Simulation of Simplicity: A Technique to Cope with Degenerate Cases in Geometric Algorithms

By Herbert Edelsbrunner and Ernst Peter Mucke

Synopsis

Documentation

data Sign Source #

The sign of an expression

Constructors

Negative 
Positive 

Instances

Instances details
Bounded Sign Source # 
Instance details

Defined in Algorithms.Geometry.SoS.Sign

Enum Sign Source # 
Instance details

Defined in Algorithms.Geometry.SoS.Sign

Methods

succ :: Sign -> Sign #

pred :: Sign -> Sign #

toEnum :: Int -> Sign #

fromEnum :: Sign -> Int #

enumFrom :: Sign -> [Sign] #

enumFromThen :: Sign -> Sign -> [Sign] #

enumFromTo :: Sign -> Sign -> [Sign] #

enumFromThenTo :: Sign -> Sign -> Sign -> [Sign] #

Eq Sign Source # 
Instance details

Defined in Algorithms.Geometry.SoS.Sign

Methods

(==) :: Sign -> Sign -> Bool #

(/=) :: Sign -> Sign -> Bool #

Ord Sign Source # 
Instance details

Defined in Algorithms.Geometry.SoS.Sign

Methods

compare :: Sign -> Sign -> Ordering #

(<) :: Sign -> Sign -> Bool #

(<=) :: Sign -> Sign -> Bool #

(>) :: Sign -> Sign -> Bool #

(>=) :: Sign -> Sign -> Bool #

max :: Sign -> Sign -> Sign #

min :: Sign -> Sign -> Sign #

Show Sign Source # 
Instance details

Defined in Algorithms.Geometry.SoS.Sign

Methods

showsPrec :: Int -> Sign -> ShowS #

show :: Sign -> String #

showList :: [Sign] -> ShowS #

flipSign :: Sign -> Sign Source #

Flip Positive = Negative.

signFromTerms :: (Num r, Eq r) => [r] -> Sign Source #

Given the terms, in decreasing order of significance, computes the sign

i.e. expects a list of terms, we base the sign on the sign of the first non-zero term.

pre: the list contains at least one such a term.

type SoS d = (Arity d, HasDeterminant (d + 1)) Source #

A dimension d has support for SoS when we can: compute a dterminant of a d+1 by d+1 dimensional matrix.

sideTest :: (SoS d, Num r, Ord r, Ord i) => (Point d r :+ i) -> Vector d (Point d r :+ i) -> Sign Source #

Given a query point q, and a vector of d points defining a hyperplane test if q lies above or below the hyperplane. Each point is assumed to have an unique index of type i that can be used to disambiguate it in case of degeneracies.

some 1D examples:

>>> sideTest (Point1 0 :+ 0) (Vector1 $ Point1 2 :+ 1)
Negative
>>> sideTest (Point1 10 :+ 0) (Vector1 $ Point1 2 :+ 1)
Positive
>>> sideTest (Point1 2 :+ 0) (Vector1 $ Point1 2 :+ 1)
Positive
>>> sideTest (Point1 2 :+ 3) (Vector1 $ Point1 2 :+ 1)
Negative

some 2D examples:

>>> sideTest (Point2 1 2 :+ 0) $ Vector2 (Point2 0 0 :+ 1) (Point2 2 2 :+ 3)
Positive
>>> sideTest (Point2 1 (-2) :+ 0) $ Vector2 (Point2 0 0 :+ 1) (Point2 2 2 :+ 3)
Negative
>>> sideTest (Point2 1 1 :+ 0) $ Vector2 (Point2 0 0 :+ 1) (Point2 2 2 :+ 3)
Positive
>>> sideTest (Point2 1 1 :+ 10) $ Vector2 (Point2 0 0 :+ 1) (Point2 2 2 :+ 3)
Negative
>>> sideTest (Point2 1 1 :+ 10) $ Vector2 (Point2 0 0 :+ 3) (Point2 2 2 :+ 1)
Negative

sideTest' :: (Num r, Ord r, Ord i, HasDeterminant (d + 1), Arity d, Arity (d + 1)) => Point d (Symbolic i r) -> Vector d (Point d (Symbolic i r)) -> Sign Source #

Given a point q and a vector of d points defining a hyperplane, test on which side of the hyperplane q lies.

TODO: Specify what the sign means

toSymbolic :: (Ord i, Arity d) => (Point d r :+ i) -> Point d (Symbolic (i, Int) r) Source #

Given an input point, transform its number type to include symbolic $varepsilon$ expressions so that we can use SoS.

signDet :: (HasDeterminant d, Ord i, Num r, Ord r) => Matrix d d (Symbolic i r) -> Sign Source #

pre: computes the sign of the determinant