geos-0.3.0: Bindings for GEOS.

Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Geos.Geometry

Synopsis

Documentation

data Geometry a where Source #

data Point Source #

Instances
Eq Point Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Methods

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

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

Data Point Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Methods

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 #

toConstr :: Point -> Constr #

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 # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Methods

compare :: Point -> Point -> Ordering #

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

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

(>) :: Point -> Point -> Bool #

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

max :: Point -> Point -> Point #

min :: Point -> Point -> Point #

Read Point Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Show Point Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Methods

showsPrec :: Int -> Point -> ShowS #

show :: Point -> String #

showList :: [Point] -> ShowS #

Generic Point Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Associated Types

type Rep Point :: Type -> Type #

Methods

from :: Point -> Rep Point x #

to :: Rep Point x -> Point #

type Rep Point Source # 
Instance details

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)))

data LinearRing Source #

Instances
Eq LinearRing Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Data LinearRing Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LinearRing -> c LinearRing #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LinearRing #

toConstr :: LinearRing -> Constr #

dataTypeOf :: LinearRing -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LinearRing) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LinearRing) #

gmapT :: (forall b. Data b => b -> b) -> LinearRing -> LinearRing #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LinearRing -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LinearRing -> r #

gmapQ :: (forall d. Data d => d -> u) -> LinearRing -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LinearRing -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LinearRing -> m LinearRing #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LinearRing -> m LinearRing #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LinearRing -> m LinearRing #

Ord LinearRing Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Read LinearRing Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Show LinearRing Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Generic LinearRing Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Associated Types

type Rep LinearRing :: Type -> Type #

Semigroup LinearRing Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Monoid LinearRing Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

type Rep LinearRing Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

data LineString Source #

Instances
Eq LineString Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Data LineString Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LineString -> c LineString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LineString #

toConstr :: LineString -> Constr #

dataTypeOf :: LineString -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LineString) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LineString) #

gmapT :: (forall b. Data b => b -> b) -> LineString -> LineString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LineString -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LineString -> r #

gmapQ :: (forall d. Data d => d -> u) -> LineString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LineString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LineString -> m LineString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LineString -> m LineString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LineString -> m LineString #

Ord LineString Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Read LineString Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Show LineString Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Generic LineString Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Associated Types

type Rep LineString :: Type -> Type #

Semigroup LineString Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Monoid LineString Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

type Rep LineString Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

data Polygon Source #

In a polygon, the fist LinearRing is the shell, and any following are holes.

Instances
Eq Polygon Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Methods

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

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

Data Polygon Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Methods

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 # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Read Polygon Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Show Polygon Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Generic Polygon Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Associated Types

type Rep Polygon :: Type -> Type #

Methods

from :: Polygon -> Rep Polygon x #

to :: Rep Polygon x -> Polygon #

type Rep Polygon Source # 
Instance details

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
Eq MultiPoint Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Data MultiPoint Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MultiPoint -> c MultiPoint #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MultiPoint #

toConstr :: MultiPoint -> Constr #

dataTypeOf :: MultiPoint -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MultiPoint) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MultiPoint) #

gmapT :: (forall b. Data b => b -> b) -> MultiPoint -> MultiPoint #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MultiPoint -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MultiPoint -> r #

gmapQ :: (forall d. Data d => d -> u) -> MultiPoint -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MultiPoint -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MultiPoint -> m MultiPoint #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MultiPoint -> m MultiPoint #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MultiPoint -> m MultiPoint #

Ord MultiPoint Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Read MultiPoint Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Show MultiPoint Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Generic MultiPoint Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Associated Types

type Rep MultiPoint :: Type -> Type #

Semigroup MultiPoint Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Monoid MultiPoint Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

type Rep MultiPoint Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

type Rep MultiPoint = D1 (MetaData "MultiPoint" "Data.Geometry.Geos.Geometry" "geos-0.3.0-inplace" True) (C1 (MetaCons "MultiPoint" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector Point))))

data MultiLineString Source #

Instances
Eq MultiLineString Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Data MultiLineString Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MultiLineString -> c MultiLineString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MultiLineString #

toConstr :: MultiLineString -> Constr #

dataTypeOf :: MultiLineString -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MultiLineString) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MultiLineString) #

gmapT :: (forall b. Data b => b -> b) -> MultiLineString -> MultiLineString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MultiLineString -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MultiLineString -> r #

gmapQ :: (forall d. Data d => d -> u) -> MultiLineString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MultiLineString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MultiLineString -> m MultiLineString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MultiLineString -> m MultiLineString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MultiLineString -> m MultiLineString #

Ord MultiLineString Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Read MultiLineString Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Show MultiLineString Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Generic MultiLineString Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Associated Types

type Rep MultiLineString :: Type -> Type #

type Rep MultiLineString Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

type Rep MultiLineString = D1 (MetaData "MultiLineString" "Data.Geometry.Geos.Geometry" "geos-0.3.0-inplace" True) (C1 (MetaCons "MultiLineString" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector LineString))))

data MultiPolygon Source #

Instances
Eq MultiPolygon Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Data MultiPolygon Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MultiPolygon -> c MultiPolygon #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MultiPolygon #

toConstr :: MultiPolygon -> Constr #

dataTypeOf :: MultiPolygon -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MultiPolygon) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MultiPolygon) #

gmapT :: (forall b. Data b => b -> b) -> MultiPolygon -> MultiPolygon #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MultiPolygon -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MultiPolygon -> r #

gmapQ :: (forall d. Data d => d -> u) -> MultiPolygon -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MultiPolygon -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MultiPolygon -> m MultiPolygon #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MultiPolygon -> m MultiPolygon #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MultiPolygon -> m MultiPolygon #

Ord MultiPolygon Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Read MultiPolygon Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Show MultiPolygon Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Generic MultiPolygon Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Associated Types

type Rep MultiPolygon :: Type -> Type #

type Rep MultiPolygon Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

type Rep MultiPolygon = D1 (MetaData "MultiPolygon" "Data.Geometry.Geos.Geometry" "geos-0.3.0-inplace" True) (C1 (MetaCons "MultiPolygon" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector Polygon))))

data Some :: (* -> *) -> * where Source #

Constructors

Some :: f a -> Some f 
Instances
Eq (Some Geometry) Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Show (Some Geometry) Source # 
Instance details

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
Eq Coordinate Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Data Coordinate Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Coordinate -> c Coordinate #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Coordinate #

toConstr :: Coordinate -> Constr #

dataTypeOf :: Coordinate -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Coordinate) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Coordinate) #

gmapT :: (forall b. Data b => b -> b) -> Coordinate -> Coordinate #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Coordinate -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Coordinate -> r #

gmapQ :: (forall d. Data d => d -> u) -> Coordinate -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Coordinate -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Coordinate -> m Coordinate #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Coordinate -> m Coordinate #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Coordinate -> m Coordinate #

Ord Coordinate Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Read Coordinate Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Show Coordinate Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Generic Coordinate Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

Associated Types

type Rep Coordinate :: Type -> Type #

type Rep Coordinate Source # 
Instance details

Defined in Data.Geometry.Geos.Geometry

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 #

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.

withSomeGeometry :: Some Geometry -> (forall a. Geometry a -> b) -> b Source #

mapSomeGeometry :: (forall a. Geometry a -> b) -> Some Geometry -> b Source #

the same as withSomeGeometry with its arguments reversed.