PIPS
type.c File Reference
#include <stdio.h>
#include <string.h>
#include <stdlib.h>
#include "genC.h"
#include "linear.h"
#include "ri.h"
#include "effects.h"
#include "ri-util.h"
#include "prettyprint.h"
#include "effects-util.h"
#include "misc.h"
#include "text-util.h"
+ Include dependency graph for type.c:

Go to the source code of this file.

Functions

entity effect_field_dimension_entity (expression exp, list l_fields)
 type.c More...
 
static int effect_indices_first_pointer_dimension_rank (list current_l_ind, type current_type, bool *exact_p)
 recursively walks thru current_l_ind and current_type in parallel until a pointer dimension is found. More...
 
static int effect_reference_first_pointer_dimension_rank (reference ref, bool *exact_p)
 walks thru ref indices and ref entity type arborescence in parallel until a pointer dimension is found. More...
 
bool effect_reference_contains_pointer_dimension_p (reference ref, bool *exact_p)
 
bool effect_reference_dereferencing_p (reference ref, bool *exact_p)
 
static type r_cell_reference_to_type (list ref_l_ind, type current_type, bool *to_be_freed)
 Lines 291 to 682. More...
 
type cell_reference_to_type (reference ref, bool *to_be_freed)
 computes the type of a cell reference representing a memory access path. More...
 
type cell_to_type (cell c, bool *to_be_freed)
 
type points_to_reference_to_type (reference ref, bool *to_be_freed)
 FI: I need more generality than is offered by cell_to_type() More...
 
static void substitute_unbounded_call (call c)
 
static expression eliminate_calls_to_unbounded (expression e)
 Allocate a copy of expression "e" where calls to the unbounded function are replaced by calls to the zero function so that typing can be performed. More...
 
type points_to_expression_to_type (expression e, bool *to_be_freed)
 FI: I need more generality than is offered by expression_to_type() because fields are assimilated to subscripts. More...
 
type points_to_expression_to_concrete_type (expression e)
 The type returned is stored in a hash-table. More...
 
type points_to_expression_to_pointed_type (expression e)
 Return a new allocated type "t" of the address pointed by expression "e", if expression "e" denotes an address. More...
 
type points_to_cell_to_type (cell c, bool *to_be_freed)
 FI: I need more generality than is offered by cell_to_type() More...
 
type points_to_cell_to_concrete_type (cell c)
 
type points_to_reference_to_concrete_type (reference r)
 
bool basic_concrete_types_compatible_for_effects_interprocedural_translation_p (type real_ct, type formal_ct)
 tests if the actual argument type and the formal argument type are compatible with the current state of the interprocedural translation algorithms. More...
 
bool types_compatible_for_effects_interprocedural_translation_p (type real_arg_t, type formal_arg_t)
 tests if the actual argument type and the formal argument type are compatible with the current state of the interprocedural translation algorithms. More...
 
void points_to_cell_types_compatibility (cell l, cell r)
 Make sure that cell l can points towards cell r. More...
 
bool points_to_source_cell_compatible_p (cell c)
 
bool points_to_sink_cell_compatible_p (cell c __attribute__((unused)))
 
list find_points_to_subscript_for_type (cell c, type t)
 Find the subscript in the reference of cell "c" that would make the reference type be "t" if the subscript list were truncated just after it. More...
 
bool adapt_reference_to_type (reference r, type et, int(*line_number_func)(void))
 FI: a really stupid function... More...
 
bool reference_unbounded_indices_p (reference r)
 This function should be at expression.c. More...
 
bool strict_constant_path_p (reference r)
 
bool can_be_constant_path_p (reference r)
 TODO most of the time return same result that !effect_reference_dereferencing_p for the moment want to test if r can be a constant path for instance a[i] have to return false (something else?) a[0], a[1], i, j, a[*], var points by formal parameter (_p_0, ...), element of strut (s.id, ...), heap element have to return true. More...
 

Function Documentation

◆ adapt_reference_to_type()

bool adapt_reference_to_type ( reference  r,
type  et,
int(*)(void)  line_number_func 
)

FI: a really stupid function...

Why do we add zero subscript right away when building the sink cell to remove them later? Let's now remove the excessive subscripts of "r" with respect to type "at"...

Parameters
ett

Definition at line 1327 of file type.c.

