Skip to content

Instantly share code, notes, and snippets.

@rahulmutt
Last active November 22, 2017 22:27
Show Gist options
  • Star 4 You must be signed in to star a gist
  • Fork 1 You must be signed in to fork a gist
  • Save rahulmutt/355505bce57c7c2cffd7d4cf5edddad4 to your computer and use it in GitHub Desktop.
Save rahulmutt/355505bce57c7c2cffd7d4cf5edddad4 to your computer and use it in GitHub Desktop.
Documents how the Java Foreign Function Interface will look in GHCVM, a Haskell to JVM compiler.

Table of Contents generated with DocToc

Changelog - V0.2

  • Added direct support for Java array types
    • Added JArray# primitive type
    • Added JArrayElem type family
    • Added IsJArray typeclass
  • Object# s -> JObject# s
  • SuperObject# -> Object#
  • Implements has been merged into Extends
  • Added Java Generics section
  • Changed "interface" to "wrapper" in the Single Method Interfaces section to more closely match GHC.
  • Added JavaFX Example section
  • Added some more primitives to Java.hs like class#.
  • Added the JavaContext typeclass to allow using new in multiple monads.
  • All Java methods (static, instance, and constructors) now run in the Java monad. Static methods have a generic signature in the class parameter. This is done so that there's a clear separation of Haskell and Java code.
  • Defined java function to run arbitrary Java monadic actions without setting the this reference.
  • The definition of initJava changed and its operator is now >..
  • Removed runAndExecJava, runAndExecJavaPure, execJava, and execJavPure because they are unnecessary.
  • Updated the example in Overview to include inner classes.
  • Added a new section Using the Java Monad to explain how to use the new combinators.

Overview

We discuss in this document how the FFI will work once implemented in GHCVM.

Checkout the Foreign.Java module (Java.hs attached to this Gist) to see the source of the functions/operators in the Haskell code.

The following sample class gives a taste of how the FFI will work.

package com.samplecompany.sample;

public class SampleClass extends SampleParent implements SampleInterface {
    /* Pretend that this class also has private, protected, and package-local methods and fields.
       Because methods with such access specifiers cannot be accessed from the outside,
       they are irrelevant in this discussion of FFI. */
    
    /* Static Methods & Fields */
    public static int d;
    public static final int e = 1;
    
    public static void impure(String s) {
        System.out.println(s):
    }
    
    public static double pure(double x) {
        return Math.sin(x);
    }
    
    /* Instance Methods & Fields */
    public int c;
    
    public SampleClass() {
        this(0):
    }
    
    public SampleClass(int c) {
        setC(c);
    }
    
    public int setC() {
        setC(0);
    }

    public int setC(int c) {
        this.c = c;
    }
    
    public int setC(int[] c) {
        setC(c[0]);
    }

    public int setC(Integer... c) {
        setC(c[0].intValue());
    }
    
    public void doubleMe() {
        setC(2 * this.c);
    }
    
    public void computeHugeTransaction() {
        /* Pretend that there's a lot of computation here,
           so that this method takes some time (say a couple seconds)
           to execute. */
    }

    public static class SampleInnerClass {
        int a = 0;
        public int getA() {return a;}
        public SampleInnerClass(int a) {
            this.a = a;
        }
        public static void yo() {
            System.out.println("yo"):
        }
    }
}

The following Haskell code imports the methods from the class above.

module Com.Samplecompany.Sample.SampleClass where

import Foreign.Java

-- Tag for use in the type parameter of JObject#
-- The # indicates that it's a tag for a primitive type constructor,
-- but it does NOT mean that it's a primitive type.
data SampleClass#

-- These synonyms are used for making it easier on the eyes
type SampleClass = JObject SampleClass#
type SampleClassM = Java SampleClass#

-- Encoding all the Java-level information for SampleClass
-- Assume SampleParent and SampleInterface are defined somewhere else
instance JClass SampleClass#
type instance JParent SampleClass# = SampleParent#
instance Extends SampleClass# SampleParent#
instance Extends SampleClass# SampleInterface#

