{-# LANGUAGE OverloadedStrings #-}
module Clod.Config
(
configDirName
, clodIgnoreFile
, clodConfigDir
, getDataFileName
) where
import System.Environment (lookupEnv)
import System.FilePath ((</>))
import qualified Paths_clod as Paths
configDirName :: IO String
configDirName :: IO String
configDirName = do
Maybe String
envValue <- String -> IO (Maybe String)
lookupEnv String
"CLOD_DIR"
String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ case Maybe String
envValue of
Just String
value | Bool -> Bool
not (String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
value) -> String
value
Maybe String
_ -> String
".clod"
clodIgnoreFile :: IO String
clodIgnoreFile :: IO String
clodIgnoreFile = do
Maybe String
envValue <- String -> IO (Maybe String)
lookupEnv String
"CLODIGNORE"
String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ case Maybe String
envValue of
Just String
value | Bool -> Bool
not (String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
value) -> String
value
Maybe String
_ -> String
".clodignore"
clodConfigDir :: FilePath -> IO FilePath
clodConfigDir :: String -> IO String
clodConfigDir String
rootPath = do
String
dirName <- IO String
configDirName
String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ String
rootPath String -> String -> String
</> String
dirName
getDataFileName :: FilePath -> IO FilePath
getDataFileName :: String -> IO String
getDataFileName = String -> IO String
Paths.getDataFileName