{-# LINE 1 "src/Database/PostgreSQL/LibPQ/Oid.hsc" #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Database.PostgreSQL.LibPQ.Oid where



import Foreign.C.Types (CUInt)
import Foreign.Storable (Storable)

newtype Oid = Oid CUInt
  deriving stock (Oid -> Oid -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Oid -> Oid -> Bool
$c/= :: Oid -> Oid -> Bool
== :: Oid -> Oid -> Bool
$c== :: Oid -> Oid -> Bool
Eq, Eq Oid
Oid -> Oid -> Bool
Oid -> Oid -> Ordering
Oid -> Oid -> Oid
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 :: Oid -> Oid -> Oid
$cmin :: Oid -> Oid -> Oid
max :: Oid -> Oid -> Oid
$cmax :: Oid -> Oid -> Oid
>= :: Oid -> Oid -> Bool
$c>= :: Oid -> Oid -> Bool
> :: Oid -> Oid -> Bool
$c> :: Oid -> Oid -> Bool
<= :: Oid -> Oid -> Bool
$c<= :: Oid -> Oid -> Bool
< :: Oid -> Oid -> Bool
$c< :: Oid -> Oid -> Bool
compare :: Oid -> Oid -> Ordering
$ccompare :: Oid -> Oid -> Ordering
Ord, ReadPrec [Oid]
ReadPrec Oid
Int -> ReadS Oid
ReadS [Oid]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Oid]
$creadListPrec :: ReadPrec [Oid]
readPrec :: ReadPrec Oid
$creadPrec :: ReadPrec Oid
readList :: ReadS [Oid]
$creadList :: ReadS [Oid]
readsPrec :: Int -> ReadS Oid
$creadsPrec :: Int -> ReadS Oid
Read, Int -> Oid -> ShowS
[Oid] -> ShowS
Oid -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Oid] -> ShowS
$cshowList :: [Oid] -> ShowS
show :: Oid -> String
$cshow :: Oid -> String
showsPrec :: Int -> Oid -> ShowS
$cshowsPrec :: Int -> Oid -> ShowS
Show)
  deriving newtype (Ptr Oid -> IO Oid
Ptr Oid -> Int -> IO Oid
Ptr Oid -> Int -> Oid -> IO ()
Ptr Oid -> Oid -> IO ()
Oid -> Int
forall b. Ptr b -> Int -> IO Oid
forall b. Ptr b -> Int -> Oid -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr Oid -> Oid -> IO ()
$cpoke :: Ptr Oid -> Oid -> IO ()
peek :: Ptr Oid -> IO Oid
$cpeek :: Ptr Oid -> IO Oid
pokeByteOff :: forall b. Ptr b -> Int -> Oid -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Oid -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO Oid
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Oid
pokeElemOff :: Ptr Oid -> Int -> Oid -> IO ()
$cpokeElemOff :: Ptr Oid -> Int -> Oid -> IO ()
peekElemOff :: Ptr Oid -> Int -> IO Oid
$cpeekElemOff :: Ptr Oid -> Int -> IO Oid
alignment :: Oid -> Int
$calignment :: Oid -> Int
sizeOf :: Oid -> Int
$csizeOf :: Oid -> Int
Storable)

invalidOid :: Oid
invalidOid :: Oid
invalidOid = CUInt -> Oid
Oid (CUInt
0)
{-# LINE 16 "src/Database/PostgreSQL/LibPQ/Oid.hsc" #-}