{-# LANGUAGE CPP, ForeignFunctionInterface #-}
{-# OPTIONS_NHC98 -cpp #-}
{-# OPTIONS_JHC -fcpp -fffi #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Distribution.Simple.Utils
-- Copyright   :  Isaac Jones, Simon Marlow 2003-2004
--                portions Copyright (c) 2007, Galois Inc.
--
-- Maintainer  :  cabal-devel@haskell.org
-- Portability :  portable
--
-- A large and somewhat miscellaneous collection of utility functions used
-- throughout the rest of the Cabal lib and in other tools that use the Cabal
-- lib like @cabal-install@. It has a very simple set of logging actions. It
-- has low level functions for running programs, a bunch of wrappers for
-- various directory and file functions that do extra logging.

{- All rights reserved.

Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions are
met:

    * Redistributions of source code must retain the above copyright
      notice, this list of conditions and the following disclaimer.

    * Redistributions in binary form must reproduce the above
      copyright notice, this list of conditions and the following
      disclaimer in the documentation and/or other materials provided
      with the distribution.

    * Neither the name of Isaac Jones nor the names of other
      contributors may be used to endorse or promote products derived
      from this software without specific prior written permission.

THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -}

module Distribution.Simple.Utils (
        cabalVersion,

        -- * logging and errors
        die,
        dieWithLocation,
        topHandler,
        warn, notice, setupMessage, info, debug,
        chattyTry,

        -- * running programs
        rawSystemExit,
        rawSystemExitWithEnv,
        rawSystemStdout,
        rawSystemStdInOut,
        maybeExit,
        xargs,
        findProgramLocation,
        findProgramVersion,

        -- * copying files
        smartCopySources,
        createDirectoryIfMissingVerbose,
        copyFileVerbose,
        copyDirectoryRecursiveVerbose,
        copyFiles,

        -- * installing files
        installOrdinaryFile,
        installExecutableFile,
        installOrdinaryFiles,
        installDirectoryContents,

        -- * File permissions
        setFileOrdinary,
        setFileExecutable,

        -- * file names
        currentDir,

        -- * finding files
        findFile,
        findFirstFile,
        findFileWithExtension,
        findFileWithExtension',
        findModuleFile,
        findModuleFiles,
        getDirectoryContentsRecursive,

        -- * simple file globbing
        matchFileGlob,
        matchDirFileGlob,
        parseFileGlob,
        FileGlob(..),

        -- * temp files and dirs
        withTempFile,
        withTempDirectory,

        -- * .cabal and .buildinfo files
        defaultPackageDesc,
        findPackageDesc,
        defaultHookedPackageDesc,
        findHookedPackageDesc,

        -- * reading and writing files safely
        withFileContents,
        writeFileAtomic,
        rewriteFile,

        -- * Unicode
        fromUTF8,
        toUTF8,
        readUTF8File,
        withUTF8FileContents,
        writeUTF8File,
        normaliseLineEndings,

        -- * generic utils
        equating,
        comparing,
        isInfixOf,
        intercalate,
        lowercase,
        wrapText,
        wrapLine,
  ) where

import Control.Monad
    ( when, unless, filterM )
#ifdef __GLASGOW_HASKELL__
import Control.Concurrent.MVar
    ( newEmptyMVar, putMVar, takeMVar )
#endif
import Data.List
    ( nub, unfoldr, isPrefixOf, tails, intersperse )
import Data.Char as Char
    ( toLower, chr, ord )
import Data.Bits
    ( Bits((.|.), (.&.), shiftL, shiftR) )

import System.Directory
    ( getDirectoryContents, doesDirectoryExist, doesFileExist, removeFile
    , findExecutable )
import System.Environment
    ( getProgName )
import System.Cmd
    ( rawSystem )
import System.Exit
    ( exitWith, ExitCode(..) )
import System.FilePath
    ( normalise, (</>), (<.>), takeDirectory, splitFileName
    , splitExtension, splitExtensions, splitDirectories )
import System.Directory
    ( createDirectory, renameFile, removeDirectoryRecursive )
import System.IO
    ( Handle, openFile, openBinaryFile, IOMode(ReadMode), hSetBinaryMode
    , hGetContents, stderr, stdout, hPutStr, hFlush, hClose )
import System.IO.Error as IO.Error
    ( isDoesNotExistError, isAlreadyExistsError
    , ioeSetFileName, ioeGetFileName, ioeGetErrorString )
#if !(defined(__HUGS__) || (defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ < 608))
import System.IO.Error
    ( ioeSetLocation, ioeGetLocation )
#endif
import System.IO.Unsafe
    ( unsafeInterleaveIO )
import qualified Control.Exception as Exception

import Distribution.Text
    ( display, simpleParse )
import Distribution.Package
    ( PackageIdentifier )
import Distribution.ModuleName (ModuleName)
import qualified Distribution.ModuleName as ModuleName
import Distribution.Version
    (Version(..))

import Control.Exception (evaluate)
import System.Process (runProcess)

#ifdef __GLASGOW_HASKELL__
import Control.Concurrent (forkIO)
import System.Process (runInteractiveProcess, waitForProcess)
#else
import System.Cmd (system)
import System.Directory (getTemporaryDirectory)
#endif

import Distribution.Compat.CopyFile
         ( copyFile, copyOrdinaryFile, copyExecutableFile
         , setFileOrdinary, setFileExecutable, setDirOrdinary )
import Distribution.Compat.TempFile
         ( openTempFile, openNewBinaryFile, createTempDirectory )
import Distribution.Compat.Exception
         ( IOException, throwIOIO, tryIO, catchIO, catchExit, onException )
import Distribution.Verbosity

#ifdef VERSION_base
import qualified Paths_Cabal (version)
#endif

-- We only get our own version number when we're building with ourselves
cabalVersion :: Version
#if defined(VERSION_base)
cabalVersion = version :: VersionPaths_Cabal.version
#elif defined(CABAL_VERSION)
cabalVersion = Version [CABAL_VERSION] []
#else
cabalVersion = Version [1,9999] []  --used when bootstrapping
#endif

-- ----------------------------------------------------------------------------
-- Exception and logging utils

dieWithLocation :: FilePath -> Maybe Int -> String -> IO a
dieWithLocation filename lineno msg =
  ioError :: IOError -> IO aioError (.) :: (b -> c) -> (a -> b) -> a -> c. setLocation :: Maybe a -> IOError -> IOErrorsetLocation lineno :: Maybe Intlineno
          (.) :: (b -> c) -> (a -> b) -> a -> c. flip :: (a -> b -> c) -> b -> a -> cflip ioeSetFileName :: IOError -> FilePath -> IOErrorioeSetFileName (normalise :: FilePath -> FilePathnormalise filename :: FilePathfilename)
          ($) :: (a -> b) -> a -> b$ userError :: String -> IOErroruserError msg :: Stringmsg
  where
#if defined(__HUGS__) || (defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ < 608)
    setLocation _        err = err
#else
    setLocation Nothing  err = err :: IOErrorerr
    setLocation (Just n) err = ioeSetLocation :: IOError -> String -> IOErrorioeSetLocation err :: IOErrorerr (show :: Show a => a -> Stringshow n :: an)
#endif

die :: String -> IO a
die msg = ioError :: IOError -> IO aioError (userError :: String -> IOErroruserError msg :: Stringmsg)

topHandler :: IO a -> IO a
topHandler prog = catchIO :: IO a -> (IOException -> IO a) -> IO acatchIO prog :: IO aprog handle :: IOError -> IO bhandle
  where
    handle ioe = do
      hFlush :: Handle -> IO ()hFlush stdout :: Handlestdout
      pname <- getProgName :: IO StringgetProgName
      hPutStr :: Handle -> String -> IO ()hPutStr stderr :: Handlestderr (mesage :: [Char] -> Stringmesage pname :: [Char]pname)
      exitWith :: ExitCode -> IO aexitWith (ExitFailure :: Int -> ExitCodeExitFailure 1)
      where
        mesage pname = wrapText :: String -> StringwrapText (pname :: [Char]pname (++) :: [a] -> [a] -> [a]++ ": " (++) :: [a] -> [a] -> [a]++ file :: FilePathfile (++) :: [a] -> [a] -> [a]++ detail :: Stringdetail)
        file         = case ioeGetFileName :: IOError -> Maybe FilePathioeGetFileName ioe :: IOErrorioe of
                         Nothing   -> ""
                         Just path -> path :: FilePathpath (++) :: [a] -> [a] -> [a]++ location :: [Char]location (++) :: [a] -> [a] -> [a]++ ": "
#if defined(__HUGS__) || (defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ < 608)
        location     = ""
#else
        location     = case ioeGetLocation :: IOError -> StringioeGetLocation ioe :: IOErrorioe of
                         l@(n:_) | n :: an (>=) :: Ord a => a -> a -> Bool>= '0' (&&) :: Bool -> Bool -> Bool&& n :: an (<=) :: Ord a => a -> a -> Bool<= '9' -> ':' (:) :: a -> [a] -> [a]: l :: [String]l
                         _                              -> ""
#endif
        detail       = ioeGetErrorString :: IOError -> StringioeGetErrorString ioe :: IOErrorioe

-- | Non fatal conditions that may be indicative of an error or problem.
--
-- We display these at the 'normal' verbosity level.
--
warn :: Verbosity -> String -> IO ()
warn verbosity msg =
  when :: Monad m => Bool -> m () -> m ()when (verbosity :: Verbosityverbosity (>=) :: Ord a => a -> a -> Bool>= normal :: Verbositynormal) ($) :: (a -> b) -> a -> b$ do
    hFlush :: Handle -> IO ()hFlush stdout :: Handlestdout
    hPutStr :: Handle -> String -> IO ()hPutStr stderr :: Handlestderr (wrapText :: String -> StringwrapText ("Warning: " (++) :: [a] -> [a] -> [a]++ msg :: Stringmsg))

-- | Useful status messages.
--
-- We display these at the 'normal' verbosity level.
--
-- This is for the ordinary helpful status messages that users see. Just
-- enough information to know that things are working but not floods of detail.
--
notice :: Verbosity -> String -> IO ()
notice verbosity msg =
  when :: Monad m => Bool -> m () -> m ()when (verbosity :: Verbosityverbosity (>=) :: Ord a => a -> a -> Bool>= normal :: Verbositynormal) ($) :: (a -> b) -> a -> b$
    putStr :: String -> IO ()putStr (wrapText :: String -> StringwrapText msg :: Stringmsg)

setupMessage :: Verbosity -> String -> PackageIdentifier -> IO ()
setupMessage verbosity msg pkgid =
    notice :: Verbosity -> String -> IO ()notice verbosity :: Verbosityverbosity (msg :: Stringmsg (++) :: [a] -> [a] -> [a]++ ' '(:) :: a -> [a] -> [a]: display :: Text a => a -> Stringdisplay pkgid :: PackageIdentifierpkgid (++) :: [a] -> [a] -> [a]++ "...")

-- | More detail on the operation of some action.
--
-- We display these messages when the verbosity level is 'verbose'
--
info :: Verbosity -> String -> IO ()
info verbosity msg =
  when :: Monad m => Bool -> m () -> m ()when (verbosity :: Verbosityverbosity (>=) :: Ord a => a -> a -> Bool>= verbose :: Verbosityverbose) ($) :: (a -> b) -> a -> b$
    putStr :: String -> IO ()putStr (wrapText :: String -> StringwrapText msg :: Stringmsg)

-- | Detailed internal debugging information
--
-- We display these messages when the verbosity level is 'deafening'
--
debug :: Verbosity -> String -> IO ()
debug verbosity msg =
  when :: Monad m => Bool -> m () -> m ()when (verbosity :: Verbosityverbosity (>=) :: Ord a => a -> a -> Bool>= deafening :: Verbositydeafening) ($) :: (a -> b) -> a -> b$ do
    putStr :: String -> IO ()putStr (wrapText :: String -> StringwrapText msg :: Stringmsg)
    hFlush :: Handle -> IO ()hFlush stdout :: Handlestdout

-- | Perform an IO action, catching any IO exceptions and printing an error
--   if one occurs.
chattyTry :: String  -- ^ a description of the action we were attempting
          -> IO ()   -- ^ the action itself
          -> IO ()
chattyTry desc action =
  catchIO :: IO a -> (IOException -> IO a) -> IO acatchIO action :: IO ()action ($) :: (a -> b) -> a -> b$ \exception ->
    putStrLn :: String -> IO ()putStrLn ($) :: (a -> b) -> a -> b$ "Error while " (++) :: [a] -> [a] -> [a]++ desc :: Stringdesc (++) :: [a] -> [a] -> [a]++ ": " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow exception :: IOExceptionexception

-- -----------------------------------------------------------------------------
-- Helper functions

-- | Wraps text to the default line width. Existing newlines are preserved.
wrapText :: String -> String
wrapText = unlines :: [String] -> Stringunlines
         (.) :: (b -> c) -> (a -> b) -> a -> c. concatMap :: (a -> [b]) -> [a] -> [b]concatMap (map :: (a -> b) -> [a] -> [b]map unwords :: [String] -> Stringunwords
                    (.) :: (b -> c) -> (a -> b) -> a -> c. wrapLine :: Int -> [String] -> [[String]]wrapLine 79
                    (.) :: (b -> c) -> (a -> b) -> a -> c. words :: String -> [String]words)
         (.) :: (b -> c) -> (a -> b) -> a -> c. lines :: String -> [String]lines

-- | Wraps a list of words to a list of lines of words of a particular width.
wrapLine :: Int -> [String] -> [[String]]
wrapLine width = wrap :: Int -> [String] -> [String] -> [[String]]wrap 0 [] :: [a][]
  where wrap :: Int -> [String] -> [String] -> [[String]]
        wrap 0   []   (w:ws)
          | length :: [a] -> Intlength w :: Stringw (+) :: Num a => a -> a -> a+ 1 (>) :: Ord a => a -> a -> Bool> width :: Intwidth
          = wrap :: Int -> [String] -> [String] -> [[String]]wrap (length :: [a] -> Intlength w :: Stringw) [w :: Stringw] ws :: [String]ws
        wrap col line (w:ws)
          | col :: Intcol (+) :: Num a => a -> a -> a+ length :: [a] -> Intlength w :: Stringw (+) :: Num a => a -> a -> a+ 1 (>) :: Ord a => a -> a -> Bool> width :: Intwidth
          = reverse :: [a] -> [a]reverse line :: [String]line (:) :: a -> [a] -> [a]: wrap :: Int -> [String] -> [String] -> [[String]]wrap 0 [] :: [a][] (w :: Stringw(:) :: a -> [a] -> [a]:ws :: [String]ws)
        wrap col line (w:ws)
          = let col' = col :: Intcol (+) :: Num a => a -> a -> a+ length :: [a] -> Intlength w :: Stringw (+) :: Num a => a -> a -> a+ 1
             in wrap :: Int -> [String] -> [String] -> [[String]]wrap col' :: Intcol' (w :: Stringw(:) :: a -> [a] -> [a]:line :: [String]line) ws :: [String]ws
        wrap _ []   [] = [] :: [a][]
        wrap _ line [] = [reverse :: [a] -> [a]reverse line :: [String]line]

-- -----------------------------------------------------------------------------
-- rawSystem variants
maybeExit :: IO ExitCode -> IO ()
maybeExit cmd = do
  res <- cmd :: IO ExitCodecmd
  unless :: Monad m => Bool -> m () -> m ()unless (res :: Maybe FilePathres (==) :: Eq a => a -> a -> Bool== ExitSuccess :: ExitCodeExitSuccess) ($) :: (a -> b) -> a -> b$ exitWith :: ExitCode -> IO aexitWith res :: Maybe FilePathres

printRawCommandAndArgs :: Verbosity -> FilePath -> [String] -> IO ()
printRawCommandAndArgs verbosity path args
 | verbosity :: Verbosityverbosity (>=) :: Ord a => a -> a -> Bool>= deafening :: Verbositydeafening = print :: Show a => a -> IO ()print (path :: FilePathpath, args :: [String]args)
 | verbosity :: Verbosityverbosity (>=) :: Ord a => a -> a -> Bool>= verbose :: Verbosityverbose   = putStrLn :: String -> IO ()putStrLn ($) :: (a -> b) -> a -> b$ unwords :: [String] -> Stringunwords (path :: FilePathpath (:) :: a -> [a] -> [a]: args :: [String]args)
 | otherwise :: Boolotherwise              = return :: Monad m => forall a. a -> m areturn ()

printRawCommandAndArgsAndEnv :: Verbosity
                             -> FilePath
                             -> [String]
                             -> [(String, String)]
                             -> IO ()
printRawCommandAndArgsAndEnv verbosity path args env
 | verbosity :: Verbosityverbosity (>=) :: Ord a => a -> a -> Bool>= deafening :: Verbositydeafening = do putStrLn :: String -> IO ()putStrLn ("Environment: " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow env :: [(String, String)]env)
                               print :: Show a => a -> IO ()print (path :: FilePathpath, args :: [String]args)
 | verbosity :: Verbosityverbosity (>=) :: Ord a => a -> a -> Bool>= verbose :: Verbosityverbose   = putStrLn :: String -> IO ()putStrLn ($) :: (a -> b) -> a -> b$ unwords :: [String] -> Stringunwords (path :: FilePathpath (:) :: a -> [a] -> [a]: args :: [String]args)
 | otherwise :: Boolotherwise              = return :: Monad m => forall a. a -> m areturn ()

-- Exit with the same exitcode if the subcommand fails
rawSystemExit :: Verbosity -> FilePath -> [String] -> IO ()
rawSystemExit verbosity path args = do
  printRawCommandAndArgs ::
  Verbosity -> FilePath -> [String] -> IO ()printRawCommandAndArgs verbosity :: Verbosityverbosity path :: FilePathpath args :: [String]args
  hFlush :: Handle -> IO ()hFlush stdout :: Handlestdout
  exitcode <- rawSystem :: String -> [String] -> IO ExitCoderawSystem path :: FilePathpath args :: [String]args
  unless :: Monad m => Bool -> m () -> m ()unless (exitcode :: ExitCodeexitcode (==) :: Eq a => a -> a -> Bool== ExitSuccess :: ExitCodeExitSuccess) ($) :: (a -> b) -> a -> b$ do
    debug :: Verbosity -> String -> IO ()debug verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ path :: FilePathpath (++) :: [a] -> [a] -> [a]++ " returned " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow exitcode :: ExitCodeexitcode
    exitWith :: ExitCode -> IO aexitWith exitcode :: ExitCodeexitcode

rawSystemExitWithEnv :: Verbosity
                     -> FilePath
                     -> [String]
                     -> [(String, String)]
                     -> IO ()
rawSystemExitWithEnv verbosity path args env = do
    printRawCommandAndArgsAndEnv ::
  Verbosity -> FilePath -> [String] -> [(String, String)] -> IO ()printRawCommandAndArgsAndEnv verbosity :: Verbosityverbosity path :: FilePathpath args :: [String]args env :: [(String, String)]env
    hFlush :: Handle -> IO ()hFlush stdout :: Handlestdout
    ph <- runProcess ::
  FilePath
  -> [String]
  -> Maybe FilePath
  -> Maybe [(String, String)]
  -> Maybe Handle
  -> Maybe Handle
  -> Maybe Handle
  -> IO ProcessHandlerunProcess path :: FilePathpath args :: [String]args Nothing :: Maybe aNothing (Just :: a -> Maybe aJust env :: [(String, String)]env) Nothing :: Maybe aNothing Nothing :: Maybe aNothing Nothing :: Maybe aNothing
    exitcode <- waitForProcess :: ProcessHandle -> IO ExitCodewaitForProcess ph :: ProcessHandleph
    unless :: Monad m => Bool -> m () -> m ()unless (exitcode :: ExitCodeexitcode (==) :: Eq a => a -> a -> Bool== ExitSuccess :: ExitCodeExitSuccess) ($) :: (a -> b) -> a -> b$ do
        debug :: Verbosity -> String -> IO ()debug verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ path :: FilePathpath (++) :: [a] -> [a] -> [a]++ " returned " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow exitcode :: ExitCodeexitcode
        exitWith :: ExitCode -> IO aexitWith exitcode :: ExitCodeexitcode

-- | Run a command and return its output.
--
-- The output is assumed to be text in the locale encoding.
--
rawSystemStdout :: Verbosity -> FilePath -> [String] -> IO String
rawSystemStdout verbosity path args = do
  (output, errors, exitCode) <- rawSystemStdInOut ::
  Verbosity
  -> FilePath
  -> [String]
  -> Maybe (String, Bool)
  -> Bool
  -> IO (String, String, ExitCode)rawSystemStdInOut verbosity :: Verbosityverbosity path :: FilePathpath args :: [String]args
                                                  Nothing :: Maybe aNothing False :: BoolFalse
  when :: Monad m => Bool -> m () -> m ()when (exitCode :: ExitCodeexitCode (/=) :: Eq a => a -> a -> Bool/= ExitSuccess :: ExitCodeExitSuccess) ($) :: (a -> b) -> a -> b$
    die :: String -> IO adie errors :: Stringerrors
  return :: Monad m => forall a. a -> m areturn output :: Stringoutput

-- | Run a command and return its output, errors and exit status. Optionally
-- also supply some input. Also provides control over whether the binary/text
-- mode of the input and output.
--
rawSystemStdInOut :: Verbosity
                  -> FilePath -> [String]
                  -> Maybe (String, Bool) -- ^ input text and binary mode
                  -> Bool                 -- ^ output in binary mode
                  -> IO (String, String, ExitCode) -- ^ output, errors, exit
rawSystemStdInOut verbosity path args input outputBinary = do
  printRawCommandAndArgs ::
  Verbosity -> FilePath -> [String] -> IO ()printRawCommandAndArgs verbosity :: Verbosityverbosity path :: FilePathpath args :: [String]args

#ifdef __GLASGOW_HASKELL__
  bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO cException.bracket
     (runInteractiveProcess ::
  FilePath
  -> [String]
  -> Maybe FilePath
  -> Maybe [(String, String)]
  -> IO (Handle, Handle, Handle, ProcessHandle)runInteractiveProcess path :: FilePathpath args :: [String]args Nothing :: Maybe aNothing Nothing :: Maybe aNothing)
     (\(inh,outh,errh,_) -> hClose :: Handle -> IO ()hClose inh :: Handleinh (>>) :: Monad m => forall a b. m a -> m b -> m b>> hClose :: Handle -> IO ()hClose outh :: Handleouth (>>) :: Monad m => forall a b. m a -> m b -> m b>> hClose :: Handle -> IO ()hClose errh :: Handleerrh)
    ($) :: (a -> b) -> a -> b$ \(inh,outh,errh,pid) -> do

      -- output mode depends on what the caller wants
      hSetBinaryMode :: Handle -> Bool -> IO ()hSetBinaryMode outh :: Handleouth outputBinary :: BooloutputBinary
      -- but the errors are always assumed to be text (in the current locale)
      hSetBinaryMode :: Handle -> Bool -> IO ()hSetBinaryMode errh :: Handleerrh False :: BoolFalse

      -- fork off a couple threads to pull on the stderr and stdout
      -- so if the process writes to stderr we do not block.

      err <- hGetContents :: Handle -> IO StringhGetContents errh :: Handleerrh
      out <- hGetContents :: Handle -> IO StringhGetContents outh :: Handleouth

      mv <- newEmptyMVar :: IO (MVar a)newEmptyMVar
      let force str = (evaluate :: a -> IO aevaluate (length :: [a] -> Intlength str :: Stringstr) (>>) :: Monad m => forall a b. m a -> m b -> m b>> return :: Monad m => forall a. a -> m areturn ())
            finally :: IO a -> IO b -> IO a`Exception.finally` putMVar :: MVar a -> a -> IO ()putMVar mv :: MVar ()mv ()
          --TODO: handle exceptions like text decoding.
      _ <- forkIO :: IO () -> IO ThreadIdforkIO ($) :: (a -> b) -> a -> b$ force :: [a] -> IO ()force out :: Stringout
      _ <- forkIO :: IO () -> IO ThreadIdforkIO ($) :: (a -> b) -> a -> b$ force :: [a] -> IO ()force err :: IOErrorerr

      -- push all the input, if any
      case input :: Maybe (String, Bool)input of
        Nothing -> return :: Monad m => forall a. a -> m areturn ()
        Just (inputStr, inputBinary) -> do
                -- input mode depends on what the caller wants
          hSetBinaryMode :: Handle -> Bool -> IO ()hSetBinaryMode inh :: Handleinh inputBinary :: BoolinputBinary
          hPutStr :: Handle -> String -> IO ()hPutStr inh :: Handleinh inputStr :: StringinputStr
          hClose :: Handle -> IO ()hClose inh :: Handleinh
          --TODO: this probably fails if the process refuses to consume
          -- or if it closes stdin (eg if it exits)

      -- wait for both to finish, in either order
      takeMVar :: MVar a -> IO atakeMVar mv :: MVar ()mv
      takeMVar :: MVar a -> IO atakeMVar mv :: MVar ()mv

      -- wait for the program to terminate
      exitcode <- waitForProcess :: ProcessHandle -> IO ExitCodewaitForProcess pid :: ProcessHandlepid
      unless :: Monad m => Bool -> m () -> m ()unless (exitcode :: ExitCodeexitcode (==) :: Eq a => a -> a -> Bool== ExitSuccess :: ExitCodeExitSuccess) ($) :: (a -> b) -> a -> b$
        debug :: Verbosity -> String -> IO ()debug verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ path :: FilePathpath (++) :: [a] -> [a] -> [a]++ " returned " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow exitcode :: ExitCodeexitcode
                       (++) :: [a] -> [a] -> [a]++ if null :: [a] -> Boolnull err :: IOErrorerr then "" else
                          " with error message:\n" (++) :: [a] -> [a] -> [a]++ err :: IOErrorerr

      return :: Monad m => forall a. a -> m areturn (out :: Stringout, err :: IOErrorerr, exitcode :: ExitCodeexitcode)
#else
  tmpDir <- getTemporaryDirectory
  withTempFile tmpDir ".cmd.stdout" $ \outName outHandle ->
   withTempFile tmpDir ".cmd.stdin" $ \inName inHandle -> do
    hClose outHandle

    case input of
      Nothing -> return ()
      Just (inputStr, inputBinary) -> do
        hSetBinaryMode inHandle inputBinary
        hPutStr inHandle inputStr
    hClose inHandle

    let quote name = "'" ++ name ++ "'"
        cmd = unwords (map quote (path:args))
           ++ " <" ++ quote inName
           ++ " >" ++ quote outName
    exitcode <- system cmd

    unless (exitcode == ExitSuccess) $
      debug verbosity $ path ++ " returned " ++ show exitcode

    Exception.bracket (openFile outName ReadMode) hClose $ \hnd -> do
      hSetBinaryMode hnd outputBinary
      output <- hGetContents hnd
      length output `seq` return (output, "", exitcode)
#endif


-- | Look for a program on the path.
findProgramLocation :: Verbosity -> FilePath -> IO (Maybe FilePath)
findProgramLocation verbosity prog = do
  debug :: Verbosity -> String -> IO ()debug verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ "searching for " (++) :: [a] -> [a] -> [a]++ prog :: IO aprog (++) :: [a] -> [a] -> [a]++ " in path."
  res <- findExecutable :: String -> IO (Maybe FilePath)findExecutable prog :: IO aprog
  case res :: Maybe FilePathres of
      Nothing   -> debug :: Verbosity -> String -> IO ()debug verbosity :: Verbosityverbosity ("Cannot find " (++) :: [a] -> [a] -> [a]++ prog :: IO aprog (++) :: [a] -> [a] -> [a]++ " on the path")
      Just path -> debug :: Verbosity -> String -> IO ()debug verbosity :: Verbosityverbosity ("found " (++) :: [a] -> [a] -> [a]++ prog :: IO aprog (++) :: [a] -> [a] -> [a]++ " at "(++) :: [a] -> [a] -> [a]++ path :: FilePathpath)
  return :: Monad m => forall a. a -> m areturn res :: Maybe FilePathres


-- | Look for a program and try to find it's version number. It can accept
-- either an absolute path or the name of a program binary, in which case we
-- will look for the program on the path.
--
findProgramVersion :: String             -- ^ version args
                   -> (String -> String) -- ^ function to select version
                                         --   number from program output
                   -> Verbosity
                   -> FilePath           -- ^ location
                   -> IO (Maybe Version)
findProgramVersion versionArg selectVersion verbosity path = do
  str <- rawSystemStdout :: Verbosity -> FilePath -> [String] -> IO StringrawSystemStdout verbosity :: Verbosityverbosity path :: FilePathpath [versionArg :: StringversionArg]
         catchIO :: IO a -> (IOException -> IO a) -> IO a`catchIO`   (\_ -> return :: Monad m => forall a. a -> m areturn "")
         catchExit :: IO a -> (ExitCode -> IO a) -> IO a`catchExit` (\_ -> return :: Monad m => forall a. a -> m areturn "")
  let version :: Maybe Version
      version = simpleParse :: Text a => String -> Maybe asimpleParse (selectVersion :: String -> StringselectVersion str :: Stringstr)
  case version :: Maybe Versionversion of
      Nothing -> warn :: Verbosity -> String -> IO ()warn verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ "cannot determine version of " (++) :: [a] -> [a] -> [a]++ path :: FilePathpath
                               (++) :: [a] -> [a] -> [a]++ " :\n" (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow str :: Stringstr
      Just v  -> debug :: Verbosity -> String -> IO ()debug verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ path :: FilePathpath (++) :: [a] -> [a] -> [a]++ " is version " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay v :: Versionv
  return :: Monad m => forall a. a -> m areturn version :: Maybe Versionversion


-- | Like the unix xargs program. Useful for when we've got very long command
-- lines that might overflow an OS limit on command line length and so you
-- need to invoke a command multiple times to get all the args in.
--
-- Use it with either of the rawSystem variants above. For example:
--
-- > xargs (32*1024) (rawSystemExit verbosity) prog fixedArgs bigArgs
--
xargs :: Int -> ([String] -> IO ())
      -> [String] -> [String] -> IO ()
xargs maxSize rawSystemFun fixedArgs bigArgs =
  let fixedArgSize = sum :: Num a => [a] -> asum (map :: (a -> b) -> [a] -> [b]map length :: [a] -> Intlength fixedArgs :: [String]fixedArgs) (+) :: Num a => a -> a -> a+ length :: [a] -> Intlength fixedArgs :: [String]fixedArgs
      chunkSize = maxSize :: IntmaxSize (-) :: Num a => a -> a -> a- fixedArgSize :: IntfixedArgSize
   in mapM_ :: Monad m => (a -> m b) -> [a] -> m ()mapM_ (rawSystemFun :: [String] -> IO ()rawSystemFun (.) :: (b -> c) -> (a -> b) -> a -> c. (fixedArgs :: [String]fixedArgs (++) :: [a] -> [a] -> [a]++)) (chunks :: Int -> [[a]] -> [[[a]]]chunks chunkSize :: IntchunkSize bigArgs :: [String]bigArgs)

  where chunks len = unfoldr :: (b -> Maybe (a, b)) -> b -> [a]unfoldr ($) :: (a -> b) -> a -> b$ \s ->
          if null :: [a] -> Boolnull s :: [[a]]s then Nothing :: Maybe aNothing
                    else Just :: a -> Maybe aJust (chunk :: [[a]] -> Int -> [[a]] -> ([[a]], [[a]])chunk [] :: [a][] len :: Intlen s :: [[a]]s)

        chunk acc _   []     = (reverse :: [a] -> [a]reverse acc :: [[a]]acc,[] :: [a][])
        chunk acc len (s:ss)
          | len' :: Intlen' (<) :: Ord a => a -> a -> Bool< len :: Intlen = chunk :: [[a]] -> Int -> [[a]] -> ([[a]], [[a]])chunk (s :: [[a]]s(:) :: a -> [a] -> [a]:acc :: [[a]]acc) (len :: Intlen(-) :: Num a => a -> a -> a-len' :: Intlen'(-) :: Num a => a -> a -> a-1) ss :: [[a]]ss
          | otherwise :: Boolotherwise  = (reverse :: [a] -> [a]reverse acc :: [[a]]acc, s :: [[a]]s(:) :: a -> [a] -> [a]:ss :: [[a]]ss)
          where len' = length :: [a] -> Intlength s :: [[a]]s

-- ------------------------------------------------------------
-- * File Utilities
-- ------------------------------------------------------------

----------------
-- Finding files

-- | Find a file by looking in a search path. The file path must match exactly.
--
findFile :: [FilePath]    -- ^search locations
         -> FilePath      -- ^File Name
         -> IO FilePath
findFile searchPath fileName =
  findFirstFile :: (a -> FilePath) -> [a] -> IO (Maybe a)findFirstFile id :: a -> aid
    [ path :: FilePathpath (</>) :: FilePath -> FilePath -> FilePath</> fileName :: FilePathfileName
    | path <- nub :: Eq a => [a] -> [a]nub searchPath :: [FilePath]searchPath]
  (>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= maybe :: b -> (a -> b) -> Maybe a -> bmaybe (die :: String -> IO adie ($) :: (a -> b) -> a -> b$ fileName :: FilePathfileName (++) :: [a] -> [a] -> [a]++ " doesn't exist") return :: Monad m => forall a. a -> m areturn

-- | Find a file by looking in a search path with one of a list of possible
-- file extensions. The file base name should be given and it will be tried
-- with each of the extensions in each element of the search path.
--
findFileWithExtension :: [String]
                      -> [FilePath]
                      -> FilePath
                      -> IO (Maybe FilePath)
findFileWithExtension extensions searchPath baseName =
  findFirstFile :: (a -> FilePath) -> [a] -> IO (Maybe a)findFirstFile id :: a -> aid
    [ path :: FilePathpath (</>) :: FilePath -> FilePath -> FilePath</> baseName :: FilePathbaseName (<.>) :: FilePath -> String -> FilePath<.> ext :: Stringext
    | path <- nub :: Eq a => [a] -> [a]nub searchPath :: [FilePath]searchPath
    , ext <- nub :: Eq a => [a] -> [a]nub extensions :: [String]extensions ]

-- | Like 'findFileWithExtension' but returns which element of the search path
-- the file was found in, and the file path relative to that base directory.
--
findFileWithExtension' :: [String]
                       -> [FilePath]
                       -> FilePath
                       -> IO (Maybe (FilePath, FilePath))
findFileWithExtension' extensions searchPath baseName =
  findFirstFile :: (a -> FilePath) -> [a] -> IO (Maybe a)findFirstFile (uncurry :: (a -> b -> c) -> (a, b) -> cuncurry (</>) :: FilePath -> FilePath -> FilePath(</>))
    [ (path :: FilePathpath, baseName :: FilePathbaseName (<.>) :: FilePath -> String -> FilePath<.> ext :: Stringext)
    | path <- nub :: Eq a => [a] -> [a]nub searchPath :: [FilePath]searchPath
    , ext <- nub :: Eq a => [a] -> [a]nub extensions :: [String]extensions ]

findFirstFile :: (a -> FilePath) -> [a] -> IO (Maybe a)
findFirstFile file = findFirst :: [a] -> IO (Maybe a)findFirst
  where findFirst []     = return :: Monad m => forall a. a -> m areturn Nothing :: Maybe aNothing
        findFirst (x:xs) = do exists <- doesFileExist :: FilePath -> IO BooldoesFileExist (file :: FilePathfile x :: ax)
                              if exists :: Boolexists
                                then return :: Monad m => forall a. a -> m areturn (Just :: a -> Maybe aJust x :: ax)
                                else findFirst :: [a] -> IO (Maybe a)findFirst xs :: [a]xs

-- | Finds the files corresponding to a list of Haskell module names.
--
-- As 'findModuleFile' but for a list of module names.
--
findModuleFiles :: [FilePath]   -- ^ build prefix (location of objects)
                -> [String]     -- ^ search suffixes
                -> [ModuleName] -- ^ modules
                -> IO [(FilePath, FilePath)]
findModuleFiles searchPath extensions moduleNames =
  mapM :: Monad m => (a -> m b) -> [a] -> m [b]mapM (findModuleFile ::
  [FilePath] -> [String] -> ModuleName -> IO (FilePath, FilePath)findModuleFile searchPath :: [FilePath]searchPath extensions :: [String]extensions) moduleNames :: [ModuleName]moduleNames

-- | Find the file corresponding to a Haskell module name.
--
-- This is similar to 'findFileWithExtension'' but specialised to a module
-- name. The function fails if the file corresponding to the module is missing.
--
findModuleFile :: [FilePath]  -- ^ build prefix (location of objects)
               -> [String]    -- ^ search suffixes
               -> ModuleName  -- ^ module
               -> IO (FilePath, FilePath)
findModuleFile searchPath extensions moduleName =
      maybe :: b -> (a -> b) -> Maybe a -> bmaybe notFound :: IO anotFound return :: Monad m => forall a. a -> m areturn
  (=<<) :: Monad m => (a -> m b) -> m a -> m b=<< findFileWithExtension' ::
  [String]
  -> [FilePath]
  -> FilePath
  -> IO (Maybe (FilePath, FilePath))findFileWithExtension' extensions :: [String]extensions searchPath :: [FilePath]searchPath
                             (toFilePath :: ModuleName -> FilePathModuleName.toFilePath moduleName :: ModuleNamemoduleName)
  where
    notFound = die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "Error: Could not find module: " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay moduleName :: ModuleNamemoduleName
                  (++) :: [a] -> [a] -> [a]++ " with any suffix: " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow extensions :: [String]extensions
                  (++) :: [a] -> [a] -> [a]++ " in the search path: " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow searchPath :: [FilePath]searchPath

-- | List all the files in a directory and all subdirectories.
--
-- The order places files in sub-directories after all the files in their
-- parent directories. The list is generated lazily so is not well defined if
-- the source directory structure changes before the list is used.
--
getDirectoryContentsRecursive :: FilePath -> IO [FilePath]
getDirectoryContentsRecursive topdir = recurseDirectories :: [FilePath] -> IO [FilePath]recurseDirectories [""]
  where
    recurseDirectories :: [FilePath] -> IO [FilePath]
    recurseDirectories []         = return :: Monad m => forall a. a -> m areturn [] :: [a][]
    recurseDirectories (dir:dirs) = unsafeInterleaveIO :: IO a -> IO aunsafeInterleaveIO ($) :: (a -> b) -> a -> b$ do
      (files, dirs') <- collect ::
  [FilePath] -> [FilePath] -> [[Char]] -> IO ([FilePath], [FilePath])collect [] :: [a][] [] :: [a][] (=<<) :: Monad m => (a -> m b) -> m a -> m b=<< getDirectoryContents :: FilePath -> IO [FilePath]getDirectoryContents (topdir :: FilePathtopdir (</>) :: FilePath -> FilePath -> FilePath</> dir :: FilePathdir)
      files' <- recurseDirectories :: [FilePath] -> IO [FilePath]recurseDirectories (dirs' :: [FilePath]dirs' (++) :: [a] -> [a] -> [a]++ dirs :: [FilePath]dirs)
      return :: Monad m => forall a. a -> m areturn (files :: [FilePath]files (++) :: [a] -> [a] -> [a]++ files' :: [FilePath]files')

      where
        collect files dirs' []              = return :: Monad m => forall a. a -> m areturn (reverse :: [a] -> [a]reverse files :: [FilePath]files, reverse :: [a] -> [a]reverse dirs' :: [FilePath]dirs')
        collect files dirs' (entry:entries) | ignore :: [Char] -> Boolignore entry :: [Char]entry
                                            = collect ::
  [FilePath] -> [FilePath] -> [[Char]] -> IO ([FilePath], [FilePath])collect files :: [FilePath]files dirs' :: [FilePath]dirs' entries :: [[Char]]entries
        collect files dirs' (entry:entries) = do
          let dirEntry = dir :: FilePathdir (</>) :: FilePath -> FilePath -> FilePath</> entry :: [Char]entry
          isDirectory <- doesDirectoryExist :: FilePath -> IO BooldoesDirectoryExist (topdir :: FilePathtopdir (</>) :: FilePath -> FilePath -> FilePath</> dirEntry :: FilePathdirEntry)
          if isDirectory :: BoolisDirectory
            then collect ::
  [FilePath] -> [FilePath] -> [[Char]] -> IO ([FilePath], [FilePath])collect files :: [FilePath]files (dirEntry :: FilePathdirEntry(:) :: a -> [a] -> [a]:dirs' :: [FilePath]dirs') entries :: [[Char]]entries
            else collect ::
  [FilePath] -> [FilePath] -> [[Char]] -> IO ([FilePath], [FilePath])collect (dirEntry :: FilePathdirEntry(:) :: a -> [a] -> [a]:files :: [FilePath]files) dirs' :: [FilePath]dirs' entries :: [[Char]]entries

        ignore ['.']      = True :: BoolTrue
        ignore ['.', '.'] = True :: BoolTrue
        ignore _          = False :: BoolFalse

----------------
-- File globbing

data FileGlob
   -- | No glob at all, just an ordinary file
   = NoGlob FilePath

   -- | dir prefix and extension, like @\"foo\/bar\/\*.baz\"@ corresponds to
   --    @FileGlob \"foo\/bar\" \".baz\"@
   | FileGlob FilePath String

parseFileGlob :: FilePath -> Maybe FileGlob
parseFileGlob filepath = case splitExtensions :: FilePath -> (FilePath, String)splitExtensions filepath :: FilePathfilepath of
  (filepath', ext) -> case splitFileName :: FilePath -> (String, String)splitFileName filepath' :: FilePathfilepath' of
    (dir, "*") | '*' elem :: Eq a => a -> [a] -> Bool`elem` dir :: FilePathdir
              (||) :: Bool -> Bool -> Bool|| '*' elem :: Eq a => a -> [a] -> Bool`elem` ext :: Stringext
              (||) :: Bool -> Bool -> Bool|| null :: [a] -> Boolnull ext :: Stringext            -> Nothing :: Maybe aNothing
               | null :: [a] -> Boolnull dir :: FilePathdir            -> Just :: a -> Maybe aJust (FileGlob :: FilePath -> String -> FileGlobFileGlob "." ext :: Stringext)
               | otherwise :: Boolotherwise           -> Just :: a -> Maybe aJust (FileGlob :: FilePath -> String -> FileGlobFileGlob dir :: FilePathdir ext :: Stringext)
    _          | '*' elem :: Eq a => a -> [a] -> Bool`elem` filepath :: FilePathfilepath -> Nothing :: Maybe aNothing
               | otherwise :: Boolotherwise           -> Just :: a -> Maybe aJust (NoGlob :: FilePath -> FileGlobNoGlob filepath :: FilePathfilepath)

matchFileGlob :: FilePath -> IO [FilePath]
matchFileGlob = matchDirFileGlob :: FilePath -> FilePath -> IO [FilePath]matchDirFileGlob "."

matchDirFileGlob :: FilePath -> FilePath -> IO [FilePath]
matchDirFileGlob dir filepath = case parseFileGlob :: FilePath -> Maybe FileGlobparseFileGlob filepath :: FilePathfilepath of
  Nothing -> die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "invalid file glob '" (++) :: [a] -> [a] -> [a]++ filepath :: FilePathfilepath
                (++) :: [a] -> [a] -> [a]++ "'. Wildcards '*' are only allowed in place of the file"
                (++) :: [a] -> [a] -> [a]++ " name, not in the directory name or file extension."
                (++) :: [a] -> [a] -> [a]++ " If a wildcard is used it must be with an file extension."
  Just (NoGlob filepath') -> return :: Monad m => forall a. a -> m areturn [filepath' :: FilePathfilepath']
  Just (FileGlob dir' ext) -> do
    files <- getDirectoryContents :: FilePath -> IO [FilePath]getDirectoryContents (dir :: FilePathdir (</>) :: FilePath -> FilePath -> FilePath</> dir' :: FilePathdir')
    case   [ dir' :: FilePathdir' (</>) :: FilePath -> FilePath -> FilePath</> file :: FilePathfile
           | file <- files :: [FilePath]files
           , let (name, ext') = splitExtensions :: FilePath -> (FilePath, String)splitExtensions file :: FilePathfile
           , not :: Bool -> Boolnot (null :: [a] -> Boolnull name :: Stringname) (&&) :: Bool -> Bool -> Bool&& ext' :: Stringext' (==) :: Eq a => a -> a -> Bool== ext :: Stringext ] of
      []      -> die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "filepath wildcard '" (++) :: [a] -> [a] -> [a]++ filepath :: FilePathfilepath
                    (++) :: [a] -> [a] -> [a]++ "' does not match any files."
      matches -> return :: Monad m => forall a. a -> m areturn matches :: [FilePath]matches

----------------------------------------
-- Copying and installing files and dirs

-- | Same as 'createDirectoryIfMissing' but logs at higher verbosity levels.
--
createDirectoryIfMissingVerbose :: Verbosity
                                -> Bool     -- ^ Create its parents too?
                                -> FilePath
                                -> IO ()
createDirectoryIfMissingVerbose verbosity create_parents path0
  | create_parents :: Boolcreate_parents = createDirs :: [FilePath] -> IO ()createDirs (parents :: FilePath -> [FilePath]parents path0 :: FilePathpath0)
  | otherwise :: Boolotherwise      = createDirs :: [FilePath] -> IO ()createDirs (take :: Int -> [a] -> [a]take 1 (parents :: FilePath -> [FilePath]parents path0 :: FilePathpath0))
  where
    parents = reverse :: [a] -> [a]reverse (.) :: (b -> c) -> (a -> b) -> a -> c. scanl1 :: (a -> a -> a) -> [a] -> [a]scanl1 (</>) :: FilePath -> FilePath -> FilePath(</>) (.) :: (b -> c) -> (a -> b) -> a -> c. splitDirectories :: FilePath -> [FilePath]splitDirectories (.) :: (b -> c) -> (a -> b) -> a -> c. normalise :: FilePath -> FilePathnormalise

    createDirs []         = return :: Monad m => forall a. a -> m areturn ()
    createDirs (dir:[])   = createDir :: FilePath -> (IOException -> IO ()) -> IO ()createDir dir :: FilePathdir throwIOIO :: IOException -> IO athrowIOIO
    createDirs (dir:dirs) =
      createDir :: FilePath -> (IOException -> IO ()) -> IO ()createDir dir :: FilePathdir ($) :: (a -> b) -> a -> b$ \_ -> do
        createDirs :: [FilePath] -> IO ()createDirs dirs :: [FilePath]dirs
        createDir :: FilePath -> (IOException -> IO ()) -> IO ()createDir dir :: FilePathdir throwIOIO :: IOException -> IO athrowIOIO

    createDir :: FilePath -> (IOException -> IO ()) -> IO ()
    createDir dir notExistHandler = do
      r <- tryIO :: IO a -> IO (Either IOException a)tryIO ($) :: (a -> b) -> a -> b$ createDirectoryVerbose :: Verbosity -> FilePath -> IO ()createDirectoryVerbose verbosity :: Verbosityverbosity dir :: FilePathdir
      case (r :: Either IOException ()r :: Either IOException ()) of
        Right ()                   -> return :: Monad m => forall a. a -> m areturn ()
        Left  e
          | isDoesNotExistError :: IOError -> BoolisDoesNotExistError  e :: IOExceptione -> notExistHandler :: IOException -> IO ()notExistHandler e :: IOExceptione
          -- createDirectory (and indeed POSIX mkdir) does not distinguish
          -- between a dir already existing and a file already existing. So we
          -- check for it here. Unfortunately there is a slight race condition
          -- here, but we think it is benign. It could report an exeption in
          -- the case that the dir did exist but another process deletes the
          -- directory and creates a file in its place before we can check
          -- that the directory did indeed exist.
          | isAlreadyExistsError :: IOError -> BoolisAlreadyExistsError e :: IOExceptione -> (do
              isDir <- doesDirectoryExist :: FilePath -> IO BooldoesDirectoryExist dir :: FilePathdir
              if isDir :: BoolisDir then return :: Monad m => forall a. a -> m areturn ()
                       else throwIOIO :: IOException -> IO athrowIOIO e :: IOExceptione
              ) catchIO :: IO a -> (IOException -> IO a) -> IO a`catchIO` ((\_ -> return :: Monad m => forall a. a -> m areturn ()) :: IOException -> IO ())
          | otherwise :: Boolotherwise              -> throwIOIO :: IOException -> IO athrowIOIO e :: IOExceptione

createDirectoryVerbose :: Verbosity -> FilePath -> IO ()
createDirectoryVerbose verbosity dir = do
  info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ "creating " (++) :: [a] -> [a] -> [a]++ dir :: FilePathdir
  createDirectory :: FilePath -> IO ()createDirectory dir :: FilePathdir
  setDirOrdinary :: FilePath -> IO ()setDirOrdinary dir :: FilePathdir

-- | Copies a file without copying file permissions. The target file is created
-- with default permissions. Any existing target file is replaced.
--
-- At higher verbosity levels it logs an info message.
--
copyFileVerbose :: Verbosity -> FilePath -> FilePath -> IO ()
copyFileVerbose verbosity src dest = do
  info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ("copy " (++) :: [a] -> [a] -> [a]++ src :: FilePathsrc (++) :: [a] -> [a] -> [a]++ " to " (++) :: [a] -> [a] -> [a]++ dest :: FilePathdest)
  copyFile :: FilePath -> FilePath -> IO ()copyFile src :: FilePathsrc dest :: FilePathdest

-- | Install an ordinary file. This is like a file copy but the permissions
-- are set appropriately for an installed file. On Unix it is \"-rw-r--r--\"
-- while on Windows it uses the default permissions for the target directory.
--
installOrdinaryFile :: Verbosity -> FilePath -> FilePath -> IO ()
installOrdinaryFile verbosity src dest = do
  info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ("Installing " (++) :: [a] -> [a] -> [a]++ src :: FilePathsrc (++) :: [a] -> [a] -> [a]++ " to " (++) :: [a] -> [a] -> [a]++ dest :: FilePathdest)
  copyOrdinaryFile :: FilePath -> FilePath -> IO ()copyOrdinaryFile src :: FilePathsrc dest :: FilePathdest

-- | Install an executable file. This is like a file copy but the permissions
-- are set appropriately for an installed file. On Unix it is \"-rwxr-xr-x\"
-- while on Windows it uses the default permissions for the target directory.
--
installExecutableFile :: Verbosity -> FilePath -> FilePath -> IO ()
installExecutableFile verbosity src dest = do
  info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ("Installing executable " (++) :: [a] -> [a] -> [a]++ src :: FilePathsrc (++) :: [a] -> [a] -> [a]++ " to " (++) :: [a] -> [a] -> [a]++ dest :: FilePathdest)
  copyExecutableFile :: FilePath -> FilePath -> IO ()copyExecutableFile src :: FilePathsrc dest :: FilePathdest

-- | Copies a bunch of files to a target directory, preserving the directory
-- structure in the target location. The target directories are created if they
-- do not exist.
--
-- The files are identified by a pair of base directory and a path relative to
-- that base. It is only the relative part that is preserved in the
-- destination.
--
-- For example:
--
-- > copyFiles normal "dist/src"
-- >    [("", "src/Foo.hs"), ("dist/build/", "src/Bar.hs")]
--
-- This would copy \"src\/Foo.hs\" to \"dist\/src\/src\/Foo.hs\" and
-- copy \"dist\/build\/src\/Bar.hs\" to \"dist\/src\/src\/Bar.hs\".
--
-- This operation is not atomic. Any IO failure during the copy (including any
-- missing source files) leaves the target in an unknown state so it is best to
-- use it with a freshly created directory so that it can be simply deleted if
-- anything goes wrong.
--
copyFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
copyFiles verbosity targetDir srcFiles = do

  -- Create parent directories for everything
  let dirs = map :: (a -> b) -> [a] -> [b]map (targetDir :: FilePathtargetDir (</>) :: FilePath -> FilePath -> FilePath</>) (.) :: (b -> c) -> (a -> b) -> a -> c. nub :: Eq a => [a] -> [a]nub (.) :: (b -> c) -> (a -> b) -> a -> c. map :: (a -> b) -> [a] -> [b]map (takeDirectory :: FilePath -> FilePathtakeDirectory (.) :: (b -> c) -> (a -> b) -> a -> c. snd :: (a, b) -> bsnd) ($) :: (a -> b) -> a -> b$ srcFiles :: [FilePath]srcFiles
  mapM_ :: Monad m => (a -> m b) -> [a] -> m ()mapM_ (createDirectoryIfMissingVerbose ::
  Verbosity -> Bool -> FilePath -> IO ()createDirectoryIfMissingVerbose verbosity :: Verbosityverbosity True :: BoolTrue) dirs :: [FilePath]dirs

  -- Copy all the files
  sequence_ :: Monad m => [m a] -> m ()sequence_ [ let src  = srcBase :: FilePathsrcBase   (</>) :: FilePath -> FilePath -> FilePath</> srcFile :: FilePathsrcFile
                  dest = targetDir :: FilePathtargetDir (</>) :: FilePath -> FilePath -> FilePath</> srcFile :: FilePathsrcFile
               in copyFileVerbose :: Verbosity -> FilePath -> FilePath -> IO ()copyFileVerbose verbosity :: Verbosityverbosity src :: FilePathsrc dest :: FilePathdest
            | (srcBase, srcFile) <- srcFiles :: [FilePath]srcFiles ]

-- | This is like 'copyFiles' but uses 'installOrdinaryFile'.
--
installOrdinaryFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
installOrdinaryFiles verbosity targetDir srcFiles = do

  -- Create parent directories for everything
  let dirs = map :: (a -> b) -> [a] -> [b]map (targetDir :: FilePathtargetDir (</>) :: FilePath -> FilePath -> FilePath</>) (.) :: (b -> c) -> (a -> b) -> a -> c. nub :: Eq a => [a] -> [a]nub (.) :: (b -> c) -> (a -> b) -> a -> c. map :: (a -> b) -> [a] -> [b]map (takeDirectory :: FilePath -> FilePathtakeDirectory (.) :: (b -> c) -> (a -> b) -> a -> c. snd :: (a, b) -> bsnd) ($) :: (a -> b) -> a -> b$ srcFiles :: [FilePath]srcFiles
  mapM_ :: Monad m => (a -> m b) -> [a] -> m ()mapM_ (createDirectoryIfMissingVerbose ::
  Verbosity -> Bool -> FilePath -> IO ()createDirectoryIfMissingVerbose verbosity :: Verbosityverbosity True :: BoolTrue) dirs :: [FilePath]dirs

  -- Copy all the files
  sequence_ :: Monad m => [m a] -> m ()sequence_ [ let src  = srcBase :: FilePathsrcBase   (</>) :: FilePath -> FilePath -> FilePath</> srcFile :: FilePathsrcFile
                  dest = targetDir :: FilePathtargetDir (</>) :: FilePath -> FilePath -> FilePath</> srcFile :: FilePathsrcFile
               in installOrdinaryFile :: Verbosity -> FilePath -> FilePath -> IO ()installOrdinaryFile verbosity :: Verbosityverbosity src :: FilePathsrc dest :: FilePathdest
            | (srcBase, srcFile) <- srcFiles :: [FilePath]srcFiles ]

-- | This installs all the files in a directory to a target location,
-- preserving the directory layout. All the files are assumed to be ordinary
-- rather than executable files.
--
installDirectoryContents :: Verbosity -> FilePath -> FilePath -> IO ()
installDirectoryContents verbosity srcDir destDir = do
  info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ("copy directory '" (++) :: [a] -> [a] -> [a]++ srcDir :: FilePathsrcDir (++) :: [a] -> [a] -> [a]++ "' to '" (++) :: [a] -> [a] -> [a]++ destDir :: FilePathdestDir (++) :: [a] -> [a] -> [a]++ "'.")
  srcFiles <- getDirectoryContentsRecursive :: FilePath -> IO [FilePath]getDirectoryContentsRecursive srcDir :: FilePathsrcDir
  installOrdinaryFiles ::
  Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()installOrdinaryFiles verbosity :: Verbosityverbosity destDir :: FilePathdestDir [ (srcDir :: FilePathsrcDir, f :: FilePathf) | f <- srcFiles :: [FilePath]srcFiles ]

---------------------------------
-- Deprecated file copy functions

{-# DEPRECATED smartCopySources
      "Use findModuleFiles and copyFiles or installOrdinaryFiles" #-}
smartCopySources :: Verbosity -> [FilePath] -> FilePath
                 -> [ModuleName] -> [String] -> IO ()
smartCopySources verbosity searchPath targetDir moduleNames extensions =
      findModuleFiles ::
  [FilePath] -> [String] -> [ModuleName] -> IO [(FilePath, FilePath)]findModuleFiles searchPath :: [FilePath]searchPath extensions :: [String]extensions moduleNames :: [ModuleName]moduleNames
  (>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= copyFiles ::
  Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()copyFiles verbosity :: Verbosityverbosity targetDir :: FilePathtargetDir

{-# DEPRECATED copyDirectoryRecursiveVerbose
      "You probably want installDirectoryContents instead" #-}
copyDirectoryRecursiveVerbose :: Verbosity -> FilePath -> FilePath -> IO ()
copyDirectoryRecursiveVerbose verbosity srcDir destDir = do
  info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ("copy directory '" (++) :: [a] -> [a] -> [a]++ srcDir :: FilePathsrcDir (++) :: [a] -> [a] -> [a]++ "' to '" (++) :: [a] -> [a] -> [a]++ destDir :: FilePathdestDir (++) :: [a] -> [a] -> [a]++ "'.")
  srcFiles <- getDirectoryContentsRecursive :: FilePath -> IO [FilePath]getDirectoryContentsRecursive srcDir :: FilePathsrcDir
  copyFiles ::
  Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()copyFiles verbosity :: Verbosityverbosity destDir :: FilePathdestDir [ (srcDir :: FilePathsrcDir, f :: FilePathf) | f <- srcFiles :: [FilePath]srcFiles ]

---------------------------
-- Temporary files and dirs

-- | Use a temporary filename that doesn't already exist.
--
withTempFile :: FilePath -- ^ Temp dir to create the file in
             -> String   -- ^ File name template. See 'openTempFile'.
             -> (FilePath -> Handle -> IO a) -> IO a
withTempFile tmpDir template action =
  bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO cException.bracket
    (openTempFile :: FilePath -> String -> IO (FilePath, Handle)openTempFile tmpDir :: FilePathtmpDir template :: Stringtemplate)
    (\(name, handle) -> hClose :: Handle -> IO ()hClose handle :: IOError -> IO bhandle (>>) :: Monad m => forall a b. m a -> m b -> m b>> removeFile :: FilePath -> IO ()removeFile name :: Stringname)
    (uncurry :: (a -> b -> c) -> (a, b) -> cuncurry action :: IO ()action)

-- | Create and use a temporary directory.
--
-- Creates a new temporary directory inside the given directory, making use
-- of the template. The temp directory is deleted after use. For example:
--
-- > withTempDirectory verbosity "src" "sdist." $ \tmpDir -> do ...
--
-- The @tmpDir@ will be a new subdirectory of the given directory, e.g.
-- @src/sdist.342@.
--
withTempDirectory :: Verbosity -> FilePath -> String -> (FilePath -> IO a) -> IO a
withTempDirectory _verbosity targetDir template =
  bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO cException.bracket
    (createTempDirectory :: FilePath -> String -> IO FilePathcreateTempDirectory targetDir :: FilePathtargetDir template :: Stringtemplate)
    removeDirectoryRecursive :: FilePath -> IO ()(removeDirectoryRecursive :: FilePath -> IO ()removeDirectoryRecursive)

-----------------------------------
-- Safely reading and writing files

-- | Gets the contents of a file, but guarantee that it gets closed.
--
-- The file is read lazily but if it is not fully consumed by the action then
-- the remaining input is truncated and the file is closed.
--
withFileContents :: FilePath -> (String -> IO a) -> IO a
withFileContents name action =
  bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO cException.bracket (openFile :: FilePath -> IOMode -> IO HandleopenFile name :: Stringname ReadMode :: IOModeReadMode) hClose :: Handle -> IO ()hClose
                    (\hnd -> hGetContents :: Handle -> IO StringhGetContents hnd :: Handlehnd (>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= action :: IO ()action)

-- | Writes a file atomically.
--
-- The file is either written sucessfully or an IO exception is raised and
-- the original file is left unchanged.
--
-- On windows it is not possible to delete a file that is open by a process.
-- This case will give an IO exception but the atomic property is not affected.
--
writeFileAtomic :: FilePath -> String -> IO ()
writeFileAtomic targetFile content = do
  (tmpFile, tmpHandle) <- openNewBinaryFile :: FilePath -> String -> IO (FilePath, Handle)openNewBinaryFile targetDir :: FilePathtargetDir template :: Stringtemplate
  do  hPutStr :: Handle -> String -> IO ()hPutStr tmpHandle :: HandletmpHandle content :: Stringcontent
      hClose :: Handle -> IO ()hClose tmpHandle :: HandletmpHandle
      renameFile :: FilePath -> FilePath -> IO ()renameFile tmpFile :: FilePathtmpFile targetFile :: FilePathtargetFile
   onException :: IO a -> IO b -> IO a`onException` do hClose :: Handle -> IO ()hClose tmpHandle :: HandletmpHandle
                    removeFile :: FilePath -> IO ()removeFile tmpFile :: FilePathtmpFile
  where
    template = targetName :: StringtargetName (<.>) :: FilePath -> String -> FilePath<.> "tmp"
    targetDir | null :: [a] -> Boolnull targetDir_ :: StringtargetDir_ = currentDir :: FilePathcurrentDir
              | otherwise :: Boolotherwise       = targetDir_ :: StringtargetDir_
    --TODO: remove this when takeDirectory/splitFileName is fixed
    --      to always return a valid dir
    (targetDir_,targetName) = splitFileName :: FilePath -> (String, String)splitFileName targetFile :: FilePathtargetFile

-- | Write a file but only if it would have new content. If we would be writing
-- the same as the existing content then leave the file as is so that we do not
-- update the file's modification time.
--
rewriteFile :: FilePath -> String -> IO ()
rewriteFile path newContent =
  flip :: (a -> b -> c) -> b -> a -> cflip catchIO :: IO a -> (IOException -> IO a) -> IO acatchIO mightNotExist :: IOError -> IO ()mightNotExist ($) :: (a -> b) -> a -> b$ do
    existingContent <- readFile :: FilePath -> IO StringreadFile path :: FilePathpath
    _ <- evaluate :: a -> IO aevaluate (length :: [a] -> Intlength existingContent :: StringexistingContent)
    unless :: Monad m => Bool -> m () -> m ()unless (existingContent :: StringexistingContent (==) :: Eq a => a -> a -> Bool== newContent :: StringnewContent) ($) :: (a -> b) -> a -> b$
      writeFileAtomic :: FilePath -> String -> IO ()writeFileAtomic path :: FilePathpath newContent :: StringnewContent
  where
    mightNotExist e | isDoesNotExistError :: IOError -> BoolisDoesNotExistError e :: IOExceptione = writeFileAtomic :: FilePath -> String -> IO ()writeFileAtomic path :: FilePathpath newContent :: StringnewContent
                    | otherwise :: Boolotherwise             = ioError :: IOError -> IO aioError e :: IOExceptione

-- | The path name that represents the current directory.
-- In Unix, it's @\".\"@, but this is system-specific.
-- (E.g. AmigaOS uses the empty string @\"\"@ for the current directory.)
currentDir :: FilePath
currentDir = "."

-- ------------------------------------------------------------
-- * Finding the description file
-- ------------------------------------------------------------

-- |Package description file (/pkgname/@.cabal@)
defaultPackageDesc :: Verbosity -> IO FilePath
defaultPackageDesc _verbosity = findPackageDesc :: FilePath -> IO FilePathfindPackageDesc currentDir :: FilePathcurrentDir

-- |Find a package description file in the given directory.  Looks for
-- @.cabal@ files.
findPackageDesc :: FilePath    -- ^Where to look
                -> IO FilePath -- ^<pkgname>.cabal
findPackageDesc dir
 = do files <- getDirectoryContents :: FilePath -> IO [FilePath]getDirectoryContents dir :: FilePathdir
      -- to make sure we do not mistake a ~/.cabal/ dir for a <pkgname>.cabal
      -- file we filter to exclude dirs and null base file names:
      cabalFiles <- filterM :: Monad m => (a -> m Bool) -> [a] -> m [a]filterM doesFileExist :: FilePath -> IO BooldoesFileExist
                       [ dir :: FilePathdir (</>) :: FilePath -> FilePath -> FilePath</> file :: FilePathfile
                       | file <- files :: [FilePath]files
                       , let (name, ext) = splitExtension :: FilePath -> (String, String)splitExtension file :: FilePathfile
                       , not :: Bool -> Boolnot (null :: [a] -> Boolnull name :: Stringname) (&&) :: Bool -> Bool -> Bool&& ext :: Stringext (==) :: Eq a => a -> a -> Bool== ".cabal" ]
      case cabalFiles :: [FilePath]cabalFiles of
        []          -> noDesc :: IO anoDesc
        [cabalFile] -> return :: Monad m => forall a. a -> m areturn cabalFile :: FilePathcabalFile
        multiple    -> multiDesc :: [String] -> IO amultiDesc multiple :: [FilePath]multiple

  where
    noDesc :: IO a
    noDesc = die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "No cabal file found.\n"
                (++) :: [a] -> [a] -> [a]++ "Please create a package description file <pkgname>.cabal"

    multiDesc :: [String] -> IO a
    multiDesc l = die :: String -> IO adie ($) :: (a -> b) -> a -> b$ "Multiple cabal files found.\n"
                    (++) :: [a] -> [a] -> [a]++ "Please use only one of: "
                    (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow l :: [String]l

-- |Optional auxiliary package information file (/pkgname/@.buildinfo@)
defaultHookedPackageDesc :: IO (Maybe FilePath)
defaultHookedPackageDesc = findHookedPackageDesc :: FilePath -> IO (Maybe FilePath)findHookedPackageDesc currentDir :: FilePathcurrentDir

-- |Find auxiliary package information in the given directory.
-- Looks for @.buildinfo@ files.
findHookedPackageDesc
    :: FilePath                 -- ^Directory to search
    -> IO (Maybe FilePath)      -- ^/dir/@\/@/pkgname/@.buildinfo@, if present
findHookedPackageDesc dir = do
    files <- getDirectoryContents :: FilePath -> IO [FilePath]getDirectoryContents dir :: FilePathdir
    buildInfoFiles <- filterM :: Monad m => (a -> m Bool) -> [a] -> m [a]filterM doesFileExist :: FilePath -> IO BooldoesFileExist
                        [ dir :: FilePathdir (</>) :: FilePath -> FilePath -> FilePath</> file :: FilePathfile
                        | file <- files :: [FilePath]files
                        , let (name, ext) = splitExtension :: FilePath -> (String, String)splitExtension file :: FilePathfile
                        , not :: Bool -> Boolnot (null :: [a] -> Boolnull name :: Stringname) (&&) :: Bool -> Bool -> Bool&& ext :: Stringext (==) :: Eq a => a -> a -> Bool== buildInfoExt :: StringbuildInfoExt ]
    case buildInfoFiles :: [FilePath]buildInfoFiles of
        [] -> return :: Monad m => forall a. a -> m areturn Nothing :: Maybe aNothing
        [f] -> return :: Monad m => forall a. a -> m areturn (Just :: a -> Maybe aJust f :: FilePathf)
        _ -> die :: String -> IO adie ("Multiple files with extension " (++) :: [a] -> [a] -> [a]++ buildInfoExt :: StringbuildInfoExt)

buildInfoExt  :: String
buildInfoExt = ".buildinfo"

-- ------------------------------------------------------------
-- * Unicode stuff
-- ------------------------------------------------------------

-- This is a modification of the UTF8 code from gtk2hs and the
-- utf8-string package.

fromUTF8 :: String -> String
fromUTF8 []     = [] :: [a][]
fromUTF8 (c:cs)
  | c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\x7F' = c :: Charc (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs :: [Char]cs
  | c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\xBF' = replacementChar :: CharreplacementChar (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs :: [Char]cs
  | c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\xDF' = twoBytes :: Char -> [Char] -> [Char]twoBytes c :: Charc cs :: [Char]cs
  | c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\xEF' = moreBytes :: Int -> Int -> [Char] -> Int -> [Char]moreBytes 3 0x800     cs :: [Char]cs (ord :: Char -> Intord c :: Charc (.&.) :: Bits a => a -> a -> a.&. 0xF)
  | c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\xF7' = moreBytes :: Int -> Int -> [Char] -> Int -> [Char]moreBytes 4 0x10000   cs :: [Char]cs (ord :: Char -> Intord c :: Charc (.&.) :: Bits a => a -> a -> a.&. 0x7)
  | c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\xFB' = moreBytes :: Int -> Int -> [Char] -> Int -> [Char]moreBytes 5 0x200000  cs :: [Char]cs (ord :: Char -> Intord c :: Charc (.&.) :: Bits a => a -> a -> a.&. 0x3)
  | c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\xFD' = moreBytes :: Int -> Int -> [Char] -> Int -> [Char]moreBytes 6 0x4000000 cs :: [Char]cs (ord :: Char -> Intord c :: Charc (.&.) :: Bits a => a -> a -> a.&. 0x1)
  | otherwise :: Boolotherwise   = replacementChar :: CharreplacementChar (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs :: [Char]cs
  where
    twoBytes c0 (c1:cs')
      | ord :: Char -> Intord c1 :: Charc1 (.&.) :: Bits a => a -> a -> a.&. 0xC0 (==) :: Eq a => a -> a -> Bool== 0x80
      = let d = ((ord :: Char -> Intord c0 :: Charc0 (.&.) :: Bits a => a -> a -> a.&. 0x1F) shiftL :: Bits a => a -> Int -> a`shiftL` 6)
             (.|.) :: Bits a => a -> a -> a.|. (ord :: Char -> Intord c1 :: Charc1 (.&.) :: Bits a => a -> a -> a.&. 0x3F)
         in if d :: Intd (>=) :: Ord a => a -> a -> Bool>= 0x80
               then  chr :: Int -> Charchr d :: Intd           (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs' :: [Char]cs'
               else  replacementChar :: CharreplacementChar (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs' :: [Char]cs'
    twoBytes _ cs' = replacementChar :: CharreplacementChar (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs' :: [Char]cs'

    moreBytes :: Int -> Int -> [Char] -> Int -> [Char]
    moreBytes 1 overlong cs' acc
      | overlong :: Intoverlong (<=) :: Ord a => a -> a -> Bool<= acc :: [[a]]acc (&&) :: Bool -> Bool -> Bool&& acc :: [[a]]acc (<=) :: Ord a => a -> a -> Bool<= 0x10FFFF
     (&&) :: Bool -> Bool -> Bool&& (acc :: [[a]]acc (<) :: Ord a => a -> a -> Bool< 0xD800 (||) :: Bool -> Bool -> Bool|| 0xDFFF (<) :: Ord a => a -> a -> Bool< acc :: [[a]]acc)
     (&&) :: Bool -> Bool -> Bool&& (acc :: [[a]]acc (<) :: Ord a => a -> a -> Bool< 0xFFFE (||) :: Bool -> Bool -> Bool|| 0xFFFF (<) :: Ord a => a -> a -> Bool< acc :: [[a]]acc)
      = chr :: Int -> Charchr acc :: [[a]]acc (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs' :: [Char]cs'

      | otherwise :: Boolotherwise
      = replacementChar :: CharreplacementChar (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs' :: [Char]cs'

    moreBytes byteCount overlong (cn:cs') acc
      | ord :: Char -> Intord cn :: Charcn (.&.) :: Bits a => a -> a -> a.&. 0xC0 (==) :: Eq a => a -> a -> Bool== 0x80
      = moreBytes :: Int -> Int -> [Char] -> Int -> [Char]moreBytes (byteCount :: IntbyteCount(-) :: Num a => a -> a -> a-1) overlong :: Intoverlong cs' :: [Char]cs'
          ((acc :: [[a]]acc shiftL :: Bits a => a -> Int -> a`shiftL` 6) (.|.) :: Bits a => a -> a -> a.|. ord :: Char -> Intord cn :: Charcn (.&.) :: Bits a => a -> a -> a.&. 0x3F)

    moreBytes _ _ cs' _
      = replacementChar :: CharreplacementChar (:) :: a -> [a] -> [a]: fromUTF8 :: String -> StringfromUTF8 cs' :: [Char]cs'

    replacementChar = '\xfffd'

toUTF8 :: String -> String
toUTF8 []        = [] :: [a][]
toUTF8 (c:cs)
  | c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\x07F' = c :: Charc
                 (:) :: a -> [a] -> [a]: toUTF8 :: String -> StringtoUTF8 cs :: [Char]cs
  | c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\x7FF' = chr :: Int -> Charchr (0xC0 (.|.) :: Bits a => a -> a -> a.|. (w :: Stringw shiftR :: Bits a => a -> Int -> a`shiftR` 6))
                 (:) :: a -> [a] -> [a]: chr :: Int -> Charchr (0x80 (.|.) :: Bits a => a -> a -> a.|. (w :: Stringw (.&.) :: Bits a => a -> a -> a.&. 0x3F))
                 (:) :: a -> [a] -> [a]: toUTF8 :: String -> StringtoUTF8 cs :: [Char]cs
  | c :: Charc (<=) :: Ord a => a -> a -> Bool<= '\xFFFF'= chr :: Int -> Charchr (0xE0 (.|.) :: Bits a => a -> a -> a.|.  (w :: Stringw shiftR :: Bits a => a -> Int -> a`shiftR` 12))
                 (:) :: a -> [a] -> [a]: chr :: Int -> Charchr (0x80 (.|.) :: Bits a => a -> a -> a.|. ((w :: Stringw shiftR :: Bits a => a -> Int -> a`shiftR` 6)  (.&.) :: Bits a => a -> a -> a.&. 0x3F))
                 (:) :: a -> [a] -> [a]: chr :: Int -> Charchr (0x80 (.|.) :: Bits a => a -> a -> a.|.  (w :: Stringw (.&.) :: Bits a => a -> a -> a.&. 0x3F))
                 (:) :: a -> [a] -> [a]: toUTF8 :: String -> StringtoUTF8 cs :: [Char]cs
  | otherwise :: Boolotherwise    = chr :: Int -> Charchr (0xf0 (.|.) :: Bits a => a -> a -> a.|.  (w :: Stringw shiftR :: Bits a => a -> Int -> a`shiftR` 18))
                 (:) :: a -> [a] -> [a]: chr :: Int -> Charchr (0x80 (.|.) :: Bits a => a -> a -> a.|. ((w :: Stringw shiftR :: Bits a => a -> Int -> a`shiftR` 12)  (.&.) :: Bits a => a -> a -> a.&. 0x3F))
                 (:) :: a -> [a] -> [a]: chr :: Int -> Charchr (0x80 (.|.) :: Bits a => a -> a -> a.|. ((w :: Stringw shiftR :: Bits a => a -> Int -> a`shiftR` 6)  (.&.) :: Bits a => a -> a -> a.&. 0x3F))
                 (:) :: a -> [a] -> [a]: chr :: Int -> Charchr (0x80 (.|.) :: Bits a => a -> a -> a.|.  (w :: Stringw (.&.) :: Bits a => a -> a -> a.&. 0x3F))
                 (:) :: a -> [a] -> [a]: toUTF8 :: String -> StringtoUTF8 cs :: [Char]cs
  where w = ord :: Char -> Intord c :: Charc

-- | Ignore a Unicode byte order mark (BOM) at the beginning of the input
--
ignoreBOM :: String -> String
ignoreBOM ('\xFEFF':string) = string :: Stringstring
ignoreBOM string            = string :: Stringstring

-- | Reads a UTF8 encoded text file as a Unicode String
--
-- Reads lazily using ordinary 'readFile'.
--
readUTF8File :: FilePath -> IO String
readUTF8File f = fmap :: Functor f => forall a b. (a -> b) -> f a -> f bfmap (ignoreBOM :: String -> StringignoreBOM (.) :: (b -> c) -> (a -> b) -> a -> c. fromUTF8 :: String -> StringfromUTF8)
               (.) :: (b -> c) -> (a -> b) -> a -> c. hGetContents :: Handle -> IO StringhGetContents (=<<) :: Monad m => (a -> m b) -> m a -> m b=<< openBinaryFile :: FilePath -> IOMode -> IO HandleopenBinaryFile f :: FilePathf ReadMode :: IOModeReadMode

-- | Reads a UTF8 encoded text file as a Unicode String
--
-- Same behaviour as 'withFileContents'.
--
withUTF8FileContents :: FilePath -> (String -> IO a) -> IO a
withUTF8FileContents name action =
  bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO cException.bracket
    (openBinaryFile :: FilePath -> IOMode -> IO HandleopenBinaryFile name :: Stringname ReadMode :: IOModeReadMode)
    hClose :: Handle -> IO ()hClose
    (\hnd -> hGetContents :: Handle -> IO StringhGetContents hnd :: Handlehnd (>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= action :: IO ()action (.) :: (b -> c) -> (a -> b) -> a -> c. ignoreBOM :: String -> StringignoreBOM (.) :: (b -> c) -> (a -> b) -> a -> c. fromUTF8 :: String -> StringfromUTF8)

-- | Writes a Unicode String as a UTF8 encoded text file.
--
-- Uses 'writeFileAtomic', so provides the same guarantees.
--
writeUTF8File :: FilePath -> String -> IO ()
writeUTF8File path = writeFileAtomic :: FilePath -> String -> IO ()writeFileAtomic path :: FilePathpath (.) :: (b -> c) -> (a -> b) -> a -> c. toUTF8 :: String -> StringtoUTF8

-- | Fix different systems silly line ending conventions
normaliseLineEndings :: String -> String
normaliseLineEndings [] = [] :: [a][]
normaliseLineEndings ('\r':'\n':s) = '\n' (:) :: a -> [a] -> [a]: normaliseLineEndings :: String -> StringnormaliseLineEndings s :: [[a]]s -- windows
normaliseLineEndings ('\r':s)      = '\n' (:) :: a -> [a] -> [a]: normaliseLineEndings :: String -> StringnormaliseLineEndings s :: [[a]]s -- old osx
normaliseLineEndings (  c :s)      =   c :: Charc  (:) :: a -> [a] -> [a]: normaliseLineEndings :: String -> StringnormaliseLineEndings s :: [[a]]s

-- ------------------------------------------------------------
-- * Common utils
-- ------------------------------------------------------------

equating :: Eq a => (b -> a) -> b -> b -> Bool
equating p x y = p :: b -> ap x :: ax (==) :: Eq a => a -> a -> Bool== p :: b -> ap y :: by

comparing :: Ord a => (b -> a) -> b -> b -> Ordering
comparing p x y = p :: b -> ap x :: ax compare :: Ord a => a -> a -> Ordering`compare` p :: b -> ap y :: by

isInfixOf :: String -> String -> Bool
isInfixOf needle haystack = any :: (a -> Bool) -> [a] -> Boolany (isPrefixOf :: Eq a => [a] -> [a] -> BoolisPrefixOf needle :: Stringneedle) (tails :: [a] -> [[a]]tails haystack :: Stringhaystack)

intercalate :: [a] -> [[a]] -> [a]
intercalate sep = concat :: [[a]] -> [a]concat (.) :: (b -> c) -> (a -> b) -> a -> c. intersperse :: a -> [a] -> [a]intersperse sep :: [a]sep

lowercase :: String -> String
lowercase = map :: (a -> b) -> [a] -> [b]map toLower :: Char -> CharChar.toLower