unix-compat-0.7.2: Portable POSIX-compatibility layer.
Safe HaskellNone
LanguageHaskell2010

System.PosixCompat.Types

Description

This module re-exports the types from System.Posix.Types on all platforms.

On Windows UserID, GroupID and LinkCount are missing, so they are redefined by this module.

Documentation

type DeviceID = CDev #

newtype Fd #

Constructors

Fd CInt 

Instances

Instances details
Bits Fd 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(.&.) :: Fd -> Fd -> Fd

(.|.) :: Fd -> Fd -> Fd

xor :: Fd -> Fd -> Fd

complement :: Fd -> Fd

shift :: Fd -> Int -> Fd

rotate :: Fd -> Int -> Fd

zeroBits :: Fd

bit :: Int -> Fd

setBit :: Fd -> Int -> Fd

clearBit :: Fd -> Int -> Fd

complementBit :: Fd -> Int -> Fd

testBit :: Fd -> Int -> Bool

bitSizeMaybe :: Fd -> Maybe Int

bitSize :: Fd -> Int

isSigned :: Fd -> Bool

shiftL :: Fd -> Int -> Fd

unsafeShiftL :: Fd -> Int -> Fd

shiftR :: Fd -> Int -> Fd

unsafeShiftR :: Fd -> Int -> Fd

rotateL :: Fd -> Int -> Fd

rotateR :: Fd -> Int -> Fd

popCount :: Fd -> Int

FiniteBits Fd 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

finiteBitSize :: Fd -> Int

countLeadingZeros :: Fd -> Int

countTrailingZeros :: Fd -> Int

Bounded Fd 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

minBound :: Fd

maxBound :: Fd

Enum Fd 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

succ :: Fd -> Fd

pred :: Fd -> Fd

toEnum :: Int -> Fd

fromEnum :: Fd -> Int

enumFrom :: Fd -> [Fd]

enumFromThen :: Fd -> Fd -> [Fd]

enumFromTo :: Fd -> Fd -> [Fd]

enumFromThenTo :: Fd -> Fd -> Fd -> [Fd]

Storable Fd 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: Fd -> Int

alignment :: Fd -> Int

peekElemOff :: Ptr Fd -> Int -> IO Fd

pokeElemOff :: Ptr Fd -> Int -> Fd -> IO ()

peekByteOff :: Ptr b -> Int -> IO Fd

pokeByteOff :: Ptr b -> Int -> Fd -> IO ()

peek :: Ptr Fd -> IO Fd

poke :: Ptr Fd -> Fd -> IO ()

Ix Fd 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

range :: (Fd, Fd) -> [Fd]

index :: (Fd, Fd) -> Fd -> Int

unsafeIndex :: (Fd, Fd) -> Fd -> Int

inRange :: (Fd, Fd) -> Fd -> Bool

rangeSize :: (Fd, Fd) -> Int

unsafeRangeSize :: (Fd, Fd) -> Int

Num Fd 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(+) :: Fd -> Fd -> Fd

(-) :: Fd -> Fd -> Fd

(*) :: Fd -> Fd -> Fd

negate :: Fd -> Fd

abs :: Fd -> Fd

signum :: Fd -> Fd

fromInteger :: Integer -> Fd

Read Fd 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS Fd

readList :: ReadS [Fd]

readPrec :: ReadPrec Fd

readListPrec :: ReadPrec [Fd]

Integral Fd 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

quot :: Fd -> Fd -> Fd

rem :: Fd -> Fd -> Fd

div :: Fd -> Fd -> Fd

mod :: Fd -> Fd -> Fd

quotRem :: Fd -> Fd -> (Fd, Fd)

divMod :: Fd -> Fd -> (Fd, Fd)

toInteger :: Fd -> Integer

Real Fd 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: Fd -> Rational

Show Fd 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> Fd -> ShowS

show :: Fd -> String

showList :: [Fd] -> ShowS

Eq Fd 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: Fd -> Fd -> Bool

(/=) :: Fd -> Fd -> Bool

Ord Fd 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: Fd -> Fd -> Ordering

(<) :: Fd -> Fd -> Bool

(<=) :: Fd -> Fd -> Bool

(>) :: Fd -> Fd -> Bool

(>=) :: Fd -> Fd -> Bool

max :: Fd -> Fd -> Fd

min :: Fd -> Fd -> Fd

type Limit = CLong #

type EpochTime = CTime #

type UserID = CUid #

type GroupID = CGid #

newtype CBlkSize #

Constructors

CBlkSize Int32 

Instances

Instances details
Bits CBlkSize 
Instance details

Defined in GHC.Internal.System.Posix.Types

FiniteBits CBlkSize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Bounded CBlkSize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum CBlkSize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Storable CBlkSize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CBlkSize -> Int

alignment :: CBlkSize -> Int

peekElemOff :: Ptr CBlkSize -> Int -> IO CBlkSize

pokeElemOff :: Ptr CBlkSize -> Int -> CBlkSize -> IO ()

peekByteOff :: Ptr b -> Int -> IO CBlkSize

pokeByteOff :: Ptr b -> Int -> CBlkSize -> IO ()

peek :: Ptr CBlkSize -> IO CBlkSize

poke :: Ptr CBlkSize -> CBlkSize -> IO ()

Ix CBlkSize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CBlkSize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Read CBlkSize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CBlkSize

readList :: ReadS [CBlkSize]

readPrec :: ReadPrec CBlkSize

readListPrec :: ReadPrec [CBlkSize]

Integral CBlkSize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CBlkSize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CBlkSize -> Rational

Show CBlkSize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CBlkSize -> ShowS

show :: CBlkSize -> String

showList :: [CBlkSize] -> ShowS

Eq CBlkSize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CBlkSize -> CBlkSize -> Bool

(/=) :: CBlkSize -> CBlkSize -> Bool

Ord CBlkSize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CBlkSize -> CBlkSize -> Ordering

(<) :: CBlkSize -> CBlkSize -> Bool

(<=) :: CBlkSize -> CBlkSize -> Bool

(>) :: CBlkSize -> CBlkSize -> Bool

(>=) :: CBlkSize -> CBlkSize -> Bool

max :: CBlkSize -> CBlkSize -> CBlkSize

min :: CBlkSize -> CBlkSize -> CBlkSize

type FileID = CIno #

newtype CNlink #

Constructors

CNlink Word16 

Instances

newtype CBlkCnt #

Constructors

CBlkCnt Int64 

Instances

Instances details
Bits CBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(.&.) :: CBlkCnt -> CBlkCnt -> CBlkCnt

(.|.) :: CBlkCnt -> CBlkCnt -> CBlkCnt

xor :: CBlkCnt -> CBlkCnt -> CBlkCnt

complement :: CBlkCnt -> CBlkCnt

shift :: CBlkCnt -> Int -> CBlkCnt

rotate :: CBlkCnt -> Int -> CBlkCnt

zeroBits :: CBlkCnt

bit :: Int -> CBlkCnt

setBit :: CBlkCnt -> Int -> CBlkCnt

clearBit :: CBlkCnt -> Int -> CBlkCnt

complementBit :: CBlkCnt -> Int -> CBlkCnt

testBit :: CBlkCnt -> Int -> Bool

bitSizeMaybe :: CBlkCnt -> Maybe Int

bitSize :: CBlkCnt -> Int

isSigned :: CBlkCnt -> Bool

shiftL :: CBlkCnt -> Int -> CBlkCnt

unsafeShiftL :: CBlkCnt -> Int -> CBlkCnt

shiftR :: CBlkCnt -> Int -> CBlkCnt

unsafeShiftR :: CBlkCnt -> Int -> CBlkCnt

rotateL :: CBlkCnt -> Int -> CBlkCnt

rotateR :: CBlkCnt -> Int -> CBlkCnt

popCount :: CBlkCnt -> Int

FiniteBits CBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Bounded CBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum CBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Storable CBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CBlkCnt -> Int

alignment :: CBlkCnt -> Int

peekElemOff :: Ptr CBlkCnt -> Int -> IO CBlkCnt

pokeElemOff :: Ptr CBlkCnt -> Int -> CBlkCnt -> IO ()

peekByteOff :: Ptr b -> Int -> IO CBlkCnt

pokeByteOff :: Ptr b -> Int -> CBlkCnt -> IO ()

peek :: Ptr CBlkCnt -> IO CBlkCnt

poke :: Ptr CBlkCnt -> CBlkCnt -> IO ()

Ix CBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Read CBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CBlkCnt

readList :: ReadS [CBlkCnt]

readPrec :: ReadPrec CBlkCnt

readListPrec :: ReadPrec [CBlkCnt]

Integral CBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CBlkCnt -> Rational

Show CBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CBlkCnt -> ShowS

show :: CBlkCnt -> String

showList :: [CBlkCnt] -> ShowS

Eq CBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CBlkCnt -> CBlkCnt -> Bool

(/=) :: CBlkCnt -> CBlkCnt -> Bool

Ord CBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CBlkCnt -> CBlkCnt -> Ordering

(<) :: CBlkCnt -> CBlkCnt -> Bool

(<=) :: CBlkCnt -> CBlkCnt -> Bool

(>) :: CBlkCnt -> CBlkCnt -> Bool

(>=) :: CBlkCnt -> CBlkCnt -> Bool

max :: CBlkCnt -> CBlkCnt -> CBlkCnt

min :: CBlkCnt -> CBlkCnt -> CBlkCnt

type ClockTick = CClock #

newtype CPid #

Constructors

CPid Int32 

Instances

Instances details
Bits CPid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(.&.) :: CPid -> CPid -> CPid

(.|.) :: CPid -> CPid -> CPid

xor :: CPid -> CPid -> CPid

complement :: CPid -> CPid

shift :: CPid -> Int -> CPid

rotate :: CPid -> Int -> CPid

zeroBits :: CPid

bit :: Int -> CPid

setBit :: CPid -> Int -> CPid

clearBit :: CPid -> Int -> CPid

complementBit :: CPid -> Int -> CPid

testBit :: CPid -> Int -> Bool

bitSizeMaybe :: CPid -> Maybe Int

bitSize :: CPid -> Int

isSigned :: CPid -> Bool

shiftL :: CPid -> Int -> CPid

unsafeShiftL :: CPid -> Int -> CPid

shiftR :: CPid -> Int -> CPid

unsafeShiftR :: CPid -> Int -> CPid

rotateL :: CPid -> Int -> CPid

rotateR :: CPid -> Int -> CPid

popCount :: CPid -> Int

FiniteBits CPid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

finiteBitSize :: CPid -> Int

countLeadingZeros :: CPid -> Int

countTrailingZeros :: CPid -> Int

Bounded CPid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum CPid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

succ :: CPid -> CPid

pred :: CPid -> CPid

toEnum :: Int -> CPid

fromEnum :: CPid -> Int

enumFrom :: CPid -> [CPid]

enumFromThen :: CPid -> CPid -> [CPid]

enumFromTo :: CPid -> CPid -> [CPid]

enumFromThenTo :: CPid -> CPid -> CPid -> [CPid]

Storable CPid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CPid -> Int

alignment :: CPid -> Int

peekElemOff :: Ptr CPid -> Int -> IO CPid

pokeElemOff :: Ptr CPid -> Int -> CPid -> IO ()

peekByteOff :: Ptr b -> Int -> IO CPid

pokeByteOff :: Ptr b -> Int -> CPid -> IO ()

peek :: Ptr CPid -> IO CPid

poke :: Ptr CPid -> CPid -> IO ()

Ix CPid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

range :: (CPid, CPid) -> [CPid]

index :: (CPid, CPid) -> CPid -> Int

unsafeIndex :: (CPid, CPid) -> CPid -> Int

inRange :: (CPid, CPid) -> CPid -> Bool

rangeSize :: (CPid, CPid) -> Int

unsafeRangeSize :: (CPid, CPid) -> Int

Num CPid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(+) :: CPid -> CPid -> CPid

(-) :: CPid -> CPid -> CPid

(*) :: CPid -> CPid -> CPid

negate :: CPid -> CPid

abs :: CPid -> CPid

signum :: CPid -> CPid

fromInteger :: Integer -> CPid

Read CPid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CPid

readList :: ReadS [CPid]

readPrec :: ReadPrec CPid

readListPrec :: ReadPrec [CPid]

Integral CPid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

quot :: CPid -> CPid -> CPid

rem :: CPid -> CPid -> CPid

div :: CPid -> CPid -> CPid

mod :: CPid -> CPid -> CPid

quotRem :: CPid -> CPid -> (CPid, CPid)

divMod :: CPid -> CPid -> (CPid, CPid)

toInteger :: CPid -> Integer

Real CPid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CPid -> Rational

Show CPid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CPid -> ShowS

show :: CPid -> String

showList :: [CPid] -> ShowS

Eq CPid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CPid -> CPid -> Bool

(/=) :: CPid -> CPid -> Bool

Ord CPid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CPid -> CPid -> Ordering

(<) :: CPid -> CPid -> Bool

(<=) :: CPid -> CPid -> Bool

(>) :: CPid -> CPid -> Bool

(>=) :: CPid -> CPid -> Bool

max :: CPid -> CPid -> CPid

min :: CPid -> CPid -> CPid

type ByteCount = CSize #

newtype CCc #

Constructors

CCc Word8 

Instances

Instances details
Enum CCc 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

succ :: CCc -> CCc

pred :: CCc -> CCc

toEnum :: Int -> CCc

fromEnum :: CCc -> Int

enumFrom :: CCc -> [CCc]

enumFromThen :: CCc -> CCc -> [CCc]

enumFromTo :: CCc -> CCc -> [CCc]

enumFromThenTo :: CCc -> CCc -> CCc -> [CCc]

Storable CCc 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CCc -> Int

alignment :: CCc -> Int

peekElemOff :: Ptr CCc -> Int -> IO CCc

pokeElemOff :: Ptr CCc -> Int -> CCc -> IO ()

peekByteOff :: Ptr b -> Int -> IO CCc

pokeByteOff :: Ptr b -> Int -> CCc -> IO ()

peek :: Ptr CCc -> IO CCc

poke :: Ptr CCc -> CCc -> IO ()

Num CCc 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(+) :: CCc -> CCc -> CCc

(-) :: CCc -> CCc -> CCc

(*) :: CCc -> CCc -> CCc

negate :: CCc -> CCc

abs :: CCc -> CCc

signum :: CCc -> CCc

fromInteger :: Integer -> CCc

Read CCc 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CCc

readList :: ReadS [CCc]

readPrec :: ReadPrec CCc

readListPrec :: ReadPrec [CCc]

Real CCc 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CCc -> Rational

Show CCc 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CCc -> ShowS

show :: CCc -> String

showList :: [CCc] -> ShowS

Eq CCc 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CCc -> CCc -> Bool

(/=) :: CCc -> CCc -> Bool

Ord CCc 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CCc -> CCc -> Ordering

(<) :: CCc -> CCc -> Bool

(<=) :: CCc -> CCc -> Bool

(>) :: CCc -> CCc -> Bool

(>=) :: CCc -> CCc -> Bool

max :: CCc -> CCc -> CCc

min :: CCc -> CCc -> CCc

newtype CClockId #

Constructors

CClockId Word32 

Instances

Instances details
Bits CClockId 
Instance details

Defined in GHC.Internal.System.Posix.Types

FiniteBits CClockId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Bounded CClockId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum CClockId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Storable CClockId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CClockId -> Int

alignment :: CClockId -> Int

peekElemOff :: Ptr CClockId -> Int -> IO CClockId

pokeElemOff :: Ptr CClockId -> Int -> CClockId -> IO ()

peekByteOff :: Ptr b -> Int -> IO CClockId

pokeByteOff :: Ptr b -> Int -> CClockId -> IO ()

peek :: Ptr CClockId -> IO CClockId

poke :: Ptr CClockId -> CClockId -> IO ()

Ix CClockId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CClockId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Read CClockId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CClockId

readList :: ReadS [CClockId]

readPrec :: ReadPrec CClockId

readListPrec :: ReadPrec [CClockId]

Integral CClockId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CClockId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CClockId -> Rational

Show CClockId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CClockId -> ShowS

show :: CClockId -> String

showList :: [CClockId] -> ShowS

Eq CClockId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CClockId -> CClockId -> Bool

(/=) :: CClockId -> CClockId -> Bool

Ord CClockId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CClockId -> CClockId -> Ordering

(<) :: CClockId -> CClockId -> Bool

(<=) :: CClockId -> CClockId -> Bool

(>) :: CClockId -> CClockId -> Bool

(>=) :: CClockId -> CClockId -> Bool

max :: CClockId -> CClockId -> CClockId

min :: CClockId -> CClockId -> CClockId

newtype CDev #

Constructors

CDev Int32 

Instances

Instances details
Bits CDev 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(.&.) :: CDev -> CDev -> CDev

