{-# OPTIONS_GHC -fno-warn-missing-methods -fno-warn-orphans #-} {-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses , ConstraintKinds, UndecidableInstances , UndecidableSuperClasses #-} -- Copyright (C) 2010, 2011 Petr Rockai -- -- Permission is hereby granted, free of charge, to any person -- obtaining a copy of this software and associated documentation -- files (the "Software"), to deal in the Software without -- restriction, including without limitation the rights to use, copy, -- modify, merge, publish, distribute, sublicense, and/or sell copies -- of the Software, and to permit persons to whom the Software is -- furnished to do so, subject to the following conditions: -- -- The above copyright notice and this permission notice shall be -- included in all copies or substantial portions of the Software. -- -- THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, -- EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -- MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND -- NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS -- BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN -- ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN -- CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE -- SOFTWARE. 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 -- a semantic, Tree-based interface for patch application 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 ) -- ApplyMonadOver (ApplyMonadBase m) ~ m is *not* required in general, -- since ApplyMonadBase is not injective => 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 -- Latest name, current original name. type OrigFileNameOf = (FileName, FileName) -- Touched files, new file list (after removes etc.) and rename details type FilePathMonadState = ([FileName], [FileName], [OrigFileNameOf]) type FilePathMonad = State FilePathMonadState -- |trackOrigRename takes an old and new name and attempts to apply the mapping -- to the OrigFileNameOf pair. If the old name is the most up-to-date name of -- the file in question, the first element of the OFNO will match, otherwise if -- the up-to-date name was originally old, the second element will match. 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 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. 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 -- We can't check it actually is a directory here 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