{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TemplateHaskell, TypeFamilies, TypeSynonymInstances #-} module GDAL.OGRLineString.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.OGRLineString.RawType import GDAL.OGRLineString.FFI import GDAL.OGRLineString.Interface import GDAL.OGRLineString.Cast import GDAL.OGRLineString.RawType import GDAL.OGRLineString.Cast import GDAL.OGRLineString.Interface import GDAL.OGRPointIterator.RawType import GDAL.OGRPointIterator.Cast import GDAL.OGRPointIterator.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.OGRSimpleCurve.RawType import GDAL.OGRSimpleCurve.Cast import GDAL.OGRSimpleCurve.Interface import GDAL.OGRCurve.RawType import GDAL.OGRCurve.Cast import GDAL.OGRCurve.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 () => IOGRLineString (OGRLineString) where instance () => IOGRSimpleCurve (OGRLineString) where instance () => IOGRCurve (OGRLineString) where getNumPoints = xform0 c_ogrlinestring_getnumpoints getPointIterator = xform0 c_ogrlinestring_getpointiterator instance () => IOGRGeometry (OGRLineString) where getGeometryType = xform0 c_ogrlinestring_getgeometrytype getEnvelope = xform1 c_ogrlinestring_getenvelope intersects = xform1 c_ogrlinestring_intersects equals = xform1 c_ogrlinestring_equals disjoint = xform1 c_ogrlinestring_disjoint touches = xform1 c_ogrlinestring_touches crosses = xform1 c_ogrlinestring_crosses within = xform1 c_ogrlinestring_within contains = xform1 c_ogrlinestring_contains overlaps = xform1 c_ogrlinestring_overlaps boundary = xform0 c_ogrlinestring_boundary distance = xform1 c_ogrlinestring_distance convexHull = xform0 c_ogrlinestring_convexhull buffer = xform2 c_ogrlinestring_buffer intersection = xform1 c_ogrlinestring_intersection union = xform1 c_ogrlinestring_union unionCascaded = xform0 c_ogrlinestring_unioncascaded difference = xform1 c_ogrlinestring_difference symDifference = xform1 c_ogrlinestring_symdifference centroid = xform1 c_ogrlinestring_centroid simplify = xform1 c_ogrlinestring_simplify delaunayTriangulation = xform2 c_ogrlinestring_delaunaytriangulation polygonize = xform0 c_ogrlinestring_polygonize distance3D = xform1 c_ogrlinestring_distance3d instance () => IDeletable (OGRLineString) where delete = xform0 c_ogrlinestring_delete