Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Geometry a where
- PointGeometry :: Point -> SRID -> Geometry Point
- LineStringGeometry :: LineString -> SRID -> Geometry LineString
- LinearRingGeometry :: LinearRing -> SRID -> Geometry LinearRing
- PolygonGeometry :: Polygon -> SRID -> Geometry Polygon
- MultiPointGeometry :: MultiPoint -> SRID -> Geometry MultiPoint
- MultiLineStringGeometry :: MultiLineString -> SRID -> Geometry MultiLineString
- MultiPolygonGeometry :: MultiPolygon -> SRID -> Geometry MultiPolygon
- CollectionGeometry :: GeometryCollection -> SRID -> Geometry GeometryCollection
- data GeometryConstructionError
- data Point
- point :: Coordinate -> Point
- data LinearRing
- linearRing :: CoordinateSequence -> Either GeometryConstructionError LinearRing
- data LineString
- lineString :: CoordinateSequence -> Either GeometryConstructionError LineString
- data Polygon
- polygon :: Vector LinearRing -> Either GeometryConstructionError Polygon
- data MultiPoint
- multiPoint :: Vector Point -> MultiPoint
- data MultiLineString
- multiLineString :: Vector LineString -> MultiLineString
- data MultiPolygon
- multiPolygon :: Vector Polygon -> MultiPolygon
- data GeometryCollection
- geometryCollection :: Vector (Some Geometry) -> GeometryCollection
- data Some :: (* -> *) -> * where
- data Coordinate
- coordinate2 :: Double -> Double -> Coordinate
- coordinate3 :: Double -> Double -> Double -> Coordinate
- type SRID = Maybe Int
- binaryPredicate :: (GeomConst -> GeomConst -> Geos Bool) -> Geometry a -> Geometry b -> Bool
- convertGeometryFromRaw :: (Geometry a, CoordSeqInput a ~ cb, CoordinateSequence cb) => a -> Geos (Some Geometry)
- convertGeometryToRaw :: (Geometry a, CoordSeqInput a ~ cb, CoordinateSequence cb) => Geometry b -> Geos a
- convertMultiPolygonFromRaw :: (Geometry a, CoordSeqInput a ~ ca, CoordinateSequence ca) => a -> Geos MultiPolygon
- ensurePoint :: Some Geometry -> Maybe (Geometry Point)
- ensureLineString :: Some Geometry -> Maybe (Geometry LineString)
- ensureLinearRing :: Some Geometry -> Maybe (Geometry LinearRing)
- ensurePolygon :: Some Geometry -> Maybe (Geometry Polygon)
- ensureMultiPoint :: Some Geometry -> Maybe (Geometry MultiPoint)
- ensureMultiPolygon :: Some Geometry -> Maybe (Geometry MultiPolygon)
- ensureMultiLineString :: Some Geometry -> Maybe (Geometry MultiLineString)
- ensureGeometryCollection :: Some Geometry -> Maybe (Geometry GeometryCollection)
- interpolate :: Geometry LineString -> Double -> Geometry Point
- interpolateNormalized :: Geometry LineString -> Double -> Geometry Point
- project :: Geometry LineString -> Geometry Point -> Double
- projectNormalized :: Geometry LineString -> Geometry Point -> Double
- equalsExact :: Geometry a -> Geometry a -> Double -> Bool
- equals :: Geometry a -> Geometry a -> Bool
- area :: Geometry a -> Double
- geometryLength :: Geometry a -> Double
- distance :: Geometry a -> Geometry a -> Double
- hausdorffDistance :: Geometry a -> Geometry a -> Double
- nearestPoints :: Geometry a -> Geometry a -> (Coordinate, Coordinate)
- withSomeGeometry :: Some Geometry -> (forall a. Geometry a -> b) -> b
- mapSomeGeometry :: (forall a. Geometry a -> b) -> Some Geometry -> b
Documentation
data Geometry a where Source #
PointGeometry :: Point -> SRID -> Geometry Point | |
LineStringGeometry :: LineString -> SRID -> Geometry LineString | |
LinearRingGeometry :: LinearRing -> SRID -> Geometry LinearRing | |
PolygonGeometry :: Polygon -> SRID -> Geometry Polygon | |
MultiPointGeometry :: MultiPoint -> SRID -> Geometry MultiPoint | |
MultiLineStringGeometry :: MultiLineString -> SRID -> Geometry MultiLineString | |
MultiPolygonGeometry :: MultiPolygon -> SRID -> Geometry MultiPolygon | |
CollectionGeometry :: GeometryCollection -> SRID -> Geometry GeometryCollection |
Instances
Eq (Geometry a) Source # | |
Eq (Some Geometry) Source # | |
Show (Geometry a) Source # | |
Show (Some Geometry) Source # | |
Relatable (Geometry a) Source # | |
Defined in Data.Geometry.Geos.Relatable contains :: Geometry a -> Geometry b -> Bool Source # coveredBy :: Geometry a -> Geometry b -> Bool Source # covers :: Geometry a -> Geometry b -> Bool Source # crosses :: Geometry a -> Geometry b -> Bool Source # disjoint :: Geometry a -> Geometry b -> Bool Source # intersects :: Geometry a -> Geometry b -> Bool Source # overlaps :: Geometry a -> Geometry b -> Bool Source # |
Instances
Eq Point Source # | |
Data Point Source # | |
Defined in Data.Geometry.Geos.Geometry gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Point -> c Point # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Point # dataTypeOf :: Point -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Point) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Point) # gmapT :: (forall b. Data b => b -> b) -> Point -> Point # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Point -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Point -> r # gmapQ :: (forall d. Data d => d -> u) -> Point -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Point -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Point -> m Point # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Point -> m Point # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Point -> m Point # | |
Ord Point Source # | |
Read Point Source # | |
Show Point Source # | |
Generic Point Source # | |
type Rep Point Source # | |
Defined in Data.Geometry.Geos.Geometry type Rep Point = D1 (MetaData "Point" "Data.Geometry.Geos.Geometry" "geos-0.3.0-inplace" True) (C1 (MetaCons "Point" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Coordinate))) |
point :: Coordinate -> Point Source #
data LinearRing Source #
Instances
linearRing :: CoordinateSequence -> Either GeometryConstructionError LinearRing Source #
data LineString Source #
Instances
lineString :: CoordinateSequence -> Either GeometryConstructionError LineString Source #
In a polygon, the fist LinearRing is the shell, and any following are holes.
Instances
Eq Polygon Source # | |
Data Polygon Source # | |
Defined in Data.Geometry.Geos.Geometry gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Polygon -> c Polygon # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Polygon # toConstr :: Polygon -> Constr # dataTypeOf :: Polygon -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Polygon) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Polygon) # gmapT :: (forall b. Data b => b -> b) -> Polygon -> Polygon # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Polygon -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Polygon -> r # gmapQ :: (forall d. Data d => d -> u) -> Polygon -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Polygon -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Polygon -> m Polygon # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Polygon -> m Polygon # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Polygon -> m Polygon # | |
Ord Polygon Source # | |
Defined in Data.Geometry.Geos.Geometry | |
Read Polygon Source # | |
Show Polygon Source # | |
Generic Polygon Source # | |
type Rep Polygon Source # | |
Defined in Data.Geometry.Geos.Geometry type Rep Polygon = D1 (MetaData "Polygon" "Data.Geometry.Geos.Geometry" "geos-0.3.0-inplace" True) (C1 (MetaCons "Polygon" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector LinearRing)))) |
data MultiPoint Source #
Instances
multiPoint :: Vector Point -> MultiPoint Source #
data MultiLineString Source #
Instances
data MultiPolygon Source #
Instances
multiPolygon :: Vector Polygon -> MultiPolygon Source #
data GeometryCollection Source #
Instances
Eq GeometryCollection Source # | |
Defined in Data.Geometry.Geos.Geometry (==) :: GeometryCollection -> GeometryCollection -> Bool # (/=) :: GeometryCollection -> GeometryCollection -> Bool # | |
Show GeometryCollection Source # | |
Defined in Data.Geometry.Geos.Geometry showsPrec :: Int -> GeometryCollection -> ShowS # show :: GeometryCollection -> String # showList :: [GeometryCollection] -> ShowS # | |
Generic GeometryCollection Source # | |
Defined in Data.Geometry.Geos.Geometry type Rep GeometryCollection :: Type -> Type # from :: GeometryCollection -> Rep GeometryCollection x # to :: Rep GeometryCollection x -> GeometryCollection # | |
type Rep GeometryCollection Source # | |
Defined in Data.Geometry.Geos.Geometry |
data Coordinate Source #
Coordinate is the lightweight class used to store coordinates. Coordinate objects are two-dimensional points, with an additional z-ordinate. |
Instances
coordinate2 :: Double -> Double -> Coordinate Source #
coordinate3 :: Double -> Double -> Double -> Coordinate Source #
type SRID = Maybe Int Source #
In all geometry types, SRID is used for compatability and is NOT used in calculations. For example, the distance
between two PointGeometry with an SRID of `Just 4326` will return a distance between two points in Euclidean space in the units the PointGeometry is initialized with. It will not calculate the distance on a spheroid.
binaryPredicate :: (GeomConst -> GeomConst -> Geos Bool) -> Geometry a -> Geometry b -> Bool Source #
convertGeometryFromRaw :: (Geometry a, CoordSeqInput a ~ cb, CoordinateSequence cb) => a -> Geos (Some Geometry) Source #
convertGeometryToRaw :: (Geometry a, CoordSeqInput a ~ cb, CoordinateSequence cb) => Geometry b -> Geos a Source #
convertMultiPolygonFromRaw :: (Geometry a, CoordSeqInput a ~ ca, CoordinateSequence ca) => a -> Geos MultiPolygon Source #
ensureLineString :: Some Geometry -> Maybe (Geometry LineString) Source #
ensureLinearRing :: Some Geometry -> Maybe (Geometry LinearRing) Source #
ensureMultiPoint :: Some Geometry -> Maybe (Geometry MultiPoint) Source #
interpolate :: Geometry LineString -> Double -> Geometry Point Source #
Given a distance, returns the point (or closest point) within the geometry LineString that distance.
interpolateNormalized :: Geometry LineString -> Double -> Geometry Point Source #
Like interpolate
, but takes the distance as a double between 0 and 1.
project :: Geometry LineString -> Geometry Point -> Double Source #
Returns the distance from the origin of LineString to the point projected on the geometry (that is to a point of the line the closest to the given point).
projectNormalized :: Geometry LineString -> Geometry Point -> Double Source #
Like project
, but returns the distance as a Double between 0 and 1.
equalsExact :: Geometry a -> Geometry a -> Double -> Bool Source #
Returns True if the two geometries are exactly equal, up to a specified tolerance. The tolerance value should be a floating point number representing the error tolerance in the comparison, e.g., equalsExact g1 g2 0.001
will compare equality to within one thousandth of a unit.
geometryLength :: Geometry a -> Double Source #
Returns the length of this geometry (e.g., 0 for a Point, the length of a LineString, or the circumference of a Polygon).
distance :: Geometry a -> Geometry a -> Double Source #
NOTE: distance
calculations are linear – in other words, distance
does not perform a spherical calculation even if the SRID specifies a geographic coordinate system.
nearestPoints :: Geometry a -> Geometry a -> (Coordinate, Coordinate) Source #
Returns the closest points of the two geometries. The first point comes from g1 geometry and the second point comes from g2.
mapSomeGeometry :: (forall a. Geometry a -> b) -> Some Geometry -> b Source #
the same as withSomeGeometry
with its arguments reversed.