Haskell Core Libraries (Cabal package)ContentsIndex
Distribution.Setup
PortabilityGHC, Hugs
Stabilityalpha
MaintainerIsaac Jones <ijones@syntaxpolice.org>
Description
Explanation: Data types and parser for the standard command-line setup. Will also return commands it doesn't know about.
Synopsis
data Action
= ConfigCmd ConfigFlags
| BuildCmd
| CleanCmd
| CopyCmd (Maybe FilePath)
| HaddockCmd
| ProgramaticaCmd
| InstallCmd Bool
| SDistCmd
| RegisterCmd Bool Bool
| UnregisterCmd Bool Bool
| HelpCmd
data ConfigFlags = ConfigFlags {
configHcFlavor :: (Maybe CompilerFlavor)
configHcPath :: (Maybe FilePath)
configHcPkg :: (Maybe FilePath)
configHaddock :: (Maybe FilePath)
configHappy :: (Maybe FilePath)
configAlex :: (Maybe FilePath)
configHsc2hs :: (Maybe FilePath)
configCpphs :: (Maybe FilePath)
configPrefix :: (Maybe FilePath)
configVerbose :: Int
configUser :: Bool
}
type CopyFlags = (Maybe FilePath, Int)
type InstallFlags = (Bool, Int)
type RegisterFlags = (Bool, Bool, Int)
data CompilerFlavor
= GHC
| NHC
| Hugs
| HBC
| Helium
| OtherCompiler String
data Compiler = Compiler {
compilerFlavor :: CompilerFlavor
compilerVersion :: Version
compilerPath :: FilePath
compilerPkgTool :: FilePath
}
parseGlobalArgs :: [String] -> IO (Action, [String])
parseConfigureArgs :: ConfigFlags -> [String] -> [OptDescr a] -> IO (ConfigFlags, [a], [String])
parseBuildArgs :: [String] -> [OptDescr a] -> IO (Int, [a], [String])
parseCleanArgs :: [String] -> [OptDescr a] -> IO (Int, [a], [String])
parseHaddockArgs :: [String] -> [OptDescr a] -> IO (Int, [a], [String])
parseProgramaticaArgs :: [String] -> [OptDescr a] -> IO (Int, [a], [String])
parseInstallArgs :: InstallFlags -> [String] -> [OptDescr a] -> IO (InstallFlags, [a], [String])
parseSDistArgs :: [String] -> [OptDescr a] -> IO (Int, [a], [String])
parseRegisterArgs :: RegisterFlags -> [String] -> [OptDescr a] -> IO (RegisterFlags, [a], [String])
parseUnregisterArgs :: RegisterFlags -> [String] -> [OptDescr a] -> IO (RegisterFlags, [a], [String])
parseCopyArgs :: CopyFlags -> [String] -> [OptDescr a] -> IO (CopyFlags, [a], [String])
Documentation
data Action
Constructors
ConfigCmd ConfigFlags
BuildCmd
CleanCmd
CopyCmd (Maybe FilePath)
HaddockCmd
ProgramaticaCmd
InstallCmd Bool
SDistCmd
RegisterCmd Bool Bool
UnregisterCmd Bool Bool
HelpCmd
show/hide Instances
data ConfigFlags
Flags to configure command
Constructors
ConfigFlags
configHcFlavor :: (Maybe CompilerFlavor)
configHcPath :: (Maybe FilePath)given compiler location
configHcPkg :: (Maybe FilePath)given hc-pkg location
configHaddock :: (Maybe FilePath)Haddock path
configHappy :: (Maybe FilePath)Happy path
configAlex :: (Maybe FilePath)Alex path
configHsc2hs :: (Maybe FilePath)Hsc2hs path
configCpphs :: (Maybe FilePath)Cpphs path
configPrefix :: (Maybe FilePath)installation prefix
configVerbose :: Intverbosity level
configUser :: Bool
  • -user flag?
show/hide Instances
type CopyFlags = (Maybe FilePath, Int)
Flags to copy: (Copy Location, verbose)
type InstallFlags = (Bool, Int)
Flags to install: (user package, verbose)
type RegisterFlags = (Bool, Bool, Int)
Flags to register and unregister: (user package, gen-script, verbose)
data CompilerFlavor
Constructors
GHC
NHC
Hugs
HBC
Helium
OtherCompiler String
show/hide Instances
data Compiler
Constructors
Compiler
compilerFlavor :: CompilerFlavor
compilerVersion :: Version
compilerPath :: FilePath
compilerPkgTool :: FilePath
show/hide Instances
parseGlobalArgs :: [String] -> IO (Action, [String])
parseConfigureArgs :: ConfigFlags -> [String] -> [OptDescr a] -> IO (ConfigFlags, [a], [String])
parseBuildArgs :: [String] -> [OptDescr a] -> IO (Int, [a], [String])
parseCleanArgs :: [String] -> [OptDescr a] -> IO (Int, [a], [String])
parseHaddockArgs :: [String] -> [OptDescr a] -> IO (Int, [a], [String])
parseProgramaticaArgs :: [String] -> [OptDescr a] -> IO (Int, [a], [String])
parseInstallArgs :: InstallFlags -> [String] -> [OptDescr a] -> IO (InstallFlags, [a], [String])
parseSDistArgs :: [String] -> [OptDescr a] -> IO (Int, [a], [String])
parseRegisterArgs :: RegisterFlags -> [String] -> [OptDescr a] -> IO (RegisterFlags, [a], [String])
parseUnregisterArgs :: RegisterFlags -> [String] -> [OptDescr a] -> IO (RegisterFlags, [a], [String])
parseCopyArgs :: CopyFlags -> [String] -> [OptDescr a] -> IO (CopyFlags, [a], [String])
Produced by Haddock version 0.7