From 3cabdeaa61c6aeb1cbbefa2432ea5231270c9f98 Mon Sep 17 00:00:00 2001 From: odersky Date: Wed, 14 Feb 2024 14:04:52 +0100 Subject: [PATCH 1/5] Parsing and desugaring of new into modifier on parameter types --- .../src/dotty/tools/dotc/ast/Desugar.scala | 23 ++--- compiler/src/dotty/tools/dotc/ast/Trees.scala | 1 + compiler/src/dotty/tools/dotc/ast/untpd.scala | 14 ++- .../dotty/tools/dotc/core/Definitions.scala | 5 +- .../src/dotty/tools/dotc/core/StdNames.scala | 2 +- .../src/dotty/tools/dotc/core/Types.scala | 30 +----- .../dotty/tools/dotc/parsing/Parsers.scala | 95 +++++++++++++------ .../src/dotty/tools/dotc/parsing/Tokens.scala | 3 + .../tools/dotc/printing/PlainPrinter.scala | 6 +- .../tools/dotc/printing/RefinedPrinter.scala | 5 +- .../src/dotty/tools/dotc/typer/Checking.scala | 2 +- .../src/dotty/tools/dotc/typer/Typer.scala | 3 - docs/_docs/internals/syntax.md | 6 ++ .../scala/annotation/allowConversions.scala | 10 -- 14 files changed, 107 insertions(+), 98 deletions(-) delete mode 100644 library/src/scala/annotation/allowConversions.scala diff --git a/compiler/src/dotty/tools/dotc/ast/Desugar.scala b/compiler/src/dotty/tools/dotc/ast/Desugar.scala index 9591bc5a93f0..d73e9b29c492 100644 --- a/compiler/src/dotty/tools/dotc/ast/Desugar.scala +++ b/compiler/src/dotty/tools/dotc/ast/Desugar.scala @@ -178,21 +178,7 @@ object desugar { val valName = normalizeName(vdef, tpt).asTermName var mods1 = vdef.mods - def dropInto(tpt: Tree): Tree = tpt match - case Into(tpt1) => - mods1 = vdef.mods.withAddedAnnotation( - TypedSplice( - Annotation(defn.AllowConversionsAnnot, tpt.span.startPos).tree)) - tpt1 - case ByNameTypeTree(tpt1) => - cpy.ByNameTypeTree(tpt)(dropInto(tpt1)) - case PostfixOp(tpt1, op) if op.name == tpnme.raw.STAR => - cpy.PostfixOp(tpt)(dropInto(tpt1), op) - case _ => - tpt - - val vdef1 = cpy.ValDef(vdef)(name = valName, tpt = dropInto(tpt)) - .withMods(mods1) + val vdef1 = cpy.ValDef(vdef)(name = valName).withMods(mods1) if isSetterNeeded(vdef) then val setterParam = makeSyntheticParameter(tpt = SetterParamTree().watching(vdef)) @@ -1876,8 +1862,11 @@ object desugar { assert(ctx.mode.isExpr || ctx.reporter.errorsReported || ctx.mode.is(Mode.Interactive), ctx.mode) Select(t, op.name) case PrefixOp(op, t) => - val nspace = if (ctx.mode.is(Mode.Type)) tpnme else nme - Select(t, nspace.UNARY_PREFIX ++ op.name) + if op.name == tpnme.into then + Annotated(t, New(ref(defn.IntoAnnot.typeRef), Nil :: Nil)) + else + val nspace = if (ctx.mode.is(Mode.Type)) tpnme else nme + Select(t, nspace.UNARY_PREFIX ++ op.name) case ForDo(enums, body) => makeFor(nme.foreach, nme.foreach, enums, body) orElse tree case ForYield(enums, body) => diff --git a/compiler/src/dotty/tools/dotc/ast/Trees.scala b/compiler/src/dotty/tools/dotc/ast/Trees.scala index 4ec41b95a90b..a6dad7aa6ec3 100644 --- a/compiler/src/dotty/tools/dotc/ast/Trees.scala +++ b/compiler/src/dotty/tools/dotc/ast/Trees.scala @@ -304,6 +304,7 @@ object Trees { def withFlags(flags: FlagSet): ThisTree[Untyped] = withMods(untpd.Modifiers(flags)) def withAddedFlags(flags: FlagSet): ThisTree[Untyped] = withMods(rawMods | flags) + def withAddedAnnotation(annot: Tree[Untyped]): ThisTree[Untyped] = withMods(rawMods.withAddedAnnotation(annot)) /** Destructively update modifiers. To be used with care. */ def setMods(mods: untpd.Modifiers): Unit = myMods = mods diff --git a/compiler/src/dotty/tools/dotc/ast/untpd.scala b/compiler/src/dotty/tools/dotc/ast/untpd.scala index aabfdd97d7bd..eb5ec1872ff5 100644 --- a/compiler/src/dotty/tools/dotc/ast/untpd.scala +++ b/compiler/src/dotty/tools/dotc/ast/untpd.scala @@ -118,7 +118,6 @@ object untpd extends Trees.Instance[Untyped] with UntypedTreeInfo { case class ContextBounds(bounds: TypeBoundsTree, cxBounds: List[Tree])(implicit @constructorOnly src: SourceFile) extends TypTree case class PatDef(mods: Modifiers, pats: List[Tree], tpt: Tree, rhs: Tree)(implicit @constructorOnly src: SourceFile) extends DefTree case class ExtMethods(paramss: List[ParamClause], methods: List[Tree])(implicit @constructorOnly src: SourceFile) extends Tree - case class Into(tpt: Tree)(implicit @constructorOnly src: SourceFile) extends Tree case class MacroTree(expr: Tree)(implicit @constructorOnly src: SourceFile) extends Tree case class ImportSelector(imported: Ident, renamed: Tree = EmptyTree, bound: Tree = EmptyTree)(implicit @constructorOnly src: SourceFile) extends Tree { @@ -552,6 +551,12 @@ object untpd extends Trees.Instance[Untyped] with UntypedTreeInfo { ValDef(nme.syntheticParamName(n), if (tpt == null) TypeTree() else tpt, EmptyTree) .withFlags(flags) + def isInto(t: Tree)(using Context): Boolean = t match + case PrefixOp(Ident(tpnme.into), _) => true + case Function(_, res) => isInto(res) + case Parens(t) => isInto(t) + case _ => false + def lambdaAbstract(params: List[ValDef] | List[TypeDef], tpt: Tree)(using Context): Tree = params match case Nil => tpt @@ -666,9 +671,6 @@ object untpd extends Trees.Instance[Untyped] with UntypedTreeInfo { def ExtMethods(tree: Tree)(paramss: List[ParamClause], methods: List[Tree])(using Context): Tree = tree match case tree: ExtMethods if (paramss eq tree.paramss) && (methods == tree.methods) => tree case _ => finalize(tree, untpd.ExtMethods(paramss, methods)(tree.source)) - def Into(tree: Tree)(tpt: Tree)(using Context): Tree = tree match - case tree: Into if tpt eq tree.tpt => tree - case _ => finalize(tree, untpd.Into(tpt)(tree.source)) def ImportSelector(tree: Tree)(imported: Ident, renamed: Tree, bound: Tree)(using Context): Tree = tree match { case tree: ImportSelector if (imported eq tree.imported) && (renamed eq tree.renamed) && (bound eq tree.bound) => tree case _ => finalize(tree, untpd.ImportSelector(imported, renamed, bound)(tree.source)) @@ -734,8 +736,6 @@ object untpd extends Trees.Instance[Untyped] with UntypedTreeInfo { cpy.PatDef(tree)(mods, transform(pats), transform(tpt), transform(rhs)) case ExtMethods(paramss, methods) => cpy.ExtMethods(tree)(transformParamss(paramss), transformSub(methods)) - case Into(tpt) => - cpy.Into(tree)(transform(tpt)) case ImportSelector(imported, renamed, bound) => cpy.ImportSelector(tree)(transformSub(imported), transform(renamed), transform(bound)) case Number(_, _) | TypedSplice(_) => @@ -791,8 +791,6 @@ object untpd extends Trees.Instance[Untyped] with UntypedTreeInfo { this(this(this(x, pats), tpt), rhs) case ExtMethods(paramss, methods) => this(paramss.foldLeft(x)(apply), methods) - case Into(tpt) => - this(x, tpt) case ImportSelector(imported, renamed, bound) => this(this(this(x, imported), renamed), bound) case Number(_, _) => diff --git a/compiler/src/dotty/tools/dotc/core/Definitions.scala b/compiler/src/dotty/tools/dotc/core/Definitions.scala index 3cde29ee3d79..9d610f23a067 100644 --- a/compiler/src/dotty/tools/dotc/core/Definitions.scala +++ b/compiler/src/dotty/tools/dotc/core/Definitions.scala @@ -642,8 +642,6 @@ class Definitions { @tu lazy val RepeatedParamClass: ClassSymbol = enterSpecialPolyClass(tpnme.REPEATED_PARAM_CLASS, Covariant, Seq(ObjectType, SeqType)) - @tu lazy val IntoType: TypeSymbol = enterAliasType(tpnme.INTO, HKTypeLambda(TypeBounds.empty :: Nil)(_.paramRefs(0))) - // fundamental classes @tu lazy val StringClass: ClassSymbol = requiredClass("java.lang.String") def StringType: Type = StringClass.typeRef @@ -1002,7 +1000,6 @@ class Definitions { @tu lazy val JavaAnnotationClass: ClassSymbol = requiredClass("java.lang.annotation.Annotation") // Annotation classes - @tu lazy val AllowConversionsAnnot: ClassSymbol = requiredClass("scala.annotation.allowConversions") @tu lazy val AnnotationDefaultAnnot: ClassSymbol = requiredClass("scala.annotation.internal.AnnotationDefault") @tu lazy val AssignedNonLocallyAnnot: ClassSymbol = requiredClass("scala.annotation.internal.AssignedNonLocally") @tu lazy val BeanPropertyAnnot: ClassSymbol = requiredClass("scala.beans.BeanProperty") @@ -1018,6 +1015,7 @@ class Definitions { @tu lazy val ImplicitAmbiguousAnnot: ClassSymbol = requiredClass("scala.annotation.implicitAmbiguous") @tu lazy val ImplicitNotFoundAnnot: ClassSymbol = requiredClass("scala.annotation.implicitNotFound") @tu lazy val InlineParamAnnot: ClassSymbol = requiredClass("scala.annotation.internal.InlineParam") + @tu lazy val IntoAnnot: ClassSymbol = requiredClass("scala.annotation.internal.into") @tu lazy val ErasedParamAnnot: ClassSymbol = requiredClass("scala.annotation.internal.ErasedParam") @tu lazy val MainAnnot: ClassSymbol = requiredClass("scala.main") @tu lazy val MappedAlternativeAnnot: ClassSymbol = requiredClass("scala.annotation.internal.MappedAlternative") @@ -2137,7 +2135,6 @@ class Definitions { orType, RepeatedParamClass, ByNameParamClass2x, - IntoType, AnyValClass, NullClass, NothingClass, diff --git a/compiler/src/dotty/tools/dotc/core/StdNames.scala b/compiler/src/dotty/tools/dotc/core/StdNames.scala index a2e78add1338..9772199678d7 100644 --- a/compiler/src/dotty/tools/dotc/core/StdNames.scala +++ b/compiler/src/dotty/tools/dotc/core/StdNames.scala @@ -131,7 +131,7 @@ object StdNames { val EXCEPTION_RESULT_PREFIX: N = "exceptionResult" val EXPAND_SEPARATOR: N = str.EXPAND_SEPARATOR val IMPORT: N = "" - val INTO: N = "" + val INTO: N = "$into" val MODULE_SUFFIX: N = str.MODULE_SUFFIX val OPS_PACKAGE: N = "" val OVERLOADED: N = "" diff --git a/compiler/src/dotty/tools/dotc/core/Types.scala b/compiler/src/dotty/tools/dotc/core/Types.scala index 2b1f6394acdc..fd17a41ca339 100644 --- a/compiler/src/dotty/tools/dotc/core/Types.scala +++ b/compiler/src/dotty/tools/dotc/core/Types.scala @@ -419,8 +419,8 @@ object Types extends TypeUtils { typeSymbol eq defn.RepeatedParamClass /** Is this a parameter type that allows implicit argument converson? */ - def isConvertibleParam(using Context): Boolean = - typeSymbol eq defn.IntoType + def isInto(using Context): Boolean = + typeSymbol eq ??? /** Is this the type of a method that has a repeated parameter type as * last parameter type? @@ -4131,34 +4131,14 @@ object Types extends TypeUtils { case ExprType(resType) => ExprType(addAnnotation(resType, cls, param)) case _ => AnnotatedType(tp, Annotation(cls, param.span)) - def wrapConvertible(tp: Type) = - AppliedType(defn.IntoType.typeRef, tp :: Nil) - - /** Add `Into[..] to the type itself and if it is a function type, to all its - * curried result type(s) as well. - */ - def addInto(tp: Type): Type = tp match - case tp @ AppliedType(tycon, args) if tycon.typeSymbol == defn.RepeatedParamClass => - tp.derivedAppliedType(tycon, addInto(args.head) :: Nil) - case tp @ AppliedType(tycon, args) if defn.isFunctionNType(tp) => - wrapConvertible(tp.derivedAppliedType(tycon, args.init :+ addInto(args.last))) - case tp @ defn.RefinedFunctionOf(rinfo) => - wrapConvertible(tp.derivedRefinedType(refinedInfo = addInto(rinfo))) - case tp: MethodOrPoly => - tp.derivedLambdaType(resType = addInto(tp.resType)) - case ExprType(resType) => - ExprType(addInto(resType)) - case _ => - wrapConvertible(tp) - def paramInfo(param: Symbol) = - var paramType = param.info.annotatedToRepeated + var paramType = param.info + .annotatedToRepeated + //.mapIntoAnnot(defn.IntoType.appliedTo(_)) if param.is(Inline) then paramType = addAnnotation(paramType, defn.InlineParamAnnot, param) if param.is(Erased) then paramType = addAnnotation(paramType, defn.ErasedParamAnnot, param) - if param.hasAnnotation(defn.AllowConversionsAnnot) then - paramType = addInto(paramType) paramType apply(params.map(_.name.asTermName))( diff --git a/compiler/src/dotty/tools/dotc/parsing/Parsers.scala b/compiler/src/dotty/tools/dotc/parsing/Parsers.scala index 50380e5b14d3..6c2e69658927 100644 --- a/compiler/src/dotty/tools/dotc/parsing/Parsers.scala +++ b/compiler/src/dotty/tools/dotc/parsing/Parsers.scala @@ -73,6 +73,9 @@ object Parsers { enum ParseKind: case Expr, Type, Pattern + enum IntoOK: + case Yes, No, Nested + type StageKind = Int object StageKind { val None = 0 @@ -1484,7 +1487,7 @@ object Parsers { /** Same as [[typ]], but if this results in a wildcard it emits a syntax error and * returns a tree for type `Any` instead. */ - def toplevelTyp(): Tree = rejectWildcardType(typ()) + def toplevelTyp(intoOK: IntoOK = IntoOK.No): Tree = rejectWildcardType(typ(intoOK)) private def getFunction(tree: Tree): Option[Function] = tree match { case Parens(tree1) => getFunction(tree1) @@ -1535,12 +1538,21 @@ object Parsers { * | `(' [ FunArgType {`,' FunArgType } ] `)' * | '(' [ TypedFunParam {',' TypedFunParam } ')' * MatchType ::= InfixType `match` <<< TypeCaseClauses >>> + * IntoType ::= [‘into’] IntoTargetType + * | ‘( IntoType ‘)’ + * IntoTargetType ::= Type + * | FunTypeArgs (‘=>’ | ‘?=>’) IntoType */ - def typ(): Tree = + def typ(intoOK: IntoOK = IntoOK.No): Tree = val start = in.offset var imods = Modifiers() val erasedArgs: ListBuffer[Boolean] = ListBuffer() + def nestedIntoOK(token: Int) = + if token == TLARROW then IntoOK.No + else if intoOK == IntoOK.Nested then IntoOK.Yes + else intoOK + def functionRest(params: List[Tree]): Tree = val paramSpan = Span(start, in.lastOffset) atSpan(start, in.offset) { @@ -1569,8 +1581,9 @@ object Parsers { else accept(ARROW) + def resType() = typ(nestedIntoOK(token)) val resultType = - if isPure then capturesAndResult(typ) else typ() + if isPure then capturesAndResult(resType) else resType() if token == TLARROW then for case ValDef(_, tpt, _) <- params do if isByNameType(tpt) then @@ -1605,6 +1618,12 @@ object Parsers { syntaxError(ErasedTypesCanOnlyBeFunctionTypes(), implicitKwPos(start)) t + def isIntoPrefix: Boolean = + intoOK == IntoOK.Yes + && in.isIdent(nme.into) + && in.featureEnabled(Feature.into) + && canStartTypeTokens.contains(in.lookahead.token) + var isValParamList = false if in.token == LPAREN then in.nextToken() @@ -1635,17 +1654,36 @@ object Parsers { funArgType() commaSeparatedRest(t, funArg) accept(RPAREN) + + val intoAllowed = + intoOK == IntoOK.Yes + && args.lengthCompare(1) == 0 + && (!canFollowSimpleTypeTokens.contains(in.token) || followingIsVararg()) + val byNameAllowed = in.isArrow || isPureArrow + + def sanitize(arg: Tree): Tree = arg match + case ByNameTypeTree(t) if !byNameAllowed => + syntaxError(ByNameParameterNotSupported(t), t.span) + t + case PrefixOp(id @ Ident(tpnme.into), t) if !intoAllowed => + syntaxError(em"no `into` modifier allowed here", id.span) + t + case Parens(t) => + cpy.Parens(arg)(sanitize(t)) + case arg: FunctionWithMods => + val body1 = sanitize(arg.body) + if body1 eq arg.body then arg + else FunctionWithMods(arg.args, body1, arg.mods, arg.erasedParams).withSpan(arg.span) + case Function(args, res) if !intoAllowed => + cpy.Function(arg)(args, sanitize(res)) + case arg => + arg + + val args1 = args.mapConserve(sanitize) if isValParamList || in.isArrow || isPureArrow then functionRest(args) else - val args1 = args.mapConserve: t => - if isByNameType(t) then - syntaxError(ByNameParameterNotSupported(t), t.span) - stripByNameType(t) - else - t - val tuple = atSpan(start): - makeTupleOrParens(args1) + val tuple = atSpan(start)(makeTupleOrParens(args1)) typeRest: infixTypeRest: refinedTypeRest: @@ -1660,7 +1698,7 @@ object Parsers { LambdaTypeTree(tparams, toplevelTyp()) else if in.token == ARROW || isPureArrow(nme.PUREARROW) then val arrowOffset = in.skipToken() - val body = toplevelTyp() + val body = toplevelTyp(nestedIntoOK(in.token)) atSpan(start, arrowOffset): getFunction(body) match case Some(f) => @@ -1673,6 +1711,8 @@ object Parsers { typ() else if in.token == INDENT then enclosed(INDENT, typ()) + else if isIntoPrefix then + PrefixOp(typeIdent(), typ(IntoOK.Nested)) else typeRest(infixType()) end typ @@ -2047,18 +2087,13 @@ object Parsers { else core() - private def maybeInto(tp: () => Tree) = - if in.isIdent(nme.into) - && in.featureEnabled(Feature.into) - && canStartTypeTokens.contains(in.lookahead.token) - then atSpan(in.skipToken()) { Into(tp()) } - else tp() - /** FunArgType ::= Type * | `=>' Type * | `->' [CaptureSet] Type */ - val funArgType: () => Tree = () => paramTypeOf(typ) + val funArgType: () => Tree = + () => paramTypeOf(() => typ(IntoOK.Yes)) + // We allow intoOK and filter out afterwards in typ() /** ParamType ::= ParamValueType * | `=>' ParamValueType @@ -2067,15 +2102,21 @@ object Parsers { def paramType(): Tree = paramTypeOf(paramValueType) /** ParamValueType ::= Type [`*'] + * | IntoType + * | ‘(’ IntoType ‘)’ `*' */ - def paramValueType(): Tree = { - val t = maybeInto(toplevelTyp) - if (isIdent(nme.raw.STAR)) { + def paramValueType(): Tree = + val t = toplevelTyp(IntoOK.Yes) + if isIdent(nme.raw.STAR) then + if !t.isInstanceOf[Parens] && isInto(t) then + syntaxError( + em"""`*` cannot directly follow `into` parameter + |the `into` parameter needs to be put in parentheses""", + in.offset) in.nextToken() - atSpan(startOffset(t)) { PostfixOp(t, Ident(tpnme.raw.STAR)) } - } + atSpan(startOffset(t)): + PostfixOp(t, Ident(tpnme.raw.STAR)) else t - } /** TypeArgs ::= `[' Type {`,' Type} `]' * NamedTypeArgs ::= `[' NamedTypeArg {`,' NamedTypeArg} `]' @@ -3315,7 +3356,7 @@ object Parsers { /** ContextTypes ::= FunArgType {‘,’ FunArgType} */ def contextTypes(paramOwner: ParamOwner, numLeadParams: Int, impliedMods: Modifiers): List[ValDef] = - val tps = commaSeparated(() => paramTypeOf(toplevelTyp)) + val tps = commaSeparated(() => paramTypeOf(() => toplevelTyp())) var counter = numLeadParams def nextIdx = { counter += 1; counter } val paramFlags = if paramOwner.isClass then LocalParamAccessor else Param diff --git a/compiler/src/dotty/tools/dotc/parsing/Tokens.scala b/compiler/src/dotty/tools/dotc/parsing/Tokens.scala index fbf4e8d701dd..dee3e976ddb1 100644 --- a/compiler/src/dotty/tools/dotc/parsing/Tokens.scala +++ b/compiler/src/dotty/tools/dotc/parsing/Tokens.scala @@ -238,6 +238,9 @@ object Tokens extends TokensCommon { final val canStartPatternTokens = atomicExprTokens | openParensTokens | BitSet(USCORE, QUOTE) + val canFollowSimpleTypeTokens = + BitSet(AT, WITH, COLONop, COLONfollow, COLONeol, LBRACE, IDENTIFIER, BACKQUOTED_IDENT, ARROW, CTXARROW, MATCH, FORSOME) + final val templateIntroTokens: TokenSet = BitSet(CLASS, TRAIT, OBJECT, ENUM, CASECLASS, CASEOBJECT) final val dclIntroTokens: TokenSet = BitSet(DEF, VAL, VAR, TYPE, GIVEN) diff --git a/compiler/src/dotty/tools/dotc/printing/PlainPrinter.scala b/compiler/src/dotty/tools/dotc/printing/PlainPrinter.scala index 8fc0c568e125..06f015e66f8d 100644 --- a/compiler/src/dotty/tools/dotc/printing/PlainPrinter.scala +++ b/compiler/src/dotty/tools/dotc/printing/PlainPrinter.scala @@ -285,7 +285,11 @@ class PlainPrinter(_ctx: Context) extends Printer { toTextGlobal(tp.resultType) } case AnnotatedType(tpe, annot) => - if annot.symbol == defn.InlineParamAnnot || annot.symbol == defn.ErasedParamAnnot then toText(tpe) + if annot.symbol == defn.InlineParamAnnot || annot.symbol == defn.ErasedParamAnnot + then toText(tpe) + else if annot.symbol == defn.IntoAnnot && !printDebug then + atPrec(GlobalPrec): + Str("into ") ~ toText(tpe) else toTextLocal(tpe) ~ " " ~ toText(annot) case tp: TypeVar => def toTextCaret(tp: Type) = if printDebug then toTextLocal(tp) ~ Str("^") else toText(tp) diff --git a/compiler/src/dotty/tools/dotc/printing/RefinedPrinter.scala b/compiler/src/dotty/tools/dotc/printing/RefinedPrinter.scala index 5d8b448e409c..fbdbd0bf6e8b 100644 --- a/compiler/src/dotty/tools/dotc/printing/RefinedPrinter.scala +++ b/compiler/src/dotty/tools/dotc/printing/RefinedPrinter.scala @@ -244,7 +244,7 @@ class RefinedPrinter(_ctx: Context) extends PlainPrinter(_ctx) { case _ => val tsym = tycon.typeSymbol if tycon.isRepeatedParam then toTextLocal(args.head) ~ "*" - else if tp.isConvertibleParam then "into " ~ toText(args.head) + else if tp.isInto then atPrec(GlobalPrec)( "into " ~ toText(args.head) ) else if defn.isFunctionSymbol(tsym) then toTextFunction(tp) else if isInfixType(tp) then val l :: r :: Nil = args: @unchecked @@ -647,6 +647,9 @@ class RefinedPrinter(_ctx: Context) extends PlainPrinter(_ctx) { && Feature.ccEnabled && !printDebug && Phases.checkCapturesPhase.exists // might be missing on -Ytest-pickler then toTextRetainsAnnot + else if annot.symbol.enclosingClass == defn.IntoAnnot && !printDebug then + atPrec(GlobalPrec): + Str("into ") ~ toText(arg) else toTextAnnot case EmptyTree => "" diff --git a/compiler/src/dotty/tools/dotc/typer/Checking.scala b/compiler/src/dotty/tools/dotc/typer/Checking.scala index eadca79cd78b..24619d1048cb 100644 --- a/compiler/src/dotty/tools/dotc/typer/Checking.scala +++ b/compiler/src/dotty/tools/dotc/typer/Checking.scala @@ -1089,7 +1089,7 @@ trait Checking { if sym.name == nme.apply && sym.owner.derivesFrom(defn.ConversionClass) && !sym.info.isErroneous - && !expected.isConvertibleParam + && !expected.isInto then def conv = methPart(tree) match case Select(qual, _) => qual.symbol.orElse(sym.owner) diff --git a/compiler/src/dotty/tools/dotc/typer/Typer.scala b/compiler/src/dotty/tools/dotc/typer/Typer.scala index 765554059374..094c979cf688 100644 --- a/compiler/src/dotty/tools/dotc/typer/Typer.scala +++ b/compiler/src/dotty/tools/dotc/typer/Typer.scala @@ -2335,9 +2335,6 @@ class Typer(@constructorOnly nestingLevel: Int = 0) extends Namer && checkedArgs(1).tpe.derivesFrom(defn.RuntimeExceptionClass) then report.error(em"throws clause cannot be defined for RuntimeException", checkedArgs(1).srcPos) - else if tycon == defn.IntoType then - // is defined in package scala but this should be hidden from user programs - report.error(em"not found: ", tpt1.srcPos) else if (ctx.isJava) if tycon eq defn.ArrayClass then checkedArgs match { diff --git a/docs/_docs/internals/syntax.md b/docs/_docs/internals/syntax.md index cfa77c6ff965..10f068e53c7f 100644 --- a/docs/_docs/internals/syntax.md +++ b/docs/_docs/internals/syntax.md @@ -211,6 +211,12 @@ FunArgType ::= Type FunArgTypes ::= FunArgType { ‘,’ FunArgType } ParamType ::= [‘=>’] ParamValueType ParamValueType ::= Type [‘*’] PostfixOp(t, "*") + | IntoType + | ‘(’ IntoType ‘)’ ‘*’ PostfixOp(t, "*") +IntoType ::= [‘into’] IntoTargetType Into(t) + | ‘(’ IntoType ‘)’ +IntoTargetType ::= Type + | FunTypeArgs (‘=>’ | ‘?=>’) IntoType TypeArgs ::= ‘[’ Types ‘]’ ts Refinement ::= :<<< [RefineDcl] {semi [RefineDcl]} >>> ds TypeBounds ::= [‘>:’ Type] [‘<:’ Type] TypeBoundsTree(lo, hi) diff --git a/library/src/scala/annotation/allowConversions.scala b/library/src/scala/annotation/allowConversions.scala deleted file mode 100644 index 9d752ee26d21..000000000000 --- a/library/src/scala/annotation/allowConversions.scala +++ /dev/null @@ -1,10 +0,0 @@ -package scala.annotation -import annotation.experimental - -/** An annotation on a parameter type that allows implicit conversions - * for its arguments. Intended for use by Scala 2, to annotate Scala 2 - * libraries. Scala 3 uses the `into` modifier on the parameter - * type instead. - */ -@experimental -class allowConversions extends scala.annotation.StaticAnnotation From 692bf77064747fab4783f5c0bcc8e936c0db6d70 Mon Sep 17 00:00:00 2001 From: odersky Date: Wed, 14 Feb 2024 17:35:10 +0100 Subject: [PATCH 2/5] Typechecking with into modifiers --- .../dotty/tools/dotc/core/Definitions.scala | 1 + .../src/dotty/tools/dotc/core/Types.scala | 44 +++++++++++-- .../tools/dotc/printing/PlainPrinter.scala | 6 +- .../tools/dotc/printing/RefinedPrinter.scala | 1 - .../src/dotty/tools/dotc/typer/Checking.scala | 2 +- .../dotty/tools/dotc/typer/RefChecks.scala | 54 +++++++++++++++- .../tools/vulpix/TestConfiguration.scala | 2 + .../src/scala/annotation/internal/Into.scala | 14 +++++ tests/neg-custom-args/convertible.check | 21 +++++++ tests/neg/into-override.check | 21 +++++++ tests/neg/into-override.scala | 23 +++++++ tests/neg/into-syntax.check | 61 +++++++++++++++++++ tests/neg/into-syntax.scala | 27 ++++++++ tests/pos/into-class.scala | 15 +++++ .../stdlibExperimentalDefinitions.scala | 3 +- tests/run/convertible.scala | 20 +++--- tests/warn/convertible.scala | 18 +++++- 17 files changed, 306 insertions(+), 27 deletions(-) create mode 100644 library/src/scala/annotation/internal/Into.scala create mode 100644 tests/neg-custom-args/convertible.check create mode 100644 tests/neg/into-override.check create mode 100644 tests/neg/into-override.scala create mode 100644 tests/neg/into-syntax.check create mode 100644 tests/neg/into-syntax.scala create mode 100644 tests/pos/into-class.scala diff --git a/compiler/src/dotty/tools/dotc/core/Definitions.scala b/compiler/src/dotty/tools/dotc/core/Definitions.scala index 9d610f23a067..bf6f12c4f9f9 100644 --- a/compiler/src/dotty/tools/dotc/core/Definitions.scala +++ b/compiler/src/dotty/tools/dotc/core/Definitions.scala @@ -1016,6 +1016,7 @@ class Definitions { @tu lazy val ImplicitNotFoundAnnot: ClassSymbol = requiredClass("scala.annotation.implicitNotFound") @tu lazy val InlineParamAnnot: ClassSymbol = requiredClass("scala.annotation.internal.InlineParam") @tu lazy val IntoAnnot: ClassSymbol = requiredClass("scala.annotation.internal.into") + @tu lazy val IntoParamAnnot: ClassSymbol = requiredClass("scala.annotation.internal.$into") @tu lazy val ErasedParamAnnot: ClassSymbol = requiredClass("scala.annotation.internal.ErasedParam") @tu lazy val MainAnnot: ClassSymbol = requiredClass("scala.main") @tu lazy val MappedAlternativeAnnot: ClassSymbol = requiredClass("scala.annotation.internal.MappedAlternative") diff --git a/compiler/src/dotty/tools/dotc/core/Types.scala b/compiler/src/dotty/tools/dotc/core/Types.scala index fd17a41ca339..71f9ab196ed2 100644 --- a/compiler/src/dotty/tools/dotc/core/Types.scala +++ b/compiler/src/dotty/tools/dotc/core/Types.scala @@ -419,8 +419,9 @@ object Types extends TypeUtils { typeSymbol eq defn.RepeatedParamClass /** Is this a parameter type that allows implicit argument converson? */ - def isInto(using Context): Boolean = - typeSymbol eq ??? + def isInto(using Context): Boolean = this match + case AnnotatedType(_, annot) => annot.symbol == defn.IntoParamAnnot + case _ => false /** Is this the type of a method that has a repeated parameter type as * last parameter type? @@ -1927,7 +1928,9 @@ object Types extends TypeUtils { case res => res } defn.FunctionNOf( - mt.paramInfos.mapConserve(_.translateFromRepeated(toArray = isJava)), + mt.paramInfos.mapConserve: + _.translateFromRepeated(toArray = isJava) + .mapIntoAnnot(defn.IntoParamAnnot, null), result1, isContextual) if mt.hasErasedParams then defn.PolyFunctionOf(mt) @@ -1975,6 +1978,38 @@ object Types extends TypeUtils { case _ => this } + /** A mapping between mapping one kind of into annotation to another or + * dropping into annotations. + * @param from the into annotation to map + * @param to either the replacement annotation symbol, or `null` + * in which case the `from` annotations are dropped. + */ + def mapIntoAnnot(from: ClassSymbol, to: ClassSymbol | Null)(using Context): Type = this match + case self @ AnnotatedType(tp, annot) => + val tp1 = tp.mapIntoAnnot(from, to) + if annot.symbol == from then + if to == null then tp1 + else AnnotatedType(tp1, Annotation(to, from.span)) + else self.derivedAnnotatedType(tp1, annot) + case AppliedType(tycon, arg :: Nil) if tycon.typeSymbol == defn.RepeatedParamClass => + val arg1 = arg.mapIntoAnnot(from, to) + if arg1 eq arg then this + else AppliedType(tycon, arg1 :: Nil) + case defn.FunctionOf(argTypes, resType, isContextual) => + val resType1 = resType.mapIntoAnnot(from, to) + if resType1 eq resType then this + else defn.FunctionOf(argTypes, resType1, isContextual) + case RefinedType(parent, rname, mt: MethodOrPoly) => + val mt1 = mt.mapIntoAnnot(from, to) + if mt1 eq mt then this + else RefinedType(parent.mapIntoAnnot(from, to), rname, mt1) + case mt: MethodOrPoly => + mt.derivedLambdaType(resType = mt.resType.mapIntoAnnot(from, to)) + case tp: ExprType => + tp.derivedExprType(tp.resType.mapIntoAnnot(from, to)) + case _ => + this + /** A type capturing `ref` */ def capturing(ref: CaptureRef)(using Context): Type = if captureSet.accountsFor(ref) then this @@ -4122,6 +4157,7 @@ object Types extends TypeUtils { /** Produce method type from parameter symbols, with special mappings for repeated * and inline parameters: * - replace @repeated annotations on Seq or Array types by types + * - map into annotations to $into annotations * - add @inlineParam to inline parameters * - add @erasedParam to erased parameters * - wrap types of parameters that have an @allowConversions annotation with Into[_] @@ -4134,7 +4170,7 @@ object Types extends TypeUtils { def paramInfo(param: Symbol) = var paramType = param.info .annotatedToRepeated - //.mapIntoAnnot(defn.IntoType.appliedTo(_)) + .mapIntoAnnot(defn.IntoAnnot, defn.IntoParamAnnot) if param.is(Inline) then paramType = addAnnotation(paramType, defn.InlineParamAnnot, param) if param.is(Erased) then diff --git a/compiler/src/dotty/tools/dotc/printing/PlainPrinter.scala b/compiler/src/dotty/tools/dotc/printing/PlainPrinter.scala index 06f015e66f8d..1a52f61d3153 100644 --- a/compiler/src/dotty/tools/dotc/printing/PlainPrinter.scala +++ b/compiler/src/dotty/tools/dotc/printing/PlainPrinter.scala @@ -287,9 +287,9 @@ class PlainPrinter(_ctx: Context) extends Printer { case AnnotatedType(tpe, annot) => if annot.symbol == defn.InlineParamAnnot || annot.symbol == defn.ErasedParamAnnot then toText(tpe) - else if annot.symbol == defn.IntoAnnot && !printDebug then - atPrec(GlobalPrec): - Str("into ") ~ toText(tpe) + else if (annot.symbol == defn.IntoAnnot || annot.symbol == defn.IntoParamAnnot) + && !printDebug + then atPrec(GlobalPrec)( Str("into ") ~ toText(tpe) ) else toTextLocal(tpe) ~ " " ~ toText(annot) case tp: TypeVar => def toTextCaret(tp: Type) = if printDebug then toTextLocal(tp) ~ Str("^") else toText(tp) diff --git a/compiler/src/dotty/tools/dotc/printing/RefinedPrinter.scala b/compiler/src/dotty/tools/dotc/printing/RefinedPrinter.scala index fbdbd0bf6e8b..893b34f48396 100644 --- a/compiler/src/dotty/tools/dotc/printing/RefinedPrinter.scala +++ b/compiler/src/dotty/tools/dotc/printing/RefinedPrinter.scala @@ -244,7 +244,6 @@ class RefinedPrinter(_ctx: Context) extends PlainPrinter(_ctx) { case _ => val tsym = tycon.typeSymbol if tycon.isRepeatedParam then toTextLocal(args.head) ~ "*" - else if tp.isInto then atPrec(GlobalPrec)( "into " ~ toText(args.head) ) else if defn.isFunctionSymbol(tsym) then toTextFunction(tp) else if isInfixType(tp) then val l :: r :: Nil = args: @unchecked diff --git a/compiler/src/dotty/tools/dotc/typer/Checking.scala b/compiler/src/dotty/tools/dotc/typer/Checking.scala index 24619d1048cb..56f67574a72d 100644 --- a/compiler/src/dotty/tools/dotc/typer/Checking.scala +++ b/compiler/src/dotty/tools/dotc/typer/Checking.scala @@ -1082,7 +1082,7 @@ trait Checking { /** If `tree` is an application of a new-style implicit conversion (using the apply * method of a `scala.Conversion` instance), check that the expected type is - * a convertible formal parameter type or that implicit conversions are enabled. + * annotated with @$into or that implicit conversions are enabled. */ def checkImplicitConversionUseOK(tree: Tree, expected: Type)(using Context): Unit = val sym = tree.symbol diff --git a/compiler/src/dotty/tools/dotc/typer/RefChecks.scala b/compiler/src/dotty/tools/dotc/typer/RefChecks.scala index f0914a9f6664..6be3aa0b36d5 100644 --- a/compiler/src/dotty/tools/dotc/typer/RefChecks.scala +++ b/compiler/src/dotty/tools/dotc/typer/RefChecks.scala @@ -8,7 +8,7 @@ import Symbols.*, Types.*, Contexts.*, Flags.*, Names.*, NameOps.*, NameKinds.* import StdNames.*, Denotations.*, Phases.*, SymDenotations.* import NameKinds.DefaultGetterName import util.Spans.* -import scala.collection.mutable +import scala.collection.{mutable, immutable} import ast.* import MegaPhase.* import config.Printers.{checks, noPrinter, capt} @@ -368,6 +368,52 @@ object RefChecks { && atPhase(typerPhase): loop(member.info.paramInfoss, other.info.paramInfoss) + /** A map of all occurrences of `into` in a member type. + * Key: number of parameter carrying `into` annotation(s) + * Value: A list of all depths of into annotations, where each + * function arrow increases the depth. + * Example: + * def foo(x: into A, y: => [X] => into (x: X) => into B): C + * produces the map + * (0 -> List(0), 1 -> List(1, 2)) + */ + type IntoOccurrenceMap = immutable.Map[Int, List[Int]] + + def intoOccurrences(tp: Type): IntoOccurrenceMap = + + def traverseInfo(depth: Int, tp: Type): List[Int] = tp match + case AnnotatedType(tp, annot) if annot.symbol == defn.IntoParamAnnot => + depth :: traverseInfo(depth, tp) + case AppliedType(tycon, arg :: Nil) if tycon.typeSymbol == defn.RepeatedParamClass => + traverseInfo(depth, arg) + case defn.FunctionOf(_, resType, _) => + traverseInfo(depth + 1, resType) + case RefinedType(parent, rname, mt: MethodOrPoly) => + traverseInfo(depth, mt) + case tp: MethodOrPoly => + traverseInfo(depth + 1, tp.resType) + case tp: ExprType => + traverseInfo(depth, tp.resType) + case _ => + Nil + + def traverseParams(n: Int, formals: List[Type], acc: IntoOccurrenceMap): IntoOccurrenceMap = + if formals.isEmpty then acc + else + val occs = traverseInfo(0, formals.head) + traverseParams(n + 1, formals.tail, if occs.isEmpty then acc else acc + (n -> occs)) + + def traverse(n: Int, tp: Type, acc: IntoOccurrenceMap): IntoOccurrenceMap = tp match + case tp: PolyType => + traverse(n, tp.resType, acc) + case tp: MethodType => + traverse(n + tp.paramInfos.length, tp.resType, traverseParams(n, tp.paramInfos, acc)) + case _ => + acc + + traverse(0, tp, immutable.Map.empty) + end intoOccurrences + val checker = if makeOverridingPairsChecker == null then OverridingPairsChecker(clazz, self) else makeOverridingPairsChecker(clazz, self) @@ -572,6 +618,8 @@ object RefChecks { overrideError(i"needs to be declared with @targetName(${"\""}${other.targetName}${"\""}) so that external names match") else overrideError("cannot have a @targetName annotation since external names would be different") + else if intoOccurrences(memberTp(self)) != intoOccurrences(otherTp(self)) then + overrideError("has different occurrences of `into` modifiers", compareTypes = true) else if other.is(ParamAccessor) && !isInheritedAccessor(member, other) then // (1.12) report.errorOrMigrationWarning( em"cannot override val parameter ${other.showLocated}", @@ -1002,9 +1050,9 @@ object RefChecks { end checkNoPrivateOverrides def checkVolatile(sym: Symbol)(using Context): Unit = - if sym.isVolatile && !sym.is(Mutable) then + if sym.isVolatile && !sym.is(Mutable) then report.warning(VolatileOnVal(), sym.srcPos) - + /** Check that unary method definition do not receive parameters. * They can only receive inferred parameters such as type parameters and implicit parameters. */ diff --git a/compiler/test/dotty/tools/vulpix/TestConfiguration.scala b/compiler/test/dotty/tools/vulpix/TestConfiguration.scala index 04be00fe921e..1defe3f4f53d 100644 --- a/compiler/test/dotty/tools/vulpix/TestConfiguration.scala +++ b/compiler/test/dotty/tools/vulpix/TestConfiguration.scala @@ -66,7 +66,9 @@ object TestConfiguration { val yCheckOptions = Array("-Ycheck:all") val commonOptions = Array("-indent") ++ checkOptions ++ noCheckOptions ++ yCheckOptions + val noYcheckCommonOptions = Array("-indent") ++ checkOptions ++ noCheckOptions val defaultOptions = TestFlags(basicClasspath, commonOptions) + val noYcheckOptions = TestFlags(basicClasspath, noYcheckCommonOptions) val unindentOptions = TestFlags(basicClasspath, Array("-no-indent") ++ checkOptions ++ noCheckOptions ++ yCheckOptions) val withCompilerOptions = defaultOptions.withClasspath(withCompilerClasspath).withRunClasspath(withCompilerClasspath) diff --git a/library/src/scala/annotation/internal/Into.scala b/library/src/scala/annotation/internal/Into.scala new file mode 100644 index 000000000000..a256636406c2 --- /dev/null +++ b/library/src/scala/annotation/internal/Into.scala @@ -0,0 +1,14 @@ +package scala.annotation.internal +import annotation.experimental + +/** An annotation on (part of) a parameter type that allows implicit conversions + * for its arguments. The `into` modifier on parameter types in Scala 3 is + * mapped to this annotation. We can also install a more generally accessible + * alias so that Scala 2 libraries can use the feature. + */ +@experimental +class into() extends annotation.StaticAnnotation + +@experimental +class $into() extends annotation.StaticAnnotation + diff --git a/tests/neg-custom-args/convertible.check b/tests/neg-custom-args/convertible.check new file mode 100644 index 000000000000..c1ba6e9e6934 --- /dev/null +++ b/tests/neg-custom-args/convertible.check @@ -0,0 +1,21 @@ +-- [E120] Naming Error: tests/neg-custom-args/convertible.scala:15:6 --------------------------------------------------- +15 |trait C[X] extends A[X]: // error + | ^ + | Name clash between defined and inherited member: + | def f(x: X): Unit in trait A at line 10 and + | override def f(x: into X): Unit in trait C at line 16 + | have the same type after erasure. + | + | Consider adding a @targetName annotation to one of the conflicting definitions + | for disambiguation. +-- [E120] Naming Error: tests/neg-custom-args/convertible.scala:18:6 --------------------------------------------------- +18 |class D[X] extends B[X], C[X] // error + | ^ + | Name clash between inherited members: + | override def f(x: X): Unit in trait B at line 13 and + | override def f(x: into X): Unit in trait C at line 16 + | have the same type after erasure. + | + | Consider adding a @targetName annotation to one of the conflicting definitions + | for disambiguation. +there was 1 feature warning; re-run with -feature for details diff --git a/tests/neg/into-override.check b/tests/neg/into-override.check new file mode 100644 index 000000000000..812470494a8b --- /dev/null +++ b/tests/neg/into-override.check @@ -0,0 +1,21 @@ +-- [E164] Declaration Error: tests/neg/into-override.scala:16:15 ------------------------------------------------------- +16 | override def f(x: into X) = super.f(x) // error + | ^ + | error overriding method f in trait A of type (x: X): Unit; + | method f of type (x: into X): Unit has different occurrences of `into` modifiers + | + | longer explanation available when compiling with `-explain` +-- [E164] Declaration Error: tests/neg/into-override.scala:18:6 -------------------------------------------------------- +18 |class D[X] extends B[X], C[X] // error + | ^ + | error overriding method f in trait B of type (x: X): Unit; + | method f in trait C of type (x: into X): Unit has different occurrences of `into` modifiers + | + | longer explanation available when compiling with `-explain` +-- [E164] Declaration Error: tests/neg/into-override.scala:21:15 ------------------------------------------------------- +21 | override def f(x: X) = super.f(x) // error + | ^ + | error overriding method f in trait C of type (x: into X): Unit; + | method f of type (x: X): Unit has different occurrences of `into` modifiers + | + | longer explanation available when compiling with `-explain` diff --git a/tests/neg/into-override.scala b/tests/neg/into-override.scala new file mode 100644 index 000000000000..645ae8756003 --- /dev/null +++ b/tests/neg/into-override.scala @@ -0,0 +1,23 @@ +//> using options -Xfatal-warnings + +import language.experimental.into + +class Text(val str: String) + +given Conversion[String, Text] = Text(_) + +trait A[X]: + def f(x: X): Unit = () + +trait B[X] extends A[X]: + override def f(x: X) = super.f(x) + +trait C[X] extends A[X]: + override def f(x: into X) = super.f(x) // error + +class D[X] extends B[X], C[X] // error + +trait E[X] extends C[X]: + override def f(x: X) = super.f(x) // error + +def f = new D[Text].f("abc") diff --git a/tests/neg/into-syntax.check b/tests/neg/into-syntax.check new file mode 100644 index 000000000000..ad1f95db93be --- /dev/null +++ b/tests/neg/into-syntax.check @@ -0,0 +1,61 @@ +-- [E040] Syntax Error: tests/neg/into-syntax.scala:7:22 --------------------------------------------------------------- +7 | def f1(x: List[into Int]) = () // error // error + | ^^^ + | ',' or ']' expected, but identifier found +-- Error: tests/neg/into-syntax.scala:11:20 ---------------------------------------------------------------------------- +11 | def f4(x: into Int*) = () // error + | ^ + | `*` cannot directly follow `into` parameter + | the `into` parameter needs to be put in parentheses +-- [E040] Syntax Error: tests/neg/into-syntax.scala:21:23 -------------------------------------------------------------- +21 | def f11(x: ((y: into Int) => into Int => Int)*) = () // error // error + | ^^^ + | ')' expected, but identifier found +-- Error: tests/neg/into-syntax.scala:24:14 ---------------------------------------------------------------------------- +24 | def f14(x: (into Int) => Int) = () // error + | ^^^^ + | no `into` modifier allowed here +-- Error: tests/neg/into-syntax.scala:25:14 ---------------------------------------------------------------------------- +25 | def f15(x: (into Int, into Int)) = () // error // error + | ^^^^ + | no `into` modifier allowed here +-- Error: tests/neg/into-syntax.scala:25:24 ---------------------------------------------------------------------------- +25 | def f15(x: (into Int, into Int)) = () // error // error + | ^^^^ + | no `into` modifier allowed here +-- Error: tests/neg/into-syntax.scala:26:14 ---------------------------------------------------------------------------- +26 | def f16(x: (into Int, into Int) => Int) = () // error // error + | ^^^^ + | no `into` modifier allowed here +-- Error: tests/neg/into-syntax.scala:26:24 ---------------------------------------------------------------------------- +26 | def f16(x: (into Int, into Int) => Int) = () // error // error + | ^^^^ + | no `into` modifier allowed here +-- [E040] Syntax Error: tests/neg/into-syntax.scala:27:27 -------------------------------------------------------------- +27 | def f17(x: into (y: into Int, z: into Int) => into Int) = () // error // error // error + | ^^^ + | ')' expected, but identifier found +-- [E019] Syntax Error: tests/neg/into-syntax.scala:27:44 -------------------------------------------------------------- +27 | def f17(x: into (y: into Int, z: into Int) => into Int) = () // error // error // error + | ^ + | Missing return type + | + | longer explanation available when compiling with `-explain` +-- [E006] Not Found Error: tests/neg/into-syntax.scala:7:17 ------------------------------------------------------------ +7 | def f1(x: List[into Int]) = () // error // error + | ^^^^ + | Not found: type into - did you mean into.type? + | + | longer explanation available when compiling with `-explain` +-- [E006] Not Found Error: tests/neg/into-syntax.scala:21:18 ----------------------------------------------------------- +21 | def f11(x: ((y: into Int) => into Int => Int)*) = () // error // error + | ^^^^ + | Not found: type into - did you mean into.type? + | + | longer explanation available when compiling with `-explain` +-- [E006] Not Found Error: tests/neg/into-syntax.scala:27:22 ----------------------------------------------------------- +27 | def f17(x: into (y: into Int, z: into Int) => into Int) = () // error // error // error + | ^^^^ + | Not found: type into - did you mean into.type? + | + | longer explanation available when compiling with `-explain` diff --git a/tests/neg/into-syntax.scala b/tests/neg/into-syntax.scala new file mode 100644 index 000000000000..8f48a603adf6 --- /dev/null +++ b/tests/neg/into-syntax.scala @@ -0,0 +1,27 @@ +//> using options -feature + +import language.experimental.into + + +object x1: + def f1(x: List[into Int]) = () // error // error +object x3: + def f3(x: ((into Int))) = () // ok +object x4: + def f4(x: into Int*) = () // error +object x5: + def f5(x: ((into Int))*) = () // ok + +object x6: + def f6(x: (into Int)*) = () // ok + def f7(x: (Int => into Int)*) = () // ok + def f8(x: (Int => (into Int))*) = () // ok + def f9(x: (y: Int) => into Int) = () // ok + def f10(x: ((y: Int) => into Int)*) = () // ok + def f11(x: ((y: into Int) => into Int => Int)*) = () // error // error + +object x7: + def f14(x: (into Int) => Int) = () // error + def f15(x: (into Int, into Int)) = () // error // error + def f16(x: (into Int, into Int) => Int) = () // error // error + def f17(x: into (y: into Int, z: into Int) => into Int) = () // error // error // error diff --git a/tests/pos/into-class.scala b/tests/pos/into-class.scala new file mode 100644 index 000000000000..2638b9a0234a --- /dev/null +++ b/tests/pos/into-class.scala @@ -0,0 +1,15 @@ +import language.experimental.into + +class Text(str: String) + +case class C(x: into Text) + +case class D(x: Text) + +given Conversion[String, Text] = Text(_) + +def Test = + val c = C("a") + val d = new C("b") + val e = c.copy() + val f = c.copy(x = "d") diff --git a/tests/run-tasty-inspector/stdlibExperimentalDefinitions.scala b/tests/run-tasty-inspector/stdlibExperimentalDefinitions.scala index 888e5c36405d..247f7ecc8e9b 100644 --- a/tests/run-tasty-inspector/stdlibExperimentalDefinitions.scala +++ b/tests/run-tasty-inspector/stdlibExperimentalDefinitions.scala @@ -57,7 +57,8 @@ val experimentalDefinitionInLibrary = Set( "scala.caps$", //// New feature: into - "scala.annotation.allowConversions", + "scala.annotation.internal.into", + "scala.annotation.internal.$into", //// New feature: @publicInBinary "scala.annotation.publicInBinary", diff --git a/tests/run/convertible.scala b/tests/run/convertible.scala index 0670d1949fd9..7a92964a1f31 100644 --- a/tests/run/convertible.scala +++ b/tests/run/convertible.scala @@ -1,4 +1,4 @@ -//> using options -Xfatal-warnings +//> using options -feature -Xfatal-warnings import language.experimental.into @@ -8,27 +8,23 @@ given Conversion[String, Text] = Text(_) @main def Test = - def f(x: into Text, y: => into Text, zs: into Text*) = - println(s"${x.str} ${y.str} ${zs.map(_.str).mkString(" ")}") + def f(xxx: into Text, yyy: => into Text, zs: (into Text)*) = + println(s"${xxx.str} ${yyy.str} ${zs.map(_.str).mkString(" ")}") f("abc", "def") // ok f("abc", "def", "xyz", "uvw") // ok f("abc", "def", "xyz", Text("uvw")) // ok - def g(x: into () => Text) = + def g(x: () => into Text) = println(x().str) g(() => "hi") -trait A[X]: - def f(x: X): Unit = () +trait C[X]: + def f(x: into X) = x -trait B[X] extends A[X]: - override def f(x: X) = super.f(x) +class D[X] extends C[X] -trait C[X] extends A[X]: - override def f(x: into X) = super.f(x) +def f = new D[Text].f("abc") -class D[X] extends B[X], C[X] -def f = new D[Text].f("abc") diff --git a/tests/warn/convertible.scala b/tests/warn/convertible.scala index c98006ecdc9b..b830093fc891 100644 --- a/tests/warn/convertible.scala +++ b/tests/warn/convertible.scala @@ -18,13 +18,27 @@ object Test: def g(x: into Text) = println(x.str) + def g2(x: into Text) = + println(x.str) + + def g3(x: Text) = + println(x.str) g("abc") // OK val gg = g - gg("abc") // straight eta expansion is also OK + gg("abc") // warn, eta expansion does not preserve into + + val c1 = if ??? then g else g2 + c1("abc") // warn, eta expansion does not preserve into + + val c2 = if ??? then g else g3 + c2("abc") // warn, eta expesnion does not preserve into + + val c3 = if ??? then g3 else g + c3("abc") // warn, eta expesnion does not preserve into def h1[X](x: X)(y: X): Unit = () def h(x: into Text) = val y = h1(x) - y("abc") // warn, inference through type variable does not propagate \ No newline at end of file + y("abc") // warn, eta expesnion does not preserve into \ No newline at end of file From b518d75306c7744a3acacfbbb9034a4965658849 Mon Sep 17 00:00:00 2001 From: odersky Date: Wed, 14 Feb 2024 18:38:35 +0100 Subject: [PATCH 3/5] Update doc page and move into annotation to annotation package --- .../dotty/tools/dotc/core/Definitions.scala | 2 +- .../reference/experimental/into-modifier.md | 67 +++++++++++++++---- .../src/scala/annotation/internal/$into.scala | 15 +++++ .../{internal/Into.scala => into.scala} | 10 +-- tests/neg-custom-args/convertible.check | 21 ------ tests/pos/into-sam.scala | 18 +++++ .../stdlibExperimentalDefinitions.scala | 2 +- 7 files changed, 91 insertions(+), 44 deletions(-) create mode 100644 library/src/scala/annotation/internal/$into.scala rename library/src/scala/annotation/{internal/Into.scala => into.scala} (52%) delete mode 100644 tests/neg-custom-args/convertible.check create mode 100644 tests/pos/into-sam.scala diff --git a/compiler/src/dotty/tools/dotc/core/Definitions.scala b/compiler/src/dotty/tools/dotc/core/Definitions.scala index bf6f12c4f9f9..789e744fbfc9 100644 --- a/compiler/src/dotty/tools/dotc/core/Definitions.scala +++ b/compiler/src/dotty/tools/dotc/core/Definitions.scala @@ -1015,7 +1015,7 @@ class Definitions { @tu lazy val ImplicitAmbiguousAnnot: ClassSymbol = requiredClass("scala.annotation.implicitAmbiguous") @tu lazy val ImplicitNotFoundAnnot: ClassSymbol = requiredClass("scala.annotation.implicitNotFound") @tu lazy val InlineParamAnnot: ClassSymbol = requiredClass("scala.annotation.internal.InlineParam") - @tu lazy val IntoAnnot: ClassSymbol = requiredClass("scala.annotation.internal.into") + @tu lazy val IntoAnnot: ClassSymbol = requiredClass("scala.annotation.into") @tu lazy val IntoParamAnnot: ClassSymbol = requiredClass("scala.annotation.internal.$into") @tu lazy val ErasedParamAnnot: ClassSymbol = requiredClass("scala.annotation.internal.ErasedParam") @tu lazy val MainAnnot: ClassSymbol = requiredClass("scala.main") diff --git a/docs/_docs/reference/experimental/into-modifier.md b/docs/_docs/reference/experimental/into-modifier.md index 2ee4c74539b3..0c1d24b1d970 100644 --- a/docs/_docs/reference/experimental/into-modifier.md +++ b/docs/_docs/reference/experimental/into-modifier.md @@ -32,10 +32,10 @@ The `into` modifier on the type of `elems` means that implicit conversions can b `into` also allows conversions on the results of function arguments. For instance, consider the new proposed signature of the `flatMap` method on `List[A]`: ```scala - def flatMap[B](f: into A => IterableOnce[B]): List[B] + def flatMap[B](f: A => into IterableOnce[B]): List[B] ``` -This allows a conversion of the actual argument to the function type `A => IterableOnce[B]`. Crucially, it also allows that conversion to be applied to -the function result. So the following would work: +This accepts all actual arguments `f` that, when applied to an `A`, give a result +that is convertible to `IterableOnce[B]`. So the following would work: ```scala scala> val xs = List(1, 2, 3) scala> xs.flatMap(x => x.toString * x) @@ -49,7 +49,7 @@ When applied to a vararg parameter, `into` allows a conversion on each argument number of `IterableOnce[Char]` arguments, and also allows implicit conversions into `IterableOnce[Char]`: ```scala -def concatAll(xss: into IterableOnce[Char]*): List[Char] = +def concatAll(xss: (into IterableOnce[Char])*): List[Char] = xss.foldLeft(List[Char]())(_ ++ _) ``` Here, the call @@ -58,24 +58,63 @@ concatAll(List('a'), "bc", Array('d', 'e')) ``` would apply two _different_ implicit conversions: the conversion from `String` to `Iterable[Char]` gets applied to the second argument and the conversion from `Array[Char]` to `Iterable[Char]` gets applied to the third argument. +Note that a vararg parameter type with into modifiers needs to be put in parentheses, as is shown in the example above. This is to make the precedence clear: each element of the argument sequence is converted by itself. + ## Retrofitting Scala 2 libraries -A new annotation `allowConversions` has the same effect as an `into` modifier. It is defined as an `@experimental` class in package `scala.annotation`. It is intended to be used for retrofitting Scala 2 library code so that Scala 3 conversions can be applied to arguments without language imports. For instance, the definitions of +There is also an annotation `@into` in the `scala.annotation` package that has +has the same effect as an `into` modifier. It is intended to be used for retrofitting Scala 2 library code so that Scala 3 conversions can be applied to arguments without language imports. For instance, the definitions of `++` and `flatMap` in the Scala 2.13 `List` class could be retrofitted as follows. ```scala - def ++ (@allowConversions elems: IterableOnce[A]): List[A] - def flatMap[B](@allowConversions f: A => IterableOnce[B]): List[B] + def ++ (elems: IterableOnce[A] @into): List[A] + def flatMap[B](f: A => IterableOnce[B] @into): List[B] +``` +For Scala 3 code, the `into` modifier is preferred, because it adheres to the principle that annotations should not influence typing and type inference in Scala. + +## Restrictions + +The `into` modifier is only allowed in the types method parameters. It can be given either for the whole type, or some result type of a top-level function type, but not anywhere else. The `into` modifier does not propagate outside the method. In particular, a partially applied method does not propagate `into` modifiers to its result. + +**Example:** + +Say we have +```scala +def f(x: Int)(y: into Text): Unit +``` +then +```scala +f(3) : Text => Unit +``` +Note the `into` modifier is not longer present on the type of `f(3)`. Therefore, follow-on arguments to `f(3)` do not allow implicit conversions. Generally it is not possible to +define function types that allow implicit conversions on their arguments, but it is possible to define SAM types that allow conversions. E.g. +```scala +trait ConvArg: + def apply(x: into Text): Unit + +val x: ConvArg = f(3)(_) +``` + +Note this is similar to the way vararg parameters are handled in Scala. If we have +```scala +def g(x: Int)(y: Int*): Unit +``` +then +```scala +g(4) : Seq[Int] => Unit ``` -For Scala 3 code, the `into` modifier is preferred. First, because it is shorter, -and second, because it adheres to the principle that annotations should not influence -typing and type inference in Scala. +Observe that the vararg annotation also got dropped in the result type of `g(4)`. ## Syntax changes The addition to the grammar is: ``` -ParamType ::= [‘=>’] ParamValueType -ParamValueType ::= [‘into‘] ExactParamType -ExactParamType ::= Type [‘*’] +ParamType ::= [‘=>’] ParamValueType +ParamValueType ::= Type [‘*’] + | IntoType + | ‘(’ IntoType ‘)’ ‘*’ +IntoType ::= [‘into’] IntoTargetType + | ‘(’ IntoType ‘)’ +IntoTargetType ::= Type + | FunTypeArgs (‘=>’ | ‘?=>’) IntoType ``` -As the grammar shows, `into` can only applied to the type of a parameter; it is illegal in other positions. +As the grammar shows, `into` can only applied to the type of a parameter; it is illegal in other positions. Also, `into` modifiers in vararg types have to be enclosed in parentheses. diff --git a/library/src/scala/annotation/internal/$into.scala b/library/src/scala/annotation/internal/$into.scala new file mode 100644 index 000000000000..7009d829483f --- /dev/null +++ b/library/src/scala/annotation/internal/$into.scala @@ -0,0 +1,15 @@ +package scala.annotation.internal +import annotation.experimental + +/** An internal annotation on (part of) a parameter type that allows implicit conversions + * for its arguments. The publicly visible `into` annotation in the parent package + * `annotation` gets mapped to `$into` by the compiler in all places where + * conversions should be allowed. The reason for the split into two annotations + * is that `annotation.into` is given in source code and may propagate in unspecified + * ways through type inference. By contrast `$into` is constrained to be occur only + * on parameters of method types. This makes implicit conversion insertion + * predictable and independent of the un-specified aspects of type inference. + */ +@experimental +class $into() extends annotation.StaticAnnotation + diff --git a/library/src/scala/annotation/internal/Into.scala b/library/src/scala/annotation/into.scala similarity index 52% rename from library/src/scala/annotation/internal/Into.scala rename to library/src/scala/annotation/into.scala index a256636406c2..70a53ff9478d 100644 --- a/library/src/scala/annotation/internal/Into.scala +++ b/library/src/scala/annotation/into.scala @@ -1,14 +1,10 @@ -package scala.annotation.internal +package scala.annotation import annotation.experimental /** An annotation on (part of) a parameter type that allows implicit conversions * for its arguments. The `into` modifier on parameter types in Scala 3 is - * mapped to this annotation. We can also install a more generally accessible - * alias so that Scala 2 libraries can use the feature. + * mapped to this annotation. The annotation is intended to be used directly in + * Scala 2 sources only. For Scala 3, the `into` modifier should be preferred. */ @experimental class into() extends annotation.StaticAnnotation - -@experimental -class $into() extends annotation.StaticAnnotation - diff --git a/tests/neg-custom-args/convertible.check b/tests/neg-custom-args/convertible.check deleted file mode 100644 index c1ba6e9e6934..000000000000 --- a/tests/neg-custom-args/convertible.check +++ /dev/null @@ -1,21 +0,0 @@ --- [E120] Naming Error: tests/neg-custom-args/convertible.scala:15:6 --------------------------------------------------- -15 |trait C[X] extends A[X]: // error - | ^ - | Name clash between defined and inherited member: - | def f(x: X): Unit in trait A at line 10 and - | override def f(x: into X): Unit in trait C at line 16 - | have the same type after erasure. - | - | Consider adding a @targetName annotation to one of the conflicting definitions - | for disambiguation. --- [E120] Naming Error: tests/neg-custom-args/convertible.scala:18:6 --------------------------------------------------- -18 |class D[X] extends B[X], C[X] // error - | ^ - | Name clash between inherited members: - | override def f(x: X): Unit in trait B at line 13 and - | override def f(x: into X): Unit in trait C at line 16 - | have the same type after erasure. - | - | Consider adding a @targetName annotation to one of the conflicting definitions - | for disambiguation. -there was 1 feature warning; re-run with -feature for details diff --git a/tests/pos/into-sam.scala b/tests/pos/into-sam.scala new file mode 100644 index 000000000000..7513b5c5b0de --- /dev/null +++ b/tests/pos/into-sam.scala @@ -0,0 +1,18 @@ + +//> using options -feature -Xfatal-warnings + +import language.experimental.into + +class Text(val str: String) + +given Conversion[String, Text] = Text(_) +object Test: + def f(x: Int)(y: into Text): Unit = () + val _: Text => Unit = f(3) + + trait ConvArg: + def apply(x: into Text): Unit + + val x: ConvArg = f(3)(_) + + x("abc") diff --git a/tests/run-tasty-inspector/stdlibExperimentalDefinitions.scala b/tests/run-tasty-inspector/stdlibExperimentalDefinitions.scala index 247f7ecc8e9b..ca48dd2d8a5f 100644 --- a/tests/run-tasty-inspector/stdlibExperimentalDefinitions.scala +++ b/tests/run-tasty-inspector/stdlibExperimentalDefinitions.scala @@ -57,7 +57,7 @@ val experimentalDefinitionInLibrary = Set( "scala.caps$", //// New feature: into - "scala.annotation.internal.into", + "scala.annotation.into", "scala.annotation.internal.$into", //// New feature: @publicInBinary From bd5e331dbe45ebc2805e44cff006ac3ddf947ee4 Mon Sep 17 00:00:00 2001 From: odersky Date: Thu, 15 Feb 2024 10:40:26 +0100 Subject: [PATCH 4/5] Fix typos --- docs/_docs/reference/experimental/into-modifier.md | 4 ++-- library/src/scala/annotation/internal/$into.scala | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/docs/_docs/reference/experimental/into-modifier.md b/docs/_docs/reference/experimental/into-modifier.md index 0c1d24b1d970..358bd0305699 100644 --- a/docs/_docs/reference/experimental/into-modifier.md +++ b/docs/_docs/reference/experimental/into-modifier.md @@ -73,7 +73,7 @@ For Scala 3 code, the `into` modifier is preferred, because it adheres to the pr ## Restrictions -The `into` modifier is only allowed in the types method parameters. It can be given either for the whole type, or some result type of a top-level function type, but not anywhere else. The `into` modifier does not propagate outside the method. In particular, a partially applied method does not propagate `into` modifiers to its result. +The `into` modifier is only allowed in the types of method parameters. It can be given either for the whole type, or some result type of a top-level function type, but not anywhere else. The `into` modifier does not propagate outside the method. In particular, a partially applied method does not propagate `into` modifiers to its result. **Example:** @@ -117,4 +117,4 @@ IntoType ::= [‘into’] IntoTargetType IntoTargetType ::= Type | FunTypeArgs (‘=>’ | ‘?=>’) IntoType ``` -As the grammar shows, `into` can only applied to the type of a parameter; it is illegal in other positions. Also, `into` modifiers in vararg types have to be enclosed in parentheses. +As the grammar shows, `into` can only applied in the type of a parameter; it is illegal in other positions. Also, `into` modifiers in vararg types have to be enclosed in parentheses. diff --git a/library/src/scala/annotation/internal/$into.scala b/library/src/scala/annotation/internal/$into.scala index 7009d829483f..4d8788724e25 100644 --- a/library/src/scala/annotation/internal/$into.scala +++ b/library/src/scala/annotation/internal/$into.scala @@ -6,7 +6,7 @@ import annotation.experimental * `annotation` gets mapped to `$into` by the compiler in all places where * conversions should be allowed. The reason for the split into two annotations * is that `annotation.into` is given in source code and may propagate in unspecified - * ways through type inference. By contrast `$into` is constrained to be occur only + * ways through type inference. By contrast `$into` is constrained to occur only * on parameters of method types. This makes implicit conversion insertion * predictable and independent of the un-specified aspects of type inference. */ From cea5af1bdd0d4eb63d297cc756571ec17c46157e Mon Sep 17 00:00:00 2001 From: odersky Date: Tue, 27 Feb 2024 19:57:16 +0100 Subject: [PATCH 5/5] Implement review suggestions --- compiler/src/dotty/tools/dotc/core/Types.scala | 4 ++-- docs/_docs/reference/experimental/into-modifier.md | 2 +- tests/warn/convertible.scala | 6 +++--- 3 files changed, 6 insertions(+), 6 deletions(-) diff --git a/compiler/src/dotty/tools/dotc/core/Types.scala b/compiler/src/dotty/tools/dotc/core/Types.scala index 71f9ab196ed2..e38fbbb4b355 100644 --- a/compiler/src/dotty/tools/dotc/core/Types.scala +++ b/compiler/src/dotty/tools/dotc/core/Types.scala @@ -1928,7 +1928,7 @@ object Types extends TypeUtils { case res => res } defn.FunctionNOf( - mt.paramInfos.mapConserve: + mt.paramInfos.mapConserve: _.translateFromRepeated(toArray = isJava) .mapIntoAnnot(defn.IntoParamAnnot, null), result1, isContextual) @@ -1989,7 +1989,7 @@ object Types extends TypeUtils { val tp1 = tp.mapIntoAnnot(from, to) if annot.symbol == from then if to == null then tp1 - else AnnotatedType(tp1, Annotation(to, from.span)) + else AnnotatedType(tp1, Annotation(to, annot.tree.span)) else self.derivedAnnotatedType(tp1, annot) case AppliedType(tycon, arg :: Nil) if tycon.typeSymbol == defn.RepeatedParamClass => val arg1 = arg.mapIntoAnnot(from, to) diff --git a/docs/_docs/reference/experimental/into-modifier.md b/docs/_docs/reference/experimental/into-modifier.md index 358bd0305699..54da5f976320 100644 --- a/docs/_docs/reference/experimental/into-modifier.md +++ b/docs/_docs/reference/experimental/into-modifier.md @@ -63,7 +63,7 @@ Note that a vararg parameter type with into modifiers needs to be put in parenth ## Retrofitting Scala 2 libraries There is also an annotation `@into` in the `scala.annotation` package that has -has the same effect as an `into` modifier. It is intended to be used for retrofitting Scala 2 library code so that Scala 3 conversions can be applied to arguments without language imports. For instance, the definitions of +the same effect as an `into` modifier. It is intended to be used for retrofitting Scala 2 library code so that Scala 3 conversions can be applied to arguments without language imports. For instance, the definitions of `++` and `flatMap` in the Scala 2.13 `List` class could be retrofitted as follows. ```scala def ++ (elems: IterableOnce[A] @into): List[A] diff --git a/tests/warn/convertible.scala b/tests/warn/convertible.scala index b830093fc891..b701cac32cec 100644 --- a/tests/warn/convertible.scala +++ b/tests/warn/convertible.scala @@ -32,13 +32,13 @@ object Test: c1("abc") // warn, eta expansion does not preserve into val c2 = if ??? then g else g3 - c2("abc") // warn, eta expesnion does not preserve into + c2("abc") // warn, eta expansion does not preserve into val c3 = if ??? then g3 else g - c3("abc") // warn, eta expesnion does not preserve into + c3("abc") // warn, eta expansion does not preserve into def h1[X](x: X)(y: X): Unit = () def h(x: into Text) = val y = h1(x) - y("abc") // warn, eta expesnion does not preserve into \ No newline at end of file + y("abc") // warn, eta expansion does not preserve into \ No newline at end of file