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

data RawNodeElement

newtype NodeElement = NodeElement (Ptr RawNodeElement)
                        deriving (NodeElement -> NodeElement -> Bool
(NodeElement -> NodeElement -> Bool)
-> (NodeElement -> NodeElement -> Bool) -> Eq NodeElement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeElement -> NodeElement -> Bool
== :: NodeElement -> NodeElement -> Bool
$c/= :: NodeElement -> NodeElement -> Bool
/= :: NodeElement -> NodeElement -> Bool
Eq, Eq NodeElement
Eq NodeElement
-> (NodeElement -> NodeElement -> Ordering)
-> (NodeElement -> NodeElement -> Bool)
-> (NodeElement -> NodeElement -> Bool)
-> (NodeElement -> NodeElement -> Bool)
-> (NodeElement -> NodeElement -> Bool)
-> (NodeElement -> NodeElement -> NodeElement)
-> (NodeElement -> NodeElement -> NodeElement)
-> Ord NodeElement
NodeElement -> NodeElement -> Bool
NodeElement -> NodeElement -> Ordering
NodeElement -> NodeElement -> NodeElement
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 :: NodeElement -> NodeElement -> Ordering
compare :: NodeElement -> NodeElement -> Ordering
$c< :: NodeElement -> NodeElement -> Bool
< :: NodeElement -> NodeElement -> Bool
$c<= :: NodeElement -> NodeElement -> Bool
<= :: NodeElement -> NodeElement -> Bool
$c> :: NodeElement -> NodeElement -> Bool
> :: NodeElement -> NodeElement -> Bool
$c>= :: NodeElement -> NodeElement -> Bool
>= :: NodeElement -> NodeElement -> Bool
$cmax :: NodeElement -> NodeElement -> NodeElement
max :: NodeElement -> NodeElement -> NodeElement
$cmin :: NodeElement -> NodeElement -> NodeElement
min :: NodeElement -> NodeElement -> NodeElement
Ord, Int -> NodeElement -> ShowS
[NodeElement] -> ShowS
NodeElement -> String
(Int -> NodeElement -> ShowS)
-> (NodeElement -> String)
-> ([NodeElement] -> ShowS)
-> Show NodeElement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NodeElement -> ShowS
showsPrec :: Int -> NodeElement -> ShowS
$cshow :: NodeElement -> String
show :: NodeElement -> String
$cshowList :: [NodeElement] -> ShowS
showList :: [NodeElement] -> ShowS
Show)

instance () => FPtr (NodeElement) where
        type Raw NodeElement = RawNodeElement
        get_fptr :: NodeElement -> Ptr (Raw NodeElement)
get_fptr (NodeElement Ptr RawNodeElement
ptr) = Ptr (Raw NodeElement)
Ptr RawNodeElement
ptr
        cast_fptr_to_obj :: Ptr (Raw NodeElement) -> NodeElement
cast_fptr_to_obj = Ptr (Raw NodeElement) -> NodeElement
Ptr RawNodeElement -> NodeElement
NodeElement