Skip to content

Commit

Permalink
Merge pull request #5 from fujimura/follow-mv-and-count-commits
Browse files Browse the repository at this point in the history
Follow file move and count changes
  • Loading branch information
fujimura authored Feb 3, 2024
2 parents d5627b0 + 82b225d commit ba197de
Show file tree
Hide file tree
Showing 10 changed files with 280 additions and 73 deletions.
4 changes: 4 additions & 0 deletions .ghci
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as T
import qualified Text.Trifecta.Parser as P
5 changes: 4 additions & 1 deletion .github/workflows/ci.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,10 @@ jobs:
with:
ghc-version: ${{ matrix.ghc }}
cabal-version: ${{ matrix.cabal }}
- run: cabal test --test-show-details=direct
- run: |
git config --global user.email "[email protected]"
git config --global user.name "John Doe"
cabal test --test-show-details=direct
build:
name: Build on GHC ${{ matrix.ghc }}
runs-on: ubuntu-latest
Expand Down
29 changes: 14 additions & 15 deletions README.md
Original file line number Diff line number Diff line change
@@ -1,12 +1,11 @@

# git-freq ![ci](https://github.com/fujimura/git-freq/actions/workflows/ci.yaml/badge.svg)

A Git subcommand to show total addition, deletion per file
A Git subcommand to show total addition, deletion, count of changes per file

## Installation

```
$ stack install git-freq
$ cabal install git-freq
```

## Usage
Expand All @@ -19,20 +18,20 @@ See `git freq --help` for more options.

## Example

