{-# LANGUAGE OverloadedStrings #-}

-- |
-- Module      : Clod.Config
-- Description : Configuration handling for the Clod application
-- Copyright   : (c) Fuzz Leonard, 2025
-- License     : MIT
-- Maintainer  : cyborg@bionicfuzz.com
-- Stability   : experimental
--
-- This module provides functions for handling configuration options
-- including environment variables and default values.

module Clod.Config
  ( -- * Configuration functions
    configDirName
  , clodIgnoreFile
  , clodConfigDir
  , getDataFileName
  ) where

import System.Environment (lookupEnv)
import System.FilePath ((</>))
import qualified Paths_clod as Paths

-- | Get configuration directory name
--
-- Returns the configuration directory name, checking the CLOD_DIR
-- environment variable first and falling back to ".clod" if not set.
--
-- @
-- configDir <- configDirName  -- Returns ".clod" or value of CLOD_DIR
-- @
configDirName :: IO String
configDirName :: IO String
configDirName = do
  envValue <- String -> IO (Maybe String)
lookupEnv String
"CLOD_DIR"
  return $ case 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"

-- | Get clodignore file name
--
-- Returns the clodignore file name, checking the CLODIGNORE
-- environment variable first and falling back to ".clodignore" if not set.
--
-- @
-- ignoreFile <- clodIgnoreFile  -- Returns ".clodignore" or value of CLODIGNORE
-- @
clodIgnoreFile :: IO String
clodIgnoreFile :: IO String
clodIgnoreFile = do
  envValue <- String -> IO (Maybe String)
lookupEnv String
"CLODIGNORE"
  return $ case 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"

-- | Build the config directory path from project root
--
-- @
-- configDir <- clodConfigDir "/path/to/project"  -- Returns "/path/to/project/.clod" or environment override
-- @
clodConfigDir :: FilePath -> IO FilePath
clodConfigDir :: String -> IO String
clodConfigDir String
rootPath = do
  dirName <- IO String
configDirName
  return $ rootPath </> dirName

-- | Get the path to a data file included with the package
-- This uses the Paths_clod module generated by Cabal
getDataFileName :: FilePath -> IO FilePath
getDataFileName :: String -> IO String
getDataFileName = String -> IO String
Paths.getDataFileName