dev: cli: Move Template Haskell to get git hash from Hledger.Cli.Version

to Hledger.Cli.

Since the git hash changes whenever any file in the repository changes,
this means Hledger.Cli.Version needs to be recompiled all the time.
Since it is at the bottom of the module hierarchy, this means that the
whole hledger package needs to be recompiled. We instead move the
TemplateHaskell splice to one of the top modules, so much less needs to
be recompiled.

Note: Ghc seems to be able to get out of most of the recompiling a lot
of the time (due to caching?), but this makes things more reliable.
This commit is contained in:
Stephen Morgan 2021-08-31 00:12:13 +10:00 committed by Simon Michael
parent 1c402edb06
commit 83aa7324eb
6 changed files with 23 additions and 20 deletions

View File

@ -5,6 +5,7 @@
module Hledger.UI.UIOptions
where
import Data.Default
import Data.List (intercalate)
import System.Environment
@ -25,7 +26,7 @@ progname :: String
progname = "hledger-ui"
prognameandversion :: String
prognameandversion = versionStringFor progname
prognameandversion = versionStringForProgname progname
uiflags = [
-- flagNone ["debug-ui"] (setboolopt "rules-file") "run with no terminal output, showing console"

View File

@ -31,7 +31,7 @@ progname :: String
progname = "hledger-web"
prognameandversion :: String
prognameandversion = versionStringFor progname
prognameandversion = versionStringForProgname progname
webflags :: [Flag RawOpts]

View File

@ -1,3 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-|
Hledger.Cli re-exports the options, utilities and commands provided by
@ -14,9 +15,13 @@ module Hledger.Cli (
module Hledger.Cli.Utils,
module Hledger.Cli.Version,
module Hledger,
module System.Console.CmdArgs.Explicit
module System.Console.CmdArgs.Explicit,
prognameandversion,
versionStringForProgname
)
where
import GitHash (tGitInfoCwdTry)
import System.Console.CmdArgs.Explicit hiding (Name) -- don't clash with hledger-ui
import Hledger
@ -26,4 +31,9 @@ import Hledger.Cli.DocFiles
import Hledger.Cli.Utils
import Hledger.Cli.Version
-- | The program name and the best version information we can obtain
-- from git describe or build variables.
prognameandversion = versionStringForProgname progname
versionStringForProgname = versionStringFor $$tGitInfoCwdTry
-- unit tests (tests_Hledger_Cli) are defined in Hledger.Cli.Commands

View File

@ -228,15 +228,15 @@ commandsFromCommandsList s =
[w | c:l <- s, c `elem` [' ','+'], let w:_ = words l]
knownCommands :: [String]
knownCommands = sort . commandsFromCommandsList $ commandsList prognameandversion []
knownCommands = sort . commandsFromCommandsList . drop 1 $ commandsList progname [] -- progname will not be seen
-- | Print the commands list, modifying the template above based on
-- the currently available addons. Missing addons will be removed, and
-- extra addons will be added under Misc.
printCommandsList :: [String] -> IO ()
printCommandsList addonsFound =
printCommandsList :: String -> [String] -> IO ()
printCommandsList progversion addonsFound =
putStr . unlines . concatMap adjustline $
commandsList prognameandversion (map ('+':) unknownCommandsFound)
commandsList progversion (map ('+':) unknownCommandsFound)
where
commandsFound = map (' ':) builtinCommandNames ++ map ('+':) addonsFound
unknownCommandsFound = addonsFound \\ knownCommands

View File

@ -169,7 +169,7 @@ main = do
= putStrLn prognameandversion
-- \| (null externalcmd) && "binary-filename" `inRawOpts` rawopts = putStrLn $ binaryfilename progname
-- \| "--browse-args" `elem` args = System.Console.CmdArgs.Helper.execute "cmdargs-browser" mainmode' args >>= (putStr . show)
| isNullCommand = dbgIO "" "no command, showing commands list" >> printCommandsList addons
| isNullCommand = dbgIO "" "no command, showing commands list" >> printCommandsList prognameandversion addons
| isBadCommand = badCommandError
-- builtin commands
@ -265,4 +265,3 @@ flagstomove = inputflags ++ reportflags ++ helpflags
noargflagstomove = concatMap flagNames $ filter ((==FlagNone).flagInfo) flagstomove
reqargflagstomove = -- filter (/= "debug") $
concatMap flagNames $ filter ((==FlagReq ).flagInfo) flagstomove

View File

@ -1,5 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
{-
Version number-related utilities. See also the Makefile.
-}
@ -7,12 +6,11 @@ Version number-related utilities. See also the Makefile.
module Hledger.Cli.Version (
packageversion,
progname,
prognameandversion,
versionStringFor,
)
where
import GitHash (giDescribe, tGitInfoCwdTry)
import GitHash (GitInfo, giDescribe)
import System.Info (os, arch)
import Hledger.Utils
@ -56,11 +54,6 @@ buildversion = prettify . splitAtElement '.' $ packageversion ++ patchlevel
progname :: String
progname = "hledger"
-- | The program name and the best version information we can obtain
-- from git describe or build variables.
prognameandversion :: String
prognameandversion = versionStringFor progname
-- | Given a program name, make a version string consisting of:
--
-- * the program name
@ -70,11 +63,11 @@ prognameandversion = versionStringFor progname
-- * the platform (OS) name
-- * the processor architecture name.
--
versionStringFor :: String -> String
versionStringFor progname = concat [
versionStringFor :: Either String GitInfo -> String -> String
versionStringFor gitinfo progname = concat [
progname
, " "
, either (const buildversion) giDescribe $$tGitInfoCwdTry
, either (const buildversion) giDescribe gitinfo
, ", "
, os'
, "-"