Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class (Monad m, Monad (ApplyMonadBase m), ApplyMonadStateOperations state m, ToTree state) => ApplyMonad (state :: (* -> *) -> *) m where
- type ApplyMonadBase m :: * -> *
- nestedApply :: m x -> state (ApplyMonadBase m) -> m (x, state (ApplyMonadBase m))
- liftApply :: (state (ApplyMonadBase m) -> ApplyMonadBase m x) -> state (ApplyMonadBase m) -> m (x, state (ApplyMonadBase m))
- getApplyState :: m (state (ApplyMonadBase m))
- 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)
- class ApplyMonadState (state :: (* -> *) -> *) where
- type ApplyMonadStateOperations state :: (* -> *) -> Constraint
- withFileNames :: Maybe [OrigFileNameOf] -> [AnchoredPath] -> FilePathMonad a -> FilePathMonadState
- withFiles :: [(AnchoredPath, ByteString)] -> RestrictedApply a -> [(AnchoredPath, ByteString)]
- class ToTree s where
- class Monad 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 ()
Documentation
class (Monad m, Monad (ApplyMonadBase m), ApplyMonadStateOperations state m, ToTree state) => ApplyMonad (state :: (* -> *) -> *) m where Source #
type ApplyMonadBase m :: * -> * Source #
nestedApply :: m x -> state (ApplyMonadBase m) -> m (x, state (ApplyMonadBase m)) Source #
liftApply :: (state (ApplyMonadBase m) -> ApplyMonadBase m x) -> state (ApplyMonadBase m) -> m (x, state (ApplyMonadBase m)) Source #
getApplyState :: m (state (ApplyMonadBase m)) Source #
Instances
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
Monad m => ApplyMonadTrans Tree m Source # | |
Defined in Darcs.Patch.ApplyMonad runApplyMonad :: ApplyMonadOver Tree m x -> Tree m -> m (x, Tree m) Source # | |
Monad m => ApplyMonadTrans ObjectMap m Source # | |
Defined in Darcs.Patch.Prim.FileUUID.Apply runApplyMonad :: ApplyMonadOver ObjectMap m x -> ObjectMap m -> m (x, ObjectMap m) Source # |
class ApplyMonadState (state :: (* -> *) -> *) Source #
type ApplyMonadStateOperations state :: (* -> *) -> Constraint Source #
Instances
ApplyMonadState Tree Source # | |
Defined in Darcs.Patch.ApplyMonad type ApplyMonadStateOperations Tree :: (Type -> Type) -> Constraint Source # | |
ApplyMonadState ObjectMap Source # | |
Defined in Darcs.Patch.Prim.FileUUID.Apply type ApplyMonadStateOperations ObjectMap :: (Type -> Type) -> Constraint Source # |
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.
withFiles :: [(AnchoredPath, ByteString)] -> RestrictedApply a -> [(AnchoredPath, ByteString)] Source #
class Monad m => ApplyMonadTree m where Source #
mDoesDirectoryExist, mDoesFileExist, mReadFilePS, mCreateDirectory, mRemoveDirectory, 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 #