{-# LANGUAGE FlexibleInstances, FlexibleContexts, TypeFamilies, 
             MultiParamTypeClasses, OverlappingInstances, IncoherentInstances #-}

module HROOT.Hist.TGraphBentErrors.Cast where


import Foreign.Ptr
import Foreign.ForeignPtr (castForeignPtr, newForeignPtr_)
import Foreign.ForeignPtr.Unsafe
import FFICXX.Runtime.Cast
import System.IO.Unsafe

import HROOT.Hist.TGraphBentErrors.RawType
import HROOT.Hist.TGraphBentErrors.Interface

instance (ITGraphBentErrors a, FPtr a) => Castable a (Ptr RawTGraphBentErrors) where
  cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
  uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_ 

instance Castable TGraphBentErrors (Ptr RawTGraphBentErrors) where
  cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
  uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_