| Portability | non-portable (TypeFamilies) |
|---|---|
| Stability | experimental |
| Maintainer | julian.fleischer@fu-berlin.de |
| Safe Haskell | None |
Foreign.Java.Bindings.Support
Description
This module provides type classes and instances for supporting the high level bindings. This module should not be imported directly.
- object' :: String -> Q
- class JBoolean a where
- class JChar a where
- class JByte a where
- class JShort a where
- class JInt a where
- class JLong a where
- class JFloat a where
- class JDouble a where
- class Array a where
- asMaybeArrayObject :: a -> Java (Maybe JObject)
- class BooleanResult m where
- toBooleanResult :: Either JThrowable Bool -> Java m
- class CharResult m where
- toCharResult :: Either JThrowable Word16 -> Java m
- class ByteResult m where
- toByteResult :: Either JThrowable Int8 -> Java m
- class ShortResult m where
- toShortResult :: Either JThrowable Int16 -> Java m
- class IntResult m where
- toIntResult :: Either JThrowable Int32 -> Java m
- class LongResult m where
- toLongResult :: Either JThrowable Int64 -> Java m
- class FloatResult m where
- toFloatResult :: Either JThrowable Float -> Java m
- class DoubleResult m where
- toDoubleResult :: Either JThrowable Double -> Java m
- class VoidResult m where
- toVoidResult :: Either JThrowable () -> Java m
- class JavaArray (ArrayResultType m) (ArrayResultComponent m) => ArrayResult m where
- type ArrayResultType m
- type ArrayResultComponent m
- toArrayResult :: Either JThrowable (Maybe (JArray (ArrayResultType m))) -> Java m
- class ObjectResult m where
- toObjectResult :: Either JThrowable (Maybe JObject) -> Java m
- class InstanceOf a where
- type CoercedType a
- instanceOf :: JavaObject o => o -> a -> Java Bool
- whenInstanceOf :: JavaObject o => o -> a -> (CoercedType a -> Java d) -> Java (Maybe d)
- coerce :: JavaObject o => o -> a -> Java (Maybe (CoercedType a))
- class UnsafeCast a where
- unsafeFromJObject :: JObject -> Java a
- registerCallbacks :: JClass -> Java Bool
- type WrappedFun = Ptr JVM -> Ptr JObjectRef -> Ptr JObjectRef -> Ptr JObjectRef -> IO (Ptr JObjectRef)
- runJava_ :: Ptr JVM -> Java a -> IO a
- wrap_ :: WrappedFun -> IO (FunPtr WrappedFun)
- freeFunPtr :: FunPtr WrappedFun -> IO ()
- wrap :: Java () -> IO (FunPtr WrappedFun)
- intify :: Java () -> IO Int64
- sushimaki :: String -> Java () -> Java JObject
- delete :: JObject -> Java ()
Documentation
class BooleanResult m whereSource
The result of a function call that is of type boolean.
Methods
toBooleanResult :: Either JThrowable Bool -> Java mSource
Instances
class CharResult m whereSource
The result of a function call that is of type char.
Methods
toCharResult :: Either JThrowable Word16 -> Java mSource
Instances
class ByteResult m whereSource
The result of a function call that is of type byte.
Methods
toByteResult :: Either JThrowable Int8 -> Java mSource
Instances
class ShortResult m whereSource
The result of a function call that is of type short.
Methods
toShortResult :: Either JThrowable Int16 -> Java mSource
Instances
The result of a function call that is of type int.
Methods
toIntResult :: Either JThrowable Int32 -> Java mSource
class LongResult m whereSource
The result of a function call that is of type long.
Methods
toLongResult :: Either JThrowable Int64 -> Java mSource
Instances
class FloatResult m whereSource
The result of a function call that is of type float.
Methods
toFloatResult :: Either JThrowable Float -> Java mSource
Instances
class DoubleResult m whereSource
The result of a function call that is of type double.
Methods
toDoubleResult :: Either JThrowable Double -> Java mSource
Instances
class VoidResult m whereSource
The result of a function call that is of type void.
Methods
toVoidResult :: Either JThrowable () -> Java mSource
Instances
| VoidResult () | |
| VoidResult (Maybe JThrowable) | |
| VoidResult (Either JThrowable ()) |
class JavaArray (ArrayResultType m) (ArrayResultComponent m) => ArrayResult m whereSource
An array result of a function call.
Associated Types
type ArrayResultType m Source
The JVM machine type of the components of the array.
type ArrayResultComponent m Source
The type of the component of the array as returned by the low level JNI call.
Methods
toArrayResult :: Either JThrowable (Maybe (JArray (ArrayResultType m))) -> Java mSource
Convert the array to a sophisticated type.
Instances
| ArrayResult [Bool] | |
| ArrayResult [Char] | |
| ArrayResult [Double] | |
| ArrayResult [Float] | |
| ArrayResult [Int8] | |
| ArrayResult [Int16] | |
| ArrayResult [Int32] | |
| ArrayResult [Int64] | |
| ArrayResult [Word16] | |
| ArrayResult [String] | |
| ArrayResult a => ArrayResult (Either JThrowable a) |
class ObjectResult m whereSource
The result of a function call that is of type object.
Methods
toObjectResult :: Either JThrowable (Maybe JObject) -> Java mSource
Instances
| ObjectResult [Char] | |
| UnsafeCast a => ObjectResult (Maybe a) | |
| UnsafeCast a => ObjectResult (Either (Maybe JThrowable) a) | |
| UnsafeCast a => ObjectResult (Either JThrowable (Maybe a)) | |
| UnsafeCast a => ObjectResult (Value JThrowable a) |
class InstanceOf a whereSource
A convenient alternative to isInstanceOf.
Minimal complete definition: coerce or whenInstanceOf.
Associated Types
type CoercedType a Source
Methods
instanceOf :: JavaObject o => o -> a -> Java BoolSource
Check if the object of type a is an instance
of the type represented by b.
whenInstanceOf :: JavaObject o => o -> a -> (CoercedType a -> Java d) -> Java (Maybe d)Source
Check if the object of type a is an instance
of the type c, represented by b. If so, it will coerce
the object of type a and pass it to the given action.
If a was an instance of c (where c is represented
by b) this function will return , where Just dd is
the result of the optional computation. If not, Nothing
is returned.
coerce :: JavaObject o => o -> a -> Java (Maybe (CoercedType a))Source
Coerces the given object of type a to an object of
c, where c is represented by a value of type b.
Returns if this is not possible.
Nothing
class UnsafeCast a whereSource
For INTERNAL use only. Is however not in a hidden module, so that other libraries can link against it.
registerCallbacks :: JClass -> Java BoolSource
Yepp. Register callbacks. Do it.
type WrappedFun = Ptr JVM -> Ptr JObjectRef -> Ptr JObjectRef -> Ptr JObjectRef -> IO (Ptr JObjectRef)Source
wrap_ :: WrappedFun -> IO (FunPtr WrappedFun)Source
freeFunPtr :: FunPtr WrappedFun -> IO ()Source