Cabal-1.1.6: A framework for packaging Haskell softwareContentsIndex
Distribution.Program
Synopsis
data Program = Program {
programName :: String
programBinName :: String
programArgs :: [String]
programLocation :: ProgramLocation
}
data ProgramLocation
= EmptyLocation
| UserSpecified FilePath
| FoundOnSystem FilePath
data ProgramConfiguration = ProgramConfiguration (Map String Program)
withProgramFlag :: Program -> String
programOptsFlag :: Program -> String
programOptsField :: Program -> String
defaultProgramConfiguration :: ProgramConfiguration
updateProgram :: Maybe Program -> ProgramConfiguration -> ProgramConfiguration
userSpecifyPath :: String -> FilePath -> ProgramConfiguration -> ProgramConfiguration
userSpecifyArgs :: String -> String -> ProgramConfiguration -> ProgramConfiguration
lookupProgram :: String -> ProgramConfiguration -> IO (Maybe Program)
lookupPrograms :: ProgramConfiguration -> IO [(String, Maybe Program)]
rawSystemProgram :: Int -> Program -> [String] -> IO ()
rawSystemProgramConf :: Int -> String -> ProgramConfiguration -> [String] -> IO ()
simpleProgram :: String -> Program
ghcProgram :: Program
ghcPkgProgram :: Program
nhcProgram :: Program
jhcProgram :: Program
hugsProgram :: Program
ranlibProgram :: Program
arProgram :: Program
alexProgram :: Program
hsc2hsProgram :: Program
c2hsProgram :: Program
cpphsProgram :: Program
haddockProgram :: Program
greencardProgram :: Program
ldProgram :: Program
cppProgram :: Program
pfesetupProgram :: Program
Documentation
data Program
Represents a program which cabal may call.
Constructors
Program
programName :: StringThe simple name of the program, eg ghc
programBinName :: StringThe name of this program's binary, eg ghc-6.4
programArgs :: [String]Default command-line args for this program
programLocation :: ProgramLocationLocation of the program. eg. /usr/bin/ghc-6.4
show/hide Instances
data ProgramLocation
Similar to Maybe, but tells us whether it's specifed by user or not. This includes not just the path, but the program as well.
Constructors
EmptyLocation
UserSpecified FilePath
FoundOnSystem FilePath
show/hide Instances
data ProgramConfiguration
Constructors
ProgramConfiguration (Map String Program)
show/hide Instances
withProgramFlag :: Program -> String
The flag for giving a path to this program. eg --with-alex=/usr/bin/alex
programOptsFlag :: Program -> String
The flag for giving args for this program. eg --haddock-options=-s http://foo
programOptsField :: Program -> String
The foo.cabal field for giving args for this program. eg haddock-options: -s http://foo
defaultProgramConfiguration :: ProgramConfiguration
The default list of programs and their arguments. These programs are typically used internally to Cabal.
updateProgram :: Maybe Program -> ProgramConfiguration -> ProgramConfiguration
Update this program's entry in the configuration. No changes if you pass in Nothing.
userSpecifyPath
:: StringProgram name
-> FilePathuser-specified path to filename
-> ProgramConfiguration
-> ProgramConfiguration
User-specify this path. Basically override any path information for this program in the configuration. If it's not a known program, add it.
userSpecifyArgs
:: StringProgram name
-> Stringuser-specified args
-> ProgramConfiguration
-> ProgramConfiguration
User-specify the arguments for this program. Basically override any args information for this program in the configuration. If it's not a known program, add it.
lookupProgram :: String -> ProgramConfiguration -> IO (Maybe Program)
Looks up a program in the given configuration. If there's no location information in the configuration, then we use IO to look on the system in PATH for the program. If the program is not in the configuration at all, we return Nothing. FIX: should we build a simpleProgram in that case? Do we want a way to specify NOT to find it on the system (populate programLocation).
lookupPrograms :: ProgramConfiguration -> IO [(String, Maybe Program)]
rawSystemProgram
:: IntVerbosity
-> ProgramThe program to run
-> [String]Any extra arguments to add
-> IO ()
Runs the given program.
rawSystemProgramConf
:: Intverbosity
-> StringThe name of the program to run
-> ProgramConfigurationlook up the program here
-> [String]Any extra arguments to add
-> IO ()
simpleProgram :: String -> Program
ghcProgram :: Program
ghcPkgProgram :: Program
nhcProgram :: Program
jhcProgram :: Program
hugsProgram :: Program
ranlibProgram :: Program
arProgram :: Program
alexProgram :: Program
hsc2hsProgram :: Program
c2hsProgram :: Program
cpphsProgram :: Program
haddockProgram :: Program
greencardProgram :: Program
ldProgram :: Program
cppProgram :: Program
pfesetupProgram :: Program
Produced by Haddock version 0.8