-- Importing the static methods. Static methods are imported into a generic Java monad so that they can be used inside any Java monad.
foreign import java unsafe "com.samplecompany.sample.SampleClass impure" impure :: String -> Java a ()
foreign import java unsafe "com.samplecompany.sample.SampleClass pure" pure :: Double -> Double
foreign import java unsafe "com.samplecompany.sample.SampleClass d" getD :: Java a Int
foreign import java unsafe "com.samplecompany.sample.SampleClass d" setD :: Int -> Java a ()
foreign import java unsafe "com.samplecompany.sample.SampleClass e" e :: Int

foreign import java unsafe "c" getC :: SampleClassM Int
foreign import java unsafe "c" setC :: Int -> SampleClassM ()
foreign import java unsafe "SampleClass" new :: Java a SampleClass
foreign import java unsafe "SampleClass" new2 :: Int -> Java a SampleClass
foreign import java unsafe "setC" setDefaultC :: SampleClassM ()
foreign import java unsafe "setC" setC :: Int -> SampleClassM ()
foreign import java unsafe "setC" setArrayC :: IntArray -> SampleClassM ()

-- You can use [JInteger] or JArray JInteger
foreign import java unsafe "setC" setVarArgC :: [JInteger] -> SampleClassM ()
foreign import java unsafe doubleMe :: SampleClassM ()
foreign import java unsafe "computeWithCAndD" :: Int -> SampleClassM Int

-- The safe import will ensure execution of this function won't block the other Haskell threads,
-- but at the cost of speed in calling/returning from the function
foreign import java safe "computeHugeTransaction" computeHugeTransaction :: SampleClassM ()

-- Importing the inner class methods
-- The compiler knows that this definition is an inner class because
-- of the naming convention - take a look at the module name above
data SampleInnerClass#
type SampleInnerClass = JObject SampleInnerClass#
type SampleInnerClassM = Java SampleInnerClass#
instance JClass SampleInnerClass#
type instance JParent SampleInnerClass# = Object#

foreign import java unsafe getA :: SampleInnerClassM Int
foreign import java unsafe "SampleInnerClass" newSampleInner :: Java a SampleInnerClass
foreign import java unsafe "com.samplecompany.sample.SampleClass.SampleInnerClass yo" yo :: Java a ()

The following Haskell code uses the Java code imported above.

module SampleFFI where

import Com.Samplecompany.Sample.SampleClass as SampleClass

getC :: SampleClass -> Int
getC obj = obj .< SampleClass.getC

sumObjs :: [SampleClass] -> Int
sumObjs objs = foldl1 (+) . map getC

main : IO ()
main = do
    -- Note that the import doesn't require us to use the SampleClass. prefix,
    -- but we use it anyways. This coding convention should be used in GHCVM
    -- programs for the sake of clarity
    
    -- This sample program demonstrates the basic pattern of GHCVM programs
    -- 1.) Create and initialize your Java objects
    -- 2.) Freeze them into Haskell using the `java` function.
    -- 3.) Perform pure operations on them.
    objects <- java $ forM [1..10] $ \i -> 
        SampleClass.new i >.> doubleMe
    print $ sumObjs objects
    -- Will print 110

Design Guidelines

In this design we aim to:

  • Avoid adding unnecessary syntactic extensions to GHC Haskell's syntax. (Template Haskell should be used if conciseness is desired.)
  • Use existing mechanisms of abstraction when possible.
  • Define only the minimal number of new primitives to accomplish the task.

Pre-requisites for the FFI

The new types introduced for the Java FFI are as follows:

  • the JObject# c primitive: Just as the state of the external world is represented by State# s, the internal state of a Java object is represented by JObject# c. The c type variable should be instantiated by a tag object (typically a type with no value). A very important feature of this type is that it will never have the value null. If you want to represent a type which can take a null value, use Maybe.
  • the JArray# c primitive: Represents c[] array type. So for an array of ints, JObject# (JArray# c).
  • the *Array# primitives: For all the primitive array types.
  • the JObject c type: Wraps an JObject# c just like an Int wraps an Int#.
  • the Java monad: All the instance methods must execute in this monad, which stores the this object. You can think of this as the IO monad augmented with an object's internal state. Static methods will not use the this reference stored in the monad when executing inside the monad.

Using the FFI

foreign import [safety] [java-calling-convention] [java-name] [haskell-name] :: [arg1] -> .. -> [argN] -> [res]
  1. safety should be either
  • unsafe: Same as calling a Java method in Java with the only overhead being unwrapping of Haskell types. Should be used for small and fast executing Java methods.
  • safe: Has the overhead of saving and loading the Haskell RTS Context. Should be used if the target Java method calls into the Haskell RTS or the method will execute for a long time.
  1. java-calling-convention should be either
  • java: In this calling convention, the corresponding method call is made by wrapping/unwrapping Haskell types and Java objects as necessary.
  • easyjava: Same as java with the typeclasses FromJava, ToJava, and Extends used so that the Haskell function implementing the Java method is easy to call without lots of data type conversion/casting Java objects to be seen in Haskell code. See footnote [1].
  1. java-name is optional when the target class/method can be inferred from the haskell-name and the haskell-type. If present, it can either be "[qualified-class-name] [method-name]" or just "[method-name]" if the class can be inferred from context (if the result type is a Java monad). You can also put field names in place of method names when referencing fields.

  2. haskell-name is what you want to the method to be named in Haskell.

  3. argi These are the argument types. All of these must be primitive wrappers like Int, Double, JObject c, and so on. All the FFI will do is unwrap the arguments to primitive types to send off to the native Java call. If you want to send null to an argument, make sure you define the argument type as Maybe (JObject c).

  4. res This is the result type. It can be a primitive wrapper of a Java type or the IO monad parametrized by said type or the Java monad parametrized by the tag object and a Java primitive wrapper. If a Java object is expected as a return value and there is a chance of that object being null, make sure the primitive wrapper is wrapped with a Maybe.

Using the Java Monad

The Java monad defined in Java.hs is the key to effective use of the Java FFI in GHCVM. It defines some key combinators that can be used for almost any situation:

  • Java Monad to IO
  • a .> b: Runs the Java action b on the Java object a and executes it in the IO monad.
  • a .< b: Runs the Java action b on the Java object a and executes it purely. (Warning: This is unsafe and should only be used for objects that don't get modified very much and should only be used for methods that perform pure computations.)
  • Java Monad Combinators
  • a <.> b: Creates a new Java action such that Java action b is applied to the pure Java object a and merged with the current monadic context - this means that b will be run using a as the this reference.
  • a >. b: Creates a new Java action such that Java action b produces a Java object and runs the Java action b on it and returns the result.
  • a >.> b: Creates a new Java action such that Java action b produces a Java object and runs the Java action b on it and returns the object produced.

FFI Generation Utilities

Looking at the examples, it seems as though most of the FFI bindings can be generated by looking at a class file directly. Other than the core Java APIs that are in the JDK, or common Java frameworks, it is not common to use many of the API methods defined by a given library, so manual foreign imports are better in that one imports only those methods that one actually uses.

I imagine that small FFI helper libraries are written that simplify the process using Template Haskell by letting you specify which methods to import. An example is shown below:

-- The call below will automatically generate the bindings for add and addAll by directly mapping the Java method signature to a Haskell function type.
-- importJava :: String -> [String] -> Q Exp 
-- This function will find the given class in the classpath, parse it, and read the method/field signatures.
-- Due to the stage restriction, you should import all the required methods in a separate Haskell module,
-- and import that module as required throughout your application.
importJava "java.util.ArrayList" ["add", "addAll"]
-- OR a custom quasiquoter for readability
[import| java.util.ArrayList (add, addAll) |]

This TH function could be extended to support purity specifications, nullity, etc.

Because Template Haskell probably won't be available for some time, an external or internal utility can be implemented which take files that describe which methods need to be imported and automatically reads the class files and generates the natural FFI import. This can be integrated into an IDE to provide nice code completion of Java methods inside of Haskell code.

Single-Method Interfaces

In Java 8, lambdas can be used in place of defining a new interface implementation when passing in arguments implementing a single-method interface. A similar mechanism could exist in Haskell where you can send in a Haskell function with the same signature as the single-method. This would essentially be an extension to the foreign export where you can export a Haskell function (with appropriate type) directly to be an inteface implementation.

Example:

public class Main {
    public static int test(SingleMethodInterface smi) {
        return smi.singleMethod(1, 1.0);
    }
}

public static interface SingleMethodInterface {
    int singleMethod(int a, double b);
}
sumImp :: Int -> Double -> Int
sumImp i d = i + truncate d 

foreign export java "wrapper" newSMI :: (Int -> Double -> Int) -> Java a SingleMethodInterface

foreign import java "Main test" test :: SingleMethodInterface -> Java a Int

main = do
    result <- java $ do
        smi <- newSMI sumImp
        return $ test smi
    print result

While this is the way to define interfaces without any extensions, it could help if the compiler could go further and directly accept Haskell functions for SMIs without going through the "wrapper" export. This can be done in the future.

Foreign Exports

The natural way is to export a static method which calls into the RTS, similar to how it is done in GHC.

An example of a static export:

The Haskell file that does the export

module Hello.Java where

double :: Int -> Int
double x = 2 * x

foreign export java double :: Int -> Int
-- This will be exported as the static method of class hello.Java,
-- the class which is generated by GHCVM when compiling this module.

The Java class that is generated

package hello;

public class Java {

    public static int double(int x) {
        /* Code to initialize RTS, 
           convert x to Haskell type Int,
           call the Haskell double function in the RTS context,
           convert the Haskell-typed result to a Java type and return. */
    }

    /* Other code generated by GHCVM for the Hello.Java module here... */
}

Now we discuss subclassing an existing Java class within Haskell. Given the development of foreign import's so far, the natural way of doing it would be to set the return type of the export to the Java monad, and having the FFI take that as a signal to export a instance method that calls into the RTS into the appropriate class.

An example of an instance export:

NOTE: Our example will be extending the Activity class in the Android API.

The following file demonstrates writing Java code inside of Haskell.

import Android.App.Activity
import Android.View.View
import Android.Snackbar as Snackbar

{- 
Assume that in Android.App.Activity, the following imports are defined:

type ResourceId = Int

onCreate :: (Extends c Activity#) => Bundle -> Java c ()
setContentView :: (Extends c Activity#) => ResourceId -> Java c ()
findViewById :: (Extends c Activity#, Extends d View#) => ResourceId -> Java c (JObject d)
setActionBar :: (Extends c Activity#, Extends d View#) => JObject d -> Java c ()

Assume that in Android.View.View, the following imports are defined:

setOnClickListener :: (Extends c View#, Extends d OnClickListener#) => JObject d -> Java c ()

Assume that in Android.Snackbar, the following imports are defined:

make :: Extends c View# => JObject c -> String -> Int -> Java a Snackbar
setAction :: (Extends c Snackbar#, Extends d OnClickListener#) => String -> Maybe (JObject d) -> Java c Snackbar
show :: Extends c Snackbar# => Java c ()
lENGTH_LONG :: Int

And assume that all the Android API classes have been imported as well.
-} 

{-# ANN type MyActivity# "mypackage.MyActivity" #-}
data MyActivity#
type MyActivity = JObject MyActivity#

type instance JParent MyActivity# = Activity#

clickListener :: View -> Java a ()
clickListener view =
    Snackbar.make view "Some action" Snackbar.lENGTH_LONG
        >. setAction "Action" Nothing
        >. Snackbar.show
    
foreign export java "wrapper" newOnClick :: (View -> Java a ()) -> Java a OnClickListener

onCreate' :: Bundle -> Java MyActivity# ()
onCreate' savedInstanceState = do
    onCreate savedInstanceState
    -- This corresponds to R.layout.myactivity
    -- Assume that GHCVM support for Android will include utilities 
    -- to automate the generation of bindings to layout/vew ids
    setContentView r_layout_myactivity
    (toolbar :: Toolbar) <- findViewById r_id_toolbar 
    setActionBar toolbar
    (button :: Button) <- findViewById r_id_button
    listener <- newOnClick clickListener
    button <.> setOnClickListener listener

foreign export java "onCreate" onCreate' :: Bundle -> Java MyActivity# ()

NOTE: Since you can't add methods to existing classes, a foreign export with a Java monad return type signals to the compiler that you wish to generate a new class. Static exports obviate the need for defining static methods, so they are not supported (and not really needed anyways). I'm not aware of any Java framework that forces you to define any particular static methods to work. If so, please inform me.

While there is a wee bit of redundancy, it avoids unnecessary new syntatic additions to GHC Haskell. As mentioned before, Template Haskell can be use to remove the redundancy.

The following file shows the semantically equivalent Java file if it was hand-written.

package mypackage;

/* Assume required imports are present. */

public class MyActivity extends Activity {
    
    /* NOTE: Semantically, the following method definition will execute,
             but you have to imagine that the initialization/finalization of the Haskell RTS
             is going on before and after the method call. */
    @Override
    public void onCreate(Bundle savedInstanceState) {
        super.onCreate(savedInstanceState);
        setContentView(R.layout.myactivity);
        Toolbar toolbar = (Toolbar) findViewById(R.id.toolbar);
        setActionBar(toolbar);
        Button button = (Button) findViewById(R.id.button);
        button.setOnClickListener(new View.OnClickListener() {
            @Override
            public void onClick(View view) {
                Snackbar.make(view, "Some action", Snackbar.LENGTH_LONG)
                        .setAction("Action", null)
                        .show();
            }
        });
    }
}

The problem with calling into the GHC RTS over and over again is that it is a tad heavyweight. It is interesting to consider the possibility of giving the option of exporting functions into a lightweight RTS so that the overhead is low for platforms like Android. An alternative is to export strictly rather than lazily (see GHC 8.0's Strict extension).

A lightweight RTS should be investigated if one would want to use foreign export's in production applications on platforms that are resource-limited, like Android.

Java Generics

If no support for Java generics was given in GHCVM, one would have to do all the cumbersome typecasts in order to achieve the same functionality. Thus, it makes sense to support generics in the FFI and allow the code generator to handle all the casting.

Importing into Haskell

This java class declaration

class SomeGenericClass<W, X super A, Y extends B & C> {
    public X a;
    public <Z super D> X someGenericMethod(Z a) {...}
    public static <U> void someStaticGenericMethod(U a) {..}
}

can be imported as follows:

-- A GADT declaration is used to represent the type bounds.
-- DatatypeContexts are not supported to discourage their use.
-- The data constructor can have any name since it's not going to be
-- used anywhere.
data SomeGenericClass# w x y where
    SomeGenericClass_ :: (Extends A# x, Extends y B#, Extends y C#)
                      => SomeGenericClass w x y
type SomeGenericClass w x y = JObject (SomeGenericClass# w x y)
           
foreign import java unsafe someGenericMethod :: 
    (Extends D# z) => JObject z -> Java (SomeGenericClass w x y) (JObject x)
foreign import java unsafe "SomeGenericClass someStaticGenericMethod" ::
    JObject u -> Java a ()
    

The desugaring of the generic foreign imports will ensure that appropriate casts are inserted wherever necessary. In fact, the qualified class name which is associated with the annotation of the tagged object type will be used during code generation.

Exporting to Java

There is no reason to generate generic classes within Haskell (prompt me if there is), but there can be cases where subclassing generic classes instantiated to a certain type is required. The method will be similar to what was described in the Foreign Exports section, with the extensions above.

When generating code for a class, bridge methods must be taken into account.

Conclusion

Implementing this is a bit tricky from the codegen side since we have to implement Java's type erasure and that means generating the appropriate casts at the call site. This feature may be deferred post the first release since implementation would probably take some time.

Putting It All Together: JavaFX Example

The following example is adapted from Frege:

module Main where

import JavaFX
import JavaFX.Types.Group as Group
import JavaFX.Types.Scene as Scene
import JavaFX.Types.VBox as VBox
import JavaFX.Types.Button as Button
import JavaFX.Types.Insets as Insets

{- Assume that all relevant JavaFX classes/interfaces have been imported 
appropriately and that the following functions have been foreign-imported
with the given signatures.

-- javafx.application.Application
launch :: JClass c => Class c -> [JString] -> Java a ()

-- javafx.stage.Stage
show :: Extends c Stage# => Java c ()

-- javafx.scene.Parent
getChildren :: Extends c Parent# => Java c (ObservableList Node#)

-- javafx.scene.control.ButtonBase
setOnAction :: Extends c ButtonBase# => EventHandler ActionEvent# -> Java c ()

-- java.util.List
add :: Extends c (List# e) => JObject e -> Java c ()

-- Utility functions
addNode :: (Extends c Parent#, Extends b Node#) => Java c (JObject b) -> Java c ()
addNode builder = do
    node <- builder
    children <- getChildren
    children <.> add node

withStage :: (Group -> Stage -> Java a Group) -> Stage -> Java a ()
withStage populate stage = do
    content <- Group.new
    scene <- Scene.new content
    stage <.> setScene scene
    populate content stage
    stage <.> show

action_ :: (Extends c ButtonBase#) => Java a () -> Java c ()
action_ jaction = do
    handler <- newEventHandler (\(_ :: ActionEvent) -> jaction)
    setOnAction handler

actionIO_ :: (Extends c ButtonBase#) => IO () -> Java c ()
actionIO_ ioAction = do
    handler <- newEventHandler (\(_ :: ActionEvent) -> ioToJava ioAction)
    setOnAction handler
    
foreign import java "wrapper" newEventHandler :: (JObject t -> Java (EventHandler# t) ()) -> Java a (EventHandler t)
-}

-- This will be defined in the GHCVM Prelude, but defined here to
-- demonstrate string conversions. The actual implementation will 
-- probably have better support from the runtime system to avoids
-- the unnecessary Haskell-Java conversions.
getJavaArgs :: Java a [JString]
getJavaArgs = do
    args <- ioToJava getArgs
    jargs <- mapM toJString jargs
    return $ newJArrayWith jargs

main :: IO ()
main = java $ do
    args <- getJavaArgs
    launch (class# MainApplication#) args
 
data MainApplication#
type instance JParent MainApplication# = Application#

start :: Stage -> Java MainApplication# ()
start = withStage buildUI

buildUI :: Group -> Stage -> Java a Group
buildUI root stage = do
    stage <.> setTitle "GHCVM Hello World"
    root <.> addNode $ 
        VBox.new 5.0 >.> do
            setPadding $ Insets.new 10 10 10 10
            addNode $ Button.new "Please click me for Java action"
                   >.> withThis $ \this -> action_ $ this <.> setText "Thanks!"
            addNode $ Button.new "Print current thread to console"
                   >.> actionIO_ $ myThreadId >>= print
            addNode $ Button.new "Combining IO and Java actions"
                   >.> withThis $ \this ->
                         actionIO_ $ do
                             thread <- myThreadId
                             this .> setText $ show thread
            addNode $ Button.new "Async example"
                   >.> actionIO_ $ forkIO $ print "printed outside UI thread"
            addNode $ Button.new "Async plus wait for completion"
                   >.> actionIO_ $ do
                           var <- newEmptyMVar
                           forkIO $
                               putStrLn "printed outside UI thread"
                               putMVar var "Done"
                           takeMVar var
                           putStrLn "Completed, proceed in UI thread"
            mapM addNode . map (Button.new . ("Button " ++) . show) [1..5]

foreign export java start :: Stage -> Java MainApplication# ()

Suggestions

I'm looking forward to suggestions and feedback, like:

  • Improvement of the core Foreign.Java API
  • Better naming of functions, operators, types, and typeclasses
  • Feature requests for effective interoperation with commonly used Java frameworks (Java EE, Spring, etc.)
  • Alternative implementations

Conclusion

The first release of GHCVM will have support for most of the features mentioned above.

Template Haskell will only be supported in the second release or beyond because it requires the implementation of GHCVMi, so a FFI generator will either be implemented inside the compiler itself or as an external tool.

Appendix: Internal details

Motivation

A Java object consists of state (a set of fields) and operations on the object (a set of methods) that modify the state and potentially perform side effects. Thinking about a Java object in terms of Haskell, an object can be very naturally represented by a StateT $ObjectRep IO monad where $ObjectRep can be the set of fields of the object. Methods on the object can be thought of as state monadic actions where the monad threads the this pointer through as actions are combined.

We already have a representation of the state of the external world, namely State# RealWorld, and now we need a representation of the internal state of a Java object. While we could keep track of the fields of the object as part of a Haskell ADT as the state, it becomes very cumbersome and it's also very inefficient always maintaining a Haskell ADT in parallel to every object. So we opt for creating a new primitive JObject# s where s is a type variable which should be instantiated to a tag type. Just like an raw integer value backs an Int# value in GHC, a raw object of class represented by s will back an JObject# s value.

Implementation

The only extension we make to GHC is adding a new primitive JObject# s along with any necessary primitive operations like cast# :: JObject# a -> JObject# b. Note that s is a normal Haskell type that represents a Java class with a no-data-constructor type definition. That type must have a GHC annotation if the module naming/type naming convention for foreign imports is not followed (shown in FFI examples). The JObject# s type will be backed by a native java reference and allows for easy manipulation of Java objects in Haskell while being fairly fast.

The rest of the implementation is all in the pure Haskell Foriegn.Java module and overriding the dsForeignsHook, tcForeignImportsHook, and tcForeignExportsHook hooks in the GHC API which tell the compiler how to handle the foreign import & export declarations.

Footnotes

[1] Not too sure if it's worth implementing this - if people find it would be nice, I'll add it in. Maybe this can be implemented as a Template Haskell layer instead of the FFI syntax?

Example:

foreign import unsafe easyjava "com.someclass.SomeClass someMethod" someMethod :: Int -> JObject SomeOtherClass# -> JObject SomeOtherInterface# -> Java SomeClass# ()
-- The above will get desugared to:
someMethod :: (ToJava a Int, Extends b SomeOtherClass#, Extends c SomeOtherInterface#, Extends d SomeClass#)
           => a
           -> JObject b
           -> JObject c
           -> Java d ()
module Foreign.Java where
-- This is used to wrap primitive Java objects.
-- This can be thought of as the parallel between Int and Int#
data JObject a = JObject (JObject# a)
-- The tag for java.lang.Object
{-# ANN type Object# "java.lang.Object" #-}
data Object# -- the Object# type constructor is already defined
type Object = JObject Object#
foreign import java unsafe "Object" newObject :: IO Object
-- Every Java class and interface must be an instance of JClass
class JClass a where
class JClass b => JInterface b where
-- Returns the direct superclass of the given class
type family JParent (c :: *) :: *
-- Class 'a' transitively extends Class 'b' where
-- 'extends' can mean subclassing or implementing an interface
class (JClass a, JClass b) => Extends a b where
-- Properties of Java inheritance
instance (JClass a) => Extends a Object# -- Unique Common Ancestor
instance (JClass a) => Extends a a -- Reflexivity
instance (Extends a b, Extends b c) => Extends a c -- Transitivity
-- This typeclass is used to convert Haskell types to Java types
class ToJava a b where
toJava :: a -> b
-- This typeclass is used to bring Java objects into Haskell world
class FromJava a b where
fromJava :: a -> b
-- Java array operations
class IsJArray a where
type family JArrayElem (a :: *) :: *
newJArray :: Int -> IO (JObject a)
(.!) :: Int -> Java a (JArrayElem a)
(.!=) :: Int -> JArrayElem a -> Java a ()
-- Wrapper for the primitive operation that compiles to the arraylength
-- JVM bytecode.
alength :: IsJArray a => JObject a -> Java a Int
-- Utility function to quickly convert Haskell lists to Java arrays
newJArrayWith :: IsJArray a => [JArrayElem a] -> IO (JObject a)
-- All of the following instances are wrappers around primitive operations that
-- compile directly to the *aload & *astore JVM bytecodes. The definitions
-- have been omitted for simplicity, but the they are straightforward
-- once the primitive operations are defined.
type JArray a = JObject (JArray# a)
instance (JClass c) => IsArray (Array# c) where
type instance JArrayElem (JArray# a) = JObject a
data BooleanArray#
type BooleanArray = JObject BooleanArray#
instance IsArray BooleanArray# where
type instance JArrayElem BooleanArray# = Boolean
data ByteArray#
type ByteArray = JObject ByteArray#
instance IsArray ByteArray# where
type instance JArrayElem ByteArray# = Byte
data CharArray#
type CharArray = JObject CharArray#
instance IsArray CharArray# where
type instance JArrayElem CharArray# = JChar
data ShortArray#
type ShortArray = JObject ShortArray#
instance IsArray ShortArray# where
type instance JArrayElem ShortArray# = Short
data IntArray#
type IntArray = JObject IntArray#
instance IsArray IntArray# where
type instance JArrayElem IntArray# = Int
data LongArray#
type LongArray = JObject LongArray#
instance IsArray LongArray# where
type instance JArrayElem LongArray# = Long
data FloatArray#
type FloatArray = JObject FloatArray#
instance IsArray FloatArray# where
type instance JArrayElem FloatArray# = Float
data DoubleArray#
type DoubleArray = JObject DoubleArray#
instance IsArray DoubleArray# where
type instance JArrayElem DoubleArray# = Double
-- java.lang.String
{-# ANN type String# "java.lang.String" #-}
data String#
-- We distinguish between the lazy Haskell String and the immutable Java String
type JString = JObject String#
-- Some primitive operation is used to efficiently translate between the two.
toJString :: String -> Java a JString
-- The Java Monad
newtype Java c a = Java { runJava_ :: State# RealWorld -> JObject# c -> (# State# RealWorld, JObject# c, a #) }
instance JClass c => Monad (Java c) where
return x = Java $ \s o -> (# s, o, x #)
jaction >>= f = Java $ \s o ->
let (# s', o', x #) = runJava_ jaction s o
in runJava_ (f x) s' o'
-- Intended for use when a result is desired
runJava :: JClass c => JObject c -> Java c a -> IO a
runJava (JObject obj) jaction = IO $ \s ->
let (# s', o', x #) = runJava_ jaction s obj
in (# s', x #)
-- WARNING: Do not use this if the underlying object is frequently modified.
runJavaPure :: JClass c => JObject c -> Java c a -> a
runJavaPure jobj = unsafePerformIO . runJava jobj
-- Intended for initialization of Java objects
initJava :: JClass c => Java a (JObject c) -> Java c b -> Java a b
initJava genaction jaction = do
jobj <- genaction
jobj <.> jaction
initJavaObj :: JClass c => Java a (JObject c) -> Java c b -> Java a (JObject c)
initJavaObj genaction jaction = do
jobj <- genaction
jobj <.> jaction
return jobj
globalObject :: Object
globalObject = unsafePerformIO . newObject
java :: JClass c => Java Object# a -> IO a
java = runJava globalObject
-- It's better to avoid this when possible as you are interleaving Haskell
-- actions inside the Java monad
ioToJava :: IO a -> Java c a
ioToJava (IO action) = Java $ \s o ->
let (# s', x #) = action s
in (# s', o, x#)
-- Assume both of these are implemented by primitive operations
safeCast :: Extends c d => JObject c -> JObject d
unsafeCast :: JObject c -> JObject d
super :: Extends c d => Java d a -> Java c a
super superJAction = Java $ \s o ->
let (# s', o', x #) = runJava_ superJAction s (cast# o :: JObject# d)
in (# s', o, x #)
with :: (JClass c, JClass d) => JObject d -> Java d a -> Java c a
with (JObject obj) jaction = Java $ \s o ->
let (# s', o', x #) = runJava_ jaction s obj
in (# s', o, x #)
withThis :: (JClass c) => (JObject c -> Java c a) -> Java c a
withThis thisAction = Java $ \s o ->
let jobj = JObject o
in thisAction jobj s o
-- Class literals
-- Will be implemented as a primitive operation
class# :: JClass c => c -> Class c
-- Some operators to make the code nicer to read
infixl 0 .>
(.>) = runJava
infixl 0 .<
(.<) = runJavaPure
infix 0 <.>
(<.>) = with
infixl 0 >.
(>.) = initJava
infixl 0 >.>
(>.>) = initJavaObj
@alexanderkjeldaas
Copy link

Could you add an inner class to SampleClass?

@rahulmutt
Copy link
Author

rahulmutt commented May 31, 2016

@alexanderkjeldaas Updated as per request :)

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment