Scala Generic List addition - scala

I have function:
def listSum[T](xs :List[T])(implicit abc : Numeric[T]): T = {
xs.sum
}
val IntList: List[Int] = List (1, 2, 3, 4)
val DList: List[Double] = List (1.0, 2.0, 3, 4)
the code example above works fine, but when I change to the function below it stops working with error
could not find implicit value for parameter abc: Numeric[AnyVal]
Since AnyVal is the base type I can do the addition, can't I ?
where are all the implicits defined?
def listSum(xs :List[AnyVal])(implicit abc : Numeric[AnyVal]) = {
xs.sum
}
val AList: List[AnyVal] = List (1, 2, 3, 4)
Also this is not working , I think for the same reason .
def listSum[T](xs :List[T])(implicit abc : Numeric[T]): T = {
xs.sum
}
val BList : List[Boolean] = List(true, false)
println(listSum(BList))

There are several incorrent assumptions in your question:
AnyVal is the supertype of all primitive types and value classes. Along with AnyRef it's one of two type branches, rooted in the Any type, which is true supertype of all.
Numeric type is not covariant which means that existence of Numeric[Int] does not imply existence of Numeric[AnyVal], which is very logical, if you think for a second. Integer numbers is subdomain of Real numbers, but knowing how to multiply integers does not mean you know how to multiply reals.
Subtyping polymorphism is not directly related to restricted parametric polymorphism. First is mostly handled runtime while second is generally for compile-time. They interact in very specific ways in scala.
There is no single place where implicit values are defined. There are multiple places for each specific type and place in code.

All the implicit definitions for Numeric[T] are defined in scala/math/Numeric.scala
(assuming scala 2.10.4)
There is no implicit definition for Numeric[AnyVal], so this is why you get the error for your first example (this makes sense, because one cannot define numeric operations without knowing anything about the underlying type)
There is also no implicit definition for Numeric[Boolean], which is why you get the error for your second example (this also makes sense, because one cannot define the plus, minus, times, negate, etc. operation on Booleans without assuming anything about the specific domain of the project).
you can define an implicit Numeric[Boolean] yourself if that makes sense for your project, but it would be better to avoid using the implicit Numeric[T] for the Boolean type.

Related

Why does Scala sometimes ignore types that are clearly defined?

so here's the problem I keep running into various situations with Scala - it seemingly ignores the implied type, even when the situation is clear. Granted this could be my understanding I admit, but when it comes to underscore placeholders I keep running into trouble. For example below (this is fictional just to prove the point).The 2nd position of trait X has to be <:X[,] of some kind. There's no ambiguity here - so anywhere that scala sees this position, regardless of how weak it's coded - the contact is X and I should have access to functions like "doesX". Isn't that indisputable? No matter how poorly I deal with that position in the code, I must at least get X. Why does Scala constantly ignore this fact when you get deep into the type system? Any pointers would be appreciated, thank you!
object TestRun extends App {
trait X[T, Y<:X[_,_]] {
def doesX:Unit
def providesY:Y
}
class Test extends X[Int,Test]{
override def doesX: Unit = println("etc..")
def providesY:Test = new Test
}
val a:X[_,_] = new Test //yes I know I could define a better here, its just to demo. I shouldn't have to explicitly relabel the 2nd _ as _<:X[_,<:X[ etc..
val b = a.providesY //clearly this has to be at least a (something) WITH X, but scala claims this as "Any"
b.doesX //error won't compile!!
//trait
}
When you write:
val a: X[_, _] = new Test
^
// This is treated as if the type parameter is Any, for the most part
You are telling the compiler that a is an X, where you don't care what its type parameters are. That is, the unbounded wildcard _ is assumed to have an upper-bound of Any, and that's it.
providesY uses the second type parameter of X to determine its return type, but for a the compiler was told that to discard it. So b is just an Any. This is easier to see using the REPL:
scala> val a: X[_, _] = new Test
a: X[_, _] = Test#27abe2cd
scala> val b = a.providesY
b: Any = Test#f5f2bb7
Therefore, b.doesX fails to compile because the compiler now thinks it is Any. The simple solution is not to use wild cards for types (or any existential types in general, most of the time you do not want this).
scala> val a: X[Int, Test] = new Test
a: X[Int,Test] = Test#1134affc
scala> val b = a.providesY
b: Test = Test#6fc6f14e
scala> b.doesX
etc..
Or you could simply leave off the type annotation, and let the compiler infer the correct type.

Scala : Does variable type inference affect performance?

In Scala, you can declare a variable by specifying the type, like this: (method 1)
var x : String = "Hello World"
or you can let Scala automatically detect the variable type (method 2)
var x = "Hello World"
Why would you use method 1? Does it have a performance benefit?
And once the variable has been declared, will it behave exactly the same in all situations wether it has been declared by method 1 or method 2?
Type inference is done at compile time - it's essentially the compiler figuring out what you mean, filling in the blanks, and then compiling the resulting code.
What this means is that there can be no runtime cost to type inference. The compile time cost, however, can sometimes be prohibitive and require you to explicitly annotate some of your expressions.
You will not have any performance difference using this two variants.
They will both be compiled to the same code.
The other answers assume that the compiler inferred what you think it inferred.
It is easy to demonstrate that specifying the type in a definition will set the expected type for the RHS of the definition and guide type inference.
For example, in this method that builds a collection of something, A is inferred to be Nothing, which may not be what you wanted:
scala> def build[A, B, C <: Iterable[B]](bs: B*)(implicit cbf: CanBuildFrom[A, B, C]): C = {
| val b = cbf(); println(b.getClass); b ++= bs; b.result }
build: [A, B, C <: Iterable[B]](bs: B*)(implicit cbf: scala.collection.generic.CanBuildFrom[A,B,C])C
scala> val xs = build(1,2,3)
class scala.collection.immutable.VectorBuilder
xs: scala.collection.immutable.IndexedSeq[Int] = Vector(1, 2, 3)
scala> val xs: List[Int] = build(1,2,3)
class scala.collection.mutable.ListBuffer
xs: List[Int] = List(1, 2, 3)
scala> val xs: Seq[Int] = build(1,2,3)
class scala.collection.immutable.VectorBuilder
xs: Seq[Int] = Vector(1, 2, 3)
Obviously, it matters for runtime performance whether you get a List or a Vector.
This is a lame example, but in many expressions you wouldn't notice the type of an intermediate collection unless it caused a performance problem.
Sample conversations:
https://groups.google.com/forum/#!msg/scala-language/mQ-bIXbC1zs/wgSD4Up5gYMJ
http://grokbase.com/p/gg/scala-user/137mgpjg98/another-funny-quirk
Why is Seq.newBuilder returning a ListBuffer?
https://groups.google.com/forum/#!topic/scala-user/1SjYq_qFuKk
In the simple example you gave, there is no difference in the generated byte code, and therefore no difference in performance. It would also make no noticeable difference in compilation speed.
In more complex code (likely involving implicits) you could run into cases where compile-type performance would be noticeably improved by specifying some types. However, I would completely ignore this until and unless you run into it -- specify types or not for other, better reasons.
More in line with your question, there is one very important case where it is a good idea to specify the type to ensure good run-time performance. Consider this code:
val x = new AnyRef { def sayHi() = println("Howdy!") }
x.sayHi
That code uses reflection to call sayHi, and that's a huge performance hit. Recent versions of Scala will warn you about this code for that reason, unless you have enabled the language feature for it:
warning: reflective access of structural type member method sayHi should be enabled
by making the implicit value scala.language.reflectiveCalls visible.
This can be achieved by adding the import clause 'import scala.language.reflectiveCalls'
or by setting the compiler option -language:reflectiveCalls.
See the Scala docs for value scala.language.reflectiveCalls for a discussion
why the feature should be explicitly enabled.
You might then change the code to this, which does not make use of reflection:
trait Talkative extends AnyRef { def sayHi(): Unit }
val x = new Talkative { def sayHi() = println("Howdy!") }
x.sayHi
For this reason you generally want to specify the type of the variable when you are defining classes this way; that way if you inadvertently add a method that would require reflection to call, you'll get a compilation error -- the method won't be defined for the variable's type. So while it is not the case that specifying the type makes the code run faster, it is the case that if the code would be slow, specifying the type makes it fail to compile.
val x: AnyRef = new AnyRef { def sayHi() = println("Howdy!") }
x.sayHi // ERROR: sayHi is not defined on AnyRef
There are of course other reasons why you might want to specify a type. They are required for the formal parameters of methods/functions, and for the return types of methods that are recursive or overloaded.
Also, you should always specify return types for methods in a public API (unless they are just trivially obvious), or you might end up with different method signatures than you intended, and then risk breaking existing clients of your API when you fix the signature.
You may of course want to deliberately widen a type so that you can assign other types of things to a variable later, e.g.
var shape: Shape = new Circle(1.0)
shape = new Square(1.0)
But in these cases there is no performance impact.
It is also possible that specifying a type will cause a conversion, and of course that will have whatever performance impact the conversion imposes.

