Copyright | Copyright (C) 2004-2011 John Goerzen |
---|---|
License | BSD3 |
Maintainer | John Goerzen <jgoerzen@complete.org> |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell98 |
Haskell Virtual FS -- generic support for real or virtual filesystem in Haskell
Copyright (c) 2004-2005 John Goerzen, jgoerzen@complete.org
The idea of this module is to provide virtualization of filesystem calls. In addition to the "real" system filesystem, you can also provide access to other, virtual, filesystems using the same set of calls. Examples of such virtual filesystems might include a remote FTP server, WebDAV server, a local Hashtable, a ConfigParser object, or any other data structure you can represent as a tree of named nodes containing strings.
Each HVFS
function takes a HVFS
"handle" (HVFS
instance) as its
first parameter. If you wish to operate on the standard system filesystem,
you can just use SystemFS
.
The MissingH.HVFS.IO.InstanceHelpers module contains some code to help you make your own HVFS instances.
The HVFSOpenable
class works together with the System.IO.HVIO module
to provide a complete virtual filesystem and I/O model that allows you
to open up virtual filesystem files and act upon them in a manner similar
to standard Handles.
Synopsis
- class Show a => HVFS a where
- class Show a => HVFSStat a where
- class HVFS a => HVFSOpenable a where
- data HVFSOpenEncap = HVIO a => HVFSOpenEncap a
- data HVFSStatEncap = HVFSStat a => HVFSStatEncap a
- withStat :: forall b. HVFSStatEncap -> (forall a. HVFSStat a => a -> b) -> b
- withOpen :: forall b. HVFSOpenEncap -> (forall a. HVIO a => a -> b) -> b
- data SystemFS = SystemFS
- type FilePath = String
- type DeviceID = CDev
- type FileID = CIno
- type FileMode = CMode
- type LinkCount = CNlink
- type UserID = CUid
- type GroupID = CGid
- type FileOffset = COff
- type EpochTime = CTime
- data IOMode
Implementation Classes / Types
class Show a => HVFS a where Source #
The main HVFS class.
Default implementations of these functions are provided:
vGetModificationTime
-- implemented in terms ofvGetFileStatus
vRaiseError
vDoesFileExist
-- implemented in terms ofvGetFileStatus
vDoesDirectoryExist
-- implemented in terms ofvGetFileStatus
vDoesExist
-- implemented in terms ofvGetSymbolicLinkStatus
vGetSymbolicLinkStatus
-- set to callvGetFileStatus
.
Default implementations of all other functions will generate an isIllegalOperation error, since they are assumed to be un-implemented.
You should always provide at least a vGetFileStatus
call, and almost
certainly several of the others.
Most of these functions correspond to functions in System.Directory or System.Posix.Files. Please see detailed documentation on them there.
vGetCurrentDirectory :: a -> IO FilePath Source #
vSetCurrentDirectory :: a -> FilePath -> IO () Source #
vGetDirectoryContents :: a -> FilePath -> IO [FilePath] Source #
vDoesFileExist :: a -> FilePath -> IO Bool Source #
vDoesDirectoryExist :: a -> FilePath -> IO Bool Source #
vDoesExist :: a -> FilePath -> IO Bool Source #
True if the file exists, regardless of what type it is. This is even True if the given path is a broken symlink.
vCreateDirectory :: a -> FilePath -> IO () Source #
vRemoveDirectory :: a -> FilePath -> IO () Source #
vRenameDirectory :: a -> FilePath -> FilePath -> IO () Source #
vRemoveFile :: a -> FilePath -> IO () Source #
vRenameFile :: a -> FilePath -> FilePath -> IO () Source #
vGetFileStatus :: a -> FilePath -> IO HVFSStatEncap Source #
vGetSymbolicLinkStatus :: a -> FilePath -> IO HVFSStatEncap Source #
vGetModificationTime :: a -> FilePath -> IO ClockTime Source #
vRaiseError :: a -> IOErrorType -> String -> Maybe FilePath -> IO c Source #
Raise an error relating to actions on this class.
vCreateSymbolicLink :: a -> FilePath -> FilePath -> IO () Source #
Instances
class Show a => HVFSStat a where Source #
Evaluating types of files and information about them.
This corresponds to the System.Posix.Types.FileStatus type, and indeed, that is one instance of this class.
Inplementators must, at minimum, implement vIsDirectory
and
vIsRegularFile
.
Default implementations of everything else are provided, returning reasonable values.
A default implementation of this is not currently present on Windows.
vDeviceID :: a -> DeviceID Source #
vFileID :: a -> FileID Source #
vFileMode :: a -> FileMode Source #
Refers to file permissions, NOT the st_mode field from stat(2)
vLinkCount :: a -> LinkCount Source #
vFileOwner :: a -> UserID Source #
vFileGroup :: a -> GroupID Source #
vSpecialDeviceID :: a -> DeviceID Source #
vFileSize :: a -> FileOffset Source #
vAccessTime :: a -> EpochTime Source #
vModificationTime :: a -> EpochTime Source #
vStatusChangeTime :: a -> EpochTime Source #
vIsBlockDevice :: a -> Bool Source #
vIsCharacterDevice :: a -> Bool Source #
vIsNamedPipe :: a -> Bool Source #
vIsRegularFile :: a -> Bool Source #
vIsDirectory :: a -> Bool Source #
vIsSymbolicLink :: a -> Bool Source #
Instances
class HVFS a => HVFSOpenable a where Source #
Types that can open a HVIO object should be instances of this class.
You need only implement vOpen
.
vOpen :: a -> FilePath -> IOMode -> IO HVFSOpenEncap Source #
vReadFile :: a -> FilePath -> IO String Source #
vWriteFile :: a -> FilePath -> String -> IO () Source #
vOpenBinaryFile :: a -> FilePath -> IOMode -> IO HVFSOpenEncap Source #
Instances
HVFSOpenable SystemFS Source # | |
HVFSOpenable MemoryVFS Source # | |
Defined in System.IO.HVFS.InstanceHelpers | |
HVFSOpenable a => HVFSOpenable (HVFSChroot a) Source # | |
Defined in System.IO.HVFS.Combinators vOpen :: HVFSChroot a -> FilePath -> IOMode -> IO HVFSOpenEncap Source # vReadFile :: HVFSChroot a -> FilePath -> IO String Source # vWriteFile :: HVFSChroot a -> FilePath -> String -> IO () Source # vOpenBinaryFile :: HVFSChroot a -> FilePath -> IOMode -> IO HVFSOpenEncap Source # | |
HVFSOpenable a => HVFSOpenable (HVFSReadOnly a) Source # | |
Defined in System.IO.HVFS.Combinators vOpen :: HVFSReadOnly a -> FilePath -> IOMode -> IO HVFSOpenEncap Source # vReadFile :: HVFSReadOnly a -> FilePath -> IO String Source # vWriteFile :: HVFSReadOnly a -> FilePath -> String -> IO () Source # vOpenBinaryFile :: HVFSReadOnly a -> FilePath -> IOMode -> IO HVFSOpenEncap Source # |
data HVFSStatEncap Source #
Encapsulate a HVFSStat
result. This is required due to Haskell
typing restrictions. You can get at it with:
case encap of HVFSStatEncap x -> -- now use x
HVFSStat a => HVFSStatEncap a |
withStat :: forall b. HVFSStatEncap -> (forall a. HVFSStat a => a -> b) -> b Source #
Convenience function for working with stat -- takes a stat result and a function that uses it, and returns the result.
Here is an example from the HVFS source:
vGetModificationTime fs fp = do s <- vGetFileStatus fs fp return $ epochToClockTime (withStat s vModificationTime)
See epochToClockTime
for more information.
withOpen :: forall b. HVFSOpenEncap -> (forall a. HVIO a => a -> b) -> b Source #
Instances
Re-exported types from other modules
File and directory names are values of type String
, whose precise
meaning is operating system dependent. Files can be opened, yielding a
handle which can then be used to operate on the contents of that file.
type FileOffset = COff #
See openFile
Orphan instances
Show FileStatus Source # | |
showsPrec :: Int -> FileStatus -> ShowS # show :: FileStatus -> String # showList :: [FileStatus] -> ShowS # |