{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TemplateHaskell, TypeFamilies, TypeSynonymInstances #-} module GDAL.OGRCurvePolygon.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.OGRCurvePolygon.RawType import GDAL.OGRCurvePolygon.FFI import GDAL.OGRCurvePolygon.Interface import GDAL.OGRCurvePolygon.Cast import GDAL.OGRCurvePolygon.RawType import GDAL.OGRCurvePolygon.Cast import GDAL.OGRCurvePolygon.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.OGRSurface.RawType import GDAL.OGRSurface.Cast import GDAL.OGRSurface.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 () => IOGRCurvePolygon (OGRCurvePolygon) where instance () => IOGRSurface (OGRCurvePolygon) where instance () => IOGRGeometry (OGRCurvePolygon) where getGeometryType = xform0 c_ogrcurvepolygon_getgeometrytype getEnvelope = xform1 c_ogrcurvepolygon_getenvelope intersects = xform1 c_ogrcurvepolygon_intersects equals = xform1 c_ogrcurvepolygon_equals disjoint = xform1 c_ogrcurvepolygon_disjoint touches = xform1 c_ogrcurvepolygon_touches crosses = xform1 c_ogrcurvepolygon_crosses within = xform1 c_ogrcurvepolygon_within contains = xform1 c_ogrcurvepolygon_contains overlaps = xform1 c_ogrcurvepolygon_overlaps boundary = xform0 c_ogrcurvepolygon_boundary distance = xform1 c_ogrcurvepolygon_distance convexHull = xform0 c_ogrcurvepolygon_convexhull buffer = xform2 c_ogrcurvepolygon_buffer intersection = xform1 c_ogrcurvepolygon_intersection union = xform1 c_ogrcurvepolygon_union unionCascaded = xform0 c_ogrcurvepolygon_unioncascaded difference = xform1 c_ogrcurvepolygon_difference symDifference = xform1 c_ogrcurvepolygon_symdifference centroid = xform1 c_ogrcurvepolygon_centroid simplify = xform1 c_ogrcurvepolygon_simplify delaunayTriangulation = xform2 c_ogrcurvepolygon_delaunaytriangulation polygonize = xform0 c_ogrcurvepolygon_polygonize distance3D = xform1 c_ogrcurvepolygon_distance3d instance () => IDeletable (OGRCurvePolygon) where delete = xform0 c_ogrcurvepolygon_delete