{-# LANGUAGE FlexibleInstances, FlexibleContexts, TypeFamilies,
  MultiParamTypeClasses, OverlappingInstances, IncoherentInstances
  #-}
module GDAL.OGRFeature.Cast where
import Foreign.Ptr
import FFICXX.Runtime.Cast
import System.IO.Unsafe
import GDAL.OGRFeature.RawType
import GDAL.OGRFeature.Interface

instance (IOGRFeature a, FPtr a) =>
         Castable (a) (Ptr RawOGRFeature)
         where
        cast :: forall r. a -> (Ptr RawOGRFeature -> IO r) -> IO r
cast a
x Ptr RawOGRFeature -> IO r
f = Ptr RawOGRFeature -> IO r
f (Ptr (Raw a) -> Ptr RawOGRFeature
forall a b. Ptr a -> Ptr b
castPtr (a -> Ptr (Raw a)
forall a. FPtr a => a -> Ptr (Raw a)
get_fptr a
x))
        uncast :: forall r. Ptr RawOGRFeature -> (a -> IO r) -> IO r
uncast Ptr RawOGRFeature
x a -> IO r
f = a -> IO r
f (Ptr (Raw a) -> a
forall a. FPtr a => Ptr (Raw a) -> a
cast_fptr_to_obj (Ptr RawOGRFeature -> Ptr (Raw a)
forall a b. Ptr a -> Ptr b
castPtr Ptr RawOGRFeature
x))

instance () => Castable (OGRFeature) (Ptr RawOGRFeature) where
        cast :: forall r. OGRFeature -> (Ptr RawOGRFeature -> IO r) -> IO r
cast OGRFeature
x Ptr RawOGRFeature -> IO r
f = Ptr RawOGRFeature -> IO r
f (Ptr RawOGRFeature -> Ptr RawOGRFeature
forall a b. Ptr a -> Ptr b
castPtr (OGRFeature -> Ptr (Raw OGRFeature)
forall a. FPtr a => a -> Ptr (Raw a)
get_fptr OGRFeature
x))
        uncast :: forall r. Ptr RawOGRFeature -> (OGRFeature -> IO r) -> IO r
uncast Ptr RawOGRFeature
x OGRFeature -> IO r
f = OGRFeature -> IO r
f (Ptr (Raw OGRFeature) -> OGRFeature
forall a. FPtr a => Ptr (Raw a) -> a
cast_fptr_to_obj (Ptr RawOGRFeature -> Ptr RawOGRFeature
forall a b. Ptr a -> Ptr b
castPtr Ptr RawOGRFeature
x))