Scala contravariance - real life example

I understand covariance and contravariance in scala. Covariance has many applications in the real world, but I can not think of any for contravariance applications, except the same old examples for Functions.
Can someone shed some light on real world examples of contravariance use?
In my opinion, the two most simple examples after Function are ordering and equality. However, the first is not contra-variant in Scala's standard library, and the second doesn't even exist in it. So, I'm going to use Scalaz equivalents: Order and Equal.
Next, I need some class hierarchy, preferably one which is familiar and, of course, it both concepts above must make sense for it. If Scala had a Number superclass of all numeric types, that would have been perfect. Unfortunately, it has no such thing.
So I'm going to try to make the examples with collections. To make it simple, let's just consider Seq[Int] and List[Int]. It should be clear that List[Int] is a subtype of Seq[Int], ie, List[Int] <: Seq[Int].
So, what can we do with it? First, let's write something that compares two lists:
def smaller(a: List[Int], b: List[Int])(implicit ord: Order[List[Int]]) =
if (ord.order(a,b) == LT) a else b
Now I'm going to write an implicit Order for Seq[Int]:
implicit val seqOrder = new Order[Seq[Int]] {
def order(a: Seq[Int], b: Seq[Int]) =
if (a.size < b.size) LT
else if (b.size < a.size) GT
else EQ
}
With these definitions, I can now do something like this:
scala> smaller(List(1), List(1, 2, 3))
res0: List[Int] = List(1)
Note that I'm asking for an Order[List[Int]], but I'm passing a Order[Seq[Int]]. This means that Order[Seq[Int]] <: Order[List[Int]]. Given that Seq[Int] >: List[Int], this is only possible because of contra-variance.
The next question is: does it make any sense?
Let's consider smaller again. I want to compare two lists of integers. Naturally, anything that compares two lists is acceptable, but what's the logic of something that compares two Seq[Int] being acceptable?
Note in the definition of seqOrder how the things being compared becomes parameters to it. Obviously, a List[Int] can be a parameter to something expecting a Seq[Int]. From that follows that a something that compares Seq[Int] is acceptable in place of something that compares List[Int]: they both can be used with the same parameters.
What about the reverse? Let's say I had a method that only compared :: (list's cons), which, together with Nil, is a subtype of List. I obviously could not use this, because smaller might well receive a Nil to compare. It follows that an Order[::[Int]] cannot be used instead of Order[List[Int]].
Let's proceed to equality, and write a method for it:
def equalLists(a: List[Int], b: List[Int])(implicit eq: Equal[List[Int]]) = eq.equal(a, b)
Because Order extends Equal, I can use it with the same implicit above:
scala> equalLists(List(4, 5, 6), List(1, 2, 3)) // we are comparing lengths!
res3: Boolean = true
The logic here is the same one. Anything that can tell whether two Seq[Int] are the same can, obviously, also tell whether two List[Int] are the same. From that, it follows that Equal[Seq[Int]] <: Equal[List[Int]], which is true because Equal is contra-variant.
This example is from the last project I was working on. Say you have a type-class PrettyPrinter[A] that provides logic for pretty-printing objects of type A. Now if B >: A (i.e. if B is superclass of A) and you know how to pretty-print B (i.e. have an instance of PrettyPrinter[B] available) then you can use the same logic to pretty-print A. In other words, B >: A implies PrettyPrinter[B] <: PrettyPrinter[A]. So you can declare PrettyPrinter[A] contravariant on A.
scala> trait Animal
defined trait Animal
scala> case class Dog(name: String) extends Animal
defined class Dog
scala> trait PrettyPrinter[-A] {
| def pprint(a: A): String
| }
defined trait PrettyPrinter
scala> def pprint[A](a: A)(implicit p: PrettyPrinter[A]) = p.pprint(a)
pprint: [A](a: A)(implicit p: PrettyPrinter[A])String
scala> implicit object AnimalPrettyPrinter extends PrettyPrinter[Animal] {
| def pprint(a: Animal) = "[Animal : %s]" format (a)
| }
defined module AnimalPrettyPrinter
scala> pprint(Dog("Tom"))
res159: String = [Animal : Dog(Tom)]
Some other examples would be Ordering type-class from Scala standard library, Equal, Show (isomorphic to PrettyPrinter above), Resource type-classes from Scalaz etc.
Edit:
As Daniel pointed out, Scala's Ordering isn't contravariant. (I really don't know why.) You may instead consider scalaz.Order which is intended for the same purpose as scala.Ordering but is contravariant on its type parameter.
Addendum:
Supertype-subtype relationship is but one type of relationship that can exist between two types. There can be many such relationships possible. Let's consider two types A and B related with function f: B => A (i.e. an arbitrary relation). Data-type F[_] is said to be a contravariant functor if you can define an operation contramap for it that can lift a function of type B => A to F[A => B].
The following laws need to be satisfied:
x.contramap(identity) == x
x.contramap(f).contramap(g) == x.contramap(f compose g)
All of the data types discussed above (Show, Equal etc.) are contravariant functors. This property lets us do useful things such as the one illustrated below:
Suppose you have a class Candidate defined as:
case class Candidate(name: String, age: Int)
You need an Order[Candidate] which orders candidates by their age. Now you know that there is an Order[Int] instance available. You can obtain an Order[Candidate] instance from that with the contramap operation:
val byAgeOrder: Order[Candidate] =
implicitly[Order[Int]] contramap ((_: Candidate).age)
An example based on a real-world event-driven software system. Such a system is based on broad categories of events, like events related to the functioning of the system (system events), events generated by user actions (user events) and so on.
A possible event hierarchy:
trait Event
trait UserEvent extends Event
trait SystemEvent extends Event
trait ApplicationEvent extends SystemEvent
trait ErrorEvent extends ApplicationEvent
Now the programmers working on the event-driven system need to find a way to register/process the events generated in the system. They will create a trait, Sink, that is used to mark components in need to be notified when an event has been fired.
trait Sink[-In] {
def notify(o: In)
}
As a consequence of marking the type parameter with the - symbol, the Sink type became contravariant.
A possible way to notify interested parties that an event happened is to write a method and to pass it the corresponding event. This method will hypothetically do some processing and then it will take care of notifying the event sink:
def appEventFired(e: ApplicationEvent, s: Sink[ApplicationEvent]): Unit = {
// do some processing related to the event
// notify the event sink
s.notify(e)
}
def errorEventFired(e: ErrorEvent, s: Sink[ErrorEvent]): Unit = {
// do some processing related to the event
// notify the event sink
s.notify(e)
}
A couple of hypothetical Sink implementations.
trait SystemEventSink extends Sink[SystemEvent]
val ses = new SystemEventSink {
override def notify(o: SystemEvent): Unit = ???
}
trait GenericEventSink extends Sink[Event]
val ges = new GenericEventSink {
override def notify(o: Event): Unit = ???
}
The following method calls are accepted by the compiler:
appEventFired(new ApplicationEvent {}, ses)
errorEventFired(new ErrorEvent {}, ges)
appEventFired(new ApplicationEvent {}, ges)
Looking at the series of calls you notice that it is possible to call a method expecting a Sink[ApplicationEvent] with a Sink[SystemEvent] and even with a Sink[Event]. Also, you can call the method expecting a Sink[ErrorEvent] with a Sink[Event].
By replacing invariance with a contravariance constraint, a Sink[SystemEvent] becomes a subtype of Sink[ApplicationEvent]. Therefore, contravariance can also be thought of as a ‘widening’ relationship, since types are ‘widened’ from more specific to more generic.
Conclusion
This example has been described in a series of articles about variance found on my blog
In the end, I think it helps to also understand the theory behind it...
Short answer that might help people who were super confused like me and didn't want to read these long winded examples:
Imagine you have 2 classes Animal, and Cat, which extends Animal. Now, imagine that you have a type Printer[Cat], that contains the functionality for printing Cats. And you have a method like this:
def print(p: Printer[Cat], cat: Cat) = p.print(cat)
but the thing is, that since Cat is an Animal, Printer[Animal] should also be able to print Cats, right?
Well, if Printer[T] were defined like Printer[-T], i.e. contravariant, then we could pass Printer[Animal] to the print function above and use its functionality to print cats.
This is why contravariance exists. Another example, from C#, for example, is the class IComparer which is contravariant as well. Why? Because we should be able to use Animal comparers to compare Cats, too.

Map from Class[T] to T without casting

I want to map from class tokens to instances along the lines of the following code:
trait Instances {
def put[T](key: Class[T], value: T)
def get[T](key: Class[T]): T
}
Can this be done without having to resolve to casts in the get method?
Update:
How could this be done for the more general case with some Foo[T] instead of Class[T]?
You can try retrieving the object from your map as an Any, then using your Class[T] to “cast reflectively”:
trait Instances {
private val map = collection.mutable.Map[Class[_], Any]()
def put[T](key: Class[T], value: T) { map += (key -> value) }
def get[T](key: Class[T]): T = key.cast(map(key))
}
With help of a friend of mine, we defined the map with keys as Manifest instead of Class which gives a better api when calling.
I didnt get your updated question about "general case with some Foo[T] instead of Class[T]". But this should work for the cases you specified.
object Instances {
private val map = collection.mutable.Map[Manifest[_], Any]()
def put[T: Manifest](value: T) = map += manifest[T] -> value
def get[T: Manifest]: T = map(manifest[T]).asInstanceOf[T]
def main (args: Array[String] ) {
put(1)
put("2")
println(get[Int])
println(get[String])
}
}
If you want to do this without any casting (even within get) then you will need to write a heterogeneous map. For reasons that should be obvious, this is tricky. :-) The easiest way would probably be to use a HList-like structure and build a find function. However, that's not trivial since you need to define some way of checking type equality for two arbitrary types.
I attempted to get a little tricky with tuples and existential types. However, Scala doesn't provide a unification mechanism (pattern matching doesn't work). Also, subtyping ties the whole thing in knots and basically eliminates any sort of safety it might have provided:
val xs: List[(Class[A], A) forSome { type A }] = List(
classOf[String] -> "foo", classOf[Int] -> 42)
val search = classOf[String]
val finalResult = xs collect { case (`search`, result) => result } headOption
In this example, finalResult will be of type Any. This is actually rightly so, since subtyping means that we don't really know anything about A. It's not why the compiler is choosing that type, but it is a correct choice. Take for example:
val xs: List[(Class[A], A) forSome { type A }] = List(classOf[Boolean] -> 'bippy)
This is totally legal! Subtyping means that A in this case will be chosen as Any. It's hardly what we want, but it is what you will get. Thus, in order to express this constraint without tracking all of the types individual (using a HMap), Scala would need to be able to express the constraint that a type is a specific type and nothing else. Unfortunately, Scala does not have this ability, and so we're basically stuck on the generic constraint front.
Update Actually, it's not legal. Just tried it and the compiler kicked it out. I think that only worked because Class is invariant in its type parameter. So, if Foo is a definite type that is invariant, you should be safe from this case. It still doesn't solve the unification problem, but at least it's sound. Unfortunately, type constructors are assumed to be in a magical super-position between co-, contra- and invariance, so if it's truly an arbitrary type Foo of kind * => *, then you're still sunk on the existential front.
In summary: it should be possible, but only if you fully encode Instances as a HMap. Personally, I would just cast inside get. Much simpler!

How do I form the union of scala SortedMaps?

(I'm using Scala nightlies, and see the same behaviour in 2.8.0b1 RC4. I'm a Scala newcomer.)
I have two SortedMaps that I'd like to form the union of. Here's the code I'd like to use:
import scala.collection._
object ViewBoundExample {
class X
def combine[Y](a: SortedMap[X, Y], b: SortedMap[X, Y]): SortedMap[X, Y] = {
a ++ b
}
implicit def orderedX(x: X): Ordered[X] = new Ordered[X] { def compare(that: X) = 0 }
}
The idea here is the 'implicit' statement means Xs can be converted to Ordered[X]s, and then it makes sense combine SortedMaps into another SortedMap, rather than just a map.
When I compile, I get
sieversii:scala-2.8.0.Beta1-RC4 scott$ bin/scalac -versionScala compiler version
2.8.0.Beta1-RC4 -- Copyright 2002-2010, LAMP/EPFL
sieversii:scala-2.8.0.Beta1-RC4 scott$ bin/scalac ViewBoundExample.scala
ViewBoundExample.scala:8: error: type arguments [ViewBoundExample.X] do not
conform to method ordered's type parameter bounds [A <: scala.math.Ordered[A]]
a ++ b
^
one error found
It seems my problem would go away if that type parameter bound was [A <% scala.math.Ordered[A]], rather than [A <: scala.math.Ordered[A]]. Unfortunately, I can't even work out where the method 'ordered' lives! Can anyone help me track it down?
Failing that, what am I meant to do to produce the union of two SortedMaps? If I remove the return type of combine (or change it to Map) everything works fine --- but then I can't rely on the return being sorted!
Currently, what you are using is the scala.collection.SortedMap trait, whose ++ method is inherited from the MapLike trait. Therefore, you see the following behaviour:
scala> import scala.collection.SortedMap
import scala.collection.SortedMap
scala> val a = SortedMap(1->2, 3->4)
a: scala.collection.SortedMap[Int,Int] = Map(1 -> 2, 3 -> 4)
scala> val b = SortedMap(2->3, 4->5)
b: scala.collection.SortedMap[Int,Int] = Map(2 -> 3, 4 -> 5)
scala> a ++ b
res0: scala.collection.Map[Int,Int] = Map(1 -> 2, 2 -> 3, 3 -> 4, 4 -> 5)
scala> b ++ a
res1: scala.collection.Map[Int,Int] = Map(1 -> 2, 2 -> 3, 3 -> 4, 4 -> 5)
The type of the return result of ++ is a Map[Int, Int], because this would be the only type it makes sense the ++ method of a MapLike object to return. It seems that ++ keeps the sorted property of the SortedMap, which I guess it is because ++ uses abstract methods to do the concatenation, and those abstract methods are defined as to keep the order of the map.
To have the union of two sorted maps, I suggest you use scala.collection.immutable.SortedMap.
scala> import scala.collection.immutable.SortedMap
import scala.collection.immutable.SortedMap
scala> val a = SortedMap(1->2, 3->4)
a: scala.collection.immutable.SortedMap[Int,Int] = Map(1 -> 2, 3 -> 4)
scala> val b = SortedMap(2->3, 4->5)
b: scala.collection.immutable.SortedMap[Int,Int] = Map(2 -> 3, 4 -> 5)
scala> a ++ b
res2: scala.collection.immutable.SortedMap[Int,Int] = Map(1 -> 2, 2 -> 3, 3 -> 4, 4 -> 5)
scala> b ++ a
res3: scala.collection.immutable.SortedMap[Int,Int] = Map(1 -> 2, 2 -> 3, 3 -> 4, 4 -> 5)
This implementation of the SortedMap trait declares a ++ method which returns a SortedMap.
Now a couple of answers to your questions about the type bounds:
Ordered[T] is a trait which if mixed in a class it specifies that that class can be compared using <, >, =, >=, <=. You just have to define the abstract method compare(that: T) which returns -1 for this < that, 1 for this > that and 0 for this == that. Then all other methods are implemented in the trait based on the result of compare.
T <% U represents a view bound in Scala. This means that type T is either a subtype of U or it can be implicitly converted to U by an implicit conversion in scope. The code works if you put <% but not with <: as X is not a subtype of Ordered[X] but can be implicitly converted to Ordered[X] using the OrderedX implicit conversion.
Edit: Regarding your comment. If you are using the scala.collection.immutable.SortedMap, you are still programming to an interface not to an implementation, as the immutable SortedMap is defined as a trait. You can view it as a more specialised trait of scala.collection.SortedMap, which provides additional operations (like the ++ which returns a SortedMap) and the property of being immutable. This is in line with the Scala philosophy - prefer immutability - therefore I don't see any problem of using the immutable SortedMap. In this case you can guarantee the fact that the result will definitely be sorted, and this can't be changed as the collection is immutable.
Though, I still find it strange that the scala.collection.SortedMap does not provide a ++ method witch returns a SortedMap as a result. All the limited testing I have done seem to suggest that the result of a concatenation of two scala.collection.SortedMaps indeed produces a map which keeps the sorted property.
Have you picked a tough nut to crack as a beginner to Scala! :-)
Ok, brief tour, don't expect to fully understand it right now. First, note that the problem happens at the method ++. Searching for its definition, we find it at the trait MapLike, receiving either an Iterator or a Traversable. Since y is a SortedMap, then it is the Traversable version being used.
Note in its extensive type signature that there is a CanBuildFrom being passed. It is being passed implicitly, so you don't normally need to worry about it. However, to understand what is going on, this time you do.
You can locate CanBuildFrom by either clicking on it where it appears in the definition of ++, or by filtering. As mentioned by Randall on the comments, there's an unmarked blank field on the upper left of the scaladoc page. You just have to click there and type, and it will return matches for whatever it is you typed.
So, look up the trait CanBuildFrom on ScalaDoc and select it. It has a large number of subclasses, each one responsible for building a specific type of collection. Search for and click on the subclass SortedMapCanBuildFrom. This is the class of the object you need to produce a SortedMap from a Traversable. Note on the instance constructor (the constructor for the class) that it receives an implicit Ordering parameter. Now we are getting closer.
This time, use the filter filter to search for Ordering. Its companion object (click on the small "o" the name) hosts an implicit that will generate Orderings, as companion objects are examined for implicits generating instances or conversions for that class. It is defined inside the trait LowPriorityOrderingImplicits, which object Ordering extends, and looking at it you'll see the method ordered[A <: Ordered[A]], which will produce the Ordering required... or would produce it, if only there wasn't a problem.
One might assume the implicit conversion from X to Ordered[X] would be enough, just as I had before looking more carefully into this. That, however, is a conversion of objects, and ordered expects to receive a type which is a subtype of Ordered[X]. While one can convert an object of type X to an object of type Ordered[X], X, itself, is not a subtype of Ordered[X], so it can't be passed as a parameter to ordered.
On the other hand, you can create an implicit val Ordering[X], instead of the def Ordered[X], and you'll get around the problem. Specifically:
object ViewBoundExample {
class X
def combine[Y](a: SortedMap[X, Y], b: SortedMap[X, Y]): SortedMap[X, Y] = {
a ++ b
}
implicit val orderingX = new Ordering[X] { def compare(x: X, y: X) = 0 }
}
I think most people initial reaction to Ordered/Ordering must be one of perplexity: why have classes for the same thing? The former extends java.lang.Comparable, whereas the latter extends java.util.Comparator. Alas, the type signature for compare pretty much sums the main difference:
def compare(that: A): Int // Ordered
def compare(x: T, y: T): Int // Ordering
The use of an Ordered[A] requires for either A to extend Ordered[A], which would require one to be able to modify A's definition, or to pass along a method which can convert an A into an Ordered[A]. Scala is perfectly capable of doing the latter easily, but then you have to convert each instance before comparing.
On the other hand, the use of Ordering[A] requires the creation of a single object, such as demonstrated above. When you use it, you just pass two objects of type A to compare -- no objects get created in the process.
So there are some performance gains to be had, but there is a much more important reason for Scala's preference for Ordering over Ordered. Look again on the companion object to Ordering. You'll note that there are several implicits for many of Scala classes defined in there. You may recall I mentioned earlier that an implicit for class T will be searched for inside the companion object of T, and that's exactly what is going on.
This could be done for Ordered as well. However, and this is the sticking point, that means every method supporting both Ordering and Ordered would fail! That's because Scala would look for an implicit to make it work, and would find two: one for Ordering, one for Ordered. Being unable to decide which is it you wanted, Scala gives up with an error message. So, a choice had to be made, and Ordering had more going on for it.
Duh, I forgot to explain why the signature isn't defined as ordered[A <% Ordered[A]], instead of ordered[A <: Ordered[A]]. I suspect doing so would cause the double implicits failure I have mentioned before, but I'll ask the guy who actually did this stuff and had the double implicit problems whether this particular method is problematic.