Parse results into matches

This commit is contained in:
Joshua Clayton 2016-04-28 22:21:18 -04:00
parent 1249a0e823
commit a5230f163e
5 changed files with 74 additions and 4 deletions

View File

@ -1,9 +1,12 @@
module Main where
import Unused.TermSearch (search)
import Unused.Parser (parseLines)
main :: IO ()
main = do
tokens <- pure . lines =<< getContents
results <- pure . concat =<< mapM search tokens
putStrLn $ unlines results
terms <- pure . lines =<< getContents
results <- pure . concat =<< mapM search terms
let matches = parseLines $ unlines results
print matches

56
src/Unused/Parser.hs Normal file
View File

@ -0,0 +1,56 @@
module Unused.Parser
( parseLines
) where
import Control.Monad (void)
import Text.Parsec.String (Parser)
import Text.Parsec
import Unused.Types
parseLines :: String -> [TermMatch]
parseLines s =
either (const []) id $ parse parseTermMatches "matches" s
parseTermMatches :: Parser [TermMatch]
parseTermMatches = do
tm <- many1 $ do
m <- parseTermMatch
void eol
return m
eof
return tm
parseTermMatch :: Parser TermMatch
parseTermMatch = do
term' <- termParser
colonSep
path' <- pathParser
colonSep
occurrences' <- occurrenceParser
return $ TermMatch term' path' $ toInt occurrences'
where
toInt i = read i :: Int
colonSep = do { void $ try $ char ':' }
termChars :: Parser Char
termChars = alphaNum <|> char '_' <|> char '!' <|> char '?' <|> char '='
termParser :: Parser String
termParser = many1 termChars
pathParser :: Parser String
pathParser = many1 $ alphaNum <|> char '.' <|> char '/' <|> char '_' <|> char '-'
occurrenceParser :: Parser String
occurrenceParser = many1 digit
eol :: Parser String
eol = try (string "\n\r")
<|> try (string "\r\n")
<|> string "\n"
<|> string "\r"
<?> "end of line"

View File

@ -2,7 +2,6 @@ module Unused.TermSearch
( search
) where
import System.IO
import System.Process
search :: String -> IO [String]

9
src/Unused/Types.hs Normal file
View File

@ -0,0 +1,9 @@
module Unused.Types
( TermMatch(..)
) where
data TermMatch = TermMatch
{ term :: String
, path :: String
, occurrences :: Int
} deriving Show

View File

@ -16,8 +16,11 @@ cabal-version: >=1.10
library
hs-source-dirs: src
exposed-modules: Unused.TermSearch
, Unused.Parser
, Unused.Types
build-depends: base >= 4.7 && < 5
, process
, parsec
default-language: Haskell2010
executable unused