Copyright | (c) The University of Glasgow 2002 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | provisional |
Portability | non-portable (requires POSIX) |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
POSIX data types: Haskell equivalents of the types defined by the
<sys/types.h>
C header on a POSIX system.
- newtype CDev = CDev Word64
- newtype CIno = CIno Word64
- newtype CMode = CMode Word32
- newtype COff = COff Int64
- newtype CPid = CPid Int32
- newtype CSsize = CSsize Int64
- newtype CGid = CGid Word32
- newtype CNlink = CNlink Word64
- newtype CUid = CUid Word32
- newtype CCc = CCc Word8
- newtype CSpeed = CSpeed Word32
- newtype CTcflag = CTcflag Word32
- newtype CRLim = CRLim Word64
- newtype Fd = Fd CInt
- type LinkCount = CNlink
- type UserID = CUid
- type GroupID = CGid
- type ByteCount = CSize
- type ClockTick = CClock
- type EpochTime = CTime
- type FileOffset = COff
- type ProcessID = CPid
- type ProcessGroupID = CPid
- type DeviceID = CDev
- type FileID = CIno
- type FileMode = CMode
- type Limit = CLong
POSIX data types
Bounded CDev Source | |
Enum CDev Source | |
Eq CDev Source | |
Integral CDev Source | |
Num CDev Source | |
Ord CDev Source | |
Read CDev Source | |
Real CDev Source | |
toRational :: CDev -> Rational Source | |
Show CDev Source | |
FiniteBits CDev Source | |
finiteBitSize :: CDev -> Int Source countLeadingZeros :: CDev -> Int Source countTrailingZeros :: CDev -> Int Source | |
Bits CDev Source | |
(.&.) :: CDev -> CDev -> CDev Source (.|.) :: CDev -> CDev -> CDev Source xor :: CDev -> CDev -> CDev Source complement :: CDev -> CDev Source shift :: CDev -> Int -> CDev Source rotate :: CDev -> Int -> CDev Source setBit :: CDev -> Int -> CDev Source clearBit :: CDev -> Int -> CDev Source complementBit :: CDev -> Int -> CDev Source testBit :: CDev -> Int -> Bool Source bitSizeMaybe :: CDev -> Maybe Int Source isSigned :: CDev -> Bool Source shiftL :: CDev -> Int -> CDev Source unsafeShiftL :: CDev -> Int -> CDev Source shiftR :: CDev -> Int -> CDev Source unsafeShiftR :: CDev -> Int -> CDev Source rotateL :: CDev -> Int -> CDev Source | |
Storable CDev Source | |
Bounded CIno Source | |
Enum CIno Source | |
Eq CIno Source | |
Integral CIno Source | |
Num CIno Source | |
Ord CIno Source | |
Read CIno Source | |
Real CIno Source | |
toRational :: CIno -> Rational Source | |
Show CIno Source | |
FiniteBits CIno Source | |
finiteBitSize :: CIno -> Int Source countLeadingZeros :: CIno -> Int Source countTrailingZeros :: CIno -> Int Source | |
Bits CIno Source | |
(.&.) :: CIno -> CIno -> CIno Source (.|.) :: CIno -> CIno -> CIno Source xor :: CIno -> CIno -> CIno Source complement :: CIno -> CIno Source shift :: CIno -> Int -> CIno Source rotate :: CIno -> Int -> CIno Source setBit :: CIno -> Int -> CIno Source clearBit :: CIno -> Int -> CIno Source complementBit :: CIno -> Int -> CIno Source testBit :: CIno -> Int -> Bool Source bitSizeMaybe :: CIno -> Maybe Int Source isSigned :: CIno -> Bool Source shiftL :: CIno -> Int -> CIno Source unsafeShiftL :: CIno -> Int -> CIno Source shiftR :: CIno -> Int -> CIno Source unsafeShiftR :: CIno -> Int -> CIno Source rotateL :: CIno -> Int -> CIno Source | |
Storable CIno Source | |
Bounded COff Source | |
Enum COff Source | |
Eq COff Source | |
Integral COff Source | |
Num COff Source | |
Ord COff Source | |
Read COff Source | |
Real COff Source | |
toRational :: COff -> Rational Source | |
Show COff Source | |
FiniteBits COff Source | |
finiteBitSize :: COff -> Int Source countLeadingZeros :: COff -> Int Source countTrailingZeros :: COff -> Int Source | |
Bits COff Source | |
(.&.) :: COff -> COff -> COff Source (.|.) :: COff -> COff -> COff Source xor :: COff -> COff -> COff Source complement :: COff -> COff Source shift :: COff -> Int -> COff Source rotate :: COff -> Int -> COff Source setBit :: COff -> Int -> COff Source clearBit :: COff -> Int -> COff Source complementBit :: COff -> Int -> COff Source testBit :: COff -> Int -> Bool Source bitSizeMaybe :: COff -> Maybe Int Source isSigned :: COff -> Bool Source shiftL :: COff -> Int -> COff Source unsafeShiftL :: COff -> Int -> COff Source shiftR :: COff -> Int -> COff Source unsafeShiftR :: COff -> Int -> COff Source rotateL :: COff -> Int -> COff Source | |
Storable COff Source | |
Bounded CPid Source | |
Enum CPid Source | |
Eq CPid Source | |
Integral CPid Source | |
Num CPid Source | |
Ord CPid Source | |
Read CPid Source | |
Real CPid Source | |
toRational :: CPid -> Rational Source | |
Show CPid Source | |
FiniteBits CPid Source | |
finiteBitSize :: CPid -> Int Source countLeadingZeros :: CPid -> Int Source countTrailingZeros :: CPid -> Int Source | |
Bits CPid Source | |
(.&.) :: CPid -> CPid -> CPid Source (.|.) :: CPid -> CPid -> CPid Source xor :: CPid -> CPid -> CPid Source complement :: CPid -> CPid Source shift :: CPid -> Int -> CPid Source rotate :: CPid -> Int -> CPid Source setBit :: CPid -> Int -> CPid Source clearBit :: CPid -> Int -> CPid Source complementBit :: CPid -> Int -> CPid Source testBit :: CPid -> Int -> Bool Source bitSizeMaybe :: CPid -> Maybe Int Source isSigned :: CPid -> Bool Source shiftL :: CPid -> Int -> CPid Source unsafeShiftL :: CPid -> Int -> CPid Source shiftR :: CPid -> Int -> CPid Source unsafeShiftR :: CPid -> Int -> CPid Source rotateL :: CPid -> Int -> CPid Source | |
Storable CPid Source | |
Bounded CGid Source | |
Enum CGid Source | |
Eq CGid Source | |
Integral CGid Source | |
Num CGid Source | |
Ord CGid Source | |
Read CGid Source | |
Real CGid Source | |
toRational :: CGid -> Rational Source | |
Show CGid Source | |
FiniteBits CGid Source | |
finiteBitSize :: CGid -> Int Source countLeadingZeros :: CGid -> Int Source countTrailingZeros :: CGid -> Int Source | |
Bits CGid Source | |
(.&.) :: CGid -> CGid -> CGid Source (.|.) :: CGid -> CGid -> CGid Source xor :: CGid -> CGid -> CGid Source complement :: CGid -> CGid Source shift :: CGid -> Int -> CGid Source rotate :: CGid -> Int -> CGid Source setBit :: CGid -> Int -> CGid Source clearBit :: CGid -> Int -> CGid Source complementBit :: CGid -> Int -> CGid Source testBit :: CGid -> Int -> Bool Source bitSizeMaybe :: CGid -> Maybe Int Source isSigned :: CGid -> Bool Source shiftL :: CGid -> Int -> CGid Source unsafeShiftL :: CGid -> Int -> CGid Source shiftR :: CGid -> Int -> CGid Source unsafeShiftR :: CGid -> Int -> CGid Source rotateL :: CGid -> Int -> CGid Source | |
Storable CGid Source | |
Bounded CUid Source | |
Enum CUid Source | |
Eq CUid Source | |
Integral CUid Source | |
Num CUid Source | |
Ord CUid Source | |
Read CUid Source | |
Real CUid Source | |
toRational :: CUid -> Rational Source | |
Show CUid Source | |
FiniteBits CUid Source | |
finiteBitSize :: CUid -> Int Source countLeadingZeros :: CUid -> Int Source countTrailingZeros :: CUid -> Int Source | |
Bits CUid Source | |
(.&.) :: CUid -> CUid -> CUid Source (.|.) :: CUid -> CUid -> CUid Source xor :: CUid -> CUid -> CUid Source complement :: CUid -> CUid Source shift :: CUid -> Int -> CUid Source rotate :: CUid -> Int -> CUid Source setBit :: CUid -> Int -> CUid Source clearBit :: CUid -> Int -> CUid Source complementBit :: CUid -> Int -> CUid Source testBit :: CUid -> Int -> Bool Source bitSizeMaybe :: CUid -> Maybe Int Source isSigned :: CUid -> Bool Source shiftL :: CUid -> Int -> CUid Source unsafeShiftL :: CUid -> Int -> CUid Source shiftR :: CUid -> Int -> CUid Source unsafeShiftR :: CUid -> Int -> CUid Source rotateL :: CUid -> Int -> CUid Source | |
Storable CUid Source | |
Enum CCc Source | |
Eq CCc Source | |
Num CCc Source | |
Ord CCc Source | |
Read CCc Source | |
Real CCc Source | |
toRational :: CCc -> Rational Source | |
Show CCc Source | |
Storable CCc Source | |
Enum CSpeed Source | |
succ :: CSpeed -> CSpeed Source pred :: CSpeed -> CSpeed Source toEnum :: Int -> CSpeed Source fromEnum :: CSpeed -> Int Source enumFrom :: CSpeed -> [CSpeed] Source enumFromThen :: CSpeed -> CSpeed -> [CSpeed] Source enumFromTo :: CSpeed -> CSpeed -> [CSpeed] Source enumFromThenTo :: CSpeed -> CSpeed -> CSpeed -> [CSpeed] Source | |
Eq CSpeed Source | |
Num CSpeed Source | |
Ord CSpeed Source | |
Read CSpeed Source | |
Real CSpeed Source | |
toRational :: CSpeed -> Rational Source | |
Show CSpeed Source | |
Storable CSpeed Source | |
sizeOf :: CSpeed -> Int Source alignment :: CSpeed -> Int Source peekElemOff :: Ptr CSpeed -> Int -> IO CSpeed Source pokeElemOff :: Ptr CSpeed -> Int -> CSpeed -> IO () Source peekByteOff :: Ptr b -> Int -> IO CSpeed Source pokeByteOff :: Ptr b -> Int -> CSpeed -> IO () Source |
Bounded Fd Source | |
Enum Fd Source | |
Eq Fd Source | |
Integral Fd Source | |
Num Fd Source | |
Ord Fd Source | |
Read Fd Source | |
Real Fd Source | |
toRational :: Fd -> Rational Source | |
Show Fd Source | |
FiniteBits Fd Source | |
finiteBitSize :: Fd -> Int Source countLeadingZeros :: Fd -> Int Source countTrailingZeros :: Fd -> Int Source | |
Bits Fd Source | |
(.&.) :: Fd -> Fd -> Fd Source (.|.) :: Fd -> Fd -> Fd Source complement :: Fd -> Fd Source shift :: Fd -> Int -> Fd Source rotate :: Fd -> Int -> Fd Source setBit :: Fd -> Int -> Fd Source clearBit :: Fd -> Int -> Fd Source complementBit :: Fd -> Int -> Fd Source testBit :: Fd -> Int -> Bool Source bitSizeMaybe :: Fd -> Maybe Int Source shiftL :: Fd -> Int -> Fd Source unsafeShiftL :: Fd -> Int -> Fd Source shiftR :: Fd -> Int -> Fd Source unsafeShiftR :: Fd -> Int -> Fd Source rotateL :: Fd -> Int -> Fd Source | |
Storable Fd Source | |
type FileOffset = COff Source
type ProcessGroupID = CPid Source