1
0
Fork 0
mirror of https://code.sup39.dev/repos/Wqawg synced 2024-12-31 05:24:51 +09:00

Fix: Sharer and repo in SSH address path weren't being lowercased in SSH server

The sharer and repo were being taken and used as is to check push permissions,
which is how it's supposed to be, *but* they were also being used as is to
build the repo path! So sharer and repo names that aren't all lowercase were
getting "No such repository" errors when trying to push.

I changed `RepoSpec` to hold `ShrIdent` and `RpIdent` instead of plain `Text`,
to avoid confusions like that and be clear and explicit about the
representation, and failures to find a repo after verifying it against the DB
are now logged as errors to help with debugging.

I hope this fixes the problem.
This commit is contained in:
fr33domlover 2018-06-18 08:30:57 +00:00
parent 6088b1e117
commit 9ed1f4c99d

View file

@ -53,6 +53,7 @@ import qualified Formatting as F
import Vervis.Model import Vervis.Model
import Vervis.Model.Ident import Vervis.Model.Ident
import Vervis.Model.Role import Vervis.Model.Role
import Vervis.Path
import Vervis.Settings import Vervis.Settings
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
@ -69,8 +70,8 @@ type SshChanDB = SqlPersistT Channel
type SshSessDB = SqlPersistT Session type SshSessDB = SqlPersistT Session
data RepoSpec data RepoSpec
= SpecUserRepo Text Text = SpecUserRepo ShrIdent RpIdent
| SpecRepo Text | SpecRepo RpIdent
deriving Show deriving Show
data Action data Action
@ -145,15 +146,15 @@ darcsRepoSpecP = f <$>
part <*> part <*>
optional (char '/' *> optional (part <* optional (char '/'))) optional (char '/' *> optional (part <* optional (char '/')))
where where
f sharer (Just (Just repo)) = SpecUserRepo sharer repo f sharer (Just (Just repo)) = SpecUserRepo (text2shr sharer) (text2rp repo)
f repo _ = SpecRepo repo f repo _ = SpecRepo (text2rp repo)
part = takeWhile1 $ \ c -> c /= '/' && c /= '\'' part = takeWhile1 $ \ c -> c /= '/' && c /= '\''
gitRepoSpecP :: Parser RepoSpec gitRepoSpecP :: Parser RepoSpec
gitRepoSpecP = f <$> (msh *> part) <*> optional (char '/' *> part) gitRepoSpecP = f <$> (msh *> part) <*> optional (char '/' *> part)
where where
f repo Nothing = SpecRepo repo f repo Nothing = SpecRepo (text2rp repo)
f sharer (Just repo) = SpecUserRepo sharer repo f sharer (Just repo) = SpecUserRepo (text2shr sharer) (text2rp repo)
part = takeWhile1 $ \ c -> c /= '/' && c /= '\'' part = takeWhile1 $ \ c -> c /= '/' && c /= '\''
msh = optional (satisfy $ \ c -> c == '/' || c == '~') msh = optional (satisfy $ \ c -> c == '/' || c == '~')
@ -177,17 +178,16 @@ detectAction (Execute s) =
Right action -> Right action Right action -> Right action
detectAction _ = Left "Unsupported channel request" detectAction _ = Left "Unsupported channel request"
resolveSpec :: RepoSpec -> Channel (Text, Text) resolveSpec :: RepoSpec -> Channel (ShrIdent, RpIdent)
resolveSpec (SpecUserRepo u r) = return (u, r) resolveSpec (SpecUserRepo u r) = return (u, r)
resolveSpec (SpecRepo r) = do resolveSpec (SpecRepo r) = do
u <- T.pack . authUser <$> askAuthDetails u <- text2shr . T.pack . authUser <$> askAuthDetails
return (u, r) return (u, r)
resolveSpec' :: FilePath -> RepoSpec -> Channel (Text, Text, FilePath) resolveSpec' :: FilePath -> RepoSpec -> Channel (ShrIdent, RpIdent, FilePath)
resolveSpec' repoDir spec = do resolveSpec' root spec = do
(u, r) <- resolveSpec spec (u, r) <- resolveSpec spec
let repoPath = repoDir </> T.unpack u </> T.unpack r return (u, r, repoDir root u r)
return (u, r, repoPath)
execute :: FilePath -> [String] -> Channel () execute :: FilePath -> [String] -> Channel ()
execute cmd args = do execute cmd args = do
@ -204,24 +204,33 @@ execute cmd args = do
(verifyPipe mIn, verifyPipe mOut, verifyPipe mErr, ph) (verifyPipe mIn, verifyPipe mOut, verifyPipe mErr, ph)
spawnProcess $ verifyPipes <$> createProcess config spawnProcess $ verifyPipes <$> createProcess config
whenDarcsRepoExists :: FilePath -> Channel ActionResult -> Channel ActionResult whenRepoExists
whenDarcsRepoExists repoPath action = do :: Text
looksGood <- liftIO $ doesDirectoryExist $ repoPath </> "_darcs" -> (FilePath -> IO Bool)
-> Bool
-> FilePath
-> Channel ActionResult
-> Channel ActionResult
whenRepoExists vcs checkFS checkedDB repoPath action = do
looksGood <- liftIO $ checkFS repoPath
if looksGood if looksGood
then action then action
else return $ ARFail "No such darcs repository" else do
when checkedDB $ lift $ $logErrorS src $
T.concat [vcs, " repo not found! ", T.pack repoPath]
return $ ARFail $ T.concat ["No such ", vcs, " repository"]
whenGitRepoExists :: FilePath -> Channel ActionResult -> Channel ActionResult whenDarcsRepoExists
whenGitRepoExists repoPath action = do :: Bool -> FilePath -> Channel ActionResult -> Channel ActionResult
looksGood <- liftIO $ isRepo $ fromString repoPath whenDarcsRepoExists =
if looksGood whenRepoExists "Darcs" $ doesDirectoryExist . (</> "_darcs")
then action
else return $ ARFail "No such git repository"
canPushTo :: Text -> Text -> Channel Bool whenGitRepoExists
canPushTo shr' rp' = do :: Bool -> FilePath -> Channel ActionResult -> Channel ActionResult
let shr = text2shr shr' whenGitRepoExists = whenRepoExists "Git" $ isRepo . fromString
rp = text2rp rp'
canPushTo :: ShrIdent -> RpIdent -> Channel Bool
canPushTo shr rp = do
pid <- authId <$> askAuthDetails pid <- authId <$> askAuthDetails
ma <- runChanDB $ runMaybeT $ do ma <- runChanDB $ runMaybeT $ do
Entity sid _sharer <- MaybeT $ getBy $ UniqueSharer shr Entity sid _sharer <- MaybeT $ getBy $ UniqueSharer shr
@ -241,27 +250,27 @@ runAction repoDir _wantReply action =
case action of case action of
DarcsTransferMode spec -> do DarcsTransferMode spec -> do
(_sharer, _repo, repoPath) <- resolveSpec' repoDir spec (_sharer, _repo, repoPath) <- resolveSpec' repoDir spec
whenDarcsRepoExists repoPath $ do whenDarcsRepoExists False repoPath $ do
execute "darcs" ["transfer-mode", "--repodir", repoPath] execute "darcs" ["transfer-mode", "--repodir", repoPath]
return ARProcess return ARProcess
DarcsApply spec -> do DarcsApply spec -> do
(sharer, repo, repoPath) <- resolveSpec' repoDir spec (sharer, repo, repoPath) <- resolveSpec' repoDir spec
can <- canPushTo sharer repo can <- canPushTo sharer repo
if can if can
then whenDarcsRepoExists repoPath $ do then whenDarcsRepoExists True repoPath $ do
execute "darcs" ["apply", "--all", "--repodir", repoPath] execute "darcs" ["apply", "--all", "--repodir", repoPath]
return ARProcess return ARProcess
else return $ ARFail "You can't push to this repository" else return $ ARFail "You can't push to this repository"
GitUploadPack spec -> do GitUploadPack spec -> do
(_sharer, _repo, repoPath) <- resolveSpec' repoDir spec (_sharer, _repo, repoPath) <- resolveSpec' repoDir spec
whenGitRepoExists repoPath $ do whenGitRepoExists False repoPath $ do
execute "git-upload-pack" [repoPath] execute "git-upload-pack" [repoPath]
return ARProcess return ARProcess
GitReceivePack spec -> do GitReceivePack spec -> do
(sharer, repo, repoPath) <- resolveSpec' repoDir spec (sharer, repo, repoPath) <- resolveSpec' repoDir spec
can <- canPushTo sharer repo can <- canPushTo sharer repo
if can if can
then whenGitRepoExists repoPath $ do then whenGitRepoExists True repoPath $ do
execute "git-receive-pack" [repoPath] execute "git-receive-pack" [repoPath]
return ARProcess return ARProcess
else return $ ARFail "You can't push to this repository" else return $ ARFail "You can't push to this repository"