{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE Trustworthy #-}
module GHC.Internal.Foreign.C.ConstPtr (
    ConstPtr(..)
) where
import GHC.Internal.Base
import GHC.Internal.Ptr
import GHC.Internal.Show
type ConstPtr :: Type -> Type
type role ConstPtr phantom
newtype ConstPtr a = ConstPtr { forall a. ConstPtr a -> Ptr a
unConstPtr :: Ptr a }
    deriving (ConstPtr a -> ConstPtr a -> Bool
(ConstPtr a -> ConstPtr a -> Bool)
-> (ConstPtr a -> ConstPtr a -> Bool) -> Eq (ConstPtr a)
forall a. ConstPtr a -> ConstPtr a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. ConstPtr a -> ConstPtr a -> Bool
== :: ConstPtr a -> ConstPtr a -> Bool
$c/= :: forall a. ConstPtr a -> ConstPtr a -> Bool
/= :: ConstPtr a -> ConstPtr a -> Bool
Eq, Eq (ConstPtr a)
Eq (ConstPtr a) =>
(ConstPtr a -> ConstPtr a -> Ordering)
-> (ConstPtr a -> ConstPtr a -> Bool)
-> (ConstPtr a -> ConstPtr a -> Bool)
-> (ConstPtr a -> ConstPtr a -> Bool)
-> (ConstPtr a -> ConstPtr a -> Bool)
-> (ConstPtr a -> ConstPtr a -> ConstPtr a)
-> (ConstPtr a -> ConstPtr a -> ConstPtr a)
-> Ord (ConstPtr a)
ConstPtr a -> ConstPtr a -> Bool
ConstPtr a -> ConstPtr a -> Ordering
ConstPtr a -> ConstPtr a -> ConstPtr a
forall a. Eq (ConstPtr a)
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
forall a. ConstPtr a -> ConstPtr a -> Bool
forall a. ConstPtr a -> ConstPtr a -> Ordering
forall a. ConstPtr a -> ConstPtr a -> ConstPtr a
$ccompare :: forall a. ConstPtr a -> ConstPtr a -> Ordering
compare :: ConstPtr a -> ConstPtr a -> Ordering
$c< :: forall a. ConstPtr a -> ConstPtr a -> Bool
< :: ConstPtr a -> ConstPtr a -> Bool
$c<= :: forall a. ConstPtr a -> ConstPtr a -> Bool
<= :: ConstPtr a -> ConstPtr a -> Bool
$c> :: forall a. ConstPtr a -> ConstPtr a -> Bool
> :: ConstPtr a -> ConstPtr a -> Bool
$c>= :: forall a. ConstPtr a -> ConstPtr a -> Bool
>= :: ConstPtr a -> ConstPtr a -> Bool
$cmax :: forall a. ConstPtr a -> ConstPtr a -> ConstPtr a
max :: ConstPtr a -> ConstPtr a -> ConstPtr a
$cmin :: forall a. ConstPtr a -> ConstPtr a -> ConstPtr a
min :: ConstPtr a -> ConstPtr a -> ConstPtr a
Ord)
instance Show (ConstPtr a) where
    showsPrec :: Int -> ConstPtr a -> ShowS
showsPrec Int
d (ConstPtr Ptr a
p) = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"ConstPtr " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Ptr a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Ptr a
p