forked from PostgREST/postgrest
-
Notifications
You must be signed in to change notification settings - Fork 0
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
ci: Fix triggering events and release actions
* Run CI only on pull requests, push to main and push to tags matching v*. This avoids running the CI more than once for a single user action * Change pre-releases, which are now identified by a version number with 4 components (e.g., 1.1.1.1) * Change how release artifacts are packaged, ensuring they are executable and compressed with xz
- Loading branch information
1 parent
243e4f0
commit 0e0e18d
Showing
3 changed files
with
52 additions
and
25 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -1,29 +1,41 @@ | ||
{-# LANGUAGE TemplateHaskell #-} | ||
{-# OPTIONS_GHC -fno-warn-type-defaults #-} | ||
module PostgREST.Version | ||
( docsVersion | ||
, prettyVersion | ||
) where | ||
|
||
import qualified Data.Text as T | ||
|
||
import Data.Version (versionBranch) | ||
import Data.Version (showVersion, versionBranch) | ||
import Development.GitRev (gitHash) | ||
import Paths_postgrest (version) | ||
|
||
import Protolude | ||
|
||
|
||
-- | User friendly version number | ||
-- | User friendly version number such as '1.1.1'. | ||
-- Pre-release versions are tagged as such, e.g., '1.1.1.1 (pre-release)'. | ||
-- If a git hash is available, it's added to the version, e.g., '1.1.1 (abcdef0)'. | ||
prettyVersion :: Text | ||
prettyVersion = | ||
T.intercalate "." (map show $ versionBranch version) <> gitRev | ||
T.pack (showVersion version) <> preRelease <> gitRev | ||
where | ||
gitRev = | ||
if $(gitHash) == "UNKNOWN" | ||
then mempty | ||
else " (" <> T.take 7 $(gitHash) <> ")" | ||
if $(gitHash) == ("UNKNOWN" :: Text) then | ||
mempty | ||
else | ||
" (" <> T.take 7 $(gitHash) <> ")" | ||
preRelease = if isPreRelease then " (pre-release)" else mempty | ||
|
||
-- | Version number used in docs | ||
|
||
-- | Version number used in docs. | ||
-- Uses only the two first components of the version. Example: 'v1.1' | ||
docsVersion :: Text | ||
docsVersion = "v" <> T.dropEnd 1 (T.dropWhileEnd (/= '.') prettyVersion) | ||
docsVersion = | ||
"v" <> (T.intercalate "." . map show . take 2 $ versionBranch version) | ||
|
||
|
||
-- | Versions with four components (e.g., '1.1.1.1') are treated as pre-releases. | ||
isPreRelease :: Bool | ||
isPreRelease = | ||
length (versionBranch version) == 4 |