* Merge with edge-vector-mergepoint-20040918.
[official-gcc.git] / gcc / fortran / trans-stmt.c
blob53e9a85a216423381feb8873fb2a3556c088f7fd
1 /* Statement translation -- generate GCC trees from gfc_code.
2 Copyright (C) 2002, 2003, 2004 Free Software Foundation, Inc.
3 Contributed by Paul Brook <paul@nowt.org>
4 and Steven Bosscher <s.bosscher@student.tudelft.nl>
6 This file is part of GCC.
8 GCC is free software; you can redistribute it and/or modify it under
9 the terms of the GNU General Public License as published by the Free
10 Software Foundation; either version 2, or (at your option) any later
11 version.
13 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
14 WARRANTY; without even the implied warranty of MERCHANTABILITY or
15 FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
16 for more details.
18 You should have received a copy of the GNU General Public License
19 along with GCC; see the file COPYING. If not, write to the Free
20 Software Foundation, 59 Temple Place - Suite 330, Boston, MA
21 02111-1307, USA. */
24 #include "config.h"
25 #include "system.h"
26 #include "coretypes.h"
27 #include "tree.h"
28 #include "tree-gimple.h"
29 #include <stdio.h>
30 #include "ggc.h"
31 #include "toplev.h"
32 #include "real.h"
33 #include <gmp.h>
34 #include "gfortran.h"
35 #include "trans.h"
36 #include "trans-stmt.h"
37 #include "trans-types.h"
38 #include "trans-array.h"
39 #include "trans-const.h"
40 #include "arith.h"
42 int has_alternate_specifier;
44 typedef struct iter_info
46 tree var;
47 tree start;
48 tree end;
49 tree step;
50 struct iter_info *next;
52 iter_info;
54 typedef struct temporary_list
56 tree temporary;
57 struct temporary_list *next;
59 temporary_list;
61 typedef struct forall_info
63 iter_info *this_loop;
64 tree mask;
65 tree pmask;
66 tree maskindex;
67 int nvar;
68 tree size;
69 struct forall_info *outer;
70 struct forall_info *next_nest;
72 forall_info;
74 static void gfc_trans_where_2 (gfc_code *, tree, tree, forall_info *,
75 stmtblock_t *, temporary_list **temp);
77 /* Translate a F95 label number to a LABEL_EXPR. */
79 tree
80 gfc_trans_label_here (gfc_code * code)
82 return build1_v (LABEL_EXPR, gfc_get_label_decl (code->here));
85 /* Translate a label assignment statement. */
86 tree
87 gfc_trans_label_assign (gfc_code * code)
89 tree label_tree;
90 gfc_se se;
91 tree len;
92 tree addr;
93 tree len_tree;
94 char *label_str;
95 int label_len;
97 /* Start a new block. */
98 gfc_init_se (&se, NULL);
99 gfc_start_block (&se.pre);
100 gfc_conv_expr (&se, code->expr);
101 len = GFC_DECL_STRING_LEN (se.expr);
102 addr = GFC_DECL_ASSIGN_ADDR (se.expr);
104 label_tree = gfc_get_label_decl (code->label);
106 if (code->label->defined == ST_LABEL_TARGET)
108 label_tree = gfc_build_addr_expr (pvoid_type_node, label_tree);
109 len_tree = integer_minus_one_node;
111 else
113 label_str = code->label->format->value.character.string;
114 label_len = code->label->format->value.character.length;
115 len_tree = build_int_cst (NULL_TREE, label_len);
116 label_tree = gfc_build_string_const (label_len + 1, label_str);
117 label_tree = gfc_build_addr_expr (pchar_type_node, label_tree);
120 gfc_add_modify_expr (&se.pre, len, len_tree);
121 gfc_add_modify_expr (&se.pre, addr, label_tree);
123 return gfc_finish_block (&se.pre);
126 /* Translate a GOTO statement. */
128 tree
129 gfc_trans_goto (gfc_code * code)
131 tree assigned_goto;
132 tree target;
133 tree tmp;
134 tree assign_error;
135 tree range_error;
136 gfc_se se;
139 if (code->label != NULL)
140 return build1_v (GOTO_EXPR, gfc_get_label_decl (code->label));
142 /* ASSIGNED GOTO. */
143 gfc_init_se (&se, NULL);
144 gfc_start_block (&se.pre);
145 gfc_conv_expr (&se, code->expr);
146 assign_error =
147 gfc_build_string_const (37, "Assigned label is not a target label");
148 tmp = GFC_DECL_STRING_LEN (se.expr);
149 tmp = build2 (NE_EXPR, boolean_type_node, tmp, integer_minus_one_node);
150 gfc_trans_runtime_check (tmp, assign_error, &se.pre);
152 assigned_goto = GFC_DECL_ASSIGN_ADDR (se.expr);
153 target = build1 (GOTO_EXPR, void_type_node, assigned_goto);
155 code = code->block;
156 if (code == NULL)
158 gfc_add_expr_to_block (&se.pre, target);
159 return gfc_finish_block (&se.pre);
162 /* Check the label list. */
163 range_error =
164 gfc_build_string_const (34, "Assigned label is not in the list");
168 tmp = gfc_get_label_decl (code->label);
169 tmp = gfc_build_addr_expr (pvoid_type_node, tmp);
170 tmp = build2 (EQ_EXPR, boolean_type_node, tmp, assigned_goto);
171 tmp = build3_v (COND_EXPR, tmp, target, build_empty_stmt ());
172 gfc_add_expr_to_block (&se.pre, tmp);
173 code = code->block;
175 while (code != NULL);
176 gfc_trans_runtime_check (boolean_true_node, range_error, &se.pre);
177 return gfc_finish_block (&se.pre);
181 /* Translate an ENTRY statement. Just adds a label for this entry point. */
182 tree
183 gfc_trans_entry (gfc_code * code)
185 return build1_v (LABEL_EXPR, code->ext.entry->label);
189 /* Translate the CALL statement. Builds a call to an F95 subroutine. */
191 tree
192 gfc_trans_call (gfc_code * code)
194 gfc_se se;
196 /* A CALL starts a new block because the actual arguments may have to
197 be evaluated first. */
198 gfc_init_se (&se, NULL);
199 gfc_start_block (&se.pre);
201 gcc_assert (code->resolved_sym);
202 has_alternate_specifier = 0;
204 /* Translate the call. */
205 gfc_conv_function_call (&se, code->resolved_sym, code->ext.actual);
207 /* A subroutine without side-effect, by definition, does nothing! */
208 TREE_SIDE_EFFECTS (se.expr) = 1;
210 /* Chain the pieces together and return the block. */
211 if (has_alternate_specifier)
213 gfc_code *select_code;
214 gfc_symbol *sym;
215 select_code = code->next;
216 gcc_assert(select_code->op == EXEC_SELECT);
217 sym = select_code->expr->symtree->n.sym;
218 se.expr = convert (gfc_typenode_for_spec (&sym->ts), se.expr);
219 gfc_add_modify_expr (&se.pre, sym->backend_decl, se.expr);
221 else
222 gfc_add_expr_to_block (&se.pre, se.expr);
224 gfc_add_block_to_block (&se.pre, &se.post);
225 return gfc_finish_block (&se.pre);
229 /* Translate the RETURN statement. */
231 tree
232 gfc_trans_return (gfc_code * code ATTRIBUTE_UNUSED)
234 if (code->expr)
236 gfc_se se;
237 tree tmp;
238 tree result;
240 /* if code->expr is not NULL, this return statement must appear
241 in a subroutine and current_fake_result_decl has already
242 been generated. */
244 result = gfc_get_fake_result_decl (NULL);
245 if (!result)
247 gfc_warning ("An alternate return at %L without a * dummy argument",
248 &code->expr->where);
249 return build1_v (GOTO_EXPR, gfc_get_return_label ());
252 /* Start a new block for this statement. */
253 gfc_init_se (&se, NULL);
254 gfc_start_block (&se.pre);
256 gfc_conv_expr (&se, code->expr);
258 tmp = build2 (MODIFY_EXPR, TREE_TYPE (result), result, se.expr);
259 gfc_add_expr_to_block (&se.pre, tmp);
261 tmp = build1_v (GOTO_EXPR, gfc_get_return_label ());
262 gfc_add_expr_to_block (&se.pre, tmp);
263 gfc_add_block_to_block (&se.pre, &se.post);
264 return gfc_finish_block (&se.pre);
266 else
267 return build1_v (GOTO_EXPR, gfc_get_return_label ());
271 /* Translate the PAUSE statement. We have to translate this statement
272 to a runtime library call. */
274 tree
275 gfc_trans_pause (gfc_code * code)
277 tree gfc_int4_type_node = gfc_get_int_type (4);
278 gfc_se se;
279 tree args;
280 tree tmp;
281 tree fndecl;
283 /* Start a new block for this statement. */
284 gfc_init_se (&se, NULL);
285 gfc_start_block (&se.pre);
288 if (code->expr == NULL)
290 tmp = build_int_cst (gfc_int4_type_node, code->ext.stop_code);
291 args = gfc_chainon_list (NULL_TREE, tmp);
292 fndecl = gfor_fndecl_pause_numeric;
294 else
296 gfc_conv_expr_reference (&se, code->expr);
297 args = gfc_chainon_list (NULL_TREE, se.expr);
298 args = gfc_chainon_list (args, se.string_length);
299 fndecl = gfor_fndecl_pause_string;
302 tmp = gfc_build_function_call (fndecl, args);
303 gfc_add_expr_to_block (&se.pre, tmp);
305 gfc_add_block_to_block (&se.pre, &se.post);
307 return gfc_finish_block (&se.pre);
311 /* Translate the STOP statement. We have to translate this statement
312 to a runtime library call. */
314 tree
315 gfc_trans_stop (gfc_code * code)
317 tree gfc_int4_type_node = gfc_get_int_type (4);
318 gfc_se se;
319 tree args;
320 tree tmp;
321 tree fndecl;
323 /* Start a new block for this statement. */
324 gfc_init_se (&se, NULL);
325 gfc_start_block (&se.pre);
328 if (code->expr == NULL)
330 tmp = build_int_cst (gfc_int4_type_node, code->ext.stop_code);
331 args = gfc_chainon_list (NULL_TREE, tmp);
332 fndecl = gfor_fndecl_stop_numeric;
334 else
336 gfc_conv_expr_reference (&se, code->expr);
337 args = gfc_chainon_list (NULL_TREE, se.expr);
338 args = gfc_chainon_list (args, se.string_length);
339 fndecl = gfor_fndecl_stop_string;
342 tmp = gfc_build_function_call (fndecl, args);
343 gfc_add_expr_to_block (&se.pre, tmp);
345 gfc_add_block_to_block (&se.pre, &se.post);
347 return gfc_finish_block (&se.pre);
351 /* Generate GENERIC for the IF construct. This function also deals with
352 the simple IF statement, because the front end translates the IF
353 statement into an IF construct.
355 We translate:
357 IF (cond) THEN
358 then_clause
359 ELSEIF (cond2)
360 elseif_clause
361 ELSE
362 else_clause
363 ENDIF
365 into:
367 pre_cond_s;
368 if (cond_s)
370 then_clause;
372 else
374 pre_cond_s
375 if (cond_s)
377 elseif_clause
379 else
381 else_clause;
385 where COND_S is the simplified version of the predicate. PRE_COND_S
386 are the pre side-effects produced by the translation of the
387 conditional.
388 We need to build the chain recursively otherwise we run into
389 problems with folding incomplete statements. */
391 static tree
392 gfc_trans_if_1 (gfc_code * code)
394 gfc_se if_se;
395 tree stmt, elsestmt;
397 /* Check for an unconditional ELSE clause. */
398 if (!code->expr)
399 return gfc_trans_code (code->next);
401 /* Initialize a statement builder for each block. Puts in NULL_TREEs. */
402 gfc_init_se (&if_se, NULL);
403 gfc_start_block (&if_se.pre);
405 /* Calculate the IF condition expression. */
406 gfc_conv_expr_val (&if_se, code->expr);
408 /* Translate the THEN clause. */
409 stmt = gfc_trans_code (code->next);
411 /* Translate the ELSE clause. */
412 if (code->block)
413 elsestmt = gfc_trans_if_1 (code->block);
414 else
415 elsestmt = build_empty_stmt ();
417 /* Build the condition expression and add it to the condition block. */
418 stmt = build3_v (COND_EXPR, if_se.expr, stmt, elsestmt);
420 gfc_add_expr_to_block (&if_se.pre, stmt);
422 /* Finish off this statement. */
423 return gfc_finish_block (&if_se.pre);
426 tree
427 gfc_trans_if (gfc_code * code)
429 /* Ignore the top EXEC_IF, it only announces an IF construct. The
430 actual code we must translate is in code->block. */
432 return gfc_trans_if_1 (code->block);
436 /* Translage an arithmetic IF expression.
438 IF (cond) label1, label2, label3 translates to
440 if (cond <= 0)
442 if (cond < 0)
443 goto label1;
444 else // cond == 0
445 goto label2;
447 else // cond > 0
448 goto label3;
451 tree
452 gfc_trans_arithmetic_if (gfc_code * code)
454 gfc_se se;
455 tree tmp;
456 tree branch1;
457 tree branch2;
458 tree zero;
460 /* Start a new block. */
461 gfc_init_se (&se, NULL);
462 gfc_start_block (&se.pre);
464 /* Pre-evaluate COND. */
465 gfc_conv_expr_val (&se, code->expr);
467 /* Build something to compare with. */
468 zero = gfc_build_const (TREE_TYPE (se.expr), integer_zero_node);
470 /* If (cond < 0) take branch1 else take branch2.
471 First build jumps to the COND .LT. 0 and the COND .EQ. 0 cases. */
472 branch1 = build1_v (GOTO_EXPR, gfc_get_label_decl (code->label));
473 branch2 = build1_v (GOTO_EXPR, gfc_get_label_decl (code->label2));
475 tmp = build2 (LT_EXPR, boolean_type_node, se.expr, zero);
476 branch1 = build3_v (COND_EXPR, tmp, branch1, branch2);
478 /* if (cond <= 0) take branch1 else take branch2. */
479 branch2 = build1_v (GOTO_EXPR, gfc_get_label_decl (code->label3));
480 tmp = build2 (LE_EXPR, boolean_type_node, se.expr, zero);
481 branch1 = build3_v (COND_EXPR, tmp, branch1, branch2);
483 /* Append the COND_EXPR to the evaluation of COND, and return. */
484 gfc_add_expr_to_block (&se.pre, branch1);
485 return gfc_finish_block (&se.pre);
489 /* Translate the DO construct. This obviously is one of the most
490 important ones to get right with any compiler, but especially
491 so for Fortran.
493 Currently we calculate the loop count before entering the loop, but
494 it may be possible to optimize if step is a constant. The main
495 advantage is that the loop test is a single GENERIC node
497 We translate a do loop from:
499 DO dovar = from, to, step
500 body
501 END DO
505 pre_dovar;
506 pre_from;
507 pre_to;
508 pre_step;
509 temp1=to_expr-from_expr;
510 step_temp=step_expr;
511 range_temp=step_tmp/range_temp;
512 for ( ; range_temp > 0 ; range_temp = range_temp - 1)
514 body;
515 cycle_label:
516 dovar_temp = dovar
517 dovar=dovar_temp + step_temp;
519 exit_label:
521 Some optimization is done for empty do loops. We can't just let
522 dovar=to because it's possible for from+range*loopcount!=to. Anyone
523 who writes empty DO deserves sub-optimal (but correct) code anyway.
525 TODO: Large loop counts
526 Does not work loop counts which do not fit into a signed integer kind,
527 i.e. Does not work for loop counts > 2^31 for integer(kind=4) variables
528 We must support the full range. */
530 tree
531 gfc_trans_do (gfc_code * code)
533 gfc_se se;
534 tree dovar;
535 tree from;
536 tree to;
537 tree step;
538 tree count;
539 tree type;
540 tree cond;
541 tree cycle_label;
542 tree exit_label;
543 tree tmp;
544 stmtblock_t block;
545 stmtblock_t body;
547 gfc_start_block (&block);
549 /* Create GIMPLE versions of all expressions in the iterator. */
551 gfc_init_se (&se, NULL);
552 gfc_conv_expr_lhs (&se, code->ext.iterator->var);
553 gfc_add_block_to_block (&block, &se.pre);
554 dovar = se.expr;
555 type = TREE_TYPE (dovar);
557 gfc_init_se (&se, NULL);
558 gfc_conv_expr_type (&se, code->ext.iterator->start, type);
559 gfc_add_block_to_block (&block, &se.pre);
560 from = se.expr;
562 gfc_init_se (&se, NULL);
563 gfc_conv_expr_type (&se, code->ext.iterator->end, type);
564 gfc_add_block_to_block (&block, &se.pre);
565 to = se.expr;
567 gfc_init_se (&se, NULL);
568 gfc_conv_expr_type (&se, code->ext.iterator->step, type);
570 /* We don't want this changing part way through. */
571 gfc_make_safe_expr (&se);
572 gfc_add_block_to_block (&block, &se.pre);
573 step = se.expr;
575 /* Initialize loop count. This code is executed before we enter the
576 loop body. We generate: count = (to + step - from) / step. */
578 tmp = fold (build2 (MINUS_EXPR, type, step, from));
579 tmp = fold (build2 (PLUS_EXPR, type, to, tmp));
580 tmp = fold (build2 (TRUNC_DIV_EXPR, type, tmp, step));
582 count = gfc_create_var (type, "count");
583 gfc_add_modify_expr (&block, count, tmp);
585 /* Initialize the DO variable: dovar = from. */
586 gfc_add_modify_expr (&block, dovar, from);
588 /* Loop body. */
589 gfc_start_block (&body);
591 /* Cycle and exit statements are implemented with gotos. */
592 cycle_label = gfc_build_label_decl (NULL_TREE);
593 exit_label = gfc_build_label_decl (NULL_TREE);
595 /* Start with the loop condition. Loop until count <= 0. */
596 cond = build2 (LE_EXPR, boolean_type_node, count, integer_zero_node);
597 tmp = build1_v (GOTO_EXPR, exit_label);
598 TREE_USED (exit_label) = 1;
599 tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt ());
600 gfc_add_expr_to_block (&body, tmp);
602 /* Put these labels where they can be found later. We put the
603 labels in a TREE_LIST node (because TREE_CHAIN is already
604 used). cycle_label goes in TREE_PURPOSE (backend_decl), exit
605 label in TREE_VALUE (backend_decl). */
607 code->block->backend_decl = tree_cons (cycle_label, exit_label, NULL);
609 /* Main loop body. */
610 tmp = gfc_trans_code (code->block->next);
611 gfc_add_expr_to_block (&body, tmp);
613 /* Label for cycle statements (if needed). */
614 if (TREE_USED (cycle_label))
616 tmp = build1_v (LABEL_EXPR, cycle_label);
617 gfc_add_expr_to_block (&body, tmp);
620 /* Increment the loop variable. */
621 tmp = build2 (PLUS_EXPR, type, dovar, step);
622 gfc_add_modify_expr (&body, dovar, tmp);
624 /* Decrement the loop count. */
625 tmp = build2 (MINUS_EXPR, type, count, gfc_index_one_node);
626 gfc_add_modify_expr (&body, count, tmp);
628 /* End of loop body. */
629 tmp = gfc_finish_block (&body);
631 /* The for loop itself. */
632 tmp = build1_v (LOOP_EXPR, tmp);
633 gfc_add_expr_to_block (&block, tmp);
635 /* Add the exit label. */
636 tmp = build1_v (LABEL_EXPR, exit_label);
637 gfc_add_expr_to_block (&block, tmp);
639 return gfc_finish_block (&block);
643 /* Translate the DO WHILE construct.
645 We translate
647 DO WHILE (cond)
648 body
649 END DO
653 for ( ; ; )
655 pre_cond;
656 if (! cond) goto exit_label;
657 body;
658 cycle_label:
660 exit_label:
662 Because the evaluation of the exit condition `cond' may have side
663 effects, we can't do much for empty loop bodies. The backend optimizers
664 should be smart enough to eliminate any dead loops. */
666 tree
667 gfc_trans_do_while (gfc_code * code)
669 gfc_se cond;
670 tree tmp;
671 tree cycle_label;
672 tree exit_label;
673 stmtblock_t block;
675 /* Everything we build here is part of the loop body. */
676 gfc_start_block (&block);
678 /* Cycle and exit statements are implemented with gotos. */
679 cycle_label = gfc_build_label_decl (NULL_TREE);
680 exit_label = gfc_build_label_decl (NULL_TREE);
682 /* Put the labels where they can be found later. See gfc_trans_do(). */
683 code->block->backend_decl = tree_cons (cycle_label, exit_label, NULL);
685 /* Create a GIMPLE version of the exit condition. */
686 gfc_init_se (&cond, NULL);
687 gfc_conv_expr_val (&cond, code->expr);
688 gfc_add_block_to_block (&block, &cond.pre);
689 cond.expr = fold (build1 (TRUTH_NOT_EXPR, boolean_type_node, cond.expr));
691 /* Build "IF (! cond) GOTO exit_label". */
692 tmp = build1_v (GOTO_EXPR, exit_label);
693 TREE_USED (exit_label) = 1;
694 tmp = build3_v (COND_EXPR, cond.expr, tmp, build_empty_stmt ());
695 gfc_add_expr_to_block (&block, tmp);
697 /* The main body of the loop. */
698 tmp = gfc_trans_code (code->block->next);
699 gfc_add_expr_to_block (&block, tmp);
701 /* Label for cycle statements (if needed). */
702 if (TREE_USED (cycle_label))
704 tmp = build1_v (LABEL_EXPR, cycle_label);
705 gfc_add_expr_to_block (&block, tmp);
708 /* End of loop body. */
709 tmp = gfc_finish_block (&block);
711 gfc_init_block (&block);
712 /* Build the loop. */
713 tmp = build1_v (LOOP_EXPR, tmp);
714 gfc_add_expr_to_block (&block, tmp);
716 /* Add the exit label. */
717 tmp = build1_v (LABEL_EXPR, exit_label);
718 gfc_add_expr_to_block (&block, tmp);
720 return gfc_finish_block (&block);
724 /* Translate the SELECT CASE construct for INTEGER case expressions,
725 without killing all potential optimizations. The problem is that
726 Fortran allows unbounded cases, but the back-end does not, so we
727 need to intercept those before we enter the equivalent SWITCH_EXPR
728 we can build.
730 For example, we translate this,
732 SELECT CASE (expr)
733 CASE (:100,101,105:115)
734 block_1
735 CASE (190:199,200:)
736 block_2
737 CASE (300)
738 block_3
739 CASE DEFAULT
740 block_4
741 END SELECT
743 to the GENERIC equivalent,
745 switch (expr)
747 case (minimum value for typeof(expr) ... 100:
748 case 101:
749 case 105 ... 114:
750 block1:
751 goto end_label;
753 case 200 ... (maximum value for typeof(expr):
754 case 190 ... 199:
755 block2;
756 goto end_label;
758 case 300:
759 block_3;
760 goto end_label;
762 default:
763 block_4;
764 goto end_label;
767 end_label: */
769 static tree
770 gfc_trans_integer_select (gfc_code * code)
772 gfc_code *c;
773 gfc_case *cp;
774 tree end_label;
775 tree tmp;
776 gfc_se se;
777 stmtblock_t block;
778 stmtblock_t body;
780 gfc_start_block (&block);
782 /* Calculate the switch expression. */
783 gfc_init_se (&se, NULL);
784 gfc_conv_expr_val (&se, code->expr);
785 gfc_add_block_to_block (&block, &se.pre);
787 end_label = gfc_build_label_decl (NULL_TREE);
789 gfc_init_block (&body);
791 for (c = code->block; c; c = c->block)
793 for (cp = c->ext.case_list; cp; cp = cp->next)
795 tree low, high;
796 tree label;
798 /* Assume it's the default case. */
799 low = high = NULL_TREE;
801 if (cp->low)
803 low = gfc_conv_constant_to_tree (cp->low);
805 /* If there's only a lower bound, set the high bound to the
806 maximum value of the case expression. */
807 if (!cp->high)
808 high = TYPE_MAX_VALUE (TREE_TYPE (se.expr));
811 if (cp->high)
813 /* Three cases are possible here:
815 1) There is no lower bound, e.g. CASE (:N).
816 2) There is a lower bound .NE. high bound, that is
817 a case range, e.g. CASE (N:M) where M>N (we make
818 sure that M>N during type resolution).
819 3) There is a lower bound, and it has the same value
820 as the high bound, e.g. CASE (N:N). This is our
821 internal representation of CASE(N).
823 In the first and second case, we need to set a value for
824 high. In the thirth case, we don't because the GCC middle
825 end represents a single case value by just letting high be
826 a NULL_TREE. We can't do that because we need to be able
827 to represent unbounded cases. */
829 if (!cp->low
830 || (cp->low
831 && mpz_cmp (cp->low->value.integer,
832 cp->high->value.integer) != 0))
833 high = gfc_conv_constant_to_tree (cp->high);
835 /* Unbounded case. */
836 if (!cp->low)
837 low = TYPE_MIN_VALUE (TREE_TYPE (se.expr));
840 /* Build a label. */
841 label = build_decl (LABEL_DECL, NULL_TREE, NULL_TREE);
842 DECL_CONTEXT (label) = current_function_decl;
844 /* Add this case label.
845 Add parameter 'label', make it match GCC backend. */
846 tmp = build3 (CASE_LABEL_EXPR, void_type_node, low, high, label);
847 gfc_add_expr_to_block (&body, tmp);
850 /* Add the statements for this case. */
851 tmp = gfc_trans_code (c->next);
852 gfc_add_expr_to_block (&body, tmp);
854 /* Break to the end of the construct. */
855 tmp = build1_v (GOTO_EXPR, end_label);
856 gfc_add_expr_to_block (&body, tmp);
859 tmp = gfc_finish_block (&body);
860 tmp = build3_v (SWITCH_EXPR, se.expr, tmp, NULL_TREE);
861 gfc_add_expr_to_block (&block, tmp);
863 tmp = build1_v (LABEL_EXPR, end_label);
864 gfc_add_expr_to_block (&block, tmp);
866 return gfc_finish_block (&block);
870 /* Translate the SELECT CASE construct for LOGICAL case expressions.
872 There are only two cases possible here, even though the standard
873 does allow three cases in a LOGICAL SELECT CASE construct: .TRUE.,
874 .FALSE., and DEFAULT.
876 We never generate more than two blocks here. Instead, we always
877 try to eliminate the DEFAULT case. This way, we can translate this
878 kind of SELECT construct to a simple
880 if {} else {};
882 expression in GENERIC. */
884 static tree
885 gfc_trans_logical_select (gfc_code * code)
887 gfc_code *c;
888 gfc_code *t, *f, *d;
889 gfc_case *cp;
890 gfc_se se;
891 stmtblock_t block;
893 /* Assume we don't have any cases at all. */
894 t = f = d = NULL;
896 /* Now see which ones we actually do have. We can have at most two
897 cases in a single case list: one for .TRUE. and one for .FALSE.
898 The default case is always separate. If the cases for .TRUE. and
899 .FALSE. are in the same case list, the block for that case list
900 always executed, and we don't generate code a COND_EXPR. */
901 for (c = code->block; c; c = c->block)
903 for (cp = c->ext.case_list; cp; cp = cp->next)
905 if (cp->low)
907 if (cp->low->value.logical == 0) /* .FALSE. */
908 f = c;
909 else /* if (cp->value.logical != 0), thus .TRUE. */
910 t = c;
912 else
913 d = c;
917 /* Start a new block. */
918 gfc_start_block (&block);
920 /* Calculate the switch expression. We always need to do this
921 because it may have side effects. */
922 gfc_init_se (&se, NULL);
923 gfc_conv_expr_val (&se, code->expr);
924 gfc_add_block_to_block (&block, &se.pre);
926 if (t == f && t != NULL)
928 /* Cases for .TRUE. and .FALSE. are in the same block. Just
929 translate the code for these cases, append it to the current
930 block. */
931 gfc_add_expr_to_block (&block, gfc_trans_code (t->next));
933 else
935 tree true_tree, false_tree;
937 true_tree = build_empty_stmt ();
938 false_tree = build_empty_stmt ();
940 /* If we have a case for .TRUE. and for .FALSE., discard the default case.
941 Otherwise, if .TRUE. or .FALSE. is missing and there is a default case,
942 make the missing case the default case. */
943 if (t != NULL && f != NULL)
944 d = NULL;
945 else if (d != NULL)
947 if (t == NULL)
948 t = d;
949 else
950 f = d;
953 /* Translate the code for each of these blocks, and append it to
954 the current block. */
955 if (t != NULL)
956 true_tree = gfc_trans_code (t->next);
958 if (f != NULL)
959 false_tree = gfc_trans_code (f->next);
961 gfc_add_expr_to_block (&block, build3_v (COND_EXPR, se.expr,
962 true_tree, false_tree));
965 return gfc_finish_block (&block);
969 /* Translate the SELECT CASE construct for CHARACTER case expressions.
970 Instead of generating compares and jumps, it is far simpler to
971 generate a data structure describing the cases in order and call a
972 library subroutine that locates the right case.
973 This is particularly true because this is the only case where we
974 might have to dispose of a temporary.
975 The library subroutine returns a pointer to jump to or NULL if no
976 branches are to be taken. */
978 static tree
979 gfc_trans_character_select (gfc_code *code)
981 tree init, node, end_label, tmp, type, args, *labels;
982 stmtblock_t block, body;
983 gfc_case *cp, *d;
984 gfc_code *c;
985 gfc_se se;
986 int i, n;
988 static tree select_struct;
989 static tree ss_string1, ss_string1_len;
990 static tree ss_string2, ss_string2_len;
991 static tree ss_target;
993 if (select_struct == NULL)
995 tree gfc_int4_type_node = gfc_get_int_type (4);
997 select_struct = make_node (RECORD_TYPE);
998 TYPE_NAME (select_struct) = get_identifier ("_jump_struct");
1000 #undef ADD_FIELD
1001 #define ADD_FIELD(NAME, TYPE) \
1002 ss_##NAME = gfc_add_field_to_struct \
1003 (&(TYPE_FIELDS (select_struct)), select_struct, \
1004 get_identifier (stringize(NAME)), TYPE)
1006 ADD_FIELD (string1, pchar_type_node);
1007 ADD_FIELD (string1_len, gfc_int4_type_node);
1009 ADD_FIELD (string2, pchar_type_node);
1010 ADD_FIELD (string2_len, gfc_int4_type_node);
1012 ADD_FIELD (target, pvoid_type_node);
1013 #undef ADD_FIELD
1015 gfc_finish_type (select_struct);
1018 cp = code->block->ext.case_list;
1019 while (cp->left != NULL)
1020 cp = cp->left;
1022 n = 0;
1023 for (d = cp; d; d = d->right)
1024 d->n = n++;
1026 if (n != 0)
1027 labels = gfc_getmem (n * sizeof (tree));
1028 else
1029 labels = NULL;
1031 for(i = 0; i < n; i++)
1033 labels[i] = gfc_build_label_decl (NULL_TREE);
1034 TREE_USED (labels[i]) = 1;
1035 /* TODO: The gimplifier should do this for us, but it has
1036 inadequacies when dealing with static initializers. */
1037 FORCED_LABEL (labels[i]) = 1;
1040 end_label = gfc_build_label_decl (NULL_TREE);
1042 /* Generate the body */
1043 gfc_start_block (&block);
1044 gfc_init_block (&body);
1046 for (c = code->block; c; c = c->block)
1048 for (d = c->ext.case_list; d; d = d->next)
1050 tmp = build1_v (LABEL_EXPR, labels[d->n]);
1051 gfc_add_expr_to_block (&body, tmp);
1054 tmp = gfc_trans_code (c->next);
1055 gfc_add_expr_to_block (&body, tmp);
1057 tmp = build1_v (GOTO_EXPR, end_label);
1058 gfc_add_expr_to_block (&body, tmp);
1061 /* Generate the structure describing the branches */
1062 init = NULL_TREE;
1063 i = 0;
1065 for(d = cp; d; d = d->right, i++)
1067 node = NULL_TREE;
1069 gfc_init_se (&se, NULL);
1071 if (d->low == NULL)
1073 node = tree_cons (ss_string1, null_pointer_node, node);
1074 node = tree_cons (ss_string1_len, integer_zero_node, node);
1076 else
1078 gfc_conv_expr_reference (&se, d->low);
1080 node = tree_cons (ss_string1, se.expr, node);
1081 node = tree_cons (ss_string1_len, se.string_length, node);
1084 if (d->high == NULL)
1086 node = tree_cons (ss_string2, null_pointer_node, node);
1087 node = tree_cons (ss_string2_len, integer_zero_node, node);
1089 else
1091 gfc_init_se (&se, NULL);
1092 gfc_conv_expr_reference (&se, d->high);
1094 node = tree_cons (ss_string2, se.expr, node);
1095 node = tree_cons (ss_string2_len, se.string_length, node);
1098 tmp = gfc_build_addr_expr (pvoid_type_node, labels[i]);
1099 node = tree_cons (ss_target, tmp, node);
1101 tmp = build1 (CONSTRUCTOR, select_struct, nreverse (node));
1102 init = tree_cons (NULL_TREE, tmp, init);
1105 type = build_array_type (select_struct, build_index_type
1106 (build_int_cst (NULL_TREE, n - 1)));
1108 init = build1 (CONSTRUCTOR, type, nreverse(init));
1109 TREE_CONSTANT (init) = 1;
1110 TREE_INVARIANT (init) = 1;
1111 TREE_STATIC (init) = 1;
1112 /* Create a static variable to hold the jump table. */
1113 tmp = gfc_create_var (type, "jumptable");
1114 TREE_CONSTANT (tmp) = 1;
1115 TREE_INVARIANT (tmp) = 1;
1116 TREE_STATIC (tmp) = 1;
1117 DECL_INITIAL (tmp) = init;
1118 init = tmp;
1120 /* Build an argument list for the library call */
1121 init = gfc_build_addr_expr (pvoid_type_node, init);
1122 args = gfc_chainon_list (NULL_TREE, init);
1124 tmp = build_int_cst (NULL_TREE, n);
1125 args = gfc_chainon_list (args, tmp);
1127 tmp = gfc_build_addr_expr (pvoid_type_node, end_label);
1128 args = gfc_chainon_list (args, tmp);
1130 gfc_init_se (&se, NULL);
1131 gfc_conv_expr_reference (&se, code->expr);
1133 args = gfc_chainon_list (args, se.expr);
1134 args = gfc_chainon_list (args, se.string_length);
1136 gfc_add_block_to_block (&block, &se.pre);
1138 tmp = gfc_build_function_call (gfor_fndecl_select_string, args);
1139 tmp = build1 (GOTO_EXPR, void_type_node, tmp);
1140 gfc_add_expr_to_block (&block, tmp);
1142 tmp = gfc_finish_block (&body);
1143 gfc_add_expr_to_block (&block, tmp);
1144 tmp = build1_v (LABEL_EXPR, end_label);
1145 gfc_add_expr_to_block (&block, tmp);
1147 if (n != 0)
1148 gfc_free (labels);
1150 return gfc_finish_block (&block);
1154 /* Translate the three variants of the SELECT CASE construct.
1156 SELECT CASEs with INTEGER case expressions can be translated to an
1157 equivalent GENERIC switch statement, and for LOGICAL case
1158 expressions we build one or two if-else compares.
1160 SELECT CASEs with CHARACTER case expressions are a whole different
1161 story, because they don't exist in GENERIC. So we sort them and
1162 do a binary search at runtime.
1164 Fortran has no BREAK statement, and it does not allow jumps from
1165 one case block to another. That makes things a lot easier for
1166 the optimizers. */
1168 tree
1169 gfc_trans_select (gfc_code * code)
1171 gcc_assert (code && code->expr);
1173 /* Empty SELECT constructs are legal. */
1174 if (code->block == NULL)
1175 return build_empty_stmt ();
1177 /* Select the correct translation function. */
1178 switch (code->expr->ts.type)
1180 case BT_LOGICAL: return gfc_trans_logical_select (code);
1181 case BT_INTEGER: return gfc_trans_integer_select (code);
1182 case BT_CHARACTER: return gfc_trans_character_select (code);
1183 default:
1184 gfc_internal_error ("gfc_trans_select(): Bad type for case expr.");
1185 /* Not reached */
1190 /* Generate the loops for a FORALL block. The normal loop format:
1191 count = (end - start + step) / step
1192 loopvar = start
1193 while (1)
1195 if (count <=0 )
1196 goto end_of_loop
1197 <body>
1198 loopvar += step
1199 count --
1201 end_of_loop: */
1203 static tree
1204 gfc_trans_forall_loop (forall_info *forall_tmp, int nvar, tree body, int mask_flag)
1206 int n;
1207 tree tmp;
1208 tree cond;
1209 stmtblock_t block;
1210 tree exit_label;
1211 tree count;
1212 tree var, start, end, step, mask, maskindex;
1213 iter_info *iter;
1215 iter = forall_tmp->this_loop;
1216 for (n = 0; n < nvar; n++)
1218 var = iter->var;
1219 start = iter->start;
1220 end = iter->end;
1221 step = iter->step;
1223 exit_label = gfc_build_label_decl (NULL_TREE);
1224 TREE_USED (exit_label) = 1;
1226 /* The loop counter. */
1227 count = gfc_create_var (TREE_TYPE (var), "count");
1229 /* The body of the loop. */
1230 gfc_init_block (&block);
1232 /* The exit condition. */
1233 cond = build2 (LE_EXPR, boolean_type_node, count, integer_zero_node);
1234 tmp = build1_v (GOTO_EXPR, exit_label);
1235 tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt ());
1236 gfc_add_expr_to_block (&block, tmp);
1238 /* The main loop body. */
1239 gfc_add_expr_to_block (&block, body);
1241 /* Increment the loop variable. */
1242 tmp = build2 (PLUS_EXPR, TREE_TYPE (var), var, step);
1243 gfc_add_modify_expr (&block, var, tmp);
1245 /* Advance to the next mask element. */
1246 if (mask_flag)
1248 mask = forall_tmp->mask;
1249 maskindex = forall_tmp->maskindex;
1250 if (mask)
1252 tmp = build2 (PLUS_EXPR, gfc_array_index_type,
1253 maskindex, gfc_index_one_node);
1254 gfc_add_modify_expr (&block, maskindex, tmp);
1257 /* Decrement the loop counter. */
1258 tmp = build2 (MINUS_EXPR, TREE_TYPE (var), count, gfc_index_one_node);
1259 gfc_add_modify_expr (&block, count, tmp);
1261 body = gfc_finish_block (&block);
1263 /* Loop var initialization. */
1264 gfc_init_block (&block);
1265 gfc_add_modify_expr (&block, var, start);
1267 /* Initialize the loop counter. */
1268 tmp = fold (build2 (MINUS_EXPR, TREE_TYPE (var), step, start));
1269 tmp = fold (build2 (PLUS_EXPR, TREE_TYPE (var), end, tmp));
1270 tmp = fold (build2 (TRUNC_DIV_EXPR, TREE_TYPE (var), tmp, step));
1271 gfc_add_modify_expr (&block, count, tmp);
1273 /* The loop expression. */
1274 tmp = build1_v (LOOP_EXPR, body);
1275 gfc_add_expr_to_block (&block, tmp);
1277 /* The exit label. */
1278 tmp = build1_v (LABEL_EXPR, exit_label);
1279 gfc_add_expr_to_block (&block, tmp);
1281 body = gfc_finish_block (&block);
1282 iter = iter->next;
1284 return body;
1288 /* Generate the body and loops according to MASK_FLAG and NEST_FLAG.
1289 if MASK_FLAG is nonzero, the body is controlled by maskes in forall
1290 nest, otherwise, the body is not controlled by maskes.
1291 if NEST_FLAG is nonzero, generate loops for nested forall, otherwise,
1292 only generate loops for the current forall level. */
1294 static tree
1295 gfc_trans_nested_forall_loop (forall_info * nested_forall_info, tree body,
1296 int mask_flag, int nest_flag)
1298 tree tmp;
1299 int nvar;
1300 forall_info *forall_tmp;
1301 tree pmask, mask, maskindex;
1303 forall_tmp = nested_forall_info;
1304 /* Generate loops for nested forall. */
1305 if (nest_flag)
1307 while (forall_tmp->next_nest != NULL)
1308 forall_tmp = forall_tmp->next_nest;
1309 while (forall_tmp != NULL)
1311 /* Generate body with masks' control. */
1312 if (mask_flag)
1314 pmask = forall_tmp->pmask;
1315 mask = forall_tmp->mask;
1316 maskindex = forall_tmp->maskindex;
1318 if (mask)
1320 /* If a mask was specified make the assignment conditional. */
1321 if (pmask)
1322 tmp = gfc_build_indirect_ref (mask);
1323 else
1324 tmp = mask;
1325 tmp = gfc_build_array_ref (tmp, maskindex);
1327 body = build3_v (COND_EXPR, tmp, body, build_empty_stmt ());
1330 nvar = forall_tmp->nvar;
1331 body = gfc_trans_forall_loop (forall_tmp, nvar, body, mask_flag);
1332 forall_tmp = forall_tmp->outer;
1335 else
1337 nvar = forall_tmp->nvar;
1338 body = gfc_trans_forall_loop (forall_tmp, nvar, body, mask_flag);
1341 return body;
1345 /* Allocate data for holding a temporary array. Returns either a local
1346 temporary array or a pointer variable. */
1348 static tree
1349 gfc_do_allocate (tree bytesize, tree size, tree * pdata, stmtblock_t * pblock,
1350 tree elem_type)
1352 tree tmpvar;
1353 tree type;
1354 tree tmp;
1355 tree args;
1357 if (INTEGER_CST_P (size))
1359 tmp = fold (build2 (MINUS_EXPR, gfc_array_index_type, size,
1360 gfc_index_one_node));
1362 else
1363 tmp = NULL_TREE;
1365 type = build_range_type (gfc_array_index_type, gfc_index_zero_node, tmp);
1366 type = build_array_type (elem_type, type);
1367 if (gfc_can_put_var_on_stack (bytesize))
1369 gcc_assert (INTEGER_CST_P (size));
1370 tmpvar = gfc_create_var (type, "temp");
1371 *pdata = NULL_TREE;
1373 else
1375 tmpvar = gfc_create_var (build_pointer_type (type), "temp");
1376 *pdata = convert (pvoid_type_node, tmpvar);
1378 args = gfc_chainon_list (NULL_TREE, bytesize);
1379 if (gfc_index_integer_kind == 4)
1380 tmp = gfor_fndecl_internal_malloc;
1381 else if (gfc_index_integer_kind == 8)
1382 tmp = gfor_fndecl_internal_malloc64;
1383 else
1384 gcc_unreachable ();
1385 tmp = gfc_build_function_call (tmp, args);
1386 tmp = convert (TREE_TYPE (tmpvar), tmp);
1387 gfc_add_modify_expr (pblock, tmpvar, tmp);
1389 return tmpvar;
1393 /* Generate codes to copy the temporary to the actual lhs. */
1395 static tree
1396 generate_loop_for_temp_to_lhs (gfc_expr *expr, tree tmp1, tree size,
1397 tree count3, tree count1, tree count2, tree wheremask)
1399 gfc_ss *lss;
1400 gfc_se lse, rse;
1401 stmtblock_t block, body;
1402 gfc_loopinfo loop1;
1403 tree tmp, tmp2;
1404 tree index;
1405 tree wheremaskexpr;
1407 /* Walk the lhs. */
1408 lss = gfc_walk_expr (expr);
1410 if (lss == gfc_ss_terminator)
1412 gfc_start_block (&block);
1414 gfc_init_se (&lse, NULL);
1416 /* Translate the expression. */
1417 gfc_conv_expr (&lse, expr);
1419 /* Form the expression for the temporary. */
1420 tmp = gfc_build_array_ref (tmp1, count1);
1422 /* Use the scalar assignment as is. */
1423 gfc_add_block_to_block (&block, &lse.pre);
1424 gfc_add_modify_expr (&block, lse.expr, tmp);
1425 gfc_add_block_to_block (&block, &lse.post);
1427 /* Increment the count1. */
1428 tmp = fold (build2 (PLUS_EXPR, TREE_TYPE (count1), count1, size));
1429 gfc_add_modify_expr (&block, count1, tmp);
1430 tmp = gfc_finish_block (&block);
1432 else
1434 gfc_start_block (&block);
1436 gfc_init_loopinfo (&loop1);
1437 gfc_init_se (&rse, NULL);
1438 gfc_init_se (&lse, NULL);
1440 /* Associate the lss with the loop. */
1441 gfc_add_ss_to_loop (&loop1, lss);
1443 /* Calculate the bounds of the scalarization. */
1444 gfc_conv_ss_startstride (&loop1);
1445 /* Setup the scalarizing loops. */
1446 gfc_conv_loop_setup (&loop1);
1448 gfc_mark_ss_chain_used (lss, 1);
1449 /* Initialize count2. */
1450 gfc_add_modify_expr (&block, count2, gfc_index_zero_node);
1452 /* Start the scalarized loop body. */
1453 gfc_start_scalarized_body (&loop1, &body);
1455 /* Setup the gfc_se structures. */
1456 gfc_copy_loopinfo_to_se (&lse, &loop1);
1457 lse.ss = lss;
1459 /* Form the expression of the temporary. */
1460 if (lss != gfc_ss_terminator)
1462 index = fold (build2 (PLUS_EXPR, gfc_array_index_type,
1463 count1, count2));
1464 rse.expr = gfc_build_array_ref (tmp1, index);
1466 /* Translate expr. */
1467 gfc_conv_expr (&lse, expr);
1469 /* Use the scalar assignment. */
1470 tmp = gfc_trans_scalar_assign (&lse, &rse, expr->ts.type);
1472 /* Form the mask expression according to the mask tree list. */
1473 if (wheremask)
1475 tmp2 = wheremask;
1476 if (tmp2 != NULL)
1477 wheremaskexpr = gfc_build_array_ref (tmp2, count3);
1478 tmp2 = TREE_CHAIN (tmp2);
1479 while (tmp2)
1481 tmp1 = gfc_build_array_ref (tmp2, count3);
1482 wheremaskexpr = build2 (TRUTH_AND_EXPR, TREE_TYPE (tmp1),
1483 wheremaskexpr, tmp1);
1484 tmp2 = TREE_CHAIN (tmp2);
1486 tmp = build3_v (COND_EXPR, wheremaskexpr, tmp, build_empty_stmt ());
1489 gfc_add_expr_to_block (&body, tmp);
1491 /* Increment count2. */
1492 tmp = fold (build2 (PLUS_EXPR, gfc_array_index_type,
1493 count2, gfc_index_one_node));
1494 gfc_add_modify_expr (&body, count2, tmp);
1496 /* Increment count3. */
1497 if (count3)
1499 tmp = fold (build2 (PLUS_EXPR, gfc_array_index_type,
1500 count3, gfc_index_one_node));
1501 gfc_add_modify_expr (&body, count3, tmp);
1504 /* Generate the copying loops. */
1505 gfc_trans_scalarizing_loops (&loop1, &body);
1506 gfc_add_block_to_block (&block, &loop1.pre);
1507 gfc_add_block_to_block (&block, &loop1.post);
1508 gfc_cleanup_loop (&loop1);
1510 /* Increment count1. */
1511 tmp = fold (build2 (PLUS_EXPR, TREE_TYPE (count1), count1, size));
1512 gfc_add_modify_expr (&block, count1, tmp);
1513 tmp = gfc_finish_block (&block);
1515 return tmp;
1519 /* Generate codes to copy rhs to the temporary. TMP1 is the address of temporary
1520 LSS and RSS are formed in function compute_inner_temp_size(), and should
1521 not be freed. */
1523 static tree
1524 generate_loop_for_rhs_to_temp (gfc_expr *expr2, tree tmp1, tree size,
1525 tree count3, tree count1, tree count2,
1526 gfc_ss *lss, gfc_ss *rss, tree wheremask)
1528 stmtblock_t block, body1;
1529 gfc_loopinfo loop;
1530 gfc_se lse;
1531 gfc_se rse;
1532 tree tmp, tmp2, index;
1533 tree wheremaskexpr;
1535 gfc_start_block (&block);
1537 gfc_init_se (&rse, NULL);
1538 gfc_init_se (&lse, NULL);
1540 if (lss == gfc_ss_terminator)
1542 gfc_init_block (&body1);
1543 gfc_conv_expr (&rse, expr2);
1544 lse.expr = gfc_build_array_ref (tmp1, count1);
1546 else
1548 /* Initialize count2. */
1549 gfc_add_modify_expr (&block, count2, gfc_index_zero_node);
1551 /* Initialize the loop. */
1552 gfc_init_loopinfo (&loop);
1554 /* We may need LSS to determine the shape of the expression. */
1555 gfc_add_ss_to_loop (&loop, lss);
1556 gfc_add_ss_to_loop (&loop, rss);
1558 gfc_conv_ss_startstride (&loop);
1559 gfc_conv_loop_setup (&loop);
1561 gfc_mark_ss_chain_used (rss, 1);
1562 /* Start the loop body. */
1563 gfc_start_scalarized_body (&loop, &body1);
1565 /* Translate the expression. */
1566 gfc_copy_loopinfo_to_se (&rse, &loop);
1567 rse.ss = rss;
1568 gfc_conv_expr (&rse, expr2);
1570 /* Form the expression of the temporary. */
1571 index = fold (build2 (PLUS_EXPR, gfc_array_index_type, count1, count2));
1572 lse.expr = gfc_build_array_ref (tmp1, index);
1575 /* Use the scalar assignment. */
1576 tmp = gfc_trans_scalar_assign (&lse, &rse, expr2->ts.type);
1578 /* Form the mask expression according to the mask tree list. */
1579 if (wheremask)
1581 tmp2 = wheremask;
1582 if (tmp2 != NULL)
1583 wheremaskexpr = gfc_build_array_ref (tmp2, count3);
1584 tmp2 = TREE_CHAIN (tmp2);
1585 while (tmp2)
1587 tmp1 = gfc_build_array_ref (tmp2, count3);
1588 wheremaskexpr = build2 (TRUTH_AND_EXPR, TREE_TYPE (tmp1),
1589 wheremaskexpr, tmp1);
1590 tmp2 = TREE_CHAIN (tmp2);
1592 tmp = build3_v (COND_EXPR, wheremaskexpr, tmp, build_empty_stmt ());
1595 gfc_add_expr_to_block (&body1, tmp);
1597 if (lss == gfc_ss_terminator)
1599 gfc_add_block_to_block (&block, &body1);
1601 else
1603 /* Increment count2. */
1604 tmp = fold (build2 (PLUS_EXPR, gfc_array_index_type,
1605 count2, gfc_index_one_node));
1606 gfc_add_modify_expr (&body1, count2, tmp);
1608 /* Increment count3. */
1609 if (count3)
1611 tmp = fold (build2 (PLUS_EXPR, gfc_array_index_type,
1612 count3, gfc_index_one_node));
1613 gfc_add_modify_expr (&body1, count3, tmp);
1616 /* Generate the copying loops. */
1617 gfc_trans_scalarizing_loops (&loop, &body1);
1619 gfc_add_block_to_block (&block, &loop.pre);
1620 gfc_add_block_to_block (&block, &loop.post);
1622 gfc_cleanup_loop (&loop);
1623 /* TODO: Reuse lss and rss when copying temp->lhs. Need to be careful
1624 as tree nodes in SS may not be valid in different scope. */
1626 /* Increment count1. */
1627 tmp = fold (build2 (PLUS_EXPR, TREE_TYPE (count1), count1, size));
1628 gfc_add_modify_expr (&block, count1, tmp);
1630 tmp = gfc_finish_block (&block);
1631 return tmp;
1635 /* Calculate the size of temporary needed in the assignment inside forall.
1636 LSS and RSS are filled in this function. */
1638 static tree
1639 compute_inner_temp_size (gfc_expr *expr1, gfc_expr *expr2,
1640 stmtblock_t * pblock,
1641 gfc_ss **lss, gfc_ss **rss)
1643 gfc_loopinfo loop;
1644 tree size;
1645 int i;
1646 tree tmp;
1648 *lss = gfc_walk_expr (expr1);
1649 *rss = NULL;
1651 size = gfc_index_one_node;
1652 if (*lss != gfc_ss_terminator)
1654 gfc_init_loopinfo (&loop);
1656 /* Walk the RHS of the expression. */
1657 *rss = gfc_walk_expr (expr2);
1658 if (*rss == gfc_ss_terminator)
1660 /* The rhs is scalar. Add a ss for the expression. */
1661 *rss = gfc_get_ss ();
1662 (*rss)->next = gfc_ss_terminator;
1663 (*rss)->type = GFC_SS_SCALAR;
1664 (*rss)->expr = expr2;
1667 /* Associate the SS with the loop. */
1668 gfc_add_ss_to_loop (&loop, *lss);
1669 /* We don't actually need to add the rhs at this point, but it might
1670 make guessing the loop bounds a bit easier. */
1671 gfc_add_ss_to_loop (&loop, *rss);
1673 /* We only want the shape of the expression, not rest of the junk
1674 generated by the scalarizer. */
1675 loop.array_parameter = 1;
1677 /* Calculate the bounds of the scalarization. */
1678 gfc_conv_ss_startstride (&loop);
1679 gfc_conv_loop_setup (&loop);
1681 /* Figure out how many elements we need. */
1682 for (i = 0; i < loop.dimen; i++)
1684 tmp = fold (build2 (MINUS_EXPR, gfc_array_index_type,
1685 gfc_index_one_node, loop.from[i]));
1686 tmp = fold (build2 (PLUS_EXPR, gfc_array_index_type,
1687 tmp, loop.to[i]));
1688 size = fold (build2 (MULT_EXPR, gfc_array_index_type, size, tmp));
1690 gfc_add_block_to_block (pblock, &loop.pre);
1691 size = gfc_evaluate_now (size, pblock);
1692 gfc_add_block_to_block (pblock, &loop.post);
1694 /* TODO: write a function that cleans up a loopinfo without freeing
1695 the SS chains. Currently a NOP. */
1698 return size;
1702 /* Calculate the overall iterator number of the nested forall construct. */
1704 static tree
1705 compute_overall_iter_number (forall_info *nested_forall_info, tree inner_size,
1706 stmtblock_t *block)
1708 tree tmp, number;
1709 stmtblock_t body;
1711 /* TODO: optimizing the computing process. */
1712 number = gfc_create_var (gfc_array_index_type, "num");
1713 gfc_add_modify_expr (block, number, gfc_index_zero_node);
1715 gfc_start_block (&body);
1716 if (nested_forall_info)
1717 tmp = build2 (PLUS_EXPR, gfc_array_index_type, number,
1718 inner_size);
1719 else
1720 tmp = inner_size;
1721 gfc_add_modify_expr (&body, number, tmp);
1722 tmp = gfc_finish_block (&body);
1724 /* Generate loops. */
1725 if (nested_forall_info != NULL)
1726 tmp = gfc_trans_nested_forall_loop (nested_forall_info, tmp, 0, 1);
1728 gfc_add_expr_to_block (block, tmp);
1730 return number;
1734 /* Allocate temporary for forall construct according to the information in
1735 nested_forall_info. INNER_SIZE is the size of temporary needed in the
1736 assignment inside forall. PTEMP1 is returned for space free. */
1738 static tree
1739 allocate_temp_for_forall_nest (forall_info * nested_forall_info, tree type,
1740 tree inner_size, stmtblock_t * block,
1741 tree * ptemp1)
1743 tree unit;
1744 tree temp1;
1745 tree tmp;
1746 tree bytesize, size;
1748 /* Calculate the total size of temporary needed in forall construct. */
1749 size = compute_overall_iter_number (nested_forall_info, inner_size, block);
1751 unit = TYPE_SIZE_UNIT (type);
1752 bytesize = fold (build2 (MULT_EXPR, gfc_array_index_type, size, unit));
1754 *ptemp1 = NULL;
1755 temp1 = gfc_do_allocate (bytesize, size, ptemp1, block, type);
1757 if (*ptemp1)
1758 tmp = gfc_build_indirect_ref (temp1);
1759 else
1760 tmp = temp1;
1762 return tmp;
1766 /* Handle assignments inside forall which need temporary. */
1767 static void
1768 gfc_trans_assign_need_temp (gfc_expr * expr1, gfc_expr * expr2, tree wheremask,
1769 forall_info * nested_forall_info,
1770 stmtblock_t * block)
1772 tree type;
1773 tree inner_size;
1774 gfc_ss *lss, *rss;
1775 tree count, count1, count2;
1776 tree tmp, tmp1;
1777 tree ptemp1;
1778 tree mask, maskindex;
1779 forall_info *forall_tmp;
1781 /* Create vars. count1 is the current iterator number of the nested forall.
1782 count2 is the current iterator number of the inner loops needed in the
1783 assignment. */
1784 count1 = gfc_create_var (gfc_array_index_type, "count1");
1785 count2 = gfc_create_var (gfc_array_index_type, "count2");
1787 /* Count is the wheremask index. */
1788 if (wheremask)
1790 count = gfc_create_var (gfc_array_index_type, "count");
1791 gfc_add_modify_expr (block, count, gfc_index_zero_node);
1793 else
1794 count = NULL;
1796 /* Initialize count1. */
1797 gfc_add_modify_expr (block, count1, gfc_index_zero_node);
1799 /* Calculate the size of temporary needed in the assignment. Return loop, lss
1800 and rss which are used in function generate_loop_for_rhs_to_temp(). */
1801 inner_size = compute_inner_temp_size (expr1, expr2, block, &lss, &rss);
1803 /* The type of LHS. Used in function allocate_temp_for_forall_nest */
1804 type = gfc_typenode_for_spec (&expr1->ts);
1806 /* Allocate temporary for nested forall construct according to the
1807 information in nested_forall_info and inner_size. */
1808 tmp1 = allocate_temp_for_forall_nest (nested_forall_info, type,
1809 inner_size, block, &ptemp1);
1811 /* Initialize the maskindexes. */
1812 forall_tmp = nested_forall_info;
1813 while (forall_tmp != NULL)
1815 mask = forall_tmp->mask;
1816 maskindex = forall_tmp->maskindex;
1817 if (mask)
1818 gfc_add_modify_expr (block, maskindex, gfc_index_zero_node);
1819 forall_tmp = forall_tmp->next_nest;
1822 /* Generate codes to copy rhs to the temporary . */
1823 tmp = generate_loop_for_rhs_to_temp (expr2, tmp1, inner_size, count,
1824 count1, count2, lss, rss, wheremask);
1826 /* Generate body and loops according to the information in
1827 nested_forall_info. */
1828 tmp = gfc_trans_nested_forall_loop (nested_forall_info, tmp, 1, 1);
1829 gfc_add_expr_to_block (block, tmp);
1831 /* Reset count1. */
1832 gfc_add_modify_expr (block, count1, gfc_index_zero_node);
1834 /* Reset maskindexed. */
1835 forall_tmp = nested_forall_info;
1836 while (forall_tmp != NULL)
1838 mask = forall_tmp->mask;
1839 maskindex = forall_tmp->maskindex;
1840 if (mask)
1841 gfc_add_modify_expr (block, maskindex, gfc_index_zero_node);
1842 forall_tmp = forall_tmp->next_nest;
1845 /* Reset count. */
1846 if (wheremask)
1847 gfc_add_modify_expr (block, count, gfc_index_zero_node);
1849 /* Generate codes to copy the temporary to lhs. */
1850 tmp = generate_loop_for_temp_to_lhs (expr1, tmp1, inner_size, count,
1851 count1, count2, wheremask);
1853 /* Generate body and loops according to the information in
1854 nested_forall_info. */
1855 tmp = gfc_trans_nested_forall_loop (nested_forall_info, tmp, 1, 1);
1856 gfc_add_expr_to_block (block, tmp);
1858 if (ptemp1)
1860 /* Free the temporary. */
1861 tmp = gfc_chainon_list (NULL_TREE, ptemp1);
1862 tmp = gfc_build_function_call (gfor_fndecl_internal_free, tmp);
1863 gfc_add_expr_to_block (block, tmp);
1868 /* Translate pointer assignment inside FORALL which need temporary. */
1870 static void
1871 gfc_trans_pointer_assign_need_temp (gfc_expr * expr1, gfc_expr * expr2,
1872 forall_info * nested_forall_info,
1873 stmtblock_t * block)
1875 tree type;
1876 tree inner_size;
1877 gfc_ss *lss, *rss;
1878 gfc_se lse;
1879 gfc_se rse;
1880 gfc_ss_info *info;
1881 gfc_loopinfo loop;
1882 tree desc;
1883 tree parm;
1884 tree parmtype;
1885 stmtblock_t body;
1886 tree count;
1887 tree tmp, tmp1, ptemp1;
1888 tree mask, maskindex;
1889 forall_info *forall_tmp;
1891 count = gfc_create_var (gfc_array_index_type, "count");
1892 gfc_add_modify_expr (block, count, gfc_index_zero_node);
1894 inner_size = integer_one_node;
1895 lss = gfc_walk_expr (expr1);
1896 rss = gfc_walk_expr (expr2);
1897 if (lss == gfc_ss_terminator)
1899 type = gfc_typenode_for_spec (&expr1->ts);
1900 type = build_pointer_type (type);
1902 /* Allocate temporary for nested forall construct according to the
1903 information in nested_forall_info and inner_size. */
1904 tmp1 = allocate_temp_for_forall_nest (nested_forall_info,
1905 type, inner_size, block, &ptemp1);
1906 gfc_start_block (&body);
1907 gfc_init_se (&lse, NULL);
1908 lse.expr = gfc_build_array_ref (tmp1, count);
1909 gfc_init_se (&rse, NULL);
1910 rse.want_pointer = 1;
1911 gfc_conv_expr (&rse, expr2);
1912 gfc_add_block_to_block (&body, &rse.pre);
1913 gfc_add_modify_expr (&body, lse.expr, rse.expr);
1914 gfc_add_block_to_block (&body, &rse.post);
1916 /* Increment count. */
1917 tmp = fold (build2 (PLUS_EXPR, gfc_array_index_type,
1918 count, gfc_index_one_node));
1919 gfc_add_modify_expr (&body, count, tmp);
1921 tmp = gfc_finish_block (&body);
1923 /* Initialize the maskindexes. */
1924 forall_tmp = nested_forall_info;
1925 while (forall_tmp != NULL)
1927 mask = forall_tmp->mask;
1928 maskindex = forall_tmp->maskindex;
1929 if (mask)
1930 gfc_add_modify_expr (block, maskindex, gfc_index_zero_node);
1931 forall_tmp = forall_tmp->next_nest;
1934 /* Generate body and loops according to the information in
1935 nested_forall_info. */
1936 tmp = gfc_trans_nested_forall_loop (nested_forall_info, tmp, 1, 1);
1937 gfc_add_expr_to_block (block, tmp);
1939 /* Reset count. */
1940 gfc_add_modify_expr (block, count, gfc_index_zero_node);
1942 /* Reset maskindexes. */
1943 forall_tmp = nested_forall_info;
1944 while (forall_tmp != NULL)
1946 mask = forall_tmp->mask;
1947 maskindex = forall_tmp->maskindex;
1948 if (mask)
1949 gfc_add_modify_expr (block, maskindex, gfc_index_zero_node);
1950 forall_tmp = forall_tmp->next_nest;
1952 gfc_start_block (&body);
1953 gfc_init_se (&lse, NULL);
1954 gfc_init_se (&rse, NULL);
1955 rse.expr = gfc_build_array_ref (tmp1, count);
1956 lse.want_pointer = 1;
1957 gfc_conv_expr (&lse, expr1);
1958 gfc_add_block_to_block (&body, &lse.pre);
1959 gfc_add_modify_expr (&body, lse.expr, rse.expr);
1960 gfc_add_block_to_block (&body, &lse.post);
1961 /* Increment count. */
1962 tmp = fold (build2 (PLUS_EXPR, gfc_array_index_type,
1963 count, gfc_index_one_node));
1964 gfc_add_modify_expr (&body, count, tmp);
1965 tmp = gfc_finish_block (&body);
1967 /* Generate body and loops according to the information in
1968 nested_forall_info. */
1969 tmp = gfc_trans_nested_forall_loop (nested_forall_info, tmp, 1, 1);
1970 gfc_add_expr_to_block (block, tmp);
1972 else
1974 gfc_init_loopinfo (&loop);
1976 /* Associate the SS with the loop. */
1977 gfc_add_ss_to_loop (&loop, rss);
1979 /* Setup the scalarizing loops and bounds. */
1980 gfc_conv_ss_startstride (&loop);
1982 gfc_conv_loop_setup (&loop);
1984 info = &rss->data.info;
1985 desc = info->descriptor;
1987 /* Make a new descriptor. */
1988 parmtype = gfc_get_element_type (TREE_TYPE (desc));
1989 parmtype = gfc_get_array_type_bounds (parmtype, loop.dimen,
1990 loop.from, loop.to, 1);
1992 /* Allocate temporary for nested forall construct. */
1993 tmp1 = allocate_temp_for_forall_nest (nested_forall_info, parmtype,
1994 inner_size, block, &ptemp1);
1995 gfc_start_block (&body);
1996 gfc_init_se (&lse, NULL);
1997 lse.expr = gfc_build_array_ref (tmp1, count);
1998 lse.direct_byref = 1;
1999 rss = gfc_walk_expr (expr2);
2000 gfc_conv_expr_descriptor (&lse, expr2, rss);
2002 gfc_add_block_to_block (&body, &lse.pre);
2003 gfc_add_block_to_block (&body, &lse.post);
2005 /* Increment count. */
2006 tmp = fold (build2 (PLUS_EXPR, gfc_array_index_type,
2007 count, gfc_index_one_node));
2008 gfc_add_modify_expr (&body, count, tmp);
2010 tmp = gfc_finish_block (&body);
2012 /* Initialize the maskindexes. */
2013 forall_tmp = nested_forall_info;
2014 while (forall_tmp != NULL)
2016 mask = forall_tmp->mask;
2017 maskindex = forall_tmp->maskindex;
2018 if (mask)
2019 gfc_add_modify_expr (block, maskindex, gfc_index_zero_node);
2020 forall_tmp = forall_tmp->next_nest;
2023 /* Generate body and loops according to the information in
2024 nested_forall_info. */
2025 tmp = gfc_trans_nested_forall_loop (nested_forall_info, tmp, 1, 1);
2026 gfc_add_expr_to_block (block, tmp);
2028 /* Reset count. */
2029 gfc_add_modify_expr (block, count, gfc_index_zero_node);
2031 /* Reset maskindexes. */
2032 forall_tmp = nested_forall_info;
2033 while (forall_tmp != NULL)
2035 mask = forall_tmp->mask;
2036 maskindex = forall_tmp->maskindex;
2037 if (mask)
2038 gfc_add_modify_expr (block, maskindex, gfc_index_zero_node);
2039 forall_tmp = forall_tmp->next_nest;
2041 parm = gfc_build_array_ref (tmp1, count);
2042 lss = gfc_walk_expr (expr1);
2043 gfc_init_se (&lse, NULL);
2044 gfc_conv_expr_descriptor (&lse, expr1, lss);
2045 gfc_add_modify_expr (&lse.pre, lse.expr, parm);
2046 gfc_start_block (&body);
2047 gfc_add_block_to_block (&body, &lse.pre);
2048 gfc_add_block_to_block (&body, &lse.post);
2050 /* Increment count. */
2051 tmp = fold (build2 (PLUS_EXPR, gfc_array_index_type,
2052 count, gfc_index_one_node));
2053 gfc_add_modify_expr (&body, count, tmp);
2055 tmp = gfc_finish_block (&body);
2057 tmp = gfc_trans_nested_forall_loop (nested_forall_info, tmp, 1, 1);
2058 gfc_add_expr_to_block (block, tmp);
2060 /* Free the temporary. */
2061 if (ptemp1)
2063 tmp = gfc_chainon_list (NULL_TREE, ptemp1);
2064 tmp = gfc_build_function_call (gfor_fndecl_internal_free, tmp);
2065 gfc_add_expr_to_block (block, tmp);
2070 /* FORALL and WHERE statements are really nasty, especially when you nest
2071 them. All the rhs of a forall assignment must be evaluated before the
2072 actual assignments are performed. Presumably this also applies to all the
2073 assignments in an inner where statement. */
2075 /* Generate code for a FORALL statement. Any temporaries are allocated as a
2076 linear array, relying on the fact that we process in the same order in all
2077 loops.
2079 forall (i=start:end:stride; maskexpr)
2080 e<i> = f<i>
2081 g<i> = h<i>
2082 end forall
2083 (where e,f,g,h<i> are arbitary expressions possibly involving i)
2084 Translates to:
2085 count = ((end + 1 - start) / staride)
2086 masktmp(:) = maskexpr(:)
2088 maskindex = 0;
2089 for (i = start; i <= end; i += stride)
2091 if (masktmp[maskindex++])
2092 e<i> = f<i>
2094 maskindex = 0;
2095 for (i = start; i <= end; i += stride)
2097 if (masktmp[maskindex++])
2098 e<i> = f<i>
2101 Note that this code only works when there are no dependencies.
2102 Forall loop with array assignments and data dependencies are a real pain,
2103 because the size of the temporary cannot always be determined before the
2104 loop is executed. This problem is compounded by the presence of nested
2105 FORALL constructs.
2108 static tree
2109 gfc_trans_forall_1 (gfc_code * code, forall_info * nested_forall_info)
2111 stmtblock_t block;
2112 stmtblock_t body;
2113 tree *var;
2114 tree *start;
2115 tree *end;
2116 tree *step;
2117 gfc_expr **varexpr;
2118 tree tmp;
2119 tree assign;
2120 tree size;
2121 tree bytesize;
2122 tree tmpvar;
2123 tree sizevar;
2124 tree lenvar;
2125 tree maskindex;
2126 tree mask;
2127 tree pmask;
2128 int n;
2129 int nvar;
2130 int need_temp;
2131 gfc_forall_iterator *fa;
2132 gfc_se se;
2133 gfc_code *c;
2134 gfc_saved_var *saved_vars;
2135 iter_info *this_forall, *iter_tmp;
2136 forall_info *info, *forall_tmp;
2137 temporary_list *temp;
2139 gfc_start_block (&block);
2141 n = 0;
2142 /* Count the FORALL index number. */
2143 for (fa = code->ext.forall_iterator; fa; fa = fa->next)
2144 n++;
2145 nvar = n;
2147 /* Allocate the space for var, start, end, step, varexpr. */
2148 var = (tree *) gfc_getmem (nvar * sizeof (tree));
2149 start = (tree *) gfc_getmem (nvar * sizeof (tree));
2150 end = (tree *) gfc_getmem (nvar * sizeof (tree));
2151 step = (tree *) gfc_getmem (nvar * sizeof (tree));
2152 varexpr = (gfc_expr **) gfc_getmem (nvar * sizeof (gfc_expr *));
2153 saved_vars = (gfc_saved_var *) gfc_getmem (nvar * sizeof (gfc_saved_var));
2155 /* Allocate the space for info. */
2156 info = (forall_info *) gfc_getmem (sizeof (forall_info));
2157 n = 0;
2158 for (fa = code->ext.forall_iterator; fa; fa = fa->next)
2160 gfc_symbol *sym = fa->var->symtree->n.sym;
2162 /* allocate space for this_forall. */
2163 this_forall = (iter_info *) gfc_getmem (sizeof (iter_info));
2165 /* Create a temporary variable for the FORALL index. */
2166 tmp = gfc_typenode_for_spec (&sym->ts);
2167 var[n] = gfc_create_var (tmp, sym->name);
2168 gfc_shadow_sym (sym, var[n], &saved_vars[n]);
2170 /* Record it in this_forall. */
2171 this_forall->var = var[n];
2173 /* Replace the index symbol's backend_decl with the temporary decl. */
2174 sym->backend_decl = var[n];
2176 /* Work out the start, end and stride for the loop. */
2177 gfc_init_se (&se, NULL);
2178 gfc_conv_expr_val (&se, fa->start);
2179 /* Record it in this_forall. */
2180 this_forall->start = se.expr;
2181 gfc_add_block_to_block (&block, &se.pre);
2182 start[n] = se.expr;
2184 gfc_init_se (&se, NULL);
2185 gfc_conv_expr_val (&se, fa->end);
2186 /* Record it in this_forall. */
2187 this_forall->end = se.expr;
2188 gfc_make_safe_expr (&se);
2189 gfc_add_block_to_block (&block, &se.pre);
2190 end[n] = se.expr;
2192 gfc_init_se (&se, NULL);
2193 gfc_conv_expr_val (&se, fa->stride);
2194 /* Record it in this_forall. */
2195 this_forall->step = se.expr;
2196 gfc_make_safe_expr (&se);
2197 gfc_add_block_to_block (&block, &se.pre);
2198 step[n] = se.expr;
2200 /* Set the NEXT field of this_forall to NULL. */
2201 this_forall->next = NULL;
2202 /* Link this_forall to the info construct. */
2203 if (info->this_loop == NULL)
2204 info->this_loop = this_forall;
2205 else
2207 iter_tmp = info->this_loop;
2208 while (iter_tmp->next != NULL)
2209 iter_tmp = iter_tmp->next;
2210 iter_tmp->next = this_forall;
2213 n++;
2215 nvar = n;
2217 /* Work out the number of elements in the mask array. */
2218 tmpvar = NULL_TREE;
2219 lenvar = NULL_TREE;
2220 size = gfc_index_one_node;
2221 sizevar = NULL_TREE;
2223 for (n = 0; n < nvar; n++)
2225 if (lenvar && TREE_TYPE (lenvar) != TREE_TYPE (start[n]))
2226 lenvar = NULL_TREE;
2228 /* size = (end + step - start) / step. */
2229 tmp = fold (build2 (MINUS_EXPR, TREE_TYPE (start[n]),
2230 step[n], start[n]));
2231 tmp = fold (build2 (PLUS_EXPR, TREE_TYPE (end[n]), end[n], tmp));
2233 tmp = fold (build2 (FLOOR_DIV_EXPR, TREE_TYPE (tmp), tmp, step[n]));
2234 tmp = convert (gfc_array_index_type, tmp);
2236 size = fold (build2 (MULT_EXPR, gfc_array_index_type, size, tmp));
2239 /* Record the nvar and size of current forall level. */
2240 info->nvar = nvar;
2241 info->size = size;
2243 /* Link the current forall level to nested_forall_info. */
2244 forall_tmp = nested_forall_info;
2245 if (forall_tmp == NULL)
2246 nested_forall_info = info;
2247 else
2249 while (forall_tmp->next_nest != NULL)
2250 forall_tmp = forall_tmp->next_nest;
2251 info->outer = forall_tmp;
2252 forall_tmp->next_nest = info;
2255 /* Copy the mask into a temporary variable if required.
2256 For now we assume a mask temporary is needed. */
2257 if (code->expr)
2259 /* Allocate the mask temporary. */
2260 bytesize = fold (build2 (MULT_EXPR, gfc_array_index_type, size,
2261 TYPE_SIZE_UNIT (boolean_type_node)));
2263 mask = gfc_do_allocate (bytesize, size, &pmask, &block, boolean_type_node);
2265 maskindex = gfc_create_var_np (gfc_array_index_type, "mi");
2266 /* Record them in the info structure. */
2267 info->pmask = pmask;
2268 info->mask = mask;
2269 info->maskindex = maskindex;
2271 gfc_add_modify_expr (&block, maskindex, gfc_index_zero_node);
2273 /* Start of mask assignment loop body. */
2274 gfc_start_block (&body);
2276 /* Evaluate the mask expression. */
2277 gfc_init_se (&se, NULL);
2278 gfc_conv_expr_val (&se, code->expr);
2279 gfc_add_block_to_block (&body, &se.pre);
2281 /* Store the mask. */
2282 se.expr = convert (boolean_type_node, se.expr);
2284 if (pmask)
2285 tmp = gfc_build_indirect_ref (mask);
2286 else
2287 tmp = mask;
2288 tmp = gfc_build_array_ref (tmp, maskindex);
2289 gfc_add_modify_expr (&body, tmp, se.expr);
2291 /* Advance to the next mask element. */
2292 tmp = build2 (PLUS_EXPR, gfc_array_index_type,
2293 maskindex, gfc_index_one_node);
2294 gfc_add_modify_expr (&body, maskindex, tmp);
2296 /* Generate the loops. */
2297 tmp = gfc_finish_block (&body);
2298 tmp = gfc_trans_nested_forall_loop (info, tmp, 0, 0);
2299 gfc_add_expr_to_block (&block, tmp);
2301 else
2303 /* No mask was specified. */
2304 maskindex = NULL_TREE;
2305 mask = pmask = NULL_TREE;
2308 c = code->block->next;
2310 /* TODO: loop merging in FORALL statements. */
2311 /* Now that we've got a copy of the mask, generate the assignment loops. */
2312 while (c)
2314 switch (c->op)
2316 case EXEC_ASSIGN:
2317 /* A scalar or array assignment. */
2318 need_temp = gfc_check_dependency (c->expr, c->expr2, varexpr, nvar);
2319 /* Teporaries due to array assignment data dependencies introduce
2320 no end of problems. */
2321 if (need_temp)
2322 gfc_trans_assign_need_temp (c->expr, c->expr2, NULL,
2323 nested_forall_info, &block);
2324 else
2326 /* Use the normal assignment copying routines. */
2327 assign = gfc_trans_assignment (c->expr, c->expr2);
2329 /* Reset the mask index. */
2330 if (mask)
2331 gfc_add_modify_expr (&block, maskindex, gfc_index_zero_node);
2333 /* Generate body and loops. */
2334 tmp = gfc_trans_nested_forall_loop (nested_forall_info, assign, 1, 1);
2335 gfc_add_expr_to_block (&block, tmp);
2338 break;
2340 case EXEC_WHERE:
2342 /* Translate WHERE or WHERE construct nested in FORALL. */
2343 temp = NULL;
2344 gfc_trans_where_2 (c, NULL, NULL, nested_forall_info, &block, &temp);
2346 while (temp)
2348 tree args;
2349 temporary_list *p;
2351 /* Free the temporary. */
2352 args = gfc_chainon_list (NULL_TREE, temp->temporary);
2353 tmp = gfc_build_function_call (gfor_fndecl_internal_free, args);
2354 gfc_add_expr_to_block (&block, tmp);
2356 p = temp;
2357 temp = temp->next;
2358 gfc_free (p);
2361 break;
2363 /* Pointer assignment inside FORALL. */
2364 case EXEC_POINTER_ASSIGN:
2365 need_temp = gfc_check_dependency (c->expr, c->expr2, varexpr, nvar);
2366 if (need_temp)
2367 gfc_trans_pointer_assign_need_temp (c->expr, c->expr2,
2368 nested_forall_info, &block);
2369 else
2371 /* Use the normal assignment copying routines. */
2372 assign = gfc_trans_pointer_assignment (c->expr, c->expr2);
2374 /* Reset the mask index. */
2375 if (mask)
2376 gfc_add_modify_expr (&block, maskindex, gfc_index_zero_node);
2378 /* Generate body and loops. */
2379 tmp = gfc_trans_nested_forall_loop (nested_forall_info, assign,
2380 1, 1);
2381 gfc_add_expr_to_block (&block, tmp);
2383 break;
2385 case EXEC_FORALL:
2386 tmp = gfc_trans_forall_1 (c, nested_forall_info);
2387 gfc_add_expr_to_block (&block, tmp);
2388 break;
2390 default:
2391 gcc_unreachable ();
2394 c = c->next;
2397 /* Restore the original index variables. */
2398 for (fa = code->ext.forall_iterator, n = 0; fa; fa = fa->next, n++)
2399 gfc_restore_sym (fa->var->symtree->n.sym, &saved_vars[n]);
2401 /* Free the space for var, start, end, step, varexpr. */
2402 gfc_free (var);
2403 gfc_free (start);
2404 gfc_free (end);
2405 gfc_free (step);
2406 gfc_free (varexpr);
2407 gfc_free (saved_vars);
2409 if (pmask)
2411 /* Free the temporary for the mask. */
2412 tmp = gfc_chainon_list (NULL_TREE, pmask);
2413 tmp = gfc_build_function_call (gfor_fndecl_internal_free, tmp);
2414 gfc_add_expr_to_block (&block, tmp);
2416 if (maskindex)
2417 pushdecl (maskindex);
2419 return gfc_finish_block (&block);
2423 /* Translate the FORALL statement or construct. */
2425 tree gfc_trans_forall (gfc_code * code)
2427 return gfc_trans_forall_1 (code, NULL);
2431 /* Evaluate the WHERE mask expression, copy its value to a temporary.
2432 If the WHERE construct is nested in FORALL, compute the overall temporary
2433 needed by the WHERE mask expression multiplied by the iterator number of
2434 the nested forall.
2435 ME is the WHERE mask expression.
2436 MASK is the temporary which value is mask's value.
2437 NMASK is another temporary which value is !mask.
2438 TEMP records the temporary's address allocated in this function in order to
2439 free them outside this function.
2440 MASK, NMASK and TEMP are all OUT arguments. */
2442 static tree
2443 gfc_evaluate_where_mask (gfc_expr * me, forall_info * nested_forall_info,
2444 tree * mask, tree * nmask, temporary_list ** temp,
2445 stmtblock_t * block)
2447 tree tmp, tmp1;
2448 gfc_ss *lss, *rss;
2449 gfc_loopinfo loop;
2450 tree ptemp1, ntmp, ptemp2;
2451 tree inner_size;
2452 stmtblock_t body, body1;
2453 gfc_se lse, rse;
2454 tree count;
2455 tree tmpexpr;
2457 gfc_init_loopinfo (&loop);
2459 /* Calculate the size of temporary needed by the mask-expr. */
2460 inner_size = compute_inner_temp_size (me, me, block, &lss, &rss);
2462 /* Allocate temporary for where mask. */
2463 tmp = allocate_temp_for_forall_nest (nested_forall_info, boolean_type_node,
2464 inner_size, block, &ptemp1);
2465 /* Record the temporary address in order to free it later. */
2466 if (ptemp1)
2468 temporary_list *tempo;
2469 tempo = (temporary_list *) gfc_getmem (sizeof (temporary_list));
2470 tempo->temporary = ptemp1;
2471 tempo->next = *temp;
2472 *temp = tempo;
2475 /* Allocate temporary for !mask. */
2476 ntmp = allocate_temp_for_forall_nest (nested_forall_info, boolean_type_node,
2477 inner_size, block, &ptemp2);
2478 /* Record the temporary in order to free it later. */
2479 if (ptemp2)
2481 temporary_list *tempo;
2482 tempo = (temporary_list *) gfc_getmem (sizeof (temporary_list));
2483 tempo->temporary = ptemp2;
2484 tempo->next = *temp;
2485 *temp = tempo;
2488 /* Variable to index the temporary. */
2489 count = gfc_create_var (gfc_array_index_type, "count");
2490 /* Initialize count. */
2491 gfc_add_modify_expr (block, count, gfc_index_zero_node);
2493 gfc_start_block (&body);
2495 gfc_init_se (&rse, NULL);
2496 gfc_init_se (&lse, NULL);
2498 if (lss == gfc_ss_terminator)
2500 gfc_init_block (&body1);
2502 else
2504 /* Initialize the loop. */
2505 gfc_init_loopinfo (&loop);
2507 /* We may need LSS to determine the shape of the expression. */
2508 gfc_add_ss_to_loop (&loop, lss);
2509 gfc_add_ss_to_loop (&loop, rss);
2511 gfc_conv_ss_startstride (&loop);
2512 gfc_conv_loop_setup (&loop);
2514 gfc_mark_ss_chain_used (rss, 1);
2515 /* Start the loop body. */
2516 gfc_start_scalarized_body (&loop, &body1);
2518 /* Translate the expression. */
2519 gfc_copy_loopinfo_to_se (&rse, &loop);
2520 rse.ss = rss;
2521 gfc_conv_expr (&rse, me);
2523 /* Form the expression of the temporary. */
2524 lse.expr = gfc_build_array_ref (tmp, count);
2525 tmpexpr = gfc_build_array_ref (ntmp, count);
2527 /* Use the scalar assignment to fill temporary TMP. */
2528 tmp1 = gfc_trans_scalar_assign (&lse, &rse, me->ts.type);
2529 gfc_add_expr_to_block (&body1, tmp1);
2531 /* Fill temporary NTMP. */
2532 tmp1 = build1 (TRUTH_NOT_EXPR, TREE_TYPE (lse.expr), lse.expr);
2533 gfc_add_modify_expr (&body1, tmpexpr, tmp1);
2535 if (lss == gfc_ss_terminator)
2537 gfc_add_block_to_block (&body, &body1);
2539 else
2541 /* Increment count. */
2542 tmp1 = fold (build2 (PLUS_EXPR, gfc_array_index_type, count,
2543 gfc_index_one_node));
2544 gfc_add_modify_expr (&body1, count, tmp1);
2546 /* Generate the copying loops. */
2547 gfc_trans_scalarizing_loops (&loop, &body1);
2549 gfc_add_block_to_block (&body, &loop.pre);
2550 gfc_add_block_to_block (&body, &loop.post);
2552 gfc_cleanup_loop (&loop);
2553 /* TODO: Reuse lss and rss when copying temp->lhs. Need to be careful
2554 as tree nodes in SS may not be valid in different scope. */
2557 tmp1 = gfc_finish_block (&body);
2558 /* If the WHERE construct is inside FORALL, fill the full temporary. */
2559 if (nested_forall_info != NULL)
2560 tmp1 = gfc_trans_nested_forall_loop (nested_forall_info, tmp1, 1, 1);
2563 gfc_add_expr_to_block (block, tmp1);
2565 *mask = tmp;
2566 *nmask = ntmp;
2568 return tmp1;
2572 /* Translate an assignment statement in a WHERE statement or construct
2573 statement. The MASK expression is used to control which elements
2574 of EXPR1 shall be assigned. */
2576 static tree
2577 gfc_trans_where_assign (gfc_expr *expr1, gfc_expr *expr2, tree mask,
2578 tree count1, tree count2)
2580 gfc_se lse;
2581 gfc_se rse;
2582 gfc_ss *lss;
2583 gfc_ss *lss_section;
2584 gfc_ss *rss;
2586 gfc_loopinfo loop;
2587 tree tmp;
2588 stmtblock_t block;
2589 stmtblock_t body;
2590 tree index, maskexpr, tmp1;
2592 #if 0
2593 /* TODO: handle this special case.
2594 Special case a single function returning an array. */
2595 if (expr2->expr_type == EXPR_FUNCTION && expr2->rank > 0)
2597 tmp = gfc_trans_arrayfunc_assign (expr1, expr2);
2598 if (tmp)
2599 return tmp;
2601 #endif
2603 /* Assignment of the form lhs = rhs. */
2604 gfc_start_block (&block);
2606 gfc_init_se (&lse, NULL);
2607 gfc_init_se (&rse, NULL);
2609 /* Walk the lhs. */
2610 lss = gfc_walk_expr (expr1);
2611 rss = NULL;
2613 /* In each where-assign-stmt, the mask-expr and the variable being
2614 defined shall be arrays of the same shape. */
2615 gcc_assert (lss != gfc_ss_terminator);
2617 /* The assignment needs scalarization. */
2618 lss_section = lss;
2620 /* Find a non-scalar SS from the lhs. */
2621 while (lss_section != gfc_ss_terminator
2622 && lss_section->type != GFC_SS_SECTION)
2623 lss_section = lss_section->next;
2625 gcc_assert (lss_section != gfc_ss_terminator);
2627 /* Initialize the scalarizer. */
2628 gfc_init_loopinfo (&loop);
2630 /* Walk the rhs. */
2631 rss = gfc_walk_expr (expr2);
2632 if (rss == gfc_ss_terminator)
2634 /* The rhs is scalar. Add a ss for the expression. */
2635 rss = gfc_get_ss ();
2636 rss->next = gfc_ss_terminator;
2637 rss->type = GFC_SS_SCALAR;
2638 rss->expr = expr2;
2641 /* Associate the SS with the loop. */
2642 gfc_add_ss_to_loop (&loop, lss);
2643 gfc_add_ss_to_loop (&loop, rss);
2645 /* Calculate the bounds of the scalarization. */
2646 gfc_conv_ss_startstride (&loop);
2648 /* Resolve any data dependencies in the statement. */
2649 gfc_conv_resolve_dependencies (&loop, lss_section, rss);
2651 /* Setup the scalarizing loops. */
2652 gfc_conv_loop_setup (&loop);
2654 /* Setup the gfc_se structures. */
2655 gfc_copy_loopinfo_to_se (&lse, &loop);
2656 gfc_copy_loopinfo_to_se (&rse, &loop);
2658 rse.ss = rss;
2659 gfc_mark_ss_chain_used (rss, 1);
2660 if (loop.temp_ss == NULL)
2662 lse.ss = lss;
2663 gfc_mark_ss_chain_used (lss, 1);
2665 else
2667 lse.ss = loop.temp_ss;
2668 gfc_mark_ss_chain_used (lss, 3);
2669 gfc_mark_ss_chain_used (loop.temp_ss, 3);
2672 /* Start the scalarized loop body. */
2673 gfc_start_scalarized_body (&loop, &body);
2675 /* Translate the expression. */
2676 gfc_conv_expr (&rse, expr2);
2677 if (lss != gfc_ss_terminator && loop.temp_ss != NULL)
2679 gfc_conv_tmp_array_ref (&lse);
2680 gfc_advance_se_ss_chain (&lse);
2682 else
2683 gfc_conv_expr (&lse, expr1);
2685 /* Form the mask expression according to the mask tree list. */
2686 index = count1;
2687 tmp = mask;
2688 if (tmp != NULL)
2689 maskexpr = gfc_build_array_ref (tmp, index);
2690 else
2691 maskexpr = NULL;
2693 tmp = TREE_CHAIN (tmp);
2694 while (tmp)
2696 tmp1 = gfc_build_array_ref (tmp, index);
2697 maskexpr = build2 (TRUTH_AND_EXPR, TREE_TYPE (tmp1), maskexpr, tmp1);
2698 tmp = TREE_CHAIN (tmp);
2700 /* Use the scalar assignment as is. */
2701 tmp = gfc_trans_scalar_assign (&lse, &rse, expr1->ts.type);
2702 tmp = build3_v (COND_EXPR, maskexpr, tmp, build_empty_stmt ());
2704 gfc_add_expr_to_block (&body, tmp);
2706 if (lss == gfc_ss_terminator)
2708 /* Increment count1. */
2709 tmp = fold (build2 (PLUS_EXPR, gfc_array_index_type,
2710 count1, gfc_index_one_node));
2711 gfc_add_modify_expr (&body, count1, tmp);
2713 /* Use the scalar assignment as is. */
2714 gfc_add_block_to_block (&block, &body);
2716 else
2718 gcc_assert (lse.ss == gfc_ss_terminator
2719 && rse.ss == gfc_ss_terminator);
2721 if (loop.temp_ss != NULL)
2723 /* Increment count1 before finish the main body of a scalarized
2724 expression. */
2725 tmp = fold (build2 (PLUS_EXPR, gfc_array_index_type,
2726 count1, gfc_index_one_node));
2727 gfc_add_modify_expr (&body, count1, tmp);
2728 gfc_trans_scalarized_loop_boundary (&loop, &body);
2730 /* We need to copy the temporary to the actual lhs. */
2731 gfc_init_se (&lse, NULL);
2732 gfc_init_se (&rse, NULL);
2733 gfc_copy_loopinfo_to_se (&lse, &loop);
2734 gfc_copy_loopinfo_to_se (&rse, &loop);
2736 rse.ss = loop.temp_ss;
2737 lse.ss = lss;
2739 gfc_conv_tmp_array_ref (&rse);
2740 gfc_advance_se_ss_chain (&rse);
2741 gfc_conv_expr (&lse, expr1);
2743 gcc_assert (lse.ss == gfc_ss_terminator
2744 && rse.ss == gfc_ss_terminator);
2746 /* Form the mask expression according to the mask tree list. */
2747 index = count2;
2748 tmp = mask;
2749 if (tmp != NULL)
2750 maskexpr = gfc_build_array_ref (tmp, index);
2751 else
2752 maskexpr = NULL;
2754 tmp = TREE_CHAIN (tmp);
2755 while (tmp)
2757 tmp1 = gfc_build_array_ref (tmp, index);
2758 maskexpr = build2 (TRUTH_AND_EXPR, TREE_TYPE (tmp1),
2759 maskexpr, tmp1);
2760 tmp = TREE_CHAIN (tmp);
2762 /* Use the scalar assignment as is. */
2763 tmp = gfc_trans_scalar_assign (&lse, &rse, expr1->ts.type);
2764 tmp = build3_v (COND_EXPR, maskexpr, tmp, build_empty_stmt ());
2765 gfc_add_expr_to_block (&body, tmp);
2767 /* Increment count2. */
2768 tmp = fold (build2 (PLUS_EXPR, gfc_array_index_type,
2769 count2, gfc_index_one_node));
2770 gfc_add_modify_expr (&body, count2, tmp);
2772 else
2774 /* Increment count1. */
2775 tmp = fold (build2 (PLUS_EXPR, gfc_array_index_type,
2776 count1, gfc_index_one_node));
2777 gfc_add_modify_expr (&body, count1, tmp);
2780 /* Generate the copying loops. */
2781 gfc_trans_scalarizing_loops (&loop, &body);
2783 /* Wrap the whole thing up. */
2784 gfc_add_block_to_block (&block, &loop.pre);
2785 gfc_add_block_to_block (&block, &loop.post);
2786 gfc_cleanup_loop (&loop);
2789 return gfc_finish_block (&block);
2793 /* Translate the WHERE construct or statement.
2794 This fuction can be called iteratively to translate the nested WHERE
2795 construct or statement.
2796 MASK is the control mask, and PMASK is the pending control mask.
2797 TEMP records the temporary address which must be freed later. */
2799 static void
2800 gfc_trans_where_2 (gfc_code * code, tree mask, tree pmask,
2801 forall_info * nested_forall_info, stmtblock_t * block,
2802 temporary_list ** temp)
2804 gfc_expr *expr1;
2805 gfc_expr *expr2;
2806 gfc_code *cblock;
2807 gfc_code *cnext;
2808 tree tmp, tmp1, tmp2;
2809 tree count1, count2;
2810 tree mask_copy;
2811 int need_temp;
2813 /* the WHERE statement or the WHERE construct statement. */
2814 cblock = code->block;
2815 while (cblock)
2817 /* Has mask-expr. */
2818 if (cblock->expr)
2820 /* Ensure that the WHERE mask be evaluated only once. */
2821 tmp2 = gfc_evaluate_where_mask (cblock->expr, nested_forall_info,
2822 &tmp, &tmp1, temp, block);
2824 /* Set the control mask and the pending control mask. */
2825 /* It's a where-stmt. */
2826 if (mask == NULL)
2828 mask = tmp;
2829 pmask = tmp1;
2831 /* It's a nested where-stmt. */
2832 else if (mask && pmask == NULL)
2834 tree tmp2;
2835 /* Use the TREE_CHAIN to list the masks. */
2836 tmp2 = copy_list (mask);
2837 pmask = chainon (mask, tmp1);
2838 mask = chainon (tmp2, tmp);
2840 /* It's a masked-elsewhere-stmt. */
2841 else if (mask && cblock->expr)
2843 tree tmp2;
2844 tmp2 = copy_list (pmask);
2846 mask = pmask;
2847 tmp2 = chainon (tmp2, tmp);
2848 pmask = chainon (mask, tmp1);
2849 mask = tmp2;
2852 /* It's a elsewhere-stmt. No mask-expr is present. */
2853 else
2854 mask = pmask;
2856 /* Get the assignment statement of a WHERE statement, or the first
2857 statement in where-body-construct of a WHERE construct. */
2858 cnext = cblock->next;
2859 while (cnext)
2861 switch (cnext->op)
2863 /* WHERE assignment statement. */
2864 case EXEC_ASSIGN:
2865 expr1 = cnext->expr;
2866 expr2 = cnext->expr2;
2867 if (nested_forall_info != NULL)
2869 int nvar;
2870 gfc_expr **varexpr;
2872 nvar = nested_forall_info->nvar;
2873 varexpr = (gfc_expr **)
2874 gfc_getmem (nvar * sizeof (gfc_expr *));
2875 need_temp = gfc_check_dependency (expr1, expr2, varexpr,
2876 nvar);
2877 if (need_temp)
2878 gfc_trans_assign_need_temp (expr1, expr2, mask,
2879 nested_forall_info, block);
2880 else
2882 /* Variables to control maskexpr. */
2883 count1 = gfc_create_var (gfc_array_index_type, "count1");
2884 count2 = gfc_create_var (gfc_array_index_type, "count2");
2885 gfc_add_modify_expr (block, count1, gfc_index_zero_node);
2886 gfc_add_modify_expr (block, count2, gfc_index_zero_node);
2888 tmp = gfc_trans_where_assign (expr1, expr2, mask, count1,
2889 count2);
2890 tmp = gfc_trans_nested_forall_loop (nested_forall_info,
2891 tmp, 1, 1);
2892 gfc_add_expr_to_block (block, tmp);
2895 else
2897 /* Variables to control maskexpr. */
2898 count1 = gfc_create_var (gfc_array_index_type, "count1");
2899 count2 = gfc_create_var (gfc_array_index_type, "count2");
2900 gfc_add_modify_expr (block, count1, gfc_index_zero_node);
2901 gfc_add_modify_expr (block, count2, gfc_index_zero_node);
2903 tmp = gfc_trans_where_assign (expr1, expr2, mask, count1,
2904 count2);
2905 gfc_add_expr_to_block (block, tmp);
2908 break;
2910 /* WHERE or WHERE construct is part of a where-body-construct. */
2911 case EXEC_WHERE:
2912 /* Ensure that MASK is not modified by next gfc_trans_where_2. */
2913 mask_copy = copy_list (mask);
2914 gfc_trans_where_2 (cnext, mask_copy, NULL, nested_forall_info,
2915 block, temp);
2916 break;
2918 default:
2919 gcc_unreachable ();
2922 /* The next statement within the same where-body-construct. */
2923 cnext = cnext->next;
2925 /* The next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt. */
2926 cblock = cblock->block;
2931 /* As the WHERE or WHERE construct statement can be nested, we call
2932 gfc_trans_where_2 to do the translation, and pass the initial
2933 NULL values for both the control mask and the pending control mask. */
2935 tree
2936 gfc_trans_where (gfc_code * code)
2938 stmtblock_t block;
2939 temporary_list *temp, *p;
2940 tree args;
2941 tree tmp;
2943 gfc_start_block (&block);
2944 temp = NULL;
2946 gfc_trans_where_2 (code, NULL, NULL, NULL, &block, &temp);
2948 /* Add calls to free temporaries which were dynamically allocated. */
2949 while (temp)
2951 args = gfc_chainon_list (NULL_TREE, temp->temporary);
2952 tmp = gfc_build_function_call (gfor_fndecl_internal_free, args);
2953 gfc_add_expr_to_block (&block, tmp);
2955 p = temp;
2956 temp = temp->next;
2957 gfc_free (p);
2959 return gfc_finish_block (&block);
2963 /* CYCLE a DO loop. The label decl has already been created by
2964 gfc_trans_do(), it's in TREE_PURPOSE (backend_decl) of the gfc_code
2965 node at the head of the loop. We must mark the label as used. */
2967 tree
2968 gfc_trans_cycle (gfc_code * code)
2970 tree cycle_label;
2972 cycle_label = TREE_PURPOSE (code->ext.whichloop->backend_decl);
2973 TREE_USED (cycle_label) = 1;
2974 return build1_v (GOTO_EXPR, cycle_label);
2978 /* EXIT a DO loop. Similair to CYCLE, but now the label is in
2979 TREE_VALUE (backend_decl) of the gfc_code node at the head of the
2980 loop. */
2982 tree
2983 gfc_trans_exit (gfc_code * code)
2985 tree exit_label;
2987 exit_label = TREE_VALUE (code->ext.whichloop->backend_decl);
2988 TREE_USED (exit_label) = 1;
2989 return build1_v (GOTO_EXPR, exit_label);
2993 /* Translate the ALLOCATE statement. */
2995 tree
2996 gfc_trans_allocate (gfc_code * code)
2998 gfc_alloc *al;
2999 gfc_expr *expr;
3000 gfc_se se;
3001 tree tmp;
3002 tree parm;
3003 gfc_ref *ref;
3004 tree stat;
3005 tree pstat;
3006 tree error_label;
3007 stmtblock_t block;
3009 if (!code->ext.alloc_list)
3010 return NULL_TREE;
3012 gfc_start_block (&block);
3014 if (code->expr)
3016 tree gfc_int4_type_node = gfc_get_int_type (4);
3018 stat = gfc_create_var (gfc_int4_type_node, "stat");
3019 pstat = gfc_build_addr_expr (NULL, stat);
3021 error_label = gfc_build_label_decl (NULL_TREE);
3022 TREE_USED (error_label) = 1;
3024 else
3026 pstat = integer_zero_node;
3027 stat = error_label = NULL_TREE;
3031 for (al = code->ext.alloc_list; al != NULL; al = al->next)
3033 expr = al->expr;
3035 gfc_init_se (&se, NULL);
3036 gfc_start_block (&se.pre);
3038 se.want_pointer = 1;
3039 se.descriptor_only = 1;
3040 gfc_conv_expr (&se, expr);
3042 ref = expr->ref;
3044 /* Find the last reference in the chain. */
3045 while (ref && ref->next != NULL)
3047 gcc_assert (ref->type != REF_ARRAY || ref->u.ar.type == AR_ELEMENT);
3048 ref = ref->next;
3051 if (ref != NULL && ref->type == REF_ARRAY)
3053 /* An array. */
3054 gfc_array_allocate (&se, ref, pstat);
3056 else
3058 /* A scalar or derived type. */
3059 tree val;
3061 val = gfc_create_var (ppvoid_type_node, "ptr");
3062 tmp = gfc_build_addr_expr (ppvoid_type_node, se.expr);
3063 gfc_add_modify_expr (&se.pre, val, tmp);
3065 tmp = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (se.expr)));
3066 parm = gfc_chainon_list (NULL_TREE, val);
3067 parm = gfc_chainon_list (parm, tmp);
3068 parm = gfc_chainon_list (parm, pstat);
3069 tmp = gfc_build_function_call (gfor_fndecl_allocate, parm);
3070 gfc_add_expr_to_block (&se.pre, tmp);
3072 if (code->expr)
3074 tmp = build1_v (GOTO_EXPR, error_label);
3075 parm =
3076 build2 (NE_EXPR, boolean_type_node, stat, integer_zero_node);
3077 tmp = build3_v (COND_EXPR, parm, tmp, build_empty_stmt ());
3078 gfc_add_expr_to_block (&se.pre, tmp);
3082 tmp = gfc_finish_block (&se.pre);
3083 gfc_add_expr_to_block (&block, tmp);
3086 /* Assign the value to the status variable. */
3087 if (code->expr)
3089 tmp = build1_v (LABEL_EXPR, error_label);
3090 gfc_add_expr_to_block (&block, tmp);
3092 gfc_init_se (&se, NULL);
3093 gfc_conv_expr_lhs (&se, code->expr);
3094 tmp = convert (TREE_TYPE (se.expr), stat);
3095 gfc_add_modify_expr (&block, se.expr, tmp);
3098 return gfc_finish_block (&block);
3102 tree
3103 gfc_trans_deallocate (gfc_code * code)
3105 gfc_se se;
3106 gfc_alloc *al;
3107 gfc_expr *expr;
3108 tree var;
3109 tree tmp;
3110 tree type;
3111 stmtblock_t block;
3113 gfc_start_block (&block);
3115 for (al = code->ext.alloc_list; al != NULL; al = al->next)
3117 expr = al->expr;
3118 gcc_assert (expr->expr_type == EXPR_VARIABLE);
3120 gfc_init_se (&se, NULL);
3121 gfc_start_block (&se.pre);
3123 se.want_pointer = 1;
3124 se.descriptor_only = 1;
3125 gfc_conv_expr (&se, expr);
3127 if (expr->symtree->n.sym->attr.dimension)
3129 tmp = gfc_array_deallocate (se.expr);
3130 gfc_add_expr_to_block (&se.pre, tmp);
3132 else
3134 type = build_pointer_type (TREE_TYPE (se.expr));
3135 var = gfc_create_var (type, "ptr");
3136 tmp = gfc_build_addr_expr (type, se.expr);
3137 gfc_add_modify_expr (&se.pre, var, tmp);
3139 tmp = gfc_chainon_list (NULL_TREE, var);
3140 tmp = gfc_chainon_list (tmp, integer_zero_node);
3141 tmp = gfc_build_function_call (gfor_fndecl_deallocate, tmp);
3142 gfc_add_expr_to_block (&se.pre, tmp);
3144 tmp = gfc_finish_block (&se.pre);
3145 gfc_add_expr_to_block (&block, tmp);
3148 return gfc_finish_block (&block);