{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TemplateHaskell, TypeFamilies, TypeSynonymInstances #-} module GDAL.OGRCurve.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.OGRCurve.RawType import GDAL.OGRCurve.FFI import GDAL.OGRCurve.Interface import GDAL.OGRCurve.Cast import GDAL.OGRCurve.RawType import GDAL.OGRCurve.Cast import GDAL.OGRCurve.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.OGRPoint.RawType import GDAL.OGRPoint.Cast import GDAL.OGRPoint.Interface import GDAL.OGRPointIterator.RawType import GDAL.OGRPointIterator.Cast import GDAL.OGRPointIterator.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 () => IOGRCurve (OGRCurve) where getNumPoints = xform0 c_ogrcurve_getnumpoints getPointIterator = xform0 c_ogrcurve_getpointiterator instance () => IOGRGeometry (OGRCurve) where getGeometryType = xform0 c_ogrcurve_getgeometrytype getEnvelope = xform1 c_ogrcurve_getenvelope intersects = xform1 c_ogrcurve_intersects equals = xform1 c_ogrcurve_equals disjoint = xform1 c_ogrcurve_disjoint touches = xform1 c_ogrcurve_touches crosses = xform1 c_ogrcurve_crosses within = xform1 c_ogrcurve_within contains = xform1 c_ogrcurve_contains overlaps = xform1 c_ogrcurve_overlaps boundary = xform0 c_ogrcurve_boundary distance = xform1 c_ogrcurve_distance convexHull = xform0 c_ogrcurve_convexhull buffer = xform2 c_ogrcurve_buffer intersection = xform1 c_ogrcurve_intersection union = xform1 c_ogrcurve_union unionCascaded = xform0 c_ogrcurve_unioncascaded difference = xform1 c_ogrcurve_difference symDifference = xform1 c_ogrcurve_symdifference centroid = xform1 c_ogrcurve_centroid simplify = xform1 c_ogrcurve_simplify delaunayTriangulation = xform2 c_ogrcurve_delaunaytriangulation polygonize = xform0 c_ogrcurve_polygonize distance3D = xform1 c_ogrcurve_distance3d instance () => IDeletable (OGRCurve) where delete = xform0 c_ogrcurve_delete