Win32 Libraries (Win32 package)Source codeContentsIndex
System.Win32.FileMapping
Portabilityportable
Stabilityprovisional
MaintainerEsa Ilari Vuokko <ei@vuokko.info>
Description
A collection of FFI declarations for interfacing with Win32 mapped files.
Synopsis
mapFile :: FilePath -> IO (ForeignPtr a, Int)
mapFileBs :: FilePath -> IO ByteString
data MappedObject = MappedObject HANDLE HANDLE FileMapAccess
withMappedFile :: FilePath -> Bool -> Maybe Bool -> (Integer -> MappedObject -> IO a) -> IO a
withMappedArea :: MappedObject -> Integer -> Int -> (Ptr a -> IO b) -> IO b
type ProtectSectionFlags = DWORD
sEC_COMMIT :: ProtectSectionFlags
sEC_IMAGE :: ProtectSectionFlags
sEC_NOCACHE :: ProtectSectionFlags
sEC_RESERVE :: ProtectSectionFlags
type FileMapAccess = DWORD
fILE_MAP_ALL_ACCESS :: FileMapAccess
fILE_MAP_COPY :: FileMapAccess
fILE_MAP_READ :: FileMapAccess
fILE_MAP_WRITE :: FileMapAccess
createFileMapping :: Maybe HANDLE -> ProtectFlags -> DDWORD -> Maybe String -> IO HANDLE
openFileMapping :: FileMapAccess -> BOOL -> Maybe String -> IO HANDLE
mapViewOfFileEx :: HANDLE -> FileMapAccess -> DDWORD -> SIZE_T -> Ptr a -> IO (Ptr b)
mapViewOfFile :: HANDLE -> FileMapAccess -> DDWORD -> SIZE_T -> IO (Ptr a)
unmapViewOfFile :: Ptr a -> IO ()
c_OpenFileMapping :: DWORD -> BOOL -> LPCTSTR -> IO HANDLE
c_CreateFileMapping :: HANDLE -> Ptr () -> DWORD -> DWORD -> DWORD -> LPCTSTR -> IO HANDLE
c_MapViewOfFileEx :: HANDLE -> DWORD -> DWORD -> DWORD -> SIZE_T -> Ptr a -> IO (Ptr b)
c_UnmapViewOfFile :: Ptr a -> IO BOOL
c_UnmapViewOfFileFinaliser :: FunPtr (Ptr a -> IO ())
Documentation
mapFile :: FilePath -> IO (ForeignPtr a, Int)
Maps file fully and returns ForeignPtr and length of the mapped area. The mapped file is opened read-only and shared reading.
mapFileBs :: FilePath -> IO ByteString
As mapFile, but returns ByteString
data MappedObject
Constructors
MappedObject HANDLE HANDLE FileMapAccess
withMappedFile
:: FilePathPath
-> BoolWrite? (False = read-only)
-> Maybe BoolSharing mode, no sharing, share read, share read+write
-> (Integer -> MappedObject -> IO a)Action
-> IO a
Opens an existing file and creates mapping object to it.
withMappedArea
:: MappedObjectMapped object, from withMappedFile
-> IntegerPosition in file
-> IntSize of mapped area
-> (Ptr a -> IO b)Action
-> IO b
Maps area into memory.
type ProtectSectionFlags = DWORD
sEC_COMMIT :: ProtectSectionFlags
sEC_IMAGE :: ProtectSectionFlags
sEC_NOCACHE :: ProtectSectionFlags
sEC_RESERVE :: ProtectSectionFlags
type FileMapAccess = DWORD
fILE_MAP_ALL_ACCESS :: FileMapAccess
fILE_MAP_COPY :: FileMapAccess
fILE_MAP_READ :: FileMapAccess
fILE_MAP_WRITE :: FileMapAccess
createFileMapping :: Maybe HANDLE -> ProtectFlags -> DDWORD -> Maybe String -> IO HANDLE
openFileMapping :: FileMapAccess -> BOOL -> Maybe String -> IO HANDLE
mapViewOfFileEx :: HANDLE -> FileMapAccess -> DDWORD -> SIZE_T -> Ptr a -> IO (Ptr b)
mapViewOfFile :: HANDLE -> FileMapAccess -> DDWORD -> SIZE_T -> IO (Ptr a)
unmapViewOfFile :: Ptr a -> IO ()
c_OpenFileMapping :: DWORD -> BOOL -> LPCTSTR -> IO HANDLE
c_CreateFileMapping :: HANDLE -> Ptr () -> DWORD -> DWORD -> DWORD -> LPCTSTR -> IO HANDLE
c_MapViewOfFileEx :: HANDLE -> DWORD -> DWORD -> DWORD -> SIZE_T -> Ptr a -> IO (Ptr b)
c_UnmapViewOfFile :: Ptr a -> IO BOOL
c_UnmapViewOfFileFinaliser :: FunPtr (Ptr a -> IO ())
Produced by Haddock version 0.8