{-# LANGUAGE ForeignFunctionInterface, TypeFamilies,
  MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances,
  EmptyDataDecls, ExistentialQuantification, ScopedTypeVariables #-}
module OGDF.EdgeElement.RawType where
import Foreign.Ptr
import FFICXX.Runtime.Cast

data RawEdgeElement

newtype EdgeElement = EdgeElement (Ptr RawEdgeElement)
                        deriving (EdgeElement -> EdgeElement -> Bool
(EdgeElement -> EdgeElement -> Bool)
-> (EdgeElement -> EdgeElement -> Bool) -> Eq EdgeElement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EdgeElement -> EdgeElement -> Bool
== :: EdgeElement -> EdgeElement -> Bool
$c/= :: EdgeElement -> EdgeElement -> Bool
/= :: EdgeElement -> EdgeElement -> Bool
Eq, Eq EdgeElement
Eq EdgeElement
-> (EdgeElement -> EdgeElement -> Ordering)
-> (EdgeElement -> EdgeElement -> Bool)
-> (EdgeElement -> EdgeElement -> Bool)
-> (EdgeElement -> EdgeElement -> Bool)
-> (EdgeElement -> EdgeElement -> Bool)
-> (EdgeElement -> EdgeElement -> EdgeElement)
-> (EdgeElement -> EdgeElement -> EdgeElement)
-> Ord EdgeElement
EdgeElement -> EdgeElement -> Bool
EdgeElement -> EdgeElement -> Ordering
EdgeElement -> EdgeElement -> EdgeElement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: EdgeElement -> EdgeElement -> Ordering
compare :: EdgeElement -> EdgeElement -> Ordering
$c< :: EdgeElement -> EdgeElement -> Bool
< :: EdgeElement -> EdgeElement -> Bool
$c<= :: EdgeElement -> EdgeElement -> Bool
<= :: EdgeElement -> EdgeElement -> Bool
$c> :: EdgeElement -> EdgeElement -> Bool
> :: EdgeElement -> EdgeElement -> Bool
$c>= :: EdgeElement -> EdgeElement -> Bool
>= :: EdgeElement -> EdgeElement -> Bool
$cmax :: EdgeElement -> EdgeElement -> EdgeElement
max :: EdgeElement -> EdgeElement -> EdgeElement
$cmin :: EdgeElement -> EdgeElement -> EdgeElement
min :: EdgeElement -> EdgeElement -> EdgeElement
Ord, Int -> EdgeElement -> ShowS
[EdgeElement] -> ShowS
EdgeElement -> String
(Int -> EdgeElement -> ShowS)
-> (EdgeElement -> String)
-> ([EdgeElement] -> ShowS)
-> Show EdgeElement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EdgeElement -> ShowS
showsPrec :: Int -> EdgeElement -> ShowS
$cshow :: EdgeElement -> String
show :: EdgeElement -> String
$cshowList :: [EdgeElement] -> ShowS
showList :: [EdgeElement] -> ShowS
Show)

instance () => FPtr (EdgeElement) where
        type Raw EdgeElement = RawEdgeElement
        get_fptr :: EdgeElement -> Ptr (Raw EdgeElement)
get_fptr (EdgeElement Ptr RawEdgeElement
ptr) = Ptr (Raw EdgeElement)
Ptr RawEdgeElement
ptr
        cast_fptr_to_obj :: Ptr (Raw EdgeElement) -> EdgeElement
cast_fptr_to_obj = Ptr (Raw EdgeElement) -> EdgeElement
Ptr RawEdgeElement -> EdgeElement
EdgeElement