Code Monkey home page Code Monkey logo

inline-java's Introduction

inline-java: Call any JVM function from Haskell

Build

The Haskell standard includes a native foreign function interface (FFI). Using it can be a bit involved and only C support is implemented in GHC. inline-java lets you call any JVM function directly, from Haskell, without the need to write your own foreign import declarations using the FFI. In the style of inline-c for C and inline-r for calling R, inline-java lets you name any function to call inline in your code. It is implemented on top of the jni and jvm packages using a GHC Core plugin to orchestrate compilation and loading of the inlined Java snippets.

Example

Graphical Hello World using Java Swing:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE OverloadedStrings #-}
module Main where

import Data.Text (Text)
import Language.Java
import Language.Java.Inline

main :: IO ()
main = withJVM [] $ do
    message <- reflect ("Hello World!" :: Text)
    [java| {
      javax.swing.JOptionPane.showMessageDialog(null, $message);
      } |]

Building it

Requirements:

  • the Bazel build tool, and
  • the Nix package manager.

To build:

$ nix-shell --pure --run "bazel build //..."

To test:

$ nix-shell --pure --run "bazel test //..."

Using the safe interface

There is an experimental interface which catches common memory management mistakes at compile time via the LinearTypes language extension.

For examples of how to use the safe interface you can check the tests, the directory server example and the wizzardo-http benchmark.

Further reading

Check the tutorial on how to use inline-java. If you want to know more about how it is implemented, look at our post on the plugin implementation.

There is also a post which gives an overview of the safe interface.

Debugging

The generated java output can be dumped to stderr by passing to GHC

-fplugin-opt=Language.Java.Inline.Plugin:dump-java

If -ddump-to-file is in effect, the java code is dumped to <module>.dump-java instead.

Troubleshooting

Build-time error package or class Blah does not exist

inline-java is going to invoke the javac compiler, and any classes used in java quotations need to be reachable via the CLASSPATH environment variable. For instance,

CLASSPATH=/path/to/my.jar:/some/other/path ghc --make program.hs

Run-time error ThreadNotAttached

Haskell threads need to be attached to the JVM before making JNI calls. Foreign.JNI.withJVM attaches the calling thread, and other threads can be attached with Foreign.JNI.runInAttachedThread. When the JVM calls into Haskell, the thread is already attached.

Run-time error ThreadNotBound

JNI calls need to be done from bound threads. The thread invoking the main function of a program is bound. Threads created with forkOS are bound. In other threads, Control.Concurrent.runInBoundThread can be used to run a computation in a bound thread.

Run-time error java.lang.NoClassDefFoundError

Classes might not be found at runtime if they are not in a folder or jar listed in the parameter -Djava.class.path=<classpath> passed to withJVM.

withJVM ["-Djava.class.path=/path/to/my.jar:/some/other/path"] $ do
  ...

Additionally, classes might not be found if a thread other than the one calling main is trying to use them. One solution is to have the thread calling main load all the classes in advance. Then the classes will be available in the JVM for other threads that need them. Calling Language.Java.Inline.loadJavaWrappers will have the effect of loading all classes needed for java quotations, which will suffice in many cases.

Another option is to set the context class loader of other threads, so they earn the ability to load classes on their own. This might work when the thread was attached to the JVM via the JNI, and the context class loader is just null.

loader <- [java| Thread.currentThread().getContextClassLoader() |]
            `Language.Java.withLocalRef` Foreign.JNI.newGlobalRef
...
forkOS $ runInAttachedThread $ do
  [java| { Thread.currentThread().setContextClassLoader($loader); } |]
  ...

Run-time error JVMException

Any java exception that goes from Java to Haskell will be wrapped as a value of type JVMException with a reference to the Java object representing the exception. The message and the stack trace of the exception can be retrieved from the exception object with more JNI calls, e.g.

\(JVMException e) -> [java| { $e.printStackTrace(); } |]

or with JNI.Foreign.showException.

License

Copyright (c) 2015-2016 EURL Tweag.

All rights reserved.

inline-java is free software, and may be redistributed under the terms specified in the LICENSE file.

Sponsors

         Tweag I/O              LeapYear

inline-java is maintained by Tweag I/O.

Have questions? Need help? Tweet at @tweagio.

inline-java's People

Contributors

akagr avatar alpmestan avatar angerman avatar buonuomo avatar dzhus avatar edsko avatar facundominguez avatar fuuzetsu avatar grosa1 avatar matil019 avatar mboes avatar mitchellwrosen avatar mrkkrp avatar nbacquey avatar robinbb-leapyear avatar thufschmitt avatar yeole-modus avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

inline-java's Issues

ghc: could not execute: ./cpphs-cpp

Describe the bug
I've just added inline-java to "https://github.com/input-output-hk/plutus".
I get "ghc: could not execute: ./cpphs-cpp" during "stack build ."
(I'm not using nix at this point as I want to make sure that it works with plain stack)

I've tried "stack install cpphs" - the installation worked but didn't help the issue

Environment
MacOS Catalina 10.15.4

loadJavaWrappers leaks one local reference per class to load

loadJavaWrappers creates local references with defineClass which are not removed explicitly. They are removed when the frame in which loadJavaWrappers is invoked is popped.

We could easily clean these rerefences, but then we would retain no references to the classes that we have loaded which exposes them to being unloaded.

We could avoid the leak by creating a java array to all the references that we create in loadJavaWrappers, and then we keep just this array reference by making it a global reference with no finalizer.

High-level jvm wrappers order of magnitude slower than raw JNI bindings

Consider the following test program:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}

module Main where

import Control.Monad
import Data.Int
import Foreign.JNI
import Foreign.JNI.Types
import Language.Java

main :: IO ()
main = withJVM [] $ do
  klass <- findClass "java/lang/Math"
  method <- getStaticMethodID klass "incrementExact" "(I)I"
  replicateM_ 10000000 $ do
    -- callStaticIntMethod klass method [JInt 1]
    callStatic (sing :: Sing "java.lang.Math") "incrementExact" [JInt 1] :: IO Int32

On my laptop this program takes ~15 seconds to run. If you instead comment out the last line and uncomment the before last line, runtime drops to 2.1 seconds. In principle, callStatic (from jvm) and callStaticIntMethod (from jni) should have the same performance profile. But clearly they don't. We should investigate why and see if we can close the gap.

Support null values when doing batched marshaling

Grossly speaking a batch is an encoding of multiple Haskell or Java values as a bunch of primitive arrays. If we have a pair in Haskell (True, 1), a batch for the type (Bool, Int32) will have an array of Bool and an array of Int32 on which the components of the pair are stored at a given position.

On the java side, this works too: new scala.Tuple2<Boolean, Integer>(true, 1) can be stored in a couple of primitive arrays in the same way. Primitive arrays are cheap to pass from Java to Haskell.

But what do we do if the Java tuple is or contains null? There is no way to store null in primitive arrays, so we are forced to have a separate boolean array (boolean isnull[]) which tells for each position in the batch if it corresponds to a null value or not.

This is the interface that we currently have to reify a batch:

class BatchReify a where
  ...
  reifyBatch :: J (Batch a) -> Int32 -> IO (Vector a)

There are a few alternatives to handle nulls.

1. All batches can contain null.

Our interface changes to

class BatchReify a where
  ...
  reifyBatch :: J (Batch a) -> Int32 -> IO (Vector (Nullable a))

where Nullable a is isomorphic to Maybe a. All instances are forced to wrap values with the Nullable type.

2. Only batches of types of the form Nullable a may contain null.

We can have an instance like

  type instance Batch (Nullable a)
    = 'Class "scala.Tuple2" <>
         '[ 'Array ('Prim 'PrimBoolean)
          , Batch a
          ]

  instance BatchReify a => BatchReify (Nullable a) where
    ...
    reifyBatch jxs n = do
      isnull <- [java| $jxs._1() |]
      v <- [java| $jxs._2() |]
             -- reify a batch of values of type `a` and later pick the
             -- non-null values as told by the @isnull@ vector.
             >>= flip reifyBatch n
      return $ V.zipWith toNullable isnull v
      where
        toNullable :: Bool -> a -> Nullable a
        toNullable 0 a = NotNull a
        toNullable _ _ = Null

Unfortunately, the above scheme requires producing dummy/default Haskell values in the positions of the vector v that correspond to nulls. Ideally, we would find a way to skip producing these values at all.

We could change reifyBatch to:

class BatchReify a where
  ...
  reifyBatch :: J (Batch a) -> Int32 -> (Int32 -> Bool) -> IO (Vector (Maybe a))

reifyBatch j sz p produces a vector where some positions are yielded with Nothing. Only those positions whose index satisfies p provide a Just value.


Any preferences?

how to streaming jdbc resultset?

i write a simple haskell script to do jdbc thing.
but i have no idea how to streaming the data to haskell lazy sequence.
i also see jvm-streaming library, but i can't find the related example.

[nix-shell:~/my-repo/datahub/contrib/metadata-ingestion]$ bin/dataset-jdbc-generator.hs 
Note: /run/user/1000/inlinejava-898cd17b1b300692/Inline__main_Main.java uses unchecked or unsafe operations.
Note: Recompile with -Xlint:unchecked for details.
urn
aspect
version
metadata
createdon
createdby
createdfor
here...
dataset-jdbc-generator.hs: NullPointerException

dataset-jdbc-generator.hs

#! /usr/bin/env nix-shell
#! nix-shell dataset-jdbc-generator.hs.nix -i "runghc --ghc-arg=-fobject-code"

{-# LANGUAGE OverloadedStrings, FlexibleInstances, FlexibleContexts, ScopedTypeVariables #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}

{-# OPTIONS_GHC -fplugin=Language.Java.Inline.Plugin #-}


import System.Environment (lookupEnv)
import qualified Language.Haskell.TH.Syntax as TH

import Control.Concurrent (runInBoundThread)
import Language.Java (withJVM, reify, reflect)
import Language.Java.Inline (java)

import qualified Data.Text as T
import qualified Data.Text.IO as T
import Data.String.Conversions (cs)
import Text.InterpolatedString.Perl6 (q)

datasetOracleSql :: String
datasetOracleSql = [q|
    select
      c.OWNER || '.' || c.TABLE_NAME as schema_name
    , t.COMMENTS as schema_description
    , c.COLUMN_NAME as field_path
    , c.DATA_TYPE as native_data_type 
    , m.COMMENTS as description
    from ALL_TAB_COLUMNS c
      left join ALL_TAB_COMMENTS t
        on c.OWNER = t.OWNER
        and c.TABLE_NAME = t.TABLE_NAME
      left join ALL_COL_COMMENTS m
        on c.OWNER = m.OWNER
        and c.TABLE_NAME = m.TABLE_NAME
        and c.COLUMN_NAME = m.COLUMN_NAME
    where NOT REGEXP_LIKE(c.OWNER, 'ANONYMOUS|PUBLIC|SYS|SYSTEM|DBSNMP|MDSYS|CTXSYS|XDB|TSMSYS|ORACLE.*|APEX.*|TEST?*|GG_.*|\\$')
    order by schema_name, c.COLUMN_ID
|]

datasetMysqlSql :: T.Text
datasetMysqlSql = [q|
    select 
      concat(c.TABLE_SCHEMA, '.', c.TABLE_NAME) as schema_name
    , NULL as schema_description
    , c.COLUMN_NAME as field_path
    , c.DATA_TYPE as native_data_type
    , c.COLUMN_COMMENT as description
    from information_schema.columns c
    where table_schema not in ('information_schema') 
    order by schema_name, c.ORDINAL_POSITION
|]

main :: IO ()
main = do
  let
    jvmArgs = case $(TH.lift =<< TH.runIO (lookupEnv "CLASSPATH")) of
      Nothing -> []
      Just cp -> [ cs ("-Djava.class.path=" ++ cp) ]
    dbUrl :: T.Text = "jdbc:mysql://localhost:3306/datahub?useSSL=false"
    dbUser :: T.Text  = "datahub"
    dbPassword :: T.Text = "datahub"
    dbDriver :: T.Text = "com.mysql.jdbc.Driver"
    dbSQL :: T.Text = datasetMysqlSql
  runInBoundThread $ withJVM jvmArgs $ do
    [jDbUrl, jDbUser, jDbPassword, jDbDriver, jDbSQL ] <-
      mapM reflect [dbUrl, dbUser, dbPassword, dbDriver, dbSQL]
    
    result <- [java| {
      try {
        Class.forName($jDbDriver) ;
      } catch (ClassNotFoundException e) {
        e.printStackTrace() ;
        System.exit(1) ;
      }
      java.util.List<String[]> result = new java.util.ArrayList() ;
      try (java.sql.Connection con = java.sql.DriverManager.getConnection($jDbUrl, $jDbUser, $jDbPassword) ;
           java.sql.Statement st = con.createStatement(); ) {
        try (java.sql.ResultSet rs = st.executeQuery($jDbSQL)) {
          while(rs.next()) {
            String[] row  = {
              rs.getString("schema_name")
            , rs.getString("schema_description")
            , rs.getString("field_path")
            , rs.getString("native_data_type")
            , rs.getString("description")
            } ;
            System.out.println(rs.getString("field_path")) ;
            result.add(row) ;
          }
        }
        return result.toArray(new String[0][0]) ;
      } catch (java.sql.SQLException e) {
        e.printStackTrace() ;
        return null ;
      }
    } |]
    putStrLn "here..."
    xs :: [[T.Text]]  <- reify result
    putStrLn "there..."
    T.putStrLn (T.unwords (head xs))
    return ()

dataset-jdbc-generator.hs.nix

with import <nixpkgs> {} ;
let
  inline_java_git = fetchFromGitHub {
      owner = "tweag" ;
      repo = "inline-java" ;
      rev = "a897d32df99e4ed19314d2a7e245785152e9099d" ;
      sha256 = "00pk19j9g0mm9sknj3aklz01zv1dy234s3vnzg6daq1dmwd4hb68" ;
  } ; 
  haskellPackages = pkgs.haskellPackages.override {
    overrides = self: super: with pkgs.haskell.lib; {
      jni = overrideCabal (self.callCabal2nix "jni" (inline_java_git + /jni) {}) (drv: {
        preConfigure = ''
          local libdir=( "${pkgs.jdk}/lib/openjdk/jre/lib/"*"/server" )
          configureFlags+=" --extra-lib-dir=''${libdir[0]}"
        '' ;
      }) ;

      jvm = overrideCabal (self.callCabal2nix "inline-java" (inline_java_git + /jvm) {}) (drv: {
        doCheck = false ;
      }) ;
      inline-java = overrideCabal (self.callCabal2nix "inline-java" inline_java_git {}) (drv: {
        doCheck = false ;
      }) ;
    } ;
  };

in
mkShell {
  buildInputs = [
    pkgs.jdk
    pkgs.postgresql_jdbc
    pkgs.mysql_jdbc
    pkgs.mssql_jdbc

    (haskellPackages.ghcWithPackages ( p: 
      [ p.bytestring p.string-conversions
        p.interpolatedstring-perl6
        p.exceptions 
        p.inline-java
        
      ]
    ))
  ];
}

support inner classes in inline-java

Currently inline-java fails with a runtime error when trying to marshal an object of an inner class.

[java| Thread.State.NEW |] :: IO (J ('Class "java.lang.Thread.State"))

produces

Exception in thread "main" java.lang.NoSuchMethodError: inline__method_25

There are two problems with this behavior.

  1. Marshaling these objects should be possible.
  2. Ideally, inline-java should not produce these runtime errors when the user types an incorrect type.

To fix (1) we can have the user be explicit in that Thread.State is an inner class. He could do so by writing instead:

[java| Thread.State.NEW |] :: IO (J ('Class "java.lang.Thread:State"))

using : as a separator of the inner class. We can't use $ as a separator because $ is a valid character in Java identifiers.

To fix (2), the plugin could call javap on the generated bytecode and check that the signature of the methods inline__method_i are as expected. Thus, typing . instead of : would be caught at build time.

jni: Delete global reference in bound threads

The current approach is to have the Haskell GC delete the global references. Unfortunately, the GC deletes global references using unbound threads which are unsafe to use when making JNI calls.

The simplest fix of all is to wrap finalizers with Foreign.JNI.runInAttachedThread.

If the above is too slow, another solution is to implement a pool of threads to make sure finalizers are expediently executed once the GC makes up its mind to run them.

Lastly, #73 might also offer a solution to this problem.

Language.Java.Inline.Plugin can only be compiled from top level directory

This file includes a C header at compile time with TH:

    bctable_header :: String
    bctable_header = $(do
        let f = "cbits/bctable.h"
        TH.addDependentFile f
        TH.lift =<< TH.runIO (readFile f)
      )

This only works if we compile the file from the root of inline-java: this works fine for things like stack but does not work for things like bazel where the compilation might be occurring from "higher up". I don't know a good solution here.

Support inner classes in inline-java

Try the following snippet

diff --git a/dep/inline-java/tests/Language/Java/InlineSpec.hs b/dep/inline-java/tests/Language/Java/InlineSpec.hs
index 6c50a70..2f7f1a6 100644
--- a/dep/inline-java/tests/Language/Java/InlineSpec.hs
+++ b/dep/inline-java/tests/Language/Java/InlineSpec.hs
@@ -51,3 +51,8 @@ spec = do
         let foo = 1 :: Int32
         ([java| { class Foo { int f() { return $foo; } }; return 1; } |]
           >>= reify) `shouldReturn` (1 :: Int32)
+
+      it "Supports using antiquotation variables of inner classes" $ do
+        foo <- [java| p.Outer.Inner.A |] :: IO (J ('Class "p.Outer$Inner"))
+        _ <- [java| $foo |] :: IO JObject
+        return ()

with

package p;

public class Outer {
  public static enum Inner { A, B, C }
}

the result is

[1 of 3] Compiling Language.Java.InlineSpec ( tests/Language/Java/InlineSpec.hs, .stack-work/dist/x86_64-linux-nix/Cabal-1000.24.2.0/build/spec/spec-tmp/Language/Java/InlineSpec.o )
/run/user/1000/inlinejava21090/Inline__main_Language_Java_InlineSpec.java:60: error: cannot find symbol
  public static java.lang.Object function_6989586621679076301 (final p.Outer$Inner $foo)
                                                                      ^
  symbol:   class Outer$Inner
  location: package p
1 error      
callProcess: javac "/run/user/1000/inlinejava21090/Inline__main_Language_Java_InlineSpec.java" (exit 1): failed

The problem seems to be that the jni package wants the name of the inner class to be p.Outer$Inner (this is the same name that javap prints) and inline-java wants p.Outer.Inner.

Once we understand what syntax these names are expected to have, we can see what inline-java can do to translate them into java source names (e.g. p.Outer.Inner), and what jni can do to translate them to JNI internal names (e.g. p/Outer$Inner).

In principle, replacing '$' with '.' wouldn't work because class names can contain '$'. But it could be an acceptable stop-gap.

Support building code with external Java dependencies

By default, all of Java's extensive standard library is in scope. So a fair number of code snippets can be written inline. But they're limited to the standard library.

Tools like Gradle and Maven, much like Cabal, bring other packages into scope. That way packages that uses classes defined in those packages can be built. Because inline-java calls javac directly, we need to replicate the classpath settings that those tools generate, so as to call javac the way they do.

There are two options here:

  • detect the presence of build.gradle or maven .pom files, and coax a classpath out of the respective build tools.
  • call those build tools in place of naked javac, that way we don't fiddle with the classpath nor any other build setting. Problem is, we need to somehow convince those tools to build the out-of-band .java file that inline-java generates, despite not being part of the source sets a priori.

Document the performance cost of local/global refs creation

The JNI defines two types of object references: local references (only valid in the current thread, dies at the end of current call frame) and global references (globally valid, GC controlled lifetime).

The jvm package, like jni, currently always creates local references. But objects with local references are hard to handle: need to make sure they don't get shared with other threads, and need to make sure the local reference gets discarded eventually (i.e. doesn't leak). Types might help dealing with local references safely, but this can have a big impact on API's and on the ease of writing bindings. Global references have a major advantage: we can treat global object like any other Haskell value: create it, and then largely don't worry about its lifetime (the GC will take care of it).

We could in theory create global references always, removing the local references handed to us by default by the JNI. Is this viable? It depends on the performance cost. If there are no performance implications, then there is great value in forgetting about local references altogether (no impact on API's, no lifetimes to worry about...). If the performance gap between local and global references is noticeable but not too large, then it may still be worth it to create global references by default and then optimize them away in special cases.

tl;dr: designing a proper solution to #7 requires data. Which design point is the best compromise will depend on the data.

Variadic safe API

#133 and #135 both make call variadic, in the sense that the concrete type of call can change depending on the number of arguments provided. #135 only covers the unsafe API. Using the same approach in the safe API requires generalizing it to variadic functions in an abstract monad.

JVM memory leaks

One well known difficulty of interoperating two languages with automatic memory management is that the two garbage collectors tend to cut the grass under each other's feet. This is because each language has its own heap, which the GC of the other language can't traverse. A common solution to this problem (see e.g. HaskellR docs) is to add the objects referenced by one heap as GC roots in the other heap. Even then cycles can be an issue, but those are uncommon and/or can often be statically ruled out.

But unlike HaskellR, The jvm package has still left the memory management conundrum largely as "future work". In practice though, things work surprisingly well as-is. This is because the JNI does much of the work for us already. When the JNI provides a reference to some object, the reference is implicitly added as a GC root. So jvm is at least safe, in that objects won't just disappear under the Haskell program's feet (but see below). What's more, the JNI automatically pops these GC roots when the control flow returns from a native activation frame on the call stack, so leaks are not an issue in the (common) simple cases.

However, with the JNI we have other problems:

  • references are thread local. That means that the programmer shouldn't play games trying to store Java references in long-lived structures shared between multiple threads. There is currently no mechanism in place to statically protect the programmer from herself. Reference can be made thread-global at a small performance cost. Probably best to let the programmer do so explicitly. But we don't even have bindings for that yet.
  • Even JVM object references in long-lived thread-local structures won't do. Because then dynamic scope of the reference would be extruding from its lexical scope (remember that the JNI invalidates these references upon returning from a native call).

Both of these issues can be solved using monadic regions, in the style of Kiselyov and Shan. Regions give static guarantees that thread-local object references can't escape the lexical scope (i.e. can't live longer than the current activation frame).

One thing to keep in mind, however, is that monadic regions do have costs:

  • Need an ST-monad like transformer on top of IO, with a dummy type variable to track the active region. So no longer vanilla IO.
  • Imposes a monadic style everywhere when accessing Java objects, even in code that could otherwise be considered pure and written in direct style.
  • Regions impose a stack like discipline to memory management. Our experience suggests this is quite okay in practice, since it just means some objects end up living slightly longer (but predictably so) than they otherwise should, but ideally the programmer would retain a more fine grained control over the lifetime of resources.

A long term solution to both of those problems is to extend GHC with linear types. Tweag I/O is currently working with GHC HQ and Gothenburg university on precisely that (see https://ghc.haskell.org/trac/ghc/wiki/LinearTypes for an early writeup of the proposal). Linear types in this context would make it possible to avoid the inconvenience of a stack-like memory management discipline. One would still be able to free objects whenever, while still avoiding two GC's killing each other in a duel. Short term though I reckon our only bet is to embrace monadic regions if the programmers do need the extra static checking.

To summarize, I see two action items here:

  • introduce monadic regions for extra static checking of local references to JVM objects.
  • introduce an interface to allow the programmer to explicitly graduate local references to global references for advanced use cases. These global references would be modeled as a ForeignPtr in Haskell, so as to associate finalizers, which remove the global reference from the JVM once the object becomes unreachable.

This is all still up for discussion. For example, an alternative we could consider is to use only global references everywhere, with finalizers, no local references. But I worry about the performance overhead of such a strategy, which we'd have to measure carefully.

cc @robinbb @alpmestan @dcoutts

jni failed with no `jvm` command

I'm using Fedora Linux, openjdk and openjdk-devel are installed in the system, but none of them export command jvm. When I'm building java-inline and in particular jni library I get the following error

--  While building package jni-0.2.3 using:
      /home/sigrlami/.stack/setup-exe-cache/x86_64-linux/Cabal-simple_mPHDZzAJ_1.24.2.0_ghc-8.0.2 --builddir=.stack-work/dist/x86_64-linux/Cabal-1.24.2.0 configure --with-ghc=/home/sigrlami/.stack/programs/x86_64-linux/ghc-8.0.2/bin/ghc --with-ghc-pkg=/home/sigrlami/.stack/programs/x86_64-linux/ghc-8.0.2/bin/ghc-pkg --user --package-db=clear --package-db=global --package-db=/home/sigrlami/.stack/snapshots/x86_64-linux/lts-8.22/8.0.2/pkgdb --package-db=/home/sigrlami/work/projects-hs/tenderoom/tenders/api/.stack-work/install/x86_64-linux/lts-8.22/8.0.2/pkgdb --libdir=/home/sigrlami/work/projects-hs/tenderoom/tenders/api/.stack-work/install/x86_64-linux/lts-8.22/8.0.2/lib --bindir=/home/sigrlami/work/projects-hs/tenderoom/tenders/api/.stack-work/install/x86_64-linux/lts-8.22/8.0.2/bin --datadir=/home/sigrlami/work/projects-hs/tenderoom/tenders/api/.stack-work/install/x86_64-linux/lts-8.22/8.0.2/share --libexecdir=/home/sigrlami/work/projects-hs/tenderoom/tenders/api/.stack-work/install/x86_64-linux/lts-8.22/8.0.2/libexec --sysconfdir=/home/sigrlami/work/projects-hs/tenderoom/tenders/api/.stack-work/install/x86_64-linux/lts-8.22/8.0.2/etc --docdir=/home/sigrlami/work/projects-hs/tenderoom/tenders/api/.stack-work/install/x86_64-linux/lts-8.22/8.0.2/doc/jni-0.2.3 --htmldir=/home/sigrlami/work/projects-hs/tenderoom/tenders/api/.stack-work/install/x86_64-linux/lts-8.22/8.0.2/doc/jni-0.2.3 --haddockdir=/home/sigrlami/work/projects-hs/tenderoom/tenders/api/.stack-work/install/x86_64-linux/lts-8.22/8.0.2/doc/jni-0.2.3 --dependency=base=base-4.9.1.0 --dependency=bytestring=bytestring-0.10.8.1 --dependency=containers=containers-0.5.7.1 --dependency=inline-c=inline-c-0.5.6.1-2pSLvIEC8gg9yL15JFH39 --dependency=singletons=singletons-2.2-AjIoW7ouIQy1XUxXDvyPLZ --dependency=thread-local-storage=thread-local-storage-0.1.1-FpcC9hY7QTfBqXOxscYOUn
    Process exited with code: ExitFailure 1
    Logs have been written to: /home/sigrlami/work/projects-hs/tenderoom/tenders/api/.stack-work/logs/jni-0.2.3.log

    Configuring jni-0.2.3...
    Cabal-simple_mPHDZzAJ_1.24.2.0_ghc-8.0.2: Missing dependency on a foreign
    library:
    * Missing C library: jvm
    This problem can usually be solved by installing the system package that
    provides this library (you may need the "-dev" version). If the library is
    already installed but in a non-standard location then you can use the flags
    --extra-include-dirs= and --extra-lib-dirs= to specify where it is.

I can create an environment variable, but need to point jvm to somewhere. Can you tell where jvm variable should point in OpenJDK?

Import syntax

This small example is in the docs:

imports "javax.swing.JOptionPane"

hello :: IO ()
hello = do
    message <- reflect ("Hello World!" :: Text)
    [java| JOptionPane.showMessageDialog(null, $message) |]

but the "imports" part is just made-up syntax. Are there plans to add support for imports so you don't have to fully qualify every type?

how to run inline-java by runghc?

i use nix-shell to setup the inline-java environment,
and i also can ghc compile and run the file.

but i have no idea how to use 'runghc' to run it.
and i want to know whether it can be support to do?

[larluo@nixos-larluo:~/my-repo/datahub/contrib/metadata-ingestion]$ nix-shell ./bin/dataset-jdbc-generator.hs.nix

[nix-shell:~/my-repo/datahub/contrib/metadata-ingestion]$ runghc ./bin/dataset-jdbc-generator.hs

bin/dataset-jdbc-generator.hs: error:
    inline-java Plugin: found invalid qqMarker.

<no location info>: error: 
Compilation had errors


*** Exception: ExitFailure 1

the related file is:

[nix-shell:~/my-repo/datahub/contrib/metadata-ingestion]$ cat bin/dataset-jdbc-generator.hs
#! /usr/bin/env nix-shell                                                                                                                                                     
#! nix-shell dataset-jdbc-generator.hs.nix -i runghc                                                                                                                                

{-# LANGUAGE OverloadedStrings, FlexibleInstances, FlexibleContexts, ScopedTypeVariables #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}

import Language.Java (withJVM)
import Language.Java.Inline

main :: IO ()
main = withJVM [] [java| {
  System.out.println("Hello Java!") ;
} |]

[nix-shell:~/my-repo/datahub/contrib/metadata-ingestion]$ cat bin/dataset-jdbc-generator.hs.nix
with import <nixpkgs> {} ;                                                                                                                                                    
let                                                                                                                                                                           
  inline_java_git = fetchFromGitHub {                                                                                                                                         
      owner = "tweag" ;                                                                                                                                                       
      repo = "inline-java" ;                                                                                                                                                  
      rev = "a897d32df99e4ed19314d2a7e245785152e9099d" ;                                                                                                                      
      sha256 = "00pk19j9g0mm9sknj3aklz01zv1dy234s3vnzg6daq1dmwd4hb68" ;                                                                                                       
  } ;                                                                                                                                                                         
  haskellPackages = pkgs.haskellPackages.override {                                                                                                                           
    overrides = self: super: with pkgs.haskell.lib; {                                                                                                                         
      jni = overrideCabal (self.callCabal2nix "jni" (inline_java_git + /jni) {}) (drv: {                                                                                      
        preConfigure = ''                                                                                                                                                     
          local libdir=( "${pkgs.jdk}/lib/openjdk/jre/lib/"*"/server" )                                                                                                       
          configureFlags+=" --extra-lib-dir=''${libdir[0]}"                                                                                                                   
        '' ;                                                                                                                                                                  
      }) ;                                                                                                                                                                    
                                                                                                                                                                              
      jvm = overrideCabal (self.callCabal2nix "inline-java" (inline_java_git + /jvm) {}) (drv: {                                                                              
        doCheck = false ;                                                                                                                                                     
      }) ;                                                                                                                                                                    
      inline-java = overrideCabal (self.callCabal2nix "inline-java" inline_java_git {}) (drv: {
        doCheck = false ;                  
      }) ;                                 
    } ;                                    
  };                                       
                                           
in
mkShell {
  buildInputs = [
    pkgs.jdk
    (haskellPackages.ghcWithPackages ( p: 
      [ p.bytestring p.string-conversions
        p.exceptions 
        p.inline-java
      ]
    ))
  ];
}

Improve NoSuchMethod and NoSuchField error messages

Looking up methods to invoke using the jvm or jni packages can produce errors like

Exception in thread "main" java.lang.NoSuchMethodError: fooMethod

if the types that the caller specifies on the Haskell side do not match the type signature of a method in a given Java class. Moreover, inline-java can produce these errors when handling references to instances of inner classes as discussed in #89.

The error would be much more helpful if it said something like

Exception in thread "main" java.lang.NoSuchMethodError: fooMethod  (Ljava.lang.Thread.State;)J
Possible type signatures for fooMethod in class :
(Ljava.lang.Thread$State;)J
...

The first line gives the JNI type signature that was used for the lookup. The following line gives the name of the class on which the lookup was made. And the following lines list the type signatures for all the available overloadings of fooMethod in the given class or any of its superclasses.

These errors are produced by getFieldID and getMethodID in the JNI package. A combination of isInstanceOf to identify the exception and then the reflection api of java to get the relevant method overloadings looks necessary.

The quasiquoter fails when using type synonyms.

The following program succeeds:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}

import Data.Int
import Foreign.JNI
import Language.Java
import Language.Java.Inline

type JL = J ('Class "java.lang.Long")

main :: IO Int32
main = withJVM [] $ do
    jlong <- new [JLong 1] :: IO (J ('Class "java.lang.Long"))
--  let jlong = jlong :: JL
    [java| {
      System.out.println($jlong);
      return 0;
      } |]
$ runghc --version
runghc 8.0.2
$ runghc --ghc-arg=-fobject-code t.hs
1

But if we uncomment the line let jlong = jlong :: JL we get

$ runghc --ghc-arg=-fobject-code t.hs
t.hs:16:11: error:
    • unliftJType: cannot unlift ty_0
    • In a stmt of a 'do' block:
        (((unsafeUncoerce . coerce)
          <$>
            ((Language.Java.Inline.loadJavaWrappers
              >>
                (callStatic
                   (sing :: Sing "io.tweag.inlinejava.Inline__main_Main")
                   (Data.String.fromString "function_6989586621679035869")
                   [coerce jlong_a4c5])) ::
               IO (J (Class "java.lang.Object")))))
      In the second argument of ‘($)’, namely
        ‘do { jlong <- new [JLong 1] :: IO (J (Class "java.lang.Long"));
              let jlong = ...;
              (((unsafeUncoerce . coerce)
                <$>
                  ((Language.Java.Inline.loadJavaWrappers
                    >>
                      (callStatic
                         (sing :: Sing "io.tweag.inlinejava.Inline__main_Main")
                         (Data.String.fromString "function_6989586621679035869")
                         [coerce jlong_a4c5])) ::
                     IO (J (Class "java.lang.Object"))))) }’
      In the expression:
        withJVM []
        $ do { jlong <- new [JLong 1] :: IO (J (Class "java.lang.Long"));
               let jlong = ...;
               (((unsafeUncoerce . coerce)
                 <$>
                   ((Language.Java.Inline.loadJavaWrappers
                     >>
                       (callStatic
                          (sing :: Sing "io.tweag.inlinejava.Inline__main_Main")
                          (Data.String.fromString "function_6989586621679035869")
                          [coerce jlong_a4c5])) ::
                      IO (J (Class "java.lang.Object"))))) }

t.hs:16:11: error:
    • Q monad failure
    • In a stmt of a 'do' block:
        (((unsafeUncoerce . coerce)
          <$>
            ((Language.Java.Inline.loadJavaWrappers
              >>
                (callStatic
                   (sing :: Sing "io.tweag.inlinejava.Inline__main_Main")
                   (Data.String.fromString "function_6989586621679035869")
                   [coerce jlong_a4c5])) ::
               IO (J (Class "java.lang.Object")))))
      In the second argument of ‘($)’, namely
        ‘do { jlong <- new [JLong 1] :: IO (J (Class "java.lang.Long"));
              let jlong = ...;
              (((unsafeUncoerce . coerce)
                <$>
                  ((Language.Java.Inline.loadJavaWrappers
                    >>
                      (callStatic
                         (sing :: Sing "io.tweag.inlinejava.Inline__main_Main")
                         (Data.String.fromString "function_6989586621679035869")
                         [coerce jlong_a4c5])) ::
                     IO (J (Class "java.lang.Object"))))) }’
      In the expression:
        withJVM []
        $ do { jlong <- new [JLong 1] :: IO (J (Class "java.lang.Long"));
               let jlong = ...;
               (((unsafeUncoerce . coerce)
                 <$>
                   ((Language.Java.Inline.loadJavaWrappers
                     >>
                       (callStatic
                          (sing :: Sing "io.tweag.inlinejava.Inline__main_Main")
                          (Data.String.fromString "function_6989586621679035869")
                          [coerce jlong_a4c5])) ::
                      IO (J (Class "java.lang.Object"))))) }

Cannot compile on MacOS

I am having problems compiling inline-java on MacOS.

Particularly, jni package cannot be built because it can't find the jvm library:

$ stack build jni --extra-lib-dirs=$JAVA_HOME/jre/lib/server/ --extra-include-dirs $JAVA_HOME/include --extra-include-dirs $JAVA_HOME/include/darwin
jni-0.6.0: configure
jni-0.6.0: build

--  While building custom Setup.hs for package jni-0.6.0 using:
      /Users/araga/.stack/setup-exe-cache/x86_64-osx/Cabal-simple_mPHDZzAJ_2.0.1.0_ghc-8.2.2 --builddir=.stack-work/dist/x86_64-osx/Cabal-2.0.1.0 build --ghc-options " -ddump-hi -ddump-to-file -fdiagnostics-color=always"
    Process exited with code: ExitFailure 1
    Logs have been written to: /Users/araga/src/arbor/sparkle-attacks/.stack-work/logs/jni-0.6.0.log

    Configuring jni-0.6.0...
    Preprocessing library for jni-0.6.0..
    dyld: Library not loaded: @rpath/libjvm.dylib
      Referenced from: /private/var/folders/3x/l50y6rts50j_9jqyp0fl7lqh0000gn/T/stack58755/jni-0.6.0/.stack-work/dist/x86_64-osx/Cabal-2.0.1.0/build/Foreign/JNI/NativeMethod_hsc_make
      Reason: image not found
    running .stack-work/dist/x86_64-osx/Cabal-2.0.1.0/build/Foreign/JNI/NativeMethod_hsc_make failed (exit code -6)
    command was: .stack-work/dist/x86_64-osx/Cabal-2.0.1.0/build/Foreign/JNI/NativeMethod_hsc_make  >.stack-work/dist/x86_64-osx/Cabal-2.0.1.0/build/Foreign/JNI/NativeMethod.hs

I have tried providing --ghc-options "-optl-Wl,-rpath,$JAVA_HOME/jre/lib/server" but it doesn't help.

I have also tried adding these options to my stack.yaml file:

ghc-options:
  "*": -optl-Wl,-rpath,$JAVA_HOME/jre/lib/server

and

ghc-options:
  jni: -optl-Wl,-rpath,/Library/Java/JavaVirtualMachines/jdk1.8.0_112.jdk/Contents/Home/jre/lib/server

but it doesn't help either.

Can anyone advice on how to configure my project to build it successfully with inline-java?

Ambiguous type for Language.Java.unsafeUncoerce

I'm trying to play with library and get the following error on build

   /home/sigrlami/work/projects-hs/tenderoom/tenders/api-pdf/src/Main.hs:100:11: error:
        • Ambiguous type variables ‘a0’, ‘ty0’ arising from a use of ‘unsafeUncoerce’
          prevents the constraint ‘(Coercible a0 ty0)’ from being solved.
          Probable fix: use a type annotation to specify what ‘a0’, ‘ty0’ should be.
          These potential instances exist:
            instance Coercible Int32 ('Prim "int")
              -- Defined in ‘Language.Java’
            instance singletons-2.2:Data.Singletons.SingI ty =>
                     Coercible (J ty) ty
              -- Defined in ‘Language.Java’
            instance Coercible () 'Void -- Defined in ‘Language.Java’
            ...plus four others
            ...plus four instances involving out-of-scope types
            (use -fprint-potential-instances to see them all)
        • In the first argument of ‘(.)’, namely ‘unsafeUncoerce’
          In the first argument of ‘(<$>)’, namely
            ‘(unsafeUncoerce . coerce)’
          In a stmt of a 'do' block:
            (((unsafeUncoerce . coerce)
              <$>
                ((Language.Java.Inline.loadJavaWrappers
                  >>
                    (callStatic
                       (sing :: Sing "io.tweag.inlinejava.Inline__main_Main")
                       (fromString "function_6989586621679164823")
                       [coerce cpath_aE7R])) ::
                   IO (J (Class "java.lang.Object")))))

for a very simple example

{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE DataKinds           #-}
{-# LANGUAGE QuasiQuotes         #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Main where

import           Control.Applicative
import           Control.Concurrent
import qualified Control.Exception                    as Exception
import           Control.Lens
import           Control.Monad                        (forever)
import           Control.Monad.IO.Class
import           Data.Aeson
import qualified Data.ByteString                      as BS
import qualified Data.ByteString.Char8                as BSC
import qualified Data.ByteString.Lazy                 as BSL
import           Data.Maybe
import           Data.Monoid
import qualified Data.Text                            as T
import qualified Data.Text.Encoding                   as T
import           Data.Time
import           Network.Wai
import           Network.Wai.Handler.Warp             (run)
import           Network.Wai.Middleware.Cors
import           Network.Wai.Middleware.RequestLogger (logStdoutDev)
import           Options.Applicative
import           Servant
import           Servant.API
import           Servant.API.BasicAuth
import           System.Directory
import           System.Environment
import           System.IO
import qualified System.IO                            as IO
import           Text.Read

import           Data.Int (Int32)
import           Data.String (fromString)
import           Foreign.JNI (withJVM)
import           Language.Java
import           Language.Java.Inline

import           Api

-----------------------------------------------------------------------------

data Options =
  Options { opPort     :: Maybe String
          , opJavaPath :: Maybe String
          , opMode     :: Bool
          }

optionsParser :: Parser Options
optionsParser = Options
  <$> optional (strOption
      ( long    "port"
     <> short   'p'
     <> metavar "PORT"
     <> help    "port to run server" ))
  <*> optional (strOption
      ( long    "java"
     <> short   'j'
     <> metavar "JAVA"
     <> help    "path to java classpath of the library" ))
  <*> flag False True
      ( long "development"
     <> short 'd'
     <> long "Switch, to run in development mode (by default = false)")

-- | Description of the utility.
optionsDesc :: InfoMod Options -- ^ parser description
optionsDesc = headerDesc <> fullDesc
  where headerDesc = header ""

-- | Parser of the command-line options.
parser :: ParserInfo Options
parser = info (helper <*> optionsParser) optionsDesc

--------------------------------------------------------------------------------

main :: IO ()
main = do
  opts <- execParser parser
  let port = case opPort $ opts of
               Nothing  -> 3005
               Just val -> (read val) :: Int
      javaClassPath = BSC.pack $ fromMaybe "" $ opJavaPath $ opts
        
  withJVM [javaClassPath] $ do
    cpath <- reflect javaClassPath
    [java| {
      System.out.println("Checking Java env ");
      System.out.println("  current path is:" );
      System.out.println("    " + $cpath );
      return 0;
      }
    |]
                              
  putStrLn $ "|INFO | api-pdf | Loading server on port " ++ (show port) ++ "..."
  
  putStrLn $ "|INFO | api-pdf | Running production"
  run port $
     logStdoutDev $
         serve restAPIv1 server
         

How can I fix this?

Android support

According to experiments by @angerman, building for Android is possible but Android does require slightly different linker flags when building. #70 has more about this, but we want to achieve the same effect using a configure script.

Inheritance

Hi, are there any plans to add support for Java inheritance? From scanning the docs, all I found was

upcast :: J a -> J (Class "java.lang.Object")

and

unsafeCast :: J a -> J b

However, it would be nice to have some sort of

upcast :: Extends a b => J b -> J a

instance Extends a (J (Class "java.lang.Object"))

instead.

Thanks!

Handle modified UTF-8 correctly

We need to make sure that we are converting strings correctly between Java and Haskell.

Strings are converted in the jvm packages in the Reify and Reflect instances of Text, and in the jni package in the Foreign.JNI.String module.

Probably we should take a look at how UTF-8 encoding is implemented in https://www.stackage.org/haddock/lts-16.19/base-4.13.0.0/System-IO.html#v:utf8 and https://www.stackage.org/haddock/lts-16.19/text-1.2.4.0/Data-Text-Encoding.html#v:encodeUtf8, and try to imitate those.

We have a spec here: http://docs.oracle.com/javase/8/docs/technotes/guides/jni/spec/types.html#modified_utf_8_strings

Bound the queue of the finalizer thread

Currently the queue of the finalizer thread is unbounded, which can lead to memory exhaustion if the worker thread cannot keep up with the submission rate.

Ideally, the queue would be bounded to some configurable value, and the submiters would be blocked when the queue is full.

Perhaps the value can be configured with a new call setFinalizerThreadQueueSize :: Int -> IO (), and we would have some "large" default value.

Cannot clone submodules

I understand that the submodules are needed to build the project with ghc HEAD (which looks like a hard requirement at the moment). But it seems like the reference for the ghc-heap-view submodule is invalid:

koen@koen-desktop ~/Code/inline-java $ git submodule update --init --recursive
...
Cloning into 'vendor/ghc-heap-view'...
remote: Counting objects: 623, done.
remote: Compressing objects: 100% (4/4), done.
remote: Total 623 (delta 0), reused 0 (delta 0), pack-reused 619
Receiving objects: 100% (623/623), 203.72 KiB | 339.00 KiB/s, done.
Resolving deltas: 100% (314/314), done.
Checking connectivity... done.
fatal: reference is not a tree: 4475a4c128cbee3323dc657134b847e2f8170772
...
Unable to checkout '4475a4c128cbee3323dc657134b847e2f8170772' in submodule path 'vendor/ghc-heap-view'

Implement a compiler plugin to aid code generation

We don't have yet a good way to know which type the program expects for a given quasiquotation, therefore, the implementation assumes that all generated java stubs return java.lang.Object. At runtime, we can check that the type of the actual object matches the type that the program needs, but it would be better if we could learn about it at build time.

To address this we can implement a GHC plugin. It would work roughly as follows.

Given a module like

module M where
import Language.Java.Inline

io1 :: IO Int32
io1 = [java| 1  |]

io2 :: Int32 -> Int32 -> IO Int32
io2 x y = [java| $x + $y |]

TH produces a Haskell module like

module M where
import Language.Java.Inline

io1 :: IO Int32
io1 = callAnnotation (Proxy :: Proxy 1)
                     (callStatic "Inlinejava_M" "function1" [])
                     ()

io2 :: Int32 -> Int32 -> IO Int32
io2 x y = callAnnotation (Proxy :: Proxy 2)
                         (callStatic "Inlinejava_M" "function2" [coerce x, coerce y])
                         (x, y)

{-# ANN module (1, "1", []) #-}
{-# ANN module (2, "$x + $y", ["x", "y"]) #-}

where callAnnotation is an auxiliary function to carry the types we are interested in to the plugin phase.

callAnnotation :: Proxy i -> IO b -> args_tuple -> IO b
callAnnotation _ iob _ = iob

The module annotations would carry the AST of the java code in the quasiquotations and the names of the antiquotations, together with an index that is used to learn to which occurrence of callAnnotation they correspond.

Next, the compiler plugin makes a pass over the initial core to collect the types b and args_tuple from all the occurrences of callAnnotation. Then matches them with the corresponding values from the ANN pragmas. Then it produces the java code

class Inlinejava_M {
  int function1() { return 1; }
  int function2(int $x, int $y) { return $x + $y; }
}

Next this code is compiled with javac and the bytecode is included in a global bytecode table.
We can no longer use the static pointer table because, by this point, static pointers have already been desugared to core.

One could conceivably do away with the ANN pragmas. For this, the implementation should get the quasiquotation text and the variable names from core. In principle, this would make it more fragile to changes in how ghc desugars the output of the typechecker, so the current proposal might be preferable.

Generated java module names clash when package has multiple executables

inline-java generates java classes with names of the form Inline__<package>_<module_name> which most of the time allows to identify the Haskell module it belongs to. Unfortunately, there is an exception: Inline__main_Main.java

If the Main module of two executables in the same package use inline-java, the classes generated for both modules will have the same name, and one of them won't be possible to load.

The simplest fix might be to include a generated unique number in the class name of Main modules.

Handle encoding correctly when doing substitutions.

Right now jni is converting . to / in types to produce type signatures. However, any byte with the value . is converted. Many unicode characters use this byte and would be incorrectly handled.

#90 introduces the same problem in the inline-java Plugin.

Issues compiling on OSX

The ghc-heap-view submodule fails to checkout mboes/ghc-heap-view@4475a4c for some reason. Works with mboes/ghc-heap-view@614301c (patch here).

Build of the jni package fails with:

Preprocessing library jni-0.1...
[3 of 3] Compiling Foreign.JNI      ( src/Foreign/JNI.hs, .stack-work/dist/x86_64-osx-nix/Cabal-1.25.0.0/build/Foreign/JNI.o )

src/Foreign/JNI.hs:336:1: error:
    Invalid type signature: call Void Method :: ...
    Should be of form <variable> :: <type>

I guess that's my preprocessor's fault? I'm not really that familiar with this style of CPP macros.

Support type parameters

Is your feature request related to a problem? Please describe.

It is difficult to use quasiquotations that are type safe and can be reused with different types.

f :: (IsReferenceType a, Coercible a) => a -> IO a
f obj = [java| $obj |]

The above code is rejected because at compile time, inline-java doesn't know which Java type to give to $obj.
We can do casts instead:

f :: (IsReferenceType a, Coercible a) => a -> IO a
f (coerce -> JObject obj) = unsafeUncoerce . JObject <$> [java| $obj |]

which can fail at runtime if the user gets the types wrong.

Describe the solution you'd like

Ideally, we would have in Java code like

public <A> A f (A $obj) { return $obj; }

and our initial definition would be accepted

f :: (IsReferenceType a, Coercible a) => a -> IO a
f obj = [java| $obj |]

The code generated by inline-java would be responsible for making the appropriate casts.

There is some room to decide where type variables are allowed in a type. Here's an example where the type variable appears nested within a type.

f :: (IsReferenceType a, Coercible a) => a -> IO (J ('Iface "java.util.List" <> '[ Ty a ]))
f _ = [java| new ArrayList<A>() |]

And we also would have to consider if/how to deal with bounded type parameters.

Enums

An example for how to bind to java enums would be great. I've tried several different things and none have worked out so far. For example, for some enum Day = MONDAY | TUESDAY | ... enum, this code:

type Day = J ('Class "foobar.Day")

dayMonday :: IO Day
dayMonday = [java| { foobar.Day.MONDAY } |]

seems to work (it compiles), and I also believe it can be underneath an unsafePerformIO, but regardless - actually trying to use this function throws

Exception in thread "main" java.lang.NoSuchMethodError: function_6989586621679038179
blah: JVMException (J 0x000000000208c638)

Introduce type-level regions

There are three problems that could be addressed by the introduction of type-level regions:

  1. Preventing reference leaks. Related #7
  2. Caching class references (by using a reader monad). Related #72
  3. Ensuring local references are used in the thread they belong to

There are alternative ways to address each of these issues but using regions might yield a simpler and still effective design.

Handle asynchronous Java exceptions

From @alpmestan on February 29, 2016 15:40

From the JNI spec:

Asynchronous Exceptions
In cases of multiple threads, threads other than the current thread may post an asynchronous exception. An asynchronous exception does not immediately affect the execution of the native code in the current thread, until:

  • the native code calls one of the JNI functions that could raise synchronous exceptions, or
  • the native code uses ExceptionOccurred() to explicitly check for synchronous and asynchronous
    exceptions.

Note that only those JNI functions that could potentially raise synchronous exceptions check for asynchronous exceptions.
Native methods should insert ExceptionOccurred() checks in necessary places (such as in a tight loop without other exception checks) to ensure that the current thread responds to asynchronous exceptions in a reasonable amount of time.

Copied from original issue: tweag/sparkle#19

InlineSpec not being run

Hey,

More of a question, is it possible that the InlineSpec under tests/Language/Java/InlineSpec.hs is not run when launching 'stack test'? I added a failing test but nothing seems to happen when running stack test from the root of the project. The other test suite, under jvm/ is being run, that I can see.

Kasper

Better support for custom class loaders

The JVM supports programmable class loaders. It's possible to override the default system class loader with a custom one. But as @facundominguez found out in tweag/sparkle#72, which class loader gets used to resolve a particular class name is a property of the dynamic scope. If one forks a new thread, the call stack starts empty, so the class loader reverts to the default system one on that thread.

I'm not sure how to solve this best, but the basic objective of this ticket is: provide a mechanism to "inherit" the class loader when from the parent thread in the child thread. This is an inherent problem in any language interfacing with Java with the JNI, not just Haskell. But nothing wrong with us building some good abstractions on top to deal with this nicely.

Free attached threads

From @alpmestan on February 29, 2016 15:46

When Haskell threads die, we should tell Java about it so that it frees the corresponding Thread object and removes it from the ThreadGroup. Otherwise we're leaking memory.

Copied from original issue: tweag/sparkle#21

Gradle process doesn't exist

I already have a small interop between haskell and java, but having custom-setup leads to following error, when I'm trying to hook 3rd party lib:

--  While building package api-pdf-0.2.0.0 using:
      /home/sigrlami/work/projects-hs/api-pdf/.stack-work/dist/x86_64-linux/Cabal-1.24.2.0/setup/setup --builddir=.stack-work/dist/x86_64-linux/Cabal-1.24.2.0 build exe:api-pdf --ghc-options " -ddump-hi -ddump-to-file"
    Process exited with code: ExitFailure 1
    Logs have been written to: /home/sigrlami/work/projects-hs/api-pdf/.stack-work/logs/api-pdf-0.2.0.0.log

    Configuring api-pdf-0.2.0.0...
    gradle: readCreateProcess: runInteractiveProcess: exec: does not exist (No
    such file or directory)

gradle command is available in the environment, I can do installDist and build. I'm not sure what it is looking for. I looked up https://github.com/tweag/inline-java/blob/master/src/Language/Java/Inline/Cabal.hs but couldn't deduce something useful.

How can I fix this? cc: @alpmestan

Don't rely on optimizations to avoid reference leaks.

The jvm package relies on the compiler to float code like:

unsafePerformIO $ findClass "java/lang/String" >>= newGlobalRefNonFinalized

so the class is effectively created only once.

If the optimization does not happen, a global reference is created every time the control flow passes over the expression.

Some solutions:
1 Collect the global references in an environment and run java calls on a monad which carries this environment and reuses the references when they have been already created.
2. Collect the global references in a global and mutable table where java calls can look them up.
3. Create the global references in global and inmutable variables. These are defined as methods of a class KnownReferenceType:

class IsReferenceType ty => KnownReferenceType (ty :: JType) where
  findTaggedClass :: Tagged ty JClass
  -- can define a default instance here
  1. Use a compiler plugin to generate the instances of KnownReferenceType. We would examine the code and whenever we find that KnownReferenceType ty is needed, we generate an instance for it, provided that ty is enough instantiated to know which class is needed. We would have to investigate whether the plugin interface allows to do this.

We have tried (3). It requires the programmer to declare multiple instances: one instance every time a method of a class is going to be called. It solves the problem and helps finding typos, but it would be better not to have to write the instances.

Fix instances of Reify and Reflect for lists of references.

These instances used to work when reify j produced a global reference of j. But now, reify [j] will delete the very local references that it is returning, and reflect [j] will delete the input j likely surprising the user.

Perhaps reify and reflect could be fixed by using local frames depending on how expensive they are.

  instance Reify a => Reify [a] where
    reify jobj = do
        n <- getArrayLength jobj
        forM [0..n-1] $ \i -> do
          jx <- getObjectArrayElement jobj i
          x  <- reify jx
          deleteLocalRef jx
          return x

  instance Reflect a => Reflect [a] where
    reflect xs = do
      let n = fromIntegral (length xs)
      array <- newArray n :: IO (J ('Array (Interp a)))
      forM_ (zip [0..n-1] xs) $ \(i, x) -> do
        jx <- reflect x
        setObjectArrayElement array i jx
        deleteLocalRef jx
      return array

Upload docs to hackage?

Due to build time dependencies on java there are no haddocks on hackage. Maybe consider uploading them manually.

Don't write on stderr each time an Exception occurs

Currently, each time an Exception occurs on the Java side, it is caught in JNI.Unsafe.Internal, printed on stderr, and tranformed into a JVMException on the Haskell side, where it is thrown with throwIO.

It's problematic because this printing on stderr occurs even if the exception is caught afterwards, and may clutter stdout, particularly on test cases, where multiple exceptions may be expected.

Instead, we could capture the message of the Java Exception, and include it in the Show instance for JVMException. This would allow us to print it only when needed

Make getMethodID/findClass pure

From @alpmestan on February 29, 2016 15:44

When one of these two functions is called with a literal method name, the compiler can automatically float the call to top level and make it a CAF, thus seamlessly sharing method lookups across all callers.

Methods are static objects: they don't change over time. Unless of course you take into account class unloading. But that's like saying all calls to any function in any dynamic library should be in IO, because the library could be unlinked from the address space conceivably.

Alternatively, the user could memoize calls manually, by maintaining and passing around hash tables. This is obviously less than ideal.

Copied from original issue: tweag/sparkle#20

Import a local .jar

How would one import from a local .jar file? Would I have to install it globally?

inline-java doesn't build on windows

All of the java related packages seems to be broken. I am not able to install jvm, inline-java using cabal. After quite some struggle, I was able to install jni-0.6.1, but ghc is not able to load it.

Getting following error while installng jvm :
ghc.exe: unable to load package jni-0.6.1' ghc.exe: | C:\Users\parde\AppData\Roaming\cabal\x86_64-windows-ghc-8.6.5\jni-0.6.1-1nqvRZd4IqkECn3WTF5lOt\HSjni-0.6.1-1nqvRZd4IqkECn3WTF5lOt.o: unknown symbol __emutls_get_address'
cabal: Leaving directory '.'
cabal: Error: some packages failed to install:
jvm-0.4.2-1aztzhkOAgCho7SY0VoSP failed during the building phase

Streamline callbacks to haskell with inline-java

Many libraries in java call back into user code to perform its functions. One notable example is GUI libraries. We have another example in jvm-streaming. https://github.com/tweag/inline-java/blob/master/jvm-streaming/src/main/haskell/Language/Java/Streaming.hs#L92

    iterator <-
      [java| new Iterator() {
          private boolean end = false;
          private Object lookahead;
          @Override
          public boolean hasNext() { return !end; }

          @Override
          public Object next() {
            if (hasNext()) {
              final Object temp = lookahead;
              lookahead = hsNext();
              return temp;
            } else
              throw new java.util.NoSuchElementException();
          }

          @Override
          public void remove() { throw new UnsupportedOperationException(); }
          private native void hsFinalize(long tblPtr);
          private native Object hsNext();
          @Override
          public void finalize() { hsFinalize($tblPtr); }
        } |]

The iterator is passed to a function that will retrieve values from Haskell via the native methods of our anonymous Iterator class.

Various housekeeping tasks are necessary to link Haskell functions with those native methods. This issue is about designing and implementing a mechanism that would allow to automate the housekeeping. Suppose we implemented somehow a new quasiquoter like:

    iterator <-
      [new| Iterator() {
          private boolean end = false;
          private Object lookahead;
          @Override
          public boolean hasNext() { return !end; }

          @Override
          public Object next() {
            if (hasNext()) {
              final Object temp = lookahead;
              lookahead = hsNext();
              return temp;
            } else
              throw new java.util.NoSuchElementException();
          }

          @Override
          public void remove() { throw new UnsupportedOperationException(); }
          private native Object $$hsNext();
          @Override
          public void finalize() { hsFinalize(); }
        } |]

Which is capable of identifying hsNext, link it with the corresponding Haskell function and automatically synthesize hsFinalize.

A major challenge with this approach is to produce the FFI wrappers of the haskell functions. Template Haskell can produce FFI wrappers with addTopDecls, but the type information necessary to do so would be available only after type-checking.

Prepare jvm-batching.jar to be released in maven central

The jvm-batching package offers some java interfaces that need to be public.

We could just refer people to the inline-java github repo to build the jar, but probably it is going to be easier to manage the Java dependencies if we upload the package to maven central.

We need to write the metadata and the instructions to build and upload the jar.

This ticket comes from the discussion in #10.

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.