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
This commit is contained in:
Pascal Hartig
2019-01-23 08:00:35 -08:00
committed by Facebook Github Bot
parent e36b5d1ceb
commit 64d3f34fe5
2 changed files with 49 additions and 29 deletions

View File

@@ -1,11 +1,10 @@
#!/usr/bin/env stack #!/usr/bin/env stack
-- stack --resolver lts-12.7 --install-ghc runghc --package turtle --package system-filepath --package pseudomacros --package foldl -- stack --resolver lts-13.4 --install-ghc runghc --package turtle --package system-filepath --package pseudomacros --package foldl
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE KindSignatures #-} {-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
import Prelude hiding (FilePath) import Prelude hiding (FilePath)
@@ -13,7 +12,6 @@ import Turtle
import Data.Maybe (catMaybes) import Data.Maybe (catMaybes)
import Control.Monad (forM_) import Control.Monad (forM_)
import PseudoMacros (__FILE__)
import qualified Filesystem.Path.CurrentOS as Path import qualified Filesystem.Path.CurrentOS as Path
import qualified Data.Text as T import qualified Data.Text as T
@@ -21,10 +19,16 @@ import qualified Control.Foldl as F
-- * Global settings -- * Global settings
replacements :: [(FilePath, Pattern Version)] releaseReplacements :: [(FilePath, Pattern Version)]
replacements = releaseReplacements =
[("gradle.properties", "VERSION_NAME=" *> version) [("gradle.properties", "VERSION_NAME=" *> anyVersion)
,("docs/getting-started.md", spaces >> "debugImplementation 'com.facebook.flipper:flipper:" *> version <* "'") ,("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 :: FilePath -> FilePath
@@ -33,8 +37,16 @@ flipperPath basePath =
-- * Patterns -- * Patterns
version :: Pattern Version releaseVersion :: Pattern Version
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) Version <$> plus digit <> "." <> plus digit <> "." <> plus (char '-' <|> alphaNum)
-- * Application logic -- * Application logic
@@ -44,16 +56,18 @@ newtype Version = Version Text
unversion (Version v) = v unversion (Version v) = v
parser :: Turtle.Parser Version data BumpMode = ModeRelease | ModeSnapshot
parser = Version <$> argText "version" "Version to bump to, e.g. 1.0.2" deriving (Show, Eq)
-- | Provide a path to the directory this very file resides in through some data BumpArguments = BumpArguments
-- arcane magic. { argVersion :: Version
thisDirectory :: IO FilePath , argMode :: BumpMode
thisDirectory = do } deriving (Show, Eq)
let filePath :: FilePath = $__FILE__
currentDir <- pwd parser :: Turtle.Parser BumpArguments
return . Path.parent $ currentDir </> filePath 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. -- | Find the root of the project, indicated by the presence of a ".hg" folder.
findProjectRoot :: FilePath -> IO (Maybe FilePath) findProjectRoot :: FilePath -> IO (Maybe FilePath)
@@ -73,21 +87,25 @@ findProjectRoot dir = go $ Path.splitDirectories dir
else else
go ds' go ds'
replaceLine :: Version -> Pattern Version -> Line -> Shell Line replaceLine :: Version -> Pattern Version -> Pattern Version -> Line -> Shell Line
replaceLine newVersion pttrn l = replaceLine newVersion matcher pttrn l =
if match pttrn (lineToText l) == empty then pure l if match pttrn (lineToText l) == empty then pure l
else sed (const (unversion newVersion) <$> version) $ pure l else sed (unversion newVersion <$ anyVersion) $ pure l
main :: IO () main :: IO ()
main = do main = do
newVersion <- options "Flipper Version Bumper" parser args <- options "Flipper Version Bumper" parser
let isVersionValid = match version (unversion newVersion) 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 when (null isVersionValid) $ do
printf ("Invalid version specified: "%w%".\n") newVersion printf ("Invalid version specified: "%w%".\n") newVersion
exit $ ExitFailure 2 exit $ ExitFailure 2
directory <- thisDirectory projectRoot <- findProjectRoot =<< pwd
projectRoot <- findProjectRoot directory
let flipperDir = flipperPath <$> projectRoot let flipperDir = flipperPath <$> projectRoot
flipperDir_ <- case flipperDir of flipperDir_ <- case flipperDir of
Just f -> pure f Just f -> pure f
@@ -98,6 +116,6 @@ main = do
let absPath = flipperDir_ </> path let absPath = flipperDir_ </> path
printf ("Updating version in "%w%"\n") absPath printf ("Updating version in "%w%"\n") absPath
lines <- T.lines <$> readTextFile absPath lines <- T.lines <$> readTextFile absPath
newLines :: [Line] <- flip fold F.mconcat . sequence $ replaceLine newVersion pttrn <$> catMaybes (textToLine <$> lines) newLines :: [Line] <- flip fold F.mconcat . sequence $ replaceLine newVersion versionMatcher pttrn <$> catMaybes (textToLine <$> lines)
writeTextFile absPath . T.unlines $ lineToText <$> newLines writeTextFile absPath . T.unlines $ lineToText <$> newLines
echo "Done!" echo "Done!"

View File

@@ -1,9 +1,11 @@
#!/bin/bash #!/bin/bash
BASEDIR="$( cd "$( dirname "${BASH_SOURCE[0]}" )" && pwd )" BASEDIR="$( cd "$( dirname "${BASH_SOURCE[0]}" )" && pwd )"
# Run from here so we know we're having fbsource in our $PWD.
cd "$BASEDIR" || exit
case $OSTYPE in case $OSTYPE in
darwin*) "$BASEDIR"/bump.mac "$@" ;; darwin*) ./bump.mac "$@" ;;
linux-gnu) "$BASEDIR"/bump.lnx64 "$@" ;; linux-gnu) ./bump.lnx64 "$@" ;;
*) echo "Unknown OS. Using source version using https://haskellstack.org/" && "$BASEDIR"/bump.hs "$@" ;; *) echo "Unknown OS. Using source version via https://haskellstack.org/" && ./bump.hs "$@" ;;
esac esac