geos-0.1.1.1: Bindings for GEOS.

Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Geos.Types

Synopsis

Documentation

class Relatable a where Source #

Methods

contains :: a -> Geometry b -> Bool Source #

coveredBy :: a -> Geometry b -> Bool Source #

covers :: a -> Geometry b -> Bool Source #

crosses :: a -> Geometry b -> Bool Source #

Returns True if the DE-9IM intersection matrix for the two Geometries is T*T****** (for a point and a curve,a point and an area or a line and an area) 0******** (for two curves).

disjoint :: a -> Geometry b -> Bool Source #

Returns True if the DE-9IM intersection matrix for the two geometries is FF*FF****.

intersects :: a -> Geometry b -> Bool Source #

Returns True if disjoint is False.

overlaps :: a -> Geometry b -> Bool Source #

Returns true if the DE-9IM intersection matrix for the two geometries is T*T***T** (for two points or two surfaces) 1*T***T** (for two curves).

touches :: a -> Geometry b -> Bool Source #

Returns True if the DE-9IM intersection matrix for the two geometries is FT*******, F**T***** or F***T****.

within :: a -> Geometry b -> Bool Source #

Returns True if the DE-9IM intersection matrix for the two geometries is T*F**F***.

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

Constructors

Some :: f a -> Some f 

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

data Coordinate Source #

Instances

Eq Coordinate Source # 
Data Coordinate Source # 

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 # 
Read Coordinate Source # 
Show Coordinate Source # 

newtype Point Source #

Constructors

Point Coordinate 

Instances

Eq Point Source # 

Methods

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

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

Data Point Source # 

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 # 

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 # 
Show Point Source # 

Methods

showsPrec :: Int -> Point -> ShowS #

show :: Point -> String #

showList :: [Point] -> ShowS #

newtype LinearRing Source #

Instances

Eq LinearRing Source # 
Data LinearRing Source # 

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 # 
Read LinearRing Source # 
Show LinearRing Source # 
Monoid LinearRing Source # 

newtype LineString Source #

Instances

Eq LineString Source # 
Data LineString Source # 

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 # 
Read LineString Source # 
Show LineString Source # 
Monoid LineString Source # 

newtype Polygon Source #

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

Constructors

Polygon (Vector LinearRing) 

Instances

Eq Polygon Source # 

Methods

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

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

Data Polygon Source # 

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 # 
Read Polygon Source # 
Show Polygon Source # 

newtype MultiPoint Source #

Constructors

MultiPoint (Vector Point) 

Instances

Eq MultiPoint Source # 
Data MultiPoint Source # 

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 # 
Read MultiPoint Source # 
Show MultiPoint Source # 
Monoid MultiPoint Source # 

newtype MultiLineString Source #

Instances

Eq MultiLineString Source # 
Data MultiLineString Source # 

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 # 
Read MultiLineString Source # 
Show MultiLineString Source # 

newtype MultiPolygon Source #

Constructors

MultiPolygon (Vector Polygon) 

Instances

Eq MultiPolygon Source # 
Data MultiPolygon Source # 

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 # 
Read MultiPolygon Source # 
Show MultiPolygon Source #