This commit is contained in:
Joey Hess 2010-10-16 16:20:49 -04:00
parent 6d13ae10cf
commit 909f619c07
16 changed files with 27 additions and 11 deletions

View file

@ -13,6 +13,7 @@ module Annex (
) where
import Control.Monad.State
import qualified GitRepo as Git
import Types
import qualified BackendTypes as Backend

View file

@ -27,6 +27,7 @@ import System.Directory
import System.FilePath
import Data.String.Utils
import System.Posix.Files
import BackendList
import Locations
import qualified GitRepo as Git

View file

@ -15,6 +15,7 @@ import System.IO
import System.Cmd
import System.Exit
import Control.Exception
import BackendTypes
import LocationLog
import Locations

View file

@ -3,8 +3,9 @@
module Backend.SHA1 (backend) where
import qualified Backend.File
import Data.Digest.Pure.SHA
import qualified Backend.File
import BackendTypes
backend = Backend.File.backend {

View file

@ -7,6 +7,7 @@ import Control.Monad.State (liftIO)
import Data.String.Utils
import System.Cmd
import System.Exit
import BackendTypes
backend = Backend {

View file

@ -4,14 +4,15 @@
module Backend.WORM (backend) where
import Control.Monad.State
import qualified Backend.File
import BackendTypes
import Utility
import System.FilePath
import System.Posix.Files
import Data.Digest.Pure.SHA -- slow, but we only checksum filenames
import qualified Data.ByteString.Lazy.Char8 as B
import qualified Backend.File
import BackendTypes
import Utility
backend = Backend.File.backend {
name = "WORM",
getKey = keyValue

View file

@ -7,6 +7,7 @@ module BackendTypes where
import Control.Monad.State (StateT)
import Data.String.Utils
import qualified GitRepo as Git
-- command-line flags

View file

@ -10,6 +10,7 @@ import System.Path
import Data.String.Utils
import List
import IO
import qualified GitRepo as Git
import qualified Annex
import Utility

View file

@ -5,6 +5,7 @@ module Core where
import System.IO
import System.Directory
import Control.Monad.State (liftIO)
import Types
import Locations
import UUID

View file

@ -42,6 +42,7 @@ import Data.String.Utils
import Data.Map as Map hiding (map, split)
import Network.URI
import Maybe
import Utility
{- A git repository can be on local disk or remote. Not to be confused

View file

@ -29,6 +29,7 @@ import qualified Data.Map as Map
import System.IO
import System.Directory
import Data.Char
import qualified GitRepo as Git
import Utility
import UUID

View file

@ -11,6 +11,7 @@ module Locations (
) where
import Data.String.Utils
import Types
import qualified BackendTypes as Backend
import qualified GitRepo as Git

View file

@ -12,6 +12,7 @@ import qualified Data.Map as Map
import Data.String.Utils
import List
import Maybe
import Types
import qualified GitRepo as Git
import qualified Annex

View file

@ -21,7 +21,9 @@ import Maybe
import List
import System.Cmd.Utils
import System.IO
import System.Directory
import qualified Data.Map as M
import qualified GitRepo as Git
import Types
import Locations
@ -112,6 +114,7 @@ describeUUID uuid desc = do
m <- uuidMap
let m' = M.insert uuid desc m
log <- uuidLog
liftIO $ createDirectoryIfMissing True (parentDir log)
liftIO $ withFileLocked log WriteMode (\h -> hPutStr h $ serialize m')
where
serialize m = unlines $ map (\(u, d) -> u++" "++d) $ M.toList m

View file

@ -16,12 +16,12 @@ use. Some are used to archive data, others hold backups, and yet others
come with me when I'm away from home to carry data that doesn't fit on my
netbook. Maintaining all that was a nightmare, lots of ad-hoc moving files
around, rsyncing files (unison is too slow), and deleting multiple copies
of files from multiple places. I realized what what I needed was revision
control where each drive was a repository, and where copying the files
around, and deciding which copies were safe to delete was automated.
of files from multiple places. I realized what what I needed was a form of
revision control where each drive was a repository, and where copying the
files around, and deciding which copies were safe to delete was automated.
I posted about this to the VCS-home mailing list and got a great suggestion
to make it support arbitrary key-value stores. A week of coding later,
and git-annex is born.
to make it support arbitrary key-value stores, for more generality and
flexability. A week of coding later, and git-annex is born.
Enough broad picture, here's how it actually looks:

View file

@ -3,17 +3,17 @@
import Control.Exception
import System.IO
import System.Environment
import qualified Annex
import Types
import Core
import Commands
import Annex
import qualified GitRepo as Git
main = do
args <- getArgs
gitrepo <- Git.repoFromCwd
state <- new gitrepo
state <- Annex.new gitrepo
(flags, actions) <- parseCmd args state
tryRun state $ [startup flags] ++ actions ++ [shutdown]