4

Inspired by the previous question what is the easiest way to pass a list of integers from java to a frege function? and a comment in the answers by @Ingo, I tried

(Foo/myfregefunction (java.util.List. [1,2,3,4]))

but get (ctor = constructor):

CompilerException java.lang.IllegalArgumentException: No matching ctor found for interface java.util.List

Any ideas? At least java.util.List didn’t yield a ClassCastException; does this mean this is on the right track?

I can send Frege pretty much any Java collection type from Clojure, see Converting Clojure data structures to Java collections.

BTW, using plain (Foo/myfregefunction [1,2,3,4]) instead yields ClassCastException clojure.lang.PersistentVector cannot be cast to free.runtime.Lazy, to which @Ingo points out, “A clojure list is not a frege list.” Similar response when casting as java.util.ArrayList.

On the Frege side, the code is something like

module Foo where

myfregefunction :: [Int] -> Int
-- do something with the list here
Community
  • 1
  • 1
0dB
  • 675
  • 5
  • 13

2 Answers2

5

Ok, not knowing Clojure, but from the link you gave I take it you need to give the name of an instantiable class (i.e. java.util.ArraList) since java.util.List is just an interface and so cannot be constructed.

For the Frege side, which is the consumer in this case, it suffices to assume the interface.

The whole thing gets a bit complicated, since Frege knows that java lists are mutable. This means that there cannot exist a pure function

∀ s a. Mutable s (List a) → [a]

and every attempt to write such a function in a pure language must fail and will be rejected by the compiler.

Instead, what we need is a ST action to wrap the pure part (in this case, your function myfregefunction). ST is the monad that makes it possible to deal with mutable data. This would go like this:

import Java.Util(List, Iterator)   -- java types we need

fromClojure !list = 
    List.iterator list >>= _.toList >>= pure . myfregefunction

From clojure, you can now call something like (forgive me if I get the clojure syntax wrong (edits welcome)):

(frege.prelude.PreludeBase$TST/run (Foo/fromClojure (java.util.ArrayList. [1,2,3,4])))

This interfacing via Java has two disadvantages, IMHO. For one, we introduce mutability, which the Frege compiler doesn't allow us to ignore, so the interface gets more complicated. And in addition, list data will be duplicated. I don't know how Clojure is doing it, but on the Frege side, at least, there is this code that goes over the iterator and collects the data into a Frege list.

So a better way would be to make Frege aware of what a clojure.lang.PersistentVector is and work directly on the clojure data in Frege. I know of someone who has done it this way with clojure persistent hash maps, so I guess it should be possible to do the same for lists.

(At this point I cannot but point out how valuable it would be to contribute a well thought-out Clojure/Frege interface library!)

Edit: As the self-answer from @0dB suggests, he's about to implement the superior solution mentioned in the previous paragraphs. I encourage everyone to support this noble undertaking with upvotes.

A third way would be to construct the Frege list directly in Clojure.

