jni-0.7.0: Complete JNI raw bindings.
Safe HaskellNone
LanguageHaskell2010

Foreign.JNI.Types

Synopsis

Documentation

data JType Source #

Not part of the JNI. The kind of J type indices. Useful to reflect the object's class at the type-level.

Constructors

Class Symbol

Class name

Iface Symbol

Interface name

Prim Symbol

Primitive type

Array JType

Array type

Generic JType [JType]

Parameterized (generic) type

Void

Void special type

Instances

Instances details
SingI 'Void Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

sing :: Sing 'Void

(KnownSymbol sym, SingI sym) => SingI ('Class sym :: JType) Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

sing :: Sing ('Class sym)

(KnownSymbol sym, SingI sym) => SingI ('Iface sym :: JType) Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

sing :: Sing ('Iface sym)

(KnownSymbol sym, SingI sym) => SingI ('Prim sym :: JType) Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

sing :: Sing ('Prim sym)

SingI ty => SingI ('Array ty :: JType) Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

sing :: Sing ('Array ty)

(SingI ty, SingI tys) => SingI ('Generic ty tys :: JType) Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

sing :: Sing ('Generic ty tys)

type Sing Source # 
Instance details

Defined in Foreign.JNI.Types

type Sing = SJType

class SingI ty => IsPrimitiveType (ty :: JType) Source #

The class of Java types that are "unboxed".

Instances

Instances details
KnownSymbol sym => IsPrimitiveType ('Prim sym) Source # 
Instance details

Defined in Foreign.JNI.Types

class IsReferenceType (ty :: JType) Source #

Instances

Instances details
IsReferenceType ('Class sym) Source # 
Instance details

Defined in Foreign.JNI.Types

IsReferenceType ('Iface sym) Source # 
Instance details

Defined in Foreign.JNI.Types

IsReferenceType ('Array ty) Source # 
Instance details

Defined in Foreign.JNI.Types

IsReferenceType ty => IsReferenceType ('Generic ty tys) Source # 
Instance details

Defined in Foreign.JNI.Types

type family Sing :: k -> Type #

Instances

Instances details
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SBool
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SOrdering
type Sing 
Instance details

Defined in Data.Singletons.TypeLits.Internal

type Sing = SNat
type Sing 
Instance details

Defined in Data.Singletons.TypeLits.Internal

type Sing = SSymbol
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple0
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SVoid
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SAll
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SAny
type Sing Source # 
Instance details

Defined in Foreign.JNI.Types

type Sing = SJType
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SList :: [a] -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SMaybe :: Maybe a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SMin :: Min a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SMax :: Max a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SFirst :: First a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SLast :: Last a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SWrappedMonoid :: WrappedMonoid m -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SOption :: Option a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SIdentity :: Identity a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Sing = SFirst :: First a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Sing = SLast :: Last a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SDual :: Dual a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SSum :: Sum a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SProduct :: Product a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Sing = SDown :: Down a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SNonEmpty :: NonEmpty a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sing = SEndo :: Endo a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sing = SMaxInternal :: MaxInternal a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sing = SMinInternal :: MinInternal a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SEither :: Either a b -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple2 :: (a, b) -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Sing = SArg :: Arg a b -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Proxy

type Sing = SProxy :: Proxy t -> Type
type Sing 
Instance details

Defined in Data.Singletons.Internal

type Sing = SWrappedSing :: WrappedSing a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Internal

type Sing = SLambda :: (k1 ~> k2) -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Sing = SStateL :: StateL s a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Sing = SStateR :: StateR s a -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple3 :: (a, b, c) -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Const

type Sing = SConst :: Const a b -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple4 :: (a, b, c, d) -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple5 :: (a, b, c, d, e) -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple6 :: (a, b, c, d, e, f) -> Type
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple7 :: (a, b, c, d, e, f, g) -> Type

data SJType (a :: JType) where Source #

Constructors

SClass :: String -> SJType ('Class sym) 
SIface :: String -> SJType ('Iface sym) 
SPrim :: String -> SJType ('Prim sym) 
SArray :: SJType ty -> SJType ('Array ty) 
SGeneric :: SJType ty -> Sing tys -> SJType ('Generic ty tys) 
SVoid :: SJType 'Void 

Instances

Instances details
Show (SJType a) Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

showsPrec :: Int -> SJType a -> ShowS #

show :: SJType a -> String #

showList :: [SJType a] -> ShowS #

type (<>) a g = 'Generic a g Source #

Shorthand for parametized Java types.

JNI types

newtype J (a :: JType) Source #

Type indexed Java Objects.

Constructors

J (ForeignPtr (J a)) 

Instances

Instances details
Eq (J a) Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

(==) :: J a -> J a -> Bool #

(/=) :: J a -> J a -> Bool #

Show (J a) Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

showsPrec :: Int -> J a -> ShowS #

show :: J a -> String #

showList :: [J a] -> ShowS #

jnull :: J a Source #

The null reference.

upcast :: J a -> JObject Source #

Any object can be cast to Object.

arrayUpcast :: IsReferenceType ty => J ('Array ty) -> JObjectArray Source #

Any array of a reference type can be casted to an array of Objects.

unsafeCast :: J a -> J b Source #

Unsafe type cast. Should only be used to downcast.

generic :: J a -> J (a <> g) Source #

Parameterize the type of an object, making its type a generic type.

unsafeUngeneric :: J (a <> g) -> J a Source #

Get the base type of a generic type.

jtypeOf :: JValue -> SomeSing JType Source #

Get the Java type of a value.

singToIsReferenceType :: Sing (ty :: JType) -> Maybe (Dict (IsReferenceType ty)) Source #

Produces evidence for IsReferenceType from a `Sing ty`.

referenceTypeName :: IsReferenceType ty => Sing (ty :: JType) -> ReferenceTypeName Source #

The name of a type, suitable for passing to findClass.

data Signature Source #

A string representing a signature, well-formed by construction.

Instances

Instances details
Eq Signature Source # 
Instance details

Defined in Foreign.JNI.Internal

Ord Signature Source # 
Instance details

Defined in Foreign.JNI.Internal

Show Signature Source # 
Instance details

Defined in Foreign.JNI.Internal

signature :: Sing (ty :: JType) -> Signature Source #

Construct a JNI type signature from a Java type.

methodSignature :: [SomeSing JType] -> Sing (ty :: JType) -> MethodSignature Source #

Construct a method's JNI type signature, given the type of the arguments and the return type.

newtype JVM Source #

A JVM instance.

Constructors

JVM_ (Ptr JVM) 

Instances

Instances details
Eq JVM Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

(==) :: JVM -> JVM -> Bool #

(/=) :: JVM -> JVM -> Bool #

Show JVM Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

showsPrec :: Int -> JVM -> ShowS #

show :: JVM -> String #

showList :: [JVM] -> ShowS #

Storable JVM Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

sizeOf :: JVM -> Int #

alignment :: JVM -> Int #

peekElemOff :: Ptr JVM -> Int -> IO JVM #

pokeElemOff :: Ptr JVM -> Int -> JVM -> IO () #

peekByteOff :: Ptr b -> Int -> IO JVM #

pokeByteOff :: Ptr b -> Int -> JVM -> IO () #

peek :: Ptr JVM -> IO JVM #

poke :: Ptr JVM -> JVM -> IO () #

NFData JVM Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

rnf :: JVM -> () #

newtype JNIEnv Source #

The thread-local JNI context. Do not share this object between threads.

Constructors

JNIEnv_ (Ptr JNIEnv) 

Instances

Instances details
Eq JNIEnv Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

(==) :: JNIEnv -> JNIEnv -> Bool #

(/=) :: JNIEnv -> JNIEnv -> Bool #

Show JNIEnv Source # 
Instance details

Defined in Foreign.JNI.Types

Storable JNIEnv Source # 
Instance details

Defined in Foreign.JNI.Types

NFData JNIEnv Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

rnf :: JNIEnv -> () #

newtype JMethodID Source #

A thread-local reference to a method of an object.

Constructors

JMethodID_ (Ptr JMethodID) 

Instances

Instances details
Eq JMethodID Source # 
Instance details

Defined in Foreign.JNI.Types

Show JMethodID Source # 
Instance details

Defined in Foreign.JNI.Types

Storable JMethodID Source # 
Instance details

Defined in Foreign.JNI.Types

NFData JMethodID Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

rnf :: JMethodID -> () #

newtype JFieldID Source #

A thread-local reference to a field of an object.

Constructors

JFieldID_ (Ptr JFieldID) 

Instances

Instances details
Eq JFieldID Source # 
Instance details

Defined in Foreign.JNI.Types

Show JFieldID Source # 
Instance details

Defined in Foreign.JNI.Types

Storable JFieldID Source # 
Instance details

Defined in Foreign.JNI.Types

NFData JFieldID Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

rnf :: JFieldID -> () #

data JValue Source #

A union type for uniformly passing arguments to methods.

Constructors

JBoolean Word8 
JByte CChar 
JChar Word16 
JShort Int16 
JInt Int32 
JLong Int64 
JFloat Float 
JDouble Double 
forall a.SingI a => JObject !(J a) 

Instances

Instances details
Eq JValue Source # 
Instance details

Defined in Foreign.JNI.Types

Methods

(==) :: JValue -> JValue -> Bool #

(/=) :: JValue -> JValue -> Bool #

Show JValue Source # 
Instance details

Defined in Foreign.JNI.Types

withJValues :: [JValue] -> (Ptr JValue -> IO a) -> IO a Source #

withJValue jvalues f provides a pointer to an array containing the given jvalues.

The array is valid only while evaluating f.

Conversions

objectFromPtr :: Ptr (J a) -> IO (J a) Source #

Turn the raw pointer into an object.

unsafeObjectToPtr :: J a -> Ptr (J a) Source #

Get a raw pointer to an object. This is unsafe because if the argument is the last usage occurrence of the given foreign pointer, then its finalizer(s) will be run, which potentially invalidates the plain pointer just obtained.

JNI defined object types

type JObject = J ('Class "java.lang.Object") Source #

type JClass = J ('Class "java.lang.Class") Source #

type JString = J ('Class "java.lang.String") Source #

type JArray a = J ('Array a) Source #

type JObjectArray = JArray ('Class "java.lang.Object") Source #

type JBooleanArray = JArray ('Prim "boolean") Source #

type JByteArray = JArray ('Prim "byte") Source #

type JCharArray = JArray ('Prim "char") Source #

type JShortArray = JArray ('Prim "short") Source #

type JIntArray = JArray ('Prim "int") Source #

type JLongArray = JArray ('Prim "long") Source #

type JFloatArray = JArray ('Prim "float") Source #

type JDoubleArray = JArray ('Prim "double") Source #

type JThrowable = J ('Class "java.lang.Throwable") Source #

type JByteBuffer = J ('Class "java.nio.ByteBuffer") Source #

inline-c contexts

jniCtx :: Context Source #