terrahs-0.5: Simple library for GIS Programs in Haskell.Source codeContentsIndex
TerraHS
Contents
The TeGeoObject type
The TeGeoObjects class
The Value type
The Attribute type
The Values class
The Attributes class
The Databases Module class
The Object Module class
Synopsis
data TeDatabase
= TeMySQL String String String String
| TePostgreSQL
class TeDatabases a where
loadLayer :: Ptr a -> String -> IO TeLayerPtr
errorMessage :: Ptr a -> IO String
loadRaster :: Ptr a -> String -> IO (TeRaster Double)
importRaster :: Ptr a -> String -> TeRaster Double -> IO Bool
importRasterWParameter :: Ptr a -> String -> Double -> TeRaster Double -> IO Bool
data TeGeometry
= GPt TePoint
| GPg TePolygon
| GLn TeLine2D
| GCl TeCell
data TePoint = TePoint TeCoord2D
data TePolygon = TePolygon [TeLinearRing]
data TeLine2D = TeLine2D [TeCoord2D]
data TeCell = TeCell TeBox Int32 Int32
data TeBox = TeBox Double Double Double Double
data TePointSet = TePointSet [TePoint]
data TePolygonSet = TePolygonSet [TePolygon]
data TeLineSet = TeLineSet [TeLine2D]
data TeCellSet = TeCellSet [TeCell]
data TeSTInstance = TeSTInstance
class Topology a b where
teintersects :: a -> b -> Bool
tetouches :: a -> b -> Bool
tecrosses :: a -> b -> Bool
tedisjoint :: a -> b -> Bool
tewithin :: a -> b -> Bool
teequals :: a -> b -> Bool
teoverlaps :: a -> b -> Bool
tecoveredby :: a -> b -> Bool
tecontains :: a -> b -> Bool
tecontainedBy :: b -> a -> Bool
class Overlay a where
teunion :: a -> a -> [TeGeometry]
tedifference :: a -> a -> [TeGeometry]
teintersection :: a -> a -> [TeGeometry]
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 TeRaster a = TeRaster (Grd a)
loadRasterFile :: String -> IO (TeRaster Double)
class Rasters r where
getValues :: r a -> [[a]]
setValues :: [[a]] -> r a
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
class Connection c where
open :: c -> IO (Ptr c)
close :: Ptr c -> IO ()
class Connection c => Databases a c where
retrieve :: Ptr c -> String -> IO a
store :: Ptr c -> String -> a -> IO Bool
class Pointer a where
new :: a -> IO (Ptr a)
fromPointer :: Ptr a -> IO a
delete :: Ptr a -> IO ()
class Convert a b where
to :: a -> b
from :: b -> a
class Element a b where
getElement :: Ptr a -> Int32 -> IO b
class Size a where
size :: Ptr a -> IO Int32
Documentation
data TeDatabase Source
Constructors
TeMySQL String String String String
TePostgreSQL
show/hide Instances
class TeDatabases a whereSource
Methods
loadLayer :: Ptr a -> String -> IO TeLayerPtrSource
Load information about a particular layer
errorMessage :: Ptr a -> IO StringSource
Gets the last error message
loadRaster :: Ptr a -> String -> IO (TeRaster Double)Source
importRaster :: Ptr a -> String -> TeRaster Double -> IO BoolSource
importRasterWParameter :: Ptr a -> String -> Double -> TeRaster Double -> IO BoolSource
show/hide Instances
data TeGeometry Source
Constructors
GPt TePoint
GPg TePolygon
GLn TeLine2D
GCl TeCell
show/hide Instances
data TePoint Source
The type TePoint represents 2D Points.
Constructors
TePoint TeCoord2D
show/hide Instances
data TePolygon Source
The type TePolygon represents a 2D polygon . In TerraLib, a 2D polygon consists of an outer ring and a list of inner ring In Haskell, a 2D polygon consists of a list TeLinearRing
Constructors
TePolygon [TeLinearRing]
show/hide Instances
data TeLine2D Source
The type TeLine2D represents a simple 2D line, composed of 2D xy points
Constructors
TeLine2D [TeCoord2D]
show/hide Instances
data TeCell Source
Constructors
TeCell TeBox Int32 Int32
show/hide Instances
data TeBox Source
The type TeBox represents a rectangular box. Used by all geometrical representations in TerraLib Library
Constructors
TeBox Double Double Double Double
show/hide Instances
data TePointSet Source
The type TePointSet represents a sets of 2D Points.
Constructors
TePointSet [TePoint]
show/hide Instances
data TePolygonSet Source
The type TePolygonSet represents a set of 2D polygon .
Constructors
TePolygonSet [TePolygon]
show/hide Instances
data TeLineSet Source
The type TeLineSet is a set of a simple 2D line
Constructors
TeLineSet [TeLine2D]
show/hide Instances
data TeCellSet Source
Constructors
TeCellSet [TeCell]
show/hide Instances
data TeSTInstance Source
The type TeSTInstance represent an instance in a time of a spatial element
Constructors
TeSTInstance
show/hide Instances
class Topology a b whereSource
Operators that test topologival relation between two objects.
Methods
teintersects :: a -> b -> BoolSource
tetouches :: a -> b -> BoolSource
tecrosses :: a -> b -> BoolSource
tedisjoint :: a -> b -> BoolSource
tewithin :: a -> b -> BoolSource
teequals :: a -> b -> BoolSource
teoverlaps :: a -> b -> BoolSource
tecoveredby :: a -> b -> BoolSource
tecontains :: a -> b -> BoolSource
tecontainedBy :: b -> a -> BoolSource
show/hide Instances
class Overlay a whereSource
Returns the result of objects overlay
Methods
teunion :: a -> a -> [TeGeometry]Source
tedifference :: a -> a -> [TeGeometry]Source
teintersection :: a -> a -> [TeGeometry]Source
show/hide Instances
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
data TeRaster a Source
The type TeRaster represents a geographic layer
Constructors
TeRaster (Grd a)
show/hide Instances
loadRasterFile :: String -> IO (TeRaster Double)Source
class Rasters r whereSource
Methods
getValues :: r a -> [[a]]Source
setValues :: [[a]] -> r aSource
show/hide Instances
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
The Databases Module class
class Connection c whereSource
Methods
open :: c -> IO (Ptr c)Source
open a connection to a database
close :: Ptr c -> IO ()Source
close a opened connection
show/hide Instances
class Connection c => Databases a c whereSource
Methods
retrieve :: Ptr c -> String -> IO aSource
load a object list from database
store :: Ptr c -> String -> a -> IO BoolSource
save a object list a to database Foreign.Ptr.Ptr c
show/hide Instances
The Object Module class
class Pointer a whereSource
The class Pointer is a class for handling pointers to objects, ex: TePoint and TePointPtr
Methods
new :: a -> IO (Ptr a)Source
create a pointer from haskell object
fromPointer :: Ptr a -> IO aSource
create a haskell object from a pointer
delete :: Ptr a -> IO ()Source
delete a pointer from memory
show/hide Instances
class Convert a b whereSource
The class Convert permit the converts from diferents objects
Methods
to :: a -> bSource
convert from a to b
from :: b -> aSource
convert from b to a
class Element a b whereSource
Methods
getElement :: Ptr a -> Int32 -> IO bSource
show/hide Instances
class Size a whereSource
Methods
size :: Ptr a -> IO Int32Source
show/hide Instances
Produced by Haddock version 2.4.2