1329 {
1330  bool succeed_p = true;
1331  bool to_be_freed;
1333  type rt = points_to_reference_to_type(r, &to_be_freed);
1335  while(!array_pointer_type_equal_p(at, t) && !ENDP(reference_indices(r))) {
1336  if(to_be_freed) free_type(t);
1337  list sl = reference_indices(r);
1338  list last = gen_last(sl);
1339  expression e = EXPRESSION(CAR(last));
1340  if(expression_field_p(e))
1341  break;
1342  int l1 = (int) gen_length(sl);
1343  gen_remove_once(&sl, (void *) e);
1344  int l2 = (int) gen_length(sl);
1345  if(l1==l2)
1346  pips_internal_error("gen_remove() is ineffective.\n");
1347  reference_indices(r) = sl;
1348  type nrt = points_to_reference_to_type(r, &to_be_freed);
1349  t = compute_basic_concrete_type(nrt);
1350  }
1351  if(!array_pointer_string_type_equal_p(at, t)) {
1352  // FI: this function used to be in library alias_classes
1353  // It should be passed as a functional argument.
1354  //int points_to_context_statement_line_number(void);
1355  pips_user_warning("There may be a typing error at line %d (e.g. improper malloc call).\n Reference \"%s\" with type \"%s\" cannot be adapted to type \"%s\".\n",
1356  // points_to_context_statement_line_number());
1357  (*line_number_func)(),
1361  //pips_internal_error("Cell type mismatch.");
1362  succeed_p = false;
1363  }
1364  if(to_be_freed) free_type(t);
1365  return succeed_p;
1366 }
void free_type(type p)
Definition: ri.c:2658
void const char const char const int
type points_to_reference_to_type(reference ref, bool *to_be_freed)
FI: I need more generality than is offered by cell_to_type()
Definition: type.c:527
#define ENDP(l)
Test if a list is empty.
Definition: newgen_list.h:66
void gen_remove_once(list *pl, const void *o)
Remove the first occurence of o in list pl:
Definition: list.c:691
size_t gen_length(const list l)
Definition: list.c:150
#define CAR(pcons)
Get the value of the first element of a list.
Definition: newgen_list.h:92
list gen_last(list l)
Return the last element of a list.
Definition: list.c:578
#define pips_user_warning
Definition: misc-local.h:146
#define pips_internal_error
Definition: misc-local.h:149
string reference_to_string(reference r)
Definition: expression.c:87
string type_to_full_string_definition(type t)
Provide a full ASCII description of type "t".
Definition: type.c:45
bool expression_field_p(expression e)
The expression is of kind "s.a", where "s" is a struct and a "a" field.
Definition: expression.c:491
bool array_pointer_string_type_equal_p(type t1, type t2)
Assume that a pointer to type x is equal to a 1-D array of x.
Definition: type.c:658
bool array_pointer_type_equal_p(type t1, type t2)
assume that a pointer to type x is equal to a 1-D array of x
Definition: type.c:609
type compute_basic_concrete_type(type t)
computes a new type which is the basic concrete type of the input type (this new type is not stored i...
Definition: type.c:3556
#define EXPRESSION(x)
EXPRESSION.
Definition: ri.h:1217
#define reference_indices(x)
Definition: ri.h:2328
The structure used to build lists in NewGen.
Definition: newgen_list.h:41

References array_pointer_string_type_equal_p(), array_pointer_type_equal_p(), CAR, compute_basic_concrete_type(), ENDP, EXPRESSION, expression_field_p(), free_type(), gen_last(), gen_length(), gen_remove_once(), int, pips_internal_error, pips_user_warning, points_to_reference_to_type(), reference_indices, reference_to_string(), and type_to_full_string_definition().

Referenced by dereferencing_subscript_to_points_to(), expression_to_points_to_cells(), filter_formal_context_according_to_actual_context(), new_filter_formal_context_according_to_actual_context(), points_to_with_stripped_sink(), process_casted_sinks(), process_casted_sources(), subscript_to_points_to_sinks(), and subscripted_reference_to_points_to().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ basic_concrete_types_compatible_for_effects_interprocedural_translation_p()

bool basic_concrete_types_compatible_for_effects_interprocedural_translation_p ( type  real_ct,
type  formal_ct 
)

tests if the actual argument type and the formal argument type are compatible with the current state of the interprocedural translation algorithms.

Input types are

See also
basic_concrete_type .

safe default result

easiest case

we do not take care of array dimension sizes

well, basic_equal_strict_p is at the same time too restrictive for derived and too optimistic for pointers and arrays because dimensions are skipped

skip same number of array and pointer dimensions until we reach the ultimate basic or there are no more corresponding dimensions

we have a void * as actual argument

translation cannot be accurate

we are sure here that gen_length(formal_dims) != 0

we have a void * as actual argument

translation cannot be accurate

we are sure here that gen_length(real_dims) != 0

store types and not bct becasue bct cannot be equal, since a new type is generated each time. We really need a global table for bcts

It should be a strict type equality here, but I don't think type_equal_p is very robust when types are declared in headers

Parameters
real_cteal_ct
formal_ctormal_ct

Definition at line 699 of file type.c.

700 {
701  static list real_structured_types = NIL;
702  static list formal_structured_types = NIL;
703 
704  pips_debug(8,"real_ct : %s \t formal_ct: %s\n",
705  string_of_type(real_ct),
706  string_of_type(formal_ct));
707 
708  bool result = false; /* safe default result */
709  /* easiest case */
710  if (real_ct == formal_ct)
711  {
712  pips_debug(8, "types are equal\n");
713  result = true;
714  }
715 
716  else if (type_tag(real_ct) != type_tag(formal_ct))
717  {
718  pips_debug(8, "not same type tags\n");
719  result = false;
720  }
721 
722  else
723  {
724  switch(type_tag(real_ct))
725  {
726  case is_type_void:
727  result = true;
728  break;
729  case is_type_variable:
730  {
731  pips_debug(8, "variable case\n");
732  basic real_b = variable_basic(type_variable(real_ct));
733  list real_dims = variable_dimensions(type_variable(real_ct));
734  basic formal_b = variable_basic(type_variable(formal_ct));
735  list formal_dims = variable_dimensions(type_variable(formal_ct));
736 
737  bool finished = false;
738  /* we do not take care of array dimension sizes */
739  while (! finished)
740  {
741  if (gen_length(real_dims) == gen_length(formal_dims))
742  {
743  /* well, basic_equal_strict_p is at the same time too restrictive
744  for derived and too optimistic for pointers and arrays because
745  dimensions are skipped
746  */
747  if (basic_pointer_p(real_b) && basic_pointer_p(formal_b))
748  {
749  pips_debug(8, "pointer case\n");
750  result =
752  (basic_pointer(real_b), basic_pointer(formal_b));
753  }
754  else if (basic_derived_p(real_b) && basic_derived_p(formal_b))
755  {
756  entity real_basic_e = basic_derived(real_b);
757  entity formal_basic_e = basic_derived(formal_b);
758  pips_debug(8, "derived case, real: %s, formal: %s\n",
759  entity_name(real_basic_e),
760  entity_name(formal_basic_e));
761  if (same_entity_p(real_basic_e, formal_basic_e))
762  {
763  pips_debug(8, "same entities (1) \n");
764  result = true;
765  }
766  else
767  {
768  type formal_dt = entity_type(formal_basic_e);
769  type real_dt = entity_type(real_basic_e);
770 
771  void * found_formal_t = (type) gen_find_eq(formal_dt,formal_structured_types);
772  void * found_real_t = (type) gen_find_eq(real_dt,real_structured_types);
773 
774  if (!gen_chunk_undefined_p(found_formal_t))
775  {
776  pips_debug(8, "types already encountered (1) \n");
777  result = gen_position(found_formal_t, formal_structured_types)
778  == gen_position(found_real_t, real_structured_types);
779  }
780  else
781  {
782  pips_debug(8, "types not encountered (1) \n");
783  formal_structured_types = gen_type_cons(formal_dt, formal_structured_types);
784  real_structured_types = gen_type_cons(real_dt, real_structured_types);
786  list old_formal_structured_types = formal_structured_types;
787  list old_real_structured_types = real_structured_types;
788  POP(formal_structured_types);
789  POP(real_structured_types);
790  CDR(old_formal_structured_types) = NIL;
791  CDR(old_real_structured_types) = NIL;
792  gen_free_list(old_formal_structured_types);
793  gen_free_list(old_real_structured_types);
794  }
795  }
796  }
797  else
798  result = basic_equal_p(real_b, formal_b);
799  finished = true;
800  }
801  else
802  {
803  /* skip same number of array and pointer dimensions until we reach the
804  ultimate basic or there are no more corresponding dimensions
805  */
806  if (basic_pointer_p(real_b) && gen_length(real_dims) == 0)
807  {
808  real_ct = basic_pointer(real_b);
809  if (type_void_p(real_ct))
810  {
811  /* we have a void * as actual argument */
812  /* translation cannot be accurate */
813  finished = true;
814  }
815  else if (type_variable_p(real_ct))
816  {
817  real_b = variable_basic(type_variable(real_ct));
818  real_dims = variable_dimensions(type_variable(real_ct));
819  formal_dims = CDR(formal_dims); /* we are sure here that gen_length(formal_dims) != 0*/
820  }
821  else
822  finished = true;
823  }
824  else if (basic_pointer_p(formal_b) && gen_length(formal_dims) == 0)
825  {
826  formal_ct = basic_pointer(formal_b);
827  if (type_void_p(formal_ct))
828  {
829  /* we have a void * as actual argument */
830  /* translation cannot be accurate */
831  finished = true;
832  }
833  else if (type_variable_p(formal_ct))
834  {
835  formal_b = variable_basic(type_variable(formal_ct));
836  formal_dims = variable_dimensions(type_variable(formal_ct));
837  real_dims = CDR(real_dims); /* we are sure here that gen_length(real_dims) != 0*/
838  }
839  else
840  finished = true;
841  }
842  else
843  finished = true;
844  }
845  }
846  }
847  break;
848  case is_type_struct:
849  case is_type_union:
850  case is_type_enum:
851  pips_debug(8, "struct, union or enum case\n");
852  list real_fields = type_fields(real_ct);
853  list formal_fields = type_fields(formal_ct);
854  if (gen_length(real_fields) == gen_length(formal_fields))
855  {
856  result = true;
857  while(result && !ENDP(real_fields))
858  {
859  entity real_fe = ENTITY(CAR(real_fields));
860  entity formal_fe = ENTITY(CAR(formal_fields));
861  pips_debug(8, "fields, real: %s, formal: %s\n",
862  entity_name(real_fe),
863  entity_name(formal_fe));
864 
865  if (same_entity_p(real_fe, formal_fe))
866  {
867  pips_debug(8, "same entities (2)\n");
868  result = true;
869  }
870  else
871  {
872  type real_ft = entity_type(real_fe);
873  type formal_ft = entity_type(formal_fe);
874 
875  void * found_formal_ft = (type) gen_find_eq(formal_ft,formal_structured_types);
876  void * found_real_ft = (type) gen_find_eq(real_ft,real_structured_types);
877 
878  if (!gen_chunk_undefined_p(found_formal_ft))
879  {
880  pips_debug(8, "types already encountered (2)\n");
881  result = gen_position(found_formal_ft, formal_structured_types)
882  == gen_position(found_real_ft, real_structured_types);
883  }
884  else
885  {
886  pips_debug(8, "types not encountered (2)\n");
887  /* store types and not bct becasue bct cannot be equal,
888  since a new type is generated each time.
889  We really need a global table for bcts */
890  formal_structured_types = gen_type_cons(formal_ft, formal_structured_types);
891  real_structured_types = gen_type_cons(real_ft, real_structured_types);
892  type real_fbct = entity_basic_concrete_type(real_fe);
893  type formal_fbct = entity_basic_concrete_type(formal_fe);
894  /* It should be a strict type equality here, but I don't think type_equal_p
895  is very robust when types are declared in headers
896  */
897  result =
899  (real_fbct, formal_fbct);
900 
901  list old_formal_structured_types = formal_structured_types;
902  list old_real_structured_types = real_structured_types;
903  POP(formal_structured_types);
904  POP(real_structured_types);
905  CDR(old_formal_structured_types) = NIL;
906  CDR(old_real_structured_types) = NIL;
907  gen_free_list(old_formal_structured_types);
908  gen_free_list(old_real_structured_types);
909  }
910  }
911  POP(real_fields);
912  POP(formal_fields);
913  }
914  }
915  break;
916  case is_type_functional:
917  pips_debug(8, "functional case\n");
918  result = true;
919  break;
920  default:
921  pips_internal_error("unexpected function argument type: %s\n", type_to_string(real_ct) );
922  }
923  }
924  pips_debug(8, "returning %s\n", result? "true":"false");
925  return result;
926 }
list gen_type_cons(type p, list l)
Definition: ri.c:2671
struct _newgen_struct_type_ * type
bool basic_concrete_types_compatible_for_effects_interprocedural_translation_p(type real_ct, type formal_ct)
tests if the actual argument type and the formal argument type are compatible with the current state ...
Definition: type.c:699
#define gen_chunk_undefined_p(c)
Definition: genC.h:75
int gen_position(const void *item, const list l)
Element ranks are strictly positive as for first, second, and so on.
Definition: list.c:995
#define POP(l)
Modify a list pointer to point on the next element of the list.
Definition: newgen_list.h:59
#define NIL
The empty list (nil in Lisp)
Definition: newgen_list.h:47
void gen_free_list(list l)
free the spine of the list
Definition: list.c:327
#define CDR(pcons)
Get the list less its first element.
Definition: newgen_list.h:111
void * gen_find_eq(const void *item, const list seq)
Definition: list.c:422
#define pips_debug
these macros use the GNU extensions that allow variadic macros, including with an empty list.
Definition: misc-local.h:145
string string_of_type(const type t)
Definition: type.c:56
bool same_entity_p(entity e1, entity e2)
predicates on entities
Definition: entity.c:1321
list type_fields(type t)
Definition: type.c:3073
bool basic_equal_p(basic b1, basic b2)
Definition: type.c:927
type entity_basic_concrete_type(entity e)
retrieves or computes and then returns the basic concrete type of an entity
Definition: type.c:3677
string type_to_string(const type t)
type.c
Definition: type.c:51
#define basic_pointer(x)
Definition: ri.h:637
#define basic_derived(x)
Definition: ri.h:640
#define type_tag(x)
Definition: ri.h:2940
#define ENTITY(x)
ENTITY.
Definition: ri.h:2755
#define type_variable(x)
Definition: ri.h:2949
#define basic_pointer_p(x)
Definition: ri.h:635
#define basic_derived_p(x)
Definition: ri.h:638
#define type_void_p(x)
Definition: ri.h:2959
#define entity_name(x)
Definition: ri.h:2790
#define variable_dimensions(x)
Definition: ri.h:3122
@ is_type_void
Definition: ri.h:2904
@ is_type_enum
Definition: ri.h:2907
@ is_type_functional
Definition: ri.h:2901
@ is_type_variable
Definition: ri.h:2900
@ is_type_union
Definition: ri.h:2906
@ is_type_struct
Definition: ri.h:2905
#define entity_type(x)
Definition: ri.h:2792
#define type_variable_p(x)
Definition: ri.h:2947
#define variable_basic(x)
Definition: ri.h:3120

References basic_concrete_types_compatible_for_effects_interprocedural_translation_p(), basic_derived, basic_derived_p, basic_equal_p(), basic_pointer, basic_pointer_p, CAR, CDR, ENDP, ENTITY, entity_basic_concrete_type(), entity_name, entity_type, gen_chunk_undefined_p, gen_find_eq(), gen_free_list(), gen_length(), gen_position(), gen_type_cons(), is_type_enum, is_type_functional, is_type_struct, is_type_union, is_type_variable, is_type_void, NIL, pips_debug, pips_internal_error, POP, same_entity_p(), string_of_type(), type_fields(), type_tag, type_to_string(), type_variable, type_variable_p, type_void_p, variable_basic, and variable_dimensions.

Referenced by basic_concrete_types_compatible_for_effects_interprocedural_translation_p(), c_convex_effects_on_actual_parameter_forward_translation(), and types_compatible_for_effects_interprocedural_translation_p().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ can_be_constant_path_p()

bool can_be_constant_path_p ( reference  r)

TODO most of the time return same result that !effect_reference_dereferencing_p for the moment want to test if r can be a constant path for instance a[i] have to return false (something else?) a[0], a[1], i, j, a[*], var points by formal parameter (_p_0, ...), element of strut (s.id, ...), heap element have to return true.

  • !effect_reference_dereferencing_p(r, &exact_p) can return true when it's not a constant path like a[i] (a[i] and not a[*]) can make a side effect for the declaration of variable in parameter (only?), don't know why for instance with Semantics-New/Pointer.sub/memcopy01 void memcopy01([...], char dst[size]) --> void memcopy01([...], char dst[i])
  • store_independent_reference_p(r) can return false for some cp like a[0], can't permit to treat the array return false for the structure too, can't permit to treat the struct can return true for i, j, ... that can be a constant path but not strictly a constant path param r reference to analyze to see if it's a constant path return true if r can be constant path

This function is not used by the points-to analysis, but by semantics

Definition at line 1492 of file type.c.

1493 {
1494  bool constant_path = true;
1495 
1496  if (strict_constant_path_p(r))
1497  constant_path = true;
1498  else {
1499  bool exact_p = true;
1500  if (!effect_reference_dereferencing_p(r, &exact_p)) {
1501  constant_path = true;
1502  }
1503  else {
1504  constant_path = false;
1505  }
1506  }
1507 
1508  return constant_path;
1509 }
bool strict_constant_path_p(reference r)
Definition: type.c:1407
bool effect_reference_dereferencing_p(reference ref, bool *exact_p)
Definition: type.c:233

References effect_reference_dereferencing_p(), and strict_constant_path_p().

Referenced by update_reflhs_with_rhs_to_transformer().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ cell_reference_to_type()

type cell_reference_to_type ( reference  ref,
bool to_be_freed 
)

computes the type of a cell reference representing a memory access path.

Cell references are not compatible with entity typing: spurious dimensions are added to handle struct fields and the dereferencing operator. BEWARE : does not work if field entity indices have been converted to ranks.

Parameters
refis a reference from a cell.
Returns
a newly allocated type corresponding to the type of the memory cells targeted by the access path.

in particular, gets rid of non-store effect references

A reference to a function returns a pointer to a function of the very same time

FI: for some abstract locations that have type unknown instead of type variable, with basic overloaded

Parameters
refef
to_be_freedo_be_freed

Definition at line 466 of file type.c.

467 {
468  debug_on("EFFECTS-UTIL_DEBUG_LEVEL");
469  type t = type_undefined;
471  *to_be_freed= false;
472 
473  pips_debug(6, "input reference: %s \n", reference_to_string(ref));
474 
475  if (ENDP(reference_indices(ref))) /* in particular, gets rid of non-store effect references */
476  {
477  t = ref_type;
478  }
479  else
480  {
481  if(type_variable_p(ref_type))
482  {
483  t = r_cell_reference_to_type(reference_indices(ref), ref_type, to_be_freed);
484  }
485  else if(type_functional_p(ref_type))
486  {
487  /* A reference to a function returns a pointer to a function
488  of the very same time */
492  NIL, NIL));
493  *to_be_freed = true;
494  }
495  else if(type_unknown_p(ref_type)) {
496  /* FI: for some abstract locations that have type unknown
497  instead of type variable, with basic overloaded */
498  t = ref_type;
499  *to_be_freed = false;
500  }
501  else
502  {
503  pips_internal_error("Bad reference type tag %d \"%s\" for reference %s",
504  type_tag(ref_type),
505  type_to_string(ref_type),
507  }
508  }
509  debug_off();
510  return t;
511 }
basic make_basic(enum basic_utype tag, void *val)
Definition: ri.c:155
type copy_type(type p)
TYPE.
Definition: ri.c:2655
variable make_variable(basic a1, list a2, list a3)
Definition: ri.c:2895
type make_type(enum type_utype tag, void *val)
Definition: ri.c:2706
static reference ref
Current stmt (an integer)
Definition: adg_read_paf.c:163
static type r_cell_reference_to_type(list ref_l_ind, type current_type, bool *to_be_freed)
Lines 291 to 682.
Definition: type.c:315
#define debug_on(env)
Definition: misc-local.h:157
#define debug_off()
Definition: misc-local.h:160
#define type_functional_p(x)
Definition: ri.h:2950
@ is_basic_pointer
Definition: ri.h:578
#define type_unknown_p(x)
Definition: ri.h:2956
#define reference_variable(x)
Definition: ri.h:2326
#define type_undefined
Definition: ri.h:2883

References copy_type(), debug_off, debug_on, ENDP, entity_basic_concrete_type(), entity_name, is_basic_pointer, is_type_variable, make_basic(), make_type(), make_variable(), NIL, pips_debug, pips_internal_error, r_cell_reference_to_type(), ref, reference_indices, reference_to_string(), reference_variable, type_functional_p, type_tag, type_to_string(), type_undefined, type_unknown_p, and type_variable_p.

Referenced by cell_to_type(), formal_points_to_parameter(), multiple_pointer_assignment_to_post_pv(), points_to_reference_to_type(), and references_may_conflict_p().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ cell_to_type()

type cell_to_type ( cell  c,
bool to_be_freed 
)
Parameters
to_be_freedo_be_freed

Definition at line 513 of file type.c.

514 {
515  pips_assert("a cell cannot be a gap yet\n", !cell_gap_p(c));
517 
518  return cell_reference_to_type(ref, to_be_freed);
519 }
type cell_reference_to_type(reference ref, bool *to_be_freed)
computes the type of a cell reference representing a memory access path.
Definition: type.c:466
#define cell_reference(x)
Definition: effects.h:469
#define cell_preference(x)
Definition: effects.h:472
#define cell_reference_p(x)
Definition: effects.h:467
#define cell_gap_p(x)
Definition: effects.h:473
#define pips_assert(what, predicate)
common macros, two flavors depending on NDEBUG
Definition: misc-local.h:172
#define preference_reference(x)
Definition: ri.h:2102

References cell_gap_p, cell_preference, cell_reference, cell_reference_p, cell_reference_to_type(), pips_assert, preference_reference, and ref.

Referenced by cell_to_nowhere_sink(), external_call_to_post_pv(), generic_stub_source_to_sinks(), k_limit_points_to(), module_initial_parameter_pv(), safe_intrinsic_to_post_pv(), struct_assignment_to_points_to(), type_compatible_super_cell(), and type_compatible_with_points_to_cell_p().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ effect_field_dimension_entity()

entity effect_field_dimension_entity ( expression  exp,
list  l_fields 
)

type.c

Parameters
expis an effect index expression which is either the rank or an entity corresponding to a struct, union or enum field
l_fieldsis the list of fields of the corresponding struct, union or enum
Returns
the entity corresponding to the field.
Parameters
expxp
l_fields_fields

Definition at line 51 of file type.c.

52 {
54  {
55  int rank = expression_to_int(exp);
56  return ENTITY(gen_nth(rank-1, l_fields));
57  }
58  else
59  {
60  return expression_to_entity(exp);
61  }
62 }
gen_chunk gen_nth(int n, const list l)
to be used as ENTITY(gen_nth(3, l))...
Definition: list.c:710
bool expression_constant_p(expression)
HPFC module by Fabien COELHO.
Definition: expression.c:2453
static entity rank
int expression_to_int(expression exp)
================================================================
Definition: expression.c:2205
entity expression_to_entity(expression e)
just returns the entity of an expression, or entity_undefined
Definition: expression.c:3140
#define exp
Avoid some warnings from "gcc -Wshadow".
Definition: vasnprintf.c:207

References ENTITY, exp, expression_constant_p(), expression_to_entity(), expression_to_int(), gen_nth(), and rank.

Referenced by effect_indices_first_pointer_dimension_rank().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ effect_indices_first_pointer_dimension_rank()

static int effect_indices_first_pointer_dimension_rank ( list  current_l_ind,
type  current_type,
bool exact_p 
)
static

recursively walks thru current_l_ind and current_type in parallel until a pointer dimension is found.

Parameters
current_l_indis a list of effect reference indices.
current_typeis the corresponding type in the original entity type arborescence
exact_pis a pointer to a bool, which is set to true if the result is not an approximation.
Returns
-1 if no index corresponds to a pointer dimension in current_l_ind, the rank of the least index that may correspond to a pointer dimension in current_l_ind otherwise. If this information is exact, *exact_p is set to true.

ssume there is no pointer

FI: I do not understand this assert beacause an array may be referenced with a limited number of subscript to initialize a pointer.

irst skip array dimensions if any

Definition at line 72 of file type.c.

73 {
74  int result = -1; /*assume there is no pointer */
75  basic current_basic = variable_basic(type_variable(current_type));
76  size_t current_nb_dim = gen_length(variable_dimensions(type_variable(current_type)));
77 
78  pips_debug(8, "input type : %s\n", type_to_string(current_type));
79  pips_debug(8, "current_basic : %s, and number of dimensions %d\n", basic_to_string(current_basic), (int) current_nb_dim);
80 
81  /* FI: I do not understand this assert beacause an array may be
82  * referenced with a limited number of subscript to initialize a
83  * pointer.
84  */
85  //pips_assert("there should be no store effect on variable names\n",
86  // gen_length(current_l_ind) >= current_nb_dim);
87  if(gen_length(current_l_ind) <= current_nb_dim) {
88  // This is an array or sub-array element address computation
89  *exact_p = true;
90  return result;
91  }
92 
93  switch (basic_tag(current_basic))
94  {
95  case is_basic_pointer:
96  {
97  // no need to test if gen_length(current_l_ind) >= current_nb_dim because of previous assert
98  result = (int) current_nb_dim;
99  *exact_p = true;
100  break;
101  }
102  case is_basic_derived:
103  {
104  int i;
105  current_type = entity_type(basic_derived(current_basic));
106 
107  if (type_enum_p(current_type))
108  result = -1;
109  else
110  {
111  /*first skip array dimensions if any*/
112  for(i=0; i< (int) current_nb_dim; i++, POP(current_l_ind));
113 
114  if (same_string_p(entity_user_name(basic_derived(current_basic)), "_IO_FILE") && gen_length(current_l_ind) == 0)
115  {
116  pips_debug(8, "_IO_FILE_ array: no pointer dimension\n");
117  result = -1;
118  }
119  else
120  {
121  pips_assert("there must be at least one index left for the field\n", gen_length(current_l_ind) > 0);
122 
123  list l_fields = derived_type_fields(current_type);
124 
125  entity current_field_entity = effect_field_dimension_entity(EXPRESSION(CAR(current_l_ind)), l_fields);
126 
127  if (variable_phi_p(current_field_entity) || same_string_p(entity_local_name(current_field_entity), UNBOUNDED_DIMENSION_NAME))
128  {
129  while (!ENDP(l_fields))
130  {
131  int tmp_result = -1;
132  entity current_field_entity = ENTITY(CAR(l_fields));
133  type current_type = entity_basic_concrete_type(current_field_entity);
134  size_t current_nb_dim = gen_length(variable_dimensions(type_variable(current_type)));
135 
136  if (gen_length(CDR(current_l_ind)) >= current_nb_dim)
137  // consider this field only if it can be an effect on this field
138  tmp_result = effect_indices_first_pointer_dimension_rank(CDR(current_l_ind), current_type, exact_p);
139 
140  POP(l_fields);
141  if (tmp_result >= 0)
142  result = result < 0 ? tmp_result : (tmp_result <= result ? tmp_result : result);
143  }
144 
145  *exact_p = (result < 0);
146  if (result >= 0) result += i+1; // do not forget the field index and array dimensions!
147  }
148  else
149  {
150  current_type = entity_basic_concrete_type(current_field_entity);
151  pips_assert("current_type is of kind variable", type_variable_p(current_type));
152  result = effect_indices_first_pointer_dimension_rank(CDR(current_l_ind), current_type, exact_p);
153  if (result >=0) result += i+1; // do not forget the field index and array dimensions!
154  }
155  }
156  }
157  break;
158  }
159  default:
160  {
161  result = -1;
162  *exact_p = true;
163  break;
164  }
165  }
166 
167  pips_debug(8, "returning %d\n", result);
168  return result;
169 
170 }
#define variable_phi_p(e)
true if e is a phi variable PHI entities have a name like: REGIONS:PHI#, where # is a number.
static int effect_indices_first_pointer_dimension_rank(list current_l_ind, type current_type, bool *exact_p)
recursively walks thru current_l_ind and current_type in parallel until a pointer dimension is found.
Definition: type.c:72
entity effect_field_dimension_entity(expression exp, list l_fields)
type.c
Definition: type.c:51
#define same_string_p(s1, s2)
string basic_to_string(basic b)
RI-UTIL Library: Functions dealing with and constants related to PIPS intermediate representation ri....
Definition: type.c:87
#define UNBOUNDED_DIMENSION_NAME
Definition: ri-util-local.h:74
const char * entity_user_name(entity e)
Since entity_local_name may contain PIPS special characters such as prefixes (label,...
Definition: entity.c:487
const char * entity_local_name(entity e)
entity_local_name modified so that it does not core when used in vect_fprint, since someone thought t...
Definition: entity.c:453
list derived_type_fields(type t)
Definition: type.c:5354
#define type_enum_p(x)
Definition: ri.h:2968
@ is_basic_derived
Definition: ri.h:579
#define basic_tag(x)
Definition: ri.h:613

References basic_derived, basic_tag, basic_to_string(), CAR, CDR, derived_type_fields(), effect_field_dimension_entity(), ENDP, ENTITY, entity_basic_concrete_type(), entity_local_name(), entity_type, entity_user_name(), EXPRESSION, gen_length(), int, is_basic_derived, is_basic_pointer, pips_assert, pips_debug, POP, same_string_p, type_enum_p, type_to_string(), type_variable, type_variable_p, UNBOUNDED_DIMENSION_NAME, variable_basic, variable_dimensions, and variable_phi_p.

Referenced by effect_reference_first_pointer_dimension_rank().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ effect_reference_contains_pointer_dimension_p()

bool effect_reference_contains_pointer_dimension_p ( reference  ref,
bool exact_p 
)
Parameters
refis an effect reference
exact_pis a pointer to a bool, which is set to true if the result is not an approximation.
Returns
false if no index corresponds to a pointer dimension, false if any index may correspond to a pointer dimension. If this information is exact, *exact_p is set to true.
Parameters
refef
exact_pxact_p

Definition at line 219 of file type.c.

220 {
221  int pointer_rank;
222  pointer_rank = effect_reference_first_pointer_dimension_rank(ref, exact_p);
223  return (pointer_rank >= 0);
224 }
static int effect_reference_first_pointer_dimension_rank(reference ref, bool *exact_p)
walks thru ref indices and ref entity type arborescence in parallel until a pointer dimension is foun...
Definition: type.c:180

References effect_reference_first_pointer_dimension_rank(), and ref.

+ Here is the call graph for this function:

◆ effect_reference_dereferencing_p()

bool effect_reference_dereferencing_p ( reference  ref,
bool exact_p 
)
Parameters
refis an effect reference
exact_pis a pointer to a bool, which is set to true if the result is not an approximation.
Returns
true if the effect reference may dereference a pointer, false otherwise.

FI: ANY_MODULE:ANYWHERE should not be indexed because any indexing can be eliminated as it results in ANY_MODULE:ANYWHERE

FI: ANY_MODULE:ANYWHERE_b0, 1, 2 should not be indexed because any indexing can be eliminated and the reference replaced by a non-indexed reference to ANY_MODULE:ANYWHERE_bi , j, k depending on the type of the reference.

no dereferencement if scalar reference, in particular, gets rid of non store effect references

Parameters
refef
exact_pxact_p

Definition at line 233 of file type.c.

234 {
235  list l_ind = reference_indices(ref);
236  bool result;
237  int p_rank;
239 
240  //if (entity_all_locations_p(reference_variable(ref)))
242  {
243  if(ENDP(l_ind)) {
244  // result = true;
245  result = false;
246  *exact_p = false;
247  }
248  else {
249  if(entity_all_locations_p(e)) {
250  /* FI: *ANY_MODULE*:*ANYWHERE* should not be indexed because
251  * any indexing can be eliminated as it results in
252  * *ANY_MODULE*:*ANYWHERE*
253  */
254  pips_internal_error("Unexpected indexing of an abstract location.\n");
255  }
257  /* FI: *ANY_MODULE*:*ANYWHERE*_b0, 1, 2 should not be
258  * indexed because any indexing can be eliminated and the
259  * reference replaced by a non-indexed reference to
260  * *ANY_MODULE*:*ANYWHERE*_bi , j, k depending on the type
261  * of the reference.
262  */
263  pips_internal_error("Unexpected indexing of an abstract location.\n");
264  }
265  else {
267 
268  if (p_rank == -1)
269  result = false;
270  else
271  result = p_rank < (int) gen_length(l_ind);
272  }
273  }
274  }
275  else
276  {
277  if (ENDP(l_ind)) /* no dereferencement if scalar reference, in particular, gets rid
278  of non store effect references */
279  p_rank = -1;
280  else
282 
283  if (p_rank == -1)
284  result = false;
285  else
286  result = p_rank < (int) gen_length(l_ind);
287  }
288  return result;
289 }
bool entity_abstract_location_p(entity al)
bool entity_all_locations_p(entity e)
test if an entity is the top of the lattice
bool entity_typed_anywhere_locations_p(entity e)
Test if an entity is the bottom of the lattice.

References effect_reference_first_pointer_dimension_rank(), ENDP, entity_abstract_location_p(), entity_all_locations_p(), entity_typed_anywhere_locations_p(), gen_length(), int, pips_internal_error, ref, reference_indices, and reference_variable.

Referenced by can_be_constant_path_p(), convex_effect_to_constant_path_effects_with_pointer_values(), convex_effect_to_constant_path_effects_with_points_to(), effect_to_constant_path_effects_with_points_to(), generic_eval_cell_with_points_to(), references_may_conflict_p(), and simple_effect_to_constant_path_effects_with_pointer_values().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ effect_reference_first_pointer_dimension_rank()

static int effect_reference_first_pointer_dimension_rank ( reference  ref,
bool exact_p 
)
static

walks thru ref indices and ref entity type arborescence in parallel until a pointer dimension is found.

Parameters
refis an effect reference
exact_pis a pointer to a bool, which is set to true if the result is not an approximation.
Returns
-1 if no index corresponds to a pointer dimension, the rank of the least index that may correspond to a pointer dimension in current_l_ind otherwise. If this information is exact, *exact_p is set to true.

if (FILE_star_effect_reference_p(ref))

Definition at line 180 of file type.c.

181 {
183  list current_l_ind = reference_indices(ref);
184  type ent_type = entity_basic_concrete_type(ent);
185  int result;
186 
187  pips_debug(8, "input reference : %s\n", words_to_string(effect_words_reference(ref)));
188 
189  if (!type_variable_p(ent_type))
190  {
191  result = -1;
192  }
193  else
194  {
195  if (false)
196  /* if (FILE_star_effect_reference_p(ref)) */
197  {
198  result = 0;
199  *exact_p = true;
200  }
201  else
202  {
203  type current_type = entity_basic_concrete_type(ent);
204  result = effect_indices_first_pointer_dimension_rank(current_l_ind, current_type, exact_p);
205  }
206  }
207 
208  pips_debug(8, "returning %d\n", result);
209  return result;
210 
211 }
list effect_words_reference(reference)
prettyprint.c
Definition: prettyprint.c:68
string words_to_string(cons *lw)
Definition: print.c:211

References effect_indices_first_pointer_dimension_rank(), effect_words_reference(), entity_basic_concrete_type(), pips_debug, ref, reference_indices, reference_variable, type_variable_p, and words_to_string().

Referenced by effect_reference_contains_pointer_dimension_p(), and effect_reference_dereferencing_p().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ eliminate_calls_to_unbounded()

static expression eliminate_calls_to_unbounded ( expression  e)
static

Allocate a copy of expression "e" where calls to the unbounded function are replaced by calls to the zero function so that typing can be performed.

Definition at line 584 of file type.c.

585 {
587  return e;
588 }
static void substitute_unbounded_call(call c)
Definition: type.c:570
#define gen_recurse(start, domain_number, flt, rwt)
Definition: genC.h:283
bool gen_true(__attribute__((unused)) gen_chunk *unused)
Return true and ignore the argument.
Definition: genClib.c:2780
#define call_domain
newgen_callees_domain_defined
Definition: ri.h:58

References call_domain, gen_recurse, gen_true(), and substitute_unbounded_call().

Referenced by points_to_expression_to_type().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ find_points_to_subscript_for_type()

list find_points_to_subscript_for_type ( cell  c,
type  t 
)

Find the subscript in the reference of cell "c" that would make the reference type be "t" if the subscript list were truncated just after it.

Select the longest possible subscript list.

Core dump if it is not possible.

No smart implementation: trial and error (probably already implemented somewhere else.

Let's try to add a zero subscript instead...

For the time being, no need to restore the reference in case of failure.

Definition at line 1274 of file type.c.

1275 {
1276  list csl = list_undefined;
1278  entity v = reference_variable(r);
1279  type rt = points_to_reference_to_concrete_type(r); // reference type
1280  list sl = reference_indices(r); // subscript list
1281  list rsl = gen_nreverse(sl); // temporary side-effect on "r" (and "c")
1282  list crsl = rsl; // current reverse subscript list
1283 
1284  while(!array_pointer_type_equal_p(t, rt) && !ENDP(crsl)) {
1285  POP(crsl);
1286  list nsl = gen_copy_seq(crsl);
1287  reference nr = make_reference(v, nsl);
1289  reference_indices(nr) = NIL;
1290  free_reference(nr);
1291  }
1292 
1294 
1295  if(!ENDP(crsl)) {
1296  csl = crsl;
1297  }
1298  else {
1299  if(array_pointer_type_equal_p(t, rt)) {
1300  // dereferencing18.c: only one element is allocated. 0 is the
1301  // only possible subscript;
1302  csl = NIL; // ==crsl
1303  }
1304  else {
1305  /* Let's try to add a zero subscript instead... */
1307  list nsl = CONS(EXPRESSION, z, NIL);
1308  /* For the time being, no need to restore the reference in case of
1309  failure. */
1312  if(array_pointer_type_equal_p(t, rt))
1313  csl = nsl;
1314  else
1315  pips_internal_error("Type t and reference r are incompatible.\n");
1316  }
1317  }
1318 
1319  return csl;
1320 }
void free_reference(reference p)
Definition: ri.c:2050
reference make_reference(entity a1, list a2)
Definition: ri.c:2083
type points_to_reference_to_concrete_type(reference r)
Definition: type.c:685
reference cell_any_reference(cell)
API for reference.
Definition: effects.c:77
list gen_nreverse(list cp)
reverse a list in place
Definition: list.c:304
list gen_copy_seq(list l)
Copy a list structure.
Definition: list.c:501
#define CONS(_t_, _i_, _l_)
List element cell constructor (insert an element at the beginning of a list)
Definition: newgen_list.h:150
list gen_nconc(list cp1, list cp2)
physically concatenates CP1 and CP2 but do not duplicates the elements
Definition: list.c:344
#define list_undefined
Undefined list definition :-)
Definition: newgen_list.h:69
expression make_zero_expression(void)
Make a zero expression.
Definition: expression.c:1212

References array_pointer_type_equal_p(), cell_any_reference(), CONS, ENDP, EXPRESSION, free_reference(), gen_copy_seq(), gen_nconc(), gen_nreverse(), list_undefined, make_reference(), make_zero_expression(), NIL, pips_internal_error, points_to_reference_to_concrete_type(), POP, reference_indices, and reference_variable.

Referenced by offset_points_to_cell().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ points_to_cell_to_concrete_type()

type points_to_cell_to_concrete_type ( cell  c)

◆ points_to_cell_to_type()

◆ points_to_cell_types_compatibility()

void points_to_cell_types_compatibility ( cell  l,
cell  r 
)

Make sure that cell l can points towards cell r.

FI-AM/FC: Unfortunately, a lot of specification work is missing to develop this function while taking care of abstract locations and their lattice.

  1. Restrictions on cell "l"

    1.1 "l" cannot be the abstract nowhere/undefined cell

...

Note: this should be part of points_to_set_consistent_p(), which is called consistent_points_to_set(), but this function goes beyond checking the compatibility. It enforces it when legal and possible.

Maybe this function should be relocated in alias-classes

Beware of possible side-effects on l

FI, 10 August 2012: this function is a mess. No side effect should be applied. it should be redesigned to check compatibility cases one after the other and it should be renamed points_to_cell_types_compatibility_p()

FI, 14 August 2012: the dimension of the sink entity and sink reference must be greater than the dimension of the source reference. This is not checked yet.

FI, 19 August 2012: all cells used in a points-to arc must be scalar, either pointers or basic types

&& overloaded_type_p(urt)

The source points towards an array and the cell is an element of this array.

Formal parameters and potentially stubs can be assumed to points towards an array although they are declared as pointers to a scalar.

This should never be a problem when sink cells are always array elements and not arrays.

Here we may be in trouble because of the heap modeling malloc() returns by default a "void *", or sometimes a "char *" which may be casted into anything...

The dimension of the allocated array should be given by the size of the pointed type and by the size of the right type.

Also, we have different heap modelling, with different flexibilities

& !all_heap_locations_typed_cell_p(r)

all_heap_locations_typed_cell_p(r)

There must be a typing issue.

This may happen with the heap model

Is it an (implicit) array of pointers

This may happen with the heap model

Definition at line 985 of file type.c.

986 {
988  if(null_cell_p(r))
989  ;
991  // FI: I'm not sure enought filtering has been performed... to
992  // have here type information, especially with an anywhere or a
993  // nowhere/undefined not typed
994 
995  // FI : tests supplementaires pour eviter les cells qui ne sont pas typees:-(
996 
997  bool l_to_be_freed, r_to_be_freed;
998  type lt = points_to_cell_to_type(l, &l_to_be_freed);
999  type rt = points_to_cell_to_type(r, &r_to_be_freed);
1002  if(C_pointer_type_p(ult)) {
1003  type pt = pointer_type_p(ult) ?
1006 
1007  // Several options are possible
1008 
1009  bool get_bool_property(const char *);
1010  if(array_pointer_type_equal_p(pt, urt))
1011  ; // the pointed type is the type of the right cell
1012  // FI: we could/should add a compatibility type between void
1013  // and any scalar type
1014  // The problem occurs in Pointers/fulguro13 because a cast is
1015  // not processed:
1016  // fgUINT16 *array_s = (fgUINT16 *) vct->array;
1017  // FI->AM/FC/PJ: we need a trick to handle the casts or the
1018  // typing of the points-to graph is not possible
1019  else if(scalar_type_p(pt) && type_void_p(urt)) {
1020  // A void * pointer may be assigned to anything?
1021  ; // OK, they are compatible...
1022  }
1023  else if(type_void_p(pt) /* && overloaded_type_p(urt)*/ ) {
1024  // a void * is expected to point toward any type, which is
1025  // encoded with overloaded but could be anything when casts
1026  // or functions, user or intrinsic, are used. See fulguro03.c
1027  ;
1028  }
1029  else if(overloaded_type_p(urt)) {
1030  // This is compatible with any pointed type pt by definition
1031  // of overloaded. See fulguro03.c
1032  ;
1033  }
1034  else if(array_type_p(pt) && scalar_type_p(urt)) {
1035  /* The source points towards an array and the cell is an
1036  element of this array. */
1038  basic rb = variable_basic(type_variable(urt));
1039  if(basic_equal_p(pb, rb)) {
1040  ; // OK
1041  }
1042  else {
1043  pips_internal_error("???");
1044  }
1045  }
1046  else if(array_type_p(urt)
1047  && !get_bool_property("POINTS_TO_STRICT_POINTER_TYPES")) {
1048  /* Formal parameters and potentially stubs can be assumed to
1049  * points towards an array although they are declared as
1050  * pointers to a scalar.
1051  *
1052  * This should never be a problem when sink cells are always
1053  * array elements and not arrays.
1054  */
1055  if(type_variable_p(pt)) {
1057  basic rb = variable_basic(type_variable(urt));
1058  if(basic_equal_p(pb,rb)) {
1059  ; // OK, they are compatible
1060  }
1061  else {
1062  fprintf(stderr, "Type pointed by source \"pt\": \"");
1063  print_type(pt);
1064  fprintf(stderr, "\"\nSink type \"urt\": \"");
1065  print_type(urt);
1066  pips_internal_error("\"\nIncompatible basics.\n");
1067  }
1068  }
1069  else {
1070  fprintf(stderr, "Pointed type \"pt\": ");
1071  print_type(pt);
1072  pips_internal_error("Unexpected type \"pt\".\n");
1073  }
1074  }
1075  else if(array_type_p(urt)
1076  && get_bool_property("POINTS_TO_STRICT_POINTER_TYPES")) {
1077  // Pointers/assignment10.c
1078  if(type_variable_p(pt)) {
1080  basic rb = variable_basic(type_variable(urt));
1081  if(basic_equal_p(pb,rb)) {
1082  // OK, they are compatible, but r must be subscripted
1084  }
1085  else {
1086  fprintf(stderr, "Type pointed by source \"pt\": \"");
1087  print_type(pt);
1088  fprintf(stderr, "\"\nSink type \"urt\": \"");
1089  print_type(urt);
1090  pips_internal_error("\"\nIncompatible basics.\n");
1091  }
1092  }
1093  }
1094  else if(type_functional_p(urt)) {
1095  // FI->AM: we should check that the function is a constant
1096  // with no parameters
1097  type ret_t = functional_result(type_functional(urt));
1098  type u_ret_t = compute_basic_concrete_type(ret_t);
1099  if(pointer_type_p(u_ret_t)) {
1100  pips_internal_error("This should be useless.\n");
1101  // FI->AM: must be useless... Designed for C constant strings, but...
1102  type p_u_ret_t = type_to_pointed_type(u_ret_t);
1103  if(array_pointer_type_equal_p(pt, p_u_ret_t))
1104  ;
1105  else
1106  pips_internal_error("Type mismatch.\n");
1107  free_type(u_ret_t);
1108  }
1109  else if(string_type_p(u_ret_t)) {
1110  // FI: hidden pointer...
1111  // char * fmt; ftm = "foo";
1112  variable ptv = type_variable(pt);
1113  basic ptb = variable_basic(ptv);
1114  if(basic_int_p(ptb) && basic_int(ptb)==1)
1115  ; // char
1116  else
1117  pips_internal_error("Illegal string assignment...\n");
1118  }
1119  else {
1120  pips_internal_error("Illegal assignment to pointer...\n");
1121  }
1122  }
1123  else {
1124  /* Here we may be in trouble because of the heap modeling
1125  * malloc() returns by default a "void *", or sometimes a
1126  * "char *" which may be casted into anything...
1127  *
1128  * The dimension of the allocated array should be given by
1129  * the size of the pointed type and by the size of the right
1130  * type.
1131  *
1132  * Also, we have different heap modelling, with different flexibilities
1133  */
1135  /*&& !all_heap_locations_typed_cell_p(r) */) {
1136  pips_internal_error("Type mistake for heap allocation. Probably a user error. It should have been trapped at a higher level.\n");
1137  type nt = copy_type(pt);
1138  if(array_type_p(nt)
1139  || get_bool_property("POINTS_TO_STRICT_POINTER_TYPES"))
1140  ; // Do not add a dimension to an existing array.
1141  else if(!type_void_p(nt)) {
1142  variable v = type_variable(nt);
1144  // FI FI FI: should be computed... and checked
1146  dimension d = make_dimension(z, s, NIL);
1148  }
1149  // FI: could be a function entity_type_substitution()...
1150  // but interference with r_to_be_freed
1151  r_to_be_freed = true;
1152  reference rr = cell_any_reference(r);
1153  entity rv = reference_variable(rr);
1154  // This assignment breaks the internal consistency of heap modelling
1156  pips_internal_error("Incompatible types for \"%s\".\n",
1157  entity_name(rv));
1158  entity_type(rv) = nt;
1159  }
1160  else if(all_heap_locations_cell_p(r))
1161  ; // always compatible
1162  else if(false /* all_heap_locations_typed_cell_p(r)*/)
1163  ; // FI: I am not sure what to do...
1164  else if(null_cell_p(r)) {
1165  ; // always compatible
1166  }
1167  else if(anywhere_cell_p(r)) {
1168  ; // not typed anywhere, always compatible
1169  }
1170  else if(nowhere_cell_p(r)) {
1171  ; // not typed nowhere/undefined, always compatible
1172  }
1173  else {
1174  /* There must be a typing issue. */
1175  fprintf(stderr, "Type pointed by source cell, \"pt\": \"");
1176  void print_points_to_cell(cell); // FI: library organization
1178  fprintf(stderr, "\" with type: \"");
1179  print_type(pt);
1180  fprintf(stderr, "\"\nType of sink cell, \"urt\": \"");
1182  fprintf(stderr, "\" with type: \"");
1183  print_type(urt);
1184  fprintf(stderr, "\"\n");
1185  pips_internal_error("Incompatible Types.\n");
1186  }
1187  }
1188  }
1189  else if(array_type_p(ult)) {
1190  /* This may happen with the heap model */
1191  extern bool get_bool_property(const char *);
1192  if(!get_bool_property("POINTS_TO_STRICT_POINTER_TYPES")) {
1193  /* Is it an (implicit) array of pointers*/
1194  basic ultb = variable_basic(type_variable(ult));
1195  if(basic_pointer_p(ultb)) { // Array
1196  // FI: "pt" should be freed later...
1197  // FI: should have been done earlier when building l
1198  // reference lr = cell_any_reference(l);
1199  // reference_add_zero_subscripts(lr, ult);
1202  // FI: subscripts must be added to the source reference lr
1203  // FI: implicit typing of pointers as array of pointers
1204  reference lr = cell_any_reference(l);
1206  }
1207  else {
1208  // FI: error message could be improved...
1209  pips_internal_error("Incompatible types.\n");
1210  }
1211  }
1212  else
1213  pips_internal_error("Not an array of pointers.\n");
1214  }
1215  else
1216  pips_internal_error("The source is an array but not a pointer.\n");
1217  }
1218  else if(overloaded_type_p(ult)) {
1219  /* This may happen with the heap model */
1220  ; // A pointer type is assumed
1221  }
1222  else {
1223  // Could be checked by points_to_source_cell_compatible_p()
1224  pips_internal_error("The source is not a pointer.\n");
1225  }
1226 
1227  if(l_to_be_freed) free_type(lt);
1228  if(r_to_be_freed) free_type(rt);
1229  free_type(ult), free_type(urt);
1230  }
1231  }
1232  return;
1233 }
dimension make_dimension(expression a1, expression a2, list a3)
Definition: ri.c:565
bool points_to_sink_cell_compatible_p(cell c __attribute__((unused)))
Definition: type.c:1258
bool points_to_source_cell_compatible_p(cell c)
Definition: type.c:1241
bool anywhere_cell_p(cell)
Is it an anywhere cell?
Definition: effects.c:367
bool all_heap_locations_cell_p(cell)
Definition: effects.c:432
bool nowhere_cell_p(cell)
Target of an undefined pointer.
Definition: effects.c:455
bool null_cell_p(cell)
Definition: effects.c:466
void points_to_cell_add_zero_subscripts(cell)
Definition: effects.c:1615
bool heap_cell_p(cell)
Any heap cell, more or less abstract or typed.
Definition: effects.c:420
bool get_bool_property(const string)
FC 2015-07-20: yuk, moved out to prevent an include cycle dependency include "properties....
#define print_points_to_cell(x)
Definition: print.c:377
void print_type(type t)
For debugging.
Definition: type.c:111
void reference_add_zero_subscripts(reference r, type t)
Definition: expression.c:261
expression make_unbounded_expression()
Definition: expression.c:4339
expression int_to_expression(_int i)
transform an int into an expression and generate the corresponding entity if necessary; it is not cle...
Definition: expression.c:1188
bool array_type_p(type t)
Definition: type.c:2942
bool type_equal_up_to_typedefs_and_qualifiers_p(type t1, type t2)
Definition: type.c:557
bool string_type_p(type t)
Definition: type.c:2854
type type_to_pointed_type(type t)
returns t if t is not a pointer type, and the pointed type if t is a pointer type.
Definition: type.c:5265
type array_type_to_element_type(type t)
returns the type of the elements of an array type, as a newly allocated type.
Definition: type.c:5700
bool pointer_type_p(type t)
Check for scalar pointers.
Definition: type.c:2993
bool scalar_type_p(type t)
Definition: type.c:2955
bool overloaded_type_p(type t)
Returns true if t is a variable type with a basic overloaded.
Definition: type.c:2666
bool C_pointer_type_p(type t)
Returns OK for "char[]" as well as for "char *".
Definition: type.c:3011
#define functional_result(x)
Definition: ri.h:1444
#define basic_int_p(x)
Definition: ri.h:614
#define basic_int(x)
Definition: ri.h:616
#define type_functional(x)
Definition: ri.h:2952
int fprintf()
test sc_min : ce test s'appelle par : programme fichier1.data fichier2.data ...

