Copyright | Copyright (C) 2005-2011 John Goerzen |
---|---|
License | BSD-3-Clause |
Stability | stable |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
System.IO.PlafCompat
Description
On Unix, exports System.Posix.Types and System.Posix.Files.
On Windows, exports System.Posix.Types and System.IO.WindowsCompat.
The result should be roughly the same set of defined variables and types.
Synopsis
- nullFileName :: String
- createLink :: FilePath -> FilePath -> IO ()
- createSymbolicLink :: FilePath -> FilePath -> IO ()
- getSymbolicLinkStatus :: FilePath -> IO FileStatus
- readSymbolicLink :: FilePath -> IO FilePath
- accessTime :: FileStatus -> EpochTime
- deviceID :: FileStatus -> DeviceID
- fileGroup :: FileStatus -> GroupID
- fileID :: FileStatus -> FileID
- fileMode :: FileStatus -> FileMode
- fileOwner :: FileStatus -> UserID
- fileSize :: FileStatus -> FileOffset
- getFileStatus :: FilePath -> IO FileStatus
- isBlockDevice :: FileStatus -> Bool
- isCharacterDevice :: FileStatus -> Bool
- isDirectory :: FileStatus -> Bool
- isNamedPipe :: FileStatus -> Bool
- isRegularFile :: FileStatus -> Bool
- isSocket :: FileStatus -> Bool
- isSymbolicLink :: FileStatus -> Bool
- linkCount :: FileStatus -> LinkCount
- modificationTime :: FileStatus -> EpochTime
- specialDeviceID :: FileStatus -> DeviceID
- statusChangeTime :: FileStatus -> EpochTime
- newtype FileStatus = FileStatus (ForeignPtr CStat)
- groupExecuteMode :: FileMode
- groupReadMode :: FileMode
- groupWriteMode :: FileMode
- intersectFileModes :: FileMode -> FileMode -> FileMode
- otherExecuteMode :: FileMode
- otherReadMode :: FileMode
- otherWriteMode :: FileMode
- ownerExecuteMode :: FileMode
- ownerReadMode :: FileMode
- ownerWriteMode :: FileMode
- setGroupIDMode :: FileMode
- setUserIDMode :: FileMode
- blockSpecialMode :: FileMode
- characterSpecialMode :: FileMode
- namedPipeMode :: FileMode
- regularFileMode :: FileMode
- directoryMode :: FileMode
- fileTypeModes :: FileMode
- socketMode :: FileMode
- symbolicLinkMode :: FileMode
- data PathVar
- newtype CAttributes = CAttributes Word64
- pattern DontSync :: StatxFlags
- pattern EmptyPath :: StatxFlags
- newtype ExtendedFileStatus = ExtendedFileStatus (ForeignPtr CStatx)
- pattern ForceSync :: StatxFlags
- pattern NoAutoMount :: StatxFlags
- pattern StatxAll :: StatxMask
- pattern StatxAtime :: StatxMask
- pattern StatxBasicStats :: StatxMask
- pattern StatxBlocks :: StatxMask
- pattern StatxBtime :: StatxMask
- pattern StatxCtime :: StatxMask
- newtype StatxFlags = StatxFlags CInt
- pattern StatxGid :: StatxMask
- pattern StatxIno :: StatxMask
- newtype StatxMask = StatxMask CInt
- pattern StatxMntId :: StatxMask
- pattern StatxMode :: StatxMask
- pattern StatxMtime :: StatxMask
- pattern StatxNlink :: StatxMask
- pattern StatxSize :: StatxMask
- pattern StatxType :: StatxMask
- pattern StatxUid :: StatxMask
- pattern SymlinkNoFollow :: StatxFlags
- pattern SyncAsStat :: StatxFlags
- accessModes :: FileMode
- accessTimeHiRes :: FileStatus -> POSIXTime
- accessTimeHiResX :: ExtendedFileStatus -> POSIXTime
- creationTimeHiResX :: ExtendedFileStatus -> POSIXTime
- defaultStatxFlags :: StatxFlags
- defaultStatxMask :: StatxMask
- deviceIDX :: ExtendedFileStatus -> DeviceID
- fileAppendX :: ExtendedFileStatus -> Bool
- fileBlockSize :: FileStatus -> Maybe CBlkSize
- fileBlockSizeX :: ExtendedFileStatus -> CBlkSize
- fileBlocks :: FileStatus -> Maybe CBlkCnt
- fileBlocksX :: ExtendedFileStatus -> Word64
- fileCompressedX :: ExtendedFileStatus -> Bool
- fileDaxX :: ExtendedFileStatus -> Bool
- fileEncryptedX :: ExtendedFileStatus -> Bool
- fileGroupX :: ExtendedFileStatus -> GroupID
- fileIDX :: ExtendedFileStatus -> FileID
- fileImmutableX :: ExtendedFileStatus -> Bool
- fileModeX :: ExtendedFileStatus -> FileMode
- fileNoDumpX :: ExtendedFileStatus -> Bool
- fileOwnerX :: ExtendedFileStatus -> UserID
- fileSizeX :: ExtendedFileStatus -> Word64
- fileVerityX :: ExtendedFileStatus -> Bool
- getFdPathVar :: Fd -> PathVar -> IO Limit
- getFdStatus :: Fd -> IO FileStatus
- groupModes :: FileMode
- haveStatx :: Bool
- isBlockDeviceX :: ExtendedFileStatus -> Bool
- isCharacterDeviceX :: ExtendedFileStatus -> Bool
- isDirectoryX :: ExtendedFileStatus -> Bool
- isNamedPipeX :: ExtendedFileStatus -> Bool
- isRegularFileX :: ExtendedFileStatus -> Bool
- isSocketX :: ExtendedFileStatus -> Bool
- isSymbolicLinkX :: ExtendedFileStatus -> Bool
- linkCountX :: ExtendedFileStatus -> CNlink
- modificationTimeHiRes :: FileStatus -> POSIXTime
- modificationTimeHiResX :: ExtendedFileStatus -> POSIXTime
- mountIDX :: ExtendedFileStatus -> Word64
- nullFileMode :: FileMode
- otherModes :: FileMode
- ownerModes :: FileMode
- setFdMode :: Fd -> FileMode -> IO ()
- setFdOwnerAndGroup :: Fd -> UserID -> GroupID -> IO ()
- setFdSize :: Fd -> FileOffset -> IO ()
- setFdTimesHiRes :: Fd -> POSIXTime -> POSIXTime -> IO ()
- setFileCreationMask :: FileMode -> IO FileMode
- specialDeviceIDX :: ExtendedFileStatus -> DeviceID
- statusChangeTimeHiRes :: FileStatus -> POSIXTime
- statusChangeTimeHiResX :: ExtendedFileStatus -> POSIXTime
- stdFileMode :: FileMode
- touchFd :: Fd -> IO ()
- unionFileModes :: FileMode -> FileMode -> FileMode
- rename :: FilePath -> FilePath -> IO ()
- createDevice :: FilePath -> FileMode -> DeviceID -> IO ()
- createNamedPipe :: FilePath -> FileMode -> IO ()
- fileAccess :: FilePath -> Bool -> Bool -> Bool -> IO Bool
- fileExist :: FilePath -> IO Bool
- getExtendedFileStatus :: Maybe Fd -> FilePath -> StatxFlags -> StatxMask -> IO ExtendedFileStatus
- getPathVar :: FilePath -> PathVar -> IO Limit
- removeLink :: FilePath -> IO ()
- setFileMode :: FilePath -> FileMode -> IO ()
- setFileSize :: FilePath -> FileOffset -> IO ()
- setFileTimes :: FilePath -> EpochTime -> EpochTime -> IO ()
- setFileTimesHiRes :: FilePath -> POSIXTime -> POSIXTime -> IO ()
- setOwnerAndGroup :: FilePath -> UserID -> GroupID -> IO ()
- setSymbolicLinkOwnerAndGroup :: FilePath -> UserID -> GroupID -> IO ()
- setSymbolicLinkTimesHiRes :: FilePath -> POSIXTime -> POSIXTime -> IO ()
- touchFile :: FilePath -> IO ()
- touchSymbolicLink :: FilePath -> IO ()
- newtype Fd = Fd CInt
- type ProcessID = CPid
- type DeviceID = CDev
- type FileID = CIno
- type FileMode = CMode
- type LinkCount = CNlink
- type UserID = CUid
- type GroupID = CGid
- type FileOffset = COff
- type EpochTime = CTime
- type ProcessGroupID = CPid
- type ByteCount = CSize
- newtype CSsize = CSsize Int64
- newtype CBlkCnt = CBlkCnt Int64
- newtype CBlkSize = CBlkSize Int32
- newtype CCc = CCc Word8
- newtype CClockId = CClockId Word32
- newtype CDev = CDev Int32
- newtype CFsBlkCnt = CFsBlkCnt Word32
- newtype CFsFilCnt = CFsFilCnt Word32
- newtype CGid = CGid Word32
- newtype CId = CId Word32
- newtype CIno = CIno Word64
- newtype CKey = CKey Int32
- newtype CMode = CMode Word16
- newtype CNfds = CNfds Word32
- newtype CNlink = CNlink Word16
- newtype COff = COff Int64
- newtype CPid = CPid Int32
- newtype CRLim = CRLim Word64
- newtype CSocklen = CSocklen Word32
- newtype CSpeed = CSpeed Word64
- newtype CTcflag = CTcflag Word64
- newtype CUid = CUid Word32
- type ClockTick = CClock
- type Limit = CLong
Documentation
nullFileName :: String Source #
The name of the null device. NUL: on Windows, /dev/null everywhere else.
createLink :: FilePath -> FilePath -> IO () #
createSymbolicLink :: FilePath -> FilePath -> IO () #
getSymbolicLinkStatus :: FilePath -> IO FileStatus #
readSymbolicLink :: FilePath -> IO FilePath #
accessTime :: FileStatus -> EpochTime #
deviceID :: FileStatus -> DeviceID #
fileGroup :: FileStatus -> GroupID #
fileID :: FileStatus -> FileID #
fileMode :: FileStatus -> FileMode #
fileOwner :: FileStatus -> UserID #
fileSize :: FileStatus -> FileOffset #
getFileStatus :: FilePath -> IO FileStatus #
isBlockDevice :: FileStatus -> Bool #
isCharacterDevice :: FileStatus -> Bool #
isDirectory :: FileStatus -> Bool #
isNamedPipe :: FileStatus -> Bool #
isRegularFile :: FileStatus -> Bool #
isSocket :: FileStatus -> Bool #
isSymbolicLink :: FileStatus -> Bool #
linkCount :: FileStatus -> LinkCount #
modificationTime :: FileStatus -> EpochTime #
specialDeviceID :: FileStatus -> DeviceID #
statusChangeTime :: FileStatus -> EpochTime #
newtype FileStatus #
Constructors
FileStatus (ForeignPtr CStat) |
Instances
intersectFileModes :: FileMode -> FileMode -> FileMode #
socketMode :: FileMode #
newtype CAttributes #
Constructors
CAttributes Word64 |
Instances
pattern DontSync :: StatxFlags #
pattern EmptyPath :: StatxFlags #
newtype ExtendedFileStatus #
Constructors
ExtendedFileStatus (ForeignPtr CStatx) |
pattern ForceSync :: StatxFlags #
pattern NoAutoMount :: StatxFlags #
pattern StatxAtime :: StatxMask #
pattern StatxBasicStats :: StatxMask #
pattern StatxBlocks :: StatxMask #
pattern StatxBtime :: StatxMask #
pattern StatxCtime :: StatxMask #
newtype StatxFlags #
Constructors
StatxFlags CInt |
Instances
Constructors
StatxMask CInt |
Instances
pattern StatxMntId :: StatxMask #
pattern StatxMtime :: StatxMask #
pattern StatxNlink :: StatxMask #
pattern SymlinkNoFollow :: StatxFlags #
pattern SyncAsStat :: StatxFlags #
accessModes :: FileMode #
accessTimeHiRes :: FileStatus -> POSIXTime #
accessTimeHiResX :: ExtendedFileStatus -> POSIXTime #
creationTimeHiResX :: ExtendedFileStatus -> POSIXTime #
deviceIDX :: ExtendedFileStatus -> DeviceID #
fileAppendX :: ExtendedFileStatus -> Bool #
fileBlockSize :: FileStatus -> Maybe CBlkSize #
fileBlocks :: FileStatus -> Maybe CBlkCnt #
fileBlocksX :: ExtendedFileStatus -> Word64 #
fileCompressedX :: ExtendedFileStatus -> Bool #
fileDaxX :: ExtendedFileStatus -> Bool #
fileEncryptedX :: ExtendedFileStatus -> Bool #
fileGroupX :: ExtendedFileStatus -> GroupID #
fileIDX :: ExtendedFileStatus -> FileID #
fileImmutableX :: ExtendedFileStatus -> Bool #
fileModeX :: ExtendedFileStatus -> FileMode #
fileNoDumpX :: ExtendedFileStatus -> Bool #
fileOwnerX :: ExtendedFileStatus -> UserID #
fileSizeX :: ExtendedFileStatus -> Word64 #
fileVerityX :: ExtendedFileStatus -> Bool #
getFdPathVar :: Fd -> PathVar -> IO Limit #
getFdStatus :: Fd -> IO FileStatus #
groupModes :: FileMode #
isBlockDeviceX :: ExtendedFileStatus -> Bool #
isCharacterDeviceX :: ExtendedFileStatus -> Bool #
isDirectoryX :: ExtendedFileStatus -> Bool #
isNamedPipeX :: ExtendedFileStatus -> Bool #
isRegularFileX :: ExtendedFileStatus -> Bool #
isSocketX :: ExtendedFileStatus -> Bool #
isSymbolicLinkX :: ExtendedFileStatus -> Bool #
linkCountX :: ExtendedFileStatus -> CNlink #
modificationTimeHiRes :: FileStatus -> POSIXTime #
modificationTimeHiResX :: ExtendedFileStatus -> POSIXTime #
mountIDX :: ExtendedFileStatus -> Word64 #
otherModes :: FileMode #
ownerModes :: FileMode #
setFdOwnerAndGroup :: Fd -> UserID -> GroupID -> IO () #
setFdSize :: Fd -> FileOffset -> IO () #
setFdTimesHiRes :: Fd -> POSIXTime -> POSIXTime -> IO () #
setFileCreationMask :: FileMode -> IO FileMode #
statusChangeTimeHiRes :: FileStatus -> POSIXTime #
statusChangeTimeHiResX :: ExtendedFileStatus -> POSIXTime #
stdFileMode :: FileMode #
unionFileModes :: FileMode -> FileMode -> FileMode #
createDevice :: FilePath -> FileMode -> DeviceID -> IO () #
createNamedPipe :: FilePath -> FileMode -> IO () #
fileAccess :: FilePath -> Bool -> Bool -> Bool -> IO Bool #
getExtendedFileStatus :: Maybe Fd -> FilePath -> StatxFlags -> StatxMask -> IO ExtendedFileStatus #
getPathVar :: FilePath -> PathVar -> IO Limit #
removeLink :: FilePath -> IO () #
setFileMode :: FilePath -> FileMode -> IO () #
setFileSize :: FilePath -> FileOffset -> IO () #
setFileTimes :: FilePath -> EpochTime -> EpochTime -> IO () #
setFileTimesHiRes :: FilePath -> POSIXTime -> POSIXTime -> IO () #
setOwnerAndGroup :: FilePath -> UserID -> GroupID -> IO () #
setSymbolicLinkOwnerAndGroup :: FilePath -> UserID -> GroupID -> IO () #
setSymbolicLinkTimesHiRes :: FilePath -> POSIXTime -> POSIXTime -> IO () #
touchSymbolicLink :: FilePath -> IO () #
Constructors
Fd CInt |
Instances
Bits Fd | |
Defined in GHC.Internal.System.Posix.Types Methods complement :: Fd -> Fd complementBit :: Fd -> Int -> Fd bitSizeMaybe :: Fd -> Maybe Int unsafeShiftL :: Fd -> Int -> Fd unsafeShiftR :: Fd -> Int -> Fd | |
FiniteBits Fd | |
Defined in GHC.Internal.System.Posix.Types | |
Bounded Fd | |
Defined in GHC.Internal.System.Posix.Types | |
Enum Fd | |
Storable Fd | |
Defined in GHC.Internal.System.Posix.Types Methods peekElemOff :: Ptr Fd -> Int -> IO Fd pokeElemOff :: Ptr Fd -> Int -> Fd -> IO () peekByteOff :: Ptr b -> Int -> IO Fd pokeByteOff :: Ptr b -> Int -> Fd -> IO () | |
Ix Fd | |
Num Fd | |
Read Fd | |
Defined in GHC.Internal.System.Posix.Types | |
Integral Fd | |
Real Fd | |
Defined in GHC.Internal.System.Posix.Types Methods toRational :: Fd -> Rational | |
Show Fd | |
Eq Fd | |
Ord Fd | |
type FileOffset = COff #
type ProcessGroupID = CPid #
Constructors
CSsize Int64 |
Instances
Constructors
CBlkCnt Int64 |
Instances
Constructors
CBlkSize Int32 |
Instances
Constructors
CCc Word8 |
Instances
Enum CCc | |
Storable CCc | |
Defined in GHC.Internal.System.Posix.Types Methods peekElemOff :: Ptr CCc -> Int -> IO CCc pokeElemOff :: Ptr CCc -> Int -> CCc -> IO () peekByteOff :: Ptr b -> Int -> IO CCc pokeByteOff :: Ptr b -> Int -> CCc -> IO () | |
Num CCc | |
Read CCc | |
Defined in GHC.Internal.System.Posix.Types | |
Real CCc | |
Defined in GHC.Internal.System.Posix.Types Methods toRational :: CCc -> Rational | |
Show CCc | |
Eq CCc | |
Ord CCc | |
Constructors
CClockId Word32 |
Instances
Constructors
CDev Int32 |
Instances
Bits CDev | |
Defined in GHC.Internal.System.Posix.Types Methods complement :: CDev -> CDev clearBit :: CDev -> Int -> CDev complementBit :: CDev -> Int -> CDev testBit :: CDev -> Int -> Bool bitSizeMaybe :: CDev -> Maybe Int unsafeShiftL :: CDev -> Int -> CDev unsafeShiftR :: CDev -> Int -> CDev rotateL :: CDev -> Int -> CDev | |
FiniteBits CDev | |
Defined in GHC.Internal.System.Posix.Types Methods finiteBitSize :: CDev -> Int countLeadingZeros :: CDev -> Int countTrailingZeros :: CDev -> Int | |
Bounded CDev | |
Defined in GHC.Internal.System.Posix.Types | |
Enum CDev | |
Storable CDev | |
Defined in GHC.Internal.System.Posix.Types Methods peekElemOff :: Ptr CDev -> Int -> IO CDev pokeElemOff :: Ptr CDev -> Int -> CDev -> IO () peekByteOff :: Ptr b -> Int -> IO CDev pokeByteOff :: Ptr b -> Int -> CDev -> IO () | |
Ix CDev | |
Num CDev | |
Read CDev | |
Defined in GHC.Internal.System.Posix.Types | |
Integral CDev | |
Real CDev | |
Defined in GHC.Internal.System.Posix.Types Methods toRational :: CDev -> Rational | |
Show CDev | |
Eq CDev | |
Ord CDev | |
Constructors
CFsBlkCnt Word32 |
Instances
Constructors
CFsFilCnt Word32 |
Instances
Constructors
CGid Word32 |
Instances
Bits CGid | |
Defined in GHC.Internal.System.Posix.Types Methods complement :: CGid -> CGid clearBit :: CGid -> Int -> CGid complementBit :: CGid -> Int -> CGid testBit :: CGid -> Int -> Bool bitSizeMaybe :: CGid -> Maybe Int unsafeShiftL :: CGid -> Int -> CGid unsafeShiftR :: CGid -> Int -> CGid rotateL :: CGid -> Int -> CGid | |
FiniteBits CGid | |
Defined in GHC.Internal.System.Posix.Types Methods finiteBitSize :: CGid -> Int countLeadingZeros :: CGid -> Int countTrailingZeros :: CGid -> Int | |
Bounded CGid | |
Defined in GHC.Internal.System.Posix.Types | |
Enum CGid | |
Storable CGid | |
Defined in GHC.Internal.System.Posix.Types Methods peekElemOff :: Ptr CGid -> Int -> IO CGid pokeElemOff :: Ptr CGid -> Int -> CGid -> IO () peekByteOff :: Ptr b -> Int -> IO CGid pokeByteOff :: Ptr b -> Int -> CGid -> IO () | |
Ix CGid | |
Num CGid | |
Read CGid | |
Defined in GHC.Internal.System.Posix.Types | |
Integral CGid | |
Real CGid | |
Defined in GHC.Internal.System.Posix.Types Methods toRational :: CGid -> Rational | |
Show CGid | |
Eq CGid | |
Ord CGid | |
Constructors
CId Word32 |
Instances
Bits CId | |
Defined in GHC.Internal.System.Posix.Types Methods complement :: CId -> CId complementBit :: CId -> Int -> CId bitSizeMaybe :: CId -> Maybe Int unsafeShiftL :: CId -> Int -> CId unsafeShiftR :: CId -> Int -> CId | |
FiniteBits CId | |
Defined in GHC.Internal.System.Posix.Types | |
Bounded CId | |
Defined in GHC.Internal.System.Posix.Types | |
Enum CId | |
Storable CId | |
Defined in GHC.Internal.System.Posix.Types Methods peekElemOff :: Ptr CId -> Int -> IO CId pokeElemOff :: Ptr CId -> Int -> CId -> IO () peekByteOff :: Ptr b -> Int -> IO CId pokeByteOff :: Ptr b -> Int -> CId -> IO () | |
Ix CId | |
Num CId | |
Read CId | |
Defined in GHC.Internal.System.Posix.Types | |
Integral CId | |
Real CId | |
Defined in GHC.Internal.System.Posix.Types Methods toRational :: CId -> Rational | |
Show CId | |
Eq CId | |
Ord CId | |
Constructors
CIno Word64 |
Instances
Bits CIno | |
Defined in GHC.Internal.System.Posix.Types Methods complement :: CIno -> CIno clearBit :: CIno -> Int -> CIno complementBit :: CIno -> Int -> CIno testBit :: CIno -> Int -> Bool bitSizeMaybe :: CIno -> Maybe Int unsafeShiftL :: CIno -> Int -> CIno unsafeShiftR :: CIno -> Int -> CIno rotateL :: CIno -> Int -> CIno | |
FiniteBits CIno | |
Defined in GHC.Internal.System.Posix.Types Methods finiteBitSize :: CIno -> Int countLeadingZeros :: CIno -> Int countTrailingZeros :: CIno -> Int | |
Bounded CIno | |
Defined in GHC.Internal.System.Posix.Types | |
Enum CIno | |
Storable CIno | |
Defined in GHC.Internal.System.Posix.Types Methods peekElemOff :: Ptr CIno -> Int -> IO CIno pokeElemOff :: Ptr CIno -> Int -> CIno -> IO () peekByteOff :: Ptr b -> Int -> IO CIno pokeByteOff :: Ptr b -> Int -> CIno -> IO () | |
Ix CIno | |
Num CIno | |
Read CIno | |
Defined in GHC.Internal.System.Posix.Types | |
Integral CIno | |
Real CIno | |
Defined in GHC.Internal.System.Posix.Types Methods toRational :: CIno -> Rational | |
Show CIno | |
Eq CIno | |
Ord CIno | |
Constructors
CKey Int32 |
Instances
Bits CKey | |
Defined in GHC.Internal.System.Posix.Types Methods complement :: CKey -> CKey clearBit :: CKey -> Int -> CKey complementBit :: CKey -> Int -> CKey testBit :: CKey -> Int -> Bool bitSizeMaybe :: CKey -> Maybe Int unsafeShiftL :: CKey -> Int -> CKey unsafeShiftR :: CKey -> Int -> CKey rotateL :: CKey -> Int -> CKey | |
FiniteBits CKey | |
Defined in GHC.Internal.System.Posix.Types Methods finiteBitSize :: CKey -> Int countLeadingZeros :: CKey -> Int countTrailingZeros :: CKey -> Int | |
Bounded CKey | |
Defined in GHC.Internal.System.Posix.Types | |
Enum CKey | |
Storable CKey | |
Defined in GHC.Internal.System.Posix.Types Methods peekElemOff :: Ptr CKey -> Int -> IO CKey pokeElemOff :: Ptr CKey -> Int -> CKey -> IO () peekByteOff :: Ptr b -> Int -> IO CKey pokeByteOff :: Ptr b -> Int -> CKey -> IO () | |
Ix CKey | |
Num CKey | |
Read CKey | |
Defined in GHC.Internal.System.Posix.Types | |
Integral CKey | |
Real CKey | |
Defined in GHC.Internal.System.Posix.Types Methods toRational :: CKey -> Rational | |
Show CKey | |
Eq CKey | |
Ord CKey | |
Constructors
CMode Word16 |
Instances
Constructors
CNfds Word32 |
Instances
Constructors
CNlink Word16 |
Instances
Constructors
COff Int64 |
Instances
Bits COff | |
Defined in GHC.Internal.System.Posix.Types Methods complement :: COff -> COff clearBit :: COff -> Int -> COff complementBit :: COff -> Int -> COff testBit :: COff -> Int -> Bool bitSizeMaybe :: COff -> Maybe Int unsafeShiftL :: COff -> Int -> COff unsafeShiftR :: COff -> Int -> COff rotateL :: COff -> Int -> COff | |
FiniteBits COff | |
Defined in GHC.Internal.System.Posix.Types Methods finiteBitSize :: COff -> Int countLeadingZeros :: COff -> Int countTrailingZeros :: COff -> Int | |
Bounded COff | |
Defined in GHC.Internal.System.Posix.Types | |
Enum COff | |
Storable COff | |
Defined in GHC.Internal.System.Posix.Types Methods peekElemOff :: Ptr COff -> Int -> IO COff pokeElemOff :: Ptr COff -> Int -> COff -> IO () peekByteOff :: Ptr b -> Int -> IO COff pokeByteOff :: Ptr b -> Int -> COff -> IO () | |
Ix COff | |
Num COff | |
Read COff | |
Defined in GHC.Internal.System.Posix.Types | |
Integral COff | |
Real COff | |
Defined in GHC.Internal.System.Posix.Types Methods toRational :: COff -> Rational | |
Show COff | |
Eq COff | |
Ord COff | |
Constructors
CPid Int32 |
Instances
Bits CPid | |
Defined in GHC.Internal.System.Posix.Types Methods complement :: CPid -> CPid clearBit :: CPid -> Int -> CPid complementBit :: CPid -> Int -> CPid testBit :: CPid -> Int -> Bool bitSizeMaybe :: CPid -> Maybe Int unsafeShiftL :: CPid -> Int -> CPid unsafeShiftR :: CPid -> Int -> CPid rotateL :: CPid -> Int -> CPid | |
FiniteBits CPid | |
Defined in GHC.Internal.System.Posix.Types Methods finiteBitSize :: CPid -> Int countLeadingZeros :: CPid -> Int countTrailingZeros :: CPid -> Int | |
Bounded CPid | |
Defined in GHC.Internal.System.Posix.Types | |
Enum CPid | |
Storable CPid | |
Defined in GHC.Internal.System.Posix.Types Methods peekElemOff :: Ptr CPid -> Int -> IO CPid pokeElemOff :: Ptr CPid -> Int -> CPid -> IO () peekByteOff :: Ptr b -> Int -> IO CPid pokeByteOff :: Ptr b -> Int -> CPid -> IO () | |
Ix CPid | |
Num CPid | |
Read CPid | |
Defined in GHC.Internal.System.Posix.Types | |
Integral CPid | |
Real CPid | |
Defined in GHC.Internal.System.Posix.Types Methods toRational :: CPid -> Rational | |
Show CPid | |
Eq CPid | |
Ord CPid | |
Constructors
CRLim Word64 |
Instances
Constructors
CSocklen Word32 |
Instances
Constructors
CSpeed Word64 |
Instances
Enum CSpeed | |
Defined in GHC.Internal.System.Posix.Types | |
Storable CSpeed | |
Defined in GHC.Internal.System.Posix.Types Methods peekElemOff :: Ptr CSpeed -> Int -> IO CSpeed pokeElemOff :: Ptr CSpeed -> Int -> CSpeed -> IO () peekByteOff :: Ptr b -> Int -> IO CSpeed pokeByteOff :: Ptr b -> Int -> CSpeed -> IO () | |
Num CSpeed | |
Read CSpeed | |
Defined in GHC.Internal.System.Posix.Types | |
Real CSpeed | |
Defined in GHC.Internal.System.Posix.Types Methods toRational :: CSpeed -> Rational | |
Show CSpeed | |
Eq CSpeed | |
Ord CSpeed | |
Constructors
CTcflag Word64 |
Instances
Constructors
CUid Word32 |
Instances
Bits CUid | |
Defined in GHC.Internal.System.Posix.Types Methods complement :: CUid -> CUid clearBit :: CUid -> Int -> CUid complementBit :: CUid -> Int -> CUid testBit :: CUid -> Int -> Bool bitSizeMaybe :: CUid -> Maybe Int unsafeShiftL :: CUid -> Int -> CUid unsafeShiftR :: CUid -> Int -> CUid rotateL :: CUid -> Int -> CUid | |
FiniteBits CUid | |
Defined in GHC.Internal.System.Posix.Types Methods finiteBitSize :: CUid -> Int countLeadingZeros :: CUid -> Int countTrailingZeros :: CUid -> Int | |
Bounded CUid | |
Defined in GHC.Internal.System.Posix.Types | |
Enum CUid | |
Storable CUid | |
Defined in GHC.Internal.System.Posix.Types Methods peekElemOff :: Ptr CUid -> Int -> IO CUid pokeElemOff :: Ptr CUid -> Int -> CUid -> IO () peekByteOff :: Ptr b -> Int -> IO CUid pokeByteOff :: Ptr b -> Int -> CUid -> IO () | |
Ix CUid | |
Num CUid | |
Read CUid | |
Defined in GHC.Internal.System.Posix.Types | |
Integral CUid | |
Real CUid | |
Defined in GHC.Internal.System.Posix.Types Methods toRational :: CUid -> Rational | |
Show CUid | |
Eq CUid | |
Ord CUid | |