| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Conduit.VFS.Types
Description
Synopsis
- type FilePath = String
- data ConduitT i o (m :: Type -> Type) r
- type VFSSource m = ConduitT Void FilePath m ()
- type VFSPipe m = ConduitT FilePath FilePath m ()
- type VFSSink m r = ConduitT FilePath Void m r
- data VFileType
- = VFile
- | VDirectory
- class Monad m => ReadVFSC m where
- vfsTypeC :: ConduitT FilePath (FilePath, Maybe VFileType) m ()
- vfsContentsC :: ConduitT FilePath (FilePath, ByteString) m ()
- vfsContentsEitherC :: ConduitT FilePath (Either FilePath ByteString) m ()
- vfsChildrenC :: VFSPipe m
- vfsChildFilesC :: VFSPipe m
- vfsChildDirsC :: VFSPipe m
- vfsDescendentsC :: VFSPipe m
- vfsDescFilesC :: VFSPipe m
- vfsDescDirsC :: VFSPipe m
- class Monad m => WriteVFSC m where
- vfsWriteSink :: ConduitT (FilePath, ByteString) Void m ()
- vfsWriteEitherSink :: ConduitT (Either FilePath ByteString) Void m ()
- vfsRemoveSink :: VFSSink m ()
- class (ReadVFSC m, WriteVFSC m) => VFSC m where
- vfsTouchSink :: ConduitT (VFileType, FilePath) Void m ()
- type ByteString = ByteString
Documentation
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.
data ConduitT i o (m :: Type -> Type) r #
Core datatype of the conduit package. This type represents a general
component which can consume a stream of input values i, produce a stream
of output values o, perform actions in the m monad, and produce a final
result r. The type synonyms provided here are simply wrappers around this
type.
Since 1.3.0
Instances
type VFSSource m = ConduitT Void FilePath m () Source #
The type of conduits that generate file paths.
type VFSPipe m = ConduitT FilePath FilePath m () Source #
The type of conduits that consume file paths and generate file paths.
The types that our virtual file system supports.
Constructors
| VFile | A node containing bytes |
| VDirectory | A node containing zero or more other nodes |
Instances
| Bounded VFileType Source # | |
| Enum VFileType Source # | |
Defined in Data.Conduit.VFS.Types Methods succ :: VFileType -> VFileType # pred :: VFileType -> VFileType # fromEnum :: VFileType -> Int # enumFrom :: VFileType -> [VFileType] # enumFromThen :: VFileType -> VFileType -> [VFileType] # enumFromTo :: VFileType -> VFileType -> [VFileType] # enumFromThenTo :: VFileType -> VFileType -> VFileType -> [VFileType] # | |
| Eq VFileType Source # | |
| Ord VFileType Source # | |
| Show VFileType Source # | |
| Generic VFileType Source # | |
| type Rep VFileType Source # | |
class Monad m => ReadVFSC m where Source #
A class denoting that the type is usable as VFS conduits for reading.
Minimal complete definition
(vfsContentsEitherC | vfsContentsC), vfsTypeC, (vfsChildrenC | vfsDescendentsC)
Methods
vfsTypeC :: ConduitT FilePath (FilePath, Maybe VFileType) m () Source #
Given an input path, generates a tuple of the input path itself and the input path's VFileType (or Nothing if the node does not exist).
Note that a directory containing no elements may be reported by the VFS as not existing.
vfsContentsC :: ConduitT FilePath (FilePath, ByteString) m () Source #
Given an input of FilePath files, generates a tuple containing the input and the bytestring for the contents of the file.
Note that the entire contents of the file are pulled into memory. If the input FilePath does not denote a VFile, it should be dropped.
vfsContentsEitherC :: ConduitT FilePath (Either FilePath ByteString) m () Source #
Given an input of FilePath files, generates a Left of the input, followed by zero or more Right values holding a bytestring. The concatenation of the
Right values after a given Left and before the next Left (or EOS) are the bytes of the input value. If the input FilePath does not denote a VFile,
it should be dropped.
vfsChildrenC :: VFSPipe m Source #
Given an input of FilePath directories, generates the non-special direct children, each path-prepended (using </>) with the parent directory.
If an input FilePath is not a VDirectory, it should be passed through directly.
vfsChildFilesC :: VFSPipe m Source #
Given an input of FilePath directories, generates the non-special direct children that are files, each path-prepended (using </>) with the
parent directory. If an input FilePath is not a VDirectory, it should be passed through directly.
vfsChildDirsC :: VFSPipe m Source #
Given an input of FilePath directories, generates the non-special direct children that are files, each path-prepended (using </>) with the
parent directory. If an input FilePath is not a VDirectory, it should be dropped.
vfsDescendentsC :: VFSPipe m Source #
Given an input of FilePath directories, generates all the paths in the VFS that have the input as a prefix, with the outputs being each
path-prepended (using </>) with the corresponding input directory. If an input FilePath is not a VDirectory, it should be passed through
directly.
vfsDescFilesC :: VFSPipe m Source #
Given an input FilePath directories, generates all the paths in the VFS that are files and have the input as a prefix, with the outputs being
each path-prepended (using </>) with the corresponding input directory. If an input FilePath is not a VDirectory, it should be passed through directly.
vfsDescDirsC :: VFSPipe m Source #
Given an input of FilePath directories, generates all the paths in the VFS that are directories and have the input as a prefix, with the outputs being
each path-prepended (using </>) with the corresponding input directory. If an input FilePath is not a VDirectory, it should be dropped.
Instances
class Monad m => WriteVFSC m where Source #
A class denoting that the type is usable as VFS conduits for writing.
Minimal complete definition
Methods
vfsWriteSink :: ConduitT (FilePath, ByteString) Void m () Source #
Given an input tuple of FilePath files and their bytestring contents, writes the contents to the filepath. This write should be atomic if possible, and if
it is not an atomic operation, the implementation's documentation should make this clear. This write should also create any necessary directories that may
not have previously existed.
vfsWriteEitherSink :: ConduitT (Either FilePath ByteString) Void m () Source #
Given an input of either FilePath files or bytestring contents, writes the contents to the filepath. The write is marked as complete when the next
FilePath input or end-of-stream is reached. This write should be atomic at completion if possible, and if it is not an atomic operation, the
implementation's documentation should make this clear. This write should also create any necessary directories that may not have previously existed.
vfsRemoveSink :: VFSSink m () Source #
Given FilePath inputs, remove those nodes from the VFS. If the path denotes a directory, the directory is
removed along with all of its descendents. If the path denotes a file, the file itself is removed. After a removal,
any newly-empty directories may also be removed.
Instances
class (ReadVFSC m, WriteVFSC m) => VFSC m where Source #
A class denoting that the type is usable as VFS conduits for both reading and writing.
Minimal complete definition
Nothing
Methods
vfsTouchSink :: ConduitT (VFileType, FilePath) Void m () Source #
Given an input tuple of a filetype and a filepath, ensure that a node exists at the filepath. If it does not exist, it should be created as either
a directory or a zero-length file, as denoted by the filetype, with any missing parent directories created. Note that a directory which does not
contain a node may be reported as not present by the VFS, and therefore an acceptable implementation for VDirectory inputs is simply 'return ()'
Instances
| Monad m => VFSC (PureVFS m) Source # | A class denoting that the type is usable as VFS conduits for reading and writing. |
Defined in Data.Conduit.VFS.Pure | |
| MonadUnliftIO m => VFSC (InMemoryVFS m) Source # | |
Defined in Data.Conduit.VFS.InMemory Methods vfsTouchSink :: ConduitT (VFileType, FilePath) Void (InMemoryVFS m) () Source # | |
| MonadUnliftIO m => VFSC (DiskVFS m) Source # | A class denoting that the type is usable as VFS conduits for reading and writing. |
Defined in Data.Conduit.VFS.Disk | |
type ByteString = ByteString Source #