mirror of
https://code.sup39.dev/repos/Wqawg
synced 2024-12-29 00:44:52 +09:00
Make the hook config file path include the instance host
Before this patch, if you ran more than 1 instance as the same OS user, they'd use the same config file path and overwrite it and cause post hooks to have errors due to wrong config being used.
This commit is contained in:
parent
65d730393a
commit
a700dc4208
7 changed files with 63 additions and 41 deletions
|
@ -34,15 +34,18 @@ import qualified Data.ByteString as B
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import qualified Data.Text.IO as TIO
|
import qualified Data.Text.IO as TIO
|
||||||
|
|
||||||
writeDefaultsFile :: FilePath -> FilePath -> Text -> Text -> IO ()
|
writeDefaultsFile :: FilePath -> FilePath -> Text -> Text -> Text -> IO ()
|
||||||
writeDefaultsFile path cmd sharer repo = do
|
writeDefaultsFile path cmd authority sharer repo = do
|
||||||
let file = path </> "_darcs" </> "prefs" </> "defaults"
|
let file = path </> "_darcs" </> "prefs" </> "defaults"
|
||||||
TIO.writeFile file $ defaultsContent cmd sharer repo
|
TIO.writeFile file $ defaultsContent cmd authority sharer repo
|
||||||
setFileMode file $ ownerReadMode .|. ownerWriteMode
|
setFileMode file $ ownerReadMode .|. ownerWriteMode
|
||||||
where
|
where
|
||||||
defaultsContent :: FilePath -> Text -> Text -> Text
|
defaultsContent :: FilePath -> Text -> Text -> Text -> Text
|
||||||
defaultsContent hook sharer repo =
|
defaultsContent hook authority sharer repo =
|
||||||
T.concat ["apply posthook ", T.pack hook, " ", sharer, " ", repo]
|
T.concat
|
||||||
|
[ "apply posthook "
|
||||||
|
, T.pack hook, " ", authority, " ", sharer, " ", repo
|
||||||
|
]
|
||||||
|
|
||||||
{-
|
{-
|
||||||
initialRepoTree :: FileName -> DirTree B.ByteString
|
initialRepoTree :: FileName -> DirTree B.ByteString
|
||||||
|
@ -75,18 +78,20 @@ createRepo
|
||||||
-> FilePath
|
-> FilePath
|
||||||
-- ^ Path of Vervis hook program
|
-- ^ Path of Vervis hook program
|
||||||
-> Text
|
-> Text
|
||||||
|
-- ^ Instance HTTP authority
|
||||||
|
-> Text
|
||||||
-- ^ Repo sharer textual ID
|
-- ^ Repo sharer textual ID
|
||||||
-> Text
|
-> Text
|
||||||
-- ^ Repo textual ID
|
-- ^ Repo textual ID
|
||||||
-> IO ()
|
-> IO ()
|
||||||
createRepo parent name cmd sharer repo = do
|
createRepo parent name cmd authority sharer repo = do
|
||||||
let path = parent </> name
|
let path = parent </> name
|
||||||
createDirectory path
|
createDirectory path
|
||||||
let settings = proc "darcs" ["init", "--no-working-dir", "--repodir", path]
|
let settings = proc "darcs" ["init", "--no-working-dir", "--repodir", path]
|
||||||
(_, _, _, ph) <- createProcess settings
|
(_, _, _, ph) <- createProcess settings
|
||||||
ec <- waitForProcess ph
|
ec <- waitForProcess ph
|
||||||
case ec of
|
case ec of
|
||||||
ExitSuccess -> writeDefaultsFile path cmd sharer repo
|
ExitSuccess -> writeDefaultsFile path cmd authority sharer repo
|
||||||
ExitFailure n -> error $ "darcs init failed with exit code " ++ show n
|
ExitFailure n -> error $ "darcs init failed with exit code " ++ show n
|
||||||
|
|
||||||
readPristineRoot :: FilePath -> IO (Maybe Int, Hash)
|
readPristineRoot :: FilePath -> IO (Maybe Int, Hash)
|
||||||
|
|
|
@ -54,18 +54,21 @@ instance SpecToEventTime GitTime where
|
||||||
specToEventTime = specToEventTime . gitTimeUTC
|
specToEventTime = specToEventTime . gitTimeUTC
|
||||||
specsToEventTimes = specsToEventTimes . fmap gitTimeUTC
|
specsToEventTimes = specsToEventTimes . fmap gitTimeUTC
|
||||||
|
|
||||||
hookContent :: FilePath -> Text -> Text -> Text
|
hookContent :: FilePath -> Text -> Text -> Text -> Text
|
||||||
hookContent hook sharer repo =
|
hookContent hook authority sharer repo =
|
||||||
T.concat ["#!/bin/sh\nexec ", T.pack hook, " ", sharer, " ", repo]
|
T.concat
|
||||||
|
[ "#!/bin/sh\nexec ", T.pack hook
|
||||||
|
, " ", authority, " ", sharer, " ", repo
|
||||||
|
]
|
||||||
|
|
||||||
writeHookFile :: FilePath -> FilePath -> Text -> Text -> IO ()
|
writeHookFile :: FilePath -> FilePath -> Text -> Text -> Text -> IO ()
|
||||||
writeHookFile path cmd sharer repo = do
|
writeHookFile path cmd authority sharer repo = do
|
||||||
let file = path </> "hooks" </> "post-receive"
|
let file = path </> "hooks" </> "post-receive"
|
||||||
TIO.writeFile file $ hookContent cmd sharer repo
|
TIO.writeFile file $ hookContent cmd authority sharer repo
|
||||||
setFileMode file ownerModes
|
setFileMode file ownerModes
|
||||||
|
|
||||||
initialRepoTree :: FilePath -> Text -> Text -> FileName -> DirTree Text
|
initialRepoTree :: FilePath -> Text -> Text -> Text -> FileName -> DirTree Text
|
||||||
initialRepoTree hook sharer repo dir =
|
initialRepoTree hook authority sharer repo dir =
|
||||||
Dir dir
|
Dir dir
|
||||||
[ Dir "branches" []
|
[ Dir "branches" []
|
||||||
, File "config"
|
, File "config"
|
||||||
|
@ -77,7 +80,7 @@ initialRepoTree hook sharer repo dir =
|
||||||
"Unnamed repository; edit this file to name the repository."
|
"Unnamed repository; edit this file to name the repository."
|
||||||
, File "HEAD" "ref: refs/heads/master"
|
, File "HEAD" "ref: refs/heads/master"
|
||||||
, Dir "hooks"
|
, Dir "hooks"
|
||||||
[ File "post-receive" $ hookContent hook sharer repo
|
[ File "post-receive" $ hookContent hook authority sharer repo
|
||||||
]
|
]
|
||||||
, Dir "info"
|
, Dir "info"
|
||||||
[ File "exclude" ""
|
[ File "exclude" ""
|
||||||
|
@ -105,12 +108,14 @@ createRepo
|
||||||
-> FilePath
|
-> FilePath
|
||||||
-- ^ Path of Vervis hook program
|
-- ^ Path of Vervis hook program
|
||||||
-> Text
|
-> Text
|
||||||
|
-- ^ Instance HTTP authority
|
||||||
|
-> Text
|
||||||
-- ^ Repo sharer textual ID
|
-- ^ Repo sharer textual ID
|
||||||
-> Text
|
-> Text
|
||||||
-- ^ Repo textual ID
|
-- ^ Repo textual ID
|
||||||
-> IO ()
|
-> IO ()
|
||||||
createRepo path name cmd sharer repo = do
|
createRepo path name cmd authority sharer repo = do
|
||||||
let tree = path :/ initialRepoTree cmd sharer repo name
|
let tree = path :/ initialRepoTree cmd authority sharer repo name
|
||||||
result <- writeDirectoryWith TIO.writeFile tree
|
result <- writeDirectoryWith TIO.writeFile tree
|
||||||
let errs = failures $ dirTree result
|
let errs = failures $ dirTree result
|
||||||
when (not . null $ errs) $
|
when (not . null $ errs) $
|
||||||
|
|
|
@ -61,13 +61,13 @@ import Yesod.Persist.Core
|
||||||
import Yesod.Static
|
import Yesod.Static
|
||||||
|
|
||||||
import qualified Data.Text as T (unpack)
|
import qualified Data.Text as T (unpack)
|
||||||
import qualified Data.HashMap.Strict as M (empty)
|
|
||||||
|
|
||||||
import Database.Persist.Schema.PostgreSQL (schemaBackend)
|
import Database.Persist.Schema.PostgreSQL (schemaBackend)
|
||||||
import Yesod.Mail.Send (runMailer)
|
import Yesod.Mail.Send (runMailer)
|
||||||
|
|
||||||
import Control.Concurrent.ResultShare
|
import Control.Concurrent.ResultShare
|
||||||
import Data.KeyFile
|
import Data.KeyFile
|
||||||
|
import Network.FedURI
|
||||||
import Yesod.MonadSite
|
import Yesod.MonadSite
|
||||||
|
|
||||||
import Control.Concurrent.Local
|
import Control.Concurrent.Local
|
||||||
|
@ -187,8 +187,8 @@ makeFoundation appSettings = do
|
||||||
|
|
||||||
-- Perform database migration using our application's logging settings.
|
-- Perform database migration using our application's logging settings.
|
||||||
--runLoggingT (runSqlPool (runMigration migrateAll) pool) logFunc
|
--runLoggingT (runSqlPool (runMigration migrateAll) pool) logFunc
|
||||||
|
let hLocal = appInstanceHost appSettings
|
||||||
flip runWorker app $ runSiteDB $ do
|
flip runWorker app $ runSiteDB $ do
|
||||||
let hLocal = appInstanceHost appSettings
|
|
||||||
r <- migrateDB hLocal hashidsCtx
|
r <- migrateDB hLocal hashidsCtx
|
||||||
case r of
|
case r of
|
||||||
Left err -> do
|
Left err -> do
|
||||||
|
@ -202,7 +202,8 @@ makeFoundation appSettings = do
|
||||||
writePostReceiveHooks
|
writePostReceiveHooks
|
||||||
writePostApplyHooks
|
writePostApplyHooks
|
||||||
|
|
||||||
writeHookConfig Config
|
let hostString = T.unpack $ renderAuthority hLocal
|
||||||
|
writeHookConfig hostString Config
|
||||||
{ configSecret = hookSecretText appHookSecret
|
{ configSecret = hookSecretText appHookSecret
|
||||||
, configPort = fromIntegral $ appPort appSettings
|
, configPort = fromIntegral $ appPort appSettings
|
||||||
, configMaxCommits = 20
|
, configMaxCommits = 20
|
||||||
|
|
|
@ -63,6 +63,8 @@ import qualified Database.Esqueleto as E
|
||||||
|
|
||||||
import qualified Development.Darcs.Internal.Patch.Parser as P
|
import qualified Development.Darcs.Internal.Patch.Parser as P
|
||||||
|
|
||||||
|
import Network.FedURI
|
||||||
|
import Yesod.ActivityPub
|
||||||
import Yesod.MonadSite
|
import Yesod.MonadSite
|
||||||
|
|
||||||
import Darcs.Local.Repository
|
import Darcs.Local.Repository
|
||||||
|
@ -334,6 +336,8 @@ writePostApplyHooks = do
|
||||||
E.where_ $ r E.^. RepoVcs E.==. E.val VCSDarcs
|
E.where_ $ r E.^. RepoVcs E.==. E.val VCSDarcs
|
||||||
return (s E.^. SharerIdent, r E.^. RepoIdent)
|
return (s E.^. SharerIdent, r E.^. RepoIdent)
|
||||||
hook <- asksSite $ appPostApplyHookFile . appSettings
|
hook <- asksSite $ appPostApplyHookFile . appSettings
|
||||||
|
authority <- asksSite $ renderAuthority . siteInstanceHost
|
||||||
for_ repos $ \ (E.Value shr, E.Value rp) -> do
|
for_ repos $ \ (E.Value shr, E.Value rp) -> do
|
||||||
path <- askRepoDir shr rp
|
path <- askRepoDir shr rp
|
||||||
liftIO $ writeDefaultsFile path hook (shr2text shr) (rp2text rp)
|
liftIO $
|
||||||
|
writeDefaultsFile path hook authority (shr2text shr) (rp2text rp)
|
||||||
|
|
|
@ -67,6 +67,8 @@ import qualified Data.Text.Encoding.Error as TE (lenientDecode)
|
||||||
import qualified Data.Vector as V (fromList)
|
import qualified Data.Vector as V (fromList)
|
||||||
import qualified Database.Esqueleto as E
|
import qualified Database.Esqueleto as E
|
||||||
|
|
||||||
|
import Network.FedURI
|
||||||
|
import Yesod.ActivityPub
|
||||||
import Yesod.MonadSite
|
import Yesod.MonadSite
|
||||||
|
|
||||||
import Data.ByteString.Char8.Local (takeLine)
|
import Data.ByteString.Char8.Local (takeLine)
|
||||||
|
@ -339,6 +341,7 @@ writePostReceiveHooks = do
|
||||||
E.where_ $ r E.^. RepoVcs E.==. E.val VCSGit
|
E.where_ $ r E.^. RepoVcs E.==. E.val VCSGit
|
||||||
return (s E.^. SharerIdent, r E.^. RepoIdent)
|
return (s E.^. SharerIdent, r E.^. RepoIdent)
|
||||||
hook <- asksSite $ appPostReceiveHookFile . appSettings
|
hook <- asksSite $ appPostReceiveHookFile . appSettings
|
||||||
|
authority <- asksSite $ renderAuthority . siteInstanceHost
|
||||||
for_ repos $ \ (E.Value shr, E.Value rp) -> do
|
for_ repos $ \ (E.Value shr, E.Value rp) -> do
|
||||||
path <- askRepoDir shr rp
|
path <- askRepoDir shr rp
|
||||||
liftIO $ writeHookFile path hook (shr2text shr) (rp2text rp)
|
liftIO $ writeHookFile path hook authority (shr2text shr) (rp2text rp)
|
||||||
|
|
|
@ -86,6 +86,7 @@ import qualified Data.Text.Lazy.Encoding as L (decodeUtf8With)
|
||||||
import qualified Database.Esqueleto as E
|
import qualified Database.Esqueleto as E
|
||||||
|
|
||||||
import Data.MediaType
|
import Data.MediaType
|
||||||
|
import Network.FedURI
|
||||||
import Web.ActivityPub hiding (Repo)
|
import Web.ActivityPub hiding (Repo)
|
||||||
import Yesod.ActivityPub
|
import Yesod.ActivityPub
|
||||||
import Yesod.FedURI
|
import Yesod.FedURI
|
||||||
|
@ -145,6 +146,7 @@ postReposR user = do
|
||||||
liftIO $ createDirectoryIfMissing True parent
|
liftIO $ createDirectoryIfMissing True parent
|
||||||
let repoName =
|
let repoName =
|
||||||
unpack $ CI.foldedCase $ unRpIdent $ nrpIdent nrp
|
unpack $ CI.foldedCase $ unRpIdent $ nrpIdent nrp
|
||||||
|
host <- asksSite siteInstanceHost
|
||||||
case nrpVcs nrp of
|
case nrpVcs nrp of
|
||||||
VCSDarcs -> do
|
VCSDarcs -> do
|
||||||
hook <- getsYesod $ appPostApplyHookFile . appSettings
|
hook <- getsYesod $ appPostApplyHookFile . appSettings
|
||||||
|
@ -153,6 +155,7 @@ postReposR user = do
|
||||||
parent
|
parent
|
||||||
repoName
|
repoName
|
||||||
hook
|
hook
|
||||||
|
(renderAuthority host)
|
||||||
(shr2text user)
|
(shr2text user)
|
||||||
(rp2text $ nrpIdent nrp)
|
(rp2text $ nrpIdent nrp)
|
||||||
VCSGit -> do
|
VCSGit -> do
|
||||||
|
@ -162,6 +165,7 @@ postReposR user = do
|
||||||
parent
|
parent
|
||||||
repoName
|
repoName
|
||||||
hook
|
hook
|
||||||
|
(renderAuthority host)
|
||||||
(shr2text user)
|
(shr2text user)
|
||||||
(rp2text $ nrpIdent nrp)
|
(rp2text $ nrpIdent nrp)
|
||||||
pid <- requireAuthId
|
pid <- requireAuthId
|
||||||
|
|
|
@ -149,15 +149,15 @@ instance FromJSON Push
|
||||||
|
|
||||||
instance ToJSON Push
|
instance ToJSON Push
|
||||||
|
|
||||||
getVervisCachePath :: IO FilePath
|
getVervisCachePath :: String -> IO FilePath
|
||||||
getVervisCachePath = getXdgDirectory XdgCache "vervis"
|
getVervisCachePath host = (</> host) <$> getXdgDirectory XdgCache "vervis"
|
||||||
|
|
||||||
hookConfigFileName :: String
|
hookConfigFileName :: String
|
||||||
hookConfigFileName = "hook-config.json"
|
hookConfigFileName = "hook-config.json"
|
||||||
|
|
||||||
writeHookConfig :: Config -> IO ()
|
writeHookConfig :: String -> Config -> IO ()
|
||||||
writeHookConfig config = do
|
writeHookConfig host config = do
|
||||||
cachePath <- getVervisCachePath
|
cachePath <- getVervisCachePath host
|
||||||
createDirectoryIfMissing True cachePath
|
createDirectoryIfMissing True cachePath
|
||||||
encodeFile (cachePath </> hookConfigFileName) config
|
encodeFile (cachePath </> hookConfigFileName) config
|
||||||
|
|
||||||
|
@ -306,17 +306,17 @@ reportNewCommits config sharer repo = do
|
||||||
|
|
||||||
postReceive :: IO ()
|
postReceive :: IO ()
|
||||||
postReceive = do
|
postReceive = do
|
||||||
cachePath <- getVervisCachePath
|
(host, sharer, repo) <- do
|
||||||
|
args <- getArgs
|
||||||
|
case args of
|
||||||
|
[h, s, r] -> return (h, T.pack s, T.pack r)
|
||||||
|
_ -> die "Unexpected number of arguments"
|
||||||
|
cachePath <- getVervisCachePath host
|
||||||
config <- do
|
config <- do
|
||||||
mc <- decodeFileStrict' $ cachePath </> hookConfigFileName
|
mc <- decodeFileStrict' $ cachePath </> hookConfigFileName
|
||||||
case mc of
|
case mc of
|
||||||
Nothing -> die "Parsing hook config failed"
|
Nothing -> die "Parsing hook config failed"
|
||||||
Just c -> return c
|
Just c -> return c
|
||||||
args <- getArgs
|
|
||||||
(sharer, repo) <-
|
|
||||||
case args of
|
|
||||||
[s, r] -> return (T.pack s, T.pack r)
|
|
||||||
_ -> die "Unexpected number of arguments"
|
|
||||||
reportNewCommits config sharer repo
|
reportNewCommits config sharer repo
|
||||||
|
|
||||||
reportNewPatches :: Config -> Text -> Text -> IO ()
|
reportNewPatches :: Config -> Text -> Text -> IO ()
|
||||||
|
@ -416,15 +416,15 @@ reportNewPatches config sharer repo = do
|
||||||
|
|
||||||
postApply :: IO ()
|
postApply :: IO ()
|
||||||
postApply = do
|
postApply = do
|
||||||
cachePath <- getVervisCachePath
|
(host, sharer, repo) <- do
|
||||||
|
args <- getArgs
|
||||||
|
case args of
|
||||||
|
[h, s, r] -> return (h, T.pack s, T.pack r)
|
||||||
|
_ -> die "Unexpected number of arguments"
|
||||||
|
cachePath <- getVervisCachePath host
|
||||||
config <- do
|
config <- do
|
||||||
mc <- decodeFileStrict' $ cachePath </> hookConfigFileName
|
mc <- decodeFileStrict' $ cachePath </> hookConfigFileName
|
||||||
case mc of
|
case mc of
|
||||||
Nothing -> die "Parsing hook config failed"
|
Nothing -> die "Parsing hook config failed"
|
||||||
Just c -> return c
|
Just c -> return c
|
||||||
args <- getArgs
|
|
||||||
(sharer, repo) <-
|
|
||||||
case args of
|
|
||||||
[s, r] -> return (T.pack s, T.pack r)
|
|
||||||
_ -> die "Unexpected number of arguments"
|
|
||||||
reportNewPatches config sharer repo
|
reportNewPatches config sharer repo
|
||||||
|
|
Loading…
Reference in a new issue