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

data RawTShape

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

instance () => FPtr (TShape) where
        type Raw TShape = RawTShape
        get_fptr :: TShape -> Ptr (Raw TShape)
get_fptr (TShape Ptr RawTShape
ptr) = Ptr (Raw TShape)
Ptr RawTShape
ptr
        cast_fptr_to_obj :: Ptr (Raw TShape) -> TShape
cast_fptr_to_obj = Ptr (Raw TShape) -> TShape
Ptr RawTShape -> TShape
TShape