jvm-0.5.0: Call JVM methods from Haskell.
Safe HaskellNone
LanguageHaskell2010

Language.Java.Unsafe

Description

High-level helper functions for interacting with Java objects, mapping them to Haskell values and vice versa. The Reify and Reflect classes together are to Java what Foreign.Storable is to C: they provide a means to marshallunmarshall Java objects fromto Haskell data types.

A typical pattern for wrapping Java API's using this module is:

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

import Language.Java.Unsafe as J

newtype Object = Object (J ('Class "java.lang.Object"))
  deriving (J.Coercible, J.Interpretation, J.Reify, J.Reflect)

clone :: Object -> IO Object
clone obj = J.call obj "clone" []

equals :: Object -> Object -> IO Bool
equals obj1 obj2 = J.call obj1 "equals" [jvalue obj2]

...

To call Java methods using quasiquoted Java syntax instead, see Language.Java.Inline.

The functions in this module are considered unsafe, as opposed to those in Language.Java.Safe, which guarantee that local references are not leaked. Functions with a VariadicIO constraint in their context are variadic, meaning that you can apply them to any number of arguments, provided they are Coercible.

NOTE 1: To use any function in this module, you'll need an initialized JVM in the current process, using withJVM or otherwise.

NOTE 2: Functions in this module memoize (cache) any implicitly performed class and method lookups, for performance. This memoization is safe only when no new named classes are defined at runtime.

Synopsis

JVM instance management

withJVM :: [ByteString] -> IO a -> IO a #

JVM calls

classOf :: forall a sym. (Ty a ~ 'Class sym, Coercible a, KnownSymbol sym) => a -> String Source #

Get the Java class of an object or anything Coercible to one.

getClass :: IsReferenceType ty => Sing (ty :: JType) -> IO JClass Source #

Yields a class referece. It behaves as findClass unless setGetClassFunction is used.

setGetClassFunction :: (forall ty. IsReferenceType ty => Sing (ty :: JType) -> IO JClass) -> IO () Source #

Sets the function to use for loading classes.

findClass is used by default.

new :: forall a f sym. (Ty a ~ 'Class sym, Coercible a (J ('Class sym)), Coercible a, VariadicIO f a) => f Source #

Creates a new instance of the class whose name is resolved from the return type. For instance,

do x :: J ('Class "java.lang.Integer") <- new 42
   return x

You can pass any number of Coercible arguments to the constructor.

newArray :: forall ty. SingI ty => Int32 -> IO (J ('Array ty)) Source #

Creates a new Java array of the given size. The type of the elements of the resulting array is determined by the return type a call to newArray has, at the call site, and must not be left ambiguous.

To create a Java array of 50 booleans:

do arr :: J ('Array ('Prim "boolean")) <- newArray 50
   return arr

toArray :: forall ty. (SingI ty, IsReferenceType ty) => [J ty] -> IO (J ('Array ty)) Source #

Creates an array from a list of references.

call :: forall a b ty f. (VariadicIO f b, ty ~ Ty a, IsReferenceType ty, Coercible a, Coercible b, Coercible a (J ty)) => a -> String -> f Source #

The Swiss Army knife for calling Java methods. Give it an object or any data type coercible to one and any number of Coercible arguments. Based on the types of each argument, and based on the return type, call will invoke the named method using of the call*Method family of functions in the JNI API.

When the method name is overloaded, use upcast or unsafeCast appropriately on the class instance and/or on the arguments to invoke the right method.

Example:

call obj "frobnicate" x y z

callStatic Source #

Arguments

:: forall a ty f. (ty ~ Ty a, Coercible a, VariadicIO f a) 
=> String

Class name

-> String

Method name

-> f 

Same as call, but for static methods.

Example:

callStatic "java.lang.Integer" "parseInt" jstr

getStaticField Source #

Arguments

:: forall a ty. (ty ~ Ty a, Coercible a) 
=> String

Class name

-> String

Static field name

-> IO a 

Get a static field.

type VariadicIO f b = (ReturnTypeIO f ~ b, VariadicIO_ f) Source #

Document that a function is variadic

VariadicIO f b constraints f to be of the form

a₁ -> ... -> aₙ -> IO b

for any value of n, where the context provides

(Coercible a₁, ... , Coercible aₙ)

Reference management

push :: (MonadCatch m, MonadIO m) => m (Pop a) -> m a Source #

Open a new scope for allocating (JNI) local references to JVM objects.

pushWithSizeHint :: forall a m. (MonadCatch m, MonadIO m) => Int32 -> m (Pop a) -> m a Source #

Like push, but specify explicitly a minimum size for the frame. You probably don't need this.

data Pop a where Source #

Constructors

PopValue :: a -> Pop a 
PopObject :: (ty ~ Ty a, Coercible a, Coercible a (J ty), IsReferenceType ty) => a -> Pop a 

pop :: Monad m => m (Pop ()) Source #

Equivalent to 'popWithValue ()'.

popWithObject :: (ty ~ Ty a, Coercible a, Coercible a (J ty), IsReferenceType ty, Monad m) => a -> m (Pop a) Source #

Pop a frame and return a JVM object.

popWithValue :: Monad m => a -> m (Pop a) Source #

Pop a frame and return a value. This value MUST NOT be an object reference created in the popped frame. In that case use popWithObject instead.

withLocalRef :: (MonadMask m, MonadIO m, Coercible o (J ty)) => m o -> (o -> m a) -> m a Source #

Create a local ref and delete it when the given action completes.

Coercions

data CoercionFailure Source #

A JNI call may cause a (Java) exception to be raised. This module raises it as a Haskell exception wrapping the Java exception.

Constructors

CoercionFailure 

class SingI (Ty a) => Coercible a where Source #

Tag data types that can be coerced in O(1) time without copy to a Java object or primitive type (i.e. have the same representation) by declaring an instance of this type class for that data type.

Minimal complete definition

Nothing

Associated Types

type Ty a :: JType Source #

Methods

coerce :: a -> JValue Source #

default coerce :: Coercible a (J (Ty a)) => a -> JValue Source #

unsafeUncoerce :: JValue -> a Source #

default unsafeUncoerce :: Coercible (J (Ty a)) a => JValue -> a Source #

Instances

Instances details
Coercible Bool Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Ty Bool :: JType Source #

Methods

coerce :: Bool -> JValue Source #

unsafeUncoerce :: JValue -> Bool Source #

Coercible Char Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Ty Char :: JType Source #

Methods

coerce :: Char -> JValue Source #

unsafeUncoerce :: JValue -> Char Source #

Coercible Double Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Ty Double :: JType Source #

Methods

coerce :: Double -> JValue Source #

unsafeUncoerce :: JValue -> Double Source #

Coercible Float Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Ty Float :: JType Source #

Methods

coerce :: Float -> JValue Source #

unsafeUncoerce :: JValue -> Float Source #

Coercible Int16 Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Ty Int16 :: JType Source #

Methods

coerce :: Int16 -> JValue Source #

unsafeUncoerce :: JValue -> Int16 Source #

Coercible Int32 Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Ty Int32 :: JType Source #

Methods

coerce :: Int32 -> JValue Source #

unsafeUncoerce :: JValue -> Int32 Source #

Coercible Int64 Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Ty Int64 :: JType Source #

Methods

coerce :: Int64 -> JValue Source #

unsafeUncoerce :: JValue -> Int64 Source #

Coercible Word16 Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Ty Word16 :: JType Source #

Methods

coerce :: Word16 -> JValue Source #

unsafeUncoerce :: JValue -> Word16 Source #

Coercible () Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Ty () :: JType Source #

Methods

coerce :: () -> JValue Source #

unsafeUncoerce :: JValue -> () Source #

Coercible CChar Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Ty CChar :: JType Source #

Methods

coerce :: CChar -> JValue Source #

unsafeUncoerce :: JValue -> CChar Source #

SingI ty => Coercible (J ty) Source #

The identity instance.

Instance details

Defined in Language.Java.Unsafe

Associated Types

type Ty (J ty) :: JType Source #

Methods

coerce :: J ty -> JValue Source #

unsafeUncoerce :: JValue -> J ty Source #

Coercible (Choice a) Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Ty (Choice a) :: JType Source #

Methods

coerce :: Choice a -> JValue Source #

unsafeUncoerce :: JValue -> Choice a Source #

jvalue :: (ty ~ Ty a, Coercible a) => a -> JValue Source #

Inject a value (of primitive or reference type) to a JValue. This datatype is useful for e.g. passing arguments as a list of homogeneous type. Synonym for coerce.

jobject :: (ty ~ Ty a, Coercible a, IsReferenceType ty) => a -> J ty Source #

If ty is a reference type, then it should be possible to get an object from a value.

Conversions

class (SingI (Interp a), IsReferenceType (Interp a)) => Interpretation (a :: k) Source #

The Interp type family is used by both Reify and Reflect. In order to benefit from -XGeneralizedNewtypeDeriving of new instances, we make this an associated type family instead of a standalone one.

Associated Types

type Interp a :: JType Source #

Map a Haskell type to the symbolic representation of a Java type.

Instances

Instances details
Interpretation Bool Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp Bool :: JType Source #

Interpretation Double Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp Double :: JType Source #

Interpretation Float Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp Float :: JType Source #

Interpretation Int16 Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp Int16 :: JType Source #

Interpretation Int32 Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp Int32 :: JType Source #

Interpretation Int64 Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp Int64 :: JType Source #

Interpretation Word16 Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp Word16 :: JType Source #

Interpretation () Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp () :: JType Source #

Interpretation CChar Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp CChar :: JType Source #

Interpretation ByteString Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp ByteString :: JType Source #

Interpretation Text Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp Text :: JType Source #

Interpretation a => Interpretation ([a] :: Type) Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp [a] :: JType Source #

(SingI ty, IsReferenceType ty) => Interpretation (J ty :: Type) Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp (J ty) :: JType Source #

Interpretation (IOVector a) => Interpretation (Vector a :: Type) Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp (Vector a) :: JType Source #

Interpretation (IOVector Double) Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp (IOVector Double) :: JType Source #

Interpretation (IOVector Float) Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp (IOVector Float) :: JType Source #

Interpretation (IOVector Int16) Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp (IOVector Int16) :: JType Source #

Interpretation (IOVector Int32) Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp (IOVector Int32) :: JType Source #

Interpretation (IOVector Int64) Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp (IOVector Int64) :: JType Source #

Interpretation (IOVector Word16) Source # 
Instance details

Defined in Language.Java.Unsafe

Associated Types

type Interp (IOVector Word16) :: JType Source #

Static (Interpretation Bool) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation Bool))

Static (Interpretation Double) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation Double))

Static (Interpretation Float) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation Float))

