Skip to content

Commit

Permalink
Add build information
Browse files Browse the repository at this point in the history
  • Loading branch information
TravisCardwell committed Apr 23, 2024
1 parent e1be523 commit ba8b244
Show file tree
Hide file tree
Showing 3 changed files with 73 additions and 2 deletions.
61 changes: 61 additions & 0 deletions app/Build.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,61 @@
------------------------------------------------------------------------------
-- |
-- Module : Build
-- Description : build information
-- Copyright : Copyright (c) 2021-2024 Travis Cardwell
-- License : MIT
------------------------------------------------------------------------------

{-# LANGUAGE CPP #-}

module Build
( version
) where

-- https://hackage.haskell.org/package/base
import Control.Monad ((<=<))
import qualified Data.Char as Char
import qualified Data.List as List
import qualified Data.Version
import System.IO.Error (tryIOError)
import qualified System.Info

-- http://hackage.haskell.org/package/template-haskell
import Language.Haskell.TH (ExpQ, runIO, stringE)

-- (lsupg)
import qualified LsUpg

------------------------------------------------------------------------------

-- | Compiler version string (internal)
--
-- The full compiler version is used when it is available.
compilerVersion :: String
compilerVersion = Data.Version.showVersion
#if MIN_VERSION_base (4,15,0)
System.Info.fullCompilerVersion
#else
System.Info.compilerVersion
#endif

------------------------------------------------------------------------------

-- | Version string with build information when built on Alpine
--
-- @since 0.4.0.0
version :: ExpQ
version = stringE <=< runIO $ do
mAlpineVersion <-
either (const Nothing) (Just . List.dropWhileEnd Char.isSpace) <$>
tryIOError (readFile "/etc/alpine-release")
pure $ case mAlpineVersion of
Just alpineVersion -> unwords
[ LsUpg.version
, "built on Alpine"
, alpineVersion
, "using"
, System.Info.compilerName
, compilerVersion
]
Nothing -> LsUpg.version
10 changes: 9 additions & 1 deletion app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@
------------------------------------------------------------------------------

{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}

module Main (main) where
Expand Down Expand Up @@ -39,6 +40,7 @@ import qualified LsUpg.Component as Component
import LsUpg.Component.Nix (defaultNixPath)

-- (lsupg:executable)
import qualified Build
import qualified LibOA

------------------------------------------------------------------------------
Expand Down Expand Up @@ -150,6 +152,12 @@ runSpecified Options{..} =
intercalate ", " (map TTC.render names)
exitWith $ ExitFailure 2

------------------------------------------------------------------------------
-- $Version

version :: String
version = $(Build.version)

------------------------------------------------------------------------------
-- $Main

Expand All @@ -163,7 +171,7 @@ main = do
where
pinfo :: OA.ParserInfo Options
pinfo
= OA.info (LibOA.helper <*> LibOA.versioner LsUpg.version <*> options)
= OA.info (LibOA.helper <*> LibOA.versioner version <*> options)
$ mconcat
[ OA.fullDesc
, OA.progDesc "list items that can be upgraded"
Expand Down
4 changes: 3 additions & 1 deletion lsupg.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -81,10 +81,12 @@ executable lsupg
hs-source-dirs: app
main-is: Main.hs
other-modules:
LibOA
Build
, LibOA
build-depends:
base
, lsupg
, template-haskell
, ttc
, typed-process
if flag(optparse-applicative_ge_0_18)
Expand Down

0 comments on commit ba8b244

Please sign in to comment.