Move bump to project folder
Summary: Makes building a bit easier and I can have my own README in there. Reviewed By: jknoxville Differential Revision: D13784725 fbshipit-source-id: b694c1ce812d4e383ad44faeacd8e0094a96b432
This commit is contained in:
committed by
Facebook Github Bot
parent
a70f47cb0e
commit
7e911ed5e8
3
scripts/bump/.gitignore
vendored
Normal file
3
scripts/bump/.gitignore
vendored
Normal file
@@ -0,0 +1,3 @@
|
||||
.stack-work
|
||||
Setup.hs
|
||||
*.cabal
|
||||
43
scripts/bump/README.md
Normal file
43
scripts/bump/README.md
Normal file
@@ -0,0 +1,43 @@
|
||||
# bump
|
||||
|
||||
A small script for changing version numbers automatically.
|
||||
|
||||
## Usage
|
||||
|
||||
Requires [stack](http://haskellstack.org/) to be installed.
|
||||
|
||||
```
|
||||
./bump.hs --help
|
||||
```
|
||||
|
||||
Alternatively, use the pre-checked-in binaries from the superfolder
|
||||
through `bump.sh`.
|
||||
|
||||
To bump a release version, just pass the new version number.
|
||||
|
||||
```
|
||||
bump 1.2.3
|
||||
```
|
||||
|
||||
To bump to a snapshot release, run with `--snapshot`:
|
||||
|
||||
```
|
||||
bump --snapshot 1.2.4-SNAPSHOT
|
||||
```
|
||||
|
||||
## Building
|
||||
|
||||
To build the native binaries, run
|
||||
|
||||
```
|
||||
stack build
|
||||
```
|
||||
|
||||
The binary is then placed in `.stack-work/install/x86_64-osx/**/bin/bump`.
|
||||
|
||||
To cross-compile for Linux (required for internal CI), run
|
||||
|
||||
```
|
||||
stack docker pull
|
||||
stack build --docker
|
||||
```
|
||||
121
scripts/bump/bump.hs
Executable file
121
scripts/bump/bump.hs
Executable file
@@ -0,0 +1,121 @@
|
||||
#!/usr/bin/env stack
|
||||
-- stack --resolver lts-13.4 --install-ghc runghc --package turtle --package system-filepath --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!"
|
||||
14
scripts/bump/package.yaml
Normal file
14
scripts/bump/package.yaml
Normal file
@@ -0,0 +1,14 @@
|
||||
name: bump
|
||||
version: 0.1.0.0
|
||||
|
||||
dependencies:
|
||||
- base >= 4.7 && < 5
|
||||
- turtle
|
||||
- system-filepath
|
||||
- foldl
|
||||
- text
|
||||
|
||||
executables:
|
||||
bump:
|
||||
source-dirs: .
|
||||
main: bump.hs
|
||||
3
scripts/bump/stack.yaml
Normal file
3
scripts/bump/stack.yaml
Normal file
@@ -0,0 +1,3 @@
|
||||
packages:
|
||||
- .
|
||||
resolver: lts-13.4
|
||||
Reference in New Issue
Block a user