(.|.) :: CDev -> CDev -> CDev

xor :: CDev -> CDev -> CDev

complement :: CDev -> CDev

shift :: CDev -> Int -> CDev

rotate :: CDev -> Int -> CDev

zeroBits :: CDev

bit :: Int -> CDev

setBit :: CDev -> Int -> CDev

clearBit :: CDev -> Int -> CDev

complementBit :: CDev -> Int -> CDev

testBit :: CDev -> Int -> Bool

bitSizeMaybe :: CDev -> Maybe Int

bitSize :: CDev -> Int

isSigned :: CDev -> Bool

shiftL :: CDev -> Int -> CDev

unsafeShiftL :: CDev -> Int -> CDev

shiftR :: CDev -> Int -> CDev

unsafeShiftR :: CDev -> Int -> CDev

rotateL :: CDev -> Int -> CDev

rotateR :: CDev -> Int -> CDev

popCount :: CDev -> Int

FiniteBits CDev 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

finiteBitSize :: CDev -> Int

countLeadingZeros :: CDev -> Int

countTrailingZeros :: CDev -> Int

Bounded CDev 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum CDev 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

succ :: CDev -> CDev

pred :: CDev -> CDev

toEnum :: Int -> CDev

fromEnum :: CDev -> Int

enumFrom :: CDev -> [CDev]

enumFromThen :: CDev -> CDev -> [CDev]

enumFromTo :: CDev -> CDev -> [CDev]

enumFromThenTo :: CDev -> CDev -> CDev -> [CDev]

Storable CDev 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CDev -> Int

alignment :: CDev -> Int

peekElemOff :: Ptr CDev -> Int -> IO CDev

pokeElemOff :: Ptr CDev -> Int -> CDev -> IO ()

peekByteOff :: Ptr b -> Int -> IO CDev

pokeByteOff :: Ptr b -> Int -> CDev -> IO ()

peek :: Ptr CDev -> IO CDev

poke :: Ptr CDev -> CDev -> IO ()

Ix CDev 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

range :: (CDev, CDev) -> [CDev]

index :: (CDev, CDev) -> CDev -> Int

unsafeIndex :: (CDev, CDev) -> CDev -> Int

inRange :: (CDev, CDev) -> CDev -> Bool

rangeSize :: (CDev, CDev) -> Int

unsafeRangeSize :: (CDev, CDev) -> Int

Num CDev 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(+) :: CDev -> CDev -> CDev

(-) :: CDev -> CDev -> CDev

(*) :: CDev -> CDev -> CDev

negate :: CDev -> CDev

abs :: CDev -> CDev

signum :: CDev -> CDev

fromInteger :: Integer -> CDev

Read CDev 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CDev

readList :: ReadS [CDev]

readPrec :: ReadPrec CDev

readListPrec :: ReadPrec [CDev]

Integral CDev 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

quot :: CDev -> CDev -> CDev

rem :: CDev -> CDev -> CDev

div :: CDev -> CDev -> CDev

mod :: CDev -> CDev -> CDev

quotRem :: CDev -> CDev -> (CDev, CDev)

divMod :: CDev -> CDev -> (CDev, CDev)

toInteger :: CDev -> Integer

Real CDev 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CDev -> Rational

Show CDev 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CDev -> ShowS

show :: CDev -> String

showList :: [CDev] -> ShowS

Eq CDev 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CDev -> CDev -> Bool

(/=) :: CDev -> CDev -> Bool

Ord CDev 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CDev -> CDev -> Ordering

(<) :: CDev -> CDev -> Bool

(<=) :: CDev -> CDev -> Bool

(>) :: CDev -> CDev -> Bool

(>=) :: CDev -> CDev -> Bool

max :: CDev -> CDev -> CDev

min :: CDev -> CDev -> CDev

newtype CFsBlkCnt #

Constructors

CFsBlkCnt Word32 

Instances

Instances details
Bits CFsBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

FiniteBits CFsBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Bounded CFsBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum CFsBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Storable CFsBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CFsBlkCnt -> Int

alignment :: CFsBlkCnt -> Int

peekElemOff :: Ptr CFsBlkCnt -> Int -> IO CFsBlkCnt

pokeElemOff :: Ptr CFsBlkCnt -> Int -> CFsBlkCnt -> IO ()

peekByteOff :: Ptr b -> Int -> IO CFsBlkCnt

pokeByteOff :: Ptr b -> Int -> CFsBlkCnt -> IO ()

peek :: Ptr CFsBlkCnt -> IO CFsBlkCnt

poke :: Ptr CFsBlkCnt -> CFsBlkCnt -> IO ()

Ix CFsBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CFsBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Read CFsBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CFsBlkCnt

readList :: ReadS [CFsBlkCnt]

readPrec :: ReadPrec CFsBlkCnt

readListPrec :: ReadPrec [CFsBlkCnt]

Integral CFsBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CFsBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CFsBlkCnt -> Rational

Show CFsBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CFsBlkCnt -> ShowS

show :: CFsBlkCnt -> String

showList :: [CFsBlkCnt] -> ShowS

Eq CFsBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CFsBlkCnt -> CFsBlkCnt -> Bool

(/=) :: CFsBlkCnt -> CFsBlkCnt -> Bool

Ord CFsBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CFsBlkCnt -> CFsBlkCnt -> Ordering

(<) :: CFsBlkCnt -> CFsBlkCnt -> Bool

(<=) :: CFsBlkCnt -> CFsBlkCnt -> Bool

(>) :: CFsBlkCnt -> CFsBlkCnt -> Bool

(>=) :: CFsBlkCnt -> CFsBlkCnt -> Bool

max :: CFsBlkCnt -> CFsBlkCnt -> CFsBlkCnt

min :: CFsBlkCnt -> CFsBlkCnt -> CFsBlkCnt

newtype CFsFilCnt #

Constructors

CFsFilCnt Word32 

Instances

Instances details
Bits CFsFilCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

FiniteBits CFsFilCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Bounded CFsFilCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum CFsFilCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Storable CFsFilCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CFsFilCnt -> Int

alignment :: CFsFilCnt -> Int

peekElemOff :: Ptr CFsFilCnt -> Int -> IO CFsFilCnt

pokeElemOff :: Ptr CFsFilCnt -> Int -> CFsFilCnt -> IO ()

peekByteOff :: Ptr b -> Int -> IO CFsFilCnt

pokeByteOff :: Ptr b -> Int -> CFsFilCnt -> IO ()

peek :: Ptr CFsFilCnt -> IO CFsFilCnt

poke :: Ptr CFsFilCnt -> CFsFilCnt -> IO ()

Ix CFsFilCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CFsFilCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Read CFsFilCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CFsFilCnt

readList :: ReadS [CFsFilCnt]

readPrec :: ReadPrec CFsFilCnt

readListPrec :: ReadPrec [CFsFilCnt]

Integral CFsFilCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CFsFilCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CFsFilCnt -> Rational

Show CFsFilCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CFsFilCnt -> ShowS

show :: CFsFilCnt -> String

showList :: [CFsFilCnt] -> ShowS

Eq CFsFilCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CFsFilCnt -> CFsFilCnt -> Bool

(/=) :: CFsFilCnt -> CFsFilCnt -> Bool

Ord CFsFilCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CFsFilCnt -> CFsFilCnt -> Ordering

(<) :: CFsFilCnt -> CFsFilCnt -> Bool

(<=) :: CFsFilCnt -> CFsFilCnt -> Bool

(>) :: CFsFilCnt -> CFsFilCnt -> Bool

(>=) :: CFsFilCnt -> CFsFilCnt -> Bool

max :: CFsFilCnt -> CFsFilCnt -> CFsFilCnt

min :: CFsFilCnt -> CFsFilCnt -> CFsFilCnt

newtype CGid #

Constructors

CGid Word32 

Instances

Instances details
Bits CGid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(.&.) :: CGid -> CGid -> CGid

(.|.) :: CGid -> CGid -> CGid

xor :: CGid -> CGid -> CGid

complement :: CGid -> CGid

shift :: CGid -> Int -> CGid

rotate :: CGid -> Int -> CGid

zeroBits :: CGid

bit :: Int -> CGid

setBit :: CGid -> Int -> CGid

clearBit :: CGid -> Int -> CGid

complementBit :: CGid -> Int -> CGid

testBit :: CGid -> Int -> Bool

bitSizeMaybe :: CGid -> Maybe Int

bitSize :: CGid -> Int

isSigned :: CGid -> Bool

shiftL :: CGid -> Int -> CGid

