{-# LANGUAGE TemplateHaskell #-}
module Hydra.Version where
import Hydra.Prelude
import Development.GitRev qualified as GitRev
import Foreign.C (CString)
import GHC.Foreign (peekCStringLen)
import GHC.IO (unsafeDupablePerformIO)
import GHC.IO.Encoding (utf8)
unknownVersion :: String
unknownVersion :: String
unknownVersion = String
"UNKNOWN"
gitDescribe :: Maybe String
gitDescribe :: Maybe String
gitDescribe
| String
fromGit String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
unknownVersion = Maybe String
forall a. Maybe a
Nothing
| Bool
otherwise = String -> Maybe String
forall a. a -> Maybe a
Just String
fromGit
where
fromGit :: String
fromGit = $(GitRev.gitDescribe)
gitRevision :: Maybe String
gitRevision :: Maybe String
gitRevision
| String
fromGit String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
unknownVersion = Maybe String
forall a. Maybe a
Nothing
| Bool
otherwise = String -> Maybe String
forall a. a -> Maybe a
Just String
fromGit
where
fromGit :: String
fromGit = $(GitRev.gitHash)
foreign import ccall "&_hydra_gitrev" c_gitrev :: CString
embeddedRevision :: Maybe String
embeddedRevision :: Maybe String
embeddedRevision
| String
embedded String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
placeholder = Maybe String
forall a. Maybe a
Nothing
| Bool
otherwise = String -> Maybe String
forall a. a -> Maybe a
Just String
embedded
where
embedded :: String
embedded = IO String -> String
forall a. IO a -> a
unsafeDupablePerformIO (TextEncoding -> CStringLen -> IO String
peekCStringLen TextEncoding
utf8 (CString
c_gitrev, Int
40))
placeholder :: String
placeholder = Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
40 Char
'0'