module System.FileSystem ( -- * Several type synonyms InApp , DirName , FileName -- * Types -- ** @ByteString@ -- | A re-export of the 'ByteString' type. -- The content of a 'File' is stored in a 'ByteString'. , ByteString -- ** @ClockTime@ -- | A re-export of the 'ClockTime' type. -- 'ClockTime' is used to represents modification times. , ClockTime -- ** @File@ -- | The 'File' type and basic functions to operate with it. , File , emptyFile , newFile , getFileName , setFileName , getFileContent , setFileContent , getModifTime , setModifTime , fileSize -- ** @FileSystem@ , FileSystem , emptyFileSystem -- * Across the @FileSystem@ -- ** Mapping , mapFileSystem , mapFiles -- ** Folding , foldFileSystem , foldFiles -- * Computations over a @FileSystem@ -- ** Types -- *** @FST@ monad transformer , FSState , FST , runFST , FS, runFS -- *** 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 'DirName's, -- 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 'FilePath's: -- -- > | FilePath | List-based path | -- > ------------------------------------ -- > | "aa\bb\cc" | ["aa","bb",cc"] | -- > | "dir\file" | (["dir"],"file") | -- > | "a\b\f.hs" | (["a","b"],"f.hs") | , DirPath , toDirPath , fromDirPath , FPath , toFPath , fromFPath -- ** 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 , putFileL , putFile , getFileL , getFile , modFileL , modFile , moveFileL , moveFile -- *** Writing and reading -- | Writing and reading files in a 'FSMonad' environment. -- **** Pure operations , fs_writeFileL , fs_writeFile , fs_readFileL , fs_readFile -- **** 'IO' monad operations , writeFileTimeL , writeFileTime -- *** @System.Directory@ operations -- | All these functions are analogous to those defined in "System.Directory". , fs_getDirectoryContentsL , fs_getDirectoryContents , fs_doesFileExistL , fs_doesFileExist , fs_doesDirectoryExistL , fs_doesDirectoryExist , fs_createDirectoryL , fs_createDirectory , fs_removeDirectoryL , fs_removeDirectory , fs_removeFileL , fs_removeFile , fs_renameDirectoryL , fs_renameDirectory , fs_renameFileL , fs_renameFile , fs_copyFileL , fs_copyFile , fs_getModificationTimeL , fs_getModificationTime -- * 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 ) where import Data.ByteString (ByteString, length) import System.Time (ClockTime,getClockTime) import Control.Arrow (first , (***)) import System.FilePath (splitFileName) import Data.Maybe (isJust,fromJust) import Control.Monad.State (runStateT,MonadIO,liftIO) -- import System.FileSystem.Types import System.FileSystem.Across import System.FileSystem.IO import System.FileSystem.Computations import System.FileSystem.Utils import System.FileSystem.Instances import System.FileSystem.Class -- | Create an empty file with the given 'FileName'. emptyFile :: FileName -> File emptyFile = File emptyFD -- | Build a new file with an initial 'FileName' and content. newFile :: FileName -> ByteString -> File newFile = curry $ uncurry (flip setFileContent) . first emptyFile -- | Get the name of a 'File'. getFileName :: File -> FileName getFileName = getFN -- | Rename a 'File' with the given 'FileName'. setFileName :: FileName -> File -> File setFileName fn f = f { getFN = fn } -- | Extract the content of a 'File'. getFileContent :: File -> ByteString getFileContent = getCnt . getFD -- | Set the content of a 'File' to the given 'ByteString'. setFileContent :: ByteString -> File -> File setFileContent c f = f { getFD = (getFD f) { getCnt = c } } -- | Get the last modification time of a 'File'. getModifTime :: File -> ClockTime getModifTime = getLmt . getFD -- | Set the last modification time of a 'File'. setModifTime :: ClockTime -> File -> File setModifTime t f = f { getFD = (getFD f) { getLmt = t } } -- | Calculate the size of a 'File'. fileSize :: File -> Int fileSize = Data.ByteString.length . getFileContent -- | Map a function over all the 'File's of a 'FileSystem'. mapFiles :: InApp File -> InApp FileSystem mapFiles = mapFileSystem id -- Computations over the file system. -- | Puts a file in the given directory. It creates the parent directory if missing. putFileL :: FSMonad m => DirPath -- ^ Directory where put the 'File'. -> File -> m () putFileL dp = putPath . Path dp . Just putFile :: FSMonad m => FilePath -> File -> m () putFile = putFileL . toDirPath -- | Gets a file from the file system. -- It returns 'Nothing' if the 'File' is not found. getFileL :: FSMonad m => FPath -- ^ Path where search the 'File'. -> m (Maybe File) getFileL = getFl getFile :: FSMonad m => FilePath -> m (Maybe File) getFile = getFileL . toFPath -- | Modifies a file with the given application. It returns 'True' if the file was found and modified. modFileL :: FSMonad m => FPath -> InApp File -> m Bool modFileL fp f = do file <- getFileL fp if isJust file then do putFileL (fst fp) $ f $ fromJust file return True else return False modFile :: FSMonad m => FilePath -> InApp File -> m Bool modFile = modFileL . toFPath -- | Moves a file. -- It returns 'True' if the file exists and has been moved. moveFileL :: FSMonad m => FPath -- ^ Original path of the 'File'. -> FPath -- ^ New path for the 'File'. -> m Bool moveFileL fp1 (dp,fn) = do f1 <- getFileL fp1 if isJust f1 then do putFileL dp $ setFileName fn $ fromJust f1 fs_removeFileL fp1 return True else return False moveFile :: FSMonad m => FilePath -> FilePath -> m Bool moveFile = curry $ uncurry moveFileL . pairMap toFPath -- | Writes a file. If the files already exists, it is overwritten. fs_writeFileL :: FSMonad m => FPath -> ByteString -> m () fs_writeFileL = uncurry (.) . (putFileL *** newFile) fs_writeFile :: FSMonad m => FilePath -> ByteString -> m () fs_writeFile = fs_writeFileL . toFPath -- | 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/. writeFileTimeL :: (FSMonad m, MonadIO m) => FPath -> ByteString -> m () writeFileTimeL (dp,fn) bs = do t <- liftIO getClockTime putFileL dp . setModifTime t $ newFile fn bs writeFileTime :: (FSMonad m, MonadIO m) => FilePath -> ByteString -> m () writeFileTime = writeFileTimeL . toFPath -- | Reads a file. It returns 'Nothing' if the file can't be found. fs_readFileL :: FSMonad m => FPath -> m (Maybe ByteString) fs_readFileL = fmap (fmap getFileContent) . getFileL fs_readFile :: FSMonad m => FilePath -> m (Maybe ByteString) fs_readFile = fs_readFileL . toFPath -- | Returns all directory names and file names located in the given directory. -- It returns 'Nothing' if the directory does not exist. fs_getDirectoryContentsL :: FSMonad m => DirPath -> m (Maybe ([DirName],[FileName])) fs_getDirectoryContentsL = getDirCnt fs_getDirectoryContents :: FSMonad m => FilePath -> m (Maybe ([DirName],[FileName])) fs_getDirectoryContents = fs_getDirectoryContentsL . toDirPath -- | Checks if a file exists. fs_doesFileExistL :: FSMonad m => FPath -> m Bool fs_doesFileExistL = checkFExist fs_doesFileExist :: FSMonad m => FilePath -> m Bool fs_doesFileExist = fs_doesFileExistL . toFPath -- | Checks if a directory exists. fs_doesDirectoryExistL :: FSMonad m => DirPath -> m Bool fs_doesDirectoryExistL = checkDExist fs_doesDirectoryExist :: FSMonad m => FilePath -> m Bool fs_doesDirectoryExist = fs_doesDirectoryExistL . toDirPath -- | Creates a new directory. If the directory already exists, it does nothing. fs_createDirectoryL :: FSMonad m => DirPath -> m () fs_createDirectoryL = newDir fs_createDirectory :: FSMonad m => FilePath -> m () fs_createDirectory = fs_createDirectoryL . toDirPath -- | Removes a directory, with all its content. -- If the directory does not exist, it does nothing. fs_removeDirectoryL :: FSMonad m => DirPath -> m () fs_removeDirectoryL = rmvDir fs_removeDirectory :: FSMonad m => FilePath -> m () fs_removeDirectory = fs_removeDirectoryL . toDirPath -- | Removes a file. If the file does not exist, it does nothing. fs_removeFileL :: FSMonad m => FPath -> m () fs_removeFileL = rmvFile fs_removeFile :: FSMonad m => FilePath -> m () fs_removeFile = fs_removeFileL . toFPath -- | Renames a directory. -- If the directory can't be found, it returns 'False'. fs_renameDirectoryL :: FSMonad m => DirPath -> DirPath -> m Bool fs_renameDirectoryL = curry rnmDir fs_renameDirectory :: FSMonad m => FilePath -> FilePath -> m Bool fs_renameDirectory = curry $ rnmDir . pairMap toDirPath -- | Renames a file. First, you must specify the directory where the file is. -- If the file can't be found, it returns 'False'. fs_renameFileL :: FSMonad m => DirPath -- ^ Directory where the file is. -> FileName -- ^ Original name. -> FileName -- ^ New name. -> m Bool fs_renameFileL dp fn1 fn2 = rnmFile ( (dp,fn1) , (dp,fn2) ) fs_renameFile :: FSMonad m => FilePath -> FileName -> FileName -> m Bool fs_renameFile = fs_renameFileL . toDirPath -- | Copies a file from a location to another. -- Returns 'True' if the file was found and copied. fs_copyFileL :: FSMonad m => FPath -> FPath -> m Bool fs_copyFileL f1 f2 = fs_readFileL f1 >>= maybe ( return False ) ( bind (const $ return True) . fs_writeFileL f2) fs_copyFile :: FSMonad m => FilePath -> FilePath -> m Bool fs_copyFile = curry $ uncurry fs_copyFileL . pairMap toFPath -- | Gets the last modification time of a file. It returns 'Nothing' if the file doesn't exist. fs_getModificationTimeL :: FSMonad m => FPath -> m (Maybe ClockTime) fs_getModificationTimeL = fmap (fmap getModifTime) . getFileL fs_getModificationTime :: FSMonad m => FilePath -> m (Maybe ClockTime) fs_getModificationTime = fs_getModificationTimeL . toFPath