{-# 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 forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Ostream -> Ostream -> Bool $c/= :: Ostream -> Ostream -> Bool == :: Ostream -> Ostream -> Bool $c== :: Ostream -> Ostream -> Bool Eq, Eq 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 min :: Ostream -> Ostream -> Ostream $cmin :: Ostream -> Ostream -> Ostream max :: Ostream -> Ostream -> Ostream $cmax :: Ostream -> Ostream -> Ostream >= :: Ostream -> Ostream -> Bool $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 compare :: Ostream -> Ostream -> Ordering $ccompare :: Ostream -> Ostream -> Ordering Ord, Int -> Ostream -> ShowS [Ostream] -> ShowS Ostream -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Ostream] -> ShowS $cshowList :: [Ostream] -> ShowS show :: Ostream -> String $cshow :: Ostream -> String showsPrec :: Int -> Ostream -> ShowS $cshowsPrec :: Int -> Ostream -> ShowS Show) instance () => FPtr (Ostream) where type Raw Ostream = RawOstream get_fptr :: Ostream -> Ptr (Raw Ostream) get_fptr (Ostream Ptr RawOstream ptr) = Ptr RawOstream ptr cast_fptr_to_obj :: Ptr (Raw Ostream) -> Ostream cast_fptr_to_obj = Ptr RawOstream -> Ostream Ostream