module Distribution.Simple.Utils (
        cabalVersion,
        
        
        die, dieWithLocation,
        
        dieNoVerbosity,
        die', dieWithLocation',
        dieNoWrap,
        topHandler, topHandlerWith,
        warn,
        notice, noticeNoWrap, noticeDoc,
        setupMessage,
        info, infoNoWrap,
        debug, debugNoWrap,
        chattyTry,
        annotateIO,
        printRawCommandAndArgs, printRawCommandAndArgsAndEnv,
        
        handleDoesNotExist,
        
        rawSystemExit,
        rawSystemExitCode,
        rawSystemExitWithEnv,
        rawSystemStdout,
        rawSystemStdInOut,
        rawSystemIOWithEnv,
        createProcessWithEnv,
        maybeExit,
        xargs,
        findProgramLocation,
        findProgramVersion,
        
        
        
        
        
        IOData(..),
        IODataMode(..),
        
        smartCopySources,
        createDirectoryIfMissingVerbose,
        copyFileVerbose,
        copyDirectoryRecursiveVerbose,
        copyFiles,
        copyFileTo,
        
        installOrdinaryFile,
        installExecutableFile,
        installMaybeExecutableFile,
        installOrdinaryFiles,
        installExecutableFiles,
        installMaybeExecutableFiles,
        installDirectoryContents,
        copyDirectoryRecursive,
        
        doesExecutableExist,
        setFileOrdinary,
        setFileExecutable,
        
        currentDir,
        shortRelativePath,
        dropExeExtension,
        exeExtensions,
        
        findFile,
        findFirstFile,
        findFileWithExtension,
        findFileWithExtension',
        findAllFilesWithExtension,
        findModuleFile,
        findModuleFiles,
        getDirectoryContentsRecursive,
        
        isInSearchPath,
        addLibraryPath,
        
        matchFileGlob,
        matchDirFileGlob,
        parseFileGlob,
        FileGlob(..),
        
        moreRecentFile,
        existsAndIsMoreRecentThan,
        
        TempFileOptions(..), defaultTempFileOptions,
        withTempFile, withTempFileEx,
        withTempDirectory, withTempDirectoryEx,
        
        defaultPackageDesc,
        findPackageDesc,
        tryFindPackageDesc,
        defaultHookedPackageDesc,
        findHookedPackageDesc,
        
        withFileContents,
        writeFileAtomic,
        rewriteFile,
        rewriteFileEx,
        
        fromUTF8BS,
        fromUTF8LBS,
        toUTF8BS,
        toUTF8LBS,
        readUTF8File,
        withUTF8FileContents,
        writeUTF8File,
        normaliseLineEndings,
        
        ignoreBOM,
        
        dropWhileEndLE,
        takeWhileEndLE,
        equating,
        comparing,
        isInfixOf,
        intercalate,
        lowercase,
        listUnion,
        listUnionRight,
        ordNub,
        ordNubBy,
        ordNubRight,
        safeTail,
        unintersperse,
        wrapText,
        wrapLine,
        
        isAbsoluteOnAnyPlatform,
        isRelativeOnAnyPlatform,
  ) where
import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Text
import Distribution.Utils.Generic
import Distribution.Utils.IOData (IOData(..), IODataMode(..))
import qualified Distribution.Utils.IOData as IOData
import Distribution.ModuleName as ModuleName
import Distribution.System
import Distribution.Version
import Distribution.Compat.CopyFile
import Distribution.Compat.Internal.TempFile
import Distribution.Compat.Exception
import Distribution.Compat.Stack
import Distribution.Verbosity
import Distribution.Types.PackageId
#if __GLASGOW_HASKELL__ < 711
#ifdef VERSION_base
#define BOOTSTRAPPED_CABAL 1
#endif
#else
#ifdef CURRENT_PACKAGE_KEY
#define BOOTSTRAPPED_CABAL 1
#endif
#endif
#ifdef BOOTSTRAPPED_CABAL
import qualified Paths_Cabal (version)
#endif
import Control.Concurrent.MVar
    ( newEmptyMVar, putMVar, takeMVar )
import Data.Typeable
    ( cast )
import qualified Data.ByteString.Lazy.Char8 as BS.Char8
import System.Directory
    ( Permissions(executable), getDirectoryContents, getPermissions
    , doesDirectoryExist, doesFileExist, removeFile, findExecutable
    , getModificationTime, createDirectory, removeDirectoryRecursive )
import System.Environment
    ( getProgName )
import System.Exit
    ( exitWith, ExitCode(..) )
import System.FilePath
    ( normalise, (</>), (<.>)
    , getSearchPath, joinPath, takeDirectory, splitFileName
    , splitExtension, splitExtensions, splitDirectories
    , searchPathSeparator )
import System.IO
    ( Handle, hSetBinaryMode, hGetContents, stderr, stdout, hPutStr, hFlush
    , hClose, hSetBuffering, BufferMode(..) )
import System.IO.Error
import System.IO.Unsafe
    ( unsafeInterleaveIO )
import qualified Control.Exception as Exception
import Data.Time.Clock.POSIX (getPOSIXTime, POSIXTime)
import Control.Exception (IOException, evaluate, throwIO)
import Control.Concurrent (forkIO)
import Numeric (showFFloat)
import qualified System.Process as Process
         ( CreateProcess(..), StdStream(..), proc)
