module Distribution.Simple.Program (
Program(..)
, ProgramSearchPath
, ProgramSearchPathEntry(..)
, simpleProgram
, findProgramLocation
, findProgramVersion
, ConfiguredProgram(..)
, programPath
, ProgArg
, ProgramLocation(..)
, runProgram
, getProgramOutput
, suppressOverrideArgs
, ProgramInvocation(..)
, emptyProgramInvocation
, simpleProgramInvocation
, programInvocation
, runProgramInvocation
, getProgramInvocationOutput
, builtinPrograms
, ProgramConfiguration
, emptyProgramConfiguration
, defaultProgramConfiguration
, restoreProgramConfiguration
, addKnownProgram
, addKnownPrograms
, lookupKnownProgram
, knownPrograms
, getProgramSearchPath
, setProgramSearchPath
, userSpecifyPath
, userSpecifyPaths
, userMaybeSpecifyPath
, userSpecifyArgs
, userSpecifyArgss
, userSpecifiedArgs
, lookupProgram
, updateProgram
, configureProgram
, configureAllKnownPrograms
, reconfigurePrograms
, requireProgram
, requireProgramVersion
, runDbProgram
, getDbProgramOutput
, ghcProgram
, ghcPkgProgram
, lhcProgram
, lhcPkgProgram
, nhcProgram
, hmakeProgram
, jhcProgram
, hugsProgram
, ffihugsProgram
, uhcProgram
, gccProgram
, ranlibProgram
, arProgram
, stripProgram
, happyProgram
, alexProgram
, hsc2hsProgram
, c2hsProgram
, cpphsProgram
, hscolourProgram
, haddockProgram
, greencardProgram
, ldProgram
, tarProgram
, cppProgram
, pkgConfigProgram
, hpcProgram
, rawSystemProgram
, rawSystemProgramStdout
, rawSystemProgramConf
, rawSystemProgramStdoutConf
, findProgramOnPath
) where
import Distribution.Simple.Program.Types
import Distribution.Simple.Program.Run
import Distribution.Simple.Program.Db
import Distribution.Simple.Program.Builtin
import Distribution.Simple.Utils
( die, findProgramLocation, findProgramVersion )
import Distribution.Verbosity
( Verbosity )
runProgram :: Verbosity
-> ConfiguredProgram
-> [ProgArg]
-> IO ()
runProgram verbosity prog args =
runProgramInvocation verbosity (programInvocation prog args)
getProgramOutput :: Verbosity
-> ConfiguredProgram
-> [ProgArg]
-> IO String
getProgramOutput verbosity prog args =
getProgramInvocationOutput verbosity (programInvocation prog args)
runDbProgram :: Verbosity
-> Program
-> ProgramDb
-> [ProgArg]
-> IO ()
runDbProgram verbosity prog programDb args =
case lookupProgram prog programDb of
Nothing -> die notFound
Just configuredProg -> runProgram verbosity configuredProg args
where
notFound = "The program " ++ programName prog
++ " is required but it could not be found"
getDbProgramOutput :: Verbosity
-> Program
-> ProgramDb
-> [ProgArg]
-> IO String
getDbProgramOutput verbosity prog programDb args =
case lookupProgram prog programDb of
Nothing -> die notFound
Just configuredProg -> getProgramOutput verbosity configuredProg args
where
notFound = "The program " ++ programName prog
++ " is required but it could not be found"
rawSystemProgram :: Verbosity -> ConfiguredProgram
-> [ProgArg] -> IO ()
rawSystemProgram = runProgram
rawSystemProgramStdout :: Verbosity -> ConfiguredProgram
-> [ProgArg] -> IO String
rawSystemProgramStdout = getProgramOutput
rawSystemProgramConf :: Verbosity -> Program -> ProgramConfiguration
-> [ProgArg] -> IO ()
rawSystemProgramConf = runDbProgram
rawSystemProgramStdoutConf :: Verbosity -> Program -> ProgramConfiguration
-> [ProgArg] -> IO String
rawSystemProgramStdoutConf = getDbProgramOutput
type ProgramConfiguration = ProgramDb
emptyProgramConfiguration, defaultProgramConfiguration :: ProgramConfiguration
emptyProgramConfiguration = emptyProgramDb
defaultProgramConfiguration = defaultProgramDb
restoreProgramConfiguration :: [Program] -> ProgramConfiguration
-> ProgramConfiguration
restoreProgramConfiguration = restoreProgramDb
findProgramOnPath :: String -> Verbosity -> IO (Maybe FilePath)
findProgramOnPath = flip findProgramLocation