unsafeShiftL :: CGid -> Int -> CGid

shiftR :: CGid -> Int -> CGid

unsafeShiftR :: CGid -> Int -> CGid

rotateL :: CGid -> Int -> CGid

rotateR :: CGid -> Int -> CGid

popCount :: CGid -> Int

FiniteBits CGid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

finiteBitSize :: CGid -> Int

countLeadingZeros :: CGid -> Int

countTrailingZeros :: CGid -> Int

Bounded CGid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum CGid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

succ :: CGid -> CGid

pred :: CGid -> CGid

toEnum :: Int -> CGid

fromEnum :: CGid -> Int

enumFrom :: CGid -> [CGid]

enumFromThen :: CGid -> CGid -> [CGid]

enumFromTo :: CGid -> CGid -> [CGid]

enumFromThenTo :: CGid -> CGid -> CGid -> [CGid]

Storable CGid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CGid -> Int

alignment :: CGid -> Int

peekElemOff :: Ptr CGid -> Int -> IO CGid

pokeElemOff :: Ptr CGid -> Int -> CGid -> IO ()

peekByteOff :: Ptr b -> Int -> IO CGid

pokeByteOff :: Ptr b -> Int -> CGid -> IO ()

peek :: Ptr CGid -> IO CGid

poke :: Ptr CGid -> CGid -> IO ()

Ix CGid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

range :: (CGid, CGid) -> [CGid]

index :: (CGid, CGid) -> CGid -> Int

unsafeIndex :: (CGid, CGid) -> CGid -> Int

inRange :: (CGid, CGid) -> CGid -> Bool

rangeSize :: (CGid, CGid) -> Int

unsafeRangeSize :: (CGid, CGid) -> Int

Num CGid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(+) :: CGid -> CGid -> CGid

(-) :: CGid -> CGid -> CGid

(*) :: CGid -> CGid -> CGid

negate :: CGid -> CGid

abs :: CGid -> CGid

signum :: CGid -> CGid

fromInteger :: Integer -> CGid

Read CGid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CGid

readList :: ReadS [CGid]

readPrec :: ReadPrec CGid

readListPrec :: ReadPrec [CGid]

Integral CGid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

quot :: CGid -> CGid -> CGid

rem :: CGid -> CGid -> CGid

div :: CGid -> CGid -> CGid

mod :: CGid -> CGid -> CGid

quotRem :: CGid -> CGid -> (CGid, CGid)

divMod :: CGid -> CGid -> (CGid, CGid)

toInteger :: CGid -> Integer

Real CGid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CGid -> Rational

Show CGid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CGid -> ShowS

show :: CGid -> String

showList :: [CGid] -> ShowS

Eq CGid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CGid -> CGid -> Bool

(/=) :: CGid -> CGid -> Bool

Ord CGid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CGid -> CGid -> Ordering

(<) :: CGid -> CGid -> Bool

(<=) :: CGid -> CGid -> Bool

(>) :: CGid -> CGid -> Bool

(>=) :: CGid -> CGid -> Bool

max :: CGid -> CGid -> CGid

min :: CGid -> CGid -> CGid

newtype CId #

Constructors

CId Word32 

Instances

Instances details
Bits CId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(.&.) :: CId -> CId -> CId

(.|.) :: CId -> CId -> CId

xor :: CId -> CId -> CId

complement :: CId -> CId

shift :: CId -> Int -> CId

rotate :: CId -> Int -> CId

zeroBits :: CId

bit :: Int -> CId

setBit :: CId -> Int -> CId

clearBit :: CId -> Int -> CId

complementBit :: CId -> Int -> CId

testBit :: CId -> Int -> Bool

bitSizeMaybe :: CId -> Maybe Int

bitSize :: CId -> Int

isSigned :: CId -> Bool

shiftL :: CId -> Int -> CId

unsafeShiftL :: CId -> Int -> CId

shiftR :: CId -> Int -> CId

unsafeShiftR :: CId -> Int -> CId

rotateL :: CId -> Int -> CId

rotateR :: CId -> Int -> CId

popCount :: CId -> Int

FiniteBits CId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

finiteBitSize :: CId -> Int

countLeadingZeros :: CId -> Int

countTrailingZeros :: CId -> Int

Bounded CId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

minBound :: CId

maxBound :: CId

Enum CId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

succ :: CId -> CId

pred :: CId -> CId

toEnum :: Int -> CId

fromEnum :: CId -> Int

enumFrom :: CId -> [CId]

enumFromThen :: CId -> CId -> [CId]

enumFromTo :: CId -> CId -> [CId]

enumFromThenTo :: CId -> CId -> CId -> [CId]

Storable CId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CId -> Int

alignment :: CId -> Int

peekElemOff :: Ptr CId -> Int -> IO CId

pokeElemOff :: Ptr CId -> Int -> CId -> IO ()

peekByteOff :: Ptr b -> Int -> IO CId

pokeByteOff :: Ptr b -> Int -> CId -> IO ()

peek :: Ptr CId -> IO CId

poke :: Ptr CId -> CId -> IO ()

Ix CId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

range :: (CId, CId) -> [CId]

index :: (CId, CId) -> CId -> Int

unsafeIndex :: (CId, CId) -> CId -> Int

inRange :: (CId, CId) -> CId -> Bool

rangeSize :: (CId, CId) -> Int

unsafeRangeSize :: (CId, CId) -> Int

Num CId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(+) :: CId -> CId -> CId

(-) :: CId -> CId -> CId

(*) :: CId -> CId -> CId

negate :: CId -> CId

abs :: CId -> CId

signum :: CId -> CId

fromInteger :: Integer -> CId

Read CId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CId

readList :: ReadS [CId]

readPrec :: ReadPrec CId

readListPrec :: ReadPrec [CId]

Integral CId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

quot :: CId -> CId -> CId

rem :: CId -> CId -> CId

div :: CId -> CId -> CId

mod :: CId -> CId -> CId

quotRem :: CId -> CId -> (CId, CId)

divMod :: CId -> CId -> (CId, CId)

toInteger :: CId -> Integer

Real CId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CId -> Rational

Show CId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CId -> ShowS

show :: CId -> String

showList :: [CId] -> ShowS

Eq CId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CId -> CId -> Bool

(/=) :: CId -> CId -> Bool

Ord CId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CId -> CId -> Ordering

(<) :: CId -> CId -> Bool

(<=) :: CId -> CId -> Bool

(>) :: CId -> CId -> Bool

(>=) :: CId -> CId -> Bool

max :: CId -> CId -> CId

min :: CId -> CId -> CId

newtype CIno #

Constructors

CIno Word64 

Instances

Instances details
Bits CIno 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(.&.) :: CIno -> CIno -> CIno

(.|.) :: CIno -> CIno -> CIno

xor :: CIno -> CIno -> CIno

complement :: CIno -> CIno

shift :: CIno -> Int -> CIno

rotate :: CIno -> Int -> CIno

zeroBits :: CIno

bit :: Int -> CIno

setBit :: CIno -> Int -> CIno

clearBit :: CIno -> Int -> CIno

complementBit :: CIno -> Int -> CIno

testBit :: CIno -> Int -> Bool

bitSizeMaybe :: CIno -> Maybe Int

bitSize :: CIno -> Int

isSigned :: CIno -> Bool

shiftL :: CIno -> Int -> CIno

unsafeShiftL :: CIno -> Int -> CIno

shiftR :: CIno -> Int -> CIno

unsafeShiftR :: CIno -> Int -> CIno

rotateL :: CIno -> Int -> CIno

rotateR :: CIno -> Int -> CIno

popCount :: CIno -> Int

FiniteBits CIno 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

finiteBitSize :: CIno -> Int

countLeadingZeros :: CIno -> Int

countTrailingZeros :: CIno -> Int

Bounded CIno 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum CIno 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

succ :: CIno -> CIno

pred :: CIno -> CIno

toEnum :: Int -> CIno

fromEnum :: CIno -> Int

enumFrom :: CIno -> [CIno]

enumFromThen :: CIno -> CIno -> [CIno]

enumFromTo :: CIno -> CIno -> [CIno]

enumFromThenTo :: CIno -> CIno -> CIno -> [CIno]

Storable CIno 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CIno -> Int

alignment :: CIno -> Int

peekElemOff :: Ptr CIno -> Int -> IO CIno

pokeElemOff :: Ptr CIno -> Int -> CIno -> IO ()

peekByteOff :: Ptr b -> Int -> IO CIno

pokeByteOff :: Ptr b -> Int -> CIno -> IO ()