Static (Interpretation Int16) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation Int16))

Static (Interpretation Int32) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation Int32))

Static (Interpretation Int64) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation Int64))

(Typeable (Dict (Interpretation [a])), Typeable (Dict (Interpretation a)), Static (Interpretation a)) => Static (Interpretation [a]) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation [a]))

Static (Interpretation Word16) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation Word16))

Static (Interpretation ()) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation ()))

Static (Interpretation CChar) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation CChar))

Static (Interpretation ByteString) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation ByteString))

Static (Interpretation Text) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation Text))

(Typeable (Dict (Interpretation (J ty))), Typeable (Dict (SingI ty)), Typeable (Dict (IsReferenceType ty)), Static (SingI ty), Static (IsReferenceType ty)) => Static (Interpretation (J ty)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation (J ty)))

(Typeable (Dict (Interpretation (Vector a))), Typeable (Dict (Interpretation (IOVector a))), Static (Interpretation (IOVector a))) => Static (Interpretation (Vector a)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation (Vector a)))

Static (Interpretation (IOVector Double)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation (IOVector Double)))

Static (Interpretation (IOVector Float)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation (IOVector Float)))

Static (Interpretation (IOVector Int16)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation (IOVector Int16)))

Static (Interpretation (IOVector Int32)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation (IOVector Int32)))

