{-# LANGUAGE FlexibleInstances, FlexibleContexts, TypeFamilies, MultiParamTypeClasses, OverlappingInstances, IncoherentInstances #-} module OGDF.DRect.Cast where import Foreign.Ptr import FFICXX.Runtime.Cast import System.IO.Unsafe import OGDF.DRect.RawType import OGDF.DRect.Interface instance (IDRect a, FPtr a) => Castable (a) (Ptr RawDRect) where cast :: forall r. a -> (Ptr RawDRect -> IO r) -> IO r cast a x Ptr RawDRect -> IO r f = Ptr RawDRect -> IO r f (Ptr (Raw a) -> Ptr RawDRect 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 RawDRect -> (a -> IO r) -> IO r uncast Ptr RawDRect 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 RawDRect -> Ptr (Raw a) forall a b. Ptr a -> Ptr b castPtr Ptr RawDRect x)) instance () => Castable (DRect) (Ptr RawDRect) where cast :: forall r. DRect -> (Ptr RawDRect -> IO r) -> IO r cast DRect x Ptr RawDRect -> IO r f = Ptr RawDRect -> IO r f (Ptr RawDRect -> Ptr RawDRect forall a b. Ptr a -> Ptr b castPtr (DRect -> Ptr (Raw DRect) forall a. FPtr a => a -> Ptr (Raw a) get_fptr DRect x)) uncast :: forall r. Ptr RawDRect -> (DRect -> IO r) -> IO r uncast Ptr RawDRect x DRect -> IO r f = DRect -> IO r f (Ptr (Raw DRect) -> DRect forall a. FPtr a => Ptr (Raw a) -> a cast_fptr_to_obj (Ptr RawDRect -> Ptr RawDRect forall a b. Ptr a -> Ptr b castPtr Ptr RawDRect x))