| Safe Haskell | None |
|---|
Test.Sunlight
Contents
- data InstallResult = InstallResult {}
- installDeps :: [PackageIdentifier] -> FilePath -> FilePath -> FilePath -> FilePath -> FilePath -> IO InstallResult
- constraint :: PackageIdentifier -> String
- data PackageInstResult = PackageInstResult {}
- installPackage :: FilePath -> FilePath -> FilePath -> FilePath -> IO PackageInstResult
- testPackage :: [(String, [String])] -> IO [CmdResult]
- data InstallAndTestResult = InstallAndTestResult {}
- installAndTest :: [PackageIdentifier] -> UTCTime -> FilePath -> FilePath -> FilePath -> [(String, [String])] -> IO InstallAndTestResult
- lowestVersions :: GenericPackageDescription -> Either Dependency [PackageIdentifier]
- getDepsList :: GenericPackageDescription -> (GenericPackageDescription -> [(a, CondTree b [Dependency] c)]) -> [Dependency]
- getDependencies :: CondTree v [Dependency] a -> [Dependency]
- lowestVersion :: Dependency -> Either Dependency PackageIdentifier
- testLowestVersions :: UTCTime -> FilePath -> FilePath -> FilePath -> [(String, [String])] -> GenericPackageDescription -> Either Dependency (IO InstallAndTestResult)
- testDefaultVersions :: UTCTime -> FilePath -> FilePath -> FilePath -> [(String, [String])] -> IO InstallAndTestResult
- testMultipleVersions :: UTCTime -> (FilePath, FilePath) -> [(FilePath, FilePath)] -> FilePath -> [(String, [String])] -> GenericPackageDescription -> Either Dependency (IO (InstallAndTestResult, [InstallAndTestResult]))
- versionsReport :: ByteString -> Compiler -> Description -> UTCTime -> InstallAndTestResult -> ByteString
- minimumVersionsReport :: Compiler -> Description -> UTCTime -> InstallAndTestResult -> ByteString
- writeMinimumVersionsReport :: ByteString -> IO ()
- currentVersionsReport :: UTCTime -> [(Description, Compiler, a)] -> [InstallAndTestResult] -> Maybe ByteString
- writeCurrentVersionsReport :: ByteString -> IO ()
- randomString :: IO String
- makeResultFile :: UTCTime -> String -> String -> String -> InstallAndTestResult -> IO ()
- resultDirectory :: UTCTime -> String -> String
- type Description = String
- type Compiler = String
- type GhcPkg = String
- type Cabal = String
- data TestInputs = TestInputs {
- tiDescription :: Maybe GenericPackageDescription
- tiCabal :: Cabal
- tiLowest :: (Description, Compiler, GhcPkg)
- tiDefault :: [(Description, Compiler, GhcPkg)]
- tiTest :: [(String, [String])]
- runTests :: TestInputs -> IO ()
- dependencyError :: Dependency -> IO a
Documentation
data InstallResult Source
Result from installing the package's dependencies.
Constructors
| InstallResult | |
Instances
current directory has the unpacked tarball.
dependencies are fully or partially installed. If partially
Arguments
| :: [PackageIdentifier] | Optional constraints. Currently constraints may only be tied to specific versions (for instance, flag constraints or constraints tied to a range of versions are not allowed.) |
| -> FilePath | Install using this compiler (full path to compiler). |
| -> FilePath | Full path to ghc-pkg. |
| -> FilePath | Path to cabal executable |
| -> FilePath | Path to directory to use for user package DB. |
| -> FilePath | Directory to use for installation prefix |
| -> IO InstallResult |
constraint :: PackageIdentifier -> StringSource
Makes a PackageIdentifier into a version constraint option.
data PackageInstResult Source
Constructors
| PackageInstResult | |
Arguments
| :: FilePath | Install using this compiler (full path to compiler) |
| -> FilePath | Full path to ghc-pkg |
| -> FilePath | User DB |
| -> FilePath | Installation prefix |
| -> IO PackageInstResult |
Install a package.
Preconditions:
- dependencies have already been installed at the given prefix and registered in the given db
- current directory has the unpacked tarball.
Side effects:
- package should be installed, or exit code is non-zero
Arguments
| :: [(String, [String])] | From the package root directory, these are the commands and arguments to run to test the package. |
| -> IO [CmdResult] |
Test a package.
Preconditions:
- Package has already been built.
data InstallAndTestResult Source
Constructors
| InstallAndTestResult | |
Fields
| |
Arguments
| :: [PackageIdentifier] | Constraints |
| -> UTCTime | |
| -> FilePath | Path to compiler |
| -> FilePath | Path to ghc-pkg |
| -> FilePath | Path to cabal executable |
| -> [(String, [String])] | How to test the package |
| -> IO InstallAndTestResult |
Performs test installation.
Preconditions:
- is run from root package directory. A temporary directory is created inside this directory. All work is done within the temporary directory.
Postconditions:
- cleans up after itself; no temporary files should remain.
Arguments
| :: GenericPackageDescription | |
| -> Either Dependency [PackageIdentifier] | Left with the bad dependency if there is one; Right otherwise. |
Gets a list of PackageIdentifier with the lowest possible versions. Fails if a package has a dependency range with no minimum.
getDepsList :: GenericPackageDescription -> (GenericPackageDescription -> [(a, CondTree b [Dependency] c)]) -> [Dependency]Source
getDependencies :: CondTree v [Dependency] a -> [Dependency]Source
lowestVersion :: Dependency -> Either Dependency PackageIdentifierSource
Arguments
| :: UTCTime | |
| -> (FilePath, FilePath) | Compiler and ghc-pkg to use when testing lowest version |
| -> [(FilePath, FilePath)] | Compilers and ghc-pkg to use to test default versions |
| -> FilePath | Path to cabal executable |
| -> [(String, [String])] | How to test package |
| -> GenericPackageDescription | |
| -> Either Dependency (IO (InstallAndTestResult, [InstallAndTestResult])) |
Arguments
| :: ByteString | Description of dependencies |
| -> Compiler | |
| -> Description | |
| -> UTCTime | |
| -> InstallAndTestResult | |
| -> ByteString |
minimumVersionsReport :: Compiler -> Description -> UTCTime -> InstallAndTestResult -> ByteStringSource
writeMinimumVersionsReport :: ByteString -> IO ()Source
currentVersionsReport :: UTCTime -> [(Description, Compiler, a)] -> [InstallAndTestResult] -> Maybe ByteStringSource
writeCurrentVersionsReport :: ByteString -> IO ()Source
randomString :: IO StringSource
Gets four-character random string.
type Description = StringSource
A description for this compiler version. This will be used in
the directory name in the tree that is written to disk. I simply
use a compiler version, such as 7.4.
Path to GHC compiler. You can use a full path name or, if you use just an executable name, the PATH will be searched.
Path to ghc-pkg. If you use just an executable name, the PATH will be searched.
Path to cabal executable. Used to install package dependencies. If you use just an executable name, the PATH will be searched.
data TestInputs Source
Constructors
| TestInputs | |
Fields
| |
Instances
runTests :: TestInputs -> IO ()Source
dependencyError :: Dependency -> IO aSource