{-# LANGUAGE GeneralizedNewtypeDeriving #-} module System.FileSystem.Types ( -- * Synonyms InApp , DirName , FileName , FileCnt , DirPath , toDirPath , fromDirPath , FPath , toFPath , fromFPath -- * File , FileData (..) , emptyFD , File (..) -- * File System , FSE , FileSystem (..) , emptyFileSystem , modDirCnt -- * Path , Path (..) , isFilePath -- * FileSystem monad , FSState , FST (..) , runFST , FS , runFS ) where import Data.ByteString (ByteString,empty) import Data.Maybe (isNothing) import System.Time (ClockTime (..)) import Control.Monad.Identity (Identity (..)) import Control.Monad.State (StateT,MonadIO,runStateT,MonadTrans) import System.FilePath (splitPath , splitFileName , joinPath , combine) import Control.Arrow ( first ) -- | Internal Application: An application from somewhere over itself. type InApp a = a -> a -- | A name for a directory. type DirName = String -- | A name for a file. type FileName = String -- | The content of a file. Stored in a 'ByteString'. type FileCnt = ByteString -- | A list-based directory path. type DirPath = [DirName] -- | Translation between 'FilePath' and 'DirPath'. toDirPath :: FilePath -> DirPath toDirPath = splitPath -- | Translation between 'DirPath' and 'FilePath'. fromDirPath :: DirPath -> FilePath fromDirPath = joinPath -- | A file path, composed by the path of the directory which contains it, -- and its file name. type FPath = (DirPath,FileName) -- | Translation between 'FilePath' and 'FPath'. toFPath :: FilePath -> FPath toFPath = first splitPath . splitFileName -- | Translation between 'FPath' and 'FilePath'. fromFPath :: FPath -> FilePath fromFPath = uncurry combine . first fromDirPath -- | Information about the content of a file. data FileData = FD { getCnt :: FileCnt , getLmt :: ClockTime } deriving Eq -- | An empty file data. emptyFD :: FileData emptyFD = FD empty (TOD 0 0) -- | A complete file. data File = File { getFD :: FileData , getFN :: FileName } deriving Eq instance Show File where show (File _ fn) = "FILE[" ++ fn ++ "]" -- | File System Element: Each one of the elements in a 'FileSystem'. type FSE = Either (DirName,FileSystem) File -- | The file system structure. It stores a directory with files and subdirectories. newtype FileSystem = Directory { dirCnt :: [FSE] } deriving Show -- | An empty file system. emptyFileSystem :: FileSystem emptyFileSystem = Directory [] -- | Lift a function over a list of 'FSE' (File System Elements) -- to a function over 'FileSystem'. modDirCnt :: InApp [FSE] -> InApp FileSystem modDirCnt f fs = fs { dirCnt = f $ dirCnt fs } -- | A path to a possible 'File'. data Path = Path { pathList :: DirPath , pathFile :: Maybe File } -- | Check if a 'Path' contents a 'File'. isFilePath :: Path -> Bool isFilePath = not . isNothing . pathFile -- | The state of file system computations. -- -- Currently, a 'FileSystem' structure. type FSState = FileSystem -- | Monadic transformer which adds a 'FSState' environment. newtype FST m a = WrapFST { unwrapFST :: StateT FSState m a } deriving (Functor, Monad, MonadIO, MonadTrans) -- | Run an 'FST' computation, given an initial state. runFST :: Monad m => FST m a -> FSState -> m (a,FSState) runFST = runStateT . unwrapFST -- | Application of the 'FST' monad transformer to the 'Identity' monad. type FS = FST Identity -- | Just a composition of 'runIdentity' and 'runFST'. runFS :: FS a -> FSState -> (a,FSState) runFS c = runIdentity . runFST c