References all_heap_locations_cell_p(), anywhere_cell_p(), array_pointer_type_equal_p(), array_type_p(), array_type_to_element_type(), basic_equal_p(), basic_int, basic_int_p, basic_pointer, basic_pointer_p, C_pointer_type_p(), cell_any_reference(), compute_basic_concrete_type(), CONS, copy_type(), DIMENSION, entity_name, entity_type, fprintf(), free_type(), functional_result, get_bool_property(), heap_cell_p(), int_to_expression(), make_dimension(), make_unbounded_expression(), NIL, nowhere_cell_p(), null_cell_p(), overloaded_type_p(), pips_internal_error, pointer_type_p(), points_to_cell_add_zero_subscripts(), points_to_cell_to_type(), points_to_sink_cell_compatible_p(), points_to_source_cell_compatible_p(), print_points_to_cell, print_type(), reference_add_zero_subscripts(), reference_variable, scalar_type_p(), string_type_p(), type_equal_up_to_typedefs_and_qualifiers_p(), type_functional, type_functional_p, type_to_pointed_type(), type_variable, type_variable_p, type_void_p, variable_basic, and variable_dimensions.

Referenced by create_stub_points_to(), and gen_may_constant_paths().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ points_to_expression_to_concrete_type()

type points_to_expression_to_concrete_type ( expression  e)

