nostrdb

an unfairly fast embedded nostr database backed by lmdb
git clone git://jb55.com/nostrdb
Log | Files | Refs | Submodules | README | LICENSE

codegen_c_reader.c (90482B)


      1 #include <stdio.h>
      2 #include <assert.h>
      3 #include <string.h>
      4 
      5 #include "codegen_c.h"
      6 #include "codegen_c_sort.h"
      7 
      8 static inline int match_kw_identifier(fb_symbol_t *sym)
      9 {
     10     return (sym->ident->len == 10 &&
     11             memcmp(sym->ident->text, "identifier", 10) == 0);
     12 }
     13 
     14 /*
     15  * Use of file identifiers for undeclared roots is fuzzy, but we need an
     16  * identifer for all, so we use the one defined for the current schema
     17  * file and allow the user to override. This avoids tedious runtime file
     18  * id arguments to all create calls.
     19  *
     20  * As later addition to FlatBuffers, type hashes may replace file
     21  * identifiers when explicitly stated. These are FNV-1a hashes of the
     22  * fully qualified type name (dot separated).
     23  *
     24  * We generate the type hash both as a native integer constants for use
     25  * in switch statements, and encoded as a little endian C string for use
     26  * as a file identifier.
     27  */
     28 static void print_type_identifier(fb_output_t *out, fb_compound_type_t *ct)
     29 {
     30     uint8_t buf[17];
     31     uint8_t *p;
     32     uint8_t x;
     33     int i;
     34     const char *nsc = out->nsc;
     35     fb_scoped_name_t snt;
     36     const char *name;
     37     uint32_t type_hash;
     38     int conflict = 0;
     39     fb_symbol_t *sym;
     40     const char *file_identifier;
     41     int file_identifier_len;
     42     const char *quote;
     43 
     44     fb_clear(snt);
     45 
     46     fb_compound_name(ct, &snt);
     47     name = snt.text;
     48     type_hash = ct->type_hash;
     49 
     50     /*
     51      * It's not practical to detect all possible name conflicts, but
     52      * 'identifier' is common enough to require special handling.
     53      */
     54     for (sym = ct->members; sym; sym = sym->link) {
     55         if (match_kw_identifier(sym)) {
     56             conflict = 1;
     57             break;
     58         }
     59     }
     60     if (out->S->file_identifier.type == vt_string) {
     61         quote = "\"";
     62         file_identifier = out->S->file_identifier.s.s;
     63         file_identifier_len = out->S->file_identifier.s.len;
     64     } else {
     65         quote = "";
     66         file_identifier = "0";
     67         file_identifier_len = 1;
     68     }
     69     fprintf(out->fp,
     70             "#ifndef %s_file_identifier\n"
     71             "#define %s_file_identifier %s%.*s%s\n"
     72             "#endif\n",
     73             name, name, quote, file_identifier_len, file_identifier, quote);
     74     if (!conflict) {
     75         /* For backwards compatibility. */
     76         fprintf(out->fp,
     77                 "/* deprecated, use %s_file_identifier */\n"
     78                 "#ifndef %s_identifier\n"
     79                 "#define %s_identifier %s%.*s%s\n"
     80                 "#endif\n",
     81                 name, name, name, quote, file_identifier_len, file_identifier, quote);
     82     }
     83     fprintf(out->fp,
     84         "#define %s_type_hash ((%sthash_t)0x%lx)\n",
     85         name, nsc, (unsigned long)(type_hash));
     86     p = buf;
     87     i = 4;
     88     while (i--) {
     89         *p++ = '\\';
     90         *p++ = 'x';
     91         x = type_hash & 0x0f;
     92         x += x > 9 ? 'a' - 10 : '0';
     93         type_hash >>= 4;
     94         p[1] = x;
     95         x = type_hash & 0x0f;
     96         x += x > 9 ? 'a' - 10 : '0';
     97         type_hash >>= 4;
     98         p[0] = x;
     99         p += 2;
    100     }
    101     *p = '\0';
    102     fprintf(out->fp,
    103         "#define %s_type_identifier \"%s\"\n",
    104         name, buf);
    105 }
    106 
    107 static void print_file_extension(fb_output_t *out, fb_compound_type_t *ct)
    108 {
    109     fb_scoped_name_t snt;
    110     const char *name;
    111 
    112     fb_clear(snt);
    113     fb_compound_name(ct, &snt);
    114     name = snt.text;
    115 
    116     if (out->S->file_extension.type == vt_string) {
    117         fprintf(out->fp,
    118                 "#ifndef %s_file_extension\n"
    119                 "#define %s_file_extension \"%.*s\"\n"
    120                 "#endif\n",
    121                 name, name, out->S->file_extension.s.len, out->S->file_extension.s.s);
    122     } else {
    123         fprintf(out->fp,
    124                 "#ifndef %s_file_extension\n"
    125                 "#define %s_file_extension \"%s\"\n"
    126                 "#endif\n",
    127                 name, name, out->opts->default_bin_ext);
    128     }
    129 }
    130 
    131 /* Finds first occurrence of matching key when vector is sorted on the named field. */
    132 static void gen_find(fb_output_t *out)
    133 {
    134     const char *nsc = out->nsc;
    135 
    136     /*
    137      * E: Element accessor (elem = E(vector, index)).
    138      * L: Length accessor (length = L(vector)).
    139      * A: Field accessor (or the identity function), result must match the diff function D's first arg.
    140      * V: The vector to search (assuming sorted).
    141      * T: The scalar, enum or string key type, (either the element, or a field of the element).
    142      * K: The search key.
    143      * Kn: optional key length so external strings do not have to be zero terminated.
    144      * D: the diff function D(v, K, Kn) :: v - <K, Kn>
    145      *
    146      * returns index (0..len - 1), or not_found (-1).
    147      */
    148     fprintf(out->fp,
    149         "#include <string.h>\n"
    150         "static const size_t %snot_found = (size_t)-1;\n"
    151         "static const size_t %send = (size_t)-1;\n"
    152         "#define __%sidentity(n) (n)\n"
    153         "#define __%smin(a, b) ((a) < (b) ? (a) : (b))\n",
    154         nsc, nsc, nsc, nsc);
    155     fprintf(out->fp,
    156         "/* Subtraction doesn't work for unsigned types. */\n"
    157         "#define __%sscalar_cmp(x, y, n) ((x) < (y) ? -1 : (x) > (y))\n"
    158         "static inline int __%sstring_n_cmp(%sstring_t v, const char *s, size_t n)\n"
    159         "{ size_t nv = %sstring_len(v); int x = strncmp(v, s, nv < n ? nv : n);\n"
    160         "  return x != 0 ? x : nv < n ? -1 : nv > n; }\n"
    161         "/* `n` arg unused, but needed by string find macro expansion. */\n"
    162         "static inline int __%sstring_cmp(%sstring_t v, const char *s, size_t n) { (void)n; return strcmp(v, s); }\n",
    163         nsc, nsc, nsc, nsc, nsc, nsc);
    164     fprintf(out->fp,
    165         "/* A = identity if searching scalar vectors rather than key fields. */\n"
    166         "/* Returns lowest matching index or not_found. */\n"
    167         "#define __%sfind_by_field(A, V, E, L, K, Kn, T, D)\\\n"
    168         "{ T v__tmp; size_t a__tmp = 0, b__tmp, m__tmp; if (!(b__tmp = L(V))) { return %snot_found; }\\\n"
    169         "  --b__tmp;\\\n"
    170         "  while (a__tmp < b__tmp) {\\\n"
    171         "    m__tmp = a__tmp + ((b__tmp - a__tmp) >> 1);\\\n"
    172         "    v__tmp = A(E(V, m__tmp));\\\n"
    173         "    if ((D(v__tmp, (K), (Kn))) < 0) {\\\n"
    174         "      a__tmp = m__tmp + 1;\\\n"
    175         "    } else {\\\n"
    176         "      b__tmp = m__tmp;\\\n"
    177         "    }\\\n"
    178         "  }\\\n"
    179         "  if (a__tmp == b__tmp) {\\\n"
    180         "    v__tmp = A(E(V, a__tmp));\\\n"
    181         "    if (D(v__tmp, (K), (Kn)) == 0) {\\\n"
    182         "       return a__tmp;\\\n"
    183         "    }\\\n"
    184         "  }\\\n"
    185         "  return %snot_found;\\\n"
    186         "}\n",
    187         nsc, nsc, nsc);
    188     fprintf(out->fp,
    189         "#define __%sfind_by_scalar_field(A, V, E, L, K, T)\\\n"
    190         "__%sfind_by_field(A, V, E, L, K, 0, T, __%sscalar_cmp)\n"
    191         "#define __%sfind_by_string_field(A, V, E, L, K)\\\n"
    192         "__%sfind_by_field(A, V, E, L, K, 0, %sstring_t, __%sstring_cmp)\n"
    193         "#define __%sfind_by_string_n_field(A, V, E, L, K, Kn)\\\n"
    194         "__%sfind_by_field(A, V, E, L, K, Kn, %sstring_t, __%sstring_n_cmp)\n",
    195         nsc, nsc, nsc, nsc, nsc,
    196         nsc, nsc, nsc, nsc, nsc, nsc);
    197     fprintf(out->fp,
    198         "#define __%sdefine_find_by_scalar_field(N, NK, TK)\\\n"
    199         "static inline size_t N ## _vec_find_by_ ## NK(N ## _vec_t vec__tmp, TK key__tmp)\\\n"
    200         "__%sfind_by_scalar_field(N ## _ ## NK, vec__tmp, N ## _vec_at, N ## _vec_len, key__tmp, TK)\n",
    201         nsc, nsc);
    202     fprintf(out->fp,
    203         "#define __%sdefine_scalar_find(N, T)\\\n"
    204         "static inline size_t N ## _vec_find(N ## _vec_t vec__tmp, T key__tmp)\\\n"
    205         "__%sfind_by_scalar_field(__%sidentity, vec__tmp, N ## _vec_at, N ## _vec_len, key__tmp, T)\n",
    206         nsc, nsc, nsc);
    207     fprintf(out->fp,
    208         "#define __%sdefine_find_by_string_field(N, NK) \\\n"
    209         "/* Note: find only works on vectors sorted by this field. */\\\n"
    210         "static inline size_t N ## _vec_find_by_ ## NK(N ## _vec_t vec__tmp, const char *s__tmp)\\\n"
    211         "__%sfind_by_string_field(N ## _ ## NK, vec__tmp, N ## _vec_at, N ## _vec_len, s__tmp)\\\n"
    212         "static inline size_t N ## _vec_find_n_by_ ## NK(N ## _vec_t vec__tmp, const char *s__tmp, size_t n__tmp)\\\n"
    213         "__%sfind_by_string_n_field(N ## _ ## NK, vec__tmp, N ## _vec_at, N ## _vec_len, s__tmp, n__tmp)\n",
    214         nsc, nsc, nsc);
    215     fprintf(out->fp,
    216         "#define __%sdefine_default_find_by_scalar_field(N, NK, TK)\\\n"
    217         "static inline size_t N ## _vec_find(N ## _vec_t vec__tmp, TK key__tmp)\\\n"
    218         "{ return N ## _vec_find_by_ ## NK(vec__tmp, key__tmp); }\n",
    219         nsc);
    220     fprintf(out->fp,
    221         "#define __%sdefine_default_find_by_string_field(N, NK) \\\n"
    222         "static inline size_t N ## _vec_find(N ## _vec_t vec__tmp, const char *s__tmp)\\\n"
    223         "{ return N ## _vec_find_by_ ## NK(vec__tmp, s__tmp); }\\\n"
    224         "static inline size_t N ## _vec_find_n(N ## _vec_t vec__tmp, const char *s__tmp, size_t n__tmp)\\\n"
    225         "{ return N ## _vec_find_n_by_ ## NK(vec__tmp, s__tmp, n__tmp); }\n",
    226         nsc);
    227 }
    228 
    229 static void gen_union(fb_output_t *out)
    230 {
    231     const char *nsc = out->nsc;
    232 
    233     fprintf(out->fp,
    234         "typedef struct %sunion {\n"
    235         "    %sunion_type_t type;\n"
    236         "    %sgeneric_t value;\n"
    237         "} %sunion_t;\n"
    238         "typedef struct %sunion_vec {\n"
    239         "    const %sunion_type_t *type;\n"
    240         "    const %suoffset_t *value;\n"
    241         "} %sunion_vec_t;\n",
    242         nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc);
    243     fprintf(out->fp,
    244         "typedef struct %smutable_union {\n"
    245         "    %sunion_type_t type;\n"
    246         "    %smutable_generic_t value;\n"
    247         "} %smutable_union_t;\n"
    248         "typedef struct %smutable_union_vec {\n"
    249         "    %sunion_type_t *type;\n"
    250         "    %suoffset_t *value;\n"
    251         "} %smutable_union_vec_t;\n",
    252         nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc);
    253     fprintf(out->fp,
    254         "static inline %smutable_union_t %smutable_union_cast(%sunion_t u__tmp)\\\n"
    255         "{ %smutable_union_t mu = { u__tmp.type, (%smutable_generic_t)u__tmp.value };\\\n"
    256         "  return mu; }\n",
    257         nsc, nsc, nsc, nsc, nsc);
    258     fprintf(out->fp,
    259         "static inline %smutable_union_vec_t %smutable_union_vec_cast(%sunion_vec_t uv__tmp)\\\n"
    260         "{ %smutable_union_vec_t muv =\\\n"
    261         "  { (%sunion_type_t *)uv__tmp.type, (%suoffset_t *)uv__tmp.value }; return muv; }\n",
    262         nsc, nsc, nsc, nsc, nsc, nsc);
    263     fprintf(out->fp,
    264         "#define __%sunion_type_field(ID, t)\\\n"
    265         "{\\\n"
    266         "    __%sread_vt(ID, offset__tmp, t)\\\n"
    267         "    return offset__tmp ? __%sread_scalar_at_byteoffset(__%sutype, t, offset__tmp) : 0;\\\n"
    268         "}\n",
    269         nsc, nsc, nsc, nsc);
    270     fprintf(out->fp,
    271         "static inline %sstring_t %sstring_cast_from_union(const %sunion_t u__tmp)\\\n"
    272         "{ return %sstring_cast_from_generic(u__tmp.value); }\n",
    273         nsc, nsc, nsc, nsc);
    274     fprintf(out->fp,
    275         "#define __%sdefine_union_field(NS, ID, N, NK, T, r)\\\n"
    276         "static inline T ## _union_type_t N ## _ ## NK ## _type_get(N ## _table_t t__tmp)\\\n"
    277         "__## NS ## union_type_field(((ID) - 1), t__tmp)\\\n"
    278         "static inline NS ## generic_t N ## _ ## NK ## _get(N ## _table_t t__tmp)\\\n"
    279         "__## NS ## table_field(NS ## generic_t, ID, t__tmp, r)\\\n", nsc);
    280     if (!out->opts->cgen_no_conflicts) {
    281         fprintf(out->fp,
    282             "static inline T ## _union_type_t N ## _ ## NK ## _type(N ## _table_t t__tmp)\\\n"
    283             "__## NS ## union_type_field(((ID) - 1), t__tmp)\\\n"
    284             "static inline NS ## generic_t N ## _ ## NK(N ## _table_t t__tmp)\\\n"
    285             "__## NS ## table_field(NS ## generic_t, ID, t__tmp, r)\\\n");
    286     }
    287     fprintf(out->fp,
    288         "static inline int N ## _ ## NK ## _is_present(N ## _table_t t__tmp)\\\n"
    289         "__## NS ## field_present(ID, t__tmp)\\\n"
    290         "static inline T ## _union_t N ## _ ## NK ## _union(N ## _table_t t__tmp)\\\n"
    291         "{ T ## _union_t u__tmp = { 0, 0 }; u__tmp.type = N ## _ ## NK ## _type_get(t__tmp);\\\n"
    292         "  if (u__tmp.type == 0) return u__tmp; u__tmp.value = N ## _ ## NK ## _get(t__tmp); return u__tmp; }\\\n"
    293         "static inline NS ## string_t N ## _ ## NK ## _as_string(N ## _table_t t__tmp)\\\n"
    294         "{ return NS ## string_cast_from_generic(N ## _ ## NK ## _get(t__tmp)); }\\\n"
    295         "\n");
    296     fprintf(out->fp,
    297         "#define __%sdefine_union_vector_ops(NS, T)\\\n"
    298         "static inline size_t T ## _union_vec_len(T ## _union_vec_t uv__tmp)\\\n"
    299         "{ return NS ## vec_len(uv__tmp.type); }\\\n"
    300         "static inline T ## _union_t T ## _union_vec_at(T ## _union_vec_t uv__tmp, size_t i__tmp)\\\n"
    301         "{ T ## _union_t u__tmp = { 0, 0 }; size_t n__tmp = NS ## vec_len(uv__tmp.type);\\\n"
    302         "  FLATCC_ASSERT(n__tmp > (i__tmp) && \"index out of range\"); u__tmp.type = uv__tmp.type[i__tmp];\\\n"
    303         "  /* Unknown type is treated as NONE for schema evolution. */\\\n"
    304         "  if (u__tmp.type == 0) return u__tmp;\\\n"
    305         "  u__tmp.value = NS ## generic_vec_at(uv__tmp.value, i__tmp); return u__tmp; }\\\n"
    306         "static inline NS ## string_t T ## _union_vec_at_as_string(T ## _union_vec_t uv__tmp, size_t i__tmp)\\\n"
    307         "{ return (NS ## string_t) NS ## generic_vec_at_as_string(uv__tmp.value, i__tmp); }\\\n"
    308         "\n",
    309         nsc);
    310     fprintf(out->fp,
    311         "#define __%sdefine_union_vector(NS, T)\\\n"
    312         "typedef NS ## union_vec_t T ## _union_vec_t;\\\n"
    313         "typedef NS ## mutable_union_vec_t T ## _mutable_union_vec_t;\\\n"
    314         "static inline T ## _mutable_union_vec_t T ## _mutable_union_vec_cast(T ## _union_vec_t u__tmp)\\\n"
    315         "{ return NS ## mutable_union_vec_cast(u__tmp); }\\\n"
    316         "__## NS ## define_union_vector_ops(NS, T)\n",
    317         nsc);
    318     fprintf(out->fp,
    319         "#define __%sdefine_union(NS, T)\\\n"
    320         "typedef NS ## union_t T ## _union_t;\\\n"
    321         "typedef NS ## mutable_union_t T ## _mutable_union_t;\\\n"
    322         "static inline T ## _mutable_union_t T ## _mutable_union_cast(T ## _union_t u__tmp)\\\n"
    323         "{ return NS ## mutable_union_cast(u__tmp); }\\\n"
    324         "__## NS ## define_union_vector(NS, T)\n",
    325         nsc);
    326     fprintf(out->fp,
    327         "#define __%sdefine_union_vector_field(NS, ID, N, NK, T, r)\\\n"
    328         "__## NS ## define_vector_field(ID - 1, N, NK ## _type, T ## _vec_t, r)\\\n"
    329         "__## NS ## define_vector_field(ID, N, NK, flatbuffers_generic_vec_t, r)\\\n"
    330         "static inline T ## _union_vec_t N ## _ ## NK ## _union(N ## _table_t t__tmp)\\\n"
    331         "{ T ## _union_vec_t uv__tmp; uv__tmp.type = N ## _ ## NK ## _type_get(t__tmp);\\\n"
    332         "  uv__tmp.value = N ## _ ## NK(t__tmp);\\\n"
    333         "  FLATCC_ASSERT(NS ## vec_len(uv__tmp.type) == NS ## vec_len(uv__tmp.value)\\\n"
    334         "  && \"union vector type length mismatch\"); return uv__tmp; }\n",
    335         nsc);
    336 }
    337 
    338 /* Linearly finds first occurrence of matching key, doesn't require vector to be sorted. */
    339 static void gen_scan(fb_output_t *out)
    340 {
    341     const char *nsc = out->nsc;
    342 
    343     /*
    344      * E: Element accessor (elem = E(vector, index)).
    345      * L: Length accessor (length = L(vector)).
    346      * A: Field accessor (or the identity function), result must match the diff function D's first arg.
    347      * V: The vector to search (assuming sorted).
    348      * T: The scalar, enum or string key type, (either the element, or a field of the element).
    349      * K: The search key.
    350      * Kn: optional key length so external strings do not have to be zero terminated.
    351      * D: the diff function D(v, K, Kn) :: v - <K, Kn>
    352      *
    353      * returns index (0..len - 1), or not_found (-1).
    354      */
    355     fprintf(out->fp,
    356         "/* A = identity if searching scalar vectors rather than key fields. */\n"
    357         "/* Returns lowest matching index or not_found. */\n"
    358         "#define __%sscan_by_field(b, e, A, V, E, L, K, Kn, T, D)\\\n"
    359         "{ T v__tmp; size_t i__tmp;\\\n"
    360         "  for (i__tmp = b; i__tmp < e; ++i__tmp) {\\\n"
    361         "    v__tmp = A(E(V, i__tmp));\\\n"
    362         "    if (D(v__tmp, (K), (Kn)) == 0) {\\\n"
    363         "       return i__tmp;\\\n"
    364         "    }\\\n"
    365         "  }\\\n"
    366         "  return %snot_found;\\\n"
    367         "}\n",
    368         nsc, nsc);
    369     fprintf(out->fp,
    370         "#define __%srscan_by_field(b, e, A, V, E, L, K, Kn, T, D)\\\n"
    371         "{ T v__tmp; size_t i__tmp = e;\\\n"
    372         "  while (i__tmp-- > b) {\\\n"
    373         "    v__tmp = A(E(V, i__tmp));\\\n"
    374         "    if (D(v__tmp, (K), (Kn)) == 0) {\\\n"
    375         "       return i__tmp;\\\n"
    376         "    }\\\n"
    377         "  }\\\n"
    378         "  return %snot_found;\\\n"
    379         "}\n",
    380         nsc, nsc);
    381     fprintf(out->fp,
    382         "#define __%sscan_by_scalar_field(b, e, A, V, E, L, K, T)\\\n"
    383         "__%sscan_by_field(b, e, A, V, E, L, K, 0, T, __%sscalar_cmp)\n"
    384         "#define __%sscan_by_string_field(b, e, A, V, E, L, K)\\\n"
    385         "__%sscan_by_field(b, e, A, V, E, L, K, 0, %sstring_t, __%sstring_cmp)\n"
    386         "#define __%sscan_by_string_n_field(b, e, A, V, E, L, K, Kn)\\\n"
    387         "__%sscan_by_field(b, e, A, V, E, L, K, Kn, %sstring_t, __%sstring_n_cmp)\n",
    388         nsc, nsc, nsc, nsc, nsc,
    389         nsc, nsc, nsc, nsc, nsc, nsc);
    390     fprintf(out->fp,
    391         "#define __%srscan_by_scalar_field(b, e, A, V, E, L, K, T)\\\n"
    392         "__%srscan_by_field(b, e, A, V, E, L, K, 0, T, __%sscalar_cmp)\n"
    393         "#define __%srscan_by_string_field(b, e, A, V, E, L, K)\\\n"
    394         "__%srscan_by_field(b, e, A, V, E, L, K, 0, %sstring_t, __%sstring_cmp)\n"
    395         "#define __%srscan_by_string_n_field(b, e, A, V, E, L, K, Kn)\\\n"
    396         "__%srscan_by_field(b, e, A, V, E, L, K, Kn, %sstring_t, __%sstring_n_cmp)\n",
    397         nsc, nsc, nsc, nsc, nsc,
    398         nsc, nsc, nsc, nsc, nsc, nsc);
    399     fprintf(out->fp,
    400         "#define __%sdefine_scan_by_scalar_field(N, NK, T)\\\n"
    401         "static inline size_t N ## _vec_scan_by_ ## NK(N ## _vec_t vec__tmp, T key__tmp)\\\n"
    402         "__%sscan_by_scalar_field(0, N ## _vec_len(vec__tmp), N ## _ ## NK ## _get, vec__tmp, N ## _vec_at, N ## _vec_len, key__tmp, T)\\\n"
    403         "static inline size_t N ## _vec_scan_ex_by_ ## NK(N ## _vec_t vec__tmp, size_t begin__tmp, size_t end__tmp, T key__tmp)\\\n"
    404         "__%sscan_by_scalar_field(begin__tmp, __%smin(end__tmp, N ## _vec_len(vec__tmp)), N ## _ ## NK ## _get, vec__tmp, N ## _vec_at, N ## _vec_len, key__tmp, T)\\\n"
    405         "static inline size_t N ## _vec_rscan_by_ ## NK(N ## _vec_t vec__tmp, T key__tmp)\\\n"
    406         "__%srscan_by_scalar_field(0, N ## _vec_len(vec__tmp), N ## _ ## NK ## _get, vec__tmp, N ## _vec_at, N ## _vec_len, key__tmp, T)\\\n"
    407         "static inline size_t N ## _vec_rscan_ex_by_ ## NK(N ## _vec_t vec__tmp, size_t begin__tmp, size_t end__tmp, T key__tmp)\\\n"
    408         "__%srscan_by_scalar_field(begin__tmp, __%smin(end__tmp, N ## _vec_len(vec__tmp)), N ## _ ## NK ## _get, vec__tmp, N ## _vec_at, N ## _vec_len, key__tmp, T)\n",
    409         nsc, nsc, nsc, nsc, nsc, nsc, nsc);
    410     fprintf(out->fp,
    411         "#define __%sdefine_scalar_scan(N, T)\\\n"
    412         "static inline size_t N ## _vec_scan(N ## _vec_t vec__tmp, T key__tmp)\\\n"
    413         "__%sscan_by_scalar_field(0, N ## _vec_len(vec__tmp), __%sidentity, vec__tmp, N ## _vec_at, N ## _vec_len, key__tmp, T)\\\n"
    414         "static inline size_t N ## _vec_scan_ex(N ## _vec_t vec__tmp, size_t begin__tmp, size_t end__tmp, T key__tmp)\\\n"
    415         "__%sscan_by_scalar_field(begin__tmp, __%smin(end__tmp, N ## _vec_len(vec__tmp)), __%sidentity, vec__tmp, N ## _vec_at, N ## _vec_len, key__tmp, T)\\\n"
    416         "static inline size_t N ## _vec_rscan(N ## _vec_t vec__tmp, T key__tmp)\\\n"
    417         "__%srscan_by_scalar_field(0, N ## _vec_len(vec__tmp), __%sidentity, vec__tmp, N ## _vec_at, N ## _vec_len, key__tmp, T)\\\n"
    418         "static inline size_t N ## _vec_rscan_ex(N ## _vec_t vec__tmp, size_t begin__tmp, size_t end__tmp, T key__tmp)\\\n"
    419         "__%srscan_by_scalar_field(begin__tmp, __%smin(end__tmp, N ## _vec_len(vec__tmp)), __%sidentity, vec__tmp, N ## _vec_at, N ## _vec_len, key__tmp, T)\n",
    420         nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc);
    421     fprintf(out->fp,
    422         "#define __%sdefine_scan_by_string_field(N, NK) \\\n"
    423         "static inline size_t N ## _vec_scan_by_ ## NK(N ## _vec_t vec__tmp, const char *s__tmp)\\\n"
    424         "__%sscan_by_string_field(0, N ## _vec_len(vec__tmp), N ## _ ## NK ## _get, vec__tmp, N ## _vec_at, N ## _vec_len, s__tmp)\\\n"
    425         "static inline size_t N ## _vec_scan_n_by_ ## NK(N ## _vec_t vec__tmp, const char *s__tmp, size_t n__tmp)\\\n"
    426         "__%sscan_by_string_n_field(0, N ## _vec_len(vec__tmp), N ## _ ## NK ## _get, vec__tmp, N ## _vec_at, N ## _vec_len, s__tmp, n__tmp)\\\n"
    427         "static inline size_t N ## _vec_scan_ex_by_ ## NK(N ## _vec_t vec__tmp, size_t begin__tmp, size_t end__tmp, const char *s__tmp)\\\n"
    428         "__%sscan_by_string_field(begin__tmp, __%smin(end__tmp, N ## _vec_len(vec__tmp)), N ## _ ## NK ## _get, vec__tmp, N ## _vec_at, N ## _vec_len, s__tmp)\\\n"
    429         "static inline size_t N ## _vec_scan_ex_n_by_ ## NK(N ## _vec_t vec__tmp, size_t begin__tmp, size_t end__tmp, const char *s__tmp, size_t n__tmp)\\\n"
    430         "__%sscan_by_string_n_field(begin__tmp, __%smin( end__tmp, N ## _vec_len(vec__tmp)), N ## _ ## NK ## _get, vec__tmp, N ## _vec_at, N ## _vec_len, s__tmp, n__tmp)\\\n"
    431         "static inline size_t N ## _vec_rscan_by_ ## NK(N ## _vec_t vec__tmp, const char *s__tmp)\\\n"
    432         "__%srscan_by_string_field(0, N ## _vec_len(vec__tmp), N ## _ ## NK ## _get, vec__tmp, N ## _vec_at, N ## _vec_len, s__tmp)\\\n"
    433         "static inline size_t N ## _vec_rscan_n_by_ ## NK(N ## _vec_t vec__tmp, const char *s__tmp, size_t n__tmp)\\\n"
    434         "__%srscan_by_string_n_field(0, N ## _vec_len(vec__tmp), N ## _ ## NK ## _get, vec__tmp, N ## _vec_at, N ## _vec_len, s__tmp, n__tmp)\\\n"
    435         "static inline size_t N ## _vec_rscan_ex_by_ ## NK(N ## _vec_t vec__tmp, size_t begin__tmp, size_t end__tmp, const char *s__tmp)\\\n"
    436         "__%srscan_by_string_field(begin__tmp, __%smin(end__tmp, N ## _vec_len(vec__tmp)), N ## _ ## NK ## _get, vec__tmp, N ## _vec_at, N ## _vec_len, s__tmp)\\\n"
    437         "static inline size_t N ## _vec_rscan_ex_n_by_ ## NK(N ## _vec_t vec__tmp, size_t begin__tmp, size_t end__tmp, const char *s__tmp, size_t n__tmp)\\\n"
    438         "__%srscan_by_string_n_field(begin__tmp, __%smin( end__tmp, N ## _vec_len(vec__tmp)), N ## _ ## NK ## _get, vec__tmp, N ## _vec_at, N ## _vec_len, s__tmp, n__tmp)\n",
    439         nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc);
    440     fprintf(out->fp,
    441         "#define __%sdefine_default_scan_by_scalar_field(N, NK, TK)\\\n"
    442         "static inline size_t N ## _vec_scan(N ## _vec_t vec__tmp, TK key__tmp)\\\n"
    443         "{ return N ## _vec_scan_by_ ## NK(vec__tmp, key__tmp); }\\\n"
    444         "static inline size_t N ## _vec_scan_ex(N ## _vec_t vec__tmp, size_t begin__tmp, size_t end__tmp, TK key__tmp)\\\n"
    445         "{ return N ## _vec_scan_ex_by_ ## NK(vec__tmp, begin__tmp, end__tmp, key__tmp); }\\\n"
    446         "static inline size_t N ## _vec_rscan(N ## _vec_t vec__tmp, TK key__tmp)\\\n"
    447         "{ return N ## _vec_rscan_by_ ## NK(vec__tmp, key__tmp); }\\\n"
    448         "static inline size_t N ## _vec_rscan_ex(N ## _vec_t vec__tmp, size_t begin__tmp, size_t end__tmp, TK key__tmp)\\\n"
    449         "{ return N ## _vec_rscan_ex_by_ ## NK(vec__tmp, begin__tmp, end__tmp, key__tmp); }\n",
    450         nsc);
    451     fprintf(out->fp,
    452         "#define __%sdefine_default_scan_by_string_field(N, NK) \\\n"
    453         "static inline size_t N ## _vec_scan(N ## _vec_t vec__tmp, const char *s__tmp)\\\n"
    454         "{ return N ## _vec_scan_by_ ## NK(vec__tmp, s__tmp); }\\\n"
    455         "static inline size_t N ## _vec_scan_n(N ## _vec_t vec__tmp, const char *s__tmp, size_t n__tmp)\\\n"
    456         "{ return N ## _vec_scan_n_by_ ## NK(vec__tmp, s__tmp, n__tmp); }\\\n"
    457         "static inline size_t N ## _vec_scan_ex(N ## _vec_t vec__tmp, size_t begin__tmp, size_t end__tmp, const char *s__tmp)\\\n"
    458         "{ return N ## _vec_scan_ex_by_ ## NK(vec__tmp, begin__tmp, end__tmp, s__tmp); }\\\n"
    459         "static inline size_t N ## _vec_scan_ex_n(N ## _vec_t vec__tmp, size_t begin__tmp, size_t end__tmp, const char *s__tmp, size_t n__tmp)\\\n"
    460         "{ return N ## _vec_scan_ex_n_by_ ## NK(vec__tmp, begin__tmp, end__tmp, s__tmp, n__tmp); }\\\n"
    461         "static inline size_t N ## _vec_rscan(N ## _vec_t vec__tmp, const char *s__tmp)\\\n"
    462         "{ return N ## _vec_rscan_by_ ## NK(vec__tmp, s__tmp); }\\\n"
    463         "static inline size_t N ## _vec_rscan_n(N ## _vec_t vec__tmp, const char *s__tmp, size_t n__tmp)\\\n"
    464         "{ return N ## _vec_rscan_n_by_ ## NK(vec__tmp, s__tmp, n__tmp); }\\\n"
    465         "static inline size_t N ## _vec_rscan_ex(N ## _vec_t vec__tmp, size_t begin__tmp, size_t end__tmp, const char *s__tmp)\\\n"
    466         "{ return N ## _vec_rscan_ex_by_ ## NK(vec__tmp, begin__tmp, end__tmp, s__tmp); }\\\n"
    467         "static inline size_t N ## _vec_rscan_ex_n(N ## _vec_t vec__tmp, size_t begin__tmp, size_t end__tmp, const char *s__tmp, size_t n__tmp)\\\n"
    468         "{ return N ## _vec_rscan_ex_n_by_ ## NK(vec__tmp, begin__tmp, end__tmp, s__tmp, n__tmp); }\n",
    469         nsc);
    470 }
    471 
    472 static void gen_helpers(fb_output_t *out)
    473 {
    474     const char *nsc = out->nsc;
    475 
    476     fprintf(out->fp,
    477         /*
    478          * Include the basic primitives for accessing flatbuffer data types independent
    479          * of endianness.
    480          *
    481          * The included file must define the basic types and accessors
    482          * prefixed with the common namespace which by default is
    483          * "flatbuffers_".
    484          */
    485         "#include \"flatcc/flatcc_flatbuffers.h\"\n"
    486         "\n\n");
    487     /*
    488      * The remapping of basic types to the common namespace makes it
    489      * possible to have different definitions. The generic
    490      * `flatbuffers_uoffset_t` etc. cannot be trusted to have one specific
    491      * size since it depends on the included `flatcc/flatcc_types.h`
    492      * filer, but the namespace prefixed types can be trusted if used carefully.
    493      * For example the common namespace could be `flatbuffers_large_`
    494      * when allowing for 64 bit offsets.
    495      */
    496     if (strcmp(nsc, "flatbuffers_")) {
    497         fprintf(out->fp,
    498                 "typedef flatbuffers_uoffset_t %suoffset_t;\n"
    499                 "typedef flatbuffers_soffset_t %ssoffset_t;\n"
    500                 "typedef flatbuffers_voffset_t %svoffset_t;\n"
    501                 "typedef flatbuffers_utype_t %sutype_t;\n"
    502                 "typedef flatbuffers_bool_t %sbool_t;\n"
    503                 "\n",
    504                 nsc, nsc, nsc, nsc, nsc);
    505         fprintf(out->fp,
    506                 "#define %sendian flatbuffers_endian\n"
    507                 "__flatcc_define_basic_scalar_accessors(%s, flatbuffers_endian)"
    508                 "__flatcc_define_integer_accessors(%sbool, flatbuffers_bool_t,\\\n"
    509                 "        FLATBUFFERS_BOOL_WIDTH, flatbuffers_endian)\\\n"
    510                 "__flatcc_define_integer_accessors(%sunion_type, flatbuffers_union_type_t,\n"
    511                 "        FLATBUFFERS_UTYPE_WIDTH, flatbuffers_endian)\\\n",
    512                 "\n",
    513                 nsc, nsc, nsc);
    514         fprintf(out->fp,
    515                 "__flatcc_define_integer_accessors(__%suoffset, flatbuffers_uoffset_t,\n"
    516                 "        FLATBUFFERS_UOFFSET_WIDTH, flatbuffers_endian)\n"
    517                 "__flatcc_define_integer_accessors(__%ssoffset, flatbuffers_soffset_t,\n"
    518                 "        FLATBUFFERS_SOFFSET_WIDTH, flatbuffers_endian)\n"
    519                 "__flatcc_define_integer_accessors(__%svoffset, flatbuffers_voffset_t,\n"
    520                 "        FLATBUFFERS_VOFFSET_WIDTH, flatbuffers_endian)\n"
    521                 "__flatcc_define_integer_accessors(__%sutype, flatbuffers_utype_t,\n"
    522                 "        FLATBUFFERS_UTYPE_WIDTH, flatbuffers_endian)\n"
    523                 "__flatcc_define_integer_accessors(__%sthash, flatbuffers_thash_t,\n"
    524                 "        FLATBUFFERS_THASH_WIDTH, flatbuffers_endian)\n",
    525                 nsc, nsc, nsc, nsc, nsc);
    526         fprintf(out->fp,
    527                 "#ifndef %s_WRAP_NAMESPACE\n"
    528                 "#define %s_WRAP_NAMESPACE(ns, x) ns ## _ ## x\n"
    529                 "#endif\n",
    530                 out->nscup, out->nscup);
    531     }
    532     /* Build out a more elaborate type system based in the primitives included. */
    533     fprintf(out->fp,
    534         "#define __%sread_scalar_at_byteoffset(N, p, o) N ## _read_from_pe((uint8_t *)(p) + (o))\n"
    535         "#define __%sread_scalar(N, p) N ## _read_from_pe(p)\n",
    536         nsc, nsc);
    537     fprintf(out->fp,
    538         "#define __%sread_vt(ID, offset, t)\\\n"
    539         "%svoffset_t offset = 0;\\\n"
    540         "{   %svoffset_t id__tmp, *vt__tmp;\\\n"
    541         "    FLATCC_ASSERT(t != 0 && \"null pointer table access\");\\\n"
    542         "    id__tmp = ID;\\\n"
    543         "    vt__tmp = (%svoffset_t *)((uint8_t *)(t) -\\\n"
    544         "        __%ssoffset_read_from_pe(t));\\\n"
    545         "    if (__%svoffset_read_from_pe(vt__tmp) >= sizeof(vt__tmp[0]) * (id__tmp + 3u)) {\\\n"
    546         "        offset = __%svoffset_read_from_pe(vt__tmp + id__tmp + 2);\\\n"
    547         "    }\\\n"
    548         "}\n",
    549         nsc, nsc, nsc, nsc, nsc, nsc, nsc);
    550     fprintf(out->fp,
    551             "#define __%sfield_present(ID, t) { __%sread_vt(ID, offset__tmp, t) return offset__tmp != 0; }\n",
    552             nsc, nsc);
    553     fprintf(out->fp,
    554         "#define __%sscalar_field(T, ID, t)\\\n"
    555         "{\\\n"
    556         "    __%sread_vt(ID, offset__tmp, t)\\\n"
    557         "    if (offset__tmp) {\\\n"
    558         "        return (const T *)((uint8_t *)(t) + offset__tmp);\\\n"
    559         "    }\\\n"
    560         "    return 0;\\\n"
    561         "}\n",
    562         nsc, nsc);
    563     fprintf(out->fp,
    564         "#define __%sdefine_scalar_field(ID, N, NK, TK, T, V)\\\n"
    565         "static inline T N ## _ ## NK ## _get(N ## _table_t t__tmp)\\\n"
    566         "{ __%sread_vt(ID, offset__tmp, t__tmp)\\\n"
    567         "  return offset__tmp ? __%sread_scalar_at_byteoffset(TK, t__tmp, offset__tmp) : V;\\\n"
    568         "}\\\n", nsc, nsc, nsc);
    569     if (!out->opts->cgen_no_conflicts) {
    570         fprintf(out->fp,
    571             "static inline T N ## _ ## NK(N ## _table_t t__tmp)\\\n"
    572             "{ __%sread_vt(ID, offset__tmp, t__tmp)\\\n"
    573             "  return offset__tmp ? __%sread_scalar_at_byteoffset(TK, t__tmp, offset__tmp) : V;\\\n"
    574             "}\\\n", nsc, nsc);
    575     }
    576     fprintf(out->fp,
    577         "static inline const T *N ## _ ## NK ## _get_ptr(N ## _table_t t__tmp)\\\n"
    578         "__%sscalar_field(T, ID, t__tmp)\\\n", nsc);
    579     fprintf(out->fp,
    580         "static inline int N ## _ ## NK ## _is_present(N ## _table_t t__tmp)\\\n"
    581         "__%sfield_present(ID, t__tmp)",nsc);
    582     if (out->opts->allow_scan_for_all_fields) {
    583         fprintf(out->fp, "\\\n__%sdefine_scan_by_scalar_field(N, NK, T)\n", nsc);
    584     } else {
    585         fprintf(out->fp, "\n");
    586     }
    587     fprintf(out->fp,
    588         "#define __%sdefine_scalar_optional_field(ID, N, NK, TK, T, V)\\\n"
    589         "__%sdefine_scalar_field(ID, N, NK, TK, T, V)\\\n"
    590         "static inline TK ## _option_t N ## _ ## NK ## _option(N ## _table_t t__tmp)\\\n"
    591         "{ TK ## _option_t ret; __%sread_vt(ID, offset__tmp, t__tmp)\\\n"
    592         "  ret.is_null = offset__tmp == 0; ret.value = offset__tmp ?\\\n"
    593         "  __%sread_scalar_at_byteoffset(TK, t__tmp, offset__tmp) : V;\\\n"
    594         "  return ret; }\n", nsc, nsc, nsc, nsc);
    595     fprintf(out->fp,
    596         "#define __%sstruct_field(T, ID, t, r)\\\n"
    597         "{\\\n"
    598         "    __%sread_vt(ID, offset__tmp, t)\\\n"
    599         "    if (offset__tmp) {\\\n"
    600         "        return (T)((uint8_t *)(t) + offset__tmp);\\\n"
    601         "    }\\\n"
    602         "    FLATCC_ASSERT(!(r) && \"required field missing\");\\\n"
    603         "    return 0;\\\n"
    604         "}\n",
    605         nsc, nsc);
    606     fprintf(out->fp,
    607         "#define __%soffset_field(T, ID, t, r, adjust)\\\n"
    608         "{\\\n"
    609         "    %suoffset_t *elem__tmp;\\\n"
    610         "    __%sread_vt(ID, offset__tmp, t)\\\n"
    611         "    if (offset__tmp) {\\\n"
    612         "        elem__tmp = (%suoffset_t *)((uint8_t *)(t) + offset__tmp);\\\n"
    613         "        /* Add sizeof so C api can have raw access past header field. */\\\n"
    614         "        return (T)((uint8_t *)(elem__tmp) + adjust +\\\n"
    615         "              __%suoffset_read_from_pe(elem__tmp));\\\n"
    616         "    }\\\n"
    617         "    FLATCC_ASSERT(!(r) && \"required field missing\");\\\n"
    618         "    return 0;\\\n"
    619         "}\n",
    620         nsc, nsc, nsc, nsc, nsc);
    621     fprintf(out->fp,
    622         "#define __%svector_field(T, ID, t, r) __%soffset_field(T, ID, t, r, sizeof(%suoffset_t))\n"
    623         "#define __%stable_field(T, ID, t, r) __%soffset_field(T, ID, t, r, 0)\n",
    624         nsc, nsc, nsc, nsc, nsc);
    625     fprintf(out->fp,
    626         "#define __%sdefine_struct_field(ID, N, NK, T, r)\\\n"
    627         "static inline T N ## _ ## NK ## _get(N ## _table_t t__tmp)\\\n"
    628         "__%sstruct_field(T, ID, t__tmp, r)", nsc, nsc);
    629     if (!out->opts->cgen_no_conflicts) {
    630         fprintf(out->fp,
    631             "\\\nstatic inline T N ## _ ## NK(N ## _table_t t__tmp)\\\n"
    632             "__%sstruct_field(T, ID, t__tmp, r)", nsc);
    633     }
    634     fprintf(out->fp,
    635         "\\\nstatic inline int N ## _ ## NK ## _is_present(N ## _table_t t__tmp)\\\n"
    636         "__%sfield_present(ID, t__tmp)\n", nsc);
    637     fprintf(out->fp,
    638         "#define __%sdefine_vector_field(ID, N, NK, T, r)\\\n"
    639         "static inline T N ## _ ## NK ## _get(N ## _table_t t__tmp)\\\n"
    640         "__%svector_field(T, ID, t__tmp, r)", nsc, nsc);
    641     if (!out->opts->cgen_no_conflicts) {
    642         fprintf(out->fp,
    643             "\\\nstatic inline T N ## _ ## NK(N ## _table_t t__tmp)\\\n"
    644             "__%svector_field(T, ID, t__tmp, r)", nsc);
    645     }
    646     fprintf(out->fp,
    647         "\\\nstatic inline int N ## _ ## NK ## _is_present(N ## _table_t t__tmp)\\\n"
    648         "__%sfield_present(ID, t__tmp)\n", nsc);
    649     fprintf(out->fp,
    650         "#define __%sdefine_table_field(ID, N, NK, T, r)\\\n"
    651         "static inline T N ## _ ## NK ## _get(N ## _table_t t__tmp)\\\n"
    652         "__%stable_field(T, ID, t__tmp, r)", nsc, nsc);
    653     if (!out->opts->cgen_no_conflicts) {
    654         fprintf(out->fp,
    655             "\\\nstatic inline T N ## _ ## NK(N ## _table_t t__tmp)\\\n"
    656             "__%stable_field(T, ID, t__tmp, r)", nsc);
    657     }
    658     fprintf(out->fp,
    659         "\\\nstatic inline int N ## _ ## NK ## _is_present(N ## _table_t t__tmp)\\\n"
    660         "__%sfield_present(ID, t__tmp)\n", nsc);
    661     fprintf(out->fp,
    662         "#define __%sdefine_string_field(ID, N, NK, r)\\\n"
    663         "static inline %sstring_t N ## _ ## NK ## _get(N ## _table_t t__tmp)\\\n"
    664         "__%svector_field(%sstring_t, ID, t__tmp, r)", nsc, nsc, nsc, nsc);
    665     if (!out->opts->cgen_no_conflicts) {
    666         fprintf(out->fp,
    667         "\\\nstatic inline %sstring_t N ## _ ## NK(N ## _table_t t__tmp)\\\n"
    668         "__%svector_field(%sstring_t, ID, t__tmp, r)", nsc, nsc, nsc);
    669     }
    670     fprintf(out->fp,
    671         "\\\nstatic inline int N ## _ ## NK ## _is_present(N ## _table_t t__tmp)\\\n"
    672         "__%sfield_present(ID, t__tmp)", nsc);
    673         if (out->opts->allow_scan_for_all_fields) {
    674             fprintf(out->fp, "\\\n__%sdefine_scan_by_string_field(N, NK)\n", nsc);
    675         } else {
    676             fprintf(out->fp, "\n");
    677         }
    678     fprintf(out->fp,
    679         "#define __%svec_len(vec)\\\n"
    680         "{ return (vec) ? (size_t)__%suoffset_read_from_pe((flatbuffers_uoffset_t *)vec - 1) : 0; }\n"
    681         "#define __%sstring_len(s) __%svec_len(s)\n",
    682         nsc, nsc, nsc, nsc);
    683     fprintf(out->fp,
    684         "static inline size_t %svec_len(const void *vec)\n"
    685         "__%svec_len(vec)\n",
    686         nsc, nsc);
    687     fprintf(out->fp,
    688         /* Tb is the base type for loads. */
    689         "#define __%sscalar_vec_at(N, vec, i)\\\n"
    690         "{ FLATCC_ASSERT(%svec_len(vec) > (i) && \"index out of range\");\\\n"
    691         "  return __%sread_scalar(N, &(vec)[i]); }\n",
    692         nsc, nsc, nsc);
    693     fprintf(out->fp,
    694         "#define __%sstruct_vec_at(vec, i)\\\n"
    695         "{ FLATCC_ASSERT(%svec_len(vec) > (i) && \"index out of range\"); return (vec) + (i); }\n",
    696         nsc, nsc);
    697     fprintf(out->fp,
    698         "/* `adjust` skips past the header for string vectors. */\n"
    699         "#define __%soffset_vec_at(T, vec, i, adjust)\\\n"
    700         "{ const %suoffset_t *elem__tmp = (vec) + (i);\\\n"
    701         "  FLATCC_ASSERT(%svec_len(vec) > (i) && \"index out of range\");\\\n"
    702         "  return (T)((uint8_t *)(elem__tmp) + (size_t)__%suoffset_read_from_pe(elem__tmp) + (adjust)); }\n",
    703         nsc, nsc, nsc, nsc);
    704     fprintf(out->fp,
    705             "#define __%sdefine_scalar_vec_len(N)\\\n"
    706             "static inline size_t N ## _vec_len(N ##_vec_t vec__tmp)\\\n"
    707             "{ return %svec_len(vec__tmp); }\n",
    708             nsc, nsc);
    709     fprintf(out->fp,
    710             "#define __%sdefine_scalar_vec_at(N, T) \\\n"
    711             "static inline T N ## _vec_at(N ## _vec_t vec__tmp, size_t i__tmp)\\\n"
    712             "__%sscalar_vec_at(N, vec__tmp, i__tmp)\n",
    713             nsc, nsc);
    714     fprintf(out->fp,
    715             "typedef const char *%sstring_t;\n"
    716             "static inline size_t %sstring_len(%sstring_t s)\n"
    717             "__%sstring_len(s)\n",
    718             nsc, nsc, nsc, nsc);
    719     fprintf(out->fp,
    720             "typedef const %suoffset_t *%sstring_vec_t;\n"
    721             "typedef %suoffset_t *%sstring_mutable_vec_t;\n"
    722             "static inline size_t %sstring_vec_len(%sstring_vec_t vec)\n"
    723             "__%svec_len(vec)\n"
    724             "static inline %sstring_t %sstring_vec_at(%sstring_vec_t vec, size_t i)\n"
    725             "__%soffset_vec_at(%sstring_t, vec, i, sizeof(vec[0]))\n",
    726             nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc);
    727     fprintf(out->fp, "typedef const void *%sgeneric_t;\n", nsc);
    728     fprintf(out->fp, "typedef void *%smutable_generic_t;\n", nsc);
    729     fprintf(out->fp,
    730         "static inline %sstring_t %sstring_cast_from_generic(const %sgeneric_t p)\n"
    731         "{ return p ? ((const char *)p) + __%suoffset__size() : 0; }\n",
    732         nsc, nsc, nsc, nsc);
    733     fprintf(out->fp,
    734             "typedef const %suoffset_t *%sgeneric_vec_t;\n"
    735             "typedef %suoffset_t *%sgeneric_table_mutable_vec_t;\n"
    736             "static inline size_t %sgeneric_vec_len(%sgeneric_vec_t vec)\n"
    737             "__%svec_len(vec)\n"
    738             "static inline %sgeneric_t %sgeneric_vec_at(%sgeneric_vec_t vec, size_t i)\n"
    739             "__%soffset_vec_at(%sgeneric_t, vec, i, 0)\n"
    740             "static inline %sgeneric_t %sgeneric_vec_at_as_string(%sgeneric_vec_t vec, size_t i)\n"
    741             "__%soffset_vec_at(%sgeneric_t, vec, i, sizeof(vec[0]))\n",
    742             nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc);
    743     gen_union(out);
    744     gen_find(out);
    745     gen_scan(out);
    746     if (out->opts->cgen_sort) {
    747         gen_sort(out);
    748         fprintf(out->fp,
    749             "#define __%ssort_vector_field(N, NK, T, t)\\\n"
    750             "{ T ## _mutable_vec_t v__tmp = (T ## _mutable_vec_t) N ## _ ## NK ## _get(t);\\\n"
    751             "  if (v__tmp) T ## _vec_sort(v__tmp); }\n",
    752             nsc);
    753         fprintf(out->fp,
    754             "#define __%ssort_table_field(N, NK, T, t)\\\n"
    755             "{ T ## _sort((T ## _mutable_table_t)N ## _ ## NK ## _get(t)); }\n",
    756             nsc);
    757         fprintf(out->fp,
    758             "#define __%ssort_union_field(N, NK, T, t)\\\n"
    759             "{ T ## _sort(T ## _mutable_union_cast(N ## _ ## NK ## _union(t))); }\n",
    760             nsc);
    761         fprintf(out->fp,
    762             "#define __%ssort_table_vector_field_elements(N, NK, T, t)\\\n"
    763             "{ T ## _vec_t v__tmp = N ## _ ## NK ## _get(t); size_t i__tmp, n__tmp;\\\n"
    764             "  n__tmp = T ## _vec_len(v__tmp); for (i__tmp = 0; i__tmp < n__tmp; ++i__tmp) {\\\n"
    765             "  T ## _sort((T ## _mutable_table_t)T ## _vec_at(v__tmp, i__tmp)); }}\n",
    766             nsc);
    767         fprintf(out->fp,
    768             "#define __%ssort_union_vector_field_elements(N, NK, T, t)\\\n"
    769             "{ T ## _union_vec_t v__tmp = N ## _ ## NK ## _union(t); size_t i__tmp, n__tmp;\\\n"
    770             "  n__tmp = T ## _union_vec_len(v__tmp); for (i__tmp = 0; i__tmp < n__tmp; ++i__tmp) {\\\n"
    771             "  T ## _sort(T ## _mutable_union_cast(T ## _union_vec_at(v__tmp, i__tmp))); }}\n",
    772             nsc);
    773     } else {
    774         fprintf(out->fp, "/* sort disabled */\n");
    775     }
    776     fprintf(out->fp,
    777             "#define __%sdefine_scalar_vector(N, T)\\\n"
    778             "typedef const T *N ## _vec_t;\\\n"
    779             "typedef T *N ## _mutable_vec_t;\\\n"
    780             "__%sdefine_scalar_vec_len(N)\\\n"
    781             "__%sdefine_scalar_vec_at(N, T)\\\n"
    782             "__%sdefine_scalar_find(N, T)\\\n"
    783             "__%sdefine_scalar_scan(N, T)",
    784             nsc, nsc, nsc, nsc, nsc);
    785     if (out->opts->cgen_sort) {
    786         fprintf(out->fp, "\\\n__%sdefine_scalar_sort(N, T)\n", nsc);
    787     } else {
    788         fprintf(out->fp, "\n");
    789     }
    790     fprintf(out->fp, "\n");
    791     /* Elaborate on the included basic type system. */
    792     fprintf(out->fp,
    793             "#define __%sdefine_integer_type(N, T, W)\\\n"
    794             "__flatcc_define_integer_accessors(N, T, W, %sendian)\\\n"
    795             "__%sdefine_scalar_vector(N, T)\n",
    796             nsc, nsc, nsc);
    797     fprintf(out->fp,
    798             "__%sdefine_scalar_vector(%sbool, %sbool_t)\n"
    799             "__%sdefine_scalar_vector(%schar, char)\n"
    800             "__%sdefine_scalar_vector(%suint8, uint8_t)\n"
    801             "__%sdefine_scalar_vector(%sint8, int8_t)\n"
    802             "__%sdefine_scalar_vector(%suint16, uint16_t)\n"
    803             "__%sdefine_scalar_vector(%sint16, int16_t)\n"
    804             "__%sdefine_scalar_vector(%suint32, uint32_t)\n"
    805             "__%sdefine_scalar_vector(%sint32, int32_t)\n"
    806             "__%sdefine_scalar_vector(%suint64, uint64_t)\n"
    807             "__%sdefine_scalar_vector(%sint64, int64_t)\n"
    808             "__%sdefine_scalar_vector(%sfloat, float)\n"
    809             "__%sdefine_scalar_vector(%sdouble, double)\n"
    810             "__%sdefine_scalar_vector(%sunion_type, %sunion_type_t)\n",
    811             nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc,
    812             nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc);
    813     fprintf(out->fp,
    814             "static inline size_t %sstring_vec_find(%sstring_vec_t vec, const char *s)\n"
    815             "__%sfind_by_string_field(__%sidentity, vec, %sstring_vec_at, %sstring_vec_len, s)\n"
    816             "static inline size_t %sstring_vec_find_n(%sstring_vec_t vec, const char *s, size_t n)\n"
    817             "__%sfind_by_string_n_field(__%sidentity, vec, %sstring_vec_at, %sstring_vec_len, s, n)\n",
    818             nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc);
    819     fprintf(out->fp,
    820             "static inline size_t %sstring_vec_scan(%sstring_vec_t vec, const char *s)\n"
    821             "__%sscan_by_string_field(0, %sstring_vec_len(vec), __%sidentity, vec, %sstring_vec_at, %sstring_vec_len, s)\n"
    822             "static inline size_t %sstring_vec_scan_n(%sstring_vec_t vec, const char *s, size_t n)\n"
    823             "__%sscan_by_string_n_field(0, %sstring_vec_len(vec), __%sidentity, vec, %sstring_vec_at, %sstring_vec_len, s, n)\n"
    824             "static inline size_t %sstring_vec_scan_ex(%sstring_vec_t vec, size_t begin, size_t end, const char *s)\n"
    825             "__%sscan_by_string_field(begin, __%smin(end, %sstring_vec_len(vec)), __%sidentity, vec, %sstring_vec_at, %sstring_vec_len, s)\n"
    826             "static inline size_t %sstring_vec_scan_ex_n(%sstring_vec_t vec, size_t begin, size_t end, const char *s, size_t n)\n"
    827             "__%sscan_by_string_n_field(begin, __%smin(end, %sstring_vec_len(vec)), __%sidentity, vec, %sstring_vec_at, %sstring_vec_len, s, n)\n"
    828             "static inline size_t %sstring_vec_rscan(%sstring_vec_t vec, const char *s)\n"
    829             "__%srscan_by_string_field(0, %sstring_vec_len(vec), __%sidentity, vec, %sstring_vec_at, %sstring_vec_len, s)\n"
    830             "static inline size_t %sstring_vec_rscan_n(%sstring_vec_t vec, const char *s, size_t n)\n"
    831             "__%srscan_by_string_n_field(0, %sstring_vec_len(vec), __%sidentity, vec, %sstring_vec_at, %sstring_vec_len, s, n)\n"
    832             "static inline size_t %sstring_vec_rscan_ex(%sstring_vec_t vec, size_t begin, size_t end, const char *s)\n"
    833             "__%srscan_by_string_field(begin, __%smin(end, %sstring_vec_len(vec)), __%sidentity, vec, %sstring_vec_at, %sstring_vec_len, s)\n"
    834             "static inline size_t %sstring_vec_rscan_ex_n(%sstring_vec_t vec, size_t begin, size_t end, const char *s, size_t n)\n"
    835             "__%srscan_by_string_n_field(begin, __%smin(end, %sstring_vec_len(vec)), __%sidentity, vec, %sstring_vec_at, %sstring_vec_len, s, n)\n",
    836             nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc,
    837             nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc,
    838             nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc,
    839             nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc,
    840             nsc, nsc, nsc, nsc);
    841     if (out->opts->cgen_sort) {
    842         fprintf(out->fp, "__%sdefine_string_sort()\n", nsc);
    843     }
    844     fprintf(out->fp,
    845         "#define __%sdefine_struct_scalar_fixed_array_field(N, NK, TK, T, L)\\\n"
    846         "static inline T N ## _ ## NK ## _get(N ## _struct_t t__tmp, size_t i__tmp)\\\n"
    847         "{ if (!t__tmp || i__tmp >= L) return 0;\\\n"
    848         "  return __%sread_scalar(TK, &(t__tmp->NK[i__tmp])); }\\\n"
    849         "static inline const T *N ## _ ## NK ## _get_ptr(N ## _struct_t t__tmp)\\\n"
    850         "{ return t__tmp ? t__tmp->NK : 0; }\\\n"
    851         "static inline size_t N ## _ ## NK ## _get_len(void) { return L; }",
    852         nsc, nsc);
    853     if (!out->opts->cgen_no_conflicts) {
    854         fprintf(out->fp,
    855             "\\\nstatic inline T N ## _ ## NK (N ## _struct_t t__tmp, size_t i__tmp)\\\n"
    856             "{ return N ## _ ## NK ## _get(t__tmp, i__tmp); }");
    857     }
    858     fprintf(out->fp, "\n");;
    859     fprintf(out->fp,
    860         "#define __%sdefine_struct_struct_fixed_array_field(N, NK, T, L)\\\n"
    861         "static inline T N ## _ ## NK ## _get(N ## _struct_t t__tmp, size_t i__tmp)\\\n"
    862         "{ if (!t__tmp || i__tmp >= L) return 0; return t__tmp->NK + i__tmp; }"
    863         "static inline T N ## _ ## NK ## _get_ptr(N ## _struct_t t__tmp)\\\n"
    864         "{ return t__tmp ? t__tmp->NK : 0; }\\\n"
    865         "static inline size_t N ## _ ## NK ## _get_len(void) { return L; }",
    866         nsc);
    867     if (!out->opts->cgen_no_conflicts) {
    868         fprintf(out->fp,
    869             "\\\nstatic inline T N ## _ ## NK(N ## _struct_t t__tmp, size_t i__tmp)\\\n"
    870             "{ if (!t__tmp || i__tmp >= L) return 0; return t__tmp->NK + i__tmp; }");
    871     }
    872     fprintf(out->fp, "\n");
    873     fprintf(out->fp,
    874         "#define __%sdefine_struct_scalar_field(N, NK, TK, T)\\\n"
    875         "static inline T N ## _ ## NK ## _get(N ## _struct_t t__tmp)\\\n"
    876         "{ return t__tmp ? __%sread_scalar(TK, &(t__tmp->NK)) : 0; }\\\n"
    877         "static inline const T *N ## _ ## NK ## _get_ptr(N ## _struct_t t__tmp)\\\n"
    878         "{ return t__tmp ? &(t__tmp->NK) : 0; }",
    879         nsc, nsc);
    880     if (!out->opts->cgen_no_conflicts) {
    881         fprintf(out->fp,
    882             "\\\nstatic inline T N ## _ ## NK (N ## _struct_t t__tmp)\\\n"
    883             "{ return t__tmp ? __%sread_scalar(TK, &(t__tmp->NK)) : 0; }",
    884             nsc);
    885     }
    886     if (out->opts->allow_scan_for_all_fields) {
    887         fprintf(out->fp, "\\\n__%sdefine_scan_by_scalar_field(N, NK, T)\n", nsc);
    888     } else {
    889         fprintf(out->fp, "\n");
    890     }
    891     fprintf(out->fp,
    892             "#define __%sdefine_struct_struct_field(N, NK, T)\\\n"
    893             "static inline T N ## _ ## NK ## _get(N ## _struct_t t__tmp) { return t__tmp ? &(t__tmp->NK) : 0; }",
    894             nsc);
    895     if (!out->opts->cgen_no_conflicts) {
    896     fprintf(out->fp,
    897             "\\\nstatic inline T N ## _ ## NK (N ## _struct_t t__tmp) { return t__tmp ? &(t__tmp->NK) : 0; }\n");
    898     } else {
    899         fprintf(out->fp, "\n");
    900     }
    901     fprintf(out->fp,
    902             "/* If fid is null, the function returns true without testing as buffer is not expected to have any id. */\n"
    903             "static inline int %shas_identifier(const void *buffer, const char *fid)\n"
    904             "{ %sthash_t id, id2 = 0; if (fid == 0) { return 1; };\n"
    905             "  id2 = %stype_hash_from_string(fid);\n"
    906             "  id = __%sthash_read_from_pe(((%suoffset_t *)buffer) + 1);\n"
    907             "  return id2 == 0 || id == id2; }\n"
    908             "static inline int %shas_type_hash(const void *buffer, %sthash_t thash)\n"
    909             "{ return thash == 0 || (__%sthash_read_from_pe((%suoffset_t *)buffer + 1) == thash); }\n\n"
    910             "static inline %sthash_t %sget_type_hash(const void *buffer)\n"
    911             "{ return __%sthash_read_from_pe((flatbuffers_uoffset_t *)buffer + 1); }\n\n"
    912             "#define %sverify_endian() %shas_identifier(\"\\x00\\x00\\x00\\x00\" \"1234\", \"1234\")\n",
    913             nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc);
    914     fprintf(out->fp,
    915             "static inline void *%sread_size_prefix(void *b, size_t *size_out)\n"
    916             "{ if (size_out) { *size_out = (size_t)__%suoffset_read_from_pe(b); }\n"
    917             "  return (uint8_t *)b + sizeof(%suoffset_t); }\n", nsc, nsc, nsc);
    918     fprintf(out->fp,
    919             "/* Null file identifier accepts anything, otherwise fid should be 4 characters. */\n"
    920             "#define __%sread_root(T, K, buffer, fid)\\\n"
    921             "  ((!buffer || !%shas_identifier(buffer, fid)) ? 0 :\\\n"
    922             "  ((T ## _ ## K ## t)(((uint8_t *)buffer) +\\\n"
    923             "    __%suoffset_read_from_pe(buffer))))\n"
    924             "#define __%sread_typed_root(T, K, buffer, thash)\\\n"
    925             "  ((!buffer || !%shas_type_hash(buffer, thash)) ? 0 :\\\n"
    926             "  ((T ## _ ## K ## t)(((uint8_t *)buffer) +\\\n"
    927             "    __%suoffset_read_from_pe(buffer))))\n",
    928             nsc, nsc, nsc, nsc, nsc, nsc);
    929     fprintf(out->fp,
    930             "#define __%snested_buffer_as_root(C, N, T, K)\\\n"
    931             "static inline T ## _ ## K ## t C ## _ ## N ## _as_root_with_identifier(C ## _ ## table_t t__tmp, const char *fid__tmp)\\\n"
    932             "{ const uint8_t *buffer__tmp = C ## _ ## N(t__tmp); return __%sread_root(T, K, buffer__tmp, fid__tmp); }\\\n"
    933             "static inline T ## _ ## K ## t C ## _ ## N ## _as_typed_root(C ## _ ## table_t t__tmp)\\\n"
    934             "{ const uint8_t *buffer__tmp = C ## _ ## N(t__tmp); return __%sread_root(T, K, buffer__tmp, C ## _ ## type_identifier); }\\\n"
    935             "static inline T ## _ ## K ## t C ## _ ## N ## _as_root(C ## _ ## table_t t__tmp)\\\n"
    936             "{ const char *fid__tmp = T ## _file_identifier;\\\n"
    937             "  const uint8_t *buffer__tmp = C ## _ ## N(t__tmp); return __%sread_root(T, K, buffer__tmp, fid__tmp); }\n",
    938             nsc, nsc, nsc, nsc);
    939     fprintf(out->fp,
    940             "#define __%sbuffer_as_root(N, K)\\\n"
    941             "static inline N ## _ ## K ## t N ## _as_root_with_identifier(const void *buffer__tmp, const char *fid__tmp)\\\n"
    942             "{ return __%sread_root(N, K, buffer__tmp, fid__tmp); }\\\n"
    943             "static inline N ## _ ## K ## t N ## _as_root_with_type_hash(const void *buffer__tmp, %sthash_t thash__tmp)\\\n"
    944             "{ return __%sread_typed_root(N, K, buffer__tmp, thash__tmp); }\\\n"
    945             "static inline N ## _ ## K ## t N ## _as_root(const void *buffer__tmp)\\\n"
    946             "{ const char *fid__tmp = N ## _file_identifier;\\\n"
    947             "  return __%sread_root(N, K, buffer__tmp, fid__tmp); }\\\n"
    948             "static inline N ## _ ## K ## t N ## _as_typed_root(const void *buffer__tmp)\\\n"
    949             "{ return __%sread_typed_root(N, K, buffer__tmp, N ## _type_hash); }\n"
    950             "#define __%sstruct_as_root(N) __%sbuffer_as_root(N, struct_)\n"
    951             "#define __%stable_as_root(N) __%sbuffer_as_root(N, table_)\n",
    952             nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc, nsc);
    953     fprintf(out->fp, "\n");
    954 }
    955 
    956 int fb_gen_common_c_header(fb_output_t *out)
    957 {
    958     const char *nscup = out->nscup;
    959 
    960     fprintf(out->fp,
    961         "#ifndef %s_COMMON_READER_H\n"
    962         "#define %s_COMMON_READER_H\n",
    963         nscup, nscup);
    964     fprintf(out->fp, "\n/* " FLATCC_GENERATED_BY " */\n\n");
    965     fprintf(out->fp, "/* Common FlatBuffers read functionality for C. */\n\n");
    966     if (!out->opts->cgen_sort) {
    967         fprintf(out->fp,
    968                 "/*"
    969                 " * This code is generated without support for vector sort operations\n"
    970                 " * but find operations are supported on pre-sorted vectors.\n"
    971                 " */\n");
    972     }
    973     gen_prologue(out);
    974     gen_helpers(out);
    975     gen_epilogue(out);
    976     fprintf(out->fp,
    977         "#endif /* %s_COMMON_H */\n",
    978         nscup);
    979     return 0;
    980 }
    981 
    982 static void gen_pretext(fb_output_t *out)
    983 {
    984     const char *nsc = out->nsc;
    985     const char *nscup = out->nscup;
    986 
    987     int do_pad = out->opts->cgen_pad;
    988 
    989     fprintf(out->fp,
    990         "#ifndef %s_READER_H\n"
    991         "#define %s_READER_H\n",
    992         out->S->basenameup, out->S->basenameup);
    993 
    994     fprintf(out->fp, "\n/* " FLATCC_GENERATED_BY " */\n\n");
    995     if (do_pad) {
    996         fprintf(out->fp,
    997         "/*\n"
    998         " * Generated with 'pad' option which expects #pragma pack(1) and\n"
    999         " * #pragma pack() to be supported, and which adds extra padding\n"
   1000         " * fields to structs.\n"
   1001         " *\n"
   1002         " * This is mostly relevant for some micro controller platforms, but\n"
   1003         " * may also be needed with 'force_align' attributes > 16.\n"
   1004         " *\n"
   1005         " * The default output uses C11 <stdalign.h> alignas(n) which can be\n"
   1006         " * defined as `__attribute__((aligned (n)))` or similar on many\n"
   1007         " * older platforms.\n"
   1008         " */\n"
   1009         "\n");
   1010     }
   1011 
   1012     fprintf(out->fp,
   1013             "#ifndef %s_COMMON_READER_H\n"
   1014             "#include \"%scommon_reader.h\"\n"
   1015             "#endif\n",
   1016             nscup, nsc);
   1017     fb_gen_c_includes(out, "_reader.h", "_READER_H");
   1018 
   1019     /*
   1020      * Must be in included in every file using static_assert to ensure
   1021      * static_assert_scope.h counter can avoid conflicts.
   1022      */
   1023     fprintf(out->fp,
   1024                 "#include \"flatcc/flatcc_flatbuffers.h\"\n");
   1025     if (!do_pad) {
   1026         fprintf(out->fp,
   1027                 "#ifndef __alignas_is_defined\n"
   1028                 "#include <stdalign.h>\n"
   1029                 "#endif\n");
   1030     }
   1031     gen_prologue(out);
   1032     if (out->S->file_identifier.type == vt_string) {
   1033         fprintf(out->fp,
   1034             "#undef %sidentifier\n"
   1035             "#define %sidentifier \"%.*s\"\n",
   1036             nsc,
   1037             nsc, out->S->file_identifier.s.len, out->S->file_identifier.s.s);
   1038     } else {
   1039         fprintf(out->fp,
   1040             "#ifndef %sidentifier\n"
   1041             "#define %sidentifier 0\n"
   1042             "#endif\n",
   1043             nsc, nsc);
   1044     }
   1045     if (out->S->file_extension.type == vt_string) {
   1046         fprintf(out->fp,
   1047             "#undef %sextension\n"
   1048             "#define %sextension \"%.*s\"\n",
   1049             nsc,
   1050             nsc, out->S->file_extension.s.len, out->S->file_extension.s.s);
   1051     } else {
   1052         fprintf(out->fp,
   1053             "#ifndef %sextension\n"
   1054             "#define %sextension \"%s\"\n"
   1055             "#endif\n",
   1056             nsc, nsc, out->opts->default_bin_ext);
   1057     }
   1058     fprintf(out->fp, "\n");
   1059 }
   1060 
   1061 static void gen_footer(fb_output_t *out)
   1062 {
   1063     gen_epilogue(out);
   1064     fprintf(out->fp, "#endif /* %s_READER_H */\n", out->S->basenameup);
   1065 }
   1066 
   1067 static void gen_forward_decl(fb_output_t *out, fb_compound_type_t *ct)
   1068 {
   1069     fb_scoped_name_t snt;
   1070     const char *nsc = out->nsc;
   1071 
   1072     fb_clear(snt);
   1073 
   1074     assert(ct->symbol.kind == fb_is_struct || ct->symbol.kind == fb_is_table);
   1075 
   1076     fb_compound_name(ct, &snt);
   1077     if (ct->symbol.kind == fb_is_struct) {
   1078         if (ct->size == 0) {
   1079             gen_panic(out, "internal error: unexpected empty struct");
   1080             return;
   1081         } else {
   1082             fprintf(out->fp, "typedef struct %s %s_t;\n",
   1083                     snt.text, snt.text);
   1084         }
   1085         fprintf(out->fp, "typedef const %s_t *%s_struct_t;\n",
   1086                 snt.text, snt.text);
   1087         fprintf(out->fp, "typedef %s_t *%s_mutable_struct_t;\n",
   1088                 snt.text, snt.text);
   1089         fprintf(out->fp, "typedef const %s_t *%s_vec_t;\n",
   1090                 snt.text, snt.text);
   1091         fprintf(out->fp, "typedef %s_t *%s_mutable_vec_t;\n",
   1092                 snt.text, snt.text);
   1093     } else {
   1094         fprintf(out->fp, "typedef const struct %s_table *%s_table_t;\n",
   1095                 snt.text, snt.text);
   1096         fprintf(out->fp, "typedef struct %s_table *%s_mutable_table_t;\n",
   1097                 snt.text, snt.text);
   1098         fprintf(out->fp, "typedef const %suoffset_t *%s_vec_t;\n", nsc, snt.text);
   1099         fprintf(out->fp, "typedef %suoffset_t *%s_mutable_vec_t;\n", nsc, snt.text);
   1100     }
   1101 }
   1102 
   1103 static inline void print_doc(fb_output_t *out, const char *indent, fb_doc_t *doc)
   1104 {
   1105     long ln = 0;
   1106     int first = 1;
   1107     if (doc == 0) {
   1108         return;
   1109     }
   1110     while (doc) {
   1111         if (ln != doc->ident->linenum) {
   1112             if (first) {
   1113                 /* Not all C compilers understand // comments. */
   1114                 fprintf(out->fp, "%s/** ", indent);
   1115                 ln = doc->ident->linenum;
   1116             } else {
   1117                 fprintf(out->fp, "\n%s * ", indent);
   1118             }
   1119         }
   1120         first = 0;
   1121         fprintf(out->fp, "%.*s", (int)doc->ident->len, doc->ident->text);
   1122         ln = doc->ident->linenum;
   1123         doc = doc->link;
   1124     }
   1125     fprintf(out->fp, " */\n");
   1126 }
   1127 
   1128 static void gen_struct(fb_output_t *out, fb_compound_type_t *ct)
   1129 {
   1130     fb_member_t *member;
   1131     fb_symbol_t *sym;
   1132     unsigned align;
   1133     size_t offset = 0;
   1134     const char *tname, *tname_ns, *tname_prefix;
   1135     int n, len;
   1136     const char *s;
   1137     unsigned pad_index = 0, deprecated_index = 0, pad;
   1138     const char *kind;
   1139     int do_pad = out->opts->cgen_pad;
   1140     int is_primary_key, current_key_processed;
   1141     const char *nsc = out->nsc;
   1142 
   1143     fb_scoped_name_t snt;
   1144     fb_scoped_name_t snref;
   1145 
   1146     fb_clear(snt);
   1147     fb_clear(snref);
   1148 
   1149     assert(ct->symbol.kind == fb_is_struct);
   1150     assert(ct->align > 0 || ct->count == 0);
   1151     assert(ct->size > 0 || ct->count == 0);
   1152 
   1153     fb_compound_name(ct, &snt);
   1154     print_doc(out, "", ct->doc);
   1155     if (ct->size == 0) {
   1156         gen_panic(out, "internal error: unexpected empty struct");
   1157     } else {
   1158         if (do_pad) {
   1159             fprintf(out->fp, "#pragma pack(1)\n");
   1160         }
   1161         /*
   1162          * Unfortunately the following is not valid in C11:
   1163          *
   1164          *      struct alignas(4) mystruct { ... };
   1165          *
   1166          * we can only use alignas on members (unlike C++, and unlike
   1167          * non-portable C compiler variants).
   1168          *
   1169          * By padding the first element to the struct size we get around
   1170          * this problem. It shouldn't strictly be necessary to add padding
   1171          * fields, but compilers might not support padding above 16 bytes,
   1172          * so we do that as a precaution with an optional compiler flag.
   1173          */
   1174         fprintf(out->fp, "struct %s {\n", snt.text);
   1175         for (sym = ct->members; sym; sym = sym->link) {
   1176             current_key_processed = 0;
   1177             member = (fb_member_t *)sym;
   1178             is_primary_key = ct->primary_key == member;
   1179             print_doc(out, "    ", member->doc);
   1180             symbol_name(sym, &n, &s);
   1181             align = offset == 0 ? ct->align : member->align;
   1182             if (do_pad && (pad = (unsigned)(member->offset - offset))) {
   1183                 fprintf(out->fp, "    uint8_t __padding%u[%u];\n",
   1184                         pad_index++, pad);
   1185             }
   1186             if (member->metadata_flags & fb_f_deprecated) {
   1187                 pad = (unsigned)member->size;
   1188                 if (do_pad) {
   1189                     fprintf(out->fp, "    uint8_t __deprecated%u[%u]; /* was: '%.*s' */\n",
   1190                             deprecated_index++, pad, n, s);
   1191                 } else {
   1192                     fprintf(out->fp, "    alignas(%u) uint8_t __deprecated%u[%u]; /* was: '%.*s' */\n",
   1193                             align, deprecated_index++, pad, n, s);
   1194                 }
   1195                 offset = (unsigned)(member->offset + member->size);
   1196                 continue;
   1197             }
   1198             switch (member->type.type) {
   1199             case vt_fixed_array_type:
   1200                 tname_ns = scalar_type_ns(member->type.st, nsc);
   1201                 tname = scalar_type_name(member->type.st);
   1202                 len = (int)member->type.len;
   1203                 if (do_pad) {
   1204                     fprintf(out->fp, "    %s%s ", tname_ns, tname);
   1205                 } else {
   1206                     fprintf(out->fp, "    alignas(%u) %s%s ", align, tname_ns, tname);
   1207                 }
   1208                 fprintf(out->fp, "%.*s[%d];\n", n, s, len);
   1209                 break;
   1210             case vt_scalar_type:
   1211                 tname_ns = scalar_type_ns(member->type.st, nsc);
   1212                 tname = scalar_type_name(member->type.st);
   1213                 if (do_pad) {
   1214                     fprintf(out->fp, "    %s%s ", tname_ns, tname);
   1215                 } else {
   1216                     fprintf(out->fp, "    alignas(%u) %s%s ", align, tname_ns, tname);
   1217                 }
   1218                 fprintf(out->fp, "%.*s;\n", n, s);
   1219                 break;
   1220             case vt_fixed_array_compound_type_ref:
   1221                 assert(member->type.ct->symbol.kind == fb_is_struct || member->type.ct->symbol.kind == fb_is_enum);
   1222                 kind = member->type.ct->symbol.kind == fb_is_struct ? "" : "enum_";
   1223                 fb_compound_name(member->type.ct, &snref);
   1224                 len = (int)member->type.len;
   1225                 if (do_pad) {
   1226                     fprintf(out->fp, "    %s_%st ", snref.text, kind);
   1227                 } else {
   1228                     fprintf(out->fp, "    alignas(%u) %s_%st ", align, snref.text, kind);
   1229                 }
   1230                 fprintf(out->fp, "%.*s[%d];\n", n, s, len);
   1231                 break;
   1232             case vt_compound_type_ref:
   1233                 assert(member->type.ct->symbol.kind == fb_is_struct || member->type.ct->symbol.kind == fb_is_enum);
   1234                 kind = member->type.ct->symbol.kind == fb_is_struct ? "" : "enum_";
   1235                 fb_compound_name(member->type.ct, &snref);
   1236                 if (do_pad) {
   1237                     fprintf(out->fp, "    %s_%st ", snref.text, kind);
   1238                 } else {
   1239                     fprintf(out->fp, "    alignas(%u) %s_%st ", align, snref.text, kind);
   1240                 }
   1241                 fprintf(out->fp, "%.*s;\n", n, s);
   1242                 break;
   1243             default:
   1244                 fprintf(out->fp, "    %s ", __FLATCC_ERROR_TYPE);
   1245                 fprintf(out->fp, "%.*s;\n", n, s);
   1246                 gen_panic(out, "internal error: unexpected type during code generation");
   1247                 break;
   1248             }
   1249             offset = (unsigned)(member->offset + member->size);
   1250         }
   1251         if (do_pad && (pad = (unsigned)(ct->size - offset))) {
   1252             fprintf(out->fp, "    uint8_t __padding%u[%u];\n",
   1253                     pad_index, pad);
   1254         }
   1255         fprintf(out->fp, "};\n");
   1256         if (do_pad) {
   1257             fprintf(out->fp, "#pragma pack()\n");
   1258         }
   1259         fprintf(out->fp,
   1260                 "static_assert(sizeof(%s_t) == %"PRIu64", \"struct size mismatch\");\n\n",
   1261                 snt.text, (uint64_t)ct->size);
   1262         fprintf(out->fp,
   1263                 "static inline const %s_t *%s__const_ptr_add(const %s_t *p, size_t i) { return p + i; }\n", snt.text, snt.text, snt.text);
   1264         fprintf(out->fp,
   1265                 "static inline %s_t *%s__ptr_add(%s_t *p, size_t i) { return p + i; }\n", snt.text, snt.text, snt.text);
   1266         fprintf(out->fp,
   1267                 "static inline %s_struct_t %s_vec_at(%s_vec_t vec, size_t i)\n"
   1268                 "__%sstruct_vec_at(vec, i)\n",
   1269                 snt.text, snt.text, snt.text,
   1270                 nsc);
   1271     }
   1272     fprintf(out->fp, "static inline size_t %s__size(void) { return %"PRIu64"; }\n",
   1273             snt.text, (uint64_t)ct->size);
   1274     fprintf(out->fp,
   1275             "static inline size_t %s_vec_len(%s_vec_t vec)\n"
   1276             "__%svec_len(vec)\n",
   1277             snt.text, snt.text, nsc);
   1278     fprintf(out->fp,
   1279             "__%sstruct_as_root(%s)\n",
   1280             nsc, snt.text);
   1281     fprintf(out->fp, "\n");
   1282 
   1283     /* Create accessors which respect endianness and which return 0 on null struct access. */
   1284     for (sym = ct->members; sym; sym = sym->link) {
   1285         member = (fb_member_t *)sym;
   1286         is_primary_key = ct->primary_key == member;
   1287         if (member->metadata_flags & fb_f_deprecated) {
   1288             continue;
   1289         }
   1290         symbol_name(&member->symbol, &n, &s);
   1291         switch (member->type.type) {
   1292         case vt_fixed_array_type:
   1293             tname_ns = scalar_type_ns(member->type.st, nsc);
   1294             tname = scalar_type_name(member->type.st);
   1295             tname_prefix = scalar_type_prefix(member->type.st);
   1296             fprintf(out->fp,
   1297                 "__%sdefine_struct_scalar_fixed_array_field(%s, %.*s, %s%s, %s%s, %d)\n",
   1298                 nsc, snt.text, n, s, nsc, tname_prefix, tname_ns, tname, member->type.len);
   1299             /* TODO: if member->type.st == fb_char add string specific methods. */
   1300             break;
   1301         case vt_scalar_type:
   1302             tname_ns = scalar_type_ns(member->type.st, nsc);
   1303             tname = scalar_type_name(member->type.st);
   1304             tname_prefix = scalar_type_prefix(member->type.st);
   1305             fprintf(out->fp,
   1306                 "__%sdefine_struct_scalar_field(%s, %.*s, %s%s, %s%s)\n",
   1307                 nsc, snt.text, n, s, nsc, tname_prefix, tname_ns, tname);
   1308             if (!out->opts->allow_scan_for_all_fields && (member->metadata_flags & fb_f_key)) {
   1309                 fprintf(out->fp,
   1310                         "__%sdefine_scan_by_scalar_field(%s, %.*s, %s%s)\n",
   1311                         nsc, snt.text, n, s, tname_ns, tname);
   1312             }
   1313             if (member->metadata_flags & fb_f_key) {
   1314                 if (!is_primary_key) {
   1315                     fprintf(out->fp, "/* Note: this is not the primary key field on this struct. */\n");
   1316                 }
   1317                 fprintf(out->fp,     "/* Note: find only works on vectors sorted by this field. */\n");
   1318                 fprintf(out->fp,
   1319                         "__%sdefine_find_by_scalar_field(%s, %.*s, %s%s)\n",
   1320                         nsc, snt.text, n, s, tname_ns, tname);
   1321                 if (out->opts->cgen_sort) {
   1322                     fprintf(out->fp,
   1323                         "__%sdefine_struct_sort_by_scalar_field(%s, %.*s, %s%s, %s_t)\n",
   1324                         nsc, snt.text, n, s, tname_ns, tname, snt.text);
   1325                 }
   1326                 if (is_primary_key) {
   1327                     fprintf(out->fp,
   1328                         "__%sdefine_default_find_by_scalar_field(%s, %.*s, %s%s)\n",
   1329                         nsc, snt.text, n, s, tname_ns, tname);
   1330                     fprintf(out->fp,
   1331                         "__%sdefine_default_scan_by_scalar_field(%s, %.*s, %s%s)\n",
   1332                         nsc, snt.text, n, s, tname_ns, tname);
   1333                     if (out->opts->cgen_sort) {
   1334                         fprintf(out->fp,
   1335                             "#define %s_vec_sort %s_vec_sort_by_%.*s\n",
   1336                             snt.text, snt.text, n, s);
   1337                     }
   1338                 }
   1339                 current_key_processed = 1;
   1340             }
   1341             break;
   1342         case vt_fixed_array_compound_type_ref:
   1343             fb_compound_name(member->type.ct, &snref);
   1344             switch (member->type.ct->symbol.kind) {
   1345             case fb_is_enum:
   1346                 fprintf(out->fp,
   1347                     "__%sdefine_struct_scalar_fixed_array_field(%s, %.*s, %s, %s_enum_t, %d)\n",
   1348                     nsc, snt.text, n, s, snref.text, snref.text, member->type.len);
   1349                 break;
   1350             case fb_is_struct:
   1351                 fprintf(out->fp,
   1352                     "__%sdefine_struct_struct_fixed_array_field(%s, %.*s, %s_struct_t, %d)\n",
   1353                     nsc, snt.text, n, s, snref.text, member->type.len);
   1354                 break;
   1355             }
   1356             break;
   1357 
   1358         case vt_compound_type_ref:
   1359             fb_compound_name(member->type.ct, &snref);
   1360             switch (member->type.ct->symbol.kind) {
   1361             case fb_is_enum:
   1362                 fprintf(out->fp,
   1363                     "__%sdefine_struct_scalar_field(%s, %.*s, %s, %s_enum_t)\n",
   1364                     nsc, snt.text, n, s, snref.text, snref.text);
   1365                 if (!out->opts->allow_scan_for_all_fields && (member->metadata_flags & fb_f_key)) {
   1366                     fprintf(out->fp,
   1367                             "__%sdefine_scan_by_scalar_field(%s, %.*s, %s_enum_t)\n",
   1368                             nsc, snt.text, n, s, snref.text);
   1369                 }
   1370                 if (member->metadata_flags & fb_f_key) {
   1371                     if (!is_primary_key) {
   1372                         fprintf(out->fp, "/* Note: this is not the primary key of this table. */\n");
   1373                     }
   1374                     fprintf(out->fp,     "/* Note: find only works on vectors sorted by this field. */\n");
   1375                     fprintf(out->fp,
   1376                             "__%sdefine_find_by_scalar_field(%s, %.*s, %s_enum_t)\n",
   1377                             nsc, snt.text, n, s, snref.text);
   1378                     if (out->opts->cgen_sort) {
   1379                         fprintf(out->fp,
   1380                             "__%sdefine_struct_sort_by_scalar_field(%s, %.*s, %s_enum_t, %s_t)\n",
   1381                             nsc, snt.text, n, s, snref.text, snt.text);
   1382                     }
   1383                     if (is_primary_key) {
   1384                         fprintf(out->fp,
   1385                             "__%sdefine_default_find_by_scalar_field(%s, %.*s, %s_enum_t)\n",
   1386                             nsc, snt.text, n, s, snref.text);
   1387                         fprintf(out->fp,
   1388                             "__%sdefine_default_scan_by_scalar_field(%s, %.*s, %s_enum_t)\n",
   1389                             nsc, snt.text, n, s, snref.text);
   1390                         if (out->opts->cgen_sort) {
   1391                             fprintf(out->fp,
   1392                                 "#define %s_vec_sort %s_vec_sort_by_%.*s\n",
   1393                                 snt.text, snt.text, n, s);
   1394                         }
   1395                     }
   1396                     current_key_processed = 1;
   1397                 }
   1398                 break;
   1399             case fb_is_struct:
   1400                 /*
   1401                  * For completeness provide an accessor which returns member pointer
   1402                  * or null if container struct is null.
   1403                  */
   1404                 fprintf(out->fp,
   1405                     "__%sdefine_struct_struct_field(%s, %.*s, %s_struct_t)\n",
   1406                     nsc, snt.text, n, s, snref.text);
   1407                 break;
   1408             }
   1409 
   1410         }
   1411         if ((member->metadata_flags & fb_f_key) && !current_key_processed) {
   1412             fprintf(out->fp,
   1413                 "/* Note: field has key, but there is no support for find by fields of this type. */\n");
   1414             /*
   1415              * If the first key already exists, but was for an unsupported
   1416              * type, we do not map the next possible key to generic find.
   1417              */
   1418         }
   1419     }
   1420     fprintf(out->fp, "\n");
   1421 }
   1422 
   1423 /*
   1424  * Enums are integers, but we cannot control the size.
   1425  * To produce a typesafe and portable result, we generate constants
   1426  * instead.
   1427  */
   1428 static void gen_enum(fb_output_t *out, fb_compound_type_t *ct)
   1429 {
   1430     fb_member_t *member;
   1431     fb_symbol_t *sym;
   1432     const char *tname, *tname_ns, *s, *kind;
   1433     fb_literal_t literal;
   1434     int n, w;
   1435     int is_union;
   1436     fb_scoped_name_t snt;
   1437     const char *nsc = out->nsc;
   1438 
   1439     fb_clear(snt);
   1440 
   1441     assert(ct->symbol.kind == fb_is_enum || ct->symbol.kind == fb_is_union);
   1442     assert(ct->type.type == vt_scalar_type);
   1443 
   1444     tname_ns = scalar_type_ns(ct->type.st, nsc);
   1445     tname = scalar_type_name(ct->type.st);
   1446 
   1447     w = (int)ct->size * 8;
   1448 
   1449     is_union = ct->symbol.kind != fb_is_enum;
   1450     kind = is_union ? "union_type" : "enum";
   1451     fb_compound_name(ct, &snt);
   1452     print_doc(out, "", ct->doc);
   1453     fprintf(out->fp,
   1454             "typedef %s%s %s_%s_t;\n",
   1455             tname_ns, tname, snt.text, kind);
   1456     fprintf(out->fp,
   1457             "__%sdefine_integer_type(%s, %s_%s_t, %u)\n",
   1458             nsc, snt.text, snt.text, kind, w);
   1459     if (is_union) {
   1460         fprintf(out->fp,
   1461             "__%sdefine_union(%s, %s)\n",
   1462             nsc, nsc, snt.text);
   1463     }
   1464     for (sym = ct->members; sym; sym = sym->link) {
   1465         member = (fb_member_t *)sym;
   1466         print_doc(out, "", member->doc);
   1467         symbol_name(&member->symbol, &n, &s);
   1468         print_literal(ct->type.st, &member->value, literal);
   1469         /*
   1470          * This must be a define, not a static const integer, otherwise it
   1471          * won't work in switch statements - except with GNU extensions.
   1472          */
   1473         fprintf(out->fp,
   1474                 "#define %s_%.*s ((%s_%s_t)%s)\n",
   1475                 snt.text, n, s, snt.text, kind, literal);
   1476     }
   1477     fprintf(out->fp, "\n");
   1478 
   1479     if (is_union) {
   1480         fprintf(out->fp, "static inline const char *%s_type_name(%s_union_type_t type)\n"
   1481                 "{\n",
   1482                 snt.text, snt.text);
   1483     } else {
   1484         fprintf(out->fp, "static inline const char *%s_name(%s_enum_t value)\n"
   1485                 "{\n",
   1486                 snt.text, snt.text);
   1487     }
   1488 
   1489 
   1490     if (is_union) {
   1491         fprintf(out->fp, "    switch (type) {\n");
   1492     } else {
   1493         fprintf(out->fp, "    switch (value) {\n");
   1494     }
   1495     for (sym = ct->members; sym; sym = sym->link) {
   1496         member = (fb_member_t *)sym;
   1497         symbol_name(&member->symbol, &n, &s);
   1498         if (sym->flags & fb_duplicate) {
   1499             fprintf(out->fp,
   1500                     "    /* case %s_%.*s: return \"%.*s\"; (duplicate) */\n",
   1501                     snt.text, n, s, n, s);
   1502         } else {
   1503             fprintf(out->fp,
   1504                     "    case %s_%.*s: return \"%.*s\";\n",
   1505                     snt.text, n, s, n, s);
   1506         }
   1507     }
   1508     fprintf(out->fp,
   1509             "    default: return \"\";\n"
   1510             "    }\n"
   1511             "}\n");
   1512     fprintf(out->fp, "\n");
   1513 
   1514     if (is_union) {
   1515         fprintf(out->fp, "static inline int %s_is_known_type(%s_union_type_t type)\n"
   1516                 "{\n",
   1517                 snt.text, snt.text);
   1518     } else {
   1519         fprintf(out->fp, "static inline int %s_is_known_value(%s_enum_t value)\n"
   1520                 "{\n",
   1521                 snt.text, snt.text);
   1522     }
   1523     if (is_union) {
   1524         fprintf(out->fp, "    switch (type) {\n");
   1525     } else {
   1526         fprintf(out->fp, "    switch (value) {\n");
   1527     }
   1528     for (sym = ct->members; sym; sym = sym->link) {
   1529         member = (fb_member_t *)sym;
   1530         symbol_name(&member->symbol, &n, &s);
   1531         if (sym->flags & fb_duplicate) {
   1532             fprintf(out->fp,
   1533                     "    /* case %s_%.*s: return 1; (duplicate) */\n",
   1534                     snt.text, n, s);
   1535         } else {
   1536             fprintf(out->fp,
   1537                     "    case %s_%.*s: return 1;\n",
   1538                     snt.text, n, s);
   1539         }
   1540     }
   1541     fprintf(out->fp,
   1542             "    default: return 0;\n"
   1543             "    }\n"
   1544             "}\n");
   1545     fprintf(out->fp, "\n");
   1546 
   1547 }
   1548 
   1549 static void gen_nested_root(fb_output_t *out, fb_symbol_t *root_type, fb_symbol_t *container, fb_symbol_t *member)
   1550 {
   1551     const char *s;
   1552     int n;
   1553     const char *kind;
   1554     const char *nsc = out->nsc;
   1555     fb_scoped_name_t snt;
   1556     fb_scoped_name_t snc;
   1557 
   1558     fb_clear(snt);
   1559     fb_clear(snc);
   1560     if (!root_type) {
   1561         return;
   1562     }
   1563     /*
   1564      * Current flatc compiler only accepts tables, but here we support
   1565      * both tables and structs in so far the parser and analyzer
   1566      * allows for it.
   1567      */
   1568     switch (root_type->kind) {
   1569     case fb_is_table:
   1570         kind = "table_";
   1571         break;
   1572     case fb_is_struct:
   1573         kind = "struct_";
   1574         break;
   1575     default:
   1576         gen_panic(out, "internal error: roots can only be structs or tables");
   1577         return;
   1578     }
   1579     fb_compound_name((fb_compound_type_t *)root_type, &snt);
   1580     assert(container->kind == fb_is_table);
   1581     fb_compound_name((fb_compound_type_t *)container, &snc);
   1582     symbol_name(member, &n, &s);
   1583     fprintf(out->fp, "__%snested_buffer_as_root(%s, %.*s, %s, %s)\n", nsc, snc.text, n, s, snt.text, kind);
   1584 }
   1585 
   1586 static void gen_table(fb_output_t *out, fb_compound_type_t *ct)
   1587 {
   1588     fb_member_t *member;
   1589     fb_symbol_t *sym;
   1590     const char *s, *tname, *tname_ns, *tname_prefix;
   1591     int n, r;
   1592     int is_primary_key, current_key_processed;
   1593     const char *nsc = out->nsc;
   1594     fb_scoped_name_t snt;
   1595     fb_scoped_name_t snref;
   1596     fb_literal_t literal;
   1597     int is_optional;
   1598 
   1599     assert(ct->symbol.kind == fb_is_table);
   1600 
   1601     fb_clear(snt);
   1602     fb_clear(snref);
   1603 
   1604     fprintf(out->fp, "\n");
   1605     fb_compound_name(ct, &snt);
   1606     print_doc(out, "", ct->doc);
   1607     fprintf(out->fp,
   1608             /*
   1609              * We don't really need the struct, but it provides better
   1610              * type safety than a typedef void *.
   1611              */
   1612             "struct %s_table { uint8_t unused__; };\n"
   1613             "\n",
   1614             snt.text);
   1615     fprintf(out->fp,
   1616             "static inline size_t %s_vec_len(%s_vec_t vec)\n"
   1617             "__%svec_len(vec)\n",
   1618             snt.text, snt.text, nsc);
   1619     fprintf(out->fp,
   1620             "static inline %s_table_t %s_vec_at(%s_vec_t vec, size_t i)\n"
   1621             "__%soffset_vec_at(%s_table_t, vec, i, 0)\n",
   1622             snt.text, snt.text, snt.text, nsc, snt.text);
   1623     fprintf(out->fp,
   1624             "__%stable_as_root(%s)\n",
   1625             nsc, snt.text);
   1626     fprintf(out->fp, "\n");
   1627 
   1628     for (sym = ct->members; sym; sym = sym->link) {
   1629         current_key_processed = 0;
   1630         member = (fb_member_t *)sym;
   1631         is_primary_key = ct->primary_key == member;
   1632         is_optional = !!(member->flags & fb_fm_optional);
   1633         print_doc(out, "", member->doc);
   1634         /*
   1635          * In flatc, there can at most one key field, and it should be
   1636          * scalar or string. Here we export all keys using the
   1637          * <table>_vec_find_by_<fieldname> convention and let the parser deal with
   1638          * semantics. Keys on unsupported fields are ignored. The first
   1639          * valid find operation is also mapped to just <table>_vec_find.
   1640          */
   1641         symbol_name(&member->symbol, &n, &s);
   1642         if (member->metadata_flags & fb_f_deprecated) {
   1643             fprintf(out->fp, "/* Skipping deprecated field: '%s_%.*s' */\n\n", snt.text, n, s);
   1644             continue;
   1645         }
   1646         r = (member->metadata_flags & fb_f_required) != 0;
   1647         switch (member->type.type) {
   1648         case vt_scalar_type:
   1649             tname_ns = scalar_type_ns(member->type.st, nsc);
   1650             tname = scalar_type_name(member->type.st);
   1651             tname_prefix = scalar_type_prefix(member->type.st);
   1652             print_literal(member->type.st, &member->value, literal);
   1653             if (is_optional) {
   1654                 fprintf(out->fp,
   1655                     "__%sdefine_scalar_optional_field(%"PRIu64", %s, %.*s, %s%s, %s%s, %s)\n",
   1656                     nsc, (uint64_t)member->id, snt.text, n, s, nsc, tname_prefix, tname_ns, tname, literal);
   1657             } else {
   1658                 fprintf(out->fp,
   1659                     "__%sdefine_scalar_field(%"PRIu64", %s, %.*s, %s%s, %s%s, %s)\n",
   1660                     nsc, (uint64_t)member->id, snt.text, n, s, nsc, tname_prefix, tname_ns, tname, literal);
   1661             }
   1662             if (!out->opts->allow_scan_for_all_fields && (member->metadata_flags & fb_f_key)) {
   1663                 fprintf(out->fp,
   1664                         "__%sdefine_scan_by_scalar_field(%s, %.*s, %s%s)\n",
   1665                         nsc, snt.text, n, s, tname_ns, tname);
   1666             }
   1667             if (member->metadata_flags & fb_f_key) {
   1668                 if (!is_primary_key) {
   1669                     fprintf(out->fp, "/* Note: this is not the primary key of this table. */\n");
   1670                 }
   1671                 fprintf(out->fp,     "/* Note: find only works on vectors sorted by this field. */\n");
   1672                 fprintf(out->fp,
   1673                         "__%sdefine_find_by_scalar_field(%s, %.*s, %s%s)\n",
   1674                         nsc, snt.text, n, s, tname_ns, tname);
   1675                 if (out->opts->cgen_sort) {
   1676                     fprintf(out->fp,
   1677                         "__%sdefine_table_sort_by_scalar_field(%s, %.*s, %s%s)\n",
   1678                         nsc, snt.text, n, s, tname_ns, tname);
   1679                 }
   1680                 if (is_primary_key) {
   1681                     fprintf(out->fp,
   1682                         "__%sdefine_default_find_by_scalar_field(%s, %.*s, %s%s)\n",
   1683                         nsc, snt.text, n, s, tname_ns, tname);
   1684                     fprintf(out->fp,
   1685                         "__%sdefine_default_scan_by_scalar_field(%s, %.*s, %s%s)\n",
   1686                         nsc, snt.text, n, s, tname_ns, tname);
   1687                     if (out->opts->cgen_sort) {
   1688                         fprintf(out->fp,
   1689                             "#define %s_vec_sort %s_vec_sort_by_%.*s\n",
   1690                             snt.text, snt.text, n, s);
   1691                     }
   1692                 }
   1693                 current_key_processed = 1;
   1694             }
   1695             break;
   1696         case vt_vector_type:
   1697             /* They all use a namespace. */
   1698             tname = scalar_vector_type_name(member->type.st);
   1699             tname_ns = nsc;
   1700             fprintf(out->fp,
   1701                 "__%sdefine_vector_field(%"PRIu64", %s, %.*s, %s%s, %u)\n",
   1702                 nsc, (uint64_t)member->id, snt.text, n, s, tname_ns, tname, r);
   1703             if (member->nest) {
   1704                 gen_nested_root(out, &member->nest->symbol, &ct->symbol, &member->symbol);
   1705             }
   1706             break;
   1707         case vt_string_type:
   1708             fprintf(out->fp,
   1709                 "__%sdefine_string_field(%"PRIu64", %s, %.*s, %u)\n",
   1710                 nsc, (uint64_t)member->id, snt.text, n, s, r);
   1711             if (!out->opts->allow_scan_for_all_fields && (member->metadata_flags & fb_f_key)) {
   1712                 fprintf(out->fp,
   1713                     "__%sdefine_scan_by_string_field(%s, %.*s)\n",
   1714                     nsc, snt.text, n, s);
   1715             }
   1716             if (member->metadata_flags & fb_f_key) {
   1717                 if (!is_primary_key) {
   1718                     fprintf(out->fp, "/* Note: this is not the primary key of this table. */\n");
   1719                 }
   1720                 fprintf(out->fp,
   1721                     "__%sdefine_find_by_string_field(%s, %.*s)\n",
   1722                     nsc, snt.text, n, s);
   1723                 if (out->opts->cgen_sort) {
   1724                     fprintf(out->fp,
   1725                         "__%sdefine_table_sort_by_string_field(%s, %.*s)\n",
   1726                         nsc, snt.text, n, s);
   1727                 }
   1728                 if (is_primary_key) {
   1729                     fprintf(out->fp,
   1730                         "__%sdefine_default_find_by_string_field(%s, %.*s)\n",
   1731                         nsc, snt.text, n, s);
   1732                     fprintf(out->fp,
   1733                         "__%sdefine_default_scan_by_string_field(%s, %.*s)\n",
   1734                         nsc, snt.text, n, s);
   1735                     if (out->opts->cgen_sort) {
   1736                         fprintf(out->fp,
   1737                             "#define %s_vec_sort %s_vec_sort_by_%.*s\n",
   1738                             snt.text, snt.text, n, s);
   1739                     }
   1740                 }
   1741                 current_key_processed = 1;
   1742             }
   1743             break;
   1744         case vt_vector_string_type:
   1745             fprintf(out->fp,
   1746                 "__%sdefine_vector_field(%"PRIu64", %s, %.*s, %sstring_vec_t, %u)\n",
   1747                 nsc, (uint64_t)member->id, snt.text, n, s, nsc, r);
   1748             break;
   1749         case vt_compound_type_ref:
   1750             fb_compound_name(member->type.ct, &snref);
   1751             switch (member->type.ct->symbol.kind) {
   1752             case fb_is_struct:
   1753                 fprintf(out->fp,
   1754                     "__%sdefine_struct_field(%"PRIu64", %s, %.*s, %s_struct_t, %u)\n",
   1755                     nsc, (uint64_t)member->id, snt.text, n, s, snref.text, r);
   1756                 break;
   1757             case fb_is_table:
   1758                 fprintf(out->fp,
   1759                     "__%sdefine_table_field(%"PRIu64", %s, %.*s, %s_table_t, %u)\n",
   1760                     nsc, (uint64_t)member->id, snt.text, n, s, snref.text, r);
   1761                 break;
   1762             case fb_is_enum:
   1763                 print_literal(member->type.ct->type.st, &member->value, literal);
   1764                 if (is_optional) {
   1765                     fprintf(out->fp,
   1766                         "__%sdefine_scalar_optional_field(%"PRIu64", %s, %.*s, %s, %s_enum_t, %s)\n",
   1767                         nsc, (uint64_t)member->id, snt.text, n, s, snref.text, snref.text, literal);
   1768                 } else {
   1769                     fprintf(out->fp,
   1770                         "__%sdefine_scalar_field(%"PRIu64", %s, %.*s, %s, %s_enum_t, %s)\n",
   1771                         nsc, (uint64_t)member->id, snt.text, n, s, snref.text, snref.text, literal);
   1772                 }
   1773                 if (!out->opts->allow_scan_for_all_fields && (member->metadata_flags & fb_f_key)) {
   1774                     fprintf(out->fp,
   1775                             "__%sdefine_scan_by_scalar_field(%s, %.*s, %s_enum_t)\n",
   1776                             nsc, snt.text, n, s, snref.text);
   1777                 }
   1778                 if (member->metadata_flags & fb_f_key) {
   1779                     if (!is_primary_key) {
   1780                         fprintf(out->fp, "/* Note: this is not the primary key of this table. */\n");
   1781                     }
   1782                     fprintf(out->fp,     "/* Note: find only works on vectors sorted by this field. */\n");
   1783                     fprintf(out->fp,
   1784                             "__%sdefine_find_by_scalar_field(%s, %.*s, %s_enum_t)\n",
   1785                             nsc, snt.text, n, s, snref.text);
   1786                     if (out->opts->cgen_sort) {
   1787                         fprintf(out->fp,
   1788                                 "__%sdefine_table_sort_by_scalar_field(%s, %.*s, %s_enum_t)\n",
   1789                                 nsc, snt.text, n, s, snref.text);
   1790                     }
   1791                     if (is_primary_key) {
   1792                         fprintf(out->fp,
   1793                                 "__%sdefine_default_find_by_scalar_field(%s, %.*s, %s_enum_t)\n",
   1794                                 nsc, snt.text, n, s, snref.text);
   1795                         fprintf(out->fp,
   1796                                 "__%sdefine_default_scan_by_scalar_field(%s, %.*s, %s_enum_t)\n",
   1797                                 nsc, snt.text, n, s, snref.text);
   1798                         if (out->opts->cgen_sort) {
   1799                             fprintf(out->fp,
   1800                                     "#define %s_vec_sort %s_vec_sort_by_%.*s\n",
   1801                                     snt.text, snt.text, n, s);
   1802                         }
   1803                     }
   1804                     current_key_processed = 1;
   1805                 }
   1806                 break;
   1807             case fb_is_union:
   1808                 fprintf(out->fp,
   1809                     "__%sdefine_union_field(%s, %"PRIu64", %s, %.*s, %s, %u)\n",
   1810                     nsc, nsc, (uint64_t)member->id, snt.text, n, s, snref.text, r);
   1811                 break;
   1812             default:
   1813                 gen_panic(out, "internal error: unexpected compound type in table during code generation");
   1814                 break;
   1815             }
   1816             break;
   1817         case vt_vector_compound_type_ref:
   1818             fb_compound_name(member->type.ct, &snref);
   1819             switch (member->type.ct->symbol.kind) {
   1820             case fb_is_struct:
   1821                 break;
   1822             case fb_is_table:
   1823                 break;
   1824             case fb_is_enum:
   1825                 break;
   1826             case fb_is_union:
   1827                 break;
   1828             default:
   1829                 gen_panic(out, "internal error: unexpected vector compound type in table during code generation");
   1830                 break;
   1831             }
   1832             if (member->type.ct->symbol.kind == fb_is_union) {
   1833                 fprintf(out->fp,
   1834                     "__%sdefine_union_vector_field(%s, %"PRIu64", %s, %.*s, %s, %u)\n",
   1835                     nsc, nsc, (uint64_t)member->id, snt.text, n, s, snref.text, r);
   1836             } else {
   1837                 fprintf(out->fp,
   1838                     "__%sdefine_vector_field(%"PRIu64", %s, %.*s, %s_vec_t, %u)\n",
   1839                     nsc, (uint64_t)member->id, snt.text, n, s, snref.text, r);
   1840             }
   1841             break;
   1842         default:
   1843             gen_panic(out, "internal error: unexpected table member type during code generation");
   1844             break;
   1845         }
   1846         if ((member->metadata_flags & fb_f_key) && !current_key_processed) {
   1847             fprintf(out->fp,
   1848                 "/* Note: field has key, but there is no support for find by fields of this type. */\n");
   1849             /*
   1850              * If the first key already exists, but was for an unsupported
   1851              * type, we do not map the next possible key to generic find.
   1852              */
   1853         }
   1854     }
   1855 }
   1856 
   1857 int fb_gen_c_reader(fb_output_t *out)
   1858 {
   1859     fb_symbol_t *sym;
   1860     fb_compound_type_t *ct;
   1861 
   1862     gen_pretext(out);
   1863 
   1864     for (ct = out->S->ordered_structs; ct; ct = ct->order) {
   1865         gen_forward_decl(out, ct);
   1866     }
   1867     fprintf(out->fp, "\n");
   1868     for (sym = out->S->symbols; sym; sym = sym->link) {
   1869         switch (sym->kind) {
   1870         case fb_is_table:
   1871             gen_forward_decl(out, (fb_compound_type_t *)sym);
   1872             break;
   1873         }
   1874     }
   1875     /* Must be placed early due to nested buffer circular references. */
   1876     for (sym = out->S->symbols; sym; sym = sym->link) {
   1877         switch (sym->kind) {
   1878         case fb_is_struct:
   1879             /* Fall through. */
   1880         case fb_is_table:
   1881             print_type_identifier(out, (fb_compound_type_t *)sym);
   1882             print_file_extension(out, (fb_compound_type_t *)sym);
   1883             break;
   1884         }
   1885     }
   1886     fprintf(out->fp, "\n");
   1887     for (sym = out->S->symbols; sym; sym = sym->link) {
   1888         switch (sym->kind) {
   1889          /* Enums must come before structs in case they are referenced. */
   1890         case fb_is_enum:
   1891             gen_enum(out, (fb_compound_type_t *)sym);
   1892             break;
   1893         }
   1894     }
   1895     fprintf(out->fp, "\n");
   1896     /* Generate structs in topologically sorted order. */
   1897     for (ct = out->S->ordered_structs; ct; ct = ct->order) {
   1898             gen_struct(out, ct);
   1899     }
   1900     for (sym = out->S->symbols; sym; sym = sym->link) {
   1901         switch (sym->kind) {
   1902         case fb_is_enum:
   1903         case fb_is_struct:
   1904             /* Already generated. */
   1905             break;
   1906         case fb_is_union:
   1907             gen_enum(out, (fb_compound_type_t *)sym);
   1908             break;
   1909         case fb_is_table:
   1910             gen_table(out, (fb_compound_type_t *)sym);
   1911             break;
   1912         case fb_is_rpc_service:
   1913             /* Ignore. */
   1914             break;
   1915         default:
   1916             gen_panic(out, "internal error: unexpected schema component");
   1917             break;
   1918         }
   1919     }
   1920     fprintf(out->fp, "\n");
   1921 
   1922     if (out->opts->cgen_sort) {
   1923         fb_gen_c_sorter(out);
   1924     }
   1925 
   1926     gen_footer(out);
   1927     return 0;
   1928 }