Static (Interpretation (IOVector Int64)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation (IOVector Int64)))

Static (Interpretation (IOVector Word16)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Interpretation (IOVector Word16)))

class Interpretation a => Reify a where Source #

Extract a concrete Haskell value from the space of Java objects. That is to say, unmarshall a Java object to a Haskell value. Unlike coercing, in general reifying induces allocations and copies.

Minimal complete definition

Nothing

Methods

reify :: J (Interp a) -> IO a Source #

Invariant: The result and the argument share no direct JVM object references.

default reify :: (Coercible a, Interp a ~ Ty a) => J (Interp a) -> IO a Source #

Instances

Instances details
Reify Bool Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp Bool) -> IO Bool Source #

Reify Double Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp Double) -> IO Double Source #

Reify Float Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp Float) -> IO Float Source #

Reify Int16 Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp Int16) -> IO Int16 Source #

Reify Int32 Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp Int32) -> IO Int32 Source #

Reify Int64 Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp Int64) -> IO Int64 Source #

Reify Word16 Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp Word16) -> IO Word16 Source #

Reify () Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp ()) -> IO () Source #

Reify CChar Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp CChar) -> IO CChar Source #

Reify ByteString Source # 
Instance details

Defined in Language.Java.Unsafe

Reify Text Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp Text) -> IO Text Source #