The type returned is stored in a hash-table.

It should not be freed. See compute_basic_concrete_type().

This function is useful to avoid the conditional free.

Definition at line 617 of file type.c.

618 {
619  bool to_be_freed;
620  type t = points_to_expression_to_type(e, &to_be_freed);
622  if(to_be_freed) free_type(t);
623  return ct;
624 }
type points_to_expression_to_type(expression e, bool *to_be_freed)
FI: I need more generality than is offered by expression_to_type() because fields are assimilated to ...
Definition: type.c:592

References compute_basic_concrete_type(), free_type(), and points_to_expression_to_type().

Referenced by binary_intrinsic_call_to_points_to_sinks(), expression_to_points_to_cells(), freed_list_to_points_to(), intrinsic_call_condition_to_points_to(), intrinsic_call_to_points_to(), memory_dereferencing_p(), semantics_expression_to_points_to_sinks(), and unary_intrinsic_call_to_points_to_sinks().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ points_to_expression_to_pointed_type()

type points_to_expression_to_pointed_type ( expression  e)

Return a new allocated type "t" of the address pointed by expression "e", if expression "e" denotes an address.

"t" should not be freed.

We should return a pointer towards an array of dimension n-1. The first dimension is lost.

Build the pointed type, copy of cet except for its first dimension

Build the poiinter type

Definition at line 631 of file type.c.

632 {
633  type t = type_undefined;
634  bool to_be_freed;
635  type et = points_to_expression_to_type(e, &to_be_freed);
637  if(to_be_freed) free_type(et);
638 
639  if(pointer_type_p(cet)) {
640  type pt = type_to_pointed_type(cet);
642  }
643  else if(array_type_p(cet)) {
644  /* We should return a pointer towards an array of dimension
645  n-1. The first dimension is lost. */
646  variable cet_v = type_variable(cet);
647  list cet_v_dl = variable_dimensions(cet_v);
648  /* Build the pointed type, copy of cet except for its first dimension */
649  list ndl = gen_full_copy_list(CDR(cet_v_dl));
650  basic nat_b = copy_basic(variable_basic(cet_v));
651  variable nat_v = make_variable(nat_b, ndl, NIL);
652  type nat = make_type_variable(nat_v);
653  /* Build the poiinter type*/
654  // variable v = type_variable(nat);
655  basic b = make_basic_pointer(nat);
656  variable v = make_variable(b, NIL, NIL);
657  t = make_type_variable(v);
658  }
659  else
660  pips_internal_error("Arg. is not in definition domain.\n");
661  return t;
662 }
type make_type_variable(variable _field_)
Definition: ri.c:2715
basic copy_basic(basic p)
BASIC.
Definition: ri.c:104
basic make_basic_pointer(type _field_)
Definition: ri.c:179
list gen_full_copy_list(list l)
Copy a list structure with element copy.
Definition: list.c:535