[Lens](https://github.com/ekmett/lens) at [2587bb01](https://github.com/ekmett/lens/commit/2587bb01a1f63199130b15c9e65bf4557480318d)
[Lens](https://github.com/ekmett/lens) at [2587bb01](https://github.com/ekmett/lens/commit/60f773bdb8538d9023983e020b5cf7d0e1687df9)

```
$ git freq | head
src/Control/Lens.hs,5365,5263
src/Control/Lens/Fold.hs,5885,3471
src/Control/Lens/Internal.hs,4205,4123
src/Control/Lens/Type.hs,3493,2869
src/Control/Lens/TH.hs,3530,2066
src/Control/Lens/Setter.hs,3097,1846
src/Control/Lens/Internal/Zipper.hs,2432,2436
src/Control/Lens/Traversal.hs,2846,1628
src/Control/Exception/Lens.hs,2646,1697
src/Control/Lens/Plated.hs,2395,1715
$ git freq | tail
src/Control/Lens/Internal/Zipper.hs,1995,2003,108
src/Control/Lens/Setter.hs,3295,1929,148
src/Control/Lens/Traversal.hs,3430,1962,295
src/Control/Exception/Lens.hs,3498,2021,93
src/Language/Haskell/TH/Lens.hs,4566,1729,75
src/Control/Lens/Lens.hs,4183,2683,218
src/Control/Lens/TH.hs,4274,3386,236
src/Control/Lens/Internal.hs,4205,4130,195
src/Control/Lens/Fold.hs,6552,3766,281
src/Control/Lens.hs,5395,5297,195
```

## How to run tests
Expand Down
18 changes: 17 additions & 1 deletion git-freq.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -27,23 +27,39 @@ common dependencies
, optparse-applicative
, process
, text
, parsers
, trifecta

executable git-freq
import: dependencies, default
main-is: Main.hs
hs-source-dirs: src
other-modules:
Git.Freq
Git.NumStat
Types
Paths_git_freq

test-suite spec
import: dependencies, default
type: exitcode-stdio-1.0
main-is: Spec.hs
build-depends: hspec
build-depends:
, directory
, filepath
, hspec
, interpolate
, mockery
, silently
, temporary

build-tool-depends: hspec-discover:hspec-discover -any
hs-source-dirs: src test
other-modules:
Git.Freq
Git.NumStat
Types
Git.FreqSpec
Git.NumStatSpec
Helper
Paths_git_freq
67 changes: 34 additions & 33 deletions src/Git/Freq.hs
Original file line number Diff line number Diff line change
@@ -1,24 +1,23 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE FlexibleContexts #-}

module Git.Freq where

import Control.Arrow ((***))
import Data.ByteString (ByteString)
import Data.List (sortBy)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Text (Text)
import Data.Map.Strict (Map)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as T
import Text.Read (readMaybe)
import qualified Text.Trifecta.Parser as Parser
import qualified Text.Trifecta.Result as Parser

import System.IO.Streams (InputStream)
import qualified System.IO.Streams as Streams

type FileName = Text
type NumStat = (Int, Int)
type Change = (FileName, NumStat)
type Result = Map FileName NumStat
import Types
import Git.NumStat(numstat)

freq :: [FilePath] -> IO ()
freq paths = do
Expand All @@ -29,40 +28,42 @@ getNumStatStream :: [FilePath] -> IO (InputStream ByteString)
getNumStatStream paths = do
let args = ["log"
, "--numstat"
, "--pretty=\"%0\""
, "--pretty="
, "--reverse"
] ++ paths

(_,is,_,_) <- Streams.runInteractiveProcess "git" args Nothing Nothing
return is

freq' :: InputStream ByteString -> IO Result
freq' is = Streams.lines is >>=
Streams.map (parseLine . T.decodeUtf8) >>=
Streams.map parse >>=
Streams.mapMaybe id >>=
Streams.fold incrementChange Map.empty
Streams.fold update Map.empty

parse :: ByteString -> Maybe NumStat
parse bs = case Parser.parseByteString numstat mempty bs of
Parser.Success n -> n
Parser.Failure doc -> error $ show doc

sumChanges :: [Change] -> Result
sumChanges = foldl incrementChange Map.empty
update :: Result -> NumStat -> Result
update result (fileName,delta,mNewFileName) =
let result' = Map.alter (incr Changes { delta = delta, commits = 1 }) fileName result in
case mNewFileName of
Just newFileName -> swap fileName newFileName result'
Nothing -> result'

incrementChange :: Result -> Change -> Result
incrementChange result (fileName,numstat@(a,d)) = Map.alter f fileName result
where
f numstat' = Just $ maybe numstat ((a+) *** (d+)) numstat'
incr :: Changes -> Maybe Changes -> Maybe Changes
incr d = maybe (Just d) (\x -> Just (x <> d))

sortResult :: [Change] -> [Change]
sortResult = let f (_,(xa,xd)) (_,(ya,yd)) = (ya+yd) `compare` (xa+xd) in sortBy f
swap :: Ord k => k -> k -> Map k a -> Map k a
swap old new m = case Map.lookup old m of
Just v -> (Map.insert new v . Map.delete old) m
Nothing -> m

parseLine :: Text -> Maybe Change
parseLine = go . T.splitOn (T.pack "\t")
where go :: [Text] -> Maybe Change
go (_:_:"":_) = Nothing
go (added:deleted:filename:_) =
case (readIntMaybe added, readIntMaybe deleted) of
(Just a, Just d) -> Just (filename, (a, d))
_ -> Nothing
go _ = Nothing
readIntMaybe x = readMaybe (T.unpack x) :: Maybe Int
sortResult :: [(FileName, Changes)] -> [(FileName, Changes)]
sortResult = let f (_,x) (_,y) = x.delta `compare` y.delta in sortBy f

render :: Change -> IO ()
render (fileName,(added,deleted)) =
T.putStrLn . T.pack . mconcat $ [T.unpack fileName, ",", show added, ",", show deleted]
render :: (FileName, Changes) -> IO ()
render (fileName,Changes { delta = delta, commits = commits }) =
T.putStrLn . T.pack . mconcat $ [T.unpack fileName, ",", show delta.added, ",", show delta.deleted, ",", show commits]
43 changes: 43 additions & 0 deletions src/Git/NumStat.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,43 @@
module Git.NumStat (numstat) where

import Control.Applicative
import qualified Data.Text as T
import Text.Trifecta hiding (spaces)
import Text.Parser.LookAhead (LookAheadParsing(lookAhead))

import Types

numstat :: Parser (Maybe NumStat)
numstat = do
hyphen <- lookAhead $ optional (char '-')
case hyphen of
Just _ -> return Nothing
Nothing -> do
added <- read <$> manyTill digit tab
skipMany tab
deleted <- read <$> manyTill digit tab
skipMany tab
fm <- optional (try filemoveWithBrace <|> try filemove)
case fm of
Just (old, current) -> return $ Just (T.pack old, Delta { added = added, deleted = deleted } , Just $ T.pack current)
Nothing -> do
current <- manyTill anyChar eof
return $ Just (T.pack current, Delta { added = added, deleted = deleted }, Nothing)

filemoveWithBrace :: Parser (String, String)
filemoveWithBrace = do
before <- manyTill anyChar (char '{')
from <- manyTill anyChar space
skipSome $ string "=> "
to <- manyTill anyChar (char '}')
after <- manyTill anyChar eof

return (before ++ from ++ after, before ++ to ++ after)

filemove :: Parser (String, String)
filemove = do
from <- manyTill anyChar space
skipSome $ string "=> "
to <- manyTill anyChar eof

return (from, to)
36 changes: 36 additions & 0 deletions src/Types.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,36 @@
{-# LANGUAGE OverloadedRecordDot #-}

module Types where

import Data.Text (Text)
import Data.Map.Strict (Map)

type FileName = Text
data Delta = Delta
{ added::Int
, deleted:: Int
} deriving (Show, Eq)

instance Semigroup Delta where
x <> y = Delta { added = x.added + y.added, deleted = x.deleted + y.deleted }

instance Monoid Delta where
mempty = Delta { added = 0, deleted = 0 }

instance Ord Delta where
x `compare` y = (x.added + x.deleted) `compare` (y.added + y.deleted)

type NumStat = (FileName, Delta, Maybe FileName)

data Changes = Changes
{ delta :: Delta
, commits :: Int
} deriving (Show, Eq)

instance Semigroup Changes where
x <> y = Changes { delta = x.delta <> y.delta, commits = x.commits + y.commits }

instance Monoid Changes where
mempty = Changes { delta = Delta { added = 0, deleted = 0 }, commits = 0 }

type Result = Map FileName Changes
84 changes: 61 additions & 23 deletions test/Git/FreqSpec.hs
Original file line number Diff line number Diff line change
@@ -1,32 +1,70 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
module Git.FreqSpec ( spec ) where

import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as BS
import qualified Data.Map.Strict as Map
import System.IO.Streams (InputStream)
import qualified System.IO.Streams as Streams
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}

module Git.FreqSpec (spec) where

import Control.Exception (catch)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as BS
import qualified Data.Map.Strict as Map
import Data.String.Interpolate (i)
import System.Exit (ExitCode (ExitSuccess))
import System.IO (stdout)
import System.IO.Silently (capture, hSilence)
import System.IO.Streams (InputStream)
import qualified System.IO.Streams as Streams
import System.Process (system)

import Test.Hspec

import Git.Freq
import Git.Freq (freq, freq')
import Types
import Helper (commitFile, inTempRepo)

createMockStream :: [String] -> IO (InputStream ByteString)
createMockStream = Streams.fromByteString . BS.pack . unlines

spec :: Spec
spec = do
describe "freq'" $ do
describe "freq" $ do
around_ (hSilence [stdout] . inTempRepo) $ do

it "should summarize changes" $ do
source <- createMockStream [ "100\t0\tgit-freq.cabal"
, "20\t10\tgit-freq.cabal"
, "0\t120\tgit-freq.cabal"
, "2\t5\tREADME.md"
, "%0"
, "4\t3\t"
, "4\t\t3\tfoo"
, "2\t9\tREADME.md"
]
freq' source `shouldReturn` Map.fromList [ ("git-freq.cabal", (120, 130))
, ("README.md", (4, 14))
]
commitFile "foo.hs" [i|
putStrLn "Foo"
|]

commitFile "foo.hs" [i|
putStrLn "Foo"
putStrLn "Bar"
|]

commitFile "foo.hs" [i|
putStrLn "Bar"
|]

system "git mv foo.hs bar.hs"

Check warning on line 47 in test/Git/FreqSpec.hs

View workflow job for this annotation

GitHub Actions / Run test on GHC latest

A do-notation statement discarded a result of type ‘ExitCode’
system "git commit -a -m 'moved'"

Check warning on line 48 in test/Git/FreqSpec.hs

View workflow job for this annotation

GitHub Actions / Run test on GHC latest

A do-notation statement discarded a result of type ‘ExitCode’
system "git log --numstat"

Check warning on line 49 in test/Git/FreqSpec.hs

View workflow job for this annotation

GitHub Actions / Run test on GHC latest

A do-notation statement discarded a result of type ‘ExitCode’

let run paths = fst <$> capture (freq paths `catch` (\ExitSuccess -> return ()))

Check warning on line 51 in test/Git/FreqSpec.hs

View workflow job for this annotation

GitHub Actions / Run test on GHC latest

Pattern match(es) are non-exhaustive

run ["."] `shouldReturn` unlines ["bar.hs,2,1,4"]

describe "freq'" $ do
it "should summarize changes" $ do
source <-
createMockStream
[ "100\t0\tgit-freq.cabal",
"20\t10\tgit-freq.cabal",
"0\t120\tgit-freq.cabal",
"2\t5\tREADME.md",
--"4\t\t3\tfoo",
"2\t9\tREADME.md"
]
freq' source
`shouldReturn` Map.fromList
[ ("git-freq.cabal", Changes { delta = Delta {added =120, deleted =130}, commits = 3 }),
("README.md", Changes { delta = Delta {added = 4, deleted =14 }, commits = 2 })
]
Loading

0 comments on commit ba197de

Please sign in to comment.