module Darcs.Patch.ApplyMonad
( ApplyMonad(..), ApplyMonadTrans(..), ApplyMonadState(..)
, withFileNames, withFiles, ToTree(..)
, ApplyMonadTree(..)
) where
import Prelude ()
import Darcs.Prelude
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.Map as M
import qualified Darcs.Util.Tree.Monad as TM
import Darcs.Util.Tree ( Tree )
import Data.Maybe ( fromMaybe )
import Darcs.Util.Path
( FileName, movedirfilename, fn2fp, isParentOrEqOf, floatPath, AnchoredPath )
import Control.Monad.State.Strict
import Control.Monad.Identity( Identity )
import Darcs.Patch.MonadProgress
import GHC.Exts ( Constraint )
fn2ap :: FileName -> AnchoredPath
fn2ap = floatPath . fn2fp
class ToTree s where
toTree :: s m -> Tree m
instance ToTree Tree where
toTree = id
class (Functor m, 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)
instance (Functor m, Monad m) => ApplyMonadTrans Tree m where
type ApplyMonadOver Tree m = TM.TreeMonad m
runApplyMonad = TM.virtualTreeMonad
class ApplyMonadState (state :: (* -> *) -> *) where
type ApplyMonadStateOperations state :: (* -> *) -> Constraint
class (Functor m, Monad m) => ApplyMonadTree m where
mDoesDirectoryExist :: FileName -> m Bool
mDoesFileExist :: FileName -> m Bool
mReadFilePS :: FileName -> m B.ByteString
mCreateDirectory :: FileName -> m ()
mRemoveDirectory :: FileName -> m ()
mCreateFile :: FileName -> m ()
mCreateFile f = mModifyFilePS f $ \_ -> return B.empty
mRemoveFile :: FileName -> m ()
mRename :: FileName -> FileName -> m ()
mModifyFilePS :: FileName -> (B.ByteString -> m B.ByteString) -> m ()
mChangePref :: String -> String -> String -> m ()
mChangePref _ _ _ = return ()
instance ApplyMonadState Tree where
type ApplyMonadStateOperations Tree = ApplyMonadTree
class ( Functor m, Monad m, Functor (ApplyMonadBase 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))
instance (Functor m, Monad m) => ApplyMonad Tree (TM.TreeMonad m) where
type ApplyMonadBase (TM.TreeMonad m) = m
getApplyState = gets TM.tree
nestedApply a start = lift $ runApplyMonad a start
liftApply a start = do x <- gets TM.tree
lift $ runApplyMonad (lift $ a x) start
instance (Functor m, Monad m) => ApplyMonadTree (TM.TreeMonad m) where
mDoesDirectoryExist d = TM.directoryExists (fn2ap d)
mDoesFileExist d = TM.fileExists (fn2ap d)
mReadFilePS p = B.concat `fmap` BL.toChunks `fmap` TM.readFile (fn2ap p)
mModifyFilePS p j = do have <- TM.fileExists (fn2ap p)
x <- if have then B.concat `fmap` BL.toChunks `fmap` TM.readFile (fn2ap p)
else return B.empty
TM.writeFile (fn2ap p) . BL.fromChunks . (:[]) =<< j x
mCreateDirectory p = TM.createDirectory (fn2ap p)
mRename from to = TM.rename (fn2ap from) (fn2ap to)
mRemoveDirectory = TM.unlink . fn2ap
mRemoveFile = TM.unlink . fn2ap
type OrigFileNameOf = (FileName, FileName)
type FilePathMonadState = ([FileName], [FileName], [OrigFileNameOf])
type FilePathMonad = State FilePathMonadState
trackOrigRename :: FileName -> FileName -> OrigFileNameOf -> OrigFileNameOf
trackOrigRename old new pair@(latest, from)
| old `isParentOrEqOf` latest = (latest, movedirfilename old new latest)
| old `isParentOrEqOf` from = (latest, movedirfilename old new from)
| otherwise = pair
withFileNames :: Maybe [OrigFileNameOf] -> [FileName] -> FilePathMonad a
-> FilePathMonadState
withFileNames mbofnos fps x = execState x ([], fps, ofnos) where
ofnos = fromMaybe (map (\y -> (y, y)) fps) mbofnos
instance ApplyMonad Tree FilePathMonad where
type ApplyMonadBase FilePathMonad = Identity
instance ApplyMonadTree FilePathMonad where
mDoesDirectoryExist d = gets $ \(_, fs, _) -> d `elem` fs
mCreateDirectory = mCreateFile
mCreateFile f = modify $ \(ms, fs, rns) -> (f : ms, fs, rns)
mRemoveFile f = modify $ \(ms, fs, rns) -> (f : ms, filter (/= f) fs, rns)
mRemoveDirectory = mRemoveFile
mRename a b =
modify $ \(ms, fs, rns) -> ( a : b : ms
, map (movedirfilename a b) fs
, map (trackOrigRename a b) rns)
mModifyFilePS f _ = mCreateFile f
instance MonadProgress FilePathMonad where
runProgressActions = silentlyRunProgressActions
type RestrictedApply = State (M.Map FileName B.ByteString)
instance ApplyMonad Tree RestrictedApply where
type ApplyMonadBase RestrictedApply = Identity
instance ApplyMonadTree RestrictedApply where
mDoesDirectoryExist _ = return True
mCreateDirectory _ = return ()
mRemoveFile f = modify $ M.delete f
mRemoveDirectory _ = return ()
mRename a b = modify $ M.mapKeys (movedirfilename a b)
mModifyFilePS f j = do look <- gets $ M.lookup f
case look of
Nothing -> return ()
Just bits -> do
new <- j bits
modify $ M.insert f new
instance MonadProgress RestrictedApply where
runProgressActions = silentlyRunProgressActions
withFiles :: [(FileName, B.ByteString)] -> RestrictedApply a -> [(FileName, B.ByteString)]
withFiles p x = M.toList $ execState x $ M.fromList p