References array_type_p(), CDR, compute_basic_concrete_type(), copy_basic(), copy_type(), free_type(), gen_full_copy_list(), make_basic_pointer(), make_type_variable(), make_variable(), NIL, pips_internal_error, pointer_type_p(), points_to_expression_to_type(), type_to_pointed_type(), type_undefined, type_variable, variable_basic, and variable_dimensions.

Referenced by expression_to_points_to_sinks_with_offset(), and unary_intrinsic_call_to_points_to_sinks().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ points_to_expression_to_type()

type points_to_expression_to_type ( expression  e,
bool to_be_freed 
)

FI: I need more generality than is offered by expression_to_type() because fields are assimilated to subscripts.

In order to type t[*] as well as t[0]...

Parameters
to_be_freedo_be_freed

Definition at line 592 of file type.c.

593 {
594  type t = type_undefined;
595  syntax s = expression_syntax(e);
596  if(syntax_reference_p(s)) {
598  t = points_to_reference_to_type(r, to_be_freed);
599  }
600  else {
601  /* In order to type t[*] as well as t[0]... */
602  expression ne = copy_expression(e);
604  *to_be_freed = true;
605  t = expression_to_type(ne);
606  free_expression(ne);
607  }
608 
609  return t;
610 }
expression copy_expression(expression p)
EXPRESSION.
Definition: ri.c:850
void free_expression(expression p)
Definition: ri.c:853
static expression eliminate_calls_to_unbounded(expression e)
Allocate a copy of expression "e" where calls to the unbounded function are replaced by calls to the ...
Definition: type.c:584
type expression_to_type(expression exp)
For an array declared as int a[10][20], the type returned for a[i] is int [20].
Definition: type.c:2486
#define syntax_reference_p(x)
Definition: ri.h:2728
#define syntax_reference(x)
Definition: ri.h:2730
#define expression_syntax(x)
Definition: ri.h:1247

References copy_expression(), eliminate_calls_to_unbounded(), expression_syntax, expression_to_type(), free_expression(), points_to_reference_to_type(), syntax_reference, syntax_reference_p, and type_undefined.

Referenced by assignment_to_points_to(), check_rhs_value_types(), expression_to_points_to_sources(), pointer_arithmetic_to_points_to(), points_to_expression_to_concrete_type(), points_to_expression_to_pointed_type(), and subscript_to_points_to_sinks().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ points_to_reference_to_concrete_type()

◆ points_to_reference_to_type()

type points_to_reference_to_type ( reference  ref,
bool to_be_freed 
)

FI: I need more generality than is offered by cell_to_type()

Maybe because of fields.

Surely because of implicit arrays linked to scalar pointers

Parameters
refef
to_be_freedo_be_freed

Definition at line 527 of file type.c.

528 {
529  type t = type_undefined;
530 
532  list sl = reference_indices(ref);
533 
534  if(ENDP(sl)) {
535  t = entity_type(v);
536  *to_be_freed = false;
537  }
538  else {
539  int ns = (int) gen_length(sl);
540  expression fs = EXPRESSION(CAR(sl));
541  bool int_p = expression_integer_constant_p(fs);
542  // FI: faire un cas particulier pour des cas comme i[1] ou i est un scalaire?
543  // FI: I do not know what can happen with struct objects; they are
544  // scalar, a dimension may be added and nevertheless a field may be
545  // accessed....
546  if(entity_scalar_p(v) && ns==1 && int_p) {
547  *to_be_freed = false;
548  t = entity_type(v);
549  }
550  else {
551  expression ls = EXPRESSION(CAR(gen_last(sl)));
552  syntax lss = expression_syntax(ls);
553  if(syntax_reference_p(lss)) {
554  reference r = syntax_reference(lss);
556  if(entity_field_p(f)) {
557  t = entity_type(f);
558  *to_be_freed = false;
559  }
560  }
561  }
562  }
563 
564  if(type_undefined_p(t))
565  t = cell_reference_to_type(ref, to_be_freed);
566 
567  return t;
568 }
int f(int off1, int off2, int n, float r[n], float a[n], float b[n])
Definition: offsets.c:15
bool entity_field_p(entity e)
e is the field of a structure
Definition: entity.c:857
bool expression_integer_constant_p(expression e)
Definition: expression.c:2417
bool entity_scalar_p(entity)
The concrete type of e is a scalar type.
Definition: variable.c:1113
#define type_undefined_p(x)
Definition: ri.h:2884

References CAR, cell_reference_to_type(), ENDP, entity_field_p(), entity_scalar_p(), entity_type, EXPRESSION, expression_integer_constant_p(), expression_syntax, f(), gen_last(), gen_length(), int, ref, reference_indices, reference_variable, syntax_reference, syntax_reference_p, type_undefined, and type_undefined_p.

Referenced by adapt_reference_to_type(), create_scalar_stub_sink_cell(), gen_may_constant_paths(), gen_must_constant_paths(), opkill_may_constant_path(), opkill_must_constant_path(), points_to_cell_to_type(), points_to_expression_to_type(), points_to_reference_to_concrete_type(), points_to_reference_to_typed_index(), and reference_add_field_dimension().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ points_to_sink_cell_compatible_p()

bool points_to_sink_cell_compatible_p ( cell c   __attribute__(unused))

Definition at line 1258 of file type.c.

1259 {
1260  bool compatible_p = true;
1261 
1262  return compatible_p;
1263 }

Referenced by points_to_cell_types_compatibility().

+ Here is the caller graph for this function:

◆ points_to_source_cell_compatible_p()

bool points_to_source_cell_compatible_p ( cell  c)

Definition at line 1241 of file type.c.

1242 {
1243  bool compatible_p = true;
1244 
1245  if(nowhere_cell_p(c))
1246  compatible_p = false;
1247  else if(null_cell_p(c))
1248  compatible_p = false;
1249 
1250  return compatible_p;
1251 }

References nowhere_cell_p(), and null_cell_p().

Referenced by points_to_cell_types_compatibility().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ r_cell_reference_to_type()

static type r_cell_reference_to_type ( list  ref_l_ind,
type  current_type,
bool to_be_freed 
)
static

Lines 291 to 682.

r_cell_reference_to_type cell_reference_to_type(reference ref, bool *to_be_freed) cell_to_type(cell c, bool * to_be_freed)

points_to_reference_to_type(reference r, bool * to_be_freed)

substitute_unbounded_call eliminate_calls_to_unbounded(expression e)

points_to_expression_to_type points_to_expression_to_concrete_type points_to_expression_to_pointed_type

points_to_cell_to_type points_to_cell_to_concrete_type

points_to_reference_to_concrete_type(reference r) cell references

the return type

current basic

current type array dimensions

the remainder of the function heavily relies on the following assumption

We have reached the current type and there are no array dimensions to skip

skip common array dimensions if any

We have reached the current basic

Warning : qualifiers are set to NIL, because I do not see the need for something else for the moment. BC.

Sub arrays are pointers to arrays, not arrays, at least for gcc

a[10][20][30] -> a is int (*)[20][30] -> a[1] is int *[30] -> a[1][2] is int *

Beatrice's version

The cell reference contains indices that go beyond the current type array dimensions. This can happen if and only if the current basic is a pointer or a derived (typedef have been eliminated by the use of basic_concrete_type).

if the input type is a bct, then I think there is no need to compute the bct of a basic_pointer. BC.

ype new_current_type = compute_basic_concrete_type(basic_pointer(current_basic));

pop the pointer dimension

free_type(new_current_type);

the next reference index should be a field entity

pop the field dimension

Definition at line 315 of file type.c.

