Files
flipper/scripts/bump.hs
Pascal Hartig 64d3f34fe5 Improve version bumping logic
Summary:
Currently, when bumping the version, the script will override "-SNAPSHOT" mentions in both the docs and the properties. This requires some manual fixup after every release. With this change, you can pass "-s" or "--snapshot" to change the version number to a snapshot release and it will only affect the places where that change is necessary.

Did some overall cleanup, too, like getting rid of the macro magic to determine the current location which messes with tooling.

This does *not* include the updated binaries yet. I'll put them up as a separate diff.

Reviewed By: priteshrnandgaonkar

Differential Revision: D13782177

fbshipit-source-id: 87ad0ab20a5f544ddb6aa3e2d30949bbabbabfc4
2019-01-23 08:03:32 -08:00

122 lines
4.0 KiB
Haskell
Executable File

#!/usr/bin/env stack
-- stack --resolver lts-13.4 --install-ghc runghc --package turtle --package system-filepath --package pseudomacros --package foldl
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
import Prelude hiding (FilePath)
import Turtle
import Data.Maybe (catMaybes)
import Control.Monad (forM_)
import qualified Filesystem.Path.CurrentOS as Path
import qualified Data.Text as T
import qualified Control.Foldl as F
-- * Global settings
releaseReplacements :: [(FilePath, Pattern Version)]
releaseReplacements =
[("gradle.properties", "VERSION_NAME=" *> anyVersion)
,("docs/getting-started.md", spaces >> "debugImplementation 'com.facebook.flipper:flipper:" *> releaseVersion <* "'")
]
snapshotReplacements :: [(FilePath, Pattern Version)]
snapshotReplacements =
[("gradle.properties", "VERSION_NAME=" *> anyVersion)
,("docs/getting-started.md", spaces >> "debugImplementation 'com.facebook.flipper:flipper:" *> snapshotVersion <* "'")
]
flipperPath :: FilePath -> FilePath
flipperPath basePath =
basePath </> "xplat" </> "sonar"
-- * Patterns
releaseVersion :: Pattern Version
releaseVersion =
Version <$> plus digit <> "." <> plus digit <> "." <> plus digit
snapshotVersion :: Pattern Version
snapshotVersion =
Version <$> plus digit <> "." <> plus digit <> "." <> plus digit <> "-SNAPSHOT"
anyVersion :: Pattern Version
anyVersion =
Version <$> plus digit <> "." <> plus digit <> "." <> plus (char '-' <|> alphaNum)
-- * Application logic
newtype Version = Version Text
deriving (Show, Eq)
unversion (Version v) = v
data BumpMode = ModeRelease | ModeSnapshot
deriving (Show, Eq)
data BumpArguments = BumpArguments
{ argVersion :: Version
, argMode :: BumpMode
} deriving (Show, Eq)
parser :: Turtle.Parser BumpArguments
parser = BumpArguments
<$> (Version <$> argText "version" "Version to bump to, e.g. 1.0.2")
<*> ((\b -> if b then ModeSnapshot else ModeRelease) <$> switch "snapshot" 's' "Change SNAPSHOT references instead of release ones")
-- | Find the root of the project, indicated by the presence of a ".hg" folder.
findProjectRoot :: FilePath -> IO (Maybe FilePath)
findProjectRoot dir = go $ Path.splitDirectories dir
where
go :: forall (m :: * -> *).
MonadIO m =>
[FilePath] -> m (Maybe FilePath)
go [] = return Nothing
go ds = do
let ds' = init ds
dir' = Path.concat ds'
hg = dir' </> ".hg"
hgExists <- testdir hg
if hgExists then
return $ Just dir'
else
go ds'
replaceLine :: Version -> Pattern Version -> Pattern Version -> Line -> Shell Line
replaceLine newVersion matcher pttrn l =
if match pttrn (lineToText l) == empty then pure l
else sed (unversion newVersion <$ anyVersion) $ pure l
main :: IO ()
main = do
args <- options "Flipper Version Bumper" parser
let newVersion = argVersion args
let (versionMatcher, replacements) = case argMode args of
ModeRelease -> (releaseVersion, releaseReplacements)
ModeSnapshot -> (snapshotVersion, snapshotReplacements)
let isVersionValid = match versionMatcher (unversion newVersion)
when (null isVersionValid) $ do
printf ("Invalid version specified: "%w%".\n") newVersion
exit $ ExitFailure 2
projectRoot <- findProjectRoot =<< pwd
let flipperDir = flipperPath <$> projectRoot
flipperDir_ <- case flipperDir of
Just f -> pure f
Nothing -> die "Couldn't determine flipper location."
printf ("Starting bump to "%w%".\n") newVersion
forM_ replacements $ \(path, pttrn) -> do
let absPath = flipperDir_ </> path
printf ("Updating version in "%w%"\n") absPath
lines <- T.lines <$> readTextFile absPath
newLines :: [Line] <- flip fold F.mconcat . sequence $ replaceLine newVersion versionMatcher pttrn <$> catMaybes (textToLine <$> lines)
writeTextFile absPath . T.unlines $ lineToText <$> newLines
echo "Done!"