System.FileSystem
- type InApp a = a -> a
- type DirName = String
- type FileName = String
- data ByteString
- data ClockTime
- data File
- emptyFile :: FileName -> File
- newFile :: FileName -> ByteString -> File
- getFileName :: File -> FileName
- setFileName :: FileName -> File -> File
- getFileContent :: File -> ByteString
- setFileContent :: ByteString -> File -> File
- getModifTime :: File -> ClockTime
- setModifTime :: ClockTime -> File -> File
- fileSize :: File -> Int
- data FileSystem
- emptyFileSystem :: FileSystem
- mapFileSystem :: InApp DirName -> InApp File -> InApp FileSystem
- mapFiles :: InApp File -> InApp FileSystem
- foldFileSystem :: FilePath -> Either (FilePath -> t -> Either DirName File -> t) (FilePath -> Either DirName File -> t -> t) -> t -> FileSystem -> t
- foldFiles :: Either (t -> File -> t) (File -> t -> t) -> t -> FileSystem -> t
- type FSState = FileSystem
- data FST m a
- runFST :: Monad m => FST m a -> FSState -> m (a, FSState)
- type FS = FST Identity
- runFS :: FS a -> FSState -> (a, FSState)
- type DirPath = [DirName]
- toDirPath :: FilePath -> DirPath
- fromDirPath :: DirPath -> FilePath
- type FPath = (DirPath, FileName)
- toFPath :: FilePath -> FPath
- fromFPath :: FPath -> FilePath
- putFileL :: FSMonad m => DirPath -> File -> m ()
- putFile :: FSMonad m => FilePath -> File -> m ()
- getFileL :: FSMonad m => FPath -> m (Maybe File)
- getFile :: FSMonad m => FilePath -> m (Maybe File)
- modFileL :: FSMonad m => FPath -> InApp File -> m Bool
- modFile :: FSMonad m => FilePath -> InApp File -> m Bool
- moveFileL :: FSMonad m => FPath -> FPath -> m Bool
- moveFile :: FSMonad m => FilePath -> FilePath -> m Bool
- fs_writeFileL :: FSMonad m => FPath -> ByteString -> m ()
- fs_writeFile :: FSMonad m => FilePath -> ByteString -> m ()
- fs_readFileL :: FSMonad m => FPath -> m (Maybe ByteString)
- fs_readFile :: FSMonad m => FilePath -> m (Maybe ByteString)
- writeFileTimeL :: (FSMonad m, MonadIO m) => FPath -> ByteString -> m ()
- writeFileTime :: (FSMonad m, MonadIO m) => FilePath -> ByteString -> m ()
- fs_getDirectoryContentsL :: FSMonad m => DirPath -> m (Maybe ([DirName], [FileName]))
- fs_getDirectoryContents :: FSMonad m => FilePath -> m (Maybe ([DirName], [FileName]))
- fs_doesFileExistL :: FSMonad m => FPath -> m Bool
- fs_doesFileExist :: FSMonad m => FilePath -> m Bool
- fs_doesDirectoryExistL :: FSMonad m => DirPath -> m Bool
- fs_doesDirectoryExist :: FSMonad m => FilePath -> m Bool
- fs_createDirectoryL :: FSMonad m => DirPath -> m ()
- fs_createDirectory :: FSMonad m => FilePath -> m ()
- fs_removeDirectoryL :: FSMonad m => DirPath -> m ()
- fs_removeDirectory :: FSMonad m => FilePath -> m ()
- fs_removeFileL :: FSMonad m => FPath -> m ()
- fs_removeFile :: FSMonad m => FilePath -> m ()
- fs_renameDirectoryL :: FSMonad m => DirPath -> DirPath -> m Bool
- fs_renameDirectory :: FSMonad m => FilePath -> FilePath -> m Bool
- fs_renameFileL :: FSMonad m => DirPath -> FileName -> FileName -> m Bool
- fs_renameFile :: FSMonad m => FilePath -> FileName -> FileName -> m Bool
- fs_copyFileL :: FSMonad m => FPath -> FPath -> m Bool
- fs_copyFile :: FSMonad m => FilePath -> FilePath -> m Bool
- fs_getModificationTimeL :: FSMonad m => FPath -> m (Maybe ClockTime)
- fs_getModificationTime :: FSMonad m => FilePath -> m (Maybe ClockTime)
- module System.FileSystem.IO
- module System.FileSystem.Instances
- module System.FileSystem.Class
Several type synonyms
Types
ByteString
A re-export of the ByteString type.
The content of a File is stored in a ByteString.
data ByteString
A space-efficient representation of a Word8 vector, supporting many
efficient operations. A ByteString contains 8-bit characters only.
Instances of Eq, Ord, Read, Show, Data, Typeable
ClockTime
data ClockTime
A representation of the internal clock time.
Clock times may be compared, converted to strings, or converted to an
external calendar time CalendarTime for I/O or other manipulations.
File
The File type and basic functions to operate with it.
newFile :: FileName -> ByteString -> FileSource
Build a new file with an initial FileName and content.
getFileName :: File -> FileNameSource
Get the name of a File.
getFileContent :: File -> ByteStringSource
Extract the content of a File.
setFileContent :: ByteString -> File -> FileSource
Set the content of a File to the given ByteString.
getModifTime :: File -> ClockTimeSource
Get the last modification time of a File.
FileSystem
data FileSystem Source
The file system structure. It stores a directory with files and subdirectories.
Instances
emptyFileSystem :: FileSystemSource
An empty file system.
Across the FileSystem
Mapping
mapFileSystem :: InApp DirName -> InApp File -> InApp FileSystemSource
Map a pair of applications (one over DirName, and the other over File) through a FileSystem.
mapFiles :: InApp File -> InApp FileSystemSource
Map a function over all the Files of a FileSystem.
Folding
Arguments
| :: FilePath | Root path |
| -> Either (FilePath -> t -> Either DirName File -> t) (FilePath -> Either DirName File -> t -> t) | Folding operator, with current |
| -> t | The initial value |
| -> FileSystem | The |
| -> t | Result |
Folding function for FileSystems.
foldFiles :: Either (t -> File -> t) (File -> t -> t) -> t -> FileSystem -> tSource
An usage of foldFileSystem, folding only Files, ignoring the FilePath where they are.
Computations over a FileSystem
Types
FST monad transformer
type FSState = FileSystemSource
The state of file system computations.
Currently, a FileSystem structure.
Monadic transformer which adds a FSState environment.
runFST :: Monad m => FST m a -> FSState -> m (a, FSState)Source
Run an FST computation, given an initial state.
List-based paths
List-based paths is an alternative to FilePath
that represents a path as a list of names.
While directory paths are a simple list of DirNames,
file paths are a pair: (DirPath,FileName).
First component is the directory where the file is,
and the second is the name of the file.
Below you can see a list of examples of how
to represent several FilePaths:
| FilePath | List-based path | ------------------------------------ | "aa\bb\cc" | ["aa","bb",cc"] | | "dir\file" | (["dir"],"file") | | "a\b\f.hs" | (["a","b"],"f.hs") |
type FPath = (DirPath, FileName)Source
A file path, composed by the path of the directory which contains it, and its file name.
Computations
Computations within a FSMonad environment.
All functions have a list-based path version (with L at the end),
and a normal FilePath version.
Use toDirPath (toFPath) and fromDirPath (fromFPath) to change between both formats.
Also, to avoid name collisions, function with existing names
have fs_ as preffix.
Put/Get File operations
Puts a file in the given directory. It creates the parent directory if missing.
modFileL :: FSMonad m => FPath -> InApp File -> m BoolSource
Modifies a file with the given application. It returns True if the file was found and modified.
Moves a file.
It returns True if the file exists and has been moved.
Writing and reading
Writing and reading files in a FSMonad environment.
Pure operations
fs_writeFileL :: FSMonad m => FPath -> ByteString -> m ()Source
Writes a file. If the files already exists, it is overwritten.
fs_writeFile :: FSMonad m => FilePath -> ByteString -> m ()Source
fs_readFileL :: FSMonad m => FPath -> m (Maybe ByteString)Source
Reads a file. It returns Nothing if the file can't be found.
fs_readFile :: FSMonad m => FilePath -> m (Maybe ByteString)Source
IO monad operations
writeFileTimeL :: (FSMonad m, MonadIO m) => FPath -> ByteString -> m ()Source
Writes a file, changing its last modification time to the current time. If the file already exists, it is overwritten. Note that MonadIO instance is needed.
writeFileTime :: (FSMonad m, MonadIO m) => FilePath -> ByteString -> m ()Source
System.Directory operations
All these functions are analogous to those defined in System.Directory.
fs_getDirectoryContentsL :: FSMonad m => DirPath -> m (Maybe ([DirName], [FileName]))Source
Returns all directory names and file names located in the given directory.
It returns Nothing if the directory does not exist.
fs_doesFileExistL :: FSMonad m => FPath -> m BoolSource
Checks if a file exists.
fs_doesFileExist :: FSMonad m => FilePath -> m BoolSource
fs_doesDirectoryExistL :: FSMonad m => DirPath -> m BoolSource
Checks if a directory exists.
fs_doesDirectoryExist :: FSMonad m => FilePath -> m BoolSource
fs_createDirectoryL :: FSMonad m => DirPath -> m ()Source
Creates a new directory. If the directory already exists, it does nothing.
fs_createDirectory :: FSMonad m => FilePath -> m ()Source
fs_removeDirectoryL :: FSMonad m => DirPath -> m ()Source
Removes a directory, with all its content. If the directory does not exist, it does nothing.
fs_removeDirectory :: FSMonad m => FilePath -> m ()Source
fs_removeFileL :: FSMonad m => FPath -> m ()Source
Removes a file. If the file does not exist, it does nothing.
fs_removeFile :: FSMonad m => FilePath -> m ()Source
fs_renameDirectoryL :: FSMonad m => DirPath -> DirPath -> m BoolSource
Renames a directory.
If the directory can't be found, it returns False.
Arguments
| :: FSMonad m | |
| => DirPath | Directory where the file is. |
| -> FileName | Original name. |
| -> FileName | New name. |
| -> m Bool |
Renames a file. First, you must specify the directory where the file is.
If the file can't be found, it returns False.
fs_copyFileL :: FSMonad m => FPath -> FPath -> m BoolSource
Copies a file from a location to another.
Returns True if the file was found and copied.
fs_getModificationTimeL :: FSMonad m => FPath -> m (Maybe ClockTime)Source
Gets the last modification time of a file. It returns Nothing if the file doesn't exist.
Re-exports
IO interface
module System.FileSystem.IO
Class instances
Some needed class instances.
module System.FileSystem.Instances
FSMonad class
If you want to use another monad, instead of FST,
make your type instance of the class here defined, FSMonad.
module System.FileSystem.Class