{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}

-- Compatibility layer for GHC.ResponseFile
-- Implementation from base 4.12.0 is used.
-- http://hackage.haskell.org/package/base-4.12.0.0/src/LICENSE
module Distribution.Compat.ResponseFile (expandResponse, escapeArgs) where

import Distribution.Compat.Prelude

import GHC.ResponseFile (escapeArgs, unescapeArgs)

import Prelude ()

import System.FilePath
import System.IO (hPutStrLn, stderr)
import System.IO.Error

-- | The arg file / response file parser.
--
-- This is not a well-documented capability, and is a bit eccentric
-- (try @cabal \@foo \@bar@ to see what that does), but is crucial
-- for allowing complex arguments to cabal and cabal-install when
-- using command prompts with strongly-limited argument length.
expandResponse :: [String] -> IO [String]
expandResponse :: [String] -> IO [String]
expandResponse = Int -> String -> [String] -> IO [String]
go Int
recursionLimit String
"."
  where
    recursionLimit :: Int
recursionLimit = Int
100

    go :: Int -> FilePath -> [String] -> IO [String]
    go :: Int -> String -> [String] -> IO [String]
go Int
n String
dir
      | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 = ([[String]] -> [String]) -> IO [[String]] -> IO [String]
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (IO [[String]] -> IO [String])
-> ([String] -> IO [[String]]) -> [String] -> IO [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> IO [String]) -> [String] -> IO [[String]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (Int -> String -> String -> IO [String]
expand Int
n String
dir)
      | Bool
otherwise = IO [String] -> [String] -> IO [String]
forall a b. a -> b -> a
const (IO [String] -> [String] -> IO [String])
-> IO [String] -> [String] -> IO [String]
forall a b. (a -> b) -> a -> b
$ Handle -> String -> IO ()
hPutStrLn Handle
stderr String
"Error: response file recursion limit exceeded." IO () -> IO [String] -> IO [String]
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO [String]
forall a. IO a
exitFailure

    expand :: Int -> FilePath -> String -> IO [String]
    expand :: Int -> String -> String -> IO [String]
expand Int
n String
dir arg :: String
arg@(Char
'@' : String
f) = Int -> String -> IO [String]
readRecursively Int
n (String
dir String -> String -> String
</> String
f) IO [String] -> (IOError -> IO [String]) -> IO [String]
forall a. IO a -> (IOError -> IO a) -> IO a
`catchIOError` IO [String] -> IOError -> IO [String]
forall a b. a -> b -> a
const (String -> IO ()
forall a. Show a => a -> IO ()
print String
"?" IO () -> IO [String] -> IO [String]
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [String
arg])
    expand Int
_n String
_dir String
x = [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [String
x]

    readRecursively :: Int -> FilePath -> IO [String]
    readRecursively :: Int -> String -> IO [String]
readRecursively Int
n String
f = Int -> String -> [String] -> IO [String]
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) (String -> String
takeDirectory String
f) ([String] -> IO [String]) -> IO [String] -> IO [String]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> [String]
unescapeArgs (String -> [String]) -> IO String -> IO [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO String
readFile String
f