Ingo
  • 36,037
  • 5
  • 53
  • 100
  • Just for the sake of completeness: you should also be able to use `to-array` from Clojure and take this as `JArray a` on the Frege side. This is nice when you can work on the arrays directly but perhaps not the most efficient way if you need the list API for processing. – Dierk Dec 20 '15 at 10:31
  • OK, I’ll try out your first path and the `to-array / JArray` idea by @Dierk just to get things connected. Since Clojure also avoids mutability, it would be nice to avoid all the overhead you mention, so I’ll look at Adam’s approach one more time and see if I can put it to use. (To anyone interested, the persistent hash map solution that @Ingo mentions can be found at [Adam Bard](https://adambard.com/blog/interfacing-frege-and-ring/).) – 0dB Dec 20 '15 at 12:39
  • 1
    There is no need to call `(java.util.ArrayList. [1,2,3,4])` - `[1,2,3,4]` already implements List and is not mutable. `[]` in clojure also implements Iterable if that helps as well. – noisesmith Dec 20 '15 at 12:49
  • Interim update: @noisesmith is right. I also had to coerce Long (Clojure) to Int (Frege), so now path 1 by @Ingo looks like this and I have my first successful “connection” passing [Int] from Clojure to Frege: `(frege.prelude.PreludeBase$TST/run (Foo/fromClojure (map int [1,2,3,4])))`. (Why did `int-array` not work?, hm.) Not the prettiest solution but maybe we’re getting somewhere. – 0dB Dec 20 '15 at 13:30
  • Well, if the numbers are Long, you just tell Frege, Long is as well supported as Int. But when you say `[Int] -> Int` the code stubbornly insists on Ints. :) – Ingo Dec 20 '15 at 13:46
  • `int-array` did not work because an array is not a List – noisesmith Dec 20 '15 at 13:51
  • @noisesmith in this case you need to tell on the Frege side that you're expecting an Array: `myfregefunction :: JArray Long -> Long` Here, the incoming array is immutable, hence the function is pure and we don't need a wrapper like `fromClojure` – Ingo Dec 20 '15 at 14:02
  • 1
    @Ingo, yes, I had tried switching to `[Long]`, but one of my functions uses `replicate ∷ Int → α → [α]` . @noisesmith, got it, thanks. @Ingo, hm, switching to `JArray Int` means (for another function) looking into how to handle recursion with `JArray Int` instead of [Int] (e. g. looking for an empty JArray instead of `[]`) and how to translate pattern matching `(x:xs)`. Or can I cast `JArray Int` to `[Int]`? (That’s what the wrapper does?!) But, since I now have a working interim solution (thanks, guys!), I might be spending less time on improving it but instead checking out Adam’s approach. – 0dB Dec 20 '15 at 14:37
  • @0dB You can use `genericReplicate` from Data.List. It takes any integral type as first argument, instead of `Int` – Ingo Dec 20 '15 at 14:40
  • @Ingo, OK, I see how Util.fr works. And, the approach by [Adam](https://adambard.com/blog/interfacing-frege-and-ring/) for `PersistentMap` makes do without a state monad, for the reasons that @noisesmith points out, so I should be able to get something similar up and running here. But, both in Util.fr (`toList`) and in Adam’s solution (`fromKVList`), the code always iterates once over the input data to get a Frege data structure. Hm. Any way to avoid that? – 0dB Dec 24 '15 at 12:47
  • I know that clojure can build a vector in constant time by using an array as it's "backing array" - maybe frege could do a similar trick with a clojure vector? Or perhaps you could find a way to natively use the methods (conj, get) on the vector from frege?[ – noisesmith Dec 24 '15 at 16:20
  • That is what I propose: find out the API of the «clojure data structure of your choice» then just write it doen in terms of Frege native definitions, and this will allow you then to pass such a value directly to a Frege function. – Ingo Dec 24 '15 at 20:57
  • Will do, @Ingo, @noisesmith, and will report back. I'll check `clojure.lang.PersistentVector`. – 0dB Dec 25 '15 at 13:11
  • 1
    @Ingo, @noisesmith, @Dierk, looks like I’m getting somewhere. Annotating `native clojure.lang.IPersistentVector`, using `pure native` for the methods needed, and adding translation functions for Frege list to IPersistentVector and back, now `(ClojureInterface/fromClojure [7,8,11,13,17])` yields `[8 11 13 17]`, with no wrapping or unwrapping on the Clojure side needed. (The Frege function `fromClojure` just applies `tail` to the input.). @Ingo, when this is ready for publishing, should I just add and mark some edits in your answer? – 0dB Dec 31 '15 at 09:46
  • 1
    @0dB great to hear this! You could simply add an answer, and I would edit my answer to point out that you've worked out the superior solution. Please do also consider to maintain your clojure-bindings in an OSS repo, and we'll happy to point there every time someone comes up with a similar problem. – Ingo Dec 31 '15 at 10:26
  • @Ingo, answer added. If it can be made more helpful, let me know. And if you have any pointers on how I can move forward even more towards an interface concept, that would be great. – 0dB Jan 01 '16 at 19:45
1

Based on the answer by @Ingo,

a better way would be to make Frege aware of what a clojure.lang.PersistentVector is and work directly on the clojure data in Frege.

and comments thereto as well as the solution for PersistentMap by Adam Bard, I came up with a working solution:

module foo.Foo where

[EDIT] As Ingo points out, being an instance of ListView gives us list comprehension, head, tail, …

instance ListView PersistentVector

We need to annotate a Clojure class for use in Frege (pure native basically makes the Java methods available to Frege without needing any monad to handle mutability, possible because—in general—data is immutable in Clojure, too):

data PersistentVector a = native clojure.lang.IPersistentVector where
  -- methods needed to create new instances
  pure native empty clojure.lang.PersistentVector.EMPTY :: PersistentVector a
  pure native cons :: PersistentVector a -> a -> PersistentVector a
  -- methods needed to transform instance into Frege list
  pure native valAt :: PersistentVector a -> Int -> a
  pure native length :: PersistentVector a -> Int

Now there follow some functions that are added to this data type for creating a Clojure vector from Frege list or the other way around:

  fromList :: [a] -> PersistentVector a
  fromList = fold cons empty

  toList :: PersistentVector a -> [a]
  toList pv = map pv.valAt [0..(pv.length - 1)]

Note my use of the "dot" notation; see the excellent article by @Dierk, The power of the dot.

[EDIT] For ListView (and some fun in Frege with PersistentVector) we need to also implement uncons, null and take (sorry for the quick & dirty solutions here; I will try to fix that soon):

  null :: PersistentVector a -> Bool
  null x = x.length == 0

  uncons :: PersistentVector a -> Maybe (a, PersistentVector a)
  uncons x
    | null x = Nothing
    -- quick & dirty (using fromList, toList); try to use first and rest from Clojure here
    | otherwise = Just (x.valAt 0, fromList $ drop 1 $ toList x)

  take :: Int -> PersistentVector a -> PersistentVector a
  -- quick and dirty (using fromList, toList); improve this
  take n = fromList • PreludeList.take n • toList

In my quick & dirty solution above, note the use of PreludeList.take to avoid calling take in the namespace that PersistentVector creates, and how I did not have to prefix fromList, toList, cons and empty.

With this setup (you can leave out uncons, null and take as well as the instance declaration at the top, if you don’t want to do anything with PersistentVector in Frege directly) you can now call a Frege function that takes and returns a list by wrapping it properly:

fromClojure :: PersistentVector a -> PersistentVector a
fromClojure = PersistentVector.fromList • myfregefn • PersistentVector.toList

-- sample (your function here)
myfregefn :: [a] -> [a]
myfregefn = tail

In Clojure we just call (foo.Foo/fromClojure [1 2 3 4]) and get a Clojure vector back with whatever processing myfregefn does (in this example [2 3 4]). If myfregefn returns something that both Clojure and Frege understand (String, Long, …), leave out the PersistentVector.fromList (and fix the type signature). Try both out, tail as above for getting back a list and head for getting back, say, a Long or a String.

For the wrapper and for your Frege function, make sure the type signatures 'match', e. g. PersistentVector a matches [a].

Moving forward: I am doing this because I would like to port some of my Clojure programs to Frege, “a function at a time“. I am sure I will be encountering some more complex data structures that I will have to look into, and, I am still looking into the suggestions by Ingo to improve things.

0dB
  • 675
  • 5
  • 13
  • 1
    Well, this is a good start, at least. It can surely be enhanced, though. First, fromList is just `fold PV.cons PV.empty`. Next, I would wrap the PV in an iterator like data structure (look at frege.data.Iterators for inspiration). Based on that, we can implement all sorts of type classes, like Functor, Foldable, even Monad, if you like, but also the Frege specific ListView and ListMonoid classes. This would give us fmap, fold, head, tail, null, uncons, toList, (++) to name a few and the ability to use (wrapped) PVs in list comprehensions. – Ingo Jan 01 '16 at 21:48
  • Just a technical note: `module Foo` creates a class `Foo` in the unnamed (java) package, you wont be able to import this in any module that is not itself in that package. (This is the way java works.) Hence, for library kind of stuff a module name with more components is mandatory. – Ingo Jan 01 '16 at 21:52
  • @Ingo, thanks, I’ll look into `Iterators` and see where I can go from there. (BTW, let me know if it would be more appropriate to move such ‘research’ to the Frege Google Group.) Yeah, I should have seen `fold` right away . Regarding package names, right, now I remember why I always use `x.Y` in Clojure as well. – 0dB Jan 02 '16 at 10:40
  • 1
    @Ingo, I shortened my answer to make it easier to understand the “interim solution” (which technically solves the problem described in my original question but just “isn’t there yet” from an architecture point-of-view) and will report back when I have implemented wrapping PV. – 0dB Jan 03 '16 at 14:56
  • @Ingo, OK, I see how to make PV an instance of `ListView` etc.. But am I right in thinking that I then would still need to use `toList` and `fromList`? Or is it somehow the path to being able to call Frege code from both Frege and from Clojure, without any ‘awareness’ needed on either side (e. g. some transformation between the data types happening in the background as needed)? – 0dB Jan 04 '16 at 20:06
  • 1
    More like the former one. Let's say you have something similar to ArrayIterator in Data.Iterators, but based on PVs. From what I've seen from you, the API seems to be quite array-like: We know the length pf the PV, and have O(1) access to the elements at every index (correct me if I'm wrong). Now, in the iterator we maintain: a reference to the original PV, the length and the "current" index. Then, for example, `null` is just a check if the curremt index >= the PV length. `length` is just PV.length - current index. `tail` is just advancing the index, and so forth. (1/2) – Ingo Jan 04 '16 at 23:22
  • 1
    In this way, it is possible to implement most list functions, and they would work without ever creating a real list. But, since we also have `cons` in PV, we can do even more (assuming cons works non destructive). The idea is to write your code as polymorphic as possible, using typeclasses like ListView, Monoid, Foldable, Traversable, Functor, Applicative, Monad, etc. Now, if you do this, it suddenly doesn't matter anymore whether you have a list or a PV wrapped in an Iterator. You need then just one function that takes a PV from Clojure, wraps it, and off it goes! – Ingo Jan 04 '16 at 23:33
  • 1
    @Ingo, yes, I see that about using `Iterator` and being polymorphic (and then being able to treat PV and list the same), should be easy. OK, looks like we won't be able to do without explicit wrapping. – 0dB Jan 05 '16 at 16:38
  • 1
    indeed not, since a native type has kind * and cannot directly implement higher kinded type classes. – Ingo Jan 05 '16 at 22:09
  • @Ingo, in `Iterators.fr`, which interface (class) do `from` and `to` come from? (Otherwise e. g. `ArrayIterator` is instance of `ListView`). Reg. 'kind', yikes, that was the section in LYAH that I only skimmed over (the “type of a type”). – 0dB Jan 06 '16 at 14:51
  • 1
    `from` and `to` are not from any interface. We could write 4 top level functions `boxString`, `unboxString`, `boxArray` and `unboxArray` that could do the same. But since Frege data types have their own namespace, it is more convenient to choose short names, and the supposed usage is like `StringIterator.from "foo"`. Of course, we can abbreviate StringIterator via `type` definitions or import aliases. – Ingo Jan 06 '16 at 23:23
  • 1
    Yes, you don't need to be a type system expert to recognize that, for example, the type constructors Int and [] are fundamentally different. Int denotes a type a value can have, but [] does not. The former kind we denote with `*`. The latter one with `* -> *` in English: give me a type of kind `*` and the resulting type expression will itself be a type of kind `*`. Thus, `[] Char` (which is usually written `[Char]`) *is* a type a value can have. For fun, try to find out what the kind of the following type constructor S is: `data S f g x = S (f x) (g x)` – Ingo Jan 06 '16 at 23:32
  • @Ingo, PV is now an instance of `ListView`, with quick & dirty implementations for `uncons` and `take` (which I will try to find more native solutions for or do something like what you do in `Iterators`). BTW, how do I call Frege `take` to avoid the naming conflict I "resolved" by using `genericTake`? (I could not find the package it is in.) – 0dB Jan 10 '16 at 09:37
  • 1
    take is a class operation of ListView, so there is nothing like *the* take. There is one take for each data type that implements ListView. For an example, go to the REPL (or online REPL), enter `take 10 [1,2,3]` and then enter the `:java` command to see the generated code. – Ingo Jan 10 '16 at 11:01
  • 1
    @Ingo, perfect, `PreludeList.take` (seen in the Java code) does the job. (That is what I meant: _which_ `take` should I use to get the one for lists .) My quick & dirty `ListView` solution is now letting me have fun playing around—list comprehension etc. all work for PV now. I’ll rewrite the implementations sometime. – 0dB Jan 10 '16 at 11:46