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