peek :: Ptr CIno -> IO CIno

poke :: Ptr CIno -> CIno -> IO ()

Ix CIno 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

range :: (CIno, CIno) -> [CIno]

index :: (CIno, CIno) -> CIno -> Int

unsafeIndex :: (CIno, CIno) -> CIno -> Int

inRange :: (CIno, CIno) -> CIno -> Bool

rangeSize :: (CIno, CIno) -> Int

unsafeRangeSize :: (CIno, CIno) -> Int

Num CIno 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(+) :: CIno -> CIno -> CIno

(-) :: CIno -> CIno -> CIno

(*) :: CIno -> CIno -> CIno

negate :: CIno -> CIno

abs :: CIno -> CIno

signum :: CIno -> CIno

fromInteger :: Integer -> CIno

Read CIno 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CIno

readList :: ReadS [CIno]

readPrec :: ReadPrec CIno

readListPrec :: ReadPrec [CIno]

Integral CIno 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

quot :: CIno -> CIno -> CIno

rem :: CIno -> CIno -> CIno

div :: CIno -> CIno -> CIno

mod :: CIno -> CIno -> CIno

quotRem :: CIno -> CIno -> (CIno, CIno)

divMod :: CIno -> CIno -> (CIno, CIno)

toInteger :: CIno -> Integer

Real CIno 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CIno -> Rational

Show CIno 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CIno -> ShowS

show :: CIno -> String

showList :: [CIno] -> ShowS

Eq CIno 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CIno -> CIno -> Bool

(/=) :: CIno -> CIno -> Bool

Ord CIno 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CIno -> CIno -> Ordering

(<) :: CIno -> CIno -> Bool

(<=) :: CIno -> CIno -> Bool

(>) :: CIno -> CIno -> Bool

(>=) :: CIno -> CIno -> Bool

max :: CIno -> CIno -> CIno

min :: CIno -> CIno -> CIno

newtype CKey #

Constructors

CKey Int32 

Instances

Instances details
Bits CKey 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(.&.) :: CKey -> CKey -> CKey

(.|.) :: CKey -> CKey -> CKey

xor :: CKey -> CKey -> CKey

complement :: CKey -> CKey

shift :: CKey -> Int -> CKey

rotate :: CKey -> Int -> CKey

zeroBits :: CKey

bit :: Int -> CKey

setBit :: CKey -> Int -> CKey

clearBit :: CKey -> Int -> CKey

complementBit :: CKey -> Int -> CKey

testBit :: CKey -> Int -> Bool

bitSizeMaybe :: CKey -> Maybe Int

bitSize :: CKey -> Int

isSigned :: CKey -> Bool

shiftL :: CKey -> Int -> CKey

unsafeShiftL :: CKey -> Int -> CKey

shiftR :: CKey -> Int -> CKey

unsafeShiftR :: CKey -> Int -> CKey

rotateL :: CKey -> Int -> CKey

rotateR :: CKey -> Int -> CKey

popCount :: CKey -> Int

FiniteBits CKey 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

finiteBitSize :: CKey -> Int

countLeadingZeros :: CKey -> Int

countTrailingZeros :: CKey -> Int

Bounded CKey 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum CKey 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

succ :: CKey -> CKey

pred :: CKey -> CKey

toEnum :: Int -> CKey

fromEnum :: CKey -> Int

enumFrom :: CKey -> [CKey]

enumFromThen :: CKey -> CKey -> [CKey]

enumFromTo :: CKey -> CKey -> [CKey]

enumFromThenTo :: CKey -> CKey -> CKey -> [CKey]

Storable CKey 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CKey -> Int

alignment :: CKey -> Int

peekElemOff :: Ptr CKey -> Int -> IO CKey

pokeElemOff :: Ptr CKey -> Int -> CKey -> IO ()

peekByteOff :: Ptr b -> Int -> IO CKey

pokeByteOff :: Ptr b -> Int -> CKey -> IO ()

peek :: Ptr CKey -> IO CKey

poke :: Ptr CKey -> CKey -> IO ()

Ix CKey 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

range :: (CKey, CKey) -> [CKey]

index :: (CKey, CKey) -> CKey -> Int

unsafeIndex :: (CKey, CKey) -> CKey -> Int

inRange :: (CKey, CKey) -> CKey -> Bool

rangeSize :: (CKey, CKey) -> Int

unsafeRangeSize :: (CKey, CKey) -> Int

Num CKey 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(+) :: CKey -> CKey -> CKey

(-) :: CKey -> CKey -> CKey

(*) :: CKey -> CKey -> CKey

negate :: CKey -> CKey

abs :: CKey -> CKey

signum :: CKey -> CKey

fromInteger :: Integer -> CKey

Read CKey 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CKey

readList :: ReadS [CKey]

readPrec :: ReadPrec CKey

readListPrec :: ReadPrec [CKey]

Integral CKey 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

quot :: CKey -> CKey -> CKey

rem :: CKey -> CKey -> CKey

div :: CKey -> CKey -> CKey

mod :: CKey -> CKey -> CKey

quotRem :: CKey -> CKey -> (CKey, CKey)

divMod :: CKey -> CKey -> (CKey, CKey)

toInteger :: CKey -> Integer

Real CKey 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CKey -> Rational

Show CKey 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CKey -> ShowS

show :: CKey -> String

showList :: [CKey] -> ShowS

Eq CKey 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CKey -> CKey -> Bool

(/=) :: CKey -> CKey -> Bool

Ord CKey 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CKey -> CKey -> Ordering

(<) :: CKey -> CKey -> Bool

(<=) :: CKey -> CKey -> Bool

(>) :: CKey -> CKey -> Bool

(>=) :: CKey -> CKey -> Bool

max :: CKey -> CKey -> CKey

min :: CKey -> CKey -> CKey

newtype CMode #

Constructors

CMode Word16 

Instances

Instances details
Bits CMode 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(.&.) :: CMode -> CMode -> CMode

(.|.) :: CMode -> CMode -> CMode

xor :: CMode -> CMode -> CMode

complement :: CMode -> CMode

shift :: CMode -> Int -> CMode

rotate :: CMode -> Int -> CMode

zeroBits :: CMode

bit :: Int -> CMode

setBit :: CMode -> Int -> CMode

clearBit :: CMode -> Int -> CMode

complementBit :: CMode -> Int -> CMode

testBit :: CMode -> Int -> Bool

bitSizeMaybe :: CMode -> Maybe Int

bitSize :: CMode -> Int

isSigned :: CMode -> Bool

shiftL :: CMode -> Int -> CMode

unsafeShiftL :: CMode -> Int -> CMode

shiftR :: CMode -> Int -> CMode

unsafeShiftR :: CMode -> Int -> CMode

rotateL :: CMode -> Int -> CMode

rotateR :: CMode -> Int -> CMode

popCount :: CMode -> Int

FiniteBits CMode 
Instance details

Defined in GHC.Internal.System.Posix.Types

Bounded CMode 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum CMode 
Instance details

Defined in GHC.Internal.System.Posix.Types

Storable CMode 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CMode -> Int

alignment :: CMode -> Int

peekElemOff :: Ptr CMode -> Int -> IO CMode

pokeElemOff :: Ptr CMode -> Int -> CMode -> IO ()

peekByteOff :: Ptr b -> Int -> IO CMode

pokeByteOff :: Ptr b -> Int -> CMode -> IO ()

peek :: Ptr CMode -> IO CMode

poke :: Ptr CMode -> CMode -> IO ()

Ix CMode 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

range :: (CMode, CMode) -> [CMode]

index :: (CMode, CMode) -> CMode -> Int

unsafeIndex :: (CMode, CMode) -> CMode -> Int

inRange :: (CMode, CMode) -> CMode -> Bool

rangeSize :: (CMode, CMode) -> Int

unsafeRangeSize :: (CMode, CMode) -> Int

Num CMode 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(+) :: CMode -> CMode -> CMode

(-) :: CMode -> CMode -> CMode

(*) :: CMode -> CMode -> CMode

negate :: CMode -> CMode

abs :: CMode -> CMode

signum :: CMode -> CMode

fromInteger :: Integer -> CMode

Read CMode 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CMode

readList :: ReadS [CMode]

readPrec :: ReadPrec CMode

readListPrec :: ReadPrec [CMode]

Integral CMode 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

quot :: CMode -> CMode -> CMode

rem :: CMode -> CMode -> CMode

div :: CMode -> CMode -> CMode

mod :: CMode -> CMode -> CMode

quotRem :: CMode -> CMode -> (CMode, CMode)

divMod :: CMode -> CMode -> (CMode, CMode)

toInteger :: CMode -> Integer

Real CMode 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CMode -> Rational

Show CMode 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CMode -> ShowS

show :: CMode -> String

showList :: [CMode] -> ShowS

Eq CMode 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CMode -> CMode -> Bool

(/=) :: CMode -> CMode -> Bool

Ord CMode 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CMode -> CMode -> Ordering

(<) :: CMode -> CMode -> Bool

(<=) :: CMode -> CMode -> Bool

(>) :: CMode -> CMode -> Bool

(>=) :: CMode -> CMode -> Bool

max :: CMode -> CMode -> CMode

min :: CMode -> CMode -> CMode

newtype CNfds #

Constructors

CNfds Word32 

Instances

Instances details
Bits CNfds 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(.&.) :: CNfds -> CNfds -> CNfds

(.|.) :: CNfds -> CNfds -> CNfds

xor :: CNfds -> CNfds -> CNfds

complement :: CNfds -> CNfds

shift :: CNfds -> Int -> CNfds

rotate :: CNfds -> Int -> CNfds

zeroBits :: CNfds

bit :: Int -> CNfds

setBit :: CNfds -> Int -> CNfds

clearBit :: CNfds -> Int -> CNfds

complementBit :: CNfds -> Int -> CNfds

testBit :: CNfds -> Int -> Bool

bitSizeMaybe :: CNfds -> Maybe Int

bitSize :: CNfds -> Int

isSigned :: CNfds -> Bool

shiftL :: CNfds -> Int -> CNfds

unsafeShiftL :: CNfds -> Int -> CNfds

shiftR :: CNfds -> Int -> CNfds

unsafeShiftR :: CNfds -> Int -> CNfds

rotateL :: CNfds -> Int -> CNfds

rotateR :: CNfds -> Int -> CNfds

popCount :: CNfds -> Int

FiniteBits CNfds 
Instance details

Defined in GHC.Internal.System.Posix.Types

Bounded CNfds 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum CNfds 
Instance details

Defined in GHC.Internal.System.Posix.Types

Storable CNfds 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CNfds -> Int

alignment :: CNfds -> Int

peekElemOff :: Ptr CNfds -> Int -> IO CNfds

pokeElemOff :: Ptr CNfds -> Int -> CNfds -> IO ()

peekByteOff :: Ptr b -> Int -> IO CNfds

pokeByteOff :: Ptr b -> Int -> CNfds -> IO ()

peek :: Ptr CNfds -> IO CNfds

poke :: Ptr CNfds -> CNfds -> IO ()

Ix CNfds 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

range :: (CNfds, CNfds) -> [CNfds]

index :: (CNfds, CNfds) -> CNfds -> Int

unsafeIndex :: (CNfds, CNfds) -> CNfds -> Int

inRange :: (CNfds, CNfds) -> CNfds -> Bool

rangeSize :: (CNfds, CNfds) -> Int

unsafeRangeSize :: (CNfds, CNfds) -> Int

Num CNfds 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(+) :: CNfds -> CNfds -> CNfds

(-) :: CNfds -> CNfds -> CNfds

(*) :: CNfds -> CNfds -> CNfds

negate :: CNfds -> CNfds

abs :: CNfds -> CNfds

signum :: CNfds -> CNfds

fromInteger :: Integer -> CNfds

Read CNfds 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CNfds

readList :: ReadS [CNfds]

readPrec :: ReadPrec CNfds

readListPrec :: ReadPrec [CNfds]

Integral CNfds 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

quot :: CNfds -> CNfds -> CNfds

rem :: CNfds -> CNfds -> CNfds

div :: CNfds -> CNfds -> CNfds

mod :: CNfds -> CNfds -> CNfds

quotRem :: CNfds -> CNfds -> (CNfds, CNfds)

divMod :: CNfds -> CNfds -> (CNfds, CNfds)

toInteger :: CNfds -> Integer

Real CNfds 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CNfds -> Rational

Show CNfds 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CNfds -> ShowS

show :: CNfds -> String

showList :: [CNfds] -> ShowS

Eq CNfds 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CNfds -> CNfds -> Bool

(/=) :: CNfds -> CNfds -> Bool

Ord CNfds 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CNfds -> CNfds -> Ordering

(<) :: CNfds -> CNfds -> Bool

(<=) :: CNfds -> CNfds -> Bool

(>) :: CNfds -> CNfds -> Bool

(>=) :: CNfds -> CNfds -> Bool

max :: CNfds -> CNfds -> CNfds

min :: CNfds -> CNfds -> CNfds

newtype COff #

Constructors

COff Int64 

Instances

Instances details
Bits COff 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(.&.) :: COff -> COff -> COff

(.|.) :: COff -> COff -> COff

xor :: COff -> COff -> COff

complement :: COff -> COff

shift :: COff -> Int -> COff

rotate :: COff -> Int -> COff

zeroBits :: COff

bit :: Int -> COff

setBit :: COff -> Int -> COff

clearBit :: COff -> Int -> COff

complementBit :: COff -> Int -> COff

testBit :: COff -> Int -> Bool

bitSizeMaybe :: COff -> Maybe Int

bitSize :: COff -> Int

isSigned :: COff -> Bool

shiftL :: COff -> Int -> COff

unsafeShiftL :: COff -> Int -> COff

shiftR :: COff -> Int -> COff

unsafeShiftR :: COff -> Int -> COff

rotateL :: COff -> Int -> COff

rotateR :: COff -> Int -> COff

popCount :: COff -> Int

FiniteBits COff 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

finiteBitSize :: COff -> Int

countLeadingZeros :: COff -> Int

countTrailingZeros :: COff -> Int

Bounded COff 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum COff 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

succ :: COff -> COff

pred :: COff -> COff

toEnum :: Int -> COff

fromEnum :: COff -> Int

enumFrom :: COff -> [COff]

enumFromThen :: COff -> COff -> [COff]

enumFromTo :: COff -> COff -> [COff]

enumFromThenTo :: COff -> COff -> COff -> [COff]

Storable COff 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: COff -> Int

alignment :: COff -> Int

peekElemOff :: Ptr COff -> Int -> IO COff

pokeElemOff :: Ptr COff -> Int -> COff -> IO ()

peekByteOff :: Ptr b -> Int -> IO COff

pokeByteOff :: Ptr b -> Int -> COff -> IO ()

peek :: Ptr COff -> IO COff

poke :: Ptr COff -> COff -> IO ()

Ix COff 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

range :: (COff, COff) -> [COff]

index :: (COff, COff) -> COff -> Int

unsafeIndex :: (COff, COff) -> COff -> Int

inRange :: (COff, COff) -> COff -> Bool

rangeSize :: (COff, COff) -> Int

unsafeRangeSize :: (COff, COff) -> Int

Num COff 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(+) :: COff -> COff -> COff

(-) :: COff -> COff -> COff

(*) :: COff -> COff -> COff

negate :: COff -> COff

abs :: COff -> COff

signum :: COff -> COff

fromInteger :: Integer -> COff

Read COff 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS COff

readList :: ReadS [COff]

readPrec :: ReadPrec COff

readListPrec :: ReadPrec [COff]

Integral COff 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

quot :: COff -> COff -> COff

rem :: COff -> COff -> COff

div :: COff -> COff -> COff

mod :: COff -> COff -> COff

quotRem :: COff -> COff -> (COff, COff)

divMod :: COff -> COff -> (COff, COff)

toInteger :: COff -> Integer

Real COff 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: COff -> Rational

Show COff 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> COff -> ShowS

show :: COff -> String

showList :: [COff] -> ShowS

Eq COff 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: COff -> COff -> Bool

(/=) :: COff -> COff -> Bool

Ord COff 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: COff -> COff -> Ordering

(<) :: COff -> COff -> Bool

(<=) :: COff -> COff -> Bool

(>) :: COff -> COff -> Bool

(>=) :: COff -> COff -> Bool

max :: COff -> COff -> COff

min :: COff -> COff -> COff

newtype CRLim #

Constructors

CRLim Word64 

Instances

Instances details
Bits CRLim 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(.&.) :: CRLim -> CRLim -> CRLim

(.|.) :: CRLim -> CRLim -> CRLim

xor :: CRLim -> CRLim -> CRLim

complement :: CRLim -> CRLim

shift :: CRLim -> Int -> CRLim

rotate :: CRLim -> Int -> CRLim

zeroBits :: CRLim

bit :: Int -> CRLim

setBit :: CRLim -> Int -> CRLim

clearBit :: CRLim -> Int -> CRLim

complementBit :: CRLim -> Int -> CRLim

testBit :: CRLim -> Int -> Bool

bitSizeMaybe :: CRLim -> Maybe Int

bitSize :: CRLim -> Int

isSigned :: CRLim -> Bool

shiftL :: CRLim -> Int -> CRLim

unsafeShiftL :: CRLim -> Int -> CRLim

shiftR :: CRLim -> Int -> CRLim

unsafeShiftR :: CRLim -> Int -> CRLim

rotateL :: CRLim -> Int -> CRLim

rotateR :: CRLim -> Int -> CRLim

popCount :: CRLim -> Int

FiniteBits CRLim 
Instance details

Defined in GHC.Internal.System.Posix.Types

Bounded CRLim 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum CRLim 
Instance details

Defined in GHC.Internal.System.Posix.Types

Storable CRLim 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CRLim -> Int

alignment :: CRLim -> Int

peekElemOff :: Ptr CRLim -> Int -> IO CRLim

pokeElemOff :: Ptr CRLim -> Int -> CRLim -> IO ()

peekByteOff :: Ptr b -> Int -> IO CRLim

pokeByteOff :: Ptr b -> Int -> CRLim -> IO ()

peek :: Ptr CRLim -> IO CRLim

poke :: Ptr CRLim -> CRLim -> IO ()

Ix CRLim 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

range :: (CRLim, CRLim) -> [CRLim]

index :: (CRLim, CRLim) -> CRLim -> Int

unsafeIndex :: (CRLim, CRLim) -> CRLim -> Int

inRange :: (CRLim, CRLim) -> CRLim -> Bool

rangeSize :: (CRLim, CRLim) -> Int

unsafeRangeSize :: (CRLim, CRLim) -> Int

Num CRLim 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(+) :: CRLim -> CRLim -> CRLim

(-) :: CRLim -> CRLim -> CRLim

(*) :: CRLim -> CRLim -> CRLim

negate :: CRLim -> CRLim

abs :: CRLim -> CRLim

signum :: CRLim -> CRLim

fromInteger :: Integer -> CRLim

Read CRLim 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CRLim

readList :: ReadS [CRLim]

readPrec :: ReadPrec CRLim

readListPrec :: ReadPrec [CRLim]

Integral CRLim 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

quot :: CRLim -> CRLim -> CRLim

rem :: CRLim -> CRLim -> CRLim

div :: CRLim -> CRLim -> CRLim

mod :: CRLim -> CRLim -> CRLim

quotRem :: CRLim -> CRLim -> (CRLim, CRLim)

divMod :: CRLim -> CRLim -> (CRLim, CRLim)

toInteger :: CRLim -> Integer

Real CRLim 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CRLim -> Rational

Show CRLim 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CRLim -> ShowS

show :: CRLim -> String

showList :: [CRLim] -> ShowS

Eq CRLim 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CRLim -> CRLim -> Bool

(/=) :: CRLim -> CRLim -> Bool

Ord CRLim 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CRLim -> CRLim -> Ordering

(<) :: CRLim -> CRLim -> Bool

(<=) :: CRLim -> CRLim -> Bool

(>) :: CRLim -> CRLim -> Bool

(>=) :: CRLim -> CRLim -> Bool

max :: CRLim -> CRLim -> CRLim

min :: CRLim -> CRLim -> CRLim

newtype CSocklen #

Constructors

CSocklen Word32 

Instances

Instances details
Bits CSocklen 
Instance details

Defined in GHC.Internal.System.Posix.Types

FiniteBits CSocklen 
Instance details

Defined in GHC.Internal.System.Posix.Types

Bounded CSocklen 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum CSocklen 
Instance details

Defined in GHC.Internal.System.Posix.Types

Storable CSocklen 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CSocklen -> Int

alignment :: CSocklen -> Int

peekElemOff :: Ptr CSocklen -> Int -> IO CSocklen

pokeElemOff :: Ptr CSocklen -> Int -> CSocklen -> IO ()

peekByteOff :: Ptr b -> Int -> IO CSocklen

pokeByteOff :: Ptr b -> Int -> CSocklen -> IO ()

peek :: Ptr CSocklen -> IO CSocklen

poke :: Ptr CSocklen -> CSocklen -> IO ()

Ix CSocklen 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CSocklen 
Instance details

Defined in GHC.Internal.System.Posix.Types

Read CSocklen 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CSocklen

readList :: ReadS [CSocklen]

readPrec :: ReadPrec CSocklen

readListPrec :: ReadPrec [CSocklen]

Integral CSocklen 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CSocklen 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CSocklen -> Rational

Show CSocklen 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CSocklen -> ShowS

show :: CSocklen -> String

showList :: [CSocklen] -> ShowS

Eq CSocklen 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CSocklen -> CSocklen -> Bool

(/=) :: CSocklen -> CSocklen -> Bool

Ord CSocklen 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CSocklen -> CSocklen -> Ordering

(<) :: CSocklen -> CSocklen -> Bool

(<=) :: CSocklen -> CSocklen -> Bool

(>) :: CSocklen -> CSocklen -> Bool

(>=) :: CSocklen -> CSocklen -> Bool

max :: CSocklen -> CSocklen -> CSocklen

min :: CSocklen -> CSocklen -> CSocklen

newtype CSpeed #

Constructors

CSpeed Word64 

Instances

Instances details
Enum CSpeed 
Instance details

Defined in GHC.Internal.System.Posix.Types

Storable CSpeed 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CSpeed -> Int

alignment :: CSpeed -> Int

peekElemOff :: Ptr CSpeed -> Int -> IO CSpeed

pokeElemOff :: Ptr CSpeed -> Int -> CSpeed -> IO ()

peekByteOff :: Ptr b -> Int -> IO CSpeed

pokeByteOff :: Ptr b -> Int -> CSpeed -> IO ()

peek :: Ptr CSpeed -> IO CSpeed

poke :: Ptr CSpeed -> CSpeed -> IO ()

Num CSpeed 
Instance details

Defined in GHC.Internal.System.Posix.Types

Read CSpeed 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CSpeed

readList :: ReadS [CSpeed]

readPrec :: ReadPrec CSpeed

readListPrec :: ReadPrec [CSpeed]

Real CSpeed 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CSpeed -> Rational

Show CSpeed 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CSpeed -> ShowS

show :: CSpeed -> String

showList :: [CSpeed] -> ShowS

Eq CSpeed 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CSpeed -> CSpeed -> Bool

(/=) :: CSpeed -> CSpeed -> Bool

Ord CSpeed 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CSpeed -> CSpeed -> Ordering

(<) :: CSpeed -> CSpeed -> Bool

(<=) :: CSpeed -> CSpeed -> Bool

(>) :: CSpeed -> CSpeed -> Bool

(>=) :: CSpeed -> CSpeed -> Bool

max :: CSpeed -> CSpeed -> CSpeed

min :: CSpeed -> CSpeed -> CSpeed

newtype CSsize #

Constructors

CSsize Int64 

Instances

Instances details
Bits CSsize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(.&.) :: CSsize -> CSsize -> CSsize

(.|.) :: CSsize -> CSsize -> CSsize

xor :: CSsize -> CSsize -> CSsize

complement :: CSsize -> CSsize

shift :: CSsize -> Int -> CSsize

rotate :: CSsize -> Int -> CSsize

zeroBits :: CSsize

bit :: Int -> CSsize

setBit :: CSsize -> Int -> CSsize

clearBit :: CSsize -> Int -> CSsize

complementBit :: CSsize -> Int -> CSsize

testBit :: CSsize -> Int -> Bool

bitSizeMaybe :: CSsize -> Maybe Int

bitSize :: CSsize -> Int

isSigned :: CSsize -> Bool

shiftL :: CSsize -> Int -> CSsize

unsafeShiftL :: CSsize -> Int -> CSsize

shiftR :: CSsize -> Int -> CSsize

unsafeShiftR :: CSsize -> Int -> CSsize

rotateL :: CSsize -> Int -> CSsize

rotateR :: CSsize -> Int -> CSsize

popCount :: CSsize -> Int

FiniteBits CSsize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Bounded CSsize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum CSsize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Storable CSsize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CSsize -> Int

alignment :: CSsize -> Int

peekElemOff :: Ptr CSsize -> Int -> IO CSsize

pokeElemOff :: Ptr CSsize -> Int -> CSsize -> IO ()

peekByteOff :: Ptr b -> Int -> IO CSsize

pokeByteOff :: Ptr b -> Int -> CSsize -> IO ()

peek :: Ptr CSsize -> IO CSsize

poke :: Ptr CSsize -> CSsize -> IO ()

Ix CSsize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

range :: (CSsize, CSsize) -> [CSsize]

index :: (CSsize, CSsize) -> CSsize -> Int

unsafeIndex :: (CSsize, CSsize) -> CSsize -> Int

inRange :: (CSsize, CSsize) -> CSsize -> Bool

rangeSize :: (CSsize, CSsize) -> Int

unsafeRangeSize :: (CSsize, CSsize) -> Int

Num CSsize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Read CSsize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CSsize

readList :: ReadS [CSsize]

readPrec :: ReadPrec CSsize

readListPrec :: ReadPrec [CSsize]

Integral CSsize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CSsize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CSsize -> Rational

Show CSsize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CSsize -> ShowS

show :: CSsize -> String

showList :: [CSsize] -> ShowS

Eq CSsize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CSsize -> CSsize -> Bool

(/=) :: CSsize -> CSsize -> Bool

Ord CSsize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CSsize -> CSsize -> Ordering

(<) :: CSsize -> CSsize -> Bool

(<=) :: CSsize -> CSsize -> Bool

(>) :: CSsize -> CSsize -> Bool

(>=) :: CSsize -> CSsize -> Bool

max :: CSsize -> CSsize -> CSsize

min :: CSsize -> CSsize -> CSsize

newtype CTcflag #

Constructors

CTcflag Word64 

Instances

Instances details
Bits CTcflag 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(.&.) :: CTcflag -> CTcflag -> CTcflag

(.|.) :: CTcflag -> CTcflag -> CTcflag

xor :: CTcflag -> CTcflag -> CTcflag

complement :: CTcflag -> CTcflag

shift :: CTcflag -> Int -> CTcflag

rotate :: CTcflag -> Int -> CTcflag

zeroBits :: CTcflag

bit :: Int -> CTcflag

setBit :: CTcflag -> Int -> CTcflag

clearBit :: CTcflag -> Int -> CTcflag

complementBit :: CTcflag -> Int -> CTcflag

testBit :: CTcflag -> Int -> Bool

bitSizeMaybe :: CTcflag -> Maybe Int

bitSize :: CTcflag -> Int

isSigned :: CTcflag -> Bool

shiftL :: CTcflag -> Int -> CTcflag

unsafeShiftL :: CTcflag -> Int -> CTcflag

shiftR :: CTcflag -> Int -> CTcflag

unsafeShiftR :: CTcflag -> Int -> CTcflag

rotateL :: CTcflag -> Int -> CTcflag

rotateR :: CTcflag -> Int -> CTcflag

popCount :: CTcflag -> Int

FiniteBits CTcflag 
Instance details

Defined in GHC.Internal.System.Posix.Types

Bounded CTcflag 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum CTcflag 
Instance details

Defined in GHC.Internal.System.Posix.Types

Storable CTcflag 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CTcflag -> Int

alignment :: CTcflag -> Int

peekElemOff :: Ptr CTcflag -> Int -> IO CTcflag

pokeElemOff :: Ptr CTcflag -> Int -> CTcflag -> IO ()

peekByteOff :: Ptr b -> Int -> IO CTcflag

pokeByteOff :: Ptr b -> Int -> CTcflag -> IO ()

peek :: Ptr CTcflag -> IO CTcflag

poke :: Ptr CTcflag -> CTcflag -> IO ()

Ix CTcflag 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CTcflag 
Instance details

Defined in GHC.Internal.System.Posix.Types

Read CTcflag 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CTcflag

readList :: ReadS [CTcflag]

readPrec :: ReadPrec CTcflag

readListPrec :: ReadPrec [CTcflag]

Integral CTcflag 
Instance details

Defined in GHC.Internal.System.Posix.Types

Real CTcflag 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CTcflag -> Rational

Show CTcflag 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CTcflag -> ShowS

show :: CTcflag -> String

showList :: [CTcflag] -> ShowS

Eq CTcflag 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CTcflag -> CTcflag -> Bool

(/=) :: CTcflag -> CTcflag -> Bool

Ord CTcflag 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CTcflag -> CTcflag -> Ordering

(<) :: CTcflag -> CTcflag -> Bool

(<=) :: CTcflag -> CTcflag -> Bool

(>) :: CTcflag -> CTcflag -> Bool

(>=) :: CTcflag -> CTcflag -> Bool

max :: CTcflag -> CTcflag -> CTcflag

min :: CTcflag -> CTcflag -> CTcflag

newtype CUid #

Constructors

CUid Word32 

Instances

Instances details
Bits CUid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(.&.) :: CUid -> CUid -> CUid

(.|.) :: CUid -> CUid -> CUid

xor :: CUid -> CUid -> CUid

complement :: CUid -> CUid

shift :: CUid -> Int -> CUid

rotate :: CUid -> Int -> CUid

zeroBits :: CUid

bit :: Int -> CUid

setBit :: CUid -> Int -> CUid

clearBit :: CUid -> Int -> CUid

complementBit :: CUid -> Int -> CUid

testBit :: CUid -> Int -> Bool

bitSizeMaybe :: CUid -> Maybe Int

bitSize :: CUid -> Int

isSigned :: CUid -> Bool

shiftL :: CUid -> Int -> CUid

unsafeShiftL :: CUid -> Int -> CUid

shiftR :: CUid -> Int -> CUid

unsafeShiftR :: CUid -> Int -> CUid

rotateL :: CUid -> Int -> CUid

rotateR :: CUid -> Int -> CUid

popCount :: CUid -> Int

FiniteBits CUid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

finiteBitSize :: CUid -> Int

countLeadingZeros :: CUid -> Int

countTrailingZeros :: CUid -> Int

Bounded CUid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Enum CUid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

succ :: CUid -> CUid

pred :: CUid -> CUid

toEnum :: Int -> CUid

fromEnum :: CUid -> Int

enumFrom :: CUid -> [CUid]

enumFromThen :: CUid -> CUid -> [CUid]

enumFromTo :: CUid -> CUid -> [CUid]

enumFromThenTo :: CUid -> CUid -> CUid -> [CUid]

Storable CUid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

sizeOf :: CUid -> Int

alignment :: CUid -> Int

peekElemOff :: Ptr CUid -> Int -> IO CUid

pokeElemOff :: Ptr CUid -> Int -> CUid -> IO ()

peekByteOff :: Ptr b -> Int -> IO CUid

pokeByteOff :: Ptr b -> Int -> CUid -> IO ()

peek :: Ptr CUid -> IO CUid

poke :: Ptr CUid -> CUid -> IO ()

Ix CUid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

range :: (CUid, CUid) -> [CUid]

index :: (CUid, CUid) -> CUid -> Int

unsafeIndex :: (CUid, CUid) -> CUid -> Int

inRange :: (CUid, CUid) -> CUid -> Bool

rangeSize :: (CUid, CUid) -> Int

unsafeRangeSize :: (CUid, CUid) -> Int

Num CUid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(+) :: CUid -> CUid -> CUid

(-) :: CUid -> CUid -> CUid

(*) :: CUid -> CUid -> CUid

negate :: CUid -> CUid

abs :: CUid -> CUid

signum :: CUid -> CUid

fromInteger :: Integer -> CUid

Read CUid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

readsPrec :: Int -> ReadS CUid

readList :: ReadS [CUid]

readPrec :: ReadPrec CUid

readListPrec :: ReadPrec [CUid]

Integral CUid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

quot :: CUid -> CUid -> CUid

rem :: CUid -> CUid -> CUid

div :: CUid -> CUid -> CUid

mod :: CUid -> CUid -> CUid

quotRem :: CUid -> CUid -> (CUid, CUid)

divMod :: CUid -> CUid -> (CUid, CUid)

toInteger :: CUid -> Integer

Real CUid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

toRational :: CUid -> Rational

Show CUid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

showsPrec :: Int -> CUid -> ShowS

show :: CUid -> String

showList :: [CUid] -> ShowS

Eq CUid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CUid -> CUid -> Bool

(/=) :: CUid -> CUid -> Bool

Ord CUid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CUid -> CUid -> Ordering

(<) :: CUid -> CUid -> Bool

(<=) :: CUid -> CUid -> Bool

(>) :: CUid -> CUid -> Bool

(>=) :: CUid -> CUid -> Bool

max :: CUid -> CUid -> CUid

min :: CUid -> CUid -> CUid