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

data RawOstream

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

instance () => FPtr (Ostream) where
        type Raw Ostream = RawOstream
        get_fptr :: Ostream -> Ptr (Raw Ostream)
get_fptr (Ostream Ptr RawOstream
ptr) = Ptr (Raw Ostream)
Ptr RawOstream
ptr
        cast_fptr_to_obj :: Ptr (Raw Ostream) -> Ostream
cast_fptr_to_obj = Ptr (Raw Ostream) -> Ostream
Ptr RawOstream -> Ostream
Ostream