inline-java-0.9.0: Java interop via inline Java code in Haskell modules.
Safe HaskellNone
LanguageHaskell2010

Language.Java.Inline.Unsafe

Description

Inline Java quasiquotation

See the GHC manual for an introduction to quasiquotation. The quasiquoter exported in this module allows embedding arbitrary Java expressions and blocks of statements inside Haskell code. You can call any Java method and define arbitrary inline code using Java syntax. No FFI required.

Here is the same example as in Language.Java, but with inline Java calls:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE QuasiQuotes #-}
module Object where

import Language.Java as J
import Language.Java.Inline.Unsafe

newtype Object = Object (J ('Class "java.lang.Object"))
instance Coercible Object

clone :: Object -> IO Object
clone obj = [java| $obj.clone() |]

equals :: Object -> Object -> IO Bool
equals obj1 obj2 = [java| $obj1.equals($obj2) |]

...

The functions in this module are considered unsafe in opposition to those in Language.Java.Inline.Safe, which ensure that local references are not leaked.

Synopsis

Documentation

java :: QuasiQuoter Source #

Java code quasiquoter. Example:

imports "javax.swing.JOptionPane"

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

A quasiquote is a snippet of Java code. The code is assumed to be a block (sequence of statements) if the first non whitespace character is a { (curly brace) character. Otherwise it's parsed as an expression. Variables with an initial $ (dollar) sign are allowed. They have a special meaning: they stand for antiqotation variables (think of them as format specifiers in printf format string). An antiquotation variable $foo is well-scoped if there exists a variable with the name foo in the Haskell context of the quasiquote, whose type is Coercible to a Java primitive or reference type.

imports :: String -> Q [Dec] Source #

Declares import statements to be included in the java compilation unit. e.g.

imports "java.util.*"

loadJavaWrappers :: IO () Source #

Idempotent action that loads all wrappers in every module of the current program into the JVM. You shouldn't need to call this yourself.