module Halfs.Directory (Directory(..), getChildrenInodeNums, addChild, removeChild, getChildWithName, getChildrenNames, filePathsNoDots, hasChild, DirectoryMap, dirInodeNum, -- intentionally not exporting DirectoryCache -- constructor because we don't want anyone -- messing with its dirty bit. DirectoryCache(..), emptyDirectoryCache, addDirectoryToCache, getDirectoryFromCache, directoryCacheToList, dirCacheDirty, markDirectoryCacheClean, rmDirectoryFromCache) where import Halfs.Inode(Inode(..), InodeMetadata(..), inodeAddLink) import {-# SOURCE #-} Halfs.FileHandle (FileHandle, fhInodeNum) import Data.Integral (INInt) --base import Data.Map(Map) import qualified Data.Map as Map import Control.Exception(assert) -- |Maps strings to inode numbers type DirectoryMap = Map String INInt data Directory = Directory {dirFile :: FileHandle ,dirContents :: DirectoryMap ,dirDirty :: Bool } dirInodeNum :: Directory -> INInt dirInodeNum d = fhInodeNum $ dirFile d addChild :: Directory -- ^to add to -> Inode -- ^new child's inode -> String -- ^Name -> Maybe (Directory, Inode) -- ^Nothing if already exists (updated version of parent directory, updated version of child's inode) addChild (Directory dirFH theContents _) inode name = case Map.lookup name theContents of Just _ -> Nothing -- shouldn't be there! Nothing -> Just ((Directory dirFH (Map.insert name (assert (inodeNum > 0) inodeNum) theContents) True ,inodeAddLink inode)) where inodeNum = inode_num $ metaData inode -- |Does this directory have the given file in it? hasChild :: Directory -> String -> Bool hasChild Directory{dirContents=theMap} s = Map.member s theMap removeChild :: Directory -> String -> Directory removeChild (Directory f c _) k = Directory f (Map.delete k c) True -- |Get the inode numbers from the contents of this directory getChildrenInodeNums :: Directory -> [INInt] getChildrenInodeNums = Map.elems . dirContents getChildrenNames :: Directory -> [String] getChildrenNames = Map.keys . dirContents getChildWithName :: Directory -> String -> Maybe INInt getChildWithName dir str = let e = Map.lookup str (dirContents dir) in assert (notLEZ e) e -- Check to make sure that the number is valid; 0 is invalid because -- its not the child of anything. where notLEZ Nothing = True notLEZ (Just n) = n > 0 filePathsNoDots :: [FilePath] -> [FilePath] filePathsNoDots = filter (\x -> (x /= ".") && (x /= "..")) -- ------------------------------------------------------------ -- * directory cache -- ------------------------------------------------------------ -- |Maps from inode numbers to directories. data DirectoryCache = DirectoryCache { dirCacheDirty :: Bool , _dirCache :: Map INInt Directory} emptyDirectoryCache :: DirectoryCache emptyDirectoryCache = DirectoryCache False Map.empty directoryCacheToList :: DirectoryCache -> [Directory] directoryCacheToList (DirectoryCache _ c) = Map.elems c -- |Also used for updating. If this directory is marked dirty, then -- the cache will also be marked dirty. addDirectoryToCache :: DirectoryCache -> Directory -> DirectoryCache addDirectoryToCache (DirectoryCache cacheDirty c) d = DirectoryCache (if dirDirty d then True else cacheDirty) (Map.insert (dirInodeNum d) d c) markDirectoryCacheClean :: DirectoryCache -> DirectoryCache markDirectoryCacheClean (DirectoryCache _ c) = DirectoryCache False c getDirectoryFromCache :: DirectoryCache -> INInt -> Maybe Directory getDirectoryFromCache (DirectoryCache _ c) i = Map.lookup i c -- |Does not complain if the item does not exist. Directory cache -- stays clean. rmDirectoryFromCache :: DirectoryCache -> INInt -> DirectoryCache rmDirectoryFromCache (DirectoryCache _ c) i = DirectoryCache False (Map.delete i c)