Skip to content

Instantly share code, notes, and snippets.

@khanage
Created September 5, 2016 13:56
Show Gist options
  • Save khanage/8ac1717f8991a53027180b7765396a7e to your computer and use it in GitHub Desktop.
Save khanage/8ac1717f8991a53027180b7765396a7e to your computer and use it in GitHub Desktop.
Opens up the branches page for a given repo on osx with chrome installed
#!/usr/bin/env stack
-- stack --resolver lts-6.5 --install-ghc runghc --package turtle --package parsec --package text --package either
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
import Control.Monad.Trans.Either
import Data.Functor.Identity (Identity)
import Data.Monoid ((<>))
import Data.Text (pack)
import Text.Parsec as P
import Turtle hiding (Parser)
main :: IO ()
main = sh $
do resultFromShellSilliness <- inshell shellSilliness empty
eitherT logErrorAndDie success $
do when (resultFromShellSilliness == "") complainAboutPwd
branchesAddress <- runParserInEitherT parseAddr resultFromShellSilliness
_ <- shell ("/usr/bin/open -a \"/Applications/Google Chrome.app\" '" <> branchesAddress <> "'") empty
right $ "Opening " <> branchesAddress
where
-- get the uri of the first stash remote
shellSilliness = "git remote -v | grep \"stash\" | head -n 1 | awk '{print $2}'"
logErrorAndDie errorMessage = echo errorMessage >> exit (ExitFailure 1)
success successMessage = echo successMessage >> exit ExitSuccess
complainAboutPwd = pwd >>= \dir -> left (repr dir <> " did not have a stash remote.")
runParserInEitherT parser =
bimapEitherT repr id . hoistEither . runParser parser () "Stash parser"
parseAddr
:: ParsecT Text u Identity Text
parseAddr =
asStashBranchUri
<$> parseProtocol
<* discardUser
<*> parseHost
<* discardScm
<*> parseProject
<*> parseRepoName
where
asStashBranchUri protocol host project repo =
protocol <> "://" <> pack host <> "/projects/" <> pack project <> "/repos/" <> pack repo <> "/branches"
parseProtocol =
let tryGetAnS = P.string "http" *> P.optionMaybe (P.char 's') <* P.string "://"
in maybe "http" (const "https") <$> tryGetAnS
discardUser = manyTill P.anyChar (P.char '@')
parseHost = manyTill P.anyChar (P.char '/')
discardScm = string "scm/"
parseProject = manyTill P.anyChar (P.char '/')
parseRepoName = manyTill P.anyChar (P.try (P.string ".git"))
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment