Scala: reflection against named arguments - scala

I'm trying to pass named arguments to a function from a regular Scala object like string/list/map, where the name of the argument and it's value are both variable (in my case from parsed user input). Is there a way to do this in Scala? I'm in principal looking for a short program in scala, similar to this in python:
def surprise(animal, color):
print('Oh, a ' + color + ' ' + animal + '!')
arguments = {'animal': 'cat', 'color': 'black'}
surprise(**arguments)
Since python can unpack dictionaries into named arguments, this results in
Oh, a black cat!
I've been searching for this functionality in scala, but I could not find it. Can anyone give me an example on how to accomplish this in scala?
Thanks in advance!

I would say, it is not that easy as in python, but I will try to propose couple of solutions. You need to extract your parameters from json (or other user input) with types and with order. It could be done using, for example, helper case class and play-json:
def surprise(animal: String, color: String): Unit = {
println(s"Oh, a $color $animal!")
}
import play.api.libs.json.{JsValue, Json}
case class FuncArguments(animal: String, color: String)
implicit val funcArgumentsFormat = Json.format[FuncArguments]
implicit def jsValueToFuncArguments(json: JsValue): FuncArguments =
json.as[FuncArguments]
def surprise2(json: JsValue): Unit = {
(surprise _).tupled(FuncArguments.unapply(json).get)
}
case class has same signature as your method. implicit val funcArgumentsFormatis play-json format to extract your data into case class (unsafe, because of as. Will throw Exception in case of missing required argument names/types in json), implicit def jsValueToFuncArguments converts your json into case class (theoretically also unsafe, because of Option.get, but do not think that you can get exception here). And helper function surprise2 to convert json into arguments.
Another approach would be, for example, to use some reflection:
import play.api.libs.json.{JsValue, Json}
class SomeClass {
def surprise(animal: String, color: String): Unit = {
println(s"Oh, a $color $animal!")
}
}
def surprise3(json: JsValue): Unit = {
val method = classOf[SomeClass].getMethods.find(_.getName == "surprise").get
val params = method.getParameters
val values = params.map(_.getName).map(name => (json \ name).as[String])
val ref = new SomeClass
method.invoke(ref, values: _*)
}
In this example we have an assumption that all fields have the same type String, your function is inside class. Play-json is used for parsing. You get method, than argument names, than extract values for arguments (in same order as arguments) and than just apply them to function.
And calls:
val json = Json.obj("animal" -> "cat", "color" -> "black")
surprise2(json)
surprise3(json)

Related

Is it possible to call a scala macro from generic scala code?

I'm trying to use Scala macros to convert untyped, Map[String, Any]-like expressions to their corresponding typed case class expressions.
The following scala macro (almost) gets the job done:
trait ToTyped[+T] {
def apply(term: Any): T
}
object TypeConversions {
// At compile-time, "type-check" an untyped expression and convert it to
// its appropriate typed value.
def toTyped[T]: ToTyped[T] = macro toTypedImpl[T]
def toTypedImpl[T: c.WeakTypeTag](c: Context): c.Expr[ToTyped[T]] = {
import c.universe._
val tpe = weakTypeOf[T]
if (tpe <:< typeOf[Int] || tpe <:< typeOf[String]) {
c.Expr[ToTyped[T]](
q"""new ToTyped[$tpe] {
def apply(term: Any): $tpe = term.asInstanceOf[$tpe]
}""")
} else {
val companion = tpe.typeSymbol.companion
val maybeConstructor = tpe.decls.collectFirst {
case m: MethodSymbol if m.isPrimaryConstructor => m
}
val constructorFields = maybeConstructor.get.paramLists.head
val subASTs = constructorFields.map { field =>
val fieldName = field.asTerm.name
val fieldDecodedName = fieldName.toString
val fieldType = tpe.decl(fieldName).typeSignature
q"""
val subTerm = term.asInstanceOf[Map[String, Any]]($fieldDecodedName)
TypeConversions.toTyped[$fieldType](subTerm)
"""
}
c.Expr[ToTyped[T]](
q"""new ToTyped[$tpe] {
def apply(term: Any): $tpe = $companion(..$subASTs)
}""")
}
}
}
Using the above toTyped function, I can convert for example an untyped person value to its corresponding typed Person case class:
object TypeConversionTests {
case class Person(name: String, age: Int, address: Address)
case class Address(street: String, num: Int, zip: Int)
val untypedPerson = Map(
"name" -> "Max",
"age" -> 27,
"address" -> Map("street" -> "Palm Street", "num" -> 7, "zip" -> 12345))
val typedPerson = TypeConversions.toTyped[Person](untypedPerson)
typedPerson shouldEqual Person("Max", 27, Address("Palm Street", 7, 12345))
}
However, my problem arises when trying to use the toTyped macro from above in generic scala code. Suppose I have a generic function indirection that uses the toTyped macro:
object CanIUseScalaMacrosAndGenerics {
def indirection[T](value: Any): T = TypeConversions.toTyped[T](value)
import TypeConversionTests._
val indirectlyTyped = indirection[Person](untypedPerson)
indirectlyTyped shouldEqual Person("Max", 27, Address("Palm Street", 7, 12345))
Here, I get a compile-time error from the toTyped macro complaining that the type T is not yet instantiated with a concrete type. I think the reason for the error is that from the perspective of toTyped inside indirection, the type T is still generic and not inferred to be Person just yet. And therefore the macro cannot build the corresponding Person case class when called via indirection. However, from the perspective of the call-site indirection[Person](untypedPerson), we have T == Person, so I wonder if there is a way to obtain the instantiated type of T (i.e., Person) inside the macro toTyped.
Put differently: Can I combine the Scala macro toTyped with the generic function indirection and yet be able to figure out the instantiated type for type parameter T inside the toTyped macro? Or am I on a hopeless track here and there is no way to combine Scala macros and generics like this? In the latter case I would like to know if the only solution here is to push the macro usage so far "out" that I can call it instantiated as toTyped[Person] rather than as toTyped[T].
Any insights are very much appreciated. Thank you! :-)
Macros need to be expanded. Every time you use a function which body is a macro, Scala will have to generate the code and put it there. As you suspect, this is very very specific and contradict the idea of parametric polymorphism where you write code independent of specific knowledge about your type.
Type classes are one of solutions to the general problem when you want to have one generic (parametric) definition and multiple per-type implementations of certain parts of your algorithm. You basically, define something that you could consider interface which (most likely) need to follow some contract (speaking in OOP terminology) and pass this interface as as argument:
// example
trait SpecificPerType[T] {
def doSomethingSpecific(t: T): String
}
val specificForString: SpecificPerType[String] = new SpecificPerType[String] {
def doSomethingSpecific(t: String): String = s"MyString: $t"
}
val specificForInt: SpecificPerType[Int] = new SpecificPerType[Int] {
def doSomethingSpecific(t: Int): String = s"MyInt: $t"
}
def genericAlgorithm[T](values: List[T])(specific: SpecificPerType[T]): String =
values.map(specific.doSomethingSpecific).mkString("\n")
genericAlgorithm(List(1,2,3))(specificForInt)
genericAlgorithm(List("a","b","c"))(specificForString)
As you can see, it would be pretty annoying to pass this specific part around, which is one of the reasons implicits were introduced.
So you could write it using implicits like this:
implicit val specificForString: SpecificPerType[String] = new SpecificPerType[String] {
def doSomethingSpecific(t: String): String = s"MyString: $t"
}
implicit val specificForInt: SpecificPerType[Int] = new SpecificPerType[Int] {
def doSomethingSpecific(t: Int): String = s"MyInt: $t"
}
def genericAlgorithm[T](values: List[T])(implicit specific: SpecificPerType[T]): String =
values.map(specific.doSomethingSpecific).mkString("\n")
/* for implicits with one type parameter there exist a special syntax
allowing to express them as if they were type constraints e.g.:
def genericAlgorithm[T: SpecificPerType](values: List[T]): String =
values.map(implicitly[SpecificPerType[T]].doSomethingSpecific).mkString("\n")
implicitly[SpecificPerType[T]] is a summoning that let you access implicit
by type, rather than by its variable's name
*/
genericAlgorithm(List(1,2,3)) // finds specificForString using its type
genericAlgorithm(List("a","b","c")) // finds specificForInt using its type
If you generate that trait implementation using macro, you will be able to have a generic algorithm e.g.:
implicit def generate[T]: SpecificPerType[T] =
macro SpecificPerTypeMacros.impl // assuming that you defined this macro there
As far as I can tell, this (extracting macros into type classes) is one of common patterns when it comes to being
able to generate some code with macros while, still building logic on top of it
using normal, parametric code.
(Just to be clear: I do not claim that the role of type classes is limited as the carriers of macro generated code).

What is the type of a field of a Scala class?

I would like to write a function like the following:
def printFieldOfClass(field: ???) =
println(field)
Suppose there is a case class definition such as case class A(id: String). It would then be possible to call printFieldOfClass(A.id) which would print the string "A.id". If we, however, try to call printFieldOfClass(A.idd), I would want the code not to compile. Is this even possible? And if so, what is the type of the parameter field?
Help is much appreciated!
EDIT: As there seems to be some confusion about what I am trying to do, let me clarify: I do not want to pass an instance of the case class, I much rather want to pass a reference to some field in a class definition. Also I do not want my function to be hard wired to any such class, it should work with all Scala classes, like so: printFieldOfClass(SomeClassTheFunctionDoesNotKnowAbout.someField) should either print "SomeClassTheFunctionDoesNotKnowAbout.someField" in case SomeClassTheFunctionDoesNotKnowAbout's definition specifies a field someField or, if the class has no such field, the call should not compile.
This isn't possible if printFieldOfClass is a normal method, as the comments explain. But you can make it a macro instead. It's basically a function which runs at compile-time, receives the syntax tree of its argument and generates a new tree to replace it. There are quite a few introductions to Scala macros, and writing another one in the answer doesn't make sense. But I don't advise trying it until you are very comfortable with Scala in general.
An example which does something close to what you want:
import scala.annotation.tailrec
import scala.language.experimental.macros
import scala.reflect.macros.blackbox
object Macros {
def nameOfImpl(c: blackbox.Context)(x: c.Tree): c.Tree = {
import c.universe._
#tailrec def extract(x: c.Tree): String = x match {
case Ident(TermName(s)) => s
case Select(_, TermName(s)) => s
case Function(_, body) => extract(body)
case Block(_, expr) => extract(expr)
case Apply(func, _) => extract(func)
}
val name = extract(x)
q"$name"
}
def nameOfMemberImpl(c: blackbox.Context)(f: c.Tree): c.Tree = nameOfImpl(c)(f)
def nameOf(x: Any): String = macro nameOfImpl
def nameOf[T](f: T => Any): String = macro nameOfMemberImpl
}
//
// Sample usage:
//
val someVariable = ""
Macros.nameOf(someVariable) // "someVariable"
def someFunction(x: Int): String = ???
Macros.nameOf(someFunction _) // "someFunction"
case class SomeClass(someParam: String)
val myClass = SomeClass("")
Macros.nameOf(myClass.someParam) // "someParam"
// without having an instance of the class:
Macros.nameOf[SomeClass](_.someParam) // "someParam"

Scala Capture Expression Name without a Macro

I'm trying to grab the name of an expression call without using a macro. I have the following example code:
case class Person(name: String, age: Int)
case class MyClass[T]() {
def doSomething(value: Any)
}
val p = Person("Bob",40)
val my = MyClass[Person]
my.doSomething(p.name)
my.doSomething(p.age)
Is there a simple way inside the method doSomething to capture the expression name being used when making the call, for example capture a String value of name and age?
I know if I turn doSomething into a macro the passed parameter is an Expr of Context and I can get the name using the Tree of the Expr, however given the complex nature of macros I'm sort of thing to avoid using one in this case.
The short answer is no. There is currently no way of getting an abstract syntax tree (AST) except with macros.
You could use reify here with some success, but that itself is a macro, and this would require the doSomething caller to have to use reify, which is strange. For example, in the following code doSomething returns the property name together with the value of the property for the instance passed to the case class constructor:
import scala.reflect.runtime.universe._
import scala.reflect.runtime._
import scala.tools.reflect.ToolBox
case class Person(name: String, age: Int)
case class MyClass[T](t: T) {
val tb = currentMirror.mkToolBox()
def doSomething[U](expr: Expr[T => U]) = Some(expr.tree) collect {
case f#Function(_, Select(_, property)) =>
val func = tb.eval(f).asInstanceOf[T => U]
property.decoded -> func(t)
}
}
Which can be called as:
val p = Person("Bob",40)
val my = MyClass(p)
//The caller needs to use reify, which is strange!
my.doSomething(reify((_:Person).name)) //Some(("name", "Bob"))
my.doSomething(reify { (p:Person) => p.age }) //Some(("age",40))
But this is fragile and error prone, and at this point you might as well write a macro!
Your other option is to pass in a String name of the property and use reflection to get that property from the instance.
You can look at the docs for Trees and macros to learn more.

Refering to self type of a trait

I wrote a trait to mix into a class the ability to serialize itself to query string parameters, leveraging an existing JSON Writes instance. In order to use that Writes instance as a parameter, I need to know the type into which this trait is being mixed. I'm getting that using a type parameter (which should be the class itself) and a self-type annotation. I'm wondering if there's a DRYer way of doing this, which doesn't require the type parameter?
Here's my code:
trait ConvertibleToQueryString[T] {
this: T =>
/** Transformation of field names in obj to query string keys */
def objToQueryStringMapping: Map[JsPath, JsPath] = Map.empty
/**
* Convert a model to a Map, for serialization to a query string, to be used
* in a REST API call.
* #param writes writer for `obj`
* #return
*/
def toQueryStringMap(implicit writes: Writes[T]): Map[String, String] = {
// Get a map of key -> JsValue from obj
val mapObj = Json.toJson(this).transform(moveKeys(objToQueryStringMapping)).get.value
// Convert the JsValue values of the map to query strings
mapObj.mapValues(jsValueToQueryStringValue).filter(_._2.nonEmpty).toMap
}
}
, to be used as such:
case class MyClass(param1: String, param2: Int) extends ConvertibleToQueryString[MyClass]
, that final type parameter being the thing that's annoying me. It's fully unconstrained, but it should really just be "the type of the class I get mixed into". Is there a way to express this?
Why not use the pimp-encrich-my-library pattern:
implicit class ConvertibleToQueryString[T: Writes](x: T) {
def objToQueryStringMapping: Map[JsPath, JsPath] = Map.empty
def toQueryStringMap: Map[String, String] = {
// Get a map of key -> JsValue from obj
val mapObj = Json.toJson(x).transform(moveKeys(objToQueryStringMapping)).get.value
// Convert the JsValue values of the map to query strings
mapObj.mapValues(jsValueToQueryStringValue).filter(_._2.nonEmpty).toMap
}
}
Now you don't need the extends ... at all on the classes you want to serialize.

Introspect argument passed to a Scala macro

I would like to program a Scala macro that takes an instance of a case class as argument. All objects that can be passed to the macro have to implement a specific marker trait.
The following snippet shows the marker trait and two example case classes implementing it:
trait Domain
case class Country( id: String, name: String ) extends Domain
case class Town( id: String, longitude: Double, latitude: Double ) extends Domain
Now, I would like to write the following code using macros to avoid the heaviness of runtime reflection and its thread unsafety:
object Test extends App {
// instantiate example domain object
val myCountry = Country( "CH", "Switzerland" )
// this is a macro call
logDomain( myCountry )
}
The macro logDomain is implemented in a different project and looks similar to:
object Macros {
def logDomain( domain: Domain ): Unit = macro logDomainMacroImpl
def logDomainMacroImpl( c: Context )( domain: c.Expr[Domain] ): c.Expr[Unit] = {
// Here I would like to introspect the argument object but do not know how?
// I would like to generate code that prints out all val's with their values
}
}
The macro's purpose should be to generate code that - at runtime - outputs all values (id and name) of the given object and prints them as shown next:
id (String) : CH
name (String) : Switzerland
To achieve this, I would have to dynamically inspect the passed type argument and determine its members (vals). Then I would have to generate an AST representing the code that creates the log output. The macro should work regardless of what specific object implementing the marker trait "Domain" is passed to the macro.
At this point I am lost. I would appreciate if someone could give me a starting point or point me to some documentation? I am relatively new to Scala and have not found a solution in the Scala API docs or the Macro guide.
Listing the accessors of a case class is such a common operation when you're working with macros that I tend to keep a method like this around:
def accessors[A: u.WeakTypeTag](u: scala.reflect.api.Universe) = {
import u._
u.weakTypeOf[A].declarations.collect {
case acc: MethodSymbol if acc.isCaseAccessor => acc
}.toList
}
This will give us all the case class accessor method symbols for A, if it has any. Note that I'm using the general reflection API here—there's no need to make this macro-specific yet.
We can wrap this method up with some other convenience stuff:
trait ReflectionUtils {
import scala.reflect.api.Universe
def accessors[A: u.WeakTypeTag](u: Universe) = {
import u._
u.weakTypeOf[A].declarations.collect {
case acc: MethodSymbol if acc.isCaseAccessor => acc
}.toList
}
def printfTree(u: Universe)(format: String, trees: u.Tree*) = {
import u._
Apply(
Select(reify(Predef).tree, "printf"),
Literal(Constant(format)) :: trees.toList
)
}
}
And now we can write the actual macro code pretty concisely:
trait Domain
object Macros extends ReflectionUtils {
import scala.language.experimental.macros
import scala.reflect.macros.Context
def log[D <: Domain](domain: D): Unit = macro log_impl[D]
def log_impl[D <: Domain: c.WeakTypeTag](c: Context)(domain: c.Expr[D]) = {
import c.universe._
if (!weakTypeOf[D].typeSymbol.asClass.isCaseClass) c.abort(
c.enclosingPosition,
"Need something typed as a case class!"
) else c.Expr(
Block(
accessors[D](c.universe).map(acc =>
printfTree(c.universe)(
"%s (%s) : %%s\n".format(
acc.name.decoded,
acc.typeSignature.typeSymbol.name.decoded
),
Select(domain.tree.duplicate, acc.name)
)
),
c.literalUnit.tree
)
)
}
}
Note that we still need to keep track of the specific case class type we're dealing with, but type inference will take care of that at the call site—we won't need to specify the type parameter explicitly.
Now we can open a REPL, paste in your case class definitions, and then write the following:
scala> Macros.log(Town("Washington, D.C.", 38.89, 77.03))
id (String) : Washington, D.C.
longitude (Double) : 38.89
latitude (Double) : 77.03
Or:
scala> Macros.log(Country("CH", "Switzerland"))
id (String) : CH
name (String) : Switzerland
As desired.
From what I can see, you need to solve two problems: 1) get the necessary information from the macro argument, 2) generate trees that represent the code you need.
In Scala 2.10 these things are done with the reflection API. Follow Is there a tutorial on Scala 2.10's reflection API yet? to see what documentation is available for it.
import scala.reflect.macros.Context
import language.experimental.macros
trait Domain
case class Country(id: String, name: String) extends Domain
case class Town(id: String, longitude: Double, latitude: Double) extends Domain
object Macros {
def logDomain(domain: Domain): Unit = macro logDomainMacroImpl
def logDomainMacroImpl(c: Context)(domain: c.Expr[Domain]): c.Expr[Unit] = {
import c.universe._
// problem 1: getting the list of all declared vals and their types
// * declarations return declared, but not inherited members
// * collect filters out non-methods
// * isCaseAccessor only leaves accessors of case class vals
// * typeSignature is how you get types of members
// (for generic members you might need to use typeSignatureIn)
val vals = typeOf[Country].declarations.toList.collect{ case sym if sym.isMethod => sym.asMethod }.filter(_.isCaseAccessor)
val types = vals map (_.typeSignature)
// problem 2: generating the code which would print:
// id (String) : CH
// name (String) : Switzerland
//
// usually reify is of limited usefulness
// (see https://stackoverflow.com/questions/13795490/how-to-use-type-calculated-in-scala-macro-in-a-reify-clause)
// but here it's perfectly suitable
// a subtle detail: `domain` will be possibly used multiple times
// therefore we need to duplicate it
val stmts = vals.map(v => c.universe.reify(println(
c.literal(v.name.toString).splice +
"(" + c.literal(v.returnType.toString).splice + ")" +
" : " + c.Expr[Any](Select(domain.tree.duplicate, v)).splice)).tree)
c.Expr[Unit](Block(stmts, Literal(Constant(()))))
}
}