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

data RawDRect

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

instance () => FPtr (DRect) where
        type Raw DRect = RawDRect
        get_fptr :: DRect -> Ptr (Raw DRect)
get_fptr (DRect Ptr RawDRect
ptr) = Ptr (Raw DRect)
Ptr RawDRect
ptr
        cast_fptr_to_obj :: Ptr (Raw DRect) -> DRect
cast_fptr_to_obj = Ptr (Raw DRect) -> DRect
Ptr RawDRect -> DRect
DRect