{-# 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 :: [[Char]] -> IO [[Char]]
expandResponse = Int -> [Char] -> [[Char]] -> IO [[Char]]
go Int
recursionLimit [Char]
"."
  where
    recursionLimit :: Int
recursionLimit = Int
100

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

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

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