aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2013-10-01 19:12:25 -0400
committerGravatar Joey Hess <joey@kitenet.net>2013-10-01 19:12:25 -0400
commit04adde9fa47297d6549419513cfddbd785dc2de1 (patch)
treec6a2e1db43fa4942aef8ba4e2a7d608a8872d92b
parent2e3990d125b96a13545b55a203f41e3bf09e75e3 (diff)
parentc843ade78f57bdfe7bed5f77749c71f9a9e6e20a (diff)
Merge branch 'sshgcrypt'
-rw-r--r--Assistant/MakeRemote.hs37
-rw-r--r--Assistant/Pairing/MakeRemote.hs10
-rw-r--r--Assistant/Ssh.hs74
-rw-r--r--Command/GCryptSetup.hs35
-rw-r--r--Git/Config.hs11
-rw-r--r--GitAnnexShell.hs22
-rw-r--r--Remote/GCrypt.hs54
-rw-r--r--debian/changelog2
-rw-r--r--doc/design/assistant/encrypted_git_remotes.mdwn7
-rw-r--r--doc/forum/Android:_is_constant_high_cpu_usage_to_be_expected__63__/comment_1_7880fc38792a1fcbf3e5c47e8bcaabce._comment8
-rw-r--r--doc/forum/Import_options/comment_2_21da91f08cb6b28ae3e79ade033db516._comment17
-rw-r--r--doc/forum/Newbie_stuck_at___34__Unable_to_connect_to_the_Jabber_server__34__/comment_3_92a52b523ed4c68b70ddcabc2a050b76._comment12
-rw-r--r--doc/git-annex-shell.mdwn4
13 files changed, 207 insertions, 86 deletions
diff --git a/Assistant/MakeRemote.hs b/Assistant/MakeRemote.hs
index 2619039c0..32a3fd6f5 100644
--- a/Assistant/MakeRemote.hs
+++ b/Assistant/MakeRemote.hs
@@ -9,7 +9,6 @@ module Assistant.MakeRemote where
import Assistant.Common
import Assistant.Ssh
-import Assistant.Sync
import qualified Types.Remote as R
import qualified Remote
import Remote.List
@@ -21,47 +20,20 @@ import qualified Command.InitRemote
import Logs.UUID
import Logs.Remote
import Git.Remote
-import Config
-import Config.Cost
import Creds
import Assistant.Gpg
import Utility.Gpg (KeyId)
-import qualified Data.Text as T
import qualified Data.Map as M
-{- Sets up and begins syncing with a new ssh or rsync remote. -}
-makeSshRemote :: Bool -> SshData -> Maybe Cost -> Assistant Remote
-makeSshRemote forcersync sshdata mcost = do
- r <- liftAnnex $
- addRemote $ maker (sshRepoName sshdata)
- (sshUrl forcersync sshdata)
- liftAnnex $ maybe noop (setRemoteCost r) mcost
- syncRemote r
- return r
+{- Sets up a new git or rsync remote, accessed over ssh. -}
+makeSshRemote :: SshData -> Annex RemoteName
+makeSshRemote sshdata = maker (sshRepoName sshdata) (genSshUrl sshdata)
where
- rsync = forcersync || rsyncOnly sshdata
maker
- | rsync = makeRsyncRemote
+ | onlyCapability sshdata RsyncCapable = makeRsyncRemote
| otherwise = makeGitRemote
-{- Generates a ssh or rsync url from a SshData. -}
-sshUrl :: Bool -> SshData -> String
-sshUrl forcersync sshdata = addtrailingslash $ T.unpack $ T.concat $
- if (forcersync || rsyncOnly sshdata)
- then [u, h, T.pack ":", sshDirectory sshdata]
- else [T.pack "ssh://", u, h, d]
- where
- u = maybe (T.pack "") (\v -> T.concat [v, T.pack "@"]) $ sshUserName sshdata
- h = sshHostName sshdata
- d
- | T.pack "/" `T.isPrefixOf` sshDirectory sshdata = sshDirectory sshdata
- | T.pack "~/" `T.isPrefixOf` sshDirectory sshdata = T.concat [T.pack "/", sshDirectory sshdata]
- | otherwise = T.concat [T.pack "/~/", sshDirectory sshdata]
- addtrailingslash s
- | "/" `isSuffixOf` s = s
- | otherwise = s ++ "/"
-
{- Runs an action that returns a name of the remote, and finishes adding it. -}
addRemote :: Annex RemoteName -> Annex Remote
addRemote a = do
@@ -146,7 +118,6 @@ makeRemote basename location a = do
g <- gitRepo
if not (any samelocation $ Git.remotes g)
then do
-
let name = uniqueRemoteName basename 0 g
a name
return name
diff --git a/Assistant/Pairing/MakeRemote.hs b/Assistant/Pairing/MakeRemote.hs
index edd27e35a..144b236a4 100644
--- a/Assistant/Pairing/MakeRemote.hs
+++ b/Assistant/Pairing/MakeRemote.hs
@@ -12,7 +12,9 @@ import Assistant.Ssh
import Assistant.Pairing
import Assistant.Pairing.Network
import Assistant.MakeRemote
+import Assistant.Sync
import Config.Cost
+import Config
import Network.Socket
import qualified Data.Text as T
@@ -22,7 +24,7 @@ import qualified Data.Text as T
setupAuthorizedKeys :: PairMsg -> FilePath -> IO ()
setupAuthorizedKeys msg repodir = do
validateSshPubKey pubkey
- unlessM (liftIO $ addAuthorizedKeys False repodir pubkey) $
+ unlessM (liftIO $ addAuthorizedKeys True repodir pubkey) $
error "failed setting up ssh authorized keys"
where
pubkey = remoteSshPubKey $ pairMsgData msg
@@ -43,7 +45,9 @@ finishedLocalPairing msg keypair = do
, "git-annex-shell -c configlist " ++ T.unpack (sshDirectory sshdata)
]
Nothing
- void $ makeSshRemote False sshdata (Just semiExpensiveRemoteCost)
+ r <- liftAnnex $ addRemote $ makeSshRemote sshdata
+ liftAnnex $ setRemoteCost r semiExpensiveRemoteCost
+ syncRemote r
{- Mostly a straightforward conversion. Except:
- * Determine the best hostname to use to contact the host.
@@ -63,7 +67,7 @@ pairMsgToSshData msg = do
, sshRepoName = genSshRepoName hostname dir
, sshPort = 22
, needsPubKey = True
- , rsyncOnly = False
+ , sshCapabilities = [GitAnnexShellCapable, GitCapable, RsyncCapable]
}
{- Finds the best hostname to use for the host that sent the PairMsg.
diff --git a/Assistant/Ssh.hs b/Assistant/Ssh.hs
index a62319096..f316aa500 100644
--- a/Assistant/Ssh.hs
+++ b/Assistant/Ssh.hs
@@ -1,6 +1,6 @@
{- git-annex assistant ssh utilities
-
- - Copyright 2012 Joey Hess <joey@kitenet.net>
+ - Copyright 2012-2013 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
@@ -11,6 +11,7 @@ import Common.Annex
import Utility.Tmp
import Utility.UserInfo
import Utility.Shell
+import Utility.Rsync
import Git.Remote
import Data.Text (Text)
@@ -25,10 +26,19 @@ data SshData = SshData
, sshRepoName :: String
, sshPort :: Int
, needsPubKey :: Bool
- , rsyncOnly :: Bool
+ , sshCapabilities :: [SshServerCapability]
}
deriving (Read, Show, Eq)
+data SshServerCapability = GitAnnexShellCapable | GitCapable | RsyncCapable
+ deriving (Read, Show, Eq)
+
+hasCapability :: SshData -> SshServerCapability -> Bool
+hasCapability d c = c `elem` sshCapabilities d
+
+onlyCapability :: SshData -> SshServerCapability -> Bool
+onlyCapability d c = all (== c) (sshCapabilities d)
+
data SshKeyPair = SshKeyPair
{ sshPubKey :: String
, sshPrivKey :: String
@@ -52,6 +62,48 @@ sshDir = do
genSshHost :: Text -> Maybe Text -> String
genSshHost host user = maybe "" (\v -> T.unpack v ++ "@") user ++ T.unpack host
+{- Generates a ssh or rsync url from a SshData. -}
+genSshUrl :: SshData -> String
+genSshUrl sshdata = addtrailingslash $ T.unpack $ T.concat $
+ if (onlyCapability sshdata RsyncCapable)
+ then [u, h, T.pack ":", sshDirectory sshdata]
+ else [T.pack "ssh://", u, h, d]
+ where
+ u = maybe (T.pack "") (\v -> T.concat [v, T.pack "@"]) $ sshUserName sshdata
+ h = sshHostName sshdata
+ d
+ | T.pack "/" `T.isPrefixOf` sshDirectory sshdata = sshDirectory sshdata
+ | T.pack "~/" `T.isPrefixOf` sshDirectory sshdata = T.concat [T.pack "/", sshDirectory sshdata]
+ | otherwise = T.concat [T.pack "/~/", sshDirectory sshdata]
+ addtrailingslash s
+ | "/" `isSuffixOf` s = s
+ | otherwise = s ++ "/"
+
+{- Reverses genSshUrl -}
+parseSshUrl :: String -> Maybe SshData
+parseSshUrl u
+ | "ssh://" `isPrefixOf` u = fromssh (drop (length "ssh://") u)
+ | otherwise = fromrsync u
+ where
+ mkdata (userhost, dir) = Just $ SshData
+ { sshHostName = T.pack host
+ , sshUserName = if null user then Nothing else Just $ T.pack user
+ , sshDirectory = T.pack dir
+ , sshRepoName = genSshRepoName host dir
+ -- dummy values, cannot determine from url
+ , sshPort = 22
+ , needsPubKey = True
+ , sshCapabilities = []
+ }
+ where
+ (user, host) = if '@' `elem` userhost
+ then separate (== '@') userhost
+ else ("", userhost)
+ fromrsync s
+ | not (rsyncUrlIsShell u) = Nothing
+ | otherwise = mkdata $ separate (== ':') s
+ fromssh = mkdata . break (== '/')
+
{- Generates a git remote name, like host_dir or host -}
genSshRepoName :: String -> FilePath -> String
genSshRepoName host dir
@@ -92,12 +144,12 @@ validateSshPubKey pubkey
safeincomment c = isAlphaNum c || c == '@' || c == '-' || c == '_' || c == '.'
addAuthorizedKeys :: Bool -> FilePath -> SshPubKey -> IO Bool
-addAuthorizedKeys rsynconly dir pubkey = boolSystem "sh"
- [ Param "-c" , Param $ addAuthorizedKeysCommand rsynconly dir pubkey ]
+addAuthorizedKeys gitannexshellonly dir pubkey = boolSystem "sh"
+ [ Param "-c" , Param $ addAuthorizedKeysCommand gitannexshellonly dir pubkey ]
removeAuthorizedKeys :: Bool -> FilePath -> SshPubKey -> IO ()
-removeAuthorizedKeys rsynconly dir pubkey = do
- let keyline = authorizedKeysLine rsynconly dir pubkey
+removeAuthorizedKeys gitannexshellonly dir pubkey = do
+ let keyline = authorizedKeysLine gitannexshellonly dir pubkey
sshdir <- sshDir
let keyfile = sshdir </> "authorized_keys"
ls <- lines <$> readFileStrict keyfile
@@ -110,7 +162,7 @@ removeAuthorizedKeys rsynconly dir pubkey = do
- present.
-}
addAuthorizedKeysCommand :: Bool -> FilePath -> SshPubKey -> String
-addAuthorizedKeysCommand rsynconly dir pubkey = intercalate "&&"
+addAuthorizedKeysCommand gitannexshellonly dir pubkey = intercalate "&&"
[ "mkdir -p ~/.ssh"
, intercalate "; "
[ "if [ ! -e " ++ wrapper ++ " ]"
@@ -122,7 +174,7 @@ addAuthorizedKeysCommand rsynconly dir pubkey = intercalate "&&"
, "chmod 600 ~/.ssh/authorized_keys"
, unwords
[ "echo"
- , shellEscape $ authorizedKeysLine rsynconly dir pubkey
+ , shellEscape $ authorizedKeysLine gitannexshellonly dir pubkey
, ">>~/.ssh/authorized_keys"
]
]
@@ -141,11 +193,11 @@ addAuthorizedKeysCommand rsynconly dir pubkey = intercalate "&&"
runshell var = "exec git-annex-shell -c \"" ++ var ++ "\""
authorizedKeysLine :: Bool -> FilePath -> SshPubKey -> String
-authorizedKeysLine rsynconly dir pubkey
+authorizedKeysLine gitannexshellonly dir pubkey
+ | gitannexshellonly = limitcommand ++ pubkey
{- TODO: Locking down rsync is difficult, requiring a rather
- long perl script. -}
- | rsynconly = pubkey
- | otherwise = limitcommand ++ pubkey
+ | otherwise = pubkey
where
limitcommand = "command=\"GIT_ANNEX_SHELL_DIRECTORY="++shellEscape dir++" ~/.ssh/git-annex-shell\",no-agent-forwarding,no-port-forwarding,no-X11-forwarding "
diff --git a/Command/GCryptSetup.hs b/Command/GCryptSetup.hs
new file mode 100644
index 000000000..a27e470c1
--- /dev/null
+++ b/Command/GCryptSetup.hs
@@ -0,0 +1,35 @@
+{- git-annex command
+ -
+ - Copyright 2013 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Command.GCryptSetup where
+
+import Common.Annex
+import Command
+import Annex.UUID
+import qualified Remote.GCrypt
+import qualified Git
+
+def :: [Command]
+def = [dontCheck repoExists $ noCommit $
+ command "gcryptsetup" paramValue seek
+ SectionPlumbing "sets up gcrypt repository"]
+
+seek :: [CommandSeek]
+seek = [withStrings start]
+
+start :: String -> CommandStart
+start gcryptid = next $ next $ do
+ g <- gitRepo
+ u <- getUUID
+ gu <- Remote.GCrypt.getGCryptUUID True g
+ if u == NoUUID && gu == Nothing
+ then if Git.repoIsLocalBare g
+ then do
+ void $ Remote.GCrypt.setupRepo gcryptid g
+ return True
+ else error "cannot use gcrypt in a non-bare repository"
+ else error "gcryptsetup permission denied"
diff --git a/Git/Config.hs b/Git/Config.hs
index db795b7a7..a41712add 100644
--- a/Git/Config.hs
+++ b/Git/Config.hs
@@ -177,3 +177,14 @@ fromFile r f = fromPipe r "git"
, File f
, Param "--list"
]
+
+{- Changes a git config setting in the specified config file.
+ - (Creates the file if it does not already exist.) -}
+changeFile :: FilePath -> String -> String -> IO Bool
+changeFile f k v = boolSystem "git"
+ [ Param "config"
+ , Param "--file"
+ , File f
+ , Param k
+ , Param v
+ ]
diff --git a/GitAnnexShell.hs b/GitAnnexShell.hs
index c34b3b307..b5f6804e7 100644
--- a/GitAnnexShell.hs
+++ b/GitAnnexShell.hs
@@ -30,24 +30,26 @@ import qualified Command.RecvKey
import qualified Command.SendKey
import qualified Command.TransferInfo
import qualified Command.Commit
+import qualified Command.GCryptSetup
cmds_readonly :: [Command]
cmds_readonly = concat
- [ Command.ConfigList.def
- , Command.InAnnex.def
- , Command.SendKey.def
- , Command.TransferInfo.def
+ [ gitAnnexShellCheck Command.ConfigList.def
+ , gitAnnexShellCheck Command.InAnnex.def
+ , gitAnnexShellCheck Command.SendKey.def
+ , gitAnnexShellCheck Command.TransferInfo.def
]
cmds_notreadonly :: [Command]
cmds_notreadonly = concat
- [ Command.RecvKey.def
- , Command.DropKey.def
- , Command.Commit.def
+ [ gitAnnexShellCheck Command.RecvKey.def
+ , gitAnnexShellCheck Command.DropKey.def
+ , gitAnnexShellCheck Command.Commit.def
+ , Command.GCryptSetup.def
]
cmds :: [Command]
-cmds = map gitAnnexShellCheck $ map adddirparam $ cmds_readonly ++ cmds_notreadonly
+cmds = map adddirparam $ cmds_readonly ++ cmds_notreadonly
where
adddirparam c = c { cmdparamdesc = "DIRECTORY " ++ cmdparamdesc c }
@@ -191,8 +193,8 @@ checkEnv var = do
{- Modifies a Command to check that it is run in either a git-annex
- repository, or a repository with a gcrypt-id set. -}
-gitAnnexShellCheck :: Command -> Command
-gitAnnexShellCheck = addCheck okforshell . dontCheck repoExists
+gitAnnexShellCheck :: [Command] -> [Command]
+gitAnnexShellCheck = map $ addCheck okforshell . dontCheck repoExists
where
okforshell = unlessM (isInitialized <||> isJust . gcryptId <$> Annex.getGitConfig) $
error "Not a git-annex or gcrypt repository."
diff --git a/Remote/GCrypt.hs b/Remote/GCrypt.hs
index acbf3cd68..8ba640bac 100644
--- a/Remote/GCrypt.hs
+++ b/Remote/GCrypt.hs
@@ -9,7 +9,8 @@ module Remote.GCrypt (
remote,
gen,
getGCryptUUID,
- coreGCryptId
+ coreGCryptId,
+ setupRepo
) where
import qualified Data.Map as M
@@ -163,7 +164,7 @@ gCryptSetup mu c = go $ M.lookup "gitrepo" c
{- Run a git fetch and a push to the git repo in order to get
- its gcrypt-id set up, so that later git annex commands
- - will use the remote as a ggcrypt remote. The fetch is
+ - will use the remote as a gcrypt remote. The fetch is
- needed if the repo already exists; the push is needed
- if the repo has not yet been initialized by gcrypt. -}
void $ inRepo $ Git.Command.runBool
@@ -185,51 +186,50 @@ gCryptSetup mu c = go $ M.lookup "gitrepo" c
method <- setupRepo gcryptid =<< inRepo (Git.Construct.fromRemoteLocation gitrepo)
gitConfigSpecialRemote u c' "gcrypt" (fromAccessMethod method)
return (c', u)
- else error "uuid mismatch"
+ else error $ "uuid mismatch " ++ show (u, mu, gcryptid)
{- Sets up the gcrypt repository. The repository is either a local
- repo, or it is accessed via rsync directly, or it is accessed over ssh
- and git-annex-shell is available to manage it.
-
- - The gcrypt-id is stored in the gcrypt repository for later
- - double-checking and identification. This is always done using rsync.
+ - The GCryptID is recorded in the repository's git config for later use.
+ - Also, if the git config has receive.denyNonFastForwards set, disable
+ - it; gcrypt relies on being able to fast-forward branches.
-}
setupRepo :: Git.GCrypt.GCryptId -> Git.Repo -> Annex AccessMethod
setupRepo gcryptid r
| Git.repoIsUrl r = do
- accessmethod <- rsyncsetup
+ (_, _, accessmethod) <- rsyncTransport r
case accessmethod of
- AccessDirect -> return AccessDirect
- AccessShell -> ifM usablegitannexshell
+ AccessDirect -> rsyncsetup
+ AccessShell -> ifM gitannexshellsetup
( return AccessShell
- , return AccessDirect
+ , rsyncsetup
)
| Git.repoIsLocalUnknown r = localsetup =<< liftIO (Git.Config.read r)
| otherwise = localsetup r
where
localsetup r' = do
- liftIO $ Git.Command.run [Param "config", Param coreGCryptId, Param gcryptid] r'
+ let setconfig k v = liftIO $ Git.Command.run [Param "config", Param k, Param v] r'
+ setconfig coreGCryptId gcryptid
+ setconfig denyNonFastForwards (Git.Config.boolConfig False)
return AccessDirect
- {- Download any git config file from the remote,
- - add the gcryptid to it, and send it back.
- -
- - At the same time, create the objectDir on the remote,
- - which is needed for direct rsync to work.
+ {- As well as modifying the remote's git config,
+ - create the objectDir on the remote,
+ - which is needed for direct rsync of objects to work.
-}
rsyncsetup = Remote.Rsync.withRsyncScratchDir $ \tmp -> do
liftIO $ createDirectoryIfMissing True $ tmp </> objectDir
- (rsynctransport, rsyncurl, accessmethod) <- rsyncTransport r
+ (rsynctransport, rsyncurl, _) <- rsyncTransport r
let tmpconfig = tmp </> "config"
void $ liftIO $ rsync $ rsynctransport ++
[ Param $ rsyncurl ++ "/config"
, Param tmpconfig
]
- liftIO $ appendFile tmpconfig $ unlines
- [ ""
- , "[core]"
- , "\tgcrypt-id = " ++ gcryptid
- ]
+ liftIO $ do
+ void $ Git.Config.changeFile tmpconfig coreGCryptId gcryptid
+ void $ Git.Config.changeFile tmpconfig denyNonFastForwards (Git.Config.boolConfig False)
ok <- liftIO $ rsync $ rsynctransport ++
[ Params "--recursive"
, Param $ tmp ++ "/"
@@ -237,12 +237,14 @@ setupRepo gcryptid r
]
unless ok $
error "Failed to connect to remote to set it up."
- return accessmethod
+ return AccessDirect
+
+ {- Ask git-annex-shell to configure the repository as a gcrypt
+ - repository. May fail if it is too old. -}
+ gitannexshellsetup = Ssh.onRemote r (boolSystem, False)
+ "gcryptsetup" [ Param gcryptid ] []
- {- Check if git-annex shell is installed, and is a new enough
- - version to work in a gcrypt repo. -}
- usablegitannexshell = either (const False) (const True)
- <$> Ssh.onRemote r (Git.Config.fromPipe r, Left undefined) "configlist" [] []
+ denyNonFastForwards = "receive.denyNonFastForwards"
shellOrRsync :: Remote -> Annex a -> Annex a -> Annex a
shellOrRsync r ashell arsync = case method of
diff --git a/debian/changelog b/debian/changelog
index 6727315c0..f7c79e6ea 100644
--- a/debian/changelog
+++ b/debian/changelog
@@ -28,6 +28,8 @@ git-annex (4.20130921) UNRELEASED; urgency=low
written by MacGPG.
* assistant: More robust inotify handling; avoid crashing if a directory
cannot be read.
+ * Disable receive.denyNonFastForwards when setting up a gcrypt special
+ remote, since gcrypt needs to be able to fast-forward the master branch.
-- Joey Hess <joeyh@debian.org> Sun, 22 Sep 2013 19:42:29 -0400
diff --git a/doc/design/assistant/encrypted_git_remotes.mdwn b/doc/design/assistant/encrypted_git_remotes.mdwn
index 63b7be67a..915f64d28 100644
--- a/doc/design/assistant/encrypted_git_remotes.mdwn
+++ b/doc/design/assistant/encrypted_git_remotes.mdwn
@@ -3,14 +3,15 @@ using [git-remote-gcrypt](https://github.com/blake2-ppc/git-remote-gcrypt).
There are at least two use cases for this in the assistant:
-* Storing an encrypted git repository on a local drive.
+* Storing an encrypted git repository on a local drive. **done**
* Or on a remote server. This could even allow using github. But more
likely would be a shell server that has git-annex-shell on it so can
also store file contents, and which is not trusted with unencrypted data.
+ **done**
git-remote-gcrypt is already usable with git-annex. What's needed is
to make sure it's installed (ie, get it packaged into distros or embedded
-into git-annex), and make it easy to set up from the webapp.
+into git-annex), and make it easy to set up from the webapp. **done**
Hmm, this will need gpg key creation, so would also be a good opportunity
to make the webapp allow using that for special remotes too.
@@ -18,4 +19,4 @@ to make the webapp allow using that for special remotes too.
One change is needed in git-annex core.. It currently does not support
storing encrypted files on git remotes, only on special remotes. Perhaps
the way to deal with this is to make it consider git-remote-grypt remotes
-to be a special remote type?
+to be a special remote type? **done**
diff --git a/doc/forum/Android:_is_constant_high_cpu_usage_to_be_expected__63__/comment_1_7880fc38792a1fcbf3e5c47e8bcaabce._comment b/doc/forum/Android:_is_constant_high_cpu_usage_to_be_expected__63__/comment_1_7880fc38792a1fcbf3e5c47e8bcaabce._comment
new file mode 100644
index 000000000..28f3dfb92
--- /dev/null
+++ b/doc/forum/Android:_is_constant_high_cpu_usage_to_be_expected__63__/comment_1_7880fc38792a1fcbf3e5c47e8bcaabce._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawmKKg3Vmzk7KwRGRKjHVdtyoj1JfxLX6NM"
+ nickname="Tom"
+ subject="comment 1"
+ date="2013-10-01T17:38:03Z"
+ content="""
+I've had this issue as well. Saw a comment on Joey's blog that implies he knows about it and that a fix will be released soon.
+"""]]
diff --git a/doc/forum/Import_options/comment_2_21da91f08cb6b28ae3e79ade033db516._comment b/doc/forum/Import_options/comment_2_21da91f08cb6b28ae3e79ade033db516._comment
new file mode 100644
index 000000000..a3e259624
--- /dev/null
+++ b/doc/forum/Import_options/comment_2_21da91f08cb6b28ae3e79ade033db516._comment
@@ -0,0 +1,17 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkeJKC5Sy0stmcTWyePOLEVv0G-x1yaT_w"
+ nickname="Josef"
+ subject="Additional Comments"
+ date="2013-09-30T21:33:31Z"
+ content="""
+Imported several thousand files to annex and would like to add the following comments:
+
+- it would be great to have an option to exclude hidden dot files from import,
+
+- empty directories should be deleted when files located in the directories are deleted,
+
+- \"git annex add\" seems to process directories and files alphabetically, unfortunately import processes files in a different order, which makes it hard to predict which files are deleted when deduplicating,
+
+Cheers,
+
+"""]]
diff --git a/doc/forum/Newbie_stuck_at___34__Unable_to_connect_to_the_Jabber_server__34__/comment_3_92a52b523ed4c68b70ddcabc2a050b76._comment b/doc/forum/Newbie_stuck_at___34__Unable_to_connect_to_the_Jabber_server__34__/comment_3_92a52b523ed4c68b70ddcabc2a050b76._comment
new file mode 100644
index 000000000..9b1d95e78
--- /dev/null
+++ b/doc/forum/Newbie_stuck_at___34__Unable_to_connect_to_the_Jabber_server__34__/comment_3_92a52b523ed4c68b70ddcabc2a050b76._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawmKKg3Vmzk7KwRGRKjHVdtyoj1JfxLX6NM"
+ nickname="Tom"
+ subject="comment 3"
+ date="2013-10-01T18:33:05Z"
+ content="""
+I've got the same issue on Xubuntu 13.04. I installed using this script: https://github.com/zerodogg/scriptbucket/blob/master/gitannex-install
+
+`git-annex version` makes no mention of DNS or ADNS
+
+`host` command is installed on my machine. any suggestions on how best to fix for this setup?
+"""]]
diff --git a/doc/git-annex-shell.mdwn b/doc/git-annex-shell.mdwn
index 38659d0e2..c866154ac 100644
--- a/doc/git-annex-shell.mdwn
+++ b/doc/git-annex-shell.mdwn
@@ -60,6 +60,10 @@ first "/~/" or "/~user/" is expanded to the specified home directory.
This commits any staged changes to the git-annex branch.
It also runs the annex-content hook.
+* gcryptsetup gcryptid
+
+ Sets up a repository as a gcrypt repository.
+
# OPTIONS
Most options are the same as in git-annex. The ones specific