Files
swift-mirror/stdlib/unittest/StdlibUnittest.swift.gyb
Dmitri Hrybenko 397d2fb8c3 stdlib: coding style: when colon specifies is-a relationship, we put
spaces on both sides of it

Swift SVN r23935
2014-12-15 06:55:30 +00:00

1519 lines
44 KiB
Swift

//===--- StdlibUnittest.swift.gyb -----------------------------*- swift -*-===//
//
// This source file is part of the Swift.org open source project
//
// Copyright (c) 2014 - 2015 Apple Inc. and the Swift project authors
// Licensed under Apache License v2.0 with Runtime Library Exception
//
// See http://swift.org/LICENSE.txt for license information
// See http://swift.org/CONTRIBUTORS.txt for the list of Swift project authors
//
//===----------------------------------------------------------------------===//
import Darwin
import ObjectiveC
public struct SourceLoc {
let file: String
let line: UWord
let comment: String?
public init(_ file: String, _ line: UWord, comment: String? = nil) {
self.file = file
self.line = line
self.comment = comment
}
public func withCurrentLoc(
file: String = __FILE__, line: UWord = __LINE__
) -> SourceLocStack {
return SourceLocStack(self).with(SourceLoc(file, line))
}
}
public struct SourceLocStack {
let locs: _UnitTestArray<SourceLoc>
public init() {
locs = []
}
public init(_ loc: SourceLoc) {
locs = [ loc ]
}
init(_locs: _UnitTestArray<SourceLoc>) {
locs = _locs
}
var isEmpty: Bool {
return locs.isEmpty
}
public func with(loc: SourceLoc) -> SourceLocStack {
var locs = self.locs
locs.append(loc)
return SourceLocStack(_locs: locs)
}
public func withCurrentLoc(
file: String = __FILE__, line: UWord = __LINE__
) -> SourceLocStack {
return with(SourceLoc(file, line))
}
}
func _printStackTrace(stackTrace: SourceLocStack?) {
if let s = stackTrace {
println("stacktrace:")
for i in 0..<s.locs.count {
let loc = s.locs[s.locs.count - i - 1]
let comment = (loc.comment != nil) ? " ; \(loc.comment!)" : ""
println(" #\(i): \(loc.file):\(loc.line)\(comment)")
}
}
}
// FIXME: these variables should be atomic, since multiple threads can call
// `expect*()` functions.
var _anyExpectFailed = false
var _seenExpectCrash = false
public func expectEqual<T : Equatable>(
expected: T, actual: T,
stackTrace: SourceLocStack? = nil,
_ collectMoreInfo: (()->String)? = nil,
file: String = __FILE__, line: UWord = __LINE__
) {
expectEqual(expected, actual, {$0 == $1},
stackTrace: stackTrace, collectMoreInfo,
file: file, line: line)
}
public func expectEqual<T>(
expected: T, actual: T, equal: (T,T)->Bool,
stackTrace: SourceLocStack? = nil,
_ collectMoreInfo: (()->String)? = nil,
file: String = __FILE__, line: UWord = __LINE__
) {
if !equal(expected, actual) {
_anyExpectFailed = true
println("check failed at \(file), line \(line)")
_printStackTrace(stackTrace)
println("expected: \"\(expected)\" (of type \(_stdlib_getDemangledTypeName(expected)))")
println("actual: \"\(actual)\" (of type \(_stdlib_getDemangledTypeName(expected)))")
if collectMoreInfo != nil { println(collectMoreInfo!()) }
println()
}
}
public func expectNotEqual<T : Equatable>(
expected: T, actual: T,
stackTrace: SourceLocStack? = nil,
file: String = __FILE__, line: UWord = __LINE__
) {
if expected == actual {
_anyExpectFailed = true
println("check failed at \(file), line \(line)")
_printStackTrace(stackTrace)
println("unexpected value: \"\(actual)\" (of type \(_stdlib_getDemangledTypeName(actual)))")
println()
}
}
// Can not write a sane set of overloads using generics because of:
// <rdar://problem/17015923> Array->NSArray implicit conversion insanity
public func expectOptionalEqual<T : Equatable>(
expected: T, actual: T?,
file: String = __FILE__, line: UWord = __LINE__
) {
if (actual == nil) || expected != actual! {
_anyExpectFailed = true
println("check failed at \(file), line \(line)")
println("expected: \"\(expected)\" (of type \(_stdlib_getDemangledTypeName(expected)))")
println("actual: \"\(actual)\" (of type \(_stdlib_getDemangledTypeName(actual)))")
println()
}
}
// Array<T> is not Equatable if T is. Provide additional overloads.
// Same for Dictionary.
%for (Generic, EquatableType) in [
% ('<T : Equatable>', 'ContiguousArray<T>'),
% ('<T : Equatable>', '_UnitTestArray<T>'),
% ('<T : Equatable>', 'Slice<T>'),
% ('<T : Equatable>', 'Array<T>'),
% ('<T, U : Equatable>', 'Dictionary<T, U>'),
% ('<T : ForwardIndexType>', 'T')]:
public func expectEqual${Generic}(
expected: ${EquatableType}, actual: ${EquatableType},
stackTrace: SourceLocStack? = nil,
_ collectMoreInfo: (()->String)? = nil,
file: String = __FILE__, line: UWord = __LINE__
) {
expectEqual(
expected, actual,
// FIXME: Simpler closures don't work here due to
// <rdar://problem/17716712> and <rdar://problem/17717618>
{ (x: ${EquatableType}, y: ${EquatableType})->Bool in x == y },
stackTrace: stackTrace, collectMoreInfo,
file: file, line: line)
}
public func expectEqualSequence${Generic}(
expected: ${EquatableType}, actual: ${EquatableType},
stackTrace: SourceLocStack? = nil,
_ collectMoreInfo: (()->String)? = nil,
file: String = __FILE__, line: UWord = __LINE__
) {
expectEqual(
expected, actual,
// FIXME: Simpler closures don't work here due to
// <rdar://problem/17716712> and <rdar://problem/17717618>
{ (x: ${EquatableType}, y: ${EquatableType})->Bool in x == y },
stackTrace: stackTrace, collectMoreInfo,
file: file, line: line)
}
func _expectNotEqual${Generic}(
expected: ${EquatableType}, actual: ${EquatableType},
file: String = __FILE__, line: UWord = __LINE__
) {
if expected == actual {
_anyExpectFailed = true
println("check failed at \(file), line \(line)")
println("unexpected value: \"\(actual)\" (of type \(_stdlib_getDemangledTypeName(actual)))")
println()
}
}
%end
%for ComparableType in ['Int']:
public func expectLE(
expected: ${ComparableType}, actual: ${ComparableType},
file: String = __FILE__, line: UWord = __LINE__
) {
if !(expected <= actual) {
_anyExpectFailed = true
println("check failed at \(file), line \(line)")
println("expected: \"\(expected)\"")
println("actual: \"\(actual)\"")
println()
}
}
public func expectGE(
expected: ${ComparableType}, actual: ${ComparableType},
file: String = __FILE__, line: UWord = __LINE__
) {
if !(expected >= actual) {
_anyExpectFailed = true
println("check failed at \(file), line \(line)")
println("expected: \"\(expected)\"")
println("actual: \"\(actual)\"")
println()
}
}
%end
public func expectType<T>(_: T.Type, inout x: T) {}
public func isSequenceType<X : SequenceType>(x: X) -> X { return x }
public struct AssertionResult : Printable, BooleanType {
init(isPass: Bool) {
self._isPass = isPass
}
public var boolValue: Bool {
return _isPass
}
public func withDescription(description: String) -> AssertionResult {
var result = self
result.description += description
return result
}
let _isPass: Bool
public var description: String = ""
}
public func assertionSuccess() -> AssertionResult {
return AssertionResult(isPass: true)
}
public func assertionFailure() -> AssertionResult {
return AssertionResult(isPass: false)
}
%for BoolType in ['Bool', 'AssertionResult']:
public func expectTrue(
actual: ${BoolType},
stackTrace: SourceLocStack? = nil,
_ collectMoreInfo: (()->String)? = nil,
file: String = __FILE__, line: UWord = __LINE__
) {
if !actual {
_anyExpectFailed = true
println("check failed at \(file), line \(line)")
_printStackTrace(stackTrace)
println("expected: true")
println("actual: \(actual)")
if collectMoreInfo != nil { println(collectMoreInfo!()) }
println()
}
}
public func expectFalse(
actual: ${BoolType},
stackTrace: SourceLocStack? = nil,
_ collectMoreInfo: (()->String)? = nil,
file: String = __FILE__, line: UWord = __LINE__
) {
if actual {
_anyExpectFailed = true
println("check failed at \(file), line \(line)")
_printStackTrace(stackTrace)
println("expected: false")
println("actual: \(actual)")
if collectMoreInfo != nil { println(collectMoreInfo!()) }
println()
}
}
%end
public func expectEmpty<T>(
value: Optional<T>,
stackTrace: SourceLocStack? = nil,
file: String = __FILE__, line: UWord = __LINE__
) {
if value != nil {
_anyExpectFailed = true
println("check failed at \(file), line \(line)")
_printStackTrace(stackTrace)
println("expected optional to be empty")
println("actual: \"\(value)\"")
println()
}
}
public func expectNotEmpty<T>(
value: Optional<T>,
file: String = __FILE__, line: UWord = __LINE__
) {
if value == nil {
_anyExpectFailed = true
println("check failed at \(file), line \(line)")
println("expected optional to be non-empty")
println()
}
}
public func expectCrashLater() {
println("\(_stdlibUnittestStreamPrefix);expectCrash;\(_anyExpectFailed)")
var stderr = _Stderr()
println("\(_stdlibUnittestStreamPrefix);expectCrash", &stderr)
_seenExpectCrash = true
}
func _defaultTestSuiteFailedCallback() {
abort()
}
var _testSuiteFailedCallback: () -> () = _defaultTestSuiteFailedCallback
public func _setTestSuiteFailedCallback(callback: () -> ()) {
_testSuiteFailedCallback = callback
}
var _runTestsInProcess: Bool {
return contains(Process.arguments, "--stdlib-unittest-in-process")
}
var _isChildProcess: Bool {
return contains(Process.arguments, "--stdlib-unittest-run-child")
}
func _stdlib_getline() -> String? {
var result = _UnitTestArray<UInt8>()
while true {
let c = getchar()
if c == EOF {
return nil
}
if c == CInt(UnicodeScalar("\n").value) {
return String._fromWellFormedCodeUnitSequence(UTF8.self, input: result)
}
result.append(UInt8(c))
}
}
struct _FDInputStream {
let fd: CInt
var isEOF: Bool = false
var _buffer = _UnitTestArray<UInt8>(count: 256, repeatedValue: 0)
var _bufferUsed: Int = 0
init(fd: CInt) {
self.fd = fd
}
mutating func getline() -> String? {
if let newlineIndex =
find(_buffer[0..<_bufferUsed], UInt8(UnicodeScalar("\n").value)) {
var result = String._fromWellFormedCodeUnitSequence(
UTF8.self, input: _buffer[0..<newlineIndex])
_buffer.removeRange(0...newlineIndex)
_bufferUsed -= newlineIndex + 1
return result
}
if isEOF && _bufferUsed > 0 {
var result = String._fromWellFormedCodeUnitSequence(
UTF8.self, input: _buffer[0..<_bufferUsed])
_buffer.removeAll()
_bufferUsed = 0
return result
}
return nil
}
mutating func read() {
let minFree = 128
var bufferFree = _buffer.count - _bufferUsed
if bufferFree < minFree {
_buffer.reserveCapacity(minFree - bufferFree)
while bufferFree < minFree {
_buffer.append(0)
++bufferFree
}
}
let readResult: ssize_t = _buffer.withUnsafeMutableBufferPointer {
(_buffer) in
return Darwin.read(
self.fd, _buffer.baseAddress + self._bufferUsed, size_t(bufferFree))
}
if readResult == 0 {
isEOF = true
return
}
if readResult < 0 {
fatalError("read() returned error")
}
_bufferUsed += readResult
}
}
func _printDebuggingAdvice() {
println("To debug, run:")
println("$ \(Process.arguments[0]) --stdlib-unittest-in-process")
}
var _allTestSuites: _UnitTestArray<TestSuite> = []
var _testSuiteNameToIndex: [String : Int] = [:]
let _stdlibUnittestStreamPrefix = "__STDLIB_UNITTEST__"
@asmname("swift_stdlib_installTrapInterceptor")
func _stdlib_installTrapInterceptor()
func _childProcess() {
_stdlib_installTrapInterceptor()
while let line = _stdlib_getline() {
let parts = line._split(";")
let testSuiteName = parts[0]
let testName = parts[1]
let testSuite = _allTestSuites[_testSuiteNameToIndex[testSuiteName]!]
_anyExpectFailed = false
testSuite._runTest(testName)
println("\(_stdlibUnittestStreamPrefix);end;\(_anyExpectFailed)")
var stderr = _Stderr()
println("\(_stdlibUnittestStreamPrefix);end", &stderr)
}
}
struct _ParentProcess {
var _pid: pid_t = -1
var _childStdinFD: CInt = -1
var _childStdoutFD: CInt = -1
var _childStderrFD: CInt = -1
mutating func _spawnChild() {
(_pid, _childStdinFD, _childStdoutFD, _childStderrFD) =
spawnChild([ "--stdlib-unittest-run-child" ])
}
mutating func _waitForChild() -> ProcessTerminationStatus {
let status = posixWaitpid(_pid)
_pid = -1
if close(_childStdinFD) != 0 {
preconditionFailure("close() failed")
}
if close(_childStdoutFD) != 0 {
preconditionFailure("close() failed")
}
if close(_childStderrFD) != 0 {
preconditionFailure("close() failed")
}
return status
}
/// Returns the values of the corresponding variables in the child process.
mutating func _runTestInChild(testSuiteName: String, _ testName: String)
-> (anyExpectFailed: Bool, seenExpectCrash: Bool,
status: ProcessTerminationStatus?,
crashStdout: _UnitTestArray<String>, crashStderr: _UnitTestArray<String>) {
if _pid <= 0 {
_spawnChild()
}
var childStdin = _FDOutputStream(fd: _childStdinFD)
var childStdout = _FDInputStream(fd: _childStdoutFD)
var childStderr = _FDInputStream(fd: _childStderrFD)
println("\(testSuiteName);\(testName)", &childStdin)
var readfds = _stdlib_fd_set()
var writefds = _stdlib_fd_set()
var errorfds = _stdlib_fd_set()
var stdoutSeenCrashDelimiter = false
var stderrSeenCrashDelimiter = false
var stdoutEnd = false
var stderrEnd = false
var capturedCrashStdout = _UnitTestArray<String>()
var capturedCrashStderr = _UnitTestArray<String>()
var anyExpectFailedInChild = false
while !((childStdout.isEOF && childStderr.isEOF) ||
(stdoutEnd && stderrEnd)) {
readfds.zero()
errorfds.zero()
if !childStdout.isEOF {
readfds.set(_childStdoutFD)
errorfds.set(_childStdoutFD)
}
if !childStderr.isEOF {
readfds.set(_childStderrFD)
errorfds.set(_childStderrFD)
}
var ret: CInt
do {
ret = _stdlib_select(&readfds, &writefds, &errorfds, nil)
} while ret == -1 && errno == EINTR
if ret <= 0 {
fatalError("select() returned an error")
}
if readfds.isset(_childStdoutFD) || errorfds.isset(_childStdoutFD) {
childStdout.read()
while var line = childStdout.getline() {
if let index = findSubstring(line, _stdlibUnittestStreamPrefix) {
let controlMessage = line[index..<line.endIndex]._split(";")
switch controlMessage[1] {
case "expectCrash":
stdoutSeenCrashDelimiter = true
anyExpectFailedInChild = controlMessage[2] == "true"
case "end":
stdoutEnd = true
anyExpectFailedInChild = controlMessage[2] == "true"
default:
fatalError("unexpected message")
}
line = line[line.startIndex..<index]
if line.isEmpty {
continue
}
}
if stdoutSeenCrashDelimiter {
capturedCrashStdout.append(line)
}
println("out>>> \(line)")
}
continue
}
if readfds.isset(_childStderrFD) || errorfds.isset(_childStderrFD) {
childStderr.read()
while var line = childStderr.getline() {
if let index = findSubstring(line, _stdlibUnittestStreamPrefix) {
let controlMessage = line[index..<line.endIndex]._split(";")
switch controlMessage[1] {
case "expectCrash":
stderrSeenCrashDelimiter = true
case "end":
stderrEnd = true
default:
fatalError("unexpected message")
}
line = line[line.startIndex..<index]
if line.isEmpty {
continue
}
}
if stderrSeenCrashDelimiter {
capturedCrashStderr.append(line)
}
println("err>>> \(line)")
}
continue
}
}
if stdoutEnd && stderrEnd {
return (
anyExpectFailedInChild,
stdoutSeenCrashDelimiter || stderrSeenCrashDelimiter, nil,
capturedCrashStdout, capturedCrashStderr)
}
// We reached EOF on stdout and stderr, it looks like child crashed (of
// course it could have closed the file descriptors, but we assume it did
// not).
let status = _waitForChild()
return (
anyExpectFailedInChild,
stdoutSeenCrashDelimiter || stderrSeenCrashDelimiter, status,
capturedCrashStdout, capturedCrashStderr)
}
mutating func run() {
for testSuite in _allTestSuites {
var uxpassedTests = _UnitTestArray<String>()
var failedTests = _UnitTestArray<String>()
var skippedTests = _UnitTestArray<String>()
for t in testSuite._tests {
let fullTestName = "\(testSuite.name).\(t.name)"
let activeSkips = t.getActiveSkipPredicates()
if !activeSkips.isEmpty {
skippedTests += [ t.name ]
println("[ SKIP ] \(fullTestName) (skip: \(activeSkips))")
continue
}
let activeXFails = t.getActiveXFailPredicates()
let expectXFail = !activeXFails.isEmpty
let activeXFailsText = expectXFail ? " (XFAIL: \(activeXFails))" : ""
println("[ RUN ] \(fullTestName)\(activeXFailsText)")
var expectCrash = false
var childTerminationStatus: ProcessTerminationStatus? = nil
var crashStdout = _UnitTestArray<String>()
var crashStderr = _UnitTestArray<String>()
if _runTestsInProcess {
_anyExpectFailed = false
testSuite._runTest(t.name)
} else {
(_anyExpectFailed, expectCrash, childTerminationStatus, crashStdout,
crashStderr) =
_runTestInChild(testSuite.name, t.name)
}
// Determine if the test passed, not taking XFAILs into account.
var testPassed = false
var testFailureExplanation = ""
switch (_anyExpectFailed, childTerminationStatus, expectCrash) {
case (_, .None, false):
testPassed = !_anyExpectFailed
case (_, .None, true):
testPassed = false
testFailureExplanation = "expecting a crash, but the test did not crash"
case (_, .Some(let status), false):
testPassed = false
testFailureExplanation = "the test crashed unexpectedly"
case (_, .Some(let status), true):
testPassed = !_anyExpectFailed
default:
preconditionFailure("unreachable")
}
if testPassed && t.crashOutputMatches.count > 0 {
// If we still think that the test passed, check if the crash
// output matches our expectations.
let crashOutput = crashStdout + crashStderr
for expectedCrashOutput in t.crashOutputMatches {
var found = false
for s in crashOutput {
if findSubstring(s, expectedCrashOutput) != nil {
found = true
break
}
}
if !found {
println("did not find expected string after crash: \(expectedCrashOutput.debugDescription)")
testPassed = false
}
}
}
// Apply XFAILs.
switch (testPassed, expectXFail) {
case (true, false):
println("[ OK ] \(fullTestName)")
case (true, true):
uxpassedTests += [ t.name ]
println("[ UXPASS ] \(fullTestName)")
case (false, false):
failedTests += [ t.name ]
println("[ FAIL ] \(fullTestName)")
case (false, true):
println("[ XFAIL ] \(fullTestName)")
default:
preconditionFailure("unreachable")
}
}
if !uxpassedTests.isEmpty || !failedTests.isEmpty {
println("\(testSuite.name): Some tests failed, aborting")
println("UXPASS: \(uxpassedTests)")
println("FAIL: \(failedTests)")
println("SKIP: \(skippedTests)")
_printDebuggingAdvice()
_testSuiteFailedCallback()
} else {
println("\(testSuite.name): All tests passed")
}
}
}
}
public func runAllTests() {
autoreleasepool {
_stdlib_initializeReturnAutoreleased()
}
if _isChildProcess {
_childProcess()
} else {
var parent = _ParentProcess()
parent.run()
}
}
public class TestSuite {
public init(_ name: String) {
self.name = name
_precondition(
_testNameToIndex[name] == nil,
"test suite with the same name already exists")
_allTestSuites.append(self)
_testSuiteNameToIndex[name] = _allTestSuites.count - 1
}
public func test(name: String, _ testFunction: () -> ()) {
_TestBuilder(testSuite: self, name: name).code(testFunction)
}
public func test(name: String) -> _TestBuilder {
return _TestBuilder(testSuite: self, name: name)
}
public func setUp(code: () -> ()) {
_precondition(_testSetUpCode == nil, "set-up code already set")
_testSetUpCode = code
}
public func tearDown(code: () -> ()) {
_precondition(_testTearDownCode == nil, "tear-down code already set")
_testTearDownCode = code
}
func _runTest(testName: String) {
if let f = _testSetUpCode {
f()
}
_tests[_testNameToIndex[testName]!].code()
if let f = _testTearDownCode {
f()
}
}
struct _Test {
let name: String
let xfail: _UnitTestArray<TestRunPredicate>
let skip: _UnitTestArray<TestRunPredicate>
let crashOutputMatches: [String] = []
let code: () -> ()
func getActiveXFailPredicates() -> _UnitTestArray<TestRunPredicate> {
return xfail.filter { $0.evaluate() }
}
func getActiveSkipPredicates() -> _UnitTestArray<TestRunPredicate> {
return skip.filter { $0.evaluate() }
}
}
public struct _TestBuilder {
let _testSuite: TestSuite
var _name: String
var _data: _Data = _Data()
class _Data {
var _xfail: _UnitTestArray<TestRunPredicate> = []
var _skip: _UnitTestArray<TestRunPredicate> = []
var _crashOutputMatches: [String] = []
}
init(testSuite: TestSuite, name: String) {
_testSuite = testSuite
_name = name
}
public func xfail(predicate: TestRunPredicate) -> _TestBuilder {
_data._xfail.append(predicate)
return self
}
public func skip(predicate: TestRunPredicate) -> _TestBuilder {
_data._skip.append(predicate)
return self
}
public func crashOutputMatches(string: String) -> _TestBuilder {
_data._crashOutputMatches.append(string)
return self
}
public func code(testFunction: () -> ()) {
_testSuite._tests.append(_Test(
name: _name, xfail: _data._xfail, skip: _data._skip,
crashOutputMatches: _data._crashOutputMatches, code: testFunction))
_testSuite._testNameToIndex[_name] = _testSuite._tests.count - 1
}
}
var name: String
var _tests: _UnitTestArray<_Test> = []
/// Code that is run before every test.
var _testSetUpCode: (() -> ())?
/// Code that is run after every test.
var _testTearDownCode: (() -> ())?
/// Maps test name to index in `_tests`.
var _testNameToIndex: [String : Int] = [:]
}
@asmname("swift_stdlib_getSystemVersionPlistProperty")
func _stdlib_getSystemVersionPlistPropertyImpl(
propertyName: UnsafePointer<CChar>) -> UnsafePointer<CChar>
func _stdlib_getSystemVersionPlistProperty(propertyName: String) -> String? {
return String.fromCString(
_stdlib_getSystemVersionPlistPropertyImpl(propertyName))
}
public enum OSVersion : Printable {
case OSX(major: Int, minor: Int, bugFix: Int)
case iOS(major: Int, minor: Int, bugFix: Int)
case iOSSimulator
public var description: String {
switch self {
case OSX(var major, var minor, var bugFix):
return "OS X \(major).\(minor).\(bugFix)"
case iOS(var major, var minor, var bugFix):
return "iOS \(major).\(minor).\(bugFix)"
case iOSSimulator:
return "iOSSimulator"
}
}
}
func _parseDottedVersion(s: String) -> _UnitTestArray<Int> {
return _UnitTestArray(lazy(s._split(".")).map { $0.toInt()! })
}
public func _parseDottedVersionTriple(s: String) -> (Int, Int, Int) {
var array = _parseDottedVersion(s)
if array.count >= 4 {
fatalError("unexpected version")
}
return (
array.count >= 1 ? array[0] : 0,
array.count >= 2 ? array[1] : 0,
array.count >= 3 ? array[2] : 0)
}
func _getOSVersion() -> OSVersion {
#if os(iOS) && (arch(i386) || arch(x86_64))
// On simulator, the plist file that we try to read turns out to be host's
// plist file, which indicates OS X.
//
// FIXME: how to get the simulator version *without* UIKit?
return .iOSSimulator
#else
let productName = _stdlib_getSystemVersionPlistProperty("ProductName")!
let productVersion = _stdlib_getSystemVersionPlistProperty("ProductVersion")!
let (major, minor, bugFix) = _parseDottedVersionTriple(productVersion)
switch productName {
case "Mac OS X":
return .OSX(major: major, minor: minor, bugFix: bugFix)
case "iPhone OS":
return .iOS(major: major, minor: minor, bugFix: bugFix)
default:
fatalError("could not determine OS version")
}
#endif
}
var _runningOSVersion: OSVersion = _getOSVersion()
var _overrideOSVersion: OSVersion? = nil
/// Override the OS version for testing.
public func _setOverrideOSVersion(v: OSVersion) {
_overrideOSVersion = v
}
func _getRunningOSVersion() -> OSVersion {
// Allow overriding the OS version for testing.
return _overrideOSVersion ?? _runningOSVersion
}
public enum TestRunPredicate : Printable {
case Custom(() -> Bool, reason: String)
case OSXAny(/*reason:*/ String)
case OSXMajor(Int, reason: String)
case OSXMinor(Int, Int, reason: String)
case OSXMinorRange(Int, Range<Int>, reason: String)
case OSXBugFix(Int, Int, Int, reason: String)
case OSXBugFixRange(Int, Int, Range<Int>, reason: String)
case iOSAny(/*reason:*/ String)
case iOSMajor(Int, reason: String)
case iOSMinor(Int, Int, reason: String)
case iOSMinorRange(Int, Range<Int>, reason: String)
case iOSBugFix(Int, Int, Int, reason: String)
case iOSBugFixRange(Int, Int, Range<Int>, reason: String)
case iOSSimulatorAny(/*reason:*/ String)
public var description: String {
switch self {
case Custom(_, let reason):
return "Custom(reason: \(reason))"
case OSXAny(let reason):
return "OSX(*, reason: \(reason))"
case OSXMajor(let major, let reason):
return "OSX(\(major).*, reason: \(reason))"
case OSXMinor(let major, let minor, let reason):
return "OSX(\(major).\(minor), reason: \(reason))"
case OSXMinorRange(let major, let minorRange, let reason):
return "OSX(\(major).[\(minorRange)], reason: \(reason))"
case OSXBugFix(let major, let minor, let bugFix, let reason):
return "OSX(\(major).\(minor).\(bugFix), reason: \(reason))"
case OSXBugFixRange(let major, let minor, let bugFixRange, let reason):
return "OSX(\(major).\(minor).[\(bugFixRange)], reason: \(reason))"
case iOSAny(let reason):
return "iOS(*, reason: \(reason))"
case iOSMajor(let major, let reason):
return "iOS(\(major).*, reason: \(reason))"
case iOSMinor(let major, let minor, let reason):
return "iOS(\(major).\(minor), reason: \(reason))"
case iOSMinorRange(let major, let minorRange, let reason):
return "iOS(\(major).[\(minorRange)], reason: \(reason))"
case iOSBugFix(let major, let minor, let bugFix, let reason):
return "iOS(\(major).\(minor).\(bugFix), reason: \(reason))"
case iOSBugFixRange(let major, let minor, let bugFixRange, let reason):
return "iOS(\(major).\(minor).[\(bugFixRange)], reason: \(reason))"
case iOSSimulatorAny(let reason):
return "iOSSimulatorAny(*, reason: \(reason))"
}
}
public func evaluate() -> Bool {
switch self {
case Custom(let predicate, _):
return predicate()
case OSXAny:
switch _getRunningOSVersion() {
case .OSX:
return true
default:
return false
}
case OSXMajor(let major, _):
switch _getRunningOSVersion() {
case .OSX(major, _, _):
return true
default:
return false
}
case OSXMinor(let major, let minor, _):
switch _getRunningOSVersion() {
case .OSX(major, minor, _):
return true
default:
return false
}
case OSXMinorRange(let major, let minorRange, _):
switch _getRunningOSVersion() {
case .OSX(major, let runningMinor, _):
return contains(minorRange, runningMinor)
default:
return false
}
case OSXBugFix(let major, let minor, let bugFix, _):
switch _getRunningOSVersion() {
case .OSX(major, minor, bugFix):
return true
default:
return false
}
case OSXBugFixRange(let major, let minor, let bugFixRange, _):
switch _getRunningOSVersion() {
case .OSX(major, minor, let runningBugFix):
return contains(bugFixRange, runningBugFix)
default:
return false
}
case iOSAny:
switch _getRunningOSVersion() {
case .iOS:
return true
default:
return false
}
case iOSMajor(let major, _):
switch _getRunningOSVersion() {
case .iOS(major, _, _):
return true
default:
return false
}
case iOSMinor(let major, let minor, _):
switch _getRunningOSVersion() {
case .iOS(major, minor, _):
return true
default:
return false
}
case iOSMinorRange(let major, let minorRange, _):
switch _getRunningOSVersion() {
case .iOS(major, let runningMinor, _):
return contains(minorRange, runningMinor)
default:
return false
}
case iOSBugFix(let major, let minor, let bugFix, _):
switch _getRunningOSVersion() {
case .iOS(major, minor, bugFix):
return true
default:
return false
}
case iOSBugFixRange(let major, let minor, let bugFixRange, _):
switch _getRunningOSVersion() {
case .iOS(major, minor, let runningBugFix):
return contains(bugFixRange, runningBugFix)
default:
return false
}
case iOSSimulatorAny:
switch _getRunningOSVersion() {
case .iOSSimulator:
return true
default:
return false
}
}
}
}
//
// Helpers that verify invariants of various stdlib types.
//
public func checkEquatable<T : Equatable>(
expectedEqual: Bool, lhs: T, rhs: T, stackTrace: SourceLocStack,
_ collectMoreInfo: (()->String)? = nil
) {
// Test operator '==' that is found through witness tables.
expectEqual(
expectedEqual, lhs == rhs, stackTrace: stackTrace, collectMoreInfo)
expectEqual(
!expectedEqual, lhs != rhs, stackTrace: stackTrace, collectMoreInfo)
}
public func checkEquatable<T : Equatable>(
expectedEqual: Bool, lhs: T, rhs: T,
_ collectMoreInfo: (()->String)? = nil,
file: String = __FILE__, line: UWord = __LINE__
) {
checkEquatable(
expectedEqual, lhs, rhs, SourceLocStack().with(SourceLoc(file, line)))
}
public func checkHashable<T : Hashable>(
expectedEqual: Bool, lhs: T, rhs: T, stackTrace: SourceLocStack,
_ collectMoreInfo: (()->String)? = nil
) {
// Test operator '==' that is found through witness tables.
expectEqual(
expectedEqual, lhs == rhs, stackTrace: stackTrace, collectMoreInfo)
expectEqual(
!expectedEqual, lhs != rhs, stackTrace: stackTrace, collectMoreInfo)
// Test 'hashValue'.
//
// If objects are not equal, then the hash value can be different or it can
// collide.
if expectedEqual {
expectEqual(lhs.hashValue, rhs.hashValue)
}
}
public func checkHashable<T : Hashable>(
expectedEqual: Bool, lhs: T, rhs: T,
_ collectMoreInfo: (()->String)? = nil,
file: String = __FILE__, line: UWord = __LINE__
) {
checkHashable(
expectedEqual, lhs, rhs, SourceLocStack(SourceLoc(file, line)),
collectMoreInfo)
}
public enum ExpectedComparisonResult {
case LT, EQ, GT
public func isLT() -> Bool {
return self == .LT
}
public func isEQ() -> Bool {
return self == .EQ
}
public func isGT() -> Bool {
return self == .GT
}
public func isLE() -> Bool {
return isLT() || isEQ()
}
public func isGE() -> Bool {
return isGT() || isEQ()
}
public func isNE() -> Bool {
return !isEQ()
}
public func flip() -> ExpectedComparisonResult {
switch self {
case .LT:
return .GT
case .EQ:
return .EQ
case .GT:
return .LT
}
}
}
public func checkComparable<T : Comparable>(
expected: ExpectedComparisonResult,
lhs: T, rhs: T, stackTrace: SourceLocStack
) {
expectEqual(expected.isLT(), lhs < rhs, stackTrace: stackTrace)
expectEqual(expected.isLE(), lhs <= rhs, stackTrace: stackTrace)
expectEqual(expected.isGE(), lhs >= rhs, stackTrace: stackTrace)
expectEqual(expected.isGT(), lhs > rhs, stackTrace: stackTrace)
}
public func checkComparable<T : Comparable>(
expected: ExpectedComparisonResult,
lhs: T, rhs: T,
file: String = __FILE__, line: UWord = __LINE__
) {
checkComparable(expected, lhs, rhs, SourceLocStack(SourceLoc(file, line)))
}
// Generate two overloads: one for _UnitTestArray (which will get
// picked up when the caller passes a literal), and another that
// accepts any appropriate Collection type.
% for genericParam, Element, Expected in zip(
% ('Expected: CollectionType', 'Element'),
% ('Expected.Generator.Element', 'Element'),
% ('Expected', '_UnitTestArray<Element>')):
public func checkGenerator<
G : GeneratorType, ${genericParam}
where ${Element} == G.Element, ${Element} : Equatable
>(
expected: ${Expected},
generator: G, stackTrace: SourceLocStack
) {
// Copying a `GeneratorType` is allowed.
var mutableGen = generator
var actual: _UnitTestArray<${Element}> = []
while let e = mutableGen.next() {
actual.append(e)
}
expectEqualSequence(expected, actual, stackTrace: stackTrace.withCurrentLoc())
// Having returned `.None` once, a `GeneratorType` should not generate more
// elements.
for i in 0..<10 {
expectEmpty(mutableGen.next(), stackTrace: stackTrace.withCurrentLoc())
}
}
public func checkSequence<
${genericParam}, S : SequenceType
where S.Generator.Element == ${Element}, ${Element} : Equatable
>(
expected: ${Expected},
sequence: S, stackTrace: SourceLocStack
) {
let expectedCount: Int = numericCast(count(expected))
checkGenerator(expected, sequence.generate(), stackTrace.withCurrentLoc())
expectGE(expectedCount, underestimateCount(sequence))
}
public func checkCollection<
${genericParam}, C : CollectionType
where C.Generator.Element == ${Element}, ${Element} : Equatable
>(
expected: ${Expected},
collection: C, stackTrace: SourceLocStack
) {
// A `CollectionType` is a multi-pass `SequenceType`.
for i in 0..<3 {
checkSequence(expected, collection, stackTrace.withCurrentLoc())
}
expectEqual(count(expected).toIntMax(), count(collection).toIntMax(),
stackTrace: stackTrace.withCurrentLoc())
for i in 0..<3 {
let startIndex = collection.startIndex
let endIndex = collection.endIndex
var actual: _UnitTestArray<${Element}> = []
var index = collection.startIndex
while index != collection.endIndex {
// Iteration should not change `startIndex` or `endIndex`.
expectEqual(startIndex, collection.startIndex)
expectEqual(endIndex, collection.endIndex)
actual.append(collection[index])
++index
}
expectEqualSequence(
expected, actual, stackTrace: stackTrace.withCurrentLoc())
}
}
public func checkSliceableWithBidirectionalIndex<
${genericParam}, S : Sliceable
where S.Generator.Element == ${Element},
S.SubSlice.Generator.Element == ${Element},
S.Index : BidirectionalIndexType,
${Element} : Equatable
>(
expected: ${Expected},
sliceable: S, stackTrace: SourceLocStack) {
// A `Sliceable` is a `CollectionType`.
checkCollection(expected, sliceable, stackTrace.withCurrentLoc())
let expectedArray = _UnitTestArray(expected)
var start = sliceable.startIndex
for startNumericIndex in 0...expectedArray.count {
if start != sliceable.endIndex {
++start
--start
++start
--start
}
var end = start
for endNumericIndex in startNumericIndex...expectedArray.count {
if end != sliceable.endIndex {
++end
--end
++end
--end
}
let expectedSlice = expectedArray[startNumericIndex..<endNumericIndex]
let slice = sliceable[start..<end]
checkCollection(expectedSlice, slice, stackTrace.withCurrentLoc())
if end != sliceable.endIndex {
++end
}
}
if start != sliceable.endIndex {
++start
}
}
}
% end
public func nthIndex<C: CollectionType>(x: C, n: Int) -> C.Index {
return advance(x.startIndex, numericCast(n))
}
public func nth<C: CollectionType>(x: C, n: Int) -> C.Generator.Element {
return x[nthIndex(x, n)]
}
public func checkRangeReplaceable<
C: RangeReplaceableCollectionType,
N: CollectionType
where
C.Generator.Element : Equatable, C.Generator.Element == N.Generator.Element
>(
makeCollection: ()->C,
makeNewValues: (Int)->N
) {
typealias A = C
// First make an independent copy of the array that we can use for
// comparison later.
let source = _UnitTestArray<A.Generator.Element>(makeCollection())
for (ix, i) in enumerate(indices(source)) {
for (jx_, j) in enumerate(i..<source.endIndex) {
let jx = jx_ + ix
let oldCount = jx - ix
for newCount in 0..<(2 * oldCount) {
let newValues = makeNewValues(newCount)
func reportFailure(inout a: A, message: String) {
println("\(message) when replacing indices \(ix)...\(jx)")
println(" in \(_UnitTestArray(source)) with \(_UnitTestArray(newValues))")
println(" yielding \(_UnitTestArray(a))")
println("====================================")
expectTrue(false)
}
var a = makeCollection()
a.replaceRange(nthIndex(a, ix)..<nthIndex(a, jx), with: newValues)
let growth = newCount - oldCount
let expectedCount = source.count + growth
let actualCount = numericCast(count(a)) as Int
if actualCount != expectedCount {
reportFailure(
&a, "\(actualCount) != expected count \(expectedCount)")
}
for (kx, k) in enumerate(indices(a)) {
let expectedValue = kx < ix ? nth(source, kx)
: kx < jx + growth ? nth(newValues, kx - ix)
: nth(source, kx - growth)
if a[k] != expectedValue {
reportFailure(
&a,
// FIXME: why do we need to break this string into two parts?
"a[\(kx)] = "
+ "\(a[k]) != expected value \(expectedValue)")
}
}
}
}
}
}
public func expectEqualSequence<
Expected: SequenceType,
Actual: SequenceType
where Expected.Generator.Element == Actual.Generator.Element,
Expected.Generator.Element : Equatable
>(
expected: Expected, actual: Actual,
stackTrace: SourceLocStack? = nil,
_ collectMoreInfo: (()->String)? = nil,
file: String = __FILE__, line: UWord = __LINE__
) {
expectEqualSequence(
expected, actual, { $0 == $1 }, stackTrace: stackTrace,
collectMoreInfo: collectMoreInfo, file: file, line: line)
}
public func expectEqualSequence<
Expected: SequenceType,
Actual: SequenceType
where Expected.Generator.Element == Actual.Generator.Element
>(
expected: Expected, actual: Actual,
sameValue: (Expected.Generator.Element, Expected.Generator.Element)->Bool,
stackTrace: SourceLocStack? = nil,
collectMoreInfo: (()->String)? = nil,
file: String = __FILE__, line: UWord = __LINE__
) {
if !equal(expected, actual, sameValue) {
_anyExpectFailed = true
println("check failed at \(file), line \(line)")
_printStackTrace(stackTrace)
println("expected elements: \"\(expected)\"")
println("actual: \"\(actual)\" (of type \(_stdlib_getDemangledTypeName(actual)))")
if collectMoreInfo != nil { println(collectMoreInfo!()) }
println()
}
}
public func expectEqualsUnordered<
Expected : SequenceType,
Actual : SequenceType
where Expected.Generator.Element == Actual.Generator.Element
>(
expected: Expected, actual: Actual,
compare: (Expected.Generator.Element, Expected.Generator.Element)
-> ExpectedComparisonResult,
stackTrace: SourceLocStack? = nil,
collectMoreInfo: (()->String)? = nil,
file: String = __FILE__, line: UWord = __LINE__
) {
let x: [Expected.Generator.Element] = sorted(
Array(expected), compose(compare, { $0.isLT() }))
let y: [Actual.Generator.Element] = sorted(
Array(actual), compose(compare, { $0.isLT() }))
expectEqualSequence(
x, y, compose(compare, { $0.isEQ() }), stackTrace: stackTrace,
collectMoreInfo: collectMoreInfo, file: file, line: line)
}
public func expectEqualFunctionsForDomain<ArgumentType, Result : Equatable>(
arguments: [ArgumentType], function1: ArgumentType -> Result,
function2: ArgumentType -> Result
) {
for a in arguments {
let expected = function1(a)
let actual = function2(a)
expectEqual(expected, actual) {
"where the argument is: \(a)"
}
}
}
public func expectEqualMethodsForDomain<
SelfType, ArgumentType, Result : Equatable
>(
selfs: [SelfType], arguments: [ArgumentType],
function1: SelfType -> ArgumentType -> Result,
function2: SelfType -> ArgumentType -> Result
) {
for s in selfs {
for a in arguments {
let expected = function1(s)(a)
let actual = function2(s)(a)
expectEqual(expected, actual) {
"where the first argument is: \(s)\nand the second argument is: \(a)"
}
}
}
}
public func expectEqualUnicodeScalars(
expected: _UnitTestArray<UInt32>, actual: String,
stackTrace: SourceLocStack? = nil,
collectMoreInfo: (()->String)? = nil,
file: String = __FILE__, line: UWord = __LINE__
) {
let actualUnicodeScalars = _UnitTestArray(lazy(actual.unicodeScalars).map { $0.value })
if !equal(expected, actualUnicodeScalars) {
_anyExpectFailed = true
println("check failed at \(file), line \(line)")
_printStackTrace(stackTrace)
println("expected elements: \"\(asHex(expected))\"")
println("actual: \"\(asHex(actualUnicodeScalars))\"")
if collectMoreInfo != nil { println(collectMoreInfo!()) }
println()
}
}
public func expectPrinted<T>(
#expectedOneOf: _UnitTestArray<String>, object: T,
file: StaticString = __FILE__, line: UWord = __LINE__
) {
let actual = toString(object)
if !contains(expectedOneOf, actual) {
_anyExpectFailed = true
println("check failed at \(file), line \(line)")
println("expected: any of \(expectedOneOf.debugDescription)")
println("actual: \"\(actual)\"")
println()
}
}
public func expectPrinted<T>(
expected: String, object: T,
file: StaticString = __FILE__, line: UWord = __LINE__
) {
expectPrinted(expectedOneOf: [expected], object, file: file, line: line)
}
public func expectDebugPrinted<T>(
#expectedOneOf: _UnitTestArray<String>, object: T,
file: StaticString = __FILE__, line: UWord = __LINE__
) {
let actual = toDebugString(object)
if !contains(expectedOneOf, actual) {
_anyExpectFailed = true
println("check failed at \(file), line \(line)")
println("expected: any of \(expectedOneOf.debugDescription)")
println("actual: \"\(actual)\"")
println()
}
}
public func expectDebugPrinted<T>(
expected: String, object: T,
file: StaticString = __FILE__, line: UWord = __LINE__
) {
expectDebugPrinted(expectedOneOf: [expected], object, file: file, line: line)
}
func compose<A, B, C>(f: A -> B, g: B -> C) -> A -> C {
return { a in
return g(f(a))
}
}
// ${'Local Variables'}:
// eval: (read-only-mode 1)
// End: