% Copyright (C) 2003-2004 Jan Scheffczyk and David Roundy % % This program is free software; you can redistribute it and/or modify % it under the terms of the GNU General Public License as published by % the Free Software Foundation; either version 2, or (at your option) % any later version. % % This program is distributed in the hope that it will be useful, % but WITHOUT ANY WARRANTY; without even the implied warranty of % MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the % GNU General Public License for more details. % % You should have received a copy of the GNU General Public License % along with this program; see the file COPYING. If not, write to % the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, % Boston, MA 02110-1301, USA. NOTE: this documentation belongs in a ``libdarcs API'' chapter, which currently doesn't exist. \begin{code} module Darcs.PopulationData ( Population(..), PopTree(..), Info(..), setPopState, notModified, setState, DirMark(..), getPopFrom ) where import Darcs.Patch.Info import FastPackedString import Darcs.Utils ( withCurrentDirectory ) import System.Directory ( doesDirectoryExist, getDirectoryContents ) \end{code} the population of a darcs repository (simpler Slurpy) PatchInfo: state when last modified PopTree: the directory listing \begin{code} data Population = Pop PatchInfo PopTree deriving (Show, Eq) setPopState :: PatchInfo -> Population -> Population setPopState i (Pop _ tr) = Pop i tr \end{code} directory listing \begin{code} data PopTree = PopDir !Info ![PopTree] | PopFile !Info deriving ( Ord, Eq ) \end{code} info of a directory member \begin{code} data DirMark = AddedFile | RemovedFile | MovedFile String | ModifiedFile | DullFile | AddedDir | RemovedDir | MovedDir !String | DullDir deriving ( Ord, Eq ) data Info = Info {nameI :: !PackedString, -- name of the element modifiedByI :: !PatchInfo, -- last patch modifying this element modifiedHowI :: !DirMark, -- how was it modified createdByI :: !(Maybe PatchInfo), -- this can be unknown when restored backwards! creationNameI :: !(Maybe PackedString)} -- the original name of the element deriving ( Ord, Eq ) \end{code} was an Info record not modified? \begin{code} notModified :: Info -> Bool notModified i = (modifiedHowI i == DullFile) || (modifiedHowI i == DullDir) \end{code} set the modifier for an Info record \begin{code} setState :: Info -> PatchInfo -> Info setState i pinfo = i { modifiedByI = pinfo } instance Show PopTree where show s = showPop "" s showPop :: String -> PopTree -> String showPop indent (PopDir i fs) = indent ++ show i ++ "\n" ++ unlines (map (showPop (' ':indent)) fs) showPop indent (PopFile i) = indent ++ show i instance Show Info where show i = show (nameI i) ++ " " ++ show (modifiedHowI i) ++ " at state " ++ show (modifiedByI i) instance Show DirMark where show AddedFile = "File added" show RemovedFile = "File removed" show (MovedFile s) = "File moved to " ++ s show ModifiedFile = "File modified" show DullFile = "File old" show AddedDir = "Dir added" show RemovedDir = "Dir removed" show (MovedDir s) = "Dir moved from " ++ s show DullDir = "Dir old" \end{code} read the population from a given directory ``dirname'' all folders and documents get the given time ``t'' This needs to be here in order to avoid a circular dependency between Population and Pristine. \begin{code} getPopFrom :: FilePath -> PatchInfo -> IO Population getPopFrom the_directory pinfo = withCurrentDirectory the_directory $ do popT <- getPopFrom_helper "." return (Pop pinfo popT) where getPopFrom_helper :: FilePath -> IO PopTree getPopFrom_helper dirname = do isdir <- doesDirectoryExist dirname let n = packString dirname if isdir then do fnames <- getDirectoryContents dirname sl <- withCurrentDirectory dirname (sequence $ map getPopFrom_helper $ filter not_hidden fnames) let i = Info {nameI = n, modifiedByI = pinfo, modifiedHowI = DullDir, createdByI = Just pinfo, creationNameI = Just n} return $ PopDir i sl else do let i = Info {nameI = n, modifiedByI = pinfo, modifiedHowI = DullFile, createdByI = Just pinfo, creationNameI = Just n} return $ PopFile i not_hidden :: FilePath -> Bool not_hidden ('.':_) = False not_hidden ('_':_) = False not_hidden _ = True \end{code}