316 {
317  type t = type_undefined; /* the return type */
318 
319  switch (type_tag(current_type))
320  {
321  case is_type_variable:
322  {
323  basic current_basic = variable_basic(type_variable(current_type)); /* current basic */
324  list l_current_dim = variable_dimensions(type_variable(current_type)); /* current type array dimensions */
325  int current_nb_dim = gen_length(l_current_dim);
326  int ref_l_ind_nb_dim = (int) gen_length(ref_l_ind);
327  int common_nb_dim = MIN(current_nb_dim, ref_l_ind_nb_dim);
328 
329  pips_debug(8, "input type : %s\n", type_to_string(current_type));
330  pips_debug(8, "current_basic : %s, and number of dimensions %d\n", basic_to_string(current_basic), current_nb_dim);
331  pips_debug(8, "common number of dimensions: %d\n", common_nb_dim);
332  /* the remainder of the function heavily relies on the following assumption */
333  //pips_assert("there should be no memory access paths to variable names\n", (int) gen_length(ref_l_ind) >= current_nb_dim);
334 
335  if (ENDP(ref_l_ind)) /* We have reached the current type and there are no array dimensions to skip */
336  {
337  t = current_type;
338  *to_be_freed = false;
339  }
340  else
341  {
342  /* skip common array dimensions if any */
343  for(int i=0; i< common_nb_dim; i++, POP(ref_l_ind), POP(l_current_dim));
344 
345  if (ENDP(ref_l_ind)) /* We have reached the current basic */
346  {
347  /* Warning : qualifiers are set to NIL, because I do not see
348  the need for something else for the moment. BC.
349  */
350  /* Sub arrays are pointers to arrays, not arrays, at least for gcc
351  *
352  * a[10][20][30] -> a is int (*)[20][30]
353  * -> a[1] is int *[30]
354  * -> a[1][2] is int *
355  */
356  if(ENDP(l_current_dim)) {
357  /* Beatrice's version */
359  make_variable(copy_basic(current_basic),
360  gen_full_copy_list(l_current_dim),
361  NIL));
362  }
363  else {
364  list n_dims = CDR(l_current_dim);
366  make_variable(copy_basic(current_basic),
367  gen_full_copy_list(n_dims),
368  NIL));
369  t = type_to_pointer_type(t);
370  }
371  *to_be_freed = true;
372  }
373  else
374  {
375  /* The cell reference contains indices that go beyond the current type array dimensions.
376  This can happen if and only if the current basic is a pointer or a derived
377  (typedef have been eliminated by the use of basic_concrete_type).
378  */
379  switch (basic_tag(current_basic))
380  {
381  case is_basic_pointer:
382  {
383  /* if the input type is a bct, then I think there is no need to compute the bct of a basic_pointer. BC.*/
384  /*type new_current_type = compute_basic_concrete_type(basic_pointer(current_basic));*/
385  type new_current_type = basic_pointer(current_basic);
386  POP(ref_l_ind); /* pop the pointer dimension */
387  t = r_cell_reference_to_type(ref_l_ind, new_current_type, to_be_freed);
388  /* free_type(new_current_type);*/
389  break;
390  }
391  case is_basic_derived:
392  {
393  /* the next reference index should be a field entity */
394  expression next_index = EXPRESSION(CAR(ref_l_ind));
395  syntax s = expression_syntax(next_index);
396  if (syntax_reference_p(s))
397  {
398  entity next_index_e = reference_variable(syntax_reference(s));
399  if (entity_field_p(next_index_e))
400  {
401  type new_current_type = entity_basic_concrete_type(next_index_e);
402  POP(ref_l_ind); /* pop the field dimension */
403  t = r_cell_reference_to_type(ref_l_ind, new_current_type, to_be_freed);
404  }
405  else
406  pips_internal_error("the current basic tag is derived, but corresponding index is not a field entity");
407  }
408  else
409  pips_internal_error("the current basic tag is derived, but corresponding index is not a reference");
410  break;
411  }
412  case is_basic_overloaded:
413  {
414  t = current_type;
415  *to_be_freed = false;
416  break;
417  }
418  default:
419  {
420  pips_internal_error("unexpected basic tag");
421  }
422  }
423  }
424  }
425 
426  ifdebug(8)
427  {
428  if (type_variable_p(t))
429  {
430  variable v = type_variable(t);
431  pips_debug(8, "output type is: %s\n", type_to_string(t));
432  pips_debug(8, "with basic : %s, and number of dimensions %d\n",
434  (int) gen_length(variable_dimensions(v)));
435  pips_debug(8, "*to_be_freed = %s\n", *to_be_freed? "true": "false");
436  }
437  }
438  break;
439  }
440  case is_type_void:
441  {
442  t = copy_type(current_type);
443  *to_be_freed = true;
444 
445  ifdebug(8)
446  {
447  pips_debug(8, "output type is: void\n");
448  pips_debug(8, "*to_be_freed = true\n");
449  }
450  break;
451  }
452  default:
453  pips_internal_error("non void and non variable case: not handled yet here, please report\n");
454  }
455  return t;
456 }
#define MIN(x, y)
minimum and maximum if they are defined somewhere else, they are very likely to be defined the same w...
type type_to_pointer_type(type t)
allocate a new type "pt" which includes directly "t".
Definition: type.c:5253
@ is_basic_overloaded
Definition: ri.h:574
#define ifdebug(n)
Definition: sg.c:47

References basic_pointer, basic_tag, basic_to_string(), CAR, CDR, copy_basic(), copy_type(), ENDP, entity_basic_concrete_type(), entity_field_p(), EXPRESSION, expression_syntax, gen_full_copy_list(), gen_length(), ifdebug, int, is_basic_derived, is_basic_overloaded, is_basic_pointer, is_type_variable, is_type_void, make_type(), make_variable(), MIN, NIL, pips_debug, pips_internal_error, POP, reference_variable, syntax_reference, syntax_reference_p, type_tag, type_to_pointer_type(), type_to_string(), type_undefined, type_variable, type_variable_p, variable_basic, and variable_dimensions.

Referenced by cell_reference_to_type().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ reference_unbounded_indices_p()

bool reference_unbounded_indices_p ( reference  r)

This function should be at expression.c.

It already exist and is called reference_with_unbounded_indices_p() but includes two cases that should be disjoint: constant indices and unbounded ones.

Definition at line 1373 of file type.c.

1374 {
1375  list sel = reference_indices(r);
1376  bool unbounded_p = true;
1377 
1378  FOREACH(EXPRESSION, se, sel) {
1379  if(!unbounded_expression_p(se)) {
1380  unbounded_p = false;
1381  break;
1382  }
1383  }
1384  return unbounded_p;
1385 }
#define FOREACH(_fe_CASTER, _fe_item, _fe_list)
Apply/map an instruction block on all the elements of a list.
Definition: newgen_list.h:179
bool unbounded_expression_p(expression e)
Definition: expression.c:4329

References EXPRESSION, FOREACH, reference_indices, and unbounded_expression_p().

Referenced by strict_constant_path_p().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ strict_constant_path_p()

bool strict_constant_path_p ( reference  r)

Definition at line 1407 of file type.c.

1408 {
1409  bool constant_path = false;
1410  entity v = reference_variable(r);
1411  list l_ind = reference_indices(r);
1412 
1413  // Test the different top and bottom area
1414  if (entity_all_locations_p(v)
1418  ) {
1419  constant_path = true;
1420  }
1423  ) {
1424  constant_path = true;
1425  }
1428  ) {
1429  constant_path = true;
1430  }
1433  ) {
1434  constant_path = true;
1435  }
1438  ) {
1439  constant_path = true;
1440  }
1441  else if (entity_abstract_location_p(v)) { // Maybe this test permit to eliminate the 4 test just before?
1442  constant_path = true;
1443  }
1444  // Test if it's the constant NULL
1445  else if (entity_null_locations_p(v)) {
1446  constant_path = true;
1447  }
1448  // Test if it's a formal parameter
1449  else if (entity_stub_sink_p(v)) {
1450  constant_path = true;
1451  }
1452  // Test if it's a heap element
1453  else if (heap_area_p(v)) {
1454  constant_path = true;
1455  }
1456  // Maybe not efficient enough, for array of struct or struct of array?
1457  // Test if it's a structure
1458  else if (struct_type_p(entity_type(v)) && !ENDP(l_ind)) {
1459  constant_path = true;
1460  }
1461  // Test if it's a array with only *
1462  else if (!ENDP(l_ind)) {
1463  // see reference_unbounded_indices_p
1464  constant_path = reference_unbounded_indices_p(r);
1465  }
1466 
1467  return constant_path;
1468 }
bool entity_all_module_static_locations_p(entity e)
test if an entity is the a static area
bool entity_null_locations_p(entity e)
test if an entity is the NULL POINTER
bool entity_all_dynamic_locations_p(entity e)
test if an entity is the set of all dynamic locations
bool entity_stub_sink_p(entity e)
test if an entity is a stub sink for a formal parameter e.g.
bool entity_all_static_locations_p(entity e)
test if an entity is the set of all static locations
bool entity_nowhere_locations_p(entity e)
test if an entity is the bottom of the lattice
bool entity_all_module_locations_p(entity e)
test if an entity is the set of locations defined in a module
bool entity_anywhere_locations_p(entity e)
test if an entity is the bottom of the lattice
bool entity_all_module_heap_locations_p(entity e)
test if an entity is the a heap area
bool entity_all_module_dynamic_locations_p(entity e)
test if an entity is the a dynamic area
bool entity_all_module_stack_locations_p(entity e)
test if an entity is the a stack area
bool entity_all_stack_locations_p(entity e)
test if an entity is the set of all stack locations
bool entity_all_heap_locations_p(entity e)
test if an entity is the set of all heap locations
bool entity_typed_nowhere_locations_p(entity e)
test if an entity is the bottom of the lattice
bool reference_unbounded_indices_p(reference r)
This function should be at expression.c.
Definition: type.c:1373
bool heap_area_p(entity aire)
Definition: area.c:86
bool struct_type_p(type t)
Returns true if t is of type derived and if the derived type is a struct.
Definition: type.c:3121

References ENDP, entity_abstract_location_p(), entity_all_dynamic_locations_p(), entity_all_heap_locations_p(), entity_all_locations_p(), entity_all_module_dynamic_locations_p(), entity_all_module_heap_locations_p(), entity_all_module_locations_p(), entity_all_module_stack_locations_p(), entity_all_module_static_locations_p(), entity_all_stack_locations_p(), entity_all_static_locations_p(), entity_anywhere_locations_p(), entity_nowhere_locations_p(), entity_null_locations_p(), entity_stub_sink_p(), entity_type, entity_typed_anywhere_locations_p(), entity_typed_nowhere_locations_p(), heap_area_p(), reference_indices, reference_unbounded_indices_p(), reference_variable, and struct_type_p().

Referenced by can_be_constant_path_p().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ substitute_unbounded_call()

static void substitute_unbounded_call ( call  c)
static

Definition at line 570 of file type.c.

571 {
572  entity f = call_function(c);
573  const char* fn = entity_local_name(f);
575  entity z = int_to_entity(0);
576  call_function(c) = z;
577  }
578 }
entity int_to_entity(_int c)
Definition: constant.c:453
#define call_function(x)
Definition: ri.h:709

References call_function, entity_local_name(), f(), int_to_entity(), same_string_p, and UNBOUNDED_DIMENSION_NAME.

Referenced by eliminate_calls_to_unbounded().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ types_compatible_for_effects_interprocedural_translation_p()

bool types_compatible_for_effects_interprocedural_translation_p ( type  real_arg_t,
type  formal_arg_t 
)

tests if the actual argument type and the formal argument type are compatible with the current state of the interprocedural translation algorithms.

safe default result

Parameters
real_arg_teal_arg_t
formal_arg_tormal_arg_t

Definition at line 932 of file type.c.

933 {
934  bool result = false; /* safe default result */
935 
936  if (real_arg_t == formal_arg_t)
937  result = true;
938  else
939  {
940  type real_arg_ct = compute_basic_concrete_type(real_arg_t);
941  type formal_arg_ct = compute_basic_concrete_type(formal_arg_t);
942 
943  result =
945  (real_arg_ct, formal_arg_ct);
946 
947  free_type(real_arg_ct);
948  free_type(formal_arg_ct);
949  }
950 
951  return result;
952 }

References basic_concrete_types_compatible_for_effects_interprocedural_translation_p(), compute_basic_concrete_type(), and free_type().

Referenced by c_convex_effects_on_formal_parameter_backward_translation().

+ Here is the call graph for this function:
+ Here is the caller graph for this function: