{-# LANGUAGE OverloadedStrings #-} {-| Module : Text.JSON.WebHooks.Bitbucket Description : Parses Bitbucket WebHook using Aeson lense Copyright : (c) Philip Woods 2015 License : AGPL-3 Maintainer : elzairthesorcerer@gmail.com Stability : experimental Portabiltity : Linux -} module Text.JSON.WebHooks.Bitbucket ( parseHook, testHook ) where import Control.Applicative ((<$>)) import Control.Lens ((^?!),(^..), traverse, to) import Data.Aeson.Lens (key, _Array, _String) import qualified Data.ByteString.Lazy.Char8 as BS import Data.Info (ProjectInfo(..)) import Data.List (nub) import qualified Data.Text as DT -- | Parse Webhook request using lenses and return a list containing -- information on every mentioned project; filter duplicate entries parseHook :: BS.ByteString -- ^ Input JSON -> [ProjectInfo] -- ^ The list of repositories -- and branches in JSON parseHook contents = let name = stripSlashes $ extractRepositoryName contents branches = extractBranches contents in nub $ (\b -> ProjectInfo{provider = "bitbucket", repository = name, branch = b, preCommands = Nothing, hostInfo = Nothing}) <$> branches -- | Strip first and last character from string stripSlashes :: DT.Text -- ^ \/repository\/name\/ -> DT.Text -- ^ repository\/name stripSlashes input = DT.reverse $ DT.drop 1 $ DT.reverse $ DT.drop 1 input -- | Extract name of repository from JSON extractRepositoryName :: BS.ByteString -- ^ Input JSON -> DT.Text -- ^ Repository Name extractRepositoryName str = str ^?! key "repository" . key "absolute_url" . _String -- | Extract names of branches from JSON extractBranches :: BS.ByteString -- ^ Input JSON -> [DT.Text] -- ^ List of branch names extractBranches str = str ^.. key "commits" . _Array . traverse . to (\o -> (o ^?! key "branch" . _String)) -- | test function for parseHook testHook :: FilePath -> IO [ProjectInfo] testHook file = do contents <- BS.readFile file return $ parseHook contents