| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
MMAP
Description
Provides mmap: mapping files into memory.
Synopsis
- data MmapException = MmapException
- data MunmapException = MunmapException {}
- c_mmap :: Ptr () -> CSize -> ProtOption -> MmapFlags -> Fd -> COff -> IO (Ptr ())
- c_munmap :: Ptr () -> CSize -> IO CInt
- mmap :: Ptr () -> CSize -> ProtOption -> MmapFlags -> Fd -> COff -> IO (Ptr ())
- munmap :: Ptr () -> CSize -> IO ()
- newtype ProtOption = ProtOption {
- unProtOption :: CInt
- protExec :: ProtOption
- protRead :: ProtOption
- protWrite :: ProtOption
- protNone :: ProtOption
- newtype MmapSharedFlag = MmapSharedFlag {}
- mapShared :: MmapSharedFlag
- mapPrivate :: MmapSharedFlag
- newtype MmapOptionalFlag = MmapOptionalFlag {}
- map32Bit :: MmapOptionalFlag
- mapAnonymous :: MmapOptionalFlag
- mapDenywrite :: MmapOptionalFlag
- mapFile :: MmapOptionalFlag
- mapFixed :: MmapOptionalFlag
- mapHugetlb :: MmapOptionalFlag
- mapLocked :: MmapOptionalFlag
- mapNonblock :: MmapOptionalFlag
- mapNoreserve :: MmapOptionalFlag
- mapStack :: MmapOptionalFlag
- newtype MmapFlags = MmapFlags {
- unMmapFlags :: CInt
- mkMmapFlags :: MmapSharedFlag -> MmapOptionalFlag -> MmapFlags
Documentation
data MmapException Source #
Exception thrown when mmap fails.
Constructors
| MmapException |
Instances
| Exception MmapException Source # | |
Defined in MMAP Methods toException :: MmapException -> SomeException # fromException :: SomeException -> Maybe MmapException # displayException :: MmapException -> String # | |
| Show MmapException Source # | |
Defined in MMAP Methods showsPrec :: Int -> MmapException -> ShowS # show :: MmapException -> String # showList :: [MmapException] -> ShowS # | |
| Eq MmapException Source # | |
Defined in MMAP Methods (==) :: MmapException -> MmapException -> Bool # (/=) :: MmapException -> MmapException -> Bool # | |
| Ord MmapException Source # | |
Defined in MMAP Methods compare :: MmapException -> MmapException -> Ordering # (<) :: MmapException -> MmapException -> Bool # (<=) :: MmapException -> MmapException -> Bool # (>) :: MmapException -> MmapException -> Bool # (>=) :: MmapException -> MmapException -> Bool # max :: MmapException -> MmapException -> MmapException # min :: MmapException -> MmapException -> MmapException # | |
data MunmapException Source #
Exception thrown when munmap fails.
Constructors
| MunmapException | |
Fields
| |
Instances
| Exception MunmapException Source # | |
Defined in MMAP Methods toException :: MunmapException -> SomeException # | |
| Show MunmapException Source # | |
Defined in MMAP Methods showsPrec :: Int -> MunmapException -> ShowS # show :: MunmapException -> String # showList :: [MunmapException] -> ShowS # | |
| Eq MunmapException Source # | |
Defined in MMAP Methods (==) :: MunmapException -> MunmapException -> Bool # (/=) :: MunmapException -> MunmapException -> Bool # | |
| Ord MunmapException Source # | |
Defined in MMAP Methods compare :: MunmapException -> MunmapException -> Ordering # (<) :: MunmapException -> MunmapException -> Bool # (<=) :: MunmapException -> MunmapException -> Bool # (>) :: MunmapException -> MunmapException -> Bool # (>=) :: MunmapException -> MunmapException -> Bool # max :: MunmapException -> MunmapException -> MunmapException # min :: MunmapException -> MunmapException -> MunmapException # | |
munmap - unmap mmap'ed memory.
This is the raw C function, and its return value must be checked
according to man mmap.
See munmap for a variant that turns bad return values into exceptions.
mmap :: Ptr () -> CSize -> ProtOption -> MmapFlags -> Fd -> COff -> IO (Ptr ()) Source #
Convenience around c_mmap, throwing a MmapException on a negative return value.
munmap :: Ptr () -> CSize -> IO () Source #
Convenience around c_munmap, throwing a MunmapException on a negative return value.
newtype ProtOption Source #
Describes the desired memory protection of the mapping (and must not conflict with the open mode of the file).
Constructors
| ProtOption | |
Fields
| |
Instances
| Monoid ProtOption Source # | |
Defined in MMAP Methods mempty :: ProtOption # mappend :: ProtOption -> ProtOption -> ProtOption # mconcat :: [ProtOption] -> ProtOption # | |
| Semigroup ProtOption Source # | |
Defined in MMAP Methods (<>) :: ProtOption -> ProtOption -> ProtOption # sconcat :: NonEmpty ProtOption -> ProtOption # stimes :: Integral b => b -> ProtOption -> ProtOption # | |
| Show ProtOption Source # | |
Defined in MMAP Methods showsPrec :: Int -> ProtOption -> ShowS # show :: ProtOption -> String # showList :: [ProtOption] -> ShowS # | |
| Eq ProtOption Source # | |
Defined in MMAP | |
| Ord ProtOption Source # | |
Defined in MMAP Methods compare :: ProtOption -> ProtOption -> Ordering # (<) :: ProtOption -> ProtOption -> Bool # (<=) :: ProtOption -> ProtOption -> Bool # (>) :: ProtOption -> ProtOption -> Bool # (>=) :: ProtOption -> ProtOption -> Bool # max :: ProtOption -> ProtOption -> ProtOption # min :: ProtOption -> ProtOption -> ProtOption # | |
protExec :: ProtOption Source #
Pages may be executed.
protRead :: ProtOption Source #
Pages may be read.
protWrite :: ProtOption Source #
Pages may be written.
protNone :: ProtOption Source #
Pages may not be accessed.
newtype MmapSharedFlag Source #
Determines whether updates to the mapping are visible to other processes mapping the same region, and whether updates are carried through to the underlying file.
This behavior is determined by including exactly one of
mapShared and mapPrivate.
Constructors
| MmapSharedFlag | |
Fields | |
Instances
mapShared :: MmapSharedFlag Source #
Share this mapping. Updates to the mapping are visible to
other processes that map the file, and are carried through to
the underlying file. The file may not actually be updated
until msync(2) or munmap() is called..
mapPrivate :: MmapSharedFlag Source #
Create a private copy-on-write mapping. Updates to the mapping
are not visible to other processes mapping the same file, and
are not carried through to the underlying file. It is unspecified
whether changes made to the file after the mmap() call are
visible in the mapped region.
newtype MmapOptionalFlag Source #
And MmapSharedFlag with one or more MmapOptionalFlags.
Constructors
| MmapOptionalFlag | |
Fields | |
Instances
map32Bit :: MmapOptionalFlag Source #
See man mmap for a description.
mapAnonymous :: MmapOptionalFlag Source #
See man mmap for a description.
mapDenywrite :: MmapOptionalFlag Source #
See man mmap for a description.
mapFile :: MmapOptionalFlag Source #
See man mmap for a description.
mapFixed :: MmapOptionalFlag Source #
See man mmap for a description.
mapHugetlb :: MmapOptionalFlag Source #
See man mmap for a description.
mapLocked :: MmapOptionalFlag Source #
See man mmap for a description.
mapNonblock :: MmapOptionalFlag Source #
See man mmap for a description.
mapNoreserve :: MmapOptionalFlag Source #
See man mmap for a description.
mapStack :: MmapOptionalFlag Source #
See man mmap for a description.
An MmapSharedFlag with one or more MmapOptionalFlags.
Constructors
| MmapFlags | |
Fields
| |
Instances
| Show MmapFlags Source # | |
| Eq MmapFlags Source # | |
| Ord MmapFlags Source # | |
mkMmapFlags :: MmapSharedFlag -> MmapOptionalFlag -> MmapFlags Source #
Create MmapFlags to be passed to c_mmap from an MmapSharedFlag
and one or more MmapOptionalFlags (combine them via (<>),
mempty for none).