module Effectful.Posix.Files.Dynamic
(
PosixFiles (..),
setFileMode,
setFdMode,
setFileCreationMask,
fileAccess,
fileExist,
getFileStatus,
getFdStatus,
getSymbolicLinkStatus,
createNamedPipe,
createDevice,
createLink,
removeLink,
createSymbolicLink,
readSymbolicLink,
rename,
setOwnerAndGroup,
setFdOwnerAndGroup,
setSymbolicLinkOwnerAndGroup,
setFileTimes,
touchFile,
setFileSize,
setFdSize,
getPathVar,
getFdPathVar,
runPosixFiles,
PathType (..),
displayPathType,
throwIfWrongPathType,
isPathType,
getPathType,
)
where
import Control.Monad (unless)
import Data.Functor ((<&>))
import Effectful
( Dispatch (Dynamic),
DispatchOf,
Eff,
Effect,
IOE,
type (:>),
)
import Effectful.Dispatch.Dynamic (HasCallStack, reinterpret_, send)
import Effectful.Dynamic.Utils (ShowEffect (showEffectCons))
import Effectful.Posix.Files.Static qualified as Static
import FileSystem.IO qualified as FS.IO
import FileSystem.PathType
( PathType
( PathTypeDirectory,
PathTypeFile,
PathTypeOther,
PathTypeSymbolicLink
),
displayPathType,
)
import GHC.IO.Exception (IOErrorType (InappropriateType))
import System.OsString.Internal.Types (OsString (OsString))
import System.Posix.Files.PosixString (FileStatus, PathVar)
import System.Posix.Files.PosixString qualified as PFiles
import System.Posix.PosixString (PosixPath)
import System.Posix.Types
( DeviceID,
EpochTime,
Fd,
FileMode,
FileOffset,
GroupID,
Limit,
UserID,
)
data PosixFiles :: Effect where
SetFileMode :: PosixPath -> FileMode -> PosixFiles m ()
SetFdMode :: Fd -> FileMode -> PosixFiles m ()
SetFileCreationMask :: FileMode -> PosixFiles m FileMode
FileAccess :: PosixPath -> Bool -> Bool -> Bool -> PosixFiles m Bool
FileExist :: PosixPath -> PosixFiles m Bool
GetFileStatus :: PosixPath -> PosixFiles m FileStatus
GetFdStatus :: Fd -> PosixFiles m FileStatus
GetSymbolicLinkStatus :: PosixPath -> PosixFiles m FileStatus
CreateNamedPipe :: PosixPath -> FileMode -> PosixFiles m ()
CreateDevice :: PosixPath -> FileMode -> DeviceID -> PosixFiles m ()
CreateLink :: PosixPath -> PosixPath -> PosixFiles m ()
RemoveLink :: PosixPath -> PosixFiles m ()
CreateSymbolicLink :: PosixPath -> PosixPath -> PosixFiles m ()
ReadSymbolicLink :: PosixPath -> PosixFiles m PosixPath
Rename :: PosixPath -> PosixPath -> PosixFiles m ()
SetOwnerAndGroup :: PosixPath -> UserID -> GroupID -> PosixFiles m ()
SetFdOwnerAndGroup :: Fd -> UserID -> GroupID -> PosixFiles m ()
SetSymbolicLinkOwnerAndGroup ::
PosixPath -> UserID -> GroupID -> PosixFiles m ()
SetFileTimes :: PosixPath -> EpochTime -> EpochTime -> PosixFiles m ()
TouchFile :: PosixPath -> PosixFiles m ()
SetFileSize :: PosixPath -> FileOffset -> PosixFiles m ()
SetFdSize :: Fd -> FileOffset -> PosixFiles m ()
GetPathVar :: PosixPath -> PathVar -> PosixFiles m Limit
GetFdPathVar :: Fd -> PathVar -> PosixFiles m Limit
type instance DispatchOf PosixFiles = Dynamic
instance ShowEffect PosixFiles where
showEffectCons :: forall (m :: * -> *) a. PosixFiles m a -> String
showEffectCons = \case
SetFileMode PosixPath
_ FileMode
_ -> String
"SetFileMode"
SetFdMode Fd
_ FileMode
_ -> String
"SetFdMode"
SetFileCreationMask FileMode
_ -> String
"SetFileCreationMask"
FileAccess PosixPath
_ Bool
_ Bool
_ Bool
_ -> String
"FileAccess"
FileExist PosixPath
_ -> String
"FileExist"
GetFileStatus PosixPath
_ -> String
"GetFileStatus"
GetFdStatus Fd
_ -> String
"GetFdStatus"
GetSymbolicLinkStatus PosixPath
_ -> String
"GetSymbolicLinkStatus"
CreateNamedPipe PosixPath
_ FileMode
_ -> String
"CreateNamedPipe"
CreateDevice PosixPath
_ FileMode
_ DeviceID
_ -> String
"CreateDevice"
CreateLink PosixPath
_ PosixPath
_ -> String
"CreateLink"
RemoveLink PosixPath
_ -> String
"RemoveLink"
CreateSymbolicLink PosixPath
_ PosixPath
_ -> String
"CreateSymbolicLink"
ReadSymbolicLink PosixPath
_ -> String
"ReadSymbolicLink"
Rename PosixPath
_ PosixPath
_ -> String
"Rename"
SetOwnerAndGroup PosixPath
_ UserID
_ GroupID
_ -> String
"SetOwnerAndGroup"
SetFdOwnerAndGroup Fd
_ UserID
_ GroupID
_ -> String
"SetFdOwnerAndGroup"
SetSymbolicLinkOwnerAndGroup PosixPath
_ UserID
_ GroupID
_ -> String
"SetSymbolicLinkOwnerAndGroup"
SetFileTimes PosixPath
_ EpochTime
_ EpochTime
_ -> String
"SetFileTimes"
TouchFile PosixPath
_ -> String
"TouchFile"
SetFileSize PosixPath
_ FileOffset
_ -> String
"SetFileSize"
SetFdSize Fd
_ FileOffset
_ -> String
"SetFdSize"
GetPathVar PosixPath
_ PathVar
_ -> String
"GetPathVar"
GetFdPathVar Fd
_ PathVar
_ -> String
"GetFdPathVar"
runPosixFiles ::
(HasCallStack, IOE :> es) =>
Eff (PosixFiles : es) a ->
Eff es a
runPosixFiles :: forall (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, IOE :> es) =>
Eff (PosixFiles : es) a -> Eff es a
runPosixFiles = (Eff (PosixFiles : es) a -> Eff es a)
-> EffectHandler_ PosixFiles (PosixFiles : es)
-> Eff (PosixFiles : es) a
-> Eff es a
forall (e :: (* -> *) -> * -> *)
(handlerEs :: [(* -> *) -> * -> *]) a (es :: [(* -> *) -> * -> *])
b.
(HasCallStack, DispatchOf e ~ 'Dynamic) =>
(Eff handlerEs a -> Eff es b)
-> EffectHandler_ e handlerEs -> Eff (e : es) a -> Eff es b
reinterpret_ Eff (PosixFiles : es) a -> Eff es a
forall (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, IOE :> es) =>
Eff (PosixFiles : es) a -> Eff es a
Static.runPosixFiles (EffectHandler_ PosixFiles (PosixFiles : es)
-> Eff (PosixFiles : es) a -> Eff es a)
-> EffectHandler_ PosixFiles (PosixFiles : es)
-> Eff (PosixFiles : es) a
-> Eff es a
forall a b. (a -> b) -> a -> b
$ \case
SetFileMode PosixPath
p FileMode
m -> PosixPath -> FileMode -> Eff (PosixFiles : es) ()
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> FileMode -> Eff es ()
Static.setFileMode PosixPath
p FileMode
m
SetFdMode Fd
fd FileMode
m -> Fd -> FileMode -> Eff (PosixFiles : es) ()
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
Fd -> FileMode -> Eff es ()
Static.setFdMode Fd
fd FileMode
m
SetFileCreationMask FileMode
m -> FileMode -> Eff (PosixFiles : es) FileMode
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
FileMode -> Eff es FileMode
Static.setFileCreationMask FileMode
m
FileAccess PosixPath
p Bool
b Bool
c Bool
d -> PosixPath -> Bool -> Bool -> Bool -> Eff (PosixFiles : es) Bool
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Bool -> Bool -> Bool -> Eff es Bool
Static.fileAccess PosixPath
p Bool
b Bool
c Bool
d
FileExist PosixPath
p -> PosixPath -> Eff (PosixFiles : es) Bool
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Eff es Bool
Static.fileExist PosixPath
p
GetFileStatus PosixPath
p -> PosixPath -> Eff (PosixFiles : es) FileStatus
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Eff es FileStatus
Static.getFileStatus PosixPath
p
GetFdStatus Fd
fd -> Fd -> Eff (PosixFiles : es) FileStatus
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
Fd -> Eff es FileStatus
Static.getFdStatus Fd
fd
GetSymbolicLinkStatus PosixPath
p -> PosixPath -> Eff (PosixFiles : es) FileStatus
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Eff es FileStatus
Static.getSymbolicLinkStatus PosixPath
p
CreateNamedPipe PosixPath
p FileMode
m -> PosixPath -> FileMode -> Eff (PosixFiles : es) ()
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> FileMode -> Eff es ()
Static.createNamedPipe PosixPath
p FileMode
m
CreateDevice PosixPath
p FileMode
m DeviceID
did -> PosixPath -> FileMode -> DeviceID -> Eff (PosixFiles : es) ()
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> FileMode -> DeviceID -> Eff es ()
Static.createDevice PosixPath
p FileMode
m DeviceID
did
CreateLink PosixPath
p1 PosixPath
p2 -> PosixPath -> PosixPath -> Eff (PosixFiles : es) ()
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> PosixPath -> Eff es ()
Static.createLink PosixPath
p1 PosixPath
p2
RemoveLink PosixPath
p -> PosixPath -> Eff (PosixFiles : es) ()
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Eff es ()
Static.removeLink PosixPath
p
CreateSymbolicLink PosixPath
p1 PosixPath
p2 -> PosixPath -> PosixPath -> Eff (PosixFiles : es) ()
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> PosixPath -> Eff es ()
Static.createSymbolicLink PosixPath
p1 PosixPath
p2
ReadSymbolicLink PosixPath
p -> PosixPath -> Eff (PosixFiles : es) PosixPath
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Eff es PosixPath
Static.readSymbolicLink PosixPath
p
Rename PosixPath
p1 PosixPath
p2 -> PosixPath -> PosixPath -> Eff (PosixFiles : es) ()
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> PosixPath -> Eff es ()
Static.rename PosixPath
p1 PosixPath
p2
SetOwnerAndGroup PosixPath
p UserID
uid GroupID
gid -> PosixPath -> UserID -> GroupID -> Eff (PosixFiles : es) ()
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> UserID -> GroupID -> Eff es ()
Static.setOwnerAndGroup PosixPath
p UserID
uid GroupID
gid
SetFdOwnerAndGroup Fd
fd UserID
uid GroupID
gid ->
Fd -> UserID -> GroupID -> Eff (PosixFiles : es) ()
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
Fd -> UserID -> GroupID -> Eff es ()
Static.setFdOwnerAndGroup Fd
fd UserID
uid GroupID
gid
SetSymbolicLinkOwnerAndGroup PosixPath
p UserID
uid GroupID
gid ->
PosixPath -> UserID -> GroupID -> Eff (PosixFiles : es) ()
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> UserID -> GroupID -> Eff es ()
Static.setSymbolicLinkOwnerAndGroup PosixPath
p UserID
uid GroupID
gid
SetFileTimes PosixPath
p EpochTime
t1 EpochTime
t2 -> PosixPath -> EpochTime -> EpochTime -> Eff (PosixFiles : es) ()
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> EpochTime -> EpochTime -> Eff es ()
Static.setFileTimes PosixPath
p EpochTime
t1 EpochTime
t2
TouchFile PosixPath
p -> PosixPath -> Eff (PosixFiles : es) ()
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Eff es ()
Static.touchFile PosixPath
p
SetFileSize PosixPath
p FileOffset
oset -> PosixPath -> FileOffset -> Eff (PosixFiles : es) ()
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> FileOffset -> Eff es ()
Static.setFileSize PosixPath
p FileOffset
oset
SetFdSize Fd
fd FileOffset
oset -> Fd -> FileOffset -> Eff (PosixFiles : es) ()
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
Fd -> FileOffset -> Eff es ()
Static.setFdSize Fd
fd FileOffset
oset
GetPathVar PosixPath
p PathVar
m -> PosixPath -> PathVar -> Eff (PosixFiles : es) CLong
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> PathVar -> Eff es CLong
Static.getPathVar PosixPath
p PathVar
m
GetFdPathVar Fd
fd PathVar
m -> Fd -> PathVar -> Eff (PosixFiles : es) CLong
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
Fd -> PathVar -> Eff es CLong
Static.getFdPathVar Fd
fd PathVar
m
setFileMode ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
FileMode ->
Eff es ()
setFileMode :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> FileMode -> Eff es ()
setFileMode PosixPath
p = PosixFiles (Eff es) () -> Eff es ()
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) () -> Eff es ())
-> (FileMode -> PosixFiles (Eff es) ()) -> FileMode -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> FileMode -> PosixFiles (Eff es) ()
forall (m :: * -> *). PosixPath -> FileMode -> PosixFiles m ()
SetFileMode PosixPath
p
setFdMode ::
( HasCallStack,
PosixFiles :> es
) =>
Fd ->
FileMode ->
Eff es ()
setFdMode :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
Fd -> FileMode -> Eff es ()
setFdMode Fd
p = PosixFiles (Eff es) () -> Eff es ()
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) () -> Eff es ())
-> (FileMode -> PosixFiles (Eff es) ()) -> FileMode -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Fd -> FileMode -> PosixFiles (Eff es) ()
forall (m :: * -> *). Fd -> FileMode -> PosixFiles m ()
SetFdMode Fd
p
setFileCreationMask ::
( HasCallStack,
PosixFiles :> es
) =>
FileMode ->
Eff es FileMode
setFileCreationMask :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
FileMode -> Eff es FileMode
setFileCreationMask = PosixFiles (Eff es) FileMode -> Eff es FileMode
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) FileMode -> Eff es FileMode)
-> (FileMode -> PosixFiles (Eff es) FileMode)
-> FileMode
-> Eff es FileMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileMode -> PosixFiles (Eff es) FileMode
forall (m :: * -> *). FileMode -> PosixFiles m FileMode
SetFileCreationMask
fileAccess ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
Bool ->
Bool ->
Bool ->
Eff es Bool
fileAccess :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Bool -> Bool -> Bool -> Eff es Bool
fileAccess PosixPath
p Bool
b Bool
c = PosixFiles (Eff es) Bool -> Eff es Bool
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) Bool -> Eff es Bool)
-> (Bool -> PosixFiles (Eff es) Bool) -> Bool -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> Bool -> Bool -> Bool -> PosixFiles (Eff es) Bool
forall (m :: * -> *).
PosixPath -> Bool -> Bool -> Bool -> PosixFiles m Bool
FileAccess PosixPath
p Bool
b Bool
c
fileExist ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
Eff es Bool
fileExist :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Eff es Bool
fileExist = PosixFiles (Eff es) Bool -> Eff es Bool
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) Bool -> Eff es Bool)
-> (PosixPath -> PosixFiles (Eff es) Bool)
-> PosixPath
-> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> PosixFiles (Eff es) Bool
forall (m :: * -> *). PosixPath -> PosixFiles m Bool
FileExist
getFileStatus ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
Eff es FileStatus
getFileStatus :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Eff es FileStatus
getFileStatus = PosixFiles (Eff es) FileStatus -> Eff es FileStatus
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) FileStatus -> Eff es FileStatus)
-> (PosixPath -> PosixFiles (Eff es) FileStatus)
-> PosixPath
-> Eff es FileStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> PosixFiles (Eff es) FileStatus
forall (m :: * -> *). PosixPath -> PosixFiles m FileStatus
GetFileStatus
getFdStatus ::
( HasCallStack,
PosixFiles :> es
) =>
Fd ->
Eff es FileStatus
getFdStatus :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
Fd -> Eff es FileStatus
getFdStatus = PosixFiles (Eff es) FileStatus -> Eff es FileStatus
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) FileStatus -> Eff es FileStatus)
-> (Fd -> PosixFiles (Eff es) FileStatus)
-> Fd
-> Eff es FileStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Fd -> PosixFiles (Eff es) FileStatus
forall (m :: * -> *). Fd -> PosixFiles m FileStatus
GetFdStatus
getSymbolicLinkStatus ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
Eff es FileStatus
getSymbolicLinkStatus :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Eff es FileStatus
getSymbolicLinkStatus = PosixFiles (Eff es) FileStatus -> Eff es FileStatus
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) FileStatus -> Eff es FileStatus)
-> (PosixPath -> PosixFiles (Eff es) FileStatus)
-> PosixPath
-> Eff es FileStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> PosixFiles (Eff es) FileStatus
forall (m :: * -> *). PosixPath -> PosixFiles m FileStatus
GetSymbolicLinkStatus
createNamedPipe ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
FileMode ->
Eff es ()
createNamedPipe :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> FileMode -> Eff es ()
createNamedPipe PosixPath
p = PosixFiles (Eff es) () -> Eff es ()
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) () -> Eff es ())
-> (FileMode -> PosixFiles (Eff es) ()) -> FileMode -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> FileMode -> PosixFiles (Eff es) ()
forall (m :: * -> *). PosixPath -> FileMode -> PosixFiles m ()
CreateNamedPipe PosixPath
p
createDevice ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
FileMode ->
DeviceID ->
Eff es ()
createDevice :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> FileMode -> DeviceID -> Eff es ()
createDevice PosixPath
p FileMode
m = PosixFiles (Eff es) () -> Eff es ()
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) () -> Eff es ())
-> (DeviceID -> PosixFiles (Eff es) ()) -> DeviceID -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> FileMode -> DeviceID -> PosixFiles (Eff es) ()
forall (m :: * -> *).
PosixPath -> FileMode -> DeviceID -> PosixFiles m ()
CreateDevice PosixPath
p FileMode
m
createLink ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
PosixPath ->
Eff es ()
createLink :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> PosixPath -> Eff es ()
createLink PosixPath
p = PosixFiles (Eff es) () -> Eff es ()
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) () -> Eff es ())
-> (PosixPath -> PosixFiles (Eff es) ()) -> PosixPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> PosixPath -> PosixFiles (Eff es) ()
forall (m :: * -> *). PosixPath -> PosixPath -> PosixFiles m ()
CreateLink PosixPath
p
removeLink ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
Eff es ()
removeLink :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Eff es ()
removeLink = PosixFiles (Eff es) () -> Eff es ()
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) () -> Eff es ())
-> (PosixPath -> PosixFiles (Eff es) ()) -> PosixPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> PosixFiles (Eff es) ()
forall (m :: * -> *). PosixPath -> PosixFiles m ()
RemoveLink
createSymbolicLink ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
PosixPath ->
Eff es ()
createSymbolicLink :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> PosixPath -> Eff es ()
createSymbolicLink PosixPath
p = PosixFiles (Eff es) () -> Eff es ()
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) () -> Eff es ())
-> (PosixPath -> PosixFiles (Eff es) ()) -> PosixPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> PosixPath -> PosixFiles (Eff es) ()
forall (m :: * -> *). PosixPath -> PosixPath -> PosixFiles m ()
CreateSymbolicLink PosixPath
p
readSymbolicLink ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
Eff es PosixPath
readSymbolicLink :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Eff es PosixPath
readSymbolicLink = PosixFiles (Eff es) PosixPath -> Eff es PosixPath
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) PosixPath -> Eff es PosixPath)
-> (PosixPath -> PosixFiles (Eff es) PosixPath)
-> PosixPath
-> Eff es PosixPath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> PosixFiles (Eff es) PosixPath
forall (m :: * -> *). PosixPath -> PosixFiles m PosixPath
ReadSymbolicLink
rename ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
PosixPath ->
Eff es ()
rename :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> PosixPath -> Eff es ()
rename PosixPath
p = PosixFiles (Eff es) () -> Eff es ()
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) () -> Eff es ())
-> (PosixPath -> PosixFiles (Eff es) ()) -> PosixPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> PosixPath -> PosixFiles (Eff es) ()
forall (m :: * -> *). PosixPath -> PosixPath -> PosixFiles m ()
Rename PosixPath
p
setOwnerAndGroup ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
UserID ->
GroupID ->
Eff es ()
setOwnerAndGroup :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> UserID -> GroupID -> Eff es ()
setOwnerAndGroup PosixPath
p UserID
uid = PosixFiles (Eff es) () -> Eff es ()
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) () -> Eff es ())
-> (GroupID -> PosixFiles (Eff es) ()) -> GroupID -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> UserID -> GroupID -> PosixFiles (Eff es) ()
forall (m :: * -> *).
PosixPath -> UserID -> GroupID -> PosixFiles m ()
SetOwnerAndGroup PosixPath
p UserID
uid
setFdOwnerAndGroup ::
( HasCallStack,
PosixFiles :> es
) =>
Fd ->
UserID ->
GroupID ->
Eff es ()
setFdOwnerAndGroup :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
Fd -> UserID -> GroupID -> Eff es ()
setFdOwnerAndGroup Fd
fd UserID
uid = PosixFiles (Eff es) () -> Eff es ()
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) () -> Eff es ())
-> (GroupID -> PosixFiles (Eff es) ()) -> GroupID -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Fd -> UserID -> GroupID -> PosixFiles (Eff es) ()
forall (m :: * -> *). Fd -> UserID -> GroupID -> PosixFiles m ()
SetFdOwnerAndGroup Fd
fd UserID
uid
setSymbolicLinkOwnerAndGroup ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
UserID ->
GroupID ->
Eff es ()
setSymbolicLinkOwnerAndGroup :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> UserID -> GroupID -> Eff es ()
setSymbolicLinkOwnerAndGroup PosixPath
p UserID
uid = PosixFiles (Eff es) () -> Eff es ()
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) () -> Eff es ())
-> (GroupID -> PosixFiles (Eff es) ()) -> GroupID -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> UserID -> GroupID -> PosixFiles (Eff es) ()
forall (m :: * -> *).
PosixPath -> UserID -> GroupID -> PosixFiles m ()
SetSymbolicLinkOwnerAndGroup PosixPath
p UserID
uid
setFileTimes ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
EpochTime ->
EpochTime ->
Eff es ()
setFileTimes :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> EpochTime -> EpochTime -> Eff es ()
setFileTimes PosixPath
p EpochTime
t = PosixFiles (Eff es) () -> Eff es ()
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) () -> Eff es ())
-> (EpochTime -> PosixFiles (Eff es) ()) -> EpochTime -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> EpochTime -> EpochTime -> PosixFiles (Eff es) ()
forall (m :: * -> *).
PosixPath -> EpochTime -> EpochTime -> PosixFiles m ()
SetFileTimes PosixPath
p EpochTime
t
touchFile ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
Eff es ()
touchFile :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Eff es ()
touchFile = PosixFiles (Eff es) () -> Eff es ()
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) () -> Eff es ())
-> (PosixPath -> PosixFiles (Eff es) ()) -> PosixPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> PosixFiles (Eff es) ()
forall (m :: * -> *). PosixPath -> PosixFiles m ()
TouchFile
setFileSize ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
FileOffset ->
Eff es ()
setFileSize :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> FileOffset -> Eff es ()
setFileSize PosixPath
p = PosixFiles (Eff es) () -> Eff es ()
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) () -> Eff es ())
-> (FileOffset -> PosixFiles (Eff es) ())
-> FileOffset
-> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> FileOffset -> PosixFiles (Eff es) ()
forall (m :: * -> *). PosixPath -> FileOffset -> PosixFiles m ()
SetFileSize PosixPath
p
setFdSize ::
( HasCallStack,
PosixFiles :> es
) =>
Fd ->
FileOffset ->
Eff es ()
setFdSize :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
Fd -> FileOffset -> Eff es ()
setFdSize Fd
fd = PosixFiles (Eff es) () -> Eff es ()
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) () -> Eff es ())
-> (FileOffset -> PosixFiles (Eff es) ())
-> FileOffset
-> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Fd -> FileOffset -> PosixFiles (Eff es) ()
forall (m :: * -> *). Fd -> FileOffset -> PosixFiles m ()
SetFdSize Fd
fd
getPathVar ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
PathVar ->
Eff es Limit
getPathVar :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> PathVar -> Eff es CLong
getPathVar PosixPath
p = PosixFiles (Eff es) CLong -> Eff es CLong
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) CLong -> Eff es CLong)
-> (PathVar -> PosixFiles (Eff es) CLong)
-> PathVar
-> Eff es CLong
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> PathVar -> PosixFiles (Eff es) CLong
forall (m :: * -> *). PosixPath -> PathVar -> PosixFiles m CLong
GetPathVar PosixPath
p
getFdPathVar ::
( HasCallStack,
PosixFiles :> es
) =>
Fd ->
PathVar ->
Eff es Limit
getFdPathVar :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
Fd -> PathVar -> Eff es CLong
getFdPathVar Fd
fd = PosixFiles (Eff es) CLong -> Eff es CLong
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (PosixFiles (Eff es) CLong -> Eff es CLong)
-> (PathVar -> PosixFiles (Eff es) CLong)
-> PathVar
-> Eff es CLong
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Fd -> PathVar -> PosixFiles (Eff es) CLong
forall (m :: * -> *). Fd -> PathVar -> PosixFiles m CLong
GetFdPathVar Fd
fd
throwIfWrongPathType ::
( HasCallStack,
PosixFiles :> es
) =>
String ->
PathType ->
PosixPath ->
Eff es ()
throwIfWrongPathType :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
String -> PathType -> PosixPath -> Eff es ()
throwIfWrongPathType String
location PathType
expected PosixPath
path = do
actual <- PosixPath -> Eff es PathType
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Eff es PathType
getPathType PosixPath
path
let err =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Expected path to have type ",
PathType -> String
forall a. IsString a => PathType -> a
displayPathType PathType
expected,
String
", but detected ",
PathType -> String
forall a. IsString a => PathType -> a
displayPathType PathType
actual
]
unless (expected == actual) $
FS.IO.throwPathIOError
(OsString path)
location
InappropriateType
err
isPathType ::
( HasCallStack,
PosixFiles :> es
) =>
PathType ->
PosixPath ->
Eff es Bool
isPathType :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PathType -> PosixPath -> Eff es Bool
isPathType PathType
expected = (PathType -> Bool) -> Eff es PathType -> Eff es Bool
forall a b. (a -> b) -> Eff es a -> Eff es b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (PathType -> PathType -> Bool
forall a. Eq a => a -> a -> Bool
== PathType
expected) (Eff es PathType -> Eff es Bool)
-> (PosixPath -> Eff es PathType) -> PosixPath -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixPath -> Eff es PathType
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Eff es PathType
getPathType
getPathType ::
( HasCallStack,
PosixFiles :> es
) =>
PosixPath ->
Eff es PathType
getPathType :: forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Eff es PathType
getPathType PosixPath
path =
PosixPath -> Eff es FileStatus
forall (es :: [(* -> *) -> * -> *]).
(HasCallStack, PosixFiles :> es) =>
PosixPath -> Eff es FileStatus
getSymbolicLinkStatus PosixPath
path Eff es FileStatus -> (FileStatus -> PathType) -> Eff es PathType
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \FileStatus
status ->
if
| FileStatus -> Bool
PFiles.isSymbolicLink FileStatus
status -> PathType
PathTypeSymbolicLink
| FileStatus -> Bool
PFiles.isDirectory FileStatus
status -> PathType
PathTypeDirectory
| FileStatus -> Bool
PFiles.isRegularFile FileStatus
status -> PathType
PathTypeFile
| Bool
otherwise -> PathType
PathTypeOther