damus

nostr ios client
git clone git://jb55.com/damus
Log | Files | Refs | README | LICENSE

flatcc_builder.h (80046B)


      1 #ifndef FLATCC_BUILDER_H
      2 #define FLATCC_BUILDER_H
      3 
      4 #ifdef __cplusplus
      5 extern "C" {
      6 #endif
      7 
      8 /**
      9  * Library for building untyped FlatBuffers. Intended as a support
     10  * library for generated C code to produce typed builders, but might
     11  * also be useful in runtime environments and as support for scripting
     12  * languages.
     13  *
     14  * The builder has two API layers: a stack based `start/end` approach,
     15  * and a direct `create`, and they may be mixed freely. The direct
     16  * approach may be used as part of more specialized optimizations such
     17  * as rewriting buffers while the stack approach is convenient for state
     18  * machine driven parsers without a stack, or with a very simple stack
     19  * without extra allocations.
     20  *
     21  * The builder emits partial buffer sequences to a user provided emitter
     22  * function and does not require a full buffer reprensenation in memory.
     23  * For this reason it also does not support sorting or other operations
     24  * that requires representing the buffer, but post-processors can easily
     25  * do this, and the generated schema specific code and provide functions
     26  * to handle this.
     27  *
     28  * A custom allocator with a default realloc implementation can place
     29  * restraints on resource consumption and provide initial allocation
     30  * sizes for various buffers and stacks in use.
     31  *
     32  * A buffer under construction uses a virtual address space for the
     33  * completed part of the buffer, starting at 0 and growing in both
     34  * directions, or just down depending on whether vtables should be
     35  * clustered at the end or not. Clustering may help caching and
     36  * preshipping that part of the buffer.
     37  *
     38  * Because an offset cannot be known before its reference location is
     39  * defined, every completed table, vector, etc. returns a reference into
     40  * the virtual address range. If the final buffer keeps the 0 offset,
     41  * these references remain stable an may be used for external references
     42  * into the buffer.
     43  *
     44  * The maximum buffer that can be constructed is in praxis limited to
     45  * half the UOFFSET_MAX size, typically 2^31 bytes, not counting
     46  * clustered vtables that may consume and additional 2^31 bytes
     47  * (positive address range), but in praxis cannot because vtable
     48  * references are signed and thus limited to 2^31 bytes (or equivalent
     49  * depending on the flatbuffer types chosen).
     50  *
     51  * CORRECTION: in various places rules are mentioned about nesting and using
     52  * a reference at most once. In fact, DAG's are also valid flatbuffers.
     53  * This means a reference may be reused as long as each individual use
     54  * obeys the rules and, for example, circular references are not
     55  * constructed (circular types are ok, but objects graphs with cycles
     56  * are not permitted). Be especially aware of the offset vector create
     57  * call which translates the references into offsets - this can be
     58  * reverted by noting the reference in vector and calculate the base
     59  * used for the offset to restore the original references after the
     60  * vector has been emitted.
     61  */
     62 
     63 #include <stdlib.h>
     64 #ifndef UINT8_MAX
     65 #include <stdint.h>
     66 #endif
     67 
     68 #include "flatcc_flatbuffers.h"
     69 #include "flatcc_emitter.h"
     70 #include "flatcc_refmap.h"
     71 
     72 /* It is possible to enable logging here. */
     73 #ifndef FLATCC_BUILDER_ASSERT
     74 #define FLATCC_BUILDER_ASSERT(cond, reason) FLATCC_ASSERT(cond)
     75 #endif
     76 
     77 /*
     78  * Eror handling is not convenient and correct use should not cause
     79  * errors beyond possibly memory allocation, but assertions are a
     80  * good way to trace problems.
     81  *
     82  * Note: some internal assertion will remain if disabled.
     83  */
     84 #ifndef FLATCC_BUILDER_ASSERT_ON_ERROR
     85 #define FLATCC_BUILDER_ASSERT_ON_ERROR 1
     86 #endif
     87 
     88 /*
     89  * If set, checks user input agains state and returns error,
     90  * otherwise errors are ignored (assuming they won't happen).
     91  * Errors will be asserted if enabled and checks are not skipped.
     92  */
     93 #ifndef FLATCC_BUILDER_SKIP_CHECKS
     94 #define FLATCC_BUILDER_SKIP_CHECKS 0
     95 #endif
     96 
     97 
     98 /*
     99  * When adding the same field to a table twice this is either an error
    100  * or the existing field is returned, potentially introducing garbage
    101  * if the type is a vector, table, or string. When implementing parsers
    102  * it may be convenient to not treat this as an error.
    103  */
    104 #ifndef FLATCC_BUILDER_ALLOW_REPEAT_TABLE_ADD
    105 #define FLATCC_BUILDER_ALLOW_REPEAT_TABLE_ADD 0
    106 #endif
    107 
    108 /**
    109  * This type must have same size as `flatbuffers_uoffset_t`
    110  * and must be a signed type.
    111  */
    112 typedef flatbuffers_soffset_t flatcc_builder_ref_t;
    113 typedef flatbuffers_utype_t flatcc_builder_utype_t;
    114 
    115 /**
    116  * This type must be compatible with code generation that
    117  * creates union specific ref types.
    118  */
    119 typedef struct flatcc_builder_union_ref {
    120     flatcc_builder_utype_t type;
    121     flatcc_builder_ref_t value;
    122 } flatcc_builder_union_ref_t;
    123 
    124 typedef struct flatcc_builder_union_vec_ref {
    125     flatcc_builder_ref_t type;
    126     flatcc_builder_ref_t value;
    127 } flatcc_builder_union_vec_ref_t;
    128 
    129 /**
    130  * Virtual tables are off by one to avoid being mistaken for error at
    131  * position 0, and it makes them detectable as such because no other
    132  * reference is uneven. Vtables are emitted at their actual location
    133  * which is one less than the reference value.
    134  */
    135 typedef flatbuffers_soffset_t flatcc_builder_vt_ref_t;
    136 
    137 typedef flatbuffers_uoffset_t flatcc_builder_identifier_t;
    138 
    139 /**
    140  * Hints to custom allocators so they can provide initial alloc sizes
    141  * etc. There will be at most one buffer for each allocation type per
    142  * flatcc_builder instance. Buffers containing only structs may avoid
    143  * allocation altogether using a `create` call. The vs stack must hold
    144  * vtable entries for all open tables up to their requested max id, but
    145  * unused max id overlap on the stack. The final vtables only store the
    146  * largest id actually added. The fs stack must hold stack frames for
    147  * the nesting levels expected in the buffer, each about 50-100 bytes.
    148  * The ds stack holds open vectors, table data, and nested buffer state.
    149  * `create` calls bypass the `ds` and `fs` stack and are thus faster.
    150  * The vb buffer holds a copy of all vtables seen and emitted since last
    151  * vtable flush. The patch log holds a uoffset for every table field
    152  * added to currently open tables. The hash table holds a uoffset entry
    153  * for each hash slot where the allocator decides how many to provide
    154  * above a certain minimum. The vd buffer allocates vtable descriptors
    155  * which is a reference to an emitted vtable, an offset to a cached
    156  * vtable, and a link to next descriptor with same hash. Calling `reset`
    157  * after build can either keep the allocation levels for the next
    158  * buffer, or reduce the buffers already allocated by requesting 1 byte
    159  * allocations (meaning provide a default).
    160  *
    161  * The user stack is not automatically allocated, but when entered
    162  * explicitly, the boundary is rembered in the current live
    163  * frame.
    164  */
    165 enum flatcc_builder_alloc_type {
    166     /* The stack where vtables are build. */
    167     flatcc_builder_alloc_vs,
    168     /* The stack where data structures are build. */
    169     flatcc_builder_alloc_ds,
    170     /* The virtual table buffer cache, holds a copy of each vt seen. */
    171     flatcc_builder_alloc_vb,
    172     /* The patch log, remembers table fields with outstanding offset refs. */
    173     flatcc_builder_alloc_pl,
    174     /* The stack of frames for nested types. */
    175     flatcc_builder_alloc_fs,
    176     /* The hash table part of the virtual table cache. */
    177     flatcc_builder_alloc_ht,
    178     /* The vtable descriptor buffer, i.e. list elements for emitted vtables. */
    179     flatcc_builder_alloc_vd,
    180     /* User stack frame for custom data. */
    181     flatcc_builder_alloc_us,
    182 
    183     /* Number of allocation buffers. */
    184     flatcc_builder_alloc_buffer_count
    185 };
    186 
    187 /** Must reflect the `flatcc_builder_alloc_type` enum. */
    188 #define FLATCC_BUILDER_ALLOC_BUFFER_COUNT flatcc_builder_alloc_buffer_count
    189 
    190 #ifndef FLATCC_BUILDER_ALLOC
    191 #define FLATCC_BUILDER_ALLOC(n) FLATCC_ALLOC(n)
    192 #endif
    193 
    194 #ifndef FLATCC_BUILDER_FREE
    195 #define FLATCC_BUILDER_FREE(p) FLATCC_FREE(p)
    196 #endif
    197 
    198 #ifndef FLATCC_BUILDER_REALLOC
    199 #define FLATCC_BUILDER_REALLOC(p, n) FLATCC_REALLOC(p, n)
    200 #endif
    201 
    202 #ifndef FLATCC_BUILDER_ALIGNED_ALLOC
    203 #define FLATCC_BUILDER_ALIGNED_ALLOC(a, n) FLATCC_ALIGNED_ALLOC(a, n)
    204 #endif
    205 
    206 #ifndef FLATCC_BUILDER_ALIGNED_FREE
    207 #define FLATCC_BUILDER_ALIGNED_FREE(p) FLATCC_ALIGNED_FREE(p)
    208 #endif
    209 
    210 /**
    211  * Emits data to a conceptual deque by appending to either front or
    212  * back, starting from offset 0.
    213  *
    214  * Each emit call appends a strictly later or earlier sequence than the
    215  * last emit with same offset sign. Thus a buffer is gradually grown at
    216  * both ends. `len` is the combined length of all iov entries such that
    217  * `offset + len` yields the former offset for negative offsets and
    218  * `offset + len` yields the next offset for non-negative offsets.
    219  * The bulk of the data will be in the negative range, possibly all of
    220  * it. The first emitted emitted range will either start or end at
    221  * offset 0. If offset 0 is emitted, it indicates the start of clustered
    222  * vtables. The last positive (non-zero) offset may be zero padding to
    223  * place the buffer in a full multiple of `block_align`, if set.
    224  *
    225  * No iov entry is empty, 0 < iov_count <= FLATCC_IOV_COUNT_MAX.
    226  *
    227  * The source data are in general ephemeral and should be consumed
    228  * immediately, as opposed to caching iov.
    229  *
    230  * For high performance applications:
    231  *
    232  * The `create` calls may reference longer living data, but header
    233  * fields etc. will still be short lived. If an emitter wants to
    234  * reference data in another buffer rather than copying, it should
    235  * inspect the memory range. The length of an iov entry may also be used
    236  * since headers are never very long (anything starting at 16 bytes can
    237  * safely be assumed to be user provided, or static zero padding). It is
    238  * guaranteed that data pointers in `create` calls receive a unique slot
    239  * separate from temporary headers, in the iov table which may be used
    240  * for range checking or hashing (`create_table` is the only call that
    241  * mutates the data buffer). It is also guaranteed (with the exception
    242  * of `create_table` and `create_cached_vtable`) that data provided to
    243  * create calls are not referenced at all by the builder, and these data
    244  * may therefore de-facto be handles rather than direct pointers when
    245  * the emitter and data provider can agree on such a protocol. This does
    246  * NOT apply to any start/end/add/etc. calls which do copy to stack.
    247  * `flatcc_builder_padding_base` may be used to test if an iov entry is
    248  * zero padding which always begins at that address.
    249  *
    250  * Future: the emit interface could be extended with a type code
    251  * and return an existing object insted of the emitted if, for
    252  * example, they are identical. Outside this api level, generated
    253  * code could provide a table comparison function to help such
    254  * deduplication. It would be optional because two equal objects
    255  * are not necessarily identical. The emitter already receives
    256  * one object at time.
    257  *
    258  * Returns 0 on success and otherwise causes the flatcc_builder
    259  * to fail.
    260  */
    261 typedef int flatcc_builder_emit_fun(void *emit_context,
    262         const flatcc_iovec_t *iov, int iov_count, flatbuffers_soffset_t offset, size_t len);
    263 
    264 /*
    265  * Returns a pointer to static padding used in emitter calls. May
    266  * sometimes also be used for empty defaults such as identifier.
    267  */
    268 extern const uint8_t flatcc_builder_padding_base[];
    269 
    270 /**
    271  * `request` is a minimum size to be returned, but allocation is
    272  * expected to grow exponentially or in reasonable chunks. Notably,
    273  * `alloc_type = flatcc_builder_alloc_ht` will only use highest available
    274  * power of 2. The allocator may shrink if `request` is well below
    275  * current size but should avoid repeated resizing on small changes in
    276  * request sizes. If `zero_fill` is non-zero, allocated data beyond
    277  * the current size must be zeroed. The buffer `b` may be null with 0
    278  * length initially. `alloc_context` is completely implementation
    279  * dependendent, and not needed when just relying on realloc. The
    280  * resulting buffer may be the same or different with moved data, like
    281  * realloc. Returns -1 with unmodified buffer on failure or 0 on
    282  * success. The `alloc_type` identifies the buffer type. This may be
    283  * used to cache buffers between instances of builders, or to decide a
    284  * default allocation size larger than requested. If `need` is zero the
    285  * buffer should be deallocate if non-zero, and return success (0)
    286  * regardless.
    287  */
    288 typedef int flatcc_builder_alloc_fun(void *alloc_context,
    289         flatcc_iovec_t *b, size_t request, int zero_fill, int alloc_type);
    290 
    291 /*
    292  * The number of hash slots there will be allocated space for. The
    293  * allocator may provide more. The size returned should be
    294  * `sizeof(flatbuffers_uoffset_t) * count`, where the size is a power of
    295  * 2 (or the rest is wasted). The hash table can store many more entries
    296  * than slots using linear search. The table does not resize.
    297  */
    298 #ifndef FLATCC_BUILDER_MIN_HASH_COUNT
    299 #define FLATCC_BUILDER_MIN_HASH_COUNT 64
    300 #endif
    301 
    302 typedef struct __flatcc_builder_buffer_frame __flatcc_builder_buffer_frame_t;
    303 struct __flatcc_builder_buffer_frame {
    304     flatcc_builder_identifier_t identifier;
    305     flatcc_builder_ref_t mark;
    306     flatbuffers_uoffset_t vs_end;
    307     flatbuffers_uoffset_t nest_id;
    308     uint16_t flags;
    309     uint16_t block_align;
    310 };
    311 
    312 typedef struct __flatcc_builder_vector_frame __flatcc_builder_vector_frame_t;
    313 struct __flatcc_builder_vector_frame {
    314     flatbuffers_uoffset_t elem_size;
    315     flatbuffers_uoffset_t count;
    316     flatbuffers_uoffset_t max_count;
    317 };
    318 
    319 typedef struct __flatcc_builder_table_frame __flatcc_builder_table_frame_t;
    320 struct __flatcc_builder_table_frame {
    321     flatbuffers_uoffset_t vs_end;
    322     flatbuffers_uoffset_t pl_end;
    323     uint32_t vt_hash;
    324     flatbuffers_voffset_t id_end;
    325 };
    326 
    327 /*
    328  * Store state for nested structures such as buffers, tables and vectors.
    329  *
    330  * For less busy data and data where access to a previous state is
    331  * irrelevant, the frame may store the current state directly. Otherwise
    332  * the current state is maintained in the flatcc_builder_t structure in a
    333  * possibly derived form (e.g. ds pointer instead of ds_end offset) and
    334  * the frame is used to store the previous state when the frame is
    335  * entered.
    336  *
    337  * Most operations have a start/update/end cycle the decides the
    338  * liftetime of a frame, but these generally also have a direct form
    339  * (create) that does not use a frame at all. These still do some
    340  * state updates notably passing min_align to parent which may also be
    341  * an operation without a frame following the child level operation
    342  * (e.g. create struct, create buffer). Ending a frame results in the
    343  * same kind of updates.
    344  */
    345 typedef struct __flatcc_builder_frame __flatcc_builder_frame_t;
    346 struct __flatcc_builder_frame {
    347     flatbuffers_uoffset_t ds_first;
    348     flatbuffers_uoffset_t type_limit;
    349     flatbuffers_uoffset_t ds_offset;
    350     uint16_t align;
    351     uint16_t type;
    352     union {
    353         __flatcc_builder_table_frame_t table;
    354         __flatcc_builder_vector_frame_t vector;
    355         __flatcc_builder_buffer_frame_t buffer;
    356     } container;
    357 };
    358 
    359 /**
    360  * The main flatcc_builder structure. Can be stack allocated and must
    361  * be initialized with `flatcc_builder_init` and cleared with
    362  * `flatcc_builder_clear` to reclaim memory. Between buffer builds,
    363  * `flatcc_builder_reset` may be used.
    364  */
    365 typedef struct flatcc_builder flatcc_builder_t;
    366 
    367 struct flatcc_builder {
    368     /* Next entry on reserved stack in `alloc_pl` buffer. */
    369     flatbuffers_voffset_t *pl;
    370     /* Next entry on reserved stack in `alloc_vs` buffer. */
    371     flatbuffers_voffset_t *vs;
    372     /* One above the highest entry in vs, used to track vt_size. */
    373     flatbuffers_voffset_t id_end;
    374     /* The evolving vtable hash updated with every new field. */
    375     uint32_t vt_hash;
    376 
    377     /* Pointer to ds_first. */
    378     uint8_t *ds;
    379     /* Offset from `ds` on current frame. */
    380     flatbuffers_uoffset_t ds_offset;
    381     /* ds buffer size relative to ds_first, clamped to max size of current type. */
    382     flatbuffers_uoffset_t ds_limit;
    383 
    384     /* ds_first, ds_first + ds_offset is current ds stack range. */
    385     flatbuffers_uoffset_t ds_first;
    386     /* Points to currently open frame in `alloc_fs` buffer. */
    387     __flatcc_builder_frame_t *frame;
    388 
    389     /* Only significant to emitter function, if at all. */
    390     void *emit_context;
    391     /* Only significant to allocator function, if at all. */
    392     void *alloc_context;
    393     /* Customizable write function that both appends and prepends data. */
    394     flatcc_builder_emit_fun *emit;
    395     /* Customizable allocator that also deallocates. */
    396     flatcc_builder_alloc_fun *alloc;
    397     /* Buffers indexed by `alloc_type` */
    398     flatcc_iovec_t buffers[FLATCC_BUILDER_ALLOC_BUFFER_COUNT];
    399     /* Number of slots in ht given as 1 << ht_width. */
    400     size_t ht_width;
    401 
    402     /* The location in vb to add next cached vtable. */
    403     flatbuffers_uoffset_t vb_end;
    404     /* Where to allocate next vtable descriptor for hash table. */
    405     flatbuffers_uoffset_t vd_end;
    406     /* Ensure final buffer is aligned to at least this. Nested buffers get their own `min_align`. */
    407     uint16_t min_align;
    408     /* The current active objects alignment isolated from nested activity. */
    409     uint16_t align;
    410     /* The current buffers block alignment used when emitting buffer. */
    411     uint16_t block_align;
    412     /* Signed virtual address range used for `flatcc_builder_ref_t` and emitter. */
    413     flatcc_builder_ref_t emit_start;
    414     flatcc_builder_ref_t emit_end;
    415     /* 0 for top level, and end of buffer ref for nested buffers (can also be 0). */
    416     flatcc_builder_ref_t buffer_mark;
    417     /* Next nest_id. */
    418     flatbuffers_uoffset_t nest_count;
    419     /* Unique id to prevent sharing of vtables across buffers. */
    420     flatbuffers_uoffset_t nest_id;
    421     /* Current nesting level. Helpful to state-machines with explicit stack and to check `max_level`. */
    422     int level;
    423     /* Aggregate check for allocated frame and max_level. */
    424     int limit_level;
    425     /* Track size prefixed buffer. */
    426     uint16_t buffer_flags;
    427 
    428     /* Settings that may happen with no frame allocated. */
    429 
    430     flatcc_builder_identifier_t identifier;
    431 
    432     /* Settings that survive reset (emitter, alloc, and contexts also survive): */
    433 
    434     /* If non-zero, vtable cache gets flushed periodically. */
    435     size_t vb_flush_limit;
    436     /* If non-zero, fails on deep nesting to help drivers with a stack, such as recursive parsers etc. */
    437     int max_level;
    438     /* If non-zero, do not cluster vtables at end, only emit negative offsets (0 by default). */
    439     int disable_vt_clustering;
    440 
    441     /* Set if the default emitter is being used. */
    442     int is_default_emitter;
    443     /* Only used with default emitter. */
    444     flatcc_emitter_t default_emit_context;
    445 
    446     /* Offset to the last entered user frame on the user frame stack, after frame header, or 0. */
    447     size_t user_frame_offset;
    448 
    449     /* The offset to the end of the most recent user frame. */
    450     size_t user_frame_end;
    451 
    452     /* The optional user supplied refmap for cloning DAG's - not shared with nested buffers. */
    453     flatcc_refmap_t *refmap;
    454 };
    455 
    456 /**
    457  * Call this before any other API call.
    458  *
    459  * The emitter handles the completed chunks of the buffer that will no
    460  * longer be required by the builder. It is largely a `write` function
    461  * that can append to both positive and negative offsets.
    462  *
    463  * No memory is allocated during init. Buffers will be allocated as
    464  * needed. The `emit_context` is only used by the emitter, if at all.
    465  *
    466  * `flatcc_builder_reset/clear` calls are automtically forwarded to the
    467  * default emitter.
    468  *
    469  * Returns -1 on failure, 0 on success.
    470  */
    471 int flatcc_builder_init(flatcc_builder_t *B);
    472 
    473 /**
    474  * Use instead of `flatcc_builder_init` when providing a custom allocator
    475  * or emitter. Leave emitter or allocator null to use default.
    476  * Cleanup of emit and alloc context must be handled manually after
    477  * the builder is cleared or reset, except if emitter is null the
    478  * default will be automatically cleared and reset.
    479  *
    480  * Returns -1 on failure, 0 on success.
    481  */
    482 int flatcc_builder_custom_init(flatcc_builder_t *B,
    483         flatcc_builder_emit_fun *emit, void *emit_context,
    484         flatcc_builder_alloc_fun *alloc, void *alloc_context);
    485 
    486 /*
    487  * Returns (flatcc_emitter_t *) if the default context is used.
    488  * Other emitter might have null contexts.
    489  */
    490 void *flatcc_builder_get_emit_context(flatcc_builder_t *B);
    491 
    492 /**
    493  * Prepares builder for a new build. The emitter is not told when a
    494  * buffer is finished or when a new begins, and must be told so
    495  * separately. Allocated buffers will be zeroed, but may optionally be
    496  * reduced to their defaults (signalled by reallocating each non-empty
    497  * buffer to a single byte). General settings are cleared optionally,
    498  * such as cache flushing. Buffer specific settings such as buffer
    499  * identifier are always cleared.
    500  *
    501  * Returns -1 if allocator complains during buffer reduction, 0 on
    502  * success.
    503  */
    504 int flatcc_builder_custom_reset(flatcc_builder_t *B,
    505         int reduce_buffers, int set_defaults);
    506 
    507 /*
    508  * Same as `flatcc_builder_custom_reset` with default arguments
    509  * where buffers are not reduced and default settings are not reset.
    510  */
    511 int flatcc_builder_reset(flatcc_builder_t *B);
    512 
    513 /**
    514  * Deallocates all memory by calling allocate with a zero size request
    515  * on each buffer, then zeroing the builder structure itself.
    516  */
    517 void flatcc_builder_clear(flatcc_builder_t *B);
    518 
    519 /**
    520  * Allocates to next higher power of 2 using system realloc and ignores
    521  * `alloc_context`. Only reduces size if a small subsequent increase in
    522  * size would not trigger a reallocation. `alloc_type` is used to
    523  * set minimum sizes. Hash tables are allocated to the exact requested
    524  * size. See also `alloc_fun`.
    525  */
    526 int flatcc_builder_default_alloc(void *alloc_context,
    527         flatcc_iovec_t *b, size_t request, int zero_fill, int alloc_type);
    528 
    529 /**
    530  * If non-zero, the vtable cache will get flushed whenever it reaches
    531  * the given limit at a point in time where more space is needed. The
    532  * limit is not exact as it is only tested when reallocation is
    533  * required.
    534  */
    535 void flatcc_builder_set_vtable_cache_limit(flatcc_builder_t *B, size_t size);
    536 
    537 /**
    538  * Manual flushing of vtable for long running tasks. Mostly used
    539  * internally to deal with nested buffers.
    540  */
    541 void flatcc_builder_flush_vtable_cache(flatcc_builder_t *B);
    542 
    543 /**
    544  * Low-level support function to aid in constructing nested buffers without
    545  * allocation. Not for regular use.
    546  *
    547  * Call where `start_buffer` would have been placed when using
    548  * `create_buffer` in a nested context. Save the return value on a stack
    549  * as argument to `pop_buffer_alignment`.
    550  *
    551  * The call resets the current derived buffer alignment so the nested
    552  * buffer will not be aligned to more than required.
    553  *
    554  * Often it will not be necessary to be so careful with alignment since
    555  * the alignment cannot be invalid by failing to use push and pop, but
    556  * for code generation it will ensure the correct result every time.
    557  */
    558 uint16_t flatcc_builder_push_buffer_alignment(flatcc_builder_t *B);
    559 
    560 /**
    561  * Low-level call.
    562  *
    563  * Call with the return value from push_buffer_alignment after a nested
    564  * `create_buffer_call`. The alignments merge back up in the buffer
    565  * hierarchy so the top level buffer gets the largest of all aligments.
    566  */
    567 void flatcc_builder_pop_buffer_alignment(flatcc_builder_t *B, uint16_t buffer_align);
    568 
    569 /**
    570  * This value may be of interest when the buffer has been ended, for
    571  * example when subsequently allocating memory for the buffer to ensure
    572  * that memory is properly aligned.
    573  */
    574 uint16_t flatcc_builder_get_buffer_alignment(flatcc_builder_t *B);
    575 
    576 /**
    577  * Level 0 means no buffer is started, otherwise it increments with
    578  * start calls and decrements with end calls (approximately for
    579  * optimized operations such as table vectors).
    580  *
    581  * If `max_level` has been set, `get_level` always returns a value <=
    582  * `max_level` provided no start call has failed.
    583  *
    584  * Level continues to increment inside nested buffers.
    585  */
    586 int flatcc_builder_get_level(flatcc_builder_t *B);
    587 
    588 /**
    589  * Setting the max level triggers a failure on start of new nestings
    590  * when the level is reached. May be used to protect recursive descend
    591  * parsers etc. or later buffer readers.
    592  *
    593  * The builder itself is not sensitive to depth, and the allocator is a
    594  * better way to protect resource abuse.
    595  *
    596  * `max_level` is not reset inside nested buffers.
    597  */
    598 void flatcc_builder_set_max_level(flatcc_builder_t *B, int level);
    599 
    600 /**
    601  * By default ordinary data such as tables are placed in front of
    602  * earlier produced content and vtables are placed at the very end thus
    603  * clustering vtables together. This can be disabled so all content is
    604  * placed in front. Nested buffers ignores this setting because they can
    605  * only place content in front because they cannot blend with the
    606  * containing buffers content. Clustering could be more cache friendly
    607  * and also enables pre-shipping of the vtables during transmission.
    608  */
    609 void flatcc_builder_set_vtable_clustering(flatcc_builder_t *B, int enable);
    610 
    611 /**
    612  * Sets a new user supplied refmap which maps source pointers to
    613  * references and returns the old refmap, or null. It is also
    614  * possible to disable an existing refmap by setting a null
    615  * refmap.
    616  *
    617  * A clone or pick operation may use this map when present,
    618  * depending on the data type. If a hit is found, the stored
    619  * reference will be used instead of performing a new clone or
    620  * pick operation. It is also possible to manually populate the
    621  * refmap. Note that the builder does not have a concept of
    622  * clone or pick - these are higher level recursive operations
    623  * to add data from one buffer to another - but such code may
    624  * rely on the builder to provide the current refmap during
    625  * recursive operations. For this reason, the builder makes no
    626  * calls to the refmap interface on its own - it just stores the
    627  * current refmap such that recursive operations can find it.
    628  *
    629  * Refmaps MUST be reset, replaced or disabled if a source
    630  * pointer may be reused for different purposes - for example if
    631  * repeatedly reading FlatBuffers into the same memory buffer
    632  * and performing a clone into a buffer under construction.
    633  * Refmaps may also be replaced if the same object is to be
    634  * cloned several times keeping the internal DAG structure
    635  * intact with every new clone being an independent object.
    636  *
    637  * Refmaps must also be replaced or disabled prior to starting a
    638  * nested buffer and after stopping it, or when cloning a object
    639  * as a nested root. THIS IS VERY EASY TO GET WRONG!  The
    640  * builder does a lot of bookkeeping for nested buffers but not
    641  * in this case. Shared references may happen and they WILL fail
    642  * verification and they WILL break when copying out a nested
    643  * buffer to somewhere else. The user_frame stack may be used
    644  * for pushing refmaps, but often user codes recursive stack
    645  * will work just as well.
    646  *
    647  * It is entirely optional to use refmaps when cloning - they
    648  * preserve DAG structure and may speed up operations or slow
    649  * them down, depending on the source material.
    650  *
    651  * Refmaps may consume a lot of space when large offset vectors
    652  * are cloned when these do not have significant shared
    653  * references. They may also be very cheap to use without any
    654  * dynamic allocation when objects are small and have at most a
    655  * few references.
    656  *
    657  * Refmaps only support init, insert, find, reset, clear but not
    658  * delete. There is a standard implementation in the runtime
    659  * source tree but it can easily be replaced compile time and it
    660  * may also be left out if unused. The builder wraps reset, insert,
    661  * and find so the user does not have to check if a refmap is
    662  * present but other operations must be done direcly on the
    663  * refmap.
    664  *
    665  * The builder wrapped refmap operations are valid on a null
    666  * refmap which will find nothing and insert nothing.
    667  *
    668  * The builder will reset the refmap during a builder reset and
    669  * clear the refmap during a builder clear operation. If the
    670  * refmap goes out of scope before that happens it is important
    671  * to call set_refmap with null and manually clear the refmap.
    672  */
    673 static inline flatcc_refmap_t *flatcc_builder_set_refmap(flatcc_builder_t *B, flatcc_refmap_t *refmap)
    674 {
    675     flatcc_refmap_t *refmap_old;
    676 
    677     refmap_old = B->refmap;
    678     B->refmap = refmap;
    679     return refmap_old;
    680 }
    681 
    682 /* Retrieves the current refmap, or null. */
    683 static inline flatcc_refmap_t *flatcc_builder_get_refmap(flatcc_builder_t *B)
    684 {
    685     return B->refmap;
    686 }
    687 
    688 /* Finds a reference, or a null reference if no refmap is active.  * */
    689 static inline flatcc_builder_ref_t flatcc_builder_refmap_find(flatcc_builder_t *B, const void *src)
    690 {
    691     return B->refmap ? flatcc_refmap_find(B->refmap, src) : flatcc_refmap_not_found;
    692 }
    693 
    694 /*
    695  * Inserts into the current refmap with the inseted ref upon
    696  * upon success, or not_found on failure (default 0), or just
    697  * returns ref if refmap is absent.
    698  *
    699  * Note that if an existing item exists, the ref is replaced
    700  * and the new, not the old, ref is returned.
    701  */
    702 static inline flatcc_builder_ref_t flatcc_builder_refmap_insert(flatcc_builder_t *B, const void *src, flatcc_builder_ref_t ref)
    703 {
    704     return B->refmap ? flatcc_refmap_insert(B->refmap, src, ref) : ref;
    705 }
    706 
    707 static inline void flatcc_builder_refmap_reset(flatcc_builder_t *B)
    708 {
    709     if (B->refmap) flatcc_refmap_reset(B->refmap);
    710 }
    711 
    712 
    713 typedef uint16_t flatcc_builder_buffer_flags_t;
    714 static const flatcc_builder_buffer_flags_t flatcc_builder_is_nested = 1;
    715 static const flatcc_builder_buffer_flags_t flatcc_builder_with_size = 2;
    716 
    717 /* The flag size in the API needs to match the internal size. */
    718 static_assert(sizeof(flatcc_builder_buffer_flags_t) ==
    719               sizeof(((flatcc_builder_t *)0)->buffer_flags), "flag size mismatch");
    720 
    721 /**
    722  * An alternative to start buffer, start struct/table ... end buffer.
    723  *
    724  * This call is mostly of interest as a means to quicly create a zero
    725  * allocation top-level buffer header following a call to create_struct,
    726  * or to create_vtable/create_table. For that, it is quite simple to
    727  * use. For general buffer construction without allocation, more care is
    728  * needed, as discussed below.
    729  *
    730  * If the content is created with `start/end_table` calls, or similar,
    731  * it is better to use `start/end_buffer` since stack allocation is used
    732  * anyway.
    733  *
    734  * The buffer alignment must be provided manually as it is not derived
    735  * from constructed content, unlike `start/end_buffer`. Typically
    736  * `align` would be same argument as provided to `create_struct`.
    737  * `get_buffer_alignment` may also used (note: `get_buffer_alignment`
    738  * may return different after the call because it will be updated with
    739  * the `block_align` argument to `create_buffer` but that is ok).
    740  *
    741  * The buffer may be constructed as a nested buffer with the `is_nested
    742  * = 1` flag. As a nested buffer a ubyte vector header is placed before
    743  * the aligned buffer header. A top-level buffer will normally have
    744  * flags set to 0.
    745  *
    746  * A top-level buffer may also be constructed with the `with_size = 2`
    747  * flag for top level buffers. It adds a size prefix similar to
    748  * `is_nested` but the size is part of the aligned buffer. A size
    749  * prefixed top level buffer must be accessed with a size prefix aware
    750  * reader, or the buffer given to a standard reader must point to after
    751  * the size field while keeping the buffer aligned to the size field
    752  * (this will depend on the readers API which may be an arbitrary other
    753  * language).
    754  *
    755  * If the `with_size` is used with the `is_nested` flag, the size is
    756  * added as usual and all fields remain aligned as before, but padding
    757  * is adjusted to ensure the buffer is aligned to the size field so
    758  * that, for example, the nested buffer with size can safely be copied
    759  * to a new memory buffer for consumption.
    760  *
    761  * Generally, references may only be used within the same buffer
    762  * context. With `create_buffer` this becomes less precise. The rule
    763  * here is that anything that would be valid with start/end_buffer
    764  * nestings is also valid when removing the `start_buffer` call and
    765  * replacing `end_buffer` with `create_buffer`.
    766  *
    767  * Note the additional burden of tracking buffer alignment manually -
    768  * To help with this use `push_buffer_alignment` where `start_buffer`
    769  * would have been placed, and  `pop_buffer_alignment after the
    770  * `create_buffer` call, and use `get_buffer_alignemnt` as described
    771  * above.
    772  *
    773  * `create_buffer` is not suitable as a container for buffers created
    774  * with `start/end_buffer` as these make assumptions about context that
    775  * create buffer does not provide. Also, there is no point in doing so,
    776  * since the idea of `create_buffer` is to avoid allocation in the first
    777  * place.
    778  */
    779 flatcc_builder_ref_t flatcc_builder_create_buffer(flatcc_builder_t *B,
    780         const char identifier[FLATBUFFERS_IDENTIFIER_SIZE],
    781         uint16_t block_align,
    782         flatcc_builder_ref_t ref, uint16_t align, flatcc_builder_buffer_flags_t flags);
    783 
    784 /**
    785  * Creates a struct within the current buffer without using any
    786  * allocation.
    787  *
    788  * The struct should be used as a root in the `end_buffer` call or as a
    789  * union value as there are no other ways to use struct while conforming
    790  * to the FlatBuffer format - noting that tables embed structs in their
    791  * own data area except in union fields.
    792  *
    793  * The struct should be in little endian format and follow the usual
    794  * FlatBuffers alignment rules, although this API won't care about what
    795  * is being stored.
    796  *
    797  * May also be used to simply emit a struct through the emitter
    798  * interface without being in a buffer and without being a valid
    799  * FlatBuffer.
    800  */
    801 flatcc_builder_ref_t flatcc_builder_create_struct(flatcc_builder_t *B,
    802         const void *data, size_t size, uint16_t align);
    803 
    804 /**
    805  * Starts a struct and returns a pointer that should be used immediately
    806  * to fill in the struct in protocol endian format, and when done,
    807  * `end_struct` should be called. The returned reference should be used
    808  * as argument to `end_buffer` or as a union value. See also
    809  * `create_struct`.
    810  */
    811 void *flatcc_builder_start_struct(flatcc_builder_t *B,
    812         size_t size, uint16_t align);
    813 
    814 /**
    815  * Return a pointer also returned at start struct, e.g. for endian
    816  * conversion.
    817  */
    818 void *flatcc_builder_struct_edit(flatcc_builder_t *B);
    819 
    820 /**
    821  * Emits the struct started by `start_struct` and returns a reference to
    822  * be used as root in an enclosing `end_buffer` call or as a union
    823  * value.  As mentioned in `create_struct`, these can also be used more
    824  * freely, but not while being conformant FlatBuffers.
    825  */
    826 flatcc_builder_ref_t flatcc_builder_end_struct(flatcc_builder_t *B);
    827 
    828 /**
    829  * The buffer always aligns to at least the offset size (typically 4)
    830  * and the internal alignment requirements of the buffer content which
    831  * is derived as content is added.
    832  *
    833  * In addition, block_align can be specified. This ensures the resulting
    834  * buffer is at least aligned to the block size and that the total size
    835  * is zero padded to fill a block multiple if necessary. Because the
    836  * emitter operates on a virtual address range before the full buffer is
    837  * aligned, it may have to make assumptions based on that: For example,
    838  * it may be processing encryption blocks in the fly, and the resulting
    839  * buffer should be aligned to the encryption block size, even if the
    840  * content is just a byte aligned struct. Block align helps ensure this.
    841  * If the block align as 1 there will be no attempt to zero pad at the
    842  * end, but the content may still warrant padding after the header. End
    843  * padding is only needed with clustered vtables (which is the default).
    844  *
    845  * `block_align` is allowed to be 0 meaning it will inherit from parent if
    846  * present, and otherwise it defaults to 1.
    847  *
    848  * The identifier may be null, and it may optionally be set later with
    849  * `set_identifier` before the `end_buffer` call.
    850  *
    851  * General note:
    852  *
    853  * Only references returned with this buffer as current (i.e. last
    854  * unended buffer) can be stored in other objects (tables, offset
    855  * vectors) also belonging to this buffer, or used as the root argument
    856  * to `end_buffer`. A reference may be stored at most once, and unused
    857  * references will result in buffer garbage. All calls must be balanced
    858  * around the respective start / end operations, but may otherwise nest
    859  * freely, including nested buffers. Nested buffers are supposed to be
    860  * stored in a table offset field to comply with FlatBuffers, but the
    861  * API does not place any restrictions on where references are stored,
    862  * as long as they are indicated as offset fields.
    863  *
    864  * All alignment in all API calls must be between 1 and 256 and must be a
    865  * power of 2. This is not checked. Only if explicitly documented can it
    866  * also be 0 for a default value.
    867  *
    868  * `flags` can be `with_size` but `is_nested` is derived from context
    869  * see also `create_buffer`.
    870  */
    871 int flatcc_builder_start_buffer(flatcc_builder_t *B,
    872         const char identifier[FLATBUFFERS_IDENTIFIER_SIZE],
    873         uint16_t block_align, flatcc_builder_buffer_flags_t flags);
    874 
    875 /**
    876  * The root object should be a struct or a table to conform to the
    877  * FlatBuffers format, but technically it can also be a vector or a
    878  * string, or even a child buffer (which is also vector as seen by the
    879  * buffer). The object must be created within the current buffer
    880  * context, that is, while the current buffer is the deepest nested
    881  * buffer on the stack.
    882  */
    883 flatcc_builder_ref_t flatcc_builder_end_buffer(flatcc_builder_t *B, flatcc_builder_ref_t root);
    884 
    885 /**
    886  * The embed buffer is mostly intended to add an existing buffer as a
    887  * nested buffer. The buffer will be wrapped in a ubyte vector such that
    888  * the buffer is aligned at vector start, after the size field.
    889  *
    890  * If `align` is 0 it will default to 8 so that all FlatBuffer numeric
    891  * types will be readable. NOTE: generally do not count on align 0 being
    892  * valid or even checked by the API, but in this case it may be
    893  * difficult to know the internal buffer alignment, and 1 would be the wrong
    894  * choice.
    895  *
    896  * If `block_align` is set (non-zero), the buffer is placed in an isolated
    897  * block multiple. This may cost up to almost 2 block sizes in padding.
    898  * If the `block_align` argument is 0, it inherits from the parent
    899  * buffer block_size, or defaults to 1.
    900  *
    901  * The `align` argument must be set to respect the buffers internal
    902  * alignment requirements, but if the buffer is smaller it will not be
    903  * padded to isolate the buffer. For example a buffer of with
    904  * `align = 64` and `size = 65` may share its last 64 byte block with
    905  * other content, but not if `block_align = 64`.
    906  *
    907  * Because the ubyte size field is not, by default, part of the aligned
    908  * buffer, significant space can be wasted if multiple blocks are added
    909  * in sequence with a large block size.
    910  *
    911  * In most cases the distinction between the two alignments is not
    912  * important, but it allows separate configuration of block internal
    913  * alignment and block size, which can be important for auto-generated
    914  * code that may know the alignment of the buffer, but not the users
    915  * operational requirements.
    916  *
    917  * If the buffer is embedded without a parent buffer, it will simply
    918  * emit the buffer through the emit interface, but may also add padding
    919  * up to block alignment. At top-level there will be no size field
    920  * header.
    921  *
    922  * If `with_size` flag is set, the buffer is aligned to size field and
    923  * the above note about padding space no longer applies. The size field
    924  * is added regardless. The `is_nested` flag has no effect since it is
    925  * impplied.
    926  */
    927 flatcc_builder_ref_t flatcc_builder_embed_buffer(flatcc_builder_t *B,
    928         uint16_t block_align,
    929         const void *data, size_t size, uint16_t align, flatcc_builder_buffer_flags_t flags);
    930 
    931 /**
    932  * Applies to the innermost open buffer. The identifier may be null or
    933  * contain all zero. Overrides any identifier given to the start buffer
    934  * call.
    935  */
    936 void flatcc_builder_set_identifier(flatcc_builder_t *B,
    937         const char identifier[FLATBUFFERS_IDENTIFIER_SIZE]);
    938 
    939 enum flatcc_builder_type {
    940     flatcc_builder_empty = 0,
    941     flatcc_builder_buffer,
    942     flatcc_builder_struct,
    943     flatcc_builder_table,
    944     flatcc_builder_vector,
    945     flatcc_builder_offset_vector,
    946     flatcc_builder_string,
    947     flatcc_builder_union_vector
    948 };
    949 
    950 /**
    951  * Returns the object type currently on the stack, for example if
    952  * needing to decide how to close a buffer. Because a table is
    953  * automatically added when starting a table buffer,
    954  * `flatcc_builder_table_buffer` should not normally be seen and the level
    955  * should be 2 before when closing a top-level table buffer, and 0
    956  * after. A `flatcc_builder_struct_buffer` will be visible at level 1.
    957  *
    958  */
    959 enum flatcc_builder_type flatcc_builder_get_type(flatcc_builder_t *B);
    960 
    961 /**
    962  * Similar to `get_type` but for a specific level. `get_type_at(B, 1)`
    963  * will return `flatcc_builder_table_buffer` if this is the root buffer
    964  * type. get_type_at(B, 0) is always `flatcc_builder_empty` and so are any
    965  * level above `get_level`.
    966  */
    967 enum flatcc_builder_type flatcc_builder_get_type_at(flatcc_builder_t *B, int level);
    968 
    969 /**
    970  * The user stack is available for custom data. It may be used as
    971  * a simple stack by extending or reducing the inner-most frame.
    972  *
    973  * A frame has a size and a location on the user stack. Entering
    974  * a frame ensures the start is aligned to sizeof(size_t) and
    975  * ensures the requested space is available without reallocation.
    976  * When exiting a frame, the previous frame is restored.
    977  *
    978  * A user frame works completely independently of the builders
    979  * frame stack for tracking tables vectors etc. and does not have
    980  * to be completely at exit, but obviously it is not valid to
    981  * exit more often the entered.
    982  *
    983  * The frame is zeroed when entered.
    984  *
    985  * Returns a non-zero handle to the user frame upon success or
    986  * 0 on allocation failure.
    987  */
    988 size_t flatcc_builder_enter_user_frame(flatcc_builder_t *B, size_t size);
    989 
    990 /**
    991  * Makes the parent user frame current, if any. It is not valid to call
    992  * if there isn't any current frame. Returns handle to parent frame if
    993  * any, or 0.
    994  */
    995 size_t flatcc_builder_exit_user_frame(flatcc_builder_t *B);
    996 
    997 /**
    998  * Exits the frame represented by the given handle. All more
    999  * recently entered frames will also be exited. Returns the parent
   1000  * frame handle if any, or 0.
   1001  */
   1002 size_t flatcc_builder_exit_user_frame_at(flatcc_builder_t *B, size_t handle);
   1003 
   1004 /**
   1005  * Returns a non-zero handle to the current inner-most user frame if
   1006  * any, or 0.
   1007  */
   1008 size_t flatcc_builder_get_current_user_frame(flatcc_builder_t *B);
   1009 
   1010 /*
   1011  * Returns a pointer to the user frame at the given handle. Any active
   1012  * frame can be accessed in this manner but the pointer is invalidated
   1013  * by user frame enter and exit operations.
   1014  */
   1015 void *flatcc_builder_get_user_frame_ptr(flatcc_builder_t *B, size_t handle);
   1016 
   1017 /**
   1018  * Returns the size of the buffer and the logical start and end address
   1019  * of with respect to the emitters address range. `end` - `start` also
   1020  * yields the size. During construction `size` is the emitted number of
   1021  * bytes and after buffer close it is the actual buffer size - by then
   1022  * the start is also the return value of close buffer. End marks the end
   1023  * of the virtual table cluster block.
   1024  *
   1025  * NOTE: there is no guarantee that all vtables end up in the cluster
   1026  * block if there is placed a limit on the vtable size, or if nested
   1027  * buffers are being used. On the other hand, if these conditions are
   1028  * met, it is guaranteed that all vtables are present if the vtable
   1029  * block is available (this depends on external transmission - the
   1030  * vtables are always emitted before tables using them). In all cases
   1031  * the vtables will behave as valid vtables in a flatbuffer.
   1032  */
   1033 size_t flatcc_builder_get_buffer_size(flatcc_builder_t *B);
   1034 
   1035 /**
   1036  * Returns the reference to the start of the emitter buffer so far, or
   1037  * in total after buffer end, in the virtual address range used
   1038  * by the emitter. Start is also returned by buffer end.
   1039  */
   1040 flatcc_builder_ref_t flatcc_builder_get_buffer_start(flatcc_builder_t *B);
   1041 
   1042 /**
   1043  * Returns the reference to the end of buffer emitted so far. When
   1044  * clustering vtables, this is the end of tables, or after buffer end,
   1045  * also zero padding if block aligned. If clustering is disabled, this
   1046  * method will return 0 as the buffer only grows down then.
   1047  */
   1048 flatcc_builder_ref_t flatcc_builder_get_buffer_mark(flatcc_builder_t *B);
   1049 
   1050 /**
   1051  * Creates the vtable in the current buffer context, somewhat similar to
   1052  * how create_vector operates. Each call results in a new table even if
   1053  * an identical has already been emitted.
   1054  *
   1055  * Also consider `create_cached_vtable` which will reuse existing
   1056  * vtables.
   1057  *
   1058  * This is low-low-level function intended to support
   1059  * `create_cached_vtable` or equivalent, and `create_table`, both of
   1060  * which are normally used indirectly via `start_table`, `table_add`,
   1061  * `table_add_offset`..., `table_end`.
   1062  *
   1063  * Creates a vtable as a verbatim copy. This means the vtable must
   1064  * include the header fields containing the vtable size and the table
   1065  * size in little endian voffset_t encoding followed by the vtable
   1066  * entries in same encoding.
   1067  *
   1068  * The function may be used to copy vtables from other other buffers
   1069  * since they are directly transferable.
   1070  *
   1071  * The returned reference is actually the emitted location + 1. This
   1072  * ensures the vtable is not mistaken for error because 0 is a valid
   1073  * vtable reference. `create_table` is aware of this and substracts one
   1074  * before computing the final offset relative to the table. This also
   1075  * means vtable references are uniquely identifiable by having the
   1076  * lowest bit set.
   1077  *
   1078  * vtable references may be reused within the same buffer, not any
   1079  * parent or other related buffer (technically this is possible though,
   1080  * as long as it is within same builder context, but it will not construct
   1081  * valid FlatBuffers because the buffer cannot be extracted in isolation).
   1082  */
   1083 flatcc_builder_vt_ref_t flatcc_builder_create_vtable(flatcc_builder_t *B,
   1084         const flatbuffers_voffset_t *vt,
   1085         flatbuffers_voffset_t vt_size);
   1086 
   1087 /**
   1088  * Support function to `create_vtable`. See also the uncached version
   1089  * `create_vtable`.
   1090  *
   1091  * Looks up the constructed vtable on the vs stack too see if it matches
   1092  * a cached entry. If not, it emits a new vtable either at the end if
   1093  * top-level and clustering is enabled, or at the front (always for
   1094  * nested buffers).
   1095  *
   1096  * If the same vtable was already emitted in a different buffer, but not
   1097  * in the current buffer, the cache entry will be reused, but a new
   1098  * table will be emitted the first it happens in the same table.
   1099  *
   1100  * The returned reference is + 1 relative to the emitted address range
   1101  * to identify it as a vtable and to avoid mistaking the valid 0
   1102  * reference for an error (clustered vtables tend to start at the end at
   1103  * the virtual address 0, and up).
   1104  *
   1105  * The hash function can be chosen arbitrarily but may result in
   1106  * duplicate emitted vtables if different hash functions are being used
   1107  * concurrently, such as mixing the default used by `start/end table`
   1108  * with a custom function (this is not incorrect, it only increases the
   1109  * buffer size and cache pressure).
   1110  *
   1111  * If a vtable has a unique ID by other means than hashing the content,
   1112  * such as an integer id, and offset into another buffer, or a pointer,
   1113  * a good hash may be multiplication by a 32-bit prime number. The hash
   1114  * table is not very sensitive to collissions as it uses externally
   1115  * chained hashing with move to front semantics.
   1116  */
   1117 flatcc_builder_vt_ref_t flatcc_builder_create_cached_vtable(flatcc_builder_t *B,
   1118         const flatbuffers_voffset_t *vt,
   1119         flatbuffers_voffset_t vt_size, uint32_t vt_hash);
   1120 
   1121 /*
   1122  * Based on Knuth's prime multiplier.
   1123  *
   1124  * This is an incremental hash that is called with id and size of each
   1125  * non-empty field, and finally with the two vtable header fields
   1126  * when vtables are constructed via `table_add/table_add_offset`.
   1127  *
   1128  */
   1129 #ifndef FLATCC_SLOW_MUL
   1130 #ifndef FLATCC_BUILDER_INIT_VT_HASH
   1131 #define FLATCC_BUILDER_INIT_VT_HASH(hash) { (hash) = (uint32_t)0x2f693b52UL; }
   1132 #endif
   1133 #ifndef FLATCC_BUILDER_UPDATE_VT_HASH
   1134 #define FLATCC_BUILDER_UPDATE_VT_HASH(hash, id, offset) \
   1135         { (hash) = (((((uint32_t)id ^ (hash)) * (uint32_t)2654435761UL)\
   1136                 ^ (uint32_t)(offset)) * (uint32_t)2654435761UL); }
   1137 #endif
   1138 #ifndef FLATCC_BUILDER_BUCKET_VT_HASH
   1139 #define FLATCC_BUILDER_BUCKET_VT_HASH(hash, width) (((uint32_t)(hash)) >> (32 - (width)))
   1140 #endif
   1141 #endif
   1142 
   1143 /*
   1144  * By default we use Bernsteins hash as fallback if multiplication is slow.
   1145  *
   1146  * This just have to be simple, fast, and work on devices without fast
   1147  * multiplication. We are not too sensitive to collisions. Feel free to
   1148  * experiment and replace.
   1149  */
   1150 #ifndef FLATCC_BUILDER_INIT_VT_HASH
   1151 #define FLATCC_BUILDER_INIT_VT_HASH(hash) { (hash) = 5381; }
   1152 #endif
   1153 #ifndef FLATCC_BUILDER_UPDATE_VT_HASH
   1154 #define FLATCC_BUILDER_UPDATE_VT_HASH(hash, id, offset) \
   1155         { (hash) = ((((hash) << 5) ^ (id)) << 5) ^ (offset); }
   1156 #endif
   1157 #ifndef FLATCC_BUILDER_BUCKET_VT_HASH
   1158 #define FLATCC_BUILDER_BUCKET_VT_HASH(hash, width) (((1 << (width)) - 1) & (hash))
   1159 #endif
   1160 
   1161 
   1162 
   1163 /**
   1164  * Normally use `start_table` instead of this call.
   1165  *
   1166  * This is a low-level call only intended for high-performance
   1167  * applications that repeatedly churn about similar tables of known
   1168  * layout, or as a support layer for other builders that maintain their
   1169  * own allocation rather than using the stack of this builder.
   1170  *
   1171  * Creates a table from an already emitted vtable, actual data that is
   1172  * properly aligned relative to data start and in little endian
   1173  * encoding. Unlike structs, tables can have offset fields. These must
   1174  * be stored as flatcc_builder_ref_t types (which have uoffset_t size) as
   1175  * returned by the api in native encoding. The `offsets` table contain
   1176  * voffsets relative to `data` start (this is different from how vtables
   1177  * store offsets because they are relative to a table header). The
   1178  * `offsets` table is only used temporarily to translate the stored
   1179  * references and is not part of final buffer content. `offsets` may be
   1180  * null if `offset_count` is 0. `align` should be the highest aligned
   1181  * field in the table, but `size` need not be a multiple of `align`.
   1182  * Aside from endian encoding, the vtable must record a table size equal
   1183  * to `size + sizeof(flatbuffers_uoffset_t)` because it includes the
   1184  * table header field size. The vtable is not accessed by this call (nor
   1185  * is it available). Unlike other references, the vtable reference may
   1186  * be shared between tables in the same buffer (not with any related
   1187  * buffer such as a parent buffer).
   1188  *
   1189  * The operation will not use any allocation, but will update the
   1190  * alignment of the containing buffer if any.
   1191  *
   1192  * Note: unlike other create calls, except `create_offset_vector`,
   1193  * the source data is modified in order to translate references intok
   1194  * offsets before emitting the table.
   1195  */
   1196 flatcc_builder_ref_t flatcc_builder_create_table(flatcc_builder_t *B,
   1197         const void *data, size_t size, uint16_t align,
   1198         flatbuffers_voffset_t *offsets, int offset_count,
   1199         flatcc_builder_vt_ref_t vt_ref);
   1200 
   1201 /**
   1202  * Starts a table, typically following a start_buffer call as an
   1203  * alternative to starting a struct, or to create table fields to be
   1204  * stored in a parent table, or in an offset vector.
   1205  * A number of `table_add` and table_add_offset` call may be placed
   1206  * before the `end_table` call. Struct fields should NOT use `struct`
   1207  * related call (because table structs are in-place), rather they should
   1208  * use the `table_add` call with the appropriate size and alignment.
   1209  *
   1210  * A table, like other reference returning calls, may also be started
   1211  * outside a buffer if the buffer header and alignment is of no
   1212  * interest to the application, for example as part of an externally
   1213  * built buffer.
   1214  *
   1215  * `count` must be larger than the largest id used for this table
   1216  * instance. Normally it is set to the number of fields defined in the
   1217  * schema, but it may be less if memory is constrained and only few
   1218  * fields with low valued id's are in use. The count can extended later
   1219  * with `reserve_table` if necessary. `count` may be also be set to a
   1220  * large enough value such as FLATBUFFERS_ID_MAX + 1 if memory is not a
   1221  * concern (reserves about twice the maximum vtable size to track the
   1222  * current vtable and voffsets where references must be translated to
   1223  * offsets at table end). `count` may be zero if for example
   1224  * `reserve_table` is being used.
   1225  *
   1226  * Returns -1 on error, 0 on success.
   1227  */
   1228 int flatcc_builder_start_table(flatcc_builder_t *B, int count);
   1229 
   1230 /**
   1231  * Call before adding a field with an id that is not below the count set
   1232  * at table start. Not needed in most cases. For performance reasons
   1233  * the builder does not check all bounds all the the time, but the user
   1234  * can do so if memory constraints prevent start_table from using a
   1235  * conservative value. See also `table_start`.
   1236  *
   1237  * Note: this call has absolutely no effect on the table layout, it just
   1238  * prevents internal buffer overruns.
   1239  *
   1240  * Returns -1 on error, 0 on success.
   1241  */
   1242 int flatcc_builder_reserve_table(flatcc_builder_t *B, int count);
   1243 
   1244 /**
   1245  * Completes the table constructed on the internal stack including
   1246  * emitting a vtable, or finding a matching vtable that has already been
   1247  * emitted to the same buffer. (Vtables cannot be shared between
   1248  * buffers, but they can between tables of the same buffer).
   1249  *
   1250  * Note: there is a considerable, but necessary, amount of bookkeeping
   1251  * involved in constructing tables. The `create_table` call is much
   1252  * faster, but it also expects a lot of work to be done already.
   1253  *
   1254  * Tables can be created with no fields added. This will result in an
   1255  * empty vtable and a table with just a vtable reference. If a table is
   1256  * used as a sub-table, such a table might also not be stored at all,
   1257  * but we do not return a special reference for that, nor do we provide
   1258  * and option to not create the table in this case. This may be
   1259  * interpreted as the difference between a null table (not stored in
   1260  * parent), and an empty table with a unique offset (and thus identity)
   1261  * different from other empty tables.
   1262  */
   1263 flatcc_builder_ref_t flatcc_builder_end_table(flatcc_builder_t *B);
   1264 
   1265 /**
   1266  * Optionally this method can be called just before `flatcc_builder_end_table`
   1267  * to verify that all required fields have been set.
   1268  * Each entry is a table field id.
   1269  *
   1270  * Union fields should use the type field when checking for presence and
   1271  * may also want to check the soundness of the union field overall using
   1272  * `check_union_field` with the id one higher than the type field id.
   1273  *
   1274  * This funcion is typically called by an assertion in generated builder
   1275  * interfaces while release builds may want to avoid this performance
   1276  * overhead.
   1277  *
   1278  * Returns 1 if all fields are matched, 0 otherwise.
   1279  */
   1280 int flatcc_builder_check_required(flatcc_builder_t *B, const flatbuffers_voffset_t *required, int count);
   1281 
   1282 /**
   1283  * Same as `check_required` when called with a single element.
   1284  *
   1285  * Typically used when direct calls are more convenient than building an
   1286  * array first. Useful when dealing with untrusted intput such as parsed
   1287  * text from an external source.
   1288  */
   1289 int flatcc_builder_check_required_field(flatcc_builder_t *B, flatbuffers_voffset_t id);
   1290 
   1291 /**
   1292  * Checks that a union field is valid.
   1293  *
   1294  * The criteria is:
   1295  *
   1296  * If the type field is not present (at id - 1), or it holds a zero value,
   1297  * then the table field (at id) must be present.
   1298  *
   1299  * Generated builder code may be able to enforce valid unions without
   1300  * this check by setting both type and table together, but e.g. parsers
   1301  * may receive the type and the table independently and then it makes
   1302  * sense to validate the union fields before table completion.
   1303  *
   1304  * Note that an absent union field is perfectly valid. If a union is
   1305  * required, the type field (id - 1), should be checked separately
   1306  * while the table field should only be checked here because it can
   1307  * (and must) be absent when the type is NONE (= 0).
   1308  */
   1309 int flatcc_builder_check_union_field(flatcc_builder_t *B, flatbuffers_voffset_t id);
   1310 
   1311 /**
   1312  * A struct, enum or scalar added should be stored in little endian in
   1313  * the return pointer location. The pointer is short lived and will
   1314  * not necessarily survive other builder calls.
   1315  *
   1316  * A union type field can also be set using this call. In fact, this is
   1317  * the only way to deal with unions via this API. Consequently, it is
   1318  * the users repsonsibility to ensure the appropriate type is added
   1319  * at the next higher id.
   1320  *
   1321  * Null and default values:
   1322  *
   1323  * FlatBuffers does not officially  provide an option for null values
   1324  * because it does not distinguish between default values and values
   1325  * that are not present. At this api level, we do not deal with defaults
   1326  * at all. Callee should test the stored value against the default value
   1327  * and only add the field if it does not match the default. This only
   1328  * applies to scalar and enum values. Structs cannot have defaults so
   1329  * their absence means null, and strings, vectors and subtables do have
   1330  * natural null values different from the empty object and empty objects
   1331  * with different identity is also possible.
   1332  *
   1333  * To handle Null for scalars, the following approach is recommended:
   1334  *
   1335  * Provide a schema-specific `add` operation that only calls this
   1336  * low-level add method if the default does not match, and also provide
   1337  * another `set` operation that always stores the value, regardless of
   1338  * default. For most readers this will be transparent, except for extra
   1339  * space used, but for Null aware readers, these can support operations
   1340  * to test for Null/default/other value while still supporting the
   1341  * normal read operation that returns default when a value is absent
   1342  * (i.e. Null).
   1343  *
   1344  * It is valid to call with a size of 0 - the effect being adding the
   1345  * vtable entry. The call may also be dropped in this case to reduce
   1346  * the vtable size - the difference will be in null detection.
   1347  */
   1348 void *flatcc_builder_table_add(flatcc_builder_t *B, int id, size_t size, uint16_t align);
   1349 
   1350 /**
   1351  * Returns a pointer to the buffer holding the last field added. The
   1352  * size argument must match the field size added. May, for example, be
   1353  * used to perform endian conversion after initially updating field
   1354  * as a native struct. Must be called before the table is ended.
   1355  */
   1356 void *flatcc_builder_table_edit(flatcc_builder_t *B, size_t size);
   1357 
   1358 /**
   1359  * Similar to `table_add` but copies source data into the buffer before
   1360  * it is returned. Useful when adding a larger struct already encoded in
   1361  * little endian.
   1362  */
   1363 void *flatcc_builder_table_add_copy(flatcc_builder_t *B, int id, const void *data, size_t size, uint16_t align);
   1364 
   1365 /**
   1366  * Add a string, vector, or sub-table depending on the type if the
   1367  * field identifier. The offset ref obtained when the field object was
   1368  * closed should be stored as is in the given pointer. The pointer
   1369  * is only valid short term, so create the object before calling
   1370  * add to table, but the owner table can be started earlier. Never mix
   1371  * refs from nested buffers with parent buffers.
   1372  *
   1373  * Also uses this method to add nested buffers. A nested buffer is
   1374  * simple a buffer created while another buffer is open. The buffer
   1375  * close operation provides the necessary reference.
   1376  *
   1377  * When the table closes, all references get converted into offsets.
   1378  * Before that point, it is not required that the offset is written
   1379  * to.
   1380  */
   1381 flatcc_builder_ref_t *flatcc_builder_table_add_offset(flatcc_builder_t *B, int id);
   1382 
   1383 /*
   1384  * Adds a union type and reference in a single operation and returns 0
   1385  * on success. Stores the type field at `id - 1` and the value at
   1386  * `id`. The `value` is a reference to a table, to a string, or to a
   1387  * standalone `struct` outside the table.
   1388  *
   1389  * If the type is 0, the value field must also be 0.
   1390  *
   1391  * Unions can also be added as separate calls to the type and the offset
   1392  * separately which can lead to better packing when the type is placed
   1393  * together will other small fields.
   1394  */
   1395 int flatcc_builder_table_add_union(flatcc_builder_t *B, int id,
   1396         flatcc_builder_union_ref_t uref);
   1397 
   1398 /*
   1399  * Adds a union type vector and value vector in a single operations
   1400  * and returns 0 on success.
   1401  *
   1402  * If both the type and value vector is null, nothing is added.
   1403  * Otherwise both must be present and have the same length.
   1404  *
   1405  * Any 0 entry in the type vector must also have a 0 entry in
   1406  * the value vector.
   1407  */
   1408 int flatcc_builder_table_add_union_vector(flatcc_builder_t *B, int id,
   1409         flatcc_builder_union_vec_ref_t uvref);
   1410 /**
   1411  * Creates a vector in a single operation using an externally supplied
   1412  * buffer. This completely bypasses the stack, but the size must be
   1413  * known and the content must be little endian. Do not use for strings
   1414  * and offset vectors. Other flatbuffer vectors could be used as a
   1415  * source, but the length prefix is not required.
   1416  *
   1417  * Set `max_count` to `FLATBUFFERS_COUNT_MAX(elem_size)` before a call
   1418  * to any string or vector operation to the get maximum safe vector
   1419  * size, or use (size_t)-1 if overflow is not a concern.
   1420  *
   1421  * The max count property is a global property that remains until
   1422  * explicitly changed.
   1423  *
   1424  * `max_count` is to prevent malicous or accidental overflow which is
   1425  * difficult to detect by multiplication alone, depending on the type
   1426  * sizes being used and having `max_count` thus avoids a division for
   1427  * every vector created. `max_count` does not guarantee a vector will
   1428  * fit in an empty buffer, it just ensures the internal size checks do
   1429  * not overflow. A safe, sane limit woud be max_count / 4 because that
   1430  * is half the maximum buffer size that can realistically be
   1431  * constructed, corresponding to a vector size of `UOFFSET_MAX / 4`
   1432  * which can always hold the vector in 1GB excluding the size field when
   1433  * sizeof(uoffset_t) = 4.
   1434  */
   1435 flatcc_builder_ref_t flatcc_builder_create_vector(flatcc_builder_t *B,
   1436         const void *data, size_t count, size_t elem_size, uint16_t align, size_t max_count);
   1437 
   1438 /**
   1439  * Starts a vector on the stack.
   1440  *
   1441  * Do not use these calls for string or offset vectors, but do store
   1442  * scalars, enums and structs, always in little endian encoding.
   1443  *
   1444  * Use `extend_vector` subsequently to add zero, one or more elements
   1445  * at time.
   1446  *
   1447  * See `create_vector` for `max_count` argument (strings and offset
   1448  * vectors have a fixed element size and does not need this argument).
   1449  *
   1450  * Returns 0 on success.
   1451  */
   1452 int flatcc_builder_start_vector(flatcc_builder_t *B, size_t elem_size,
   1453         uint16_t align, size_t max_count);
   1454 
   1455 /**
   1456  * Emits the vector constructed on the stack by start_vector.
   1457  *
   1458  * The vector may be accessed in the emitted stream using the returned
   1459  * reference, even if the containing buffer is still under construction.
   1460  * This may be useful for sorting. This api does not support sorting
   1461  * because offset vectors cannot read their references after emission,
   1462  * and while plain vectors could be sorted, it has been chosen that this
   1463  * task is better left as a separate processing step. Generated code can
   1464  * provide sorting functions that work on final in-memory buffers.
   1465  */
   1466 flatcc_builder_ref_t flatcc_builder_end_vector(flatcc_builder_t *B);
   1467 
   1468 /** Returns the number of elements currently on the stack. */
   1469 size_t flatcc_builder_vector_count(flatcc_builder_t *B);
   1470 
   1471 /**
   1472  * Returns a pointer ot the first vector element on stack,
   1473  * accessible up to the number of elements currently on stack.
   1474  */
   1475 void *flatcc_builder_vector_edit(flatcc_builder_t *B);
   1476 
   1477 /**
   1478  * Returns a zero initialized buffer to a new region of the vector which
   1479  * is extended at the end. The buffer must be consumed before other api
   1480  * calls that may affect the stack, including `extend_vector`.
   1481  *
   1482  * Do not use for strings, offset or union vectors. May be used for nested
   1483  * buffers, but these have dedicated calls to provide better alignment.
   1484  */
   1485 void *flatcc_builder_extend_vector(flatcc_builder_t *B, size_t count);
   1486 
   1487 /**
   1488  * A specialized `vector_extend` that pushes a single element.
   1489  *
   1490  * Returns the buffer holding a modifiable copy of the added content,
   1491  * or null on error. Note: for structs, care must be taken to ensure
   1492  * the source has been zero padded. For this reason it may be better to
   1493  * use extend(B, 1) and assign specific fields instead.
   1494  */
   1495 void *flatcc_builder_vector_push(flatcc_builder_t *B, const void *data);
   1496 
   1497 /**
   1498  * Pushes multiple elements at a time.
   1499  *
   1500  * Returns the buffer holding a modifiable copy of the added content,
   1501  * or null on error.
   1502  */
   1503 void *flatcc_builder_append_vector(flatcc_builder_t *B, const void *data, size_t count);
   1504 
   1505 /**
   1506  * Removes elements already added to vector that has not been ended.
   1507  * For example, a vector of parsed list may remove the trailing comma,
   1508  * or the vector may simply overallocate to get some temporary working
   1509  * space. The total vector size must never become negative.
   1510  *
   1511  * Returns -1 if the count as larger than current count, or 0 on success.
   1512  */
   1513 int flatcc_builder_truncate_vector(flatcc_builder_t *B, size_t count);
   1514 
   1515 /*
   1516  * Similar to `create_vector` but with references that get translated
   1517  * into offsets. The references must, as usual, belong to the current
   1518  * buffer. Strings, scalar and struct vectors can emit directly without
   1519  * stack allocation, but offset vectors must translate the offsets
   1520  * and therefore need the temporary space. Thus, this function is
   1521  * roughly equivalent to to start, append, end offset vector.
   1522  *
   1523  * See also `flatcc_builder_create_offset_vector_direct`.
   1524  */
   1525 flatcc_builder_ref_t flatcc_builder_create_offset_vector(flatcc_builder_t *B,
   1526         const flatcc_builder_ref_t *data, size_t count);
   1527 
   1528 /*
   1529  * NOTE: this call takes non-const source array of references
   1530  * and destroys the content.
   1531  *
   1532  * This is a faster version of `create_offset_vector` where the
   1533  * source references are destroyed. In return the vector can be
   1534  * emitted directly without passing over the stack.
   1535  */
   1536 flatcc_builder_ref_t flatcc_builder_create_offset_vector_direct(flatcc_builder_t *B,
   1537         flatcc_builder_ref_t *data, size_t count);
   1538 
   1539 
   1540 /**
   1541  * Starts a vector holding offsets to tables or strings. Before
   1542  * completion it will hold `flatcc_builder_ref_t` references because the
   1543  * offset is not known until the vector start location is known, which
   1544  * depends to the final size, which for parsers is generally unknown.
   1545  */
   1546 int flatcc_builder_start_offset_vector(flatcc_builder_t *B);
   1547 
   1548 /**
   1549  * Similar to `end_vector` but updates all stored references so they
   1550  * become offsets to the vector start.
   1551  */
   1552 flatcc_builder_ref_t flatcc_builder_end_offset_vector(flatcc_builder_t *B);
   1553 
   1554 /**
   1555  * Same as `flatcc_builder_end_offset_vector` except null references are
   1556  * permitted when the corresponding `type` entry is 0 (the 'NONE' type).
   1557  * This makes it possible to build union vectors with less overhead when
   1558  * the `type` vector is already known. Use standand offset vector calls
   1559  * prior to this call.
   1560  */
   1561 flatcc_builder_ref_t flatcc_builder_end_offset_vector_for_unions(flatcc_builder_t *B,
   1562         const flatcc_builder_utype_t *type);
   1563 
   1564 /** Returns the number of elements currently on the stack. */
   1565 size_t flatcc_builder_offset_vector_count(flatcc_builder_t *B);
   1566 
   1567 /**
   1568  * Returns a pointer ot the first vector element on stack,
   1569  * accessible up to the number of elements currently on stack.
   1570  */
   1571 void *flatcc_builder_offset_vector_edit(flatcc_builder_t *B);
   1572 
   1573 /**
   1574  * Similar to `extend_vector` but returns a buffer indexable as
   1575  * `flatcc_builder_ref_t` array. All elements must be set to a valid
   1576  * unique non-null reference, but truncate and extend may be used to
   1577  * perform edits. Unused references will leave garbage in the buffer.
   1578  * References should not originate from any other buffer than the
   1579  * current, including parents and nested buffers.  It is valid to reuse
   1580  * references in DAG form when contained in the sammer, excluding any
   1581  * nested, sibling or parent buffers.
   1582  */
   1583 flatcc_builder_ref_t *flatcc_builder_extend_offset_vector(flatcc_builder_t *B, size_t count);
   1584 
   1585 /** Similar to truncate_vector. */
   1586 int flatcc_builder_truncate_offset_vector(flatcc_builder_t *B, size_t count);
   1587 
   1588 /**
   1589  * A specialized extend that pushes a single element.
   1590  *
   1591  * Returns the buffer holding a modifiable copy of the added content,
   1592  * or null on error.
   1593  */
   1594 flatcc_builder_ref_t *flatcc_builder_offset_vector_push(flatcc_builder_t *B,
   1595         flatcc_builder_ref_t ref);
   1596 
   1597 /**
   1598  * Takes an array of refs as argument to do a multi push operation.
   1599  *
   1600  * Returns the buffer holding a modifiable copy of the added content,
   1601  * or null on error.
   1602  */
   1603 flatcc_builder_ref_t *flatcc_builder_append_offset_vector(flatcc_builder_t *B,
   1604         const flatcc_builder_ref_t *refs, size_t count);
   1605 
   1606 /**
   1607  * All union vector operations are like offset vector operations,
   1608  * except they take a struct with a type and a reference rather than
   1609  * just a reference. The finished union vector is returned as a struct
   1610  * of two references, one for the type vector and one for the table offset
   1611  * vector. Each reference goes to a separate table field where the type
   1612  * offset vector id must be one larger than the type vector.
   1613  */
   1614 
   1615 /**
   1616  * Creates a union vector which is in reality two vectors, a type vector
   1617  * and an offset vector. Both vectors references are returned.
   1618  */
   1619 flatcc_builder_union_vec_ref_t flatcc_builder_create_union_vector(flatcc_builder_t *B,
   1620         const flatcc_builder_union_ref_t *urefs, size_t count);
   1621 
   1622 /*
   1623  * NOTE: this call takes non-const source array of references
   1624  * and destroys the content. The type array remains intact.
   1625  *
   1626  * This is a faster version of `create_union_vector` where the source
   1627  * references are destroyed and where the types are given in a separate
   1628  * array. In return the vector can be emitted directly without passing
   1629  * over the stack.
   1630  *
   1631  * Unlike `create_offset_vector` we do allow null references but only if
   1632  * the union type is NONE (0).
   1633  */
   1634 flatcc_builder_union_vec_ref_t flatcc_builder_create_union_vector_direct(flatcc_builder_t *B,
   1635         const flatcc_builder_utype_t *types, flatcc_builder_ref_t *data, size_t count);
   1636 
   1637 /*
   1638  * Creates just the type vector part of a union vector. This is
   1639  * similar to a normal `create_vector` call except that the size
   1640  * and alignment are given implicitly. Can be used during
   1641  * cloning or similar operations where the types are all given
   1642  * but the values must be handled one by one as prescribed by
   1643  * the type. The values can be added separately as an offset vector.
   1644  */
   1645 flatcc_builder_ref_t flatcc_builder_create_type_vector(flatcc_builder_t *B,
   1646         const flatcc_builder_utype_t *types, size_t count);
   1647 
   1648 /**
   1649  * Starts a vector holding types and offsets to tables or strings. Before
   1650  * completion it will hold `flatcc_builder_union_ref_t` references because the
   1651  * offset is not known until the vector start location is known, which
   1652  * depends to the final size, which for parsers is generally unknown,
   1653  * and also because the union type must be separated out into a separate
   1654  * vector. It would not be practicaly to push on two different vectors
   1655  * during construction.
   1656  */
   1657 int flatcc_builder_start_union_vector(flatcc_builder_t *B);
   1658 
   1659 /**
   1660  * Similar to `end_vector` but updates all stored references so they
   1661  * become offsets to the vector start and splits the union references
   1662  * into a type vector and an offset vector.
   1663  */
   1664 flatcc_builder_union_vec_ref_t flatcc_builder_end_union_vector(flatcc_builder_t *B);
   1665 
   1666 /** Returns the number of elements currently on the stack. */
   1667 size_t flatcc_builder_union_vector_count(flatcc_builder_t *B);
   1668 
   1669 /**
   1670  * Returns a pointer ot the first vector element on stack,
   1671  * accessible up to the number of elements currently on stack.
   1672  */
   1673 void *flatcc_builder_union_vector_edit(flatcc_builder_t *B);
   1674 
   1675 /**
   1676  * Similar to `extend_offset_vector` but returns a buffer indexable as a
   1677  * `flatcc_builder_union_ref_t` array. All elements must be set to a valid
   1678  * unique non-null reference with a valid union type to match, or it
   1679  * must be null with a zero union type.
   1680  */
   1681 flatcc_builder_union_ref_t *flatcc_builder_extend_union_vector(flatcc_builder_t *B, size_t count);
   1682 
   1683 /** Similar to truncate_vector. */
   1684 int flatcc_builder_truncate_union_vector(flatcc_builder_t *B, size_t count);
   1685 
   1686 /**
   1687  * A specialized extend that pushes a single element.
   1688  *
   1689  * Returns the buffer holding a modifiable copy of the added content,
   1690  * or null on error.
   1691  */
   1692 flatcc_builder_union_ref_t *flatcc_builder_union_vector_push(flatcc_builder_t *B,
   1693         flatcc_builder_union_ref_t uref);
   1694 
   1695 /**
   1696  * Takes an array of union_refs as argument to do a multi push operation.
   1697  *
   1698  * Returns the buffer holding a modifiable copy of the added content,
   1699  * or null on error.
   1700  */
   1701 flatcc_builder_union_ref_t *flatcc_builder_append_union_vector(flatcc_builder_t *B,
   1702         const flatcc_builder_union_ref_t *urefs, size_t count);
   1703 
   1704 /**
   1705  * Faster string operation that avoids temporary stack storage. The
   1706  * string is not required to be zero-terminated, but is expected
   1707  * (unchecked) to be utf-8. Embedded zeroes would be allowed but
   1708  * ubyte vectors should be used for that. The resulting string will
   1709  * have a zero termination added, not included in length.
   1710  */
   1711 flatcc_builder_ref_t flatcc_builder_create_string(flatcc_builder_t *B,
   1712         const char *s, size_t len);
   1713 
   1714 /** `create_string` up to zero termination of source. */
   1715 flatcc_builder_ref_t flatcc_builder_create_string_str(flatcc_builder_t *B,
   1716         const char *s);
   1717 
   1718 /**
   1719  * `create_string` up to zero termination or at most max_len of source.
   1720  *
   1721  * Note that like `strncpy` it will include `max_len` characters if
   1722  * the source is longer than `max_len`, but unlike `strncpy` it will
   1723  * always add zero termination.
   1724  */
   1725 flatcc_builder_ref_t flatcc_builder_create_string_strn(flatcc_builder_t *B, const char *s, size_t max_len);
   1726 
   1727 /**
   1728  * Starts an empty string that can be extended subsequently.
   1729  *
   1730  * While the string is being created, it is guaranteed that there is
   1731  * always a null character after the end of the current string length.
   1732  * This also holds after `extend` and `append` operations. It is not
   1733  * allowed to modify the null character.
   1734  *
   1735  * Returns 0 on success.
   1736  */
   1737 int flatcc_builder_start_string(flatcc_builder_t *B);
   1738 
   1739 /**
   1740  * Similar to `extend_vector` except for the buffer return type and a
   1741  * slight speed advantage. Strings are expected to contain utf-8 content
   1742  * but this isn't verified, and null characters would be accepted. The
   1743  * length is given in bytes.
   1744  *
   1745  * Appending too much, then truncating can be used to trim string
   1746  * escapes during parsing, or convert between unicode formats etc.
   1747  */
   1748 char *flatcc_builder_extend_string(flatcc_builder_t *B, size_t len);
   1749 
   1750 /**
   1751  * Concatenes a length of string. If the string contains zeroes (which
   1752  * it formally shouldn't), they will be copied in.
   1753  *
   1754  * Returns the buffer holding a modifiable copy of the added content,
   1755  * or null on error.
   1756  */
   1757 char *flatcc_builder_append_string(flatcc_builder_t *B, const char *s, size_t len);
   1758 
   1759 /** `append_string` up to zero termination of source. */
   1760 char *flatcc_builder_append_string_str(flatcc_builder_t *B, const char *s);
   1761 
   1762 /** `append_string` up zero termination or at most max_len of source. */
   1763 char *flatcc_builder_append_string_strn(flatcc_builder_t *B, const char *s, size_t max_len);
   1764 
   1765 /**
   1766  * Similar to `truncate_vector` available for consistency and a slight
   1767  * speed advantage. Reduces string by `len` bytes - it does not set
   1768  * the length. The resulting length must not become negative. Zero
   1769  * termination is not counted.
   1770  *
   1771  * Returns -1 of the length becomes negative, 0 on success.
   1772  */
   1773 int flatcc_builder_truncate_string(flatcc_builder_t *B, size_t len);
   1774 
   1775 /**
   1776  * Similar to `end_vector` but adds a trailing zero not included
   1777  * in the length. The trailing zero is added regardless of whatever
   1778  * zero content may exist in the provided string (although it
   1779  * formally should not contain any).
   1780  */
   1781 flatcc_builder_ref_t flatcc_builder_end_string(flatcc_builder_t *B);
   1782 
   1783 /** Returns the length of string currently on the stack. */
   1784 size_t flatcc_builder_string_len(flatcc_builder_t *B);
   1785 
   1786 /**
   1787  * Returns a ponter to the start of the string
   1788  * accessible up the length of string currently on the stack.
   1789  */
   1790 char *flatcc_builder_string_edit(flatcc_builder_t *B);
   1791 
   1792 
   1793 /*
   1794  * Only for use with the default emitter.
   1795  *
   1796  * Fast acces to small buffers from default emitter.
   1797  *
   1798  * Only valid for default emitters before `flatcc_builder_clear`. The
   1799  * return buffer is not valid after a call to `flatcc_builder_reset` or
   1800  * `flatcc_builder_clear`.
   1801  *
   1802  * Returns null if the buffer size is too large to a have a linear
   1803  * memory representation or if the emitter is not the default. A valid
   1804  * size is between half and a full emitter page size depending on vtable
   1805  * content.
   1806  *
   1807  * Non-default emitters must be accessed by means specific to the
   1808  * particular emitter.
   1809  *
   1810  * If `size_out` is not null, it is set to the buffer size, or 0 if
   1811  * operation failed.
   1812  *
   1813  * The returned buffer should NOT be deallocated explicitly.
   1814  *
   1815  * The buffer size is the size reported by `flatcc_builder_get_buffer_size`.
   1816  */
   1817 void *flatcc_builder_get_direct_buffer(flatcc_builder_t *B, size_t *size_out);
   1818 
   1819 /*
   1820  * Only for use with the default emitter.
   1821  *
   1822  * Default finalizer that allocates a buffer from the default emitter.
   1823  *
   1824  * Returns null if memory could not be allocated or if the emitter is
   1825  * not the default. This is just a convenience method - there are many
   1826  * other possible ways to extract the result of the emitter depending on
   1827  * use case.
   1828  *
   1829  * If `size_out` is not null, it is set to the buffer size, or 0 if
   1830  * operation failed.
   1831  *
   1832  * The allocated buffer is aligned according to malloc which may not be
   1833  * sufficient in advanced cases - for that purpose
   1834  * `flatcc_builder_finalize_aligned_buffer` may be used.
   1835  *
   1836  * It may be worth calling `flatcc_builder_get_direct_buffer` first to see
   1837  * if the buffer is small enough to avoid copying.
   1838  *
   1839  * The returned buffer must be deallocated using `free`.
   1840  */
   1841 void *flatcc_builder_finalize_buffer(flatcc_builder_t *B, size_t *size_out);
   1842 
   1843 /*
   1844  * Only for use with the default emitter.
   1845  *
   1846  * Similar to `flatcc_builder_finalize_buffer` but ensures the returned
   1847  * memory is aligned to the overall alignment required for the buffer.
   1848  * Often it is not necessary unless special operations rely on larger
   1849  * alignments than the stored scalars.
   1850  *
   1851  * If `size_out` is not null, it is set to the buffer size, or 0 if
   1852  * operation failed.
   1853  *
   1854  * The returned buffer must be deallocated using `aligned_free` which is
   1855  * implemented via `flatcc_flatbuffers.h`. `free` will usually work but
   1856  * is not portable to platforms without posix_memalign or C11
   1857  * aligned_alloc support.
   1858  *
   1859  * NOTE: if a library might be compiled with a version of aligned_free
   1860  * that differs from the application using it, use
   1861  * `flatcc_builder_aligned_free` to make sure the correct deallocation
   1862  * function is used.
   1863  */
   1864 void *flatcc_builder_finalize_aligned_buffer(flatcc_builder_t *B, size_t *size_out);
   1865 
   1866 /*
   1867  * A stable implementation of `aligned_alloc` that is not sensitive
   1868  * to the applications compile time flags.
   1869  */
   1870 void *flatcc_builder_aligned_alloc(size_t alignment, size_t size);
   1871 
   1872 /*
   1873  * A stable implementation of `aligned_free` that is not sensitive
   1874  * to the applications compile time flags.
   1875  */
   1876 void flatcc_builder_aligned_free(void *p);
   1877 
   1878 /*
   1879  * Same allocation as `flatcc_builder_finalize_buffer` returnes. Usually
   1880  * same as `malloc` but can redefined via macros.
   1881  */
   1882 void *flatcc_builder_alloc(size_t size);
   1883 
   1884 /*
   1885  * A stable implementation of `free` when the default allocation
   1886  * methods have been redefined.
   1887  *
   1888  * Deallocates memory returned from `flatcc_builder_finalize_buffer`.
   1889  */
   1890 void flatcc_builder_free(void *p);
   1891 
   1892 /*
   1893  * Only for use with the default emitter.
   1894  *
   1895  * Convenience method to copy buffer from default emitter. Forwards
   1896  * call to default emitter and returns input pointer, or null if
   1897  * the emitter is not default or of the given size is smaller than
   1898  * the buffer size.
   1899  *
   1900  * Note: the `size` argument is the target buffers capacity, not the
   1901  * flatcc_builders buffer size.
   1902  *
   1903  * Other emitters have custom interfaces for reaching their content.
   1904  */
   1905 void *flatcc_builder_copy_buffer(flatcc_builder_t *B, void *buffer, size_t size);
   1906 
   1907 #ifdef __cplusplus
   1908 }
   1909 #endif
   1910 
   1911 #endif /* FLATCC_BUILDER_H */