[WIP] Implement SE-0039 (Modernizing Playground Literals) (#2215)

* Implement the majority of parsing support for SE-0039.

* Parse old object literals names using new syntax and provide FixIt.

For example, parse "#Image(imageLiteral:...)" and provide a FixIt to
change it to "#imageLiteral(resourceName:...)".  Now we see something like:

test.swift:4:9: error: '#Image' has been renamed to '#imageLiteral
var y = #Image(imageLiteral: "image.jpg")
        ^~~~~~ ~~~~~~~~~~~~
        #imageLiteral resourceName

Handling the old syntax, and providing a FixIt for that, will be handled in a separate
commit.

Needs tests.  Will be provided in later commit once full parsing support is done.

* Add back pieces of syntax map for object literals.

* Add parsing support for old object literal syntax.

... and provide fixits to new syntax.

Full tests to come in later commit.

* Improve parsing of invalid object literals with old syntax.

* Do not include bracket in code completion results.

* Remove defunct code in SyntaxModel.

* Add tests for migration fixits.

* Add literals to code completion overload tests.

@akyrtzi told me this should be fine.

* Clean up response tests not to include full paths.

* Further adjust offsets.

* Mark initializer for _ColorLiteralConvertible in UIKit as @nonobjc.

* Put attribute in the correct place.
This commit is contained in:
Ted Kremenek
2016-04-25 07:19:26 -07:00
parent ca5d7bd204
commit b8bbed8c13
31 changed files with 438 additions and 247 deletions

1
.gitignore vendored
View File

@@ -39,3 +39,4 @@ docs/_build
#==============================================================================#
CMakeCache.txt
CMakeFiles
.atom-build.json

View File

@@ -1046,12 +1046,14 @@ ERROR(expected_rsquare_array_expr,PointsToFirstBadToken,
"expected ']' in container literal expression", ())
// Object literal expressions
ERROR(expected_identifier_after_l_square_lit,none,
"expected identifier after '[#' in object literal expression", ())
ERROR(expected_object_literal_identifier,none,
"expected identifier after '#' in object literal expression", ())
ERROR(expected_arg_list_in_object_literal,none,
"expected argument list in object literal", ())
ERROR(expected_r_square_lit_after_object_literal,none,
"expected '#]' at end of object literal expression", ())
ERROR(object_literal_legacy_name,none,
"'%0' has been renamed to '%1", (StringRef, StringRef))
ERROR(legacy_object_literal_syntax,none,
"object literal syntax no longer uses '[# ... #]'", ())
// If expressions
ERROR(expected_expr_after_if_question,none,

View File

@@ -514,8 +514,8 @@ ERROR(pattern_used_in_type,none,
NOTE(note_module_as_type,none,
"cannot use module %0 as a type", (Identifier))
ERROR(use_unknown_object_literal,none,
"use of unknown object literal name %0", (Identifier))
ERROR(use_unknown_object_literal_protocol,none,
"cannot deduce protocol for %0 literal", (StringRef))
ERROR(object_literal_default_type_missing,none,
"could not infer type of %0 literal", (StringRef))
NOTE(object_literal_resolve_import,none,

View File

@@ -831,27 +831,31 @@ public:
};
// ObjectLiteralExpr - An expression of the form
// '[#Color(red: 1, blue: 0, green: 0, alpha: 1)#]' with a name and a list
// '#colorLiteral(red: 1, blue: 0, green: 0, alpha: 1)' with a name and a list
// argument. The components of the list argument are meant to be themselves
// constant.
class ObjectLiteralExpr : public LiteralExpr {
Identifier Name;
public:
/// The kind of object literal.
enum LiteralKind : unsigned {
#define POUND_OBJECT_LITERAL(Name, Desc, Proto) Name,
#include "swift/Parse/Tokens.def"
};
private:
LiteralKind LitKind;
Expr *Arg;
Expr *SemanticExpr;
SourceLoc LLitLoc;
SourceLoc NameLoc;
SourceLoc RLitLoc;
SourceLoc PoundLoc;
public:
ObjectLiteralExpr(SourceLoc LLitLoc, Identifier Name, SourceLoc NameLoc,
Expr *Arg, SourceLoc RLitLoc, bool implicit = false)
ObjectLiteralExpr(SourceLoc PoundLoc, LiteralKind LitKind,
Expr *Arg, bool implicit = false)
: LiteralExpr(ExprKind::ObjectLiteral, implicit),
Name(Name), Arg(Arg), SemanticExpr(nullptr),
LLitLoc(LLitLoc), NameLoc(NameLoc), RLitLoc(RLitLoc) {}
LitKind(LitKind), Arg(Arg), SemanticExpr(nullptr),
PoundLoc(PoundLoc) {}
Identifier getName() const { return Name; }
SourceLoc getNameLoc() const { return NameLoc; }
LiteralKind getLiteralKind() const { return LitKind; }
Expr *getArg() const { return Arg; }
void setArg(Expr *arg) { Arg = arg; }
@@ -859,8 +863,15 @@ public:
Expr *getSemanticExpr() const { return SemanticExpr; }
void setSemanticExpr(Expr *expr) { SemanticExpr = expr; }
SourceLoc getSourceLoc() const { return NameLoc; }
SourceRange getSourceRange() const { return SourceRange(LLitLoc, RLitLoc); }
SourceLoc getSourceLoc() const { return PoundLoc; }
SourceRange getSourceRange() const {
return SourceRange(PoundLoc, Arg->getEndLoc());
}
/// Return the string form of the literal name.
StringRef getLiteralKindRawName() const;
StringRef getLiteralKindPlainName() const;
static bool classof(const Expr *E) {
return E->getKind() == ExprKind::ObjectLiteral;

View File

@@ -1177,8 +1177,17 @@ public:
Expr *parseExprAnonClosureArg();
ParserResult<Expr> parseExprList(tok LeftTok, tok RightTok);
// NOTE: used only for legacy support for old object literal syntax.
// Will be removed in the future.
bool isCollectionLiteralStartingWithLSquareLit();
ParserResult<Expr> parseExprObjectLiteral();
/// Parse an object literal.
///
/// \param LK The literal kind as determined by the first token.
/// \param NewName New name for a legacy literal.
ParserResult<Expr> parseExprObjectLiteral(ObjectLiteralExpr::LiteralKind LK,
StringRef NewName = StringRef());
ParserResult<Expr> parseExprCallSuffix(ParserResult<Expr> fn,
Identifier firstSelectorPiece
= Identifier(),

View File

@@ -38,6 +38,29 @@
#define POUND_KEYWORD(kw)
#endif
/// POUND_NORMAL_KEYWORD(kw)
/// Keywords except object and config keywords in the #foo namespace.
#ifndef POUND_NORMAL_KEYWORD
#define POUND_NORMAL_KEYWORD(kw) POUND_KEYWORD(kw)
#endif
/// POUND_OBJECT_LITERAL(kw, desc, proto)
/// Every keyword in the #foo namespace representing an object literal.
#ifndef POUND_OBJECT_LITERAL
#define POUND_OBJECT_LITERAL(kw, desc, proto) POUND_KEYWORD(kw)
#endif
/// POUND_OLD_OBJECT_LITERAL(kw, new_kw, old_arg, new_arg)
/// Every keyword in the #foo namespace representing an object literal.
#ifndef POUND_OLD_OBJECT_LITERAL
#define POUND_OLD_OBJECT_LITERAL(kw, new_kw, old_arg, new_arg) POUND_KEYWORD(kw)
#endif
/// POUND_CONFIG(kw)
/// Every keyword in the #foo namespace representing a configuration.
#ifndef POUND_CONFIG
#define POUND_CONFIG(kw) POUND_KEYWORD(kw)
#endif
/// SIL_KEYWORD(kw)
/// Expands for every SIL keyword. These are only keywords when parsing SIL.
@@ -140,9 +163,6 @@ PUNCTUATOR(r_brace, "}")
PUNCTUATOR(l_square, "[")
PUNCTUATOR(r_square, "]")
PUNCTUATOR(l_square_lit, "[#")
PUNCTUATOR(r_square_lit, "#]")
PUNCTUATOR(period, ".")
PUNCTUATOR(period_prefix, ".")
PUNCTUATOR(comma, ",")
@@ -165,6 +185,11 @@ PUNCTUATOR(question_infix,"?") // if not left-bound
PUNCTUATOR(sil_dollar, "$") // Only in SIL mode.
PUNCTUATOR(sil_exclamation, "!") // Only in SIL mode.
// Legacy punctuators used for migrating old object literal syntax.
// NOTE: Remove in the future.
PUNCTUATOR(l_square_lit, "[#")
PUNCTUATOR(r_square_lit, "#]")
// Keywords in the # namespace. "if" becomes "tok::pound_if".
POUND_KEYWORD(if)
POUND_KEYWORD(else)
@@ -173,9 +198,22 @@ POUND_KEYWORD(endif)
POUND_KEYWORD(line)
POUND_KEYWORD(setline)
POUND_KEYWORD(sourceLocation)
POUND_KEYWORD(available)
POUND_KEYWORD(selector)
// Keywords in the # namespace that are build configurations.
POUND_CONFIG(available)
// Declaratively define object literals, including their
// corresponding protocols.
POUND_OBJECT_LITERAL(fileLiteral, "file reference", FileReferenceLiteralConvertible)
POUND_OBJECT_LITERAL(imageLiteral, "image", ImageLiteralConvertible)
POUND_OBJECT_LITERAL(colorLiteral, "color", ColorLiteralConvertible)
POUND_OLD_OBJECT_LITERAL(FileReference, fileLiteral, fileReferenceLiteral, resourceName)
POUND_OLD_OBJECT_LITERAL(Image, imageLiteral, imageLiteral, resourceName)
POUND_OLD_OBJECT_LITERAL(Color, colorLiteral, colorLiteralRed, red)
POUND_KEYWORD(file)
POUND_KEYWORD(column)
POUND_KEYWORD(function)
@@ -188,3 +226,7 @@ POUND_KEYWORD(dsohandle)
#undef SIL_KEYWORD
#undef PUNCTUATOR
#undef POUND_KEYWORD
#undef POUND_NORMAL_KEYWORD
#undef POUND_OBJECT_LITERAL
#undef POUND_OLD_OBJECT_LITERAL
#undef POUND_CONFIG

View File

@@ -1623,9 +1623,8 @@ public:
}
void visitObjectLiteralExpr(ObjectLiteralExpr *E) {
printCommon(E, "object_literal")
<< " name=" << E->getName();
OS << '\n';
printCommon(E, "object_literal")
<< " kind='" << E->getLiteralKindPlainName() << "'\n";
printRec(E->getArg());
}

View File

@@ -743,9 +743,8 @@ shallowCloneImpl(const MagicIdentifierLiteralExpr *E, ASTContext &Ctx) {
static LiteralExpr *
shallowCloneImpl(const ObjectLiteralExpr *E, ASTContext &Ctx) {
auto res = new (Ctx) ObjectLiteralExpr(E->getStartLoc(), E->getName(),
E->getNameLoc(), E->getArg(),
E->getEndLoc());
auto res = new (Ctx) ObjectLiteralExpr(E->getStartLoc(), E->getLiteralKind(),
E->getArg());
res->setSemanticExpr(E->getSemanticExpr());
return res;
}
@@ -846,6 +845,22 @@ StringLiteralExpr::StringLiteralExpr(StringRef Val, SourceRange Range,
unicode::isSingleExtendedGraphemeCluster(Val);
}
StringRef ObjectLiteralExpr::getLiteralKindRawName() const {
switch (LitKind) {
#define POUND_OBJECT_LITERAL(Name, Desc, Proto) case Name: return #Name;
#include "swift/Parse/Tokens.def"
}
llvm_unreachable("unspecified literal");
}
StringRef ObjectLiteralExpr::getLiteralKindPlainName() const {
switch (LitKind) {
#define POUND_OBJECT_LITERAL(Name, Desc, Proto) case Name: return Desc;
#include "swift/Parse/Tokens.def"
}
llvm_unreachable("unspecified literal");
}
void DeclRefExpr::setSpecialized() {
if (isSpecialized())
return;

View File

@@ -3228,10 +3228,9 @@ public:
auto floatType = context.getFloatDecl()->getDeclaredType();
addFromProto(LK::ColorLiteral, "", [&](Builder &builder) {
builder.addLeftBracket();
builder.addTextChunk("#Color");
builder.addTextChunk("#colorLiteral");
builder.addLeftParen();
builder.addCallParameter(context.getIdentifier("colorLiteralRed"),
builder.addCallParameter(context.getIdentifier("red"),
floatType, false, true);
builder.addComma();
builder.addCallParameter(context.getIdentifier("green"), floatType,
@@ -3243,20 +3242,15 @@ public:
builder.addCallParameter(context.getIdentifier("alpha"), floatType,
false, true);
builder.addRightParen();
builder.addTextChunk("#");
builder.addRightBracket();
});
auto stringType = context.getStringDecl()->getDeclaredType();
addFromProto(LK::ImageLiteral, "", [&](Builder &builder) {
builder.addLeftBracket();
builder.addTextChunk("#Image");
builder.addTextChunk("#imageLiteral");
builder.addLeftParen();
builder.addCallParameter(context.getIdentifier("imageLiteral"),
builder.addCallParameter(context.getIdentifier("resourceName"),
stringType, false, true);
builder.addRightParen();
builder.addTextChunk("#");
builder.addRightBracket();
});
// Add tuple completion (item, item).

View File

@@ -84,10 +84,6 @@ SyntaxModelContext::SyntaxModelContext(SourceFile &SrcFile)
Length = Tok.getLength();
if (LiteralStartLoc.hasValue() && Length.hasValue()) {
// We are still inside an object literal until we hit a r_square_lit.
if (Tok.getKind() != tok::r_square_lit) {
continue;
}
Kind = SyntaxNodeKind::ObjectLiteral;
Nodes.emplace_back(Kind, CharSourceRange(SM, LiteralStartLoc.getValue(),
Tok.getRange().getEnd()));
@@ -99,20 +95,23 @@ SyntaxModelContext::SyntaxModelContext(SourceFile &SrcFile)
#define KEYWORD(X) case tok::kw_##X: Kind = SyntaxNodeKind::Keyword; break;
#include "swift/Parse/Tokens.def"
#undef KEYWORD
case tok::pound_selector:
case tok::pound_file:
case tok::pound_column:
case tok::pound_function:
case tok::pound_dsohandle:
#define POUND_NORMAL_KEYWORD(Name) case tok::pound_##Name:
#define POUND_OBJECT_LITERAL(Name, Desc, Proto) case tok::pound_##Name:
#define POUND_OLD_OBJECT_LITERAL(Name, NewName, OldArg, NewArg) case tok::pound_##Name:
#include "swift/Parse/Tokens.def"
Kind = SyntaxNodeKind::Keyword;
break;
#define POUND_CONFIG(Name) case tok::pound_##Name:
#include "swift/Parse/Tokens.def"
Kind = SyntaxNodeKind::BuildConfigKeyword;
break;
case tok::pound_line:
Kind = Tok.isAtStartOfLine() ? SyntaxNodeKind::BuildConfigKeyword :
SyntaxNodeKind::Keyword;
break;
case tok::pound_available:
Kind = SyntaxNodeKind::BuildConfigKeyword;
break;
case tok::identifier:
if (Tok.getText().startswith("<#"))
Kind = SyntaxNodeKind::EditorPlaceholder;
@@ -189,11 +188,6 @@ SyntaxModelContext::SyntaxModelContext(SourceFile &SrcFile)
break;
}
case tok::l_square_lit: {
LiteralStartLoc = Loc;
continue;
}
default:
continue;
}
@@ -490,11 +484,13 @@ std::pair<bool, Expr *> ModelASTWalker::walkToExprPre(Expr *E) {
} else if (auto *ObjectE = dyn_cast<ObjectLiteralExpr>(E)) {
SyntaxStructureNode SN;
SN.Kind = SyntaxStructureKind::ObjectLiteralExpression;
SN.Range = charSourceRangeFromSourceRange(SM, E->getSourceRange());
SourceLoc NRStart = ObjectE->getNameLoc();
SourceLoc NREnd = NRStart.getAdvancedLoc(ObjectE->getName().getLength());
SN.Range = charSourceRangeFromSourceRange(SM, ObjectE->getSourceRange());
SourceLoc NRStart = ObjectE->getSourceLoc().getAdvancedLoc(1);
SourceLoc NREnd =
NRStart.getAdvancedLoc(ObjectE->getLiteralKindRawName().size());
SN.NameRange = CharSourceRange(SM, NRStart, NREnd);
SN.BodyRange = innerCharSourceRangeFromSourceRange(SM, E->getSourceRange());
SN.BodyRange =
innerCharSourceRangeFromSourceRange(SM, ObjectE->getSourceRange());
pushStructureNode(SN, E);
} else if (auto *ArrayE = dyn_cast<ArrayExpr>(E)) {

View File

@@ -578,9 +578,11 @@ void Lexer::lexIdentifier() {
/// lexHash - Handle #], #! for shebangs, and the family of #identifiers.
void Lexer::lexHash() {
const char *TokStart = CurPtr-1;
// NOTE: legacy punctuator. Remove in the future.
if (*CurPtr == ']') { // #]
CurPtr++;
return formToken(tok::r_square_lit, TokStart);
CurPtr++;
return formToken(tok::r_square_lit, TokStart);
}
// Allow a hashbang #! line at the beginning of the file.
@@ -1620,11 +1622,16 @@ Restart:
case '@': return formToken(tok::at_sign, TokStart);
case '{': return formToken(tok::l_brace, TokStart);
case '[': {
if (*CurPtr == '#') { // [#
CurPtr++;
return formToken(tok::l_square_lit, TokStart);
}
return formToken(tok::l_square, TokStart);
// NOTE: Legacy punctuator for old object literal syntax.
// Remove in the future.
if (*CurPtr == '#') { // [#
// NOTE: Do NOT include the '#' in the token, unlike in earlier
// versions of Swift that supported the old object literal syntax
// directly. The '#' will be lexed as part of the object literal
// keyword token itself.
return formToken(tok::l_square_lit, TokStart);
}
return formToken(tok::l_square, TokStart);
}
case '(': return formToken(tok::l_paren, TokStart);
case '}': return formToken(tok::r_brace, TokStart);

View File

@@ -1145,21 +1145,6 @@ ParserResult<Expr> Parser::parseExprPostfix(Diag<> ID, bool isExprBasic) {
Result = parseExprCollection();
break;
case tok::l_square_lit: // [#Color(...)#], [#Image(...)#]
// If this is actually a collection literal starting with '[#', handle it
// as such.
if (isCollectionLiteralStartingWithLSquareLit()) {
// Split the token into two.
SourceLoc LSquareLoc = consumeStartingCharacterOfCurrentToken();
// Consume the '[' token.
Result = parseExprCollection(LSquareLoc);
break;
}
Result = parseExprObjectLiteral();
break;
case tok::pound_available: {
// For better error recovery, parse but reject #available in an expr
// context.
@@ -1174,6 +1159,59 @@ ParserResult<Expr> Parser::parseExprPostfix(Diag<> ID, bool isExprBasic) {
break;
}
// NOTE: This is for migrating the old object literal syntax.
// Eventually this block can be removed.
case tok::l_square_lit: {// [#Color(...)#], [#Image(...)#]
// If this is actually a collection literal starting with '[#', handle it
// as such.
if (isCollectionLiteralStartingWithLSquareLit()) {
// Split the token into two.
SourceLoc LSquareLoc = consumeStartingCharacterOfCurrentToken();
// Consume the '[' token.
Result = parseExprCollection(LSquareLoc);
break;
}
auto LSquareLoc = Tok.getLoc();
auto LSquareTokRange = Tok.getRange();
(void)consumeToken(tok::l_square_lit);
if (Tok.is(tok::pound)) {
consumeToken();
if (!Tok.is(tok::identifier))
diagnose(LSquareLoc, diag::expected_object_literal_identifier);
skipUntil(tok::r_square_lit);
Result = makeParserError();
}
else {
Result = parseExprPostfix(ID, isExprBasic);
}
// This should be an invariant based on the check in
// isCollectionLiteralStartingWithLSquareLit().
auto RSquareTokRange = Tok.getRange();
(void)consumeToken(tok::r_square_lit);
// Issue a diagnostic for the legacy syntax and provide a fixit
// to strip away the '[#' and '#]'
diagnose(LSquareLoc, diag::legacy_object_literal_syntax)
.fixItRemoveChars(LSquareTokRange.getStart(), LSquareTokRange.getEnd())
.fixItRemoveChars(RSquareTokRange.getStart(), RSquareTokRange.getEnd());
break;
}
#define POUND_OBJECT_LITERAL(Name, Desc, Proto) case tok::pound_##Name:\
Result = parseExprObjectLiteral(ObjectLiteralExpr::Name);\
break;
#include "swift/Parse/Tokens.def"
#define POUND_OLD_OBJECT_LITERAL(Name, NewName, NewArg, OldArg)\
case tok::pound_##Name:\
Result = parseExprObjectLiteral(ObjectLiteralExpr::NewName, "#" #NewName);\
break;
#include "swift/Parse/Tokens.def"
case tok::code_complete:
Result = makeParserResult(new (Context) CodeCompletionExpr(Tok.getRange()));
Result.setHasCodeCompletion();
@@ -2367,30 +2405,41 @@ ParserResult<Expr> Parser::parseExprList(tok LeftTok, tok RightTok) {
/*Implicit=*/false));
}
// NOTE: this is to detect the old object literal syntax.
// This will be removed in the future.
bool Parser::isCollectionLiteralStartingWithLSquareLit() {
BacktrackingScope backtracking(*this);
(void)consumeToken(tok::l_square_lit);
if (!consumeIf(tok::identifier)) return false;
// Skip over a parenthesized argument, if present.
if (Tok.is(tok::l_paren)) skipSingle();
return Tok.isNot(tok::r_square_lit);
}
BacktrackingScope backtracking(*this);
(void)consumeToken(tok::l_square_lit);
switch (Tok.getKind()) {
// Handle both dengerate '#' and '# identifier'.
case tok::pound:
(void) consumeToken();
if (Tok.is(tok::identifier)) skipSingle();
break;
#define POUND_OBJECT_LITERAL(kw, desc, proto)\
case tok::pound_##kw: (void)consumeToken(); break;
#define POUND_OLD_OBJECT_LITERAL(kw, new_kw, old_arg, new_arg)\
case tok::pound_##kw: (void)consumeToken(); break;
#include "swift/Parse/Tokens.def"
default:
return true;
}
// Skip over a parenthesized argument, if present.
if (Tok.is(tok::l_paren)) skipSingle();
return Tok.isNot(tok::r_square_lit);
}
/// \brief Parse an object literal expression.
///
/// expr-literal:
/// '[#' identifier expr-paren '#]'
/// '#' identifier expr-paren
ParserResult<Expr>
Parser::parseExprObjectLiteral() {
SourceLoc LLitLoc = consumeToken(tok::l_square_lit);
Identifier Name;
SourceLoc NameLoc;
if (parseIdentifier(Name, NameLoc,
diag::expected_identifier_after_l_square_lit)) {
return makeParserError();
}
Parser::parseExprObjectLiteral(ObjectLiteralExpr::LiteralKind LitKind,
StringRef NewName) {
auto PoundTok = Tok;
SourceLoc PoundLoc = consumeToken();
// Parse a tuple of args
if (!Tok.is(tok::l_paren)) {
diagnose(Tok, diag::expected_arg_list_in_object_literal);
@@ -2404,13 +2453,45 @@ Parser::parseExprObjectLiteral() {
if (Arg.isParseError()) {
return makeParserError();
}
if (!Tok.is(tok::r_square_lit)) {
diagnose(Tok, diag::expected_r_square_lit_after_object_literal);
// If the legacy name was used (e.g., #Image instead of #imageLiteral)
// prompt an error and a fixit.
if (!NewName.empty()) {
auto diag =
diagnose(PoundTok, diag::object_literal_legacy_name,
PoundTok.getText(), NewName);
auto Range = PoundTok.getRange();
// Create a FixIt for the keyword.
diag.fixItReplaceChars(Range.getStart(), Range.getEnd(), NewName);
// Try and construct a FixIt for the argument label.
if (TupleExpr *TE = dyn_cast_or_null<TupleExpr>(Arg.get())) {
auto ArgLoc = TE->getElementNameLoc(0);
auto FirstElementName = TE->getElementName(0);
if (ArgLoc.isValid() && !FirstElementName.empty()) {
auto OldArg = FirstElementName.str();
auto NewArg =
llvm::StringSwitch<StringRef>(OldArg)
#define POUND_OLD_OBJECT_LITERAL(kw, new_kw, old_arg, new_arg)\
.Case(#old_arg, #new_arg)
#include "swift/Parse/Tokens.def"
.Default("");
if (!NewArg.empty()) {
auto Loc = TE->getElementNameLoc(0);
diag.fixItReplaceChars(Loc,
Loc.getAdvancedLocOrInvalid(OldArg.size()),
NewArg);
}
}
}
return makeParserError();
}
SourceLoc RLitLoc = consumeToken(tok::r_square_lit);
return makeParserResult(
new (Context) ObjectLiteralExpr(LLitLoc, Name, NameLoc, Arg.get(), RLitLoc,
new (Context) ObjectLiteralExpr(PoundLoc, LitKind, Arg.get(),
/*implicit=*/false));
}

View File

@@ -4996,11 +4996,9 @@ bool FailureDiagnosis::visitObjectLiteralExpr(ObjectLiteralExpr *E) {
// Figure out what import to suggest.
auto &Ctx = CS->getASTContext();
const auto &target = Ctx.LangOpts.Target;
StringRef plainName = E->getName().str();
StringRef importModule;
StringRef importDefaultTypeName;
if (protocol == Ctx.getProtocol(KnownProtocolKind::ColorLiteralConvertible)) {
plainName = "color";
if (target.isMacOSX()) {
importModule = "AppKit";
importDefaultTypeName = "NSColor";
@@ -5010,7 +5008,6 @@ bool FailureDiagnosis::visitObjectLiteralExpr(ObjectLiteralExpr *E) {
}
} else if (protocol == Ctx.getProtocol(
KnownProtocolKind::ImageLiteralConvertible)) {
plainName = "image";
if (target.isMacOSX()) {
importModule = "AppKit";
importDefaultTypeName = "NSImage";
@@ -5020,12 +5017,12 @@ bool FailureDiagnosis::visitObjectLiteralExpr(ObjectLiteralExpr *E) {
}
} else if (protocol == Ctx.getProtocol(
KnownProtocolKind::FileReferenceLiteralConvertible)) {
plainName = "file reference";
importModule = "Foundation";
importDefaultTypeName = Ctx.getSwiftName(KnownFoundationEntity::NSURL);
}
// Emit the diagnostic.
const auto plainName = E->getLiteralKindPlainName();
TC.diagnose(E->getLoc(), diag::object_literal_default_type_missing,
plainName);
if (!importModule.empty()) {

View File

@@ -1363,8 +1363,8 @@ namespace {
auto &tc = CS.getTypeChecker();
auto protocol = tc.getLiteralProtocol(expr);
if (!protocol) {
tc.diagnose(expr->getLoc(), diag::use_unknown_object_literal,
expr->getName());
tc.diagnose(expr->getLoc(), diag::use_unknown_object_literal_protocol,
expr->getLiteralKindPlainName());
return nullptr;
}

View File

@@ -155,18 +155,11 @@ ProtocolDecl *TypeChecker::getLiteralProtocol(Expr *expr) {
}
if (auto E = dyn_cast<ObjectLiteralExpr>(expr)) {
Identifier name = E->getName();
if (name.str().equals("Color")) {
return getProtocol(expr->getLoc(),
KnownProtocolKind::ColorLiteralConvertible);
} else if (name.str().equals("Image")) {
return getProtocol(expr->getLoc(),
KnownProtocolKind::ImageLiteralConvertible);
} else if (name.str().equals("FileReference")) {
return getProtocol(expr->getLoc(),
KnownProtocolKind::FileReferenceLiteralConvertible);
} else {
return nullptr;
switch (E->getLiteralKind()) {
#define POUND_OBJECT_LITERAL(Name, Desc, Protocol)\
case ObjectLiteralExpr::Name:\
return getProtocol(expr->getLoc(), KnownProtocolKind::Protocol);
#include "swift/Parse/Tokens.def"
}
}
@@ -174,22 +167,21 @@ ProtocolDecl *TypeChecker::getLiteralProtocol(Expr *expr) {
}
DeclName TypeChecker::getObjectLiteralConstructorName(ObjectLiteralExpr *expr) {
Identifier name = expr->getName();
if (name.str().equals("Color")) {
return DeclName(Context, Context.Id_init,
{ Context.getIdentifier("colorLiteralRed"),
Context.getIdentifier("green"),
Context.getIdentifier("blue"),
Context.getIdentifier("alpha") });
} else if (name.str().equals("Image")) {
return DeclName(Context, Context.Id_init,
{ Context.getIdentifier("imageLiteral") });
} else if (name.str().equals("FileReference")) {
return DeclName(Context, Context.Id_init,
{ Context.getIdentifier("fileReferenceLiteral") });
} else {
return DeclName();
switch (expr->getLiteralKind()) {
case ObjectLiteralExpr::colorLiteral: {
return DeclName(Context, Context.Id_init,
{ Context.getIdentifier("red"),
Context.getIdentifier("green"),
Context.getIdentifier("blue"),
Context.getIdentifier("alpha") });
}
case ObjectLiteralExpr::imageLiteral:
case ObjectLiteralExpr::fileLiteral: {
return DeclName(Context, Context.Id_init,
{ Context.getIdentifier("resourceName") });
}
}
llvm_unreachable("unknown literal constructor");
}
Module *TypeChecker::getStdlibModule(const DeclContext *dc) {

View File

@@ -68,7 +68,7 @@ public func NSApplicationMain(
) -> Int32
extension NSColor : _ColorLiteralConvertible {
public required convenience init(colorLiteralRed red: Float, green: Float,
public required convenience init(red: Float, green: Float,
blue: Float, alpha: Float) {
self.init(srgbRed: CGFloat(red), green: CGFloat(green),
blue: CGFloat(blue), alpha: CGFloat(alpha))
@@ -82,7 +82,7 @@ extension NSImage : _ImageLiteralConvertible {
self.init(named: name)
}
public required convenience init(imageLiteral name: String) {
public required convenience init(resourceName name: String) {
self.init(failableImageLiteral: name)
}
}

View File

@@ -1338,7 +1338,7 @@ extension NSURL : _FileReferenceLiteralConvertible {
self.init(fileURLWithPath: fullPath)
}
public required convenience init(fileReferenceLiteral path: String) {
public required convenience init(resourceName path: String) {
self.init(failableFileReferenceLiteral: path)
}
}

View File

@@ -219,8 +219,8 @@ extension UIView : CustomPlaygroundQuickLookable {
#endif
extension UIColor : _ColorLiteralConvertible {
public required convenience init(colorLiteralRed red: Float, green: Float,
blue: Float, alpha: Float) {
@nonobjc public required convenience init(red: Float, green: Float,
blue: Float, alpha: Float) {
self.init(red: CGFloat(red), green: CGFloat(green),
blue: CGFloat(blue), alpha: CGFloat(alpha))
}
@@ -233,7 +233,7 @@ extension UIImage : _ImageLiteralConvertible {
self.init(named: name)
}
public required convenience init(imageLiteral name: String) {
public required convenience init(resourceName name: String) {
self.init(failableImageLiteral: name)
}
}

View File

@@ -197,21 +197,21 @@ public protocol StringInterpolationConvertible {
}
/// Conforming types can be initialized with color literals (e.g.
/// `[#Color(colorLiteralRed: 1, green: 0, blue: 0, alpha: 1)#]`).
/// `#colorLiteral(red: 1, green: 0, blue: 0, alpha: 1)`).
public protocol _ColorLiteralConvertible {
init(colorLiteralRed: Float, green: Float, blue: Float, alpha: Float)
init(red: Float, green: Float, blue: Float, alpha: Float)
}
/// Conforming types can be initialized with image literals (e.g.
/// `[#Image(imageLiteral: "hi.png")#]`).
/// `#imageLiteral(resourceName: "hi.png")`).
public protocol _ImageLiteralConvertible {
init(imageLiteral: String)
init(resourceName: String)
}
/// Conforming types can be initialized with strings (e.g.
/// `[#FileReference(fileReferenceLiteral: "resource.txt")#]`).
/// `#fileLiteral(resourceName: "resource.txt")`).
public protocol _FileReferenceLiteralConvertible {
init(fileReferenceLiteral: String)
init(resourceName: String)
}
/// A container is destructor safe if whether it may store to memory on

View File

@@ -40,8 +40,8 @@ func testAll0() {
// NO_CONTEXT_0-DAG: Literal[String]/None: "{#(abc)#}"[#String#];
// NO_CONTEXT_0-DAG: Literal[Array]/None: [{#(values)#}][#Array#];
// NO_CONTEXT_0-DAG: Literal[Dictionary]/None: [{#(key)#}: {#(value)#}][#Dictionary#];
// NO_CONTEXT_0-DAG: Literal[_Color]/None: [#Color({#colorLiteralRed: Float#}, {#green: Float#}, {#blue: Float#}, {#alpha: Float#})#];
// NO_CONTEXT_0-DAG: Literal[_Image]/None: [#Image({#imageLiteral: String#})#];
// NO_CONTEXT_0-DAG: Literal[_Color]/None: #colorLiteral({#red: Float#}, {#green: Float#}, {#blue: Float#}, {#alpha: Float#});
// NO_CONTEXT_0-DAG: Literal[_Image]/None: #imageLiteral({#resourceName: String#});
// NO_CONTEXT_0: End completions
}
@@ -201,32 +201,32 @@ func testTuple2() {
// TUPLE_2: Literal[Tuple]/None/TypeRelation[Identical]: ({#(values)#})[#(MyInt1, MyString1, MyDouble1)#];
struct MyColor1: _ColorLiteralConvertible {
init(colorLiteralRed: Float, green: Float, blue: Float, alpha: Float) {}
init(red: Float, green: Float, blue: Float, alpha: Float) {}
}
func testColor0() {
let x: Int = #^COLOR_0^#
}
// COLOR_0: Literal[_Color]/None: [#Color({#colorLiteralRed: Float#}, {#green: Float#}, {#blue: Float#}, {#alpha: Float#})#];
// COLOR_0: Literal[_Color]/None: #colorLiteral({#red: Float#}, {#green: Float#}, {#blue: Float#}, {#alpha: Float#});
func testColor1() {
let x: MyColor1 = #^COLOR_1^#
}
// COLOR_1: Literal[_Color]/None/TypeRelation[Identical]: [#Color({#colorLiteralRed: Float#}, {#green: Float#}, {#blue: Float#}, {#alpha: Float#})#][#MyColor1#];
// COLOR_1: Literal[_Color]/None/TypeRelation[Identical]: #colorLiteral({#red: Float#}, {#green: Float#}, {#blue: Float#}, {#alpha: Float#})[#MyColor1#];
func testColor2() {
let x: MyColor1? = #^COLOR_2^#
}
// COLOR_2: Literal[_Color]/None/TypeRelation[Convertible]: [#Color({#colorLiteralRed: Float#}, {#green: Float#}, {#blue: Float#}, {#alpha: Float#})#][#MyColor1#];
// COLOR_2: Literal[_Color]/None/TypeRelation[Convertible]: #colorLiteral({#red: Float#}, {#green: Float#}, {#blue: Float#}, {#alpha: Float#})[#MyColor1#];
struct MyImage1: _ImageLiteralConvertible {
init(imageLiteral: String) {}
init(resourceName: String) {}
}
func testImage0() {
let x: Int = #^IMAGE_0^#
}
// IMAGE_0: Literal[_Image]/None: [#Image({#imageLiteral: String#})#];
// IMAGE_0: Literal[_Image]/None: #imageLiteral({#resourceName: String#});
func testImage1() {
let x: MyImage1 = #^IMAGE_1^#
}
// IMAGE_1: Literal[_Image]/None/TypeRelation[Identical]: [#Image({#imageLiteral: String#})#][#MyImage1#];
// IMAGE_1: Literal[_Image]/None/TypeRelation[Identical]: #imageLiteral({#resourceName: String#})[#MyImage1#];

View File

@@ -1,15 +1,15 @@
// RUN: %swift-ide-test -structure -source-filename %s | FileCheck %s
struct S: _ColorLiteralConvertible {
init(colorLiteralRed: Float, green: Float, blue: Float, alpha: Float) {}
init(red: Float, green: Float, blue: Float, alpha: Float) {}
}
// CHECK: <gvar>let <name>y</name>: S = <object-literal-expression>[#<name>Color</name>(<param><name>colorLiteralRed</name>: 1</param>, <param><name>green</name>: 0</param>, <param><name>blue</name>: 0</param>, <param><name>alpha</name>: 1</param>)#]</object-literal-expression></gvar>
let y: S = [#Color(colorLiteralRed: 1, green: 0, blue: 0, alpha: 1)#]
// CHECK: <gvar>let <name>y</name>: S = <object-literal-expression>#<name>colorLiteral</name>(<param><name>red</name>: 1</param>, <param><name>green</name>: 0</param>, <param><name>blue</name>: 0</param>, <param><name>alpha</name>: 1</param>)</object-literal-expression></gvar>
let y: S = #colorLiteral(red: 1, green: 0, blue: 0, alpha: 1)
struct I: _ImageLiteralConvertible {
init?(imageLiteral: String) {}
init?(resourceName: String) {}
}
// CHECK: <gvar>let <name>z</name>: I? = <object-literal-expression>[#<name>Image</name>(<param><name>imageLiteral</name>: "hello.png"</param>)#]</object-literal-expression></gvar>
let z: I? = [#Image(imageLiteral: "hello.png")#]
// CHECK: <gvar>let <name>z</name>: I? = <object-literal-expression>#<name>imageLiteral</name>(<param><name>resourceName</name>: "hello.png"</param>)</object-literal-expression></gvar>
let z: I? = #imageLiteral(resourceName: "hello.png")

View File

@@ -17,8 +17,8 @@ import gizmo
class SwiftGizmo : Gizmo {
init(red: Float, green: Float, blue: Float) { }
func color(red red: Float, green: Float, blue: Float)
func otherColorFor(red red: Float, green: Float, blue: Float)
func color(red: Float, green: Float, blue: Float)
func otherColorFor(red: Float, green: Float, blue: Float)
}
sil_vtable SwiftGizmo {}

View File

@@ -1,6 +1,6 @@
// RUN: %target-parse-verify-swift
let _ = [##] // expected-error{{expected identifier after '[#' in object literal expression}} expected-error{{consecutive statements on a line must be separated by ';'}} {{11-11=;}} expected-error{{expected expression}}
let _ = [#what#] // expected-error{{expected argument list in object literal}} expected-error{{consecutive statements on a line must be separated by ';'}} {{15-15=;}} expected-error{{expected expression}}
let _ = [#what()#] // expected-error{{use of unknown object literal name 'what'}}
let _ = [#Color( // expected-error{{expected expression in container literal}}
let _ = [##] // expected-error{{expected identifier after '#' in object literal expression}} expected-error{{object literal syntax no longer uses '[# ... #]'}} {{9-10=}} {{11-13=}}
let _ = [#what#] // expected-error{{object literal syntax no longer uses '[# ... #]'}} {{9-10=}} {{15-17=}}
let _ = [#what()#] // expected-error{{object literal syntax no longer uses '[# ... #]'}} {{9-10=}} {{17-19=}}
let _ = [#colorLiteral( // expected-error{{expected ',' separator}} expected-error{{expected expression in list of expressions}}

View File

@@ -2,23 +2,23 @@
// REQUIRES: OS=ios
struct S: _ColorLiteralConvertible {
init(colorLiteralRed: Float, green: Float, blue: Float, alpha: Float) {}
init(red: Float, green: Float, blue: Float, alpha: Float) {}
}
let y: S = [#Color(colorLiteralRed: 1, green: 0, blue: 0, alpha: 1)#]
let y2 = [#Color(colorLiteralRed: 1, green: 0, blue: 0, alpha: 1)#] // expected-error{{could not infer type of color literal}} expected-note{{import UIKit to use 'UIColor' as the default color literal type}}
let y3 = [#Color(colorLiteralRed: 1, bleen: 0, grue: 0, alpha: 1)#] // expected-error{{cannot convert value of type '(colorLiteralRed: Int, bleen: Int, grue: Int, alpha: Int)' to expected argument type '(colorLiteralRed: Float, green: Float, blue: Float, alpha: Float)'}}
let y: S = #colorLiteral(red: 1, green: 0, blue: 0, alpha: 1)
let y2 = #colorLiteral(red: 1, green: 0, blue: 0, alpha: 1) // expected-error{{could not infer type of color literal}} expected-note{{import UIKit to use 'UIColor' as the default color literal type}}
let y3 = #colorLiteral(red: 1, bleen: 0, grue: 0, alpha: 1) // expected-error{{cannot convert value of type '(red: Int, bleen: Int, grue: Int, alpha: Int)' to expected argument type '(red: Float, green: Float, blue: Float, alpha: Float)'}}
struct I: _ImageLiteralConvertible {
init(imageLiteral: String) {}
init(resourceName: String) {}
}
let z: I = [#Image(imageLiteral: "hello.png")#]
let z2 = [#Image(imageLiteral: "hello.png")#] // expected-error{{could not infer type of image literal}} expected-note{{import UIKit to use 'UIImage' as the default image literal type}}
let z: I = #imageLiteral(resourceName: "hello.png")
let z2 = #imageLiteral(resourceName: "hello.png") // expected-error{{could not infer type of image literal}} expected-note{{import UIKit to use 'UIImage' as the default image literal type}}
struct Path: _FileReferenceLiteralConvertible {
init(fileReferenceLiteral: String) {}
init(resourceName: String) {}
}
let p1: Path = [#FileReference(fileReferenceLiteral: "what.txt")#]
let p2 = [#FileReference(fileReferenceLiteral: "what.txt")#] // expected-error{{could not infer type of file reference literal}} expected-note{{import Foundation to use 'NSURL' as the default file reference literal type}}
let p1: Path = #fileLiteral(resourceName: "what.txt")
let p2 = #fileLiteral(resourceName: "what.txt") // expected-error{{could not infer type of file reference literal}} expected-note{{import Foundation to use 'NSURL' as the default file reference literal type}}

View File

@@ -2,23 +2,23 @@
// REQUIRES: OS=macosx
struct S: _ColorLiteralConvertible {
init(colorLiteralRed: Float, green: Float, blue: Float, alpha: Float) {}
init(red: Float, green: Float, blue: Float, alpha: Float) {}
}
let y: S = [#Color(colorLiteralRed: 1, green: 0, blue: 0, alpha: 1)#]
let y2 = [#Color(colorLiteralRed: 1, green: 0, blue: 0, alpha: 1)#] // expected-error{{could not infer type of color literal}} expected-note{{import AppKit to use 'NSColor' as the default color literal type}}
let y3 = [#Color(colorLiteralRed: 1, bleen: 0, grue: 0, alpha: 1)#] // expected-error{{cannot convert value of type '(colorLiteralRed: Int, bleen: Int, grue: Int, alpha: Int)' to expected argument type '(colorLiteralRed: Float, green: Float, blue: Float, alpha: Float)'}}
let y: S = #colorLiteral(red: 1, green: 0, blue: 0, alpha: 1)
let y2 = #colorLiteral(red: 1, green: 0, blue: 0, alpha: 1) // expected-error{{could not infer type of color literal}} expected-note{{import AppKit to use 'NSColor' as the default color literal type}}
let y3 = #colorLiteral(red: 1, bleen: 0, grue: 0, alpha: 1) // expected-error{{cannot convert value of type '(red: Int, bleen: Int, grue: Int, alpha: Int)' to expected argument type '(red: Float, green: Float, blue: Float, alpha: Float)'}}
struct I: _ImageLiteralConvertible {
init(imageLiteral: String) {}
init(resourceName: String) {}
}
let z: I = [#Image(imageLiteral: "hello.png")#]
let z2 = [#Image(imageLiteral: "hello.png")#] // expected-error{{could not infer type of image literal}} expected-note{{import AppKit to use 'NSImage' as the default image literal type}}
let z: I = #imageLiteral(resourceName: "hello.png")
let z2 = #imageLiteral(resourceName: "hello.png") // expected-error{{could not infer type of image literal}} expected-note{{import AppKit to use 'NSImage' as the default image literal type}}
struct Path: _FileReferenceLiteralConvertible {
init(fileReferenceLiteral: String) {}
init(resourceName: String) {}
}
let p1: Path = [#FileReference(fileReferenceLiteral: "what.txt")#]
let p2 = [#FileReference(fileReferenceLiteral: "what.txt")#] // expected-error{{could not infer type of file reference literal}} expected-note{{import Foundation to use 'NSURL' as the default file reference literal type}}
let p1: Path = #fileLiteral(resourceName: "what.txt")
let p2 = #fileLiteral(resourceName: "what.txt") // expected-error{{could not infer type of file reference literal}} expected-note{{import Foundation to use 'NSURL' as the default file reference literal type}}

View File

@@ -18,6 +18,8 @@ func test001() {
// TOP_LEVEL_0-NEXT: aaa(x: B)
// TOP_LEVEL_0-NEXT: aaa(x: B, y: B)
// TOP_LEVEL_0-NEXT: aaa(x: B, y: B)
// TOP_LEVEL_0-NEXT: #colorLiteral(red: Float, green: Float, blue: Float, alpha: Float)
// TOP_LEVEL_0-NEXT: #imageLiteral(resourceName: String)
// TOP_LEVEL_0-NEXT: aab()
struct Foo {

View File

@@ -86,8 +86,8 @@ func test2() {
// EXPR: "abc"
// EXPR: true
// EXPR: false
// EXPR: [#Color(colorLiteralRed: Float, green: Float, blue: Float, alpha: Float)#]
// EXPR: [#Image(imageLiteral: String)#]
// EXPR: #colorLiteral(red: Float, green: Float, blue: Float, alpha: Float)
// EXPR: #imageLiteral(resourceName: String)
// EXPR: [values]
// EXPR: [key: value]
// EXPR: (values)
@@ -107,8 +107,8 @@ func test3(x: Int) {
// EXPR_TOP_1: "abc"
// EXPR_TOP_1: true
// EXPR_TOP_1: false
// EXPR_TOP_1: [#Color(colorLiteralRed: Float, green: Float, blue: Float, alpha: Float)#]
// EXPR_TOP_1: [#Image(imageLiteral: String)#]
// EXPR_TOP_1: #colorLiteral(red: Float, green: Float, blue: Float, alpha: Float)
// EXPR_TOP_1: #imageLiteral(resourceName: String)
// EXPR_TOP_1: [values]
// EXPR_TOP_1: [key: value]
// EXPR_TOP_1: (values)
@@ -132,8 +132,8 @@ func test4(x: Int) {
// EXPR_TOP_3: "abc"
// EXPR_TOP_3: true
// EXPR_TOP_3: false
// EXPR_TOP_3: [#Color(colorLiteralRed: Float, green: Float, blue: Float, alpha: Float)#]
// EXPR_TOP_3: [#Image(imageLiteral: String)#]
// EXPR_TOP_3: #colorLiteral(red: Float, green: Float, blue: Float, alpha: Float)
// EXPR_TOP_3: #imageLiteral(resourceName: String)
// EXPR_TOP_3: [values]
// EXPR_TOP_3: [key: value]
// EXPR_TOP_3: (values)

View File

@@ -1,5 +1,5 @@
// RUN: %sourcekitd-test -req=structure %s -- -module-name StructureTest %s | %sed_clean > %t.response
// RUN: diff -u %s.response %t.response
let color: S = [#Color(colorLiteralRed: 1, green: 0, blue: 0, alpha: 1)#]
let image: I? = [#Image(imageLiteral: "hello.png")#]
let color: S = #colorLiteral(red: 1, green: 0, blue: 0, alpha: 1)
let image: I? = #imageLiteral(resourceName: "hello.png")

View File

@@ -1,6 +1,6 @@
{
key.offset: 0,
key.length: 271,
key.length: 267,
key.diagnostic_stage: source.diagnostic.stage.swift.parse,
key.substructure: [
{
@@ -8,7 +8,7 @@
key.accessibility: source.lang.swift.accessibility.internal,
key.name: "color",
key.offset: 144,
key.length: 73,
key.length: 65,
key.typename: "S",
key.nameoffset: 148,
key.namelength: 5,
@@ -20,52 +20,52 @@
},
{
key.kind: source.lang.swift.expr.object_literal,
key.name: "Color",
key.name: "colorLiteral",
key.offset: 159,
key.length: 58,
key.nameoffset: 161,
key.namelength: 5,
key.bodyoffset: 161,
key.bodylength: 54,
key.length: 50,
key.nameoffset: 160,
key.namelength: 12,
key.bodyoffset: 172,
key.bodylength: 36,
key.substructure: [
{
key.kind: source.lang.swift.decl.var.parameter,
key.name: "colorLiteralRed",
key.offset: 167,
key.length: 18,
key.nameoffset: 167,
key.namelength: 15,
key.bodyoffset: 184,
key.name: "red",
key.offset: 173,
key.length: 6,
key.nameoffset: 173,
key.namelength: 3,
key.bodyoffset: 178,
key.bodylength: 1
},
{
key.kind: source.lang.swift.decl.var.parameter,
key.name: "green",
key.offset: 187,
key.offset: 181,
key.length: 8,
key.nameoffset: 187,
key.nameoffset: 181,
key.namelength: 5,
key.bodyoffset: 194,
key.bodyoffset: 188,
key.bodylength: 1
},
{
key.kind: source.lang.swift.decl.var.parameter,
key.name: "blue",
key.offset: 197,
key.offset: 191,
key.length: 7,
key.nameoffset: 197,
key.nameoffset: 191,
key.namelength: 4,
key.bodyoffset: 203,
key.bodyoffset: 197,
key.bodylength: 1
},
{
key.kind: source.lang.swift.decl.var.parameter,
key.name: "alpha",
key.offset: 206,
key.offset: 200,
key.length: 8,
key.nameoffset: 206,
key.nameoffset: 200,
key.namelength: 5,
key.bodyoffset: 213,
key.bodyoffset: 207,
key.bodylength: 1
}
]
@@ -74,30 +74,30 @@
key.kind: source.lang.swift.decl.var.global,
key.accessibility: source.lang.swift.accessibility.internal,
key.name: "image",
key.offset: 218,
key.length: 52,
key.offset: 210,
key.length: 56,
key.typename: "I?",
key.nameoffset: 222,
key.nameoffset: 214,
key.namelength: 5
},
{
key.kind: source.lang.swift.expr.object_literal,
key.name: "Image",
key.offset: 234,
key.length: 36,
key.nameoffset: 236,
key.namelength: 5,
key.bodyoffset: 236,
key.bodylength: 32,
key.name: "imageLiteral",
key.offset: 226,
key.length: 40,
key.nameoffset: 227,
key.namelength: 12,
key.bodyoffset: 239,
key.bodylength: 26,
key.substructure: [
{
key.kind: source.lang.swift.decl.var.parameter,
key.name: "imageLiteral",
key.offset: 242,
key.name: "resourceName",
key.offset: 240,
key.length: 25,
key.nameoffset: 242,
key.nameoffset: 240,
key.namelength: 12,
key.bodyoffset: 256,
key.bodyoffset: 254,
key.bodylength: 11
}
]

View File

@@ -1,4 +1,4 @@
// RUN: %sourcekitd-test -req=syntax-map %s > %t.response
// RUN: %sourcekitd-test -req=syntax-map %s | %sed_clean > %t.response
// RUN: diff -u %s.response %t.response
let x = [#Cloud(tube: true)#]
let x = #Cloud(tube: true)

View File

@@ -1,32 +1,75 @@
{
key.offset: 0,
key.length: 129,
key.length: 139,
key.diagnostic_stage: source.diagnostic.stage.swift.parse,
key.syntaxmap: [
{
key.kind: source.lang.swift.syntaxtype.comment,
key.offset: 0,
key.length: 58
key.length: 71
},
{
key.kind: source.lang.swift.syntaxtype.comment,
key.offset: 58,
key.offset: 71,
key.length: 40
},
{
key.kind: source.lang.swift.syntaxtype.keyword,
key.offset: 99,
key.offset: 112,
key.length: 3
},
{
key.kind: source.lang.swift.syntaxtype.identifier,
key.offset: 103,
key.offset: 116,
key.length: 1
},
{
key.kind: source.lang.swift.syntaxtype.objectliteral,
key.offset: 107,
key.length: 21
key.kind: source.lang.swift.syntaxtype.identifier,
key.offset: 121,
key.length: 5
},
{
key.kind: source.lang.swift.syntaxtype.identifier,
key.offset: 127,
key.length: 4
},
{
key.kind: source.lang.swift.syntaxtype.keyword,
key.offset: 133,
key.length: 4
}
],
key.diagnostics: [
{
key.line: 4,
key.column: 8,
key.filepath: syntaxmap-object-literals.swift,
key.severity: source.diagnostic.severity.error,
key.description: "consecutive statements on a line must be separated by ';'",
key.diagnostic_stage: source.diagnostic.stage.swift.parse,
key.fixits: [
{
key.offset: 119,
key.length: 0,
key.sourcetext: ";"
}
]
},
{
key.line: 4,
key.column: 9,
key.filepath: syntaxmap-object-literals.swift,
key.severity: source.diagnostic.severity.error,
key.description: "expected initial value after '='",
key.diagnostic_stage: source.diagnostic.stage.swift.parse
},
{
key.line: 4,
key.column: 9,
key.filepath: syntaxmap-object-literals.swift,
key.severity: source.diagnostic.severity.error,
key.description: "expected expression",
key.diagnostic_stage: source.diagnostic.stage.swift.parse
}
]
}