aboutsummaryrefslogtreecommitdiffstats
path: root/app/History.hs
blob: fc3b1568676afcf19b87bba8eb4166d3bb8ca7ad (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
{-# LANGUAGE OverloadedRecordDot #-}

module History (getIssues, InvalidTreeGrepperResult (..), UnknownFileExtension (..)) where

import Control.Exception (Exception, throw)
import Data.Aeson (eitherDecode)
import Data.Maybe (catMaybes)
import Data.String (fromString)
import Issue (Issue (..), fromMatch)
import Process (quote, sh)
import System.FilePath (takeExtension)
import Text.Printf (printf)
import TreeGrepper.Match qualified as G
import TreeGrepper.Result qualified as G

data UnknownFileExtension = UnknownFileExtension
  { extension :: String
  }
  deriving (Show)

instance Exception UnknownFileExtension

data InvalidTreeGrepperResult = InvalidTreeGrepperResult
  { error :: String
  }
  deriving (Show)

instance Exception InvalidTreeGrepperResult

getIssues :: FilePath -> IO [Issue]
getIssues filename = do
  let extension = takeExtension filename
      treeGrepperLanguage =
        -- TODO Add support for all tree-grepper supported files
        --
        -- tree-grepper supported files can be listed through `tree-grepper
        -- --languages`.
        case extension of
          ".elm" -> "elm"
          ".hs" -> "haskell"
          ".nix" -> "nix"
          ".sh" -> "sh"
          _ -> throw (UnknownFileExtension extension)
      treeGrepperQuery =
        case extension of
          ".elm" -> "([(line_comment) (block_comment)])"
          ".hs" -> "(comment)"
          ".nix" -> "(comment)"
          ".sh" -> "(comment)"
          _ -> throw (UnknownFileExtension extension)
      decode raw =
        case eitherDecode raw of
          Left e -> throw (InvalidTreeGrepperResult e)
          Right treeGrepperResult -> treeGrepperResult

  matches <-
    concatMap (\result -> map ((,) result) result.matches)
      . map fixTreeGrepper
      . decode
      <$> sh
        ( fromString
            ( printf
                "tree-grepper --query %s %s --format json %s"
                (quote treeGrepperLanguage)
                (quote treeGrepperQuery)
                (quote filename)
            )
        )

  catMaybes <$> mapM (uncurry fromMatch) matches

fixTreeGrepper :: G.Result -> G.Result
fixTreeGrepper treeGrepperResult =
  treeGrepperResult {G.matches = G.merge treeGrepperResult.matches}