jvm-batching-0.1.2: Provides batched marshalling of values between Java and Haskell.
Safe HaskellNone
LanguageHaskell2010

Language.Java.Batching

Description

This module provides composable batched marshalling.

Batching

Calls to Java methods via JNI are slow in general. Marshalling an array of primitive values can be as slow as marshalling a single value.

Because of this, reifying an iterator or a container is best done by accumulating multiple elements on the java side before passing them to the Haskell side. And conversely, when reflecting an iterator or container, multiple Haskell values are put together before marshalling to the Java side.

Some Haskell values can be batched trivially into arrays of primitive values. Int32 can be batched in a java int[], Double can be batched in a java double[], etc. However, other types like Tuple2 Int32 Double would require more primitive arrays. Values of type Tuple2 Int32 Double are batched in a pair of java arrays of type int[] and double[].

data Tuple2 a b = Tuple2 a b

More generally, the design aims to provide composable batchers. If one knows how to batch types a and b, one can also batch Tuple2 a b, [a], Vector a, etc.

A reference to a batch of values in Java has the type J (Batch a), where a is the Haskell type of the elements in the batch. e.g.

type instance Batch Int32 = 'Array ('Prim "int")
type instance Batch Double = 'Array ('Prim "double")
type instance Batch (Tuple2 a b) =
                'Class "scala.Tuple2" <> '[Batch a, Batch b]

When defining batching for a new type, one needs to tell how batches are represented in Java by adding a type instance to the type family Batch. In addition, procedures for adding and extracting values from the batch need to be specified on both the Haskell and the Java side.

On the Java side, batches are built using the interface io.tweag.jvm.batching.BatchWriter. On the Haskell side, these batches are read using reifyBatch.

class ( ... ) => BatchReify a where
  newBatchWriter
    :: proxy a
    -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter"
                 <> [Interp a, Batch a]
             )
          )
  reifyBatch :: J (Batch a) -> Int32 -> IO (V.Vector a)

newBatchWriter produces a java object implementing the BatchWriter interface, and reifyBatch allows to read a batch created in this fashion.

Conversely, batches can be read on the Java side using the interface io.tweag.jvm.batching.BatchReader. And on the Haskell side, these batches can be created with reflectBatch.

class ( ... ) => BatchReflect a where
 newBatchReader
   :: proxy a
   -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader"
                <> [Batch a, Interp a]
             )
         )
 reflectBatch :: V.Vector a -> IO (J (Batch a))

newBatchReader produces a java object implementing the BatchReader interface, and reflectBatch allows to create these batches from vectors of Haskell values.

The methods of BatchReify and BatchReflect offer default implementations which marshal elements in the batch one at a time. Taking advantage of batching requires defining the methods explicitly. The default implementations are useful for cases where speed is not important, for instance when the iterators to reflect or reify contain a single element or just very few.

Vectors and ByteStrings are batched with the follow scheme.

type instance Batch BS.ByteString
  = 'Class "io.tweag.jvm.batching.Tuple2" <>
       '[ 'Array ('Prim "byte")
        , 'Array ('Prim "int")
        ]

We use two arrays. One of the arrays contains the result of appending all of the ByteStrings in the batch. The other array contains the offset of each vector in the resulting array. See ArrayBatch.

Synopsis

Documentation

class (Interpretation a, SingI (Batch a)) => Batchable (a :: k) Source #

A class of types whose values can be marshaled in batches.

Associated Types

type Batch a :: JType Source #

The type of java batches for reifying and reflecting values of type a.

Instances

Instances details
Batchable Bool Source # 
Instance details

Defined in Language.Java.Batching

Associated Types

type Batch Bool :: JType Source #

Batchable Double Source # 
Instance details

Defined in Language.Java.Batching

Associated Types

type Batch Double :: JType Source #

Batchable Float Source # 
Instance details

Defined in Language.Java.Batching

Associated Types

type Batch Float :: JType Source #

Batchable Int16 Source # 
Instance details

Defined in Language.Java.Batching

Associated Types