Reify a => Reify [a] Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp [a]) -> IO [a] Source #

Interpretation (J ty) => Reify (J ty) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp (J ty)) -> IO (J ty) Source #

(Storable a, Reify (IOVector a)) => Reify (Vector a) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp (Vector a)) -> IO (Vector a) Source #

Reify (IOVector Double) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp (IOVector Double)) -> IO (IOVector Double) Source #

Reify (IOVector Float) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp (IOVector Float)) -> IO (IOVector Float) Source #

Reify (IOVector Int16) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp (IOVector Int16)) -> IO (IOVector Int16) Source #

Reify (IOVector Int32) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp (IOVector Int32)) -> IO (IOVector Int32) Source #

Reify (IOVector Int64) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp (IOVector Int64)) -> IO (IOVector Int64) Source #

Reify (IOVector Word16) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reify :: J (Interp (IOVector Word16)) -> IO (IOVector Word16) Source #

Static (Reify Bool) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify Bool))

Static (Reify Double) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify Double))

Static (Reify Float) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify Float))

Static (Reify Int16) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify Int16))

Static (Reify Int32) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify Int32))

Static (Reify Int64) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify Int64))

(Typeable (Dict (Reify [a])), Typeable (Dict (Reify a)), Static (Reify a)) => Static (Reify [a]) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify [a]))

Static (Reify Word16) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify Word16))

Static (Reify ()) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify ()))

Static (Reify CChar) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify CChar))

Static (Reify ByteString) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify ByteString))

Static (Reify Text) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify Text))

(Typeable (Dict (Reify (J ty))), Typeable (Dict (Interpretation (J ty))), Static (Interpretation (J ty))) => Static (Reify (J ty)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify (J ty)))

(Typeable (Dict (Reify (Vector a))), Typeable (Dict (Storable a)), Typeable (Dict (Reify (IOVector a))), Static (Storable a), Static (Reify (IOVector a))) => Static (Reify (Vector a)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify (Vector a)))

Static (Reify (IOVector Double)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify (IOVector Double)))

Static (Reify (IOVector Float)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify (IOVector Float)))

Static (Reify (IOVector Int16)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify (IOVector Int16)))

Static (Reify (IOVector Int32)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify (IOVector Int32)))

Static (Reify (IOVector Int64)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify (IOVector Int64)))

Static (Reify (IOVector Word16)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reify (IOVector Word16)))

class Interpretation a => Reflect a where Source #

Inject a concrete Haskell value into the space of Java objects. That is to say, marshall a Haskell value to a Java object. Unlike coercing, in general reflection induces allocations and copies.

Minimal complete definition

Nothing

Methods

reflect :: a -> IO (J (Interp a)) Source #

Invariant: The result and the argument share no direct JVM object references.

default reflect :: (Coercible a, Interp a ~ Ty a) => a -> IO (J (Interp a)) Source #

Instances

Instances details
Reflect Bool Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: Bool -> IO (J (Interp Bool)) Source #

Reflect Double Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: Double -> IO (J (Interp Double)) Source #

Reflect Float Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: Float -> IO (J (Interp Float)) Source #

Reflect Int16 Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: Int16 -> IO (J (Interp Int16)) Source #

Reflect Int32 Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: Int32 -> IO (J (Interp Int32)) Source #

Reflect Int64 Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: Int64 -> IO (J (Interp Int64)) Source #

Reflect Word16 Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: Word16 -> IO (J (Interp Word16)) Source #

Reflect () Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: () -> IO (J (Interp ())) Source #

Reflect CChar Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: CChar -> IO (J (Interp CChar)) Source #

Reflect ByteString Source # 
Instance details

Defined in Language.Java.Unsafe

Reflect Text Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: Text -> IO (J (Interp Text)) Source #

Reflect a => Reflect [a] Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: [a] -> IO (J (Interp [a])) Source #

Interpretation (J ty) => Reflect (J ty) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: J ty -> IO (J (Interp (J ty))) Source #

(Storable a, Reflect (IOVector a)) => Reflect (Vector a) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: Vector a -> IO (J (Interp (Vector a))) Source #

Reflect (IOVector Double) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: IOVector Double -> IO (J (Interp (IOVector Double))) Source #

Reflect (IOVector Float) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: IOVector Float -> IO (J (Interp (IOVector Float))) Source #

Reflect (IOVector Int16) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: IOVector Int16 -> IO (J (Interp (IOVector Int16))) Source #

Reflect (IOVector Int32) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: IOVector Int32 -> IO (J (Interp (IOVector Int32))) Source #

Reflect (IOVector Int64) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: IOVector Int64 -> IO (J (Interp (IOVector Int64))) Source #

Reflect (IOVector Word16) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

reflect :: IOVector Word16 -> IO (J (Interp (IOVector Word16))) Source #

Static (Reflect Bool) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect Bool))

Static (Reflect Double) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect Double))

Static (Reflect Float) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect Float))

Static (Reflect Int16) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect Int16))

Static (Reflect Int32) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect Int32))

Static (Reflect Int64) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect Int64))

(Typeable (Dict (Reflect [a])), Typeable (Dict (Reflect a)), Static (Reflect a)) => Static (Reflect [a]) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect [a]))

Static (Reflect Word16) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect Word16))

Static (Reflect ()) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect ()))

Static (Reflect CChar) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect CChar))

Static (Reflect ByteString) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect ByteString))

Static (Reflect Text) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect Text))

(Typeable (Dict (Reflect (J ty))), Typeable (Dict (Interpretation (J ty))), Static (Interpretation (J ty))) => Static (Reflect (J ty)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect (J ty)))

(Typeable (Dict (Reflect (Vector a))), Typeable (Dict (Storable a)), Typeable (Dict (Reflect (IOVector a))), Static (Storable a), Static (Reflect (IOVector a))) => Static (Reflect (Vector a)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect (Vector a)))

Static (Reflect (IOVector Double)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect (IOVector Double)))

Static (Reflect (IOVector Float)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect (IOVector Float)))

Static (Reflect (IOVector Int16)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect (IOVector Int16)))

Static (Reflect (IOVector Int32)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect (IOVector Int32)))

Static (Reflect (IOVector Int64)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect (IOVector Int64)))

Static (Reflect (IOVector Word16)) Source # 
Instance details

Defined in Language.Java.Unsafe

Methods

closureDict :: Closure (Dict (Reflect (IOVector Word16)))

Re-exports

sing :: SingI a => Sing a #