1
0
Fork 0
mirror of https://code.sup39.dev/repos/Wqawg synced 2025-01-09 07:06:46 +09:00
vervis/src/Vervis/Ssh.hs

273 lines
9.6 KiB
Haskell
Raw Normal View History

2016-03-06 20:58:48 +09:00
{- This file is part of Vervis.
-
- Written in 2016 by fr33domlover <fr33domlover@riseup.net>.
-
- Copying is an act of love. Please copy, reuse and share.
-
- The author(s) have dedicated all copyright and related and neighboring
- rights to this software to the public domain worldwide. This software is
- distributed without any warranty.
-
- You should have received a copy of the CC0 Public Domain Dedication along
- with this software. If not, see
- <http://creativecommons.org/publicdomain/zero/1.0/>.
-}
module Vervis.Ssh
( runSsh
)
where
import Prelude
import Control.Applicative ((<|>), optional)
2016-03-06 20:58:48 +09:00
import Control.Monad (when)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Logger
2016-03-06 20:58:48 +09:00
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Reader (ReaderT (runReaderT), ask)
import Data.Attoparsec.Text
import Data.ByteString (ByteString)
2016-03-06 20:58:48 +09:00
import Data.ByteString.Lazy (fromStrict)
import Data.Foldable (find)
import Data.Git.Storage (isRepo)
import Data.Monoid ((<>))
import Data.String (fromString)
import Data.Text (Text)
import Formatting ((%))
2016-03-06 20:58:48 +09:00
import Database.Persist
import Database.Persist.Sql
2016-03-06 20:58:48 +09:00
import Network.SSH
import Network.SSH.Channel
import Network.SSH.Crypto
import Network.SSH.Session
import System.FilePath ((</>))
import System.Process (CreateProcess (..), StdStream (..), createProcess, proc)
2016-03-06 20:58:48 +09:00
import qualified Data.Text as T
import qualified Formatting as F
2016-03-06 20:58:48 +09:00
import Vervis.Model
import Vervis.Settings
-------------------------------------------------------------------------------
-- Types
-------------------------------------------------------------------------------
type ChannelBase = LoggingT (ReaderT ConnectionPool IO)
type SessionBase = LoggingT (ReaderT ConnectionPool IO)
type UserAuthId = PersonId
2016-03-06 20:58:48 +09:00
type Channel = ChannelT UserAuthId ChannelBase
type Session = SessionT SessionBase UserAuthId ChannelBase
type SshChanDB = SqlPersistT Channel
type SshSessDB = SqlPersistT Session
2016-03-06 20:58:48 +09:00
data RepoSpec
= SpecUserRepo Text Text
| SpecRepo Text
deriving Show
data Action
= UploadPack RepoSpec
| ReceivePack RepoSpec
deriving Show
-- | Result of running an action on the server side as a response to an SSH
-- channel request.
data ActionResult
= ARDone Text -- ^ Action finished successfully with message
| ARProcess -- ^ Action executed process, the rest depends on the process
| ARFail Text -- ^ Action failed with message
-------------------------------------------------------------------------------
-- Utils
-------------------------------------------------------------------------------
src :: Text
src = "SSH"
2016-03-06 20:58:48 +09:00
runChanDB :: SshChanDB a -> Channel a
runChanDB action = do
pool <- lift . lift $ ask
2016-03-06 20:58:48 +09:00
runSqlPool action pool
runSessDB :: SshSessDB a -> Session a
runSessDB action = do
pool <- lift . lift $ ask
2016-03-06 20:58:48 +09:00
runSqlPool action pool
-------------------------------------------------------------------------------
-- Auth
-------------------------------------------------------------------------------
authorize :: Authorize -> Session (AuthResult UserAuthId)
authorize (Password _ _) = return AuthFail
2016-03-06 20:58:48 +09:00
authorize (PublicKey name key) = do
mpk <- runSessDB $ do
mp <- getBy $ UniquePersonLogin $ T.pack name
2016-03-06 20:58:48 +09:00
case mp of
Nothing -> return Nothing
Just (Entity pid _p) -> do
ks <- selectList [SshKeyPerson ==. pid] []
return $ Just (pid, ks)
case mpk of
2016-03-06 20:58:48 +09:00
Nothing -> do
lift $ $logInfoS src "Auth failed: Invalid user"
return AuthFail
Just (pid, keys) -> do
2016-03-06 20:58:48 +09:00
let eValue (Entity _ v) = v
matches =
(== key) . blobToKey . fromStrict . sshKeyContent . eValue
case find matches keys of
Nothing -> do
lift $ $logInfoS src "Auth failed: No matching key found"
return AuthFail
2016-03-06 20:58:48 +09:00
Just match -> do
lift $ $logInfoS src "Auth succeeded"
return $ AuthSuccess pid
2016-03-06 20:58:48 +09:00
-------------------------------------------------------------------------------
-- Actions
-------------------------------------------------------------------------------
repoSpecP :: Parser RepoSpec
repoSpecP = f <$> (msh *> part) <*> optional (char '/' *> part)
where
f repo Nothing = SpecRepo repo
f sharer (Just repo) = SpecUserRepo sharer repo
part = takeWhile1 $ \ c -> c /= '/' && c /= '\''
msh = optional (satisfy $ \ c -> c == '/' || c == '~')
actionP :: Parser Action
actionP = UploadPack <$> ("git-upload-pack '" *> repoSpecP <* char '\'')
<|> ReceivePack <$> ("git-receive-pack '" *> repoSpecP <* char '\'')
parseExec :: Text -> Either String Action
parseExec input = parseOnly (actionP <* endOfInput) input
detectAction :: ChannelRequest -> Either Text Action
detectAction (Execute s) =
case parseExec $ T.pack s of
Left _ -> Left "Unsupported command"
Right action -> Right action
detectAction _ = Left "Unsupported channel request"
resolveSpec :: RepoSpec -> Channel (Text, Text)
resolveSpec (SpecUserRepo u r) = return (u, r)
resolveSpec (SpecRepo r) = do
u <- T.pack . authUser <$> askAuthDetails
return (u, r)
resolveSpec' :: FilePath -> RepoSpec -> Channel (Text, Text, FilePath)
resolveSpec' repoDir spec = do
(u, r) <- resolveSpec spec
let repoPath = repoDir </> T.unpack u </> T.unpack r
return (u, r, repoPath)
execute :: FilePath -> [String] -> Channel ()
execute cmd args = do
lift $ $logDebugS src $
F.sformat ("Executing " % F.string % " " % F.shown) cmd args
let config = (proc cmd args)
{ std_in = CreatePipe
, std_out = CreatePipe
, std_err = CreatePipe
}
verifyPipe Nothing = error "createProcess didn't create all the pipes"
verifyPipe (Just h) = h
verifyPipes (mIn, mOut, mErr, ph) =
(verifyPipe mIn, verifyPipe mOut, verifyPipe mErr, ph)
spawnProcess $ verifyPipes <$> createProcess config
whenRepoExists :: FilePath -> Channel ActionResult -> Channel ActionResult
whenRepoExists repoPath action = do
looksGood <- liftIO $ isRepo $ fromString repoPath
if looksGood
then action
else return $ ARFail "No such git repository"
runAction :: FilePath -> Bool -> Action -> Channel ActionResult
runAction repoDir _wantReply action =
case action of
UploadPack spec -> do
(sharer, repo, repoPath) <- resolveSpec' repoDir spec
whenRepoExists repoPath $ do
execute "git-upload-pack" [repoPath]
return ARProcess
ReceivePack spec -> do
(sharer, repo, repoPath) <- resolveSpec' repoDir spec
-- Now we need to check whether the authenticated user (can get its
-- details with 'askAuthDetails') has write access to the repo.
-- This is currently true iff the authenticated user and the repo
-- sharer have the same ID. Since sharer names are unique, it's
-- enough to compare them.
userName <- T.pack . authUser <$> askAuthDetails
if userName == sharer
then whenRepoExists repoPath $ do
execute "git-receive-pack" [repoPath]
return ARProcess
else return $ ARFail "You can't push to this repository"
handle :: FilePath -> Bool -> ChannelRequest -> Channel ()
handle repoDir wantReply request = do
lift $ $logDebugS src $ T.pack $ show request
case detectAction request of
Left e -> do
lift $ $logDebugS src $ "Invalid action: " <> e
channelError $ T.unpack e
when wantReply channelFail
Right act -> do
lift $ $logDebugS src $ T.pack $ show act
res <- runAction repoDir wantReply act
case res of
ARDone msg -> do
lift $ $logDebugS src $ "Action done: " <> msg
channelMessage $ T.unpack msg
when wantReply channelSuccess
channelDone
ARProcess -> do
lift $ $logDebugS src "Action ran process"
when wantReply channelSuccess
ARFail msg -> do
lift $ $logDebugS src $ "Action failed: " <> msg
channelError $ T.unpack msg
when wantReply channelSuccess
channelDone
2016-03-06 20:58:48 +09:00
-------------------------------------------------------------------------------
-- Config and running
-------------------------------------------------------------------------------
ready :: LogFunc -> IO ()
ready = runLoggingT $ $logInfoS src "SSH server component starting"
2016-03-06 20:58:48 +09:00
mkConfig
:: AppSettings
-> ConnectionPool
-> LogFunc
-> IO (Config SessionBase ChannelBase UserAuthId)
mkConfig settings pool logFunc = do
2016-03-06 20:58:48 +09:00
keyPair <- keyPairFromFile $ appSshKeyFile settings
return $ Config
{ cSession = SessionConfig
{ scAuthMethods = ["publickey"]
, scAuthorize = authorize
, scKeyPair = keyPair
, scRunBaseMonad =
flip runReaderT pool . flip runLoggingT logFunc
2016-03-06 20:58:48 +09:00
}
, cChannel = ChannelConfig
{ ccRequestHandler = handle $ appRepoDir settings
, ccRunBaseMonad =
flip runReaderT pool . flip runLoggingT logFunc
2016-03-06 20:58:48 +09:00
}
, cPort = fromIntegral $ appSshPort settings
, cReadyAction = ready logFunc
2016-03-06 20:58:48 +09:00
}
runSsh :: AppSettings -> ConnectionPool -> LogFunc -> IO ()
runSsh settings pool logFunc = do
config <- mkConfig settings pool logFunc
2016-03-06 20:58:48 +09:00
startConfig config