type Batch Int16 :: JType Source #

Batchable Int32 Source # 
Instance details

Defined in Language.Java.Batching

Associated Types

type Batch Int32 :: JType Source #

Batchable Int64 Source # 
Instance details

Defined in Language.Java.Batching

Associated Types

type Batch Int64 :: JType Source #

Batchable Word16 Source # 
Instance details

Defined in Language.Java.Batching

Associated Types

type Batch Word16 :: JType Source #

Batchable ByteString Source # 
Instance details

Defined in Language.Java.Batching

Associated Types

type Batch ByteString :: JType Source #

Batchable CChar Source # 
Instance details

Defined in Language.Java.Batching

Associated Types

type Batch CChar :: JType Source #

Batchable Text Source # 
Instance details

Defined in Language.Java.Batching

Associated Types

type Batch Text :: JType Source #

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

Defined in Language.Java.Batching

Associated Types

type Batch (Vector a) :: JType Source #

Batchable (Vector Double) Source # 
Instance details

Defined in Language.Java.Batching

Associated Types

type Batch (Vector Double) :: JType Source #

Batchable (Vector Float) Source # 
Instance details

Defined in Language.Java.Batching

Associated Types

type Batch (Vector Float) :: JType Source #

Batchable (Vector Int16) Source # 
Instance details

Defined in Language.Java.Batching

Associated Types

type Batch (Vector Int16) :: JType Source #

Batchable (Vector Int32) Source # 
Instance details

Defined in Language.Java.Batching

Associated Types

type Batch (Vector Int32) :: JType Source #

Batchable (Vector Int64) Source # 
Instance details

Defined in Language.Java.Batching

Associated Types

type Batch (Vector Int64) :: JType Source #

Batchable (Vector Word16) Source # 
Instance details

Defined in Language.Java.Batching

Associated Types

type Batch (Vector Word16) :: JType Source #

Static (Batchable Bool) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (Batchable Bool))

Static (Batchable Double) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (Batchable Double))

Static (Batchable Float) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (Batchable Float))

Static (Batchable Int16) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (Batchable Int16))

Static (Batchable Int32) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (Batchable Int32))

Static (Batchable Int64) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (Batchable Int64))

Static (Batchable Word16) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (Batchable Word16))

Static (Batchable ByteString) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (Batchable ByteString))

Static (Batchable CChar) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (Batchable CChar))

Static (Batchable Text) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (Batchable Text))

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

Defined in Language.Java.Batching

Methods

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

Static (Batchable (Vector Double)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (Batchable (Vector Double)))

Static (Batchable (Vector Float)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (Batchable (Vector Float)))

Static (Batchable (Vector Int16)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (Batchable (Vector Int16)))

Static (Batchable (Vector Int32)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (Batchable (Vector Int32)))

Static (Batchable (Vector Int64)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (Batchable (Vector Int64)))

Static (Batchable (Vector Word16)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (Batchable (Vector Word16)))

class Batchable a => BatchReify a where Source #

A class for batching reification of values.

It has a method to create a batcher that creates batches in Java, and another method that refies a batch into a vector of haskell values.

The type of the batch used to appear as a class parameter but we run into https://ghc.haskell.org/trac/ghc/ticket/13582

Minimal complete definition

Nothing

Methods

newBatchWriter :: proxy a -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> [Interp a, Batch a])) Source #

Produces a batcher that aggregates elements of type ty (such as int) and produces collections of type Batch a (such as int[]).

default newBatchWriter :: Batch a ~ 'Array (Interp a) => proxy a -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> [Interp a, Batch a])) Source #

reifyBatch :: J (Batch a) -> Int32 -> IO (Vector a) Source #

Reifies the values in a batch of type Batch a. Gets the batch and the amount of elements it contains.

default reifyBatch :: (Reify a, Batch a ~ 'Array (Interp a)) => J (Batch a) -> Int32 -> IO (Vector a) Source #

Instances

Instances details
BatchReify Bool Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchWriter :: proxy Bool -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> '[Interp Bool, Batch Bool])) Source #

reifyBatch :: J (Batch Bool) -> Int32 -> IO (Vector Bool) Source #

BatchReify Double Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchWriter :: proxy Double -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> '[Interp Double, Batch Double])) Source #

reifyBatch :: J (Batch Double) -> Int32 -> IO (Vector Double) Source #

BatchReify Float Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchWriter :: proxy Float -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> '[Interp Float, Batch Float])) Source #

reifyBatch :: J (Batch Float) -> Int32 -> IO (Vector Float) Source #

BatchReify Int16 Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchWriter :: proxy Int16 -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> '[Interp Int16, Batch Int16])) Source #

reifyBatch :: J (Batch Int16) -> Int32 -> IO (Vector Int16) Source #

BatchReify Int32 Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchWriter :: proxy Int32 -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> '[Interp Int32, Batch Int32])) Source #

reifyBatch :: J (Batch Int32) -> Int32 -> IO (Vector Int32) Source #

BatchReify Int64 Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchWriter :: proxy Int64 -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> '[Interp Int64, Batch Int64])) Source #

reifyBatch :: J (Batch Int64) -> Int32 -> IO (Vector Int64) Source #

BatchReify Word16 Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchWriter :: proxy Word16 -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> '[Interp Word16, Batch Word16])) Source #

reifyBatch :: J (Batch Word16) -> Int32 -> IO (Vector Word16) Source #

BatchReify ByteString Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchWriter :: proxy ByteString -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> '[Interp ByteString, Batch ByteString])) Source #

reifyBatch :: J (Batch ByteString) -> Int32 -> IO (Vector ByteString) Source #

BatchReify CChar Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchWriter :: proxy CChar -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> '[Interp CChar, Batch CChar])) Source #

reifyBatch :: J (Batch CChar) -> Int32 -> IO (Vector CChar) Source #

BatchReify Text Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchWriter :: proxy Text -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> '[Interp Text, Batch Text])) Source #

reifyBatch :: J (Batch Text) -> Int32 -> IO (Vector Text) Source #

BatchReify a => BatchReify (Vector a) Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchWriter :: proxy (Vector a) -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> '[Interp (Vector a), Batch (Vector a)])) Source #

reifyBatch :: J (Batch (Vector a)) -> Int32 -> IO (Vector (Vector a)) Source #

BatchReify (Vector Double) Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchWriter :: proxy (Vector Double) -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> '[Interp (Vector Double), Batch (Vector Double)])) Source #

reifyBatch :: J (Batch (Vector Double)) -> Int32 -> IO (Vector0 (Vector Double)) Source #

BatchReify (Vector Float) Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchWriter :: proxy (Vector Float) -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> '[Interp (Vector Float), Batch (Vector Float)])) Source #

reifyBatch :: J (Batch (Vector Float)) -> Int32 -> IO (Vector0 (Vector Float)) Source #

BatchReify (Vector Int16) Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchWriter :: proxy (Vector Int16) -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> '[Interp (Vector Int16), Batch (Vector Int16)])) Source #

reifyBatch :: J (Batch (Vector Int16)) -> Int32 -> IO (Vector0 (Vector Int16)) Source #

BatchReify (Vector Int32) Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchWriter :: proxy (Vector Int32) -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> '[Interp (Vector Int32), Batch (Vector Int32)])) Source #

reifyBatch :: J (Batch (Vector Int32)) -> Int32 -> IO (Vector0 (Vector Int32)) Source #

BatchReify (Vector Int64) Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchWriter :: proxy (Vector Int64) -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> '[Interp (Vector Int64), Batch (Vector Int64)])) Source #

reifyBatch :: J (Batch (Vector Int64)) -> Int32 -> IO (Vector0 (Vector Int64)) Source #

BatchReify (Vector Word16) Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchWriter :: proxy (Vector Word16) -> IO (J ('Iface "io.tweag.jvm.batching.BatchWriter" <> '[Interp (Vector Word16), Batch (Vector Word16)])) Source #

reifyBatch :: J (Batch (Vector Word16)) -> Int32 -> IO (Vector0 (Vector Word16)) Source #

Static (BatchReify Bool) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReify Bool))

