imp: config file: also try home and XDG config dirs

This commit is contained in:
Simon Michael 2024-06-24 20:14:07 +01:00
parent d76677c6ad
commit f89e62cb6f
2 changed files with 34 additions and 17 deletions

View File

@ -1,5 +1,7 @@
# hledger.conf - extra options(/arguments) to be added to hledger commands. # hledger.conf - extra options(/arguments) to be added to hledger commands.
# This takes effect if found in the current directory when you run hledger. # hledger looks for this in the current directory (./hledger.conf)
# or in your home directory with a dotted name ($HOME/.hledger.conf)
# or in your XDG config directory for hledger ($HOME/.config/hledger/hledger.conf).
# 1. This first, unnamed section is typically used for general options. # 1. This first, unnamed section is typically used for general options.
# These affect all commands, or when not supported will be ignored. # These affect all commands, or when not supported will be ignored.

View File

@ -4,6 +4,7 @@ Read extra CLI arguments from a hledger config file.
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE TupleSections #-}
module Hledger.Cli.Conf ( module Hledger.Cli.Conf (
getConf getConf
@ -11,23 +12,23 @@ module Hledger.Cli.Conf (
) )
where where
import Control.Exception (IOException, catch, tryJust) import Control.Monad (void)
import Control.Monad (guard, void)
import Control.Monad.Identity (Identity) import Control.Monad.Identity (Identity)
import Data.Functor ((<&>))
import qualified Data.Map as M import qualified Data.Map as M
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as T (pack) import qualified Data.Text as T (pack)
import System.IO.Error (isDoesNotExistError) import System.Directory (getHomeDirectory, getXdgDirectory, XdgDirectory (XdgConfig), doesFileExist)
import Text.Megaparsec -- hiding (parse) import System.FilePath ((</>))
import Text.Megaparsec
import Text.Megaparsec.Char import Text.Megaparsec.Char
import Hledger (error', strip, words') import Hledger (error', strip, words')
import Hledger.Read.Common import Hledger.Read.Common
import Hledger.Utils.Parse import Hledger.Utils.Parse
import Hledger.Utils.Debug
localConfPath = "hledger.conf"
-- | A hledger config file. -- | A hledger config file.
data Conf = Conf { data Conf = Conf {
confFile :: FilePath confFile :: FilePath
@ -67,16 +68,24 @@ confLookup cmd Conf{confSections} =
M.lookup cmd $ M.lookup cmd $
M.fromList [(csName,csArgs) | ConfSection{csName,csArgs} <- confSections] M.fromList [(csName,csArgs) | ConfSection{csName,csArgs} <- confSections]
-- | Try to read a hledger config file. -- | Try to read a hledger config file from several places.
-- If none is found, this returns a null Conf. -- If no config file is found, this returns a null Conf.
-- Any other IO error will cause an exit. -- Any other IO or parse failure will raise an error.
getConf :: IO Conf getConf :: IO Conf
getConf = (do getConf = do
let f = localConfPath homedir <- getHomeDirectory
es <- tryJust (guard . isDoesNotExistError) $ readFile f xdgconfigdir <- getXdgDirectory XdgConfig "hledger"
case es of let
Left _ -> return nullconf localconf = "./hledger.conf"
Right s -> homeconf = homedir </> ".hledger.conf"
xdgconf = xdgconfigdir </> "hledger.conf"
dd = (dbg1With (("config file: "<>).fst) <$>)
mlocalconf <- readConfFile localconf
mhomeconf <- readConfFile homeconf
mxdgconf <- readConfFile xdgconf
case dd mlocalconf <|> dd mhomeconf <|> dd mxdgconf of
Nothing -> return $ traceAt 1 "no config file found" $ nullconf
Just (f,s) ->
case parseConf f (T.pack s) of case parseConf f (T.pack s) of
Left err -> error' $ errorBundlePretty err -- customErrorBundlePretty err Left err -> error' $ errorBundlePretty err -- customErrorBundlePretty err
Right ss -> return nullconf{ Right ss -> return nullconf{
@ -85,7 +94,13 @@ getConf = (do
,confFormat = 1 ,confFormat = 1
,confSections = ss ,confSections = ss
} }
) `catch` \(e :: IOException) -> error' $ show e
-- | If the specified file exists, read it and return the contents and the path;
-- if not, return Nothing. If there's any other IO error, exit the program.
readConfFile :: FilePath -> IO (Maybe (FilePath, String))
readConfFile f = do
exists <- doesFileExist f
if exists then readFile f <&> (Just.(f,)) else return Nothing
-- config file parsing -- config file parsing