Skip to content

Instantly share code, notes, and snippets.

@roman
Created September 15, 2011 22:05
Show Gist options
  • Save roman/1220620 to your computer and use it in GitHub Desktop.
Save roman/1220620 to your computer and use it in GitHub Desktop.
Experiments with Git + Haskell
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Control.Applicative
import HSH ((-|-))
import qualified HSH as Shell
import qualified Data.Attoparsec.Char8 as Parser
import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as BS
-------------------------------------------------------------------------------
newtype CommitFileInfo = CFI { unwrapCFI :: (Int, Int, ByteString) } deriving (Show)
data Commit
= Commit {
commitId :: ByteString
, commitAuthor :: ByteString
, commitEmail :: ByteString
, commitSubject :: ByteString
, commitFiles :: [CommitFileInfo]
}
deriving (Show)
-------------------------------------------------------------------------------
gitLog :: IO ByteString
gitLog =
BS.pack <$>
Shell.run ("git log --pretty=\"%h, %cn, %ce, %s\" --numstat --author=roman" :: String)
countLines :: [Commit] -> Int
countLines = foldr helper 0
where
helper (Commit { commitFiles = fs }) acc = acc + (sum $ map helper2 fs)
helper2 (CFI (a, _, _)) = a
-------------------------------------------------------------------------------
pToken = Parser.takeTill (\c -> c == ',')
<* Parser.char ','
<* Parser.skipSpace
pEOL = Parser.takeTill
(\c -> c == '\n' || c == '\r') <* Parser.skipSpace
pString = Parser.takeTill Parser.isSpace <* Parser.skipSpace
pNumber = Parser.decimal <* Parser.skipSpace
pCommitFileInfo = CFI <$> pTriple
pTriple = (,,) <$> pNumber
<*> pNumber
<*> pString
pCommit = Commit <$> pToken
<*> pToken
<*> pToken
<*> pEOL
<*> (Parser.many1 pCommitFileInfo)
-------------------------------------------------------------------------------
main :: IO ()
main = Shell.bracketCD "/home/vagrant/.vim" $
--gitLog >>= print
gitLog >>= \e ->
case Parser.parseOnly (Parser.many pCommit) e of
Right result -> print $ countLines result
Left e -> print e
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment