{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TemplateHaskell, TypeFamilies, TypeSynonymInstances #-} module GDAL.OGRPoint.Implementation where import Data.Monoid import Data.Word import Data.Int import Foreign.C import Foreign.Ptr import Language.Haskell.TH import Language.Haskell.TH.Syntax import System.IO.Unsafe import FFICXX.Runtime.Cast import FFICXX.Runtime.CodeGen.Cxx import FFICXX.Runtime.TH import GDAL.OGRPoint.RawType import GDAL.OGRPoint.FFI import GDAL.OGRPoint.Interface import GDAL.OGRPoint.Cast import GDAL.OGRPoint.RawType import GDAL.OGRPoint.Cast import GDAL.OGRPoint.Interface import GDAL.OGRPolygon.RawType import GDAL.OGRPolygon.Cast import GDAL.OGRPolygon.Interface import GDAL.OGRMultiPolygon.RawType import GDAL.OGRMultiPolygon.Cast import GDAL.OGRMultiPolygon.Interface import GDAL.OGREnvelope.RawType import GDAL.OGREnvelope.Cast import GDAL.OGREnvelope.Interface import GDAL.OGRGeometry.RawType import GDAL.OGRGeometry.Cast import GDAL.OGRGeometry.Interface import STD.Deletable.RawType import STD.Deletable.Cast import STD.Deletable.Interface instance () => IOGRPoint (OGRPoint) where instance () => IOGRGeometry (OGRPoint) where getGeometryType = xform0 c_ogrpoint_getgeometrytype getEnvelope = xform1 c_ogrpoint_getenvelope intersects = xform1 c_ogrpoint_intersects equals = xform1 c_ogrpoint_equals disjoint = xform1 c_ogrpoint_disjoint touches = xform1 c_ogrpoint_touches crosses = xform1 c_ogrpoint_crosses within = xform1 c_ogrpoint_within contains = xform1 c_ogrpoint_contains overlaps = xform1 c_ogrpoint_overlaps boundary = xform0 c_ogrpoint_boundary distance = xform1 c_ogrpoint_distance convexHull = xform0 c_ogrpoint_convexhull buffer = xform2 c_ogrpoint_buffer intersection = xform1 c_ogrpoint_intersection union = xform1 c_ogrpoint_union unionCascaded = xform0 c_ogrpoint_unioncascaded difference = xform1 c_ogrpoint_difference symDifference = xform1 c_ogrpoint_symdifference centroid = xform1 c_ogrpoint_centroid simplify = xform1 c_ogrpoint_simplify delaunayTriangulation = xform2 c_ogrpoint_delaunaytriangulation polygonize = xform0 c_ogrpoint_polygonize distance3D = xform1 c_ogrpoint_distance3d instance () => IDeletable (OGRPoint) where delete = xform0 c_ogrpoint_delete newOGRPoint :: () => IO OGRPoint newOGRPoint = xformnull c_ogrpoint_newogrpoint newOGRPoint2 :: () => CDouble -> CDouble -> IO OGRPoint newOGRPoint2 = xform1 c_ogrpoint_newogrpoint2 newOGRPoint3 :: () => CDouble -> CDouble -> CDouble -> IO OGRPoint newOGRPoint3 = xform2 c_ogrpoint_newogrpoint3 newOGRPoint4 :: () => CDouble -> CDouble -> CDouble -> CDouble -> IO OGRPoint newOGRPoint4 = xform3 c_ogrpoint_newogrpoint4 oGRPoint_getX :: () => OGRPoint -> IO CDouble oGRPoint_getX = xform0 c_ogrpoint_ogrpoint_getx oGRPoint_getY :: () => OGRPoint -> IO CDouble oGRPoint_getY = xform0 c_ogrpoint_ogrpoint_gety oGRPoint_getZ :: () => OGRPoint -> IO CDouble oGRPoint_getZ = xform0 c_ogrpoint_ogrpoint_getz oGRPoint_getM :: () => OGRPoint -> IO CDouble oGRPoint_getM = xform0 c_ogrpoint_ogrpoint_getm oGRPoint_setX :: () => OGRPoint -> CDouble -> IO () oGRPoint_setX = xform1 c_ogrpoint_ogrpoint_setx oGRPoint_setY :: () => OGRPoint -> CDouble -> IO () oGRPoint_setY = xform1 c_ogrpoint_ogrpoint_sety oGRPoint_setZ :: () => OGRPoint -> CDouble -> IO () oGRPoint_setZ = xform1 c_ogrpoint_ogrpoint_setz oGRPoint_setM :: () => OGRPoint -> CDouble -> IO () oGRPoint_setM = xform1 c_ogrpoint_ogrpoint_setm