import System.Process
         ( ProcessHandle, createProcess, rawSystem, runInteractiveProcess
         , showCommandForUser, waitForProcess)
import qualified Text.PrettyPrint as Disp
cabalVersion :: Version
#if defined(BOOTSTRAPPED_CABAL)
cabalVersion = mkVersion' Paths_Cabal.version
#elif defined(CABAL_VERSION)
cabalVersion = mkVersion [CABAL_VERSION]
#else
cabalVersion = mkVersion [1,9999]  
#endif
dieWithLocation :: FilePath -> Maybe Int -> String -> IO a
dieWithLocation filename lineno msg =
  ioError . setLocation lineno
          . flip ioeSetFileName (normalise filename)
          $ userError msg
  where
    setLocation Nothing  err = err
    setLocation (Just n) err = ioeSetLocation err (show n)
    _ = callStack 
die :: String -> IO a
die = dieNoVerbosity
dieNoVerbosity :: String -> IO a
dieNoVerbosity msg
    = ioError (userError msg)
  where
    _ = callStack 
ioeSetVerbatim :: IOError -> IOError
ioeSetVerbatim e = ioeSetLocation e "dieVerbatim"
ioeGetVerbatim :: IOError -> Bool
ioeGetVerbatim e = ioeGetLocation e == "dieVerbatim"
verbatimUserError :: String -> IOError
verbatimUserError = ioeSetVerbatim . userError
dieWithLocation' :: Verbosity -> FilePath -> Maybe Int -> String -> IO a
dieWithLocation' verbosity filename mb_lineno msg = withFrozenCallStack $ do
    ts <- getPOSIXTime
    pname <- getProgName
    ioError . verbatimUserError
            . withMetadata ts AlwaysMark VerboseTrace verbosity
            . wrapTextVerbosity verbosity
            $ pname ++ ": " ++
              filename ++ (case mb_lineno of
                            Just lineno -> ":" ++ show lineno
                            Nothing -> "") ++
              ": " ++ msg
die' :: Verbosity -> String -> IO a
die' verbosity msg = withFrozenCallStack $ do
    ts <- getPOSIXTime
    pname <- getProgName
    ioError . verbatimUserError
            . withMetadata ts AlwaysMark VerboseTrace verbosity
            . wrapTextVerbosity verbosity
            $ pname ++ ": " ++ msg
dieNoWrap :: Verbosity -> String -> IO a
dieNoWrap verbosity msg = withFrozenCallStack $ do
    
    ts <- getPOSIXTime
    ioError . verbatimUserError
            . withMetadata ts AlwaysMark VerboseTrace verbosity
            $ msg
annotateIO :: Verbosity -> IO a -> IO a
annotateIO verbosity act = do
    ts <- getPOSIXTime
    modifyIOError (f ts) act
  where
    f ts ioe = ioeSetErrorString ioe
             . withMetadata ts NeverMark VerboseTrace verbosity
             $ ioeGetErrorString ioe
topHandlerWith :: forall a. (Exception.SomeException -> IO a) -> IO a -> IO a
topHandlerWith cont prog = do
    
    
    hSetBuffering stderr LineBuffering
    Exception.catches prog [
        Exception.Handler rethrowAsyncExceptions
      , Exception.Handler rethrowExitStatus
      , Exception.Handler handle
      ]
  where
    
    rethrowAsyncExceptions :: Exception.AsyncException -> NoCallStackIO a
    rethrowAsyncExceptions a = throwIO a
    
    rethrowExitStatus :: ExitCode -> NoCallStackIO a
    rethrowExitStatus = throwIO
    
    handle :: Exception.SomeException -> NoCallStackIO a
    handle se = do
      hFlush stdout
      pname <- getProgName
      hPutStr stderr (message pname se)
      cont se
    message :: String -> Exception.SomeException -> String
    message pname (Exception.SomeException se) =
      case cast se :: Maybe Exception.IOException of
        Just ioe
         | ioeGetVerbatim ioe ->
            
            ioeGetErrorString ioe ++ "\n"
         | isUserError ioe ->
          let file         = case ioeGetFileName ioe of
                               Nothing   -> ""
                               Just path -> path ++ location ++ ": "
              location     = case ioeGetLocation ioe of
                               l@(n:_) | isDigit n -> ':' : l
                               _                        -> ""
              detail       = ioeGetErrorString ioe
          in wrapText (pname ++ ": " ++ file ++ detail)
        _ ->
          displaySomeException se ++ "\n"
displaySomeException :: Exception.Exception e => e -> String
displaySomeException se =
#if __GLASGOW_HASKELL__ < 710
    show se
#else
    Exception.displayException se
#endif
topHandler :: IO a -> IO a
topHandler prog = topHandlerWith (const $ exitWith (ExitFailure 1)) prog
warn :: Verbosity -> String -> IO ()
warn verbosity msg = withFrozenCallStack $ do
  when (verbosity >= normal) $ do
    ts <- getPOSIXTime
    hFlush stdout
    hPutStr stderr . withMetadata ts NormalMark FlagTrace verbosity
                   . wrapTextVerbosity verbosity
                   $ "Warning: " ++ msg
notice :: Verbosity -> String -> IO ()
notice verbosity msg = withFrozenCallStack $ do
  when (verbosity >= normal) $ do
    ts <- getPOSIXTime
    hPutStr stdout . withMetadata ts NormalMark FlagTrace verbosity
                   . wrapTextVerbosity verbosity
                   $ msg
noticeNoWrap :: Verbosity -> String -> IO ()
noticeNoWrap verbosity msg = withFrozenCallStack $ do
  when (verbosity >= normal) $ do
    ts <- getPOSIXTime
    hPutStr stdout . withMetadata ts NormalMark FlagTrace verbosity $ msg
noticeDoc :: Verbosity -> Disp.Doc -> IO ()
noticeDoc verbosity msg = withFrozenCallStack $ do
  when (verbosity >= normal) $ do
    ts <- getPOSIXTime
    hPutStr stdout . withMetadata ts NormalMark FlagTrace verbosity
                   . Disp.renderStyle defaultStyle $ msg
setupMessage :: Verbosity -> String -> PackageIdentifier -> IO ()
setupMessage verbosity msg pkgid = withFrozenCallStack $ do
    noticeNoWrap verbosity (msg ++ ' ': display pkgid ++ "...")
info :: Verbosity -> String -> IO ()
info verbosity msg = withFrozenCallStack $
  when (verbosity >= verbose) $ do
    ts <- getPOSIXTime
    hPutStr stdout . withMetadata ts NeverMark FlagTrace verbosity
                   . wrapTextVerbosity verbosity
                   $ msg
infoNoWrap :: Verbosity -> String -> IO ()
infoNoWrap verbosity msg = withFrozenCallStack $
  when (verbosity >= verbose) $ do
    ts <- getPOSIXTime
    hPutStr stdout . withMetadata ts NeverMark FlagTrace verbosity
                   $ msg
debug :: Verbosity -> String -> IO ()
debug verbosity msg = withFrozenCallStack $
  when (verbosity >= deafening) $ do
    ts <- getPOSIXTime
    hPutStr stdout . withMetadata ts NeverMark FlagTrace verbosity
                   . wrapTextVerbosity verbosity
                   $ msg
    
    hFlush stdout
debugNoWrap :: Verbosity -> String -> IO ()
debugNoWrap verbosity msg = withFrozenCallStack $
  when (verbosity >= deafening) $ do
    ts <- getPOSIXTime
    hPutStr stdout . withMetadata ts NeverMark FlagTrace verbosity
                   $ msg
    
    hFlush stdout
chattyTry :: String  
          -> IO ()   
          -> IO ()
chattyTry desc action =
  catchIO action $ \exception ->
    putStrLn $ "Error while " ++ desc ++ ": " ++ show exception
handleDoesNotExist :: a -> NoCallStackIO a -> NoCallStackIO a
handleDoesNotExist e =
    Exception.handleJust
      (\ioe -> if isDoesNotExistError ioe then Just ioe else Nothing)
      (\_ -> return e)
wrapTextVerbosity :: Verbosity -> String -> String
wrapTextVerbosity verb
  | isVerboseNoWrap verb = withTrailingNewline
  | otherwise            = withTrailingNewline . wrapText
withTimestamp :: Verbosity -> POSIXTime -> String -> String
withTimestamp v ts msg
  | isVerboseTimestamp v  = msg'
  | otherwise             = msg 
  where
    msg' = case lines msg of
      []      -> tsstr "\n"
      l1:rest -> unlines (tsstr (' ':l1) : map (contpfx++) rest)
    
    tsstr = showFFloat (Just 3) (realToFrac ts :: Double)
    
    contpfx = replicate (length (tsstr " ")) ' '
withOutputMarker :: Verbosity -> String -> String
withOutputMarker v xs | not (isVerboseMarkOutput v) = xs
withOutputMarker _ "" = "" 
withOutputMarker _ xs =
    "-----BEGIN CABAL OUTPUT-----\n" ++
    withTrailingNewline xs ++
    "-----END CABAL OUTPUT-----\n"
withTrailingNewline :: String -> String
withTrailingNewline "" = ""
withTrailingNewline (x:xs) = x : go x xs
  where
    go   _ (c:cs) = c : go c cs
    go '\n' "" = ""
    go   _  "" = "\n"
withCallStackPrefix :: WithCallStack (TraceWhen -> Verbosity -> String -> String)
withCallStackPrefix tracer verbosity s = withFrozenCallStack $
    (if isVerboseCallSite verbosity
        then parentSrcLocPrefix ++
             
             if isVerboseMarkOutput verbosity
                then "\n"
                else ""
        else "") ++
    (case traceWhen verbosity tracer of
        Just pre -> pre ++ prettyCallStack callStack ++ "\n"
        Nothing  -> "") ++
    s
data TraceWhen
    = AlwaysTrace
    | VerboseTrace
    | FlagTrace
    deriving (Eq)
traceWhen :: Verbosity -> TraceWhen -> Maybe String
traceWhen _ AlwaysTrace = Just ""
traceWhen v VerboseTrace | v >= verbose         = Just ""
traceWhen v FlagTrace    | isVerboseCallStack v = Just "----\n"
traceWhen _ _ = Nothing
data MarkWhen = AlwaysMark | NormalMark | NeverMark
withMetadata :: WithCallStack (POSIXTime -> MarkWhen -> TraceWhen -> Verbosity -> String -> String)
withMetadata ts marker tracer verbosity x = withFrozenCallStack $
    
    
      withTrailingNewline
    . withCallStackPrefix tracer verbosity
    . (case marker of
        AlwaysMark -> withOutputMarker verbosity
        NormalMark | not (isVerboseQuiet verbosity)
                   -> withOutputMarker verbosity
                   | otherwise
                   -> id
        NeverMark  -> id)
    
    . clearMarkers
    . withTimestamp verbosity ts
    $ x
clearMarkers :: String -> String
clearMarkers s = unlines . filter isMarker $ lines s
  where
    isMarker "-----BEGIN CABAL OUTPUT-----" = False
    isMarker "-----END CABAL OUTPUT-----"   = False
    isMarker _ = True
maybeExit :: IO ExitCode -> IO ()
maybeExit cmd = do
  res <- cmd
  unless (res == ExitSuccess) $ exitWith res
printRawCommandAndArgs :: Verbosity -> FilePath -> [String] -> IO ()
printRawCommandAndArgs verbosity path args = withFrozenCallStack $
    printRawCommandAndArgsAndEnv verbosity path args Nothing Nothing
printRawCommandAndArgsAndEnv :: Verbosity
                             -> FilePath
                             -> [String]
                             -> Maybe FilePath
                             -> Maybe [(String, String)]
                             -> IO ()
printRawCommandAndArgsAndEnv verbosity path args mcwd menv = do
    case menv of
        Just env -> debugNoWrap verbosity ("Environment: " ++ show env)
        Nothing -> return ()
    case mcwd of
        Just cwd -> debugNoWrap verbosity ("Working directory: " ++ show cwd)
        Nothing -> return ()
    infoNoWrap verbosity (showCommandForUser path args)
rawSystemExit :: Verbosity -> FilePath -> [String] -> IO ()
rawSystemExit verbosity path args = withFrozenCallStack $ do
  printRawCommandAndArgs verbosity path args
  hFlush stdout
  exitcode <- rawSystem path args
  unless (exitcode == ExitSuccess) $ do
    debug verbosity $ path ++ " returned " ++ show exitcode
    exitWith exitcode
rawSystemExitCode :: Verbosity -> FilePath -> [String] -> IO ExitCode
rawSystemExitCode verbosity path args = withFrozenCallStack $ do
  printRawCommandAndArgs verbosity path args
  hFlush stdout
  exitcode <- rawSystem path args
  unless (exitcode == ExitSuccess) $ do
    debug verbosity $ path ++ " returned " ++ show exitcode
  return exitcode
rawSystemExitWithEnv :: Verbosity
                     -> FilePath
                     -> [String]
                     -> [(String, String)]
                     -> IO ()
rawSystemExitWithEnv verbosity path args env = withFrozenCallStack $ do
    printRawCommandAndArgsAndEnv verbosity path args Nothing (Just env)
    hFlush stdout
    (_,_,_,ph) <- createProcess $
                  (Process.proc path args) { Process.env = (Just env)
#ifdef MIN_VERSION_process
#if MIN_VERSION_process(1,2,0)
                                           , Process.delegate_ctlc = True
#endif
#endif
                                           }
    exitcode <- waitForProcess ph
    unless (exitcode == ExitSuccess) $ do
        debug verbosity $ path ++ " returned " ++ show exitcode
        exitWith exitcode
rawSystemIOWithEnv :: Verbosity
                   -> FilePath
                   -> [String]
                   -> Maybe FilePath           
                   -> Maybe [(String, String)] 
                   -> Maybe Handle  
                   -> Maybe Handle  
                   -> Maybe Handle  
                   -> IO ExitCode
rawSystemIOWithEnv verbosity path args mcwd menv inp out err = withFrozenCallStack $ do
    (_,_,_,ph) <- createProcessWithEnv verbosity path args mcwd menv
                                       (mbToStd inp) (mbToStd out) (mbToStd err)
    exitcode <- waitForProcess ph
    unless (exitcode == ExitSuccess) $ do
      debug verbosity $ path ++ " returned " ++ show exitcode
    return exitcode
  where
    mbToStd :: Maybe Handle -> Process.StdStream
    mbToStd = maybe Process.Inherit Process.UseHandle
createProcessWithEnv ::
     Verbosity
  -> FilePath
  -> [String]
  -> Maybe FilePath           
  -> Maybe [(String, String)] 
  -> Process.StdStream  
  -> Process.StdStream  
  -> Process.StdStream  
  -> IO (Maybe Handle, Maybe Handle, Maybe Handle,ProcessHandle)
  
  
createProcessWithEnv verbosity path args mcwd menv inp out err = withFrozenCallStack $ do
    printRawCommandAndArgsAndEnv verbosity path args mcwd menv
    hFlush stdout
    (inp', out', err', ph) <- createProcess $
                                (Process.proc path args) {
                                    Process.cwd           = mcwd
                                  , Process.env           = menv
                                  , Process.std_in        = inp
                                  , Process.std_out       = out
                                  , Process.std_err       = err
#ifdef MIN_VERSION_process
#if MIN_VERSION_process(1,2,0)
                                  , Process.delegate_ctlc = True
#endif
#endif
                                  }
    return (inp', out', err', ph)
rawSystemStdout :: Verbosity -> FilePath -> [String] -> IO String
rawSystemStdout verbosity path args = withFrozenCallStack $ do
  (IODataText output, errors, exitCode) <- rawSystemStdInOut verbosity path args
                                                  Nothing Nothing
                                                  Nothing IODataModeText
  when (exitCode /= ExitSuccess) $
    die errors
  return output
rawSystemStdInOut :: Verbosity
                  -> FilePath                 
                  -> [String]                 
                  -> Maybe FilePath           
                  -> Maybe [(String, String)] 
                  -> Maybe IOData             
                  -> IODataMode               
                  -> IO (IOData, String, ExitCode) 
rawSystemStdInOut verbosity path args mcwd menv input outputMode = withFrozenCallStack $ do
  printRawCommandAndArgs verbosity path args
  Exception.bracket
     (runInteractiveProcess path args mcwd menv)
     (\(inh,outh,errh,_) -> hClose inh >> hClose outh >> hClose errh)
    $ \(inh,outh,errh,pid) -> do
      
      
      hSetBinaryMode errh False
      
      
      err <- hGetContents errh
      out <- IOData.hGetContents outh outputMode
      mv <- newEmptyMVar
      let force str = do
            mberr <- Exception.try (evaluate (rnf str) >> return ())
            putMVar mv (mberr :: Either IOError ())
      _ <- forkIO $ force out
      _ <- forkIO $ force err
      
      case input of
        Nothing -> return ()
        Just inputData -> do
          
          IOData.hPutContents inh inputData
          
          
      
      mberr1 <- takeMVar mv
      mberr2 <- takeMVar mv
      
      exitcode <- waitForProcess pid
      unless (exitcode == ExitSuccess) $
        debug verbosity $ path ++ " returned " ++ show exitcode
                       ++ if null err then "" else
                          " with error message:\n" ++ err
                       ++ case input of
                            Nothing       -> ""
                            Just d | IOData.null d -> ""
                            Just (IODataText inp) -> "\nstdin input:\n" ++ inp
                            Just (IODataBinary inp) -> "\nstdin input (binary):\n" ++ show inp
      
      
      reportOutputIOError mberr1
      reportOutputIOError mberr2
      return (out, err, exitcode)
  where
    reportOutputIOError :: Either IOError () -> NoCallStackIO ()
    reportOutputIOError =
      either (\e -> throwIO (ioeSetFileName e ("output of " ++ path)))
             return
findProgramLocation :: Verbosity -> FilePath -> IO (Maybe FilePath)
findProgramLocation verbosity prog = withFrozenCallStack $ do
  debug verbosity $ "searching for " ++ prog ++ " in path."
  res <- findExecutable prog
  case res of
      Nothing   -> debug verbosity ("Cannot find " ++ prog ++ " on the path")
      Just path -> debug verbosity ("found " ++ prog ++ " at "++ path)
  return res
findProgramVersion :: String             
                   -> (String -> String) 
                                         
                   -> Verbosity
                   -> FilePath           
                   -> IO (Maybe Version)
findProgramVersion versionArg selectVersion verbosity path = withFrozenCallStack $ do
  str <- rawSystemStdout verbosity path [versionArg]
         `catchIO`   (\_ -> return "")
         `catchExit` (\_ -> return "")
  let version :: Maybe Version
      version = simpleParse (selectVersion str)
  case version of
      Nothing -> warn verbosity $ "cannot determine version of " ++ path
                               ++ " :\n" ++ show str
      Just v  -> debug verbosity $ path ++ " is version " ++ display v
  return version
xargs :: Int -> ([String] -> IO ())
      -> [String] -> [String] -> IO ()
xargs maxSize rawSystemFun fixedArgs bigArgs =
  let fixedArgSize = sum (map length fixedArgs) + length fixedArgs
      chunkSize = maxSize  fixedArgSize
   in traverse_ (rawSystemFun . (fixedArgs ++)) (chunks chunkSize bigArgs)
  where chunks len = unfoldr $ \s ->
          if null s then Nothing
                    else Just (chunk [] len s)
        chunk acc _   []     = (reverse acc,[])
        chunk acc len (s:ss)
          | len' < len = chunk (s:acc) (lenlen'1) ss
          | otherwise  = (reverse acc, s:ss)
          where len' = length s
findFile :: [FilePath]    
         -> FilePath      
         -> IO FilePath
findFile searchPath fileName =
  findFirstFile id
    [ path </> fileName
    | path <- nub searchPath]
  >>= maybe (die $ fileName ++ " doesn't exist") return
findFileWithExtension :: [String]
                      -> [FilePath]
                      -> FilePath
                      -> NoCallStackIO (Maybe FilePath)
findFileWithExtension extensions searchPath baseName =
  findFirstFile id
    [ path </> baseName <.> ext
    | path <- nub searchPath
    , ext <- nub extensions ]
findAllFilesWithExtension :: [String]
                          -> [FilePath]
                          -> FilePath
                          -> NoCallStackIO [FilePath]
findAllFilesWithExtension extensions searchPath basename =
  findAllFiles id
    [ path </> basename <.> ext
    | path <- nub searchPath
    , ext <- nub extensions ]
findFileWithExtension' :: [String]
                       -> [FilePath]
                       -> FilePath
                       -> NoCallStackIO (Maybe (FilePath, FilePath))
findFileWithExtension' extensions searchPath baseName =
  findFirstFile (uncurry (</>))
    [ (path, baseName <.> ext)
    | path <- nub searchPath
    , ext <- nub extensions ]
findFirstFile :: (a -> FilePath) -> [a] -> NoCallStackIO (Maybe a)
findFirstFile file = findFirst
  where findFirst []     = return Nothing
        findFirst (x:xs) = do exists <- doesFileExist (file x)
                              if exists
                                then return (Just x)
                                else findFirst xs
findAllFiles :: (a -> FilePath) -> [a] -> NoCallStackIO [a]
findAllFiles file = filterM (doesFileExist . file)
findModuleFiles :: [FilePath]   
                -> [String]     
                -> [ModuleName] 
                -> IO [(FilePath, FilePath)]
findModuleFiles searchPath extensions moduleNames =
  traverse (findModuleFile searchPath extensions) moduleNames
findModuleFile :: [FilePath]  
               -> [String]    
               -> ModuleName  
               -> IO (FilePath, FilePath)
findModuleFile searchPath extensions mod_name =
      maybe notFound return
  =<< findFileWithExtension' extensions searchPath
                             (ModuleName.toFilePath mod_name)
  where
    notFound = die $ "Error: Could not find module: " ++ display mod_name
                  ++ " with any suffix: " ++ show extensions
                  ++ " in the search path: " ++ show searchPath
getDirectoryContentsRecursive :: FilePath -> IO [FilePath]
getDirectoryContentsRecursive topdir = recurseDirectories [""]
  where
    recurseDirectories :: [FilePath] -> IO [FilePath]
    recurseDirectories []         = return []
    recurseDirectories (dir:dirs) = unsafeInterleaveIO $ do
      (files, dirs') <- collect [] [] =<< getDirectoryContents (topdir </> dir)
      files' <- recurseDirectories (dirs' ++ dirs)
      return (files ++ files')
      where
        collect files dirs' []              = return (reverse files
                                                     ,reverse dirs')
        collect files dirs' (entry:entries) | ignore entry
                                            = collect files dirs' entries
        collect files dirs' (entry:entries) = do
          let dirEntry = dir </> entry
          isDirectory <- doesDirectoryExist (topdir </> dirEntry)
          if isDirectory
            then collect files (dirEntry:dirs') entries
            else collect (dirEntry:files) dirs' entries
        ignore ['.']      = True
        ignore ['.', '.'] = True
        ignore _          = False
isInSearchPath :: FilePath -> NoCallStackIO Bool
isInSearchPath path = fmap (elem path) getSearchPath
addLibraryPath :: OS
               -> [FilePath]
               -> [(String,String)]
               -> [(String,String)]
addLibraryPath os paths = addEnv
  where
    pathsString = intercalate [searchPathSeparator] paths
    ldPath = case os of
               OSX -> "DYLD_LIBRARY_PATH"
               _   -> "LD_LIBRARY_PATH"
    addEnv [] = [(ldPath,pathsString)]
    addEnv ((key,value):xs)
      | key == ldPath =
          if null value
             then (key,pathsString):xs
             else (key,value ++ (searchPathSeparator:pathsString)):xs
      | otherwise     = (key,value):addEnv xs
data FileGlob
   
   = NoGlob FilePath
   
   
   | FileGlob FilePath String
parseFileGlob :: FilePath -> Maybe FileGlob
parseFileGlob filepath = case splitExtensions filepath of
  (filepath', ext) -> case splitFileName filepath' of
    (dir, "*") | '*' `elem` dir
              || '*' `elem` ext
              || null ext            -> Nothing
               | null dir            -> Just (FileGlob "." ext)
               | otherwise           -> Just (FileGlob dir ext)
    _          | '*' `elem` filepath -> Nothing
               | otherwise           -> Just (NoGlob filepath)
matchFileGlob :: FilePath -> IO [FilePath]
matchFileGlob = matchDirFileGlob "."
matchDirFileGlob :: FilePath -> FilePath -> IO [FilePath]
matchDirFileGlob dir filepath = case parseFileGlob filepath of
  Nothing -> die $ "invalid file glob '" ++ filepath
                ++ "'. Wildcards '*' are only allowed in place of the file"
                ++ " name, not in the directory name or file extension."
                ++ " If a wildcard is used it must be with an file extension."
  Just (NoGlob filepath') -> return [filepath']
  Just (FileGlob dir' ext) -> do
    files <- getDirectoryContents (dir </> dir')
    case   [ dir' </> file
           | file <- files
           , let (name, ext') = splitExtensions file
           , not (null name) && ext' == ext ] of
      []      -> die $ "filepath wildcard '" ++ filepath
                    ++ "' does not match any files."
      matches -> return matches
moreRecentFile :: FilePath -> FilePath -> NoCallStackIO Bool
moreRecentFile a b = do
  exists <- doesFileExist b
  if not exists
    then return True
    else do tb <- getModificationTime b
            ta <- getModificationTime a
            return (ta > tb)
existsAndIsMoreRecentThan :: FilePath -> FilePath -> NoCallStackIO Bool
existsAndIsMoreRecentThan a b = do
  exists <- doesFileExist a
  if not exists
    then return False
    else a `moreRecentFile` b
createDirectoryIfMissingVerbose :: Verbosity
                                -> Bool     
                                -> FilePath
                                -> IO ()
createDirectoryIfMissingVerbose verbosity create_parents path0
  | create_parents = withFrozenCallStack $ createDirs (parents path0)
  | otherwise      = withFrozenCallStack $ createDirs (take 1 (parents path0))
  where
    parents = reverse . scanl1 (</>) . splitDirectories . normalise
    createDirs []         = return ()
    createDirs (dir:[])   = createDir dir throwIO
    createDirs (dir:dirs) =
      createDir dir $ \_ -> do
        createDirs dirs
        createDir dir throwIO
    createDir :: FilePath -> (IOException -> IO ()) -> IO ()
    createDir dir notExistHandler = do
      r <- tryIO $ createDirectoryVerbose verbosity dir
      case (r :: Either IOException ()) of
        Right ()                   -> return ()
        Left  e
          | isDoesNotExistError  e -> notExistHandler e
          
          
          
          
          
          
          
          | isAlreadyExistsError e -> (do
              isDir <- doesDirectoryExist dir
              unless isDir $ throwIO e
              ) `catchIO` ((\_ -> return ()) :: IOException -> IO ())
          | otherwise              -> throwIO e
createDirectoryVerbose :: Verbosity -> FilePath -> IO ()
createDirectoryVerbose verbosity dir = withFrozenCallStack $ do
  info verbosity $ "creating " ++ dir
  createDirectory dir
  setDirOrdinary dir
copyFileVerbose :: Verbosity -> FilePath -> FilePath -> IO ()
copyFileVerbose verbosity src dest = withFrozenCallStack $ do
  info verbosity ("copy " ++ src ++ " to " ++ dest)
  copyFile src dest
installOrdinaryFile :: Verbosity -> FilePath -> FilePath -> IO ()
installOrdinaryFile verbosity src dest = withFrozenCallStack $ do
  info verbosity ("Installing " ++ src ++ " to " ++ dest)
  copyOrdinaryFile src dest
installExecutableFile :: Verbosity -> FilePath -> FilePath -> IO ()
installExecutableFile verbosity src dest = withFrozenCallStack $ do
  info verbosity ("Installing executable " ++ src ++ " to " ++ dest)
  copyExecutableFile src dest
installMaybeExecutableFile :: Verbosity -> FilePath -> FilePath -> IO ()
installMaybeExecutableFile verbosity src dest = withFrozenCallStack $ do
  perms <- getPermissions src
  if (executable perms) 
    then installExecutableFile verbosity src dest
    else installOrdinaryFile   verbosity src dest
copyFileTo :: Verbosity -> FilePath -> FilePath -> IO ()
copyFileTo verbosity dir file = withFrozenCallStack $ do
  let targetFile = dir </> file
  createDirectoryIfMissingVerbose verbosity True (takeDirectory targetFile)
  installOrdinaryFile verbosity file targetFile
copyFilesWith :: (Verbosity -> FilePath -> FilePath -> IO ())
              -> Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
copyFilesWith doCopy verbosity targetDir srcFiles = withFrozenCallStack $ do
  
  let dirs = map (targetDir </>) . nub . map (takeDirectory . snd) $ srcFiles
  traverse_ (createDirectoryIfMissingVerbose verbosity True) dirs
  
  sequence_ [ let src  = srcBase   </> srcFile
                  dest = targetDir </> srcFile
               in doCopy verbosity src dest
            | (srcBase, srcFile) <- srcFiles ]
copyFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
copyFiles v fp fs = withFrozenCallStack (copyFilesWith copyFileVerbose v fp fs)
installOrdinaryFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
installOrdinaryFiles v fp fs = withFrozenCallStack (copyFilesWith installOrdinaryFile v fp fs)
installExecutableFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)]
                          -> IO ()
installExecutableFiles v fp fs = withFrozenCallStack (copyFilesWith installExecutableFile v fp fs)
installMaybeExecutableFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)]
                               -> IO ()
installMaybeExecutableFiles v fp fs = withFrozenCallStack (copyFilesWith installMaybeExecutableFile v fp fs)
installDirectoryContents :: Verbosity -> FilePath -> FilePath -> IO ()
installDirectoryContents verbosity srcDir destDir = withFrozenCallStack $ do
  info verbosity ("copy directory '" ++ srcDir ++ "' to '" ++ destDir ++ "'.")
  srcFiles <- getDirectoryContentsRecursive srcDir
  installOrdinaryFiles verbosity destDir [ (srcDir, f) | f <- srcFiles ]
copyDirectoryRecursive :: Verbosity -> FilePath -> FilePath -> IO ()
copyDirectoryRecursive verbosity srcDir destDir = withFrozenCallStack $ do
  info verbosity ("copy directory '" ++ srcDir ++ "' to '" ++ destDir ++ "'.")
  srcFiles <- getDirectoryContentsRecursive srcDir
  copyFilesWith (const copyFile) verbosity destDir [ (srcDir, f)
                                                   | f <- srcFiles ]
doesExecutableExist :: FilePath -> NoCallStackIO Bool
doesExecutableExist f = do
  exists <- doesFileExist f
  if exists
    then do perms <- getPermissions f
            return (executable perms)
    else return False
smartCopySources :: Verbosity -> [FilePath] -> FilePath
                 -> [ModuleName] -> [String] -> IO ()
smartCopySources verbosity searchPath targetDir moduleNames extensions = withFrozenCallStack $
      findModuleFiles searchPath extensions moduleNames
  >>= copyFiles verbosity targetDir
copyDirectoryRecursiveVerbose :: Verbosity -> FilePath -> FilePath -> IO ()
copyDirectoryRecursiveVerbose verbosity srcDir destDir = withFrozenCallStack $ do
  info verbosity ("copy directory '" ++ srcDir ++ "' to '" ++ destDir ++ "'.")
  srcFiles <- getDirectoryContentsRecursive srcDir
  copyFiles verbosity destDir [ (srcDir, f) | f <- srcFiles ]
data TempFileOptions = TempFileOptions {
  optKeepTempFiles :: Bool  
  }
defaultTempFileOptions :: TempFileOptions
defaultTempFileOptions = TempFileOptions { optKeepTempFiles = False }
withTempFile :: FilePath    
                -> String   
                -> (FilePath -> Handle -> IO a) -> IO a
withTempFile tmpDir template action =
  withTempFileEx defaultTempFileOptions tmpDir template action
withTempFileEx :: TempFileOptions
                 -> FilePath 
                 -> String   
                 -> (FilePath -> Handle -> IO a) -> IO a
withTempFileEx opts tmpDir template action =
  Exception.bracket
    (openTempFile tmpDir template)
    (\(name, handle) -> do hClose handle
                           unless (optKeepTempFiles opts) $
                             handleDoesNotExist () . removeFile $ name)
    (withLexicalCallStack (uncurry action))
withTempDirectory :: Verbosity -> FilePath -> String -> (FilePath -> IO a) -> IO a
withTempDirectory verbosity targetDir template f = withFrozenCallStack $
  withTempDirectoryEx verbosity defaultTempFileOptions targetDir template
    (withLexicalCallStack f)
withTempDirectoryEx :: Verbosity -> TempFileOptions
                       -> FilePath -> String -> (FilePath -> IO a) -> IO a
withTempDirectoryEx _verbosity opts targetDir template f = withFrozenCallStack $
  Exception.bracket
    (createTempDirectory targetDir template)
    (unless (optKeepTempFiles opts)
     . handleDoesNotExist () . removeDirectoryRecursive)
    (withLexicalCallStack f)
rewriteFile :: FilePath -> String -> IO ()
rewriteFile = rewriteFileEx normal
rewriteFileEx :: Verbosity -> FilePath -> String -> IO ()
rewriteFileEx verbosity path newContent =
  flip catchIO mightNotExist $ do
    existingContent <- annotateIO verbosity $ readFile path
    _ <- evaluate (length existingContent)
    unless (existingContent == newContent) $
      annotateIO verbosity $
        writeFileAtomic path (BS.Char8.pack newContent)
  where
    mightNotExist e | isDoesNotExistError e
                    = annotateIO verbosity $ writeFileAtomic path
                        (BS.Char8.pack newContent)
                    | otherwise
                    = ioError e
currentDir :: FilePath
currentDir = "."
shortRelativePath :: FilePath -> FilePath -> FilePath
shortRelativePath from to =
    case dropCommonPrefix (splitDirectories from) (splitDirectories to) of
        (stuff, path) -> joinPath (map (const "..") stuff ++ path)
  where
    dropCommonPrefix :: Eq a => [a] -> [a] -> ([a],[a])
    dropCommonPrefix (x:xs) (y:ys)
        | x == y    = dropCommonPrefix xs ys
    dropCommonPrefix xs ys = (xs,ys)
dropExeExtension :: FilePath -> FilePath
dropExeExtension filepath =
  case splitExtension filepath of
    (filepath', extension) | extension `elem` exeExtensions -> filepath'
                           | otherwise                      -> filepath
exeExtensions :: [String]
exeExtensions = case buildOS of
  
  
  
  Windows -> ["", "exe"]
  Ghcjs   -> ["", "exe"]
  _       -> [""]
defaultPackageDesc :: Verbosity -> IO FilePath
defaultPackageDesc _verbosity = tryFindPackageDesc currentDir
findPackageDesc :: FilePath                    
                -> NoCallStackIO (Either String FilePath) 
findPackageDesc dir
 = do files <- getDirectoryContents dir
      
      
      cabalFiles <- filterM doesFileExist
                       [ dir </> file
                       | file <- files
                       , let (name, ext) = splitExtension file
                       , not (null name) && ext == ".cabal" ]
      case cabalFiles of
        []          -> return (Left  noDesc)
        [cabalFile] -> return (Right cabalFile)
        multiple    -> return (Left  $ multiDesc multiple)
  where
    noDesc :: String
    noDesc = "No cabal file found.\n"
             ++ "Please create a package description file <pkgname>.cabal"
    multiDesc :: [String] -> String
    multiDesc l = "Multiple cabal files found.\n"
                  ++ "Please use only one of: "
                  ++ intercalate ", " l
tryFindPackageDesc :: FilePath -> IO FilePath
tryFindPackageDesc dir = either die return =<< findPackageDesc dir
defaultHookedPackageDesc :: IO (Maybe FilePath)
defaultHookedPackageDesc = findHookedPackageDesc currentDir
findHookedPackageDesc
    :: FilePath                 
    -> IO (Maybe FilePath)      
findHookedPackageDesc dir = do
    files <- getDirectoryContents dir
    buildInfoFiles <- filterM doesFileExist
                        [ dir </> file
                        | file <- files
                        , let (name, ext) = splitExtension file
                        , not (null name) && ext == buildInfoExt ]
    case buildInfoFiles of
        [] -> return Nothing
        [f] -> return (Just f)
        _ -> die ("Multiple files with extension " ++ buildInfoExt)
buildInfoExt  :: String
buildInfoExt = ".buildinfo"