hgeometry: Data types for geometric objects, geometric algorithms, and data structures.

[ bsd3, geometry, library ] [ Propose Tags ]

HGeometry provides some basic geometry types, and geometric algorithms and data structures for them. The main two focusses are: (1) Strong type safety, and (2) implementations of geometric algorithms and data structures with good asymptotic running time guarantees.


[Skip to Readme]

Modules

[Last Documentation]

  • Algorithms
    • Geometry
      • ConvexHull
        • Algorithms.Geometry.ConvexHull.GrahamScan
      • SmallestEnclosingBall
        • Algorithms.Geometry.SmallestEnclosingBall.RandomizedIncrementalConstruction
  • Control
    • Monad
      • State
        • Control.Monad.State.Persistent
  • Data
    • Data.Ext
    • Data.Geometry
      • Data.Geometry.Ball
      • Data.Geometry.Box
      • Data.Geometry.HalfLine
      • Data.Geometry.Interval
      • Data.Geometry.Ipe
        • Data.Geometry.Ipe.Attributes
        • Data.Geometry.Ipe.PathParser
        • Data.Geometry.Ipe.Reader
        • Data.Geometry.Ipe.Types
        • Data.Geometry.Ipe.Writer
      • Data.Geometry.Line
        • Data.Geometry.Line.Internal
      • Data.Geometry.LineSegment
      • Data.Geometry.Point
      • Data.Geometry.PolyLine
      • Data.Geometry.Polygon
      • Data.Geometry.Properties
      • Data.Geometry.Transformation
      • Data.Geometry.Triangle
      • Data.Geometry.Vector
        • Data.Geometry.Vector.VectorFixed
    • Data.Seq2
  • System
    • Random
      • System.Random.Shuffle

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.1.1.0, 0.1.1.1, 0.4.0.0, 0.5.0.0, 0.6.0.0, 0.7.0.0, 0.8.0.0, 0.9.0.0, 0.10.0.0, 0.11.0.0, 0.12.0.0, 0.12.0.1, 0.12.0.2, 0.12.0.3, 0.12.0.4, 0.13, 0.14
Dependencies base (>=4.7 && <5), bifunctors (>=4.1), bytestring (>=0.10), containers (>=0.5.5), data-clist (>=0.0.7.2), fixed-vector (>=0.6.4.0 && <0.7), hexpat (>=0.20.7), lens (>=4.2), linear (>=1.10), mtl, parsec (>=3), random, semigroups (>=0.15), singletons (>=1.0 && <1.1), text (>=0.11), validation (>=0.4), vector (>=0.10), vinyl (>=0.5 && <0.6) [details]
License BSD-3-Clause
Author Frank Staals
Maintainer f.staals@uu.nl
Category Geometry
Home page http://fstaals.net/software/hgeometry
Source repo head: git clone http://github.com/noinia/hgeometry
Uploaded by FrankStaals at 2015-05-04T15:20:41Z
Distributions
Reverse Dependencies 6 direct, 8 indirect [details]
Downloads 11728 total (66 in the last 30 days)
Rating 2.0 (votes: 1) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs not available [build log]
All reported builds failed as of 2016-12-09 [all 8 reports]

Readme for hgeometry-0.4.0.0

[back to package description]

HGeometry

Build Status Hackage

HGeometry provides some basic geometry types, and geometric algorithms and data structures for them. The main two focusses are: (1) Strong type safety, and (2) implementations of geometric algorithms and data structures with good asymptotic running time guarantees. Design choices showing these aspects are for example:

  • we provide a data type Point d r parameterized by a type-level natural number d, representing d-dimensional points (in all cases our type parameter r represents the (numeric) type for the (real)-numbers):
newtype Point (d :: Nat) (r :: *) = Point { toVec :: Vector d r }
  • the vertices of a PolyLine d p r are stored in a Data.Seq2 which enforces that a polyline is a proper polyline, and thus has at least two vertices.

Please note that aspect (2), implementing good algorithms, is much work in progress. HGeometry currently has only very basic types, and implements only two algorithms: an (optimal) \(O(n \log n)\) time algorithm for convex hull, and an \(O(n)\) expected time algorithm for smallest enclosing disk (both in \(R^2\)).

Current work is on implementing \(O(n \log n + k)\) time red-blue line segment intersection. This would also allow for efficient polygon intersection and map overlay.

A Note on the Ext (:+) data type

In many applications we do not just have geometric data, e.g. Point d rs or Polygon rs, but instead, these types have some additional properties, like a color, size, thickness, elevation, or whatever. Hence, we would like that our library provides functions that also allow us to work with ColoredPolygon rs etc. The typical Haskell approach would be to construct type-classes such as PolygonLike and define functions that work with any type that is PolygonLike. However, geometric algorithms are often hard enough by themselves, and thus we would like all the help that the type-system/compiler can give us. Hence, we choose to work with concrete types.

To still allow for some extensibility our types will use the Ext (:+) type. For example, our Polygon data type, has an extra type parameter p that allows the vertices of the polygon to cary some extra information of type p (for example a color, a size, or whatever).

data Polygon (t :: PolygonType) p r where
  SimplePolygon :: C.CList (Point 2 r :+ p)                         -> Polygon Simple p r
  MultiPolygon  :: C.CList (Point 2 r :+ p) -> [Polygon Simple p r] -> Polygon Multi  p r

In all places this extra data is accessable by the (:+) type in Data.Ext, which is essentially just a pair.

Reading and Writing Ipe files

Appart from geometric types, HGeometry provides some interface for reading and writing Ipe (http://ipe7.sourceforge.net). However, this is all very work in progress. Hence, the API is experimental and may change at any time!