[Haskell-cafe] Embedding version info in executables

Alexander V Vershilov alexander.vershilov at gmail.com
Fri Jul 11 09:46:36 UTC 2014


It's possible to use a SimpelUserHook setup type, and then in Setup.hs
add preBuild hook that will generate a file in ./dist/autobuild/, then you
can import this file in Main.hs and use this information.

I have used such Setup.hs (have not reviewed it for years), I think it may
be improved.


```
import Distribution.Simple
import Distribution.Simple.Setup
import Data.Time.LocalTime
import Distribution.PackageDescription (emptyHookedBuildInfo)
import System.Directory (createDirectoryIfMissing, doesDirectoryExist)
import System.Process (readProcess)

main = defaultMainWithHooks (simpleUserHooks{ preBuild=addGitVersion })

addGitVersion _ buildFlags = do
  let Flag dir = buildDistPref buildFlags
      buildFilePath = dir ++ "/build/autogen"
  putStrLn $ "Generating " ++ buildFilePath ++ "..."
  createDirectoryIfMissing True buildFilePath

  exists <- doesDirectoryExist "git"
  desc  <- if exists
               then readProcess "git" ["describe", "--all", "--long",
"--dirty=-modified"] ""
               else return "detached version"
  now  <- return . show =<< getZonedTime

  writeFile (buildFilePath ++ "/Build_hvmm.hs") $ unlines
    [ "module Build_hvmm where "
    , "gitDescribe::String"
    , "gitDescribe = " ++ show desc
    , "buildTime:: String"
    , "buildTime = " ++ show now
    ]
  return emptyHookedBuildInfo
```


On 11 July 2014 13:26, Roman Cheplyaka <roma at ro-che.info> wrote:
> What are existing solutions for embedding version info (git revision, build
> date/time, versions of dependencies) in Haskell programs?
>
> Roman
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Alexander


More information about the Haskell-Cafe mailing list