{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TemplateHaskell, TypeFamilies, TypeSynonymInstances #-} module GDAL.OGRGeometryCollection.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.OGRGeometryCollection.RawType import GDAL.OGRGeometryCollection.FFI import GDAL.OGRGeometryCollection.Interface import GDAL.OGRGeometryCollection.Cast import GDAL.OGRGeometryCollection.RawType import GDAL.OGRGeometryCollection.Cast import GDAL.OGRGeometryCollection.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.OGRGeometry.RawType import GDAL.OGRGeometry.Cast import GDAL.OGRGeometry.Interface import STD.Deletable.RawType import STD.Deletable.Cast import STD.Deletable.Interface instance () => IOGRGeometryCollection (OGRGeometryCollection) where instance () => IOGRGeometry (OGRGeometryCollection) where getGeometryType = xform0 c_ogrgeometrycollection_getgeometrytype getEnvelope = xform1 c_ogrgeometrycollection_getenvelope intersects = xform1 c_ogrgeometrycollection_intersects equals = xform1 c_ogrgeometrycollection_equals disjoint = xform1 c_ogrgeometrycollection_disjoint touches = xform1 c_ogrgeometrycollection_touches crosses = xform1 c_ogrgeometrycollection_crosses within = xform1 c_ogrgeometrycollection_within contains = xform1 c_ogrgeometrycollection_contains overlaps = xform1 c_ogrgeometrycollection_overlaps boundary = xform0 c_ogrgeometrycollection_boundary distance = xform1 c_ogrgeometrycollection_distance convexHull = xform0 c_ogrgeometrycollection_convexhull buffer = xform2 c_ogrgeometrycollection_buffer intersection = xform1 c_ogrgeometrycollection_intersection union = xform1 c_ogrgeometrycollection_union unionCascaded = xform0 c_ogrgeometrycollection_unioncascaded difference = xform1 c_ogrgeometrycollection_difference symDifference = xform1 c_ogrgeometrycollection_symdifference centroid = xform1 c_ogrgeometrycollection_centroid simplify = xform1 c_ogrgeometrycollection_simplify delaunayTriangulation = xform2 c_ogrgeometrycollection_delaunaytriangulation polygonize = xform0 c_ogrgeometrycollection_polygonize distance3D = xform1 c_ogrgeometrycollection_distance3d instance () => IDeletable (OGRGeometryCollection) where delete = xform0 c_ogrgeometrycollection_delete oGRGeometryCollection_getNumGeometries :: () => OGRGeometryCollection -> IO CInt oGRGeometryCollection_getNumGeometries = xform0 c_ogrgeometrycollection_ogrgeometrycollection_getnumgeometries oGRGeometryCollection_getGeometryRef :: () => OGRGeometryCollection -> CInt -> IO OGRGeometry oGRGeometryCollection_getGeometryRef = xform1 c_ogrgeometrycollection_ogrgeometrycollection_getgeometryref