Skip to content

Commit

Permalink
feat: Remove commit hash from version number
Browse files Browse the repository at this point in the history
This reduces our Template Haskell dependencies.

The commit hash never made it into the nix-based static executable
anyway. Since we'd like to move to produce more executables via nix in
the future, it will be hard to maintain the commit hash.
  • Loading branch information
wolfgangwalther committed Jun 18, 2024
1 parent c045b26 commit 0166d3c
Showing 1 changed file with 3 additions and 13 deletions.
16 changes: 3 additions & 13 deletions src/PostgREST/Version.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,10 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE CPP #-}
module PostgREST.Version
( docsVersion
, prettyVersion
) where

import qualified Data.ByteString as BS
import qualified Data.Text as T

import Development.GitRev (gitHash)
import qualified Data.Text as T

import Protolude

Expand All @@ -17,16 +13,10 @@ version = T.splitOn "." VERSION_postgrest

-- | User friendly version number such as '1.1.1'.
-- Pre-release versions are tagged as such, e.g., '1.1 (pre-release)'.
-- If a git hash is available, it's added to the version, e.g., '1.1.1 (abcdef0)'.
prettyVersion :: ByteString
prettyVersion =
VERSION_postgrest <> preRelease <> gitRev
VERSION_postgrest <> preRelease
where
gitRev =
if $(gitHash) == ("UNKNOWN" :: Text) then
mempty
else
" (" <> BS.take 7 $(gitHash) <> ")"
preRelease = if isPreRelease then " (pre-release)" else mempty


Expand Down

0 comments on commit 0166d3c

Please sign in to comment.