{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TemplateHaskell, TypeFamilies, TypeSynonymInstances #-} module GDAL.OGRPolygon.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.OGRPolygon.RawType import GDAL.OGRPolygon.FFI import GDAL.OGRPolygon.Interface import GDAL.OGRPolygon.Cast 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.OGRLinearRing.RawType import GDAL.OGRLinearRing.Cast import GDAL.OGRLinearRing.Interface import GDAL.OGRCurvePolygon.RawType import GDAL.OGRCurvePolygon.Cast import GDAL.OGRCurvePolygon.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 () => IOGRPolygon (OGRPolygon) where instance () => IOGRCurvePolygon (OGRPolygon) where instance () => IOGRSurface (OGRPolygon) where instance () => IOGRGeometry (OGRPolygon) where getGeometryType = xform0 c_ogrpolygon_getgeometrytype getEnvelope = xform1 c_ogrpolygon_getenvelope intersects = xform1 c_ogrpolygon_intersects equals = xform1 c_ogrpolygon_equals disjoint = xform1 c_ogrpolygon_disjoint touches = xform1 c_ogrpolygon_touches crosses = xform1 c_ogrpolygon_crosses within = xform1 c_ogrpolygon_within contains = xform1 c_ogrpolygon_contains overlaps = xform1 c_ogrpolygon_overlaps boundary = xform0 c_ogrpolygon_boundary distance = xform1 c_ogrpolygon_distance convexHull = xform0 c_ogrpolygon_convexhull buffer = xform2 c_ogrpolygon_buffer intersection = xform1 c_ogrpolygon_intersection union = xform1 c_ogrpolygon_union unionCascaded = xform0 c_ogrpolygon_unioncascaded difference = xform1 c_ogrpolygon_difference symDifference = xform1 c_ogrpolygon_symdifference centroid = xform1 c_ogrpolygon_centroid simplify = xform1 c_ogrpolygon_simplify delaunayTriangulation = xform2 c_ogrpolygon_delaunaytriangulation polygonize = xform0 c_ogrpolygon_polygonize distance3D = xform1 c_ogrpolygon_distance3d instance () => IDeletable (OGRPolygon) where delete = xform0 c_ogrpolygon_delete oGRPolygon_getExteriorRing :: () => OGRPolygon -> IO OGRLinearRing oGRPolygon_getExteriorRing = xform0 c_ogrpolygon_ogrpolygon_getexteriorring