diff --git a/.gitignore b/.gitignore
index fe65fc5747..b6b8d606d6 100644
--- a/.gitignore
+++ b/.gitignore
@@ -1,12 +1,8 @@
 tmp
-*.hi
-*.o
 test
 configure
 Build/SysConfig.hs
 git-annex
-git-annex-shell
-git-union-merge
 git-annex.1
 git-annex-shell.1
 git-union-merge.1
@@ -15,5 +11,5 @@ html
 *.tix
 .hpc
 Utility/Touch.hs
-Utility/StatFS.hs
+Utility/libdiskfree.o
 dist
diff --git a/Annex.hs b/Annex.hs
index ef95ff174c..a9cc680125 100644
--- a/Annex.hs
+++ b/Annex.hs
@@ -10,7 +10,6 @@
 module Annex (
 	Annex,
 	AnnexState(..),
-	OutputType(..),
 	new,
 	newState,
 	run,
@@ -19,6 +18,7 @@ module Annex (
 	changeState,
 	setFlag,
 	setField,
+	setOutput,
 	getFlag,
 	getField,
 	addCleanup,
@@ -37,12 +37,14 @@ import qualified Git
 import qualified Git.Config
 import Git.CatFile
 import Git.CheckAttr
+import Git.SharedRepository
 import qualified Git.Queue
 import Types.Backend
 import qualified Types.Remote
 import Types.Crypto
 import Types.BranchState
 import Types.TrustLevel
+import Types.Messages
 import Utility.State
 import qualified Utility.Matcher
 import qualified Data.Map as M
@@ -68,8 +70,6 @@ instance MonadBaseControl IO Annex where
 		where
 			unStAnnex (StAnnex st) = st
 
-data OutputType = NormalOutput | QuietOutput | JSONOutput
-
 type Matcher a = Either [Utility.Matcher.Token a] (Utility.Matcher.Matcher a)
 
 -- internal state storage
@@ -77,7 +77,7 @@ data AnnexState = AnnexState
 	{ repo :: Git.Repo
 	, backends :: [BackendA Annex]
 	, remotes :: [Types.Remote.RemoteA Annex]
-	, output :: OutputType
+	, output :: MessageState
 	, force :: Bool
 	, fast :: Bool
 	, auto :: Bool
@@ -88,9 +88,10 @@ data AnnexState = AnnexState
 	, forcebackend :: Maybe String
 	, forcenumcopies :: Maybe Int
 	, limit :: Matcher (FilePath -> Annex Bool)
+	, shared :: Maybe SharedRepository
 	, forcetrust :: TrustMap
 	, trustmap :: Maybe TrustMap
-	, ciphers :: M.Map EncryptedCipher Cipher
+	, ciphers :: M.Map StorableCipher Cipher
 	, lockpool :: M.Map FilePath Fd
 	, flags :: M.Map String Bool
 	, fields :: M.Map String String
@@ -102,7 +103,7 @@ newState gitrepo = AnnexState
 	{ repo = gitrepo
 	, backends = []
 	, remotes = []
-	, output = NormalOutput
+	, output = defaultMessageState
 	, force = False
 	, fast = False
 	, auto = False
@@ -113,6 +114,7 @@ newState gitrepo = AnnexState
 	, forcebackend = Nothing
 	, forcenumcopies = Nothing
 	, limit = Left []
+	, shared = Nothing
 	, forcetrust = M.empty
 	, trustmap = Nothing
 	, ciphers = M.empty
@@ -122,7 +124,8 @@ newState gitrepo = AnnexState
 	, cleanup = M.empty
 	}
 
-{- Create and returns an Annex state object for the specified git repo. -}
+{- Makes an Annex state object for the specified git repo.
+ - Ensures the config is read, if it was not already. -}
 new :: Git.Repo -> IO AnnexState
 new gitrepo = newState <$> Git.Config.read gitrepo
 
@@ -147,6 +150,11 @@ addCleanup :: String -> Annex () -> Annex ()
 addCleanup uid a = changeState $ \s ->
 	s { cleanup = M.insertWith' const uid a $ cleanup s }
 
+{- Sets the type of output to emit. -}
+setOutput :: OutputType -> Annex ()
+setOutput o = changeState $ \s ->
+	s { output = (output s) { outputType = o } }
+
 {- Checks if a flag was set. -}
 getFlag :: String -> Annex Bool
 getFlag flag = fromMaybe False . M.lookup flag <$> getState flags
diff --git a/Annex/Branch.hs b/Annex/Branch.hs
index 52089ac97d..706522f3b3 100644
--- a/Annex/Branch.hs
+++ b/Annex/Branch.hs
@@ -36,6 +36,7 @@ import qualified Git.UnionMerge
 import Git.HashObject
 import qualified Git.Index
 import Annex.CatFile
+import Annex.Perms
 
 {- Name of the branch that is used to store git-annex's information. -}
 name :: Git.Ref
@@ -64,9 +65,7 @@ siblingBranches = inRepo $ Git.Ref.matchingUniq name
 
 {- Creates the branch, if it does not already exist. -}
 create :: Annex ()
-create = do
-	_ <- getBranch
-	return ()
+create = void $ getBranch
 
 {- Returns the ref of the branch, creating it first if necessary. -}
 getBranch :: Annex Git.Ref
@@ -308,6 +307,7 @@ setIndexSha :: Git.Ref -> Annex ()
 setIndexSha ref = do
         lock <- fromRepo gitAnnexIndexLock
 	liftIO $ writeFile lock $ show ref ++ "\n"
+	setAnnexPerm lock
 
 {- Checks if there are uncommitted changes in the branch's index or journal. -}
 unCommitted :: Annex Bool
@@ -323,14 +323,14 @@ setUnCommitted = do
 	liftIO $ writeFile file "1"
 
 setCommitted :: Annex ()
-setCommitted = do
+setCommitted = void $ do
 	file <- fromRepo gitAnnexIndexDirty
-	_ <- liftIO $ tryIO $ removeFile file
-	return ()
+	liftIO $ tryIO $ removeFile file
 
 {- Stages the journal into the index. -}
 stageJournal :: Annex ()
 stageJournal = do
+	showStoringStateAction
 	fs <- getJournalFiles
 	g <- gitRepo
 	withIndex $ liftIO $ do
diff --git a/Annex/Content.hs b/Annex/Content.hs
index 8542d8775d..26b332e24c 100644
--- a/Annex/Content.hs
+++ b/Annex/Content.hs
@@ -23,16 +23,18 @@ module Annex.Content (
 	saveState,
 	downloadUrl,
 	preseedTmp,
+	freezeContent,
+	thawContent,
+	freezeContentDir,
 ) where
 
-import Control.Exception (bracket_)
-import System.Posix.Types
 import System.IO.Unsafe (unsafeInterleaveIO)
 
 import Common.Annex
 import Logs.Location
 import Annex.UUID
 import qualified Git
+import qualified Git.Config
 import qualified Annex
 import qualified Annex.Queue
 import qualified Annex.Branch
@@ -44,6 +46,8 @@ import Utility.DataUnits
 import Utility.CopyFile
 import Config
 import Annex.Exception
+import Git.SharedRepository
+import Annex.Perms
 
 {- Checks if a given key's content is currently present. -}
 inAnnex :: Key -> Annex Bool
@@ -57,8 +61,10 @@ inAnnex' a key = do
 {- A safer check; the key's content must not only be present, but
  - is not in the process of being removed. -}
 inAnnexSafe :: Key -> Annex (Maybe Bool)
-inAnnexSafe = inAnnex' $ \f -> openForLock f False >>= check
+inAnnexSafe = inAnnex' $ \f -> openforlock f >>= check
 	where
+		openforlock f = catchMaybeIO $
+			openFd f ReadOnly Nothing defaultFileFlags
 		check Nothing = return is_missing
 		check (Just h) = do
 			v <- getLock h (ReadLock, AbsoluteSeek, 0, 0)
@@ -75,30 +81,27 @@ inAnnexSafe = inAnnex' $ \f -> openForLock f False >>= check
 lockContent :: Key -> Annex a -> Annex a
 lockContent key a = do
 	file <- inRepo $ gitAnnexLocation key
-	bracketIO (openForLock file True >>= lock) unlock a
+	bracketIO (openforlock file >>= lock) unlock a
 	where
+		{- Since files are stored with the write bit disabled, have
+		 - to fiddle with permissions to open for an exclusive lock. -}
+		openforlock f = catchMaybeIO $ ifM (doesFileExist f)
+			( withModifiedFileMode f
+				(\cur -> cur `unionFileModes` ownerWriteMode)
+				open
+			, open
+			)
+			where
+				open = openFd f ReadWrite Nothing defaultFileFlags
 		lock Nothing = return Nothing
-		lock (Just l) = do
-			v <- tryIO $ setLock l (WriteLock, AbsoluteSeek, 0, 0)
+		lock (Just fd) = do
+			v <- tryIO $ setLock fd (WriteLock, AbsoluteSeek, 0, 0)
 			case v of
 				Left _ -> error "content is locked"
-				Right _ -> return $ Just l
-		unlock Nothing = return ()
+				Right _ -> return $ Just fd
+		unlock Nothing = noop
 		unlock (Just l) = closeFd l
 
-openForLock :: FilePath -> Bool -> IO (Maybe Fd)
-openForLock file writelock = bracket_ prep cleanup go
-	where
-		go = catchMaybeIO $ openFd file mode Nothing defaultFileFlags
-		mode = if writelock then ReadWrite else ReadOnly
-		{- Since files are stored with the write bit disabled,
-		 - have to fiddle with permissions to open for an
-		 - exclusive lock. -}
-		forwritelock a = 
-			when writelock $ whenM (doesFileExist file) a
-		prep = forwritelock $ allowWrite file
-		cleanup = forwritelock $ preventWrite file
-
 {- Calculates the relative path to use to link a file to a key. -}
 calcGitLink :: FilePath -> Key -> Annex FilePath
 calcGitLink file key = do
@@ -127,20 +130,20 @@ getViaTmp key action = do
 	-- When the temp file already exists, count the space
 	-- it is using as free.
 	e <- liftIO $ doesFileExist tmp
-	if e
-		then do
-			stat <- liftIO $ getFileStatus tmp
-			checkDiskSpace' (fromIntegral $ fileSize stat) key
-		else checkDiskSpace key
-
-	when e $ liftIO $ allowWrite tmp
-
-	getViaTmpUnchecked key action
+	alreadythere <- if e
+		then fromIntegral . fileSize <$> liftIO (getFileStatus tmp)
+		else return 0
+	ifM (checkDiskSpace Nothing key alreadythere)
+		( do
+			when e $ thawContent tmp
+			getViaTmpUnchecked key action
+		, return False
+		)
 
 prepTmp :: Key -> Annex FilePath
 prepTmp key = do
 	tmp <- fromRepo $ gitAnnexTmpLocation key
-	liftIO $ createDirectoryIfMissing True (parentDir tmp)
+	createAnnexDirectory (parentDir tmp)
 	return tmp
 
 {- Like getViaTmp, but does not check that there is enough disk space
@@ -169,22 +172,24 @@ withTmp key action = do
 	return res
 
 {- Checks that there is disk space available to store a given key,
- - throwing an error if not. -}
-checkDiskSpace :: Key -> Annex ()
-checkDiskSpace = checkDiskSpace' 0
-
-checkDiskSpace' :: Integer -> Key -> Annex ()
-checkDiskSpace' adjustment key = do
+ - in a destination (or the annex) printing a warning if not. -}
+checkDiskSpace :: Maybe FilePath -> Key -> Integer -> Annex Bool
+checkDiskSpace destination key alreadythere = do
 	reserve <- getDiskReserve
-	free <- inRepo $ getDiskFree . gitAnnexDir
+	free <- liftIO . getDiskFree =<< dir
+	force <- Annex.getState Annex.force
 	case (free, keySize key) of
-		(Just have, Just need) ->
-			when (need + reserve > have + adjustment) $
-				needmorespace (need + reserve - have - adjustment)
-		_ -> return ()
+		(Just have, Just need) -> do
+			let ok = (need + reserve <= have + alreadythere) || force
+			unless ok $ do
+				liftIO $ print (need, reserve, have, alreadythere)
+				needmorespace (need + reserve - have - alreadythere)
+			return ok
+		_ -> return True
 	where
-		needmorespace n = unlessM (Annex.getState Annex.force) $
-			error $ "not enough free space, need " ++ 
+		dir = maybe (fromRepo gitAnnexDir) return destination
+		needmorespace n =
+			warning $ "not enough free space, need " ++ 
 				roughSize storageUnits True n ++
 				" more" ++ forcemsg
 		forcemsg = " (use --force to override this check or adjust annex.diskreserve)"
@@ -213,15 +218,13 @@ checkDiskSpace' adjustment key = do
 moveAnnex :: Key -> FilePath -> Annex ()
 moveAnnex key src = do
 	dest <- inRepo $ gitAnnexLocation key
-	let dir = parentDir dest
-	liftIO $ ifM (doesFileExist dest)
-		( removeFile src
+	ifM (liftIO $ doesFileExist dest)
+		( liftIO $ removeFile src
 		, do
-			createDirectoryIfMissing True dir
-			allowWrite dir -- in case the directory already exists
-			moveFile src dest
-			preventWrite dest
-			preventWrite dir
+			createContentDir dest
+			liftIO $ moveFile src dest
+			freezeContent dest
+			freezeContentDir dest
 		)
 
 withObjectLoc :: Key -> ((FilePath, FilePath) -> Annex a) -> Annex a
@@ -235,10 +238,10 @@ cleanObjectLoc key = do
 	file <- inRepo $ gitAnnexLocation key
 	liftIO $ removeparents file (3 :: Int)
 	where
-		removeparents _ 0 = return ()
+		removeparents _ 0 = noop
 		removeparents file n = do
 			let dir = parentDir file
-			maybe (return ()) (const $ removeparents dir (n-1))
+			maybe noop (const $ removeparents dir (n-1))
 				=<< catchMaybeIO (removeDirectory dir)
 
 {- Removes a key's file from .git/annex/objects/ -}
@@ -252,10 +255,9 @@ removeAnnex key = withObjectLoc key $ \(dir, file) -> do
 {- Moves a key's file out of .git/annex/objects/ -}
 fromAnnex :: Key -> FilePath -> Annex ()
 fromAnnex key dest = withObjectLoc key $ \(dir, file) -> do
-	liftIO $ do
-		allowWrite dir
-		allowWrite file
-		moveFile file dest
+	liftIO $ allowWrite dir
+	thawContent file
+	liftIO $ moveFile file dest
 	cleanObjectLoc key
 
 {- Moves a key out of .git/annex/objects/ into .git/annex/bad, and
@@ -265,8 +267,8 @@ moveBad key = do
 	src <- inRepo $ gitAnnexLocation key
 	bad <- fromRepo gitAnnexBadDir
 	let dest = bad </> takeFileName src
+	createAnnexDirectory (parentDir dest)
 	liftIO $ do
-		createDirectoryIfMissing True (parentDir dest)
 		allowWrite (parentDir src)
 		moveFile src dest
 	cleanObjectLoc key
@@ -296,20 +298,21 @@ getKeysPresent = liftIO . traverse (2 :: Int) =<< fromRepo gitAnnexObjectDir
  - especially if performing a short-lived action.
  -}
 saveState :: Bool -> Annex ()
-saveState oneshot = do
-	Annex.Queue.flush False
+saveState oneshot = doSideAction $ do
+	Annex.Queue.flush
 	unless oneshot $
 		ifM alwayscommit
 			( Annex.Branch.commit "update" , Annex.Branch.stage)
 	where
-		alwayscommit = fromMaybe True . Git.configTrue
-			<$> getConfig "annex.alwayscommit" ""
+		alwayscommit = fromMaybe True . Git.Config.isTrue
+			<$> getConfig (annexConfig "alwayscommit") ""
 
 {- Downloads content from any of a list of urls. -}
 downloadUrl :: [Url.URLString] -> FilePath -> Annex Bool
 downloadUrl urls file = do
-	o <- map Param . words <$> getConfig "annex.web-options" ""
-	liftIO $ anyM (\u -> Url.download u o file) urls
+	o <- map Param . words <$> getConfig (annexConfig "web-options") ""
+	headers <- getHttpHeaders
+	liftIO $ anyM (\u -> Url.download u headers o file) urls
 
 {- Copies a key's content, when present, to a temp file.
  - This is used to speed up some rsyncs. -}
@@ -319,7 +322,7 @@ preseedTmp key file = go =<< inAnnex key
 		go False = return False
 		go True = do
 			ok <- copy
-			when ok $ liftIO $ allowWrite file
+			when ok $ thawContent file
 			return ok
 		copy = ifM (liftIO $ doesFileExist file)
 				( return True
@@ -327,3 +330,50 @@ preseedTmp key file = go =<< inAnnex key
 					s <- inRepo $ gitAnnexLocation key
 					liftIO $ copyFileExternal s file
 				)
+
+{- Blocks writing to an annexed file. The file is made unwritable
+ - to avoid accidental edits. core.sharedRepository may change
+ - who can read it. -}
+freezeContent :: FilePath -> Annex ()
+freezeContent file = liftIO . go =<< fromRepo getSharedRepository
+	where
+		go GroupShared = modifyFileMode file $
+			removeModes writeModes .
+			addModes [ownerReadMode, groupReadMode]
+		go AllShared = modifyFileMode file $
+			removeModes writeModes .
+			addModes readModes
+		go _ = preventWrite file
+
+{- Allows writing to an annexed file that freezeContent was called on
+ - before. -}
+thawContent :: FilePath -> Annex ()
+thawContent file = liftIO . go =<< fromRepo getSharedRepository
+	where
+		go GroupShared = groupWriteRead file
+		go AllShared = groupWriteRead file
+		go _ = allowWrite file
+
+{- Blocks writing to the directory an annexed file is in, to prevent the
+ - file accidentially being deleted. However, if core.sharedRepository
+ - is set, this is not done, since the group must be allowed to delete the
+ - file.
+ -}
+freezeContentDir :: FilePath -> Annex ()
+freezeContentDir file = liftIO . go =<< fromRepo getSharedRepository
+	where
+		dir = parentDir file
+		go GroupShared = groupWriteRead dir
+		go AllShared = groupWriteRead dir
+		go _ = preventWrite dir
+
+{- Makes the directory tree to store an annexed file's content,
+ - with appropriate permissions on each level. -}
+createContentDir :: FilePath -> Annex ()
+createContentDir dest = do
+	unlessM (liftIO $ doesDirectoryExist dir) $
+		createAnnexDirectory dir 
+	-- might have already existed with restricted perms
+	liftIO $ allowWrite dir
+	where
+		dir = parentDir dest
diff --git a/Annex/Journal.hs b/Annex/Journal.hs
index 34c4d98c88..ff103180ee 100644
--- a/Annex/Journal.hs
+++ b/Annex/Journal.hs
@@ -16,6 +16,7 @@ import System.IO.Binary
 import Common.Annex
 import Annex.Exception
 import qualified Git
+import Annex.Perms
 
 {- Records content for a file in the branch to the journal.
  -
@@ -23,22 +24,20 @@ import qualified Git
  - avoids git needing to rewrite the index after every change. -}
 setJournalFile :: FilePath -> String -> Annex ()
 setJournalFile file content = do
-	g <- gitRepo
-	liftIO $ doRedo (write g) $ do
-		createDirectoryIfMissing True $ gitAnnexJournalDir g
-		createDirectoryIfMissing True $ gitAnnexTmpDir g
-	where
-		-- journal file is written atomically
-		write g = do
-			let jfile = journalFile g file
-			let tmpfile = gitAnnexTmpDir g </> takeFileName jfile
-			writeBinaryFile tmpfile content
-			moveFile tmpfile jfile
+	createAnnexDirectory =<< fromRepo gitAnnexJournalDir
+	createAnnexDirectory =<< fromRepo gitAnnexTmpDir
+	-- journal file is written atomically
+	jfile <- fromRepo $ journalFile file
+	tmp <- fromRepo gitAnnexTmpDir
+	let tmpfile = tmp </> takeFileName jfile
+	liftIO $ do
+		writeBinaryFile tmpfile content
+		moveFile tmpfile jfile
 
 {- Gets any journalled content for a file in the branch. -}
 getJournalFile :: FilePath -> Annex (Maybe String)
 getJournalFile file = inRepo $ \g -> catchMaybeIO $
-	readFileStrict $ journalFile g file
+	readFileStrict $ journalFile file g
 
 {- List of files that have updated content in the journal. -}
 getJournalledFiles :: Annex [FilePath]
@@ -62,8 +61,8 @@ journalDirty = not . null <$> getJournalFiles
  - used in the branch is not necessary, and all the files are put directly
  - in the journal directory.
  -}
-journalFile :: Git.Repo -> FilePath -> FilePath
-journalFile repo file = gitAnnexJournalDir repo </> concatMap mangle file
+journalFile :: FilePath -> Git.Repo -> FilePath
+journalFile file repo = gitAnnexJournalDir repo </> concatMap mangle file
 	where
 		mangle '/' = "_"
 		mangle '_' = "__"
@@ -79,16 +78,12 @@ fileJournal = replace "//" "_" . replace "_" "/"
 lockJournal :: Annex a -> Annex a
 lockJournal a = do
 	file <- fromRepo gitAnnexJournalLock
-	bracketIO (lock file) unlock a
+	createAnnexDirectory $ takeDirectory file
+	mode <- annexFileMode
+	bracketIO (lock file mode) unlock a
 	where
-		lock file = do
-			l <- doRedo (createFile file stdFileMode) $
-				createDirectoryIfMissing True $ takeDirectory file
+		lock file mode = do
+			l <- noUmask mode $ createFile file mode
 			waitToSetLock l (WriteLock, AbsoluteSeek, 0, 0)
 			return l
 		unlock = closeFd
-
-{- Runs an action, catching failure and running something to fix it up, and
- - retrying if necessary. -}
-doRedo :: IO a -> IO b -> IO a
-doRedo a b = catchIO a $ const $ b >> a
diff --git a/Annex/LockPool.hs b/Annex/LockPool.hs
index 3fede5739b..b99a8ec4df 100644
--- a/Annex/LockPool.hs
+++ b/Annex/LockPool.hs
@@ -12,22 +12,24 @@ import System.Posix.Types (Fd)
 
 import Common.Annex
 import Annex
+import Annex.Perms
 
 {- Create a specified lock file, and takes a shared lock. -}
 lockFile :: FilePath -> Annex ()
 lockFile file = go =<< fromPool file
 	where
-		go (Just _) = return () -- already locked
+		go (Just _) = noop -- already locked
 		go Nothing = do
-			fd <- liftIO $ openFd file ReadOnly (Just stdFileMode) defaultFileFlags
+			mode <- annexFileMode
+			fd <- liftIO $ noUmask mode $
+				openFd file ReadOnly (Just mode) defaultFileFlags
 			liftIO $ waitToSetLock fd (ReadLock, AbsoluteSeek, 0, 0)
 			changePool $ M.insert file fd
 
 unlockFile :: FilePath -> Annex ()
-unlockFile file = go =<< fromPool file
+unlockFile file = maybe noop go =<< fromPool file
 	where
-		go Nothing = return ()
-		go (Just fd) = do
+		go fd = do
 			liftIO $ closeFd fd
 			changePool $ M.delete file
 
diff --git a/Annex/Perms.hs b/Annex/Perms.hs
new file mode 100644
index 0000000000..c54908b439
--- /dev/null
+++ b/Annex/Perms.hs
@@ -0,0 +1,70 @@
+{- git-annex file permissions
+ -
+ - Copyright 2012 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Annex.Perms (
+	setAnnexPerm,
+	annexFileMode,
+	createAnnexDirectory,
+	noUmask,
+) where
+
+import Common.Annex
+import Utility.FileMode
+import Git.SharedRepository
+import qualified Annex
+
+import System.Posix.Types
+
+withShared :: (SharedRepository -> Annex a) -> Annex a
+withShared a = maybe startup a =<< Annex.getState Annex.shared
+	where
+		startup = do
+			shared <- fromRepo getSharedRepository
+			Annex.changeState $ \s -> s { Annex.shared = Just shared }
+			a shared
+
+{- Sets appropriate file mode for a file or directory in the annex,
+ - other than the content files and content directory. Normally,
+ - use the default mode, but with core.sharedRepository set,
+ - allow the group to write, etc. -}
+setAnnexPerm :: FilePath -> Annex ()
+setAnnexPerm file = withShared $ liftIO . go
+	where
+		go GroupShared = groupWriteRead file
+		go AllShared = modifyFileMode file $ addModes $
+			[ ownerWriteMode, groupWriteMode ] ++ readModes
+		go _ = noop
+
+{- Gets the appropriate mode to use for creating a file in the annex
+ - (other than content files, which are locked down more). -}
+annexFileMode :: Annex FileMode
+annexFileMode = withShared $ return . go
+	where
+		go GroupShared = sharedmode
+		go AllShared = combineModes (sharedmode:readModes)
+		go _ = stdFileMode
+		sharedmode = combineModes
+			[ ownerWriteMode, groupWriteMode
+			, ownerReadMode, groupReadMode
+			]
+
+{- Creates a directory inside the gitAnnexDir, including any parent
+ - directories. Makes directories with appropriate permissions. -}
+createAnnexDirectory :: FilePath -> Annex ()
+createAnnexDirectory dir = traverse dir [] =<< top
+	where
+		top = parentDir <$> fromRepo gitAnnexDir
+		traverse d below stop
+			| d `equalFilePath` stop = done
+			| otherwise = ifM (liftIO $ doesDirectoryExist d)
+				( done
+				, traverse (parentDir d) (d:below) stop
+				)
+			where
+				done = forM_ below $ \p -> do
+					liftIO $ createDirectory p
+					setAnnexPerm p
diff --git a/Annex/Queue.hs b/Annex/Queue.hs
index f49a220690..24575e9068 100644
--- a/Annex/Queue.hs
+++ b/Annex/Queue.hs
@@ -26,15 +26,14 @@ add command params files = do
 flushWhenFull :: Annex ()
 flushWhenFull = do
 	q <- get
-	when (Git.Queue.full q) $ flush False
+	when (Git.Queue.full q) flush
 
 {- Runs (and empties) the queue. -}
-flush :: Bool -> Annex ()
-flush silent = do
+flush :: Annex ()
+flush = do
 	q <- get
 	unless (0 == Git.Queue.size q) $ do
-		unless silent $
-			showSideAction "Recording state in git"
+		showStoringStateAction
 		q' <- inRepo $ Git.Queue.flush q
 		store q'
 
@@ -47,7 +46,7 @@ new = do
 	store q
 	return q
 	where
-		queuesize = readish <$> getConfig "annex.queuesize" ""
+		queuesize = readish <$> getConfig (annexConfig "queuesize") ""
 
 store :: Git.Queue.Queue -> Annex ()
 store q = changeState $ \s -> s { repoqueue = Just q }
diff --git a/Annex/Ssh.hs b/Annex/Ssh.hs
index e6cd6a9263..8bd4fe33ab 100644
--- a/Annex/Ssh.hs
+++ b/Annex/Ssh.hs
@@ -14,9 +14,10 @@ import qualified Data.Map as M
 
 import Common.Annex
 import Annex.LockPool
-import qualified Git
+import qualified Git.Config
 import Config
 import qualified Build.SysConfig as SysConfig
+import Annex.Perms
 
 {- Generates parameters to ssh to a given host (or user@host) on a given
  - port, with connection caching. -}
@@ -46,8 +47,8 @@ sshInfo (host, port) = ifM caching
 	)
 	where
 		caching = fromMaybe SysConfig.sshconnectioncaching 
-			. Git.configTrue
-			<$> getConfig "annex.sshcaching" ""
+			. Git.Config.isTrue
+			<$> getConfig (annexConfig "sshcaching") ""
 
 cacheParams :: FilePath -> [CommandParam]
 cacheParams socketfile =
@@ -74,30 +75,29 @@ sshCleanup = do
 			-- be stopped.
 			let lockfile = socket2lock socketfile
 			unlockFile lockfile
-			fd <- liftIO $ openFd lockfile ReadWrite (Just stdFileMode) defaultFileFlags
+			mode <- annexFileMode
+			fd <- liftIO $ noUmask mode $
+				openFd lockfile ReadWrite (Just mode) defaultFileFlags
 			v <- liftIO $ tryIO $
 				setLock fd (WriteLock, AbsoluteSeek, 0, 0)
 			case v of
-				Left _ -> return ()
+				Left _ -> noop
 				Right _ -> stopssh socketfile
 			liftIO $ closeFd fd
 		stopssh socketfile = do
 			let (host, port) = socket2hostport socketfile
 			(_, params) <- sshInfo (host, port)
-			_ <- liftIO $ do
+			void $ liftIO $ do
 				-- "ssh -O stop" is noisy on stderr even with -q
 				let cmd = unwords $ toCommand $
 					[ Params "-O stop"
 					] ++ params ++ [Param host]
-				_ <- boolSystem "sh"
+				boolSystem "sh"
 					[ Param "-c"
 					, Param $ "ssh " ++ cmd ++ " >/dev/null 2>/dev/null"
 					]
-				--try $ removeFile socketfile
-				return ()
-			-- Cannot remove the lock file; other processes may
-			-- be waiting on our exclusive lock to use it.
-			return ()
+				-- Cannot remove the lock file; other processes may
+				-- be waiting on our exclusive lock to use it.
 
 hostport2socket :: String -> Maybe Integer -> FilePath
 hostport2socket host Nothing = host
diff --git a/Annex/UUID.hs b/Annex/UUID.hs
index e8306de903..517840fbad 100644
--- a/Annex/UUID.hs
+++ b/Annex/UUID.hs
@@ -16,7 +16,8 @@ module Annex.UUID (
 	getRepoUUID,
 	getUncachedUUID,
 	prepUUID,
-	genUUID
+	genUUID,
+	removeRepoUUID,
 ) where
 
 import Common.Annex
@@ -25,8 +26,8 @@ import qualified Git.Config
 import qualified Build.SysConfig as SysConfig
 import Config
 
-configkey :: String
-configkey = "annex.uuid"
+configkey :: ConfigKey
+configkey = annexConfig "uuid"
 
 {- Generates a UUID. There is a library for this, but it's not packaged,
  - so use the command line tool. -}
@@ -61,13 +62,18 @@ getRepoUUID r = do
 			when (g /= r) $ storeUUID cachekey u
 		cachekey = remoteConfig r "uuid"
 
+removeRepoUUID :: Annex ()
+removeRepoUUID = unsetConfig configkey
+
 getUncachedUUID :: Git.Repo -> UUID
-getUncachedUUID = toUUID . Git.Config.get configkey ""
+getUncachedUUID = toUUID . Git.Config.get key ""
+	where
+		(ConfigKey key) = configkey
 
 {- Make sure that the repo has an annex.uuid setting. -}
 prepUUID :: Annex ()
 prepUUID = whenM ((==) NoUUID <$> getUUID) $
 	storeUUID configkey =<< liftIO genUUID
 
-storeUUID :: String -> UUID -> Annex ()
+storeUUID :: ConfigKey -> UUID -> Annex ()
 storeUUID configfield = setConfig configfield . fromUUID
diff --git a/Annex/Version.hs b/Annex/Version.hs
index cf5d224842..7c909ae05b 100644
--- a/Annex/Version.hs
+++ b/Annex/Version.hs
@@ -21,8 +21,8 @@ supportedVersions = [defaultVersion]
 upgradableVersions :: [Version]
 upgradableVersions = ["0", "1", "2"]
 
-versionField :: String
-versionField = "annex.version"
+versionField :: ConfigKey
+versionField = annexConfig "version"
 
 getVersion :: Annex (Maybe Version)
 getVersion = handle <$> getConfig versionField ""
@@ -35,7 +35,7 @@ setVersion = setConfig versionField defaultVersion
 
 checkVersion :: Version -> Annex ()
 checkVersion v
-	| v `elem` supportedVersions = return ()
+	| v `elem` supportedVersions = noop
 	| v `elem` upgradableVersions = err "Upgrade this repository: git-annex upgrade"
 	| otherwise = err "Upgrade git-annex."
 	where
diff --git a/Backend.hs b/Backend.hs
index 19562205c8..fa32669449 100644
--- a/Backend.hs
+++ b/Backend.hs
@@ -46,7 +46,7 @@ orderedList = do
 			l' <- (lookupBackendName name :) <$> standard
 			Annex.changeState $ \s -> s { Annex.backends = l' }
 			return l'
-		standard = parseBackendList <$> getConfig "annex.backends" ""
+		standard = parseBackendList <$> getConfig (annexConfig "backends") ""
 		parseBackendList [] = list
 		parseBackendList s = map lookupBackendName $ words s
 
@@ -75,16 +75,16 @@ genKey' (b:bs) file = do
  - by examining what the file symlinks to. -}
 lookupFile :: FilePath -> Annex (Maybe (Key, Backend))
 lookupFile file = do
-	tl <- liftIO $ tryIO getsymlink
+	tl <- liftIO $ tryIO $ readSymbolicLink file
 	case tl of
 		Left _ -> return Nothing
 		Right l -> makekey l
 	where
-		getsymlink = takeFileName <$> readSymbolicLink file
-		makekey l = maybe (return Nothing) (makeret l) (fileKey l)
+		makekey l = maybe (return Nothing) (makeret l) (fileKey $ takeFileName l)
 		makeret l k = let bname = keyBackendName k in
 			case maybeLookupBackendName bname of
-				Just backend -> return $ Just (k, backend)
+				Just backend -> do
+					return $ Just (k, backend)
 				Nothing -> do
 					when (isLinkToAnnex l) $ warning $
 						"skipping " ++ file ++
diff --git a/Backend/SHA.hs b/Backend/SHA.hs
index 3adac65d8c..c2a6cf9761 100644
--- a/Backend/SHA.hs
+++ b/Backend/SHA.hs
@@ -45,7 +45,7 @@ genBackendE size =
 
 shaCommand :: SHASize -> Maybe String
 shaCommand 1 = SysConfig.sha1
-shaCommand 256 = SysConfig.sha256
+shaCommand 256 = Just SysConfig.sha256
 shaCommand 224 = SysConfig.sha224
 shaCommand 384 = SysConfig.sha384
 shaCommand 512 = SysConfig.sha512
diff --git a/Build/Configure.hs b/Build/Configure.hs
index 341b8840dc..2f79297ee9 100644
--- a/Build/Configure.hs
+++ b/Build/Configure.hs
@@ -6,6 +6,7 @@ import System.Directory
 import Data.List
 import System.Cmd.Utils
 import Control.Applicative
+import System.FilePath
 
 import Build.TestConfig
 import Utility.SafeCommand
@@ -26,15 +27,21 @@ tests =
 	, TestCase "bup" $ testCmd "bup" "bup --version >/dev/null"
 	, TestCase "gpg" $ testCmd "gpg" "gpg --version >/dev/null"
 	, TestCase "ssh connection caching" getSshConnectionCaching
-	] ++ shaTestCases [1, 256, 512, 224, 384]
+	] ++ shaTestCases False [1, 512, 224, 384] ++ shaTestCases True [256]
 
-shaTestCases :: [Int] -> [TestCase]
-shaTestCases l = map make l
-	where make n =
-		let
-			cmds = map (\x -> "sha" ++ show n ++ x) ["", "sum"]
-			key = "sha" ++ show n
-		in TestCase key $ maybeSelectCmd key cmds "</dev/null"
+shaTestCases :: Bool -> [Int] -> [TestCase]
+shaTestCases required l = map make l
+	where
+		make n = TestCase key $ selector key (shacmds n) "</dev/null"
+			where
+				key = "sha" ++ show n
+		selector = if required then selectCmd else maybeSelectCmd
+		shacmds n = concatMap (\x -> [x, osxpath </> x]) $
+			map (\x -> "sha" ++ show n ++ x) ["", "sum"]
+		-- Max OSX puts GNU tools outside PATH, so look in
+		-- the location it uses, and remember where to run them
+		-- from.
+		osxpath = "/opt/local/libexec/gnubin"
 
 tmpDir :: String
 tmpDir = "tmp"
diff --git a/CmdLine.hs b/CmdLine.hs
index 5330f40fc9..910f228b60 100644
--- a/CmdLine.hs
+++ b/CmdLine.hs
@@ -46,19 +46,19 @@ dispatch fuzzyok allargs allcmds commonoptions header getgitrepo = do
 	where
 		err msg = msg ++ "\n\n" ++ usage header allcmds commonoptions
 		cmd = Prelude.head cmds
-		(cmds, name, args) = findCmd fuzzyok allargs allcmds err
+		(fuzzy, cmds, name, args) = findCmd fuzzyok allargs allcmds err
 		(flags, params) = getOptCmd args cmd commonoptions err
-		checkfuzzy = when (length cmds > 1) $
+		checkfuzzy = when fuzzy $
 			inRepo $ Git.AutoCorrect.prepare name cmdname cmds
 
 {- Parses command line params far enough to find the Command to run, and
  - returns the remaining params.
  - Does fuzzy matching if necessary, which may result in multiple Commands. -}
-findCmd :: Bool -> Params -> [Command] -> (String -> String) -> ([Command], String, Params)
+findCmd :: Bool -> Params -> [Command] -> (String -> String) -> (Bool, [Command], String, Params)
 findCmd fuzzyok argv cmds err
 	| isNothing name = error $ err "missing command"
-	| not (null exactcmds) = (exactcmds, fromJust name, args)
-	| fuzzyok && not (null inexactcmds) = (inexactcmds, fromJust name, args)
+	| not (null exactcmds) = (False, exactcmds, fromJust name, args)
+	| fuzzyok && not (null inexactcmds) = (True, inexactcmds, fromJust name, args)
 	| otherwise = error $ err $ "unknown command " ++ fromJust name
 	where
 		(name, args) = findname argv []
@@ -88,7 +88,7 @@ tryRun = tryRun' 0
 tryRun' :: Integer -> Annex.AnnexState -> Command -> [CommandCleanup] -> IO ()
 tryRun' errnum _ cmd []
 	| errnum > 0 = error $ cmdname cmd ++ ": " ++ show errnum ++ " failed"
-	| otherwise = return ()
+	| otherwise = noop
 tryRun' errnum state cmd (a:as) = do
 	r <- run
 	handle $! r
diff --git a/Command/AddUnused.hs b/Command/AddUnused.hs
new file mode 100644
index 0000000000..c498216dc3
--- /dev/null
+++ b/Command/AddUnused.hs
@@ -0,0 +1,34 @@
+{- git-annex command
+ -
+ - Copyright 2012 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Command.AddUnused where
+
+import Common.Annex
+import Logs.Unused
+import Command
+import qualified Command.Add
+
+def :: [Command]
+def = [command "addunused" (paramRepeating paramNumRange)
+	seek "add back unused files"]
+
+seek :: [CommandSeek]
+seek = [withUnusedMaps start]
+
+start :: UnusedMaps -> Int -> CommandStart
+start = startUnused "addunused" perform (performOther "bad") (performOther "tmp")
+
+perform :: Key -> CommandPerform
+perform key = next $ Command.Add.cleanup file key True
+	where
+		file = "unused." ++ show key
+
+{- The content is not in the annex, but in another directory, and
+ - it seems better to error out, rather than moving bad/tmp content into
+ - the annex. -}
+performOther :: String -> Key -> CommandPerform
+performOther other _ = error $ "cannot addunused " ++ other ++ "content"
diff --git a/Command/AddUrl.hs b/Command/AddUrl.hs
index c87399f5dc..089606e85d 100644
--- a/Command/AddUrl.hs
+++ b/Command/AddUrl.hs
@@ -20,6 +20,7 @@ import Annex.Content
 import Logs.Web
 import qualified Option
 import Types.Key
+import Config
 
 def :: [Command]
 def = [withOptions [fileOption, pathdepthOption] $
@@ -53,8 +54,9 @@ perform url file = ifAnnexed file addurl geturl
 			liftIO $ createDirectoryIfMissing True (parentDir file)
 			ifM (Annex.getState Annex.fast)
 				( nodownload url file , download url file )
-		addurl (key, _backend) =
-			ifM (liftIO $ Url.check url $ keySize key)
+		addurl (key, _backend) = do
+			headers <- getHttpHeaders
+			ifM (liftIO $ Url.check url headers $ keySize key)
 				( do
 					setUrlPresent key url
 					next $ return True
@@ -81,7 +83,8 @@ download url file = do
 
 nodownload :: String -> FilePath -> CommandPerform
 nodownload url file = do
-	(exists, size) <- liftIO $ Url.exists url
+	headers <- getHttpHeaders
+	(exists, size) <- liftIO $ Url.exists url headers
 	if exists
 		then do
 			let key = Backend.URL.fromUrl url size
diff --git a/Command/DropUnused.hs b/Command/DropUnused.hs
index 0b2a602161..a94c2873dd 100644
--- a/Command/DropUnused.hs
+++ b/Command/DropUnused.hs
@@ -1,14 +1,13 @@
 {- git-annex command
  -
- - Copyright 2010 Joey Hess <joey@kitenet.net>
+ - Copyright 2010,2012 Joey Hess <joey@kitenet.net>
  -
  - Licensed under the GNU GPL version 3 or higher.
  -}
 
 module Command.DropUnused where
 
-import qualified Data.Map as M
-
+import Logs.Unused
 import Common.Annex
 import Command
 import qualified Annex
@@ -16,40 +15,17 @@ import qualified Command.Drop
 import qualified Remote
 import qualified Git
 import qualified Option
-import Types.Key
-
-type UnusedMap = M.Map String Key
 
 def :: [Command]
 def = [withOptions [Command.Drop.fromOption] $
-	command "dropunused" (paramRepeating paramNumber)
+	command "dropunused" (paramRepeating paramNumRange)
 		seek "drop unused file content"]
 
 seek :: [CommandSeek]
-seek = [withUnusedMaps]
+seek = [withUnusedMaps start]
 
-{- Read unused logs once, and pass the maps to each start action. -}
-withUnusedMaps :: CommandSeek
-withUnusedMaps params = do
-	unused <- readUnusedLog ""
-	unusedbad <- readUnusedLog "bad"
-	unusedtmp <- readUnusedLog "tmp"
-	return $ map (start (unused, unusedbad, unusedtmp)) params
-
-start :: (UnusedMap, UnusedMap, UnusedMap) -> FilePath -> CommandStart
-start (unused, unusedbad, unusedtmp) s = search
-	[ (unused, perform)
-	, (unusedbad, performOther gitAnnexBadLocation)
-	, (unusedtmp, performOther gitAnnexTmpLocation)
-	]
-	where
-		search [] = stop
-		search ((m, a):rest) =
-			case M.lookup s m of
-				Nothing -> search rest
-				Just key -> do
-					showStart "dropunused" s
-					next $ a key
+start :: UnusedMaps -> Int -> CommandStart
+start = startUnused "dropunused" perform (performOther gitAnnexBadLocation) (performOther gitAnnexTmpLocation)
 
 perform :: Key -> CommandPerform
 perform key = maybe droplocal dropremote =<< Remote.byName =<< from
@@ -66,15 +42,3 @@ performOther filespec key = do
 	f <- fromRepo $ filespec key
 	liftIO $ whenM (doesFileExist f) $ removeFile f
 	next $ return True
-
-readUnusedLog :: FilePath -> Annex UnusedMap
-readUnusedLog prefix = do
-	f <- fromRepo $ gitAnnexUnusedLog prefix
-	e <- liftIO $ doesFileExist f
-	if e
-		then M.fromList . map parse . lines <$> liftIO (readFile f)
-		else return M.empty
-	where
-		parse line = (num, fromJust $ readKey rest)
-			where
-				(num, rest) = separate (== ' ') line
diff --git a/Command/Fsck.hs b/Command/Fsck.hs
index dac3bfac96..38b1bbbacd 100644
--- a/Command/Fsck.hs
+++ b/Command/Fsck.hs
@@ -85,7 +85,7 @@ performRemote key file backend numcopies remote =
 			t <- fromRepo gitAnnexTmpDir
 			let tmp = t </> "fsck" ++ show pid ++ "." ++ keyFile key
 			liftIO $ createDirectoryIfMissing True t
-			let cleanup = liftIO $ catchIO (removeFile tmp) (const $ return ())
+			let cleanup = liftIO $ catchIO (removeFile tmp) (const noop)
 			cleanup
 			cleanup `after` a tmp
 		getfile tmp =
@@ -166,10 +166,9 @@ verifyLocationLog key desc = do
 	-- Since we're checking that a key's file is present, throw
 	-- in a permission fixup here too.
 	when present $ do
-		f <- inRepo $ gitAnnexLocation key
-		liftIO $ do
-			preventWrite f
-			preventWrite (parentDir f)
+		file <- inRepo $ gitAnnexLocation key
+		freezeContent file
+		freezeContentDir file
 
 	u <- getUUID
 	verifyLocationLog' key desc present u (logChange key u)
diff --git a/Command/Import.hs b/Command/Import.hs
new file mode 100644
index 0000000000..e27a421f27
--- /dev/null
+++ b/Command/Import.hs
@@ -0,0 +1,39 @@
+{- git-annex command
+ -
+ - Copyright 2012 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Command.Import where
+
+import Common.Annex
+import Command
+import qualified Annex
+import qualified Command.Add
+
+def :: [Command]
+def = [command "import" paramPaths seek "move and add files from outside git working copy"]
+
+seek :: [CommandSeek]
+seek = [withPathContents start]
+
+start :: (FilePath, FilePath) -> CommandStart
+start (srcfile, destfile) = notBareRepo $
+	ifM (liftIO $ isRegularFile <$> getSymbolicLinkStatus srcfile)
+		( do
+			showStart "import" destfile
+			next $ perform srcfile destfile
+		, stop
+		)
+
+perform :: FilePath -> FilePath -> CommandPerform
+perform srcfile destfile = do
+	whenM (liftIO $ doesFileExist destfile) $
+		unlessM (Annex.getState Annex.force) $
+			error $ "not overwriting existing " ++ destfile ++
+				" (use --force to override)"
+ 
+	liftIO $ createDirectoryIfMissing True (parentDir destfile)
+	liftIO $ moveFile srcfile destfile
+	Command.Add.perform destfile
diff --git a/Command/Lock.hs b/Command/Lock.hs
index b8aedb252b..ab97b14bcc 100644
--- a/Command/Lock.hs
+++ b/Command/Lock.hs
@@ -24,9 +24,5 @@ start file = do
 
 perform :: FilePath -> CommandPerform
 perform file = do
-	liftIO $ removeFile file
-	-- Checkout from HEAD to get rid of any changes that might be 
-	-- staged in the index, and get back to the previous symlink to
-	-- the content.
-	Annex.Queue.add "checkout" [Param "HEAD", Param "--"] [file]
+	Annex.Queue.add "checkout" [Param "--"] [file]
 	next $ return True -- no cleanup needed
diff --git a/Command/Log.hs b/Command/Log.hs
index d78b602067..aa39aea9c7 100644
--- a/Command/Log.hs
+++ b/Command/Log.hs
@@ -133,7 +133,7 @@ compareChanges format changes = concatMap diff $ zip changes (drop 1 changes)
  - *lot* for newish files. -}
 getLog :: Key -> [CommandParam] -> Annex [String]
 getLog key os = do
-	top <- fromRepo Git.workTree
+	top <- fromRepo Git.repoPath
 	p <- liftIO $ relPathCwdToFile top
 	let logfile = p </> Logs.Location.logFile key
 	inRepo $ pipeNullSplit $
diff --git a/Command/Map.hs b/Command/Map.hs
index bdb86f95a5..86e9609a7e 100644
--- a/Command/Map.hs
+++ b/Command/Map.hs
@@ -156,14 +156,14 @@ absRepo :: Git.Repo -> Git.Repo -> Annex Git.Repo
 absRepo reference r
 	| Git.repoIsUrl reference = return $ Git.Construct.localToUrl reference r
 	| Git.repoIsUrl r = return r
-	| otherwise = liftIO $ Git.Construct.fromAbsPath =<< absPath (Git.workTree r)
+	| otherwise = liftIO $ Git.Construct.fromAbsPath =<< absPath (Git.repoPath r)
 
 {- Checks if two repos are the same. -}
 same :: Git.Repo -> Git.Repo -> Bool
 same a b
-	| both Git.repoIsSsh = matching Git.Url.authority && matching Git.workTree
+	| both Git.repoIsSsh = matching Git.Url.authority && matching Git.repoPath
 	| both Git.repoIsUrl && neither Git.repoIsSsh = matching show
-	| neither Git.repoIsSsh = matching Git.workTree
+	| neither Git.repoIsSsh = matching Git.repoPath
 	| otherwise = False
 		
 	where
@@ -210,7 +210,7 @@ tryScan r
 			where
 				sshcmd = cddir ++ " && " ++
 					"git config --null --list"
-				dir = Git.workTree r
+				dir = Git.repoPath r
 				cddir
 					| "/~" `isPrefixOf` dir =
 						let (userhome, reldir) = span (/= '/') (drop 1 dir)
diff --git a/Command/Status.hs b/Command/Status.hs
index 1ee36d8b47..2540a92da8 100644
--- a/Command/Status.hs
+++ b/Command/Status.hs
@@ -30,6 +30,7 @@ import Logs.UUID
 import Logs.Trust
 import Remote
 import Config
+import Utility.Percentage
 
 -- a named computation that produces a statistic
 type Stat = StatState (Maybe (String, StatState String))
@@ -69,6 +70,7 @@ fast_stats =
 	, remote_list SemiTrusted "semitrusted"
 	, remote_list UnTrusted "untrusted"
 	, remote_list DeadTrusted "dead"
+	, disk_size
 	]
 slow_stats :: [Stat]
 slow_stats = 
@@ -78,7 +80,6 @@ slow_stats =
 	, local_annex_size
 	, known_annex_keys
 	, known_annex_size
-	, disk_size
 	, bloom_info
 	, backend_usage
 	]
@@ -108,12 +109,11 @@ nojson :: StatState String -> String -> StatState String
 nojson a _ = a
 
 showStat :: Stat -> StatState ()
-showStat s = calc =<< s
+showStat s = maybe noop calc =<< s
 	where
-		calc (Just (desc, a)) = do
+		calc (desc, a) = do
 			(lift . showHeader) desc
 			lift . showRaw =<< a
-		calc Nothing = return ()
 
 supported_backends :: Stat
 supported_backends = stat "supported backends" $ json unwords $
@@ -161,7 +161,7 @@ bloom_info = stat "bloom filter size" $ json id $ do
 	let note = aside $
 		if localkeys >= capacity
 		then "appears too small for this repository; adjust annex.bloomcapacity"
-		else "has room for " ++ show (capacity - localkeys) ++ " more local annex keys"
+		else showPercentage 1 (percentage capacity localkeys) ++ " full"
 
 	-- Two bloom filters are used at the same time, so double the size
 	-- of one.
@@ -176,8 +176,12 @@ disk_size = stat "available local disk space" $ json id $ lift $
 		<$> getDiskReserve
 		<*> inRepo (getDiskFree . gitAnnexDir)
 	where
-		calcfree reserve (Just have) =
-			roughSize storageUnits False $ nonneg $ have - reserve
+		calcfree reserve (Just have) = unwords
+			[ roughSize storageUnits False $ nonneg $ have - reserve
+			, "(+" ++ roughSize storageUnits False reserve
+			, "reserved)"
+			]
+			
 		calcfree _ _ = "unknown"
 		nonneg x
 			| x >= 0 = x
diff --git a/Command/Sync.hs b/Command/Sync.hs
index b9ef0bc979..5fb49d30c5 100644
--- a/Command/Sync.hs
+++ b/Command/Sync.hs
@@ -57,10 +57,17 @@ syncRemotes rs = ifM (Annex.getState Annex.fast) ( nub <$> pickfast , wanted )
 		wanted
 			| null rs = good =<< concat . byspeed <$> available
 			| otherwise = listed
-		listed = catMaybes <$> mapM (Remote.byName . Just) rs
+		listed = do
+			l <- catMaybes <$> mapM (Remote.byName . Just) rs
+			let s = filter special l
+			unless (null s) $
+				error $ "cannot sync special remotes: " ++
+					unwords (map Types.Remote.name s)
+			return l
 		available = filter nonspecial <$> Remote.enabledRemoteList
 		good = filterM $ Remote.Git.repoAvail . Types.Remote.repo
 		nonspecial r = Types.Remote.remotetype r == Remote.Git.remote
+		special = not . nonspecial
 		fastest = fromMaybe [] . headMaybe . byspeed
 		byspeed = map snd . sort . M.toList . costmap
 		costmap = M.fromListWith (++) . map costpair
diff --git a/Command/Unannex.hs b/Command/Unannex.hs
index 1e7313711c..bf931adfd4 100644
--- a/Command/Unannex.hs
+++ b/Command/Unannex.hs
@@ -10,7 +10,6 @@ module Command.Unannex where
 import Common.Annex
 import Command
 import qualified Annex
-import Utility.FileMode
 import Logs.Location
 import Annex.Content
 import qualified Git.Command
@@ -51,9 +50,8 @@ cleanup file key = do
 		( do
 			-- fast mode: hard link to content in annex
 			src <- inRepo $ gitAnnexLocation key
-			liftIO $ do
-				createLink src file
-				allowWrite file
+			liftIO $ createLink src file
+			thawContent file
 		, do
 			fromAnnex key file
 			logStatus key InfoMissing
diff --git a/Command/Unlock.hs b/Command/Unlock.hs
index afee101459..f3ffd31ba6 100644
--- a/Command/Unlock.hs
+++ b/Command/Unlock.hs
@@ -11,7 +11,6 @@ import Common.Annex
 import Command
 import Annex.Content
 import Utility.CopyFile
-import Utility.FileMode
 
 def :: [Command]
 def =
@@ -34,8 +33,7 @@ start file (key, _) = do
 perform :: FilePath -> Key -> CommandPerform
 perform dest key = do
 	unlessM (inAnnex key) $ error "content not present"
-	
-	checkDiskSpace key
+	unlessM (checkDiskSpace Nothing key 0) $ error "cannot unlock"
 
 	src <- inRepo $ gitAnnexLocation key
 	tmpdest <- fromRepo $ gitAnnexTmpLocation key
@@ -47,6 +45,6 @@ perform dest key = do
 			liftIO $ do
 				removeFile dest
 				moveFile tmpdest dest
-				allowWrite dest
+			thawContent dest
 			next $ return True
                 else error "copy failed!"
diff --git a/Command/Unused.hs b/Command/Unused.hs
index bc721635b7..1224d05457 100644
--- a/Command/Unused.hs
+++ b/Command/Unused.hs
@@ -19,9 +19,9 @@ import Control.Monad.ST
 
 import Common.Annex
 import Command
+import Logs.Unused
 import Annex.Content
 import Utility.FileMode
-import Utility.TempFile
 import Logs.Location
 import Config
 import qualified Annex
@@ -91,19 +91,13 @@ check file msg a c = do
 	l <- a
 	let unusedlist = number c l
 	unless (null l) $ showLongNote $ msg unusedlist
-	writeUnusedFile file unusedlist
+	writeUnusedLog file unusedlist
 	return $ c + length l
 
 number :: Int -> [a] -> [(Int, a)]
 number _ [] = []
 number n (x:xs) = (n+1, x) : number (n+1) xs
 
-writeUnusedFile :: FilePath -> [(Int, Key)] -> Annex ()
-writeUnusedFile prefix l = do
-	logfile <- fromRepo $ gitAnnexUnusedLog prefix
-	liftIO $ viaTmp writeFile logfile $
-		unlines $ map (\(n, k) -> show n ++ " " ++ show k) l
-
 table :: [(Int, Key)] -> [String]
 table l = "  NUMBER  KEY" : map cols l
 	where
@@ -189,10 +183,10 @@ exclude smaller larger = S.toList $ remove larger $ S.fromList smaller
  -}
 bloomCapacity :: Annex Int
 bloomCapacity = fromMaybe 500000 . readish
-	<$> getConfig "annex.bloomcapacity" ""
+	<$> getConfig (annexConfig "bloomcapacity") ""
 bloomAccuracy :: Annex Int
 bloomAccuracy = fromMaybe 1000 . readish
-	<$> getConfig "annex.bloomaccuracy" ""
+	<$> getConfig (annexConfig "bloomaccuracy") ""
 bloomBitsHashes :: Annex (Int, Int)
 bloomBitsHashes = do
 	capacity <- bloomCapacity
@@ -237,7 +231,7 @@ withKeysReferenced' :: v -> (Key -> v -> Annex v) -> Annex v
 withKeysReferenced' initial a = go initial =<< files
 	where
 		files = do
-			top <- fromRepo Git.workTree
+			top <- fromRepo Git.repoPath
 			inRepo $ LsFiles.inRepo [top]
 		go v [] = return v
 		go v (f:fs) = do
@@ -268,7 +262,7 @@ withKeysReferencedInGitRef a ref = do
 	showAction $ "checking " ++ Git.Ref.describe ref
 	go =<< inRepo (LsTree.lsTree ref)
 	where
-		go [] = return ()
+		go [] = noop
 		go (l:ls)
 			| isSymLink (LsTree.mode l) = do
 				content <- L.decodeUtf8 <$> catFile ref (LsTree.file l)
diff --git a/Command/Whereis.hs b/Command/Whereis.hs
index d4d268d937..eb6ea7c56d 100644
--- a/Command/Whereis.hs
+++ b/Command/Whereis.hs
@@ -46,9 +46,9 @@ perform remotemap key = do
 		untrustedheader = "The following untrusted locations may also have copies:\n"
 
 performRemote :: Key -> Remote -> Annex () 
-performRemote key remote = case whereisKey remote of
-	Nothing -> return ()
-	Just a -> do
-		ls <- a key
-		unless (null ls) $ showLongNote $
-			unlines $ map (\l -> name remote ++ ": " ++ l) ls
+performRemote key remote = maybe noop go $ whereisKey remote
+	where
+		go a = do
+			ls <- a key
+			unless (null ls) $ showLongNote $ unlines $
+				map (\l -> name remote ++ ": " ++ l) ls
diff --git a/Config.hs b/Config.hs
index 10a66e47b1..f579e40b21 100644
--- a/Config.hs
+++ b/Config.hs
@@ -1,6 +1,6 @@
 {- Git configuration
  -
- - Copyright 2011 Joey Hess <joey@kitenet.net>
+ - Copyright 2011-2012 Joey Hess <joey@kitenet.net>
  -
  - Licensed under the GNU GPL version 3 or higher.
  -}
@@ -14,29 +14,39 @@ import qualified Git.Command
 import qualified Annex
 import Utility.DataUnits
 
-type ConfigKey = String
+type UnqualifiedConfigKey = String
+data ConfigKey = ConfigKey String
 
 {- Changes a git config setting in both internal state and .git/config -}
 setConfig :: ConfigKey -> String -> Annex ()
-setConfig k value = do
-	inRepo $ Git.Command.run "config" [Param k, Param value]
-	-- re-read git config and update the repo's state
-	newg <- inRepo Git.Config.read
+setConfig (ConfigKey key) value = do
+	inRepo $ Git.Command.run "config" [Param key, Param value]
+	newg <- inRepo Git.Config.reRead
 	Annex.changeState $ \s -> s { Annex.repo = newg }
 
-{- Looks up a git config setting in git config. -}
+{- Unsets a git config setting. (Leaves it in state currently.) -}
+unsetConfig :: ConfigKey -> Annex ()
+unsetConfig (ConfigKey key) = inRepo $ Git.Command.run "config"
+        [Param "--unset", Param key]
+
+{- Looks up a setting in git config. -}
 getConfig :: ConfigKey -> String -> Annex String
-getConfig key def = fromRepo $ Git.Config.get key def
+getConfig (ConfigKey key) def = fromRepo $ Git.Config.get key def
 
 {- Looks up a per-remote config setting in git config.
  - Failing that, tries looking for a global config option. -}
-getRemoteConfig :: Git.Repo -> ConfigKey -> String -> Annex String
-getRemoteConfig r key def =
-	getConfig (remoteConfig r key) =<< getConfig key def
+getRemoteConfig :: Git.Repo -> UnqualifiedConfigKey -> String -> Annex String
+getRemoteConfig r key def = 
+	getConfig (remoteConfig r key) =<< getConfig (annexConfig key) def
 
 {- A per-remote config setting in git config. -}
-remoteConfig :: Git.Repo -> ConfigKey -> String
-remoteConfig r key = "remote." ++ fromMaybe "" (Git.remoteName r) ++ ".annex-" ++ key
+remoteConfig :: Git.Repo -> UnqualifiedConfigKey -> ConfigKey
+remoteConfig r key = ConfigKey $
+	"remote." ++ fromMaybe "" (Git.remoteName r) ++ ".annex-" ++ key
+
+{- A global annex setting in git config. -}
+annexConfig :: UnqualifiedConfigKey -> ConfigKey
+annexConfig key = ConfigKey $ "annex." ++ key
 
 {- Calculates cost for a remote. Either the default, or as configured 
  - by remote.<name>.annex-cost, or if remote.<name>.annex-cost-command
@@ -73,7 +83,7 @@ prop_cost_sane = False `notElem`
 
 {- Checks if a repo should be ignored. -}
 repoNotIgnored :: Git.Repo -> Annex Bool
-repoNotIgnored r = not . fromMaybe False . Git.configTrue
+repoNotIgnored r = not . fromMaybe False . Git.Config.isTrue
 	<$> getRemoteConfig r "ignore" ""
 
 {- If a value is specified, it is used; otherwise the default is looked up
@@ -83,16 +93,27 @@ getNumCopies v = perhaps (use v) =<< Annex.getState Annex.forcenumcopies
 	where
 		use (Just n) = return n
 		use Nothing = perhaps (return 1) =<< 
-			readish <$> getConfig "annex.numcopies" "1"
+			readish <$> getConfig (annexConfig "numcopies") "1"
 		perhaps fallback = maybe fallback (return . id)
 
 {- Gets the trust level set for a remote in git config. -}
 getTrustLevel :: Git.Repo -> Annex (Maybe String)
-getTrustLevel r = fromRepo $ Git.Config.getMaybe $ remoteConfig r "trustlevel"
+getTrustLevel r = fromRepo $ Git.Config.getMaybe key
+	where
+		(ConfigKey key) = remoteConfig r "trustlevel"
 
 {- Gets annex.diskreserve setting. -}
 getDiskReserve :: Annex Integer
 getDiskReserve = fromMaybe megabyte . readSize dataUnits
-	<$> getConfig "diskreserve" ""
+	<$> getConfig (annexConfig "diskreserve") ""
 	where
 		megabyte = 1000000
+
+{- Gets annex.httpheaders or annex.httpheaders-command setting,
+ - splitting it into lines. -}
+getHttpHeaders :: Annex [String]
+getHttpHeaders = do
+	cmd <- getConfig (annexConfig "http-headers-command") ""
+	if (null cmd)
+		then fromRepo $ Git.Config.getList "annex.http-headers"
+		else lines . snd <$> liftIO (pipeFrom "sh" ["-c", cmd])
diff --git a/Crypto.hs b/Crypto.hs
index cb1ca40d14..58c0e6d008 100644
--- a/Crypto.hs
+++ b/Crypto.hs
@@ -3,19 +3,19 @@
  - Currently using gpg; could later be modified to support different
  - crypto backends if neccessary.
  -
- - Copyright 2011 Joey Hess <joey@kitenet.net>
+ - Copyright 2011-2012 Joey Hess <joey@kitenet.net>
  -
  - Licensed under the GNU GPL version 3 or higher.
  -}
 
 module Crypto (
 	Cipher,
-	EncryptedCipher,
-	genCipher,
-	updateCipher,
+	KeyIds(..),
+	StorableCipher(..),
+	genEncryptedCipher,
+	genSharedCipher,
+	updateEncryptedCipher,
 	describeCipher,
-	storeCipher,
-	extractCipher,
 	decryptCipher,		
 	encryptKey,
 	withEncryptedHandle,
@@ -27,7 +27,6 @@ module Crypto (
 ) where
 
 import qualified Data.ByteString.Lazy.Char8 as L
-import qualified Data.Map as M
 import Data.ByteString.Lazy.UTF8 (fromString)
 import Data.Digest.Pure.SHA
 import Control.Applicative
@@ -35,8 +34,6 @@ import Control.Applicative
 import Common.Annex
 import qualified Utility.Gpg as Gpg
 import Types.Key
-import Types.Remote
-import Utility.Base64
 import Types.Crypto
 
 {- The first half of a Cipher is used for HMAC; the remainder
@@ -60,59 +57,37 @@ cipherPassphrase (Cipher c) = drop cipherHalf c
 cipherHmac :: Cipher -> String
 cipherHmac (Cipher c) = take cipherHalf c
 
-{- Creates a new Cipher, encrypted as specified in the remote's configuration -}
-genCipher :: RemoteConfig -> IO EncryptedCipher
-genCipher c = do
-	ks <- configKeyIds c
-	random <- genrandom
+{- Creates a new Cipher, encrypted to the specificed key id. -}
+genEncryptedCipher :: String -> IO StorableCipher
+genEncryptedCipher keyid = do
+	ks <- Gpg.findPubKeys keyid
+	random <- Gpg.genRandom cipherSize
 	encryptCipher (Cipher random) ks
-	where
-		genrandom = Gpg.readStrict
-			-- Armor the random data, to avoid newlines,
-			-- since gpg only reads ciphers up to the first
-			-- newline.
-			[ Params "--gen-random --armor"
-			, Param $ show randomquality
-			, Param $ show cipherSize
-			]
-		-- 1 is /dev/urandom; 2 is /dev/random
-		randomquality = 1 :: Int
 
-{- Updates an existing Cipher, re-encrypting it to add KeyIds specified in
- - the remote's configuration. -}
-updateCipher :: RemoteConfig -> EncryptedCipher -> IO EncryptedCipher
-updateCipher c encipher@(EncryptedCipher _ ks) = do
-	ks' <- configKeyIds c
-	cipher <- decryptCipher c encipher
+{- Creates a new, shared Cipher. -}
+genSharedCipher :: IO StorableCipher
+genSharedCipher = SharedCipher <$> Gpg.genRandom cipherSize
+
+{- Updates an existing Cipher, re-encrypting it to add a keyid. -}
+updateEncryptedCipher :: String -> StorableCipher -> IO StorableCipher
+updateEncryptedCipher _ (SharedCipher _) = undefined
+updateEncryptedCipher keyid encipher@(EncryptedCipher _ ks) = do
+	ks' <- Gpg.findPubKeys keyid
+	cipher <- decryptCipher encipher
 	encryptCipher cipher (merge ks ks')
 	where
 		merge (KeyIds a) (KeyIds b) = KeyIds $ a ++ b
 
-describeCipher :: EncryptedCipher -> String
+describeCipher :: StorableCipher -> String
+describeCipher (SharedCipher _) = "shared cipher"
 describeCipher (EncryptedCipher _ (KeyIds ks)) =
 	"with gpg " ++ keys ks ++ " " ++ unwords ks
 	where
 		keys [_] = "key"
 		keys _ = "keys"
 
-{- Stores an EncryptedCipher in a remote's configuration. -}
-storeCipher :: RemoteConfig -> EncryptedCipher -> RemoteConfig
-storeCipher c (EncryptedCipher t ks) = 
-	M.insert "cipher" (toB64 t) $ M.insert "cipherkeys" (showkeys ks) c
-	where
-		showkeys (KeyIds l) = join "," l
-
-{- Extracts an EncryptedCipher from a remote's configuration. -}
-extractCipher :: RemoteConfig -> Maybe EncryptedCipher
-extractCipher c = 
-	case (M.lookup "cipher" c, M.lookup "cipherkeys" c) of
-		(Just t, Just ks) -> Just $ EncryptedCipher (fromB64 t) (readkeys ks)
-		_ -> Nothing
-	where
-		readkeys = KeyIds . split ","
-
 {- Encrypts a Cipher to the specified KeyIds. -}
-encryptCipher :: Cipher -> KeyIds -> IO EncryptedCipher
+encryptCipher :: Cipher -> KeyIds -> IO StorableCipher
 encryptCipher (Cipher c) (KeyIds ks) = do
 	let ks' = nub $ sort ks -- gpg complains about duplicate recipient keyids
 	encipher <- Gpg.pipeStrict (encrypt++recipients ks') c
@@ -126,9 +101,9 @@ encryptCipher (Cipher c) (KeyIds ks) = do
 		force_recipients = Params "--no-encrypt-to --no-default-recipient"
 
 {- Decrypting an EncryptedCipher is expensive; the Cipher should be cached. -}
-decryptCipher :: RemoteConfig -> EncryptedCipher -> IO Cipher
-decryptCipher _ (EncryptedCipher encipher _) = 
-	Cipher <$> Gpg.pipeStrict decrypt encipher
+decryptCipher :: StorableCipher -> IO Cipher
+decryptCipher (SharedCipher t) = return $ Cipher t
+decryptCipher (EncryptedCipher t _) = Cipher <$> Gpg.pipeStrict decrypt t
 	where
 		decrypt = [ Param "--decrypt" ]
 
@@ -163,15 +138,7 @@ withDecryptedContent = pass withDecryptedHandle
 
 pass :: (Cipher -> IO L.ByteString -> (Handle -> IO a) -> IO a) 
       -> Cipher -> IO L.ByteString -> (L.ByteString -> IO a) -> IO a
-pass to c i a = to c i $ \h -> a =<< L.hGetContents h
-
-configKeyIds :: RemoteConfig -> IO KeyIds
-configKeyIds c = Gpg.findPubKeys $ configGet c "encryption"
-
-configGet :: RemoteConfig -> String -> String
-configGet c key = fromMaybe missing $ M.lookup key c
-	where
-		missing = error $ "missing " ++ key ++ " in remote config"
+pass to n s a = to n s $ \h -> a =<< L.hGetContents h
 
 hmacWithCipher :: Cipher -> String -> String
 hmacWithCipher c = hmacWithCipher' (cipherHmac c) 
diff --git a/Git.hs b/Git.hs
index 4278e9fcf2..7d64205634 100644
--- a/Git.hs
+++ b/Git.hs
@@ -3,7 +3,7 @@
  - This is written to be completely independant of git-annex and should be
  - suitable for other uses.
  -
- - Copyright 2010, 2011 Joey Hess <joey@kitenet.net>
+ - Copyright 2010-2012 Joey Hess <joey@kitenet.net>
  -
  - Licensed under the GNU GPL version 3 or higher.
  -}
@@ -17,19 +17,17 @@ module Git (
 	repoIsUrl,
 	repoIsSsh,
 	repoIsHttp,
+	repoIsLocal,
 	repoIsLocalBare,
 	repoDescribe,
 	repoLocation,
-	workTree,
-	gitDir,
-	configTrue,
+	repoPath,
+	localGitDir,
 	attributes,
 	hookPath,
 	assertLocal,
 ) where
 
-import qualified Data.Map as M
-import Data.Char
 import Network.URI (uriPath, uriScheme, unEscapeString)
 import System.Posix.Files
 
@@ -41,15 +39,34 @@ import Utility.FileMode
 repoDescribe :: Repo -> String
 repoDescribe Repo { remoteName = Just name } = name
 repoDescribe Repo { location = Url url } = show url
-repoDescribe Repo { location = Dir dir } = dir
+repoDescribe Repo { location = Local { worktree = Just dir } } = dir
+repoDescribe Repo { location = Local { gitdir = dir } } = dir
+repoDescribe Repo { location = LocalUnknown dir } = dir
 repoDescribe Repo { location = Unknown } = "UNKNOWN"
 
 {- Location of the repo, either as a path or url. -}
 repoLocation :: Repo -> String
 repoLocation Repo { location = Url url } = show url
-repoLocation Repo { location = Dir dir } = dir
+repoLocation Repo { location = Local { worktree = Just dir } } = dir
+repoLocation Repo { location = Local { gitdir = dir } } = dir
+repoLocation Repo { location = LocalUnknown dir } = dir
 repoLocation Repo { location = Unknown } = undefined
 
+{- Path to a repository. For non-bare, this is the worktree, for bare, 
+ - it's the gitdir, and for URL repositories, is the path on the remote
+ - host. -}
+repoPath :: Repo -> FilePath
+repoPath Repo { location = Url u } = unEscapeString $ uriPath u
+repoPath Repo { location = Local { worktree = Just d } } = d
+repoPath Repo { location = Local { gitdir = d } } = d
+repoPath Repo { location = LocalUnknown dir } = dir
+repoPath Repo { location = Unknown } = undefined
+
+{- Path to a local repository's .git directory. -}
+localGitDir :: Repo -> FilePath
+localGitDir Repo { location = Local { gitdir = d } } = d
+localGitDir _ = undefined
+
 {- Some code needs to vary between URL and normal repos,
  - or bare and non-bare, these functions help with that. -}
 repoIsUrl :: Repo -> Bool
@@ -74,11 +91,12 @@ repoIsHttp Repo { location = Url url }
 	| otherwise = False
 repoIsHttp _ = False
 
-configAvail ::Repo -> Bool
-configAvail Repo { config = c } = c /= M.empty
+repoIsLocal :: Repo -> Bool
+repoIsLocal Repo { location = Local { } } = True
+repoIsLocal _ = False
 
 repoIsLocalBare :: Repo -> Bool
-repoIsLocalBare r@(Repo { location = Dir _ }) = configAvail r && configBare r
+repoIsLocalBare Repo { location = Local { worktree = Nothing } } = True
 repoIsLocalBare _ = False
 
 assertLocal :: Repo -> a -> a
@@ -90,49 +108,18 @@ assertLocal repo action
 		]
 	| otherwise = action
 
-configBare :: Repo -> Bool
-configBare repo = maybe unknown (fromMaybe False . configTrue) $
-	M.lookup "core.bare" $ config repo
-	where
-		unknown = error $ "it is not known if git repo " ++
-			repoDescribe repo ++
-			" is a bare repository; config not read"
-
 {- Path to a repository's gitattributes file. -}
 attributes :: Repo -> FilePath
 attributes repo
-	| configBare repo = workTree repo ++ "/info/.gitattributes"
-	| otherwise = workTree repo ++ "/.gitattributes"
-
-{- Path to a repository's .git directory. -}
-gitDir :: Repo -> FilePath
-gitDir repo
-	| configBare repo = workTree repo
-	| otherwise = workTree repo </> ".git"
+	| repoIsLocalBare repo = repoPath repo ++ "/info/.gitattributes"
+	| otherwise = repoPath repo ++ "/.gitattributes"
 
 {- Path to a given hook script in a repository, only if the hook exists
  - and is executable. -}
 hookPath :: String -> Repo -> IO (Maybe FilePath)
 hookPath script repo = do
-	let hook = gitDir repo </> "hooks" </> script
+	let hook = localGitDir repo </> "hooks" </> script
 	ifM (catchBoolIO $ isexecutable hook)
 		( return $ Just hook , return Nothing )
 	where
 		isexecutable f = isExecutable . fileMode <$> getFileStatus f
-
-{- Path to a repository's --work-tree, that is, its top.
- -
- - Note that for URL repositories, this is the path on the remote host. -}
-workTree :: Repo -> FilePath
-workTree Repo { location = Url u } = unEscapeString $ uriPath u
-workTree Repo { location = Dir d } = d
-workTree Repo { location = Unknown } = undefined
-
-{- Checks if a string from git config is a true value. -}
-configTrue :: String -> Maybe Bool
-configTrue s
-	| s' == "true" = Just True
-	| s' == "false" = Just False
-	| otherwise = Nothing
-	where
-		s' = map toLower s
diff --git a/Git/AutoCorrect.hs b/Git/AutoCorrect.hs
index a18bf56197..a1ef14779b 100644
--- a/Git/AutoCorrect.hs
+++ b/Git/AutoCorrect.hs
@@ -34,7 +34,7 @@ fuzzymatches :: String -> (c -> String) -> [c] -> [c]
 fuzzymatches input showchoice choices = fst $ unzip $
 	sortBy comparecost $ filter similarEnough $ zip choices costs
         where
-                distance v = restrictedDamerauLevenshteinDistance gitEditCosts v input
+                distance = restrictedDamerauLevenshteinDistance gitEditCosts input
                 costs = map (distance . showchoice) choices
                 comparecost a b = compare (snd a) (snd b)
                 similarEnough (_, cst) = cst < similarityFloor
diff --git a/Git/Command.hs b/Git/Command.hs
index 50d4455fe7..35f0838ba9 100644
--- a/Git/Command.hs
+++ b/Git/Command.hs
@@ -1,6 +1,6 @@
 {- running git commands
  -
- - Copyright 2010, 2011 Joey Hess <joey@kitenet.net>
+ - Copyright 2010-2012 Joey Hess <joey@kitenet.net>
  -
  - Licensed under the GNU GPL version 3 or higher.
  -}
@@ -18,11 +18,12 @@ import Git.Types
 
 {- Constructs a git command line operating on the specified repo. -}
 gitCommandLine :: [CommandParam] -> Repo -> [CommandParam]
-gitCommandLine params repo@(Repo { location = Dir _ } ) =
-	-- force use of specified repo via --git-dir and --work-tree
-	[ Param ("--git-dir=" ++ gitDir repo)
-	, Param ("--work-tree=" ++ workTree repo)
-	] ++ params
+gitCommandLine params Repo { location = l@(Local _ _ ) } = setdir : settree ++ params
+	where
+		setdir = Param $ "--git-dir=" ++ gitdir l
+		settree = case worktree l of
+			Nothing -> []
+			Just t -> [Param $ "--work-tree=" ++ t]
 gitCommandLine _ repo = assertLocal repo $ error "internal"
 
 {- Runs git in the specified repo. -}
@@ -79,5 +80,5 @@ pipeNullSplit params repo =
 reap :: IO ()
 reap = do
 	-- throws an exception when there are no child processes
-	r <- catchDefaultIO (getAnyProcessStatus False True) Nothing
-	maybe (return ()) (const reap) r
+	catchDefaultIO (getAnyProcessStatus False True) Nothing
+		>>= maybe noop (const reap)
diff --git a/Git/Config.hs b/Git/Config.hs
index 8190a62ad3..dab1cdf5ea 100644
--- a/Git/Config.hs
+++ b/Git/Config.hs
@@ -1,15 +1,14 @@
 {- git repository configuration handling
  -
- - Copyright 2010,2011 Joey Hess <joey@kitenet.net>
+ - Copyright 2010-2012 Joey Hess <joey@kitenet.net>
  -
  - Licensed under the GNU GPL version 3 or higher.
  -}
 
 module Git.Config where
 
-import System.Posix.Directory
-import Control.Exception (bracket_)
 import qualified Data.Map as M
+import Data.Char
 
 import Common
 import Git
@@ -20,23 +19,37 @@ import qualified Git.Construct
 get :: String -> String -> Repo -> String
 get key defaultValue repo = M.findWithDefault defaultValue key (config repo)
 
+{- Returns a list with each line of a multiline config setting. -}
+getList :: String -> Repo -> [String]
+getList key repo = M.findWithDefault [] key (fullconfig repo)
+
 {- Returns a single git config setting, if set. -}
 getMaybe :: String -> Repo -> Maybe String
 getMaybe key repo = M.lookup key (config repo)
 
-{- Runs git config and populates a repo with its config. -}
+{- Runs git config and populates a repo with its config.
+ - Avoids re-reading config when run repeatedly. -}
 read :: Repo -> IO Repo
-read repo@(Repo { location = Dir d }) = bracketcd d $
-	{- Cannot use pipeRead because it relies on the config having
-	   been already read. Instead, chdir to the repo. -}
-	pOpen ReadFromPipe "git" ["config", "--null", "--list"] $ hRead repo
+read repo@(Repo { config = c })
+	| c == M.empty = read' repo
+	| otherwise = return repo
+
+{- Reads config even if it was read before. -}
+reRead :: Repo -> IO Repo
+reRead = read'
+
+{- Cannot use pipeRead because it relies on the config having been already
+ - read. Instead, chdir to the repo.
+ -}
+read' :: Repo -> IO Repo
+read' repo = go repo
 	where
-		bracketcd to a = bracketcd' to a =<< getCurrentDirectory
-		bracketcd' to a cwd 
-			| dirContains to cwd = a
-			| otherwise = bracket_ (changeWorkingDirectory to) (changeWorkingDirectory cwd) a
-read r = assertLocal r $
-	error $ "internal error; trying to read config of " ++ show r
+		go Repo { location = Local { gitdir = d } } = git_config d
+		go Repo { location = LocalUnknown d } = git_config d
+		go _ = assertLocal repo $ error "internal"
+		git_config d = bracketCd d $
+			pOpen ReadFromPipe "git" ["config", "--null", "--list"] $
+				hRead repo
 
 {- Reads git config from a handle and populates a repo with it. -}
 hRead :: Repo -> Handle -> IO Repo
@@ -44,19 +57,37 @@ hRead repo h = do
 	val <- hGetContentsStrict h
 	store val repo
 
-{- Stores a git config into a repo, returning the new version of the repo.
- - The git config may be multiple lines, or a single line. Config settings
- - can be updated inrementally. -}
+{- Stores a git config into a Repo, returning the new version of the Repo.
+ - The git config may be multiple lines, or a single line.
+ - Config settings can be updated incrementally.
+ -}
 store :: String -> Repo -> IO Repo
 store s repo = do
 	let c = parse s
-	let repo' = repo
+	let repo' = updateLocation $ repo
 		{ config = (M.map Prelude.head c) `M.union` config repo
 		, fullconfig = M.unionWith (++) c (fullconfig repo)
 		}
 	rs <- Git.Construct.fromRemotes repo'
 	return $ repo' { remotes = rs }
 
+{- Updates the location of a repo, based on its configuration.
+ -
+ - Git.Construct makes LocalUknown repos, of which only a directory is
+ - known. Once the config is read, this can be fixed up to a Local repo, 
+ - based on the core.bare and core.worktree settings.
+ -}
+updateLocation :: Repo -> Repo
+updateLocation r@(Repo { location = LocalUnknown d })
+	| isBare r = newloc $ Local d Nothing
+	| otherwise = newloc $ Local (d </> ".git") (Just d)
+	where
+		newloc l = r { location = getworktree l }
+		getworktree l = case workTree r of
+			Nothing -> l
+			wt -> l { worktree = wt }
+updateLocation r = r
+
 {- Parses git config --list or git config --null --list output into a
  - config map. -}
 parse :: String -> M.Map String [String]
@@ -70,3 +101,18 @@ parse s
 		ls = lines s
 		sep c = M.fromListWith (++) . map (\(k,v) -> (k, [v])) .
 			map (separate (== c))
+
+{- Checks if a string from git config is a true value. -}
+isTrue :: String -> Maybe Bool
+isTrue s
+	| s' == "true" = Just True
+	| s' == "false" = Just False
+	| otherwise = Nothing
+	where
+		s' = map toLower s
+
+isBare :: Repo -> Bool
+isBare r = fromMaybe False $ isTrue =<< getMaybe "core.bare" r
+
+workTree :: Repo -> Maybe FilePath
+workTree = getMaybe "core.worktree"
diff --git a/Git/Construct.hs b/Git/Construct.hs
index 49905f818b..b809d7318a 100644
--- a/Git/Construct.hs
+++ b/Git/Construct.hs
@@ -1,12 +1,11 @@
 {- Construction of Git Repo objects
  -
- - Copyright 2010,2011 Joey Hess <joey@kitenet.net>
+ - Copyright 2010-2012 Joey Hess <joey@kitenet.net>
  -
  - Licensed under the GNU GPL version 3 or higher.
  -}
 
 module Git.Construct (
-	fromCurrent,
 	fromCwd,
 	fromAbsPath,
 	fromPath,
@@ -21,8 +20,6 @@ module Git.Construct (
 ) where
 
 import System.Posix.User
-import System.Posix.Env (getEnv, unsetEnv)
-import System.Posix.Directory (changeWorkingDirectory)
 import qualified Data.Map as M hiding (map, split)
 import Network.URI
 
@@ -31,34 +28,12 @@ import Git.Types
 import Git
 import qualified Git.Url as Url
 
-{- Finds the current git repository.
- -
- - GIT_DIR can override the location of the .git directory.
- -
- - When GIT_WORK_TREE is set, chdir to it, so that anything using
- - this repository runs in the right location. However, this chdir is
- - done after determining GIT_DIR; git does not let GIT_WORK_TREE
- - influence the git directory.
- -
- - Both environment variables are unset, to avoid confusing other git
- - commands that also look at them. This would particularly be a problem
- - when GIT_DIR is relative and we chdir for GIT_WORK_TREE. Instead,
- - the Git module passes --work-tree and --git-dir to git commands it runs.
- -}
-fromCurrent :: IO Repo
-fromCurrent = do
-	r <- maybe fromCwd fromPath =<< getEnv "GIT_DIR"
-	maybe (return ()) changeWorkingDirectory =<< getEnv "GIT_WORK_TREE"
-	unsetEnv "GIT_DIR"
-	unsetEnv "GIT_WORK_TREE"
-	return r
-
 {- Finds the git repository used for the Cwd, which may be in a parent
  - directory. -}
 fromCwd :: IO Repo
 fromCwd = getCurrentDirectory >>= seekUp isRepoTop >>= maybe norepo makerepo
 	where
-		makerepo = newFrom . Dir
+		makerepo = newFrom . LocalUnknown
 		norepo = error "Not in a git repository."
 
 {- Local Repo constructor, accepts a relative or absolute path. -}
@@ -74,7 +49,7 @@ fromAbsPath dir
 	| otherwise =
 		error $ "internal error, " ++ dir ++ " is not absolute"
 	where
-		ret = newFrom . Dir
+		ret = newFrom . LocalUnknown
  		{- Git always looks for "dir.git" in preference to
 		 - to "dir", even if dir ends in a "/". -}
 		canondir = dropTrailingPathSeparator dir
@@ -122,7 +97,7 @@ localToUrl reference r
 		absurl =
 			Url.scheme reference ++ "//" ++
 			Url.authority reference ++
-			workTree r
+			repoPath r
 
 {- Calculates a list of a repo's configured remotes, by parsing its config. -}
 fromRemotes :: Repo -> IO [Repo]
@@ -191,7 +166,7 @@ fromRemoteLocation s repo = gen $ calcloc s
 fromRemotePath :: FilePath -> Repo -> IO Repo
 fromRemotePath dir repo = do
 	dir' <- expandTilde dir
-	fromAbsPath $ workTree repo </> dir'
+	fromAbsPath $ repoPath repo </> dir'
 
 {- Git remotes can have a directory that is specified relative
  - to the user's home directory, or that contains tilde expansions.
@@ -251,3 +226,5 @@ newFrom l = return Repo
 	, remotes = []
 	, remoteName = Nothing
 	}
+
+
diff --git a/Git/CurrentRepo.hs b/Git/CurrentRepo.hs
new file mode 100644
index 0000000000..de11ce217c
--- /dev/null
+++ b/Git/CurrentRepo.hs
@@ -0,0 +1,58 @@
+{- The current git repository.
+ -
+ - Copyright 2012 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Git.CurrentRepo where
+
+import System.Posix.Directory (changeWorkingDirectory)
+import System.Posix.Env (getEnv, unsetEnv)
+
+import Common
+import Git.Types
+import Git.Construct
+import qualified Git.Config
+
+{- Gets the current git repository.
+ -
+ - Honors GIT_DIR and GIT_WORK_TREE.
+ - Both environment variables are unset, to avoid confusing other git
+ - commands that also look at them. Instead, the Git module passes
+ - --work-tree and --git-dir to git commands it runs.
+ -
+ - When GIT_WORK_TREE or core.worktree are set, changes the working
+ - directory if necessary to ensure it is within the repository's work
+ - tree. While not needed for git commands, this is useful for anything
+ - else that looks for files in the worktree.
+ -}
+get :: IO Repo
+get = do
+	gd <- pathenv "GIT_DIR"
+	r <- configure gd =<< maybe fromCwd fromPath gd
+	wt <- maybe (Git.Config.workTree r) Just <$> pathenv "GIT_WORK_TREE"
+	case wt of
+		Nothing -> return r
+		Just d -> do
+			cwd <- getCurrentDirectory
+			unless (d `dirContains` cwd) $
+				changeWorkingDirectory d
+			return $ addworktree wt r
+	where
+		pathenv s = do
+			v <- getEnv s
+			when (isJust v) $
+				unsetEnv s
+			case v of
+				Nothing -> return Nothing
+				Just d -> Just <$> absPath d
+		configure Nothing r = Git.Config.read r
+		configure (Just d) r = do
+			r' <- Git.Config.read r
+			-- Let GIT_DIR override the default gitdir.
+			return $ changelocation r' $
+				Local { gitdir = d, worktree = worktree (location r') }
+		addworktree w r = changelocation r $
+			Local { gitdir = gitdir (location r), worktree = w }
+		changelocation r l = r { location = l }
diff --git a/Git/LsFiles.hs b/Git/LsFiles.hs
index 201d76d1d4..06d4b9f44f 100644
--- a/Git/LsFiles.hs
+++ b/Git/LsFiles.hs
@@ -69,7 +69,7 @@ typeChanged' ps l repo = do
 	fs <- pipeNullSplit (prefix ++ ps ++ suffix) repo
 	-- git diff returns filenames relative to the top of the git repo;
 	-- convert to filenames relative to the cwd, like git ls-files.
-	let top = workTree repo
+	let top = repoPath repo
 	cwd <- getCurrentDirectory
 	return $ map (\f -> relPathDirToFile cwd $ top </> f) fs
 	where
diff --git a/Git/SharedRepository.hs b/Git/SharedRepository.hs
new file mode 100644
index 0000000000..f3efa8fde9
--- /dev/null
+++ b/Git/SharedRepository.hs
@@ -0,0 +1,27 @@
+{- git core.sharedRepository handling
+ -
+ - Copyright 2012 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Git.SharedRepository where
+
+import Data.Char
+
+import Common
+import Git
+import qualified Git.Config
+
+data SharedRepository = UnShared | GroupShared | AllShared | UmaskShared Int
+
+getSharedRepository :: Repo -> SharedRepository
+getSharedRepository r =
+	case map toLower $ Git.Config.get "core.sharedrepository" "" r of
+		"1" -> GroupShared
+		"group" -> GroupShared
+		"true" -> GroupShared
+		"all" -> AllShared
+		"world" -> AllShared
+		"everybody" -> AllShared
+		v -> maybe UnShared UmaskShared (readish v)
diff --git a/Git/Types.hs b/Git/Types.hs
index 6063ad213f..deb14ebd48 100644
--- a/Git/Types.hs
+++ b/Git/Types.hs
@@ -1,6 +1,6 @@
 {- git data types
  -
- - Copyright 2010,2011 Joey Hess <joey@kitenet.net>
+ - Copyright 2010-2012 Joey Hess <joey@kitenet.net>
  -
  - Licensed under the GNU GPL version 3 or higher.
  -}
@@ -10,9 +10,21 @@ module Git.Types where
 import Network.URI
 import qualified Data.Map as M
 
-{- There are two types of repositories; those on local disk and those
- - accessed via an URL. -}
-data RepoLocation = Dir FilePath | Url URI | Unknown
+{- Support repositories on local disk, and repositories accessed via an URL.
+ -
+ - Repos on local disk have a git directory, and unless bare, a worktree.
+ -
+ - A local repo may not have had its config read yet, in which case all
+ - that's known about it is its path.
+ -
+ - Finally, an Unknown repository may be known to exist, but nothing
+ - else known about it.
+ -}
+data RepoLocation
+	= Local { gitdir :: FilePath, worktree :: Maybe FilePath }
+	| LocalUnknown FilePath
+	| Url URI
+	| Unknown
 	deriving (Show, Eq)
 
 data Repo = Repo {
diff --git a/Git/UnionMerge.hs b/Git/UnionMerge.hs
index 90bbf5c4cc..d68bb61ab1 100644
--- a/Git/UnionMerge.hs
+++ b/Git/UnionMerge.hs
@@ -97,7 +97,7 @@ calc_merge :: CatFileHandle -> [String] -> Repo -> Streamer
 calc_merge ch differ repo streamer = gendiff >>= go
 	where
 		gendiff = pipeNullSplit (map Param differ) repo
-		go [] = return ()
+		go [] = noop
 		go (info:file:rest) = mergeFile info file ch repo >>=
 			maybe (go rest) (\l -> streamer l >> go rest)
 		go (_:[]) = error "calc_merge parse error"
diff --git a/GitAnnex.hs b/GitAnnex.hs
index 5caa93499e..a4c5eb8490 100644
--- a/GitAnnex.hs
+++ b/GitAnnex.hs
@@ -11,7 +11,7 @@ import System.Console.GetOpt
 
 import Common.Annex
 import qualified Git.Config
-import qualified Git.Construct
+import qualified Git.CurrentRepo
 import CmdLine
 import Command
 import Types.TrustLevel
@@ -37,6 +37,7 @@ import qualified Command.InitRemote
 import qualified Command.Fsck
 import qualified Command.Unused
 import qualified Command.DropUnused
+import qualified Command.AddUnused
 import qualified Command.Unlock
 import qualified Command.Lock
 import qualified Command.PreCommit
@@ -53,6 +54,7 @@ import qualified Command.Semitrust
 import qualified Command.Dead
 import qualified Command.Sync
 import qualified Command.AddUrl
+import qualified Command.Import
 import qualified Command.Map
 import qualified Command.Upgrade
 import qualified Command.Version
@@ -69,6 +71,7 @@ cmds = concat
 	, Command.Lock.def
 	, Command.Sync.def
 	, Command.AddUrl.def
+	, Command.Import.def
 	, Command.Init.def
 	, Command.Describe.def
 	, Command.InitRemote.def
@@ -87,6 +90,7 @@ cmds = concat
 	, Command.Fsck.def
 	, Command.Unused.def
 	, Command.DropUnused.def
+	, Command.AddUnused.def
 	, Command.Find.def
 	, Command.Whereis.def
 	, Command.Log.def
@@ -133,4 +137,4 @@ header :: String
 header = "Usage: git-annex command [option ..]"
 
 run :: [String] -> IO ()
-run args = dispatch True args cmds options header Git.Construct.fromCurrent
+run args = dispatch True args cmds options header Git.CurrentRepo.get
diff --git a/GitAnnexShell.hs b/GitAnnexShell.hs
index 0cf81f0e21..6633037138 100644
--- a/GitAnnexShell.hs
+++ b/GitAnnexShell.hs
@@ -52,7 +52,7 @@ options = Option.common ++
 	where
 		checkuuid expected = getUUID >>= check
 			where
-				check u | u == toUUID expected = return ()
+				check u | u == toUUID expected = noop
 				check NoUUID = unexpected "uninitialized repository"
 				check u = unexpected $ "UUID " ++ fromUUID u
 				unexpected s = error $
@@ -107,7 +107,7 @@ checkNotLimited = checkEnv "GIT_ANNEX_SHELL_LIMITED"
 
 checkNotReadOnly :: String -> IO ()
 checkNotReadOnly cmd
-	| cmd `elem` map cmdname cmds_readonly = return ()
+	| cmd `elem` map cmdname cmds_readonly = noop
 	| otherwise = checkEnv "GIT_ANNEX_SHELL_READONLY"
 
 checkEnv :: String -> IO ()
diff --git a/Init.hs b/Init.hs
index 9f1988a394..bddcc696e0 100644
--- a/Init.hs
+++ b/Init.hs
@@ -29,7 +29,9 @@ initialize mdescription = do
 	maybe (recordUUID u) (describeUUID u) mdescription
 
 uninitialize :: Annex ()
-uninitialize = gitPreCommitHookUnWrite
+uninitialize = do
+	gitPreCommitHookUnWrite
+	removeRepoUUID
 
 {- Will automatically initialize if there is already a git-annex
    branch from somewhere. Otherwise, require a manual init
@@ -70,7 +72,7 @@ unlessBare :: Annex () -> Annex ()
 unlessBare = unlessM $ fromRepo Git.repoIsLocalBare
 
 preCommitHook :: Annex FilePath
-preCommitHook = (</>) <$> fromRepo Git.gitDir <*> pure "hooks/pre-commit"
+preCommitHook = (</>) <$> fromRepo Git.localGitDir <*> pure "hooks/pre-commit"
 
 preCommitScript :: String
 preCommitScript = 
diff --git a/Locations.hs b/Locations.hs
index d263f3d2ac..db456388a6 100644
--- a/Locations.hs
+++ b/Locations.hs
@@ -85,28 +85,24 @@ gitAnnexLocation key r
 	| Git.repoIsLocalBare r =
 		{- Bare repositories default to hashDirLower for new
 		 - content, as it's more portable. -}
-		check (map inrepo $ annexLocations key)
+		check $ map inrepo $ annexLocations key
 	| otherwise =
 		{- Non-bare repositories only use hashDirMixed, so
 		 - don't need to do any work to check if the file is
 		 - present. -}
-		return $ inrepo ".git" </> annexLocation key hashDirMixed
+		return $ inrepo $ annexLocation key hashDirMixed
 	where
-		inrepo d = Git.workTree r </> d
+		inrepo d = Git.localGitDir r </> d
 		check locs@(l:_) = fromMaybe l <$> firstM doesFileExist locs
 		check [] = error "internal"
 
 {- The annex directory of a repository. -}
 gitAnnexDir :: Git.Repo -> FilePath
-gitAnnexDir r
-	| Git.repoIsLocalBare r = addTrailingPathSeparator $ Git.workTree r </> annexDir
-	| otherwise = addTrailingPathSeparator $ Git.workTree r </> ".git" </> annexDir
+gitAnnexDir r = addTrailingPathSeparator $ Git.localGitDir r </> annexDir
 
 {- The part of the annex directory where file contents are stored. -}
 gitAnnexObjectDir :: Git.Repo -> FilePath
-gitAnnexObjectDir r
-	| Git.repoIsLocalBare r = addTrailingPathSeparator $ Git.workTree r </> objectDir
-	| otherwise = addTrailingPathSeparator $ Git.workTree r </> ".git" </> objectDir
+gitAnnexObjectDir r = addTrailingPathSeparator $ Git.localGitDir r </> objectDir
 
 {- .git/annex/tmp/ is used for temp files -}
 gitAnnexTmpDir :: Git.Repo -> FilePath
@@ -124,7 +120,7 @@ gitAnnexBadDir r = addTrailingPathSeparator $ gitAnnexDir r </> "bad"
 gitAnnexBadLocation :: Key -> Git.Repo -> FilePath
 gitAnnexBadLocation key r = gitAnnexBadDir r </> keyFile key
 
-{- .git/annex/*unused is used to number possibly unused keys -}
+{- .git/annex/foounused is used to number possibly unused keys -}
 gitAnnexUnusedLog :: FilePath -> Git.Repo -> FilePath
 gitAnnexUnusedLog prefix r = gitAnnexDir r </> (prefix ++ "unused")
 
@@ -159,7 +155,9 @@ gitAnnexRemotesDir r = addTrailingPathSeparator $ gitAnnexDir r </> "remotes"
 
 {- Checks a symlink target to see if it appears to point to annexed content. -}
 isLinkToAnnex :: FilePath -> Bool
-isLinkToAnnex s = ("/.git/" ++ objectDir) `isInfixOf` s
+isLinkToAnnex s = ("/" ++ d) `isInfixOf` s || d `isPrefixOf` s
+	where
+		d = ".git" </> objectDir
 
 {- Converts a key into a filename fragment without any directory.
  -
diff --git a/Logs/Location.hs b/Logs/Location.hs
index b6d59b928c..e27ece5d46 100644
--- a/Logs/Location.hs
+++ b/Logs/Location.hs
@@ -30,7 +30,7 @@ import Logs.Presence
 {- Log a change in the presence of a key's value in a repository. -}
 logChange :: Key -> UUID -> LogStatus -> Annex ()
 logChange key (UUID u) s = addLog (logFile key) =<< logNow s u
-logChange _ NoUUID _ = return ()
+logChange _ NoUUID _ = noop
 
 {- Returns a list of repository UUIDs that, according to the log, have
  - the value of a key.
diff --git a/Logs/Remote.hs b/Logs/Remote.hs
index 5c9d67df03..b75573a411 100644
--- a/Logs/Remote.hs
+++ b/Logs/Remote.hs
@@ -36,7 +36,7 @@ configSet u c = do
 
 {- Map of remotes by uuid containing key/value config maps. -}
 readRemoteLog :: Annex (M.Map UUID RemoteConfig)
-readRemoteLog = (simpleMap . parseLog parseConfig) <$> Annex.Branch.get remoteLog
+readRemoteLog = simpleMap . parseLog parseConfig <$> Annex.Branch.get remoteLog
 
 parseConfig :: String -> Maybe RemoteConfig
 parseConfig = Just . keyValToConfig . words
@@ -59,7 +59,7 @@ configToKeyVal m = map toword $ sort $ M.toList m
 		toword (k, v) = k ++ "=" ++ configEscape v
 
 configEscape :: String -> String
-configEscape = (>>= escape)
+configEscape = concatMap escape
 	where
 		escape c
 			| isSpace c || c `elem` "&" = "&" ++ show (ord c) ++ ";"
diff --git a/Logs/UUID.hs b/Logs/UUID.hs
index 18cbee61e4..d825e11273 100644
--- a/Logs/UUID.hs
+++ b/Logs/UUID.hs
@@ -73,7 +73,7 @@ recordUUID u = go . M.lookup u =<< uuidMap
 	where
 		go (Just "") = set
 		go Nothing = set
-		go _ = return ()
+		go _ = noop
 		set = describeUUID u ""
 
 {- Read the uuidLog into a simple Map.
diff --git a/Logs/UUIDBased.hs b/Logs/UUIDBased.hs
index b09d93f903..847d499237 100644
--- a/Logs/UUIDBased.hs
+++ b/Logs/UUIDBased.hs
@@ -83,7 +83,7 @@ changeLog t u v = M.insert u $ LogEntry (Date t) v
 {- Only add an LogEntry if it's newer (or at least as new as) than any
  - existing LogEntry for a UUID. -}
 addLog :: UUID -> LogEntry a -> Log a -> Log a
-addLog = M.insertWith best
+addLog = M.insertWith' best
 
 {- Converts a Log into a simple Map without the timestamp information.
  - This is a one-way trip, but useful for code that never needs to change
diff --git a/Logs/Unused.hs b/Logs/Unused.hs
new file mode 100644
index 0000000000..7d240cfe33
--- /dev/null
+++ b/Logs/Unused.hs
@@ -0,0 +1,91 @@
+{- git-annex unused log file
+ -
+ - Copyright 2010,2012 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Logs.Unused (
+	UnusedMap,
+	UnusedMaps(..),
+	writeUnusedLog,
+	readUnusedLog,
+	withUnusedMaps,
+	startUnused,
+) where
+
+import qualified Data.Map as M
+
+import Common.Annex
+import Command
+import Types.Key
+import Utility.TempFile
+
+writeUnusedLog :: FilePath -> [(Int, Key)] -> Annex ()
+writeUnusedLog prefix l = do
+	logfile <- fromRepo $ gitAnnexUnusedLog prefix
+	liftIO $ viaTmp writeFile logfile $
+		unlines $ map (\(n, k) -> show n ++ " " ++ show k) l
+
+readUnusedLog :: FilePath -> Annex UnusedMap
+readUnusedLog prefix = do
+	f <- fromRepo $ gitAnnexUnusedLog prefix
+	ifM (liftIO $ doesFileExist f)
+		( M.fromList . catMaybes . map parse . lines
+			<$> liftIO (readFile f)
+		, return M.empty
+		)
+	where
+		parse line =
+			case (readish tag, readKey rest) of
+				(Just num, Just key) -> Just (num, key)
+				_ -> Nothing
+			where
+				(tag, rest) = separate (== ' ') line
+
+type UnusedMap = M.Map Int Key
+
+data UnusedMaps = UnusedMaps
+	{ unusedMap :: UnusedMap
+	, unusedBadMap :: UnusedMap
+	, unusedTmpMap :: UnusedMap
+	}
+
+{- Read unused logs once, and pass the maps to each start action. -}
+withUnusedMaps :: (UnusedMaps -> Int -> CommandStart) -> CommandSeek
+withUnusedMaps a params = do
+	unused <- readUnusedLog ""
+	unusedbad <- readUnusedLog "bad"
+	unusedtmp <- readUnusedLog "tmp"
+	return $ map (a $ UnusedMaps unused unusedbad unusedtmp) $
+		concatMap unusedSpec params
+
+unusedSpec :: String -> [Int]
+unusedSpec spec
+	| "-" `isInfixOf` spec = range $ separate (== '-') spec
+	| otherwise = catMaybes [readish spec]
+	where
+		range (a, b) = case (readish a, readish b) of
+			(Just x, Just y) -> [x..y]
+			_ -> []
+
+{- Start action for unused content. Finds the number in the maps, and
+ - calls either of 3 actions, depending on the type of unused file. -}
+startUnused :: String
+	-> (Key -> CommandPerform)
+	-> (Key -> CommandPerform) 
+	-> (Key -> CommandPerform)
+	-> UnusedMaps -> Int -> CommandStart
+startUnused message unused badunused tmpunused maps n = search
+	[ (unusedMap maps, unused)
+	, (unusedBadMap maps, badunused)
+	, (unusedTmpMap maps, tmpunused)
+	]
+	where
+		search [] = stop
+		search ((m, a):rest) =
+			case M.lookup n m of
+				Nothing -> search rest
+				Just key -> do
+					showStart message (show n)
+					next $ a key
diff --git a/Makefile b/Makefile
index b935140576..94dc05a819 100644
--- a/Makefile
+++ b/Makefile
@@ -1,6 +1,6 @@
 PREFIX=/usr
 IGNORE=-ignore-package monads-fd
-BASEFLAGS=-Wall $(IGNORE) -outputdir tmp -IUtility
+BASEFLAGS=-Wall $(IGNORE) -outputdir tmp -IUtility -DWITH_S3
 GHCFLAGS=-O2 $(BASEFLAGS)
 
 ifdef PROFILE
@@ -12,7 +12,7 @@ GHCMAKE=ghc $(GHCFLAGS) --make
 bins=git-annex
 mans=git-annex.1 git-annex-shell.1
 sources=Build/SysConfig.hs Utility/Touch.hs
-clibs=Utility/diskfree.o
+clibs=Utility/libdiskfree.o
 
 all=$(bins) $(mans) docs
 
diff --git a/Messages.hs b/Messages.hs
index 73a7d976fd..96bf3ae4b5 100644
--- a/Messages.hs
+++ b/Messages.hs
@@ -13,6 +13,9 @@ module Messages (
 	metered,
 	MeterUpdate,
 	showSideAction,
+	doSideAction,
+	doQuietSideAction,
+	showStoringStateAction,
 	showOutput,
 	showLongNote,
 	showEndOk,
@@ -37,6 +40,7 @@ import Data.Quantity
 
 import Common
 import Types
+import Types.Messages
 import Types.Key
 import qualified Annex
 import qualified Messages.JSON as JSON
@@ -61,9 +65,9 @@ showProgress = handle q $
  - The action is passed a callback to use to update the meter. -}
 type MeterUpdate = Integer -> IO ()
 metered :: Key -> (MeterUpdate -> Annex a) -> Annex a
-metered key a = Annex.getState Annex.output >>= go (keySize key)
+metered key a = withOutputType $ go (keySize key)
 	where
-		go (Just size) Annex.NormalOutput = do
+		go (Just size) NormalOutput = do
 			progress <- liftIO $ newProgress "" size
 			meter <- liftIO $ newMeter progress "B" 25 (renderNums binaryOpts 1)
 			showOutput
@@ -72,12 +76,38 @@ metered key a = Annex.getState Annex.output >>= go (keySize key)
 				incrP progress n
 				displayMeter stdout meter
 			liftIO $ clearMeter stdout meter
-			return r	
-                go _ _ = a (const $ return ())
+			return r
+                go _ _ = a (const noop)
 
 showSideAction :: String -> Annex ()
-showSideAction s = handle q $
-	putStrLn $ "(" ++ s ++ "...)"
+showSideAction m = Annex.getState Annex.output >>= go
+	where
+		go (MessageState v StartBlock) = do
+			p
+	 		Annex.changeState $ \s -> s { Annex.output = MessageState v InBlock }
+		go (MessageState _ InBlock) = return ()
+		go _ = p
+		p = handle q $ putStrLn $ "(" ++ m ++ "...)"
+			
+showStoringStateAction :: Annex ()
+showStoringStateAction = showSideAction "Recording state in git"
+
+{- Performs an action, supressing showSideAction messages. -}
+doQuietSideAction :: Annex a -> Annex a
+doQuietSideAction = doSideAction' InBlock
+
+{- Performs an action, that may call showSideAction multiple times.
+ - Only the first will be displayed. -}
+doSideAction :: Annex a -> Annex a
+doSideAction = doSideAction' StartBlock
+
+doSideAction' :: SideActionBlock -> Annex a -> Annex a
+doSideAction' b a = do
+	o <- Annex.getState Annex.output
+	set $ o { sideActionBlock = b }
+	set o `after` a
+	where
+		set o = Annex.changeState $ \s -> s {  Annex.output = o }
 
 showOutput :: Annex ()
 showOutput = handle q $
@@ -122,9 +152,9 @@ maybeShowJSON v = handle (JSON.add v) q
 
 {- Shows a complete JSON value, only when in json mode. -}
 showFullJSON :: JSON a => [(String, a)] -> Annex Bool
-showFullJSON v = Annex.getState Annex.output >>= liftIO . go
+showFullJSON v = withOutputType $ liftIO . go
 	where
-		go Annex.JSONOutput = JSON.complete v >> return True
+		go JSONOutput = JSON.complete v >> return True
 		go _ = return False
 
 {- Performs an action that outputs nonstandard/customized output, and
@@ -153,14 +183,17 @@ setupConsole = do
 	fileEncoding stderr
 
 handle :: IO () -> IO () -> Annex ()
-handle json normal = Annex.getState Annex.output >>= go
+handle json normal = withOutputType $ go
 	where
-		go Annex.NormalOutput = liftIO normal
-		go Annex.QuietOutput = q
-		go Annex.JSONOutput = liftIO $ flushed json
+		go NormalOutput = liftIO normal
+		go QuietOutput = q
+		go JSONOutput = liftIO $ flushed json
 
 q :: Monad m => m ()
-q = return ()
+q = noop
 
 flushed :: IO () -> IO ()
 flushed a = a >> hFlush stdout
+
+withOutputType :: (OutputType -> Annex a) -> Annex a
+withOutputType a = outputType <$> Annex.getState Annex.output >>= a
diff --git a/Option.hs b/Option.hs
index 2f0d00744d..1bac2cd050 100644
--- a/Option.hs
+++ b/Option.hs
@@ -20,6 +20,7 @@ import System.Log.Logger
 
 import Common.Annex
 import qualified Annex
+import Types.Messages
 import Limit
 import Usage
 
@@ -31,11 +32,11 @@ common =
 		"avoid slow operations"
 	, Option ['a'] ["auto"] (NoArg (setauto True))
 		"automatic mode"
-	, Option ['q'] ["quiet"] (NoArg (setoutput Annex.QuietOutput))
+	, Option ['q'] ["quiet"] (NoArg (Annex.setOutput QuietOutput))
 		"avoid verbose output"
-	, Option ['v'] ["verbose"] (NoArg (setoutput Annex.NormalOutput))
+	, Option ['v'] ["verbose"] (NoArg (Annex.setOutput NormalOutput))
 		"allow verbose output (default)"
-	, Option ['j'] ["json"] (NoArg (setoutput Annex.JSONOutput))
+	, Option ['j'] ["json"] (NoArg (Annex.setOutput JSONOutput))
 		"enable JSON output"
 	, Option ['d'] ["debug"] (NoArg setdebug)
 		"show debug messages"
@@ -46,7 +47,6 @@ common =
 		setforce v = Annex.changeState $ \s -> s { Annex.force = v }
 		setfast v = Annex.changeState $ \s -> s { Annex.fast = v }
 		setauto v = Annex.changeState $ \s -> s { Annex.auto = v }
-		setoutput v = Annex.changeState $ \s -> s { Annex.output = v }
 		setforcebackend v = Annex.changeState $ \s -> s { Annex.forcebackend = Just v }
 		setdebug = liftIO $ updateGlobalLogger rootLoggerName $
 			setLevel DEBUG
diff --git a/Remote.hs b/Remote.hs
index aac45fae9d..e9e66990c5 100644
--- a/Remote.hs
+++ b/Remote.hs
@@ -194,7 +194,7 @@ showLocations key exclude = do
 		message rs us = message rs [] ++ message [] us
 
 showTriedRemotes :: [Remote] -> Annex ()
-showTriedRemotes [] = return ()	
+showTriedRemotes [] = noop
 showTriedRemotes remotes =
 	showLongNote $ "Unable to access these remotes: " ++
 		join ", " (map name remotes)
diff --git a/Remote/Bup.hs b/Remote/Bup.hs
index 1081815944..3e7e9211f9 100644
--- a/Remote/Bup.hs
+++ b/Remote/Bup.hs
@@ -184,7 +184,7 @@ storeBupUUID u buprepo = do
 
 onBupRemote :: Git.Repo -> (FilePath -> [CommandParam] -> IO a) -> FilePath -> [CommandParam] -> Annex a
 onBupRemote r a command params = do
-	let dir = shellEscape (Git.workTree r)
+	let dir = shellEscape (Git.repoPath r)
 	sshparams <- sshToRepo r [Param $
 			"cd " ++ dir ++ " && " ++ unwords (command : toCommand params)]
 	liftIO $ a "ssh" sshparams
diff --git a/Remote/Directory.hs b/Remote/Directory.hs
index 3627d9a9ad..7521e70135 100644
--- a/Remote/Directory.hs
+++ b/Remote/Directory.hs
@@ -10,7 +10,7 @@ module Remote.Directory (remote) where
 import qualified Data.ByteString.Lazy.Char8 as L
 import qualified Data.ByteString.Char8 as S
 import qualified Data.Map as M
-import Control.Exception (bracket)
+import qualified Control.Exception as E
 
 import Common.Annex
 import Types.Remote
@@ -22,6 +22,7 @@ import Remote.Helper.Encryptable
 import Crypto
 import Utility.DataUnits
 import Data.Int
+import Annex.Content
 
 remote :: RemoteType
 remote = RemoteType {
@@ -125,7 +126,7 @@ store :: FilePath -> ChunkSize -> Key -> Annex Bool
 store d chunksize k = do
 	src <- inRepo $ gitAnnexLocation k
 	metered k $ \meterupdate -> 
-		liftIO $ catchBoolIO $ storeHelper d chunksize k $ \dests ->
+		storeHelper d chunksize k $ \dests ->
 			case chunksize of
 				Nothing -> do
 					let dest = Prelude.head dests
@@ -140,7 +141,7 @@ storeEncrypted :: FilePath -> ChunkSize -> (Cipher, Key) -> Key -> Annex Bool
 storeEncrypted d chunksize (cipher, enck) k = do
 	src <- inRepo $ gitAnnexLocation k
 	metered k $ \meterupdate ->
-		liftIO $ catchBoolIO $ storeHelper d chunksize enck $ \dests ->
+		storeHelper d chunksize enck $ \dests ->
 			withEncryptedContent cipher (L.readFile src) $ \s ->
 				case chunksize of
 					Nothing -> do
@@ -165,7 +166,7 @@ storeSplit' :: MeterUpdate -> Int64 -> [FilePath] -> [S.ByteString] -> [FilePath
 storeSplit' _ _ [] _ _ = error "ran out of dests"
 storeSplit' _ _  _ [] c = return $ reverse c
 storeSplit' meterupdate chunksize (d:dests) bs c = do
-	bs' <- bracket (openFile d WriteMode) hClose (feed chunksize bs)
+	bs' <- E.bracket (openFile d WriteMode) hClose (feed chunksize bs)
 	storeSplit' meterupdate chunksize dests bs' (d:c)
 	where
 		feed _ [] _ = return []
@@ -190,11 +191,12 @@ meteredWriteFile meterupdate dest b =
  - meter after each chunk. The feeder is called to get more chunks. -}
 meteredWriteFile' :: MeterUpdate -> FilePath -> s -> (s -> IO (s, [S.ByteString])) -> IO ()
 meteredWriteFile' meterupdate dest startstate feeder =
-	bracket (openFile dest WriteMode) hClose (feed startstate [])
+	E.bracket (openFile dest WriteMode) hClose (feed startstate [])
 	where
 		feed state [] h = do
 			(state', cs) <- feeder state
-			if null cs then return () else feed state' cs h
+			unless (null cs) $
+				feed state' cs h
 		feed state (c:cs) h = do
 			S.hPut h c
 			meterupdate $ toInteger $ S.length c
@@ -207,31 +209,38 @@ meteredWriteFile' meterupdate dest startstate feeder =
  - The stored files are only put into their final place once storage is
  - complete.
  -}
-storeHelper :: FilePath -> ChunkSize -> Key -> ([FilePath] -> IO [FilePath]) -> IO Bool
-storeHelper d chunksize key a = do
-	let dir = parentDir desttemplate
-	createDirectoryIfMissing True dir
-	allowWrite dir
-	stored <- a tmpdests
-	forM_ stored $ \f -> do
-		let dest = detmpprefix f
-		renameFile f dest
-		preventWrite dest
-	when (chunksize /= Nothing) $ do
-		let chunkcount = chunkCount desttemplate
-		_ <- tryIO $ allowWrite chunkcount
-		writeFile chunkcount (show $ length stored)
-		preventWrite chunkcount
-	preventWrite dir
-	return (not $ null stored)
+storeHelper :: FilePath -> ChunkSize -> Key -> ([FilePath] -> IO [FilePath]) -> Annex Bool
+storeHelper d chunksize key a = prep <&&> check <&&> go
 	where
 		desttemplate = Prelude.head $ locations d key
+		dir = parentDir desttemplate
 		tmpdests = case chunksize of
 			Nothing -> [desttemplate ++ tmpprefix]
 			Just _ -> map (++ tmpprefix) (chunkStream desttemplate)
 		tmpprefix = ".tmp"
 		detmpprefix f = take (length f - tmpprefixlen) f
 		tmpprefixlen = length tmpprefix
+		prep = liftIO $ catchBoolIO $ do
+			createDirectoryIfMissing True dir
+			allowWrite dir
+			return True
+		{- The size is not exactly known when encrypting the key;
+		 - this assumes that at least the size of the key is
+		 - needed as free space. -}
+		check = checkDiskSpace (Just dir) key 0
+		go = liftIO $ catchBoolIO $ do
+			stored <- a tmpdests
+			forM_ stored $ \f -> do
+				let dest = detmpprefix f
+				renameFile f dest
+				preventWrite dest
+			when (chunksize /= Nothing) $ do
+				let chunkcount = chunkCount desttemplate
+				_ <- tryIO $ allowWrite chunkcount
+				writeFile chunkcount (show $ length stored)
+				preventWrite chunkcount
+			preventWrite dir
+			return (not $ null stored)
 
 retrieve :: FilePath -> ChunkSize -> Key -> FilePath -> Annex Bool
 retrieve d chunksize k f = metered k $ \meterupdate ->
diff --git a/Remote/Git.hs b/Remote/Git.hs
index 541b050994..cf7542d74e 100644
--- a/Remote/Git.hs
+++ b/Remote/Git.hs
@@ -94,7 +94,9 @@ tryGitConfigRead :: Git.Repo -> Annex Git.Repo
 tryGitConfigRead r 
 	| not $ M.null $ Git.config r = return r -- already read
 	| Git.repoIsSsh r = store $ onRemote r (pipedconfig, r) "configlist" []
-	| Git.repoIsHttp r = store $ safely geturlconfig
+	| Git.repoIsHttp r = do
+		headers <- getHttpHeaders
+		store $ safely $ geturlconfig headers
 	| Git.repoIsUrl r = return r
 	| otherwise = store $ safely $ onLocal r $ do 
 		ensureInitialized
@@ -109,8 +111,8 @@ tryGitConfigRead r
 			pOpen ReadFromPipe cmd (toCommand params) $
 				Git.Config.hRead r
 
-		geturlconfig = do
-			s <- Url.get (Git.repoLocation r ++ "/config")
+		geturlconfig headers = do
+			s <- Url.get (Git.repoLocation r ++ "/config") headers
 			withTempFile "git-annex.tmp" $ \tmpfile h -> do
 				hPutStr h s
 				hClose h
@@ -136,16 +138,16 @@ tryGitConfigRead r
  -}
 inAnnex :: Git.Repo -> Key -> Annex (Either String Bool)
 inAnnex r key
-	| Git.repoIsHttp r = checkhttp
+	| Git.repoIsHttp r = checkhttp =<< getHttpHeaders
 	| Git.repoIsUrl r = checkremote
 	| otherwise = checklocal
 	where
-		checkhttp = liftIO $ go undefined $ keyUrls r key
+		checkhttp headers = liftIO $ go undefined $ keyUrls r key
 			where
 				go e [] = return $ Left e
 				go _ (u:us) = do
 					res <- catchMsgIO $
-						Url.check u (keySize key)
+						Url.check u headers (keySize key)
 					case res of
 						Left e -> go e us
 						v -> return v
@@ -177,12 +179,8 @@ repoAvail r
  - monad using that repository. -}
 onLocal :: Git.Repo -> Annex a -> IO a
 onLocal r a = do
-	-- Avoid re-reading the repository's configuration if it was
-	-- already read.
-	state <- if M.null $ Git.config r
-		then Annex.new r
-		else return $ Annex.newState r
-	Annex.eval state $ do
+	s <- Annex.new r
+	Annex.eval s $ do
 		-- No need to update the branch; its data is not used
 		-- for anything onLocal is used to do.
 		Annex.BranchState.disableUpdate
@@ -312,8 +310,9 @@ commitOnCleanup r a = go `after` a
 		go = Annex.addCleanup (Git.repoLocation r) cleanup
 		cleanup
 			| not $ Git.repoIsUrl r = liftIO $ onLocal r $
-				Annex.Branch.commit "update"
-			| otherwise = do
+				doQuietSideAction $
+					Annex.Branch.commit "update"
+			| otherwise = void $ do
 				Just (shellcmd, shellparams) <-
 					git_annex_shell r "commit" []
 				-- Throw away stderr, since the remote may not
@@ -322,6 +321,4 @@ commitOnCleanup r a = go `after` a
 				let cmd = shellcmd ++ " "
 					++ unwords (map shellEscape $ toCommand shellparams)
 					++ ">/dev/null 2>/dev/null"
-				_ <- liftIO $
-					boolSystem "sh" [Param "-c", Param cmd]
-				return ()
+				liftIO $ boolSystem "sh" [Param "-c", Param cmd]
diff --git a/Remote/Helper/Encryptable.hs b/Remote/Helper/Encryptable.hs
index bcecb30cc4..789a1d9964 100644
--- a/Remote/Helper/Encryptable.hs
+++ b/Remote/Helper/Encryptable.hs
@@ -14,20 +14,26 @@ import Types.Remote
 import Crypto
 import qualified Annex
 import Config
+import Utility.Base64
 
 {- Encryption setup for a remote. The user must specify whether to use
  - an encryption key, or not encrypt. An encrypted cipher is created, or is
- - updated to be accessible to an additional encryption key. -}
+ - updated to be accessible to an additional encryption key. Or the user
+ - could opt to use a shared cipher, which is stored unencrypted. -}
 encryptionSetup :: RemoteConfig -> Annex RemoteConfig
-encryptionSetup c =
-	case (M.lookup "encryption" c, extractCipher c) of
-		(Nothing, Nothing) -> error "Specify encryption=key or encryption=none"
-		(Just "none", Nothing) -> return c
-		(Just "none", Just _) -> error "Cannot change encryption type of existing remote."
-		(Nothing, Just _) -> return c
-		(Just _, Nothing) -> use "encryption setup" $ genCipher c
-		(Just _, Just v) -> use "encryption updated" $ updateCipher c v
+encryptionSetup c = case (M.lookup "encryption" c, extractCipher c) of
+	(Nothing, Nothing) -> error "Specify encryption=key or encryption=none or encryption=shared"
+	(Just "none", Nothing) -> return c
+	(Nothing, Just _) -> return c
+	(Just "shared", Just (SharedCipher _)) -> return c
+	(Just "none", Just _) -> cannotchange
+	(Just "shared", Just (EncryptedCipher _ _)) -> cannotchange
+	(Just _, Just (SharedCipher _)) -> cannotchange
+	(Just "shared", Nothing) -> use "encryption setup" $ genSharedCipher
+	(Just keyid, Nothing) -> use "encryption setup" $ genEncryptedCipher keyid
+	(Just keyid, Just v) -> use "encryption updated" $ updateEncryptedCipher keyid v
 	where
+		cannotchange = error "Cannot change encryption type of existing remote."
 		use m a = do
 			cipher <- liftIO a
 			showNote $ m ++ " " ++ describeCipher cipher
@@ -78,7 +84,7 @@ remoteCipher c = go $ extractCipher c
 				Nothing -> decrypt encipher cache
 		decrypt encipher cache = do
 			showNote "gpg"
-			cipher <- liftIO $ decryptCipher c encipher
+			cipher <- liftIO $ decryptCipher encipher
 			Annex.changeState (\s -> s { Annex.ciphers = M.insert encipher cipher cache })
 			return $ Just cipher
 
@@ -88,3 +94,21 @@ cipherKey Nothing _ = return Nothing
 cipherKey (Just c) k = maybe Nothing encrypt <$> remoteCipher c
 	where
 		encrypt ciphertext = Just (ciphertext, encryptKey ciphertext k)
+
+{- Stores an StorableCipher in a remote's configuration. -}
+storeCipher :: RemoteConfig -> StorableCipher -> RemoteConfig
+storeCipher c (SharedCipher t) = M.insert "cipher" (toB64 t) c
+storeCipher c (EncryptedCipher t ks) = 
+	M.insert "cipher" (toB64 t) $ M.insert "cipherkeys" (showkeys ks) c
+	where
+		showkeys (KeyIds l) = join "," l
+
+{- Extracts an StorableCipher from a remote's configuration. -}
+extractCipher :: RemoteConfig -> Maybe StorableCipher
+extractCipher c = 
+	case (M.lookup "cipher" c, M.lookup "cipherkeys" c) of
+		(Just t, Just ks) -> Just $ EncryptedCipher (fromB64 t) (readkeys ks)
+		(Just t, Nothing) -> Just $ SharedCipher (fromB64 t)
+		_ -> Nothing
+	where
+		readkeys = KeyIds . split ","
diff --git a/Remote/Helper/Hooks.hs b/Remote/Helper/Hooks.hs
index 2864a8ed58..d85959062e 100644
--- a/Remote/Helper/Hooks.hs
+++ b/Remote/Helper/Hooks.hs
@@ -14,6 +14,7 @@ import Types.Remote
 import qualified Annex
 import Annex.LockPool
 import Config
+import Annex.Perms
 
 {- Modifies a remote's access functions to first run the
  - annex-start-command hook, and trigger annex-stop-command on shutdown.
@@ -45,10 +46,9 @@ runHooks r starthook stophook a = do
 	a
 	where
 		remoteid = show (uuid r)
-		run Nothing = return ()
-		run (Just command) = liftIO $ do
-			_ <- boolSystem "sh" [Param "-c", Param command]
-			return ()
+		run Nothing = noop
+		run (Just command) = void $ liftIO $
+			boolSystem "sh" [Param "-c", Param command]
 		firstrun lck = do
 			-- Take a shared lock; This indicates that git-annex
 			-- is using the remote, and prevents other instances
@@ -75,11 +75,13 @@ runHooks r starthook stophook a = do
 			-- succeeds, we're the only process using this remote,
 			-- so can stop it.
 			unlockFile lck
-			fd <- liftIO $ openFd lck ReadWrite (Just stdFileMode) defaultFileFlags
+			mode <- annexFileMode
+			fd <- liftIO $ noUmask mode $
+				openFd lck ReadWrite (Just mode) defaultFileFlags
 			v <- liftIO $ tryIO $
 				setLock fd (WriteLock, AbsoluteSeek, 0, 0)
 			case v of
-				Left _ -> return ()
+				Left _ -> noop
 				Right _ -> run stophook
 			liftIO $ closeFd fd
 
diff --git a/Remote/Helper/Ssh.hs b/Remote/Helper/Ssh.hs
index 4c5eef0e6c..f6742b89f6 100644
--- a/Remote/Helper/Ssh.hs
+++ b/Remote/Helper/Ssh.hs
@@ -34,7 +34,7 @@ git_annex_shell r command params
 		return $ Just ("ssh", sshparams)
 	| otherwise = return Nothing
 	where
-		dir = Git.workTree r
+		dir = Git.repoPath r
 		shellcmd = "git-annex-shell"
 		shellopts = Param command : File dir : params
 		sshcmd uuid = unwords $
diff --git a/Remote/Hook.hs b/Remote/Hook.hs
index 1c87823caa..dcac9da889 100644
--- a/Remote/Hook.hs
+++ b/Remote/Hook.hs
@@ -74,14 +74,14 @@ hookEnv k f = Just $ fileenv f ++ keyenv
 
 lookupHook :: String -> String -> Annex (Maybe String)
 lookupHook hooktype hook =do
-	command <- getConfig hookname ""
+	command <- getConfig (annexConfig hookname) ""
 	if null command
 		then do
 			warning $ "missing configuration for " ++ hookname
 			return Nothing
 		else return $ Just command
 	where
-		hookname =  "annex." ++ hooktype ++ "-" ++ hook ++ "-hook"
+		hookname = hooktype ++ "-" ++ hook ++ "-hook"
 
 runHook :: String -> String -> Key -> Maybe FilePath -> Annex Bool -> Annex Bool
 runHook hooktype hook k f a = maybe (return False) run =<< lookupHook hooktype hook
diff --git a/Remote/List.hs b/Remote/List.hs
index 57dfa43ebf..14a1771b48 100644
--- a/Remote/List.hs
+++ b/Remote/List.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
 {- git-annex remote list
  -
  - Copyright 2011 Joey Hess <joey@kitenet.net>
@@ -18,7 +20,9 @@ import Config
 import Remote.Helper.Hooks
 
 import qualified Remote.Git
+#ifdef WITH_S3
 import qualified Remote.S3
+#endif
 import qualified Remote.Bup
 import qualified Remote.Directory
 import qualified Remote.Rsync
@@ -28,7 +32,9 @@ import qualified Remote.Hook
 remoteTypes :: [RemoteType]
 remoteTypes =
 	[ Remote.Git.remote
+#ifdef WITH_S3
 	, Remote.S3.remote
+#endif
 	, Remote.Bup.remote
 	, Remote.Directory.remote
 	, Remote.Rsync.remote
diff --git a/Remote/Rsync.hs b/Remote/Rsync.hs
index 571cd8f5ee..60cbf4595f 100644
--- a/Remote/Rsync.hs
+++ b/Remote/Rsync.hs
@@ -22,9 +22,10 @@ import Utility.RsyncFile
 
 type RsyncUrl = String
 
-data RsyncOpts = RsyncOpts {
-	rsyncUrl :: RsyncUrl,
-	rsyncOptions :: [CommandParam]
+data RsyncOpts = RsyncOpts
+	{ rsyncUrl :: RsyncUrl
+	, rsyncOptions :: [CommandParam]
+	, rsyncShellEscape :: Bool
 }
 
 remote :: RemoteType
@@ -37,7 +38,7 @@ remote = RemoteType {
 
 gen :: Git.Repo -> UUID -> Maybe RemoteConfig -> Annex Remote
 gen r u c = do
-	o <- genRsyncOpts r
+	o <- genRsyncOpts r c
 	cst <- remoteCost r expensiveRemoteCost
 	return $ encryptableRemote c
 		(storeEncrypted o)
@@ -58,11 +59,13 @@ gen r u c = do
 			remotetype = remote
 		}
 
-genRsyncOpts :: Git.Repo -> Annex RsyncOpts
-genRsyncOpts r = do
+genRsyncOpts :: Git.Repo -> Maybe RemoteConfig -> Annex RsyncOpts
+genRsyncOpts r c = do
 	url <- getRemoteConfig r "rsyncurl" (error "missing rsyncurl")
-	opts <- getRemoteConfig r "rsync-options" ""
-	return $ RsyncOpts url $ map Param $ filter safe $ words opts
+	opts <- map Param . filter safe . words
+		<$> getRemoteConfig r "rsync-options" ""
+	let escape = maybe True (\m -> M.lookup "shellescape" m /= Just "no") c
+	return $ RsyncOpts url opts escape
 	where
 		safe o
 			-- Don't allow user to pass --delete to rsync;
@@ -86,7 +89,7 @@ rsyncSetup u c = do
 
 rsyncEscape :: RsyncOpts -> String -> String
 rsyncEscape o s
-	| rsyncUrlIsShell (rsyncUrl o) = shellEscape s
+	| rsyncShellEscape o && rsyncUrlIsShell (rsyncUrl o) = shellEscape s
 	| otherwise = s
 
 rsyncUrls :: RsyncOpts -> Key -> [String]
diff --git a/Remote/S3.hs b/Remote/S3.hs
index a688ffcf34..18d4915dcb 100644
--- a/Remote/S3.hs
+++ b/Remote/S3.hs
@@ -93,7 +93,7 @@ s3Setup u c = handlehost $ M.lookup "host" c
 
 		archiveorg = do
 			showNote "Internet Archive mode"
-			maybe (error "specify bucket=") (const $ return ()) $
+			maybe (error "specify bucket=") (const noop) $
 				M.lookup "bucket" archiveconfig
 			use archiveconfig
 			where
@@ -237,13 +237,13 @@ genBucket c = do
 	showAction "checking bucket"
 	loc <- liftIO $ getBucketLocation conn bucket 
 	case loc of
-		Right _ -> return ()
+		Right _ -> noop
 		Left err@(NetworkError _) -> s3Error err
 		Left (AWSError _ _) -> do
 			showAction $ "creating bucket in " ++ datacenter
 			res <- liftIO $ createBucketIn conn bucket datacenter
 			case res of
-				Right _ -> return ()
+				Right _ -> noop
 				Left err -> s3Error err
 	where
 		bucket = fromJust $ M.lookup "bucket" c
diff --git a/Remote/Web.hs b/Remote/Web.hs
index 81e6ca321c..5fc592326c 100644
--- a/Remote/Web.hs
+++ b/Remote/Web.hs
@@ -83,4 +83,5 @@ checkKey key = do
 checkKey' :: Key -> [URLString] -> Annex Bool
 checkKey' key us = untilTrue us $ \u -> do
 	showAction $ "checking " ++ u
-	liftIO $ Url.check u (keySize key)
+	headers <- getHttpHeaders
+	liftIO $ Url.check u headers (keySize key)
diff --git a/Seek.hs b/Seek.hs
index 8d4f917e72..eed4a81558 100644
--- a/Seek.hs
+++ b/Seek.hs
@@ -4,7 +4,7 @@
  - the values a user passes to a command, and prepare actions operating
  - on them.
  -
- - Copyright 2010-2011 Joey Hess <joey@kitenet.net>
+ - Copyright 2010-2012 Joey Hess <joey@kitenet.net>
  -
  - Licensed under the GNU GPL version 3 or higher.
  -}
@@ -41,6 +41,14 @@ withFilesNotInGit a params = do
 			g <- gitRepo
 			liftIO $ (\p -> LsFiles.notInRepo force p g) l
 
+withPathContents :: ((FilePath, FilePath) -> CommandStart) -> CommandSeek
+withPathContents a params = map a . concat <$> liftIO (mapM get params)
+	where
+		get p = ifM (isDirectory <$> getFileStatus p)
+			( map (\f -> (f, makeRelative p f)) <$> dirContentsRecursive p
+			, return [(p, takeFileName p)]
+			)
+
 withWords :: ([String] -> CommandStart) -> CommandSeek
 withWords a params = return [a params]
 
diff --git a/Setup.hs b/Setup.hs
index 14e6a4ea71..c36d6e4fe1 100644
--- a/Setup.hs
+++ b/Setup.hs
@@ -1,12 +1,27 @@
 {- cabal setup file -}
 
 import Distribution.Simple
+import Distribution.Simple.LocalBuildInfo
+import Distribution.Simple.Setup
 import System.Cmd
+import System.FilePath
 
 import qualified Build.Configure as Configure
 
-main = defaultMainWithHooks simpleUserHooks { preConf = configure }
+main = defaultMainWithHooks simpleUserHooks
+	{ preConf = configure
+	, instHook = install
+	}
 
 configure _ _ = do
 	Configure.run Configure.tests
 	return (Nothing, [])
+
+install pkg_descr lbi userhooks flags = do
+	r <- (instHook simpleUserHooks) pkg_descr lbi userhooks flags
+	_ <- rawSystem "ln" ["-sf", "git-annex", 
+		bindir installDirs </> "git-annex-shell"]
+	return r
+	where
+		installDirs = absoluteInstallDirs pkg_descr lbi $
+			fromFlag (copyDest defaultCopyFlags)
diff --git a/Types/Crypto.hs b/Types/Crypto.hs
index 686bf5c1a6..135522ba11 100644
--- a/Types/Crypto.hs
+++ b/Types/Crypto.hs
@@ -1,13 +1,13 @@
 {- git-annex crypto types
  -
- - Copyright 2011 Joey Hess <joey@kitenet.net>
+ - Copyright 2011-2012 Joey Hess <joey@kitenet.net>
  -
  - Licensed under the GNU GPL version 3 or higher.
  -}
 
 module Types.Crypto (
 	Cipher(..),
-	EncryptedCipher(..),
+	StorableCipher(..),
 	KeyIds(..),
 ) where
 
@@ -16,5 +16,5 @@ import Utility.Gpg (KeyIds(..))
 -- XXX ideally, this would be a locked memory region
 newtype Cipher = Cipher String
 
-data EncryptedCipher = EncryptedCipher String KeyIds
+data StorableCipher = EncryptedCipher String KeyIds | SharedCipher String
 	deriving (Ord, Eq)
diff --git a/Types/Messages.hs b/Types/Messages.hs
new file mode 100644
index 0000000000..75653d574c
--- /dev/null
+++ b/Types/Messages.hs
@@ -0,0 +1,20 @@
+{- git-annex Messages data types
+ - 
+ - Copyright 2012 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Types.Messages where
+
+data OutputType = NormalOutput | QuietOutput | JSONOutput
+
+data SideActionBlock = NoBlock | StartBlock | InBlock
+
+data MessageState = MessageState
+	{ outputType :: OutputType
+	, sideActionBlock :: SideActionBlock
+	}
+
+defaultMessageState :: MessageState
+defaultMessageState = MessageState NormalOutput NoBlock
diff --git a/Upgrade/V1.hs b/Upgrade/V1.hs
index 62e3b3b313..280742f062 100644
--- a/Upgrade/V1.hs
+++ b/Upgrade/V1.hs
@@ -59,7 +59,7 @@ upgrade = do
 			updateSymlinks
 			moveLocationLogs
 	
-			Annex.Queue.flush True
+			Annex.Queue.flush
 			setVersion
 		)
 	
@@ -82,14 +82,14 @@ moveContent = do
 updateSymlinks :: Annex ()
 updateSymlinks = do
 	showAction "updating symlinks"
-	top <- fromRepo Git.workTree
+	top <- fromRepo Git.repoPath
 	files <- inRepo $ LsFiles.inRepo [top]
 	forM_ files fixlink
 	where
 		fixlink f = do
 			r <- lookupFile1 f
 			case r of
-				Nothing -> return ()
+				Nothing -> noop
 				Just (k, _) -> do
 					link <- calcGitLink f k
 					liftIO $ removeFile f
@@ -236,4 +236,4 @@ stateDir :: FilePath
 stateDir = addTrailingPathSeparator ".git-annex"
 
 gitStateDir :: Git.Repo -> FilePath
-gitStateDir repo = addTrailingPathSeparator $ Git.workTree repo </> stateDir
+gitStateDir repo = addTrailingPathSeparator $ Git.repoPath repo </> stateDir
diff --git a/Upgrade/V2.hs b/Upgrade/V2.hs
index c57b0bf685..202ba5b167 100644
--- a/Upgrade/V2.hs
+++ b/Upgrade/V2.hs
@@ -134,4 +134,4 @@ gitAttributesUnWrite repo = do
 stateDir :: FilePath
 stateDir = addTrailingPathSeparator ".git-annex"
 gitStateDir :: Git.Repo -> FilePath
-gitStateDir repo = addTrailingPathSeparator $ Git.workTree repo </> stateDir
+gitStateDir repo = addTrailingPathSeparator $ Git.repoPath repo </> stateDir
diff --git a/Usage.hs b/Usage.hs
index b1de930ef2..e74c1490d0 100644
--- a/Usage.hs
+++ b/Usage.hs
@@ -61,6 +61,8 @@ paramUrl :: String
 paramUrl = "URL"
 paramNumber :: String
 paramNumber = "NUMBER"
+paramNumRange :: String
+paramNumRange = "NUM|RANGE"
 paramRemote :: String
 paramRemote = "REMOTE"
 paramGlob :: String
diff --git a/Utility/CopyFile.hs b/Utility/CopyFile.hs
index c42506485b..66b88e4f0c 100644
--- a/Utility/CopyFile.hs
+++ b/Utility/CopyFile.hs
@@ -1,16 +1,13 @@
 {- git-annex file copying
  -
- - Copyright 2010 Joey Hess <joey@kitenet.net>
+ - Copyright 2010,2012 Joey Hess <joey@kitenet.net>
  -
  - Licensed under the GNU GPL version 3 or higher.
  -}
 
 module Utility.CopyFile (copyFileExternal) where
 
-import System.Directory (doesFileExist, removeFile)
-import Control.Monad.IfElse
-
-import Utility.SafeCommand
+import Common
 import qualified Build.SysConfig as SysConfig
 
 {- The cp command is used, because I hate reinventing the wheel,
@@ -19,10 +16,10 @@ copyFileExternal :: FilePath -> FilePath -> IO Bool
 copyFileExternal src dest = do
 	whenM (doesFileExist dest) $
 		removeFile dest
-	boolSystem "cp" [params, File src, File dest]
+	boolSystem "cp" $ params ++ [File src, File dest]
 	where
-		params
-			| SysConfig.cp_reflink_auto = Params "--reflink=auto"
-			| SysConfig.cp_a = Params "-a"
-			| SysConfig.cp_p = Params "-p"
-			| otherwise = Params ""
+		params = map snd $ filter fst
+			[ (SysConfig.cp_reflink_auto, Param "--reflink=auto")
+			, (SysConfig.cp_a, Param "-a")
+			, (SysConfig.cp_p && not SysConfig.cp_a, Param "-p")
+			]
diff --git a/Utility/Directory.hs b/Utility/Directory.hs
index 40e65d6349..5bfd49a9c1 100644
--- a/Utility/Directory.hs
+++ b/Utility/Directory.hs
@@ -15,26 +15,54 @@ import Control.Monad
 import Control.Monad.IfElse
 import System.FilePath
 import Control.Applicative
+import Control.Exception (bracket_)
+import System.Posix.Directory
+import System.IO.Unsafe (unsafeInterleaveIO)
 
 import Utility.SafeCommand
 import Utility.TempFile
 import Utility.Exception
+import Utility.Monad
+import Utility.Path
+
+dirCruft :: FilePath -> Bool
+dirCruft "." = True
+dirCruft ".." = True
+dirCruft _ = False
 
 {- Lists the contents of a directory.
  - Unlike getDirectoryContents, paths are not relative to the directory. -}
 dirContents :: FilePath -> IO [FilePath]
-dirContents d = map (d </>) . filter notcruft <$> getDirectoryContents d
+dirContents d = map (d </>) . filter (not . dirCruft) <$> getDirectoryContents d
+
+{- Gets contents of directory, and then its subdirectories, recursively,
+ - and lazily. -}
+dirContentsRecursive :: FilePath -> IO [FilePath]
+dirContentsRecursive topdir = dirContentsRecursive' topdir [""]
+
+dirContentsRecursive' :: FilePath -> [FilePath] -> IO [FilePath]
+dirContentsRecursive' _ [] = return []
+dirContentsRecursive' topdir (dir:dirs) = unsafeInterleaveIO $ do
+	(files, dirs') <- collect [] [] =<< dirContents (topdir </> dir)
+	files' <- dirContentsRecursive' topdir (dirs' ++ dirs)
+	return (files ++ files')
 	where
-		notcruft "." = False
-		notcruft ".." = False
-		notcruft _ = True
+		collect files dirs' [] = return (reverse files, reverse dirs')
+		collect files dirs' (entry:entries)
+			| dirCruft entry = collect files dirs' entries
+			| otherwise = do
+				let dirEntry = dir </> entry
+				ifM (doesDirectoryExist $ topdir </> dirEntry)
+					( collect files (dirEntry:dirs') entries
+					, collect (dirEntry:files) dirs' entries
+					)			
 
 {- Moves one filename to another.
  - First tries a rename, but falls back to moving across devices if needed. -}
 moveFile :: FilePath -> FilePath -> IO ()
 moveFile src dest = tryIO (rename src dest) >>= onrename
 	where
-		onrename (Right _) = return ()
+		onrename (Right _) = noop
 		onrename (Left e)
 			| isPermissionError e = rethrow
 			| isDoesNotExistError e = rethrow
@@ -59,3 +87,14 @@ moveFile src dest = tryIO (rename src dest) >>= onrename
 			case r of
 				(Left _) -> return False
 				(Right s) -> return $ isDirectory s
+
+{- Runs an action in another directory. -}
+bracketCd :: FilePath -> IO a -> IO a
+bracketCd dir a = go =<< getCurrentDirectory
+	where
+		go cwd
+			| dirContains dir cwd = a
+			| otherwise = bracket_
+				(changeWorkingDirectory dir)
+				(changeWorkingDirectory cwd)
+				a
diff --git a/Utility/DiskFree.hs b/Utility/DiskFree.hs
index bde6ef8caa..ff70705621 100644
--- a/Utility/DiskFree.hs
+++ b/Utility/DiskFree.hs
@@ -15,10 +15,10 @@ import Foreign.C.Types
 import Foreign.C.String
 import Foreign.C.Error
 
-foreign import ccall unsafe "diskfree.h diskfree" c_diskfree
+foreign import ccall unsafe "libdiskfree.h diskfree" c_diskfree
 	:: CString -> IO CULLong
 
-getDiskFree :: String -> IO (Maybe Integer)
+getDiskFree :: FilePath -> IO (Maybe Integer)
 getDiskFree path = withFilePath path $ \c_path -> do
 	free <- c_diskfree c_path
 	ifM (safeErrno <$> getErrno)
diff --git a/Utility/FileMode.hs b/Utility/FileMode.hs
index 571b035039..353de7b92a 100644
--- a/Utility/FileMode.hs
+++ b/Utility/FileMode.hs
@@ -1,35 +1,67 @@
 {- File mode utilities.
  -
- - Copyright 2010 Joey Hess <joey@kitenet.net>
+ - Copyright 2010-2012 Joey Hess <joey@kitenet.net>
  -
  - Licensed under the GNU GPL version 3 or higher.
  -}
 
 module Utility.FileMode where
 
-import System.Posix.Files
+import Common
+
+import Control.Exception (bracket)
 import System.Posix.Types
 import Foreign (complement)
 
-{- Removes a FileMode from a file.
- - For example, call with otherWriteMode to chmod o-w -}
-unsetFileMode :: FilePath -> FileMode -> IO ()
-unsetFileMode f m = do
+{- Applies a conversion function to a file's mode. -}
+modifyFileMode :: FilePath -> (FileMode -> FileMode) -> IO ()
+modifyFileMode f convert = void $ modifyFileMode' f convert
+modifyFileMode' :: FilePath -> (FileMode -> FileMode) -> IO FileMode
+modifyFileMode' f convert = do
 	s <- getFileStatus f
-	setFileMode f $ fileMode s `intersectFileModes` complement m
+	let old = fileMode s
+	let new = convert old
+	when (new /= old) $
+		setFileMode f new
+	return old
+
+{- Adds the specified FileModes to the input mode, leaving the rest
+ - unchanged. -}
+addModes :: [FileMode] -> FileMode -> FileMode
+addModes ms m = combineModes (m:ms)
+
+{- Removes the specified FileModes from the input mode. -}
+removeModes :: [FileMode] -> FileMode -> FileMode
+removeModes ms m = m `intersectFileModes` complement (combineModes ms)
+
+{- Runs an action after changing a file's mode, then restores the old mode. -}
+withModifiedFileMode :: FilePath -> (FileMode -> FileMode) -> IO a -> IO a
+withModifiedFileMode file convert a = bracket setup cleanup go
+	where
+		setup = modifyFileMode' file convert
+		cleanup oldmode = modifyFileMode file (const oldmode)
+		go _ = a
+
+writeModes :: [FileMode]
+writeModes = [ownerWriteMode, groupWriteMode, otherWriteMode]
+
+readModes :: [FileMode]
+readModes = [ownerReadMode, groupReadMode, otherReadMode]
 
 {- Removes the write bits from a file. -}
 preventWrite :: FilePath -> IO ()
-preventWrite f = unsetFileMode f writebits
-	where
-		writebits = foldl unionFileModes ownerWriteMode
-					[groupWriteMode, otherWriteMode]
+preventWrite f = modifyFileMode f $ removeModes writeModes
 
-{- Turns a file's write bit back on. -}
+{- Turns a file's owner write bit back on. -}
 allowWrite :: FilePath -> IO ()
-allowWrite f = do
-	s <- getFileStatus f
-	setFileMode f $ fileMode s `unionFileModes` ownerWriteMode
+allowWrite f = modifyFileMode f $ addModes [ownerWriteMode]
+
+{- Allows owner and group to read and write to a file. -}
+groupWriteRead :: FilePath -> IO ()
+groupWriteRead f = modifyFileMode f $ addModes
+	[ ownerWriteMode, groupWriteMode
+	, ownerReadMode, groupReadMode
+	]
 
 {- Checks if a file mode indicates it's a symlink. -}
 isSymLink :: FileMode -> Bool
@@ -37,7 +69,22 @@ isSymLink mode = symbolicLinkMode `intersectFileModes` mode == symbolicLinkMode
 
 {- Checks if a file has any executable bits set. -}
 isExecutable :: FileMode -> Bool
-isExecutable mode = ebits `intersectFileModes` mode /= 0
+isExecutable mode = combineModes ebits `intersectFileModes` mode /= 0
 	where
-		ebits = ownerExecuteMode `unionFileModes`
-			groupExecuteMode `unionFileModes` otherExecuteMode
+		ebits = [ownerExecuteMode, groupExecuteMode, otherExecuteMode]
+
+{- Runs an action without that pesky umask influencing it, unless the
+ - passed FileMode is the standard one. -}
+noUmask :: FileMode -> IO a -> IO a
+noUmask mode a
+	| mode == stdFileMode = a
+	| otherwise = bracket setup cleanup go
+	where
+		setup = setFileCreationMask nullFileMode
+		cleanup = setFileCreationMask
+		go _ = a
+
+combineModes :: [FileMode] -> FileMode
+combineModes [] = undefined
+combineModes [m] = m
+combineModes (m:ms) = foldl unionFileModes m ms
diff --git a/Utility/Gpg.hs b/Utility/Gpg.hs
index 4c798f2732..ff6735ba57 100644
--- a/Utility/Gpg.hs
+++ b/Utility/Gpg.hs
@@ -94,7 +94,18 @@ findPubKeys for = KeyIds . parse <$> readStrict params
 		pubKey = isPrefixOf "pub:"
 		keyIdField s = split ":" s !! 4
 
-
+{- Creates a block of high-quality random data suitable to use as a cipher.
+ - It is armored, to avoid newlines, since gpg only reads ciphers up to the
+ - first newline. -}
+genRandom :: Int -> IO String
+genRandom size = readStrict
+	[ Params "--gen-random --armor"
+	, Param $ show randomquality
+	, Param $ show size
+	]
+	where
+		-- 1 is /dev/urandom; 2 is /dev/random
+		randomquality = 1 :: Int
 
 {- A test key. This is provided pre-generated since generating a new gpg
  - key is too much work (requires too much entropy) for a test suite to
diff --git a/Utility/Inotify.hs b/Utility/Inotify.hs
index 049737c08a..d41e997d61 100644
--- a/Utility/Inotify.hs
+++ b/Utility/Inotify.hs
@@ -53,11 +53,10 @@ watchDir i test add del dir = watchDir' False i test add del dir
 watchDir' :: Bool -> INotify -> (FilePath -> Bool) -> Maybe (FilePath -> IO ()) -> Maybe (FilePath -> IO ()) -> FilePath -> IO ()
 watchDir' scan i test add del dir = do
 	if test dir
-		then do
+		then void $ do
 			_ <- addWatch i watchevents dir go
-			_ <- mapM walk =<< dirContents dir
-			return ()
-		else return ()
+			mapM walk =<< dirContents dir
+		else noop
 	where
 		watchevents
 			| isJust add && isJust del =
@@ -69,19 +68,19 @@ watchDir' scan i test add del dir = do
 		recurse = watchDir' scan i test add del
 		walk f = ifM (catchBoolIO $ Files.isDirectory <$> getFileStatus f)
 			( recurse f
-			, if scan && isJust add then fromJust add f else return ()
+			, when (scan && isJust add) $ fromJust add f
 			)
 
-		go (Created { isDirectory = False }) = return ()
+		go (Created { isDirectory = False }) = noop
 		go (Created { filePath = subdir }) = Just recurse <@> subdir
 		go (Closed { maybeFilePath = Just f }) = add <@> f
 		go (MovedIn { isDirectory = False, filePath = f }) = add <@> f
 		go (MovedOut { isDirectory = False, filePath = f }) = del <@> f
 		go (Deleted { isDirectory = False, filePath = f }) = del <@> f
-		go _ = return ()
+		go _ = noop
 		
 		Just a <@> f = a $ dir </> f
-		Nothing <@> _ = return ()
+		Nothing <@> _ = noop
 
 {- Pauses the main thread, letting children run until program termination. -}
 waitForTermination :: IO ()
@@ -92,6 +91,5 @@ waitForTermination = do
 		check keyboardSignal mv
 	takeMVar mv
 	where
-		check sig mv = do
-			_ <- installHandler sig (CatchOnce $ putMVar mv ()) Nothing
-			return ()
+		check sig mv = void $
+			installHandler sig (CatchOnce $ putMVar mv ()) Nothing
diff --git a/Utility/Monad.hs b/Utility/Monad.hs
index 9c85d31ca8..2c9b9e9e07 100644
--- a/Utility/Monad.hs
+++ b/Utility/Monad.hs
@@ -49,3 +49,7 @@ observe observer a = do
 {- b `after` a runs first a, then b, and returns the value of a -}
 after :: Monad m => m b -> m a -> m a
 after = observe . const
+
+{- do nothing -}
+noop :: Monad m => m ()
+noop = return ()
diff --git a/Utility/Percentage.hs b/Utility/Percentage.hs
new file mode 100644
index 0000000000..309e00181d
--- /dev/null
+++ b/Utility/Percentage.hs
@@ -0,0 +1,38 @@
+{- percentages
+ -
+ - Copyright 2012 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Utility.Percentage (
+	Percentage,
+	percentage,
+	showPercentage
+) where
+
+import Data.Ratio
+
+newtype Percentage = Percentage (Ratio Integer)
+
+instance Show Percentage where
+	show = showPercentage 0
+
+{- Normally the big number comes first. But 110% is allowed if desired. :) -}
+percentage :: Integer -> Integer -> Percentage
+percentage 0 _ = Percentage 0
+percentage full have = Percentage $ have * 100 % full
+
+{- Pretty-print a Percentage, with a specified level of precision. -}
+showPercentage :: Int -> Percentage -> String
+showPercentage precision (Percentage p)
+	| precision == 0 || remainder == 0 = go $ show int
+	| otherwise = go $ show int ++ "." ++ strip0s (show remainder)
+	where
+		go v = v ++ "%"
+		int :: Integer
+		(int, frac) = properFraction (fromRational p)
+		remainder = floor (frac * multiplier) :: Integer
+		strip0s = reverse . dropWhile (== '0') . reverse
+		multiplier :: Float
+		multiplier = 10 ** (fromIntegral precision)
diff --git a/Utility/RsyncFile.hs b/Utility/RsyncFile.hs
index a691d0a0e6..db9057843c 100644
--- a/Utility/RsyncFile.hs
+++ b/Utility/RsyncFile.hs
@@ -58,7 +58,7 @@ rsyncUrlIsShell s
 	| "rsync://" `isPrefixOf` s = False
 	| otherwise = go s
 	where
-		-- host:dir is rsync protocol, while host:dir is ssh/rsh
+		-- host::dir is rsync protocol, while host:dir is ssh/rsh
 		go [] = False
 		go (c:cs)
 			| c == '/' = False -- got to directory with no colon
diff --git a/Utility/Touch.hsc b/Utility/Touch.hsc
index b53eab634e..0b1ca3d9bd 100644
--- a/Utility/Touch.hsc
+++ b/Utility/Touch.hsc
@@ -106,9 +106,8 @@ touchBoth file atime mtime follow =
 	withFilePath file $ \f -> do
 		pokeArray ptr [atime, mtime]
 		r <- syscall f ptr
-		if (r /= 0)
-			then throwErrno "touchBoth"
-			else return ()
+		when (r /= 0) $
+			throwErrno "touchBoth"
 	where
 		syscall = if follow
 			then c_lutimes
diff --git a/Utility/Url.hs b/Utility/Url.hs
index 86d66d83b5..b75229e1bc 100644
--- a/Utility/Url.hs
+++ b/Utility/Url.hs
@@ -17,13 +17,16 @@ import Common
 import qualified Network.Browser as Browser
 import Network.HTTP
 import Network.URI
+import Data.Either
 
 type URLString = String
 
+type Headers = [String]
+
 {- Checks that an url exists and could be successfully downloaded,
  - also checking that its size, if available, matches a specified size. -}
-check :: URLString -> Maybe Integer -> IO Bool
-check url expected_size = handle <$> exists url
+check :: URLString -> Headers -> Maybe Integer -> IO Bool
+check url headers expected_size = handle <$> exists url headers
 	where
 		handle (False, _) = False
 		handle (True, Nothing) = True
@@ -31,12 +34,12 @@ check url expected_size = handle <$> exists url
 
 {- Checks that an url exists and could be successfully downloaded,
  - also returning its size if available. -}
-exists :: URLString -> IO (Bool, Maybe Integer)
-exists url =
+exists :: URLString -> Headers -> IO (Bool, Maybe Integer)
+exists url headers =
 	case parseURI url of
 		Nothing -> return (False, Nothing)
 		Just u -> do
-			r <- request u HEAD
+			r <- request u headers HEAD
 			case rspCode r of
 				(2,_,_) -> return (True, size r)
 				_ -> return (False, Nothing)
@@ -50,26 +53,27 @@ exists url =
  - would not be appropriate to test at configure time and build support
  - for only one in.
  -}
-download :: URLString -> [CommandParam] -> FilePath -> IO Bool
-download url options file = ifM (inPath "wget") (wget , curl)
+download :: URLString -> Headers -> [CommandParam] -> FilePath -> IO Bool
+download url headers options file = ifM (inPath "wget") (wget , curl)
 	where
-		wget = go "wget" [Params "-c -O"]
+		headerparams = map (\h -> Param $ "--header=" ++ h) headers
+		wget = go "wget" $ headerparams ++ [Params "-c -O"]
 		{- Uses the -# progress display, because the normal
 		 - one is very confusing when resuming, showing
 		 - the remainder to download as the whole file,
 		 - and not indicating how much percent was
 		 - downloaded before the resume. -}
-		curl = go "curl" [Params "-L -C - -# -o"]
+		curl = go "curl" $ headerparams ++ [Params "-L -C - -# -o"]
 		go cmd opts = boolSystem cmd $
 			options++opts++[File file, File url]
 
 {- Downloads a small file. -}
-get :: URLString -> IO String
-get url =
+get :: URLString -> Headers -> IO String
+get url headers =
 	case parseURI url of
 		Nothing -> error "url parse error"
 		Just u -> do
-			r <- request u GET
+			r <- request u headers GET
 			case rspCode r of
 				(2,_,_) -> return $ rspBody r
 				_ -> error $ rspReason r
@@ -81,8 +85,8 @@ get url =
  - This does its own redirect following because Browser's is buggy for HEAD
  - requests.
  -}
-request :: URI -> RequestMethod -> IO (Response String)
-request url requesttype = go 5 url
+request :: URI -> Headers -> RequestMethod -> IO (Response String)
+request url headers requesttype = go 5 url
 	where
 		go :: Int -> URI -> IO (Response String)
 		go 0 _ = error "Too many redirects "
@@ -91,11 +95,12 @@ request url requesttype = go 5 url
 				Browser.setErrHandler ignore
 				Browser.setOutHandler ignore
 				Browser.setAllowRedirects False
-				snd <$> Browser.request (mkRequest requesttype u :: Request_String)
+				let req = mkRequest requesttype u :: Request_String
+				snd <$> Browser.request (addheaders req)
 			case rspCode rsp of
 				(3,0,x) | x /= 5 -> redir (n - 1) u rsp
 				_ -> return rsp
-		ignore = const $ return ()
+		ignore = const noop
 		redir n u rsp = case retrieveHeaders HdrLocation rsp of
 			[] -> return rsp
 			(Header _ newu:_) ->
@@ -104,3 +109,5 @@ request url requesttype = go 5 url
 					Just newURI -> go n newURI_abs
 						where
 							newURI_abs = fromMaybe newURI (newURI `relativeTo` u)
+		addheaders req = setHeaders req (rqHeaders req ++ userheaders)
+		userheaders = rights $ map parseHeader headers
diff --git a/Utility/diskfree.c b/Utility/libdiskfree.c
similarity index 99%
rename from Utility/diskfree.c
rename to Utility/libdiskfree.c
index b68abd0c47..a37cb75713 100644
--- a/Utility/diskfree.c
+++ b/Utility/libdiskfree.c
@@ -58,9 +58,10 @@ unsigned long long int diskfree(const char *path) {
 	unsigned long long int available, blocksize;
 	struct STATSTRUCT buf;
 
-	errno = 0;
 	if (STATCALL(path, &buf) != 0)
 		return 0; /* errno is set */
+	else
+		errno = 0;
 
 	available = buf.f_bavail;
 	blocksize = buf.f_bsize;
diff --git a/Utility/diskfree.h b/Utility/libdiskfree.h
similarity index 100%
rename from Utility/diskfree.h
rename to Utility/libdiskfree.h
diff --git a/debian/changelog b/debian/changelog
index 0884f75744..52f6c3b971 100644
--- a/debian/changelog
+++ b/debian/changelog
@@ -1,4 +1,58 @@
-git-annex (3.20120407) UNRELEASED; urgency=low
+git-annex (3.20120523) UNRELEASED; urgency=low
+
+  * sync: Show a nicer message if a user tries to sync to a special remote.
+  * lock: Reset unlocked file to index, rather than to branch head.
+  * import: New subcommand, pulls files from a directory outside the annex
+    and adds them.
+  * Fix display of warning message when encountering a file that uses an
+    unsupported backend.
+  * Require that the SHA256 backend can be used when building, since it's the
+    default.
+
+ -- Joey Hess <joeyh@debian.org>  Sun, 27 May 2012 20:55:29 -0400
+
+git-annex (3.20120522) unstable; urgency=low
+
+  * Pass -a to cp even when it supports --reflink=auto, to preserve
+    permissions.
+  * Clean up handling of git directory and git worktree.
+  * Add support for core.worktree, and fix support for GIT_WORK_TREE and
+    GIT_DIR.
+
+ -- Joey Hess <joeyh@debian.org>  Tue, 22 May 2012 11:16:13 -0400
+
+git-annex (3.20120511) unstable; urgency=low
+
+  * Rsync special remotes can be configured with shellescape=no
+    to avoid shell quoting that is normally done when using rsync over ssh.
+    This is known to be needed for certian rsync hosting providers
+    (specificially hidrive.strato.com) that use rsync over ssh but do not
+    pass it through the shell.
+  * dropunused: Allow specifying ranges to drop.
+  * addunused: New command, the opposite of dropunused, it relinks unused
+    content into the git repository.
+  * Fix use of several config settings: annex.ssh-options,
+    annex.rsync-options, annex.bup-split-options. (And adjust types to avoid
+    the bugs that broke several config settings.)
+
+ -- Joey Hess <joeyh@debian.org>  Fri, 11 May 2012 12:29:30 -0400
+
+git-annex (3.20120430) unstable; urgency=low
+
+  * Fix use of annex.diskreserve config setting.
+  * Directory special remotes now check annex.diskreserve.
+  * Support git's core.sharedRepository configuration.
+  * Add annex.http-headers and annex.http-headers-command config
+    settings, to allow custom headers to be sent with all HTTP requests.
+    (Requested by the Internet Archive)
+  * uninit: Clear annex.uuid from .git/config. Closes: #670639
+  * Added shared cipher mode to encryptable special remotes. This option
+    avoids gpg key distribution, at the expense of flexability, and with
+    the requirement that all clones of the git repository be equally trusted.
+
+ -- Joey Hess <joeyh@debian.org>  Mon, 30 Apr 2012 13:16:10 -0400
+
+git-annex (3.20120418) unstable; urgency=low
 
   * bugfix: Adding a dotfile also caused all non-dotfiles to be added.
   * bup: Properly handle key names with spaces or other things that are
@@ -7,8 +61,11 @@ git-annex (3.20120407) UNRELEASED; urgency=low
     configuration setting, doing fuzzy matching using the restricted
     Damerau-Levenshtein edit distance, just as git does. This adds a build
     dependency on the haskell edit-distance library.
+  * Renamed diskfree.c to avoid OSX case insensativity bug.
+  * cabal now installs git-annex-shell as a symlink to git-annex.
+  * cabal file now autodetects whether S3 support is available.
 
- -- Joey Hess <joeyh@debian.org>  Sun, 08 Apr 2012 12:23:42 -0400
+ -- Joey Hess <joeyh@debian.org>  Wed, 18 Apr 2012 12:11:32 -0400
 
 git-annex (3.20120406) unstable; urgency=low
 
diff --git a/debian/copyright b/debian/copyright
index 332c1e71d2..de1e08e1cd 100644
--- a/debian/copyright
+++ b/debian/copyright
@@ -7,3 +7,9 @@ License: GPL-3+
  The full text of version 3 of the GPL is distributed as doc/GPL in
  this package's source, or in /usr/share/common-licenses/GPL-3 on
  Debian systems.
+
+Files: doc/logo.png doc/logo_small.png doc/favicon.png
+Copyright: 2007 Henrik Nyh <http://henrik.nyh.se/>
+           2010 Joey Hess <joey@kitenet.net>
+License: other
+  Free to modify and redistribute with due credit, and obviously free to use.
diff --git a/doc/bare_repositories.mdwn b/doc/bare_repositories.mdwn
index bf56d81446..f40277d61d 100644
--- a/doc/bare_repositories.mdwn
+++ b/doc/bare_repositories.mdwn
@@ -26,6 +26,7 @@ Here is a quick example of how to set this up, using `origin` as the remote name
 On the server:
 
     mkdir bare-annex
+    cd bare-annex
     git init --bare
     git annex init origin
 
diff --git a/doc/bugs/Error___39__get__39__ting_files_from_rsync_remote__44___versions_3.20120315_and_3.20120430.mdwn b/doc/bugs/Error___39__get__39__ting_files_from_rsync_remote__44___versions_3.20120315_and_3.20120430.mdwn
new file mode 100644
index 0000000000..85e2433829
--- /dev/null
+++ b/doc/bugs/Error___39__get__39__ting_files_from_rsync_remote__44___versions_3.20120315_and_3.20120430.mdwn
@@ -0,0 +1,79 @@
+What steps will reproduce the problem?
+
+	$ git annex initremote rsyncremote type=rsync rsyncurl=myuser@rsync.hidrive.strato.com:/users/myuser/git-annex/Music/ encryption=0xC597DECC177AFD7C
+	$ git annex get --from rsyncremote "file"
+
+What is the expected output? What do you see instead?
+
+I expect that the requested file is copied as for every other remote, but instead I get this error:
+
+----------------------------------------
+	get <file> (from rsyncremote...) (gpg) 
+	rsync: change_dir "/users/myuser/git-annex/Music/0e5/a5b/'GPGHMACSHA1--3afd32ab8e70ac329262adeb770c330b0845b1e0" failed: No such file or directory (2)
+
+	sent 8 bytes  received 10 bytes  7.20 bytes/sec
+	total size is 0  speedup is 0.00
+	rsync error: some files/attrs were not transferred (see previous errors) (code 23) at main.c(1518) [Receiver=3.0.9]
+
+	  rsync failed -- run git annex again to resume file transfer
+
+	rsync: change_dir "/users/myuser/git-annex/Music/8k/QZ/'GPGHMACSHA1--3afd32ab8e70ac329262adeb770c330b0845b1e0" failed: No such file or directory (2)
+
+	sent 8 bytes  received 10 bytes  36.00 bytes/sec
+	total size is 0  speedup is 0.00
+	rsync error: some files/attrs were not transferred (see previous errors) (code 23) at main.c(1518) [Receiver=3.0.9]
+
+	  rsync failed -- run git annex again to resume file transfer
+failed
+	git-annex: get: 1 failed
+----------------------------------------
+
+I can verify that the directory /users/myuser/git-annex/Music/0e5/a5b/GPGHMACSHA1--3afd32ab8e70ac329262adeb770c330b0845b1e0 exists in the rsync remote, without the ' character.
+
+What version of git-annex are you using? On what operating system?
+
+I tried versions 3.20120315 and 3.20120430 on Gentoo linux.
+
+	$ uname -a
+	Linux odin 3.3.1-gentoo-odin #1 SMP Sat Apr 7 21:18:11 CEST 2012 x86_64 Intel(R) Core(TM) i5 CPU M 560 @ 2.67GHz GenuineIntel GNU/Linux
+
+	$ ghc --version
+	The Glorious Glasgow Haskell Compilation System, version 7.4.1
+
+Please provide any additional information below.
+
+The rsync remote config in .git/config:
+
+	[remote "rsyncremote"]
+		annex-rsyncurl = myuser@rsync.hidrive.strato.com:/users/myuser/git-annex/Music/
+		annex-uuid = "UUID"
+
+> Here's what the --debug flag shows is being run: --[[Joey]] 
+
+	Running: rsync ["--progress","--inplace","joey@localhost:/tmp/Music/d98/a3c/'GPGHMACSHA1--878c3a3f59965bd87b4738ab29562efd215b954c/GPGHMACSHA1--878c3a3f59965bd87b4738ab29562efd215b954c'","/home/joey/tmp/x/.git/annex/tmp/GPGHMACSHA1--878c3a3f59965bd87b4738ab29562efd215b954c"] 
+
+> But, this works for me, here, despite containing the quoting!
+> That's because here it's using rsync over ssh, which actually requires
+> that quoting. Are you using rsync
+> over the rsync protocol? If so, the workaround is to explicitly make
+> the rsyncurl start with `rsync://`
+> 
+> And if this is the case, I need
+> to adjust the code in git-annex that determines if it's using ssh or
+> the rsync protocol. It assumes that (and this is what the rsync man 
+> says AFAICS) that the rsync protocol is only used if the url starts
+> with `rsync://` or contains `::`.
+> 
+>> Nope, it is indeed using rsync over ssh as git-annex thought.
+> 
+> Hmm, I see that `hidrive.strato.com` is some kind of rsync provider?
+> Perhaps they do something with rsync over ssh that
+> avoids the need for shell quoting. For example, they might pass incoming
+> ssh connections directly into rsync, bypassing the shell
+> -- which avoids the need for this quoting. Any details you can provide
+> about them would probably be useful then. Ie, do they really use rsync
+> over ssh, is it really a `rsync.net` type rsync provider? 
+>  --[[Joey]]
+> 
+>> This was the case, and the shellescape=no config option has been added
+>> to rsync special remotes to deal with it. [[done]] --[[Joey]] 
diff --git a/doc/bugs/GIT_DIR_support_incomplete.mdwn b/doc/bugs/GIT_DIR_support_incomplete.mdwn
new file mode 100644
index 0000000000..1b9738c4f7
--- /dev/null
+++ b/doc/bugs/GIT_DIR_support_incomplete.mdwn
@@ -0,0 +1,17 @@
+`GIT_DIR` support isn't right. Git does not look for `GIT_DIR/.git`;
+git-annex does.
+
+Also, to support this scenario, support for core.worktree needs to be added
+as well:
+
+	mkdir repo workdir
+	git --work-tree=$PWD/workdir --git-dir=$PWD/repo init
+	export GIT_DIR=$PWD/repo
+	git status
+	# ok
+	git annex init "new repo"
+	# fail
+
+--[[Joey]] 
+
+> [[fixed|done]] --[[Joey]] 
diff --git a/doc/bugs/add_range_argument_to___34__git_annex_dropunused__34___.mdwn b/doc/bugs/add_range_argument_to___34__git_annex_dropunused__34___.mdwn
index bbe6007a87..471a698a0e 100644
--- a/doc/bugs/add_range_argument_to___34__git_annex_dropunused__34___.mdwn
+++ b/doc/bugs/add_range_argument_to___34__git_annex_dropunused__34___.mdwn
@@ -16,3 +16,6 @@ I work around this lack as I want to drop all unused files anyway by something l
 
 > I don't see adding my own range operations to be an improvement worth
 > making; it'd arguably only be a complication. --[[Joey]] [[done]]
+
+>> Actually, this did get implemented, since using seq could fall afoul 
+>> of command-line length limits in extreme cases.
diff --git a/doc/bugs/case-insensitive.mdwn b/doc/bugs/case-insensitive.mdwn
new file mode 100644
index 0000000000..a917f64c28
--- /dev/null
+++ b/doc/bugs/case-insensitive.mdwn
@@ -0,0 +1,20 @@
+What steps will reproduce the problem?
+
+> Building git-annex on the ghc7.0 branch on a Mac with the default case-insensitive file system
+
+What is the expected output? What do you see instead?
+
+> Expected: build successfully; instead: 
+     
+    ld: duplicate symbol _UtilityziDiskFree_zdwa_info in dist/build/git-annex/git-annex-tmp/Utility/diskfree.o and dist/build/git-annex/git-annex-tmp/Utility/DiskFree.o for architecture x86_64
+
+What version of git-annex are you using? On what operating system?
+
+> commit `0bd5c90ef0518f75d52f0c5889422d8233df847d` on a Mac OS 10.6 and 10.7, using the Haskell Platform 2012.04
+
+Please provide any additional information below.
+
+> The problem is that since `DiskFree.hs` generates `DiskFree.o` and `diskfree.c` generates `diskfree.o`, a case-insensitive file system overwrites one object file with the other.  Renaming `diskfree.c` to `diskfreec.c` and changing the corresponding filenames in `git-annex.cabal` fixes the problem.
+
+>> Man, not this again. The 80's called, they want their 
+>> unix portability wars back. [[fixed|done]]. --[[Joey]]
diff --git a/doc/bugs/git_rename_detection_on_file_move/comment_10_5ec2f965c80cc5dd31ee3c4edb695664._comment b/doc/bugs/git_rename_detection_on_file_move/comment_10_5ec2f965c80cc5dd31ee3c4edb695664._comment
new file mode 100644
index 0000000000..6ea2677289
--- /dev/null
+++ b/doc/bugs/git_rename_detection_on_file_move/comment_10_5ec2f965c80cc5dd31ee3c4edb695664._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnpdM9F8VbtQ_H5PaPMpGSxPe_d5L1eJ6w"
+ nickname="Rafael"
+ subject="comment 10"
+ date="2012-05-15T07:36:25Z"
+ content="""
+Won't git itself be fixed on this issue? It was on my plans to look into that, however I don't know how difficult it will be.
+"""]]
diff --git a/doc/bugs/unlock_then_lock_of_uncommitted_file_loses_it.mdwn b/doc/bugs/unlock_then_lock_of_uncommitted_file_loses_it.mdwn
new file mode 100644
index 0000000000..9c093de389
--- /dev/null
+++ b/doc/bugs/unlock_then_lock_of_uncommitted_file_loses_it.mdwn
@@ -0,0 +1,7 @@
+Add a file (do not commit), then unlock it, and then lock it.
+There is an error and the symlink gets deleted.
+
+The file will still be staged in the index, and the file content is still
+in the annex. --[[Joey]] 
+
+[[done]]
diff --git a/doc/design/assistant.mdwn b/doc/design/assistant.mdwn
new file mode 100644
index 0000000000..7a720a5e08
--- /dev/null
+++ b/doc/design/assistant.mdwn
@@ -0,0 +1,20 @@
+The git-annex assistant is being
+[crowd funded on Kickstarter](http://www.kickstarter.com/projects/joeyh/git-annex-assistant-like-dropbox-but-with-your-own/).
+
+This is my design and plan for developing it.
+Still being fleshed out, still many ideas and use cases to add.
+Feel free to chip in with comments! --[[Joey]]
+
+## roadmap
+
+* Month 1 "like dropbox": [[!traillink inotify]] [[!traillink syncing]]
+* Month 2 "shiny webapp": [[!traillink webapp]] [[!traillink progressbars]]
+* Month 3 "easy setup": [[!traillink configurators]] [[!traillink pairing]]
+* Month 4 "polishing": [[!traillink cloud]] [[!traillink leftovers]]
+* Months 5-6 "9k bonus round": [[!traillink Android]] [[!traillink partial_content]]
+
+## not yet on the map:
+
+* [[desymlink]]
+* [[deltas]]
+* In my overfunded nighmares: [[Windows]]
diff --git a/doc/design/assistant/android.mdwn b/doc/design/assistant/android.mdwn
new file mode 100644
index 0000000000..90dc551794
--- /dev/null
+++ b/doc/design/assistant/android.mdwn
@@ -0,0 +1,64 @@
+Porting git-annex to Android will use the Android native SDK.
+
+A hopefully small Java app will be developed, which runs the webapp
+daemon, and a web browser to display it.
+
+### programs to port
+
+These will probably need to be bundled into the Android app, unless already
+available in the App Store.
+
+* ssh (native ssh needed for scp, not a client like ConnectBot)
+* rsync
+* gpg
+* git (not all git commands are needed,
+  but core plumbing and a few like `git-add` are.)
+
+### Android specific features
+
+The app should be aware of power status, and avoid expensive background
+jobs when low on battery or run flat out when plugged in.
+
+The app should be aware of network status, and avoid expensive data
+transfers when not on wifi. This may need to be configurable.
+
+### FAT sucks
+
+The main media partition will use some awful FAT filesystem format from
+1982 that cannot support git-annex's symlinks. (Hopefully it can at least
+handle all of git's filenames.) Possible approaches to this follow.
+
+(May want to consider which of these would make a Windows port easier too.)
+
+#### bare git repo with file browser
+
+Keep only a bare git repo on Android. The app would then need to include
+a file browser to access the files in there, and adding a file would move
+it into the repo.
+
+Not ideal.
+
+Could be improved some by registering git-annex as a file handling app on
+Android, allowing you to "send to" git-annex.
+
+#### implement git smudge filters
+
+See [[todo/smudge]].
+
+Difficult. Would make git-annex generally better.
+
+#### keep files outside bare git repo
+
+Use a bare git repo but don't keep files in `annex/objects`, instead
+leave them outside the repo, and add some local mapping to find them.
+
+Problem: Would leave files unlocked to modification, which might lose a
+version git-annex dependend upon existing on the phone. (Maybe the phone
+would have to be always considered an untrusted repo, which probably
+makes sense anyway.)
+
+Problem: 
+
+#### crazy `LD_PRELOAD` wrapper
+
+Need I say more? (Also, Android's linker may not even support it.)
diff --git a/doc/design/assistant/android/comment_1_8be9a74e5fc4641c2bf2e1bb7673dd59._comment b/doc/design/assistant/android/comment_1_8be9a74e5fc4641c2bf2e1bb7673dd59._comment
new file mode 100644
index 0000000000..389eac026d
--- /dev/null
+++ b/doc/design/assistant/android/comment_1_8be9a74e5fc4641c2bf2e1bb7673dd59._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://launchpad.net/~gdr-go2"
+ nickname="gdr-go2"
+ subject="FAT symlinks"
+ date="2012-05-28T18:12:10Z"
+ content="""
+It's a linux kernel so perhaps another option would be to create a big file and mount -o loop
+"""]]
diff --git a/doc/design/assistant/cloud.mdwn b/doc/design/assistant/cloud.mdwn
new file mode 100644
index 0000000000..bec3bc36b5
--- /dev/null
+++ b/doc/design/assistant/cloud.mdwn
@@ -0,0 +1,43 @@
+The [[syncing]] design assumes the network is connected. But it's often
+not in these pre-IPV6 days, so the cloud needs to be used to bridge between
+LANS.
+
+## more cloud providers
+
+Git-annex already supports storing large files in 
+several cloud providers via [[special_remotes]].
+More should be added, such as:
+
+* Google drive (attractive because it's free, only 5 gb tho)
+* OpenStack Swift (teh future)
+* Box.com (it's free, and current method is hard to set up and a sorta
+  shakey; a better method would be to use its API)
+* Dropbox? That would be ironic.. Via its API, presumably.
+
+## limited space
+
+When syncing via the cloud, space there is probably limited, so
+users with more files than cloud space will want to be able to use the
+cloud as a temporary transfer point, which files are removed from after
+they've propigated out.
+
+Other users will want to use the cloud as the canonical or backup location
+of their data, and would want a copy of all their files to be kept there.
+That's also ok.
+
+git-annex will need a way to tell the difference between these, either
+heuristically, or via configuration.
+
+Also needed for USB keys and Android gadgets.
+
+## storing git repos in the cloud
+
+Of course, one option is to just use github etc to store the git repo.
+
+Two things can store git repos in Anazon S3:
+* <http://gabrito.com/post/storing-git-repositories-in-amazon-s3-for-high-availability>
+* <http://wiki.cs.pdx.edu/oss2009/index/projects/gits3.html>
+
+Another option is to not store the git repo in the cloud, but push/pull
+peer-to-peer. When peers cannot directly talk to one-another, this could be
+bounced through something like XMPP.
diff --git a/doc/design/assistant/comment_1_a48fcfbf97f0a373ea375cd8f07f0fc8._comment b/doc/design/assistant/comment_1_a48fcfbf97f0a373ea375cd8f07f0fc8._comment
new file mode 100644
index 0000000000..646a03398a
--- /dev/null
+++ b/doc/design/assistant/comment_1_a48fcfbf97f0a373ea375cd8f07f0fc8._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkSq2FDpK2n66QRUxtqqdbyDuwgbQmUWus"
+ nickname="Jimmy"
+ subject="comment 1"
+ date="2012-06-02T12:06:37Z"
+ content="""
+Will statically linked binaries be provided for say Linux, OSX and *BSD?  I think having some statically linked binaries will certainly help and appeal to a lot of users.
+"""]]
diff --git a/doc/design/assistant/configurators.mdwn b/doc/design/assistant/configurators.mdwn
new file mode 100644
index 0000000000..e0e938efdd
--- /dev/null
+++ b/doc/design/assistant/configurators.mdwn
@@ -0,0 +1,18 @@
+Add to the [[webapp]] some configuration of git-annex.
+
+There are some basic settings that pass through to `git config`, things
+like how much disk space to leave free, how many copies to ensure are kept
+of files, etc.
+
+The meat of the configuration will be in configuration assistants that walk
+through setting up common use cases.
+
+* Create a repository (run when the web app is started without a configured
+  repository too).
+* Clone this repo to a USB drive.
+* Clone this repo to another host. (Needs [[pairing]])
+* Set up Amazon S3.
+* Set up rsync remote.
+* Set up encryption.
+* I lost my USB drive!
+* etc -- many more possibilities
diff --git a/doc/design/assistant/deltas.mdwn b/doc/design/assistant/deltas.mdwn
new file mode 100644
index 0000000000..ff4185a18f
--- /dev/null
+++ b/doc/design/assistant/deltas.mdwn
@@ -0,0 +1,9 @@
+Speed up syncing of modified versions of existing files. 
+
+One simple way is to find the key of the old version of a file that's
+being transferred, so it can be used as the basis for rsync, or any
+other similar transfer protocol.
+
+For remotes that don't use rsync, a poor man's version could be had by
+chunking each object into multiple parts. Only modified parts need be
+transferred. Sort of sub-keys to the main key being stored.
diff --git a/doc/design/assistant/desymlink.mdwn b/doc/design/assistant/desymlink.mdwn
new file mode 100644
index 0000000000..e12cd52dc7
--- /dev/null
+++ b/doc/design/assistant/desymlink.mdwn
@@ -0,0 +1,5 @@
+While dropbox allows modifying files in the folder, git-annex freezes
+them upon creation.
+
+To allow editing files in its folder, something like [[todo/smudge]] is
+needed, to get rid of the symlinks that stand in for the files.
diff --git a/doc/design/assistant/inotify.mdwn b/doc/design/assistant/inotify.mdwn
new file mode 100644
index 0000000000..6bb810a755
--- /dev/null
+++ b/doc/design/assistant/inotify.mdwn
@@ -0,0 +1,20 @@
+Finish "git annex watch" command, which runs, in the background, watching via
+inotify for changes, and automatically annexing new files, etc.
+
+There is a `watch` branch in git that adds such a command, although currently
+it only handles adding new files, and nothing else. To make this really
+useful, it needs to:
+
+- notice deleted files and stage the deletion
+  (tricky; there's a race with add..)
+- notice renamed files, auto-fix the symlink, and stage the new file location
+- periodically auto-commit staged changes (avoid autocommitting when
+  lots of changes are coming in)
+- tunable delays before adding new files, etc
+- honor .gitignore, not adding files it excludesa
+
+Also to do:
+
+- Support OSes other than Linux; it only uses inotify currently.
+  OSX and FreeBSD use the same mechanism, and there is a Haskell interface
+  for it,
diff --git a/doc/design/assistant/leftovers.mdwn b/doc/design/assistant/leftovers.mdwn
new file mode 100644
index 0000000000..c322a27812
--- /dev/null
+++ b/doc/design/assistant/leftovers.mdwn
@@ -0,0 +1,15 @@
+Things that don't fit anywhere else:
+
+* Automatically start daemon on boot or when user logs in.
+* Somehow get content that is unavailable. This is problematic with inotify,
+  since we only get an event once the user has tried (and failed) to read
+  from the file. This is only needed if all the files in the directory 
+  are not kept synced, but in some situations (ie, low disk space phones),
+  that is likely.
+* Drop files that have not been used lately, or meet some other criteria
+  (as long as there's a copy elsewhere).
+* Perhaps automatically dropunused files that have been deleted,
+  although I cannot see a way to do that, since by the time the inotify
+  deletion event arrives, the file is deleted, and we cannot see what
+  its symlink pointed to! Alternatively, perhaps automatically
+  do an expensive unused/dropunused cleanup process.
diff --git a/doc/design/assistant/pairing.mdwn b/doc/design/assistant/pairing.mdwn
new file mode 100644
index 0000000000..f33c5e11de
--- /dev/null
+++ b/doc/design/assistant/pairing.mdwn
@@ -0,0 +1,13 @@
+For git-annex to be able to clone its repo to another host, it'd be good to
+have some way of pairing devices.
+
+It could work like this:
+
+1. Prompt for the hostname (or do avahi local machine discovery). 
+2. Enable the two hosts to ssh to one-another and run git-annex shell.
+   (A tricky problem, if ssh keys need to be added to do that.)
+3. Push over a clone of the repository. (Using git-annex-shell?)
+4. Start [[syncing]].
+
+Also look into the method used by
+<https://support.mozilla.org/en-US/kb/add-a-device-to-firefox-sync>
diff --git a/doc/design/assistant/partial_content.mdwn b/doc/design/assistant/partial_content.mdwn
new file mode 100644
index 0000000000..5572811d48
--- /dev/null
+++ b/doc/design/assistant/partial_content.mdwn
@@ -0,0 +1,14 @@
+On a regular system, a reasonable simplifying assumption is that all the
+files in the folder will be synced to the system. A user might want to
+disable syncing of some subdirectories, for eg, archived files. But in
+general, things are simpler to understand and implement if all files sync.
+
+But, an Android gadget probably cannot hold all a user's files. Indeed,
+it's likely that old files will be aggressively dropped from the Android
+after syncing to elsewhere, in order to keep enough free space on it for
+new files. 
+
+There needs to be a way for the user to browse files not on the gadget and
+request they be transferred to it. This could be done as a browser in the
+web app, or using a subdirectory full of placeholder files (not symlinks;
+see [[Android]]) that start transfer of the real file when accessed.
diff --git a/doc/design/assistant/progressbars.mdwn b/doc/design/assistant/progressbars.mdwn
new file mode 100644
index 0000000000..2ade05aa57
--- /dev/null
+++ b/doc/design/assistant/progressbars.mdwn
@@ -0,0 +1,14 @@
+Currently, git-annex takes a very lazy approch to displaying
+progress into. It just lets rsync or whatever display the progress
+for it, in the terminal.
+
+Something better is needed for the [[webapp]]. There needs to be a
+way for the web app to know what the current progress is of all transfers.
+
+To get this info for downloads, git-annex can watch the file as it arrives
+and use its size.
+
+TODO: What about uploads? Will i have to parse rsync's progresss output?
+Feed it via a named pipe? Ugh.
+
+This is one of those potentially hidden but time consuming problems.
diff --git a/doc/design/assistant/syncing.mdwn b/doc/design/assistant/syncing.mdwn
new file mode 100644
index 0000000000..0813b8b70b
--- /dev/null
+++ b/doc/design/assistant/syncing.mdwn
@@ -0,0 +1,36 @@
+Once files are added (or removed or moved), need to send those changes to
+all the other git clones, at both the git level and the key/value level.
+
+## git syncing
+
+1. At regular intervals, just run `git annex sync`, which already handles
+   bidirectional syncing.
+2. Use a git merge driver that adds both conflicting files,
+   so conflicts never break a sync.
+3. Investigate the XMPP approach like dvcs-autosync does, or other ways of
+   signaling a change out of band.
+4. Add a hook, so when there's a change to sync, a program can be run.
+
+## data syncing
+
+There are two parts to data syncing. First, map the network and second,
+decide what to sync when.
+
+Mapping the network can reuse code in `git annex map`. Once the map is
+built, we want to find paths through the network that reach all nodes
+eventually, with the least cost. This is a minimum spanning tree problem,
+except with a directed graph, so really a Arborescence problem.
+
+With the map, we can determine which nodes to push new content to. Then we
+need to control those data transfers, sending to the cheapest nodes first,
+and with appropriate rate limiting and control facilities.
+
+This probably will need lots of refinements to get working well.
+
+## other considerations
+
+It would be nice if, when a USB drive is connected,
+syncing starts automatically.
+
+This assumes the network is connected. It's often not, so the
+[[cloud]] needs to be used to bridge between LANs.
diff --git a/doc/design/assistant/webapp.mdwn b/doc/design/assistant/webapp.mdwn
new file mode 100644
index 0000000000..abf7b38c94
--- /dev/null
+++ b/doc/design/assistant/webapp.mdwn
@@ -0,0 +1,36 @@
+The webapp is a web server that displays a shiny interface.
+
+## security
+
+* Listen only to localhost.
+* Instruct the user's web browser to open an url that contains a secret
+  token. This guards against other users on the same system.
+* I would like to avoid passwords or other authentication methods,
+  it's your local system.
+* Alternative for Linux at least would be to write a small program using
+  GTK+ Webkit, that runs the webapp, and can know what user ran it, avoiding
+  needing authentication.
+
+## interface
+
+* list of files uploading and downloading
+* progress bars for each file
+* drag and drop to reorder
+* cancel and pause
+* keep it usable w/o javascript, and accessible to blind, etc
+
+## other features
+
+* there could be a UI to export a file, which would make it be served up
+  over http by the web app
+
+## implementation
+
+Hope to use Yesod.
+
+TODO: Ensure that Yesod will work on arm. Necessary for later Android port.
+Will its template haskell cause a problem? Does new GHC support TH on ARM?
+Will it use too much memory or be too slow?
+
+Hopefully Yesod comes with some good UI widgets. Otherwise, need to use
+Jquery or similar.
diff --git a/doc/design/assistant/windows.mdwn b/doc/design/assistant/windows.mdwn
new file mode 100644
index 0000000000..da669ad82c
--- /dev/null
+++ b/doc/design/assistant/windows.mdwn
@@ -0,0 +1,24 @@
+See [[todo/windows_support]]..
+
+## symlinks
+
+Apparently new versions of Windows have something very like symlinks.
+(Or really, 3 or so things not entirely unlike symlinks and all different.)
+Stackoverflow has some details.
+
+NTFS supports symbolic links two different ways: an [[!wikipedia NTFS symbolic link]] and an [[!wikipedia NTFS_junction_point]].  The former seems like the closest analogue to POSIX symlinks.
+
+Make git use them, as it (apparently) does not yet.
+
+Currently, on Windows, git checks out symlinks as files containing the symlink
+target as their contents.
+
+## POSIX
+
+Lots of ifdefs and pain to deal with POSIX calls in the code base.
+
+Or I could try to use Cygwin.
+
+## Deeper system integration
+
+[NTFS Reparse Points](http://msdn.microsoft.com/en-us/library/aa365503%28v=VS.85%29.aspx) allow a program to define how the OS will interpret a file or directory in arbitrary ways.  This requires writing a file system filter.
diff --git a/doc/design/encryption.mdwn b/doc/design/encryption.mdwn
index 647683bd9f..b7acbb732a 100644
--- a/doc/design/encryption.mdwn
+++ b/doc/design/encryption.mdwn
@@ -20,7 +20,7 @@ with more than one encryption backend in mind helps future-proofing.
 
 [[!template id=note text="""
 The basis of this scheme was originally developed by Lars Wirzenius et al
-[for Obnam](http://braawi.org/obnam/encryption/).
+[for Obnam](http://liw.fi/obnam/encryption/).
 """]]
 
 Data is encrypted by gpg, using a symmetric cipher.
diff --git a/doc/download.mdwn b/doc/download.mdwn
index 30307f3088..f0f17e141d 100644
--- a/doc/download.mdwn
+++ b/doc/download.mdwn
@@ -7,11 +7,9 @@ Other mirrors of the git repository:
 * `git://git.kitenet.net/git-annex` [[gitweb](http://git.kitenet.net/?p=git-annex.git;a=summary)]
 * [at github](https://github.com/joeyh/git-annex)
 
-To download a tarball of a particular release, use an url like
-<http://git.kitenet.net/?p=git-annex.git;a=snapshot;sf=tgz;h=refs/tags/3.20110702>
-
-From time to time, releases of git-annex are uploaded
-[to hackage](http://hackage.haskell.org/package/git-annex).
+Releases of git-annex are uploaded
+[to hackage](http://hackage.haskell.org/package/git-annex). Get your
+tarballs there, if you need them.
 
 Some operating systems include git-annex in easily prepackaged form and
 others need some manual work. See [[install]] for details.
@@ -20,17 +18,17 @@ others need some manual work. See [[install]] for details.
 
 The git repository has some branches:
 
-* `debian-stable` contains the latest backport of git-annex to Debian
-  stable.
-* `no-s3` disables the S3 special remote, for systems that lack the
- necessary haskell library. (merge it into master if you need it)
-* `no-bloom` avoids using bloom filters. (merge it into master if you need it)
-* `old-monad-control` is for systems that don't have a newer monad-control
-  library.
-* `tweak-fetch` adds support for the git tweak-fetch hook, which has
-  been proposed and implemented but not yet accepted into git.
 * `ghc7.0` supports versions of ghc older than 7.4, which
   had a major change to filename encoding.
+* `old-monad-control` is for systems that don't have a newer monad-control
+  library.
+* `no-ifelse` avoids using the IFelse library
+  (merge it into master if you need it)
+* `no-bloom` avoids using bloom filters. (merge it into master if you need it)
+* `debian-stable` contains the latest backport of git-annex to Debian
+  stable.
+* `tweak-fetch` adds support for the git tweak-fetch hook, which has
+  been proposed and implemented but not yet accepted into git.
 * `setup` contains configuration for this website
 * `pristine-tar` contains [pristine-tar](http://kitenet.net/~joey/code/pristine-tar)
   data to create tarballs of any past git-annex release.
diff --git a/doc/download/comment_1_fbd8b6d39e9d3c71791551358c863966._comment b/doc/download/comment_1_fbd8b6d39e9d3c71791551358c863966._comment
deleted file mode 100644
index 488e005278..0000000000
--- a/doc/download/comment_1_fbd8b6d39e9d3c71791551358c863966._comment
+++ /dev/null
@@ -1,8 +0,0 @@
-[[!comment format=mdwn
- username="http://peter-simons.myopenid.com/"
- ip="84.189.2.244"
- subject="Please provide stable tarballs or zipfiles"
- date="2011-03-22T13:06:58Z"
- content="""
-I'm trying to package git annex for ArchLinux and NixOS. That task would be a *lot* easier, if there were proper release archives available for download. The Gitweb site offers to create snapshot tarballs on the fly, but those tarballs have a different SHA hash every time they're generated, so they cannot be used for the purposes of a distribution. A simple solution for this problem would be to enable snapshots in zip format (because zip files look the same every time they're generated).
-"""]]
diff --git a/doc/download/comment_2_f85f72b33aedc3425f0c0c47867d02f3._comment b/doc/download/comment_2_f85f72b33aedc3425f0c0c47867d02f3._comment
deleted file mode 100644
index 5441c3e4ce..0000000000
--- a/doc/download/comment_2_f85f72b33aedc3425f0c0c47867d02f3._comment
+++ /dev/null
@@ -1,8 +0,0 @@
-[[!comment format=mdwn
- username="https://www.google.com/accounts/o8/id?id=AItOawkSq2FDpK2n66QRUxtqqdbyDuwgbQmUWus"
- nickname="Jimmy"
- subject="comment 2"
- date="2011-03-22T14:01:37Z"
- content="""
-maybe snag tarballs from <http://packages.debian.org/experimental/git-annex> ? 
-"""]]
diff --git a/doc/download/comment_3_cf6044ebe99f71158034e21197228abd._comment b/doc/download/comment_3_cf6044ebe99f71158034e21197228abd._comment
deleted file mode 100644
index b72b848f80..0000000000
--- a/doc/download/comment_3_cf6044ebe99f71158034e21197228abd._comment
+++ /dev/null
@@ -1,10 +0,0 @@
-[[!comment format=mdwn
- username="http://joey.kitenet.net/"
- nickname="joey"
- subject="comment 3"
- date="2011-03-22T18:09:21Z"
- content="""
-The tarballs produced by gitweb are actually stable. They are wrapped in a gz file with a varying timestamp however. It might be nice if gitweb passed --no-name to gzip to avoid that inconsistency.
-
-git-annex also has a [pristine-tar](http://kitenet.net/~joey/code/pristine-tar/) branch in git that can be used to recreate the tarballs I upload to Debian.
-"""]]
diff --git a/doc/download/comment_4_10fc013865c7542c2ed9d6c0963bb391._comment b/doc/download/comment_4_10fc013865c7542c2ed9d6c0963bb391._comment
deleted file mode 100644
index 9bb9aa8ae3..0000000000
--- a/doc/download/comment_4_10fc013865c7542c2ed9d6c0963bb391._comment
+++ /dev/null
@@ -1,9 +0,0 @@
-[[!comment format=mdwn
- username="https://www.google.com/accounts/o8/id?id=AItOawnOvt3TwSSDOLnoVzDNbOP1qO9OmNH5s0s"
- nickname="Fraser"
- subject="gitweb supplies --no-name as of 1.7.5.1"
- date="2011-05-19T08:19:02Z"
- content="""
-git v1.7.5.1 fixes the gitweb gzip issue.  If the git instance is updated we
-can have stable distributions (and I can finally write a FreeBSD port ^_^)
-"""]]
diff --git a/doc/download/comment_5_c6b1bc40226fc2c8ba3e558150856992._comment b/doc/download/comment_5_c6b1bc40226fc2c8ba3e558150856992._comment
deleted file mode 100644
index 76ba75edc4..0000000000
--- a/doc/download/comment_5_c6b1bc40226fc2c8ba3e558150856992._comment
+++ /dev/null
@@ -1,8 +0,0 @@
-[[!comment format=mdwn
- username="http://joey.kitenet.net/"
- nickname="joey"
- subject="comment 5"
- date="2011-05-19T16:10:35Z"
- content="""
-Hmm, I've upgraded to that version, but I see nothing in its changelog, commit log, code, or runtime behavior to indicate that it's producing stable gzip output.
-"""]]
diff --git a/doc/download/comment_6_3a52993d3553deb9a413debec9a5f92d._comment b/doc/download/comment_6_3a52993d3553deb9a413debec9a5f92d._comment
deleted file mode 100644
index 0dbd88b1e5..0000000000
--- a/doc/download/comment_6_3a52993d3553deb9a413debec9a5f92d._comment
+++ /dev/null
@@ -1,11 +0,0 @@
-[[!comment format=mdwn
- username="https://www.google.com/accounts/o8/id?id=AItOawnOvt3TwSSDOLnoVzDNbOP1qO9OmNH5s0s"
- nickname="Fraser"
- subject="comment 6"
- date="2011-05-22T23:02:39Z"
- content="""
-Whups, the fix landed in git's `maint' branch just after 1.7.5 but 1.7.5.1 was
-tagged on a different branch.
-
-Will look closer in future, and let you know when it's really released.
-"""]]
diff --git a/doc/download/comment_7_a5eebd214b135f34b18274a682211943._comment b/doc/download/comment_7_a5eebd214b135f34b18274a682211943._comment
deleted file mode 100644
index 9960e0ea85..0000000000
--- a/doc/download/comment_7_a5eebd214b135f34b18274a682211943._comment
+++ /dev/null
@@ -1,8 +0,0 @@
-[[!comment format=mdwn
- username="https://www.google.com/accounts/o8/id?id=AItOawnOvt3TwSSDOLnoVzDNbOP1qO9OmNH5s0s"
- nickname="Fraser"
- subject="comment 7"
- date="2011-05-27T01:27:37Z"
- content="""
-v1.7.5.3 has it.
-"""]]
diff --git a/doc/download/comment_8_59a976de6c7d333709b92f7cd5830850._comment b/doc/download/comment_8_59a976de6c7d333709b92f7cd5830850._comment
deleted file mode 100644
index 5aa4f8c94a..0000000000
--- a/doc/download/comment_8_59a976de6c7d333709b92f7cd5830850._comment
+++ /dev/null
@@ -1,8 +0,0 @@
-[[!comment format=mdwn
- username="http://joey.kitenet.net/"
- nickname="joey"
- subject="comment 8"
- date="2011-05-28T16:04:51Z"
- content="""
-And that is now installed on kitenet.net and verified to work.
-"""]]
diff --git a/doc/encryption.mdwn b/doc/encryption.mdwn
index 0f83bb7f90..cc61fea6f7 100644
--- a/doc/encryption.mdwn
+++ b/doc/encryption.mdwn
@@ -33,3 +33,16 @@ Note that once a key has been given access to a remote, it's not
 possible to revoke that access, short of deleting the remote. See
 [[encryption_design|design/encryption]] for other security risks
 associated with encryption.
+
+## shared cipher mode
+
+Alternatively, you can configure git-annex to use a shared cipher to
+encrypt data stored in a remote. This shared cipher is stored,
+**unencrypted** in the git repository. So it's shared amoung every
+clone of the git repository. The advantage is you don't need to set up gpg
+keys. The disadvantage is that this is **insecure** unless you
+trust every clone of the git repository with access to the encrypted data
+stored in the special remote.
+
+To use shared encryption, specify "encryption=shared" when first setting
+up a special remote.
diff --git a/doc/favicon.ico b/doc/favicon.ico
new file mode 100644
index 0000000000..5bb405931f
Binary files /dev/null and b/doc/favicon.ico differ
diff --git a/doc/forum/Getting_started_with_Amazon_S3.mdwn b/doc/forum/Getting_started_with_Amazon_S3.mdwn
new file mode 100644
index 0000000000..1ee86b57fa
--- /dev/null
+++ b/doc/forum/Getting_started_with_Amazon_S3.mdwn
@@ -0,0 +1,28 @@
+I'm just getting started with git-annex and trying to wrap my head around using it with Amazon S3. I am familiar with using git, but things are a bit different as we can't init a repo at S3 directly.
+
+I've followed http://git-annex.branchable.com/tips/using_Amazon_S3/, and performed:
+
+`git init`<br/>
+Initialized empty Git repository in /home/<br/>
+`git annex init`<br/>
+init  ok<br/>
+`git annex initremote s3 type=S3 encryption=FOOBAR bucket=foo`<br/>
+initremote s3 (encryption setup with gpg key YGTVT51715TFR) (checking bucket...) (gpg) ok<br/>
+`git annex describe s3 "Amazon S3"`<br/>
+describe s3 ok<br/>
+`git annexx add foo/`<br/>
+add foo/bar.txt<br/>
+add foo/bar.png<br/>
+...etc<br/>
+`git annex sync`<br/>
+51 files changed, 51 insertions(+)<br/>
+create mode 120000 foo/bar.txt<br/>
+create mode 120000 foo/bar.png<br/>
+...etc<br/>
+
+
+Looking at http://git-annex.branchable.com/git-annex/, I thought the files added would then be pushed to S3 by git annex sync, but that doesn't seem to be the case. I've also tried variations of got annex copy, like `git annex copy . --to s3`, without any luck.
+
+Is there a way to push to s3?
+
+Any help is appreciated!
diff --git a/doc/forum/Getting_started_with_Amazon_S3/comment_1_f50883133d5d4903cc95c0dcaa52d052._comment b/doc/forum/Getting_started_with_Amazon_S3/comment_1_f50883133d5d4903cc95c0dcaa52d052._comment
new file mode 100644
index 0000000000..b2211fa6c1
--- /dev/null
+++ b/doc/forum/Getting_started_with_Amazon_S3/comment_1_f50883133d5d4903cc95c0dcaa52d052._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="4.153.81.112"
+ subject="comment 1"
+ date="2012-05-29T19:09:50Z"
+ content="""
+`git annex sync` only syncs git metadata, not file contents, and metadata is not stored on S3, so it does notthing (much).
+
+`git annex move . --to s3` or `git annex copy . --to s3` is the right way to send the files to S3. I'm not sure why you say it's not working. I'd try it but Amazon is not letting me sign up for S3 again right now. Can you show what goes wrong with copy?
+"""]]
diff --git a/doc/forum/Getting_started_with_Amazon_S3/comment_2_e90aa3259d9a12cd67daa27d42d69ab5._comment b/doc/forum/Getting_started_with_Amazon_S3/comment_2_e90aa3259d9a12cd67daa27d42d69ab5._comment
new file mode 100644
index 0000000000..742e8d4469
--- /dev/null
+++ b/doc/forum/Getting_started_with_Amazon_S3/comment_2_e90aa3259d9a12cd67daa27d42d69ab5._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnoUOqs_lbuWyZBqyU6unHgUduJwDDgiKY"
+ nickname="Matt"
+ subject="comment 2"
+ date="2012-05-30T00:40:45Z"
+ content="""
+It's strange. I've done some testing on another machine, and this one, and the issue seems to be with adding only certain sub-directories of the git-annex directory. Would it cause an issue with git-annex if a sub-directory was a git repo?
+"""]]
diff --git a/doc/forum/Getting_started_with_Amazon_S3/comment_3_c3adce7c0f29e71ed9dd07103ede2c1a._comment b/doc/forum/Getting_started_with_Amazon_S3/comment_3_c3adce7c0f29e71ed9dd07103ede2c1a._comment
new file mode 100644
index 0000000000..450a1513ce
--- /dev/null
+++ b/doc/forum/Getting_started_with_Amazon_S3/comment_3_c3adce7c0f29e71ed9dd07103ede2c1a._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="4.153.81.112"
+ subject="comment 3"
+ date="2012-05-30T00:54:38Z"
+ content="""
+If the subdirectory has a .git, then it's a separate git repo, and inside the directory, all git (and git-annex) commands in it will operate on that nested repo and ignore the outside one.
+"""]]
diff --git a/doc/forum/Git_Annex_Transfer_Protocols.mdwn b/doc/forum/Git_Annex_Transfer_Protocols.mdwn
new file mode 100644
index 0000000000..d6a660a2d8
--- /dev/null
+++ b/doc/forum/Git_Annex_Transfer_Protocols.mdwn
@@ -0,0 +1,9 @@
+Hi,
+
+May I know, which processes git-annex is using to move/copy/get file content between repositories?
+Is it using same processes which git uses, Like send-pack, receive-pack.
+I want to use Aspera to move file contents between repositories.
+Is it enough if I customize send-pack, receive-pack of git code to do Aspera file transfer or git-annex uses any other transfer mechanism.
+
+Many Thanks,
+Royal Pinto
diff --git a/doc/forum/Git_Annex_Transfer_Protocols/comment_1_a870ec991078c95a6bb683d6962ab56e._comment b/doc/forum/Git_Annex_Transfer_Protocols/comment_1_a870ec991078c95a6bb683d6962ab56e._comment
new file mode 100644
index 0000000000..31c463470c
--- /dev/null
+++ b/doc/forum/Git_Annex_Transfer_Protocols/comment_1_a870ec991078c95a6bb683d6962ab56e._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="4.153.2.186"
+ subject="rsync over ssh"
+ date="2012-05-10T18:18:01Z"
+ content="""
+Some other protocols such as S3 for special remotes.
+"""]]
diff --git a/doc/forum/Git_Annex_Transfer_Protocols/comment_2_71419376ef50a679ea8f0f9e16991c17._comment b/doc/forum/Git_Annex_Transfer_Protocols/comment_2_71419376ef50a679ea8f0f9e16991c17._comment
new file mode 100644
index 0000000000..2e07aef088
--- /dev/null
+++ b/doc/forum/Git_Annex_Transfer_Protocols/comment_2_71419376ef50a679ea8f0f9e16991c17._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawlYu7QmD7wrbHWkoxuriaA9XcijM-g5vrQ"
+ nickname="Royal"
+ subject="Protocols to transfer file content"
+ date="2012-05-10T18:48:40Z"
+ content="""
+Thanks, Is git annex is using same protocols as normal git to transfer content between normal git repositories?
+"""]]
diff --git a/doc/forum/Git_Annex_Transfer_Protocols/comment_3_fea43664a500111ca99f4043e0dadb14._comment b/doc/forum/Git_Annex_Transfer_Protocols/comment_3_fea43664a500111ca99f4043e0dadb14._comment
new file mode 100644
index 0000000000..6e7b36e311
--- /dev/null
+++ b/doc/forum/Git_Annex_Transfer_Protocols/comment_3_fea43664a500111ca99f4043e0dadb14._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="4.153.2.186"
+ subject="comment 3"
+ date="2012-05-10T18:51:56Z"
+ content="""
+git-annex doesn't transfer git content between git repositories. You use git for that. Well, git-annex sync can run a few git commands for you to do it.
+"""]]
diff --git a/doc/forum/Git_Annex_Transfer_Protocols/comment_4_56fb2dab1d4030c9820be32b495afdf0._comment b/doc/forum/Git_Annex_Transfer_Protocols/comment_4_56fb2dab1d4030c9820be32b495afdf0._comment
new file mode 100644
index 0000000000..fef10cd813
--- /dev/null
+++ b/doc/forum/Git_Annex_Transfer_Protocols/comment_4_56fb2dab1d4030c9820be32b495afdf0._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawlYu7QmD7wrbHWkoxuriaA9XcijM-g5vrQ"
+ nickname="Royal"
+ subject="Git annex content transfer protocols"
+ date="2012-05-10T19:13:48Z"
+ content="""
+Sorry if I am not clear. Actually i meant to ask, if i have 2 git repositories which are not special remotes and I am transferring annexed file content between these repositories using git annex command (move or copy) then, which protocol it uses to transfer content? Is it uses git-send-pack git-recieve-pack or some other protocols. 
+"""]]
diff --git a/doc/forum/Git_Annex_Transfer_Protocols/comment_5_a6ec9c5a4a3c0bac1df87f1df9be140b._comment b/doc/forum/Git_Annex_Transfer_Protocols/comment_5_a6ec9c5a4a3c0bac1df87f1df9be140b._comment
new file mode 100644
index 0000000000..be25737c1d
--- /dev/null
+++ b/doc/forum/Git_Annex_Transfer_Protocols/comment_5_a6ec9c5a4a3c0bac1df87f1df9be140b._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="4.153.2.186"
+ subject="comment 5"
+ date="2012-05-10T19:17:22Z"
+ content="""
+rsync over ssh is used to transfer file contents between repositories. (You can use the -d option to see the commands git-annex runs.)
+"""]]
diff --git a/doc/forum/Git_Annex_Transfer_Protocols/comment_6_1678452fb7114aeabcf0cc3d5f6c69b0._comment b/doc/forum/Git_Annex_Transfer_Protocols/comment_6_1678452fb7114aeabcf0cc3d5f6c69b0._comment
new file mode 100644
index 0000000000..b7ef8f33c4
--- /dev/null
+++ b/doc/forum/Git_Annex_Transfer_Protocols/comment_6_1678452fb7114aeabcf0cc3d5f6c69b0._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawlYu7QmD7wrbHWkoxuriaA9XcijM-g5vrQ"
+ nickname="Royal"
+ subject="comment 6"
+ date="2012-05-10T19:21:08Z"
+ content="""
+Ok. This helped me a lot. Thank you
+"""]]
diff --git a/doc/forum/Making_git-annex_less_necessary.mdwn b/doc/forum/Making_git-annex_less_necessary.mdwn
new file mode 100644
index 0000000000..086c051398
--- /dev/null
+++ b/doc/forum/Making_git-annex_less_necessary.mdwn
@@ -0,0 +1,5 @@
+http://git-annex.branchable.com/walkthrough/ says "Git wants to first stage the entire contents of the file in its index. That can be slow for big files (sorta why git-annex exists in the first place)."<br/>
+What is git doing that git-annex isn't, other than copying the file to .git/objects rather than just moving it to .git/annex/objects, prepending it with "blob"+length, and compressing it? If git were changed to store the "blob"+length as part of the object filename rather than as part of the object file content, have a config option to use uncompressed objects for large files (and not try to pack them when creating pack files), and were used on a filesystem such as zfs or btrfs which does COW so the copy would be as fast as a move, then what speed advantage would git-annex still have over git? I realize git-annex has more features than just big file handling, and has the worm backend for even faster handling, but I'm just talking about the case with the default sha backend.<br/>
+Have such changes been proposed for git? It seems that for anybody already familiar with the git codebase, adding the config option for uncompressed objects and moving the storage location for "blob"+length would be easy changes to make, and I see no downside to them. It wouldn't break backwards compatibility because the object filename being hash."blob".length rather than just hash would indicate that the new object format is in use, and a ".raw" filename extension could be used for uncompressed objects (or more sensibly, in the new format, no additional extension for uncompressed, and ".compressed" for compressed).<br/>
+This would also eliminate the need for a git-annex object store separate from the git object store, and the complexities involved with having them separate, and the need for symlinks, and the complexities they cause. I don't think that relying on COW for speed is unreasonable once btrfs becomes the default in major Linux distros (the bsds already have zfs and hammerfs); right now part of what git-annex is doing is just working around the functional deficiency of non-COW filesystems.<br/>
+P.S. I recommend a "plain" option for the page type when submitting comments on your wiki, so I don't have to put HTML line break markup at the end of my lines.
diff --git a/doc/forum/Making_git-annex_less_necessary/comment_1_03faaa3866778d24cd03887b85dc9954._comment b/doc/forum/Making_git-annex_less_necessary/comment_1_03faaa3866778d24cd03887b85dc9954._comment
new file mode 100644
index 0000000000..3396643f66
--- /dev/null
+++ b/doc/forum/Making_git-annex_less_necessary/comment_1_03faaa3866778d24cd03887b85dc9954._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="4.153.2.245"
+ subject="comment 1"
+ date="2012-05-08T18:22:12Z"
+ content="""
+git's code base makes lots of assumptions hardcoding the size of the hash, etc. (grep its source for magic numbers 40 and 42...) I'd like to see git get parameratised hashes. SHA1 insecurity may evenutally push it in that direction. However, when I asked the git developers about this at the Gittogether last year, there were several ideas floated that would avoid parameterisation, and a lot of good thoughts about problems parameterised hashes would cause.
+
+Moving data into git proper would still leave the problems unique to large data of not being able to store it all on every clone. Which means a git-annex like thing is needed to track where the data resides and move it around.
+
+(BTW, in markdown, you separate paragraphs with blank lines. Like in email.)
+"""]]
diff --git a/doc/forum/Moving_older_version__39__s_file_content_without_doing_checkout.mdwn b/doc/forum/Moving_older_version__39__s_file_content_without_doing_checkout.mdwn
new file mode 100644
index 0000000000..3ed022b481
--- /dev/null
+++ b/doc/forum/Moving_older_version__39__s_file_content_without_doing_checkout.mdwn
@@ -0,0 +1,4 @@
+Hi,
+Is there any way I can move or copy file content of older version without doing checkout to that version, by passing commit hash as parameter in move command itself? 
+
+Thank you
diff --git a/doc/forum/Moving_older_version__39__s_file_content_without_doing_checkout/comment_1_f114b75b29123453758b493fae7f5167._comment b/doc/forum/Moving_older_version__39__s_file_content_without_doing_checkout/comment_1_f114b75b29123453758b493fae7f5167._comment
new file mode 100644
index 0000000000..a53c6bbd69
--- /dev/null
+++ b/doc/forum/Moving_older_version__39__s_file_content_without_doing_checkout/comment_1_f114b75b29123453758b493fae7f5167._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnpdM9F8VbtQ_H5PaPMpGSxPe_d5L1eJ6w"
+ nickname="Rafael"
+ subject="comment 1"
+ date="2012-05-15T07:59:57Z"
+ content="""
+I had a similiar question in forum/new_microfeatures/. I would like to fetch/copy all the annexed content from a repo, be it on the current branch, another branch, or corresponds to an old version of a file. A command like \"git annex copy --all --from=source [path]\" would then ensure I have access to all the content I need even if I have later no longer access to source. Sure I could use rsync.
+"""]]
diff --git a/doc/forum/Moving_older_version__39__s_file_content_without_doing_checkout/comment_2_e377b7614c2961b460a10e285f3db274._comment b/doc/forum/Moving_older_version__39__s_file_content_without_doing_checkout/comment_2_e377b7614c2961b460a10e285f3db274._comment
new file mode 100644
index 0000000000..18ff153ad0
--- /dev/null
+++ b/doc/forum/Moving_older_version__39__s_file_content_without_doing_checkout/comment_2_e377b7614c2961b460a10e285f3db274._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="4.153.2.51"
+ subject="comment 2"
+ date="2012-05-15T17:00:10Z"
+ content="""
+Yes, I think that [[todo/add_-all_option]] is the right approach for this. Seems unlikely you'd have some files' hashes handy without having them checked out, but operating on all content makes sense.
+
+That page discusses some problems implementing it for some commands, but should not pose a problem for `move`. It would also be possible to support `get` and `copy`, except `--auto` couldn't be used with `--all`. Even `fsck` could support it.
+"""]]
diff --git a/doc/forum/Preserving_file_access_rights_in_directory_tree_below_objects__47__/comment_2_9f51947b35ee04e473655e20d56c740a._comment b/doc/forum/Preserving_file_access_rights_in_directory_tree_below_objects__47__/comment_2_9f51947b35ee04e473655e20d56c740a._comment
new file mode 100644
index 0000000000..5d632ab860
--- /dev/null
+++ b/doc/forum/Preserving_file_access_rights_in_directory_tree_below_objects__47__/comment_2_9f51947b35ee04e473655e20d56c740a._comment
@@ -0,0 +1,16 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawlB7-aXsqwzOi2BIR_Q4sUF8sjj24H6F3c"
+ nickname="Claudius"
+ subject="comment 2"
+ date="2012-01-23T19:39:17Z"
+ content="""
+Thank you for your comment! Indeed, setting the umask to, for example, 022 has the desired effect that annex/objects etc. are executable (and in this special case also writable), my previous umask setting was 077; the \"strange\" permissions on the git directories was probably due to --shared=all, and the mode of \"440\" on the files within the git-annex tree is correct (the original file was 640 and stripped of its write permission).
+
+Using this umask setting and newgrp to switch the default group, I was successfully able to set up the repositories.
+
+However, I would like to suggest adding the execute bit to the directories below .git/annex/objects/ per default, even if the umask of the current shell differs. As the correct rights are already preserved in the actual files (minus their write permission) together with correct owner and group, the files are still protected the same way as previously, and because +x does not allow directory listings, no additional information can leak out either. Not having to set the umask to something \"sensible\" before operating git-annex would be a huge plus, too :)
+
+The reason why I am not running MPD as my user is that I am a bit wary of running an application even exposed to the local network as my main user, and I see nothing wrong with running it as its own user.
+
+Thank you again for your help and the time you put into this project!
+"""]]
diff --git a/doc/forum/What_can_be_done_in_case_of_conflict.mdwn b/doc/forum/What_can_be_done_in_case_of_conflict.mdwn
new file mode 100644
index 0000000000..42167a6091
--- /dev/null
+++ b/doc/forum/What_can_be_done_in_case_of_conflict.mdwn
@@ -0,0 +1,7 @@
+Hi,
+
+How can I resolve the conflict when it occurs?
+
+Suppose I have 2 branches (master, current), When I merge these branches or while doing cherry-pick, if I get conflict how can I resolve it?
+
+Thank You
diff --git a/doc/forum/What_can_be_done_in_case_of_conflict/comment_1_5ca86b099dfa08a50f656ea03bf1dcd9._comment b/doc/forum/What_can_be_done_in_case_of_conflict/comment_1_5ca86b099dfa08a50f656ea03bf1dcd9._comment
new file mode 100644
index 0000000000..6f1d241300
--- /dev/null
+++ b/doc/forum/What_can_be_done_in_case_of_conflict/comment_1_5ca86b099dfa08a50f656ea03bf1dcd9._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="http://joey.kitenet.net/"
+ nickname="joey"
+ subject="comment 1"
+ date="2012-04-23T14:29:03Z"
+ content="""
+You handle conflicts in annexed files the same as you would handle them in other binary files checked into git.
+
+For example, you might choose to `git rm` or `git add` the file to resolve the conflict.
+
+[[Previous_discussion|forum/A_really_stupid_question]]
+"""]]
diff --git a/doc/forum/What_happened_to_the_walkthrough__63__.mdwn b/doc/forum/What_happened_to_the_walkthrough__63__.mdwn
new file mode 100644
index 0000000000..e8098d29a1
--- /dev/null
+++ b/doc/forum/What_happened_to_the_walkthrough__63__.mdwn
@@ -0,0 +1 @@
+As of right now (2012-05-24 at 18:00 UTC), the [[Walkthrough]] page is basically empty. Its entire contents are "A walkthrough of the basic features of git-annex." No links (other than the autogenerated "what links to this page" list at the bottom) and no contents. Any idea what happened?
diff --git a/doc/forum/What_happened_to_the_walkthrough__63__/comment_1_70db0e3cfb1318e95671c23726e5541d._comment b/doc/forum/What_happened_to_the_walkthrough__63__/comment_1_70db0e3cfb1318e95671c23726e5541d._comment
new file mode 100644
index 0000000000..cbf852dbfb
--- /dev/null
+++ b/doc/forum/What_happened_to_the_walkthrough__63__/comment_1_70db0e3cfb1318e95671c23726e5541d._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawl9sYlePmv1xK-VvjBdN-5doOa_Xw-jH4U"
+ nickname="Richard"
+ subject="comment 1"
+ date="2012-05-24T19:18:55Z"
+ content="""
+It seems the pages that are supposed to be inlined are not being found even though they are in `doc/walkthrough/`.
+"""]]
diff --git a/doc/forum/What_happened_to_the_walkthrough__63__/comment_2_f9305dd19b9b5f35e66d915b8c30374b._comment b/doc/forum/What_happened_to_the_walkthrough__63__/comment_2_f9305dd19b9b5f35e66d915b8c30374b._comment
new file mode 100644
index 0000000000..9720adfbc6
--- /dev/null
+++ b/doc/forum/What_happened_to_the_walkthrough__63__/comment_2_f9305dd19b9b5f35e66d915b8c30374b._comment
@@ -0,0 +1,7 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ subject="comment 2"
+ date="2012-05-24T20:15:19Z"
+ content="""
+Broken last night during upgrade, fixed now, thanks for noticing.
+"""]]
diff --git a/doc/forum/Windows_support.mdwn b/doc/forum/Windows_support.mdwn
new file mode 100644
index 0000000000..0e9e8dcb6e
--- /dev/null
+++ b/doc/forum/Windows_support.mdwn
@@ -0,0 +1,6 @@
+Hi,
+
+Do you have any news about Windows support?
+Is this something you're currently working on?
+
+Thanks!
diff --git a/doc/forum/Windows_support/comment_1_23fa9aa3b00940a1c1b3876c35eef019._comment b/doc/forum/Windows_support/comment_1_23fa9aa3b00940a1c1b3876c35eef019._comment
new file mode 100644
index 0000000000..95323ff997
--- /dev/null
+++ b/doc/forum/Windows_support/comment_1_23fa9aa3b00940a1c1b3876c35eef019._comment
@@ -0,0 +1,9 @@
+[[!comment format=mdwn
+ username="http://joey.kitenet.net/"
+ nickname="joey"
+ subject="comment 1"
+ date="2012-03-12T06:43:02Z"
+ content="""
+[[todo/windows_support]] has everything I know about making a windows port. This badly needs someone who understand Windows to dive into it. The question of how to create a symbolic link (or the relevant Windows equivilant) from haskell on Windows
+is a good starting point..
+"""]]
diff --git a/doc/forum/__34__permission_denied__34___in_fsck_on_shared_repo.mdwn b/doc/forum/__34__permission_denied__34___in_fsck_on_shared_repo.mdwn
new file mode 100644
index 0000000000..f13aed2c2f
--- /dev/null
+++ b/doc/forum/__34__permission_denied__34___in_fsck_on_shared_repo.mdwn
@@ -0,0 +1,17 @@
+i'm getting errors in ``git annex fsck`` on a shared bare git repo with git-annex 3.20120418 local repo version 3:
+
+``git-annex: ${PATH}/${MYREPO}.git/annex/objects/${HA}/${SH}/SHA1-${HASH}/SHA1-${HASH}: setFileMode: permission denied (Operation not permitted)``
+
+the repository is shared among several users in a common group, and the repo is set up with sticky group, and with appropriate umasks, everything should work.
+
+however, even with the file having permissions -rw-rw-r-- in the directory with permissions drwxrwsr-x, owned by someone else but by a group i'm currently in (as verified by issuing `groups`), i get said error message.
+
+a strace reveals that the failing syscall is:
+
+``[pid 17626] chmod("${FILENAME}", 0100555) = -1 EPERM (Operation not permitted)``
+
+(maybe related: git annex looks for the file in another ${HA}/${SH} combination (of three digits instead of two digits each) before, i take it this is just a new feature not used by the data in my repo? also, i should add that the repository dates back to git-annex 0.13.)
+
+as a workaround, i'm currently ``sudo chown``ing all files to me before the check.
+
+why does fsck try to set permissions even if they are ok? is this a bug in my setup, and if yes, how is a shared repository set up correctly?
diff --git a/doc/forum/__34__permission_denied__34___in_fsck_on_shared_repo/comment_1_3a5202ef2116ebb5559b6f4d920755fc._comment b/doc/forum/__34__permission_denied__34___in_fsck_on_shared_repo/comment_1_3a5202ef2116ebb5559b6f4d920755fc._comment
new file mode 100644
index 0000000000..5a5cafa721
--- /dev/null
+++ b/doc/forum/__34__permission_denied__34___in_fsck_on_shared_repo/comment_1_3a5202ef2116ebb5559b6f4d920755fc._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="http://joey.kitenet.net/"
+ nickname="joey"
+ subject="comment 1"
+ date="2012-04-21T16:09:19Z"
+ content="""
+Well, the modes you show are wrong. Nothing in the annex should be writable. fsck needs to fix those. (It's true that it also always chmods even correct mode files/directories.. I've made a change avoiding that.)
+
+I have not thought or tried shared git annex repos with multiple unix users writing to them. ([[tips/Using_gitolite_with_git-annex]] would be an alternative.) Seems to me that removing content from the annex would also be a problem, since the directory will need to be chmodded to allow deleting the content from it, and that will fail if it's owned by someone else.  Perhaps git-annex needs to honor core.sharedRepository and avoid these nice safeguards on file modes then.
+"""]]
diff --git a/doc/forum/__34__permission_denied__34___in_fsck_on_shared_repo/comment_2_86663eeb75b0477f53c45f26c8e4b051._comment b/doc/forum/__34__permission_denied__34___in_fsck_on_shared_repo/comment_2_86663eeb75b0477f53c45f26c8e4b051._comment
new file mode 100644
index 0000000000..1c9bfbfe40
--- /dev/null
+++ b/doc/forum/__34__permission_denied__34___in_fsck_on_shared_repo/comment_2_86663eeb75b0477f53c45f26c8e4b051._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joey.kitenet.net/"
+ nickname="joey"
+ subject="comment 2"
+ date="2012-04-21T23:46:42Z"
+ content="""
+All right, I've made all the changes so it supports `core.sharedRepository`.
+"""]]
diff --git a/doc/forum/__34__permission_denied__34___in_fsck_on_shared_repo/comment_3_c336b2b07cd006d378e5be9639ff17ec._comment b/doc/forum/__34__permission_denied__34___in_fsck_on_shared_repo/comment_3_c336b2b07cd006d378e5be9639ff17ec._comment
new file mode 100644
index 0000000000..fd75f2f856
--- /dev/null
+++ b/doc/forum/__34__permission_denied__34___in_fsck_on_shared_repo/comment_3_c336b2b07cd006d378e5be9639ff17ec._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="http://christian.amsuess.com/chrysn"
+ nickname="chrysn"
+ subject="comment 3"
+ date="2012-04-23T14:14:28Z"
+ content="""
+thanks, that's great. will there be a way to have sharedRepository work for shared remotes (rsync, directory) too, or is that better taken care of by acls?
+
+@not thought of shared repos: we're having our family photo archive spread over our laptops, and backed up on our home storage server and on an rsync+encryption off-site server, with everyone naturally having their own accounts on all systems -- just if you need a use case.
+"""]]
diff --git a/doc/forum/__34__permission_denied__34___in_fsck_on_shared_repo/comment_4_1339cd27ca2955f30b01ecf4da7d6fe8._comment b/doc/forum/__34__permission_denied__34___in_fsck_on_shared_repo/comment_4_1339cd27ca2955f30b01ecf4da7d6fe8._comment
new file mode 100644
index 0000000000..568f11330c
--- /dev/null
+++ b/doc/forum/__34__permission_denied__34___in_fsck_on_shared_repo/comment_4_1339cd27ca2955f30b01ecf4da7d6fe8._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="http://joey.kitenet.net/"
+ nickname="joey"
+ subject="comment 4"
+ date="2012-04-23T14:35:39Z"
+ content="""
+I'm not currently planning to support sharedRepository perms on special remotes. I suppose I could be convinced otherwise, it's perhaps doable for the ones you mention (rsync might be tricky). (bup special remote already supports it of course.)
+
+thanks for the use case!
+"""]]
diff --git a/doc/forum/cloud_services_to_support.mdwn b/doc/forum/cloud_services_to_support.mdwn
index e268bc1d86..4d6bde1b54 100644
--- a/doc/forum/cloud_services_to_support.mdwn
+++ b/doc/forum/cloud_services_to_support.mdwn
@@ -1,5 +1,5 @@
 git-annex can already be used to store data in several cloud services:
-Amazon S3, rsync.net, Tahoe-LAFFS, The Internet Archive.
+Amazon S3, rsync.net, Tahoe-LAFS, The Internet Archive.
 
 I would like to support as many other cloud services as possible/reasonable.
 
diff --git a/doc/forum/error_in_installation_of_base-4.5.0.0.mdwn b/doc/forum/error_in_installation_of_base-4.5.0.0.mdwn
new file mode 100644
index 0000000000..673222ed6d
--- /dev/null
+++ b/doc/forum/error_in_installation_of_base-4.5.0.0.mdwn
@@ -0,0 +1,14 @@
+Hi,
+
+I was trying to install git-annex, but then, I got a warning saying that I need to install base-4.5.0.0 first.
+
+So, I did "sudo cabal install base-4.5.0.0". Everything was going well, until I got this error:
+
+config.status: error: cannot find input file: `base.buildinfo.in'
+cabal: Error: some packages failed to install:
+base-4.5.0.0 failed during the configure step. The exception was:
+ExitFailure 1
+
+I tried to look for information on the internet, but I did not find anything useful.
+
+I know that this is not totally related to git-annex, but anyone has any thoughts on this?
diff --git a/doc/forum/error_in_installation_of_base-4.5.0.0/comment_1_0b2f79c014e0dd9badd52b8b6aa47e0c._comment b/doc/forum/error_in_installation_of_base-4.5.0.0/comment_1_0b2f79c014e0dd9badd52b8b6aa47e0c._comment
new file mode 100644
index 0000000000..5a52a28ab1
--- /dev/null
+++ b/doc/forum/error_in_installation_of_base-4.5.0.0/comment_1_0b2f79c014e0dd9badd52b8b6aa47e0c._comment
@@ -0,0 +1,19 @@
+[[!comment format=mdwn
+ username="http://joey.kitenet.net/"
+ nickname="joey"
+ subject="comment 1"
+ date="2012-04-22T05:39:28Z"
+ content="""
+git-annex needs ghc 7.4, that's why it depends on that base version that comes with it. So you either need to upgrade your ghc, or you can build from the `ghc7.0` branch in [[git|download]], like this:
+
+<pre>
+git clone git://git-annex.branchable.com/ git-annex
+cd git-annex
+git checkout ghc7.0
+cabal update
+cabal install --only-dependencies
+cabal configure
+cabal build
+cabal install --bindir=$HOME/bin
+</pre>
+"""]]
diff --git a/doc/forum/error_in_installation_of_base-4.5.0.0/comment_2_3badd64e48fbb174cd7de1ac9589bedf._comment b/doc/forum/error_in_installation_of_base-4.5.0.0/comment_2_3badd64e48fbb174cd7de1ac9589bedf._comment
new file mode 100644
index 0000000000..3ad1a11388
--- /dev/null
+++ b/doc/forum/error_in_installation_of_base-4.5.0.0/comment_2_3badd64e48fbb174cd7de1ac9589bedf._comment
@@ -0,0 +1,31 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkaT0B6s9jQuMzQUYRVBgWqtO7BhT_ZSaE"
+ nickname="Fernando Seabra"
+ subject="comment 2"
+ date="2012-04-22T14:09:33Z"
+ content="""
+Thanks for the fast response!
+
+Unfortunately, I had another problem:
+
+==================================
+Building git-annex-3.20120419...
+Utility/libdiskfree.c: In function ‘diskfree’:
+
+Utility/libdiskfree.c:61:0:
+     warning: ‘statfs64’ is deprecated (declared at /usr/include/sys/mount.h:379)
+[  6 of 157] Compiling Build.SysConfig  ( Build/SysConfig.hs, dist/build/git-annex/git-annex-tmp/Build/SysConfig.o )
+[ 15 of 157] Compiling Utility.Touch    ( dist/build/git-annex/git-annex-tmp/Utility/Touch.hs, dist/build/git-annex/git-annex-tmp/Utility/Touch.o )
+
+Utility/Touch.hsc:118:21: Not in scope: `noop'
+cabal: Error: some packages failed to install:
+git-annex-3.20120419 failed during the building phase. The exception was:
+ExitFailure 1
+==================================
+
+I also tried to look for information on the internet, and I did not find anything useful.
+Any idea of what happened?
+
+Thanks again!
+
+"""]]
diff --git a/doc/forum/error_in_installation_of_base-4.5.0.0/comment_3_d8190061ac1c683a7b699cf42e9db694._comment b/doc/forum/error_in_installation_of_base-4.5.0.0/comment_3_d8190061ac1c683a7b699cf42e9db694._comment
new file mode 100644
index 0000000000..d9de5089e9
--- /dev/null
+++ b/doc/forum/error_in_installation_of_base-4.5.0.0/comment_3_d8190061ac1c683a7b699cf42e9db694._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joey.kitenet.net/"
+ nickname="joey"
+ subject="comment 3"
+ date="2012-04-22T15:23:26Z"
+ content="""
+That's my fault, I made a change last night that caused the noop problem. Fixed now.
+"""]]
diff --git a/doc/forum/error_in_installation_of_base-4.5.0.0/comment_4_49a4fcd2dc4f97d4055b5051feea5e3b._comment b/doc/forum/error_in_installation_of_base-4.5.0.0/comment_4_49a4fcd2dc4f97d4055b5051feea5e3b._comment
new file mode 100644
index 0000000000..ba99334511
--- /dev/null
+++ b/doc/forum/error_in_installation_of_base-4.5.0.0/comment_4_49a4fcd2dc4f97d4055b5051feea5e3b._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkaT0B6s9jQuMzQUYRVBgWqtO7BhT_ZSaE"
+ nickname="Fernando Seabra"
+ subject="comment 4"
+ date="2012-04-22T16:08:55Z"
+ content="""
+Thanks, it worked now!
+"""]]
diff --git a/doc/forum/fail_to_git_annex_add_some_files:_getFileStatus:_does_not_exist__40__v_3.20111231__41__/comment_3_692f268218690437138ae0540c879425._comment b/doc/forum/fail_to_git_annex_add_some_files:_getFileStatus:_does_not_exist__40__v_3.20111231__41__/comment_3_692f268218690437138ae0540c879425._comment
new file mode 100644
index 0000000000..d5c84b431f
--- /dev/null
+++ b/doc/forum/fail_to_git_annex_add_some_files:_getFileStatus:_does_not_exist__40__v_3.20111231__41__/comment_3_692f268218690437138ae0540c879425._comment
@@ -0,0 +1,16 @@
+[[!comment format=mdwn
+ username="http://mildred.pip.verisignlabs.com/"
+ subject="Thank you a lot"
+ date="2012-04-13T07:28:10Z"
+ content="""
+Thank you,
+
+I imagined it was something like that.
+I 'm just sorry I posted that on the forum and not on the bugs section (I hadn't discovered it at that time). but now, if people search for this error, they should find this.
+
+Note for Fedora users: unfortunately GHC 7.4 will not be shipped with Fedora 17 (which is still not released). The [feature page](https://fedoraproject.org/wiki/Features/GHC74) mention it for Fedora 18. I feel like I am using debian ... outdated packages the day of the release.
+
+And many thanks for this wonderful piece of software.
+
+Mildred
+"""]]
diff --git a/doc/forum/retrieving_previous_versions.mdwn b/doc/forum/retrieving_previous_versions.mdwn
new file mode 100644
index 0000000000..7626b7935b
--- /dev/null
+++ b/doc/forum/retrieving_previous_versions.mdwn
@@ -0,0 +1,7 @@
+Hi,
+
+This might be a stupid question, but I did not find any information about it.
+Can I retrieve previous versions of a file?
+Let's say, I wanna do a "git annex get file", but considering a specific commit id. Is it possible? Are all the versions of the files kept inside .git/annex/objects?
+
+Thanks!
diff --git a/doc/forum/retrieving_previous_versions/comment_1_a4e83f688d4ec9177e7bf520f12ed26d._comment b/doc/forum/retrieving_previous_versions/comment_1_a4e83f688d4ec9177e7bf520f12ed26d._comment
new file mode 100644
index 0000000000..ab2ecee317
--- /dev/null
+++ b/doc/forum/retrieving_previous_versions/comment_1_a4e83f688d4ec9177e7bf520f12ed26d._comment
@@ -0,0 +1,11 @@
+[[!comment format=mdwn
+ username="http://joey.kitenet.net/"
+ nickname="joey"
+ subject="comment 1"
+ date="2012-04-24T21:14:15Z"
+ content="""
+To get to a specific version of a file, you need to have a tag or a branch that includes that version of the file. Check out the branch and `git annex get $file`. 
+
+(Of course, even without a tag or branch, old file versions are retained, unless dropped with `unused`/`dropunused`.
+So you could even `git checkout $COMMITID`.)
+"""]]
diff --git a/doc/forum/tell_us_how_you__39__re_using_git-annex.mdwn b/doc/forum/tell_us_how_you__39__re_using_git-annex.mdwn
index 14ca838cf1..d289b9f50a 100644
--- a/doc/forum/tell_us_how_you__39__re_using_git-annex.mdwn
+++ b/doc/forum/tell_us_how_you__39__re_using_git-annex.mdwn
@@ -1,12 +1,6 @@
-Tell your git-annex stories here. Feel free to give as little or as much detail as appropriate about how you're using it. How's it working out for you?
+Tell your git-annex stories here. Feel free to give as little or as much detail
+as appropriate about how you're using it. How's it working out for you?
 
-I'll start with a comment a user just posted to IRC:
-
-<pre>
-oh my god, git-annex is amazing
-this is the revolution in fucking with gigantic piles of files that I've been waiting for
-</pre>
-
-And then my own story: I have a ton of drives. I have a lot of servers. I live in a cabin on **dialup** and often have 1 hour on broadband in a week to get everything I need. Without git-annex, managing all this would not be possible. It works perfectly for me, not a surprise since I wrote it, but still, it's a different level of "perfect" than anything I could put together before.
+See [[testimonials]] for some other stories.
 
 [[!meta author=Joey]]
diff --git a/doc/forum/tell_us_how_you__39__re_using_git-annex/comment_1_4884803ddee7f642a3ac995a19967a6a._comment b/doc/forum/tell_us_how_you__39__re_using_git-annex/comment_1_4884803ddee7f642a3ac995a19967a6a._comment
new file mode 100644
index 0000000000..2351378bca
--- /dev/null
+++ b/doc/forum/tell_us_how_you__39__re_using_git-annex/comment_1_4884803ddee7f642a3ac995a19967a6a._comment
@@ -0,0 +1,17 @@
+[[!comment format=mdwn
+ username="http://mildred.fr/"
+ subject="just amazing"
+ date="2012-04-12T17:12:41Z"
+ content="""
+git-annex is just amazing. I just started using it and for once, I have hope to be able to organize my files a little better than now.
+
+Currently, I have a huge homedir. From time to time, I move file away in external hard drives, then forget about them. When I want to look at them back, I just can't because I have forgotten where they are. I have also a ton of files on those drives that I can't access because they are not indexed. With git-annex I have hope to put all of these files on a git repository. I will be able to see them everywhere, and find them when I need to.
+
+I might stop loosing files for once.
+
+I might avoid having multiple copies of the same things over and over again, without knowing so. and regain some more disk space.
+
+For the moment, I'm archiving my photographs. But there is one thing that might not go very well: directory hierarchies where everything is important (file owner, specific permissions, symlinks). I won't just be able to blindly annex all of these files. But for the moment I'll stick at archiving ocuments and it should be amazing.
+
+[Mildred](http://mildred.fr)
+"""]]
diff --git a/doc/forum/tell_us_how_you__39__re_using_git-annex/comment_2_61f5054918e7b36c191454365bc7f3b7._comment b/doc/forum/tell_us_how_you__39__re_using_git-annex/comment_2_61f5054918e7b36c191454365bc7f3b7._comment
new file mode 100644
index 0000000000..3bd981c5db
--- /dev/null
+++ b/doc/forum/tell_us_how_you__39__re_using_git-annex/comment_2_61f5054918e7b36c191454365bc7f3b7._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="http://cgray.myopenid.com/"
+ nickname="cgray"
+ subject="comment 2"
+ date="2012-04-14T01:18:53Z"
+ content="""
+Git-annex has really helped me with my media files.  I have a big NAS drive where I keep all my music, tv, and movies files, each in their own git annex.  I tend to keep the media that I want to watch or listen to on my laptop and then drop it when it is done.  This way I don't have too much on my laptop at any one time, but I have a nice selection for when I'm traveling and don't have access to my NAS.
+
+Additionally, I have a mp3 player that will format itself randomly every few months or so.  I keep my podcasts on it in a git annex and in a git annex on my laptop.  When I am done with a podcast, I can delete it from the mp3 player and then sync that information with my laptop.  With this method, I have a backup of what should be on my mp3 player, so I don't need to worry about losing it all when the mp3 player decides it's had enough.
+"""]]
diff --git a/doc/forum/wishlist:_simpler_gpg_usage.mdwn b/doc/forum/wishlist:_simpler_gpg_usage.mdwn
new file mode 100644
index 0000000000..f09f817af1
--- /dev/null
+++ b/doc/forum/wishlist:_simpler_gpg_usage.mdwn
@@ -0,0 +1,10 @@
+This is my current understanding on how one must use gpg with git-annex:
+
+ * Generate(or copy around) a gpg key on every machine that needs to access the encrypted remote.
+ * git annex initremote myremote encryption=KEY for each key that you generated
+
+What I'm trying to figure out is if I can generate a no-passphrase gpg key and commit it to the repository, and have git-annex use that. That way any new clones of the annex automatically have access to any encrypted remotes, without having to do any key management.
+
+I think I can generate a no-passphrase key, but then I still have to manually copy it around to each machine.
+
+I'm not a huge gpg user so part of this is me wanting to avoid having to manage and keeping track of the keys.  This would probably be a non-issue if I used gpg on more machines and was more comfortable with it.
diff --git a/doc/forum/wishlist:_simpler_gpg_usage/comment_1_6923fa6ebc0bbe7d93edb1d01d7c46c5._comment b/doc/forum/wishlist:_simpler_gpg_usage/comment_1_6923fa6ebc0bbe7d93edb1d01d7c46c5._comment
new file mode 100644
index 0000000000..f96f5c3777
--- /dev/null
+++ b/doc/forum/wishlist:_simpler_gpg_usage/comment_1_6923fa6ebc0bbe7d93edb1d01d7c46c5._comment
@@ -0,0 +1,19 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawmBUR4O9mofxVbpb8JV9mEbVfIYv670uJo"
+ nickname="Justin"
+ subject="comment 1"
+ date="2012-04-29T01:41:57Z"
+ content="""
+Thinking about this more, I think minimally git-annex could support a
+
+    remote.<name>.gpg-options
+
+or
+
+    remote.<name>.gpg-keyring
+
+for options to be passed to gpg.  I'm not sure how automatically setting it to $ANNEX_ROOT/.gnupg/.. would work.
+
+
+I need to read the encryption code to fully understand it, but I also wonder if there is not also a way to just bypass gpg entirely and store the remote-encryption keys locally in plain text.
+"""]]
diff --git a/doc/forum/wishlist:_simpler_gpg_usage/comment_2_6fc874b6c391df242bd2592c4a65eae8._comment b/doc/forum/wishlist:_simpler_gpg_usage/comment_2_6fc874b6c391df242bd2592c4a65eae8._comment
new file mode 100644
index 0000000000..29eb11622a
--- /dev/null
+++ b/doc/forum/wishlist:_simpler_gpg_usage/comment_2_6fc874b6c391df242bd2592c4a65eae8._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="http://joey.kitenet.net/"
+ nickname="joey"
+ subject="comment 2"
+ date="2012-04-29T02:39:20Z"
+ content="""
+The encryption uses a symmetric cipher that is stored in the git repository already. It's just stored encrypted to the various gpg keys that have been configured to use it. It would certianly be possible to store the symmetric cipher unencrypted in the git repo. 
+
+I don't see your idea of gpg-options saving any work. It would still require you to do key distribution and run commands in each repo to set it up.
+"""]]
diff --git a/doc/forum/wishlist:_simpler_gpg_usage/comment_3_012f340c8c572fe598fc860c1046dabd._comment b/doc/forum/wishlist:_simpler_gpg_usage/comment_3_012f340c8c572fe598fc860c1046dabd._comment
new file mode 100644
index 0000000000..051f17a24b
--- /dev/null
+++ b/doc/forum/wishlist:_simpler_gpg_usage/comment_3_012f340c8c572fe598fc860c1046dabd._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joey.kitenet.net/"
+ nickname="joey"
+ subject="comment 3"
+ date="2012-04-29T02:41:38Z"
+ content="""
+BTW re your Tweet.. I was so happy to be able to use 'c i a' in Crypto.hs. :)
+"""]]
diff --git a/doc/forum/wishlist:_simpler_gpg_usage/comment_4_e0c2a13217b795964f3b630c001661ef._comment b/doc/forum/wishlist:_simpler_gpg_usage/comment_4_e0c2a13217b795964f3b630c001661ef._comment
new file mode 100644
index 0000000000..c9e3375414
--- /dev/null
+++ b/doc/forum/wishlist:_simpler_gpg_usage/comment_4_e0c2a13217b795964f3b630c001661ef._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawmBUR4O9mofxVbpb8JV9mEbVfIYv670uJo"
+ nickname="Justin"
+ subject="comment 4"
+ date="2012-04-29T03:09:03Z"
+ content="""
+I got a good laugh out of it :-)
+
+Storing the key unencrypted would make things easier..  I think at least for my use-cases I don't require another layer of protection on top of the ssh keys that provide access to the encrypted remotes themselves.
+"""]]
diff --git a/doc/forum/wishlist:_simpler_gpg_usage/comment_5_9668b58eb71901e1db8da7db38e068ca._comment b/doc/forum/wishlist:_simpler_gpg_usage/comment_5_9668b58eb71901e1db8da7db38e068ca._comment
new file mode 100644
index 0000000000..60b98bde5d
--- /dev/null
+++ b/doc/forum/wishlist:_simpler_gpg_usage/comment_5_9668b58eb71901e1db8da7db38e068ca._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joey.kitenet.net/"
+ nickname="joey"
+ subject="comment 5"
+ date="2012-04-29T18:04:13Z"
+ content="""
+encryption=shared is now supported
+"""]]
diff --git a/doc/git-annex.mdwn b/doc/git-annex.mdwn
index 72301c0719..c7de59cd2a 100644
--- a/doc/git-annex.mdwn
+++ b/doc/git-annex.mdwn
@@ -160,6 +160,15 @@ subdirectories).
   alternate locations from which the file can be downloaded. In this mode,
   addurl can be used both to add new files, or to add urls to existing files.
 
+* import [path ...]
+
+  Moves files from somewhere outside the git working copy, and adds them to
+  the annex. Individual files to import can be specified. 
+  If a directory is specified, all files in it are imported, and any
+  subdirectory structure inside it is preserved.
+
+	git annex import /media/camera/DCIM/
+
 # REPOSITORY SETUP COMMANDS
 
 * init [description]
@@ -235,13 +244,21 @@ subdirectories).
 
   To check for annexed data on a remote, specify --from.
 
-* dropunused [number ...]
+* dropunused [number|range ...]
 
   Drops the data corresponding to the numbers, as listed by the last
   `git annex unused`
 
+  You can also specify ranges of numbers, such as "1-1000".
+
   To drop the data from a remote, specify --from.
 
+* addunused [number|range ...]
+
+  Adds back files for the content corresponding to the numbers or ranges,
+  as listed by the last `git annex unused`. The files will have names
+  starting with "unused."
+
 * merge
 
   Automatically merges remote tracking branches */git-annex into
@@ -713,6 +730,16 @@ Here are all the supported configuration settings.
   (wget is always used in preference to curl if available).
   For example, to force ipv4 only, set it to "-4"
 
+* `annex.http-headers`
+
+  HTTP headers to send when downloading from the web. Multiple lines of
+  this option can be set, one per header.
+
+* `annex.http-headers-command`
+
+  If set, the command is run and each line of its output is used as a HTTP
+  header. This overrides annex.http-headers.
+
 * `remote.<name>.rsyncurl`
 
   Used by rsync special remotes, this configures
diff --git a/doc/index.mdwn b/doc/index.mdwn
index a54a1073e7..2de17df3ce 100644
--- a/doc/index.mdwn
+++ b/doc/index.mdwn
@@ -13,6 +13,7 @@ To get a feel for it, see the [[walkthrough]] or read about [[how_it_works]].
 * [[forum]]
 * [[comments]]
 * [[contact]]
+* [[testimonials]]
 * <a href="http://flattr.com/thing/84843/git-annex"><img src="https://api.flattr.com/button/flattr-badge-large.png" alt="Flattr this" title="Flattr this" /></a>
 
 [[News]]:
diff --git a/doc/install.mdwn b/doc/install.mdwn
index 04d961e006..fe0522aa05 100644
--- a/doc/install.mdwn
+++ b/doc/install.mdwn
@@ -8,6 +8,7 @@
 * [[openSUSE]]
 * [[ArchLinux]]
 * [[NixOS]]
+* [[Gentoo]]
 * Windows: [[sorry, not possible yet|todo/windows_support]]
 
 ## Using cabal
@@ -16,6 +17,9 @@ As a haskell package, git-annex can be installed using cabal. For example:
 
 	cabal install git-annex --bindir=$HOME/bin
 
+The above downloads the latest release. Alternatively, you can [[download]]
+it yourself and [[manually_build_with_cabal|install/cabal]].
+
 ## Installation by hand
 
 To build and use git-annex, you will need:
@@ -32,7 +36,7 @@ To build and use git-annex, you will need:
   * [TestPack](http://hackage.haskell.org/cgi-bin/hackage-scripts/package/testpack)
   * [QuickCheck 2](http://hackage.haskell.org/package/QuickCheck)
   * [HTTP](http://hackage.haskell.org/package/HTTP)
-  * [hS3](http://hackage.haskell.org/package/hS3)
+  * [hS3](http://hackage.haskell.org/package/hS3) (optional)
   * [json](http://hackage.haskell.org/package/json)
   * [IfElse](http://hackage.haskell.org/package/IfElse)
   * [bloomfilter](http://hackage.haskell.org/package/bloomfilter)
diff --git a/doc/install/ArchLinux.mdwn b/doc/install/ArchLinux.mdwn
index e531fc968e..68e8b81f1c 100644
--- a/doc/install/ArchLinux.mdwn
+++ b/doc/install/ArchLinux.mdwn
@@ -7,3 +7,13 @@ such as yaourt:
 <pre>
 $ yaourt -Sy git-annex
 </pre>
+
+----
+
+I'm told the AUR has some dependency problems currently.
+If it doesn't work, you can just use cabal:
+
+<pre>
+pacman -S git rsync curl wget gpg openssh cabal-install
+cabal install git-annex --bindir=$HOME/bin
+</pre>
diff --git a/doc/install/Fedora.mdwn b/doc/install/Fedora.mdwn
index 7e983597b2..50f1d78180 100644
--- a/doc/install/Fedora.mdwn
+++ b/doc/install/Fedora.mdwn
@@ -1,7 +1,18 @@
-Installation recipe for Fedora 14.
+Installation recipe for Fedora 14 thruough 17.
 
 <pre>
 sudo yum install ghc cabal-install
-sudo cabal update
-cabal install git-annex --bindir=$HOME/bin
+git clone git://git-annex.branchable.com/ git-annex
+cd git-annex
+git checkout ghc7.0
+cabal update
+cabal install --only-dependencies
+cabal configure
+cabal build
+cabal install --bindir=$HOME/bin
 </pre>
+
+Note: You can't just use `cabal install git-annex`, because Fedora does
+not yet ship ghc 7.4.
+
+[Status of getting a Fedora package](https://bugzilla.redhat.com/show_bug.cgi?id=662259)
diff --git a/doc/install/Gentoo.mdwn b/doc/install/Gentoo.mdwn
new file mode 100644
index 0000000000..feeaad739b
--- /dev/null
+++ b/doc/install/Gentoo.mdwn
@@ -0,0 +1,3 @@
+Gentoo users can: `emerge git-annex`
+
+A possibly more up-to-date version is in the haskell portage overlay.
diff --git a/doc/NixOS.mdwn b/doc/install/NixOS.mdwn
similarity index 67%
rename from doc/NixOS.mdwn
rename to doc/install/NixOS.mdwn
index 864184a23c..115f9fa532 100644
--- a/doc/NixOS.mdwn
+++ b/doc/install/NixOS.mdwn
@@ -2,4 +2,5 @@ Users of the [Nix package manager](http://nixos.org/) can install it by running:
 
     nix-env -i git-annex
 
-The build status of the package within Nix can be seen on the [Hydra Build Farm](http://hydra.nixos.org/job/nixpkgs/trunk/gitAndTools.gitAnnex).
+The build status of the package within Nix can be seen on the [Hydra Build
+Farm](http://hydra.nixos.org/job/nixpkgs/trunk/gitAndTools.gitAnnex).
diff --git a/doc/install/OSX.mdwn b/doc/install/OSX.mdwn
index f65e0bb4fa..3c24609684 100644
--- a/doc/install/OSX.mdwn
+++ b/doc/install/OSX.mdwn
@@ -1,19 +1,16 @@
-Install Haskel Platform from [[http://hackage.haskell.org/platform/mac.html]]. The version provided by Macports is too old to work with current versions of git-annex. Then execute
+Install the Haskell Platform from [[http://hackage.haskell.org/platform/mac.html]].
+The version provided by Macports is too old to work with current versions of git-annex.
+Then execute
 
 <pre>
 sudo port install git-core ossp-uuid md5sha1sum coreutils pcre
 
 sudo ln -s /opt/local/include/pcre.h  /usr/include/pcre.h # This is hack that allows pcre-light to find pcre
 
-# optional: this will enable the gnu tools, (to give sha224sum etc..., it does not override the BSD userland)
-export PATH=$PATH:/opt/local/libexec/gnubin
-
 sudo cabal update
 cabal install git-annex --bindir=$HOME/bin
 </pre>
 
-Originally posted by Jon at <https://gist.github.com/671785> --[[Joey]], modified by [[kristianrumberg]]
-
 See also:
 
 * [[forum/OSX__39__s_haskell-platform_statically_links_things]]
diff --git a/doc/install/OSX/comment_4_e6109a964064a2a799768a370e57801d._comment b/doc/install/OSX/comment_4_e6109a964064a2a799768a370e57801d._comment
new file mode 100644
index 0000000000..be3ba2be44
--- /dev/null
+++ b/doc/install/OSX/comment_4_e6109a964064a2a799768a370e57801d._comment
@@ -0,0 +1,30 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkO9tsPZkAxEulq2pGCdwz4md-LqB0RcMw"
+ nickname="Reimund"
+ subject="Problems with Base & Crypto"
+ date="2012-04-25T22:56:18Z"
+ content="""
+I got the following error message trying to install git-annex:
+
+    cabal: cannot configure git-annex-3.20120418. It requires base >=4.5 && <5
+    For the dependency on base >=4.5 && <5 there are these packages: base-4.5.0.0.
+    However none of them are available.
+    base-4.5.0.0 was excluded because of the top level dependency base -any
+
+These are the steps I performed to make it work
+
+1. Download [Ghc 7.4](http://www.haskell.org/ghc/download).
+2. Run `sudo cabal install git-annex --bindir=$HOME/bin`.
+3. Compilation of the Crypto-4.2.4 dependency failed since it's not updated to work with Ghc 7.4. You need to patch SHA2.hs (steps below).
+4. Run `sudo cabal install git-annex --bindir=$HOME/bin` a second time.
+
+The steps I did to patch the SHA2.hs file in Crypto-4.2.4:
+
+1. `cabal unpack crypto-4.2.4`
+2. `cd Crypto-4.2.4`
+3. `patch -p1 < crypto-4.2.4-ghc-7.4.patch`
+4. `sudo cabal install`.
+
+PS: I used [this patchfile](http://sources.gentoo.org/cgi-bin/viewvc.cgi/gentoo-x86/dev-haskell/crypto/files/crypto-4.2.4-ghc-7.4.patch?revision=1.1).
+Then I did the last step a third time.
+"""]]
diff --git a/doc/install/OSX/comment_5_50777853f808d57b957f8ce9a0f84b3d._comment b/doc/install/OSX/comment_5_50777853f808d57b957f8ce9a0f84b3d._comment
new file mode 100644
index 0000000000..eca1761786
--- /dev/null
+++ b/doc/install/OSX/comment_5_50777853f808d57b957f8ce9a0f84b3d._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnHrjHxJAm39x8DR4bnbazQO6H0nMNuY9c"
+ nickname="Damien"
+ subject="sha256"
+ date="2012-06-01T16:13:05Z"
+ content="""
+If you're missing the `sha256sum` command with Homebrew, it's provided by `coreutils`. You have to change your `$PATH` before running `cabal install git-annex.cabal`:
+
+    PATH=\"$(brew --prefix coreutils)/libexec/gnubin:$PATH\"
+"""]]
diff --git a/doc/install/OSX/comment_6_18a8df794aa0ddd294dbf17d3d4c7fe2._comment b/doc/install/OSX/comment_6_18a8df794aa0ddd294dbf17d3d4c7fe2._comment
new file mode 100644
index 0000000000..5cb813776b
--- /dev/null
+++ b/doc/install/OSX/comment_6_18a8df794aa0ddd294dbf17d3d4c7fe2._comment
@@ -0,0 +1,7 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ subject="comment 6"
+ date="2012-06-01T17:24:29Z"
+ content="""
+Last night I made it look in /opt/local/libexec/gnubin .. if there's another directory it could look in, let me know. I am reluctant to make it run the brew command directly.
+"""]]
diff --git a/doc/install/cabal.mdwn b/doc/install/cabal.mdwn
new file mode 100644
index 0000000000..180208211c
--- /dev/null
+++ b/doc/install/cabal.mdwn
@@ -0,0 +1,16 @@
+As a haskell package, git-annex can be installed using cabal. For example:
+
+	cabal update
+        cabal install git-annex --bindir=$HOME/bin
+
+The above downloads the latest release and installs it into a ~/bin/
+directory, which you can put in your PATH.
+
+But maybe you want something newer (or older). Then [[download]] the version
+you want, and use cabal as follows inside its source tree:
+
+	cabal update
+	cabal install --only-dependencies
+	cabal configure
+	cabal build
+	cabal install --bindir=$HOME/bin
diff --git a/doc/install/openSUSE.mdwn b/doc/install/openSUSE.mdwn
index 0383cbbf2a..73cbe585f6 100644
--- a/doc/install/openSUSE.mdwn
+++ b/doc/install/openSUSE.mdwn
@@ -1,4 +1,12 @@
-Unfortunately there is currently no git-annex rpm available for openSUSE; however it is possible to build it via cabal or from source as described on the [[install]] page.  Fulfilling the dependencies listed on that page should not be a problem, except for obtaining a suitable version of the Haskell library.
+Unfortunately there is currently no git-annex rpm available for openSUSE;
+however it is possible to build it via cabal or from source as described on
+the [[install]] page.  Fulfilling the dependencies listed on that page
+should not be a problem, except for obtaining a suitable version of the
+Haskell library.
 
-The last [official release of Haskell for openSUSE](https://build.opensuse.org/project/show?project=devel:languages:haskell) is quite old, and may not satisfy the dependencies needed by git-annex.  Fortunately [searching the openSUSE build service](http://software.opensuse.org/search?q=cabal&baseproject=openSUSE%3A11.4&lang=en&include_home=true&exclude_debug=true) reveals that Peter Trommler has built a [newer Haskell suite](https://build.opensuse.org/project/show?project=home%3Aptrommler%3Adevel%3Alanguages%3Ahaskell) based on ghc 7.2.
-To install this, simply click on the relevant "1-Click Install" link in the openSUSE build service search results.
+The last [official release of Haskell for openSUSE](https://build.opensuse.org/project/show?project=devel:languages:haskell)
+is quite old, and may not satisfy the dependencies needed by git-annex.
+Fortunately [searching the openSUSE build service](http://software.opensuse.org/search?q=cabal&baseproject=openSUSE%3A11.4&lang=en&include_home=true&exclude_debug=true)
+reveals that Peter Trommler has built a [newer Haskell suite](https://build.opensuse.org/project/show?project=home%3Aptrommler%3Adevel%3Alanguages%3Ahaskell)
+based on ghc 7.2. To install this, simply click on the relevant
+"1-Click Install" link in the openSUSE build service search results.
diff --git a/doc/internals.mdwn b/doc/internals.mdwn
index b2fd1e5545..a69a747e5d 100644
--- a/doc/internals.mdwn
+++ b/doc/internals.mdwn
@@ -39,6 +39,9 @@ space and then the description, followed by a timestamp. Example:
 	e605dca6-446a-11e0-8b2a-002170d25c55 laptop timestamp=1317929189.157237s
 	26339d22-446b-11e0-9101-002170d25c55 usb disk timestamp=1317929330.769997s
 
+If there are multiple lines for the same uuid, the one with the most recent
+timestamp wins. git-annex union merges this and other files.
+
 ## `remotes.log`
 
 Holds persistent configuration settings for [[special_remotes]] such as
@@ -80,7 +83,7 @@ Example:
 These files are designed to be auto-merged using git's [[union merge driver|git-union-merge]].
 The timestamps allow the most recent information to be identified.
 
-## `remote/web/aaa/bbb/*.log`
+## `aaa/bbb/*.log.web`
 
 These log files record urls used by the
 [[web_special_remote|special_remotes/web]]. Their format is similar
diff --git a/doc/news/version_3.20120106/comment_1_fb1a3135e2d9f39f2c372ccc2c50c85a._comment b/doc/news/version_3.20120106/comment_1_fb1a3135e2d9f39f2c372ccc2c50c85a._comment
deleted file mode 100644
index effd9c9a8f..0000000000
--- a/doc/news/version_3.20120106/comment_1_fb1a3135e2d9f39f2c372ccc2c50c85a._comment
+++ /dev/null
@@ -1,8 +0,0 @@
-[[!comment format=mdwn
- username="http://peter-simons.myopenid.com/"
- ip="77.186.134.113"
- subject="Not announced on Hackage?"
- date="2012-01-13T17:37:11Z"
- content="""
-We have the [latest version in NixOS](http://hydra.nixos.org/job/nixpkgs/trunk/gitAndTools.gitAnnex), but we cannot advertise that fact on Hackage because it seems the corresponding Cabal file hasn't been uploaded to <http://hackage.haskell.org/package/git-annex>. Is there any particular reason why Hackage doesn't know about this release?
-"""]]
diff --git a/doc/news/version_3.20120106/comment_2_ae292ca7294b6790233e545086c3ac2f._comment b/doc/news/version_3.20120106/comment_2_ae292ca7294b6790233e545086c3ac2f._comment
deleted file mode 100644
index 7e6920eb72..0000000000
--- a/doc/news/version_3.20120106/comment_2_ae292ca7294b6790233e545086c3ac2f._comment
+++ /dev/null
@@ -1,10 +0,0 @@
-[[!comment format=mdwn
- username="http://joey.kitenet.net/"
- nickname="joey"
- subject="comment 2"
- date="2012-01-13T17:52:46Z"
- content="""
-Uploading to hackage is a PITA (manual password entry and I am often on a slow link besides) and is not integrated with my regular release process, so I often forget to do it. I will try to upload the next release there again.
-
-You might add a page under [[install]] for your git-annex packages.
-"""]]
diff --git a/doc/news/version_3.20120106/comment_3_29ccda9ac458fd5cc9ec5508c62df6ea._comment b/doc/news/version_3.20120106/comment_3_29ccda9ac458fd5cc9ec5508c62df6ea._comment
deleted file mode 100644
index 1bb0c32cb1..0000000000
--- a/doc/news/version_3.20120106/comment_3_29ccda9ac458fd5cc9ec5508c62df6ea._comment
+++ /dev/null
@@ -1,12 +0,0 @@
-[[!comment format=mdwn
- username="http://peter-simons.myopenid.com/"
- ip="77.186.134.113"
- subject="comment 3"
- date="2012-01-13T18:48:28Z"
- content="""
-For what it's worth, the package `cabal-install` is pretty good for uploading packages to Hackages, among other things. It allows users to configure their username/password, and then making a release to Hackage is as simple as running:
-
-    cabal upload foo-version.tar.gz
-
-I use that to do releases of my stuff, too, and I'm quite happy. `cabal-install` has other features, too, of course.
-"""]]
diff --git a/doc/news/version_3.20120227/comment_1_f8fc894680f2a2e5b5e757a677414b42._comment b/doc/news/version_3.20120227/comment_1_f8fc894680f2a2e5b5e757a677414b42._comment
deleted file mode 100644
index aa3c5ce6d1..0000000000
--- a/doc/news/version_3.20120227/comment_1_f8fc894680f2a2e5b5e757a677414b42._comment
+++ /dev/null
@@ -1,8 +0,0 @@
-[[!comment format=mdwn
- username="http://peter-simons.myopenid.com/"
- ip="77.184.15.65"
- subject="Test-suite won't compile with GHC 7.4.x"
- date="2012-02-28T17:39:59Z"
- content="""
-The recent version requires GHC 7.4.x, but some dependencies for the test suite don't build with that compiler, i.e. the `testpack` library. Do you have any recommendation how to deal with that situation? I would like to update, but I would very much like to run the regression test suite, too.
-"""]]
diff --git a/doc/news/version_3.20120227/comment_2_ea5075cfecc50d5da2364931ef7a02d1._comment b/doc/news/version_3.20120227/comment_2_ea5075cfecc50d5da2364931ef7a02d1._comment
deleted file mode 100644
index d45e66026f..0000000000
--- a/doc/news/version_3.20120227/comment_2_ea5075cfecc50d5da2364931ef7a02d1._comment
+++ /dev/null
@@ -1,10 +0,0 @@
-[[!comment format=mdwn
- username="http://joey.kitenet.net/"
- nickname="joey"
- subject="comment 2"
- date="2012-02-29T04:27:47Z"
- content="""
-Here's the patch that was used to make testpack build with 7.4 on Debian:
-
-<http://anonscm.debian.org/gitweb/?p=pkg-haskell/haskell-testpack.git;a=blobdiff;f=src/Test/QuickCheck/Instances.hs;h=7e920a102a50de5812af32f9a308b80f61284caf;hp=ada6674c972a6cc518f84041172ed035e36aec98;hb=ef9f6c109bd3c20f40fa25e962c928a51e1277d8;hpb=1240a417b9e970ce71757abcb01437e5eac9ee0e>
-"""]]
diff --git a/doc/news/version_3.20120229/comment_1_18158b9be2313f49509d59295c7d3c90._comment b/doc/news/version_3.20120229/comment_1_18158b9be2313f49509d59295c7d3c90._comment
deleted file mode 100644
index c3d2cab59a..0000000000
--- a/doc/news/version_3.20120229/comment_1_18158b9be2313f49509d59295c7d3c90._comment
+++ /dev/null
@@ -1,8 +0,0 @@
-[[!comment format=mdwn
- username="http://peter-simons.myopenid.com/"
- ip="77.186.152.146"
- subject="How do you build the Crypto library with GHC 7.4.1?"
- date="2012-02-29T19:20:20Z"
- content="""
-`Crypto 4.2.4` doesn't seem to compile with GHC 7.4.1. How did you build that package?
-"""]]
diff --git a/doc/news/version_3.20120229/comment_2_03436ddda42decf8cb1b4d5316d88a75._comment b/doc/news/version_3.20120229/comment_2_03436ddda42decf8cb1b4d5316d88a75._comment
deleted file mode 100644
index b08712ee8f..0000000000
--- a/doc/news/version_3.20120229/comment_2_03436ddda42decf8cb1b4d5316d88a75._comment
+++ /dev/null
@@ -1,14 +0,0 @@
-[[!comment format=mdwn
- username="http://joey.kitenet.net/"
- nickname="joey"
- subject="comment 2"
- date="2012-02-29T22:54:01Z"
- content="""
-Probably this patch will help with Crypto:
-
-<http://anonscm.debian.org/cgi-bin/darcsweb.cgi?r=pkg-haskell/haskell-crypto;a=filediff;h=20120213034652-b2814-0019a3f92e453e9be86166d6c1f1bc0dad6e4d12.gz;f=patches/class-constraints.diff>
-
-Or, there's the `ghc7.0` branch of git-annex in git, which can be used to build with the older, stable ghc.
-
-BTW, when asking, for help, a log of the build failure is always a good idea..
-"""]]
diff --git a/doc/news/version_3.20120229/comment_3_8f7f8d4758804f1b695925934219745a._comment b/doc/news/version_3.20120229/comment_3_8f7f8d4758804f1b695925934219745a._comment
deleted file mode 100644
index a31a182cca..0000000000
--- a/doc/news/version_3.20120229/comment_3_8f7f8d4758804f1b695925934219745a._comment
+++ /dev/null
@@ -1,42 +0,0 @@
-[[!comment format=mdwn
- username="http://peter-simons.myopenid.com/"
- ip="77.186.165.208"
- subject="comment 3"
- date="2012-03-05T21:10:47Z"
- content="""
-Unfortunately, the patch you mentioned doesn't seem to address the problem. I'm getting the following compile error:
-
-    Data/Digest/SHA2.hs:111:4:
-        Could not deduce (Show a) arising from a use of `showHex'
-        from the context (Integral a)
-          bound by the instance declaration at Data/Digest/SHA2.hs:109:10-39
-        Possible fix:
-          add (Show a) to the context of the instance declaration
-        In the first argument of `(.)', namely `(showHex a)'
-        In the expression:
-          (showHex a)
-          . (' ' :)
-            . (showHex b)
-              . (' ' :)
-                . (showHex c)
-                  . (' ' :)
-                    . (showHex d)
-                      . (' ' :)
-                        . (showHex e)
-                          . (' ' :)
-                            . (showHex f) . (' ' :) . (showHex g) . (' ' :) . (showHex h)
-        In an equation for `showsPrec':
-            showsPrec _ (Hash8 a b c d e f g h)
-              = (showHex a)
-                . (' ' :)
-                  . (showHex b)
-                    . (' ' :)
-                      . (showHex c)
-                        . (' ' :)
-                          . (showHex d)
-                            . (' ' :)
-                              . (showHex e)
-                                . (' ' :)
-                                  . (showHex f) . (' ' :) . (showHex g) . (' ' :) . (showHex h)
-
-"""]]
diff --git a/doc/news/version_3.20120229/comment_4_cd90223f78571e5bdd3dfc07ab1369d7._comment b/doc/news/version_3.20120229/comment_4_cd90223f78571e5bdd3dfc07ab1369d7._comment
deleted file mode 100644
index a931c7874a..0000000000
--- a/doc/news/version_3.20120229/comment_4_cd90223f78571e5bdd3dfc07ab1369d7._comment
+++ /dev/null
@@ -1,9 +0,0 @@
-[[!comment format=mdwn
- username="http://joey.kitenet.net/"
- nickname="joey"
- subject="comment 4"
- date="2012-03-05T21:32:00Z"
- content="""
-Hmm, I was able to produce exactly the same build error, and then I downloaded the patch I linked to before, and did
-`patch -p1 < debian/patches/class-constraints.diff` and that fixed the build nicely.
-"""]]
diff --git a/doc/news/version_3.20120229/comment_5_7dbf131ff4611abbfc8fbf1ee0f66dbe._comment b/doc/news/version_3.20120229/comment_5_7dbf131ff4611abbfc8fbf1ee0f66dbe._comment
deleted file mode 100644
index afddb3fb0a..0000000000
--- a/doc/news/version_3.20120229/comment_5_7dbf131ff4611abbfc8fbf1ee0f66dbe._comment
+++ /dev/null
@@ -1,8 +0,0 @@
-[[!comment format=mdwn
- username="http://peter-simons.myopenid.com/"
- ip="77.186.165.208"
- subject="comment 5"
- date="2012-03-05T23:29:41Z"
- content="""
-I didn't realize that the patch adds a patch file to the source distribution (instead of, well, patching it). That additional level of indirection surprised me. Anyway, now I figured it out and `Crypto` compiles fine. Thanks!
-"""]]
diff --git a/doc/news/version_3.20120230.mdwn b/doc/news/version_3.20120230.mdwn
deleted file mode 100644
index 52ac369e01..0000000000
--- a/doc/news/version_3.20120230.mdwn
+++ /dev/null
@@ -1,13 +0,0 @@
-git-annex 3.20120230 released with [[!toggle text="these changes"]]
-[[!toggleable text="""
-   * "here" can be used to refer to the current repository,
-     which can read better than the old "." (which still works too).
-   * Directory special remotes now support chunking files written to them,
-     avoiding writing files larger than a specified size.
-   * Add progress bar display to the directory special remote.
-   * Add configurable hooks that are run when git-annex starts and stops
-     using a remote: remote.name.annex-start-command and
-     remote.name.annex-stop-command
-   * Fix a bug in symlink calculation code, that triggered in rare
-     cases where an annexed file is in a subdirectory that nearly
-     matched to the .git/annex/object/xx/yy subdirectories."""]]
\ No newline at end of file
diff --git a/doc/news/version_3.20120230/comment_1_b975cbd3a01ba5c2fa0f24fe739d3433._comment b/doc/news/version_3.20120230/comment_1_b975cbd3a01ba5c2fa0f24fe739d3433._comment
deleted file mode 100644
index eb5c7d257b..0000000000
--- a/doc/news/version_3.20120230/comment_1_b975cbd3a01ba5c2fa0f24fe739d3433._comment
+++ /dev/null
@@ -1,128 +0,0 @@
-[[!comment format=mdwn
- username="https://www.google.com/accounts/o8/id?id=AItOawk_LOahrm_Cdg7io-_H0CNKkaxsRRQgRFo"
- nickname="Peter"
- subject="Test suite failure"
- date="2012-03-06T11:20:35Z"
- content="""
-I managed to compile this version of git-annex with GHC 7.4.1 on NixOS, but unfortunately the test suite fails during the `addurl` test:
-
-    Testing 0:quickcheck:0:prop_idempotent_deencode_git                           
-    Testing 0:quickcheck:1:prop_idempotent_deencode                               
-    Testing 0:quickcheck:2:prop_idempotent_fileKey                                
-    Testing 0:quickcheck:3:prop_idempotent_key_read_show                          
-    Testing 0:quickcheck:4:prop_idempotent_shellEscape                            
-    Testing 0:quickcheck:5:prop_idempotent_shellEscape_multiword                  
-    Testing 0:quickcheck:6:prop_idempotent_configEscape                           
-    Testing 0:quickcheck:7:prop_parentDir_basics                                  
-    Testing 0:quickcheck:8:prop_relPathDirToFile_basics                           
-    Testing 0:quickcheck:9:prop_relPathDirToFile_regressionTest                   
-    Testing 0:quickcheck:10:prop_cost_sane                                        
-    Testing 0:quickcheck:11:prop_hmacWithCipher_sane                              
-    Testing 0:quickcheck:12:prop_TimeStamp_sane                                   
-    Testing 0:quickcheck:13:prop_addLog_sane                                      
-    Testing 1:blackbox:0:git-annex init                                           
-    Testing 1:blackbox:1:git-annex add:0                                          
-    Testing 1:blackbox:1:git-annex add:1                                          
-    Testing 1:blackbox:1:git-annex add:2                                          
-    Testing 1:blackbox:2:git-annex reinject/fromkey                               
-    Testing 1:blackbox:3:git-annex unannex:0:no content                           
-    Testing 1:blackbox:3:git-annex unannex:1:with content                         
-    Testing 1:blackbox:4:git-annex drop:0:no remotes                              
-    Testing 1:blackbox:4:git-annex drop:1:with remote                             
-    Testing 1:blackbox:4:git-annex drop:2:untrusted remote                        
-    Testing 1:blackbox:5:git-annex get                                            
-    Testing 1:blackbox:6:git-annex move                                           
-    Testing 1:blackbox:7:git-annex copy                                           
-    Testing 1:blackbox:8:git-annex unlock/lock                                    
-    Testing 1:blackbox:9:git-annex edit/commit:0                                  
-    Cases: 55  Tried: 28  Errors: 0  Failures: 0add foo (checksum...) ok
-    ok
-    (Recording state in git...)
-    Testing 1:blackbox:9:git-annex edit/commit:1                                  
-    Testing 1:blackbox:10:git-annex fix                                           
-    Testing 1:blackbox:11:git-annex trust/untrust/semitrust/dead                  
-    Testing 1:blackbox:12:git-annex fsck:0                                        
-    Cases: 55  Tried: 32  Errors: 0  Failures: 0  Only 1 of 2 trustworthy copies exist of foo
-      Back it up with git-annex copy.
-      Only 1 of 2 trustworthy copies exist of sha1foo
-      Back it up with git-annex copy.
-      Bad file size (11 B larger); moved to /tmp/nix-build-jzvhzrdysy619y4vgmafryy9ck8mz7z7-git-annex-3.20120230.drv-0/git-annex/.t/tmprepo/.git/annex/bad/SHA256-s20--e394a389d787383843decc5d3d99b6d184ffa5fddeec23b911f9ee7fc8b9ea77
-      Bad file size (11 B larger); moved to /tmp/nix-build-jzvhzrdysy619y4vgmafryy9ck8mz7z7-git-annex-3.20120230.drv-0/git-annex/.t/tmprepo/.git/annex/bad/SHA1-s25--ee80d2cec57a3810db83b80e1b320df3a3721ffa
-    Testing 1:blackbox:12:git-annex fsck:1                                        
-    Testing 1:blackbox:12:git-annex fsck:2                                        
-    Cases: 55  Tried: 34  Errors: 0  Failures: 0  Only these untrusted locations may have copies of foo
-            17575c68-d5cc-4e18-bc96-fdafe716d488 -- origin (test repo)
-            17aab099-fcde-413a-8ef1-6acc09d7d081 -- here (.t/tmprepo)
-      Back it up to trusted locations with git-annex copy.
-      Only these untrusted locations may have copies of sha1foo
-            17575c68-d5cc-4e18-bc96-fdafe716d488 -- origin (test repo)
-      Back it up to trusted locations with git-annex copy.
-    Testing 1:blackbox:12:git-annex fsck:3                                        
-    Cases: 55  Tried: 35  Errors: 0  Failures: 0  Only 1 of 2 trustworthy copies exist of foo
-      Back it up with git-annex copy.
-      The following untrusted locations may also have copies: 
-            17575c68-d5cc-4e18-bc96-fdafe716d488 -- origin (test repo)
-      Only 1 of 2 trustworthy copies exist of sha1foo
-      Back it up with git-annex copy.
-      The following untrusted locations may also have copies: 
-            17575c68-d5cc-4e18-bc96-fdafe716d488 -- origin (test repo)
-    Testing 1:blackbox:13:git-annex migrate:0                                     
-    Testing 1:blackbox:13:git-annex migrate:1                                     
-    Testing 1:blackbox:14:git-annex unused/dropunused                             
-    Testing 1:blackbox:15:git-annex addurl                                        
-    Cases: 55  Tried: 39  Errors: 0  Failures: 0git-annex: connect: timeout (Connection timed out)
-    ### Failure in: 1:blackbox:15:git-annex addurl
-    addurl failed
-    Testing 1:blackbox:16:git-annex describe                                      
-    Testing 1:blackbox:17:git-annex find                                          
-    Cases: 55  Tried: 41  Errors: 0  Failures: 1foo
-    foo
-    sha1foo
-    sha1foo
-    Testing 1:blackbox:18:git-annex merge                                         
-    Testing 1:blackbox:19:git-annex status                                        
-    Cases: 55  Tried: 43  Errors: 0  Failures: 1{\"command\":\"status\",\"supported backends\":[\"SHA256\",\"SHA1\",\"SHA512\",\"SHA224\",\"SHA384\",\"SHA256E\",\"SHA1E\",\"SHA512E\",\"SHA224E\",\"SHA384E\",\"WORM\",\"URL\"],\"supported remote types\":[\"git\",\"S3\",\"bup\",\"directory\",\"rsync\",\"web\",\"hook\"],\"trusted repositories\":[],\"semitrusted repositories\":[{\"uuid\":\"00000000-0000-0000-0000-000000000001\",\"description\":\"web\",\"here\":false},{\"uuid\":\"17575c68-d5cc-4e18-bc96-fdafe716d488\",\"description\":\"origin (test repo)\",\"here\":false},{\"uuid\":\"5b9fe416-d6ed-4df7-af67-14fc5f2ea631\",\"description\":\".t/tmprepo\",\"here\":true}],\"untrusted repositories\":[],\"dead repositories\":[],\"local annex keys\":0,\"local annex size\":\"0 bytes\",\"known annex keys\":2,\"known annex size\":\"45 bytes\",\"success\":true}
-    Testing 1:blackbox:20:git-annex version                                       
-    Cases: 55  Tried: 44  Errors: 0  Failures: 1git-annex version: 3.20120230
-    local repository version: 3
-    default repository version: 3
-    supported repository versions: 3
-    upgrade supported from repository versions: 0 1 2
-    Testing 1:blackbox:21:git-annex sync                                          
-    Cases: 55  Tried: 45  Errors: 0  Failures: 1# On branch master
-    nothing to commit (working directory clean)
-    To /tmp/nix-build-jzvhzrdysy619y4vgmafryy9ck8mz7z7-git-annex-3.20120230.drv-0/git-annex/.t/repo
-       34fa270..7242932  git-annex -> git-annex
-     * [new branch]      master -> synced/master
-    Testing 1:blackbox:22:git-annex map                                           
-    Testing 1:blackbox:23:git-annex uninit                                        
-    Cases: 55  Tried: 47  Errors: 0  Failures: 1Switched to branch 'git-annex'
-    Switched to branch 'master'
-    Deleted branch git-annex (was e636789).
-    Testing 1:blackbox:24:git-annex upgrade                                       
-    Testing 1:blackbox:25:git-annex whereis                                       
-    Testing 1:blackbox:26:git-annex hook remote                                   
-    Testing 1:blackbox:27:git-annex directory remote                              
-    Testing 1:blackbox:28:git-annex rsync remote                                  
-    Cases: 55  Tried: 52  Errors: 0  Failures: 1sending incremental file list
-    af4/
-    af4/74c/
-    af4/74c/SHA256-s20--e394a389d787383843decc5d3d99b6d184ffa5fddeec23b911f9ee7fc8b9ea77/
-    af4/74c/SHA256-s20--e394a389d787383843decc5d3d99b6d184ffa5fddeec23b911f9ee7fc8b9ea77/SHA256-s20--e394a389d787383843decc5d3d99b6d184ffa5fddeec23b911f9ee7fc8b9ea77
-              20 100%    0.00kB/s    0:00:00 (xfer#1, to-check=0/5)
-
-    sent 300 bytes  received 43 bytes  686.00 bytes/sec
-    total size is 20  speedup is 0.06
-    SHA256-s20--e394a389d787383843decc5d3d99b6d184ffa5fddeec23b911f9ee7fc8b9ea77
-              20 100%    0.00kB/s    0:00:00 (xfer#1, to-check=0/1)
-
-    sent 160 bytes  received 31 bytes  382.00 bytes/sec
-    total size is 20  speedup is 0.10
-    Testing 1:blackbox:29:git-annex bup remote                                    
-    Testing 1:blackbox:30:git-annex crypto                                        
-    Cases: 55  Tried: 55  Errors: 0  Failures: 1
-    test: failed
-    ** test suite failed!
-
-Apparently, there is a network timeout? I see from the comments in `test.hs` that the test suite tries to avoid depending on network traffic, but is it possible, maybe, that the test tries to resolve a DNS name?
-"""]]
diff --git a/doc/news/version_3.20120230/comment_2_899de1196cd1ba4a393e4ef574d7aa5e._comment b/doc/news/version_3.20120230/comment_2_899de1196cd1ba4a393e4ef574d7aa5e._comment
deleted file mode 100644
index a4cc3073d7..0000000000
--- a/doc/news/version_3.20120230/comment_2_899de1196cd1ba4a393e4ef574d7aa5e._comment
+++ /dev/null
@@ -1,8 +0,0 @@
-[[!comment format=mdwn
- username="http://joey.kitenet.net/"
- nickname="joey"
- subject="comment 2"
- date="2012-03-06T17:22:54Z"
- content="""
-My mistake, addurl --fast used to avoid the network, so the test suite ran it, but then it was changed to always look up the file size. Removed from test suite.
-"""]]
diff --git a/doc/news/version_3.20120309.mdwn b/doc/news/version_3.20120309.mdwn
deleted file mode 100644
index 869b96ccec..0000000000
--- a/doc/news/version_3.20120309.mdwn
+++ /dev/null
@@ -1,5 +0,0 @@
-git-annex 3.20120309 released with [[!toggle text="these changes"]]
-[[!toggleable text="""
-   * Fix key directory hash calculation code to behave as it did before
-     version 3.20120227 when a key contains non-ascii characters (only
-     WORM backend is likely to have been affected)."""]]
\ No newline at end of file
diff --git a/doc/news/version_3.20120315.mdwn b/doc/news/version_3.20120315.mdwn
deleted file mode 100644
index a3ccb4cf47..0000000000
--- a/doc/news/version_3.20120315.mdwn
+++ /dev/null
@@ -1,21 +0,0 @@
-git-annex 3.20120315 released with [[!toggle text="these changes"]]
-[[!toggleable text="""
-   * fsck: Fix up any broken links and misplaced content caused by the
-     directory hash calculation bug fixed in the last release.
-   * sync: Sync to lower cost remotes first.
-   * status: Fixed to run in constant space.
-   * status: More accurate display of sizes of tmp and bad keys.
-   * unused: Now uses a bloom filter, and runs in constant space.
-     Use of a bloom filter does mean it will not notice a small
-     number of unused keys. For repos with up to half a million keys,
-     it will miss one key in 1000.
-   * Added annex.bloomcapacity and annex.bloomaccuracy, which can be
-     adjusted as desired to tune the bloom filter.
-   * status: Display amount of memory used by bloom filter, and
-     detect when it's too small for the number of keys in a repository.
-   * git-annex-shell: Runs hooks/annex-content after content is received
-     or dropped.
-   * Work around a bug in rsync (IMHO) introduced by openSUSE's SIP patch.
-   * git-annex now behaves as git-annex-shell if symlinked to and run by that
-     name. The Makefile sets this up, saving some 8 mb of installed size.
-   * git-union-merge is a demo program, so it is no longer built by default."""]]
\ No newline at end of file
diff --git a/doc/news/version_3.20120405.mdwn b/doc/news/version_3.20120405.mdwn
deleted file mode 100644
index c5a7ecc22a..0000000000
--- a/doc/news/version_3.20120405.mdwn
+++ /dev/null
@@ -1,5 +0,0 @@
-git-annex 3.20120405 released with [[!toggle text="these changes"]]
-[[!toggleable text="""
-   * Rewrote free disk space checking code, moving the portability
-     handling into a small C library.
-   * status: Display amount of free disk space."""]]
\ No newline at end of file
diff --git a/doc/news/version_3.20120418.mdwn b/doc/news/version_3.20120418.mdwn
new file mode 100644
index 0000000000..93968a83e6
--- /dev/null
+++ b/doc/news/version_3.20120418.mdwn
@@ -0,0 +1,12 @@
+git-annex 3.20120418 released with [[!toggle text="these changes"]]
+[[!toggleable text="""
+   * bugfix: Adding a dotfile also caused all non-dotfiles to be added.
+   * bup: Properly handle key names with spaces or other things that are
+     not legal git refs.
+   * git-annex (but not git-annex-shell) supports the git help.autocorrect
+     configuration setting, doing fuzzy matching using the restricted
+     Damerau-Levenshtein edit distance, just as git does. This adds a build
+     dependency on the haskell edit-distance library.
+   * Renamed diskfree.c to avoid OSX case insensativity bug.
+   * cabal now installs git-annex-shell as a symlink to git-annex.
+   * cabal file now autodetects whether S3 support is available."""]]
\ No newline at end of file
diff --git a/doc/news/version_3.20120430.mdwn b/doc/news/version_3.20120430.mdwn
new file mode 100644
index 0000000000..07e1e85ad2
--- /dev/null
+++ b/doc/news/version_3.20120430.mdwn
@@ -0,0 +1,12 @@
+git-annex 3.20120430 released with [[!toggle text="these changes"]]
+[[!toggleable text="""
+   * Fix use of annex.diskreserve config setting.
+   * Directory special remotes now check annex.diskreserve.
+   * Support git's core.sharedRepository configuration.
+   * Add annex.http-headers and annex.http-headers-command config
+     settings, to allow custom headers to be sent with all HTTP requests.
+     (Requested by the Internet Archive)
+   * uninit: Clear annex.uuid from .git/config. Closes: #[670639](http://bugs.debian.org/670639)
+   * Added shared cipher mode to encryptable special remotes. This option
+     avoids gpg key distribution, at the expense of flexability, and with
+     the requirement that all clones of the git repository be equally trusted."""]]
\ No newline at end of file
diff --git a/doc/news/version_3.20120511.mdwn b/doc/news/version_3.20120511.mdwn
new file mode 100644
index 0000000000..19e8355224
--- /dev/null
+++ b/doc/news/version_3.20120511.mdwn
@@ -0,0 +1,13 @@
+git-annex 3.20120511 released with [[!toggle text="these changes"]]
+[[!toggleable text="""
+   * Rsync special remotes can be configured with shellescape=no
+     to avoid shell quoting that is normally done when using rsync over ssh.
+     This is known to be needed for certian rsync hosting providers
+     (specificially hidrive.strato.com) that use rsync over ssh but do not
+     pass it through the shell.
+   * dropunused: Allow specifying ranges to drop.
+   * addunused: New command, the opposite of dropunused, it relinks unused
+     content into the git repository.
+   * Fix use of several config settings: annex.ssh-options,
+     annex.rsync-options, annex.bup-split-options. (And adjust types to avoid
+     the bugs that broke several config settings.)"""]]
\ No newline at end of file
diff --git a/doc/news/version_3.20120522.mdwn b/doc/news/version_3.20120522.mdwn
new file mode 100644
index 0000000000..55c45900c1
--- /dev/null
+++ b/doc/news/version_3.20120522.mdwn
@@ -0,0 +1,7 @@
+git-annex 3.20120522 released with [[!toggle text="these changes"]]
+[[!toggleable text="""
+   * Pass -a to cp even when it supports --reflink=auto, to preserve
+     permissions.
+   * Clean up handling of git directory and git worktree.
+   * Add support for core.worktree, and fix support for GIT\_WORK\_TREE and
+     GIT\_DIR."""]]
\ No newline at end of file
diff --git a/doc/special_remotes/S3.mdwn b/doc/special_remotes/S3.mdwn
index d4d3d02388..195693b3b3 100644
--- a/doc/special_remotes/S3.mdwn
+++ b/doc/special_remotes/S3.mdwn
@@ -6,8 +6,8 @@ See [[tips/using_Amazon_S3]] and
 
 ## configuration
 
-The standard environment variables `ANNEX_S3_ACCESS_KEY_ID` and 
-`ANNEX_S3_SECRET_ACCESS_KEY` are used to supply login credentials
+The standard environment variables `AWS_ACCESS_KEY_ID` and 
+`AWS_SECRET_ACCESS_KEY` are used to supply login credentials
 for Amazon. When encryption is enabled, they are stored in encrypted form
 by `git annex initremote`, so you do not need to keep the environment
 variables set after the initial initalization of the remote.
diff --git a/doc/special_remotes/S3/comment_1_4a1f7a230dad6caa84831685b236fd73._comment b/doc/special_remotes/S3/comment_1_4a1f7a230dad6caa84831685b236fd73._comment
new file mode 100644
index 0000000000..17e35e7d99
--- /dev/null
+++ b/doc/special_remotes/S3/comment_1_4a1f7a230dad6caa84831685b236fd73._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnoUOqs_lbuWyZBqyU6unHgUduJwDDgiKY"
+ nickname="Matt"
+ subject="environment variables"
+ date="2012-05-29T12:40:25Z"
+ content="""
+Just noting that the environment variables `ANNEX_S3_ACCESS_KEY_ID` and `ANNEX_S3_SECRET_ACCESS_KEY` seem to have been changed to `AWS_ACCESS_KEY_ID` and `AWS_SECRET_ACCESS_KEY`
+"""]]
diff --git a/doc/special_remotes/S3/comment_2_5b22d67de946f4d34a4a3c7449d32988._comment b/doc/special_remotes/S3/comment_2_5b22d67de946f4d34a4a3c7449d32988._comment
new file mode 100644
index 0000000000..f535559aeb
--- /dev/null
+++ b/doc/special_remotes/S3/comment_2_5b22d67de946f4d34a4a3c7449d32988._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="4.153.81.112"
+ subject="comment 2"
+ date="2012-05-29T19:10:46Z"
+ content="""
+Thanks, I've fixed that. (You could have too.. this is a wiki ;)
+"""]]
diff --git a/doc/special_remotes/S3/comment_3_bcab2bd0f168954243aa9bcc9671bd94._comment b/doc/special_remotes/S3/comment_3_bcab2bd0f168954243aa9bcc9671bd94._comment
new file mode 100644
index 0000000000..abb6aacc96
--- /dev/null
+++ b/doc/special_remotes/S3/comment_3_bcab2bd0f168954243aa9bcc9671bd94._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnoUOqs_lbuWyZBqyU6unHgUduJwDDgiKY"
+ nickname="Matt"
+ subject="comment 3"
+ date="2012-05-30T00:26:33Z"
+ content="""
+Thanks! Being new here, I didn't want to overstep my boundaries. I've gone ahead and made a small edit and will do so elsewhere as needed.
+"""]]
diff --git a/doc/special_remotes/rsync.mdwn b/doc/special_remotes/rsync.mdwn
index 90d544a1e1..273469258b 100644
--- a/doc/special_remotes/rsync.mdwn
+++ b/doc/special_remotes/rsync.mdwn
@@ -16,7 +16,7 @@ These parameters can be passed to `git annex initremote` to configure rsync:
 
 * `encryption` - Required. Either "none" to disable encryption of content
   stored in rsync, 
-  or a value that can be looked up (using gpg -k) to find a gpg encryption
+  or a value that can be looked up (using `gpg -k`) to find a gpg encryption
   key that will be given access to the remote. Note that additional gpg
   keys can be given access to a remote by rerunning initremote with
   the new key id. See [[encryption]].
@@ -24,5 +24,13 @@ These parameters can be passed to `git annex initremote` to configure rsync:
 * `rsyncurl` - Required. This is the url or `hostname:/directory` to 
   pass to rsync to tell it where to store content.
 
+* `shellescape` - Optional. Set to "no" to avoid shell escaping normally
+  done when using rsync over ssh. That escaping is needed with typical
+  setups, but not with some hosting providers that do not expose rsynced
+  filenames to the shell. You'll know you need this option if `git annex get`
+  from the special remote fails with an error message containing a single
+  quote (`'`) character. If that happens, you can re-run initremote
+  setting shellescape=no.
+
 The `annex-rsync-options` git configuration setting can be used to pass
 parameters to rsync.
diff --git a/doc/testimonials.mdwn b/doc/testimonials.mdwn
new file mode 100644
index 0000000000..f053c58398
--- /dev/null
+++ b/doc/testimonials.mdwn
@@ -0,0 +1,30 @@
+<div>
+<blockquote class="twitter-tweet"><p>Git annex. Brilliant. Powerful. <a href="http://t.co/AM9B6peM" title="http://git-annex.branchable.com/">git-annex.branchable.com</a></p>&mdash; Gert van Dijk (@gertvdijk) <a href="https://twitter.com/gertvdijk/status/186456474246053888" data-datetime="2012-04-01T14:14:22+00:00">April 1, 2012</a></blockquote>
+<script src="//platform.twitter.com/widgets.js" charset="utf-8"></script>
+<blockquote class="twitter-tweet"><p>git-annex is like dropbox without the chrome. <a href="http://t.co/qcENNt3g" title="http://git-annex.branchable.com/">git-annex.branchable.com</a></p>&mdash; Wil Chung (@iamwil) <a href="https://twitter.com/iamwil/status/185997581229367296" data-datetime="2012-03-31T07:50:53+00:00">March 31, 2012</a></blockquote>
+<script src="//platform.twitter.com/widgets.js" charset="utf-8"></script>
+<blockquote class="twitter-tweet"><p>blender 2.62 + ffmpeg + dnxhd + git-annex = who needs final cut?</p>&mdash; cdotwright (@cdotwright) <a href="https://twitter.com/cdotwright/status/187645142864375808" data-datetime="2012-04-04T20:57:42+00:00">April 4, 2012</a></blockquote>
+<script src="//platform.twitter.com/widgets.js" charset="utf-8"></script>
+<blockquote class="twitter-tweet"><p>I want <a href="https://twitter.com/search/%2523git">#git</a>-annex whereis for all the stuff (not) in my room.</p>&mdash; topr (@derwelle) <a href="https://twitter.com/derwelle/status/172356564072673280" data-datetime="2012-02-22T16:26:21+00:00">February 22, 2012</a></blockquote>
+<script src="//platform.twitter.com/widgets.js" charset="utf-8"></script>
+</div>
+
+<blockquote>
+What excites me about GIT ANNEX is how it fundamentally tracks the
+backup and availability of any data you own, and allows you to share
+data with a large or small audience, ensuring that the data survives.
+</blockquote>
+-- Jason Scott <http://ascii.textfiles.com/archives/3625>
+
+Seen on IRC:
+<pre>
+oh my god, git-annex is amazing
+this is the revolution in fucking with gigantic piles of files that I've been waiting for
+</pre>
+
+And then my own story: I have a ton of drives. I have a lot of servers. I
+live in a cabin on **dialup** and often have 1 hour on broadband in a week
+to get everything I need. Without git-annex, managing all this would not be
+possible. It works perfectly for me, not a surprise since I wrote it, but
+still, it's a different level of "perfect" than anything I could put
+together before. --[[Joey]]
diff --git a/doc/tips/using_Amazon_S3.mdwn b/doc/tips/using_Amazon_S3.mdwn
index b59ca9b4f8..128819fcbb 100644
--- a/doc/tips/using_Amazon_S3.mdwn
+++ b/doc/tips/using_Amazon_S3.mdwn
@@ -4,8 +4,8 @@ Amazon S3, and use git-annex to transfer files into the cloud.
 
 First, export your S3 credentials:
 
-	# export ANNEX_S3_ACCESS_KEY_ID="08TJMT99S3511WOZEP91"
-	# export ANNEX_S3_SECRET_ACCESS_KEY="s3kr1t"
+	# export AWS_ACCESS_KEY_ID="08TJMT99S3511WOZEP91"
+	# export AWS_SECRET_ACCESS_KEY="s3kr1t"
 
 Now, create a gpg key, if you don't already have one. This will be used
 to encrypt everything stored in S3, for your privacy. Once you have
diff --git a/doc/tips/using_Amazon_S3/comment_1_666a26f95024760c99c627eed37b1966._comment b/doc/tips/using_Amazon_S3/comment_1_666a26f95024760c99c627eed37b1966._comment
new file mode 100644
index 0000000000..60d96cb44e
--- /dev/null
+++ b/doc/tips/using_Amazon_S3/comment_1_666a26f95024760c99c627eed37b1966._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnoUOqs_lbuWyZBqyU6unHgUduJwDDgiKY"
+ nickname="Matt"
+ subject="ANNEX_S3 vs AWS for keys"
+ date="2012-05-29T12:24:25Z"
+ content="""
+The instructions state ANNEX_S3_ACCESS_KEY_ID and ANNEX_SECRET_ACCESS_KEY but git-annex cannot connect with those constants. git-annex tells me to set both \"AWS_ACCESS_KEY_ID and AWS_SECRET_ACCESS_KEY\" instead, which works. This is with Xubuntu 12.04.
+"""]]
diff --git a/doc/tips/using_Amazon_S3/comment_2_f5a0883be7dbb421b584c6dc0165f1ef._comment b/doc/tips/using_Amazon_S3/comment_2_f5a0883be7dbb421b584c6dc0165f1ef._comment
new file mode 100644
index 0000000000..dc809cb126
--- /dev/null
+++ b/doc/tips/using_Amazon_S3/comment_2_f5a0883be7dbb421b584c6dc0165f1ef._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="4.153.81.112"
+ subject="comment 2"
+ date="2012-05-29T19:10:42Z"
+ content="""
+Thanks, I've fixed that. (You could have too.. this is a wiki ;)
+"""]]
diff --git a/doc/tips/what_to_do_when_you_lose_a_repository/comment_1_cf19b8dc304dc37c26717174c4a98aa4._comment b/doc/tips/what_to_do_when_you_lose_a_repository/comment_1_cf19b8dc304dc37c26717174c4a98aa4._comment
new file mode 100644
index 0000000000..a7fce26ef8
--- /dev/null
+++ b/doc/tips/what_to_do_when_you_lose_a_repository/comment_1_cf19b8dc304dc37c26717174c4a98aa4._comment
@@ -0,0 +1,11 @@
+[[!comment format=mdwn
+ username="http://dlaxalde.myopenid.com/"
+ nickname="dl"
+ subject="comment 1"
+ date="2012-05-31T14:36:33Z"
+ content="""
+Is there a way to have git-annex completely ignore a repository? I see that
+the `dead` command adds the uuid of the repository to `trust.log` but does
+not change `uuid.log`. Is it enough to remove the corresponding line in
+`uuid.log` and `trust.log`?
+"""]]
diff --git a/doc/tips/what_to_do_when_you_lose_a_repository/comment_3_fa9ca81668f5faebf2f61b10f82c97d2._comment b/doc/tips/what_to_do_when_you_lose_a_repository/comment_3_fa9ca81668f5faebf2f61b10f82c97d2._comment
new file mode 100644
index 0000000000..a8d044c287
--- /dev/null
+++ b/doc/tips/what_to_do_when_you_lose_a_repository/comment_3_fa9ca81668f5faebf2f61b10f82c97d2._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="4.153.8.243"
+ subject="comment 3"
+ date="2012-05-31T17:01:37Z"
+ content="""
+`dead` is the best we can do. The automatic merging used on the git-annex branch tends to re-add lines that are deleted in one repo when merging with another that still has them.
+"""]]
diff --git a/doc/todo/automatic_bookkeeping_watch_command.mdwn b/doc/todo/automatic_bookkeeping_watch_command.mdwn
new file mode 100644
index 0000000000..0bb86e4a13
--- /dev/null
+++ b/doc/todo/automatic_bookkeeping_watch_command.mdwn
@@ -0,0 +1,12 @@
+A "git annex watch" command would help make git-annex usable by users who
+don't know how to use git, or don't want to bother typing the git commands. 
+It would run, in the background, watching via inotify for changes, and
+automatically annexing new files, etc.
+
+The blue sky goal would be something automated like dropbox, except fully
+distributed. All files put into the repository would propagate out
+to all the other clones of it, as network links allow. Note that while
+dropbox allows modifying files, git-annex freezes them upon creation,
+so this would not be 100% equivalent to dropbox. --[[Joey]]
+
+This is a big project with its own [[design pages|design/assistant]].
diff --git a/doc/todo/http_headers.mdwn b/doc/todo/http_headers.mdwn
new file mode 100644
index 0000000000..9f61bdc931
--- /dev/null
+++ b/doc/todo/http_headers.mdwn
@@ -0,0 +1,8 @@
+The IA would find it useful to be able to control the http headers
+git-annex get, addurl, etc uses. This will allow setting cookies, for
+example.
+
+* annex-web-headers=blah 
+* Perhaps also annex-web-headers-command=blah
+
+[[done]]
diff --git a/doc/todo/windows_support/comment_1_3cc26ad8101a22e95a8c60cf0c4dedcc._comment b/doc/todo/windows_support/comment_1_3cc26ad8101a22e95a8c60cf0c4dedcc._comment
new file mode 100644
index 0000000000..fd5b6f5cd3
--- /dev/null
+++ b/doc/todo/windows_support/comment_1_3cc26ad8101a22e95a8c60cf0c4dedcc._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkRITTYYsN0TFKN7G5sZ6BWGZOTQ88Pz4s"
+ nickname="Zoltán"
+ subject="cygwin"
+ date="2012-05-15T00:14:08Z"
+ content="""
+What about [Cygwin](http://cygwin.com/)? It emulates POSIX fairly well under Windows (including signals, forking, fs (also things like /dev/null, /proc), unix file permissions), has all standard gnu utilities. It also emulates symlinks, but they are unfortunately incompatible with NTFS symlinks introduced in Vista [due to some stupid restrictions on Windows](http://cygwin.com/ml/cygwin/2009-10/msg00756.html).
+
+If git-annex could be modified to not require symlinks to work, the it would be a pretty neat solution (and you get a real shell, not some command.com on drugs (aka cmd.exe))
+"""]]
diff --git a/doc/todo/windows_support/comment_2_8acae818ce468967499050bbe3c532ea._comment b/doc/todo/windows_support/comment_2_8acae818ce468967499050bbe3c532ea._comment
new file mode 100644
index 0000000000..e37a555756
--- /dev/null
+++ b/doc/todo/windows_support/comment_2_8acae818ce468967499050bbe3c532ea._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawk5cj-itfFHq_yhJHdzk3QOPp-PNW_MjPU"
+ nickname="Michael"
+ subject="+1 Cygwin"
+ date="2012-05-23T19:30:21Z"
+ content="""
+Windows support is a must. In my experience, binary file means proprietary editor, which means Windows.
+
+Unfortunately, there's not much overlap between people who use graphical editors in Windows all day vs. people who are willing to tolerate Cygwin's setup.exe, compile a Haskell program, learn git and git-annex's 90-odd subcommands, and use a mintty terminal to manage their repository, especially now that there's a sexy GitHub app for Windows.
+
+That aside, I think Windows-based content producers are still *the* audience for git-annex. First Windows support, then a GUI, then the world.
+"""]]
diff --git a/doc/walkthrough.mdwn b/doc/walkthrough.mdwn
index f93e28393e..c288b71ded 100644
--- a/doc/walkthrough.mdwn
+++ b/doc/walkthrough.mdwn
@@ -2,23 +2,23 @@ A walkthrough of the basic features of git-annex.
 
 [[!toc]]
 
-[[!inline feeds=no show=0 template=walkthrough pagenames="""
-	creating_a_repository
-	adding_a_remote
-	adding_files
-	renaming_files
-	getting_file_content
-	syncing
-	transferring_files:_When_things_go_wrong
-	removing_files
-	removing_files:_When_things_go_wrong
-	modifying_annexed_files
-	using_ssh_remotes
-	moving_file_content_between_repositories
-	unused_data
-	fsck:_verifying_your_data
-	fsck:_when_things_go_wrong
-	backups
-	automatically_managing_content
-	more
+[[!inline feeds=no trail=yes show=0 template=walkthrough pagenames="""
+	walkthrough/creating_a_repository
+	walkthrough/adding_a_remote
+	walkthrough/adding_files
+	walkthrough/renaming_files
+	walkthrough/getting_file_content
+	walkthrough/syncing
+	walkthrough/transferring_files:_When_things_go_wrong
+	walkthrough/removing_files
+	walkthrough/removing_files:_When_things_go_wrong
+	walkthrough/modifying_annexed_files
+	walkthrough/using_ssh_remotes
+	walkthrough/moving_file_content_between_repositories
+	walkthrough/unused_data
+	walkthrough/fsck:_verifying_your_data
+	walkthrough/fsck:_when_things_go_wrong
+	walkthrough/backups
+	walkthrough/automatically_managing_content
+	walkthrough/more
 """]]
diff --git a/doc/walkthrough/unused_data.mdwn b/doc/walkthrough/unused_data.mdwn
index 518550ac02..63fb9f66d9 100644
--- a/doc/walkthrough/unused_data.mdwn
+++ b/doc/walkthrough/unused_data.mdwn
@@ -27,4 +27,4 @@ data anymore, you can easily remove it:
 
 Hint: To drop a lot of unused data, use a command like this:
 
-	# git annex dropunused `seq 1 1000`
+	# git annex dropunused 1-1000
diff --git a/doc/walkthrough/using_ssh_remotes/comment_2_365db5820d96d5daa62c19fd76fcdf1e._comment b/doc/walkthrough/using_ssh_remotes/comment_2_365db5820d96d5daa62c19fd76fcdf1e._comment
new file mode 100644
index 0000000000..8973978ad8
--- /dev/null
+++ b/doc/walkthrough/using_ssh_remotes/comment_2_365db5820d96d5daa62c19fd76fcdf1e._comment
@@ -0,0 +1,13 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="4.153.81.112"
+ subject="comment 2"
+ date="2012-05-27T20:53:05Z"
+ content="""
+When `git annex get` does nothing, it's because it doesn't know a place to get the file from.
+
+This can happen if the `git-annex` branch has not propigated from the place where the file was added.
+For example, if on the laptop you had run `git pull ssh master`, that would only pull the master branch, not the git-annex branch. 
+
+An easy way to ensure the git-annex branch is kept in sync is to run `git annex sync`
+"""]]
diff --git a/doc/walkthrough/using_ssh_remotes/comment_2_451fd0c6a25ee61ef137e8e5be0c286b._comment b/doc/walkthrough/using_ssh_remotes/comment_2_451fd0c6a25ee61ef137e8e5be0c286b._comment
new file mode 100644
index 0000000000..2121401968
--- /dev/null
+++ b/doc/walkthrough/using_ssh_remotes/comment_2_451fd0c6a25ee61ef137e8e5be0c286b._comment
@@ -0,0 +1,16 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkaT0B6s9jQuMzQUYRVBgWqtO7BhT_ZSaE"
+ nickname="Fernando Seabra"
+ subject="cannot get files"
+ date="2012-05-27T20:33:09Z"
+ content="""
+Hi,
+
+I could successfully clone my ssh repo's annex to my laptop, following these instructions.
+I'm also able to sync the repositories (laptop and ssh) when I commit new files in the ssh repo.
+
+However, every time I try to get files from the ssh repo (using 'git annex get some_file'), nothing happens.
+Do you know what can be happening?
+
+Thanks!
+"""]]
diff --git a/doc/walkthrough/using_ssh_remotes/comment_3_b2f15a46620385da26d5fe8f11ebfc1a._comment b/doc/walkthrough/using_ssh_remotes/comment_3_b2f15a46620385da26d5fe8f11ebfc1a._comment
new file mode 100644
index 0000000000..75a133d840
--- /dev/null
+++ b/doc/walkthrough/using_ssh_remotes/comment_3_b2f15a46620385da26d5fe8f11ebfc1a._comment
@@ -0,0 +1,15 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkaT0B6s9jQuMzQUYRVBgWqtO7BhT_ZSaE"
+ nickname="Fernando Seabra"
+ subject="comment 3"
+ date="2012-05-27T21:13:50Z"
+ content="""
+Thanks for the quick replay!
+
+I already did 'git annex sync', but it didn't work. The steps were: 'git clone ssh...', then 'cd annex', then 'git annex init \"laptop\"'
+
+After that, I did a 'git annex sync', and tried to get the file, but nothing happens. That's why I found it weird.
+Any other thing that might have happened?
+
+Thanks again!
+"""]]
diff --git a/doc/walkthrough/using_ssh_remotes/comment_4_433ccc87fbb0a13e32d59d77f0b4e56c._comment b/doc/walkthrough/using_ssh_remotes/comment_4_433ccc87fbb0a13e32d59d77f0b4e56c._comment
new file mode 100644
index 0000000000..3df03abc2c
--- /dev/null
+++ b/doc/walkthrough/using_ssh_remotes/comment_4_433ccc87fbb0a13e32d59d77f0b4e56c._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="4.153.81.112"
+ subject="comment 4"
+ date="2012-05-27T21:33:11Z"
+ content="""
+Try running `git annex whereis` on the file and see where it says it is.
+"""]]
diff --git a/doc/walkthrough/using_ssh_remotes/comment_5_a9805c7965da0b88a1c9f7f207c450a1._comment b/doc/walkthrough/using_ssh_remotes/comment_5_a9805c7965da0b88a1c9f7f207c450a1._comment
new file mode 100644
index 0000000000..703b89ebfa
--- /dev/null
+++ b/doc/walkthrough/using_ssh_remotes/comment_5_a9805c7965da0b88a1c9f7f207c450a1._comment
@@ -0,0 +1,18 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkaT0B6s9jQuMzQUYRVBgWqtO7BhT_ZSaE"
+ nickname="Fernando Seabra"
+ subject="comment 5"
+ date="2012-05-27T21:42:56Z"
+ content="""
+Hi,
+
+I guess the problem is with git-annex-shell. I tried to do 'git annex get file --from name_ssh_repo', and I got the following:
+
+bash: git-annex-shell: command not found; failed; exit code 127
+
+The same thing happens if I try to do 'git annex whereis'
+
+git-annex-shell is indeed installed. How can I make my shell recognize this command?
+
+Thanks a lot!
+"""]]
diff --git a/doc/walkthrough/using_ssh_remotes/comment_6_9d5c12c056892b706cf100ea01866685._comment b/doc/walkthrough/using_ssh_remotes/comment_6_9d5c12c056892b706cf100ea01866685._comment
new file mode 100644
index 0000000000..4d5961ca90
--- /dev/null
+++ b/doc/walkthrough/using_ssh_remotes/comment_6_9d5c12c056892b706cf100ea01866685._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="4.153.81.112"
+ subject="comment 6"
+ date="2012-05-27T22:08:50Z"
+ content="""
+git-annex-shell needs to be installed in the `PATH` on any host that will hold annexed files. 
+
+If you installed with cabal, it might be `.cabal/bin/`. Whereever it was installed to is apparently not on the PATH that is set when you ssh into that host. 
+
+
+"""]]
diff --git a/doc/walkthrough/using_ssh_remotes/comment_7_725e7dbb2d0a74a035127cb01ee0442c._comment b/doc/walkthrough/using_ssh_remotes/comment_7_725e7dbb2d0a74a035127cb01ee0442c._comment
new file mode 100644
index 0000000000..700b170ad6
--- /dev/null
+++ b/doc/walkthrough/using_ssh_remotes/comment_7_725e7dbb2d0a74a035127cb01ee0442c._comment
@@ -0,0 +1,16 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkaT0B6s9jQuMzQUYRVBgWqtO7BhT_ZSaE"
+ nickname="Fernando Seabra"
+ subject="comment 7"
+ date="2012-05-27T23:35:17Z"
+ content="""
+Hi,
+
+It was already installed in PATH. In fact, I can call it from the command line, and it is recognized (e.g. calling 'git-annex-shell' gives me 'git-annex-shell: bad parameters'). However, every time I do a 'git annex whereis' or 'git annex get file --from repo', it gives me the following error:
+
+bash: git-annex-shell: command not found
+Command ssh [\"-S\",\"/Users/username/annex/.git/annex/ssh/username@example.edu\",\"-o\",\"ControlMaster=auto\",\"-o\",\"ControlPersist=yes\",\"username@example.edu\",\"git-annex-shell 'configlist' '/~/annex'\"] failed; exit code 127
+
+I tried to run this ssh command, but it gives me the same 'command not found' error. It seems that the problem is with the ssh repo?
+The ssh repo has a git-annex-shell working and installed in PATH.
+"""]]
diff --git a/git-annex-shell.hs b/git-annex-shell.hs
deleted file mode 100644
index 08c1f9664d..0000000000
--- a/git-annex-shell.hs
+++ /dev/null
@@ -1,13 +0,0 @@
-{- git-annex-shell main program
- -
- - Copyright 2012 Joey Hess <joey@kitenet.net>
- -
- - Licensed under the GNU GPL version 3 or higher.
- -}
-
-import System.Environment
-
-import GitAnnexShell
-
-main :: IO ()
-main = run =<< getArgs
diff --git a/git-annex.cabal b/git-annex.cabal
index 0f28589859..e12cbb1777 100644
--- a/git-annex.cabal
+++ b/git-annex.cabal
@@ -1,5 +1,5 @@
 Name: git-annex
-Version: 3.20120407
+Version: 3.20120522
 Cabal-Version: >= 1.8
 License: GPL
 Maintainer: Joey Hess <joey@kitenet.net>
@@ -26,25 +26,34 @@ Description:
  etc that are associated with annexed files but that benefit from full
  revision control.
 
+Flag S3
+  Description: Enable S3 support
+
 Executable git-annex
   Main-Is: git-annex.hs
   Build-Depends: MissingH, hslogger, directory, filepath,
    unix, containers, utf8-string, network, mtl, bytestring, old-locale, time,
-   pcre-light, extensible-exceptions, dataenc, SHA, process, hS3, json, HTTP,
-   base >= 4.5, base < 5, monad-control, transformers-base, lifted-base,
+   pcre-light, extensible-exceptions, dataenc, SHA, process, json, HTTP,
+   base == 4.5.*, monad-control, transformers-base, lifted-base,
    IfElse, text, QuickCheck >= 2.1, bloomfilter, edit-distance
   Other-Modules: Utility.Touch
-  C-Sources: Utility/diskfree.c
+  C-Sources: Utility/libdiskfree.c
+  Extensions: CPP
 
-Executable git-annex-shell
-  Main-Is: git-annex-shell.hs
-  C-Sources: Utility/diskfree.c
+  if flag(S3)
+    Build-Depends: hS3
+    CPP-Options: -DWITH_S3
 
 Test-Suite test
   Type: exitcode-stdio-1.0
   Main-Is: test.hs
-  Build-Depends: testpack, HUnit
-  C-Sources: Utility/diskfree.c
+  Build-Depends: testpack, HUnit, MissingH, hslogger, directory, filepath,
+   unix, containers, utf8-string, network, mtl, bytestring, old-locale, time,
+   pcre-light, extensible-exceptions, dataenc, SHA, process, json, HTTP,
+   base == 4.5.*, monad-control, transformers-base, lifted-base,
+   IfElse, text, QuickCheck >= 2.1, bloomfilter, edit-distance
+  C-Sources: Utility/libdiskfree.c
+  Extensions: CPP
 
 source-repository head
   type: git
diff --git a/git-union-merge.hs b/git-union-merge.hs
index f44136bfc1..2c2e7a46bd 100644
--- a/git-union-merge.hs
+++ b/git-union-merge.hs
@@ -10,7 +10,7 @@ import System.Environment
 import Common
 import qualified Git.UnionMerge
 import qualified Git.Config
-import qualified Git.Construct
+import qualified Git.CurrentRepo
 import qualified Git.Branch
 import qualified Git.Index
 import qualified Git
@@ -22,7 +22,7 @@ usage :: IO a
 usage = error $ "bad parameters\n\n" ++ header
 
 tmpIndex :: Git.Repo -> FilePath
-tmpIndex g = Git.gitDir g </> "index.git-union-merge"
+tmpIndex g = Git.localGitDir g </> "index.git-union-merge"
 
 setup :: Git.Repo -> IO ()
 setup = cleanup -- idempotency
@@ -40,7 +40,7 @@ parseArgs = do
 main :: IO ()
 main = do
 	[aref, bref, newref] <- map Git.Ref <$> parseArgs
-	g <- Git.Config.read =<< Git.Construct.fromCurrent
+	g <- Git.Config.read =<< Git.CurrentRepo.get
 	_ <- Git.Index.override $ tmpIndex g
 	setup g
 	Git.UnionMerge.merge aref bref g
diff --git a/test.hs b/test.hs
index 5f4b0ad40e..9a0fce873e 100644
--- a/test.hs
+++ b/test.hs
@@ -25,8 +25,7 @@ import qualified Utility.SafeCommand
 import qualified Annex
 import qualified Annex.UUID
 import qualified Backend
-import qualified Git.Config
-import qualified Git.Construct
+import qualified Git.CurrentRepo
 import qualified Git.Filename
 import qualified Locations
 import qualified Types.Backend
@@ -35,9 +34,10 @@ import qualified GitAnnex
 import qualified Logs.UUIDBased
 import qualified Logs.Trust
 import qualified Logs.Remote
+import qualified Logs.Unused
 import qualified Remote
-import qualified Command.DropUnused
 import qualified Types.Key
+import qualified Types.Messages
 import qualified Config
 import qualified Crypto
 import qualified Utility.Path
@@ -494,7 +494,7 @@ test_unused = "git-annex unused/dropunused" ~: intmpclonerepo $ do
 	where
 		checkunused expectedkeys = do
 			git_annex "unused" [] @? "unused failed"
-			unusedmap <- annexeval $ Command.DropUnused.readUnusedLog ""
+			unusedmap <- annexeval $ Logs.Unused.readUnusedLog ""
 			let unusedkeys = M.elems unusedmap
 			assertEqual "unused keys differ"
 				(sort expectedkeys) (sort unusedkeys)
@@ -720,10 +720,10 @@ git_annex_expectoutput command params expected = do
 -- are not run; this should only be used for actions that query state.
 annexeval :: Types.Annex a -> IO a
 annexeval a = do
-	g <- Git.Construct.fromCurrent
-	g' <- Git.Config.read g
-	s <- Annex.new g'
-	Annex.eval s { Annex.output = Annex.QuietOutput } a
+	s <- Annex.new =<< Git.CurrentRepo.get
+	Annex.eval s $ do
+		Annex.setOutput Types.Messages.QuietOutput
+		a
 
 innewrepo :: Assertion -> Assertion
 innewrepo a = withgitrepo $ \r -> indir r a