Static (BatchReify Double) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReify Double))

Static (BatchReify Float) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReify Float))

Static (BatchReify Int16) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReify Int16))

Static (BatchReify Int32) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReify Int32))

Static (BatchReify Int64) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReify Int64))

Static (BatchReify Word16) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReify Word16))

Static (BatchReify ByteString) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReify ByteString))

Static (BatchReify CChar) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReify CChar))

Static (BatchReify Text) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReify Text))

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

Defined in Language.Java.Batching

Methods

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

Static (BatchReify (Vector Double)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReify (Vector Double)))

Static (BatchReify (Vector Float)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReify (Vector Float)))

Static (BatchReify (Vector Int16)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReify (Vector Int16)))

Static (BatchReify (Vector Int32)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReify (Vector Int32)))

Static (BatchReify (Vector Int64)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReify (Vector Int64)))

Static (BatchReify (Vector Word16)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReify (Vector Word16)))

class Batchable a => BatchReflect a where Source #

A class for batching reflection of values.

It has a method to create a batch reader that reads batches in Java, and another method that reflects a vector of haskell values into a batch.

We considered having the type of the batch appear as a class parameter but we run into https://ghc.haskell.org/trac/ghc/ticket/13582

Minimal complete definition

Nothing

Methods

newBatchReader :: proxy a -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> [Batch a, Interp a])) Source #

Produces a batch reader that receives collections of type ty1 (such as int[]) and produces values of type ty2 (such as int).

default newBatchReader :: Batch a ~ 'Array (Interp a) => proxy a -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> [Batch a, Interp a])) Source #

reflectBatch :: Vector a -> IO (J (Batch a)) Source #

Reflects the values in a vector to a batch of type ty.

default reflectBatch :: (Reflect a, Batch a ~ 'Array (Interp a)) => Vector a -> IO (J (Batch a)) Source #

Instances

Instances details
BatchReflect Bool Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchReader :: proxy Bool -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> '[Batch Bool, Interp Bool])) Source #

reflectBatch :: Vector Bool -> IO (J (Batch Bool)) Source #

BatchReflect Double Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchReader :: proxy Double -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> '[Batch Double, Interp Double])) Source #

reflectBatch :: Vector Double -> IO (J (Batch Double)) Source #

BatchReflect Float Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchReader :: proxy Float -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> '[Batch Float, Interp Float])) Source #

reflectBatch :: Vector Float -> IO (J (Batch Float)) Source #

BatchReflect Int16 Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchReader :: proxy Int16 -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> '[Batch Int16, Interp Int16])) Source #

reflectBatch :: Vector Int16 -> IO (J (Batch Int16)) Source #

BatchReflect Int32 Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchReader :: proxy Int32 -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> '[Batch Int32, Interp Int32])) Source #

reflectBatch :: Vector Int32 -> IO (J (Batch Int32)) Source #

BatchReflect Int64 Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchReader :: proxy Int64 -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> '[Batch Int64, Interp Int64])) Source #

reflectBatch :: Vector Int64 -> IO (J (Batch Int64)) Source #

BatchReflect Word16 Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchReader :: proxy Word16 -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> '[Batch Word16, Interp Word16])) Source #

reflectBatch :: Vector Word16 -> IO (J (Batch Word16)) Source #

BatchReflect ByteString Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchReader :: proxy ByteString -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> '[Batch ByteString, Interp ByteString])) Source #

reflectBatch :: Vector ByteString -> IO (J (Batch ByteString)) Source #

BatchReflect CChar Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchReader :: proxy CChar -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> '[Batch CChar, Interp CChar])) Source #

reflectBatch :: Vector CChar -> IO (J (Batch CChar)) Source #

BatchReflect Text Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchReader :: proxy Text -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> '[Batch Text, Interp Text])) Source #

reflectBatch :: Vector Text -> IO (J (Batch Text)) Source #

BatchReflect a => BatchReflect (Vector a) Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchReader :: proxy (Vector a) -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> '[Batch (Vector a), Interp (Vector a)])) Source #

reflectBatch :: Vector (Vector a) -> IO (J (Batch (Vector a))) Source #

BatchReflect (Vector Double) Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchReader :: proxy (Vector Double) -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> '[Batch (Vector Double), Interp (Vector Double)])) Source #

reflectBatch :: Vector0 (Vector Double) -> IO (J (Batch (Vector Double))) Source #

BatchReflect (Vector Float) Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchReader :: proxy (Vector Float) -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> '[Batch (Vector Float), Interp (Vector Float)])) Source #

reflectBatch :: Vector0 (Vector Float) -> IO (J (Batch (Vector Float))) Source #

BatchReflect (Vector Int16) Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchReader :: proxy (Vector Int16) -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> '[Batch (Vector Int16), Interp (Vector Int16)])) Source #

reflectBatch :: Vector0 (Vector Int16) -> IO (J (Batch (Vector Int16))) Source #

BatchReflect (Vector Int32) Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchReader :: proxy (Vector Int32) -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> '[Batch (Vector Int32), Interp (Vector Int32)])) Source #

reflectBatch :: Vector0 (Vector Int32) -> IO (J (Batch (Vector Int32))) Source #

BatchReflect (Vector Int64) Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchReader :: proxy (Vector Int64) -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> '[Batch (Vector Int64), Interp (Vector Int64)])) Source #

reflectBatch :: Vector0 (Vector Int64) -> IO (J (Batch (Vector Int64))) Source #

BatchReflect (Vector Word16) Source # 
Instance details

Defined in Language.Java.Batching

Methods

newBatchReader :: proxy (Vector Word16) -> IO (J ('Iface "io.tweag.jvm.batching.BatchReader" <> '[Batch (Vector Word16), Interp (Vector Word16)])) Source #

reflectBatch :: Vector0 (Vector Word16) -> IO (J (Batch (Vector Word16))) Source #

Static (BatchReflect Bool) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReflect Bool))

Static (BatchReflect Double) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReflect Double))

Static (BatchReflect Float) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReflect Float))

Static (BatchReflect Int16) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReflect Int16))

Static (BatchReflect Int32) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReflect Int32))

Static (BatchReflect Int64) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReflect Int64))

Static (BatchReflect Word16) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReflect Word16))

Static (BatchReflect ByteString) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReflect ByteString))

Static (BatchReflect CChar) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReflect CChar))

Static (BatchReflect Text) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReflect Text))

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

Defined in Language.Java.Batching

Methods

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

Static (BatchReflect (Vector Double)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReflect (Vector Double)))

Static (BatchReflect (Vector Float)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReflect (Vector Float)))

Static (BatchReflect (Vector Int16)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReflect (Vector Int16)))

Static (BatchReflect (Vector Int32)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReflect (Vector Int32)))

Static (BatchReflect (Vector Int64)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReflect (Vector Int64)))

Static (BatchReflect (Vector Word16)) Source # 
Instance details

Defined in Language.Java.Batching

Methods

closureDict :: Closure (Dict (BatchReflect (Vector Word16)))

Array batching

type ArrayBatch ty = 'Class "io.tweag.jvm.batching.Tuple2" <> '[ty, 'Array ('Prim "int")] Source #

Batches of arrays of variable length

The first component is an array or batch B containing the elements of all the arrays in the batch. The second component is an array of offsets F. The ith position in the offset array is the first position in B after the ith array of the batch.

Thus, the first array of the batch can be found in B between the indices 0 and F[0], the second array of the batch is between the indices F[0] and F[1], and so on.

Orphan instances

(Interpretation a, BatchReflect a) => Reflect (Vector a) Source # 
Instance details

Methods

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

(Interpretation a, BatchReify a) => Reify (Vector a) Source # 
Instance details

Methods

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

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

Methods

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

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

Methods

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

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

Associated Types

type Interp (Vector a) :: JType

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

Methods

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