PIPS
terapixify.c
Go to the documentation of this file.
1 /*
2  Copyright 1989-2016 MINES ParisTech
3 
4  This file is part of PIPS.
5 
6  PIPS is free software: you can redistribute it and/or modify it
7  under the terms of the GNU General Public License as published by
8  the Free Software Foundation, either version 3 of the License, or
9  any later version.
10 
11  PIPS is distributed in the hope that it will be useful, but WITHOUT ANY
12  WARRANTY; without even the implied warranty of MERCHANTABILITY or
13  FITNESS FOR A PARTICULAR PURPOSE.
14 
15  See the GNU General Public License for more details.
16 
17  You should have received a copy of the GNU General Public License
18  along with PIPS. If not, see <http://www.gnu.org/licenses/>.
19 
20 */
21 
22 /**
23  * @file terapixify.c
24  * apply transformations required to generate terapix microcode
25  * @author Serge Guelton <serge.guelton@enst-bretagne.fr>
26  * @date 2009-07-01
27  */
28 #ifdef HAVE_CONFIG_H
29  #include "pips_config.h"
30 #endif
31 #include <ctype.h>
32 
33 
34 #include "genC.h"
35 #include "linear.h"
36 #include "ri.h"
37 #include "effects.h"
38 #include "ri-util.h"
39 #include "workspace-util.h"
40 #include "prettyprint.h"
41 #include "effects-util.h"
42 #include "text.h"
43 #include "pipsdbm.h"
44 #include "pipsmake.h"
45 #include "resources.h"
46 #include "properties.h"
47 #include "misc.h"
48 #include "control.h"
49 #include "effects-generic.h"
50 #include "effects-simple.h"
51 #include "alias-classes.h"
52 #include "effects-convex.h"
53 #include "expressions.h"
54 #include "callgraph.h"
55 #include "text-util.h"
56 #include "transformations.h"
57 #include "parser_private.h"
58 #include "accel-util.h"
59 
60 
61 
62 
63 /**
64  * terapixify
65  */
66 
67 static
68 bool cannot_terapixify(gen_chunk * elem, bool *can_terapixify)
69 {
70  printf("found invalid construct of type %td\n",elem->i);
71  return *can_terapixify=false;
72 }
73 
74 static
75 bool can_terapixify_call_p(call c, bool *can_terapixify)
76 {
78  {
79  printf("found invalid call to %s\n",entity_user_name(call_function(c)));
80  return *can_terapixify=false;
81  }
82  return true;
83 }
84 
85 static
86 bool can_terapixify_expression_p(expression e, bool *can_terapixify)
87 {
88  basic b = expression_basic(e);
89  while( basic_pointer_p(b))
91 
92  if(!basic_int_p(b) && ! basic_overloaded_p(b))
93  {
94  list ewords = Words_Expression(e);
95  string estring = words_to_string(ewords);
96  string bstring = basic_to_string(b);
97  printf("found invalid expression %s of basic %s\n",estring, bstring);
98  free(bstring);
99  free(estring);
100  gen_free_list(ewords);
101  return *can_terapixify=false;
102  }
103  return true;
104 }
105 
106 struct entity_bool { entity e; bool b; };
107 
108 static
110 {
111  if(same_entity_p(reference_variable(r),eb->e)) eb->b=true;
112 }
113 
114 static
116 {
118 }
119 
120 static
122 {
123  struct entity_bool eb = { e, false };
125  return eb.b;
126 }
127 
128 #define TERAPIX_PTRARG_PREFIX "FIFO"
129 #define TERAPIX_LOOPARG_PREFIX "N"
130 #define TERAPIX_IMAGE_PREFIX "im"
131 #define TERAPIX_MASK_PREFIX "ma"
132 #define TERAPIX_REGISTER_PREFIX "re"
133 
134 
135 static bool terapix_renamed_local_p(const char* s, const char* prefix)
136 {
137  string found = strstr(s,prefix);
138  if(found)
139  {
140  for(found+=strlen(prefix);*found;++found)
141  if(!isdigit(*found)) return false;
142  return true;
143  }
144  return false;
145 }
146 
147 static bool terapix_renamed_entity_p(entity e, const char* prefix) {
149 }
152 }
153 
154 static bool terapix_renamed_p(const char *s)
155 {
161 }
162 
163 static
164 void do_terapix_argument_handler(entity e, string arg_prefix, size_t *arg_cnt,string ass_prefix, size_t *ass_cnt,bool force)
165 {
166  /* change parameter name and generate an assignment */
167  if(arg_prefix && (force || !terapix_renamed_p(entity_user_name(e))) ) {
168  string new_name;
169  asprintf(&new_name,"%s" MODULE_SEP_STRING "%s%zd",entity_module_name(e),arg_prefix,(*arg_cnt)++);
170  entity ne = make_entity_copy_with_new_name(e,new_name,false);
171  free(new_name);
172 
174  !ENDP(iter);
175  POP(iter))
176  {
177  entity ee = ENTITY(CAR(iter));
178  if(same_entity_p(e,ee)) {
179  CAR(iter).p=(gen_chunkp)ne;
180  }
181  }
182  /* we now have FIFOx in ne and will generate an assignment from ne to e
183  * we also have to change the storage for e ...
184  * and for images, add a dereferencing operator
185  */
188  expression assigned ;
189  if( false && ass_prefix && same_string_p(ass_prefix,TERAPIX_IMAGE_PREFIX))
190  {
191  basic bt = entity_basic(e);
192  type new_type = copy_type(basic_pointer(bt));
194  entity_type(e) = new_type;
197  substitute = entity_to_expression(e);
200  }
201  else
202  assigned = entity_to_expression(ne);
205  }
206 
207  /* to respect terapix asm, we also have to change the name of variable e */
208  if(ass_prefix && (force ||!terapix_renamed_p(entity_user_name(e)))) {
209  string new_name;
210  asprintf(&new_name,"%s" MODULE_SEP_STRING "%s%zd",entity_module_name(e),ass_prefix,(*ass_cnt)++);
211  entity ne = make_entity_copy_with_new_name(e,new_name,false);
213  free(new_name);
215  }
216 }
217 static void terapix_argument_handler(entity e, string arg_prefix, size_t *arg_cnt,string ass_prefix, size_t *ass_cnt) {
218  do_terapix_argument_handler(e,arg_prefix,arg_cnt,ass_prefix,ass_cnt,false);
219 }
220 static void force_terapix_argument_handler(entity e, string arg_prefix, size_t *arg_cnt,string ass_prefix, size_t *ass_cnt) {
221  do_terapix_argument_handler(e,arg_prefix,arg_cnt,ass_prefix,ass_cnt,true);
222 }
223 
224 static
226 {
227  return (*suitable) &= formal_parameter_p(reference_variable(r));
228 }
229 
230 static
232 {
233  bool suitable=true;
235  return suitable;
236 }
237 
238 typedef struct {
240  size_t *cnt;
242 
243 
244 static void
246 {
247  if(statement_loop_p(sl)){
248  loop l = statement_loop(sl);
249  range r = loop_range(l);
251  entity loop_bound = entity_undefined;
252  if(terapix_suitable_loop_bound_p(nb_iter))
253  {
254  set body_entities = get_referenced_entities(loop_body(l));
255  /* generate new entity if needed */
256  if(expression_reference_p(nb_iter)) /* use the reference , but we must rename it however !*/
257  {
258  loop_bound=reference_variable(expression_reference(nb_iter));
259  string new_name;
261  entity new_loop_bound=make_entity_copy_with_new_name(loop_bound,new_name,false);
263  !ENDP(iter);
264  POP(iter))
265  {
266  entity ee = ENTITY(CAR(iter));
267  if(same_entity_p(loop_bound,ee)) {
268  CAR(iter).p=(gen_chunkp)new_loop_bound;
269  }
270  }
272  loop_bound=new_loop_bound;
273  }
274  else {
275  string new_name;
276  asprintf(&new_name,TERAPIX_LOOPARG_PREFIX "%zd",(*p->cnt)++);
278  value v = entity_initial(loop_bound);
281  value_expression(v)=nb_iter;
282  AddEntityToCurrentModule(loop_bound);
283  free(new_name);
284  }
285 
286  /* patch loop */
289 
290  if(set_belong_p(body_entities,loop_bound))
292 
293 
294  /* save change for futher processing */
295  hash_put(p->ht,loop_bound,nb_iter);
296  }
297  }
298 }
299 
300 static int compare_formal_parameters(const void *v0, const void * v1) {
301  const entity f0 = *(const entity *)v0,
302  f1=*(const entity *)v1;
307  if(f0==f1) return 0;
310  return 1;
311  else
312  return o0 > o1 ? -1 : 1 ;
313  }
314  else
315  return o0 > o1 ? -1 : 1 ;
316 }
317 
320 }
321 
322 typedef struct {
324  bool res;
325 } context;
326 
328  entity op = call_function(c);
329  if(ENTITY_ASSIGN_P(op)) {
330  expression lhs = binary_call_lhs(c),
331  rhs = binary_call_rhs(c);
332  if(expression_pointer_p(lhs)) {
334  if(same_entity_p(reference_variable(r),ctxt->ref)) {
335  /* check that lhs only contains reference to mask */
336  set s = get_referenced_entities(rhs);
337  bool only_mask = true,
338  at_least_one_mask = false;
339  SET_FOREACH(entity,e,s) {
340  if(terapix_mask_entity_p(e)) {
341  at_least_one_mask=true;
342  }
343  else
344  only_mask=false;
345  }
346  set_free(s);
347  ctxt->res = only_mask && at_least_one_mask;
348  gen_recurse_stop(0);
349  }
350  }
351  }
352 }
353 
355  context c = { .ref=e, .res=false };
358  return c.res;
359 }
360 
361 /* a test is normalized when it is in the form a>0 */
363  entity op = call_function(c);
364  if(ENTITY_CONDITIONAL_P(op)) {
365  expression cond = binary_call_lhs(c);
366  if(expression_call_p(cond)) {
367  call c = expression_call(cond);
368  entity op = call_function(c);
369  if(ENTITY_GREATER_THAN_P(op)) {
370  expression etmp = MakeBinaryCall(
374  );
377  );
378  free_expression(etmp);
379  }
380  else if(ENTITY_LESS_THAN_P(op)) {
381  expression etmp = MakeBinaryCall(
385  );
389  free_expression(etmp);
390  }
391  else
392  pips_internal_error("case not handled yet\n");
393  }
394  else
395  pips_internal_error("does not know how to handle this conditional");
396  }
397 }
398 
400  if(statement_call_p(s)) {
402  if(set_belong_p(re,e)) {
404  }
405  set_free(re);
406  }
407 }
408 
409 
412  /* there should be only one caller */
413  string caller = STRING(CAR(callers));
414  /* Eeny, meeny, miny, moe */
416  if(entity_pointer_p(fa)) {
417  const char* fa_name = entity_user_name(fa);
418  entity caller_faname = FindEntityFromUserName(caller,fa_name);
419  if(entity_undefined_p(caller_faname)){
420  string tmp=strdup(fa_name);
421  tmp[strlen(tmp)-1]=0;
422  caller_faname = FindEntityFromUserName(caller,tmp);
423  free(tmp);
424  }
425  pips_assert("parameter found",!entity_undefined_p(caller_faname));
426  /* get ready for annotation insertion */
427  string pragma;
428  asprintf(&pragma,"terapix %s", fa_name);
430  string tmp = pragma;
431  asprintf(&pragma,"%s %d",pragma, dimension_size(d));
432  free(tmp);
433  }
436  pragma,false);
437  }
438  }
439 }
440 
441 /* if only one register is ever written by a sequence of assignment, take advantage of it */
443  if(statement_block_p(st)) {
444  /* first ensure it's a sequence of assignment */
447  return;
448  /* then check that the written register is always the same */
451  if(!continue_statement_p(s)) {
453  entity scalar = expression_int_scalar(lhs);
454  if(entity_undefined_p(scalar))
455  continue;
456  if(entity_undefined_p(reg))
457  reg=scalar;
458  else if(!same_entity_p(reg,scalar))
459  return;
460  }
461  }
462  /* finally, rename this entity as the accumulator P */
463 #define TERAPIX_ACC "P"
465  if(entity_undefined_p(P)) {
468  }
469  replace_entity(st,reg,P);
470  }
471 }
472 
473 typedef struct {
475  bool plus;
476  bool success;
477 } tlo_context_t ;
478 
485  make_call(
488  )
489  )
490  );
491  ctxt->success=true;
492  gen_recurse_stop(0);
493  }
494  }
495  return true;
496 }
497 
499  if(statement_loop_p(st)) {
500  loop l =statement_loop(st);
501 
502  statement sb = loop_body(l);
505  if(statement_block_p(sb)) {
507  list bblock = gen_nreverse(gen_copy_seq(block));
508  list added = NIL;
509 
510  /* look for iterators from the end */
511  FOREACH(STATEMENT,s,bblock) {
512  if(assignment_statement_p(s)) {
513  call c = statement_call(s);
514  expression lhs = binary_call_lhs(c),
515  rhs = binary_call_rhs(c);
516  if(expression_call_p(rhs)) {
517  call c = expression_call(rhs);
518  entity op = call_function(c);
519  if(ENTITY_PLUS_C_P(op) || ENTITY_MINUS_C_P(op)) {
520  bool plus = ENTITY_PLUS_C_P(op);
521  intptr_t step;
522  if(expression_equal_p(binary_call_lhs(c),lhs) &&
523  expression_integer_value(binary_call_rhs(c),&step)&&step==1) {
524  entity iterator = expression_to_entity(lhs);
525  statement copy = copy_statement(s);
528 
529  gen_remove(&block,s);
530  /* now try to hide the iteration in a pointer access somewhere */
531  tlo_context_t ctxt = {iterator,plus,false };
532  FOREACH(STATEMENT,ss,block) {
533  set re = get_referenced_entities(ss);
534  if(set_belong_p(re,iterator)) {
536  if(ctxt.success) {
537  set_free(re);
538  break;
539  }
540  }
541  set_free(re);
542  }
543  if(!ctxt.success)
545  else
546  free_statement(s);
547  added=CONS(STATEMENT,copy,added);
548  continue;
549  }
550  }
551  }
552  }
553  break;
554  }
556  gen_free_list(bblock);
557  if(!ENDP(added)) {
558  added=gen_nreverse(added);
559  insert_statement(st,make_block_statement(added),true);
560  }
561  }
562  }
563 }
564 
565 static void terapixify_loops(statement s) {
566  if(statement_loop_p(s)) {
567  loop l =statement_loop(s);
568  entity index = loop_index(l);
569  range r = loop_range(l);
573  full_loop_unroll(s);
574  if(statement_block_p(s)) {
576  list bblock= gen_copy_seq(block);
577  /* look for iterators */
578  for(list iter = bblock; !ENDP(iter) ; POP(iter)) {
579  statement s = STATEMENT(CAR(iter));
580  if(assignment_statement_p(s)) {
581  call c = statement_call(s);
582  expression lhs = binary_call_lhs(c),
583  rhs = binary_call_rhs(c);
584  if(expression_call_p(rhs)) {
585  call c = expression_call(rhs);
586  entity op = call_function(c);
587  if(ENTITY_PLUS_C_P(op) || ENTITY_MINUS_C_P(op)) {
588  bool plus = ENTITY_PLUS_C_P(op);
589  intptr_t step;
590  if(expression_equal_p(binary_call_lhs(c),lhs) &&
591  expression_integer_value(binary_call_rhs(c),&step)&&step==1) {
592  entity iterator = expression_to_entity(lhs);
593  /* now try to hide the iteration in a pointer access somewhere */
594  tlo_context_t ctxt = {iterator,plus,false };
595  FOREACH(STATEMENT,ss,iter) {
596  set re = get_referenced_entities(ss);
597  if(set_belong_p(re,iterator)) {
599  if(ctxt.success) {
600  set_free(re);
601  break;
602  }
603  }
604  set_free(re);
605  }
606  /* be optimistic: even if we failed, remove the iterator */
607  gen_remove(&block,s);
608  free_statement(s);
609  }
610  }
611  }
612  }
613  }
614  gen_free_list(bblock);
616  }
617  }
618  }
619 }
620 
622 {
624 }
625 
627 {
628  bool can_terapixify =true;
629  /* prelude */
633 
634  /* checks */
635 
636  /* make sure
637  * - only do loops remain
638  * - no call to external functions
639  * - no float / double etc
640  */
646  NULL);
647 
648  /* unroll some loops with constant trip count */
651 
652  /* reorder some loops */
654 
655 
656  /* detect initial array sizes */
658 
659  /* now, try to guess the goal of the parameters
660  * - parameters are 32 bits signed integers (TODO)
661  * - read-only arrays might be mask, but can also be images (depend of their size ?)
662  * - written arrays must be images
663  * - integer are loop parameters
664  * - others are not allowed
665  */
666  size_t nb_fifo = 1;
667  size_t nb_lu = 1;
668  size_t nb_ptr = 1;
669  size_t nb_ma = 1;
670  size_t nb_re = 5;/* reserve some register for internal use */
672  {
673  if(!entity_area_p(e))
674  {
676  basic vb = variable_basic(v);
677  if(formal_parameter_p(e))
678  {
679  if( basic_pointer_p(vb) ) /* it's a pointer */
680  {
681  string prefix = NULL;
684  if( strstr(entity_user_name(e),get_string_property("GROUP_CONSTANTS_HOLDER")) ) {
685  printf("%s seems a mask\n",entity_user_name(e));
687  }
688  else {
689  printf("%s seems an image\n",entity_user_name(e));
691  }
693  }
694  else if( entity_used_in_loop_bound_p(e) )
695  {
696  printf("%s belongs to a loop bound\n",entity_user_name(e));
697  //terapix_argument_handler(e,TERAPIX_LOOPARG_PREFIX,&nb_lu,NULL,NULL);
698  }
699  /* a rom array with only one element, outlining and isolate_statement where too smart :) */
700  else if ( strstr(entity_user_name(e),get_string_property("GROUP_CONSTANTS_HOLDER")) &&
701  entity_scalar_p(e)) {
702 
706  NIL,
707  NIL
708  )
709  );
710  expression repl = MakeUnaryCall(
713  );
716  e,
717  repl);
718  free_expression(repl);
719  /* pips bonus step: the consistency */
720  intptr_t i=1,
723  if(i++==offset) {
724  dummy d = parameter_dummy(p);
725  if(dummy_identifier_p(d))
726  {
727  entity di = dummy_identifier(d);
731  NIL,
732  NIL
733  )
734  );
735  }
739  NIL,
740  NIL
741  )
742  );
743  break;
744  }
745  }
747  list callers_statement = callers_to_statements(callers);
748  list call_sites = callers_to_call_sites(callers_statement,get_current_module_entity());
749  pips_assert("only one caller here\n",
750  !ENDP(call_sites) && ENDP(CDR(call_sites)));
751  list args = call_arguments(CALL(CAR(call_sites)));
752  for(intptr_t i=1;i<offset;i++) POP(args);
753  expression *exp = (expression*)REFCAR(args);
754  *exp=
757  *exp
758  );
759 
760 
761  for(list citer=callers,siter=callers_statement;!ENDP(citer);POP(citer),POP(siter))
762  DB_PUT_MEMORY_RESOURCE(DBR_CODE, STRING(CAR(citer)),STATEMENT(CAR(siter)));
764  gen_free_list(callers_statement);
765 
766  printf("%s seems a mask\n",entity_user_name(e));
768  }
769  }
770  else if( basic_pointer_p(vb) ) {
771  terapix_argument_handler(e,NULL,NULL,TERAPIX_IMAGE_PREFIX,&nb_ptr);
772  } else if( entity_scalar_p(e))
774  else
776  }
777  }
778 
779  /* rename all declared entities using terasm convention*/
781  bool stop=true;
782  do {
783  stop=true;
784  /* need a copy otherwise goes in infinite loop */
785  FOREACH(ENTITY,e,tmp)
786  {
787  if(entity_variable_p(e))
788  {
790  if( basic_pointer_p(variable_basic(v)) ) {/* it's a pointer */
793  stop=false;
794  }
795  else
796  terapix_argument_handler(e,NULL,NULL,TERAPIX_IMAGE_PREFIX,&nb_ptr);
797  }
798  else if( basic_int_p(variable_basic(v))) /* it's an int */
800  }
801  }
802  } while(!stop);
803  gen_free_list(tmp);
804 
805  /* reorder arguments to match terapix conventions */
807 
808  /* loops in terasm iterate over a given parameter, in the form DO I=1:N
809  * I is hidden to the user and N must be a parameter */
810  {
813  .cnt=&nb_lu
814  };
816  }
817 
819 
820  /* normalize test */
822 
823  /* try some simple optimizations */
826 
827 
828  /* validate */
831 
832  /*postlude*/
836  return true || can_terapixify;
837 }
844  NORMALIZE_EXPRESSION(*index0);
845  normalized n = expression_normalized(*index0);
846  if(normalized_linear_p(n)) {
847  for(Pvecteur piter = normalized_linear(n);
848  !VECTEUR_NUL_P(piter);
849  piter=vecteur_succ(piter)) {
850 
851  if(vecteur_var(piter)!=tw_loop_index) {
852  Value offset = vecteur_val(piter);
853  if(offset!=VALUE_ZERO) {
854  Pvecteur opv = vect_new(vecteur_var(piter),offset);
855  expression eoffset = Pvecteur_to_expression(opv),
856  Eoffset = copy_expression(eoffset);
857  vect_rm(opv);
859  SizeOfDimension(d1),
860  eoffset);
861  *index0=make_op_exp(MINUS_OPERATOR_NAME,*index0,Eoffset);
864  *index1,
865  eoffset);
866  }
867  }
868  }
869  }
870  }
871 }
872 
873 /* make sure s is of the form
874  * decl
875  * loop nest
876  *
877  * and then assume each array is a 2+ dimensional array and make sure there is no constant in the first array index. That's all.
878  */
879 static bool do_terapix_warmup(statement top) {
880  if(statement_block_p(top)) {
882  if(declaration_statement_p(s)) continue;
883  else if(statement_loop_p(s)) {
884  loop l =statement_loop(s);
887  list arrays = NIL;
888  SET_FOREACH(entity, e, re) {
890  type_variable(entity_type(e))))>1) {
891  arrays=CONS(ENTITY,e,arrays);
892  }
893  }
894  set_free(re);
895  FOREACH(ENTITY,e,arrays) {
896  gen_context_recurse(l, e,
898  }
899  gen_free_list(arrays);
900  return true;
901  }
902  else break;
903  }
904  }
905  return false;
906 }
907 
908 bool terapix_warmup(const char * module_name) {
909  /* prelude */
912 
913  /* go go power rangers */
914  bool can_terapixify =
916 
917  /* validate */
920 
921  /*postlude*/
924  return can_terapixify;
925 
926 }
927 
928 /**
929  *
930  *
931  * @param e
932  *
933  * @return
934  */
936 {
937  if(expression_call_p(e))
938  {
939  call c = expression_call(e);
940  entity op = call_function(c);
941  return ! call_constant_p(c) && (!get_bool_property("GENERATE_TWO_ADDRESSES_CODE_SKIP_DEREFERENCING") || !ENTITY_DEREFERENCING_P(op));
942  }
943  else
944  return false;
945 }
946 
947 static
949 {
950  if(statement_call_p(s))
951  {
952  call c = statement_call(s);
954  {
955  list args = call_arguments(c);
956  expression lhs = EXPRESSION(CAR(args));
957  expression rhs = EXPRESSION(CAR(CDR(args)));
959  list e_effects = proper_effects_of_expression(rhs);
960  bool conflict=false;
961  FOREACH(EFFECT,we,w_effects) {
962  FOREACH(EFFECT,e,e_effects) {
963  if((conflict=effects_may_conflict_p(e,we))) {
964  goto end;
965  }
966  }
967  }
968 end:
969  gen_full_free_list(e_effects);
971 
973  call parent_call = call_undefined;
974  do {
975  parent_call=expression_call(rhs);
976  rhs=EXPRESSION(CAR(call_arguments(parent_call)));
978  if(! expression_equal_p(lhs,rhs) )
979  {
980  /* a=b+c; -> (1) a=b; (2) a=a+c; */
982  statement thecall/*2*/= s;
983  CAR(call_arguments(parent_call)).p=(gen_chunkp)copy_expression(lhs);
984  insert_statement(thecall,theassign,true);
985  }
986  }
987  }
988  }
989 }
990 
992 {
993  /* prelude */
999 
1000  /* validate */
1003 
1004  /*postlude*/
1008  return true;
1009 }
1010 
1012 {
1013  entity op = call_function(c);
1014  if(ENTITY_DIVIDE_P(op))
1015  {
1016  expression lhs = binary_call_lhs(c);
1017  expression rhs = binary_call_rhs(c);
1019  {
1020  int accuracy = get_int_property("TERAPIX_REMOVE_DIVIDE_ACCURACY");
1021 
1024 
1028  lhs,
1033  int_to_expression(1),
1034  rhs),
1035  int_to_expression(accuracy)
1036  )
1037  ),
1038  int_to_expression(accuracy)
1039  );
1040  }
1041  else
1042  pips_user_error("terapix cannot handle division by a non-constant variable\n");
1043  }
1044 }
1046 {
1047  /* prelude */
1050 
1051  /* converts divide operator into multiply operator:
1052  * a/cste = a* (1/b) ~= a * ( 128 / cste ) / 128
1053  */
1055 
1056  /* validate */
1058 
1059  /*postlude*/
1062  return true;
1063 }
1064 
int get_int_property(const string)
call make_call(entity a1, list a2)
Definition: ri.c:269
syntax make_syntax_call(call _field_)
Definition: ri.c:2500
type make_type_variable(variable _field_)
Definition: ri.c:2715
type copy_type(type p)
TYPE.
Definition: ri.c:2655
void free_constant(constant p)
Definition: ri.c:362
basic make_basic_int(intptr_t _field_)
Definition: ri.c:158
basic make_basic_pointer(type _field_)
Definition: ri.c:179
expression copy_expression(expression p)
EXPRESSION.
Definition: ri.c:850
statement copy_statement(statement p)
STATEMENT.
Definition: ri.c:2186
variable make_variable(basic a1, list a2, list a3)
Definition: ri.c:2895
syntax copy_syntax(syntax p)
SYNTAX.
Definition: ri.c:2442
void free_expression(expression p)
Definition: ri.c:853
void free_storage(storage p)
Definition: ri.c:2231
void free_type(type p)
Definition: ri.c:2658
void free_statement(statement p)
Definition: ri.c:2189
bool db_touch_resource(const char *rname, const char *oname)
touch logical time for resource[owner], possibly behind the back of pipsdbm.
Definition: database.c:538
#define VALUE_ZERO
int Value
list callers_to_call_sites(list callers_statement, entity called_module)
given a list callers_statement of module statements returns a list of calls to module called_module
Definition: callgraph.c:149
void sort_parameters(entity module, gen_cmp_func_t cmp)
change the parameter order for function module using comparison function cmp both compilation unit an...
Definition: callgraph.c:180
list callers_to_statements(list callers)
given a list callers of module name calling module called module return a list of their body
Definition: callgraph.c:163
bool clean_up_sequences(statement s)
Recursively clean up the statement sequences by fusing them if possible and by removing useless one.
void do_loop_to_while_loop(statement)
converts a doloop to a while loop, in place
string compilation_unit_of_module(const char *)
The output is undefined if the module is referenced but not defined in the workspace,...
Definition: module.c:350
int dummy
A dummy file, to prevent empty libraries from breaking builds.
Definition: dummy.c:41
static Value offset
Definition: translation.c:283
void set_cumulated_rw_effects(statement_effects)
list load_cumulated_rw_effects_list(statement)
list effects_write_effects(list)
void reset_cumulated_rw_effects(void)
list proper_effects_of_expression(expression)
#define EFFECT(x)
EFFECT.
Definition: effects.h:608
const char * module_name(const char *s)
Return the module part of an entity name.
Definition: entity_names.c:296
void substitute_expression(void *in, expression pattern, expression into)
expression_substitution.c
char * get_string_property(const char *)
bool get_bool_property(const string)
FC 2015-07-20: yuk, moved out to prevent an include cycle dependency include "properties....
#define call_constant_p(C)
Definition: flint_check.c:51
#define gen_context_recurse(start, ctxt, domain_number, flt, rwt)
Definition: genC.h:285
#define STRING(x)
Definition: genC.h:87
#define gen_recurse(start, domain_number, flt, rwt)
Definition: genC.h:283
union gen_chunk * gen_chunkp
void gen_full_free_list(list l)
Definition: genClib.c:1023
void free(void *)
void set_conflict_testing_properties()
conflicts.c
Definition: conflicts.c:68
bool effects_may_conflict_p(effect eff1, effect eff2)
Check if two effect may conflict @description Two effects may conflict if their abstract two location...
Definition: conflicts.c:162
statement make_block_statement(list)
Make a block statement from a list of statement.
Definition: statement.c:616
void reset_current_module_entity(void)
Reset the current module entity.
Definition: static.c:97
void reset_current_module_statement(void)
Reset the current module statement.
Definition: static.c:221
const char * get_current_module_name(void)
Get the name of the current module.
Definition: static.c:121
statement set_current_module_statement(statement)
Set the current module statement.
Definition: static.c:165
statement get_current_module_statement(void)
Get the current module statement.
Definition: static.c:208
entity set_current_module_entity(entity)
static.c
Definition: static.c:66
entity get_current_module_entity(void)
Get the entity of the current module.
Definition: static.c:85
void replace_entity(void *s, entity old, entity new)
per variable version of replace_entities.
Definition: replace.c:113
void replace_entity_by_expression(void *s, entity ent, expression exp)
replace all reference to entity ent by expression exp in s.
Definition: replace.c:220
void gen_recurse_stop(void *obj)
Tells the recursion not to go in this object.
Definition: genClib.c:3251
void gen_context_multi_recurse(void *o, void *context,...)
Multi-recursion with context function visitor.
Definition: genClib.c:3373
void gen_null2(__attribute__((unused)) void *u1, __attribute__((unused)) void *u2)
idem with 2 args, to please overpeaky compiler checks
Definition: genClib.c:2758
bool gen_true2(__attribute__((unused)) gen_chunk *u1, __attribute__((unused)) void *u2)
Definition: genClib.c:2785
void gen_null(__attribute__((unused)) void *unused)
Ignore the argument.
Definition: genClib.c:2752
bool gen_true(__attribute__((unused)) gen_chunk *unused)
Return true and ignore the argument.
Definition: genClib.c:2780
instruction make_continue_instruction()
Creates a CONTINUE instruction, that is the FORTRAN nop, the ";" in C or the "pass" in Python for exa...
Definition: instruction.c:79
#define ENDP(l)
Test if a list is empty.
Definition: newgen_list.h:66
list gen_nreverse(list cp)
reverse a list in place
Definition: list.c:304
void gen_remove(list *cpp, const void *o)
remove all occurences of item o from list *cpp, which is thus modified.
Definition: list.c:685
#define POP(l)
Modify a list pointer to point on the next element of the list.
Definition: newgen_list.h:59
#define REFCAR(pc)
Get the adress of the first element of a list.
Definition: newgen_list.h:119
#define NIL
The empty list (nil in Lisp)
Definition: newgen_list.h:47
list gen_copy_seq(list l)
Copy a list structure.
Definition: list.c:501
size_t gen_length(const list l)
Definition: list.c:150
#define CONS(_t_, _i_, _l_)
List element cell constructor (insert an element at the beginning of a list)
Definition: newgen_list.h:150
#define CAR(pcons)
Get the value of the first element of a list.
Definition: newgen_list.h:92
void gen_free_list(list l)
free the spine of the list
Definition: list.c:327
#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
#define CDR(pcons)
Get the list less its first element.
Definition: newgen_list.h:111
string db_get_memory_resource(const char *rname, const char *oname, bool pure)
Return the pointer to the resource, whatever it is.
Definition: database.c:755
#define DB_PUT_MEMORY_RESOURCE(res_name, own_name, res_val)
conform to old interface.
Definition: pipsdbm-local.h:66
sequence statement_sequence(statement)
Get the sequence of a statement sequence.
Definition: statement.c:1328
list statement_block(statement)
Get the list of block statements of a statement sequence.
Definition: statement.c:1338
loop statement_loop(statement)
Get the loop of a statement.
Definition: statement.c:1374
call statement_call(statement)
Get the call of a statement.
Definition: statement.c:1406
bool statement_call_p(statement)
Definition: statement.c:364
bool statement_loop_p(statement)
Definition: statement.c:349
statement make_assign_statement(expression, expression)
Definition: statement.c:583
statement update_statement_instruction(statement, instruction)
Replace the instruction in statement s by instruction i.
Definition: statement.c:3039
bool continue_statement_p(statement)
Test if a statement is a CONTINUE, that is the FORTRAN nop, the ";" in C or the "pass" in Python....
Definition: statement.c:203
void insert_statement(statement, statement, bool)
This is the normal entry point.
Definition: statement.c:2570
bool assignment_statement_p(statement)
Test if a statement is an assignment.
Definition: statement.c:135
bool declaration_statement_p(statement)
Had to be optimized according to Beatrice Creusillet.
Definition: statement.c:224
void statement_remove_useless_label(statement, bool *)
remove the label of a statement if the statement is not unstructured.
Definition: statement.c:4275
char end
Definition: gtk_status.c:82
hash_table hash_table_make(hash_key_type key_type, size_t size)
Definition: hash.c:294
void hash_put(hash_table htp, const void *key, const void *val)
This functions stores a couple (key,val) in the hash table pointed to by htp.
Definition: hash.c:364
bool expression_constant_p(expression)
HPFC module by Fabien COELHO.
Definition: expression.c:2453
void full_loop_unroll(statement loop_statement)
get rid of the loop by body replication;
Definition: loop_unroll.c:788
#define asprintf
Definition: misc-local.h:225
#define pips_assert(what, predicate)
common macros, two flavors depending on NDEBUG
Definition: misc-local.h:172
#define pips_internal_error
Definition: misc-local.h:149
#define pips_user_error
Definition: misc-local.h:147
entity expression_int_scalar(expression exp)
================================================================
#define MODULE_SEP_STRING
Definition: naming-local.h:30
@ hash_pointer
Definition: newgen_hash.h:32
#define HASH_DEFAULT_SIZE
Definition: newgen_hash.h:26
#define same_string_p(s1, s2)
#define SET_FOREACH(type_name, the_item, the_set)
enumerate set elements in their internal order.
Definition: newgen_set.h:78
void set_free(set)
Definition: set.c:332
bool set_belong_p(const set, const void *)
Definition: set.c:194
static char * module
Definition: pips.c:74
list Words_Expression(expression obj)
of string
Definition: misc.c:2616
string basic_to_string(basic)
Definition: type.c:87
static const char * prefix
bool module_reorder(statement body)
Reorder a module and recompute order to statement if any.
Definition: reorder.c:244
#define make_expression_list(stats...)
#define ENTITY_DIVIDE_P(e)
#define GREATER_THAN_OPERATOR_NAME
#define binary_call_rhs(c)
#define ENTITY_ASSIGN_P(e)
#define MINUS_OPERATOR_NAME
#define ENTITY_DEREFERENCING_P(e)
#define PLUS_OPERATOR_NAME
#define ENTITY_LESS_THAN_P(e)
#define DEFAULT_INTEGER_TYPE_SIZE
#define NORMALIZE_EXPRESSION(e)
#define statement_block_p(stat)
#define DEREFERENCING_OPERATOR_NAME
Definition: ri-util-local.h:93
#define ENTITY_CONDITIONAL_P(e)
#define LEFT_SHIFT_OPERATOR_NAME
#define entity_declarations(e)
MISC: newgen shorthands.
#define ENTITY_PLUS_C_P(e)
#define ENTITY_GREATER_THAN_P(e)
#define ADDRESS_OF_OPERATOR_NAME
#define entity_variable_p(e)
An entity_variable_p(e) may hide a typedef and hence a functional type.
#define PRE_DECREMENT_OPERATOR_NAME
#define ENTITY_MINUS_C_P(e)
#define DIVIDE_OPERATOR_NAME
#define binary_call_lhs(c)
@ range_to_nbiter
#define PRE_INCREMENT_OPERATOR_NAME
Definition: ri-util-local.h:99
#define MINUS_C_OPERATOR_NAME
#define module_functional_parameters(func)
#define MULTIPLY_OPERATOR_NAME
#define RIGHT_SHIFT_OPERATOR_NAME
#define PLUS_C_OPERATOR_NAME
bool entity_area_p(entity e)
Definition: area.c:149
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
bool entity_array_p(entity e)
Is e a variable with an array type?
Definition: entity.c:754
bool same_entity_p(entity e1, entity e2)
predicates on entities
Definition: entity.c:1321
entity module_name_to_entity(const char *mn)
This is an alias for local_name_to_top_level_entity.
Definition: entity.c:1479
entity FindEntityFromUserName(const char *package, const char *name)
Definition: entity.c:1520
basic entity_basic(entity e)
return the basic associated to entity e if it's a function/variable/constant basic_undefined otherwis...
Definition: entity.c:1380
entity find_ith_formal_parameter(entity the_fnct, int rank)
This function gives back the ith formal parameter, which is found in the declarations of a call or a ...
Definition: entity.c:1863
const char * entity_module_name(entity e)
See comments about module_name().
Definition: entity.c:1092
bool entity_pointer_p(entity e)
Definition: entity.c:745
set get_referenced_entities(void *elem)
retrieves the set of entities used in elem beware that this entities may be formal parameters,...
Definition: entity.c:3063
entity entity_intrinsic(const char *name)
FI: I do not understand this function name (see next one!).
Definition: entity.c:1292
entity make_entity_copy_with_new_name(entity e, string global_new_name, bool move_initialization_p)
Create a copy of an entity, with (almost) identical type, storage and initial value if move_initializ...
Definition: entity.c:2463
expression range_to_expression(range r, enum range_to_expression_mode mode)
computes the distance between the lower bound and the upper bound of the range
Definition: eval.c:963
bool expression_integer_value(expression e, intptr_t *pval)
Definition: eval.c:792
expression Pvecteur_to_expression(Pvecteur vect)
AP, sep 25th 95 : some usefull functions moved from static_controlize/utils.c.
Definition: expression.c:1825
bool expression_call_p(expression e)
Definition: expression.c:415
expression entity_to_expression(entity e)
if v is a constant, returns a constant call.
Definition: expression.c:165
expression MakeBinaryCall(entity f, expression eg, expression ed)
Creates a call expression to a function with 2 arguments.
Definition: expression.c:354
bool expression_equal_p(expression e1, expression e2)
Syntactic equality e1==e2.
Definition: expression.c:1347
call expression_call(expression e)
Definition: expression.c:445
void update_expression_syntax(expression e, syntax s)
frees expression syntax of e and replace it by the new syntax s
Definition: expression.c:3564
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 expression_pointer_p(expression e)
we get the type of the expression by calling expression_to_type() which allocates a new one.
Definition: expression.c:506
expression make_op_exp(char *op_name, expression exp1, expression exp2)
================================================================
Definition: expression.c:2012
expression MakeUnaryCall(entity f, expression a)
Creates a call expression to a function with one argument.
Definition: expression.c:342
bool expression_reference_p(expression e)
Test if an expression is a reference.
Definition: expression.c:528
reference expression_reference(expression e)
Short cut, meaningful only if expression_reference_p(e) holds.
Definition: expression.c:1832
entity expression_to_entity(expression e)
just returns the entity of an expression, or entity_undefined
Definition: expression.c:3140
bool extended_expression_constant_p(expression exp)
Returns true if the value of the expression does not depend syntactically on the current store.
Definition: expression.c:2461
list module_formal_parameters(entity func)
list module_formal_parameters(entity func) input : an entity representing a function.
Definition: module.c:327
void add_pragma_str_to_statement(statement st, const char *s, bool copy_flag)
Add a string as a pragma to a statement.
Definition: pragma.c:425
type ultimate_type(type)
Definition: type.c:3466
void AddLocalEntityToDeclarations(entity, entity, statement)
Add the variable entity e to the list of variables of the function module.
Definition: variable.c:233
entity make_scalar_entity(const char *, const char *, basic)
entity make_scalar_entity(name, module_name, base)
Definition: variable.c:331
bool entity_scalar_p(entity)
The concrete type of e is a scalar type.
Definition: variable.c:1113
entity make_new_scalar_variable(entity, basic)
Definition: variable.c:741
int dimension_size(dimension)
this function computes the size of a dimension.
Definition: size.c:491
void AddEntityToCurrentModule(entity)
Add a variable entity to the current module declarations.
Definition: variable.c:260
entity make_scalar_integer_entity(const char *, const char *)
Create an integer variable of name "name" in module of name "module_name".
Definition: variable.c:1068
bool formal_parameter_p(entity)
Definition: variable.c:1489
expression SizeOfDimension(dimension)
Definition: size.c:503
basic expression_basic(expression)
Definition: type.c:1115
#define forloop_domain
newgen_extensions_domain_defined
Definition: ri.h:178
#define formal_offset(x)
Definition: ri.h:1408
#define value_tag(x)
Definition: ri.h:3064
#define dummy_identifier(x)
Definition: ri.h:1033
struct _newgen_struct_pragma_ * pragma
Definition: ri.h:295
#define loop_body(x)
Definition: ri.h:1644
#define basic_pointer(x)
Definition: ri.h:637
#define expression_domain
newgen_execution_domain_defined
Definition: ri.h:154
#define parameter_dummy(x)
Definition: ri.h:1823
#define parameter_type(x)
Definition: ri.h:1819
#define value_constant(x)
Definition: ri.h:3073
#define basic_int_p(x)
Definition: ri.h:614
#define normalized_linear_p(x)
Definition: ri.h:1779
#define call_function(x)
Definition: ri.h:709
#define callees_callees(x)
Definition: ri.h:675
#define reference_variable(x)
Definition: ri.h:2326
#define loop_domain
newgen_language_domain_defined
Definition: ri.h:218
#define range_upper(x)
Definition: ri.h:2290
#define value_intrinsic_p(x)
Definition: ri.h:3074
#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 entity_storage(x)
Definition: ri.h:2794
#define statement_domain
newgen_sizeofexpression_domain_defined
Definition: ri.h:362
@ is_value_expression
Definition: ri.h:3036
#define code_declarations(x)
Definition: ri.h:784
#define range_increment(x)
Definition: ri.h:2292
#define call_domain
newgen_callees_domain_defined
Definition: ri.h:58
#define basic_overloaded_p(x)
Definition: ri.h:623
#define storage_formal(x)
Definition: ri.h:2524
#define EXPRESSION(x)
EXPRESSION.
Definition: ri.h:1217
#define entity_undefined_p(x)
Definition: ri.h:2762
#define reference_domain
newgen_range_domain_defined
Definition: ri.h:338
#define entity_undefined
Definition: ri.h:2761
#define expression_normalized(x)
Definition: ri.h:1249
#define PARAMETER(x)
PARAMETER.
Definition: ri.h:1788
#define sequence_statements(x)
Definition: ri.h:2360
#define reference_indices(x)
Definition: ri.h:2328
#define value_code(x)
Definition: ri.h:3067
#define range_lower(x)
Definition: ri.h:2288
#define variable_dimensions(x)
Definition: ri.h:3122
#define whileloop_domain
newgen_variable_domain_defined
Definition: ri.h:466
#define statement_declarations(x)
Definition: ri.h:2460
#define loop_range(x)
Definition: ri.h:1642
#define CALL(x)
CALL.
Definition: ri.h:679
#define call_arguments(x)
Definition: ri.h:711
#define entity_type(x)
Definition: ri.h:2792
#define call_undefined
Definition: ri.h:685
#define normalized_linear(x)
Definition: ri.h:1781
#define expression_syntax(x)
Definition: ri.h:1247
#define dummy_identifier_p(x)
Definition: ri.h:1031
#define value_expression(x)
Definition: ri.h:3082
#define loop_index(x)
Definition: ri.h:1640
#define variable_basic(x)
Definition: ri.h:3120
#define STATEMENT(x)
STATEMENT.
Definition: ri.h:2413
#define storage_undefined
Definition: ri.h:2476
#define entity_initial(x)
Definition: ri.h:2796
char * strdup()
int printf()
Psysteme new_loop_bound(Psysteme scn, Pbase base_index)
Psysteme new_loop_bound(Psysteme scn, Pbase base_index) computation of the new iteration space (given...
static list * w_effects
PDSon: w_effect store all the variables modified in the sequence of statement.
#define intptr_t
Definition: stdint.in.h:294
le type des coefficients dans les vecteurs: Value est defini dans le package arithmetique
Definition: vecteur-local.h:89
FI: I do not understand why the type is duplicated at the set level.
Definition: set.c:59
The structure used to build lists in NewGen.
Definition: newgen_list.h:41
Definition: delay.c:253
bool res
Definition: terapixify.c:324
entity ref
Definition: terapixify.c:323
entity e
Definition: terapixify.c:106
Definition: statement.c:4047
entity iterator
Definition: terapixify.c:474
struct block block
#define TERAPIX_MASK_PREFIX
Definition: terapixify.c:131
bool generate_two_addresses_code(const string module_name)
Definition: terapixify.c:991
static bool terapix_renamed_p(const char *s)
Definition: terapixify.c:154
static bool terapix_pointer_initialized_from_a_mask_p(entity e)
Definition: terapixify.c:354
static bool can_terapixify_expression_p(expression e, bool *can_terapixify)
Definition: terapixify.c:86
static entity tw_loop_index
Definition: terapixify.c:838
static bool terapix_suitable_loop_bound_p(expression exp)
Definition: terapixify.c:231
static bool terapix_renamed_local_p(const char *s, const char *prefix)
Definition: terapixify.c:135
bool terapix_warmup(const char *module_name)
Definition: terapixify.c:908
static bool terapix_suitable_loop_bound_walker(reference r, bool *suitable)
Definition: terapixify.c:225
static void stmt_rm_useless_label_rwt(statement s)
Definition: terapixify.c:621
static void do_terapix_argument_handler(entity e, string arg_prefix, size_t *arg_cnt, string ass_prefix, size_t *ass_cnt, bool force)
Definition: terapixify.c:164
static void two_addresses_code_generator(statement s)
Definition: terapixify.c:948
static bool terapix_renamed_entity_p(entity e, const char *prefix)
Definition: terapixify.c:147
static void normalize_microcode_parameter_orders(entity module)
Definition: terapixify.c:318
static void do_terapix_warmup_patching(reference r, entity e)
Definition: terapixify.c:839
static bool two_addresses_code_generator_split_p(expression e)
Definition: terapixify.c:935
static void entity_used_in_reference_walker(reference r, struct entity_bool *eb)
Definition: terapixify.c:109
static void terapix_normalize_tests(call c)
a test is normalized when it is in the form a>0
Definition: terapixify.c:362
void normalize_microcode_anotate()
terapixify.c
Definition: terapixify.c:410
#define TERAPIX_IMAGE_PREFIX
Definition: terapixify.c:130
static bool cannot_terapixify(gen_chunk *elem, bool *can_terapixify)
terapixify
Definition: terapixify.c:68
static bool can_terapixify_call_p(call c, bool *can_terapixify)
Definition: terapixify.c:75
static void terapixify_loops(statement s)
Definition: terapixify.c:565
static bool terapix_mask_entity_p(entity e)
Definition: terapixify.c:150
static void entity_used_in_loop_bound_walker(loop l, struct entity_bool *eb)
Definition: terapixify.c:115
static bool do_terapix_loop_optimizer(call c, tlo_context_t *ctxt)
Definition: terapixify.c:479
static void terapix_loop_handler(statement sl, terapix_loop_handler_param *p)
Definition: terapixify.c:245
static void terapix_argument_handler(entity e, string arg_prefix, size_t *arg_cnt, string ass_prefix, size_t *ass_cnt)
Definition: terapixify.c:217
static bool do_terapix_warmup(statement top)
make sure s is of the form decl loop nest
Definition: terapixify.c:879
#define TERAPIX_ACC
static void terapixify_loop_purge(statement s, entity e)
Definition: terapixify.c:399
#define TERAPIX_PTRARG_PREFIX
Definition: terapixify.c:128
static void terapix_optimize_accumulator(statement st)
if only one register is ever written by a sequence of assignment, take advantage of it
Definition: terapixify.c:442
bool normalize_microcode(char *module_name)
Definition: terapixify.c:626
#define TERAPIX_LOOPARG_PREFIX
Definition: terapixify.c:129
static int compare_formal_parameters(const void *v0, const void *v1)
Definition: terapixify.c:300
static void do_terapix_remove_divide(call c)
Definition: terapixify.c:1011
bool terapix_remove_divide(const string module_name)
Definition: terapixify.c:1045
static void force_terapix_argument_handler(entity e, string arg_prefix, size_t *arg_cnt, string ass_prefix, size_t *ass_cnt)
Definition: terapixify.c:220
#define TERAPIX_REGISTER_PREFIX
Definition: terapixify.c:132
static void do_terapix_pointer_initialized_from_a_mask_p(call c, context *ctxt)
Definition: terapixify.c:327
void terapix_loop_optimizer(statement st)
Definition: terapixify.c:498
static bool entity_used_in_loop_bound_p(entity e)
Definition: terapixify.c:121
string words_to_string(cons *lw)
Definition: print.c:211
A gen_chunk is used to store every object.
Definition: genC.h:58
_int i
Definition: genC.h:62
#define exp
Avoid some warnings from "gcc -Wshadow".
Definition: vasnprintf.c:207
#define vecteur_val(v)
#define vecteur_var(v)
#define vecteur_succ(v)
#define VECTEUR_NUL_P(v)
Pvecteur vect_new(Variable var, Value coeff)
Pvecteur vect_new(Variable var,Value coeff): allocation d'un vecteur colineaire au vecteur de base va...
Definition: alloc.c:110
void vect_rm(Pvecteur v)
void vect_rm(Pvecteur v): desallocation des couples de v;
Definition: alloc.c:78