module System.Posix.HFuse
(
module Foreign.C.Error
, FuseOperations(..)
, defaultFuseOps
, fuseMain
, defaultExceptionHandler
, FileStat(..)
, EntryType(..)
, FileSystemStats(..)
, SyncType(..)
, getFuseContext
, FuseContext(fuseCtxUserID, fuseCtxGroupID, fuseCtxProcessID)
, entryTypeToFileMode
, OpenMode(..)
, OpenFileFlags(..)
, intersectFileModes
, unionFileModes
) where
import Prelude hiding ( Read )
import Control.Exception ( Exception, handle )
import Foreign
import Foreign.C
import Foreign.C.Error
import Foreign.Marshal
import System.Environment ( getProgName, getArgs )
import System.IO ( hPutStrLn, stderr )
import System.Posix.Types
import System.Posix.Files ( accessModes, intersectFileModes, unionFileModes )
import System.Posix.IO ( OpenMode(..), OpenFileFlags(..) )
data FileStat = FileStat { statEntryType :: EntryType
, statFileMode :: FileMode
, statLinkCount :: LinkCount
, statFileOwner :: UserID
, statFileGroup :: GroupID
, statSpecialDeviceID :: DeviceID
, statFileSize :: FileOffset
, statBlocks :: Integer
, statAccessTime :: EpochTime
, statModificationTime :: EpochTime
, statStatusChangeTime :: EpochTime
}
data EntryType
= Unknown
| NamedPipe
| CharacterSpecial
| Directory
| BlockSpecial
| RegularFile
| SymbolicLink
| Socket
entryTypeToDT :: EntryType -> Int
entryTypeToDT Unknown = (0)
entryTypeToDT NamedPipe = (1)
entryTypeToDT CharacterSpecial = (2)
entryTypeToDT Directory = (4)
entryTypeToDT BlockSpecial = (6)
entryTypeToDT RegularFile = (8)
entryTypeToDT SymbolicLink = (10)
entryTypeToDT Socket = (12)
fileTypeModes :: FileMode
fileTypeModes = (61440)
blockSpecialMode :: FileMode
blockSpecialMode = (24576)
characterSpecialMode :: FileMode
characterSpecialMode = (8192)
namedPipeMode :: FileMode
namedPipeMode = (4096)
regularFileMode :: FileMode
regularFileMode = (32768)
directoryMode :: FileMode
directoryMode = (16384)
symbolicLinkMode :: FileMode
symbolicLinkMode = (40960)
socketMode :: FileMode
socketMode = (49152)
entryTypeToFileMode :: EntryType -> FileMode
entryTypeToFileMode Unknown = 0
entryTypeToFileMode NamedPipe = namedPipeMode
entryTypeToFileMode CharacterSpecial = characterSpecialMode
entryTypeToFileMode Directory = directoryMode
entryTypeToFileMode BlockSpecial = blockSpecialMode
entryTypeToFileMode RegularFile = regularFileMode
entryTypeToFileMode SymbolicLink = symbolicLinkMode
entryTypeToFileMode Socket = socketMode
fileModeToEntryType :: FileMode -> EntryType
fileModeToEntryType mode
| fileType == namedPipeMode = NamedPipe
| fileType == characterSpecialMode = CharacterSpecial
| fileType == directoryMode = Directory
| fileType == blockSpecialMode = BlockSpecial
| fileType == regularFileMode = RegularFile
| fileType == symbolicLinkMode = SymbolicLink
| fileType == socketMode = Socket
where fileType = mode .&. (61440)
data FileSystemStats = FileSystemStats
{ fsStatBlockSize :: Integer
, fsStatBlockCount :: Integer
, fsStatBlocksFree :: Integer
, fsStatBlocksAvailable :: Integer
, fsStatFileCount :: Integer
, fsStatFilesFree :: Integer
, fsStatMaxNameLength :: Integer
}
data SyncType
= FullSync
| DataSync
deriving (Eq, Enum)
data FuseContext = FuseContext
{ fuseCtxUserID :: UserID
, fuseCtxGroupID :: GroupID
, fuseCtxProcessID :: ProcessID
}
getFuseContext :: IO FuseContext
getFuseContext =
do pCtx <- fuse_get_context
userID <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) pCtx
groupID <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) pCtx
processID <- ((\hsc_ptr -> peekByteOff hsc_ptr 12)) pCtx
return $ FuseContext { fuseCtxUserID = userID
, fuseCtxGroupID = groupID
, fuseCtxProcessID = processID
}
data FuseOperations = FuseOperations
{ fuseGetFileStat :: FilePath -> IO (Either Errno FileStat)
, fuseReadSymbolicLink :: FilePath -> IO (Either Errno FilePath)
, fuseGetDirectoryContents :: FilePath
-> IO (Either Errno [(FilePath, EntryType)])
, fuseCreateDevice :: FilePath -> EntryType -> FileMode
-> DeviceID -> IO Errno
, fuseCreateDirectory :: FilePath -> FileMode -> IO Errno
, fuseRemoveLink :: FilePath -> IO Errno
, fuseRemoveDirectory :: FilePath -> IO Errno
, fuseCreateSymbolicLink :: FilePath -> FilePath -> IO Errno
, fuseRename :: FilePath -> FilePath -> IO Errno
, fuseCreateLink :: FilePath -> FilePath -> IO Errno
, fuseSetFileMode :: FilePath -> FileMode -> IO Errno
, fuseSetOwnerAndGroup :: FilePath -> UserID -> GroupID -> IO Errno
, fuseSetFileSize :: FilePath -> FileOffset -> IO Errno
, fuseSetFileTimes :: FilePath -> EpochTime -> EpochTime -> IO Errno
, fuseOpen :: FilePath -> OpenMode -> OpenFileFlags -> IO Errno
, fuseRead :: FilePath -> ByteCount -> FileOffset
-> IO (Either Errno (String, ByteCount))
, fuseWrite :: FilePath -> String -> FileOffset
-> IO (Either Errno ByteCount)
, fuseGetFileSystemStats :: String -> IO (Either Errno FileSystemStats)
, fuseFlush :: FilePath -> IO Errno
, fuseRelease :: FilePath -> Int -> IO ()
, fuseSynchronizeFile :: FilePath -> SyncType -> IO Errno
, fuseOpenDirectory :: FilePath -> IO Errno
, fuseReleaseDirectory :: FilePath -> IO Errno
, fuseSynchronizeDirectory :: FilePath -> SyncType -> IO Errno
, fuseInit :: IO ()
, fuseDestroy :: IO ()
}
defaultFuseOps :: FuseOperations
defaultFuseOps =
FuseOperations { fuseGetFileStat = \_ -> return (Left eNOSYS)
, fuseReadSymbolicLink = \_ -> return (Left eNOSYS)
, fuseGetDirectoryContents = \_ -> return (Left eNOSYS)
, fuseCreateDevice = \_ _ _ _ -> return eNOSYS
, fuseCreateDirectory = \_ _ -> return eNOSYS
, fuseRemoveLink = \_ -> return eNOSYS
, fuseRemoveDirectory = \_ -> return eNOSYS
, fuseCreateSymbolicLink = \_ _ -> return eNOSYS
, fuseRename = \_ _ -> return eNOSYS
, fuseCreateLink = \_ _ -> return eNOSYS
, fuseSetFileMode = \_ _ -> return eNOSYS
, fuseSetOwnerAndGroup = \_ _ _ -> return eNOSYS
, fuseSetFileSize = \_ _ -> return eNOSYS
, fuseSetFileTimes = \_ _ _ -> return eNOSYS
, fuseOpen = \_ _ _ -> return eNOSYS
, fuseRead = \_ _ _ -> return (Left eNOSYS)
, fuseWrite = \_ _ _ -> return (Left eNOSYS)
, fuseGetFileSystemStats = \_ -> return (Left eNOSYS)
, fuseFlush = \_ -> return eOK
, fuseRelease = \_ _ -> return ()
, fuseSynchronizeFile = \_ _ -> return eNOSYS
, fuseOpenDirectory = \_ -> return eNOSYS
, fuseReleaseDirectory = \_ -> return eNOSYS
, fuseSynchronizeDirectory = \_ _ -> return eNOSYS
, fuseInit = return ()
, fuseDestroy = return ()
}
fuseMain :: FuseOperations -> (Exception -> IO Errno) -> IO ()
fuseMain ops handler =
allocaBytes ((124)) $ \ pOps -> do
mkGetAttr wrapGetAttr >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) pOps
mkReadLink wrapReadLink >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 4)) pOps
mkGetDir wrapGetDir >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 8)) pOps
mkMkNod wrapMkNod >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 12)) pOps
mkMkDir wrapMkDir >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 16)) pOps
mkUnlink wrapUnlink >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 20)) pOps
mkRmDir wrapRmDir >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 24)) pOps
mkSymLink wrapSymLink >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 28)) pOps
mkRename wrapRename >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 32)) pOps
mkLink wrapLink >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 36)) pOps
mkChMod wrapChMod >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 40)) pOps
mkChOwn wrapChOwn >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 44)) pOps
mkTruncate wrapTruncate >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 48)) pOps
mkUTime wrapUTime >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 52)) pOps
mkOpen wrapOpen >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 56)) pOps
mkRead wrapRead >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 60)) pOps
mkWrite wrapWrite >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 64)) pOps
mkStatFS wrapStatFS >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 68)) pOps
mkFlush wrapFlush >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 72)) pOps
mkRelease wrapRelease >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 76)) pOps
mkFSync wrapFSync >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 80)) pOps
((\hsc_ptr -> pokeByteOff hsc_ptr 84)) pOps nullPtr
((\hsc_ptr -> pokeByteOff hsc_ptr 88)) pOps nullPtr
((\hsc_ptr -> pokeByteOff hsc_ptr 92)) pOps nullPtr
((\hsc_ptr -> pokeByteOff hsc_ptr 96)) pOps nullPtr
mkOpenDir wrapOpenDir >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 100)) pOps
((\hsc_ptr -> pokeByteOff hsc_ptr 104)) pOps nullPtr
mkReleaseDir wrapReleaseDir >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 108)) pOps
mkFSyncDir wrapFSyncDir >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 112)) pOps
mkInit wrapInit >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 116)) pOps
mkDestroy wrapDestroy >>= ((\hsc_ptr -> pokeByteOff hsc_ptr 120)) pOps
prog <- getProgName
args <- getArgs
let allArgs = (prog:args)
argc = length allArgs
withMany withCString allArgs $ \ pAddrs ->
withArray pAddrs $ \ pArgv ->
do fuse_main_real argc pArgv pOps ((124))
where fuseHandler :: Exception -> IO CInt
fuseHandler e = handler e >>= return . unErrno
wrapGetAttr :: CGetAttr
wrapGetAttr pFilePath pStat = handle fuseHandler $
do filePath <- peekCString pFilePath
eitherFileStat <- (fuseGetFileStat ops) filePath
case eitherFileStat of
Left (Errno errno) -> return ( errno)
Right stat ->
do ((\hsc_ptr -> pokeByteOff hsc_ptr 16)) pStat
(entryTypeToFileMode (statEntryType stat)
`unionFileModes`
(statFileMode stat `intersectFileModes` accessModes))
((\hsc_ptr -> pokeByteOff hsc_ptr 20)) pStat (statLinkCount stat)
((\hsc_ptr -> pokeByteOff hsc_ptr 24)) pStat (statFileOwner stat)
((\hsc_ptr -> pokeByteOff hsc_ptr 28)) pStat (statFileGroup stat)
((\hsc_ptr -> pokeByteOff hsc_ptr 32)) pStat
(statSpecialDeviceID stat)
((\hsc_ptr -> pokeByteOff hsc_ptr 44)) pStat (statFileSize stat)
((\hsc_ptr -> pokeByteOff hsc_ptr 56)) pStat
(fromIntegral (statBlocks stat) :: (Int64))
((\hsc_ptr -> pokeByteOff hsc_ptr 64)) pStat (statAccessTime stat)
((\hsc_ptr -> pokeByteOff hsc_ptr 72)) pStat
(statModificationTime stat)
((\hsc_ptr -> pokeByteOff hsc_ptr 80)) pStat
(statStatusChangeTime stat)
return okErrno
wrapReadLink :: CReadLink
wrapReadLink pFilePath pBuf bufSize = handle fuseHandler $
do filePath <- peekCString pFilePath
return ( unErrno eNOSYS)
eitherTarget <- (fuseReadSymbolicLink ops) filePath
case eitherTarget of
Left (Errno errno) -> return ( errno)
Right target ->
do pokeCStringLen0 (pBuf, (fromIntegral bufSize)) target
return okErrno
wrapGetDir :: CGetDir
wrapGetDir pFilePath pDirHandle pDirFil = handle fuseHandler $
do filePath <- peekCString pFilePath
let filler (entryFilePath, entryType) =
withCString entryFilePath $ \ pEntryFilePath ->
(mkDirFil pDirFil) pDirHandle pEntryFilePath
(entryTypeToDT entryType) >>= return . Errno
eitherContents <- (fuseGetDirectoryContents ops) filePath
case eitherContents of
Left (Errno errno) -> return ( errno)
Right contents ->
do mapM_ filler contents
return okErrno
wrapMkNod :: CMkNod
wrapMkNod pFilePath mode dev = handle fuseHandler $
do filePath <- peekCString pFilePath
(Errno errno) <- (fuseCreateDevice ops) filePath
(fileModeToEntryType mode) mode dev
return ( errno)
wrapMkDir :: CMkDir
wrapMkDir pFilePath mode = handle fuseHandler $
do filePath <- peekCString pFilePath
(Errno errno) <- (fuseCreateDirectory ops) filePath mode
return ( errno)
wrapUnlink :: CUnlink
wrapUnlink pFilePath = handle fuseHandler $
do filePath <- peekCString pFilePath
(Errno errno) <- (fuseRemoveLink ops) filePath
return ( errno)
wrapRmDir :: CRmDir
wrapRmDir pFilePath = handle fuseHandler $
do filePath <- peekCString pFilePath
(Errno errno) <- (fuseRemoveDirectory ops) filePath
return ( errno)
wrapSymLink :: CSymLink
wrapSymLink pSource pDestination = handle fuseHandler $
do source <- peekCString pSource
destination <- peekCString pDestination
(Errno errno) <- (fuseCreateSymbolicLink ops) source destination
return ( errno)
wrapRename :: CRename
wrapRename pOld pNew = handle fuseHandler $
do old <- peekCString pOld
new <- peekCString pNew
(Errno errno) <- (fuseRename ops) old new
return ( errno)
wrapLink :: CLink
wrapLink pSource pDestination = handle fuseHandler $
do source <- peekCString pSource
destination <- peekCString pDestination
(Errno errno) <- (fuseCreateLink ops) source destination
return ( errno)
wrapChMod :: CChMod
wrapChMod pFilePath mode = handle fuseHandler $
do filePath <- peekCString pFilePath
(Errno errno) <- (fuseSetFileMode ops) filePath mode
return ( errno)
wrapChOwn :: CChOwn
wrapChOwn pFilePath uid gid = handle fuseHandler $
do filePath <- peekCString pFilePath
(Errno errno) <- (fuseSetOwnerAndGroup ops) filePath uid gid
return ( errno)
wrapTruncate :: CTruncate
wrapTruncate pFilePath off = handle fuseHandler $
do filePath <- peekCString pFilePath
(Errno errno) <- (fuseSetFileSize ops) filePath off
return ( errno)
wrapUTime :: CUTime
wrapUTime pFilePath pUTimBuf = handle fuseHandler $
do filePath <- peekCString pFilePath
accessTime <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) pUTimBuf
modificationTime <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) pUTimBuf
(Errno errno) <- (fuseSetFileTimes ops) filePath
accessTime modificationTime
return ( errno)
wrapOpen :: COpen
wrapOpen pFilePath pFuseFileInfo = handle fuseHandler $
do filePath <- peekCString pFilePath
(flags :: CInt) <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) pFuseFileInfo
let append = (1024) .&. flags == (1024)
noctty = (256) .&. flags == (256)
nonBlock = (2048) .&. flags == (2048)
how | (2) .&. flags == (2) = ReadWrite
| (1) .&. flags == (1) = WriteOnly
| otherwise = ReadOnly
openFileFlags = OpenFileFlags { append = append
, exclusive = False
, noctty = noctty
, nonBlock = nonBlock
, trunc = False
}
(Errno errno) <- (fuseOpen ops) filePath how openFileFlags
return ( errno)
wrapRead :: CRead
wrapRead pFilePath pBuf bufSiz off pFuseFileInfo = handle fuseHandler $
do filePath <- peekCString pFilePath
eitherRead <- (fuseRead ops) filePath bufSiz off
case eitherRead of
Left (Errno errno) -> return ( errno)
Right (bytes, byteCount) ->
do pokeCStringLen (pBuf, fromIntegral byteCount) bytes
return (fromIntegral byteCount)
wrapWrite :: CWrite
wrapWrite pFilePath pBuf bufSiz off pFuseFileInfo = handle fuseHandler $
do filePath <- peekCString pFilePath
buf <- peekCStringLen (pBuf, fromIntegral bufSiz)
eitherBytes <- (fuseWrite ops) filePath buf off
case eitherBytes of
Left (Errno errno) -> return ( errno)
Right bytes -> return (fromIntegral bytes)
wrapStatFS :: CStatFS
wrapStatFS pStr pStatFS = handle fuseHandler $
do str <- peekCString pStr
eitherStatFS <- (fuseGetFileSystemStats ops) str
case eitherStatFS of
Left (Errno errno) -> return ( errno)
Right stat ->
do ((\hsc_ptr -> pokeByteOff hsc_ptr 4)) pStatFS
(fromIntegral (fsStatBlockSize stat) :: (Int32))
((\hsc_ptr -> pokeByteOff hsc_ptr 8)) pStatFS
(fromIntegral (fsStatBlockCount stat) :: (Int32))
((\hsc_ptr -> pokeByteOff hsc_ptr 16)) pStatFS
(fromIntegral (fsStatBlocksFree stat) :: (Int32))
((\hsc_ptr -> pokeByteOff hsc_ptr 24)) pStatFS
(fromIntegral (fsStatBlocksAvailable
stat) :: (Int32))
((\hsc_ptr -> pokeByteOff hsc_ptr 32)) pStatFS
(fromIntegral (fsStatFileCount stat) :: (Int32))
((\hsc_ptr -> pokeByteOff hsc_ptr 40)) pStatFS
(fromIntegral (fsStatFilesFree stat) :: (Int32))
((\hsc_ptr -> pokeByteOff hsc_ptr 56)) pStatFS
(fromIntegral (fsStatMaxNameLength stat) :: (Int32))
return 0
wrapFlush :: CFlush
wrapFlush pFilePath pFuseFileInfo = handle fuseHandler $
do filePath <- peekCString pFilePath
(Errno errno) <- (fuseFlush ops) filePath
return ( errno)
wrapRelease :: CRelease
wrapRelease pFilePath pFuseFileInfo = handle fuseHandler $
do filePath <- peekCString pFilePath
flags <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) pFuseFileInfo
(fuseRelease ops) filePath flags
return 0
wrapFSync :: CFSync
wrapFSync pFilePath isFullSync pFuseFileInfo = handle fuseHandler $
do filePath <- peekCString pFilePath
(Errno errno) <- (fuseSynchronizeFile ops)
filePath (toEnum isFullSync)
return ( errno)
wrapOpenDir :: COpenDir
wrapOpenDir pFilePath pFuseFileInfo = handle fuseHandler $
do filePath <- peekCString pFilePath
(Errno errno) <- (fuseOpenDirectory ops) filePath
return ( errno)
wrapReleaseDir :: CReleaseDir
wrapReleaseDir pFilePath pFuseFileInfo = handle fuseHandler $
do filePath <- peekCString pFilePath
(Errno errno) <- (fuseReleaseDirectory ops) filePath
return ( errno)
wrapFSyncDir :: CFSyncDir
wrapFSyncDir pFilePath isFullSync pFuseFileInfo = handle fuseHandler $
do filePath <- peekCString pFilePath
(Errno errno) <- (fuseSynchronizeDirectory ops)
filePath (toEnum isFullSync)
return ( errno)
wrapInit :: CInit
wrapInit = handle (\e -> hPutStrLn stderr (show e) >> return nullPtr) $
do fuseInit ops
return nullPtr
wrapDestroy :: CDestroy
wrapDestroy _ = handle (\e -> hPutStrLn stderr (show e)) $
do fuseDestroy ops
defaultExceptionHandler :: (Exception -> IO Errno)
defaultExceptionHandler e = hPutStrLn stderr (show e) >> return eFAULT
unErrno :: Errno -> CInt
unErrno (Errno errno) = errno
okErrno :: CInt
okErrno = 0
pokeCStringLen :: CStringLen -> String -> IO ()
pokeCStringLen (pBuf, bufSize) src =
pokeArray pBuf $ take bufSize $ map castCharToCChar src
pokeCStringLen0 :: CStringLen -> String -> IO ()
pokeCStringLen0 (pBuf, bufSize) src =
pokeArray0 0 pBuf $ take (bufSize 1) $ map castCharToCChar src
data CFuseOperations
foreign import ccall threadsafe "fuse.h fuse_main_real"
fuse_main_real :: Int -> Ptr CString -> Ptr CFuseOperations -> CSize -> IO ()
data StructFuse
foreign import ccall threadsafe "fuse.h fuse_get_context"
fuse_get_context :: IO (Ptr StructFuse)
data CFuseFileInfo
data CStat
type CGetAttr = CString -> Ptr CStat -> IO CInt
foreign import ccall threadsafe "wrapper"
mkGetAttr :: CGetAttr -> IO (FunPtr CGetAttr)
type CReadLink = CString -> CString -> CSize -> IO CInt
foreign import ccall threadsafe "wrapper"
mkReadLink :: CReadLink -> IO (FunPtr CReadLink)
type CGetDir = CString -> Ptr CDirHandle -> FunPtr CDirFil -> IO CInt
foreign import ccall threadsafe "wrapper"
mkGetDir :: CGetDir -> IO (FunPtr CGetDir)
type CMkNod = CString -> CMode -> CDev -> IO CInt
foreign import ccall threadsafe "wrapper"
mkMkNod :: CMkNod -> IO (FunPtr CMkNod)
type CMkDir = CString -> CMode -> IO CInt
foreign import ccall threadsafe "wrapper"
mkMkDir :: CMkDir -> IO (FunPtr CMkDir)
type CUnlink = CString -> IO CInt
foreign import ccall threadsafe "wrapper"
mkUnlink :: CUnlink -> IO (FunPtr CUnlink)
type CRmDir = CString -> IO CInt
foreign import ccall threadsafe "wrapper"
mkRmDir :: CRmDir -> IO (FunPtr CRmDir)
type CSymLink = CString -> CString -> IO CInt
foreign import ccall threadsafe "wrapper"
mkSymLink :: CSymLink -> IO (FunPtr CSymLink)
type CRename = CString -> CString -> IO CInt
foreign import ccall threadsafe "wrapper"
mkRename :: CRename -> IO (FunPtr CRename)
type CLink = CString -> CString -> IO CInt
foreign import ccall threadsafe "wrapper"
mkLink :: CLink -> IO (FunPtr CLink)
type CChMod = CString -> CMode -> IO CInt
foreign import ccall threadsafe "wrapper"
mkChMod :: CChMod -> IO (FunPtr CChMod)
type CChOwn = CString -> CUid -> CGid -> IO CInt
foreign import ccall threadsafe "wrapper"
mkChOwn :: CChOwn -> IO (FunPtr CChOwn)
type CTruncate = CString -> COff -> IO CInt
foreign import ccall threadsafe "wrapper"
mkTruncate :: CTruncate -> IO (FunPtr CTruncate)
data CUTimBuf
type CUTime = CString -> Ptr CUTimBuf -> IO CInt
foreign import ccall threadsafe "wrapper"
mkUTime :: CUTime -> IO (FunPtr CUTime)
type COpen = CString -> Ptr CFuseFileInfo -> IO CInt
foreign import ccall threadsafe "wrapper"
mkOpen :: COpen -> IO (FunPtr COpen)
type CRead = CString -> CString -> CSize -> COff -> Ptr CFuseFileInfo -> IO CInt
foreign import ccall threadsafe "wrapper"
mkRead :: CRead -> IO (FunPtr CRead)
type CWrite = CString -> CString -> CSize -> COff -> Ptr CFuseFileInfo -> IO CInt
foreign import ccall threadsafe "wrapper"
mkWrite :: CWrite -> IO (FunPtr CWrite)
data CStructStatFS
type CStatFS = CString -> Ptr CStructStatFS -> IO CInt
foreign import ccall threadsafe "wrapper"
mkStatFS :: CStatFS -> IO (FunPtr CStatFS)
type CFlush = CString -> Ptr CFuseFileInfo -> IO CInt
foreign import ccall threadsafe "wrapper"
mkFlush :: CFlush -> IO (FunPtr CFlush)
type CRelease = CString -> Ptr CFuseFileInfo -> IO CInt
foreign import ccall threadsafe "wrapper"
mkRelease :: CRelease -> IO (FunPtr CRelease)
type CFSync = CString -> Int -> Ptr CFuseFileInfo -> IO CInt
foreign import ccall threadsafe "wrapper"
mkFSync :: CFSync -> IO (FunPtr CFSync)
type COpenDir = CString -> Ptr CFuseFileInfo -> IO CInt
foreign import ccall threadsafe "wrapper"
mkOpenDir :: COpenDir -> IO (FunPtr COpenDir)
type CReadDir = CString -> Ptr CFillDirBuf -> Ptr CFillDir -> COff -> Ptr CFuseFileInfo -> IO CInt
foreign import ccall threadsafe "wrapper"
mkReadDir :: CReadDir -> IO (FunPtr CReadDir)
type CReleaseDir = CString -> Ptr CFuseFileInfo -> IO CInt
foreign import ccall threadsafe "wrapper"
mkReleaseDir :: CReleaseDir -> IO (FunPtr CReleaseDir)
type CFSyncDir = CString -> Int -> Ptr CFuseFileInfo -> IO CInt
foreign import ccall threadsafe "wrapper"
mkFSyncDir :: CFSyncDir -> IO (FunPtr CFSyncDir)
type CInit = IO (Ptr CInt)
foreign import ccall threadsafe "wrapper"
mkInit :: CInit -> IO (FunPtr CInit)
type CDestroy = Ptr CInt -> IO ()
foreign import ccall threadsafe "wrapper"
mkDestroy :: CDestroy -> IO (FunPtr CDestroy)
data CDirHandle
type CDirFil = Ptr CDirHandle -> CString -> Int -> IO CInt
foreign import ccall threadsafe "dynamic"
mkDirFil :: FunPtr CDirFil -> CDirFil
data CFillDirBuf
type CFillDir = Ptr CFillDirBuf -> CString -> Ptr CStat -> COff -> IO CInt
foreign import ccall threadsafe "dynamic"
mkFillDir :: FunPtr CFillDir -> CFillDir