Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class (Monad m, ApplyMonadOperations state m) => ApplyMonad (state :: (* -> *) -> *) m | m -> state where
- readFilePS :: ObjectIdOf state -> m ByteString
- class (Monad m, ApplyMonad state (ApplyMonadOver state m)) => ApplyMonadTrans state m where
- type ApplyMonadOver state m :: * -> *
- runApplyMonad :: ApplyMonadOver state m x -> state m -> m (x, state m)
- type family ApplyMonadOperations (state :: (* -> *) -> *) :: (* -> *) -> Constraint
- withFileNames :: Maybe [OrigFileNameOf] -> [AnchoredPath] -> FilePathMonad a -> FilePathMonadState
- class MonadThrow m => ApplyMonadTree m where
- mDoesDirectoryExist :: AnchoredPath -> m Bool
- mDoesFileExist :: AnchoredPath -> m Bool
- mReadFilePS :: AnchoredPath -> m ByteString
- mCreateDirectory :: AnchoredPath -> m ()
- mRemoveDirectory :: AnchoredPath -> m ()
- mCreateFile :: AnchoredPath -> m ()
- mRemoveFile :: AnchoredPath -> m ()
- mRename :: AnchoredPath -> AnchoredPath -> m ()
- mModifyFilePS :: AnchoredPath -> (ByteString -> m ByteString) -> m ()
- mChangePref :: String -> String -> String -> m ()
- evalApplyMonad :: ApplyMonadTrans state m => ApplyMonadOver state m a -> state m -> m a
Documentation
class (Monad m, ApplyMonadOperations state m) => ApplyMonad (state :: (* -> *) -> *) m | m -> state where Source #
readFilePS :: ObjectIdOf state -> m ByteString Source #
Instances
ApplyMonad Tree DefaultIO Source # | |
Defined in Darcs.Repository.ApplyPatches | |
MonadThrow m => ApplyMonad Tree (TreeMonad m) Source # | |
Defined in Darcs.Patch.ApplyMonad readFilePS :: ObjectIdOf Tree -> TreeMonad m ByteString Source # | |
MonadThrow m => ApplyMonad ObjectMap (StateT (ObjectMap m) m) Source # | |
Defined in Darcs.Patch.Prim.FileUUID.Apply readFilePS :: ObjectIdOf ObjectMap -> StateT (ObjectMap m) m ByteString Source # |
class (Monad m, ApplyMonad state (ApplyMonadOver state m)) => ApplyMonadTrans state m where Source #
type ApplyMonadOver state m :: * -> * Source #
runApplyMonad :: ApplyMonadOver state m x -> state m -> m (x, state m) Source #
Instances
MonadThrow m => ApplyMonadTrans ObjectMap m Source # | |
Defined in Darcs.Patch.Prim.FileUUID.Apply runApplyMonad :: ApplyMonadOver ObjectMap m x -> ObjectMap m -> m (x, ObjectMap m) Source # | |
MonadThrow m => ApplyMonadTrans Tree m Source # | |
Defined in Darcs.Patch.ApplyMonad runApplyMonad :: ApplyMonadOver Tree m x -> Tree m -> m (x, Tree m) Source # |
type family ApplyMonadOperations (state :: (* -> *) -> *) :: (* -> *) -> Constraint Source #
Instances
type ApplyMonadOperations ObjectMap Source # | |
Defined in Darcs.Patch.Prim.FileUUID.Apply | |
type ApplyMonadOperations Tree Source # | |
Defined in Darcs.Patch.ApplyMonad |
withFileNames :: Maybe [OrigFileNameOf] -> [AnchoredPath] -> FilePathMonad a -> FilePathMonadState Source #
withFileNames takes a maybe list of existing rename-pairs, a list of filenames and an action, and returns the resulting triple of affected files, updated filename list and new rename details. If the rename-pairs are not present, a new list is generated from the filesnames.
class MonadThrow m => ApplyMonadTree m where Source #
mDoesDirectoryExist, mDoesFileExist, mReadFilePS, mCreateDirectory, mRemoveDirectory, mCreateFile, mRemoveFile, mRename, mModifyFilePS
mDoesDirectoryExist :: AnchoredPath -> m Bool Source #
mDoesFileExist :: AnchoredPath -> m Bool Source #
mReadFilePS :: AnchoredPath -> m ByteString Source #
mCreateDirectory :: AnchoredPath -> m () Source #
mRemoveDirectory :: AnchoredPath -> m () Source #
mCreateFile :: AnchoredPath -> m () Source #
mRemoveFile :: AnchoredPath -> m () Source #
mRename :: AnchoredPath -> AnchoredPath -> m () Source #
mModifyFilePS :: AnchoredPath -> (ByteString -> m ByteString) -> m () Source #
Instances
evalApplyMonad :: ApplyMonadTrans state m => ApplyMonadOver state m a -> state m -> m a Source #