{-# LANGUAGE OverloadedStrings #-} -- | -- Copyright: Herbert Valerio Riedel -- SPDX-License-Identifier: GPL-3.0-or-later -- module Cabal.Config where import Utils import qualified Data.Text as T import qualified Data.Text.Encoding as T import Distribution.Parsec.Parser import System.Directory (getAppUserDataDirectory) import System.Environment (lookupEnv) import System.Path.IO hackageRepoId :: T.Text hackageRepoId = "hackage.haskell.org" -- | Locate cabal configuration locateConfigFile :: IO (Path Absolute) locateConfigFile = do fp <- fmap fromFilePath (maybe (getAppUserDataDirectory "cabal") return =<< lookupEnv "CABAL_DIR") dir <- makeAbsolute fp return $ dir fragment "config" data CabalConfig = CabalConfig { ccRepos :: [(T.Text,Path Absolute)] -- (label, path) } deriving (Show) loadConfigFile :: Path Absolute -> IO CabalConfig loadConfigFile fp = do raw <- readStrictByteString fp let Right xs = readFields raw basedir' <- case [ val | Field (Name _ "remote-repo-cache") [FieldLine _ val] <- xs ] of [] -> fail ("remote-repo-cache not set in " ++ show (toFilePath fp)) vals -> return (bs2fp (last vals)) basedir <- makeAbsolute basedir' repos <- forM [ label | Section (Name _ "repository") [SecArgName _ label] _ <- xs ] $ \l -> do let l' = T.decodeUtf8 l d = basedir fragment (T.unpack l') pure (l', d) return (CabalConfig repos) where bs2fp = fromFilePath . T.unpack . T.decodeUtf8