Portability | non-portable (see LANGUAGE pragma) |
---|---|
Stability | provisional |
Maintainer | julian.fleischer@fu-berlin.de |
Safe Haskell | None |
This module contains the medium level interface to the Java Bridge.
See Foreign.Java.JNI.Safe and Foreign.Java.JNI.Unsafe for the low level interface which is a plain translation of the Java Native Interface. Information about the library can be retrieved using Foreign.Java.JNI.
High level bindings can be generated using Foreign.Java.Bindings.
- data Java a
- runJava :: Java a -> IO a
- runJava' :: [String] -> Java a -> IO a
- initJava :: [String] -> IO ()
- setUnsafe :: MonadState JVMState m => Bool -> m ()
- runJavaGui :: Java a -> IO ()
- runJavaGui' :: [String] -> Java a -> IO ()
- getClass :: String -> Java (Maybe JClass)
- getConstructor :: (Monad m, Constructor (a -> String)) => JClass -> a -> Java (m (JConstructor a))
- newObject :: JClass -> Java (Maybe JObject)
- newObjectE :: JClass -> Java (Either JThrowable (Maybe JObject))
- newObjectX :: JClass -> Java (Maybe JObject)
- newObjectFrom :: NewObject p b => JConstructor p -> b
- newObjectFromE :: NewObjectE p b => JConstructor p -> b
- newObjectFromX :: NewObjectX p b => JConstructor p -> b
- getMethod :: Method (p -> String) => JClass -> MethodDescriptor p -> Java (Maybe (JMethod p))
- getStaticMethod :: Method (p -> String) => JClass -> MethodDescriptor p -> Java (Maybe (JStaticMethod p))
- bindMethod :: (Method (p -> String), MethodCall p b) => JClass -> MethodDescriptor p -> Java (JObject -> b)
- bindStaticMethod :: (Method (p -> String), StaticCall p b) => JClass -> MethodDescriptor p -> Java b
- callMethod :: MethodCall p b => JMethod p -> JObject -> b
- callMethodE :: MethodCallE p b => JMethod p -> JObject -> b
- callMethodX :: MethodCallX p b => JMethod p -> JObject -> b
- callStaticMethod :: StaticCall p b => JStaticMethod p -> b
- callStaticMethodE :: StaticCallE p b => JStaticMethod p -> b
- callStaticMethodX :: StaticCallX p b => JStaticMethod p -> b
- getField :: Param a => JClass -> String -> a -> Java (Maybe (JField a))
- getStaticField :: Param a => JClass -> String -> a -> Java (Maybe (JStaticField a))
- readField :: Field a b => JField a -> JObject -> Java b
- readStaticField :: Field a b => JStaticField a -> Java b
- writeField :: Field a b => JField a -> JObject -> b -> Java ()
- writeStaticField :: Field a b => JStaticField a -> b -> Java ()
- arrayLength :: JArray e -> Java Int32
- class JavaArray e a | e -> a where
- class JavaObject a where
- isInstanceOf :: JObject -> JClass -> Java Bool
- io :: IO a -> Java a
- module Foreign.Java.Value
- liftIO :: MonadIO m => forall a. IO a -> m a
- forkJava :: Java a -> Java (JavaThreadId a)
- waitJava :: JavaThreadId a -> Java (Either SomeException a)
- data JVM
- data JClass
- data JObject
- data JArray e
- data JField a
- data JStaticField a
- data JMethod a
- data JStaticMethod a
- data JConstructor a
- data JThrowable
- data JavaThreadId a
- data MethodDescriptor p = String ::= p
- (-->) :: a -> x -> P a x
- void :: V
- boolean :: Z
- char :: C
- byte :: B
- short :: S
- int :: I
- long :: J
- float :: F
- double :: D
- object :: String -> L
- string :: X
- array :: x -> A x
Medium Level Java Interface
The medium level interface tries to take all the pain from the JNI. It automatically manages references (i.e. garbage collection) for you and makes sure that all operations take place in the presence of a virtual machine.
This module contains the Java
monad which basically wraps the IO
monad but allows for actions to be executed in a virtual machine.
Such actions on the other hand can only be executed within the Java
monad and not within the IO monad. See runJava
, runJavaGUI
, and
initJava
for information on how to run a computation in the JVM.
Using the medium level interface you will need to obtain references to classes and methods manually. You can avoid this by creating high level bindings (effectively some glue code) via Foreign.Java.Bindings.
Obtaining Class and Method References
In order to invoke methods in the virtual machine you first need a
reference of these methods. These can be retrieved via
getMethod
, getStaticMethod
, bindMethod
, and
bindStaticMethod
. References to constructors can be obtained using
getConstructor
. All of these functions require a class.
getClass
will lookup and load Java classes.
Here is an example for calling Thread.currentThread().getName()
and printing the result.
import Foreign.Java main = runJava $ do (Just threadClass) <- getClass "java.lang.Thread" currentThread <- threadClass `bindStaticMethod` "currentThread" ::= object "java.lang.Thread" getName <- threadClass `bindMethod` "getName" ::= string (Just thread) <- currentThread (Just name) <- getName thread io$ putStrLn name
NOTE: The boilerplate of retrieving class and method references can be avoided by using the high level java bindings offered by Foreign.Java.Bindings.
Calling Methods
All the functions that involve calling a method (callMethod
,
callStaticMethod
, and newObject
) come in three versions: E, X,
and with no suffix.
The X functions will not check for exceptions. Use them if your absolutely sure that you are calling a total function.
The E functions will check for exceptions and return a value of type
Either JThrowable a
. A Left value is returned iff an exception
occured (carrying the exception thrown) whereas a Right value
carries the result of the function. Note that such a correct result
may be Nothing (which resembles the null
reference) or void
(i.e. unit: ()
).
The functions without any suffix will check for exceptions and throw a Haskell exception. Throwing that exception will cause the computation in the JVM to be cancelled. This means that it is not possible to catch the exception within the Java monad, as the computation will be cancelled already. You can however catch such exceptions in the IO monad.
In general you should use E functions if a method throws any checked exceptions and a function without suffix if a method does not throw any checked exceptions. This way runtime exceptions will still be propagated. If you know by heart that a function can not throw any exceptions, neither checked nor unchecked exceptions, you can use an X method, which is faster as it does not check for exceptions at all. If however the method does throw an exception and you do not check it, you are entering a world of pain.
Reference
The Java Monad
Every computation in the Java Virtual Machine happens inside the Java monad. The Java monad is mightier than the IO monad, i.e. IO operations can be performed in both the IO monad as well as in the Java monad, but Java operations can be performed in the Java monad only and not in the IO monad.
Use one of runJava
or runJava'
to perform operations in the
Java monad.
runJava' :: [String] -> Java a -> IO aSource
Run a computation with support by a Java Virtual Machine, initialized with the given parameters.
This function may be used only once. If you intend to call it multiple times, you need to initialize the Java subsystem once before. If you fail to do so, this function will tear down the virtual machine once it is done.
By using initJava
the virtual machine will be alive during
the whole lifetime of your process and runJava'
will never
tear down the machine.
NOTE: According to the Java Native Interface specification it may be possible to create multiple virtual machines within a single process. However, no implementation of the JNI seems to be capable of doing so.
This function can be used to set for example the classpath of the virtual machine:
runJava' ["-Djava.class.path=java-library-dir"] $ do doSomething
NOTE: java.class.path does support relative paths.
initJava :: [String] -> IO ()Source
Initializes the Java Virtual Machine so that it can
be used by subsequent invocations of runJava
. Note that
once you start the virtual machine it will be runing throughout
the whole lifetime of the main thread of your application.
setUnsafe :: MonadState JVMState m => Bool -> m ()Source
By default java methods are invoked via the FFI using safe calls. Safe calls are slower than unsafe calls. This function controls whether safe or unsafe calls are being used to communicate with the JVM.
If your application does not invoke the JVM concurrently it is mostly safe to use unsafe calls.
runJava (setUnsafe True >> doSomething)
will perform doSomething
using unsafe calls.
runJavaGui :: Java a -> IO ()Source
Short hand for runJavaGui' []
.
runJavaGui' :: [String] -> Java a -> IO ()Source
Mac OS X needs some special treatment for initializing graphical applications, namely a Cocoa Runloop needs to be present on the main thread. Since the main thread is the application that the JVM was invoked from this has two consequences: (1) A runloop needs to be created on the main thread manually and (2) the main thread is not usable for your application.
On Mac OS X this function will fork an os thread using forkJava
and start the Cocoa main event loop. This means that this function
must be called on the main thread and that it will never terminate
(since the cocoa event queue will be running there forever).
Note that this implies that you link your application with the threaded runtime (`-threaded` in GHC).
Typically your application should look like this:
main = runJavaGui $ do stuffYourApplicationDoes
On all other platforms this is exactly the same as runJava'
(minus the fact that it returns ()
).
Classes and Objects
:: String | The name of the class. This should be a name
as would be returned by the |
-> Java (Maybe JClass) | Returns Just the JClass or Nothing, if the class does not exist. |
Finds and loads a class.
Note that this function can indeed fail with an exception and may execute code from the class to be loaded inside the virtual machine.
This is due to the fact that getClass
is a translation of the
findClass
function in the JNI which loads *and* resolves the class.
If you want to get a class definition without resolving the class,
use the method loadClass(String,boolean)
on a ClassLoader
.
Here is an example of how to do that:
main' = runJava $ do (Just classLoader) <- getClass "java.lang.ClassLoader" getSystemClassLoader <- classLoader `bindStaticMethod` "getSystemClassLoader" ::= object "java.lang.ClassLoader" (Just systemClassLoader) <- getSystemClassLoader loadClass <- classLoader `bindMethod` "loadClass" ::= string --> boolean --> object "java.lang.Class" (Just clazz) <- loadClass systemClassLoader "java.awt.EventQueue" False io$ print clazz
getConstructor :: (Monad m, Constructor (a -> String)) => JClass -> a -> Java (m (JConstructor a))Source
Object creation
newObjectE :: JClass -> Java (Either JThrowable (Maybe JObject))Source
newObjectFrom :: NewObject p b => JConstructor p -> bSource
newObjectFromE :: NewObjectE p b => JConstructor p -> bSource
newObjectFromX :: NewObjectX p b => JConstructor p -> bSource
Methods
getStaticMethod :: Method (p -> String) => JClass -> MethodDescriptor p -> Java (Maybe (JStaticMethod p))Source
bindMethod :: (Method (p -> String), MethodCall p b) => JClass -> MethodDescriptor p -> Java (JObject -> b)Source
bindStaticMethod :: (Method (p -> String), StaticCall p b) => JClass -> MethodDescriptor p -> Java bSource
Method invocation
callMethod :: MethodCall p b => JMethod p -> JObject -> bSource
callMethodE :: MethodCallE p b => JMethod p -> JObject -> bSource
callMethodX :: MethodCallX p b => JMethod p -> JObject -> bSource
callStaticMethod :: StaticCall p b => JStaticMethod p -> bSource
callStaticMethodE :: StaticCallE p b => JStaticMethod p -> bSource
callStaticMethodX :: StaticCallX p b => JStaticMethod p -> bSource
Fields
getStaticField :: Param a => JClass -> String -> a -> Java (Maybe (JStaticField a))Source
readStaticField :: Field a b => JStaticField a -> Java bSource
writeField :: Field a b => JField a -> JObject -> b -> Java ()Source
writeStaticField :: Field a b => JStaticField a -> b -> Java ()Source
Arrays
arrayLength :: JArray e -> Java Int32Source
Return the length of an JArray.
Objects
class JavaObject a whereSource
Provides basic functions that every Java Object supports.
There are instances for JObject
, JClass
, JThrowable
,
and JArray
(which are all references to objects in the
virtual machine).
Minimal complete definition: asObject
.
toString :: a -> Java StringSource
Invokes the toString
method which every Java Object has.
hashCode :: a -> Java Int32Source
Invokes the hashCode
method which every Java Object has.
asObject :: a -> Java JObjectSource
Turns the reference into a JObject. This can be used to down-cast any reference to an Object inside the JVM to a JObject.
classOf :: a -> Java JClassSource
Returns a reference to the Class of the given object.
equals :: JavaObject b => a -> b -> Java BoolSource
Checks two objects for equality using their equals
methods.
JavaObject JThrowable | Every JThrowable is a JavaObject. |
JavaObject JClass | Every JClass is a JavaObject. |
JavaObject JObject | |
JavaObject a => JavaObject (Maybe a) |
isInstanceOf :: JObject -> JClass -> Java BoolSource
Check whether the given object is an instance of the given class.
Utilities
Re-exported for convenience when dealing with high-level bindings.
module Foreign.Java.Value
Interaction with IO
forkJava :: Java a -> Java (JavaThreadId a)Source
A utility function for forking an OS thread which runs in the
Java Monad. It will return a JavaThreadId
which you can wait on
using waitJava
.
waitJava :: JavaThreadId a -> Java (Either SomeException a)Source
Wait for a Java Thread to exit. If the thread exits abnormally
(that is, if an exception occurred), this function will return
Left SomeException
. Otherwise it will return the result of the
computation as Right a
.
JVM data
A reference to a Class object.
Show JClass | |
JavaObject JClass | Every JClass is a JavaObject. |
data JStaticField a Source
Show (JStaticField a) |
data JStaticMethod a Source
Show a => Show (JStaticMethod a) |
data JConstructor a Source
Show a => Show (JConstructor a) |
data JThrowable Source
A reference to an Exception.
Show JThrowable | |
JavaObject JThrowable | Every JThrowable is a JavaObject. |
VoidResult (Maybe JThrowable) | |
UnsafeCast a => ObjectResult (Either (Maybe JThrowable) a) | |
UnsafeCast a => ObjectResult (Either JThrowable (Maybe a)) | |
UnsafeCast a => ObjectResult (Value JThrowable a) | |
ArrayResult a => ArrayResult (Either JThrowable a) | |
VoidResult (Either JThrowable ()) | |
DoubleResult (Either JThrowable Double) | |
FloatResult (Either JThrowable Float) | |
LongResult (Either JThrowable Int64) | |
IntResult (Either JThrowable Int32) | |
ShortResult (Either JThrowable Int16) | |
ByteResult (Either JThrowable Int8) | |
CharResult (Either JThrowable Word16) | |
BooleanResult (Either JThrowable Bool) |
data JavaThreadId a Source