diff --git a/gcc/jit/docs/topics/expressions.rst b/gcc/jit/docs/topics/expressions.rst index 280e0eaea6806d5001381cc2565a972575a70797..0a96872551ba582424516450dbe6b8085cdbca82 100644 --- a/gcc/jit/docs/topics/expressions.rst +++ b/gcc/jit/docs/topics/expressions.rst @@ -126,6 +126,147 @@ Simple expressions underlying string, so it is valid to pass in a pointer to an on-stack buffer. +Constructor expressions +*********************** + + The following functions make constructors for array, struct and union + types. + + The constructor rvalue can be used for assignment to locals. + It can be used to initialize global variables with + :func:`gcc_jit_global_set_initializer_rvalue`. It can also be used as a + temporary value for function calls and return values, but its address + can't be taken. + + Note that arrays in libgccjit do not collapse to pointers like in + C. I.e. if an array constructor is used as e.g. a return value, the whole + array would be returned by value - array constructors can be assigned to + array variables. + + The constructor can contain nested constructors. + + Note that a string literal rvalue can't be used to construct a char array; + the latter needs one rvalue for each char. + + These entrypoints were added in :ref:`LIBGCCJIT_ABI_19`; you can test for + their presence using: + + .. code-block:: c + #ifdef LIBGCCJIT_HAVE_CTORS + +.. function:: gcc_jit_rvalue *\ + gcc_jit_context_new_array_constructor (gcc_jit_context *ctxt,\ + gcc_jit_location *loc,\ + gcc_jit_type *type,\ + size_t num_values,\ + gcc_jit_rvalue **values) + + Create a constructor for an array as an rvalue. + + Returns NULL on error. ``values`` are copied and + do not have to outlive the context. + + ``type`` specifies what the constructor will build and has to be + an array. + + ``num_values`` specifies the number of elements in ``values`` and + it can't have more elements than the array type. + + Each value in ``values`` sets the corresponding value in the array. + If the array type itself has more elements than ``values``, the + left-over elements will be zeroed. + + Each value in ``values`` need to be the same unqualified type as the + array type's element type. + + If ``num_values`` is 0, the ``values`` parameter will be + ignored and zero initialization will be used. + + This entrypoint was added in :ref:`LIBGCCJIT_ABI_19`; you can test for its + presence using: + + .. code-block:: c + #ifdef LIBGCCJIT_HAVE_CTORS + +.. function:: gcc_jit_rvalue *\ + gcc_jit_context_new_struct_constructor (gcc_jit_context *ctxt,\ + gcc_jit_location *loc,\ + gcc_jit_type *type,\ + size_t num_values,\ + gcc_jit_field **fields,\ + gcc_jit_rvalue **value) + + + Create a constructor for a struct as an rvalue. + + Returns NULL on error. The two parameter arrays are copied and + do not have to outlive the context. + + ``type`` specifies what the constructor will build and has to be + a struct. + + ``num_values`` specifies the number of elements in ``values``. + + ``fields`` need to have the same length as ``values``, or be NULL. + + If ``fields`` is null, the values are applied in definition order. + + Otherwise, each field in ``fields`` specifies which field in the struct to + set to the corresponding value in ``values``. ``fields`` and ``values`` + are paired by index. + + The fields in ``fields`` have to be in definition order, but there + can be gaps. Any field in the struct that is not specified in + ``fields`` will be zeroed. + + The fields in ``fields`` need to be the same objects that were used + to create the struct. + + Each value has to have have the same unqualified type as the field + it is applied to. + + A NULL value element in ``values`` is a shorthand for zero initialization + of the corresponding field. + + If ``num_values`` is 0, the array parameters will be + ignored and zero initialization will be used. + + This entrypoint was added in :ref:`LIBGCCJIT_ABI_19`; you can test for its + presence using: + + .. code-block:: c + #ifdef LIBGCCJIT_HAVE_CTORS + +.. function:: gcc_jit_rvalue *\ + gcc_jit_context_new_union_constructor (gcc_jit_context *ctxt,\ + gcc_jit_location *loc,\ + gcc_jit_type *type,\ + gcc_jit_field *field,\ + gcc_jit_rvalue *value) + + Create a constructor for a union as an rvalue. + + Returns NULL on error. + + ``type`` specifies what the constructor will build and has to be + an union. + + ``field`` specifies which field to set. If it is NULL, the first + field in the union will be set.``field`` need to be the same object + that were used to create the union. + + ``value`` specifies what value to set the corresponding field to. + If ``value`` is NULL, zero initialization will be used. + + Each value has to have have the same unqualified type as the field + it is applied to. + + This entrypoint was added in :ref:`LIBGCCJIT_ABI_19`; you can test for its + presence using: + + .. code-block:: c + #ifdef LIBGCCJIT_HAVE_CTORS + Vector expressions ****************** @@ -661,6 +802,38 @@ Global variables #ifdef LIBGCCJIT_HAVE_gcc_jit_global_set_initializer +.. function:: gcc_jit_lvalue *\ + gcc_jit_global_set_initializer_rvalue (gcc_jit_lvalue *global, + gcc_jit_rvalue *init_value) + + Set the initial value of a global with an rvalue. + + The rvalue needs to be a constant expression, e.g. no function calls. + + The global can't have the ``kind`` :ref:`GCC_JIT_GLOBAL_IMPORTED`. + + As a non-comprehensive example it is OK to do the equivalent of: + + .. code-block:: c + + int foo = 3 * 2; /* rvalue from gcc_jit_context_new_binary_op. */ + int arr[] = {1,2,3,4}; /* rvalue from gcc_jit_context_new_constructor. */ + int *bar = &arr[2] + 1; /* rvalue from nested "get address" of "array access". */ + const int baz = 3; /* rvalue from gcc_jit_context_rvalue_from_int. */ + int boz = baz; /* rvalue from gcc_jit_lvalue_as_rvalue. */ + + Use together with :ref:`gcc_jit_context_new_constructor` to + initialize structs, unions and arrays. + + On success, returns the ``global`` parameter unchanged. Otherwise, ``NULL``. + + This entrypoint was added in :ref:`LIBGCCJIT_ABI_19`; you can test for its + presence using: + + .. code-block:: c + + #ifdef LIBGCCJIT_HAVE_CTORS + Working with pointers, structs and unions ----------------------------------------- diff --git a/gcc/jit/jit-common.h b/gcc/jit/jit-common.h index f88e6755b00bf308b27b29fe835533062050b058..2e723c38d789a2fbe2ea972eb2f1d4e20df1c5b6 100644 --- a/gcc/jit/jit-common.h +++ b/gcc/jit/jit-common.h @@ -202,6 +202,15 @@ enum inner_bool_option NUM_INNER_BOOL_OPTIONS }; +/* Flags for global variables class. For when the playback of the + global need to know what will happen to it later. */ +enum global_var_flags +{ + GLOBAL_VAR_FLAGS_NONE = 0, + GLOBAL_VAR_FLAGS_WILL_BE_RVAL_INIT = 1, + GLOBAL_VAR_FLAGS_WILL_BE_BLOB_INIT = 2, +}; + } // namespace gcc::jit } // namespace gcc diff --git a/gcc/jit/jit-playback.c b/gcc/jit/jit-playback.c index 783a037b11d23429eccd95ca57e1e317b732fcc8..64755b6c6fe28988d81c3af30128a77515da540c 100644 --- a/gcc/jit/jit-playback.c +++ b/gcc/jit/jit-playback.c @@ -97,6 +97,43 @@ namespace jit { Playback. **********************************************************************/ +/* Fold a readonly non-volatile variable with an initial constant value, + to that value. + + Otherwise return the argument unchanged. + + This fold is needed for setting a variable's DECL_INITIAL to the value + of a const variable. The c-frontend does this in its own special + fold (), so we lift this part out and do it explicitly where there is a + potential for variables to be used as rvalues. */ +static tree +fold_const_var (tree node) +{ + /* See c_fully_fold_internal in c-fold.c and decl_constant_value_1 + in c-typeck.c. */ + if (VAR_P (node) + && TREE_READONLY (node) + && !TREE_THIS_VOLATILE (node) + && DECL_INITIAL (node) != NULL_TREE + /* "This is invalid if initial value is not constant. + If it has either a function call, a memory reference, + or a variable, then re-evaluating it could give different + results." */ + && TREE_CONSTANT (DECL_INITIAL (node))) + { + tree ret = DECL_INITIAL (node); + /* "Avoid unwanted tree sharing between the initializer and current + function's body where the tree can be modified e.g. by the + gimplifier." */ + if (TREE_STATIC (node)) + ret = unshare_expr (ret); + + return ret; + } + + return node; +} + /* Build a STRING_CST tree for STR, or return NULL if it is NULL. The TREE_TYPE is not initialized. */ @@ -538,15 +575,28 @@ playback::context:: global_new_decl (location *loc, enum gcc_jit_global_kind kind, type *type, - const char *name) + const char *name, + enum global_var_flags flags) { gcc_assert (type); gcc_assert (name); + + tree type_tree = type->as_tree (); + tree inner = build_decl (UNKNOWN_LOCATION, VAR_DECL, get_identifier (name), - type->as_tree ()); + type_tree); + TREE_PUBLIC (inner) = (kind != GCC_JIT_GLOBAL_INTERNAL); - DECL_COMMON (inner) = 1; + + + int will_be_init = flags & (GLOBAL_VAR_FLAGS_WILL_BE_RVAL_INIT | + GLOBAL_VAR_FLAGS_WILL_BE_BLOB_INIT); + + /* A VAR_DECL with DECL_INITIAL will not end up in .common section. */ + if (!will_be_init) + DECL_COMMON (inner) = 1; + switch (kind) { default: @@ -565,6 +615,9 @@ global_new_decl (location *loc, break; } + if (TYPE_READONLY (type_tree)) + TREE_READONLY (inner) = 1; + if (loc) set_tree_location (inner, loc); @@ -589,13 +642,121 @@ playback::context:: new_global (location *loc, enum gcc_jit_global_kind kind, type *type, - const char *name) + const char *name, + enum global_var_flags flags) { - tree inner = global_new_decl (loc, kind, type, name); + tree inner = + global_new_decl (loc, kind, type, name, flags); return global_finalize_lvalue (inner); } +void +playback::context:: +global_set_init_rvalue (lvalue* variable, + rvalue* init) +{ + tree inner = variable->as_tree (); + + /* We need to fold all expressions as much as possible. The code + for a DECL_INITIAL only handles some operations, + etc addition, minus, 'address of'. See output_addressed_constants () + in varasm.c. */ + tree init_tree = init->as_tree (); + tree folded = fold_const_var (init_tree); + + if (!TREE_CONSTANT (folded)) + { + tree name = DECL_NAME (inner); + + if (name != NULL_TREE) + add_error (NULL, + "unable to convert initial value for the global variable %s" + " to a compile-time constant", + IDENTIFIER_POINTER (name)); + else + add_error (NULL, + "unable to convert initial value for global variable" + " to a compile-time constant"); + return; + } + + DECL_INITIAL (inner) = folded; +} + +playback::rvalue * +playback::context:: +new_ctor (location *loc, + type *type, + const auto_vec<field*> *fields, + const auto_vec<rvalue*> *rvalues) +{ + tree type_tree = type->as_tree (); + + /* Handle empty ctors first. I.e. set everything to 0. */ + if (rvalues->length () == 0) + return new rvalue (this, build_constructor (type_tree, NULL)); + + /* Handle arrays (and return). */ + if (TREE_CODE (type_tree) == ARRAY_TYPE) + { + int n = rvalues->length (); + /* The vec for the constructor node. */ + vec<constructor_elt, va_gc> *v = NULL; + vec_alloc (v, n); + + for (int i = 0; i < n; i++) + { + rvalue *rv = (*rvalues)[i]; + /* null rvalues indicate that the element should be zeroed. */ + if (rv) + CONSTRUCTOR_APPEND_ELT (v, + build_int_cst (size_type_node, i), + rv->as_tree ()); + else + CONSTRUCTOR_APPEND_ELT (v, + build_int_cst (size_type_node, i), + build_zero_cst (TREE_TYPE (type_tree))); + } + + tree ctor = build_constructor (type_tree, v); + + if (loc) + set_tree_location (ctor, loc); + + return new rvalue (this, ctor); + } + + /* Handle structs and unions. */ + int n = fields->length (); + + /* The vec for the constructor node. */ + vec<constructor_elt, va_gc> *v = NULL; + vec_alloc (v, n); + + /* Iterate over the fields, building initializations. */ + for (int i = 0;i < n; i++) + { + tree field = (*fields)[i]->as_tree (); + rvalue *rv = (*rvalues)[i]; + /* If the value is NULL, it means we should zero the field. */ + if (rv) + CONSTRUCTOR_APPEND_ELT (v, field, rv->as_tree ()); + else + { + tree zero_cst = build_zero_cst (TREE_TYPE (field)); + CONSTRUCTOR_APPEND_ELT (v, field, zero_cst); + } + } + + tree ctor = build_constructor (type_tree, v); + + if (loc) + set_tree_location (ctor, loc); + + return new rvalue (this, build_constructor (type_tree, v)); +} + /* Fill 'constructor_elements' with the memory content of 'initializer'. Each element of the initializer is of the size of type T. In use by new_global_initialized.*/ @@ -629,9 +790,10 @@ new_global_initialized (location *loc, size_t element_size, size_t initializer_num_elem, const void *initializer, - const char *name) + const char *name, + enum global_var_flags flags) { - tree inner = global_new_decl (loc, kind, type, name); + tree inner = global_new_decl (loc, kind, type, name, flags); vec<constructor_elt, va_gc> *constructor_elements = NULL; @@ -831,7 +993,8 @@ as_truth_value (tree expr, location *loc) if (loc) set_tree_location (typed_zero, loc); - expr = build2 (NE_EXPR, integer_type_node, expr, typed_zero); + expr = fold_build2_loc (UNKNOWN_LOCATION, + NE_EXPR, integer_type_node, expr, typed_zero); if (loc) set_tree_location (expr, loc); @@ -867,6 +1030,8 @@ new_unary_op (location *loc, gcc_assert (a); tree node = a->as_tree (); + node = fold_const_var (node); + tree inner_result = NULL; switch (op) @@ -898,6 +1063,10 @@ new_unary_op (location *loc, inner_result = build1 (inner_op, result_type->as_tree (), node); + + /* Try to fold. */ + inner_result = fold (inner_result); + if (loc) set_tree_location (inner_result, loc); @@ -922,7 +1091,10 @@ new_binary_op (location *loc, gcc_assert (b); tree node_a = a->as_tree (); + node_a = fold_const_var (node_a); + tree node_b = b->as_tree (); + node_b = fold_const_var (node_b); switch (op) { @@ -992,6 +1164,10 @@ new_binary_op (location *loc, result_type->as_tree (), node_a, node_b); + + /* Try to fold the expression. */ + inner_expr = fold (inner_expr); + if (loc) set_tree_location (inner_expr, loc); @@ -1039,10 +1215,19 @@ new_comparison (location *loc, break; } + tree node_a = a->as_tree (); + node_a = fold_const_var (node_a); + tree node_b = b->as_tree (); + node_b = fold_const_var (node_b); + tree inner_expr = build2 (inner_op, boolean_type_node, - a->as_tree (), - b->as_tree ()); + node_a, + node_b); + + /* Try to fold. */ + inner_expr = fold (inner_expr); + if (loc) set_tree_location (inner_expr, loc); return new rvalue (this, inner_expr); @@ -1142,6 +1327,8 @@ playback::context::build_cast (playback::location *loc, Only some kinds of cast are currently supported here. */ tree t_expr = expr->as_tree (); + t_expr = fold_const_var (t_expr); + tree t_dst_type = type_->as_tree (); tree t_ret = NULL; t_ret = targetm.convert_to_type (t_dst_type, t_expr); @@ -1220,7 +1407,10 @@ new_array_access (location *loc, c-family/c-common.c: pointer_int_sum */ tree t_ptr = ptr->as_tree (); + t_ptr = fold_const_var (t_ptr); tree t_index = index->as_tree (); + t_index = fold_const_var (t_index); + tree t_type_ptr = TREE_TYPE (t_ptr); tree t_type_star_ptr = TREE_TYPE (t_type_ptr); @@ -1228,6 +1418,7 @@ new_array_access (location *loc, { tree t_result = build4 (ARRAY_REF, t_type_star_ptr, t_ptr, t_index, NULL_TREE, NULL_TREE); + t_result = fold (t_result); if (loc) set_tree_location (t_result, loc); return new lvalue (this, t_result); @@ -1237,12 +1428,14 @@ new_array_access (location *loc, /* Convert index to an offset in bytes. */ tree t_sizeof = size_in_bytes (t_type_star_ptr); t_index = fold_build1 (CONVERT_EXPR, sizetype, t_index); - tree t_offset = build2 (MULT_EXPR, sizetype, t_index, t_sizeof); + tree t_offset = fold_build2_loc (UNKNOWN_LOCATION, + MULT_EXPR, sizetype, t_index, t_sizeof); /* Locate (ptr + offset). */ - tree t_address = build2 (POINTER_PLUS_EXPR, t_type_ptr, t_ptr, t_offset); + tree t_address = fold_build2_loc (UNKNOWN_LOCATION, + POINTER_PLUS_EXPR, t_type_ptr, t_ptr, t_offset); - tree t_indirection = build1 (INDIRECT_REF, t_type_star_ptr, t_address); + tree t_indirection = fold_build1 (INDIRECT_REF, t_type_star_ptr, t_address); if (loc) { set_tree_location (t_sizeof, loc); @@ -1290,7 +1483,7 @@ new_dereference (tree ptr, gcc_assert (ptr); tree type = TREE_TYPE (TREE_TYPE(ptr)); - tree datum = build1 (INDIRECT_REF, type, ptr); + tree datum = fold_build1 (INDIRECT_REF, type, ptr); if (loc) set_tree_location (datum, loc); return datum; @@ -1444,7 +1637,7 @@ get_address (location *loc) tree t_lvalue = as_tree (); tree t_thistype = TREE_TYPE (t_lvalue); tree t_ptrtype = build_pointer_type (t_thistype); - tree ptr = build1 (ADDR_EXPR, t_ptrtype, t_lvalue); + tree ptr = fold_build1 (ADDR_EXPR, t_ptrtype, t_lvalue); if (loc) get_context ()->set_tree_location (ptr, loc); if (mark_addressable (loc)) diff --git a/gcc/jit/jit-playback.h b/gcc/jit/jit-playback.h index 21ddffb228ffcbb3388a5a18dd7d781204c1b07a..6ca492cc2e006e78b5ab3e7d651760e72bddd340 100644 --- a/gcc/jit/jit-playback.h +++ b/gcc/jit/jit-playback.h @@ -109,7 +109,8 @@ public: new_global (location *loc, enum gcc_jit_global_kind kind, type *type, - const char *name); + const char *name, + enum global_var_flags flags); lvalue * new_global_initialized (location *loc, @@ -118,7 +119,19 @@ public: size_t element_size, size_t initializer_num_elem, const void *initializer, - const char *name); + const char *name, + enum global_var_flags flags); + + rvalue * + new_ctor (location *log, + type *type, + const auto_vec<field*> *fields, + const auto_vec<rvalue*> *rvalues); + + + void + global_set_init_rvalue (lvalue* variable, + rvalue* init); template <typename HOST_TYPE> rvalue * @@ -286,7 +299,8 @@ private: global_new_decl (location *loc, enum gcc_jit_global_kind kind, type *type, - const char *name); + const char *name, + enum global_var_flags flags); lvalue * global_finalize_lvalue (tree inner); diff --git a/gcc/jit/jit-recording.c b/gcc/jit/jit-recording.c index b42407909579860caafeae2317c90f6153e1f395..764e7a33c7688b36c8a74ebe444af9a47340d840 100644 --- a/gcc/jit/jit-recording.c +++ b/gcc/jit/jit-recording.c @@ -1062,6 +1062,18 @@ recording::context::new_global (recording::location *loc, return result; } +void +recording::context::new_global_init_rvalue (lvalue *variable, + rvalue *init) +{ + recording::global_init_rvalue *obj = + new recording::global_init_rvalue (this, variable, init); + record (obj); + + global *gbl = (global *) variable; + gbl->set_rvalue_init (init); /* Needed by the global for write dump. */ +} + /* Create a recording::memento_of_new_string_literal instance and add it to this context's list of mementos. @@ -1094,6 +1106,72 @@ recording::context::new_rvalue_from_vector (location *loc, return result; } +recording::rvalue * +recording::context::new_ctor (recording::location *loc, + recording::type *type, + size_t num_values, + field **fields, + rvalue **values) +{ + recording::ctor *result = new ctor (this, loc, type); + + /* Short cut for zero init. */ + if (!num_values) + { + record (result); + return result; + } + + bool is_struct_or_union = type->is_struct () || type->is_union (); + + /* We need to copy fields and values into result's auto_vec:s. + Both for structs and unions and only values for arrays. */ + if (type->is_array () != NULL) + { + result->m_values.reserve (num_values, false); + + for (size_t i = 0; i < num_values; i++) + result->m_values.quick_push (values[i]); + } + else if (is_struct_or_union && fields) + { + /* ctor values are paired with user specified fields. */ + + result->m_values.reserve (num_values, false); + result->m_fields.reserve (num_values, false); + + for (size_t i = 0; i < num_values; i++) + { + result->m_values.quick_push (values[i]); + result->m_fields.quick_push (fields[i]); + } + } + else if (is_struct_or_union && !fields) + { + /* ctor values are in definition order one by one, + so take the fields from the type object. */ + + result->m_values.reserve (num_values, false); + result->m_fields.reserve (num_values, false); + + compound_type *ct = reinterpret_cast<compound_type *>(type); + recording::fields *fields = ct->get_fields (); + + /* The entry point checks that num_values is not greater than + the amount of fields in 'fields'. */ + for (size_t i = 0; i < num_values; i++) + { + result->m_values.quick_push (values[i]); + result->m_fields.quick_push (fields->get_field (i)); + } + } + else + gcc_unreachable (); + + record (result); + return result; +} + /* Create a recording::unary_op instance and add it to this context's list of mementos. @@ -4581,11 +4659,13 @@ recording::global::replay_into (replayer *r) m_initializer_num_bytes / m_type->dereference ()->get_size (), m_initializer, - playback_string (m_name)) - : r->new_global (playback_location (r, m_loc), + playback_string (m_name), + m_flags) + : r->new_global (playback_location (r, m_loc), m_kind, m_type->playback_type (), - playback_string (m_name)); + playback_string (m_name), + m_flags); if (m_tls_model != GCC_JIT_TLS_MODEL_NONE) global->set_tls_model (recording::tls_models[m_tls_model]); @@ -4642,21 +4722,30 @@ recording::global::write_to_dump (dump &d) m_type->get_debug_string (), get_debug_string ()); - if (!m_initializer) + if (!m_initializer && !m_rvalue_init) { d.write (";\n"); - return; } - - d.write ("=\n { "); - const unsigned char *p = (const unsigned char *)m_initializer; - for (size_t i = 0; i < m_initializer_num_bytes; i++) + else if (m_initializer) { - d.write ("0x%x, ", p[i]); - if (i && !(i % 64)) - d.write ("\n "); + d.write ("=\n { "); + const unsigned char *p = (const unsigned char *)m_initializer; + for (size_t i = 0; i < m_initializer_num_bytes; i++) + { + d.write ("0x%x, ", p[i]); + if (i && !(i % 64)) + d.write ("\n "); + } + d.write ("};\n"); } - d.write ("};\n"); + else if (m_rvalue_init) + { + d.write (" = "); + d.write (m_rvalue_init->get_debug_string ()); + d.write (";\n"); + } + + return; } /* A table of enum gcc_jit_global_kind values expressed in string @@ -5123,6 +5212,201 @@ recording::memento_of_new_rvalue_from_vector::write_reproducer (reproducer &r) elements_id); } +void +recording::ctor::visit_children (rvalue_visitor *v) +{ + for (unsigned int i = 0; i < m_values.length (); i++) + v->visit (m_values[i]); +} + +recording::string * +recording::ctor::make_debug_string () +{ + //Make a compound literal-ish + pretty_printer pp; + + pp_string (&pp, "("); + pp_string (&pp, m_type->get_debug_string ()); + pp_string (&pp, ") {"); + + size_t field_n = m_fields.length (); + size_t values_n = m_values.length (); + + if (!field_n && !values_n) + ; + else if (!field_n && values_n) + { + for (size_t i = 0; i < values_n; i++) + { + if (m_values[i]) + pp_string (&pp, m_values[i]->get_debug_string ()); + else + pp_string (&pp, "0"); + if (i + 1 != values_n) + pp_string (&pp, ", "); + } + } + else if (field_n && values_n) + { + for (size_t i = 0; i < values_n; i++) + { + pp_string (&pp, "."); + pp_string (&pp, m_fields[i]->get_debug_string ()); + pp_string (&pp, "="); + if (m_values[i]) + pp_string (&pp, m_values[i]->get_debug_string ()); + else + pp_string (&pp, "0"); + if (i + 1 != values_n) + pp_string (&pp, ", "); + } + } + /* m_fields are never populated with m_values empty. */ + + pp_string (&pp, "}"); + + return new_string (pp_formatted_text (&pp)); +} + +void +recording::ctor::write_reproducer (reproducer &r) +{ + const char *id = r.make_identifier (this, "rvalue"); + type *type = get_type (); + + r.write (" gcc_jit_rvalue *%s;\n", id); + r.write (" {\n"); /* Open scope for locals. */ + + if (type->is_union ()) + { + if (m_values.length () == 0) + r.write (" gcc_jit_rvalue *value = NULL;\n"); + else + r.write (" gcc_jit_rvalue *value = %s;\n", + r.get_identifier (m_values[0])); + + if (m_fields.length () == 0) + r.write (" gcc_jit_field *field = NULL;\n"); + else + r.write (" gcc_jit_field *field = %s;\n", + r.get_identifier (m_fields[0])); + } + else + { + /* Write the array of values. */ + if (m_values.length () == 0) + r.write (" gcc_jit_rvalue **values = NULL;\n"); + else + { + r.write (" gcc_jit_rvalue *values[] = {\n"); + for (size_t i = 0; i < m_values.length (); i++) + r.write (" %s,\n", r.get_identifier (m_values[i])); + r.write (" };\n"); + } + /* Write the array of fields. */ + if (m_fields.length () == 0) + r.write (" gcc_jit_field **fields = NULL;\n"); + else + { + r.write (" gcc_jit_field *fields[] = {\n"); + for (size_t i = 0; i < m_fields.length (); i++) + r.write (" %s,\n", r.get_identifier (m_fields[i])); + r.write (" };\n"); + } + } + if (type->is_array ()) + r.write ( +" %s =\n" +" gcc_jit_context_new_array_constructor (%s,\n" +" %s, /* gcc_jit_location *loc */\n" +" %s, /* gcc_jit_type *type */\n" +" %i, /* int num_values */\n" +" values);\n", + id, + r.get_identifier (get_context ()), + r.get_identifier (m_loc), + r.get_identifier_as_type (get_type ()), + m_values.length ()); + else if (type->is_struct ()) + r.write ( +" %s =\n" +" gcc_jit_context_new_struct_constructor (%s,\n" +" %s, /* loc */\n" +" %s, /* gcc_jit_type *type */\n" +" %i, /* int num_values */\n" +" fields,\n" +" values);\n", + id, + r.get_identifier (get_context ()), + r.get_identifier (m_loc), + r.get_identifier_as_type (get_type ()), + m_values.length ()); + else if (type->is_union ()) + r.write ( +" %s =\n" +" gcc_jit_context_new_union_constructor (%s,\n" +" %s, /* loc */\n" +" %s, /* gcc_jit_type *type */\n" +" field,\n" +" value);\n", + id, + r.get_identifier (get_context ()), + r.get_identifier (m_loc), + r.get_identifier_as_type (get_type ())); + else + gcc_unreachable (); + + r.write (" }\n"); /* Close scope for locals. */ +} + +void +recording::ctor::replay_into (replayer *r) +{ + auto_vec<playback::rvalue *> playback_values; + auto_vec<playback::field *> playback_fields; + + int n = m_values.length (); + + type *type = get_type (); + + /* Handle arrays, and return. */ + if (type->is_array ()) + { + playback_values.reserve (n, false); + + for (int i = 0; i < n; i++) + { + /* null m_values element indicates zero ctor. */ + playback_values.quick_push (m_values[i] ? + m_values[i]->playback_rvalue () : + NULL); + } + set_playback_obj (r->new_ctor (playback_location (r, m_loc), + get_type ()->playback_type (), + NULL, + &playback_values)); + return; + } + /* ... else handle unions and structs. */ + + playback_values.reserve (n, false); + playback_fields.reserve (n, false); + + for (int i = 0; i < n; i++) + { + /* null m_values element indicates zero ctor. */ + playback_values.quick_push (m_values[i] ? + m_values[i]->playback_rvalue () : + NULL); + playback_fields.quick_push (m_fields[i]->playback_field ()); + } + + set_playback_obj (r->new_ctor (playback_location (r, m_loc), + get_type ()->playback_type (), + &playback_fields, + &playback_values)); +} + /* The implementation of class gcc::jit::recording::unary_op. */ /* Implementation of pure virtual hook recording::memento::replay_into @@ -7087,6 +7371,167 @@ recording::top_level_asm::write_reproducer (reproducer &r) m_asm_stmts->get_debug_string ()); } +void +recording::global_init_rvalue::replay_into (replayer *r) +{ + r->global_set_init_rvalue (m_variable->playback_lvalue (), + m_init->playback_rvalue ()); +} + +void +recording::global_init_rvalue::write_reproducer (reproducer &r) +{ + r.write ( + " gcc_jit_global_set_initializer_rvalue (%s, /* lvalue *global */\n" + " %s);/* rvalue *init */\n", + r.get_identifier (m_variable), + r.get_identifier_as_rvalue (m_init)); +} + +void +recording::global_init_rvalue::write_to_dump (dump &d) +{ + d.write ("%s;\n", get_debug_string ()); +} + +recording::string * +recording::global_init_rvalue::make_debug_string () +{ + return string::from_printf (m_ctxt, "%s = %s", + m_variable->get_debug_string (), + m_init->get_debug_string ()); +} + +enum strip_flags { + STRIP_FLAG_NONE, + STRIP_FLAG_ARR, + STRIP_FLAG_VEC +}; + +/* Strips type down to array, vector or base type (whichever comes first) + + Also saves 'ptr_depth' and sets 'flags' for array or vector types. */ +static +recording::type * +strip_and_count (recording::type *type_to_strip, + int &ptr_depth, + strip_flags &flags) +{ + recording::type *t = type_to_strip; + + while (true) + { + if (!t) + gcc_unreachable (); /* Should only happen on corrupt input. */ + + recording::type *pointed_to_type = t->is_pointer (); + if (pointed_to_type != NULL) + { + ptr_depth++; + t = pointed_to_type; + continue; + } + + recording::type *array_el = t->is_array (); + if (array_el != NULL) + { + flags = STRIP_FLAG_ARR; + break; + } + + recording::type *vec = t->dyn_cast_vector_type (); + if (vec != NULL) + { + flags = STRIP_FLAG_VEC; + break; + } + + /* unqualified () returns 'this' on base types. */ + recording::type *next = t->unqualified (); + if (next == t) + { + break; + } + t = next; + } + + return t; +} + +/* Strip qualifiers and count pointer depth, returning true + if the types' base type and pointer depth are + the same, otherwise false. + + For array and vector types the number of element also + has to match. + + Do not call this directly. Call 'types_kinda_same'. */ +bool +types_kinda_same_internal (recording::type *a, recording::type *b) +{ + int ptr_depth_a = 0; + int ptr_depth_b = 0; + recording::type *base_a; + recording::type *base_b; + + strip_flags flags_a = STRIP_FLAG_NONE; + strip_flags flags_b = STRIP_FLAG_NONE; + + base_a = strip_and_count (a, ptr_depth_a, flags_a); + base_b = strip_and_count (b, ptr_depth_b, flags_b); + + if (ptr_depth_a != ptr_depth_b) + return false; + + if (base_a == base_b) + return true; + + if (flags_a != flags_b) + return false; + + /* If the "base type" is an array or vector we might need to + check deeper. */ + if (flags_a == STRIP_FLAG_ARR) + { + recording::array_type *arr_a = + static_cast<recording::array_type*> (base_a); + recording::array_type *arr_b = + static_cast<recording::array_type*> (base_b); + + if (arr_a->num_elements () != arr_b->num_elements ()) + return false; + + /* is_array returns element type. */ + recording::type *el_a = arr_a->is_array (); + recording::type *el_b = arr_b->is_array (); + + if (el_a == el_b) + return true; + + return types_kinda_same_internal (el_a, el_b); + } + if (flags_a == STRIP_FLAG_VEC) + { + recording::vector_type *arr_a = + static_cast<recording::vector_type*> (base_a); + recording::vector_type *arr_b = + static_cast<recording::vector_type*> (base_b); + + if (arr_a->get_num_units () != arr_b->get_num_units ()) + return false; + + recording::type *el_a = arr_a->get_element_type (); + recording::type *el_b = arr_b->get_element_type (); + + if (el_a == el_b) + return true; + + return types_kinda_same_internal (el_a, el_b); + } + + return false; +} + } // namespace gcc::jit } // namespace gcc diff --git a/gcc/jit/jit-recording.h b/gcc/jit/jit-recording.h index cedb24720cfdfdf4bf45c212622e70c7035bb224..e9760c47ad0af1a10220ff3d3efc673d16d513a3 100644 --- a/gcc/jit/jit-recording.h +++ b/gcc/jit/jit-recording.h @@ -149,6 +149,17 @@ public: type *type, const char *name); + rvalue * + new_ctor (location *loc, + type *type, + size_t num_values, + field **fields, + rvalue **values); + + void + new_global_init_rvalue (lvalue *variable, + rvalue *init); + template <typename HOST_TYPE> rvalue * new_rvalue_from_const (type *type, @@ -549,6 +560,7 @@ public: virtual type *is_const () { return NULL; } virtual type *is_array () = 0; virtual struct_ *is_struct () { return NULL; } + virtual bool is_union () const { return false; } virtual bool is_void () const { return false; } virtual vector_type *is_vector () { return NULL; } virtual bool has_known_size () const { return true; } @@ -1016,6 +1028,8 @@ public: void replay_into (replayer *r) FINAL OVERRIDE; + virtual bool is_union () const FINAL OVERRIDE { return true; } + private: string * make_debug_string () FINAL OVERRIDE; void write_reproducer (reproducer &r) FINAL OVERRIDE; @@ -1421,6 +1435,23 @@ public: m_initializer_num_bytes = num_bytes; } + void set_flags (int flag_fields) + { + m_flags = (enum global_var_flags)(m_flags | flag_fields); + } + /* Returns true if any of the flags in the argument is set. */ + bool test_flags_anyof (int flag_fields) const + { + return m_flags & flag_fields; + } + + enum gcc_jit_global_kind get_kind () const + { + return m_kind; + } + + void set_rvalue_init (rvalue *val) { m_rvalue_init = val; } + private: string * make_debug_string () FINAL OVERRIDE { return m_name; } template <typename T> @@ -1433,8 +1464,10 @@ private: private: enum gcc_jit_global_kind m_kind; + enum global_var_flags m_flags = GLOBAL_VAR_FLAGS_NONE; string *m_name; void *m_initializer; + rvalue *m_rvalue_init = nullptr; /* Only needed for write_dump. */ size_t m_initializer_num_bytes; }; @@ -1519,6 +1552,32 @@ private: auto_vec<rvalue *> m_elements; }; +class ctor : public rvalue +{ +public: + ctor (context *ctxt, + location *loc, + type *type) + : rvalue (ctxt, loc, type) + { } + + void replay_into (replayer *r) FINAL OVERRIDE; + + void visit_children (rvalue_visitor *) FINAL OVERRIDE; + +private: + string * make_debug_string () FINAL OVERRIDE; + void write_reproducer (reproducer &r) FINAL OVERRIDE; + enum precedence get_precedence () const FINAL OVERRIDE + { + return PRECEDENCE_PRIMARY; + } + +public: + auto_vec<field *> m_fields; + auto_vec<rvalue *> m_values; +}; + class unary_op : public rvalue { public: @@ -2362,6 +2421,24 @@ private: string *m_asm_stmts; }; +class global_init_rvalue : public memento +{ +public: + global_init_rvalue (context *ctxt, lvalue *variable, rvalue *init) : + memento (ctxt), m_variable (variable), m_init (init) {}; + + void write_to_dump (dump &d) FINAL OVERRIDE; + +private: + void replay_into (replayer *r) FINAL OVERRIDE; + string * make_debug_string () FINAL OVERRIDE; + void write_reproducer (reproducer &r) FINAL OVERRIDE; + +private: + lvalue *m_variable; + rvalue *m_init; +}; + } // namespace gcc::jit::recording /* Create a recording::memento_of_new_rvalue_from_const instance and add @@ -2381,6 +2458,23 @@ recording::context::new_rvalue_from_const (recording::type *type, return result; } +/* Don't call this directly. Call types_kinda_same. */ +bool +types_kinda_same_internal (recording::type *a, + recording::type *b); + +/* Strip all qualifiers and count pointer depth, returning true + if the types and pointer depth are the same, otherwise false. + + For array and vector types the number of element also + has to match, aswell as the element types themself. */ +static inline bool +types_kinda_same (recording::type *a, recording::type *b) +{ + /* Handle trivial case here, to allow for inlining. */ + return a == b || types_kinda_same_internal (a, b); +} + } // namespace gcc::jit } // namespace gcc diff --git a/gcc/jit/libgccjit++.h b/gcc/jit/libgccjit++.h index 82831ff5da0488c84a565d33da6aec7343149055..25414620afb249a3fcbcfda5343740e474d608cf 100644 --- a/gcc/jit/libgccjit++.h +++ b/gcc/jit/libgccjit++.h @@ -197,6 +197,20 @@ namespace gccjit rvalue new_rvalue (type vector_type, std::vector<rvalue> elements) const; + rvalue new_struct_ctor (type type_, + std::vector<field> &fields, + std::vector<rvalue> &values, + location loc = location ()); + + rvalue new_array_ctor (type type_, + std::vector<rvalue> &values, + location loc = location ()); + + rvalue new_union_ctor (type type_, + field field, + rvalue value, + location loc = location ()); + /* Generic unary operations... */ rvalue new_unary_op (enum gcc_jit_unary_op op, type result_type, @@ -500,6 +514,7 @@ namespace gccjit rvalue get_address (location loc = location ()); lvalue set_initializer (const void *blob, size_t num_bytes); + lvalue set_initializer_rvalue (rvalue init_value); }; class param : public lvalue @@ -1831,6 +1846,81 @@ lvalue::set_initializer (const void *blob, size_t num_bytes) return *this; } +inline lvalue +lvalue::set_initializer_rvalue (rvalue init_value) +{ + return lvalue (gcc_jit_global_set_initializer_rvalue ( + get_inner_lvalue (), + init_value.get_inner_rvalue ())); +} + +inline rvalue +context::new_struct_ctor (type type_, + std::vector<field> &fields, + std::vector<rvalue> &values, + location loc) +{ + field *pfields = nullptr; + if (fields.size ()) + pfields = &fields[0]; + + gcc_jit_field **fields_arr = + reinterpret_cast<gcc_jit_field **> (pfields); + + rvalue *pvalues = nullptr; + if (values.size ()) + pvalues = &values[0]; + + gcc_jit_rvalue **values_arr = + reinterpret_cast<gcc_jit_rvalue **> (pvalues); + + return rvalue ( + gcc_jit_context_new_struct_constructor ( + m_inner_ctxt, + loc.get_inner_location (), + type_.get_inner_type (), + (int)values.size (), + fields_arr, + values_arr)); +} + +inline rvalue +context::new_array_ctor (type type_, + std::vector<rvalue> &values, + location loc) +{ + rvalue *pvalues = nullptr; + if (values.size ()) + pvalues = &values[0]; + + gcc_jit_rvalue **values_arr = + reinterpret_cast<gcc_jit_rvalue **> (pvalues); + + return rvalue ( + gcc_jit_context_new_array_constructor ( + m_inner_ctxt, + loc.get_inner_location (), + type_.get_inner_type (), + (int)values.size (), + values_arr)); +} + +inline rvalue +context::new_union_ctor (type type_, + field field, + rvalue value, + location loc) +{ + return rvalue ( + gcc_jit_context_new_union_constructor ( + m_inner_ctxt, + loc.get_inner_location (), + type_.get_inner_type (), + field.get_inner_field (), + value.get_inner_rvalue ())); +} + + // class param : public lvalue inline param::param () : lvalue () {} inline param::param (gcc_jit_param *inner) diff --git a/gcc/jit/libgccjit.c b/gcc/jit/libgccjit.c index 59cef614d4b7a9f25c60f603725f5e6d53fc87c8..5cb27a20d4180624338be26181895b88cb5943e9 100644 --- a/gcc/jit/libgccjit.c +++ b/gcc/jit/libgccjit.c @@ -1386,6 +1386,393 @@ gcc_jit_context_new_global (gcc_jit_context *ctxt, return (gcc_jit_lvalue *)ctxt->new_global (loc, kind, type, name); } +extern gcc_jit_rvalue * +gcc_jit_context_new_struct_constructor (gcc_jit_context *ctxt, + gcc_jit_location *loc, + gcc_jit_type *type, + size_t num_values, + gcc_jit_field **fields, + gcc_jit_rvalue **values) +{ + using namespace gcc::jit::recording; + + RETURN_NULL_IF_FAIL (ctxt, NULL, loc, "NULL context"); + JIT_LOG_FUNC (ctxt->get_logger ()); + RETURN_NULL_IF_FAIL (type, ctxt, loc, "NULL type"); + + RETURN_NULL_IF_FAIL_PRINTF1 (type->is_struct (), + ctxt, loc, + "constructor type is not a struct: %s", + type->get_debug_string ()); + + compound_type *ct = reinterpret_cast<compound_type *>(type); + gcc::jit::recording::fields *fields_struct = ct->get_fields (); + size_t n_fields = fields_struct->length (); + + RETURN_NULL_IF_FAIL_PRINTF1 (ct->has_known_size (), + ctxt, loc, + "struct can't be opaque: %s", + type->get_debug_string ()); + RETURN_NULL_IF_FAIL_PRINTF1 (n_fields, + ctxt, loc, + "no fields in struct: %s", + type->get_debug_string ()); + + /* If there is no array input we just short circuit to zero the struct. */ + if (!num_values) + return (gcc_jit_rvalue *)ctxt->new_ctor (loc, type, 0, NULL, NULL); + + RETURN_NULL_IF_FAIL_PRINTF3 (n_fields >= num_values, + ctxt, loc, + "more values in constructor (n=%zu) than fields" + " in target %s (n=%zu)", + num_values, + type->get_debug_string (), + n_fields); + + /* It is OK if fields are null here, indicating definiton order, + but there has to be a values array. */ + RETURN_NULL_IF_FAIL (values, + ctxt, loc, + "'values' NULL with non-zero 'num_values'"); + + size_t idx = 0; /* Runner index for fields in the type object. */ + + for (size_t i = 0; i < num_values; i++) + { + gcc::jit::recording::rvalue *rv = values[i]; + + /* rv kan be NULL, which would indicate zero init for the field. */ + gcc::jit::recording::type *rv_type = rv ? rv->get_type () : nullptr; + + /* If fields are specified we need to check that they are in + definition order. */ + if (fields) + { + gcc::jit::recording::field *f = fields[i]; + + RETURN_NULL_IF_FAIL_PRINTF1 ( + f, + ctxt, loc, + "NULL field in 'fields', at index %zu", i); + + RETURN_NULL_IF_FAIL_PRINTF3 ( + f->get_container () == + static_cast<gcc::jit::recording::type*>(type), + ctxt, loc, + "field object at index %zu (%s), was not used when creating " + "the %s", + i, + f->get_debug_string (), + type->get_debug_string ()); + + /* Fields in the constructor need to be in struct definition + order, but there can be gaps. */ + size_t j; + for (j = idx; j < n_fields; j++) + { + field *fs = fields_struct->get_field (j); + if (fs == f) + { + idx = j; /* Advance runner index for next iteration. */ + break; + } + } + + RETURN_NULL_IF_FAIL_PRINTF3 ( + j != n_fields, + ctxt, loc, + "field at index %zu in 'fields' is not in definition order " + "(struct: %s) (ctor field: %s)", + i, + type->get_debug_string (), + f->get_debug_string ()); + + /* Check that the specified field has the same type as the + value, unless the value is null (a zero value init). */ + RETURN_NULL_IF_FAIL_PRINTF5 ( + !rv || gcc::jit::types_kinda_same (rv_type, + f->get_type ()), + ctxt, loc, + "value and field not the same unqualified type, at index %zu" + " (%s.%s: %s)(value type: %s)", + i, + type->get_debug_string (), + f->get_debug_string (), + f->get_type ()->get_debug_string (), + rv_type->get_debug_string ()); + } + + /* If no fields are specified, check that the value has the same type + as the field in the definition of the struct. */ + if (rv && !fields) + { + RETURN_NULL_IF_FAIL_PRINTF5 ( + gcc::jit::types_kinda_same (rv_type, + fields_struct-> + get_field (i)->get_type ()), + ctxt, loc, + "value and field not the same unqualified type, at index %zu" + " (%s.%s: %s)(value type: %s)", + i, + type->get_debug_string (), + fields_struct->get_field (i)->get_debug_string (), + fields_struct->get_field (i)->get_type ()->get_debug_string (), + rv_type->get_debug_string ()); + } + + if (rv) + { + RETURN_NULL_IF_FAIL_PRINTF1 ( + !rv_type->is_void (), + ctxt, loc, + "can't construct the void type, at index %zu", i); + } + } + + return (gcc_jit_rvalue *)ctxt->new_ctor ( + loc, + type, + num_values, + reinterpret_cast<gcc::jit::recording::field**>(fields), + reinterpret_cast<gcc::jit::recording::rvalue**>(values)); +} + +extern gcc_jit_rvalue * +gcc_jit_context_new_union_constructor (gcc_jit_context *ctxt, + gcc_jit_location *loc, + gcc_jit_type *type, + gcc_jit_field *field, + gcc_jit_rvalue *value) +{ + using namespace gcc::jit::recording; + + RETURN_NULL_IF_FAIL (ctxt, NULL, loc, "NULL context"); + JIT_LOG_FUNC (ctxt->get_logger ()); + RETURN_NULL_IF_FAIL (type, ctxt, loc, "NULL type"); + + RETURN_NULL_IF_FAIL_PRINTF1 (type->is_union (), + ctxt, loc, + "constructor type is not an union: %s", + type->get_debug_string ()); + + compound_type *ct = reinterpret_cast<compound_type *>(type); + gcc::jit::recording::fields *fields_union = ct->get_fields (); + size_t n_fields = fields_union->length (); + + RETURN_NULL_IF_FAIL_PRINTF1 (ct->has_known_size (), + ctxt, loc, + "union can't be opaque: %s", + type->get_debug_string ()); + RETURN_NULL_IF_FAIL_PRINTF1 (n_fields, + ctxt, loc, + "no fields in union: %s", + type->get_debug_string ()); + + /* If value is NULL we are just supposed to zero the whole union. */ + if (!value) + return (gcc_jit_rvalue *)ctxt->new_ctor (loc, type, 0, NULL, NULL); + + gcc::jit::recording::type *rv_type = value->get_type (); + + RETURN_NULL_IF_FAIL ( + !rv_type->is_void (), + ctxt, loc, + "can't construct the void type"); + + if (field) + { + RETURN_NULL_IF_FAIL_PRINTF2 ( + field->get_container () == + static_cast<gcc::jit::recording::type*>(type), + ctxt, loc, + "field object (%s) was not used when creating " + "the type %s", + field->get_debug_string (), + type->get_debug_string ()); + + RETURN_NULL_IF_FAIL_PRINTF4 ( + gcc::jit::types_kinda_same (rv_type, + field->get_type ()), + ctxt, loc, + "value and field are not the same unqualified type" + " (%s.%s: %s)(value type: %s)", + type->get_debug_string (), + field->get_debug_string (), + field->get_type ()->get_debug_string (), + rv_type->get_debug_string ()); + } + /* If no field is specified, check that the value has the same type + as the first field in the definition of the union. */ + if (!field) + RETURN_NULL_IF_FAIL_PRINTF2 ( + gcc::jit::types_kinda_same (rv_type, + fields_union-> + get_field (0)->get_type ()), + ctxt, loc, + "value and first union field not the same unqualified type" + " (field type: %s)(value type: %s)", + fields_union->get_field (0)->get_type ()->get_debug_string (), + rv_type->get_debug_string ()); + + + return (gcc_jit_rvalue *)ctxt->new_ctor ( + loc, + type, + 1, + /* A NULL fields array tells new_ctor to take fields from the type obj. */ + reinterpret_cast<gcc::jit::recording::field**>(field ? &field : NULL), + reinterpret_cast<gcc::jit::recording::rvalue**>(&value)); +} + +extern gcc_jit_rvalue * +gcc_jit_context_new_array_constructor (gcc_jit_context *ctxt, + gcc_jit_location *loc, + gcc_jit_type *type, + size_t num_values, + gcc_jit_rvalue **values) +{ + using namespace gcc::jit::recording; + + RETURN_NULL_IF_FAIL (ctxt, NULL, loc, "NULL context"); + JIT_LOG_FUNC (ctxt->get_logger ()); + RETURN_NULL_IF_FAIL (type, ctxt, loc, "NULL type"); + + RETURN_NULL_IF_FAIL (type->is_array () != NULL, + ctxt, loc, + "constructor type not an array"); + + if (!num_values) + values = NULL; + + if (num_values) + { + RETURN_NULL_IF_FAIL ( + values, + ctxt, loc, + "'values' NULL with non-zero 'num_values'"); + + gcc::jit::recording::array_type *arr_type = + reinterpret_cast<gcc::jit::recording::array_type*>(type); + size_t n_el = arr_type->num_elements (); + + RETURN_NULL_IF_FAIL_PRINTF2 ( + n_el >= num_values, + ctxt, loc, + "array constructor has more values than the array type's length" + " (array type length: %zu, constructor length: %zu)", + n_el, + num_values); + + /* For arrays, all values need to be the same base type. */ + gcc::jit::recording::type *type0 = NULL; + size_t i = 0; + /* Find first non-null value. */ + for (;i < num_values; i++) + { + if (values[i]) + break; + } + + if (i < num_values) /* All values might be null and i == num_values. */ + type0 = values[i]->get_type (); + + /* If we got a type0, check that all other values have + the same type. */ + for (; i < num_values; i++) + { + if (values[i]) + RETURN_NULL_IF_FAIL_PRINTF3 ( + gcc::jit::types_kinda_same (type0, + values[i]->get_type ()), + ctxt, loc, + "value type at index %zu differ from first value type" + " (first type: %s)(different type: %s)", + i, + type0->get_debug_string (), + values[i]->get_type ()->get_debug_string ()); + } + + /* Compare type0 with the element type specified in the + type of the array. */ + if (type0) + { + gcc::jit::recording::type *el_type = + type->is_array (); + + RETURN_NULL_IF_FAIL_PRINTF2 ( + gcc::jit::types_kinda_same (type0, el_type), + ctxt, loc, + "array element value types differ from types in 'values'" + " (element type: %s)('values' type: %s)", + el_type->get_debug_string (), + type0->get_debug_string ()); + } + } + + return (gcc_jit_rvalue *)ctxt->new_ctor ( + loc, + type, + num_values, + NULL, + reinterpret_cast<gcc::jit::recording::rvalue**>(values)); +} + +/* Public entrypoint. See description in libgccjit.h. */ + +extern gcc_jit_lvalue * +gcc_jit_global_set_initializer_rvalue (gcc_jit_lvalue *global, + gcc_jit_rvalue *init_rvalue) +{ + RETURN_NULL_IF_FAIL (global, NULL, NULL,"NULL global"); + + gcc::jit::recording::context *ctxt = global->get_context (); + RETURN_NULL_IF_FAIL (ctxt, NULL, NULL,"NULL context"); + JIT_LOG_FUNC (ctxt->get_logger ()); + RETURN_NULL_IF_FAIL (init_rvalue, ctxt, NULL,"NULL init_rvalue"); + + RETURN_NULL_IF_FAIL_PRINTF1 (global->is_global (), + ctxt, NULL, + "lvalue \"%s\" not a global", + global->get_debug_string ()); + + gcc::jit::recording::global *gbl = + reinterpret_cast<gcc::jit::recording::global *> (global); + + RETURN_NULL_IF_FAIL_PRINTF1 (gbl->get_kind () != + GCC_JIT_GLOBAL_IMPORTED, + ctxt, NULL, + "can't initialize \"%s\", it is imported", + global->get_debug_string ()); + + RETURN_NULL_IF_FAIL_PRINTF4 (gcc::jit::types_kinda_same ( + global->get_type (), + init_rvalue->get_type ()), + ctxt, NULL, + "mismatching types:" + " initializing %s (type: %s) with %s (type: %s)", + global->get_debug_string (), + global->get_type ()->get_debug_string (), + init_rvalue->get_debug_string (), + init_rvalue->get_type ()->get_debug_string ()); + + /* Check that there are no initializers set for the global yet. */ + RETURN_NULL_IF_FAIL_PRINTF1 (!gbl->test_flags_anyof ( + gcc::jit::GLOBAL_VAR_FLAGS_WILL_BE_RVAL_INIT | + gcc::jit::GLOBAL_VAR_FLAGS_WILL_BE_BLOB_INIT), + ctxt, NULL, + "global variable already initialized: %s", + global->get_debug_string ()); + + /* The global need to know during playback that it will be + initialized. */ + gbl->set_flags (gcc::jit::GLOBAL_VAR_FLAGS_WILL_BE_RVAL_INIT); + + ctxt->new_global_init_rvalue (global, init_rvalue); + + return global; +} + /* Public entrypoint. See description in libgccjit.h. After error-checking, the real work is done by the @@ -1419,8 +1806,22 @@ gcc_jit_global_set_initializer (gcc_jit_lvalue *global, " global \"%s\" has size %zu whereas initializer has size %zu", global->get_debug_string (), lvalue_size, num_bytes); - reinterpret_cast <gcc::jit::recording::global *> (global) - ->set_initializer (blob, num_bytes); + /* Check that the rvalue initializer is not set for this global. + Note that we do not check if this blob type initializer is + already set, since that check was not present when the entrypoint + was initially written. */ + gcc::jit::recording::global *gbl = + reinterpret_cast<gcc::jit::recording::global *> (global); + RETURN_NULL_IF_FAIL_PRINTF1 (!gbl->test_flags_anyof ( + gcc::jit::GLOBAL_VAR_FLAGS_WILL_BE_RVAL_INIT), + NULL, NULL, + "global variable already initialized: %s", + global->get_debug_string ()); + + gbl->set_initializer (blob, num_bytes); + /* The global need to know during playback that it will be + initialized. */ + gbl->set_flags (gcc::jit::GLOBAL_VAR_FLAGS_WILL_BE_BLOB_INIT); return global; } diff --git a/gcc/jit/libgccjit.h b/gcc/jit/libgccjit.h index 024c8d79f4b6bd4c378b32c8b43e6eff7162d4a5..80a915fb8c426611f483aea41939aeefe467da25 100644 --- a/gcc/jit/libgccjit.h +++ b/gcc/jit/libgccjit.h @@ -822,6 +822,159 @@ gcc_jit_context_new_global (gcc_jit_context *ctxt, gcc_jit_type *type, const char *name); +#define LIBGCCJIT_HAVE_CTORS + +/* Create a constructor for a struct as an rvalue. + + Returns NULL on error. The two parameter arrays are copied and + do not have to outlive the context. + + `type` specifies what the constructor will build and has to be + a struct. + + `num_values` specifies the number of elements in `values`. + + `fields` need to have the same length as `values`, or be NULL. + + If `fields` is null, the values are applied in definition order. + + Otherwise, each field in `fields` specifies which field in the struct to + set to the corresponding value in `values`. `fields` and `values` + are paired by index. + + Each value has to have have the same unqualified type as the field + it is applied to. + + A NULL value element in `values` is a shorthand for zero initialization + of the corresponding field. + + The fields in `fields` have to be in definition order, but there + can be gaps. Any field in the struct that is not specified in + `fields` will be zeroed. + + The fields in `fields` need to be the same objects that were used + to create the struct. + + If `num_values` is 0, the array parameters will be + ignored and zero initialization will be used. + + The constructor rvalue can be used for assignment to locals. + It can be used to initialize global variables with + gcc_jit_global_set_initializer_rvalue. It can also be used as a + temporary value for function calls and return values. + + The constructor can contain nested constructors. + + This entrypoint was added in LIBGCCJIT_ABI_19; you can test for its + presence using: + #ifdef LIBGCCJIT_HAVE_CTORS +*/ + +extern gcc_jit_rvalue * +gcc_jit_context_new_struct_constructor (gcc_jit_context *ctxt, + gcc_jit_location *loc, + gcc_jit_type *type, + size_t num_values, + gcc_jit_field **fields, + gcc_jit_rvalue **values); + +/* Create a constructor for a union as an rvalue. + + Returns NULL on error. + + `type` specifies what the constructor will build and has to be + an union. + + `field` specifies which field to set. If it is NULL, the first + field in the union will be set. `field` need to be the same + object that were used to create the union. + + `value` specifies what value to set the corresponding field to. + If `value` is NULL, zero initialization will be used. + + Each value has to have have the same unqualified type as the field + it is applied to. + + `field` need to be the same objects that were used + to create the union. + + The constructor rvalue can be used for assignment to locals. + It can be used to initialize global variables with + gcc_jit_global_set_initializer_rvalue. It can also be used as a + temporary value for function calls and return values. + + The constructor can contain nested constructors. + + This entrypoint was added in LIBGCCJIT_ABI_19; you can test for its + presence using: + #ifdef LIBGCCJIT_HAVE_CTORS +*/ + +extern gcc_jit_rvalue * +gcc_jit_context_new_union_constructor (gcc_jit_context *ctxt, + gcc_jit_location *loc, + gcc_jit_type *type, + gcc_jit_field *field, + gcc_jit_rvalue *value); + +/* Create a constructor for an array as an rvalue. + + Returns NULL on error. `values` are copied and + do not have to outlive the context. + + `type` specifies what the constructor will build and has to be + an array. + + `num_values` specifies the number of elements in `values` and + it can't have more elements than the array type. + + Each value in `values` sets the corresponding value in the array. + If the array type itself has more elements than `values`, the + left-over elements will be zeroed. + + Each value in `values` need to be the same unqualified type as the + array type's element type. + + If `num_values` is 0, the `values` parameter will be + ignored and zero initialization will be used. + + Note that a string literal rvalue can't be used to construct a char + array. It needs one rvalue for each char. + + This entrypoint was added in LIBGCCJIT_ABI_19; you can test for its + presence using: + #ifdef LIBGCCJIT_HAVE_CTORS +*/ + +extern gcc_jit_rvalue * +gcc_jit_context_new_array_constructor (gcc_jit_context *ctxt, + gcc_jit_location *loc, + gcc_jit_type *type, + size_t num_values, + gcc_jit_rvalue **values); + +/* Set the initial value of a global of any type with an rvalue. + + The rvalue needs to be a constant expression, e.g. no function calls. + + The global can't have the 'kind' GCC_JIT_GLOBAL_IMPORTED. + + Use together with gcc_jit_context_new_constructor () to + initialize structs, unions and arrays. + + On success, returns the 'global' parameter unchanged. Otherwise, NULL. + + 'values' is copied and does not have to outlive the context. + + This entrypoint was added in LIBGCCJIT_ABI_19; you can test for its + presence using: + #ifdef LIBGCCJIT_HAVE_CTORS +*/ + +extern gcc_jit_lvalue * +gcc_jit_global_set_initializer_rvalue (gcc_jit_lvalue *global, + gcc_jit_rvalue *init_value); + #define LIBGCCJIT_HAVE_gcc_jit_global_set_initializer /* Set an initial value for a global, which must be an array of diff --git a/gcc/jit/libgccjit.map b/gcc/jit/libgccjit.map index b17671163c7ad946606b42f131de54e94df227b8..c0135e0dbd0d0f3f19843b7c998505d51abb9de6 100644 --- a/gcc/jit/libgccjit.map +++ b/gcc/jit/libgccjit.map @@ -236,3 +236,10 @@ LIBGCCJIT_ABI_18 { global: gcc_jit_lvalue_set_link_section; } LIBGCCJIT_ABI_17; + +LIBGCCJIT_ABI_19 { + gcc_jit_context_new_array_constructor; + gcc_jit_context_new_struct_constructor; + gcc_jit_context_new_union_constructor; + gcc_jit_global_set_initializer_rvalue; +} LIBGCCJIT_ABI_18; diff --git a/gcc/testsuite/jit.dg/all-non-failing-tests.h b/gcc/testsuite/jit.dg/all-non-failing-tests.h index 3e8ccbca60ea3e9219aec5644b6fea806667bf00..29afe064db62a706f64bb7cffdbbd1c9c4a2b5db 100644 --- a/gcc/testsuite/jit.dg/all-non-failing-tests.h +++ b/gcc/testsuite/jit.dg/all-non-failing-tests.h @@ -181,6 +181,13 @@ #undef create_code #undef verify_code +/* test-global-init-rvalue.c */ +#define create_code create_code_global_init_rvalue +#define verify_code verify_code_global_init_rvalue +#include "test-global-init-rvalue.c" +#undef create_code +#undef verify_code + /* test-global-set-initializer.c */ #define create_code create_code_global_set_initializer #define verify_code verify_code_global_set_initializer @@ -219,6 +226,13 @@ #undef create_code #undef verify_code +/* test-local-init-rvalue.c */ +#define create_code create_code_local_init_rvalue +#define verify_code verify_code_local_init_rvalue +#include "test-local-init-rvalue.c" +#undef create_code +#undef verify_code + /* test-long-names.c */ #define create_code create_code_long_names #define verify_code verify_code_long_names @@ -431,12 +445,18 @@ const struct testcase testcases[] = { {"builtin-types", create_code_builtin_types, verify_code_builtin_types}, + {"global_rvalue_init", + create_code_global_init_rvalue, + verify_code_global_init_rvalue}, {"hello_world", create_code_hello_world, verify_code_hello_world}, {"linked_list", create_code_linked_list, verify_code_linked_list}, + {"local_rvalue_init", + create_code_local_init_rvalue, + verify_code_local_init_rvalue}, {"long_names", create_code_long_names, verify_code_long_names}, diff --git a/gcc/testsuite/jit.dg/test-error-ctor-array-wrong-obj.c b/gcc/testsuite/jit.dg/test-error-ctor-array-wrong-obj.c new file mode 100644 index 0000000000000000000000000000000000000000..6b54b8546fc4da400da9289320e7e0a628023c7e --- /dev/null +++ b/gcc/testsuite/jit.dg/test-error-ctor-array-wrong-obj.c @@ -0,0 +1,54 @@ +/* + + Test that the proper error is triggered when we build a ctor + for an array type, but has the type wrong on an element. + +*/ + +#include <stdlib.h> +#include <stdio.h> + +#include "libgccjit.h" +#include "harness.h" + +void +create_code (gcc_jit_context *ctxt, void *user_data) +{ + gcc_jit_type *int_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_INT); + gcc_jit_type *float_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_FLOAT); + + gcc_jit_type *arr_type = + gcc_jit_context_new_array_type (ctxt, 0, int_type, 10); + + gcc_jit_rvalue *frv = gcc_jit_context_new_rvalue_from_double (ctxt, + float_type, + 12); + + gcc_jit_rvalue *ctor = gcc_jit_context_new_array_constructor + (ctxt, 0, + arr_type, + 1, + &frv); + + CHECK_VALUE (ctor, NULL); +} + +void +verify_code (gcc_jit_context *ctxt, gcc_jit_result *result) +{ + /* Ensure that the bad API usage prevents the API giving a bogus + result back. */ + CHECK_VALUE (result, NULL); + + /* Verify that the correct error message was emitted. */ + CHECK_STRING_VALUE (gcc_jit_context_get_first_error (ctxt), + "gcc_jit_context_new_array_constructor: array element " + "value types differ from types in 'values' (element " + "type: int)('values' type: float)"); + CHECK_STRING_VALUE (gcc_jit_context_get_last_error (ctxt), + "gcc_jit_context_new_array_constructor: array element " + "value types differ from types in 'values' (element " + "type: int)('values' type: float)"); +} diff --git a/gcc/testsuite/jit.dg/test-error-ctor-struct-too-big.c b/gcc/testsuite/jit.dg/test-error-ctor-struct-too-big.c new file mode 100644 index 0000000000000000000000000000000000000000..6bc20459cd5487334120a7eac748f3e8ed6952f3 --- /dev/null +++ b/gcc/testsuite/jit.dg/test-error-ctor-struct-too-big.c @@ -0,0 +1,71 @@ +/* + + Test that the proper error is triggered when we build a ctor + for an struct type, but have too many fields and values. + +*/ + +#include <stdlib.h> +#include <stdio.h> + +#include "libgccjit.h" +#include "harness.h" + +void +create_code (gcc_jit_context *ctxt, void *user_data) +{ + gcc_jit_type *int_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_INT); + + gcc_jit_field *b1 = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "a"); + gcc_jit_field *b2 = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "b"); + gcc_jit_field *b3 = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "c"); + gcc_jit_field *fields_b[] = {b1, b2, b3}; + + gcc_jit_type *struct_bar_type = + gcc_jit_struct_as_type ( + gcc_jit_context_new_struct_type (ctxt, + 0, + "bar", + 3, + fields_b)); + + gcc_jit_field *fields_ctor[] = {b1, b2, b3, b3}; + gcc_jit_rvalue *values[] = {0,0,0,0}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_bar_type, + 4, + fields_ctor, + values); + + CHECK_VALUE (ctor, NULL); +} + +void +verify_code (gcc_jit_context *ctxt, gcc_jit_result *result) +{ + /* Ensure that the bad API usage prevents the API giving a bogus + result back. */ + CHECK_VALUE (result, NULL); + + /* Verify that the correct error message was emitted. */ + CHECK_STRING_VALUE (gcc_jit_context_get_first_error (ctxt), + "gcc_jit_context_new_struct_constructor: more values in " + "constructor (n=4) than fields in target struct " + "bar (n=3)"); + CHECK_STRING_VALUE (gcc_jit_context_get_last_error (ctxt), + "gcc_jit_context_new_struct_constructor: more values in " + "constructor (n=4) than fields in target struct " + "bar (n=3)"); +} diff --git a/gcc/testsuite/jit.dg/test-error-ctor-struct-wrong-field-obj.c b/gcc/testsuite/jit.dg/test-error-ctor-struct-wrong-field-obj.c new file mode 100644 index 0000000000000000000000000000000000000000..bc191e14d07447713e8144a6aeb44ec500e553ca --- /dev/null +++ b/gcc/testsuite/jit.dg/test-error-ctor-struct-wrong-field-obj.c @@ -0,0 +1,86 @@ +/* + + Test that the proper error is triggered when we build a ctor + for an struct type, but try to use a field object that was not + used to create the struct type. + +*/ + +#include <stdlib.h> +#include <stdio.h> + +#include "libgccjit.h" +#include "harness.h" + +void +create_code (gcc_jit_context *ctxt, void *user_data) +{ + gcc_jit_type *int_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_INT); + + gcc_jit_field *b1 = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "a"); + gcc_jit_field *b2 = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "b"); + gcc_jit_field *b3 = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "c"); + gcc_jit_field *b4 = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "d"); + gcc_jit_field *b5 = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "d"); + gcc_jit_field *fields_b[] = {b1, b2, b3, b4, b5}; + + gcc_jit_type *struct_bar_type = + gcc_jit_struct_as_type ( + gcc_jit_context_new_struct_type (ctxt, + 0, + "bar", + 5, + fields_b)); + + + gcc_jit_field *b44 = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "c"); + + gcc_jit_field *fields_ctor[] = {b1, b2, b44, b5}; + gcc_jit_rvalue *values[] = {0,0,0,0}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_bar_type, + 4, + fields_ctor, + values); + + CHECK_VALUE (ctor, NULL); +} + +void +verify_code (gcc_jit_context *ctxt, gcc_jit_result *result) +{ + /* Ensure that the bad API usage prevents the API giving a bogus + result back. */ + CHECK_VALUE (result, NULL); + + /* Verify that the correct error message was emitted. */ + CHECK_STRING_VALUE (gcc_jit_context_get_first_error (ctxt), + "gcc_jit_context_new_struct_constructor: field object " + "at index 2 (c), was not used when creating the " + "struct bar"); + CHECK_STRING_VALUE (gcc_jit_context_get_last_error (ctxt), + "gcc_jit_context_new_struct_constructor: field object " + "at index 2 (c), was not used when creating the " + "struct bar"); +} diff --git a/gcc/testsuite/jit.dg/test-error-ctor-struct-wrong-type.c b/gcc/testsuite/jit.dg/test-error-ctor-struct-wrong-type.c new file mode 100644 index 0000000000000000000000000000000000000000..364610bd21fb1fb6190f6cf2aa0a59651ff46d5d --- /dev/null +++ b/gcc/testsuite/jit.dg/test-error-ctor-struct-wrong-type.c @@ -0,0 +1,76 @@ +/* + + Test that the proper error is triggered when we build a ctor + for an struct type, but has the type wrong on a field. + +*/ + +#include <stdlib.h> +#include <stdio.h> + +#include "libgccjit.h" +#include "harness.h" + +void +create_code (gcc_jit_context *ctxt, void *user_data) +{ + gcc_jit_type *int_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_INT); + gcc_jit_type *float_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_FLOAT); + + gcc_jit_field *b1 = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "a"); + gcc_jit_field *b2 = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "b"); + gcc_jit_field *b3 = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "c"); + gcc_jit_field *fields_b[] = {b1, b2, b3}; + + gcc_jit_type *struct_bar_type = + gcc_jit_struct_as_type ( + gcc_jit_context_new_struct_type (ctxt, + 0, + "bar", + 3, + fields_b)); + gcc_jit_rvalue *frv = gcc_jit_context_new_rvalue_from_double (ctxt, + float_type, + 12); + + gcc_jit_field *fields_ctor[] = {b2}; + gcc_jit_rvalue *values[] = {frv}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_bar_type, + 1, + fields_ctor, + values); + + CHECK_VALUE (ctor, NULL); +} + +void +verify_code (gcc_jit_context *ctxt, gcc_jit_result *result) +{ + /* Ensure that the bad API usage prevents the API giving a bogus + result back. */ + CHECK_VALUE (result, NULL); + + /* Verify that the correct error message was emitted. */ + CHECK_STRING_VALUE (gcc_jit_context_get_first_error (ctxt), + "gcc_jit_context_new_struct_constructor: value and " + "field not the same unqualified type, at index 0 " + "(struct bar.b: int)(value type: float)"); + CHECK_STRING_VALUE (gcc_jit_context_get_last_error (ctxt), + "gcc_jit_context_new_struct_constructor: value and " + "field not the same unqualified type, at index 0 " + "(struct bar.b: int)(value type: float)"); +} diff --git a/gcc/testsuite/jit.dg/test-error-ctor-struct-wrong-type2.c b/gcc/testsuite/jit.dg/test-error-ctor-struct-wrong-type2.c new file mode 100644 index 0000000000000000000000000000000000000000..c2309de87dfb2b8f14f40f37e9f643cb8b3040ae --- /dev/null +++ b/gcc/testsuite/jit.dg/test-error-ctor-struct-wrong-type2.c @@ -0,0 +1,77 @@ +/* + + Test that the proper error is triggered when we build a ctor + for an struct type, but has the type wrong on a field. + + Like test-error-ctor-struct-wrong-type.c, but with implicit fields. + +*/ + +#include <stdlib.h> +#include <stdio.h> + +#include "libgccjit.h" +#include "harness.h" + +void +create_code (gcc_jit_context *ctxt, void *user_data) +{ + gcc_jit_type *int_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_INT); + gcc_jit_type *float_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_FLOAT); + + gcc_jit_field *b1 = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "a"); + gcc_jit_field *b2 = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "b"); + gcc_jit_field *b3 = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "c"); + gcc_jit_field *fields_b[] = {b1, b2, b3}; + + gcc_jit_type *struct_bar_type = + gcc_jit_struct_as_type ( + gcc_jit_context_new_struct_type (ctxt, + 0, + "bar", + 3, + fields_b)); + gcc_jit_rvalue *frv = gcc_jit_context_new_rvalue_from_double (ctxt, + float_type, + 12); + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_bar_type, + 1, + 0, + &frv); + + CHECK_VALUE (ctor, NULL); +} + +void +verify_code (gcc_jit_context *ctxt, gcc_jit_result *result) +{ + /* Ensure that the bad API usage prevents the API giving a bogus + result back. */ + CHECK_VALUE (result, NULL); + + /* Verify that the correct error message was emitted. */ + CHECK_STRING_VALUE (gcc_jit_context_get_first_error (ctxt), + "gcc_jit_context_new_struct_constructor: value and " + "field not " + "the same unqualified type, " + "at index 0 (struct bar.a: int)(value type: float)"); + CHECK_STRING_VALUE (gcc_jit_context_get_last_error (ctxt), + "gcc_jit_context_new_struct_constructor: value and " + "field not " + "the same unqualified type, " + "at index 0 (struct bar.a: int)(value type: float)"); +} diff --git a/gcc/testsuite/jit.dg/test-error-ctor-union-wrong-field-name.c b/gcc/testsuite/jit.dg/test-error-ctor-union-wrong-field-name.c new file mode 100644 index 0000000000000000000000000000000000000000..2bf8ee4023e0c94bce76a8ec8eb766bf06eb4d46 --- /dev/null +++ b/gcc/testsuite/jit.dg/test-error-ctor-union-wrong-field-name.c @@ -0,0 +1,76 @@ +/* + + Test that the proper error is triggered when we build a ctor + for an union type, but don't provide a correct field. + +*/ + +#include <stdlib.h> +#include <stdio.h> + +#include "libgccjit.h" +#include "harness.h" + +void +create_code (gcc_jit_context *ctxt, void *user_data) +{ + gcc_jit_type *int_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_INT); + gcc_jit_type *float_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_FLOAT); + gcc_jit_type *double_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_DOUBLE); + + gcc_jit_field *b1 = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "a"); + gcc_jit_field *b2 = gcc_jit_context_new_field (ctxt, + 0, + float_type, + "b"); + gcc_jit_field *b3 = gcc_jit_context_new_field (ctxt, + 0, + double_type, + "c"); + gcc_jit_field *fields_b[] = {b1, b2, b3}; + + gcc_jit_type *union_bar_type = + gcc_jit_context_new_union_type (ctxt, + 0, + "bar", + 3, + fields_b); + + gcc_jit_field *b33 = gcc_jit_context_new_field (ctxt, + 0, + double_type, + "c"); + + gcc_jit_rvalue *val = + gcc_jit_context_new_rvalue_from_double (ctxt, double_type, 1); + + gcc_jit_rvalue *ctor = gcc_jit_context_new_union_constructor + (ctxt, 0, + union_bar_type, + b33, + val); + + CHECK_VALUE (ctor, NULL); +} + +void +verify_code (gcc_jit_context *ctxt, gcc_jit_result *result) +{ + /* Ensure that the bad API usage prevents the API giving a bogus + result back. */ + CHECK_VALUE (result, NULL); + + /* Verify that the correct error message was emitted. */ + CHECK_STRING_VALUE (gcc_jit_context_get_first_error (ctxt), + "gcc_jit_context_new_union_constructor: field object (c)" + " was not used when creating the type union bar"); + CHECK_STRING_VALUE (gcc_jit_context_get_last_error (ctxt), + "gcc_jit_context_new_union_constructor: field object (c)" + " was not used when creating the type union bar"); +} diff --git a/gcc/testsuite/jit.dg/test-error-global-already-init.c b/gcc/testsuite/jit.dg/test-error-global-already-init.c new file mode 100644 index 0000000000000000000000000000000000000000..ecead87fc15ef9ef63fa01f1d77e0d74a46ce944 --- /dev/null +++ b/gcc/testsuite/jit.dg/test-error-global-already-init.c @@ -0,0 +1,46 @@ +/* + + Test that we can't set the initializer on a global twice. + +*/ + +#include <stdlib.h> +#include <stdio.h> + +#include "libgccjit.h" +#include "harness.h" + +void +create_code (gcc_jit_context *ctxt, void *user_data) +{ + gcc_jit_type *int_type = gcc_jit_context_get_type (ctxt, GCC_JIT_TYPE_INT); + + gcc_jit_lvalue *bar = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + int_type, + "global_lvalueinit_int_0"); + + gcc_jit_global_set_initializer_rvalue ( + bar, + gcc_jit_context_new_rvalue_from_int (ctxt, int_type, 1)); + gcc_jit_global_set_initializer_rvalue ( + bar, + gcc_jit_context_new_rvalue_from_int (ctxt, int_type, 1)); +} + +void +verify_code (gcc_jit_context *ctxt, gcc_jit_result *result) +{ + /* Ensure that the bad API usage prevents the API giving a bogus + result back. */ + CHECK_VALUE (result, NULL); + + /* Verify that the correct error message was emitted. */ + CHECK_STRING_VALUE (gcc_jit_context_get_first_error (ctxt), + "gcc_jit_global_set_initializer_rvalue: global variable " + "already initialized: global_lvalueinit_int_0"); + CHECK_STRING_VALUE (gcc_jit_context_get_last_error (ctxt), + "gcc_jit_global_set_initializer_rvalue: global variable " + "already initialized: global_lvalueinit_int_0"); +} diff --git a/gcc/testsuite/jit.dg/test-error-global-common-section.c b/gcc/testsuite/jit.dg/test-error-global-common-section.c new file mode 100644 index 0000000000000000000000000000000000000000..2f994545165a310de4749d7bf84167a4c9fad417 --- /dev/null +++ b/gcc/testsuite/jit.dg/test-error-global-common-section.c @@ -0,0 +1,54 @@ +/* + + Test that the proper error is triggered when we initialize + a global with a global that has no DECL_INITIAL (and is marked + DECL_COMMON(NODE) = 1). + +*/ + +#include <stdlib.h> +#include <stdio.h> + +#include "libgccjit.h" +#include "harness.h" + +void +create_code (gcc_jit_context *ctxt, void *user_data) +{ + gcc_jit_type *int_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_INT); + + /* const int foo; + int bar = foo; + */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + gcc_jit_type_get_const (int_type), + "global_const_int_0"); + gcc_jit_lvalue *bar = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + int_type, + "global_lvalueinit_int_0"); + gcc_jit_global_set_initializer_rvalue (bar, + gcc_jit_lvalue_as_rvalue (foo)); +} + +void +verify_code (gcc_jit_context *ctxt, gcc_jit_result *result) +{ + /* Ensure that the bad API usage prevents the API giving a bogus + result back. */ + CHECK_VALUE (result, NULL); + + /* Verify that the correct error message was emitted. */ + CHECK_STRING_VALUE (gcc_jit_context_get_first_error (ctxt), + "unable to convert initial value for the global " + "variable global_lvalueinit_int_0 to a compile-time" + " constant"); + CHECK_STRING_VALUE (gcc_jit_context_get_last_error (ctxt), + "unable to convert initial value for the global " + "variable global_lvalueinit_int_0 to a compile-time" + " constant"); +} diff --git a/gcc/testsuite/jit.dg/test-error-global-init-too-small-array.c b/gcc/testsuite/jit.dg/test-error-global-init-too-small-array.c new file mode 100644 index 0000000000000000000000000000000000000000..2a3db7af365915aa1d4bb59ba394208adc59cb65 --- /dev/null +++ b/gcc/testsuite/jit.dg/test-error-global-init-too-small-array.c @@ -0,0 +1,65 @@ +/* + + Test that the proper error is triggered when we initialize + a global array with a ctor with too many values. + + Using gcc_jit_global_set_initializer_rvalue() + +*/ + +#include <stdlib.h> +#include <stdio.h> + +#include "libgccjit.h" +#include "harness.h" + +void +create_code (gcc_jit_context *ctxt, void *user_data) +{ /* float foo[1] = {1,2}; */ + + gcc_jit_type *float_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_FLOAT); + gcc_jit_type *arr_type = gcc_jit_context_new_array_type (ctxt, + 0, + float_type, + 1); + gcc_jit_rvalue *rval_1 = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 1); + gcc_jit_rvalue *rval_2 = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 2); + + gcc_jit_rvalue *values[] = {rval_1, rval_2}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_array_constructor (ctxt, + 0, + arr_type, + 2, + values); + if (!ctor) + return; + + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + arr_type, + "global_floatarr_12"); + gcc_jit_global_set_initializer_rvalue (foo, ctor); +} + +void +verify_code (gcc_jit_context *ctxt, gcc_jit_result *result) +{ + /* Ensure that the bad API usage prevents the API giving a bogus + result back. */ + CHECK_VALUE (result, NULL); + + /* Verify that the correct error message was emitted. */ + CHECK_STRING_VALUE (gcc_jit_context_get_first_error (ctxt), + "gcc_jit_context_new_array_constructor: array " + "constructor has more values than the array type's " + "length (array type length: 1, constructor length: 2)"); + CHECK_STRING_VALUE (gcc_jit_context_get_last_error (ctxt), + "gcc_jit_context_new_array_constructor: array " + "constructor has more values than the array type's " + "length (array type length: 1, constructor length: 2)"); +} diff --git a/gcc/testsuite/jit.dg/test-error-global-lvalue-init.c b/gcc/testsuite/jit.dg/test-error-global-lvalue-init.c new file mode 100644 index 0000000000000000000000000000000000000000..65aa8a80b49fc40357d5ff397ccdb61fdde78151 --- /dev/null +++ b/gcc/testsuite/jit.dg/test-error-global-lvalue-init.c @@ -0,0 +1,60 @@ +/* + + Test that the proper error is triggered when we initialize + a global with another non-const global's rvalue. + + Using gcc_jit_global_set_initializer_rvalue() + +*/ + +#include <stdlib.h> +#include <stdio.h> + +#include "libgccjit.h" +#include "harness.h" + +void +create_code (gcc_jit_context *ctxt, void *user_data) +{ + gcc_jit_type *int_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_INT); + + gcc_jit_lvalue *foo; + { /* int bar; */ + foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + int_type, + "global_lvalueinit_int1"); + gcc_jit_rvalue *rval = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_global_set_initializer_rvalue (foo, + rval); + } + { /* int foo = bar; */ + + gcc_jit_lvalue *bar = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + int_type, + "global_lvalueinit_int2"); + gcc_jit_global_set_initializer_rvalue (bar, + gcc_jit_lvalue_as_rvalue (foo)); + } +} + +void +verify_code (gcc_jit_context *ctxt, gcc_jit_result *result) +{ + /* Ensure that the bad API usage prevents the API giving a bogus + result back. */ + CHECK_VALUE (result, NULL); + + /* Verify that the correct error message was emitted. */ + CHECK_STRING_VALUE (gcc_jit_context_get_first_error (ctxt), + "unable to convert initial value for the global variable" + " global_lvalueinit_int2 to a compile-time constant"); + CHECK_STRING_VALUE (gcc_jit_context_get_last_error (ctxt), + "unable to convert initial value for the global variable" + " global_lvalueinit_int2 to a compile-time constant"); +} diff --git a/gcc/testsuite/jit.dg/test-error-global-nonconst-init.c b/gcc/testsuite/jit.dg/test-error-global-nonconst-init.c new file mode 100644 index 0000000000000000000000000000000000000000..9dffe06eac32a09428d1de5e2ebe3bea5e164484 --- /dev/null +++ b/gcc/testsuite/jit.dg/test-error-global-nonconst-init.c @@ -0,0 +1,80 @@ +/* + + Test that the proper error is triggered when we initialize + a global with a function call. + + Using gcc_jit_global_set_initializer_rvalue() + +*/ + +#include <stdlib.h> +#include <stdio.h> + +#include "libgccjit.h" +#include "harness.h" + +void +create_code (gcc_jit_context *ctxt, void *user_data) +{ + gcc_jit_type *int_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_INT); + + gcc_jit_function *fn_int_3; + { /* int foo () { int local = 3; return local;} */ + fn_int_3 = + gcc_jit_context_new_function (ctxt, + 0, + GCC_JIT_FUNCTION_EXPORTED, + int_type, + "fn_int_3", + 0, + 0, + 0); + gcc_jit_block *block = gcc_jit_function_new_block (fn_int_3, "start"); + gcc_jit_lvalue *local = gcc_jit_function_new_local (fn_int_3, + 0, + int_type, + "local"); + gcc_jit_rvalue *rval = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + + gcc_jit_block_add_assignment (block, 0, local, rval); + + gcc_jit_block_end_with_return (block, + 0, + gcc_jit_lvalue_as_rvalue(local)); + + } + + { /* int bar = foo(); */ + gcc_jit_rvalue *rval = + gcc_jit_context_new_call (ctxt, + 0, + fn_int_3, + 0,0); + + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + int_type, + "global_nonconst_int"); + gcc_jit_global_set_initializer_rvalue (foo, + rval); + } +} + +void +verify_code (gcc_jit_context *ctxt, gcc_jit_result *result) +{ + /* Ensure that the bad API usage prevents the API giving a bogus + result back. */ + CHECK_VALUE (result, NULL); + + /* Verify that the correct error message was emitted. */ + CHECK_STRING_VALUE (gcc_jit_context_get_first_error (ctxt), + "unable to convert initial value for the global variable" + " global_nonconst_int to a compile-time constant"); + CHECK_STRING_VALUE (gcc_jit_context_get_last_error (ctxt), + "unable to convert initial value for the global variable" + " global_nonconst_int to a compile-time constant"); +} diff --git a/gcc/testsuite/jit.dg/test-global-init-rvalue.c b/gcc/testsuite/jit.dg/test-global-init-rvalue.c new file mode 100644 index 0000000000000000000000000000000000000000..4866462ff4ab01fde8e4d0d955df7bfdfd70b927 --- /dev/null +++ b/gcc/testsuite/jit.dg/test-global-init-rvalue.c @@ -0,0 +1,1643 @@ +/* This testcase checks that gcc_jit_global_set_initializer_rvalue() works + with rvalues, especially with gcc_jit_context_new_*_constructor() for + struct, unions and arrays. */ + +#include <stdio.h> +#include <string.h> + +#include "libgccjit.h" +#include "harness.h" + +void +create_code (gcc_jit_context *ctxt, void *user_data) +{ + gcc_jit_type *int_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_INT); + gcc_jit_type *short_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_SHORT); + gcc_jit_type *pint_type = gcc_jit_type_get_pointer (int_type); + gcc_jit_type *double_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_DOUBLE); + gcc_jit_type *float_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_FLOAT); + gcc_jit_type *bool_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_BOOL); + gcc_jit_type *char_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_CHAR); + gcc_jit_type *cpchar_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_CONST_CHAR_PTR); + gcc_jit_type *size_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_SIZE_T); + + /* Make a struct: struct fi { float f; int i;} */ + gcc_jit_field *fi_f = gcc_jit_context_new_field (ctxt, + 0, + float_type, + "f"); + gcc_jit_field *fi_i = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "i"); + gcc_jit_field *fields[] = {fi_f, fi_i}; + + gcc_jit_type *struct_fi_type = + gcc_jit_struct_as_type ( + gcc_jit_context_new_struct_type (ctxt, + 0, + "fi", + 2, + fields)); + + /* Make a struct: + + struct bar { + int ii; + struct fi fi; + float ff; + } + */ + gcc_jit_field *bar_ff = gcc_jit_context_new_field (ctxt, + 0, + float_type, + "ff"); + gcc_jit_field *bar_ii = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "ii"); + gcc_jit_field *bar_fi = gcc_jit_context_new_field (ctxt, + 0, + struct_fi_type, + "fi"); + gcc_jit_field *fields2[] = {bar_ff, bar_fi, bar_ii}; + + gcc_jit_type *struct_bar_type = + gcc_jit_struct_as_type ( + gcc_jit_context_new_struct_type (ctxt, + 0, + "bar", + 3, + fields2)); + + /* Make an union: + + union ubar { + float ff; + int ii; + }; + */ + gcc_jit_field *ubar_ff = gcc_jit_context_new_field (ctxt, + 0, + float_type, + "ff"); + gcc_jit_field *ubar_ii = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "ii"); + gcc_jit_field *fields3[] = {ubar_ff, ubar_ii}; + + gcc_jit_type *ubar = gcc_jit_context_new_union_type (ctxt, + 0, + "ubar", + 2, + fields3); + + { /* struct bar bar = {.ff=1, .fi={.f=2, .i=3}, .ii=4}; + I.e. nested ctors and with fields specified + */ + gcc_jit_lvalue *bar = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + struct_bar_type, + "global_struct_bar_1234_1"); + + gcc_jit_rvalue *fval = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 2); + gcc_jit_rvalue *ival = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + + gcc_jit_rvalue *vals[] = { fval, ival}; + gcc_jit_field *fields[] = {fi_f, fi_i}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_fi_type, + 2, + fields, + vals); + + ival = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 4); + fval = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 1); + + gcc_jit_rvalue *vals2[] = {fval, ctor, ival}; + gcc_jit_field *fields2[] = {bar_ff, bar_fi, bar_ii}; + + gcc_jit_rvalue *ctor_bar = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_bar_type, + 3, + fields2, + vals2); + + gcc_jit_global_set_initializer_rvalue (bar, ctor_bar); + } + { /* struct bar bar = {1, {2, 3}, 4}; + I.e. nested ctors and fields implicit in definition order (fields=NULL) + */ + gcc_jit_lvalue *bar = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + struct_bar_type, + "global_struct_bar_1234_2"); + + gcc_jit_rvalue *fval = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 2); + gcc_jit_rvalue *ival = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + + gcc_jit_rvalue *vals[] = { fval, ival}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_fi_type, + 2, + 0, + vals); + + ival = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 4); + fval = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 1); + + gcc_jit_rvalue *vals2[] = {fval, ctor, ival}; + + gcc_jit_rvalue *ctor_bar = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_bar_type, + 3, + 0, + vals2); + + gcc_jit_global_set_initializer_rvalue (bar, ctor_bar); + } + { /* struct fi foo = {.f=2, .i=3}; */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + struct_fi_type, + "global_struct_fi_23_1"); + + gcc_jit_rvalue *fval = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 2); + gcc_jit_rvalue *ival = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + + gcc_jit_rvalue *vals[] = { fval, ival}; + gcc_jit_field *fields[] = {fi_f, fi_i}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_fi_type, + 2, + fields, + vals); + + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* struct fi foo = {2, 3}; */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + struct_fi_type, + "global_struct_fi_23_2"); + + gcc_jit_rvalue *fval = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 2); + gcc_jit_rvalue *ival = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + + gcc_jit_rvalue *vals[] = { fval, ival}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_fi_type, + 2, + 0, + vals); + + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* struct fi foo = {.i=0, .f=0}; (null init) */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + struct_fi_type, + "global_struct_fi_00_1"); + + gcc_jit_rvalue *vals[] = { 0, 0}; + gcc_jit_field *fields[] = {fi_f, fi_i}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_fi_type, + 2, + fields, + vals); + + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* struct fi foo = {0, 0}; (null fields, null elements in values) */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + struct_fi_type, + "global_struct_fi_00_2"); + + gcc_jit_rvalue *vals[] = { 0, 0}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_fi_type, + 2, + 0, + vals); + + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* struct fi foo = {.i = 0} (null init); + + Null init values. */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + struct_fi_type, + "global_struct_fi_0_1"); + + gcc_jit_rvalue *vals[] = {0}; + gcc_jit_field *fields[] = {fi_i}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_fi_type, + 1, + fields, + vals); + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* struct fi foo = {0}; + + Null init values. */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + struct_fi_type, + "global_struct_fi_0_2"); + + gcc_jit_rvalue *vals[] = {0}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_fi_type, + 1, + 0, + vals); + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* struct fi foo = {}; (null init) + + Null fields and values. */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + struct_fi_type, + "global_struct_fi_6"); + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_fi_type, + 0, + 0, + 0); + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* struct fi foo = {2 * 2, 3}; */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + struct_fi_type, + "global_struct_fi_3"); + + gcc_jit_rvalue *fval = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 2); + gcc_jit_rvalue *fval2 = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 2); + gcc_jit_rvalue *ival = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_rvalue *rval_mul = gcc_jit_context_new_binary_op (ctxt, 0, + GCC_JIT_BINARY_OP_MULT, + float_type, + fval, + fval2); + + gcc_jit_rvalue *vals[] = { rval_mul, ival}; + gcc_jit_field *fields[] = {fi_f, fi_i}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_fi_type, + 2, + fields, + vals); + + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* union ubar foo = {.ff = 3}; */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + ubar, + "global_union_ufoo_ff3"); + + gcc_jit_rvalue *fval = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 3); + + gcc_jit_rvalue *ctor = gcc_jit_context_new_union_constructor ( + ctxt, + 0, + ubar, + ubar_ff, + fval); + + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* union ubar foo = {.ii = 2}; */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + ubar, + "global_union_ufoo_ii2"); + + gcc_jit_rvalue *ival = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 2); + + gcc_jit_rvalue *ctor = gcc_jit_context_new_union_constructor ( + ctxt, + 0, + ubar, + ubar_ii, + ival); + + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* union ubar foo = {1.1f}; should init first field */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + ubar, + "global_union_ufoo_ff1c1"); + + gcc_jit_rvalue *fval = gcc_jit_context_new_rvalue_from_double ( + ctxt, float_type, 1.1); + + gcc_jit_rvalue *ctor = gcc_jit_context_new_union_constructor ( + ctxt, + 0, + ubar, + 0, + fval); + + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* union ubar foo = (union ubar){}; */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + ubar, + "global_union_ufoo_0"); + + gcc_jit_rvalue *ctor = gcc_jit_context_new_union_constructor ( + ctxt, + 0, + ubar, + 0, + 0); + + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* int foo = 3; */ + gcc_jit_rvalue *rval = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + int_type, + "global_int1_3"); + gcc_jit_global_set_initializer_rvalue (foo, + rval); + } + { /* const volatile int foo = 3; */ + gcc_jit_rvalue *rval = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + gcc_jit_type_get_const (gcc_jit_type_get_volatile (int_type)), + "global_cvint1_3"); + gcc_jit_global_set_initializer_rvalue (foo, + rval); + } + { /* Try the above, but with opposite order of global and literal calls */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + int_type, + "global_int2_3"); + gcc_jit_rvalue *rval = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_global_set_initializer_rvalue (foo, + rval); + } + { /* int foo = 3 * (3 + 3) */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + int_type, + "global_int3_18"); + gcc_jit_rvalue *rval3_0 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_rvalue *rval3_1 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_rvalue *rval3_2 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_rvalue *rval_plus = gcc_jit_context_new_binary_op (ctxt, 0, + GCC_JIT_BINARY_OP_PLUS, + int_type, + rval3_0, + rval3_1); + gcc_jit_rvalue *rval_mul = gcc_jit_context_new_binary_op (ctxt, 0, + GCC_JIT_BINARY_OP_MULT, + int_type, + rval_plus, + rval3_2); + + gcc_jit_global_set_initializer_rvalue (foo, + rval_mul); + } + { /* int foo = ~(-(((((2 | 8) & 15) ^ 0) << 3 >> 2 - 1) / 2)); */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + int_type, + "global_int_alotofoperators"); + gcc_jit_rvalue *rval_0 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 2); + gcc_jit_rvalue *rval_1 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 8); + gcc_jit_rvalue *rval_2 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 15); + gcc_jit_rvalue *rval_3 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 0); + gcc_jit_rvalue *rval_4 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_rvalue *rval_5 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 2); + gcc_jit_rvalue *rval_6 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 1); + gcc_jit_rvalue *rval_7 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 2); + + gcc_jit_rvalue *rval_or = gcc_jit_context_new_binary_op (ctxt, 0, + GCC_JIT_BINARY_OP_BITWISE_OR, + int_type, + rval_0, + rval_1); + gcc_jit_rvalue *rval_and = gcc_jit_context_new_binary_op (ctxt, 0, + GCC_JIT_BINARY_OP_BITWISE_AND, + int_type, + rval_or, + rval_2); + gcc_jit_rvalue *rval_xor = gcc_jit_context_new_binary_op (ctxt, 0, + GCC_JIT_BINARY_OP_BITWISE_XOR, + int_type, + rval_and, + rval_3); + gcc_jit_rvalue *rval_lsh = gcc_jit_context_new_binary_op (ctxt, 0, + GCC_JIT_BINARY_OP_LSHIFT, + int_type, + rval_xor, + rval_4); + gcc_jit_rvalue *rval_rsh = gcc_jit_context_new_binary_op (ctxt, 0, + GCC_JIT_BINARY_OP_RSHIFT, + int_type, + rval_lsh, + rval_5); + gcc_jit_rvalue *rval_min = gcc_jit_context_new_binary_op (ctxt, 0, + GCC_JIT_BINARY_OP_MINUS, + int_type, + rval_rsh, + rval_6); + gcc_jit_rvalue *rval_div = gcc_jit_context_new_binary_op (ctxt, 0, + GCC_JIT_BINARY_OP_DIVIDE, + int_type, + rval_min, + rval_7); + gcc_jit_rvalue *rval_umin = gcc_jit_context_new_unary_op (ctxt, 0, + GCC_JIT_UNARY_OP_MINUS, + int_type, + rval_div); + gcc_jit_rvalue *rval_neg = gcc_jit_context_new_unary_op (ctxt, 0, + GCC_JIT_UNARY_OP_BITWISE_NEGATE, + int_type, + rval_umin); + + gcc_jit_global_set_initializer_rvalue (foo, + rval_neg); + } + { /* int foo = 3; int *pfoo = &foo; */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + int_type, + "global_int4_3"); + gcc_jit_rvalue *rval = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_global_set_initializer_rvalue (foo, + rval); + + gcc_jit_lvalue *pfoo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + pint_type, + "global_pint5"); + gcc_jit_global_set_initializer_rvalue (pfoo, + gcc_jit_lvalue_get_address (foo, 0)); + } + { /* static int foo; int *pfoo = &foo; */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_INTERNAL, + int_type, + "global_int5_3"); + + gcc_jit_lvalue *pfoo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + pint_type, + "global_pint6"); + gcc_jit_global_set_initializer_rvalue (pfoo, + gcc_jit_lvalue_get_address (foo, 0)); + + gcc_jit_function *fn = + gcc_jit_context_new_function (ctxt, + 0, + GCC_JIT_FUNCTION_EXPORTED, + gcc_jit_type_get_pointer(int_type), + "fn_pint_0", + 0, + 0, + 0); + + gcc_jit_block *block = gcc_jit_function_new_block (fn, "start"); + + gcc_jit_block_end_with_return (block, + 0, + gcc_jit_lvalue_get_address (foo, 0)); + } + { /* int foo = 3; int *pfoo = &foo + 1; */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + int_type, + "global_int6_3"); + gcc_jit_rvalue *rval = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_global_set_initializer_rvalue (foo, + rval); + + gcc_jit_lvalue *pfoo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + pint_type, + "global_pint7"); + gcc_jit_global_set_initializer_rvalue (pfoo, + gcc_jit_lvalue_get_address ( + gcc_jit_context_new_array_access( + ctxt, + 0, + gcc_jit_lvalue_get_address(foo, 0), + gcc_jit_context_one(ctxt, int_type)), + 0)); + } + { /* double foo = 3; */ + gcc_jit_lvalue *double1 = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + double_type, + "global_double1_3"); + gcc_jit_rvalue *rval = gcc_jit_context_new_rvalue_from_int ( + ctxt, double_type, 3); + gcc_jit_global_set_initializer_rvalue (double1, + rval); + } + { /* double foo = 3 * 3 + 3 */ + gcc_jit_lvalue *double1 = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + double_type, + "global_double2_12"); + gcc_jit_rvalue *rval = gcc_jit_context_new_rvalue_from_int ( + ctxt, double_type, 3); + gcc_jit_rvalue *rval_mul = gcc_jit_context_new_binary_op (ctxt, 0, + GCC_JIT_BINARY_OP_MULT, + double_type, + rval, + rval); + gcc_jit_rvalue *rval_plus = gcc_jit_context_new_binary_op (ctxt, 0, + GCC_JIT_BINARY_OP_PLUS, + double_type, + rval_mul, + rval); + gcc_jit_global_set_initializer_rvalue (double1, + rval_plus); + } + { /* bool foo = 3 + 3 <= 6; */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + bool_type, + "global_bool1_1"); + gcc_jit_rvalue *rval3_0 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_rvalue *rval3_1 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_rvalue *rval6 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 6); + gcc_jit_rvalue *rval_plus = gcc_jit_context_new_binary_op (ctxt, + 0, + GCC_JIT_BINARY_OP_PLUS, + int_type, + rval3_0, + rval3_1); + gcc_jit_rvalue *rval_le = gcc_jit_context_new_comparison (ctxt, + 0, + GCC_JIT_COMPARISON_LE, + rval_plus, + rval6); + + gcc_jit_global_set_initializer_rvalue (foo, + rval_le); + } + gcc_jit_lvalue *global_intarr_1234; + { /* int foo[] = {1,2,3,4}; */ + + gcc_jit_type *arr_type = gcc_jit_context_new_array_type (ctxt, + 0, + int_type, + 4); + gcc_jit_rvalue *rval_1 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 1); + gcc_jit_rvalue *rval_2 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 2); + gcc_jit_rvalue *rval_3 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_rvalue *rval_4 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 4); + + gcc_jit_rvalue *values[] = {rval_1, rval_2, rval_3, rval_4}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_array_constructor (ctxt, + 0, + arr_type, + 4, + values); + global_intarr_1234 = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + arr_type, + "global_intarr_1234"); + gcc_jit_global_set_initializer_rvalue (global_intarr_1234, ctor); + } + { /* float foo[4] = {1,2}; */ + + gcc_jit_type *arr_type = gcc_jit_context_new_array_type (ctxt, + 0, + float_type, + 4); + gcc_jit_rvalue *rval_1 = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 1); + gcc_jit_rvalue *rval_2 = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 2); + + gcc_jit_rvalue *values[] = {rval_1, rval_2}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_array_constructor (ctxt, + 0, + arr_type, + 2, + values); + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + arr_type, + "global_floatarr_12"); + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* float foo[4] = {1,2}; + With different array objects of same size and type. */ + + gcc_jit_type *arr_type = gcc_jit_context_new_array_type (ctxt, + 0, + float_type, + 4); + gcc_jit_type *arr_type1 = gcc_jit_context_new_array_type (ctxt, + 0, + float_type, + 4); + gcc_jit_rvalue *rval_1 = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 1); + gcc_jit_rvalue *rval_2 = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 2); + + gcc_jit_rvalue *values[] = {rval_1, rval_2}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_array_constructor (ctxt, + 0, + arr_type1, + 2, + values); + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + arr_type, + "global_floatarr_12_2"); + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* float foo[4] = {1,2,0}; (null init) */ + + gcc_jit_type *arr_type = gcc_jit_context_new_array_type (ctxt, + 0, + float_type, + 4); + gcc_jit_rvalue *rval_1 = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 1); + gcc_jit_rvalue *rval_2 = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 2); + + gcc_jit_rvalue *values[] = {rval_1, rval_2, 0}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_array_constructor (ctxt, + 0, + arr_type, + 2, + values); + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + arr_type, + "global_floatarr_120"); + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* float foo[4] = {}; (null init) */ + + gcc_jit_type *arr_type = gcc_jit_context_new_array_type (ctxt, + 0, + float_type, + 4); + + gcc_jit_rvalue *ctor = gcc_jit_context_new_array_constructor (ctxt, + 0, + arr_type, + 0, + 0); + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + arr_type, + "global_floatarr_0000"); + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* float foo[4] = {NULL , NULL, 3, NULL, 5, 6}; (null init) */ + + gcc_jit_type *arr_type = gcc_jit_context_new_array_type (ctxt, + 0, + float_type, + 8); + gcc_jit_rvalue *rval3 = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 3); + gcc_jit_rvalue *rval5 = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 5); + gcc_jit_rvalue *rval6 = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 6); + + gcc_jit_rvalue *values[] = {0, 0, rval3, 0, rval5, rval6, 0 }; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_array_constructor (ctxt, + 0, + arr_type, + 7, + values); + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + arr_type, + "global_floatarr_00305600"); + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* int *foo[4] = {0, &global_intarr_1234[1], 0}; */ + + gcc_jit_type *arr_type = gcc_jit_context_new_array_type (ctxt, + 0, + pint_type, + 4); + gcc_jit_rvalue *rval_1 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 1); + gcc_jit_lvalue *arr_access = gcc_jit_context_new_array_access ( + ctxt, + 0, + gcc_jit_lvalue_as_rvalue (global_intarr_1234), + rval_1); + gcc_jit_rvalue *rval_2 = gcc_jit_lvalue_get_address (arr_access, 0); + gcc_jit_rvalue *rval_3 = gcc_jit_context_null (ctxt, pint_type); + + gcc_jit_rvalue *values[] = {0, rval_2, rval_3}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_array_constructor (ctxt, + 0, + arr_type, + 2, + values); + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + arr_type, + "global_pintarr_x2xx"); + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* char foo[4] = {'q','w','e',0}; */ + + gcc_jit_type *arr_type = gcc_jit_context_new_array_type (ctxt, + 0, + char_type, + 4); + + + gcc_jit_rvalue *rvals[] = { + gcc_jit_context_new_rvalue_from_int ( ctxt, char_type, 'q'), + gcc_jit_context_new_rvalue_from_int ( ctxt, char_type, 'w'), + gcc_jit_context_new_rvalue_from_int ( ctxt, char_type, 'e'), + gcc_jit_context_new_rvalue_from_int ( ctxt, char_type, 0) + }; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_array_constructor (ctxt, + 0, + arr_type, + 4, + rvals); + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + arr_type, + "global_chararr_qwe"); + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* int foo[2][2] = {{1,2},{3,4}}; */ + + gcc_jit_type *row_type = gcc_jit_context_new_array_type (ctxt, + 0, + int_type, + 2); + + gcc_jit_type *arr_type = gcc_jit_context_new_array_type (ctxt, + 0, + row_type, + 2); + gcc_jit_rvalue *rvals_row0[] = { + gcc_jit_context_new_rvalue_from_int ( ctxt, int_type, 1), + gcc_jit_context_new_rvalue_from_int ( ctxt, int_type, 2) + }; + gcc_jit_rvalue *rvals_row1[] = { + gcc_jit_context_new_rvalue_from_int ( ctxt, int_type, 3), + gcc_jit_context_new_rvalue_from_int ( ctxt, int_type, 4) + }; + + gcc_jit_rvalue *ctor_row0 = + gcc_jit_context_new_array_constructor (ctxt, + 0, + row_type, + 2, + rvals_row0); + gcc_jit_rvalue *ctor_row1 = + gcc_jit_context_new_array_constructor (ctxt, + 0, + row_type, + 2, + rvals_row1); + gcc_jit_rvalue *ctors_row[] = {ctor_row0, ctor_row1}; + + gcc_jit_rvalue *ctor_arr = + gcc_jit_context_new_array_constructor (ctxt, + 0, + arr_type, + 2, + ctors_row); + + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + arr_type, + "global_int2x2matrix_1234"); + + gcc_jit_global_set_initializer_rvalue (foo, ctor_arr); + } + { /* const char *foo[4] = {"qwe", "asd"}; */ + + gcc_jit_type *arr_type = gcc_jit_context_new_array_type (ctxt, + 0, + cpchar_type, + 4); + + + gcc_jit_rvalue *rvals[] = { + gcc_jit_context_new_string_literal (ctxt, "qwe"), + gcc_jit_context_new_string_literal (ctxt, "asd") + }; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_array_constructor (ctxt, + 0, + arr_type, + 2, + rvals); + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + arr_type, + "global_cpchararr_qwe_asd"); + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + { /* const int foo = 3; + int bar = foo; + */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + gcc_jit_type_get_const (int_type), + "global_const_int_3"); + gcc_jit_rvalue *rval3 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_global_set_initializer_rvalue (foo, + rval3); + gcc_jit_lvalue *bar = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + int_type, + "global_lvalueinit_int_3"); + gcc_jit_global_set_initializer_rvalue (bar, + gcc_jit_lvalue_as_rvalue (foo)); + } + { /* int foo = 3 * 2; + int arr[] = {1,2,3,4}; + int *bar = &arr[2] + 1 + + Example in the docs. + */ + + gcc_jit_type *arr_type = gcc_jit_context_new_array_type (ctxt, + 0, + int_type, + 4); + gcc_jit_rvalue *rval_1 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 1); + gcc_jit_rvalue *rval_2 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 2); + gcc_jit_rvalue *rval_3 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_rvalue *rval_4 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 4); + + gcc_jit_rvalue *values[] = {rval_1, rval_2, rval_3, rval_4}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_array_constructor (ctxt, + 0, + arr_type, + 4, + values); + gcc_jit_lvalue *global_intarr_1234 = + gcc_jit_context_new_global (ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + arr_type, + "global_intarr_1234_2"); + + gcc_jit_global_set_initializer_rvalue (global_intarr_1234, ctor); + + gcc_jit_lvalue *bar = + gcc_jit_context_new_global (ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + int_type, + "global_int_6"); + gcc_jit_global_set_initializer_rvalue + (bar, + gcc_jit_context_new_binary_op + (ctxt, 0, GCC_JIT_BINARY_OP_MULT, + int_type, + gcc_jit_context_new_rvalue_from_int (ctxt, int_type, 3), + gcc_jit_context_new_rvalue_from_int (ctxt, int_type, 2))); + + gcc_jit_lvalue *pfoo = + gcc_jit_context_new_global (ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + gcc_jit_type_get_pointer (int_type), + "global_pint_4"); + /* int *bar = &arr[2] + 1; + + In practice we could just do &foo[3] + but just prove folding this works. */ + gcc_jit_global_set_initializer_rvalue ( + pfoo, + gcc_jit_lvalue_get_address ( + gcc_jit_context_new_array_access ( + ctxt, 0, + gcc_jit_lvalue_get_address ( + gcc_jit_context_new_array_access ( + ctxt, 0, + gcc_jit_lvalue_as_rvalue (global_intarr_1234), + gcc_jit_context_new_rvalue_from_int (ctxt, int_type, 2)), + 0), + gcc_jit_context_new_rvalue_from_int (ctxt, int_type, 1)), + 0)); + } + { /* static int bar = 11; + int foo () { return bar; } */ + + gcc_jit_lvalue *bar = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_INTERNAL, + int_type, + "global_static_int_11"); + gcc_jit_rvalue *rval1 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 11); + gcc_jit_global_set_initializer_rvalue (bar, + rval1); + + gcc_jit_function *fn11 = + gcc_jit_context_new_function (ctxt, + 0, + GCC_JIT_FUNCTION_EXPORTED, + int_type, + "fn_int_11", + 0, + 0, + 0); + gcc_jit_block *block = gcc_jit_function_new_block (fn11, "start"); + + gcc_jit_block_end_with_return (block, + 0, + gcc_jit_lvalue_as_rvalue(bar)); + } + { /* static const int cbar = 11; + int cfoo () { return cbar; } */ + + gcc_jit_lvalue *bar = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_INTERNAL, + gcc_jit_type_get_const (int_type), + "global_static_cint_11"); + gcc_jit_rvalue *rval1 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 11); + gcc_jit_global_set_initializer_rvalue (bar, + rval1); + + gcc_jit_function *fn11 = + gcc_jit_context_new_function (ctxt, + 0, + GCC_JIT_FUNCTION_EXPORTED, + int_type, + "fn_cint_11", + 0, + 0, + 0); + gcc_jit_block *block = gcc_jit_function_new_block (fn11, "start"); + + gcc_jit_block_end_with_return (block, + 0, + gcc_jit_lvalue_as_rvalue(bar)); + } + { /* static const int cbar = 12; + const int* cfoo () { return &cbar; } */ + + gcc_jit_lvalue *bar = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_INTERNAL, + gcc_jit_type_get_const (int_type), + "global_static_cint_12"); + gcc_jit_rvalue *rval1 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 12); + gcc_jit_global_set_initializer_rvalue (bar, + rval1); + + gcc_jit_function *fn11 = + gcc_jit_context_new_function (ctxt, + 0, + GCC_JIT_FUNCTION_EXPORTED, + gcc_jit_type_get_pointer(int_type), + "fn_cint_12", + 0, + 0, + 0); + + gcc_jit_block *block = gcc_jit_function_new_block (fn11, "start"); + + gcc_jit_block_end_with_return (block, + 0, + gcc_jit_lvalue_get_address (bar, 0)); + } + { /* const int foo = 3; + short bar = (short)foo; + + Assure casts fold + */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + gcc_jit_type_get_const (int_type), + "global_const_int_4"); + gcc_jit_rvalue *rval3 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_global_set_initializer_rvalue (foo, + rval3); + gcc_jit_lvalue *bar = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + short_type, + "global_lvalueinit_short_3"); + gcc_jit_global_set_initializer_rvalue ( + bar, + gcc_jit_context_new_cast( ctxt, 0, + gcc_jit_lvalue_as_rvalue (foo), + short_type)); + } + { /* const int foo = 3; + const int const *bar = &foo; */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + gcc_jit_type_get_const (int_type), + "global_const_int_6"); + gcc_jit_rvalue *rval3 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + gcc_jit_global_set_initializer_rvalue (foo, + rval3); + gcc_jit_lvalue *bar = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + gcc_jit_type_get_const ( + gcc_jit_type_get_pointer ( + gcc_jit_type_get_const ( + int_type))), + "global_lvalueinit_cpcint_3"); + gcc_jit_global_set_initializer_rvalue ( + bar, + gcc_jit_lvalue_get_address (foo, 0)); + } + { /* const int __attribute__ ((aligned (64))) foo = 3; + int bar = foo; + + Assure alignement does not make the constant "miss" + or something strange. + */ + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + gcc_jit_type_get_const (gcc_jit_type_get_aligned (int_type, 64)), + "global_const_int_7"); + gcc_jit_rvalue *rval = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 4); + gcc_jit_global_set_initializer_rvalue (foo, + rval); + gcc_jit_lvalue *bar = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + int_type, + "global_lvalueinit_int_4"); + gcc_jit_global_set_initializer_rvalue (bar, + gcc_jit_lvalue_as_rvalue (foo)); + } + { + /* union upintsize { size_t s; int *p } u = {.s = 0xEEEFBEEF}; */ + gcc_jit_field *f1 = gcc_jit_context_new_field (ctxt, + 0, + size_type, + "s"); + gcc_jit_field *f2 = gcc_jit_context_new_field (ctxt, + 0, + pint_type, + "p"); + gcc_jit_field *fields1[] = {f1, f2}; + + gcc_jit_type *ubar = gcc_jit_context_new_union_type (ctxt, + 0, + "upintsize", + 2, + fields1); + gcc_jit_lvalue *foo = gcc_jit_context_new_global ( + ctxt, NULL, + GCC_JIT_GLOBAL_EXPORTED, + gcc_jit_type_get_const (ubar), + "global_const_upintsize_1"); + + gcc_jit_rvalue *val = gcc_jit_context_new_rvalue_from_long ( + ctxt, size_type, 0xEEEFBEEF); + + gcc_jit_rvalue *ctor = + gcc_jit_context_new_union_constructor (ctxt, + 0, + ubar, + f1, + val); + + gcc_jit_global_set_initializer_rvalue (foo, ctor); + } + {/* + struct B; + struct A { B* b; }; + struct B { A* a; }; + extern struct B b; + struct A a = {.b = b}; + struct B b = {.a = a}; + + See that opaque structs and circular pointers works. + */ + + gcc_jit_struct *struct_B = + gcc_jit_context_new_opaque_struct(ctxt, + 0, "B"); + + gcc_jit_field *fields_A[] = + { + gcc_jit_context_new_field (ctxt, 0, + gcc_jit_type_get_pointer ( + gcc_jit_struct_as_type (struct_B)), + "b") + }; + + gcc_jit_struct *struct_A = + gcc_jit_context_new_struct_type(ctxt, 0, "A", 1, fields_A); + + gcc_jit_field *fields_B[] = + { + gcc_jit_context_new_field (ctxt, 0, + gcc_jit_type_get_pointer ( + gcc_jit_struct_as_type (struct_A)), + "a") + }; + + gcc_jit_struct_set_fields (struct_B, 0, 1, fields_B); + + gcc_jit_lvalue *a = + gcc_jit_context_new_global (ctxt, 0, GCC_JIT_GLOBAL_EXPORTED, + gcc_jit_struct_as_type (struct_A), + "a_glb"); + gcc_jit_lvalue *b = + gcc_jit_context_new_global (ctxt, 0, GCC_JIT_GLOBAL_EXPORTED, + gcc_jit_struct_as_type (struct_B), + "b_glb"); + gcc_jit_rvalue *b_addr = gcc_jit_lvalue_get_address( b, 0); + gcc_jit_rvalue *a_ctor = + gcc_jit_context_new_struct_constructor (ctxt, 0, + gcc_jit_struct_as_type (struct_A), + 1, 0, + &b_addr); + gcc_jit_rvalue *a_addr = gcc_jit_lvalue_get_address( a, 0); + gcc_jit_rvalue *b_ctor = + gcc_jit_context_new_struct_constructor (ctxt, 0, + gcc_jit_struct_as_type (struct_B), + 1, 0, + &a_addr); + + gcc_jit_global_set_initializer_rvalue(a, a_ctor); + gcc_jit_global_set_initializer_rvalue(b, b_ctor); + } +} + +struct fi { + float f; + int i; +}; + +struct bar1 { + float ff; + struct fi fi; + int ii; +}; + +union ubar1 { + float ff; + int ii; +}; + +union upintsize { + size_t s; + int *p; +}; + +struct B_glb; +struct A_glb { + struct B_glb *b; +}; +struct B_glb { + struct A_glb *a; +}; + +int test_aligned64_works_in_linker_1 __attribute__ ((aligned (64))) = 0; +int test_aligned64_works_in_linker_2 __attribute__ ((aligned (64))) = 0; + +void +verify_code (gcc_jit_context *ctxt, gcc_jit_result *result) +{ + CHECK_NON_NULL (result); + + { + struct bar1 *bar = + gcc_jit_result_get_global (result, "global_struct_bar_1234_1"); + + CHECK_VALUE (bar->ff, 1); + CHECK_VALUE (bar->fi.f, 2); + CHECK_VALUE (bar->fi.i, 3); + CHECK_VALUE (bar->ii, 4); + } + { + struct bar1 *bar = + gcc_jit_result_get_global (result, "global_struct_bar_1234_2"); + + CHECK_VALUE (bar->ff, 1); + CHECK_VALUE (bar->fi.f, 2); + CHECK_VALUE (bar->fi.i, 3); + CHECK_VALUE (bar->ii, 4); + } + { + struct fi *fi = gcc_jit_result_get_global (result, "global_struct_fi_23_1"); + + CHECK_VALUE (fi->f, 2); + CHECK_VALUE (fi->i, 3); + } + { + struct fi *fi = gcc_jit_result_get_global (result, "global_struct_fi_23_2"); + + CHECK_VALUE (fi->f, 2); + CHECK_VALUE (fi->i, 3); + } + { + struct fi *fi = gcc_jit_result_get_global (result, "global_struct_fi_00_1"); + + CHECK_VALUE (fi->f, 0); + CHECK_VALUE (fi->i, 0); + } + { + struct fi *fi = gcc_jit_result_get_global (result, "global_struct_fi_00_2"); + + CHECK_VALUE (fi->f, 0); + CHECK_VALUE (fi->i, 0); + } + { + struct fi *fi = gcc_jit_result_get_global (result, "global_struct_fi_0_1"); + + CHECK_VALUE (fi->f, 0); + CHECK_VALUE (fi->i, 0); + } + { + struct fi *fi = gcc_jit_result_get_global (result, "global_struct_fi_0_2"); + + CHECK_VALUE (fi->f, 0); + CHECK_VALUE (fi->i, 0); + } + { + struct fi *fi = gcc_jit_result_get_global (result, "global_struct_fi_6"); + + CHECK_VALUE (fi->f, 0); + CHECK_VALUE (fi->i, 0); + } + { + struct fi *fi = gcc_jit_result_get_global (result, "global_struct_fi_3"); + + CHECK_VALUE (fi->f, 2 * 2); + CHECK_VALUE (fi->i, 3); + } + { + union ubar1 *foo = gcc_jit_result_get_global (result, + "global_union_ufoo_ff3"); + CHECK_VALUE (foo->ff, 3); + } + { + union ubar1 *foo = gcc_jit_result_get_global (result, + "global_union_ufoo_ii2"); + CHECK_VALUE (foo->ii, 2); + } + { + union ubar1 *foo = gcc_jit_result_get_global (result, + "global_union_ufoo_ff1c1"); + CHECK_VALUE (foo->ff, 1.1f); + } + { + union ubar1 *foo = gcc_jit_result_get_global (result, + "global_union_ufoo_0"); + CHECK_VALUE (foo->ii, 0); + } + { + int *foo = gcc_jit_result_get_global (result, "global_int1_3"); + + CHECK_VALUE (*foo, 3); + } + { + int *foo = gcc_jit_result_get_global (result, "global_cvint1_3"); + + CHECK_VALUE (*foo, 3); + } + { + int *foo = gcc_jit_result_get_global (result, "global_int2_3"); + + CHECK_VALUE (*foo, 3); + } + { + int *foo = gcc_jit_result_get_global (result, "global_int3_18"); + + CHECK_VALUE (*foo, 18); + } + { + int *foo = gcc_jit_result_get_global (result, "global_int_alotofoperators"); + + CHECK_VALUE (*foo, ~(-((((((2 | 8) & 15) ^ 0) << 3 >> 2) - 1) / 2))); + } + { + int *foo = gcc_jit_result_get_global (result, "global_int4_3"); + int **pfoo = gcc_jit_result_get_global (result, "global_pint5"); + + CHECK_VALUE (*foo, 3); + CHECK_VALUE (foo, *pfoo); + CHECK_VALUE (**pfoo, 3); + } + { + int * (*foo) (void) = gcc_jit_result_get_code (result, "fn_pint_0"); + int **pfoo = gcc_jit_result_get_global (result, "global_pint6"); + + CHECK_VALUE (*foo (), 0); + CHECK_VALUE (foo (), *pfoo); + CHECK_VALUE (**pfoo, 0); + } + { + int *foo = gcc_jit_result_get_global (result, "global_int6_3"); + int **pfoo = gcc_jit_result_get_global (result, "global_pint7"); + + CHECK_VALUE (*foo, 3); + CHECK_VALUE (foo + 1, *pfoo); + CHECK_VALUE (*(*pfoo - 1), 3); + } + { + double *foo = gcc_jit_result_get_global (result, "global_double1_3"); + + CHECK_VALUE (*foo, 3); + } + { + double *foo = gcc_jit_result_get_global (result, "global_double2_12"); + + CHECK_VALUE (*foo, 12); + } + { + _Bool *foo = gcc_jit_result_get_global (result, "global_bool1_1"); + + CHECK_VALUE (*foo, 1); + } + { + int *foo = gcc_jit_result_get_global (result, "global_intarr_1234"); + + CHECK_VALUE (foo[0], 1); + CHECK_VALUE (foo[1], 2); + CHECK_VALUE (foo[2], 3); + CHECK_VALUE (foo[3], 4); + } + { + float *foo = gcc_jit_result_get_global (result, "global_floatarr_12"); + + CHECK_VALUE (foo[0], 1); + CHECK_VALUE (foo[1], 2); + CHECK_VALUE (foo[2], 0); + CHECK_VALUE (foo[3], 0); + } + { + float *foo = gcc_jit_result_get_global (result, "global_floatarr_12_2"); + + CHECK_VALUE (foo[0], 1); + CHECK_VALUE (foo[1], 2); + CHECK_VALUE (foo[2], 0); + CHECK_VALUE (foo[3], 0); + } + { + float *foo = gcc_jit_result_get_global (result, "global_floatarr_120"); + + CHECK_VALUE (foo[0], 1); + CHECK_VALUE (foo[1], 2); + CHECK_VALUE (foo[2], 0); + CHECK_VALUE (foo[3], 0); + } + { + float *foo = gcc_jit_result_get_global (result, "global_floatarr_0000"); + + CHECK_VALUE (foo[0], 0); + CHECK_VALUE (foo[1], 0); + CHECK_VALUE (foo[2], 0); + CHECK_VALUE (foo[3], 0); + } + { + float *foo = gcc_jit_result_get_global (result, "global_floatarr_00305600"); + + float key[] = {0,0,3,0,5,6,0,0}; + + CHECK_VALUE (memcmp (foo, key, sizeof key), 0); + } + { + int **foo = gcc_jit_result_get_global (result, "global_pintarr_x2xx"); + + CHECK_VALUE (foo[0], 0); + CHECK_VALUE (*foo[1], 2); + } + { + char *foo = gcc_jit_result_get_global (result, "global_chararr_qwe"); + const char *key = "qwe"; + CHECK_VALUE (strcmp (foo, key), 0); + } + { + int *foo = gcc_jit_result_get_global (result, "global_int2x2matrix_1234"); + + for (int i = 0; i < 4; i++) + CHECK_VALUE (foo[i], i + 1); + } + { + const char **foo = + gcc_jit_result_get_global (result, "global_cpchararr_qwe_asd"); + + CHECK_VALUE (strcmp (foo[0], "qwe"), 0); + CHECK_VALUE (strcmp (foo[1], "asd"), 0); + } + { + int *foo = gcc_jit_result_get_global (result, "global_lvalueinit_int_3"); + + CHECK_VALUE (*foo, 3); + } + { + int **pint = + gcc_jit_result_get_global (result, "global_pint_4"); + int *foo = + gcc_jit_result_get_global (result, "global_int_6"); + CHECK_VALUE (**pint, 4); + CHECK_VALUE (*foo, 6); + } + { + int (*fn)(void) = gcc_jit_result_get_code (result, "fn_int_11"); + CHECK_VALUE (fn (), 11); + } + { + int (*fn)(void) = gcc_jit_result_get_code (result, "fn_cint_11"); + CHECK_VALUE (fn (), 11); + } + { + int *(*fn)(void) = gcc_jit_result_get_code (result, "fn_cint_12"); + CHECK_VALUE (*fn (), 12); + } + { + short *foo = + gcc_jit_result_get_code (result, "global_lvalueinit_short_3"); + CHECK_VALUE (*foo, 3); + } + { + int **foo = + gcc_jit_result_get_code (result, "global_lvalueinit_cpcint_3"); + CHECK_VALUE (**foo, 3); + } + { + int *foo = + gcc_jit_result_get_code (result, "global_lvalueinit_int_4"); + CHECK_VALUE (*foo, 4); + + int *bar = + gcc_jit_result_get_code (result, "global_const_int_7"); + CHECK_VALUE (*bar, 4); + /* The linker does not have to support up to 64 alignment, so test that + it does before testing that it works in libgccjit. */ + if ((size_t) &test_aligned64_works_in_linker_1 % 64 == 0 && + (size_t) &test_aligned64_works_in_linker_2 % 64 == 0) + CHECK_VALUE ((size_t) bar % 64, 0); /* __attribute__ ((aligned (64))) */ + } + { + union upintsize *foo = + gcc_jit_result_get_code (result, "global_const_upintsize_1"); + CHECK_VALUE (foo->p, (void*)0xEEEFBEEF); + } + { + struct A_glb *a = + gcc_jit_result_get_code (result, "a_glb"); + struct B_glb *b = + gcc_jit_result_get_code (result, "b_glb"); + + CHECK_VALUE (a->b, b); + CHECK_VALUE (b->a, a); + } +} diff --git a/gcc/testsuite/jit.dg/test-local-init-rvalue.c b/gcc/testsuite/jit.dg/test-local-init-rvalue.c new file mode 100644 index 0000000000000000000000000000000000000000..1d74679c07c06d6ca0725c7d8045f6150fa481c8 --- /dev/null +++ b/gcc/testsuite/jit.dg/test-local-init-rvalue.c @@ -0,0 +1,707 @@ +#include <stdio.h> +#include "libgccjit.h" +#include "harness.h" + +/* This testcase checks that gcc_jit_context_new_constructor() works + with locals. Tests that constructors can be used as return + values or function call values. Test that constructors can have side + effects and be assigned to locals. + */ + +void +create_code (gcc_jit_context *ctxt, void *user_data) +{ + gcc_jit_type *int_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_INT); + gcc_jit_type *pint_type = gcc_jit_type_get_pointer (int_type); + gcc_jit_type *double_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_DOUBLE); + gcc_jit_type *float_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_FLOAT); + gcc_jit_type *bool_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_BOOL); + gcc_jit_type *char_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_CHAR); + gcc_jit_type *size_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_SIZE_T); + gcc_jit_type *voidptr_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_VOID_PTR); + gcc_jit_type *void_type = gcc_jit_context_get_type (ctxt, + GCC_JIT_TYPE_VOID); + + /* Make a struct: struct fi { float f; int i;} */ + gcc_jit_field *fi_f = gcc_jit_context_new_field (ctxt, + 0, + float_type, + "f"); + gcc_jit_field *fi_i = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "i"); + gcc_jit_field *fields[] = {fi_f, fi_i}; + + gcc_jit_type *struct_fi_type = + gcc_jit_struct_as_type ( + gcc_jit_context_new_struct_type (ctxt, + 0, + "fi", + 2, + fields)); + + /* Make a struct: + + struct bar { + int ii; + int arr[50]; + float ff; + char cc; + } + */ + gcc_jit_field *bar_ff = gcc_jit_context_new_field (ctxt, + 0, + float_type, + "ff"); + gcc_jit_field *bar_ii = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "ii"); + gcc_jit_field *bar_cc = gcc_jit_context_new_field (ctxt, + 0, + char_type, + "cc"); + gcc_jit_type *int50arr_type = + gcc_jit_context_new_array_type (ctxt, + 0, + int_type, + 50); + gcc_jit_field *bar_fi = gcc_jit_context_new_field (ctxt, + 0, + int50arr_type, + "arr"); + gcc_jit_field *fields2[] = {bar_ff, bar_fi, bar_ii, bar_cc}; + + gcc_jit_type *struct_bar_type = + gcc_jit_struct_as_type ( + gcc_jit_context_new_struct_type (ctxt, + 0, + "bar", + 4, + fields2)); + + /* Make an union: + + union ubar { + float ff; + int ii; + }; + */ + gcc_jit_field *ubar_ff = gcc_jit_context_new_field (ctxt, + 0, + float_type, + "ff"); + gcc_jit_field *ubar_ii = gcc_jit_context_new_field (ctxt, + 0, + int_type, + "ii"); + gcc_jit_field *fields3[] = {ubar_ff, ubar_ii}; + gcc_jit_type *ubar = gcc_jit_context_new_union_type (ctxt, + 0, + "ubar", + 2, + fields3); + + (void) ubar; + (void) struct_bar_type; + (void) struct_fi_type; + (void) bool_type; + (void) double_type; + (void) pint_type; + (void) voidptr_type; + (void) size_type; + + gcc_jit_function *fn_int_3; + { /* int foo () { int local = 3; return local;} */ + fn_int_3 = + gcc_jit_context_new_function (ctxt, + 0, + GCC_JIT_FUNCTION_EXPORTED, + int_type, + "fn_int_3", + 0, + 0, + 0); + gcc_jit_block *block = gcc_jit_function_new_block (fn_int_3, "start"); + gcc_jit_lvalue *local = gcc_jit_function_new_local (fn_int_3, + 0, + int_type, + "local"); + gcc_jit_rvalue *rval = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 3); + + gcc_jit_block_add_assignment (block, 0, local, rval); + + gcc_jit_block_end_with_return (block, + 0, + gcc_jit_lvalue_as_rvalue(local)); + } + { /* struct fi foo() { return (struct fi){1,2};} */ + gcc_jit_function *fn = + gcc_jit_context_new_function (ctxt, + 0, + GCC_JIT_FUNCTION_EXPORTED, + struct_fi_type, + "fn_fi_1_2", + 0, + 0, + 0); + gcc_jit_block *block = gcc_jit_function_new_block (fn, "start"); + + gcc_jit_rvalue *rval_f1 = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 1); + gcc_jit_rvalue *rval_i2 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 2); + + gcc_jit_rvalue *vals[] = { rval_f1, rval_i2}; + gcc_jit_field *fields[] = {fi_f, fi_i}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_fi_type, + 2, + fields, + vals); + + gcc_jit_block_end_with_return (block, + 0, + ctor); + } + { /* + struct fi foo() + { + struct fi local = {1,2}; + local = (struct fi){5,6}; + return local; + } + */ + gcc_jit_function *fn = + gcc_jit_context_new_function (ctxt, + 0, + GCC_JIT_FUNCTION_EXPORTED, + struct_fi_type, + "fn_fi_5_6", + 0, + 0, + 0); + gcc_jit_lvalue *local = gcc_jit_function_new_local (fn, + 0, + struct_fi_type, + "local"); + gcc_jit_block *block = gcc_jit_function_new_block (fn, "start"); + + { + gcc_jit_rvalue *rval_f1 = + gcc_jit_context_new_rvalue_from_int (ctxt, float_type, 1); + gcc_jit_rvalue *rval_i2 = + gcc_jit_context_new_rvalue_from_int (ctxt, int_type, 2); + + gcc_jit_rvalue *vals[] = { rval_f1, rval_i2}; + gcc_jit_field *fields[] = {fi_f, fi_i}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_fi_type, + 2, + fields, + vals); + gcc_jit_block_add_assignment (block, 0, local, ctor); + } + { + gcc_jit_rvalue *rval_f1 = + gcc_jit_context_new_rvalue_from_int (ctxt, float_type, 5); + gcc_jit_rvalue *rval_i2 = + gcc_jit_context_new_rvalue_from_int (ctxt, int_type, 6); + + gcc_jit_rvalue *vals[] = { rval_f1, rval_i2}; + gcc_jit_field *fields[] = {fi_f, fi_i}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_fi_type, + 2, + fields, + vals); + gcc_jit_block_add_assignment (block, 0, local, ctor); + } + + gcc_jit_block_end_with_return (block, + 0, + gcc_jit_lvalue_as_rvalue(local)); + } + { /* struct fi foo() { struct fi local = {1, fn_int_3()}; + return local;} + + The ctor has a side effect (funccall) */ + gcc_jit_function *fn = + gcc_jit_context_new_function (ctxt, + 0, + GCC_JIT_FUNCTION_EXPORTED, + struct_fi_type, + "fn_fi_1_3", + 0, + 0, + 0); + gcc_jit_lvalue *local = gcc_jit_function_new_local (fn, + 0, + struct_fi_type, + "local"); + gcc_jit_block *block = gcc_jit_function_new_block (fn, "start"); + + { + gcc_jit_rvalue *rval_f1 = + gcc_jit_context_new_rvalue_from_int (ctxt, float_type, 1); + gcc_jit_rvalue *rval_i2 = + gcc_jit_context_new_call (ctxt, 0, fn_int_3, 0, 0); + + gcc_jit_rvalue *vals[] = { rval_f1, rval_i2}; + gcc_jit_field *fields[] = {fi_f, fi_i}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_fi_type, + 2, + fields, + vals); + gcc_jit_block_add_assignment (block, 0, local, ctor); + } + + gcc_jit_block_end_with_return (block, + 0, + gcc_jit_lvalue_as_rvalue(local)); + } + { /* struct fi foo(fi) { return fi;} + struct fi bar() { return foo((struct fi){3, 4}); } + */ + + gcc_jit_param *fi_param = + gcc_jit_context_new_param (ctxt, 0, struct_fi_type, "fi"); + + gcc_jit_function *fn0 = + gcc_jit_context_new_function (ctxt, + 0, + GCC_JIT_FUNCTION_EXPORTED, + struct_fi_type, + "fn_fi_x_x", + 1, + &fi_param, + 0); + gcc_jit_block *block0 = gcc_jit_function_new_block (fn0, "start"); + gcc_jit_block_end_with_return (block0, + 0, + gcc_jit_param_as_rvalue ( + gcc_jit_function_get_param (fn0, 0))); + + gcc_jit_function *fn = + gcc_jit_context_new_function (ctxt, + 0, + GCC_JIT_FUNCTION_EXPORTED, + struct_fi_type, + "fn_fi_3_4", + 0, + 0, + 0); + gcc_jit_block *block = gcc_jit_function_new_block (fn, "start"); + + gcc_jit_rvalue *rval_f1 = gcc_jit_context_new_rvalue_from_int ( + ctxt, float_type, 3); + gcc_jit_rvalue *rval_i2 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 4); + + gcc_jit_rvalue *vals[] = { rval_f1, rval_i2}; + gcc_jit_field *fields[] = {fi_f, fi_i}; + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_fi_type, + 2, + fields, + vals); + + gcc_jit_rvalue *call = gcc_jit_context_new_call (ctxt, 0, fn0, 1, &ctor); + + gcc_jit_block_end_with_return (block, + 0, + call); + } + { /* + void foo(struct bar *b) { *b = (struct bar) {.arr = {1,2}; } + */ + + gcc_jit_param *param = + gcc_jit_context_new_param (ctxt, 0, + gcc_jit_type_get_pointer (struct_bar_type), + "b"); + + + gcc_jit_function *fn = + gcc_jit_context_new_function (ctxt, + 0, + GCC_JIT_FUNCTION_EXPORTED, + void_type, + "fn_pbar_12", + 1, + ¶m, + 0); + gcc_jit_block *block = gcc_jit_function_new_block (fn, "start"); + + gcc_jit_rvalue *rval_i1 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 1); + gcc_jit_rvalue *rval_i2 = gcc_jit_context_new_rvalue_from_int ( + ctxt, int_type, 2); + + gcc_jit_rvalue *arr_vals[] = { rval_i1, rval_i2}; + + gcc_jit_rvalue *arr_ctor = gcc_jit_context_new_array_constructor + (ctxt, 0, + int50arr_type, + 2, + arr_vals); + + gcc_jit_rvalue *str_ctor = gcc_jit_context_new_struct_constructor + (ctxt, + 0, + struct_bar_type, + 1, + &bar_fi, + &arr_ctor); + + gcc_jit_param *p0 = gcc_jit_function_get_param (fn, 0); + gcc_jit_lvalue *lv0 = gcc_jit_param_as_lvalue (p0); + gcc_jit_lvalue *deref = + gcc_jit_rvalue_dereference (gcc_jit_lvalue_as_rvalue (lv0), 0); + + gcc_jit_block_add_assignment (block, 0, + deref, + str_ctor); + + gcc_jit_block_end_with_void_return (block, 0); + } + { /* struct bar foo() { struct bar local = {}; + return local;} + */ + gcc_jit_function *fn = + gcc_jit_context_new_function (ctxt, + 0, + GCC_JIT_FUNCTION_EXPORTED, + struct_bar_type, + "fn_bar_0s", + 0, + 0, + 0); + gcc_jit_lvalue *local = + gcc_jit_function_new_local (fn, + 0, + struct_bar_type, + "local"); + gcc_jit_block *block = gcc_jit_function_new_block (fn, "start"); + + gcc_jit_rvalue *ctor = gcc_jit_context_new_struct_constructor + (ctxt, 0, + struct_bar_type, + 0, + 0, + 0); + gcc_jit_block_add_assignment (block, 0, local, ctor); + + gcc_jit_block_end_with_return (block, + 0, + gcc_jit_lvalue_as_rvalue(local)); + } + { /* struct bar foo() { struct bar local; + local.arr = (int [50]){1,2,3,4,5,6}; + return local;} + */ + gcc_jit_function *fn = + gcc_jit_context_new_function (ctxt, + 0, + GCC_JIT_FUNCTION_EXPORTED, + struct_bar_type, + "fn_bar_123s", + 0, + 0, + 0); + gcc_jit_lvalue *local = + gcc_jit_function_new_local (fn, + 0, + struct_bar_type, + "local"); + gcc_jit_block *block = gcc_jit_function_new_block (fn, "start"); + + gcc_jit_rvalue *values[6]; + + for (int i = 0; i < 6; i++) + values[i] = gcc_jit_context_new_rvalue_from_int (ctxt, int_type, i + 1); + + gcc_jit_rvalue *ctor = gcc_jit_context_new_array_constructor + (ctxt, 0, + int50arr_type, + 6, + values); + + gcc_jit_lvalue *arr_lv = gcc_jit_lvalue_access_field (local, + 0, + bar_fi); + gcc_jit_block_add_assignment (block, 0, arr_lv, ctor); + + gcc_jit_block_end_with_return (block, + 0, + gcc_jit_lvalue_as_rvalue(local)); + } + { /* int[50] foo() { int arr[50]; + arr = (int [50]){1,2,3,4,5,6}; + return arr;} + + N.B: Not a typo, returning an array. + */ + gcc_jit_function *fn = + gcc_jit_context_new_function (ctxt, + 0, + GCC_JIT_FUNCTION_EXPORTED, + int50arr_type, + "fn_int50arr_123s", + 0, + 0, + 0); + gcc_jit_lvalue *local = + gcc_jit_function_new_local (fn, + 0, + int50arr_type, + "local"); + gcc_jit_block *block = gcc_jit_function_new_block (fn, "start"); + + gcc_jit_rvalue *values[6]; + + for (int i = 0; i < 6; i++) + values[i] = gcc_jit_context_new_rvalue_from_int (ctxt, int_type, i + 1); + + gcc_jit_rvalue *ctor = gcc_jit_context_new_array_constructor ( + ctxt, + 0, + int50arr_type, + 6, + values); + + gcc_jit_block_add_assignment (block, 0, local, ctor); + + gcc_jit_block_end_with_return (block, + 0, + gcc_jit_lvalue_as_rvalue(local)); + } + { /* + Verify that circular linked lists compiles, .e.g. + that visit_children does not run in circles or something. + + struct llist { struct llist *next; }; + + bool foo (void) + { + volatile struct llist a; + volatile struct llist b; + + a = (struct llist) {.next = &b}; + b = (struct llist) {.next = &a}; + + return a.next == &b; + } + */ + gcc_jit_struct *llist = + gcc_jit_context_new_opaque_struct(ctxt, + 0, "llist_lcl"); + gcc_jit_field *fields[] = + { + gcc_jit_context_new_field (ctxt, 0, + gcc_jit_type_get_pointer ( + gcc_jit_struct_as_type (llist)), + "next") + }; + gcc_jit_struct_set_fields (llist, 0, 1, fields); + gcc_jit_type *t_llist = gcc_jit_struct_as_type (llist); + + gcc_jit_function *fn = + gcc_jit_context_new_function (ctxt, + 0, + GCC_JIT_FUNCTION_EXPORTED, + bool_type, + "fn_llist", + 0, + 0, + 0); + gcc_jit_block *block = gcc_jit_function_new_block (fn, "start"); + + gcc_jit_lvalue *a = + gcc_jit_function_new_local (fn, + 0, + gcc_jit_type_get_volatile (t_llist), + "a"); + gcc_jit_lvalue *b = + gcc_jit_function_new_local (fn, + 0, + gcc_jit_type_get_volatile (t_llist), + "b"); + + gcc_jit_rvalue *a_addr = gcc_jit_lvalue_get_address( a, 0); + gcc_jit_rvalue *b_addr = gcc_jit_lvalue_get_address( b, 0); + + gcc_jit_rvalue *a_ctor = gcc_jit_context_new_struct_constructor ( + ctxt, + 0, + t_llist, + 1, + 0, + &b_addr); + + gcc_jit_rvalue *b_ctor = gcc_jit_context_new_struct_constructor ( + ctxt, + 0, + t_llist, + 1, + 0, + &a_addr); + + gcc_jit_block_add_assignment (block, 0, + a, a_ctor); + gcc_jit_block_add_assignment (block, 0, + b, b_ctor); + + gcc_jit_rvalue *cmp = + gcc_jit_context_new_comparison ( + ctxt, 0, + GCC_JIT_COMPARISON_EQ, + gcc_jit_rvalue_access_field (gcc_jit_lvalue_as_rvalue (a), + 0, fields[0]), + gcc_jit_context_new_cast (ctxt, 0, + gcc_jit_lvalue_get_address (b, 0), + gcc_jit_type_get_pointer (t_llist))); + + gcc_jit_block_end_with_return (block, + 0, cmp); + } +} + +struct fi2 { + float f; + int i; +}; + +struct bar2 { + float ff; + int arr[50]; + int ii; + char c; +}; + +union ubar2 { + float ff; + int ii; +}; + +struct int50arr { + int arr[50]; +}; + +void __attribute__((optimize(0))) +scramble_stack(void) + { + char *p = alloca(100); + for (int i = 0; i < 100; i++) + *p++ = 0xF0; + asm(""); /* Mark for side-effect */ + } + +void __attribute__((optimize(0))) +scramble_arr (char *arr, int len) +{ + for (int i = 0; i < len; i++) + *arr++ = i; + asm(""); /* Mark for side-effect */ +} + +void +verify_code (gcc_jit_context *ctxt, gcc_jit_result *result) +{ + CHECK_NON_NULL (result); + + { + struct fi2 (*fn) (void) = gcc_jit_result_get_code (result, "fn_fi_1_2"); + scramble_stack (); + struct fi2 fi = fn (); + CHECK_VALUE (fi.f, 1); + CHECK_VALUE (fi.i, 2); + } + { + struct fi2 (*fn) (void) = gcc_jit_result_get_code (result, "fn_fi_5_6"); + struct fi2 fi = fn (); + CHECK_VALUE (fi.f, 5); + CHECK_VALUE (fi.i, 6); + } + { + struct fi2 (*fn) (void) = gcc_jit_result_get_code (result, "fn_fi_1_3"); + struct fi2 fi = fn (); + CHECK_VALUE (fi.f, 1); + CHECK_VALUE (fi.i, 3); + } + { + struct fi2 (*fn) (void) = gcc_jit_result_get_code (result, "fn_fi_3_4"); + struct fi2 fi = fn (); + CHECK_VALUE (fi.f, 3); + CHECK_VALUE (fi.i, 4); + } + { + scramble_stack(); + struct bar2 (*fn) (void) = gcc_jit_result_get_code (result, "fn_bar_0s"); + struct bar2 bar = fn (); + struct bar2 key = {}; + + CHECK_VALUE (bar.ff, 0); + CHECK_VALUE (bar.ii, 0); + CHECK_VALUE (memcmp (&bar.arr, &key.arr, sizeof (key.arr)), 0); + } + { + + void (*fn) (struct bar2 *) = gcc_jit_result_get_code (result, "fn_pbar_12"); + + struct bar2 bar = (struct bar2) {}; + + scramble_arr ((char*)&bar, sizeof bar); + scramble_stack(); + + fn (&bar); + + struct bar2 key = {.arr = {1,2}}; + __builtin_clear_padding (&key); + + CHECK_VALUE (memcmp (&bar, &key, sizeof (key)), 0); + } + { + scramble_stack(); + struct bar2 (*fn) (void) = gcc_jit_result_get_code (result, "fn_bar_123s"); + struct bar2 bar = fn (); + struct bar2 key = {.arr = {1,2,3,4,5,6} }; + + CHECK_VALUE (memcmp (&bar.arr, &key.arr, sizeof (key.arr)), 0); + } + { + scramble_stack (); + /* This is abit shady. Lets just pretend that array returns à la Fortran + is the same thing as returning a struct with an array in it in C. */ + struct int50arr (*fn) (void) = + gcc_jit_result_get_code (result, "fn_int50arr_123s"); + struct int50arr ans = fn (); + int key[50] = {1,2,3,4,5,6}; + + CHECK_VALUE (memcmp (ans.arr, key, sizeof (key)), 0); + } + { + _Bool (*fn) (void) = gcc_jit_result_get_code (result, "fn_llist"); + CHECK_VALUE (fn (), 1); + } +}