OSDN Git Service

* trans-stmt.c (struct temporary_list): Delete.
[pf3gnuchains/gcc-fork.git] / gcc / fortran / trans-stmt.c
1 /* Statement translation -- generate GCC trees from gfc_code.
2    Copyright (C) 2002, 2003, 2004, 2005, 2006 Free Software Foundation,
3    Inc.
4    Contributed by Paul Brook <paul@nowt.org>
5    and Steven Bosscher <s.bosscher@student.tudelft.nl>
6
7 This file is part of GCC.
8
9 GCC is free software; you can redistribute it and/or modify it under
10 the terms of the GNU General Public License as published by the Free
11 Software Foundation; either version 2, or (at your option) any later
12 version.
13
14 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
15 WARRANTY; without even the implied warranty of MERCHANTABILITY or
16 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
17 for more details.
18
19 You should have received a copy of the GNU General Public License
20 along with GCC; see the file COPYING.  If not, write to the Free
21 Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA
22 02110-1301, USA.  */
23
24
25 #include "config.h"
26 #include "system.h"
27 #include "coretypes.h"
28 #include "tree.h"
29 #include "tree-gimple.h"
30 #include "ggc.h"
31 #include "toplev.h"
32 #include "real.h"
33 #include "gfortran.h"
34 #include "trans.h"
35 #include "trans-stmt.h"
36 #include "trans-types.h"
37 #include "trans-array.h"
38 #include "trans-const.h"
39 #include "arith.h"
40 #include "dependency.h"
41
42 typedef struct iter_info
43 {
44   tree var;
45   tree start;
46   tree end;
47   tree step;
48   struct iter_info *next;
49 }
50 iter_info;
51
52 typedef struct forall_info
53 {
54   iter_info *this_loop;
55   tree mask;
56   tree pmask;
57   tree maskindex;
58   int nvar;
59   tree size;
60   struct forall_info  *outer;
61   struct forall_info  *next_nest;
62 }
63 forall_info;
64
65 static void gfc_trans_where_2 (gfc_code *, tree, forall_info *, stmtblock_t *);
66
67 /* Translate a F95 label number to a LABEL_EXPR.  */
68
69 tree
70 gfc_trans_label_here (gfc_code * code)
71 {
72   return build1_v (LABEL_EXPR, gfc_get_label_decl (code->here));
73 }
74
75
76 /* Given a variable expression which has been ASSIGNed to, find the decl
77    containing the auxiliary variables.  For variables in common blocks this
78    is a field_decl.  */
79
80 void
81 gfc_conv_label_variable (gfc_se * se, gfc_expr * expr)
82 {
83   gcc_assert (expr->symtree->n.sym->attr.assign == 1);
84   gfc_conv_expr (se, expr);
85   /* Deals with variable in common block. Get the field declaration.  */
86   if (TREE_CODE (se->expr) == COMPONENT_REF)
87     se->expr = TREE_OPERAND (se->expr, 1);
88   /* Deals with dummy argument. Get the parameter declaration.  */
89   else if (TREE_CODE (se->expr) == INDIRECT_REF)
90     se->expr = TREE_OPERAND (se->expr, 0);
91 }
92
93 /* Translate a label assignment statement.  */
94
95 tree
96 gfc_trans_label_assign (gfc_code * code)
97 {
98   tree label_tree;
99   gfc_se se;
100   tree len;
101   tree addr;
102   tree len_tree;
103   char *label_str;
104   int label_len;
105
106   /* Start a new block.  */
107   gfc_init_se (&se, NULL);
108   gfc_start_block (&se.pre);
109   gfc_conv_label_variable (&se, code->expr);
110
111   len = GFC_DECL_STRING_LEN (se.expr);
112   addr = GFC_DECL_ASSIGN_ADDR (se.expr);
113
114   label_tree = gfc_get_label_decl (code->label);
115
116   if (code->label->defined == ST_LABEL_TARGET)
117     {
118       label_tree = gfc_build_addr_expr (pvoid_type_node, label_tree);
119       len_tree = integer_minus_one_node;
120     }
121   else
122     {
123       label_str = code->label->format->value.character.string;
124       label_len = code->label->format->value.character.length;
125       len_tree = build_int_cst (NULL_TREE, label_len);
126       label_tree = gfc_build_string_const (label_len + 1, label_str);
127       label_tree = gfc_build_addr_expr (pvoid_type_node, label_tree);
128     }
129
130   gfc_add_modify_expr (&se.pre, len, len_tree);
131   gfc_add_modify_expr (&se.pre, addr, label_tree);
132
133   return gfc_finish_block (&se.pre);
134 }
135
136 /* Translate a GOTO statement.  */
137
138 tree
139 gfc_trans_goto (gfc_code * code)
140 {
141   tree assigned_goto;
142   tree target;
143   tree tmp;
144   tree assign_error;
145   tree range_error;
146   gfc_se se;
147
148
149   if (code->label != NULL)
150     return build1_v (GOTO_EXPR, gfc_get_label_decl (code->label));
151
152   /* ASSIGNED GOTO.  */
153   gfc_init_se (&se, NULL);
154   gfc_start_block (&se.pre);
155   gfc_conv_label_variable (&se, code->expr);
156   assign_error =
157     gfc_build_cstring_const ("Assigned label is not a target label");
158   tmp = GFC_DECL_STRING_LEN (se.expr);
159   tmp = fold_build2 (NE_EXPR, boolean_type_node, tmp,
160                      build_int_cst (TREE_TYPE (tmp), -1));
161   gfc_trans_runtime_check (tmp, assign_error, &se.pre);
162
163   assigned_goto = GFC_DECL_ASSIGN_ADDR (se.expr);
164
165   code = code->block;
166   if (code == NULL)
167     {
168       target = build1 (GOTO_EXPR, void_type_node, assigned_goto);
169       gfc_add_expr_to_block (&se.pre, target);
170       return gfc_finish_block (&se.pre);
171     }
172
173   /* Check the label list.  */
174   range_error = gfc_build_cstring_const ("Assigned label is not in the list");
175
176   do
177     {
178       target = gfc_get_label_decl (code->label);
179       tmp = gfc_build_addr_expr (pvoid_type_node, target);
180       tmp = build2 (EQ_EXPR, boolean_type_node, tmp, assigned_goto);
181       tmp = build3_v (COND_EXPR, tmp,
182                       build1 (GOTO_EXPR, void_type_node, target),
183                       build_empty_stmt ());
184       gfc_add_expr_to_block (&se.pre, tmp);
185       code = code->block;
186     }
187   while (code != NULL);
188   gfc_trans_runtime_check (boolean_true_node, range_error, &se.pre);
189   return gfc_finish_block (&se.pre); 
190 }
191
192
193 /* Translate an ENTRY statement.  Just adds a label for this entry point.  */
194 tree
195 gfc_trans_entry (gfc_code * code)
196 {
197   return build1_v (LABEL_EXPR, code->ext.entry->label);
198 }
199
200
201 /* Translate the CALL statement.  Builds a call to an F95 subroutine.  */
202
203 tree
204 gfc_trans_call (gfc_code * code)
205 {
206   gfc_se se;
207   gfc_ss * ss;
208   int has_alternate_specifier;
209
210   /* A CALL starts a new block because the actual arguments may have to
211      be evaluated first.  */
212   gfc_init_se (&se, NULL);
213   gfc_start_block (&se.pre);
214
215   gcc_assert (code->resolved_sym);
216
217   ss = gfc_ss_terminator;
218   if (code->resolved_sym->attr.elemental)
219     ss = gfc_walk_elemental_function_args (ss, code->ext.actual, GFC_SS_REFERENCE);
220
221   /* Is not an elemental subroutine call with array valued arguments.  */
222   if (ss == gfc_ss_terminator)
223     {
224
225       /* Translate the call.  */
226       has_alternate_specifier
227         = gfc_conv_function_call (&se, code->resolved_sym, code->ext.actual);
228
229       /* A subroutine without side-effect, by definition, does nothing!  */
230       TREE_SIDE_EFFECTS (se.expr) = 1;
231
232       /* Chain the pieces together and return the block.  */
233       if (has_alternate_specifier)
234         {
235           gfc_code *select_code;
236           gfc_symbol *sym;
237           select_code = code->next;
238           gcc_assert(select_code->op == EXEC_SELECT);
239           sym = select_code->expr->symtree->n.sym;
240           se.expr = convert (gfc_typenode_for_spec (&sym->ts), se.expr);
241           gfc_add_modify_expr (&se.pre, sym->backend_decl, se.expr);
242         }
243       else
244         gfc_add_expr_to_block (&se.pre, se.expr);
245
246       gfc_add_block_to_block (&se.pre, &se.post);
247     }
248
249   else
250     {
251       /* An elemental subroutine call with array valued arguments has
252          to be scalarized.  */
253       gfc_loopinfo loop;
254       stmtblock_t body;
255       stmtblock_t block;
256       gfc_se loopse;
257
258       /* gfc_walk_elemental_function_args renders the ss chain in the
259          reverse order to the actual argument order.  */
260       ss = gfc_reverse_ss (ss);
261
262       /* Initialize the loop.  */
263       gfc_init_se (&loopse, NULL);
264       gfc_init_loopinfo (&loop);
265       gfc_add_ss_to_loop (&loop, ss);
266
267       gfc_conv_ss_startstride (&loop);
268       gfc_conv_loop_setup (&loop);
269       gfc_mark_ss_chain_used (ss, 1);
270
271       /* Generate the loop body.  */
272       gfc_start_scalarized_body (&loop, &body);
273       gfc_init_block (&block);
274       gfc_copy_loopinfo_to_se (&loopse, &loop);
275       loopse.ss = ss;
276
277       /* Add the subroutine call to the block.  */
278       gfc_conv_function_call (&loopse, code->resolved_sym, code->ext.actual);
279       gfc_add_expr_to_block (&loopse.pre, loopse.expr);
280
281       gfc_add_block_to_block (&block, &loopse.pre);
282       gfc_add_block_to_block (&block, &loopse.post);
283
284       /* Finish up the loop block and the loop.  */
285       gfc_add_expr_to_block (&body, gfc_finish_block (&block));
286       gfc_trans_scalarizing_loops (&loop, &body);
287       gfc_add_block_to_block (&se.pre, &loop.pre);
288       gfc_add_block_to_block (&se.pre, &loop.post);
289       gfc_cleanup_loop (&loop);
290     }
291
292   return gfc_finish_block (&se.pre);
293 }
294
295
296 /* Translate the RETURN statement.  */
297
298 tree
299 gfc_trans_return (gfc_code * code ATTRIBUTE_UNUSED)
300 {
301   if (code->expr)
302     {
303       gfc_se se;
304       tree tmp;
305       tree result;
306
307       /* if code->expr is not NULL, this return statement must appear
308          in a subroutine and current_fake_result_decl has already
309          been generated.  */
310
311       result = gfc_get_fake_result_decl (NULL);
312       if (!result)
313         {
314           gfc_warning ("An alternate return at %L without a * dummy argument",
315                         &code->expr->where);
316           return build1_v (GOTO_EXPR, gfc_get_return_label ());
317         }
318
319       /* Start a new block for this statement.  */
320       gfc_init_se (&se, NULL);
321       gfc_start_block (&se.pre);
322
323       gfc_conv_expr (&se, code->expr);
324
325       tmp = build2 (MODIFY_EXPR, TREE_TYPE (result), result, se.expr);
326       gfc_add_expr_to_block (&se.pre, tmp);
327
328       tmp = build1_v (GOTO_EXPR, gfc_get_return_label ());
329       gfc_add_expr_to_block (&se.pre, tmp);
330       gfc_add_block_to_block (&se.pre, &se.post);
331       return gfc_finish_block (&se.pre);
332     }
333   else
334     return build1_v (GOTO_EXPR, gfc_get_return_label ());
335 }
336
337
338 /* Translate the PAUSE statement.  We have to translate this statement
339    to a runtime library call.  */
340
341 tree
342 gfc_trans_pause (gfc_code * code)
343 {
344   tree gfc_int4_type_node = gfc_get_int_type (4);
345   gfc_se se;
346   tree args;
347   tree tmp;
348   tree fndecl;
349
350   /* Start a new block for this statement.  */
351   gfc_init_se (&se, NULL);
352   gfc_start_block (&se.pre);
353
354
355   if (code->expr == NULL)
356     {
357       tmp = build_int_cst (gfc_int4_type_node, code->ext.stop_code);
358       args = gfc_chainon_list (NULL_TREE, tmp);
359       fndecl = gfor_fndecl_pause_numeric;
360     }
361   else
362     {
363       gfc_conv_expr_reference (&se, code->expr);
364       args = gfc_chainon_list (NULL_TREE, se.expr);
365       args = gfc_chainon_list (args, se.string_length);
366       fndecl = gfor_fndecl_pause_string;
367     }
368
369   tmp = build_function_call_expr (fndecl, args);
370   gfc_add_expr_to_block (&se.pre, tmp);
371
372   gfc_add_block_to_block (&se.pre, &se.post);
373
374   return gfc_finish_block (&se.pre);
375 }
376
377
378 /* Translate the STOP statement.  We have to translate this statement
379    to a runtime library call.  */
380
381 tree
382 gfc_trans_stop (gfc_code * code)
383 {
384   tree gfc_int4_type_node = gfc_get_int_type (4);
385   gfc_se se;
386   tree args;
387   tree tmp;
388   tree fndecl;
389
390   /* Start a new block for this statement.  */
391   gfc_init_se (&se, NULL);
392   gfc_start_block (&se.pre);
393
394
395   if (code->expr == NULL)
396     {
397       tmp = build_int_cst (gfc_int4_type_node, code->ext.stop_code);
398       args = gfc_chainon_list (NULL_TREE, tmp);
399       fndecl = gfor_fndecl_stop_numeric;
400     }
401   else
402     {
403       gfc_conv_expr_reference (&se, code->expr);
404       args = gfc_chainon_list (NULL_TREE, se.expr);
405       args = gfc_chainon_list (args, se.string_length);
406       fndecl = gfor_fndecl_stop_string;
407     }
408
409   tmp = build_function_call_expr (fndecl, args);
410   gfc_add_expr_to_block (&se.pre, tmp);
411
412   gfc_add_block_to_block (&se.pre, &se.post);
413
414   return gfc_finish_block (&se.pre);
415 }
416
417
418 /* Generate GENERIC for the IF construct. This function also deals with
419    the simple IF statement, because the front end translates the IF
420    statement into an IF construct.
421
422    We translate:
423
424         IF (cond) THEN
425            then_clause
426         ELSEIF (cond2)
427            elseif_clause
428         ELSE
429            else_clause
430         ENDIF
431
432    into:
433
434         pre_cond_s;
435         if (cond_s)
436           {
437             then_clause;
438           }
439         else
440           {
441             pre_cond_s
442             if (cond_s)
443               {
444                 elseif_clause
445               }
446             else
447               {
448                 else_clause;
449               }
450           }
451
452    where COND_S is the simplified version of the predicate. PRE_COND_S
453    are the pre side-effects produced by the translation of the
454    conditional.
455    We need to build the chain recursively otherwise we run into
456    problems with folding incomplete statements.  */
457
458 static tree
459 gfc_trans_if_1 (gfc_code * code)
460 {
461   gfc_se if_se;
462   tree stmt, elsestmt;
463
464   /* Check for an unconditional ELSE clause.  */
465   if (!code->expr)
466     return gfc_trans_code (code->next);
467
468   /* Initialize a statement builder for each block. Puts in NULL_TREEs.  */
469   gfc_init_se (&if_se, NULL);
470   gfc_start_block (&if_se.pre);
471
472   /* Calculate the IF condition expression.  */
473   gfc_conv_expr_val (&if_se, code->expr);
474
475   /* Translate the THEN clause.  */
476   stmt = gfc_trans_code (code->next);
477
478   /* Translate the ELSE clause.  */
479   if (code->block)
480     elsestmt = gfc_trans_if_1 (code->block);
481   else
482     elsestmt = build_empty_stmt ();
483
484   /* Build the condition expression and add it to the condition block.  */
485   stmt = fold_build3 (COND_EXPR, void_type_node, if_se.expr, stmt, elsestmt);
486   
487   gfc_add_expr_to_block (&if_se.pre, stmt);
488
489   /* Finish off this statement.  */
490   return gfc_finish_block (&if_se.pre);
491 }
492
493 tree
494 gfc_trans_if (gfc_code * code)
495 {
496   /* Ignore the top EXEC_IF, it only announces an IF construct. The
497      actual code we must translate is in code->block.  */
498
499   return gfc_trans_if_1 (code->block);
500 }
501
502
503 /* Translage an arithmetic IF expression.
504
505    IF (cond) label1, label2, label3 translates to
506
507     if (cond <= 0)
508       {
509         if (cond < 0)
510           goto label1;
511         else // cond == 0
512           goto label2;
513       }
514     else // cond > 0
515       goto label3;
516
517    An optimized version can be generated in case of equal labels.
518    E.g., if label1 is equal to label2, we can translate it to
519
520     if (cond <= 0)
521       goto label1;
522     else
523       goto label3;
524 */
525
526 tree
527 gfc_trans_arithmetic_if (gfc_code * code)
528 {
529   gfc_se se;
530   tree tmp;
531   tree branch1;
532   tree branch2;
533   tree zero;
534
535   /* Start a new block.  */
536   gfc_init_se (&se, NULL);
537   gfc_start_block (&se.pre);
538
539   /* Pre-evaluate COND.  */
540   gfc_conv_expr_val (&se, code->expr);
541
542   /* Build something to compare with.  */
543   zero = gfc_build_const (TREE_TYPE (se.expr), integer_zero_node);
544
545   if (code->label->value != code->label2->value)
546     {
547       /* If (cond < 0) take branch1 else take branch2.
548          First build jumps to the COND .LT. 0 and the COND .EQ. 0 cases.  */
549       branch1 = build1_v (GOTO_EXPR, gfc_get_label_decl (code->label));
550       branch2 = build1_v (GOTO_EXPR, gfc_get_label_decl (code->label2));
551
552       if (code->label->value != code->label3->value)
553         tmp = fold_build2 (LT_EXPR, boolean_type_node, se.expr, zero);
554       else
555         tmp = fold_build2 (NE_EXPR, boolean_type_node, se.expr, zero);
556
557       branch1 = fold_build3 (COND_EXPR, void_type_node, tmp, branch1, branch2);
558     }
559   else
560     branch1 = build1_v (GOTO_EXPR, gfc_get_label_decl (code->label));
561
562   if (code->label->value != code->label3->value
563       && code->label2->value != code->label3->value)
564     {
565       /* if (cond <= 0) take branch1 else take branch2.  */
566       branch2 = build1_v (GOTO_EXPR, gfc_get_label_decl (code->label3));
567       tmp = fold_build2 (LE_EXPR, boolean_type_node, se.expr, zero);
568       branch1 = fold_build3 (COND_EXPR, void_type_node, tmp, branch1, branch2);
569     }
570
571   /* Append the COND_EXPR to the evaluation of COND, and return.  */
572   gfc_add_expr_to_block (&se.pre, branch1);
573   return gfc_finish_block (&se.pre);
574 }
575
576
577 /* Translate the simple DO construct.  This is where the loop variable has
578    integer type and step +-1.  We can't use this in the general case
579    because integer overflow and floating point errors could give incorrect
580    results.
581    We translate a do loop from:
582
583    DO dovar = from, to, step
584       body
585    END DO
586
587    to:
588
589    [Evaluate loop bounds and step]
590    dovar = from;
591    if ((step > 0) ? (dovar <= to) : (dovar => to))
592     {
593       for (;;)
594         {
595           body;
596    cycle_label:
597           cond = (dovar == to);
598           dovar += step;
599           if (cond) goto end_label;
600         }
601       }
602    end_label:
603
604    This helps the optimizers by avoiding the extra induction variable
605    used in the general case.  */
606
607 static tree
608 gfc_trans_simple_do (gfc_code * code, stmtblock_t *pblock, tree dovar,
609                      tree from, tree to, tree step)
610 {
611   stmtblock_t body;
612   tree type;
613   tree cond;
614   tree tmp;
615   tree cycle_label;
616   tree exit_label;
617   
618   type = TREE_TYPE (dovar);
619
620   /* Initialize the DO variable: dovar = from.  */
621   gfc_add_modify_expr (pblock, dovar, from);
622
623   /* Cycle and exit statements are implemented with gotos.  */
624   cycle_label = gfc_build_label_decl (NULL_TREE);
625   exit_label = gfc_build_label_decl (NULL_TREE);
626
627   /* Put the labels where they can be found later. See gfc_trans_do().  */
628   code->block->backend_decl = tree_cons (cycle_label, exit_label, NULL);
629
630   /* Loop body.  */
631   gfc_start_block (&body);
632
633   /* Main loop body.  */
634   tmp = gfc_trans_code (code->block->next);
635   gfc_add_expr_to_block (&body, tmp);
636
637   /* Label for cycle statements (if needed).  */
638   if (TREE_USED (cycle_label))
639     {
640       tmp = build1_v (LABEL_EXPR, cycle_label);
641       gfc_add_expr_to_block (&body, tmp);
642     }
643
644   /* Evaluate the loop condition.  */
645   cond = fold_build2 (EQ_EXPR, boolean_type_node, dovar, to);
646   cond = gfc_evaluate_now (cond, &body);
647
648   /* Increment the loop variable.  */
649   tmp = fold_build2 (PLUS_EXPR, type, dovar, step);
650   gfc_add_modify_expr (&body, dovar, tmp);
651
652   /* The loop exit.  */
653   tmp = build1_v (GOTO_EXPR, exit_label);
654   TREE_USED (exit_label) = 1;
655   tmp = fold_build3 (COND_EXPR, void_type_node,
656                      cond, tmp, build_empty_stmt ());
657   gfc_add_expr_to_block (&body, tmp);
658
659   /* Finish the loop body.  */
660   tmp = gfc_finish_block (&body);
661   tmp = build1_v (LOOP_EXPR, tmp);
662
663   /* Only execute the loop if the number of iterations is positive.  */
664   if (tree_int_cst_sgn (step) > 0)
665     cond = fold_build2 (LE_EXPR, boolean_type_node, dovar, to);
666   else
667     cond = fold_build2 (GE_EXPR, boolean_type_node, dovar, to);
668   tmp = fold_build3 (COND_EXPR, void_type_node,
669                      cond, tmp, build_empty_stmt ());
670   gfc_add_expr_to_block (pblock, tmp);
671
672   /* Add the exit label.  */
673   tmp = build1_v (LABEL_EXPR, exit_label);
674   gfc_add_expr_to_block (pblock, tmp);
675
676   return gfc_finish_block (pblock);
677 }
678
679 /* Translate the DO construct.  This obviously is one of the most
680    important ones to get right with any compiler, but especially
681    so for Fortran.
682
683    We special case some loop forms as described in gfc_trans_simple_do.
684    For other cases we implement them with a separate loop count,
685    as described in the standard.
686
687    We translate a do loop from:
688
689    DO dovar = from, to, step
690       body
691    END DO
692
693    to:
694
695    [evaluate loop bounds and step]
696    count = (to + step - from) / step;
697    dovar = from;
698    for (;;)
699      {
700        body;
701 cycle_label:
702        dovar += step
703        count--;
704        if (count <=0) goto exit_label;
705      }
706 exit_label:
707
708    TODO: Large loop counts
709    The code above assumes the loop count fits into a signed integer kind,
710    i.e. Does not work for loop counts > 2^31 for integer(kind=4) variables
711    We must support the full range.  */
712
713 tree
714 gfc_trans_do (gfc_code * code)
715 {
716   gfc_se se;
717   tree dovar;
718   tree from;
719   tree to;
720   tree step;
721   tree count;
722   tree count_one;
723   tree type;
724   tree cond;
725   tree cycle_label;
726   tree exit_label;
727   tree tmp;
728   stmtblock_t block;
729   stmtblock_t body;
730
731   gfc_start_block (&block);
732
733   /* Evaluate all the expressions in the iterator.  */
734   gfc_init_se (&se, NULL);
735   gfc_conv_expr_lhs (&se, code->ext.iterator->var);
736   gfc_add_block_to_block (&block, &se.pre);
737   dovar = se.expr;
738   type = TREE_TYPE (dovar);
739
740   gfc_init_se (&se, NULL);
741   gfc_conv_expr_val (&se, code->ext.iterator->start);
742   gfc_add_block_to_block (&block, &se.pre);
743   from = gfc_evaluate_now (se.expr, &block);
744
745   gfc_init_se (&se, NULL);
746   gfc_conv_expr_val (&se, code->ext.iterator->end);
747   gfc_add_block_to_block (&block, &se.pre);
748   to = gfc_evaluate_now (se.expr, &block);
749
750   gfc_init_se (&se, NULL);
751   gfc_conv_expr_val (&se, code->ext.iterator->step);
752   gfc_add_block_to_block (&block, &se.pre);
753   step = gfc_evaluate_now (se.expr, &block);
754
755   /* Special case simple loops.  */
756   if (TREE_CODE (type) == INTEGER_TYPE
757       && (integer_onep (step)
758         || tree_int_cst_equal (step, integer_minus_one_node)))
759     return gfc_trans_simple_do (code, &block, dovar, from, to, step);
760       
761   /* Initialize loop count. This code is executed before we enter the
762      loop body. We generate: count = (to + step - from) / step.  */
763
764   tmp = fold_build2 (MINUS_EXPR, type, step, from);
765   tmp = fold_build2 (PLUS_EXPR, type, to, tmp);
766   if (TREE_CODE (type) == INTEGER_TYPE)
767     {
768       tmp = fold_build2 (TRUNC_DIV_EXPR, type, tmp, step);
769       count = gfc_create_var (type, "count");
770     }
771   else
772     {
773       /* TODO: We could use the same width as the real type.
774          This would probably cause more problems that it solves
775          when we implement "long double" types.  */
776       tmp = fold_build2 (RDIV_EXPR, type, tmp, step);
777       tmp = fold_build1 (FIX_TRUNC_EXPR, gfc_array_index_type, tmp);
778       count = gfc_create_var (gfc_array_index_type, "count");
779     }
780   gfc_add_modify_expr (&block, count, tmp);
781
782   count_one = convert (TREE_TYPE (count), integer_one_node);
783
784   /* Initialize the DO variable: dovar = from.  */
785   gfc_add_modify_expr (&block, dovar, from);
786
787   /* Loop body.  */
788   gfc_start_block (&body);
789
790   /* Cycle and exit statements are implemented with gotos.  */
791   cycle_label = gfc_build_label_decl (NULL_TREE);
792   exit_label = gfc_build_label_decl (NULL_TREE);
793
794   /* Start with the loop condition.  Loop until count <= 0.  */
795   cond = fold_build2 (LE_EXPR, boolean_type_node, count,
796                       build_int_cst (TREE_TYPE (count), 0));
797   tmp = build1_v (GOTO_EXPR, exit_label);
798   TREE_USED (exit_label) = 1;
799   tmp = fold_build3 (COND_EXPR, void_type_node,
800                      cond, tmp, build_empty_stmt ());
801   gfc_add_expr_to_block (&body, tmp);
802
803   /* Put these labels where they can be found later. We put the
804      labels in a TREE_LIST node (because TREE_CHAIN is already
805      used). cycle_label goes in TREE_PURPOSE (backend_decl), exit
806      label in TREE_VALUE (backend_decl).  */
807
808   code->block->backend_decl = tree_cons (cycle_label, exit_label, NULL);
809
810   /* Main loop body.  */
811   tmp = gfc_trans_code (code->block->next);
812   gfc_add_expr_to_block (&body, tmp);
813
814   /* Label for cycle statements (if needed).  */
815   if (TREE_USED (cycle_label))
816     {
817       tmp = build1_v (LABEL_EXPR, cycle_label);
818       gfc_add_expr_to_block (&body, tmp);
819     }
820
821   /* Increment the loop variable.  */
822   tmp = build2 (PLUS_EXPR, type, dovar, step);
823   gfc_add_modify_expr (&body, dovar, tmp);
824
825   /* Decrement the loop count.  */
826   tmp = build2 (MINUS_EXPR, TREE_TYPE (count), count, count_one);
827   gfc_add_modify_expr (&body, count, tmp);
828
829   /* End of loop body.  */
830   tmp = gfc_finish_block (&body);
831
832   /* The for loop itself.  */
833   tmp = build1_v (LOOP_EXPR, tmp);
834   gfc_add_expr_to_block (&block, tmp);
835
836   /* Add the exit label.  */
837   tmp = build1_v (LABEL_EXPR, exit_label);
838   gfc_add_expr_to_block (&block, tmp);
839
840   return gfc_finish_block (&block);
841 }
842
843
844 /* Translate the DO WHILE construct.
845
846    We translate
847
848    DO WHILE (cond)
849       body
850    END DO
851
852    to:
853
854    for ( ; ; )
855      {
856        pre_cond;
857        if (! cond) goto exit_label;
858        body;
859 cycle_label:
860      }
861 exit_label:
862
863    Because the evaluation of the exit condition `cond' may have side
864    effects, we can't do much for empty loop bodies.  The backend optimizers
865    should be smart enough to eliminate any dead loops.  */
866
867 tree
868 gfc_trans_do_while (gfc_code * code)
869 {
870   gfc_se cond;
871   tree tmp;
872   tree cycle_label;
873   tree exit_label;
874   stmtblock_t block;
875
876   /* Everything we build here is part of the loop body.  */
877   gfc_start_block (&block);
878
879   /* Cycle and exit statements are implemented with gotos.  */
880   cycle_label = gfc_build_label_decl (NULL_TREE);
881   exit_label = gfc_build_label_decl (NULL_TREE);
882
883   /* Put the labels where they can be found later. See gfc_trans_do().  */
884   code->block->backend_decl = tree_cons (cycle_label, exit_label, NULL);
885
886   /* Create a GIMPLE version of the exit condition.  */
887   gfc_init_se (&cond, NULL);
888   gfc_conv_expr_val (&cond, code->expr);
889   gfc_add_block_to_block (&block, &cond.pre);
890   cond.expr = fold_build1 (TRUTH_NOT_EXPR, boolean_type_node, cond.expr);
891
892   /* Build "IF (! cond) GOTO exit_label".  */
893   tmp = build1_v (GOTO_EXPR, exit_label);
894   TREE_USED (exit_label) = 1;
895   tmp = fold_build3 (COND_EXPR, void_type_node,
896                      cond.expr, tmp, build_empty_stmt ());
897   gfc_add_expr_to_block (&block, tmp);
898
899   /* The main body of the loop.  */
900   tmp = gfc_trans_code (code->block->next);
901   gfc_add_expr_to_block (&block, tmp);
902
903   /* Label for cycle statements (if needed).  */
904   if (TREE_USED (cycle_label))
905     {
906       tmp = build1_v (LABEL_EXPR, cycle_label);
907       gfc_add_expr_to_block (&block, tmp);
908     }
909
910   /* End of loop body.  */
911   tmp = gfc_finish_block (&block);
912
913   gfc_init_block (&block);
914   /* Build the loop.  */
915   tmp = build1_v (LOOP_EXPR, tmp);
916   gfc_add_expr_to_block (&block, tmp);
917
918   /* Add the exit label.  */
919   tmp = build1_v (LABEL_EXPR, exit_label);
920   gfc_add_expr_to_block (&block, tmp);
921
922   return gfc_finish_block (&block);
923 }
924
925
926 /* Translate the SELECT CASE construct for INTEGER case expressions,
927    without killing all potential optimizations.  The problem is that
928    Fortran allows unbounded cases, but the back-end does not, so we
929    need to intercept those before we enter the equivalent SWITCH_EXPR
930    we can build.
931
932    For example, we translate this,
933
934    SELECT CASE (expr)
935       CASE (:100,101,105:115)
936          block_1
937       CASE (190:199,200:)
938          block_2
939       CASE (300)
940          block_3
941       CASE DEFAULT
942          block_4
943    END SELECT
944
945    to the GENERIC equivalent,
946
947      switch (expr)
948        {
949          case (minimum value for typeof(expr) ... 100:
950          case 101:
951          case 105 ... 114:
952            block1:
953            goto end_label;
954
955          case 200 ... (maximum value for typeof(expr):
956          case 190 ... 199:
957            block2;
958            goto end_label;
959
960          case 300:
961            block_3;
962            goto end_label;
963
964          default:
965            block_4;
966            goto end_label;
967        }
968
969      end_label:  */
970
971 static tree
972 gfc_trans_integer_select (gfc_code * code)
973 {
974   gfc_code *c;
975   gfc_case *cp;
976   tree end_label;
977   tree tmp;
978   gfc_se se;
979   stmtblock_t block;
980   stmtblock_t body;
981
982   gfc_start_block (&block);
983
984   /* Calculate the switch expression.  */
985   gfc_init_se (&se, NULL);
986   gfc_conv_expr_val (&se, code->expr);
987   gfc_add_block_to_block (&block, &se.pre);
988
989   end_label = gfc_build_label_decl (NULL_TREE);
990
991   gfc_init_block (&body);
992
993   for (c = code->block; c; c = c->block)
994     {
995       for (cp = c->ext.case_list; cp; cp = cp->next)
996         {
997           tree low, high;
998           tree label;
999
1000           /* Assume it's the default case.  */
1001           low = high = NULL_TREE;
1002
1003           if (cp->low)
1004             {
1005               low = gfc_conv_constant_to_tree (cp->low);
1006
1007               /* If there's only a lower bound, set the high bound to the
1008                  maximum value of the case expression.  */
1009               if (!cp->high)
1010                 high = TYPE_MAX_VALUE (TREE_TYPE (se.expr));
1011             }
1012
1013           if (cp->high)
1014             {
1015               /* Three cases are possible here:
1016
1017                  1) There is no lower bound, e.g. CASE (:N).
1018                  2) There is a lower bound .NE. high bound, that is
1019                     a case range, e.g. CASE (N:M) where M>N (we make
1020                     sure that M>N during type resolution).
1021                  3) There is a lower bound, and it has the same value
1022                     as the high bound, e.g. CASE (N:N).  This is our
1023                     internal representation of CASE(N).
1024
1025                  In the first and second case, we need to set a value for
1026                  high.  In the thirth case, we don't because the GCC middle
1027                  end represents a single case value by just letting high be
1028                  a NULL_TREE.  We can't do that because we need to be able
1029                  to represent unbounded cases.  */
1030
1031               if (!cp->low
1032                   || (cp->low
1033                       && mpz_cmp (cp->low->value.integer,
1034                                   cp->high->value.integer) != 0))
1035                 high = gfc_conv_constant_to_tree (cp->high);
1036
1037               /* Unbounded case.  */
1038               if (!cp->low)
1039                 low = TYPE_MIN_VALUE (TREE_TYPE (se.expr));
1040             }
1041
1042           /* Build a label.  */
1043           label = gfc_build_label_decl (NULL_TREE);
1044
1045           /* Add this case label.
1046              Add parameter 'label', make it match GCC backend.  */
1047           tmp = build3 (CASE_LABEL_EXPR, void_type_node, low, high, label);
1048           gfc_add_expr_to_block (&body, tmp);
1049         }
1050
1051       /* Add the statements for this case.  */
1052       tmp = gfc_trans_code (c->next);
1053       gfc_add_expr_to_block (&body, tmp);
1054
1055       /* Break to the end of the construct.  */
1056       tmp = build1_v (GOTO_EXPR, end_label);
1057       gfc_add_expr_to_block (&body, tmp);
1058     }
1059
1060   tmp = gfc_finish_block (&body);
1061   tmp = build3_v (SWITCH_EXPR, se.expr, tmp, NULL_TREE);
1062   gfc_add_expr_to_block (&block, tmp);
1063
1064   tmp = build1_v (LABEL_EXPR, end_label);
1065   gfc_add_expr_to_block (&block, tmp);
1066
1067   return gfc_finish_block (&block);
1068 }
1069
1070
1071 /* Translate the SELECT CASE construct for LOGICAL case expressions.
1072
1073    There are only two cases possible here, even though the standard
1074    does allow three cases in a LOGICAL SELECT CASE construct: .TRUE.,
1075    .FALSE., and DEFAULT.
1076
1077    We never generate more than two blocks here.  Instead, we always
1078    try to eliminate the DEFAULT case.  This way, we can translate this
1079    kind of SELECT construct to a simple
1080
1081    if {} else {};
1082
1083    expression in GENERIC.  */
1084
1085 static tree
1086 gfc_trans_logical_select (gfc_code * code)
1087 {
1088   gfc_code *c;
1089   gfc_code *t, *f, *d;
1090   gfc_case *cp;
1091   gfc_se se;
1092   stmtblock_t block;
1093
1094   /* Assume we don't have any cases at all.  */
1095   t = f = d = NULL;
1096
1097   /* Now see which ones we actually do have.  We can have at most two
1098      cases in a single case list: one for .TRUE. and one for .FALSE.
1099      The default case is always separate.  If the cases for .TRUE. and
1100      .FALSE. are in the same case list, the block for that case list
1101      always executed, and we don't generate code a COND_EXPR.  */
1102   for (c = code->block; c; c = c->block)
1103     {
1104       for (cp = c->ext.case_list; cp; cp = cp->next)
1105         {
1106           if (cp->low)
1107             {
1108               if (cp->low->value.logical == 0) /* .FALSE.  */
1109                 f = c;
1110               else /* if (cp->value.logical != 0), thus .TRUE.  */
1111                 t = c;
1112             }
1113           else
1114             d = c;
1115         }
1116     }
1117
1118   /* Start a new block.  */
1119   gfc_start_block (&block);
1120
1121   /* Calculate the switch expression.  We always need to do this
1122      because it may have side effects.  */
1123   gfc_init_se (&se, NULL);
1124   gfc_conv_expr_val (&se, code->expr);
1125   gfc_add_block_to_block (&block, &se.pre);
1126
1127   if (t == f && t != NULL)
1128     {
1129       /* Cases for .TRUE. and .FALSE. are in the same block.  Just
1130          translate the code for these cases, append it to the current
1131          block.  */
1132       gfc_add_expr_to_block (&block, gfc_trans_code (t->next));
1133     }
1134   else
1135     {
1136       tree true_tree, false_tree, stmt;
1137
1138       true_tree = build_empty_stmt ();
1139       false_tree = build_empty_stmt ();
1140
1141       /* If we have a case for .TRUE. and for .FALSE., discard the default case.
1142           Otherwise, if .TRUE. or .FALSE. is missing and there is a default case,
1143           make the missing case the default case.  */
1144       if (t != NULL && f != NULL)
1145         d = NULL;
1146       else if (d != NULL)
1147         {
1148           if (t == NULL)
1149             t = d;
1150           else
1151             f = d;
1152         }
1153
1154       /* Translate the code for each of these blocks, and append it to
1155          the current block.  */
1156       if (t != NULL)
1157         true_tree = gfc_trans_code (t->next);
1158
1159       if (f != NULL)
1160         false_tree = gfc_trans_code (f->next);
1161
1162       stmt = fold_build3 (COND_EXPR, void_type_node, se.expr,
1163                           true_tree, false_tree);
1164       gfc_add_expr_to_block (&block, stmt);
1165     }
1166
1167   return gfc_finish_block (&block);
1168 }
1169
1170
1171 /* Translate the SELECT CASE construct for CHARACTER case expressions.
1172    Instead of generating compares and jumps, it is far simpler to
1173    generate a data structure describing the cases in order and call a
1174    library subroutine that locates the right case.
1175    This is particularly true because this is the only case where we
1176    might have to dispose of a temporary.
1177    The library subroutine returns a pointer to jump to or NULL if no
1178    branches are to be taken.  */
1179
1180 static tree
1181 gfc_trans_character_select (gfc_code *code)
1182 {
1183   tree init, node, end_label, tmp, type, args, *labels;
1184   stmtblock_t block, body;
1185   gfc_case *cp, *d;
1186   gfc_code *c;
1187   gfc_se se;
1188   int i, n;
1189
1190   static tree select_struct;
1191   static tree ss_string1, ss_string1_len;
1192   static tree ss_string2, ss_string2_len;
1193   static tree ss_target;
1194
1195   if (select_struct == NULL)
1196     {
1197       tree gfc_int4_type_node = gfc_get_int_type (4);
1198
1199       select_struct = make_node (RECORD_TYPE);
1200       TYPE_NAME (select_struct) = get_identifier ("_jump_struct");
1201
1202 #undef ADD_FIELD
1203 #define ADD_FIELD(NAME, TYPE)                           \
1204   ss_##NAME = gfc_add_field_to_struct                   \
1205      (&(TYPE_FIELDS (select_struct)), select_struct,    \
1206       get_identifier (stringize(NAME)), TYPE)
1207
1208       ADD_FIELD (string1, pchar_type_node);
1209       ADD_FIELD (string1_len, gfc_int4_type_node);
1210
1211       ADD_FIELD (string2, pchar_type_node);
1212       ADD_FIELD (string2_len, gfc_int4_type_node);
1213
1214       ADD_FIELD (target, pvoid_type_node);
1215 #undef ADD_FIELD
1216
1217       gfc_finish_type (select_struct);
1218     }
1219
1220   cp = code->block->ext.case_list;
1221   while (cp->left != NULL)
1222     cp = cp->left;
1223
1224   n = 0;
1225   for (d = cp; d; d = d->right)
1226     d->n = n++;
1227
1228   if (n != 0)
1229     labels = gfc_getmem (n * sizeof (tree));
1230   else
1231     labels = NULL;
1232
1233   for(i = 0; i < n; i++)
1234     {
1235       labels[i] = gfc_build_label_decl (NULL_TREE);
1236       TREE_USED (labels[i]) = 1;
1237       /* TODO: The gimplifier should do this for us, but it has
1238          inadequacies when dealing with static initializers.  */
1239       FORCED_LABEL (labels[i]) = 1;
1240     }
1241
1242   end_label = gfc_build_label_decl (NULL_TREE);
1243
1244   /* Generate the body */
1245   gfc_start_block (&block);
1246   gfc_init_block (&body);
1247
1248   for (c = code->block; c; c = c->block)
1249     {
1250       for (d = c->ext.case_list; d; d = d->next)
1251         {
1252           tmp = build1_v (LABEL_EXPR, labels[d->n]);
1253           gfc_add_expr_to_block (&body, tmp);
1254         }
1255
1256       tmp = gfc_trans_code (c->next);
1257       gfc_add_expr_to_block (&body, tmp);
1258
1259       tmp = build1_v (GOTO_EXPR, end_label);
1260       gfc_add_expr_to_block (&body, tmp);
1261     }
1262
1263   /* Generate the structure describing the branches */
1264   init = NULL_TREE;
1265   i = 0;
1266
1267   for(d = cp; d; d = d->right, i++)
1268     {
1269       node = NULL_TREE;
1270
1271       gfc_init_se (&se, NULL);
1272
1273       if (d->low == NULL)
1274         {
1275           node = tree_cons (ss_string1, null_pointer_node, node);
1276           node = tree_cons (ss_string1_len, integer_zero_node, node);
1277         }
1278       else
1279         {
1280           gfc_conv_expr_reference (&se, d->low);
1281
1282           node = tree_cons (ss_string1, se.expr, node);
1283           node = tree_cons (ss_string1_len, se.string_length, node);
1284         }
1285
1286       if (d->high == NULL)
1287         {
1288           node = tree_cons (ss_string2, null_pointer_node, node);
1289           node = tree_cons (ss_string2_len, integer_zero_node, node);
1290         }
1291       else
1292         {
1293           gfc_init_se (&se, NULL);
1294           gfc_conv_expr_reference (&se, d->high);
1295
1296           node = tree_cons (ss_string2, se.expr, node);
1297           node = tree_cons (ss_string2_len, se.string_length, node);
1298         }
1299
1300       tmp = gfc_build_addr_expr (pvoid_type_node, labels[i]);
1301       node = tree_cons (ss_target, tmp, node);
1302
1303       tmp = build_constructor_from_list (select_struct, nreverse (node));
1304       init = tree_cons (NULL_TREE, tmp, init);
1305     }
1306
1307   type = build_array_type (select_struct, build_index_type
1308                            (build_int_cst (NULL_TREE, n - 1)));
1309
1310   init = build_constructor_from_list (type, nreverse(init));
1311   TREE_CONSTANT (init) = 1;
1312   TREE_INVARIANT (init) = 1;
1313   TREE_STATIC (init) = 1;
1314   /* Create a static variable to hold the jump table.  */
1315   tmp = gfc_create_var (type, "jumptable");
1316   TREE_CONSTANT (tmp) = 1;
1317   TREE_INVARIANT (tmp) = 1;
1318   TREE_STATIC (tmp) = 1;
1319   DECL_INITIAL (tmp) = init;
1320   init = tmp;
1321
1322   /* Build an argument list for the library call */
1323   init = gfc_build_addr_expr (pvoid_type_node, init);
1324   args = gfc_chainon_list (NULL_TREE, init);
1325
1326   tmp = build_int_cst (NULL_TREE, n);
1327   args = gfc_chainon_list (args, tmp);
1328
1329   tmp = gfc_build_addr_expr (pvoid_type_node, end_label);
1330   args = gfc_chainon_list (args, tmp);
1331
1332   gfc_init_se (&se, NULL);
1333   gfc_conv_expr_reference (&se, code->expr);
1334
1335   args = gfc_chainon_list (args, se.expr);
1336   args = gfc_chainon_list (args, se.string_length);
1337
1338   gfc_add_block_to_block (&block, &se.pre);
1339
1340   tmp = build_function_call_expr (gfor_fndecl_select_string, args);
1341   tmp = build1 (GOTO_EXPR, void_type_node, tmp);
1342   gfc_add_expr_to_block (&block, tmp);
1343
1344   tmp = gfc_finish_block (&body);
1345   gfc_add_expr_to_block (&block, tmp);
1346   tmp = build1_v (LABEL_EXPR, end_label);
1347   gfc_add_expr_to_block (&block, tmp);
1348
1349   if (n != 0)
1350     gfc_free (labels);
1351
1352   return gfc_finish_block (&block);
1353 }
1354
1355
1356 /* Translate the three variants of the SELECT CASE construct.
1357
1358    SELECT CASEs with INTEGER case expressions can be translated to an
1359    equivalent GENERIC switch statement, and for LOGICAL case
1360    expressions we build one or two if-else compares.
1361
1362    SELECT CASEs with CHARACTER case expressions are a whole different
1363    story, because they don't exist in GENERIC.  So we sort them and
1364    do a binary search at runtime.
1365
1366    Fortran has no BREAK statement, and it does not allow jumps from
1367    one case block to another.  That makes things a lot easier for
1368    the optimizers.  */
1369
1370 tree
1371 gfc_trans_select (gfc_code * code)
1372 {
1373   gcc_assert (code && code->expr);
1374
1375   /* Empty SELECT constructs are legal.  */
1376   if (code->block == NULL)
1377     return build_empty_stmt ();
1378
1379   /* Select the correct translation function.  */
1380   switch (code->expr->ts.type)
1381     {
1382     case BT_LOGICAL:    return gfc_trans_logical_select (code);
1383     case BT_INTEGER:    return gfc_trans_integer_select (code);
1384     case BT_CHARACTER:  return gfc_trans_character_select (code);
1385     default:
1386       gfc_internal_error ("gfc_trans_select(): Bad type for case expr.");
1387       /* Not reached */
1388     }
1389 }
1390
1391
1392 /* Generate the loops for a FORALL block.  The normal loop format:
1393     count = (end - start + step) / step
1394     loopvar = start
1395     while (1)
1396       {
1397         if (count <=0 )
1398           goto end_of_loop
1399         <body>
1400         loopvar += step
1401         count --
1402       }
1403     end_of_loop:  */
1404
1405 static tree
1406 gfc_trans_forall_loop (forall_info *forall_tmp, int nvar, tree body, int mask_flag)
1407 {
1408   int n;
1409   tree tmp;
1410   tree cond;
1411   stmtblock_t block;
1412   tree exit_label;
1413   tree count;
1414   tree var, start, end, step;
1415   iter_info *iter;
1416
1417   iter = forall_tmp->this_loop;
1418   for (n = 0; n < nvar; n++)
1419     {
1420       var = iter->var;
1421       start = iter->start;
1422       end = iter->end;
1423       step = iter->step;
1424
1425       exit_label = gfc_build_label_decl (NULL_TREE);
1426       TREE_USED (exit_label) = 1;
1427
1428       /* The loop counter.  */
1429       count = gfc_create_var (TREE_TYPE (var), "count");
1430
1431       /* The body of the loop.  */
1432       gfc_init_block (&block);
1433
1434       /* The exit condition.  */
1435       cond = fold_build2 (LE_EXPR, boolean_type_node,
1436                           count, build_int_cst (TREE_TYPE (count), 0));
1437       tmp = build1_v (GOTO_EXPR, exit_label);
1438       tmp = fold_build3 (COND_EXPR, void_type_node,
1439                          cond, tmp, build_empty_stmt ());
1440       gfc_add_expr_to_block (&block, tmp);
1441
1442       /* The main loop body.  */
1443       gfc_add_expr_to_block (&block, body);
1444
1445       /* Increment the loop variable.  */
1446       tmp = build2 (PLUS_EXPR, TREE_TYPE (var), var, step);
1447       gfc_add_modify_expr (&block, var, tmp);
1448
1449       /* Advance to the next mask element.  Only do this for the
1450          innermost loop.  */
1451       if (n == 0 && mask_flag && forall_tmp->mask)
1452         {
1453           tree maskindex = forall_tmp->maskindex;
1454           tmp = build2 (PLUS_EXPR, gfc_array_index_type,
1455                         maskindex, gfc_index_one_node);
1456           gfc_add_modify_expr (&block, maskindex, tmp);
1457         }
1458
1459       /* Decrement the loop counter.  */
1460       tmp = build2 (MINUS_EXPR, TREE_TYPE (var), count, gfc_index_one_node);
1461       gfc_add_modify_expr (&block, count, tmp);
1462
1463       body = gfc_finish_block (&block);
1464
1465       /* Loop var initialization.  */
1466       gfc_init_block (&block);
1467       gfc_add_modify_expr (&block, var, start);
1468
1469       /* Initialize maskindex counter.  Only do this before the
1470          outermost loop.  */
1471       if (n == nvar - 1 && mask_flag && forall_tmp->mask)
1472         gfc_add_modify_expr (&block, forall_tmp->maskindex,
1473                              gfc_index_zero_node);
1474
1475       /* Initialize the loop counter.  */
1476       tmp = fold_build2 (MINUS_EXPR, TREE_TYPE (var), step, start);
1477       tmp = fold_build2 (PLUS_EXPR, TREE_TYPE (var), end, tmp);
1478       tmp = fold_build2 (TRUNC_DIV_EXPR, TREE_TYPE (var), tmp, step);
1479       gfc_add_modify_expr (&block, count, tmp);
1480
1481       /* The loop expression.  */
1482       tmp = build1_v (LOOP_EXPR, body);
1483       gfc_add_expr_to_block (&block, tmp);
1484
1485       /* The exit label.  */
1486       tmp = build1_v (LABEL_EXPR, exit_label);
1487       gfc_add_expr_to_block (&block, tmp);
1488
1489       body = gfc_finish_block (&block);
1490       iter = iter->next;
1491     }
1492   return body;
1493 }
1494
1495
1496 /* Generate the body and loops according to MASK_FLAG and NEST_FLAG.
1497    if MASK_FLAG is nonzero, the body is controlled by maskes in forall
1498    nest, otherwise, the body is not controlled by maskes.
1499    if NEST_FLAG is nonzero, generate loops for nested forall, otherwise,
1500    only generate loops for the current forall level.  */
1501
1502 static tree
1503 gfc_trans_nested_forall_loop (forall_info * nested_forall_info, tree body,
1504                               int mask_flag, int nest_flag)
1505 {
1506   tree tmp;
1507   int nvar;
1508   forall_info *forall_tmp;
1509   tree pmask, mask, maskindex;
1510
1511   forall_tmp = nested_forall_info;
1512   /* Generate loops for nested forall.  */
1513   if (nest_flag)
1514     {
1515       while (forall_tmp->next_nest != NULL)
1516         forall_tmp = forall_tmp->next_nest;
1517       while (forall_tmp != NULL)
1518         {
1519           /* Generate body with masks' control.  */
1520           if (mask_flag)
1521             {
1522               pmask = forall_tmp->pmask;
1523               mask = forall_tmp->mask;
1524               maskindex = forall_tmp->maskindex;
1525
1526               if (mask)
1527                 {
1528                   /* If a mask was specified make the assignment conditional.  */
1529                   if (pmask)
1530                     tmp = build_fold_indirect_ref (mask);
1531                   else
1532                     tmp = mask;
1533                   tmp = gfc_build_array_ref (tmp, maskindex);
1534
1535                   body = build3_v (COND_EXPR, tmp, body, build_empty_stmt ());
1536                 }
1537             }
1538           nvar = forall_tmp->nvar;
1539           body = gfc_trans_forall_loop (forall_tmp, nvar, body, mask_flag);
1540           forall_tmp = forall_tmp->outer;
1541         }
1542     }
1543   else
1544     {
1545       nvar = forall_tmp->nvar;
1546       body = gfc_trans_forall_loop (forall_tmp, nvar, body, mask_flag);
1547     }
1548
1549   return body;
1550 }
1551
1552
1553 /* Allocate data for holding a temporary array.  Returns either a local
1554    temporary array or a pointer variable.  */
1555
1556 static tree
1557 gfc_do_allocate (tree bytesize, tree size, tree * pdata, stmtblock_t * pblock,
1558                  tree elem_type)
1559 {
1560   tree tmpvar;
1561   tree type;
1562   tree tmp;
1563   tree args;
1564
1565   if (INTEGER_CST_P (size))
1566     {
1567       tmp = fold_build2 (MINUS_EXPR, gfc_array_index_type, size,
1568                          gfc_index_one_node);
1569     }
1570   else
1571     tmp = NULL_TREE;
1572
1573   type = build_range_type (gfc_array_index_type, gfc_index_zero_node, tmp);
1574   type = build_array_type (elem_type, type);
1575   if (gfc_can_put_var_on_stack (bytesize))
1576     {
1577       gcc_assert (INTEGER_CST_P (size));
1578       tmpvar = gfc_create_var (type, "temp");
1579       *pdata = NULL_TREE;
1580     }
1581   else
1582     {
1583       tmpvar = gfc_create_var (build_pointer_type (type), "temp");
1584       *pdata = convert (pvoid_type_node, tmpvar);
1585
1586       args = gfc_chainon_list (NULL_TREE, bytesize);
1587       if (gfc_index_integer_kind == 4)
1588         tmp = gfor_fndecl_internal_malloc;
1589       else if (gfc_index_integer_kind == 8)
1590         tmp = gfor_fndecl_internal_malloc64;
1591       else
1592         gcc_unreachable ();
1593       tmp = build_function_call_expr (tmp, args);
1594       tmp = convert (TREE_TYPE (tmpvar), tmp);
1595       gfc_add_modify_expr (pblock, tmpvar, tmp);
1596     }
1597   return tmpvar;
1598 }
1599
1600
1601 /* Generate codes to copy the temporary to the actual lhs.  */
1602
1603 static tree
1604 generate_loop_for_temp_to_lhs (gfc_expr *expr, tree tmp1, tree count3,
1605                                tree count1, tree wheremask)
1606 {
1607   gfc_ss *lss;
1608   gfc_se lse, rse;
1609   stmtblock_t block, body;
1610   gfc_loopinfo loop1;
1611   tree tmp, tmp2;
1612   tree wheremaskexpr;
1613
1614   /* Walk the lhs.  */
1615   lss = gfc_walk_expr (expr);
1616
1617   if (lss == gfc_ss_terminator)
1618     {
1619       gfc_start_block (&block);
1620
1621       gfc_init_se (&lse, NULL);
1622
1623       /* Translate the expression.  */
1624       gfc_conv_expr (&lse, expr);
1625
1626       /* Form the expression for the temporary.  */
1627       tmp = gfc_build_array_ref (tmp1, count1);
1628
1629       /* Use the scalar assignment as is.  */
1630       gfc_add_block_to_block (&block, &lse.pre);
1631       gfc_add_modify_expr (&block, lse.expr, tmp);
1632       gfc_add_block_to_block (&block, &lse.post);
1633
1634       /* Increment the count1.  */
1635       tmp = fold_build2 (PLUS_EXPR, TREE_TYPE (count1), count1,
1636                          gfc_index_one_node);
1637       gfc_add_modify_expr (&block, count1, tmp);
1638
1639       tmp = gfc_finish_block (&block);
1640     }
1641   else
1642     {
1643       gfc_start_block (&block);
1644
1645       gfc_init_loopinfo (&loop1);
1646       gfc_init_se (&rse, NULL);
1647       gfc_init_se (&lse, NULL);
1648
1649       /* Associate the lss with the loop.  */
1650       gfc_add_ss_to_loop (&loop1, lss);
1651
1652       /* Calculate the bounds of the scalarization.  */
1653       gfc_conv_ss_startstride (&loop1);
1654       /* Setup the scalarizing loops.  */
1655       gfc_conv_loop_setup (&loop1);
1656
1657       gfc_mark_ss_chain_used (lss, 1);
1658
1659       /* Start the scalarized loop body.  */
1660       gfc_start_scalarized_body (&loop1, &body);
1661
1662       /* Setup the gfc_se structures.  */
1663       gfc_copy_loopinfo_to_se (&lse, &loop1);
1664       lse.ss = lss;
1665
1666       /* Form the expression of the temporary.  */
1667       if (lss != gfc_ss_terminator)
1668         rse.expr = gfc_build_array_ref (tmp1, count1);
1669       /* Translate expr.  */
1670       gfc_conv_expr (&lse, expr);
1671
1672       /* Use the scalar assignment.  */
1673       tmp = gfc_trans_scalar_assign (&lse, &rse, expr->ts.type);
1674
1675      /* Form the mask expression according to the mask tree list.  */
1676      if (wheremask)
1677        {
1678          wheremaskexpr = gfc_build_array_ref (wheremask, count3);
1679          tmp2 = TREE_CHAIN (wheremask);
1680          while (tmp2)
1681            {
1682              tmp1 = gfc_build_array_ref (tmp2, count3);
1683              wheremaskexpr = fold_build2 (TRUTH_AND_EXPR, TREE_TYPE (tmp1),
1684                                           wheremaskexpr, tmp1);
1685              tmp2 = TREE_CHAIN (tmp2);
1686            }
1687          tmp = fold_build3 (COND_EXPR, void_type_node,
1688                             wheremaskexpr, tmp, build_empty_stmt ());
1689        }
1690
1691       gfc_add_expr_to_block (&body, tmp);
1692
1693       /* Increment count1.  */
1694       tmp = fold_build2 (PLUS_EXPR, gfc_array_index_type,
1695                          count1, gfc_index_one_node);
1696       gfc_add_modify_expr (&body, count1, tmp);
1697
1698       /* Increment count3.  */
1699       if (count3)
1700         {
1701           tmp = fold_build2 (PLUS_EXPR, gfc_array_index_type,
1702                              count3, gfc_index_one_node);
1703           gfc_add_modify_expr (&body, count3, tmp);
1704         }
1705
1706       /* Generate the copying loops.  */
1707       gfc_trans_scalarizing_loops (&loop1, &body);
1708       gfc_add_block_to_block (&block, &loop1.pre);
1709       gfc_add_block_to_block (&block, &loop1.post);
1710       gfc_cleanup_loop (&loop1);
1711
1712       tmp = gfc_finish_block (&block);
1713     }
1714   return tmp;
1715 }
1716
1717
1718 /* Generate codes to copy rhs to the temporary. TMP1 is the address of temporary
1719    LSS and RSS are formed in function compute_inner_temp_size(), and should
1720    not be freed.  */
1721
1722 static tree
1723 generate_loop_for_rhs_to_temp (gfc_expr *expr2, tree tmp1, tree count3,
1724                                tree count1, gfc_ss *lss, gfc_ss *rss,
1725                                tree wheremask)
1726 {
1727   stmtblock_t block, body1;
1728   gfc_loopinfo loop;
1729   gfc_se lse;
1730   gfc_se rse;
1731   tree tmp, tmp2;
1732   tree wheremaskexpr;
1733
1734   gfc_start_block (&block);
1735
1736   gfc_init_se (&rse, NULL);
1737   gfc_init_se (&lse, NULL);
1738
1739   if (lss == gfc_ss_terminator)
1740     {
1741       gfc_init_block (&body1);
1742       gfc_conv_expr (&rse, expr2);
1743       lse.expr = gfc_build_array_ref (tmp1, count1);
1744     }
1745   else
1746     {
1747       /* Initialize the loop.  */
1748       gfc_init_loopinfo (&loop);
1749
1750       /* We may need LSS to determine the shape of the expression.  */
1751       gfc_add_ss_to_loop (&loop, lss);
1752       gfc_add_ss_to_loop (&loop, rss);
1753
1754       gfc_conv_ss_startstride (&loop);
1755       gfc_conv_loop_setup (&loop);
1756
1757       gfc_mark_ss_chain_used (rss, 1);
1758       /* Start the loop body.  */
1759       gfc_start_scalarized_body (&loop, &body1);
1760
1761       /* Translate the expression.  */
1762       gfc_copy_loopinfo_to_se (&rse, &loop);
1763       rse.ss = rss;
1764       gfc_conv_expr (&rse, expr2);
1765
1766       /* Form the expression of the temporary.  */
1767       lse.expr = gfc_build_array_ref (tmp1, count1);
1768     }
1769
1770   /* Use the scalar assignment.  */
1771   tmp = gfc_trans_scalar_assign (&lse, &rse, expr2->ts.type);
1772
1773   /* Form the mask expression according to the mask tree list.  */
1774   if (wheremask)
1775     {
1776       wheremaskexpr = gfc_build_array_ref (wheremask, count3);
1777       tmp2 = TREE_CHAIN (wheremask);
1778       while (tmp2)
1779         {
1780           tmp1 = gfc_build_array_ref (tmp2, count3);
1781           wheremaskexpr = fold_build2 (TRUTH_AND_EXPR, TREE_TYPE (tmp1),
1782                                        wheremaskexpr, tmp1);
1783           tmp2 = TREE_CHAIN (tmp2);
1784         }
1785       tmp = fold_build3 (COND_EXPR, void_type_node,
1786                          wheremaskexpr, tmp, build_empty_stmt ());
1787     }
1788
1789   gfc_add_expr_to_block (&body1, tmp);
1790
1791   if (lss == gfc_ss_terminator)
1792     {
1793       gfc_add_block_to_block (&block, &body1);
1794
1795       /* Increment count1.  */
1796       tmp = fold_build2 (PLUS_EXPR, TREE_TYPE (count1), count1,
1797                          gfc_index_one_node);
1798       gfc_add_modify_expr (&block, count1, tmp);
1799     }
1800   else
1801     {
1802       /* Increment count1.  */
1803       tmp = fold_build2 (PLUS_EXPR, gfc_array_index_type,
1804                          count1, gfc_index_one_node);
1805       gfc_add_modify_expr (&body1, count1, tmp);
1806
1807       /* Increment count3.  */
1808       if (count3)
1809         {
1810           tmp = fold_build2 (PLUS_EXPR, gfc_array_index_type,
1811                              count3, gfc_index_one_node);
1812           gfc_add_modify_expr (&body1, count3, tmp);
1813         }
1814
1815       /* Generate the copying loops.  */
1816       gfc_trans_scalarizing_loops (&loop, &body1);
1817
1818       gfc_add_block_to_block (&block, &loop.pre);
1819       gfc_add_block_to_block (&block, &loop.post);
1820
1821       gfc_cleanup_loop (&loop);
1822       /* TODO: Reuse lss and rss when copying temp->lhs.  Need to be careful
1823          as tree nodes in SS may not be valid in different scope.  */
1824     }
1825
1826   tmp = gfc_finish_block (&block);
1827   return tmp;
1828 }
1829
1830
1831 /* Calculate the size of temporary needed in the assignment inside forall.
1832    LSS and RSS are filled in this function.  */
1833
1834 static tree
1835 compute_inner_temp_size (gfc_expr *expr1, gfc_expr *expr2,
1836                          stmtblock_t * pblock,
1837                          gfc_ss **lss, gfc_ss **rss)
1838 {
1839   gfc_loopinfo loop;
1840   tree size;
1841   int i;
1842   tree tmp;
1843
1844   *lss = gfc_walk_expr (expr1);
1845   *rss = NULL;
1846
1847   size = gfc_index_one_node;
1848   if (*lss != gfc_ss_terminator)
1849     {
1850       gfc_init_loopinfo (&loop);
1851
1852       /* Walk the RHS of the expression.  */
1853       *rss = gfc_walk_expr (expr2);
1854       if (*rss == gfc_ss_terminator)
1855         {
1856           /* The rhs is scalar.  Add a ss for the expression.  */
1857           *rss = gfc_get_ss ();
1858           (*rss)->next = gfc_ss_terminator;
1859           (*rss)->type = GFC_SS_SCALAR;
1860           (*rss)->expr = expr2;
1861         }
1862
1863       /* Associate the SS with the loop.  */
1864       gfc_add_ss_to_loop (&loop, *lss);
1865       /* We don't actually need to add the rhs at this point, but it might
1866          make guessing the loop bounds a bit easier.  */
1867       gfc_add_ss_to_loop (&loop, *rss);
1868
1869       /* We only want the shape of the expression, not rest of the junk
1870          generated by the scalarizer.  */
1871       loop.array_parameter = 1;
1872
1873       /* Calculate the bounds of the scalarization.  */
1874       gfc_conv_ss_startstride (&loop);
1875       gfc_conv_loop_setup (&loop);
1876
1877       /* Figure out how many elements we need.  */
1878       for (i = 0; i < loop.dimen; i++)
1879         {
1880           tmp = fold_build2 (MINUS_EXPR, gfc_array_index_type,
1881                              gfc_index_one_node, loop.from[i]);
1882           tmp = fold_build2 (PLUS_EXPR, gfc_array_index_type,
1883                              tmp, loop.to[i]);
1884           size = fold_build2 (MULT_EXPR, gfc_array_index_type, size, tmp);
1885         }
1886       gfc_add_block_to_block (pblock, &loop.pre);
1887       size = gfc_evaluate_now (size, pblock);
1888       gfc_add_block_to_block (pblock, &loop.post);
1889
1890       /* TODO: write a function that cleans up a loopinfo without freeing
1891          the SS chains.  Currently a NOP.  */
1892     }
1893
1894   return size;
1895 }
1896
1897
1898 /* Calculate the overall iterator number of the nested forall construct.  */
1899
1900 static tree
1901 compute_overall_iter_number (forall_info *nested_forall_info, tree inner_size,
1902                              stmtblock_t *inner_size_body, stmtblock_t *block)
1903 {
1904   tree tmp, number;
1905   stmtblock_t body;
1906
1907   /* TODO: optimizing the computing process.  */
1908   number = gfc_create_var (gfc_array_index_type, "num");
1909   gfc_add_modify_expr (block, number, gfc_index_zero_node);
1910
1911   gfc_start_block (&body);
1912   if (inner_size_body)
1913     gfc_add_block_to_block (&body, inner_size_body);
1914   if (nested_forall_info)
1915     tmp = build2 (PLUS_EXPR, gfc_array_index_type, number,
1916                   inner_size);
1917   else
1918     tmp = inner_size;
1919   gfc_add_modify_expr (&body, number, tmp);
1920   tmp = gfc_finish_block (&body);
1921
1922   /* Generate loops.  */
1923   if (nested_forall_info != NULL)
1924     tmp = gfc_trans_nested_forall_loop (nested_forall_info, tmp, 0, 1);
1925
1926   gfc_add_expr_to_block (block, tmp);
1927
1928   return number;
1929 }
1930
1931
1932 /* Allocate temporary for forall construct.  SIZE is the size of temporary
1933    needed.  PTEMP1 is returned for space free.  */
1934
1935 static tree
1936 allocate_temp_for_forall_nest_1 (tree type, tree size, stmtblock_t * block,
1937                                  tree * ptemp1)
1938 {
1939   tree unit;
1940   tree temp1;
1941   tree tmp;
1942   tree bytesize;
1943
1944   unit = TYPE_SIZE_UNIT (type);
1945   bytesize = fold_build2 (MULT_EXPR, gfc_array_index_type, size, unit);
1946
1947   *ptemp1 = NULL;
1948   temp1 = gfc_do_allocate (bytesize, size, ptemp1, block, type);
1949
1950   if (*ptemp1)
1951     tmp = build_fold_indirect_ref (temp1);
1952   else
1953     tmp = temp1;
1954
1955   return tmp;
1956 }
1957
1958
1959 /* Allocate temporary for forall construct according to the information in
1960    nested_forall_info.  INNER_SIZE is the size of temporary needed in the
1961    assignment inside forall.  PTEMP1 is returned for space free.  */
1962
1963 static tree
1964 allocate_temp_for_forall_nest (forall_info * nested_forall_info, tree type,
1965                                tree inner_size, stmtblock_t * inner_size_body,
1966                                stmtblock_t * block, tree * ptemp1)
1967 {
1968   tree size;
1969
1970   /* Calculate the total size of temporary needed in forall construct.  */
1971   size = compute_overall_iter_number (nested_forall_info, inner_size,
1972                                       inner_size_body, block);
1973
1974   return allocate_temp_for_forall_nest_1 (type, size, block, ptemp1);
1975 }
1976
1977
1978 /* Handle assignments inside forall which need temporary.
1979
1980     forall (i=start:end:stride; maskexpr)
1981       e<i> = f<i>
1982     end forall
1983    (where e,f<i> are arbitrary expressions possibly involving i
1984     and there is a dependency between e<i> and f<i>)
1985    Translates to:
1986     masktmp(:) = maskexpr(:)
1987
1988     maskindex = 0;
1989     count1 = 0;
1990     num = 0;
1991     for (i = start; i <= end; i += stride)
1992       num += SIZE (f<i>)
1993     count1 = 0;
1994     ALLOCATE (tmp(num))
1995     for (i = start; i <= end; i += stride)
1996       {
1997         if (masktmp[maskindex++])
1998           tmp[count1++] = f<i>
1999       }
2000     maskindex = 0;
2001     count1 = 0;
2002     for (i = start; i <= end; i += stride)
2003       {
2004         if (masktmp[maskindex++])
2005           e<i> = tmp[count1++]
2006       }
2007     DEALLOCATE (tmp)
2008   */
2009 static void
2010 gfc_trans_assign_need_temp (gfc_expr * expr1, gfc_expr * expr2, tree wheremask,
2011                             forall_info * nested_forall_info,
2012                             stmtblock_t * block)
2013 {
2014   tree type;
2015   tree inner_size;
2016   gfc_ss *lss, *rss;
2017   tree count, count1;
2018   tree tmp, tmp1;
2019   tree ptemp1;
2020   stmtblock_t inner_size_body;
2021
2022   /* Create vars. count1 is the current iterator number of the nested
2023      forall.  */
2024   count1 = gfc_create_var (gfc_array_index_type, "count1");
2025
2026   /* Count is the wheremask index.  */
2027   if (wheremask)
2028     {
2029       count = gfc_create_var (gfc_array_index_type, "count");
2030       gfc_add_modify_expr (block, count, gfc_index_zero_node);
2031     }
2032   else
2033     count = NULL;
2034
2035   /* Initialize count1.  */
2036   gfc_add_modify_expr (block, count1, gfc_index_zero_node);
2037
2038   /* Calculate the size of temporary needed in the assignment. Return loop, lss
2039      and rss which are used in function generate_loop_for_rhs_to_temp().  */
2040   gfc_init_block (&inner_size_body);
2041   inner_size = compute_inner_temp_size (expr1, expr2, &inner_size_body,
2042                                         &lss, &rss);
2043
2044   /* The type of LHS. Used in function allocate_temp_for_forall_nest */
2045   type = gfc_typenode_for_spec (&expr1->ts);
2046
2047   /* Allocate temporary for nested forall construct according to the
2048      information in nested_forall_info and inner_size.  */
2049   tmp1 = allocate_temp_for_forall_nest (nested_forall_info, type, inner_size,
2050                                         &inner_size_body, block, &ptemp1);
2051
2052   /* Generate codes to copy rhs to the temporary .  */
2053   tmp = generate_loop_for_rhs_to_temp (expr2, tmp1, count, count1, lss, rss,
2054                                        wheremask);
2055
2056   /* Generate body and loops according to the information in
2057      nested_forall_info.  */
2058   tmp = gfc_trans_nested_forall_loop (nested_forall_info, tmp, 1, 1);
2059   gfc_add_expr_to_block (block, tmp);
2060
2061   /* Reset count1.  */
2062   gfc_add_modify_expr (block, count1, gfc_index_zero_node);
2063
2064   /* Reset count.  */
2065   if (wheremask)
2066     gfc_add_modify_expr (block, count, gfc_index_zero_node);
2067
2068   /* Generate codes to copy the temporary to lhs.  */
2069   tmp = generate_loop_for_temp_to_lhs (expr1, tmp1, count, count1, wheremask);
2070
2071   /* Generate body and loops according to the information in
2072      nested_forall_info.  */
2073   tmp = gfc_trans_nested_forall_loop (nested_forall_info, tmp, 1, 1);
2074   gfc_add_expr_to_block (block, tmp);
2075
2076   if (ptemp1)
2077     {
2078       /* Free the temporary.  */
2079       tmp = gfc_chainon_list (NULL_TREE, ptemp1);
2080       tmp = build_function_call_expr (gfor_fndecl_internal_free, tmp);
2081       gfc_add_expr_to_block (block, tmp);
2082     }
2083 }
2084
2085
2086 /* Translate pointer assignment inside FORALL which need temporary.  */
2087
2088 static void
2089 gfc_trans_pointer_assign_need_temp (gfc_expr * expr1, gfc_expr * expr2,
2090                                     forall_info * nested_forall_info,
2091                                     stmtblock_t * block)
2092 {
2093   tree type;
2094   tree inner_size;
2095   gfc_ss *lss, *rss;
2096   gfc_se lse;
2097   gfc_se rse;
2098   gfc_ss_info *info;
2099   gfc_loopinfo loop;
2100   tree desc;
2101   tree parm;
2102   tree parmtype;
2103   stmtblock_t body;
2104   tree count;
2105   tree tmp, tmp1, ptemp1;
2106
2107   count = gfc_create_var (gfc_array_index_type, "count");
2108   gfc_add_modify_expr (block, count, gfc_index_zero_node);
2109
2110   inner_size = integer_one_node;
2111   lss = gfc_walk_expr (expr1);
2112   rss = gfc_walk_expr (expr2);
2113   if (lss == gfc_ss_terminator)
2114     {
2115       type = gfc_typenode_for_spec (&expr1->ts);
2116       type = build_pointer_type (type);
2117
2118       /* Allocate temporary for nested forall construct according to the
2119          information in nested_forall_info and inner_size.  */
2120       tmp1 = allocate_temp_for_forall_nest (nested_forall_info, type,
2121                                             inner_size, NULL, block, &ptemp1);
2122       gfc_start_block (&body);
2123       gfc_init_se (&lse, NULL);
2124       lse.expr = gfc_build_array_ref (tmp1, count);
2125       gfc_init_se (&rse, NULL);
2126       rse.want_pointer = 1;
2127       gfc_conv_expr (&rse, expr2);
2128       gfc_add_block_to_block (&body, &rse.pre);
2129       gfc_add_modify_expr (&body, lse.expr,
2130                            fold_convert (TREE_TYPE (lse.expr), rse.expr));
2131       gfc_add_block_to_block (&body, &rse.post);
2132
2133       /* Increment count.  */
2134       tmp = fold_build2 (PLUS_EXPR, gfc_array_index_type,
2135                          count, gfc_index_one_node);
2136       gfc_add_modify_expr (&body, count, tmp);
2137
2138       tmp = gfc_finish_block (&body);
2139
2140       /* Generate body and loops according to the information in
2141          nested_forall_info.  */
2142       tmp = gfc_trans_nested_forall_loop (nested_forall_info, tmp, 1, 1);
2143       gfc_add_expr_to_block (block, tmp);
2144
2145       /* Reset count.  */
2146       gfc_add_modify_expr (block, count, gfc_index_zero_node);
2147
2148       gfc_start_block (&body);
2149       gfc_init_se (&lse, NULL);
2150       gfc_init_se (&rse, NULL);
2151       rse.expr = gfc_build_array_ref (tmp1, count);
2152       lse.want_pointer = 1;
2153       gfc_conv_expr (&lse, expr1);
2154       gfc_add_block_to_block (&body, &lse.pre);
2155       gfc_add_modify_expr (&body, lse.expr, rse.expr);
2156       gfc_add_block_to_block (&body, &lse.post);
2157       /* Increment count.  */
2158       tmp = fold_build2 (PLUS_EXPR, gfc_array_index_type,
2159                          count, gfc_index_one_node);
2160       gfc_add_modify_expr (&body, count, tmp);
2161       tmp = gfc_finish_block (&body);
2162
2163       /* Generate body and loops according to the information in
2164          nested_forall_info.  */
2165       tmp = gfc_trans_nested_forall_loop (nested_forall_info, tmp, 1, 1);
2166       gfc_add_expr_to_block (block, tmp);
2167     }
2168   else
2169     {
2170       gfc_init_loopinfo (&loop);
2171
2172       /* Associate the SS with the loop.  */
2173       gfc_add_ss_to_loop (&loop, rss);
2174
2175       /* Setup the scalarizing loops and bounds.  */
2176       gfc_conv_ss_startstride (&loop);
2177
2178       gfc_conv_loop_setup (&loop);
2179
2180       info = &rss->data.info;
2181       desc = info->descriptor;
2182
2183       /* Make a new descriptor.  */
2184       parmtype = gfc_get_element_type (TREE_TYPE (desc));
2185       parmtype = gfc_get_array_type_bounds (parmtype, loop.dimen,
2186                                             loop.from, loop.to, 1);
2187
2188       /* Allocate temporary for nested forall construct.  */
2189       tmp1 = allocate_temp_for_forall_nest (nested_forall_info, parmtype,
2190                                             inner_size, NULL, block, &ptemp1);
2191       gfc_start_block (&body);
2192       gfc_init_se (&lse, NULL);
2193       lse.expr = gfc_build_array_ref (tmp1, count);
2194       lse.direct_byref = 1;
2195       rss = gfc_walk_expr (expr2);
2196       gfc_conv_expr_descriptor (&lse, expr2, rss);
2197
2198       gfc_add_block_to_block (&body, &lse.pre);
2199       gfc_add_block_to_block (&body, &lse.post);
2200
2201       /* Increment count.  */
2202       tmp = fold_build2 (PLUS_EXPR, gfc_array_index_type,
2203                          count, gfc_index_one_node);
2204       gfc_add_modify_expr (&body, count, tmp);
2205
2206       tmp = gfc_finish_block (&body);
2207
2208       /* Generate body and loops according to the information in
2209          nested_forall_info.  */
2210       tmp = gfc_trans_nested_forall_loop (nested_forall_info, tmp, 1, 1);
2211       gfc_add_expr_to_block (block, tmp);
2212
2213       /* Reset count.  */
2214       gfc_add_modify_expr (block, count, gfc_index_zero_node);
2215
2216       parm = gfc_build_array_ref (tmp1, count);
2217       lss = gfc_walk_expr (expr1);
2218       gfc_init_se (&lse, NULL);
2219       gfc_conv_expr_descriptor (&lse, expr1, lss);
2220       gfc_add_modify_expr (&lse.pre, lse.expr, parm);
2221       gfc_start_block (&body);
2222       gfc_add_block_to_block (&body, &lse.pre);
2223       gfc_add_block_to_block (&body, &lse.post);
2224
2225       /* Increment count.  */
2226       tmp = fold_build2 (PLUS_EXPR, gfc_array_index_type,
2227                          count, gfc_index_one_node);
2228       gfc_add_modify_expr (&body, count, tmp);
2229
2230       tmp = gfc_finish_block (&body);
2231
2232       tmp = gfc_trans_nested_forall_loop (nested_forall_info, tmp, 1, 1);
2233       gfc_add_expr_to_block (block, tmp);
2234     }
2235   /* Free the temporary.  */
2236   if (ptemp1)
2237     {
2238       tmp = gfc_chainon_list (NULL_TREE, ptemp1);
2239       tmp = build_function_call_expr (gfor_fndecl_internal_free, tmp);
2240       gfc_add_expr_to_block (block, tmp);
2241     }
2242 }
2243
2244
2245 /* FORALL and WHERE statements are really nasty, especially when you nest
2246    them. All the rhs of a forall assignment must be evaluated before the
2247    actual assignments are performed. Presumably this also applies to all the
2248    assignments in an inner where statement.  */
2249
2250 /* Generate code for a FORALL statement.  Any temporaries are allocated as a
2251    linear array, relying on the fact that we process in the same order in all
2252    loops.
2253
2254     forall (i=start:end:stride; maskexpr)
2255       e<i> = f<i>
2256       g<i> = h<i>
2257     end forall
2258    (where e,f,g,h<i> are arbitrary expressions possibly involving i)
2259    Translates to:
2260     count = ((end + 1 - start) / stride)
2261     masktmp(:) = maskexpr(:)
2262
2263     maskindex = 0;
2264     for (i = start; i <= end; i += stride)
2265       {
2266         if (masktmp[maskindex++])
2267           e<i> = f<i>
2268       }
2269     maskindex = 0;
2270     for (i = start; i <= end; i += stride)
2271       {
2272         if (masktmp[maskindex++])
2273           g<i> = h<i>
2274       }
2275
2276     Note that this code only works when there are no dependencies.
2277     Forall loop with array assignments and data dependencies are a real pain,
2278     because the size of the temporary cannot always be determined before the
2279     loop is executed.  This problem is compounded by the presence of nested
2280     FORALL constructs.
2281  */
2282
2283 static tree
2284 gfc_trans_forall_1 (gfc_code * code, forall_info * nested_forall_info)
2285 {
2286   stmtblock_t block;
2287   stmtblock_t body;
2288   tree *var;
2289   tree *start;
2290   tree *end;
2291   tree *step;
2292   gfc_expr **varexpr;
2293   tree tmp;
2294   tree assign;
2295   tree size;
2296   tree bytesize;
2297   tree tmpvar;
2298   tree sizevar;
2299   tree lenvar;
2300   tree maskindex;
2301   tree mask;
2302   tree pmask;
2303   int n;
2304   int nvar;
2305   int need_temp;
2306   gfc_forall_iterator *fa;
2307   gfc_se se;
2308   gfc_code *c;
2309   gfc_saved_var *saved_vars;
2310   iter_info *this_forall, *iter_tmp;
2311   forall_info *info, *forall_tmp;
2312
2313   gfc_start_block (&block);
2314
2315   n = 0;
2316   /* Count the FORALL index number.  */
2317   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
2318     n++;
2319   nvar = n;
2320
2321   /* Allocate the space for var, start, end, step, varexpr.  */
2322   var = (tree *) gfc_getmem (nvar * sizeof (tree));
2323   start = (tree *) gfc_getmem (nvar * sizeof (tree));
2324   end = (tree *) gfc_getmem (nvar * sizeof (tree));
2325   step = (tree *) gfc_getmem (nvar * sizeof (tree));
2326   varexpr = (gfc_expr **) gfc_getmem (nvar * sizeof (gfc_expr *));
2327   saved_vars = (gfc_saved_var *) gfc_getmem (nvar * sizeof (gfc_saved_var));
2328
2329   /* Allocate the space for info.  */
2330   info = (forall_info *) gfc_getmem (sizeof (forall_info));
2331   n = 0;
2332   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
2333     {
2334       gfc_symbol *sym = fa->var->symtree->n.sym;
2335
2336       /* allocate space for this_forall.  */
2337       this_forall = (iter_info *) gfc_getmem (sizeof (iter_info));
2338
2339       /* Create a temporary variable for the FORALL index.  */
2340       tmp = gfc_typenode_for_spec (&sym->ts);
2341       var[n] = gfc_create_var (tmp, sym->name);
2342       gfc_shadow_sym (sym, var[n], &saved_vars[n]);
2343
2344       /* Record it in this_forall.  */
2345       this_forall->var = var[n];
2346
2347       /* Replace the index symbol's backend_decl with the temporary decl.  */
2348       sym->backend_decl = var[n];
2349
2350       /* Work out the start, end and stride for the loop.  */
2351       gfc_init_se (&se, NULL);
2352       gfc_conv_expr_val (&se, fa->start);
2353       /* Record it in this_forall.  */
2354       this_forall->start = se.expr;
2355       gfc_add_block_to_block (&block, &se.pre);
2356       start[n] = se.expr;
2357
2358       gfc_init_se (&se, NULL);
2359       gfc_conv_expr_val (&se, fa->end);
2360       /* Record it in this_forall.  */
2361       this_forall->end = se.expr;
2362       gfc_make_safe_expr (&se);
2363       gfc_add_block_to_block (&block, &se.pre);
2364       end[n] = se.expr;
2365
2366       gfc_init_se (&se, NULL);
2367       gfc_conv_expr_val (&se, fa->stride);
2368       /* Record it in this_forall.  */
2369       this_forall->step = se.expr;
2370       gfc_make_safe_expr (&se);
2371       gfc_add_block_to_block (&block, &se.pre);
2372       step[n] = se.expr;
2373
2374       /* Set the NEXT field of this_forall to NULL.  */
2375       this_forall->next = NULL;
2376       /* Link this_forall to the info construct.  */
2377       if (info->this_loop == NULL)
2378         info->this_loop = this_forall;
2379       else
2380         {
2381           iter_tmp = info->this_loop;
2382           while (iter_tmp->next != NULL)
2383             iter_tmp = iter_tmp->next;
2384           iter_tmp->next = this_forall;
2385         }
2386
2387       n++;
2388     }
2389   nvar = n;
2390
2391   /* Work out the number of elements in the mask array.  */
2392   tmpvar = NULL_TREE;
2393   lenvar = NULL_TREE;
2394   size = gfc_index_one_node;
2395   sizevar = NULL_TREE;
2396
2397   for (n = 0; n < nvar; n++)
2398     {
2399       if (lenvar && TREE_TYPE (lenvar) != TREE_TYPE (start[n]))
2400         lenvar = NULL_TREE;
2401
2402       /* size = (end + step - start) / step.  */
2403       tmp = fold_build2 (MINUS_EXPR, TREE_TYPE (start[n]), 
2404                          step[n], start[n]);
2405       tmp = fold_build2 (PLUS_EXPR, TREE_TYPE (end[n]), end[n], tmp);
2406
2407       tmp = fold_build2 (FLOOR_DIV_EXPR, TREE_TYPE (tmp), tmp, step[n]);
2408       tmp = convert (gfc_array_index_type, tmp);
2409
2410       size = fold_build2 (MULT_EXPR, gfc_array_index_type, size, tmp);
2411     }
2412
2413   /* Record the nvar and size of current forall level.  */
2414   info->nvar = nvar;
2415   info->size = size;
2416
2417   /* Link the current forall level to nested_forall_info.  */
2418   forall_tmp = nested_forall_info;
2419   if (forall_tmp == NULL)
2420     nested_forall_info = info;
2421   else
2422     {
2423       while (forall_tmp->next_nest != NULL)
2424         forall_tmp = forall_tmp->next_nest;
2425       info->outer = forall_tmp;
2426       forall_tmp->next_nest = info;
2427     }
2428
2429   /* Copy the mask into a temporary variable if required.
2430      For now we assume a mask temporary is needed.  */
2431   if (code->expr)
2432     {
2433       /* As the mask array can be very big, prefer compact
2434          boolean types.  */
2435       tree smallest_boolean_type_node
2436         = gfc_get_logical_type (gfc_logical_kinds[0].kind);
2437
2438       /* Allocate the mask temporary.  */
2439       bytesize = fold_build2 (MULT_EXPR, gfc_array_index_type, size,
2440                               TYPE_SIZE_UNIT (smallest_boolean_type_node));
2441
2442       mask = gfc_do_allocate (bytesize, size, &pmask, &block,
2443                               smallest_boolean_type_node);
2444
2445       maskindex = gfc_create_var_np (gfc_array_index_type, "mi");
2446       /* Record them in the info structure.  */
2447       info->pmask = pmask;
2448       info->mask = mask;
2449       info->maskindex = maskindex;
2450
2451       gfc_add_modify_expr (&block, maskindex, gfc_index_zero_node);
2452
2453       /* Start of mask assignment loop body.  */
2454       gfc_start_block (&body);
2455
2456       /* Evaluate the mask expression.  */
2457       gfc_init_se (&se, NULL);
2458       gfc_conv_expr_val (&se, code->expr);
2459       gfc_add_block_to_block (&body, &se.pre);
2460
2461       /* Store the mask.  */
2462       se.expr = convert (smallest_boolean_type_node, se.expr);
2463
2464       if (pmask)
2465         tmp = build_fold_indirect_ref (mask);
2466       else
2467         tmp = mask;
2468       tmp = gfc_build_array_ref (tmp, maskindex);
2469       gfc_add_modify_expr (&body, tmp, se.expr);
2470
2471       /* Advance to the next mask element.  */
2472       tmp = build2 (PLUS_EXPR, gfc_array_index_type,
2473                    maskindex, gfc_index_one_node);
2474       gfc_add_modify_expr (&body, maskindex, tmp);
2475
2476       /* Generate the loops.  */
2477       tmp = gfc_finish_block (&body);
2478       tmp = gfc_trans_nested_forall_loop (info, tmp, 0, 0);
2479       gfc_add_expr_to_block (&block, tmp);
2480     }
2481   else
2482     {
2483       /* No mask was specified.  */
2484       maskindex = NULL_TREE;
2485       mask = pmask = NULL_TREE;
2486     }
2487
2488   c = code->block->next;
2489
2490   /* TODO: loop merging in FORALL statements.  */
2491   /* Now that we've got a copy of the mask, generate the assignment loops.  */
2492   while (c)
2493     {
2494       switch (c->op)
2495         {
2496         case EXEC_ASSIGN:
2497           /* A scalar or array assignment.  */
2498           need_temp = gfc_check_dependency (c->expr, c->expr2, 0);
2499           /* Temporaries due to array assignment data dependencies introduce
2500              no end of problems.  */
2501           if (need_temp)
2502             gfc_trans_assign_need_temp (c->expr, c->expr2, NULL,
2503                                         nested_forall_info, &block);
2504           else
2505             {
2506               /* Use the normal assignment copying routines.  */
2507               assign = gfc_trans_assignment (c->expr, c->expr2);
2508
2509               /* Generate body and loops.  */
2510               tmp = gfc_trans_nested_forall_loop (nested_forall_info, assign, 1, 1);
2511               gfc_add_expr_to_block (&block, tmp);
2512             }
2513
2514           break;
2515
2516         case EXEC_WHERE:
2517           /* Translate WHERE or WHERE construct nested in FORALL.  */
2518           gfc_trans_where_2 (c, NULL, nested_forall_info, &block);
2519           break;
2520
2521         /* Pointer assignment inside FORALL.  */
2522         case EXEC_POINTER_ASSIGN:
2523           need_temp = gfc_check_dependency (c->expr, c->expr2, 0);
2524           if (need_temp)
2525             gfc_trans_pointer_assign_need_temp (c->expr, c->expr2,
2526                                                 nested_forall_info, &block);
2527           else
2528             {
2529               /* Use the normal assignment copying routines.  */
2530               assign = gfc_trans_pointer_assignment (c->expr, c->expr2);
2531
2532               /* Generate body and loops.  */
2533               tmp = gfc_trans_nested_forall_loop (nested_forall_info, assign,
2534                                                   1, 1);
2535               gfc_add_expr_to_block (&block, tmp);
2536             }
2537           break;
2538
2539         case EXEC_FORALL:
2540           tmp = gfc_trans_forall_1 (c, nested_forall_info);
2541           gfc_add_expr_to_block (&block, tmp);
2542           break;
2543
2544         /* Explicit subroutine calls are prevented by the frontend but interface
2545            assignments can legitimately produce them.  */
2546         case EXEC_CALL:
2547           assign = gfc_trans_call (c);
2548           tmp = gfc_trans_nested_forall_loop (nested_forall_info, assign, 1, 1);
2549           gfc_add_expr_to_block (&block, tmp);
2550           break;
2551
2552         default:
2553           gcc_unreachable ();
2554         }
2555
2556       c = c->next;
2557     }
2558
2559   /* Restore the original index variables.  */
2560   for (fa = code->ext.forall_iterator, n = 0; fa; fa = fa->next, n++)
2561     gfc_restore_sym (fa->var->symtree->n.sym, &saved_vars[n]);
2562
2563   /* Free the space for var, start, end, step, varexpr.  */
2564   gfc_free (var);
2565   gfc_free (start);
2566   gfc_free (end);
2567   gfc_free (step);
2568   gfc_free (varexpr);
2569   gfc_free (saved_vars);
2570
2571   if (pmask)
2572     {
2573       /* Free the temporary for the mask.  */
2574       tmp = gfc_chainon_list (NULL_TREE, pmask);
2575       tmp = build_function_call_expr (gfor_fndecl_internal_free, tmp);
2576       gfc_add_expr_to_block (&block, tmp);
2577     }
2578   if (maskindex)
2579     pushdecl (maskindex);
2580
2581   return gfc_finish_block (&block);
2582 }
2583
2584
2585 /* Translate the FORALL statement or construct.  */
2586
2587 tree gfc_trans_forall (gfc_code * code)
2588 {
2589   return gfc_trans_forall_1 (code, NULL);
2590 }
2591
2592
2593 /* Evaluate the WHERE mask expression, copy its value to a temporary.
2594    If the WHERE construct is nested in FORALL, compute the overall temporary
2595    needed by the WHERE mask expression multiplied by the iterator number of
2596    the nested forall.
2597    ME is the WHERE mask expression.
2598    MASK is the current execution mask upon input.
2599    CMASK is the updated execution mask on output, or NULL if not required.
2600    PMASK is the pending execution mask on output, or NULL if not required.
2601    BLOCK is the block in which to place the condition evaluation loops.  */
2602
2603 static void
2604 gfc_evaluate_where_mask (gfc_expr * me, forall_info * nested_forall_info,
2605                          tree mask, tree cmask, tree pmask,
2606                          tree mask_type, stmtblock_t * block)
2607 {
2608   tree tmp, tmp1;
2609   gfc_ss *lss, *rss;
2610   gfc_loopinfo loop;
2611   stmtblock_t body, body1;
2612   tree count, cond, mtmp;
2613   gfc_se lse, rse;
2614
2615   gfc_init_loopinfo (&loop);
2616
2617   lss = gfc_walk_expr (me);
2618   rss = gfc_walk_expr (me);
2619
2620   /* Variable to index the temporary.  */
2621   count = gfc_create_var (gfc_array_index_type, "count");
2622   /* Initialize count.  */
2623   gfc_add_modify_expr (block, count, gfc_index_zero_node);
2624
2625   gfc_start_block (&body);
2626
2627   gfc_init_se (&rse, NULL);
2628   gfc_init_se (&lse, NULL);
2629
2630   if (lss == gfc_ss_terminator)
2631     {
2632       gfc_init_block (&body1);
2633     }
2634   else
2635     {
2636       /* Initialize the loop.  */
2637       gfc_init_loopinfo (&loop);
2638
2639       /* We may need LSS to determine the shape of the expression.  */
2640       gfc_add_ss_to_loop (&loop, lss);
2641       gfc_add_ss_to_loop (&loop, rss);
2642
2643       gfc_conv_ss_startstride (&loop);
2644       gfc_conv_loop_setup (&loop);
2645
2646       gfc_mark_ss_chain_used (rss, 1);
2647       /* Start the loop body.  */
2648       gfc_start_scalarized_body (&loop, &body1);
2649
2650       /* Translate the expression.  */
2651       gfc_copy_loopinfo_to_se (&rse, &loop);
2652       rse.ss = rss;
2653       gfc_conv_expr (&rse, me);
2654     }
2655
2656   /* Variable to evalate mask condition.  */
2657   cond = gfc_create_var (mask_type, "cond");
2658   if (mask && (cmask || pmask))
2659     mtmp = gfc_create_var (mask_type, "mask");
2660   else mtmp = NULL_TREE;
2661
2662   gfc_add_block_to_block (&body1, &lse.pre);
2663   gfc_add_block_to_block (&body1, &rse.pre);
2664
2665   gfc_add_modify_expr (&body1, cond, fold_convert (mask_type, rse.expr));
2666
2667   if (mask && (cmask || pmask))
2668     {
2669       tmp = gfc_build_array_ref (mask, count);
2670       gfc_add_modify_expr (&body1, mtmp, tmp);
2671     }
2672
2673   if (cmask)
2674     {
2675       tmp1 = gfc_build_array_ref (cmask, count);
2676       tmp = cond;
2677       if (mask)
2678         tmp = build2 (TRUTH_AND_EXPR, mask_type, mtmp, tmp);
2679       gfc_add_modify_expr (&body1, tmp1, tmp);
2680     }
2681
2682   if (pmask)
2683     {
2684       tmp1 = gfc_build_array_ref (pmask, count);
2685       tmp = build1 (TRUTH_NOT_EXPR, mask_type, cond);
2686       if (mask)
2687         tmp = build2 (TRUTH_AND_EXPR, mask_type, mtmp, tmp);
2688       gfc_add_modify_expr (&body1, tmp1, tmp);
2689     }
2690
2691   gfc_add_block_to_block (&body1, &lse.post);
2692   gfc_add_block_to_block (&body1, &rse.post);
2693
2694   if (lss == gfc_ss_terminator)
2695     {
2696       gfc_add_block_to_block (&body, &body1);
2697     }
2698   else
2699     {
2700       /* Increment count.  */
2701       tmp1 = fold_build2 (PLUS_EXPR, gfc_array_index_type, count,
2702                           gfc_index_one_node);
2703       gfc_add_modify_expr (&body1, count, tmp1);
2704
2705       /* Generate the copying loops.  */
2706       gfc_trans_scalarizing_loops (&loop, &body1);
2707
2708       gfc_add_block_to_block (&body, &loop.pre);
2709       gfc_add_block_to_block (&body, &loop.post);
2710
2711       gfc_cleanup_loop (&loop);
2712       /* TODO: Reuse lss and rss when copying temp->lhs.  Need to be careful
2713          as tree nodes in SS may not be valid in different scope.  */
2714     }
2715
2716   tmp1 = gfc_finish_block (&body);
2717   /* If the WHERE construct is inside FORALL, fill the full temporary.  */
2718   if (nested_forall_info != NULL)
2719     tmp1 = gfc_trans_nested_forall_loop (nested_forall_info, tmp1, 1, 1);
2720
2721   gfc_add_expr_to_block (block, tmp1);
2722 }
2723
2724
2725 /* Translate an assignment statement in a WHERE statement or construct
2726    statement. The MASK expression is used to control which elements
2727    of EXPR1 shall be assigned.  */
2728
2729 static tree
2730 gfc_trans_where_assign (gfc_expr *expr1, gfc_expr *expr2, tree mask,
2731                         tree count1, tree count2)
2732 {
2733   gfc_se lse;
2734   gfc_se rse;
2735   gfc_ss *lss;
2736   gfc_ss *lss_section;
2737   gfc_ss *rss;
2738
2739   gfc_loopinfo loop;
2740   tree tmp;
2741   stmtblock_t block;
2742   stmtblock_t body;
2743   tree index, maskexpr, tmp1;
2744
2745 #if 0
2746   /* TODO: handle this special case.
2747      Special case a single function returning an array.  */
2748   if (expr2->expr_type == EXPR_FUNCTION && expr2->rank > 0)
2749     {
2750       tmp = gfc_trans_arrayfunc_assign (expr1, expr2);
2751       if (tmp)
2752         return tmp;
2753     }
2754 #endif
2755
2756  /* Assignment of the form lhs = rhs.  */
2757   gfc_start_block (&block);
2758
2759   gfc_init_se (&lse, NULL);
2760   gfc_init_se (&rse, NULL);
2761
2762   /* Walk the lhs.  */
2763   lss = gfc_walk_expr (expr1);
2764   rss = NULL;
2765
2766   /* In each where-assign-stmt, the mask-expr and the variable being
2767      defined shall be arrays of the same shape.  */
2768   gcc_assert (lss != gfc_ss_terminator);
2769
2770   /* The assignment needs scalarization.  */
2771   lss_section = lss;
2772
2773   /* Find a non-scalar SS from the lhs.  */
2774   while (lss_section != gfc_ss_terminator
2775          && lss_section->type != GFC_SS_SECTION)
2776     lss_section = lss_section->next;
2777
2778   gcc_assert (lss_section != gfc_ss_terminator);
2779
2780   /* Initialize the scalarizer.  */
2781   gfc_init_loopinfo (&loop);
2782
2783   /* Walk the rhs.  */
2784   rss = gfc_walk_expr (expr2);
2785   if (rss == gfc_ss_terminator)
2786    {
2787      /* The rhs is scalar.  Add a ss for the expression.  */
2788      rss = gfc_get_ss ();
2789      rss->next = gfc_ss_terminator;
2790      rss->type = GFC_SS_SCALAR;
2791      rss->expr = expr2;
2792     }
2793
2794   /* Associate the SS with the loop.  */
2795   gfc_add_ss_to_loop (&loop, lss);
2796   gfc_add_ss_to_loop (&loop, rss);
2797
2798   /* Calculate the bounds of the scalarization.  */
2799   gfc_conv_ss_startstride (&loop);
2800
2801   /* Resolve any data dependencies in the statement.  */
2802   gfc_conv_resolve_dependencies (&loop, lss_section, rss);
2803
2804   /* Setup the scalarizing loops.  */
2805   gfc_conv_loop_setup (&loop);
2806
2807   /* Setup the gfc_se structures.  */
2808   gfc_copy_loopinfo_to_se (&lse, &loop);
2809   gfc_copy_loopinfo_to_se (&rse, &loop);
2810
2811   rse.ss = rss;
2812   gfc_mark_ss_chain_used (rss, 1);
2813   if (loop.temp_ss == NULL)
2814     {
2815       lse.ss = lss;
2816       gfc_mark_ss_chain_used (lss, 1);
2817     }
2818   else
2819     {
2820       lse.ss = loop.temp_ss;
2821       gfc_mark_ss_chain_used (lss, 3);
2822       gfc_mark_ss_chain_used (loop.temp_ss, 3);
2823     }
2824
2825   /* Start the scalarized loop body.  */
2826   gfc_start_scalarized_body (&loop, &body);
2827
2828   /* Translate the expression.  */
2829   gfc_conv_expr (&rse, expr2);
2830   if (lss != gfc_ss_terminator && loop.temp_ss != NULL)
2831     {
2832       gfc_conv_tmp_array_ref (&lse);
2833       gfc_advance_se_ss_chain (&lse);
2834     }
2835   else
2836     gfc_conv_expr (&lse, expr1);
2837
2838   /* Form the mask expression according to the mask tree list.  */
2839   index = count1;
2840   tmp = mask;
2841   if (tmp != NULL)
2842     maskexpr = gfc_build_array_ref (tmp, index);
2843   else
2844     maskexpr = NULL;
2845
2846   tmp = TREE_CHAIN (tmp);
2847   while (tmp)
2848     {
2849       tmp1 = gfc_build_array_ref (tmp, index);
2850       maskexpr = build2 (TRUTH_AND_EXPR, TREE_TYPE (tmp1), maskexpr, tmp1);
2851       tmp = TREE_CHAIN (tmp);
2852     }
2853   /* Use the scalar assignment as is.  */
2854   tmp = gfc_trans_scalar_assign (&lse, &rse, expr1->ts.type);
2855   tmp = build3_v (COND_EXPR, maskexpr, tmp, build_empty_stmt ());
2856
2857   gfc_add_expr_to_block (&body, tmp);
2858
2859   if (lss == gfc_ss_terminator)
2860     {
2861       /* Increment count1.  */
2862       tmp = fold_build2 (PLUS_EXPR, gfc_array_index_type,
2863                          count1, gfc_index_one_node);
2864       gfc_add_modify_expr (&body, count1, tmp);
2865
2866       /* Use the scalar assignment as is.  */
2867       gfc_add_block_to_block (&block, &body);
2868     }
2869   else
2870     {
2871       gcc_assert (lse.ss == gfc_ss_terminator
2872                   && rse.ss == gfc_ss_terminator);
2873
2874       if (loop.temp_ss != NULL)
2875         {
2876           /* Increment count1 before finish the main body of a scalarized
2877              expression.  */
2878           tmp = fold_build2 (PLUS_EXPR, gfc_array_index_type,
2879                              count1, gfc_index_one_node);
2880           gfc_add_modify_expr (&body, count1, tmp);
2881           gfc_trans_scalarized_loop_boundary (&loop, &body);
2882
2883           /* We need to copy the temporary to the actual lhs.  */
2884           gfc_init_se (&lse, NULL);
2885           gfc_init_se (&rse, NULL);
2886           gfc_copy_loopinfo_to_se (&lse, &loop);
2887           gfc_copy_loopinfo_to_se (&rse, &loop);
2888
2889           rse.ss = loop.temp_ss;
2890           lse.ss = lss;
2891
2892           gfc_conv_tmp_array_ref (&rse);
2893           gfc_advance_se_ss_chain (&rse);
2894           gfc_conv_expr (&lse, expr1);
2895
2896           gcc_assert (lse.ss == gfc_ss_terminator
2897                       && rse.ss == gfc_ss_terminator);
2898
2899           /* Form the mask expression according to the mask tree list.  */
2900           index = count2;
2901           tmp = mask;
2902           if (tmp != NULL)
2903             maskexpr = gfc_build_array_ref (tmp, index);
2904           else
2905             maskexpr = NULL;
2906
2907           tmp = TREE_CHAIN (tmp);
2908           while (tmp)
2909             {
2910               tmp1 = gfc_build_array_ref (tmp, index);
2911               maskexpr = build2 (TRUTH_AND_EXPR, TREE_TYPE (tmp1),
2912                                  maskexpr, tmp1);
2913               tmp = TREE_CHAIN (tmp);
2914             }
2915           /* Use the scalar assignment as is.  */
2916           tmp = gfc_trans_scalar_assign (&lse, &rse, expr1->ts.type);
2917           tmp = build3_v (COND_EXPR, maskexpr, tmp, build_empty_stmt ());
2918           gfc_add_expr_to_block (&body, tmp);
2919
2920           /* Increment count2.  */
2921           tmp = fold_build2 (PLUS_EXPR, gfc_array_index_type,
2922                              count2, gfc_index_one_node);
2923           gfc_add_modify_expr (&body, count2, tmp);
2924         }
2925       else
2926         {
2927           /* Increment count1.  */
2928           tmp = fold_build2 (PLUS_EXPR, gfc_array_index_type,
2929                              count1, gfc_index_one_node);
2930           gfc_add_modify_expr (&body, count1, tmp);
2931         }
2932
2933       /* Generate the copying loops.  */
2934       gfc_trans_scalarizing_loops (&loop, &body);
2935
2936       /* Wrap the whole thing up.  */
2937       gfc_add_block_to_block (&block, &loop.pre);
2938       gfc_add_block_to_block (&block, &loop.post);
2939       gfc_cleanup_loop (&loop);
2940     }
2941
2942   return gfc_finish_block (&block);
2943 }
2944
2945
2946 /* Translate the WHERE construct or statement.
2947    This function can be called iteratively to translate the nested WHERE
2948    construct or statement.
2949    MASK is the control mask.  */
2950
2951 static void
2952 gfc_trans_where_2 (gfc_code * code, tree mask,
2953                    forall_info * nested_forall_info, stmtblock_t * block)
2954 {
2955   stmtblock_t inner_size_body;
2956   tree inner_size, size;
2957   gfc_ss *lss, *rss;
2958   tree mask_type;
2959   gfc_expr *expr1;
2960   gfc_expr *expr2;
2961   gfc_code *cblock;
2962   gfc_code *cnext;
2963   tree tmp;
2964   tree count1, count2;
2965   int need_temp;
2966   tree pcmask = NULL_TREE;
2967   tree ppmask = NULL_TREE;
2968   tree cmask = NULL_TREE;
2969   tree pmask = NULL_TREE;
2970
2971   /* the WHERE statement or the WHERE construct statement.  */
2972   cblock = code->block;
2973
2974   /* Calculate the size of temporary needed by the mask-expr.  */
2975   gfc_init_block (&inner_size_body);
2976   inner_size = compute_inner_temp_size (cblock->expr, cblock->expr,
2977                                         &inner_size_body, &lss, &rss);
2978
2979   /* Calculate the total size of temporary needed.  */
2980   size = compute_overall_iter_number (nested_forall_info, inner_size,
2981                                       &inner_size_body, block);
2982
2983   /* As the mask array can be very big, prefer compact boolean types.  */
2984   mask_type = gfc_get_logical_type (gfc_logical_kinds[0].kind);
2985
2986   /* Allocate temporary for where mask.  */
2987   cmask = allocate_temp_for_forall_nest_1 (mask_type, size, block, &pcmask);
2988
2989   if (cblock->block)
2990     {
2991       /* Allocate temporary for !mask.  */
2992       pmask = allocate_temp_for_forall_nest_1 (mask_type, size, block,
2993                                                &ppmask);
2994     }
2995   else
2996     {
2997       ppmask = NULL_TREE;
2998       pmask = NULL_TREE;
2999     }
3000
3001   while (cblock)
3002     {
3003       /* Has mask-expr.  */
3004       if (cblock->expr)
3005         {
3006           /* If this is the last clause of the WHERE construct, then
3007              we don't need to update the pending control mask (pmask).  */
3008           if (! cblock->block)
3009             pmask = NULL_TREE;
3010
3011           /* Ensure that the WHERE mask be evaluated only once.  */
3012           gfc_evaluate_where_mask (cblock->expr, nested_forall_info,
3013                                    mask, cmask, pmask, mask_type, block);
3014
3015         }
3016       /* It's a elsewhere-stmt. No mask-expr is present.  */
3017       else
3018         cmask = mask;
3019
3020       /* Get the assignment statement of a WHERE statement, or the first
3021          statement in where-body-construct of a WHERE construct.  */
3022       cnext = cblock->next;
3023       while (cnext)
3024         {
3025           switch (cnext->op)
3026             {
3027             /* WHERE assignment statement.  */
3028             case EXEC_ASSIGN:
3029               expr1 = cnext->expr;
3030               expr2 = cnext->expr2;
3031               if (nested_forall_info != NULL)
3032                 {
3033                   need_temp = gfc_check_dependency (expr1, expr2, 0);
3034                   if (need_temp)
3035                     gfc_trans_assign_need_temp (expr1, expr2, cmask,
3036                                                 nested_forall_info, block);
3037                   else
3038                     {
3039                       /* Variables to control maskexpr.  */
3040                       count1 = gfc_create_var (gfc_array_index_type, "count1");
3041                       count2 = gfc_create_var (gfc_array_index_type, "count2");
3042                       gfc_add_modify_expr (block, count1, gfc_index_zero_node);
3043                       gfc_add_modify_expr (block, count2, gfc_index_zero_node);
3044
3045                       tmp = gfc_trans_where_assign (expr1, expr2, cmask,
3046                                                     count1, count2);
3047
3048                       tmp = gfc_trans_nested_forall_loop (nested_forall_info,
3049                                                           tmp, 1, 1);
3050                       gfc_add_expr_to_block (block, tmp);
3051                     }
3052                 }
3053               else
3054                 {
3055                   /* Variables to control maskexpr.  */
3056                   count1 = gfc_create_var (gfc_array_index_type, "count1");
3057                   count2 = gfc_create_var (gfc_array_index_type, "count2");
3058                   gfc_add_modify_expr (block, count1, gfc_index_zero_node);
3059                   gfc_add_modify_expr (block, count2, gfc_index_zero_node);
3060
3061                   tmp = gfc_trans_where_assign (expr1, expr2, cmask,
3062                                                 count1, count2);
3063                   gfc_add_expr_to_block (block, tmp);
3064
3065                 }
3066               break;
3067
3068             /* WHERE or WHERE construct is part of a where-body-construct.  */
3069             case EXEC_WHERE:
3070               /* Ensure that MASK is not modified by next gfc_trans_where_2.  */
3071               gfc_trans_where_2 (cnext, cmask, nested_forall_info, block);
3072               break;
3073
3074             default:
3075               gcc_unreachable ();
3076             }
3077
3078          /* The next statement within the same where-body-construct.  */
3079          cnext = cnext->next;
3080        }
3081     /* The next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt.  */
3082     cblock = cblock->block;
3083     mask = pmask;
3084   }
3085
3086   /* If we allocated a pending mask array, deallocate it now.  */
3087   if (ppmask)
3088     {
3089       tree args = gfc_chainon_list (NULL_TREE, ppmask);
3090       tmp = build_function_call_expr (gfor_fndecl_internal_free, args);
3091       gfc_add_expr_to_block (block, tmp);
3092     }
3093
3094   /* If we allocated a current mask array, deallocate it now.  */
3095   if (pcmask)
3096     {
3097       tree args = gfc_chainon_list (NULL_TREE, pcmask);
3098       tmp = build_function_call_expr (gfor_fndecl_internal_free, args);
3099       gfc_add_expr_to_block (block, tmp);
3100     }
3101 }
3102
3103 /* Translate a simple WHERE construct or statement without dependencies.
3104    CBLOCK is the "then" clause of the WHERE statement, where CBLOCK->EXPR
3105    is the mask condition, and EBLOCK if non-NULL is the "else" clause.
3106    Currently both CBLOCK and EBLOCK are restricted to single assignments.  */
3107
3108 static tree
3109 gfc_trans_where_3 (gfc_code * cblock, gfc_code * eblock)
3110 {
3111   stmtblock_t block, body;
3112   gfc_expr *cond, *tdst, *tsrc, *edst, *esrc;
3113   tree tmp, cexpr, tstmt, estmt;
3114   gfc_ss *css, *tdss, *tsss;
3115   gfc_se cse, tdse, tsse, edse, esse;
3116   gfc_loopinfo loop;
3117   gfc_ss *edss = 0;
3118   gfc_ss *esss = 0;
3119
3120   cond = cblock->expr;
3121   tdst = cblock->next->expr;
3122   tsrc = cblock->next->expr2;
3123   edst = eblock ? eblock->next->expr : NULL;
3124   esrc = eblock ? eblock->next->expr2 : NULL;
3125
3126   gfc_start_block (&block);
3127   gfc_init_loopinfo (&loop);
3128
3129   /* Handle the condition.  */
3130   gfc_init_se (&cse, NULL);
3131   css = gfc_walk_expr (cond);
3132   gfc_add_ss_to_loop (&loop, css);
3133
3134   /* Handle the then-clause.  */
3135   gfc_init_se (&tdse, NULL);
3136   gfc_init_se (&tsse, NULL);
3137   tdss = gfc_walk_expr (tdst);
3138   tsss = gfc_walk_expr (tsrc);
3139   if (tsss == gfc_ss_terminator)
3140     {
3141       tsss = gfc_get_ss ();
3142       tsss->next = gfc_ss_terminator;
3143       tsss->type = GFC_SS_SCALAR;
3144       tsss->expr = tsrc;
3145     }
3146   gfc_add_ss_to_loop (&loop, tdss);
3147   gfc_add_ss_to_loop (&loop, tsss);
3148
3149   if (eblock)
3150     {
3151       /* Handle the else clause.  */
3152       gfc_init_se (&edse, NULL);
3153       gfc_init_se (&esse, NULL);
3154       edss = gfc_walk_expr (edst);
3155       esss = gfc_walk_expr (esrc);
3156       if (esss == gfc_ss_terminator)
3157         {
3158           esss = gfc_get_ss ();
3159           esss->next = gfc_ss_terminator;
3160           esss->type = GFC_SS_SCALAR;
3161           esss->expr = esrc;
3162         }
3163       gfc_add_ss_to_loop (&loop, edss);
3164       gfc_add_ss_to_loop (&loop, esss);
3165     }
3166
3167   gfc_conv_ss_startstride (&loop);
3168   gfc_conv_loop_setup (&loop);
3169
3170   gfc_mark_ss_chain_used (css, 1);
3171   gfc_mark_ss_chain_used (tdss, 1);
3172   gfc_mark_ss_chain_used (tsss, 1);
3173   if (eblock)
3174     {
3175       gfc_mark_ss_chain_used (edss, 1);
3176       gfc_mark_ss_chain_used (esss, 1);
3177     }
3178
3179   gfc_start_scalarized_body (&loop, &body);
3180
3181   gfc_copy_loopinfo_to_se (&cse, &loop);
3182   gfc_copy_loopinfo_to_se (&tdse, &loop);
3183   gfc_copy_loopinfo_to_se (&tsse, &loop);
3184   cse.ss = css;
3185   tdse.ss = tdss;
3186   tsse.ss = tsss;
3187   if (eblock)
3188     {
3189       gfc_copy_loopinfo_to_se (&edse, &loop);
3190       gfc_copy_loopinfo_to_se (&esse, &loop);
3191       edse.ss = edss;
3192       esse.ss = esss;
3193     }
3194
3195   gfc_conv_expr (&cse, cond);
3196   gfc_add_block_to_block (&body, &cse.pre);
3197   cexpr = cse.expr;
3198
3199   gfc_conv_expr (&tsse, tsrc);
3200   if (tdss != gfc_ss_terminator && loop.temp_ss != NULL)
3201     {
3202       gfc_conv_tmp_array_ref (&tdse);
3203       gfc_advance_se_ss_chain (&tdse);
3204     }
3205   else
3206     gfc_conv_expr (&tdse, tdst);
3207
3208   if (eblock)
3209     {
3210       gfc_conv_expr (&esse, esrc);
3211       if (edss != gfc_ss_terminator && loop.temp_ss != NULL)
3212         {
3213           gfc_conv_tmp_array_ref (&edse);
3214           gfc_advance_se_ss_chain (&edse);
3215         }
3216       else
3217         gfc_conv_expr (&edse, edst);
3218     }
3219
3220   tstmt = gfc_trans_scalar_assign (&tdse, &tsse, tdst->ts.type);
3221   estmt = eblock ? gfc_trans_scalar_assign (&edse, &esse, edst->ts.type)
3222                  : build_empty_stmt ();
3223   tmp = build3_v (COND_EXPR, cexpr, tstmt, estmt);
3224   gfc_add_expr_to_block (&body, tmp);
3225   gfc_add_block_to_block (&body, &cse.post);
3226
3227   gfc_trans_scalarizing_loops (&loop, &body);
3228   gfc_add_block_to_block (&block, &loop.pre);
3229   gfc_add_block_to_block (&block, &loop.post);
3230   gfc_cleanup_loop (&loop);
3231
3232   return gfc_finish_block (&block);
3233 }
3234
3235 /* As the WHERE or WHERE construct statement can be nested, we call
3236    gfc_trans_where_2 to do the translation, and pass the initial
3237    NULL values for both the control mask and the pending control mask.  */
3238
3239 tree
3240 gfc_trans_where (gfc_code * code)
3241 {
3242   stmtblock_t block;
3243   gfc_code *cblock;
3244   gfc_code *eblock;
3245
3246   cblock = code->block;
3247   if (cblock->next
3248       && cblock->next->op == EXEC_ASSIGN
3249       && !cblock->next->next)
3250     {
3251       eblock = cblock->block;
3252       if (!eblock)
3253         {
3254           /* A simple "WHERE (cond) x = y" statement or block is
3255              dependence free if cond is not dependent upon writing x,
3256              and the source y is unaffected by the destination x.  */
3257           if (!gfc_check_dependency (cblock->next->expr,
3258                                      cblock->expr, 0)
3259               && !gfc_check_dependency (cblock->next->expr,
3260                                         cblock->next->expr2, 0))
3261             return gfc_trans_where_3 (cblock, NULL);
3262         }
3263       else if (!eblock->expr
3264                && !eblock->block
3265                && eblock->next
3266                && eblock->next->op == EXEC_ASSIGN
3267                && !eblock->next->next)
3268         {
3269           /* A simple "WHERE (cond) x1 = y1 ELSEWHERE x2 = y2 ENDWHERE"
3270              block is dependence free if cond is not dependent on writes
3271              to x1 and x2, y1 is not dependent on writes to x2, and y2
3272              is not dependent on writes to x1, and both y's are not
3273              dependent upon their own x's.  */
3274           if (!gfc_check_dependency(cblock->next->expr,
3275                                     cblock->expr, 0)
3276               && !gfc_check_dependency(eblock->next->expr,
3277                                        cblock->expr, 0)
3278               && !gfc_check_dependency(cblock->next->expr,
3279                                        eblock->next->expr2, 0)
3280               && !gfc_check_dependency(eblock->next->expr,
3281                                        cblock->next->expr2, 0)
3282               && !gfc_check_dependency(cblock->next->expr,
3283                                        cblock->next->expr2, 0)
3284               && !gfc_check_dependency(eblock->next->expr,
3285                                        eblock->next->expr2, 0))
3286             return gfc_trans_where_3 (cblock, eblock);
3287         }
3288     }
3289
3290   gfc_start_block (&block);
3291
3292   gfc_trans_where_2 (code, NULL, NULL, &block);
3293
3294   return gfc_finish_block (&block);
3295 }
3296
3297
3298 /* CYCLE a DO loop. The label decl has already been created by
3299    gfc_trans_do(), it's in TREE_PURPOSE (backend_decl) of the gfc_code
3300    node at the head of the loop. We must mark the label as used.  */
3301
3302 tree
3303 gfc_trans_cycle (gfc_code * code)
3304 {
3305   tree cycle_label;
3306
3307   cycle_label = TREE_PURPOSE (code->ext.whichloop->backend_decl);
3308   TREE_USED (cycle_label) = 1;
3309   return build1_v (GOTO_EXPR, cycle_label);
3310 }
3311
3312
3313 /* EXIT a DO loop. Similar to CYCLE, but now the label is in
3314    TREE_VALUE (backend_decl) of the gfc_code node at the head of the
3315    loop.  */
3316
3317 tree
3318 gfc_trans_exit (gfc_code * code)
3319 {
3320   tree exit_label;
3321
3322   exit_label = TREE_VALUE (code->ext.whichloop->backend_decl);
3323   TREE_USED (exit_label) = 1;
3324   return build1_v (GOTO_EXPR, exit_label);
3325 }
3326
3327
3328 /* Translate the ALLOCATE statement.  */
3329
3330 tree
3331 gfc_trans_allocate (gfc_code * code)
3332 {
3333   gfc_alloc *al;
3334   gfc_expr *expr;
3335   gfc_se se;
3336   tree tmp;
3337   tree parm;
3338   gfc_ref *ref;
3339   tree stat;
3340   tree pstat;
3341   tree error_label;
3342   stmtblock_t block;
3343
3344   if (!code->ext.alloc_list)
3345     return NULL_TREE;
3346
3347   gfc_start_block (&block);
3348
3349   if (code->expr)
3350     {
3351       tree gfc_int4_type_node = gfc_get_int_type (4);
3352
3353       stat = gfc_create_var (gfc_int4_type_node, "stat");
3354       pstat = build_fold_addr_expr (stat);
3355
3356       error_label = gfc_build_label_decl (NULL_TREE);
3357       TREE_USED (error_label) = 1;
3358     }
3359   else
3360     {
3361       pstat = integer_zero_node;
3362       stat = error_label = NULL_TREE;
3363     }
3364
3365
3366   for (al = code->ext.alloc_list; al != NULL; al = al->next)
3367     {
3368       expr = al->expr;
3369
3370       gfc_init_se (&se, NULL);
3371       gfc_start_block (&se.pre);
3372
3373       se.want_pointer = 1;
3374       se.descriptor_only = 1;
3375       gfc_conv_expr (&se, expr);
3376
3377       ref = expr->ref;
3378
3379       /* Find the last reference in the chain.  */
3380       while (ref && ref->next != NULL)
3381         {
3382           gcc_assert (ref->type != REF_ARRAY || ref->u.ar.type == AR_ELEMENT);
3383           ref = ref->next;
3384         }
3385
3386       if (ref != NULL && ref->type == REF_ARRAY)
3387         {
3388           /* An array.  */
3389           gfc_array_allocate (&se, ref, pstat);
3390         }
3391       else
3392         {
3393           /* A scalar or derived type.  */
3394           tree val;
3395
3396           val = gfc_create_var (ppvoid_type_node, "ptr");
3397           tmp = gfc_build_addr_expr (ppvoid_type_node, se.expr);
3398           gfc_add_modify_expr (&se.pre, val, tmp);
3399
3400           tmp = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (se.expr)));
3401
3402           if (expr->ts.type == BT_CHARACTER && tmp == NULL_TREE)
3403             tmp = se.string_length;
3404
3405           parm = gfc_chainon_list (NULL_TREE, val);
3406           parm = gfc_chainon_list (parm, tmp);
3407           parm = gfc_chainon_list (parm, pstat);
3408           tmp = build_function_call_expr (gfor_fndecl_allocate, parm);
3409           gfc_add_expr_to_block (&se.pre, tmp);
3410
3411           if (code->expr)
3412             {
3413               tmp = build1_v (GOTO_EXPR, error_label);
3414               parm = fold_build2 (NE_EXPR, boolean_type_node,
3415                                   stat, build_int_cst (TREE_TYPE (stat), 0));
3416               tmp = fold_build3 (COND_EXPR, void_type_node,
3417                                  parm, tmp, build_empty_stmt ());
3418               gfc_add_expr_to_block (&se.pre, tmp);
3419             }
3420         }
3421
3422       tmp = gfc_finish_block (&se.pre);
3423       gfc_add_expr_to_block (&block, tmp);
3424     }
3425
3426   /* Assign the value to the status variable.  */
3427   if (code->expr)
3428     {
3429       tmp = build1_v (LABEL_EXPR, error_label);
3430       gfc_add_expr_to_block (&block, tmp);
3431
3432       gfc_init_se (&se, NULL);
3433       gfc_conv_expr_lhs (&se, code->expr);
3434       tmp = convert (TREE_TYPE (se.expr), stat);
3435       gfc_add_modify_expr (&block, se.expr, tmp);
3436     }
3437
3438   return gfc_finish_block (&block);
3439 }
3440
3441
3442 /* Translate a DEALLOCATE statement.
3443    There are two cases within the for loop:
3444    (1) deallocate(a1, a2, a3) is translated into the following sequence
3445        _gfortran_deallocate(a1, 0B)
3446        _gfortran_deallocate(a2, 0B)
3447        _gfortran_deallocate(a3, 0B)
3448        where the STAT= variable is passed a NULL pointer.
3449    (2) deallocate(a1, a2, a3, stat=i) is translated into the following
3450        astat = 0
3451        _gfortran_deallocate(a1, &stat)
3452        astat = astat + stat
3453        _gfortran_deallocate(a2, &stat)
3454        astat = astat + stat
3455        _gfortran_deallocate(a3, &stat)
3456        astat = astat + stat
3457     In case (1), we simply return at the end of the for loop.  In case (2)
3458     we set STAT= astat.  */
3459 tree
3460 gfc_trans_deallocate (gfc_code * code)
3461 {
3462   gfc_se se;
3463   gfc_alloc *al;
3464   gfc_expr *expr;
3465   tree apstat, astat, parm, pstat, stat, tmp, type, var;
3466   stmtblock_t block;
3467
3468   gfc_start_block (&block);
3469
3470   /* Set up the optional STAT= */
3471   if (code->expr)
3472     {
3473       tree gfc_int4_type_node = gfc_get_int_type (4);
3474
3475       /* Variable used with the library call.  */
3476       stat = gfc_create_var (gfc_int4_type_node, "stat");
3477       pstat = build_fold_addr_expr (stat);
3478
3479       /* Running total of possible deallocation failures.  */
3480       astat = gfc_create_var (gfc_int4_type_node, "astat");
3481       apstat = build_fold_addr_expr (astat);
3482
3483       /* Initialize astat to 0.  */
3484       gfc_add_modify_expr (&block, astat, build_int_cst (TREE_TYPE (astat), 0));
3485     }
3486   else
3487     {
3488       pstat = apstat = null_pointer_node;
3489       stat = astat = NULL_TREE;
3490     }
3491
3492   for (al = code->ext.alloc_list; al != NULL; al = al->next)
3493     {
3494       expr = al->expr;
3495       gcc_assert (expr->expr_type == EXPR_VARIABLE);
3496
3497       gfc_init_se (&se, NULL);
3498       gfc_start_block (&se.pre);
3499
3500       se.want_pointer = 1;
3501       se.descriptor_only = 1;
3502       gfc_conv_expr (&se, expr);
3503
3504       if (expr->rank)
3505         tmp = gfc_array_deallocate (se.expr, pstat);
3506       else
3507         {
3508           type = build_pointer_type (TREE_TYPE (se.expr));
3509           var = gfc_create_var (type, "ptr");
3510           tmp = gfc_build_addr_expr (type, se.expr);
3511           gfc_add_modify_expr (&se.pre, var, tmp);
3512
3513           parm = gfc_chainon_list (NULL_TREE, var);
3514           parm = gfc_chainon_list (parm, pstat);
3515           tmp = build_function_call_expr (gfor_fndecl_deallocate, parm);
3516         }
3517
3518       gfc_add_expr_to_block (&se.pre, tmp);
3519
3520       /* Keep track of the number of failed deallocations by adding stat
3521          of the last deallocation to the running total.  */
3522       if (code->expr)
3523         {
3524           apstat = build2 (PLUS_EXPR, TREE_TYPE (stat), astat, stat);
3525           gfc_add_modify_expr (&se.pre, astat, apstat);
3526         }
3527
3528       tmp = gfc_finish_block (&se.pre);
3529       gfc_add_expr_to_block (&block, tmp);
3530
3531     }
3532
3533   /* Assign the value to the status variable.  */
3534   if (code->expr)
3535     {
3536       gfc_init_se (&se, NULL);
3537       gfc_conv_expr_lhs (&se, code->expr);
3538       tmp = convert (TREE_TYPE (se.expr), astat);
3539       gfc_add_modify_expr (&block, se.expr, tmp);
3540     }
3541
3542   return gfc_finish_block (&block);
3543 }
3544