1/* TREELANG Compiler interface to GCC's middle end (treetree.c)
2   Called by the parser.
3
4   If you want a working example of how to write a front end to GCC,
5   you are in the right place.
6
7   Copyright (C) 1988, 1992, 1993, 1994, 1995, 1996, 1997, 1998,
8   1999, 2000, 2001, 2002, 2003, 2004, 2005 Free Software Foundation, Inc.
9
10   This code is based on toy.c written by Richard Kenner.
11
12   It was later modified by Jonathan Bartlett whose changes have all
13   been removed (by Tim Josling).
14
15   Various bits and pieces were cloned from the GCC main tree, as
16   GCC evolved, for COBOLForGCC, by Tim Josling.
17
18   It was adapted to TREELANG by Tim Josling 2001.
19
20   Updated to function-at-a-time by James A. Morrison, 2004.
21
22   -----------------------------------------------------------------------
23
24   This program is free software; you can redistribute it and/or modify it
25   under the terms of the GNU General Public License as published by the
26   Free Software Foundation; either version 2, or (at your option) any
27   later version.
28
29   This program is distributed in the hope that it will be useful,
30   but WITHOUT ANY WARRANTY; without even the implied warranty of
31   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
32   GNU General Public License for more details.
33
34   You should have received a copy of the GNU General Public License
35   along with this program; if not, write to the Free Software
36   Foundation, 51 Franklin Street, Fifth Floor,
37   Boston, MA 02110-1301, USA.
38
39   In other words, you are welcome to use, share and improve this program.
40   You are forbidden to forbid anyone else to use, share and improve
41   what you give them.   Help stamp out software-hoarding!
42
43   -----------------------------------------------------------------------  */
44
45/* Assumption: garbage collection is never called implicitly.  It will
46   not be called 'at any time' when short of memory.  It will only be
47   called explicitly at the end of each function.  This removes the
48   need for a *lot* of bother to ensure everything is in the mark trees
49   at all times.  */
50
51/* Note, it is OK to use GCC extensions such as long long in a compiler front
52   end.  This is because the GCC front ends are built using GCC.   */
53
54/* GCC headers.  */
55
56#include "config.h"
57#include "system.h"
58#include "coretypes.h"
59#include "tm.h"
60#include "tree.h"
61#include "tree-dump.h"
62#include "tree-iterator.h"
63#include "tree-gimple.h"
64#include "function.h"
65#include "flags.h"
66#include "output.h"
67#include "ggc.h"
68#include "toplev.h"
69#include "varray.h"
70#include "langhooks-def.h"
71#include "langhooks.h"
72#include "target.h"
73
74#include "cgraph.h"
75
76#include "treelang.h"
77#include "treetree.h"
78#include "opts.h"
79
80extern int option_main;
81extern char **file_names;
82
83/* Types expected by gcc's garbage collector.
84   These types exist to allow language front-ends to
85   add extra information in gcc's parse tree data structure.
86   But the treelang front end doesn't use them -- it has
87   its own parse tree data structure.
88   We define them here only to satisfy gcc's garbage collector.  */
89
90/* Language-specific identifier information.  */
91
92struct lang_identifier GTY(())
93{
94  struct tree_identifier common;
95};
96
97/* Language-specific tree node information.  */
98
99union lang_tree_node
100  GTY((desc ("TREE_CODE (&%h.generic) == IDENTIFIER_NODE")))
101{
102  union tree_node GTY ((tag ("0"),
103			desc ("tree_node_structure (&%h)")))
104    generic;
105  struct lang_identifier GTY ((tag ("1"))) identifier;
106};
107
108/* Language-specific type information.  */
109
110struct lang_type GTY(())
111{
112  char junk; /* dummy field to ensure struct is not empty */
113};
114
115/* Language-specific declaration information.  */
116
117struct lang_decl GTY(())
118{
119  char junk; /* dummy field to ensure struct is not empty */
120};
121
122struct language_function GTY(())
123{
124  char junk; /* dummy field to ensure struct is not empty */
125};
126
127static bool tree_mark_addressable (tree exp);
128static tree tree_lang_type_for_size (unsigned precision, int unsignedp);
129static tree tree_lang_type_for_mode (enum machine_mode mode, int unsignedp);
130static tree tree_lang_unsigned_type (tree type_node);
131static tree tree_lang_signed_type (tree type_node);
132static tree tree_lang_signed_or_unsigned_type (int unsignedp, tree type);
133
134/* Functions to keep track of the current scope.  */
135static void pushlevel (int ignore);
136static tree poplevel (int keep, int reverse, int functionbody);
137static tree pushdecl (tree decl);
138static tree* getstmtlist (void);
139
140/* Langhooks.  */
141static tree builtin_function (const char *name, tree type, int function_code,
142			      enum built_in_class class,
143			      const char *library_name,
144			      tree attrs);
145extern const struct attribute_spec treelang_attribute_table[];
146static tree getdecls (void);
147static int global_bindings_p (void);
148static void insert_block (tree);
149
150static void tree_push_type_decl (tree id, tree type_node);
151static void treelang_expand_function (tree fndecl);
152
153/* The front end language hooks (addresses of code for this front
154   end).  These are not really very language-dependent, i.e.
155   treelang, C, Mercury, etc. can all use almost the same definitions.  */
156
157#undef LANG_HOOKS_MARK_ADDRESSABLE
158#define LANG_HOOKS_MARK_ADDRESSABLE tree_mark_addressable
159#undef LANG_HOOKS_SIGNED_TYPE
160#define LANG_HOOKS_SIGNED_TYPE tree_lang_signed_type
161#undef LANG_HOOKS_UNSIGNED_TYPE
162#define LANG_HOOKS_UNSIGNED_TYPE tree_lang_unsigned_type
163#undef LANG_HOOKS_SIGNED_OR_UNSIGNED_TYPE
164#define LANG_HOOKS_SIGNED_OR_UNSIGNED_TYPE tree_lang_signed_or_unsigned_type
165#undef LANG_HOOKS_TYPE_FOR_MODE
166#define LANG_HOOKS_TYPE_FOR_MODE tree_lang_type_for_mode
167#undef LANG_HOOKS_TYPE_FOR_SIZE
168#define LANG_HOOKS_TYPE_FOR_SIZE tree_lang_type_for_size
169#undef LANG_HOOKS_PARSE_FILE
170#define LANG_HOOKS_PARSE_FILE treelang_parse_file
171#undef LANG_HOOKS_ATTRIBUTE_TABLE
172#define LANG_HOOKS_ATTRIBUTE_TABLE treelang_attribute_table
173
174#undef LANG_HOOKS_CALLGRAPH_EXPAND_FUNCTION
175#define LANG_HOOKS_CALLGRAPH_EXPAND_FUNCTION treelang_expand_function
176
177/* #undef LANG_HOOKS_TYPES_COMPATIBLE_P
178#define LANG_HOOKS_TYPES_COMPATIBLE_P hook_bool_tree_tree_true
179*/
180/* Hook routines and data unique to treelang.  */
181
182#undef LANG_HOOKS_INIT
183#define LANG_HOOKS_INIT treelang_init
184#undef LANG_HOOKS_NAME
185#define LANG_HOOKS_NAME	"GNU treelang"
186#undef LANG_HOOKS_FINISH
187#define LANG_HOOKS_FINISH		treelang_finish
188#undef LANG_HOOKS_INIT_OPTIONS
189#define LANG_HOOKS_INIT_OPTIONS  treelang_init_options
190#undef LANG_HOOKS_HANDLE_OPTION
191#define LANG_HOOKS_HANDLE_OPTION treelang_handle_option
192const struct lang_hooks lang_hooks = LANG_HOOKS_INITIALIZER;
193
194/* Tree code type/name/code tables.  */
195
196#define DEFTREECODE(SYM, NAME, TYPE, LENGTH) TYPE,
197
198const enum tree_code_class tree_code_type[] = {
199#include "tree.def"
200  tcc_exceptional
201};
202#undef DEFTREECODE
203
204#define DEFTREECODE(SYM, NAME, TYPE, LENGTH) LENGTH,
205
206const unsigned char tree_code_length[] = {
207#include "tree.def"
208  0
209};
210#undef DEFTREECODE
211
212#define DEFTREECODE(SYM, NAME, TYPE, LEN) NAME,
213
214const char *const tree_code_name[] = {
215#include "tree.def"
216  "@@dummy"
217};
218#undef DEFTREECODE
219
220/* Number of bits in int and char - accessed by front end.  */
221
222unsigned int tree_code_int_size = SIZEOF_INT * HOST_BITS_PER_CHAR;
223
224unsigned int tree_code_char_size = HOST_BITS_PER_CHAR;
225
226/* Return the tree stuff for this type TYPE_NUM.  */
227
228tree
229tree_code_get_type (int type_num)
230{
231  switch (type_num)
232    {
233    case SIGNED_CHAR:
234      return signed_char_type_node;
235
236    case UNSIGNED_CHAR:
237      return unsigned_char_type_node;
238
239    case SIGNED_INT:
240      return integer_type_node;
241
242    case UNSIGNED_INT:
243      return unsigned_type_node;
244
245    case VOID_TYPE:
246      return void_type_node;
247
248    default:
249      gcc_unreachable ();
250    }
251}
252
253/* Output the code for the start of an if statement.  The test
254   expression is EXP (true if not zero), and the stmt occurred at line
255   LINENO in file FILENAME.  */
256
257void
258tree_code_if_start (tree exp, location_t loc)
259{
260  tree cond_exp, cond;
261  cond_exp = fold_build2 (NE_EXPR, boolean_type_node, exp,
262			  build_int_cst (TREE_TYPE (exp), 0));
263  SET_EXPR_LOCATION (cond_exp, loc);
264  cond = build3 (COND_EXPR, void_type_node, cond_exp, NULL_TREE,
265                 NULL_TREE);
266  SET_EXPR_LOCATION (cond, loc);
267  append_to_statement_list_force (cond, getstmtlist ());
268  pushlevel (0);
269}
270
271/* Output the code for the else of an if statement.  The else occurred
272   at line LINENO in file FILENAME.  */
273
274void
275tree_code_if_else (location_t loc ATTRIBUTE_UNUSED)
276{
277  tree stmts = *getstmtlist ();
278  tree block = poplevel (1, 0, 0);
279  if (BLOCK_VARS (block))
280    {
281      tree bindexpr = build3 (BIND_EXPR, void_type_node, BLOCK_VARS (block),
282                              stmts, block);
283      stmts = alloc_stmt_list ();
284      append_to_statement_list (bindexpr, &stmts);
285    }
286
287  TREE_OPERAND (STATEMENT_LIST_TAIL (*getstmtlist ())->stmt, 1) = stmts;
288  pushlevel (0);
289}
290
291/* Output the code for the end_if an if statement.  The end_if (final brace)
292   occurred at line LINENO in file FILENAME.  */
293
294void
295tree_code_if_end (location_t loc ATTRIBUTE_UNUSED)
296{
297  tree stmts = *getstmtlist ();
298  tree block = poplevel (1, 0, 0);
299  if (BLOCK_VARS (block))
300    {
301       tree bindexpr = build3 (BIND_EXPR, void_type_node, BLOCK_VARS (block),
302                               stmts, block);
303       stmts = alloc_stmt_list ();
304       append_to_statement_list (bindexpr, &stmts);
305    }
306
307  TREE_OPERAND (STATEMENT_LIST_TAIL (*getstmtlist ())->stmt, 2) = stmts;
308}
309
310/* Create a function.  The prototype name is NAME, storage class is
311   STORAGE_CLASS, type of return variable is RET_TYPE, parameter lists
312   is PARMS, returns decl for this function.  */
313
314tree
315tree_code_create_function_prototype (unsigned char* chars,
316				     unsigned int storage_class,
317				     unsigned int ret_type,
318				     struct prod_token_parm_item* parms,
319				     location_t loc)
320{
321
322  tree id;
323  struct prod_token_parm_item* parm;
324  tree type_list = NULL_TREE;
325  tree type_node;
326  tree fn_type;
327  tree fn_decl;
328  tree parm_list = NULL_TREE;
329
330  /* Build the type.  */
331  id = get_identifier ((const char*)chars);
332  for (parm = parms; parm; parm = parm->tp.par.next)
333    {
334      gcc_assert (parm->category == parameter_category);
335      type_node = tree_code_get_type (parm->type);
336      type_list = tree_cons (NULL_TREE, type_node, type_list);
337    }
338  /* Last parm if void indicates fixed length list (as opposed to
339     printf style va_* list).  */
340  type_list = tree_cons (NULL_TREE, void_type_node, type_list);
341
342  /* The back end needs them in reverse order.  */
343  type_list = nreverse (type_list);
344
345  type_node = tree_code_get_type (ret_type);
346  fn_type = build_function_type (type_node, type_list);
347
348  id = get_identifier ((const char*)chars);
349  fn_decl = build_decl (FUNCTION_DECL, id, fn_type);
350
351  /* Nested functions not supported here.  */
352  DECL_CONTEXT (fn_decl) = NULL_TREE;
353  DECL_SOURCE_LOCATION (fn_decl) = loc;
354
355  TREE_PUBLIC (fn_decl) = 0;
356  DECL_EXTERNAL (fn_decl) = 0;
357  TREE_STATIC (fn_decl) = 0;
358  switch (storage_class)
359    {
360    case STATIC_STORAGE:
361      break;
362
363    case EXTERNAL_DEFINITION_STORAGE:
364      TREE_PUBLIC (fn_decl) = 1;
365      break;
366
367    case EXTERNAL_REFERENCE_STORAGE:
368      DECL_EXTERNAL (fn_decl) = 1;
369      break;
370
371    case AUTOMATIC_STORAGE:
372    default:
373      gcc_unreachable ();
374    }
375
376  /* Make the argument variable decls.  */
377  for (parm = parms; parm; parm = parm->tp.par.next)
378    {
379      tree parm_decl = build_decl (PARM_DECL, get_identifier
380                                   ((const char*) (parm->tp.par.variable_name)),
381                                   tree_code_get_type (parm->type));
382
383      /* Some languages have different nominal and real types.  */
384      DECL_ARG_TYPE (parm_decl) = TREE_TYPE (parm_decl);
385      gcc_assert (DECL_ARG_TYPE (parm_decl));
386      gcc_assert (fn_decl);
387      DECL_CONTEXT (parm_decl) = fn_decl;
388      DECL_SOURCE_LOCATION (parm_decl) = loc;
389      parm_list = chainon (parm_decl, parm_list);
390    }
391
392  /* Back into reverse order as the back end likes them.  */
393  parm_list = nreverse (parm_list);
394
395  DECL_ARGUMENTS (fn_decl) = parm_list;
396
397  /* Save the decls for use when the args are referred to.  */
398  for (parm = parms; parm_list;
399       parm_list = TREE_CHAIN (parm_list),
400	parm = parm->tp.par.next)
401    {
402      gcc_assert (parm); /* Too few.  */
403      *parm->tp.par.where_to_put_var_tree = parm_list;
404    }
405  gcc_assert (!parm); /* Too many.  */
406
407  /* Process declaration of function defined elsewhere.  */
408  rest_of_decl_compilation (fn_decl, 1, 0);
409
410  return fn_decl;
411}
412
413
414/* Output code for start of function; the decl of the function is in
415   PREV_SAVED (as created by tree_code_create_function_prototype),
416   the function is at line number LINENO in file FILENAME.  The
417   parameter details are in the lists PARMS. Returns nothing.  */
418
419void
420tree_code_create_function_initial (tree prev_saved,
421				   location_t loc)
422{
423  tree fn_decl;
424  tree resultdecl;
425
426  fn_decl = prev_saved;
427  gcc_assert (fn_decl);
428
429  /* Output message if not -quiet.  */
430  announce_function (fn_decl);
431
432  /* This has something to do with forcing output also.  */
433  pushdecl (fn_decl);
434
435  /* Set current function for error msgs etc.  */
436  current_function_decl = fn_decl;
437  DECL_INITIAL (fn_decl) = error_mark_node;
438
439  DECL_SOURCE_LOCATION (fn_decl) = loc;
440
441  /* Create a DECL for the functions result.  */
442  resultdecl =
443    build_decl (RESULT_DECL, NULL_TREE, TREE_TYPE (TREE_TYPE (fn_decl)));
444  DECL_CONTEXT (resultdecl) = fn_decl;
445  DECL_ARTIFICIAL (resultdecl) = 1;
446  DECL_IGNORED_P (resultdecl) = 1;
447  DECL_SOURCE_LOCATION (resultdecl) = loc;
448  DECL_RESULT (fn_decl) = resultdecl;
449
450  /* Create a new level at the start of the function.  */
451
452  pushlevel (0);
453
454  TREE_STATIC (fn_decl) = 1;
455}
456
457/* Wrapup a function contained in file FILENAME, ending at line LINENO.  */
458void
459tree_code_create_function_wrapup (location_t loc)
460{
461  tree block;
462  tree fn_decl;
463  tree stmts = *getstmtlist ();
464
465  fn_decl = current_function_decl;
466
467  /* Pop the level.  */
468
469  block = poplevel (1, 0, 1);
470
471  /* And attach it to the function.  */
472
473  DECL_SAVED_TREE (fn_decl) = build3 (BIND_EXPR, void_type_node,
474                                      BLOCK_VARS (block),
475			              stmts, block);
476
477  allocate_struct_function (fn_decl);
478  cfun->function_end_locus = loc;
479
480  /* Dump the original tree to a file.  */
481  dump_function (TDI_original, fn_decl);
482
483  /* Convert current function to GIMPLE for the middle end.  */
484  gimplify_function_tree (fn_decl);
485  dump_function (TDI_generic, fn_decl);
486
487  /* We are not inside of any scope now.  */
488  current_function_decl = NULL_TREE;
489  cfun = NULL;
490
491  /* Pass the current function off to the middle end.  */
492  (void)cgraph_node (fn_decl);
493  cgraph_finalize_function (fn_decl, false);
494}
495
496/* Create a variable.
497
498   The storage class is STORAGE_CLASS (eg LOCAL).
499   The name is CHARS/LENGTH.
500   The type is EXPRESSION_TYPE (eg UNSIGNED_TYPE).
501   The init tree is INIT.  */
502
503tree
504tree_code_create_variable (unsigned int storage_class,
505			   unsigned char* chars,
506			   unsigned int length,
507			   unsigned int expression_type,
508			   tree init,
509			   location_t loc)
510{
511  tree var_type;
512  tree var_id;
513  tree var_decl;
514
515  /* 1. Build the type.  */
516  var_type = tree_code_get_type (expression_type);
517
518  /* 2. Build the name.  */
519  gcc_assert (chars[length] == 0); /* Should be null terminated.  */
520
521  var_id = get_identifier ((const char*)chars);
522
523  /* 3. Build the decl and set up init.  */
524  var_decl = build_decl (VAR_DECL, var_id, var_type);
525
526  /* 3a. Initialization.  */
527  if (init)
528    DECL_INITIAL (var_decl) = fold_convert (var_type, init);
529  else
530    DECL_INITIAL (var_decl) = NULL_TREE;
531
532  gcc_assert (TYPE_SIZE (var_type) != 0); /* Did not calculate size.  */
533
534  DECL_CONTEXT (var_decl) = current_function_decl;
535
536  DECL_SOURCE_LOCATION (var_decl) = loc;
537
538  DECL_EXTERNAL (var_decl) = 0;
539  TREE_PUBLIC (var_decl) = 0;
540  TREE_STATIC (var_decl) = 0;
541  /* Set the storage mode and whether only visible in the same file.  */
542  switch (storage_class)
543    {
544    case STATIC_STORAGE:
545      TREE_STATIC (var_decl) = 1;
546      break;
547
548    case AUTOMATIC_STORAGE:
549      break;
550
551    case EXTERNAL_DEFINITION_STORAGE:
552      TREE_PUBLIC (var_decl) = 1;
553      break;
554
555    case EXTERNAL_REFERENCE_STORAGE:
556      DECL_EXTERNAL (var_decl) = 1;
557      break;
558
559    default:
560      gcc_unreachable ();
561    }
562
563  TYPE_NAME (TREE_TYPE (var_decl)) = TYPE_NAME (var_type);
564  return pushdecl (copy_node (var_decl));
565}
566
567
568/* Generate code for return statement.  Type is in TYPE, expression
569   is in EXP if present.  */
570
571void
572tree_code_generate_return (tree type, tree exp)
573{
574  tree setret;
575#ifdef ENABLE_CHECKING
576  tree param;
577
578  for (param = DECL_ARGUMENTS (current_function_decl);
579       param;
580       param = TREE_CHAIN (param))
581    gcc_assert (DECL_CONTEXT (param) == current_function_decl);
582#endif
583
584  if (exp && TREE_TYPE (TREE_TYPE (current_function_decl)) != void_type_node)
585    {
586      setret = fold_build2 (MODIFY_EXPR, type,
587                            DECL_RESULT (current_function_decl),
588                            fold_convert (type, exp));
589      TREE_SIDE_EFFECTS (setret) = 1;
590      TREE_USED (setret) = 1;
591      setret = build1 (RETURN_EXPR, type, setret);
592      /* Use EXPR_LOCUS so we don't lose any information about the file we
593	 are compiling.  */
594      SET_EXPR_LOCUS (setret, EXPR_LOCUS (exp));
595    }
596   else
597     setret = build1 (RETURN_EXPR, type, NULL_TREE);
598
599   append_to_statement_list_force (setret, getstmtlist ());
600}
601
602
603/* Output the code for this expression statement CODE.  */
604
605void
606tree_code_output_expression_statement (tree code, location_t loc)
607{
608  /* Output the line number information.  */
609  SET_EXPR_LOCATION (code, loc);
610  TREE_USED (code) = 1;
611  TREE_SIDE_EFFECTS (code) = 1;
612  /* put CODE into the code list.  */
613  append_to_statement_list_force (code, getstmtlist ());
614}
615
616/* Return a tree for a constant integer value in the token TOK.  No
617   size checking is done.  */
618
619tree
620tree_code_get_integer_value (unsigned char* chars, unsigned int length)
621{
622  long long int val = 0;
623  unsigned int ix;
624  unsigned int start = 0;
625  int negative = 1;
626  switch (chars[0])
627    {
628    case (unsigned char)'-':
629      negative = -1;
630      start = 1;
631      break;
632
633    case (unsigned char)'+':
634      start = 1;
635      break;
636
637    default:
638      break;
639    }
640  for (ix = start; ix < length; ix++)
641    val = val * 10 + chars[ix] - (unsigned char)'0';
642  val = val*negative;
643  return build_int_cst_wide (start == 1 ?
644				integer_type_node : unsigned_type_node,
645			     val & 0xffffffff, (val >> 32) & 0xffffffff);
646}
647
648/* Return the tree for an expression, type EXP_TYPE (see treetree.h)
649   with tree type TYPE and with operands1 OP1, OP2 (maybe), OP3 (maybe).  */
650tree
651tree_code_get_expression (unsigned int exp_type,
652                          tree type, tree op1, tree op2,
653			  tree op3 ATTRIBUTE_UNUSED,
654			  location_t loc)
655{
656  tree ret1;
657  int operator;
658
659  switch (exp_type)
660    {
661    case EXP_ASSIGN:
662      gcc_assert (op1 && op2);
663      operator = MODIFY_EXPR;
664      ret1 = fold_build2 (operator, void_type_node, op1,
665                          fold_convert (TREE_TYPE (op1), op2));
666
667      break;
668
669    case EXP_PLUS:
670      operator = PLUS_EXPR;
671      goto binary_expression;
672
673    case EXP_MINUS:
674      operator = MINUS_EXPR;
675      goto binary_expression;
676
677    case EXP_EQUALS:
678      operator = EQ_EXPR;
679      goto binary_expression;
680
681    /* Expand a binary expression.  Ensure the operands are the right type.  */
682    binary_expression:
683      gcc_assert (op1 && op2);
684      ret1  =  fold_build2 (operator, type,
685			    fold_convert (type, op1),
686			    fold_convert (type, op2));
687      break;
688
689      /* Reference to a variable.  This is dead easy, just return the
690         decl for the variable.  If the TYPE is different than the
691         variable type, convert it.  However, to keep accurate location
692	 information we wrap it in a NOP_EXPR is is easily stripped.  */
693    case EXP_REFERENCE:
694      gcc_assert (op1);
695      TREE_USED (op1) = 1;
696      if (type == TREE_TYPE (op1))
697        ret1 = build1 (NOP_EXPR, type, op1);
698      else
699        ret1 = fold_convert (type, op1);
700      break;
701
702    case EXP_FUNCTION_INVOCATION:
703      gcc_assert (op1);
704      gcc_assert(TREE_TYPE (TREE_TYPE (op1)) == type);
705      TREE_USED (op1) = 1;
706      ret1 = build_function_call_expr(op1, op2);
707      break;
708
709    default:
710      gcc_unreachable ();
711    }
712
713  /* Declarations already have a location and constants can be shared so they
714     shouldn't a location set on them.  */
715  if (! DECL_P (ret1) && ! TREE_CONSTANT (ret1))
716    SET_EXPR_LOCATION (ret1, loc);
717  return ret1;
718}
719
720/* Init parameter list and return empty list.  */
721
722tree
723tree_code_init_parameters (void)
724{
725  return NULL_TREE;
726}
727
728/* Add a parameter EXP whose expression type is EXP_PROTO to list
729   LIST, returning the new list.  */
730
731tree
732tree_code_add_parameter (tree list, tree proto_exp, tree exp)
733{
734  tree new_exp;
735  new_exp = tree_cons (NULL_TREE,
736                       fold_convert (TREE_TYPE (proto_exp),
737				     exp), NULL_TREE);
738  if (!list)
739    return new_exp;
740  return chainon (new_exp, list);
741}
742
743/* Get a stringpool entry for a string S of length L.  This is needed
744   because the GTY routines don't mark strings, forcing you to put
745   them into stringpool, which is never freed.  */
746
747const char*
748get_string (const char *s, size_t l)
749{
750  tree t;
751  t = get_identifier_with_length (s, l);
752  return IDENTIFIER_POINTER(t);
753}
754
755/* Save typing debug_tree all the time. Dump a tree T pretty and
756   concise.  */
757
758void dt (tree t);
759
760void
761dt (tree t)
762{
763  debug_tree (t);
764}
765
766/* Routines Expected by gcc:  */
767
768/* These are used to build types for various sizes.  The code below
769   is a simplified version of that of GNAT.  */
770
771#ifndef MAX_BITS_PER_WORD
772#define MAX_BITS_PER_WORD  BITS_PER_WORD
773#endif
774
775/* This variable keeps a table for types for each precision so that we only
776   allocate each of them once. Signed and unsigned types are kept separate.  */
777static GTY(()) tree signed_and_unsigned_types[MAX_BITS_PER_WORD + 1][2];
778
779/* Mark EXP saying that we need to be able to take the
780   address of it; it should not be allocated in a register.
781   Value is 1 if successful.
782
783   This implementation was copied from c-decl.c. */
784
785static bool
786tree_mark_addressable (tree exp)
787{
788  register tree x = exp;
789  while (1)
790    switch (TREE_CODE (x))
791      {
792      case COMPONENT_REF:
793      case ADDR_EXPR:
794      case ARRAY_REF:
795      case REALPART_EXPR:
796      case IMAGPART_EXPR:
797	x = TREE_OPERAND (x, 0);
798	break;
799
800      case CONSTRUCTOR:
801	TREE_ADDRESSABLE (x) = 1;
802	return 1;
803
804      case VAR_DECL:
805      case CONST_DECL:
806      case PARM_DECL:
807      case RESULT_DECL:
808	if (DECL_REGISTER (x) && !TREE_ADDRESSABLE (x)
809	    && DECL_NONLOCAL (x))
810	  {
811	    if (TREE_PUBLIC (x))
812	      {
813		error ("Global register variable %qD used in nested function.",
814		       x);
815		return 0;
816	      }
817	    pedwarn ("Register variable %qD used in nested function.", x);
818	  }
819	else if (DECL_REGISTER (x) && !TREE_ADDRESSABLE (x))
820	  {
821	    if (TREE_PUBLIC (x))
822	      {
823		error ("Address of global register variable %qD requested.",
824		       x);
825		return 0;
826	      }
827
828	    pedwarn ("Address of register variable %qD requested.", x);
829	  }
830
831	/* drops in */
832      case FUNCTION_DECL:
833	TREE_ADDRESSABLE (x) = 1;
834
835      default:
836	return 1;
837    }
838}
839
840/* Return an integer type with the number of bits of precision given by
841   PRECISION.  UNSIGNEDP is nonzero if the type is unsigned; otherwise
842   it is a signed type.  */
843
844static tree
845tree_lang_type_for_size (unsigned precision, int unsignedp)
846{
847  tree t;
848
849  if (precision <= MAX_BITS_PER_WORD
850      && signed_and_unsigned_types[precision][unsignedp] != 0)
851    return signed_and_unsigned_types[precision][unsignedp];
852
853  if (unsignedp)
854    t = signed_and_unsigned_types[precision][1]
855      = make_unsigned_type (precision);
856  else
857    t = signed_and_unsigned_types[precision][0]
858      = make_signed_type (precision);
859
860  return t;
861}
862
863/* Return a data type that has machine mode MODE.  UNSIGNEDP selects
864   an unsigned type; otherwise a signed type is returned.  */
865
866static tree
867tree_lang_type_for_mode (enum machine_mode mode, int unsignedp)
868{
869  if (SCALAR_INT_MODE_P (mode))
870    return tree_lang_type_for_size (GET_MODE_BITSIZE (mode), unsignedp);
871  else
872    return NULL_TREE;
873}
874
875/* Return the unsigned version of a TYPE_NODE, a scalar type.  */
876
877static tree
878tree_lang_unsigned_type (tree type_node)
879{
880  return tree_lang_type_for_size (TYPE_PRECISION (type_node), 1);
881}
882
883/* Return the signed version of a TYPE_NODE, a scalar type.  */
884
885static tree
886tree_lang_signed_type (tree type_node)
887{
888  return tree_lang_type_for_size (TYPE_PRECISION (type_node), 0);
889}
890
891/* Return a type the same as TYPE except unsigned or signed according to
892   UNSIGNEDP.  */
893
894static tree
895tree_lang_signed_or_unsigned_type (int unsignedp, tree type)
896{
897  if (! INTEGRAL_TYPE_P (type) || TYPE_UNSIGNED (type) == unsignedp)
898    return type;
899  else
900    return tree_lang_type_for_size (TYPE_PRECISION (type), unsignedp);
901}
902
903/* These functions and variables deal with binding contours.  We only
904   need these functions for the list of PARM_DECLs, but we leave the
905   functions more general; these are a simplified version of the
906   functions from GNAT.  */
907
908/* For each binding contour we allocate a binding_level structure which records
909   the entities defined or declared in that contour. Contours include:
910
911	the global one
912	one for each subprogram definition
913	one for each compound statement (declare block)
914
915   Binding contours are used to create GCC tree BLOCK nodes.  */
916
917struct binding_level
918{
919  /* A chain of ..._DECL nodes for all variables, constants, functions,
920     parameters and type declarations.  These ..._DECL nodes are chained
921     through the TREE_CHAIN field. Note that these ..._DECL nodes are stored
922     in the reverse of the order supplied to be compatible with the
923     back-end.  */
924  tree names;
925  /* For each level (except the global one), a chain of BLOCK nodes for all
926     the levels that were entered and exited one level down from this one.  */
927  tree blocks;
928
929  tree stmts;
930  /* The binding level containing this one (the enclosing binding level). */
931  struct binding_level *level_chain;
932};
933
934/* The binding level currently in effect.  */
935static struct binding_level *current_binding_level = NULL;
936
937/* The outermost binding level. This binding level is created when the
938   compiler is started and it will exist through the entire compilation.  */
939static struct binding_level *global_binding_level;
940
941/* Binding level structures are initialized by copying this one.  */
942static struct binding_level clear_binding_level = {NULL, NULL, NULL, NULL };
943
944/* Return non-zero if we are currently in the global binding level.  */
945
946static int
947global_bindings_p (void)
948{
949  return current_binding_level == global_binding_level ? -1 : 0;
950}
951
952
953/* Return the list of declarations in the current level. Note that this list
954   is in reverse order (it has to be so for back-end compatibility).  */
955
956static tree
957getdecls (void)
958{
959  return current_binding_level->names;
960}
961
962/* Return a STATMENT_LIST for the current block.  */
963
964static tree*
965getstmtlist (void)
966{
967  return &current_binding_level->stmts;
968}
969
970/* Enter a new binding level. The input parameter is ignored, but has to be
971   specified for back-end compatibility.  */
972
973static void
974pushlevel (int ignore ATTRIBUTE_UNUSED)
975{
976  struct binding_level *newlevel = XNEW (struct binding_level);
977
978  *newlevel = clear_binding_level;
979
980  /* Add this level to the front of the chain (stack) of levels that are
981     active.  */
982  newlevel->level_chain = current_binding_level;
983  current_binding_level = newlevel;
984  current_binding_level->stmts = alloc_stmt_list ();
985}
986
987/* Exit a binding level.
988   Pop the level off, and restore the state of the identifier-decl mappings
989   that were in effect when this level was entered.
990
991   If KEEP is nonzero, this level had explicit declarations, so
992   and create a "block" (a BLOCK node) for the level
993   to record its declarations and subblocks for symbol table output.
994
995   If FUNCTIONBODY is nonzero, this level is the body of a function,
996   so create a block as if KEEP were set and also clear out all
997   label names.
998
999   If REVERSE is nonzero, reverse the order of decls before putting
1000   them into the BLOCK.  */
1001
1002static tree
1003poplevel (int keep, int reverse, int functionbody)
1004{
1005  /* Points to a BLOCK tree node. This is the BLOCK node constructed for the
1006     binding level that we are about to exit and which is returned by this
1007     routine.  */
1008  tree block_node = NULL_TREE;
1009  tree decl_chain;
1010  tree subblock_chain = current_binding_level->blocks;
1011  tree subblock_node;
1012
1013  /* Reverse the list of *_DECL nodes if desired.  Note that the ..._DECL
1014     nodes chained through the `names' field of current_binding_level are in
1015     reverse order except for PARM_DECL node, which are explicitly stored in
1016     the right order.  */
1017  decl_chain = (reverse) ? nreverse (current_binding_level->names)
1018			 : current_binding_level->names;
1019
1020  /* If there were any declarations in the current binding level, or if this
1021     binding level is a function body, or if there are any nested blocks then
1022     create a BLOCK node to record them for the life of this function.  */
1023  if (keep || functionbody)
1024    block_node = build_block (keep ? decl_chain : 0, subblock_chain, 0, 0);
1025
1026  /* Record the BLOCK node just built as the subblock its enclosing scope.  */
1027  for (subblock_node = subblock_chain; subblock_node;
1028       subblock_node = TREE_CHAIN (subblock_node))
1029    BLOCK_SUPERCONTEXT (subblock_node) = block_node;
1030
1031  /* Clear out the meanings of the local variables of this level.  */
1032
1033  for (subblock_node = decl_chain; subblock_node;
1034       subblock_node = TREE_CHAIN (subblock_node))
1035    if (DECL_NAME (subblock_node) != 0)
1036      /* If the identifier was used or addressed via a local extern decl,
1037	 don't forget that fact.   */
1038      if (DECL_EXTERNAL (subblock_node))
1039	{
1040	  if (TREE_USED (subblock_node))
1041	    TREE_USED (DECL_NAME (subblock_node)) = 1;
1042	}
1043
1044  /* Pop the current level.  */
1045  current_binding_level = current_binding_level->level_chain;
1046
1047  if (functionbody)
1048    {
1049      /* This is the top level block of a function.  */
1050      DECL_INITIAL (current_function_decl) = block_node;
1051    }
1052  else if (block_node)
1053    {
1054      current_binding_level->blocks
1055	= chainon (current_binding_level->blocks, block_node);
1056    }
1057
1058  /* If we did not make a block for the level just exited, any blocks made for
1059     inner levels (since they cannot be recorded as subblocks in that level)
1060     must be carried forward so they will later become subblocks of something
1061     else.  */
1062  else if (subblock_chain)
1063    current_binding_level->blocks
1064      = chainon (current_binding_level->blocks, subblock_chain);
1065  if (block_node)
1066    TREE_USED (block_node) = 1;
1067
1068  return block_node;
1069}
1070
1071/* Insert BLOCK at the end of the list of subblocks of the
1072   current binding level.  This is used when a BIND_EXPR is expanded,
1073   to handle the BLOCK node inside the BIND_EXPR.  */
1074
1075static void
1076insert_block (tree block)
1077{
1078  TREE_USED (block) = 1;
1079  current_binding_level->blocks
1080    = chainon (current_binding_level->blocks, block);
1081}
1082
1083
1084/* Records a ..._DECL node DECL as belonging to the current lexical scope.
1085   Returns the ..._DECL node. */
1086
1087tree
1088pushdecl (tree decl)
1089{
1090  /* External objects aren't nested, other objects may be.  */
1091
1092  if ((DECL_EXTERNAL (decl)) || (decl==current_function_decl))
1093    DECL_CONTEXT (decl) = 0;
1094  else
1095    DECL_CONTEXT (decl) = current_function_decl;
1096
1097  /* Put the declaration on the list.  The list of declarations is in reverse
1098     order. The list will be reversed later if necessary.  This needs to be
1099     this way for compatibility with the back-end.  */
1100
1101  TREE_CHAIN (decl) = current_binding_level->names;
1102  current_binding_level->names = decl;
1103
1104  /* For the declaration of a type, set its name if it is not already set. */
1105
1106  if (TREE_CODE (decl) == TYPE_DECL
1107      && TYPE_NAME (TREE_TYPE (decl)) == 0)
1108    TYPE_NAME (TREE_TYPE (decl)) = DECL_NAME (decl);
1109
1110  /* Put automatic variables into the intermediate representation.  */
1111  if (TREE_CODE (decl) == VAR_DECL && !DECL_EXTERNAL (decl)
1112      && !TREE_STATIC (decl) && !TREE_PUBLIC (decl))
1113    tree_code_output_expression_statement (build1 (DECL_EXPR, void_type_node,
1114                                                   decl),
1115                                           DECL_SOURCE_LOCATION (decl));
1116  return decl;
1117}
1118
1119
1120static void
1121tree_push_type_decl(tree id, tree type_node)
1122{
1123  tree decl = build_decl (TYPE_DECL, id, type_node);
1124  TYPE_NAME (type_node) = id;
1125  pushdecl (decl);
1126}
1127
1128#define NULL_BINDING_LEVEL (struct binding_level *) NULL
1129
1130/* Create the predefined scalar types of C,
1131   and some nodes representing standard constants (0, 1, (void *) 0).
1132   Initialize the global binding level.
1133   Make definitions for built-in primitive functions.  */
1134
1135void
1136treelang_init_decl_processing (void)
1137{
1138  current_function_decl = NULL;
1139  current_binding_level = NULL_BINDING_LEVEL;
1140  pushlevel (0);	/* make the binding_level structure for global names */
1141  global_binding_level = current_binding_level;
1142
1143  build_common_tree_nodes (flag_signed_char, false);
1144
1145  /* set standard type names */
1146
1147  /* Define `int' and `char' last so that they are not overwritten.  */
1148  tree_push_type_decl (NULL_TREE, intQI_type_node);
1149  tree_push_type_decl (NULL_TREE, intHI_type_node);
1150  tree_push_type_decl (NULL_TREE, intSI_type_node);
1151  tree_push_type_decl (NULL_TREE, intDI_type_node);
1152#if HOST_BITS_PER_WIDE_INT >= 64
1153  tree_push_type_decl (NULL_TREE, intTI_type_node);
1154#endif
1155  tree_push_type_decl (NULL_TREE, unsigned_intQI_type_node);
1156  tree_push_type_decl (NULL_TREE, unsigned_intHI_type_node);
1157  tree_push_type_decl (NULL_TREE, unsigned_intSI_type_node);
1158  tree_push_type_decl (NULL_TREE, unsigned_intDI_type_node);
1159#if HOST_BITS_PER_WIDE_INT >= 64
1160  tree_push_type_decl (NULL_TREE, unsigned_intTI_type_node);
1161#endif
1162
1163  tree_push_type_decl (get_identifier ("int"), integer_type_node);
1164  tree_push_type_decl (get_identifier ("char"), char_type_node);
1165  tree_push_type_decl (get_identifier ("long int"),
1166			      long_integer_type_node);
1167  tree_push_type_decl (get_identifier ("unsigned int"),
1168			      unsigned_type_node);
1169  tree_push_type_decl (get_identifier ("long unsigned int"),
1170			      long_unsigned_type_node);
1171  tree_push_type_decl (get_identifier ("long long int"),
1172			      long_long_integer_type_node);
1173  tree_push_type_decl (get_identifier ("long long unsigned int"),
1174			      long_long_unsigned_type_node);
1175  tree_push_type_decl (get_identifier ("short int"),
1176			      short_integer_type_node);
1177  tree_push_type_decl (get_identifier ("short unsigned int"),
1178			      short_unsigned_type_node);
1179  tree_push_type_decl (get_identifier ("signed char"),
1180			      signed_char_type_node);
1181  tree_push_type_decl (get_identifier ("unsigned char"),
1182			      unsigned_char_type_node);
1183  size_type_node = make_unsigned_type (POINTER_SIZE);
1184  tree_push_type_decl (get_identifier ("size_t"), size_type_node);
1185  set_sizetype (size_type_node);
1186
1187  build_common_tree_nodes_2 (/* short_double= */ 0);
1188
1189  tree_push_type_decl (get_identifier ("float"), float_type_node);
1190  tree_push_type_decl (get_identifier ("double"), double_type_node);
1191  tree_push_type_decl (get_identifier ("long double"), long_double_type_node);
1192  tree_push_type_decl (get_identifier ("void"), void_type_node);
1193
1194  build_common_builtin_nodes ();
1195  (*targetm.init_builtins) ();
1196
1197  pedantic_lvalues = pedantic;
1198}
1199
1200static tree
1201handle_attribute (tree *node, tree name, tree ARG_UNUSED (args),
1202		  int ARG_UNUSED (flags), bool *no_add_attrs)
1203{
1204  if (TREE_CODE (*node) == FUNCTION_DECL)
1205    {
1206      if (strcmp (IDENTIFIER_POINTER (name), "const") == 0)
1207	TREE_READONLY (*node) = 1;
1208      if (strcmp (IDENTIFIER_POINTER (name), "nothrow") == 0)
1209	TREE_NOTHROW (*node) = 1;
1210    }
1211  else
1212    {
1213      warning (OPT_Wattributes, "%qD attribute ignored", name);
1214      *no_add_attrs = true;
1215    }
1216
1217  return NULL_TREE;
1218}
1219
1220const struct attribute_spec treelang_attribute_table[] =
1221{
1222  { "const", 0, 0, true, false, false, handle_attribute },
1223  { "nothrow", 0, 0, true, false, false, handle_attribute },
1224  { NULL, 0, 0, false, false, false, NULL },
1225};
1226
1227/* Return a definition for a builtin function named NAME and whose data type
1228   is TYPE.  TYPE should be a function type with argument types.
1229   FUNCTION_CODE tells later passes how to compile calls to this function.
1230   See tree.h for its possible values.
1231
1232   If LIBRARY_NAME is nonzero, use that for DECL_ASSEMBLER_NAME,
1233   the name to be called if we can't opencode the function.  If
1234   ATTRS is nonzero, use that for the function's attribute list.
1235
1236   copied from gcc/c-decl.c
1237*/
1238
1239static tree
1240builtin_function (const char *name, tree type, int function_code,
1241		  enum built_in_class class, const char *library_name,
1242		  tree attrs)
1243{
1244  tree decl = build_decl (FUNCTION_DECL, get_identifier (name), type);
1245  DECL_EXTERNAL (decl) = 1;
1246  TREE_PUBLIC (decl) = 1;
1247  if (library_name)
1248    SET_DECL_ASSEMBLER_NAME (decl, get_identifier (library_name));
1249  pushdecl (decl);
1250  DECL_BUILT_IN_CLASS (decl) = class;
1251  DECL_FUNCTION_CODE (decl) = function_code;
1252
1253  /* Possibly apply some default attributes to this built-in function.  */
1254  if (attrs)
1255    decl_attributes (&decl, attrs, ATTR_FLAG_BUILT_IN);
1256  else
1257    decl_attributes (&decl, NULL_TREE, 0);
1258
1259  return decl;
1260}
1261
1262/* Treelang expand function langhook.  */
1263
1264static void
1265treelang_expand_function (tree fndecl)
1266{
1267  /* We have nothing special to do while expanding functions for treelang.  */
1268  tree_rest_of_compilation (fndecl);
1269}
1270
1271#include "debug.h" /* for debug_hooks, needed by gt-treelang-treetree.h */
1272#include "gt-treelang-treetree.h"
1273