{-# LANGUAGE Safe #-}
module System.IO.HVFS.InstanceHelpers(
SimpleStat(..),
MemoryVFS,
newMemoryVFS, newMemoryVFSRef,
MemoryNode,
MemoryEntry(..),
nice_slice, getFullPath,
getFullSlice)
where
import Data.IORef (IORef, newIORef, readIORef, writeIORef)
import Data.List (genericLength)
import System.FilePath (isPathSeparator, pathSeparator, (</>))
import System.IO
import System.IO.Error (doesNotExistErrorType,
illegalOperationErrorType,
permissionErrorType)
import System.IO.HVFS
import System.IO.HVIO (newStreamReader)
import System.Path (absNormPath)
import System.Path.NameManip (slice_path)
data SimpleStat = SimpleStat {
isFile :: Bool,
fileSize :: FileOffset
} deriving (Show, Eq)
instance HVFSStat SimpleStat where
vIsRegularFile x = isFile x
vIsDirectory x = not (isFile x)
vFileSize x = fileSize x
type MemoryNode = (String, MemoryEntry)
data MemoryEntry = MemoryDirectory [MemoryNode]
| MemoryFile String
deriving (Eq, Show)
data MemoryVFS = MemoryVFS
{ content :: IORef [MemoryNode],
cwd :: IORef FilePath
}
instance Show MemoryVFS where
show _ = "<MemoryVFS>"
newMemoryVFS :: [MemoryNode] -> IO MemoryVFS
newMemoryVFS s = do r <- newIORef s
newMemoryVFSRef r
newMemoryVFSRef :: IORef [MemoryNode] -> IO MemoryVFS
newMemoryVFSRef r = do
c <- newIORef [pathSeparator]
return (MemoryVFS {content = r, cwd = c})
nice_slice :: String -> [String]
nice_slice path
| path == [pathSeparator] = []
| otherwise =
let sliced1 = slice_path path
h = head sliced1
t = tail sliced1
newh = if isPathSeparator (head h) then tail h else h
sliced2 = newh : t
in sliced2
getFullPath :: HVFS a => a -> String -> IO String
getFullPath fs path =
do cwd <- vGetCurrentDirectory fs
case (absNormPath cwd path) of
Nothing -> vRaiseError fs doesNotExistErrorType
("Trouble normalizing path " ++ path) (Just (cwd </> path))
Just newpath -> return newpath
getFullSlice :: HVFS a => a -> String -> IO [String]
getFullSlice fs fp =
do newpath <- getFullPath fs fp
return (nice_slice newpath)
findMelem :: MemoryVFS -> String -> IO MemoryEntry
findMelem x path
| path == [pathSeparator] = readIORef (content x) >>= return . MemoryDirectory
| otherwise =
let sliced1 = slice_path path
h = head sliced1
t = tail sliced1
newh = if (h /= [pathSeparator]) && isPathSeparator (head h) then tail h else h
sliced2 = newh : t
walk :: MemoryEntry -> [String] -> Either String MemoryEntry
walk y zs
| null zs = Right y
| zs == [[pathSeparator]] = Right y
| otherwise = case y of
MemoryFile _ -> Left $ "Attempt to look up name " ++ head zs ++ " in file"
MemoryDirectory y ->
let newentry = case lookup (head zs) y of
Nothing -> Left $ "Couldn't find entry " ++ head zs
Just a -> Right a
in do newobj <- newentry
walk newobj (tail zs)
in do
c <- readIORef $ content x
case walk (MemoryDirectory c) (sliced2) of
Left err -> vRaiseError x doesNotExistErrorType err Nothing
Right result -> return result
getMelem :: MemoryVFS -> String -> IO MemoryEntry
getMelem x s =
do base <- readIORef $ cwd x
case absNormPath base s of
Nothing -> vRaiseError x doesNotExistErrorType
("Trouble normalizing path " ++ s) (Just s)
Just newpath -> findMelem x newpath
instance HVFS MemoryVFS where
vGetCurrentDirectory x = readIORef $ cwd x
vSetCurrentDirectory x fp =
do curpath <- vGetCurrentDirectory x
newdir <- getMelem x fp
case newdir of
(MemoryFile _) -> vRaiseError x doesNotExistErrorType
("Attempt to cwd to non-directory " ++ fp)
(Just fp)
(MemoryDirectory _) ->
case absNormPath curpath fp of
Nothing ->
vRaiseError x illegalOperationErrorType
"Bad internal error" (Just fp)
Just y -> writeIORef (cwd x) y
vGetFileStatus x fp =
do elem <- getMelem x fp
case elem of
(MemoryFile y) -> return $ HVFSStatEncap $
SimpleStat {isFile = True,
fileSize = (genericLength y)}
(MemoryDirectory _) -> return $ HVFSStatEncap $
SimpleStat {isFile = False,
fileSize = 0}
vGetDirectoryContents x fp =
do elem <- getMelem x fp
case elem of
MemoryFile _ -> vRaiseError x doesNotExistErrorType
"Can't list contents of a file"
(Just fp)
MemoryDirectory c -> return $ map fst c
instance HVFSOpenable MemoryVFS where
vOpen x fp (ReadMode) =
do elem <- getMelem x fp
case elem of
MemoryDirectory _ -> vRaiseError x doesNotExistErrorType
"Can't open a directory"
(Just fp)
MemoryFile y -> newStreamReader y >>= return . HVFSOpenEncap
vOpen x fp _ = vRaiseError x permissionErrorType
"Only ReadMode is supported with MemoryVFS files"
(Just fp)