terrahs-0.5: Simple library for GIS Programs in Haskell.Source codeContentsIndex
Algebras.Base
Contents
The TeGeoObject type
The TeGeoObjects class
The Value type
The Attribute type
The Values class
The Attributes class
Synopsis
class Num a => Points p a | p -> a where
createPoint :: a -> a -> p
getX :: p -> a
getY :: p -> a
equal :: p -> p -> Bool
class Num a => Lines l a | l -> a where
createLine :: [(a, a)] -> l
decompToCoords :: l -> [(a, a)]
class (Num a, Lines l a) => Polygons pg l a | pg -> l a where
createPolygon :: [l] -> pg
class Ids a where
createId :: String -> a
id2string :: a -> String
data ObjectId = ObjectId String
class Set a where
union :: [a] -> [a] -> [a]
intersection :: [a] -> [a] -> [a]
difference :: [a] -> [a] -> [a]
class Topology a b => TopologyOps a b where
intersects :: a -> b -> Bool
touches :: a -> b -> Bool
crosses :: a -> b -> Bool
disjoint :: a -> b -> Bool
within :: a -> b -> Bool
equals :: a -> b -> Bool
overlaps :: a -> b -> Bool
coveredby :: a -> b -> Bool
contains :: a -> b -> Bool
containedBy :: b -> a -> Bool
class TeRelations a b => Relations a b where
relation :: a -> b -> TeSpatialRelation
centroid :: Centroid a => a -> TePoint
distance :: TePoint -> TePoint -> Double
llength :: TeLine2D -> Double
area :: TePolygon -> Double
data TeGeoObject = TeGeoObject ObjectId [Attribute] [TeGeometry]
class (Num n, Points p n, Lines l n, Polygons pg l n, Geometries g pg l p n, Ids i, Values v, Attributes at v) => GeoObjects a i at v g pg l p n | a -> i at v g pg l p n where
getId :: a -> i
getAttributes :: a -> [at]
getGeometries :: a -> [g]
data Value
= StValue String
| DbValue Double
| InValue Int32
| Undefined
data Attribute = Attr (String, Value)
class Values a where
toString :: a -> String
class Values v => Attributes a v | a -> v where
getName :: a -> String
getValue :: a -> v
getValuebyName :: [Attribute] -> String -> Value
loadRasterFile :: String -> IO (TeRaster Double)
loadRaster :: TeDatabases a => Ptr a -> String -> IO (TeRaster Double)
class Rasters r where
getValues :: r a -> [[a]]
setValues :: [[a]] -> r a
importRaster :: TeDatabases a => Ptr a -> String -> TeRaster Double -> IO Bool
importRasterWParameter :: TeDatabases a => Ptr a -> String -> Double -> TeRaster Double -> IO Bool
Documentation
class Num a => Points p a | p -> a whereSource
Methods
createPoint :: a -> a -> pSource
Create a point from two coordinates
getX :: p -> aSource
Returns the X componente of the coordinate
getY :: p -> aSource
Returns the Y componente of the coordinate
equal :: p -> p -> BoolSource
Check if the two coordinates are equal
show/hide Instances
class Num a => Lines l a | l -> a whereSource
Methods
createLine :: [(a, a)] -> lSource
Constructor - Create a line from a point list
decompToCoords :: l -> [(a, a)]Source
decomp a line to point
show/hide Instances
class (Num a, Lines l a) => Polygons pg l a | pg -> l a whereSource
Methods
createPolygon :: [l] -> pgSource
create a polygon from a line list
show/hide Instances
class Ids a whereSource
Methods
createId :: String -> aSource
id2string :: a -> StringSource
show/hide Instances
data ObjectId Source
Constructors
ObjectId String
show/hide Instances
class Set a whereSource
Methods
union :: [a] -> [a] -> [a]Source
intersection :: [a] -> [a] -> [a]Source
difference :: [a] -> [a] -> [a]Source
show/hide Instances
class Topology a b => TopologyOps a b whereSource
Methods
intersects :: a -> b -> BoolSource
touches :: a -> b -> BoolSource
crosses :: a -> b -> BoolSource
disjoint :: a -> b -> BoolSource
within :: a -> b -> BoolSource
equals :: a -> b -> BoolSource
overlaps :: a -> b -> BoolSource
coveredby :: a -> b -> BoolSource
contains :: a -> b -> BoolSource
containedBy :: b -> a -> BoolSource
show/hide Instances
class TeRelations a b => Relations a b whereSource
Methods
relation :: a -> b -> TeSpatialRelationSource
show/hide Instances
centroid :: Centroid a => a -> TePointSource
distance :: TePoint -> TePoint -> DoubleSource
llength :: TeLine2D -> DoubleSource
Returns the length of a Line 2D.
area :: TePolygon -> DoubleSource
Returns the area of a TePolygon
The TeGeoObject type
data TeGeoObject Source
Constructors
TeGeoObject ObjectId [Attribute] [TeGeometry]
show/hide Instances
The TeGeoObjects class
class (Num n, Points p n, Lines l n, Polygons pg l n, Geometries g pg l p n, Ids i, Values v, Attributes at v) => GeoObjects a i at v g pg l p n | a -> i at v g pg l p n whereSource
Methods
getId :: a -> iSource
Returns the object identification
getAttributes :: a -> [at]Source
Returns the attributes list from a geoobject
getGeometries :: a -> [g]Source
Returns the geometries list from a geoobject
show/hide Instances
The Value type
data Value Source
Constructors
StValue String
DbValue Double
InValue Int32
Undefined
show/hide Instances
The Attribute type
data Attribute Source
Constructors
Attr (String, Value)
show/hide Instances
The Values class
class Values a whereSource
Methods
toString :: a -> StringSource
show/hide Instances
The Attributes class
class Values v => Attributes a v | a -> v whereSource
Methods
getName :: a -> StringSource
getValue :: a -> vSource
show/hide Instances
getValuebyName :: [Attribute] -> String -> ValueSource
loadRasterFile :: String -> IO (TeRaster Double)Source
loadRaster :: TeDatabases a => Ptr a -> String -> IO (TeRaster Double)Source
class Rasters r whereSource
Methods
getValues :: r a -> [[a]]Source
setValues :: [[a]] -> r aSource
show/hide Instances
importRaster :: TeDatabases a => Ptr a -> String -> TeRaster Double -> IO BoolSource
importRasterWParameter :: TeDatabases a => Ptr a -> String -> Double -> TeRaster Double -> IO BoolSource
Produced by Haddock version 2.4.2