{- This file is part of funbot-git-hook. - - Written in 2015 by fr33domlover . - - ♡ 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 - . -} -- For pattern matching Data.Text values {-# LANGUAGE OverloadedStrings #-} module Main (main) where import Control.Exception (tryJust) import Control.Monad (guard, forM, liftM) import Data.Either (partitionEithers) import Data.Maybe (catMaybes, fromMaybe, mapMaybe) import Data.Git import Data.Git.Ref (fromHex) import Data.Git.Repository (configGet) import Data.Git.Storage.Object (Object (..)) import Data.Text.Template import Network.URI (URI, parseURI) import System.Directory (getCurrentDirectory) import System.FilePath (splitExtension, takeFileName) import System.IO.Error (isEOFError) import Text.Printf (printf) import qualified Data.ByteString as B import qualified Data.ByteString.Char8 as BC import qualified Data.ByteString.UTF8 as BU import qualified Data.Text as T import qualified Data.Text.Lazy as TL import qualified Data.Text.Encoding as T import qualified FunBot.Client as F import qualified FunBot.ExtEvents as F hiding (ExtEvent) ------------------------------------------------------------------------------- -- Read input lines ------------------------------------------------------------------------------- -- | Maximal number of refs to read. The bot will announce only few of them -- anyway, and we don't want to leave open the option of getting stuck in an -- infinite loop. Just make sure to set this high enough to be above actual -- normal use cases. maxRefs :: Int maxRefs = 3000 -- | Read from stdin one line of reflog data passed by git. Return 'Nothing' if -- the end of the list has been reached. readRef :: IO (Maybe (B.ByteString, B.ByteString, B.ByteString)) readRef = do res <- tryJust (guard . isEOFError) B.getLine case res of Left _ -> return Nothing Right line -> case BC.words line of [old, new, ref] -> return $ Just (old, new, ref) _ -> error "An input line must contain exactly 3 spaces" -- | Read from stdin all the reflog data passed by git. readRefs :: IO [(B.ByteString, B.ByteString, B.ByteString)] readRefs = let f triples 0 = return triples f triples left = do mtriple <- readRef case mtriple of Just triple -> f (triple : triples) (left - 1) Nothing -> return triples in liftM reverse $ f [] maxRefs ------------------------------------------------------------------------------- -- Read hash+branch pairs ------------------------------------------------------------------------------- -- | Check whether a given change is an update of a ref. Creations and -- deletions of branches aren't relevant to us. isUpdate :: B.ByteString -> B.ByteString -> Bool isUpdate old new = BC.any (/= '0') old || BC.any (/= '0') new -- | A 'stripPrefix' variant for byte strings: Strip if prefix exists, -- otherwise return the input as is. stripPrefixB :: B.ByteString -> B.ByteString -> B.ByteString stripPrefixB pref b = if pref `B.isPrefixOf` b then B.drop (B.length pref) b else b -- | Get details of a relevant change, or discard if not relevant. parseChange :: B.ByteString -> B.ByteString -> B.ByteString -> Maybe (B.ByteString, B.ByteString) parseChange old new name = if isUpdate old new then Just (new, stripPrefixB "refs/heads/" name) else Nothing -- | Read input and filter relevant changes. readChanges :: IO [(B.ByteString, B.ByteString)] readChanges = let f (old, new, name) = parseChange old new name in liftM (mapMaybe f) readRefs ------------------------------------------------------------------------------- -- Read commits and tags, filter out the rest ------------------------------------------------------------------------------- -- | Determine repo name using the system. getRepoName :: IO String getRepoName = do file <- liftM takeFileName getCurrentDirectory return $ case splitExtension file of (name, ".git") -> name _ -> file {- Get commit URL template from program arguments. getUrlTemplate :: IO (Maybe Template) getUrlTemplate = do args <- getArgs return $ case args of [] -> Nothing [arg] -> Just $ template $ T.pack arg _ -> error "Too many args! Expected at most 1, the URL template."-} -- | Get commit URL template from git config. This should probablt be in the -- global config, not the per-repo one, since the URL template is likely -- identical for all repos. getUrlTemplate :: Git -> IO (Maybe Template) getUrlTemplate git = liftM (fmap $ template . T.pack) $ configGet git "funbot" "commit-url-template" -- | Get repo owner string from git config. This would usually be in the -- per-repo config. Gitolite can make it easier, defining it in @gitolite.conf@ -- at the same place @gitweb.owner@ can be defined. Note that this is data -- /required/, therefore not finding it in the config causes an 'error'. getRepoOwner :: Git -> IO String getRepoOwner git = liftM (fromMaybe $ error "funbot.owner not found in git config") $ configGet git "funbot" "owner" -- | Apply template. subst :: Maybe Template -> Context -> TL.Text subst Nothing _ = TL.empty subst (Just t) c = render t c -- | Create a mapping from URL template variables to their values. makeContext :: T.Text -> T.Text -> T.Text -> Context makeContext repo branch commit var = case var of "repo" -> repo "branch" -> branch "commit" -> T.take 8 commit _ -> T.pack "NO_SUCH_VAR" -- | Read commit and tag data from repo, discard irrelevant input. readEventData :: Git -> IO ([Either (F.Commit, String) F.Tag], String, String) readEventData git = do repo <- getRepoName let mkCtx = makeContext $ T.pack repo owner <- getRepoOwner git templ <- getUrlTemplate git cs <- readChanges ms <- forM cs $ \ (hash, branch) -> do mobj <- getObject git (fromHex hash) True return $ case mobj of Just (ObjCommit c) -> let ctx = mkCtx (T.decodeUtf8 branch) (T.decodeUtf8 hash) author = BU.toString $ personName $ commitAuthor c title = BU.toString $ BC.takeWhile (/= '\n') $ commitMessage c url = TL.unpack $ subst templ ctx in Just $ Left ( F.Commit { F.commitAuthor = author , F.commitTitle = title , F.commitUrl = url } , BU.toString branch ) Just (ObjTag t) -> let author = BU.toString $ personName $ tagName t name = BU.toString $ BC.takeWhile (/= '\n') $ tagS t in Just $ Right F.Tag { F.tagAuthor = author , F.tagRef = name , F.tagRepo = repo , F.tagRepoOwner = owner } _ -> Nothing return (catMaybes ms, repo, owner) ------------------------------------------------------------------------------- -- Read and collect event data into push and tag events ------------------------------------------------------------------------------- -- | Collect consecutive commits to the same branch into lists. groupCommits :: [Either (F.Commit, String) F.Tag] -> ([Either ([F.Commit], String) F.Tag], Int, Int) groupCommits l = let f (Right t) xs = Right t : xs f (Left (c, b)) [] = [Left ([c], b)] f (Left (c, b)) xs@(Right _ : _) = Left ([c], b) : xs f (Left (c, b)) xs@(Left (cs, b') : r) = if b == b' then Left (c : cs, b) : r else Left ([c], b) : xs (lc, lt) = partitionEithers l in (foldr f [] l, length lc, length lt) -- | Given grouped event data, prepare event records. makeEvents :: [Either ([F.Commit], String) F.Tag] -> String -> String -> [F.ExtEvent] makeEvents gs repo owner = let mkBranch n = F.Branch { F.branchName = n , F.branchRepo = repo , F.branchRepoOwner = owner } mk (Left (cs, b)) = F.mkPushEvent F.Push { F.pushBranch = mkBranch b , F.pushCommits = cs } mk (Right t) = F.mkTagEvent t in map mk gs -- | Read input, filter relevant events. readEvents :: Git -> IO ([F.ExtEvent], Int, Int) readEvents git = do (ds, repo, owner) <- readEventData git let (gs, nc, nt) = groupCommits ds return (makeEvents gs repo owner, nc, nt) ------------------------------------------------------------------------------- -- Read input, filter relevant events and send to a funbot ------------------------------------------------------------------------------- -- | Read the funbot instance web hook URL from git config getBotClientHookUrl :: Git -> IO URI getBotClientHookUrl git = do ms <- configGet git "funbot" "bot-url" let s = fromMaybe (error "funbot.bot-url not found in git config") ms let muri = parseURI s uri = fromMaybe (error "funbot.bot-url is an invalid URL") muri return uri -- | Like 'when', but takes a 'Just' and passs the value to the action. whenJust :: Monad m => Maybe a -> (a -> m ()) -> m () whenJust (Just x) f = f x whenJust Nothing _ = return () -- | Try to send an event to the bot, print a message if failed. send :: F.Bot -> Int -> F.ExtEvent -> Int -> IO () send bot total event i = do merr <- F.sendExtEvent bot event whenJust merr $ \ err -> putStrLn $ printf "Failed to send %v of %v: %v" i total (show err) main :: IO () main = withCurrentRepo $ \ git -> do (events, nc, nt) <- readEvents git url <- getBotClientHookUrl git let bot = F.mkBot url False putStrLn $ printf "Reporting %v commits and %v tags to funbot" nc nt let len = length events pairs = zip events [1..] mapM_ (uncurry $ send bot len) pairs