{-# LANGUAGE EmptyDataDecls, ExistentialQuantification, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies, TypeSynonymInstances #-} module GDAL.OGRGeometry.Interface where import Data.Word import Data.Int import Foreign.C import Foreign.Ptr import FFICXX.Runtime.Cast import GDAL.OGRGeometry.RawType import STD.Deletable.Interface import GDAL.OGREnvelope.Interface import {-# SOURCE #-} GDAL.OGRPoint.Interface class (IDeletable a) => IOGRGeometry a where getGeometryType :: () => a -> IO CUInt getEnvelope :: (IOGREnvelope c0, FPtr c0) => a -> c0 -> IO () intersects :: (IOGRGeometry c0, FPtr c0) => a -> c0 -> IO CBool equals :: (IOGRGeometry c0, FPtr c0) => a -> c0 -> IO CBool disjoint :: (IOGRGeometry c0, FPtr c0) => a -> c0 -> IO CBool touches :: (IOGRGeometry c0, FPtr c0) => a -> c0 -> IO CBool crosses :: (IOGRGeometry c0, FPtr c0) => a -> c0 -> IO CBool within :: (IOGRGeometry c0, FPtr c0) => a -> c0 -> IO CBool contains :: (IOGRGeometry c0, FPtr c0) => a -> c0 -> IO CBool overlaps :: (IOGRGeometry c0, FPtr c0) => a -> c0 -> IO CBool boundary :: () => a -> IO OGRGeometry distance :: (IOGRGeometry c0, FPtr c0) => a -> c0 -> IO CDouble convexHull :: () => a -> IO OGRGeometry buffer :: () => a -> CDouble -> CInt -> IO OGRGeometry intersection :: (IOGRGeometry c0, FPtr c0) => a -> c0 -> IO OGRGeometry union :: (IOGRGeometry c0, FPtr c0) => a -> c0 -> IO OGRGeometry unionCascaded :: () => a -> IO OGRGeometry difference :: (IOGRGeometry c0, FPtr c0) => a -> c0 -> IO OGRGeometry symDifference :: (IOGRGeometry c0, FPtr c0) => a -> c0 -> IO OGRGeometry centroid :: (IOGRPoint c0, FPtr c0) => a -> c0 -> IO CInt simplify :: () => a -> CDouble -> IO OGRGeometry delaunayTriangulation :: () => a -> CDouble -> CInt -> IO OGRGeometry polygonize :: () => a -> IO OGRGeometry distance3D :: (IOGRGeometry c0, FPtr c0) => a -> c0 -> IO CDouble upcastOGRGeometry :: forall a . (FPtr a, IOGRGeometry a) => a -> OGRGeometry upcastOGRGeometry h = let fh = get_fptr h fh2 :: Ptr RawOGRGeometry = castPtr fh in cast_fptr_to_obj fh2 downcastOGRGeometry :: forall a . (FPtr a, IOGRGeometry a) => OGRGeometry -> a downcastOGRGeometry h = let fh = get_fptr h fh2 = castPtr fh in cast_fptr_to_obj fh2