|
{-# LANGUAGE OverloadedStrings,ScopedTypeVariables #-} |
|
import System.Environment (getArgs, getProgName) |
|
import Data.List (intercalate) |
|
import Text.Parsec.Error (ParseError) |
|
import Text.ParserCombinators.Parsec (Parser) |
|
import Text.Parsec.Prim (runParser) |
|
import Text.Parsec.Char (digit, char) |
|
import Text.Parsec.Combinator (many1, sepBy) |
|
|
|
|
|
main :: IO () |
|
main = do |
|
vsnPos <- readVSNPos |
|
interact $ parseAndIncrementVSN vsnPos |
|
|
|
|
|
-- Get the position of the version item they want |
|
readVSNPos :: IO Int |
|
readVSNPos = do |
|
cmd <- getProgName |
|
args <- getArgs |
|
|
|
return $ case args of |
|
["major"] -> 1 |
|
["minor"] -> 2 |
|
["patch"] -> 3 |
|
[] -> 3 |
|
_ -> error $ usage cmd |
|
|
|
|
|
-- The usage line when someone doesn't know what they're doing |
|
usage :: String -> String |
|
usage cmd = "Invalid usage: " ++ cmd ++ " (major|minor|patch)" |
|
|
|
|
|
-- Our main interact callback; This is where the magic happens |
|
parseAndIncrementVSN :: Int -> String -> String |
|
parseAndIncrementVSN vsnPos vsnStr = |
|
-- either raise an error or the string |
|
either (error . show) id vsn |
|
where |
|
vsn :: Either ParseError String |
|
vsn = (joinVSN . incrVSN vsnPos) `fmap` parseVersion vsnStr |
|
|
|
|
|
-- Convert the version string into a list of integers |
|
parseVersion :: String -> Either ParseError [Int] |
|
parseVersion vsn = runParser dottedVsn () "" vsn |
|
where |
|
dottedVsn :: Parser [Int] |
|
dottedVsn = vsnInt `sepBy` (char '.') |
|
|
|
vsnInt :: Parser Int |
|
vsnInt = read `fmap` many1 digit |
|
|
|
|
|
-- Convert a list of integers into a dotted version string |
|
joinVSN :: [Int] -> String |
|
joinVSN = intercalate "." . map show |
|
|
|
|
|
-- Increment the version item at the pos given |
|
-- I found the do notation easier to read than |
|
-- a list comprehension. |
|
incrVSN :: Int -> [Int] -> [Int] |
|
incrVSN pos bits = do |
|
(i,x) <- zip [1..upper] (bits ++ repeat 0) |
|
|
|
return $ if i == pos then |
|
x + 1 |
|
else |
|
x |
|
where |
|
-- this is O(n) but versions lists are usually small |
|
-- O(n) shouldn't hurt us. |
|
upper = max pos $ length bits |