sunlight-0.2.0.0: Test Cabalized package against multiple dependency versions

Safe HaskellNone

Test.Sunlight

Contents

Synopsis

Documentation

data InstallResult Source

Result from installing the package's dependencies.

Constructors

InstallResult 

current directory has the unpacked tarball.

dependencies are fully or partially installed. If partially

installDepsSource

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.

installPackageSource

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

testPackageSource

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

itDate :: UTCTime

Current time

itGhcVersion :: CmdResult

Result of ghc --version

itPkgVersion :: CmdResult

Result of ghc-pkg --version

itCabalVersion :: CmdResult

Result of cabal --version

itCompileSetup :: CmdResult

Result from compiling Setup.hs

itSdistDeps :: CmdResult

Result from running sdist to create tree from which to install dependencies

itSdistPkg :: CmdResult

Result from running sdist to create tree from which to install package

itInit :: CmdResult

Result from initializing user package DB

itDeps :: InstallResult
 
itPackage :: PackageInstResult
 
itTest :: [CmdResult]
 

installAndTestSource

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.

lowestVersionsSource

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

testLowestVersionsSource

Arguments

:: UTCTime 
-> FilePath

Path to compiler

-> FilePath

Path to ghc-pkg

-> FilePath

Path to cabal executable

-> [(String, [String])]

How to test the package

-> GenericPackageDescription 
-> Either Dependency (IO InstallAndTestResult) 

testDefaultVersionsSource

Arguments

:: UTCTime 
-> FilePath

Path to compiler

-> FilePath

Path to ghc-pkg

-> FilePath

Path to cabal executable

-> [(String, [String])]

How to test the package

-> IO InstallAndTestResult 

testMultipleVersionsSource

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])) 

versionsReportSource

Arguments

:: ByteString

Description of dependencies

-> Compiler 
-> Description 
-> UTCTime 
-> InstallAndTestResult 
-> ByteString 

randomString :: IO StringSource

Gets four-character random string.

makeResultFileSource

Arguments

:: UTCTime 
-> String

Random string

-> String

Description string, e.g. lowest or current

-> String

Compiler version description

-> InstallAndTestResult 
-> IO () 

resultDirectorySource

Arguments

:: UTCTime 
-> String

Random string

-> 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.

type Compiler = StringSource

Path to GHC compiler. You can use a full path name or, if you use just an executable name, the PATH will be searched.

type GhcPkg = StringSource

Path to ghc-pkg. If you use just an executable name, the PATH will be searched.

type Cabal = StringSource

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

tiDescription :: Maybe GenericPackageDescription

If Just, use this package description. Handy if you write your own package description in Haskell rather than in the cabal format. Otherwise, use Nothing and sunlight will look for the default cabal file and parse that.

tiCabal :: Cabal

Which cabal executable to use.

tiLowest :: (Description, Compiler, GhcPkg)

Test the minimum dependency bounds using this compiler. A report is left in the main package directory showing which package versions worked with this compiler and with the minimum bounds.

tiDefault :: [(Description, Compiler, GhcPkg)]

Test the default dependencies using these compilers. Since cabal-install will eagerly get the most recent dependencies it can find, this will test the highest possible versions. The compiler specified in tiLowest is not automatically retried here, so if you want to use that compiler specify it as well.

The last compiler in this list is assumed to be the most recent compiler. A report is left in the main package directory showing the dependencies that worked with this compiler version.

tiTest :: [(String, [String])]
 

Instances

dependencyError :: Dependency -> IO aSource