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

-- 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) where

import Prelude (mapM)
import Distribution.Compat.Prelude

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

#if MIN_VERSION_base(4,12,0)
import GHC.ResponseFile (unescapeArgs)
#else

unescapeArgs :: String -> [String]
unescapeArgs = filter (not . null) . unescape

data Quoting = NoneQ | SngQ | DblQ

unescape :: String -> [String]
unescape args = reverse . map reverse $ go args NoneQ False [] []
    where
      -- n.b., the order of these cases matters; these are cribbed from gcc

      -- case 1: end of input

      go []     _q    _bs   a as = a:as
      -- case 2: back-slash escape in progress

      go (c:cs) q     True  a as = go cs q     False (c:a) as
      -- case 3: no back-slash escape in progress, but got a back-slash

      go (c:cs) q     False a as
        | '\\' == c              = go cs q     True  a     as
      -- case 4: single-quote escaping in progress

      go (c:cs) SngQ  False a as
        | '\'' == c              = go cs NoneQ False a     as
        | otherwise              = go cs SngQ  False (c:a) as
      -- case 5: double-quote escaping in progress

      go (c:cs) DblQ  False a as
        | '"' == c               = go cs NoneQ False a     as
        | otherwise              = go cs DblQ  False (c:a) as
      -- case 6: no escaping is in progress

      go (c:cs) NoneQ False a as
        | isSpace c              = go cs NoneQ False []    (a:as)
        | '\'' == c              = go cs SngQ  False a     as
        | '"'  == c              = go cs DblQ  False a     as
        | otherwise              = go cs NoneQ False (c:a) as

#endif

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 (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 :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (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 (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 (IO [String] -> IOError -> IO [String])
-> IO [String] -> IOError -> IO [String]
forall a b. (a -> b) -> a -> b
$ String -> IO ()
forall a. Show a => a -> IO ()
print String
"?" IO () -> IO [String] -> IO [String]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [String] -> IO [String]
forall (m :: * -> *) a. Monad m => a -> m a
return [String
arg])
    expand Int
_n String
_dir String
x = [String] -> IO [String]
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