xref: /netbsd-src/external/gpl3/gcc/dist/gcc/fortran/trans-intrinsic.cc (revision 0a3071956a3a9fdebdbf7f338cf2d439b45fc728)
1 /* Intrinsic translation
2    Copyright (C) 2002-2022 Free Software Foundation, Inc.
3    Contributed by Paul Brook <paul@nowt.org>
4    and Steven Bosscher <s.bosscher@student.tudelft.nl>
5 
6 This file is part of GCC.
7 
8 GCC is free software; you can redistribute it and/or modify it under
9 the terms of the GNU General Public License as published by the Free
10 Software Foundation; either version 3, or (at your option) any later
11 version.
12 
13 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
14 WARRANTY; without even the implied warranty of MERCHANTABILITY or
15 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
16 for more details.
17 
18 You should have received a copy of the GNU General Public License
19 along with GCC; see the file COPYING3.  If not see
20 <http://www.gnu.org/licenses/>.  */
21 
22 /* trans-intrinsic.cc-- generate GENERIC trees for calls to intrinsics.  */
23 
24 #include "config.h"
25 #include "system.h"
26 #include "coretypes.h"
27 #include "memmodel.h"
28 #include "tm.h"		/* For UNITS_PER_WORD.  */
29 #include "tree.h"
30 #include "gfortran.h"
31 #include "trans.h"
32 #include "stringpool.h"
33 #include "fold-const.h"
34 #include "internal-fn.h"
35 #include "tree-nested.h"
36 #include "stor-layout.h"
37 #include "toplev.h"	/* For rest_of_decl_compilation.  */
38 #include "arith.h"
39 #include "trans-const.h"
40 #include "trans-types.h"
41 #include "trans-array.h"
42 #include "dependency.h"	/* For CAF array alias analysis.  */
43 #include "attribs.h"
44 #include "realmpfr.h"
45 
46 /* Only for gfc_trans_assign and gfc_trans_pointer_assign.  */
47 
48 /* This maps Fortran intrinsic math functions to external library or GCC
49    builtin functions.  */
50 typedef struct GTY(()) gfc_intrinsic_map_t {
51   /* The explicit enum is required to work around inadequacies in the
52      garbage collection/gengtype parsing mechanism.  */
53   enum gfc_isym_id id;
54 
55   /* Enum value from the "language-independent", aka C-centric, part
56      of gcc, or END_BUILTINS of no such value set.  */
57   enum built_in_function float_built_in;
58   enum built_in_function double_built_in;
59   enum built_in_function long_double_built_in;
60   enum built_in_function complex_float_built_in;
61   enum built_in_function complex_double_built_in;
62   enum built_in_function complex_long_double_built_in;
63 
64   /* True if the naming pattern is to prepend "c" for complex and
65      append "f" for kind=4.  False if the naming pattern is to
66      prepend "_gfortran_" and append "[rc](4|8|10|16)".  */
67   bool libm_name;
68 
69   /* True if a complex version of the function exists.  */
70   bool complex_available;
71 
72   /* True if the function should be marked const.  */
73   bool is_constant;
74 
75   /* The base library name of this function.  */
76   const char *name;
77 
78   /* Cache decls created for the various operand types.  */
79   tree real4_decl;
80   tree real8_decl;
81   tree real10_decl;
82   tree real16_decl;
83   tree complex4_decl;
84   tree complex8_decl;
85   tree complex10_decl;
86   tree complex16_decl;
87 }
88 gfc_intrinsic_map_t;
89 
90 /* ??? The NARGS==1 hack here is based on the fact that (c99 at least)
91    defines complex variants of all of the entries in mathbuiltins.def
92    except for atan2.  */
93 #define DEFINE_MATH_BUILTIN(ID, NAME, ARGTYPE) \
94   { GFC_ISYM_ ## ID, BUILT_IN_ ## ID ## F, BUILT_IN_ ## ID, \
95     BUILT_IN_ ## ID ## L, END_BUILTINS, END_BUILTINS, END_BUILTINS, \
96     true, false, true, NAME, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, \
97     NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE},
98 
99 #define DEFINE_MATH_BUILTIN_C(ID, NAME, ARGTYPE) \
100   { GFC_ISYM_ ## ID, BUILT_IN_ ## ID ## F, BUILT_IN_ ## ID, \
101     BUILT_IN_ ## ID ## L, BUILT_IN_C ## ID ## F, BUILT_IN_C ## ID, \
102     BUILT_IN_C ## ID ## L, true, true, true, NAME, NULL_TREE, NULL_TREE, \
103     NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE},
104 
105 #define LIB_FUNCTION(ID, NAME, HAVE_COMPLEX) \
106   { GFC_ISYM_ ## ID, END_BUILTINS, END_BUILTINS, END_BUILTINS, \
107     END_BUILTINS, END_BUILTINS, END_BUILTINS, \
108     false, HAVE_COMPLEX, true, NAME, NULL_TREE, NULL_TREE, NULL_TREE, \
109     NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE }
110 
111 #define OTHER_BUILTIN(ID, NAME, TYPE, CONST) \
112   { GFC_ISYM_NONE, BUILT_IN_ ## ID ## F, BUILT_IN_ ## ID, \
113     BUILT_IN_ ## ID ## L, END_BUILTINS, END_BUILTINS, END_BUILTINS, \
114     true, false, CONST, NAME, NULL_TREE, NULL_TREE, \
115     NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE},
116 
117 static GTY(()) gfc_intrinsic_map_t gfc_intrinsic_map[] =
118 {
119   /* Functions built into gcc itself (DEFINE_MATH_BUILTIN and
120      DEFINE_MATH_BUILTIN_C), then the built-ins that don't correspond
121      to any GFC_ISYM id directly, which use the OTHER_BUILTIN macro.  */
122 #include "mathbuiltins.def"
123 
124   /* Functions in libgfortran.  */
125   LIB_FUNCTION (ERFC_SCALED, "erfc_scaled", false),
126   LIB_FUNCTION (SIND, "sind", false),
127   LIB_FUNCTION (COSD, "cosd", false),
128   LIB_FUNCTION (TAND, "tand", false),
129 
130   /* End the list.  */
131   LIB_FUNCTION (NONE, NULL, false)
132 
133 };
134 #undef OTHER_BUILTIN
135 #undef LIB_FUNCTION
136 #undef DEFINE_MATH_BUILTIN
137 #undef DEFINE_MATH_BUILTIN_C
138 
139 
140 enum rounding_mode { RND_ROUND, RND_TRUNC, RND_CEIL, RND_FLOOR };
141 
142 
143 /* Find the correct variant of a given builtin from its argument.  */
144 static tree
builtin_decl_for_precision(enum built_in_function base_built_in,int precision)145 builtin_decl_for_precision (enum built_in_function base_built_in,
146 			    int precision)
147 {
148   enum built_in_function i = END_BUILTINS;
149 
150   gfc_intrinsic_map_t *m;
151   for (m = gfc_intrinsic_map; m->double_built_in != base_built_in ; m++)
152     ;
153 
154   if (precision == TYPE_PRECISION (float_type_node))
155     i = m->float_built_in;
156   else if (precision == TYPE_PRECISION (double_type_node))
157     i = m->double_built_in;
158   else if (precision == TYPE_PRECISION (long_double_type_node)
159 	   && (!gfc_real16_is_float128
160 	       || long_double_type_node != gfc_float128_type_node))
161     i = m->long_double_built_in;
162   else if (precision == TYPE_PRECISION (gfc_float128_type_node))
163     {
164       /* Special treatment, because it is not exactly a built-in, but
165 	 a library function.  */
166       return m->real16_decl;
167     }
168 
169   return (i == END_BUILTINS ? NULL_TREE : builtin_decl_explicit (i));
170 }
171 
172 
173 tree
gfc_builtin_decl_for_float_kind(enum built_in_function double_built_in,int kind)174 gfc_builtin_decl_for_float_kind (enum built_in_function double_built_in,
175 				 int kind)
176 {
177   int i = gfc_validate_kind (BT_REAL, kind, false);
178 
179   if (gfc_real_kinds[i].c_float128)
180     {
181       /* For _Float128, the story is a bit different, because we return
182 	 a decl to a library function rather than a built-in.  */
183       gfc_intrinsic_map_t *m;
184       for (m = gfc_intrinsic_map; m->double_built_in != double_built_in ; m++)
185 	;
186 
187       return m->real16_decl;
188     }
189 
190   return builtin_decl_for_precision (double_built_in,
191 				     gfc_real_kinds[i].mode_precision);
192 }
193 
194 
195 /* Evaluate the arguments to an intrinsic function.  The value
196    of NARGS may be less than the actual number of arguments in EXPR
197    to allow optional "KIND" arguments that are not included in the
198    generated code to be ignored.  */
199 
200 static void
gfc_conv_intrinsic_function_args(gfc_se * se,gfc_expr * expr,tree * argarray,int nargs)201 gfc_conv_intrinsic_function_args (gfc_se *se, gfc_expr *expr,
202 				  tree *argarray, int nargs)
203 {
204   gfc_actual_arglist *actual;
205   gfc_expr *e;
206   gfc_intrinsic_arg  *formal;
207   gfc_se argse;
208   int curr_arg;
209 
210   formal = expr->value.function.isym->formal;
211   actual = expr->value.function.actual;
212 
213    for (curr_arg = 0; curr_arg < nargs; curr_arg++,
214 	actual = actual->next,
215 	formal = formal ? formal->next : NULL)
216     {
217       gcc_assert (actual);
218       e = actual->expr;
219       /* Skip omitted optional arguments.  */
220       if (!e)
221 	{
222 	  --curr_arg;
223 	  continue;
224 	}
225 
226       /* Evaluate the parameter.  This will substitute scalarized
227          references automatically.  */
228       gfc_init_se (&argse, se);
229 
230       if (e->ts.type == BT_CHARACTER)
231 	{
232 	  gfc_conv_expr (&argse, e);
233 	  gfc_conv_string_parameter (&argse);
234           argarray[curr_arg++] = argse.string_length;
235 	  gcc_assert (curr_arg < nargs);
236 	}
237       else
238         gfc_conv_expr_val (&argse, e);
239 
240       /* If an optional argument is itself an optional dummy argument,
241 	 check its presence and substitute a null if absent.  */
242       if (e->expr_type == EXPR_VARIABLE
243 	    && e->symtree->n.sym->attr.optional
244 	    && formal
245 	    && formal->optional)
246 	gfc_conv_missing_dummy (&argse, e, formal->ts, 0);
247 
248       gfc_add_block_to_block (&se->pre, &argse.pre);
249       gfc_add_block_to_block (&se->post, &argse.post);
250       argarray[curr_arg] = argse.expr;
251     }
252 }
253 
254 /* Count the number of actual arguments to the intrinsic function EXPR
255    including any "hidden" string length arguments.  */
256 
257 static unsigned int
gfc_intrinsic_argument_list_length(gfc_expr * expr)258 gfc_intrinsic_argument_list_length (gfc_expr *expr)
259 {
260   int n = 0;
261   gfc_actual_arglist *actual;
262 
263   for (actual = expr->value.function.actual; actual; actual = actual->next)
264     {
265       if (!actual->expr)
266 	continue;
267 
268       if (actual->expr->ts.type == BT_CHARACTER)
269 	n += 2;
270       else
271 	n++;
272     }
273 
274   return n;
275 }
276 
277 
278 /* Conversions between different types are output by the frontend as
279    intrinsic functions.  We implement these directly with inline code.  */
280 
281 static void
gfc_conv_intrinsic_conversion(gfc_se * se,gfc_expr * expr)282 gfc_conv_intrinsic_conversion (gfc_se * se, gfc_expr * expr)
283 {
284   tree type;
285   tree *args;
286   int nargs;
287 
288   nargs = gfc_intrinsic_argument_list_length (expr);
289   args = XALLOCAVEC (tree, nargs);
290 
291   /* Evaluate all the arguments passed. Whilst we're only interested in the
292      first one here, there are other parts of the front-end that assume this
293      and will trigger an ICE if it's not the case.  */
294   type = gfc_typenode_for_spec (&expr->ts);
295   gcc_assert (expr->value.function.actual->expr);
296   gfc_conv_intrinsic_function_args (se, expr, args, nargs);
297 
298   /* Conversion between character kinds involves a call to a library
299      function.  */
300   if (expr->ts.type == BT_CHARACTER)
301     {
302       tree fndecl, var, addr, tmp;
303 
304       if (expr->ts.kind == 1
305 	  && expr->value.function.actual->expr->ts.kind == 4)
306 	fndecl = gfor_fndecl_convert_char4_to_char1;
307       else if (expr->ts.kind == 4
308 	       && expr->value.function.actual->expr->ts.kind == 1)
309 	fndecl = gfor_fndecl_convert_char1_to_char4;
310       else
311 	gcc_unreachable ();
312 
313       /* Create the variable storing the converted value.  */
314       type = gfc_get_pchar_type (expr->ts.kind);
315       var = gfc_create_var (type, "str");
316       addr = gfc_build_addr_expr (build_pointer_type (type), var);
317 
318       /* Call the library function that will perform the conversion.  */
319       gcc_assert (nargs >= 2);
320       tmp = build_call_expr_loc (input_location,
321 			     fndecl, 3, addr, args[0], args[1]);
322       gfc_add_expr_to_block (&se->pre, tmp);
323 
324       /* Free the temporary afterwards.  */
325       tmp = gfc_call_free (var);
326       gfc_add_expr_to_block (&se->post, tmp);
327 
328       se->expr = var;
329       se->string_length = args[0];
330 
331       return;
332     }
333 
334   /* Conversion from complex to non-complex involves taking the real
335      component of the value.  */
336   if (TREE_CODE (TREE_TYPE (args[0])) == COMPLEX_TYPE
337       && expr->ts.type != BT_COMPLEX)
338     {
339       tree artype;
340 
341       artype = TREE_TYPE (TREE_TYPE (args[0]));
342       args[0] = fold_build1_loc (input_location, REALPART_EXPR, artype,
343 				 args[0]);
344     }
345 
346   se->expr = convert (type, args[0]);
347 }
348 
349 /* This is needed because the gcc backend only implements
350    FIX_TRUNC_EXPR, which is the same as INT() in Fortran.
351    FLOOR(x) = INT(x) <= x ? INT(x) : INT(x) - 1
352    Similarly for CEILING.  */
353 
354 static tree
build_fixbound_expr(stmtblock_t * pblock,tree arg,tree type,int up)355 build_fixbound_expr (stmtblock_t * pblock, tree arg, tree type, int up)
356 {
357   tree tmp;
358   tree cond;
359   tree argtype;
360   tree intval;
361 
362   argtype = TREE_TYPE (arg);
363   arg = gfc_evaluate_now (arg, pblock);
364 
365   intval = convert (type, arg);
366   intval = gfc_evaluate_now (intval, pblock);
367 
368   tmp = convert (argtype, intval);
369   cond = fold_build2_loc (input_location, up ? GE_EXPR : LE_EXPR,
370 			  logical_type_node, tmp, arg);
371 
372   tmp = fold_build2_loc (input_location, up ? PLUS_EXPR : MINUS_EXPR, type,
373 			 intval, build_int_cst (type, 1));
374   tmp = fold_build3_loc (input_location, COND_EXPR, type, cond, intval, tmp);
375   return tmp;
376 }
377 
378 
379 /* Round to nearest integer, away from zero.  */
380 
381 static tree
build_round_expr(tree arg,tree restype)382 build_round_expr (tree arg, tree restype)
383 {
384   tree argtype;
385   tree fn;
386   int argprec, resprec;
387 
388   argtype = TREE_TYPE (arg);
389   argprec = TYPE_PRECISION (argtype);
390   resprec = TYPE_PRECISION (restype);
391 
392   /* Depending on the type of the result, choose the int intrinsic (iround,
393      available only as a builtin, therefore cannot use it for _Float128), long
394      int intrinsic (lround family) or long long intrinsic (llround).  If we
395      don't have an appropriate function that converts directly to the integer
396      type (such as kind == 16), just use ROUND, and then convert the result to
397      an integer.  We might also need to convert the result afterwards.  */
398   if (resprec <= INT_TYPE_SIZE && argprec <= LONG_DOUBLE_TYPE_SIZE)
399     fn = builtin_decl_for_precision (BUILT_IN_IROUND, argprec);
400   else if (resprec <= LONG_TYPE_SIZE)
401     fn = builtin_decl_for_precision (BUILT_IN_LROUND, argprec);
402   else if (resprec <= LONG_LONG_TYPE_SIZE)
403     fn = builtin_decl_for_precision (BUILT_IN_LLROUND, argprec);
404   else if (resprec >= argprec)
405     fn = builtin_decl_for_precision (BUILT_IN_ROUND, argprec);
406   else
407     gcc_unreachable ();
408 
409   return convert (restype, build_call_expr_loc (input_location,
410 						fn, 1, arg));
411 }
412 
413 
414 /* Convert a real to an integer using a specific rounding mode.
415    Ideally we would just build the corresponding GENERIC node,
416    however the RTL expander only actually supports FIX_TRUNC_EXPR.  */
417 
418 static tree
build_fix_expr(stmtblock_t * pblock,tree arg,tree type,enum rounding_mode op)419 build_fix_expr (stmtblock_t * pblock, tree arg, tree type,
420                enum rounding_mode op)
421 {
422   switch (op)
423     {
424     case RND_FLOOR:
425       return build_fixbound_expr (pblock, arg, type, 0);
426 
427     case RND_CEIL:
428       return build_fixbound_expr (pblock, arg, type, 1);
429 
430     case RND_ROUND:
431       return build_round_expr (arg, type);
432 
433     case RND_TRUNC:
434       return fold_build1_loc (input_location, FIX_TRUNC_EXPR, type, arg);
435 
436     default:
437       gcc_unreachable ();
438     }
439 }
440 
441 
442 /* Round a real value using the specified rounding mode.
443    We use a temporary integer of that same kind size as the result.
444    Values larger than those that can be represented by this kind are
445    unchanged, as they will not be accurate enough to represent the
446    rounding.
447     huge = HUGE (KIND (a))
448     aint (a) = ((a > huge) || (a < -huge)) ? a : (real)(int)a
449    */
450 
451 static void
gfc_conv_intrinsic_aint(gfc_se * se,gfc_expr * expr,enum rounding_mode op)452 gfc_conv_intrinsic_aint (gfc_se * se, gfc_expr * expr, enum rounding_mode op)
453 {
454   tree type;
455   tree itype;
456   tree arg[2];
457   tree tmp;
458   tree cond;
459   tree decl;
460   mpfr_t huge;
461   int n, nargs;
462   int kind;
463 
464   kind = expr->ts.kind;
465   nargs = gfc_intrinsic_argument_list_length (expr);
466 
467   decl = NULL_TREE;
468   /* We have builtin functions for some cases.  */
469   switch (op)
470     {
471     case RND_ROUND:
472       decl = gfc_builtin_decl_for_float_kind (BUILT_IN_ROUND, kind);
473       break;
474 
475     case RND_TRUNC:
476       decl = gfc_builtin_decl_for_float_kind (BUILT_IN_TRUNC, kind);
477       break;
478 
479     default:
480       gcc_unreachable ();
481     }
482 
483   /* Evaluate the argument.  */
484   gcc_assert (expr->value.function.actual->expr);
485   gfc_conv_intrinsic_function_args (se, expr, arg, nargs);
486 
487   /* Use a builtin function if one exists.  */
488   if (decl != NULL_TREE)
489     {
490       se->expr = build_call_expr_loc (input_location, decl, 1, arg[0]);
491       return;
492     }
493 
494   /* This code is probably redundant, but we'll keep it lying around just
495      in case.  */
496   type = gfc_typenode_for_spec (&expr->ts);
497   arg[0] = gfc_evaluate_now (arg[0], &se->pre);
498 
499   /* Test if the value is too large to handle sensibly.  */
500   gfc_set_model_kind (kind);
501   mpfr_init (huge);
502   n = gfc_validate_kind (BT_INTEGER, kind, false);
503   mpfr_set_z (huge, gfc_integer_kinds[n].huge, GFC_RND_MODE);
504   tmp = gfc_conv_mpfr_to_tree (huge, kind, 0);
505   cond = fold_build2_loc (input_location, LT_EXPR, logical_type_node, arg[0],
506 			  tmp);
507 
508   mpfr_neg (huge, huge, GFC_RND_MODE);
509   tmp = gfc_conv_mpfr_to_tree (huge, kind, 0);
510   tmp = fold_build2_loc (input_location, GT_EXPR, logical_type_node, arg[0],
511 			 tmp);
512   cond = fold_build2_loc (input_location, TRUTH_AND_EXPR, logical_type_node,
513 			  cond, tmp);
514   itype = gfc_get_int_type (kind);
515 
516   tmp = build_fix_expr (&se->pre, arg[0], itype, op);
517   tmp = convert (type, tmp);
518   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond, tmp,
519 			      arg[0]);
520   mpfr_clear (huge);
521 }
522 
523 
524 /* Convert to an integer using the specified rounding mode.  */
525 
526 static void
gfc_conv_intrinsic_int(gfc_se * se,gfc_expr * expr,enum rounding_mode op)527 gfc_conv_intrinsic_int (gfc_se * se, gfc_expr * expr, enum rounding_mode op)
528 {
529   tree type;
530   tree *args;
531   int nargs;
532 
533   nargs = gfc_intrinsic_argument_list_length (expr);
534   args = XALLOCAVEC (tree, nargs);
535 
536   /* Evaluate the argument, we process all arguments even though we only
537      use the first one for code generation purposes.  */
538   type = gfc_typenode_for_spec (&expr->ts);
539   gcc_assert (expr->value.function.actual->expr);
540   gfc_conv_intrinsic_function_args (se, expr, args, nargs);
541 
542   if (TREE_CODE (TREE_TYPE (args[0])) == INTEGER_TYPE)
543     {
544       /* Conversion to a different integer kind.  */
545       se->expr = convert (type, args[0]);
546     }
547   else
548     {
549       /* Conversion from complex to non-complex involves taking the real
550          component of the value.  */
551       if (TREE_CODE (TREE_TYPE (args[0])) == COMPLEX_TYPE
552 	  && expr->ts.type != BT_COMPLEX)
553 	{
554 	  tree artype;
555 
556 	  artype = TREE_TYPE (TREE_TYPE (args[0]));
557 	  args[0] = fold_build1_loc (input_location, REALPART_EXPR, artype,
558 				     args[0]);
559 	}
560 
561       se->expr = build_fix_expr (&se->pre, args[0], type, op);
562     }
563 }
564 
565 
566 /* Get the imaginary component of a value.  */
567 
568 static void
gfc_conv_intrinsic_imagpart(gfc_se * se,gfc_expr * expr)569 gfc_conv_intrinsic_imagpart (gfc_se * se, gfc_expr * expr)
570 {
571   tree arg;
572 
573   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
574   se->expr = fold_build1_loc (input_location, IMAGPART_EXPR,
575 			      TREE_TYPE (TREE_TYPE (arg)), arg);
576 }
577 
578 
579 /* Get the complex conjugate of a value.  */
580 
581 static void
gfc_conv_intrinsic_conjg(gfc_se * se,gfc_expr * expr)582 gfc_conv_intrinsic_conjg (gfc_se * se, gfc_expr * expr)
583 {
584   tree arg;
585 
586   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
587   se->expr = fold_build1_loc (input_location, CONJ_EXPR, TREE_TYPE (arg), arg);
588 }
589 
590 
591 
592 static tree
define_quad_builtin(const char * name,tree type,bool is_const)593 define_quad_builtin (const char *name, tree type, bool is_const)
594 {
595   tree fndecl;
596   fndecl = build_decl (input_location, FUNCTION_DECL, get_identifier (name),
597 		       type);
598 
599   /* Mark the decl as external.  */
600   DECL_EXTERNAL (fndecl) = 1;
601   TREE_PUBLIC (fndecl) = 1;
602 
603   /* Mark it __attribute__((const)).  */
604   TREE_READONLY (fndecl) = is_const;
605 
606   rest_of_decl_compilation (fndecl, 1, 0);
607 
608   return fndecl;
609 }
610 
611 /* Add SIMD attribute for FNDECL built-in if the built-in
612    name is in VECTORIZED_BUILTINS.  */
613 
614 static void
add_simd_flag_for_built_in(tree fndecl)615 add_simd_flag_for_built_in (tree fndecl)
616 {
617   if (gfc_vectorized_builtins == NULL
618       || fndecl == NULL_TREE)
619     return;
620 
621   const char *name = IDENTIFIER_POINTER (DECL_NAME (fndecl));
622   int *clauses = gfc_vectorized_builtins->get (name);
623   if (clauses)
624     {
625       for (unsigned i = 0; i < 3; i++)
626 	if (*clauses & (1 << i))
627 	  {
628 	    gfc_simd_clause simd_type = (gfc_simd_clause)*clauses;
629 	    tree omp_clause = NULL_TREE;
630 	    if (simd_type == SIMD_NONE)
631 	      ; /* No SIMD clause.  */
632 	    else
633 	      {
634 		omp_clause_code code
635 		  = (simd_type == SIMD_INBRANCH
636 		     ? OMP_CLAUSE_INBRANCH : OMP_CLAUSE_NOTINBRANCH);
637 		omp_clause = build_omp_clause (UNKNOWN_LOCATION, code);
638 		omp_clause = build_tree_list (NULL_TREE, omp_clause);
639 	      }
640 
641 	    DECL_ATTRIBUTES (fndecl)
642 	      = tree_cons (get_identifier ("omp declare simd"), omp_clause,
643 			   DECL_ATTRIBUTES (fndecl));
644 	  }
645     }
646 }
647 
648   /* Set SIMD attribute to all built-in functions that are mentioned
649      in gfc_vectorized_builtins vector.  */
650 
651 void
gfc_adjust_builtins(void)652 gfc_adjust_builtins (void)
653 {
654   gfc_intrinsic_map_t *m;
655   for (m = gfc_intrinsic_map;
656        m->id != GFC_ISYM_NONE || m->double_built_in != END_BUILTINS; m++)
657     {
658       add_simd_flag_for_built_in (m->real4_decl);
659       add_simd_flag_for_built_in (m->complex4_decl);
660       add_simd_flag_for_built_in (m->real8_decl);
661       add_simd_flag_for_built_in (m->complex8_decl);
662       add_simd_flag_for_built_in (m->real10_decl);
663       add_simd_flag_for_built_in (m->complex10_decl);
664       add_simd_flag_for_built_in (m->real16_decl);
665       add_simd_flag_for_built_in (m->complex16_decl);
666       add_simd_flag_for_built_in (m->real16_decl);
667       add_simd_flag_for_built_in (m->complex16_decl);
668     }
669 
670   /* Release all strings.  */
671   if (gfc_vectorized_builtins != NULL)
672     {
673       for (hash_map<nofree_string_hash, int>::iterator it
674 	   = gfc_vectorized_builtins->begin ();
675 	   it != gfc_vectorized_builtins->end (); ++it)
676 	free (CONST_CAST (char *, (*it).first));
677 
678       delete gfc_vectorized_builtins;
679       gfc_vectorized_builtins = NULL;
680     }
681 }
682 
683 /* Initialize function decls for library functions.  The external functions
684    are created as required.  Builtin functions are added here.  */
685 
686 void
gfc_build_intrinsic_lib_fndecls(void)687 gfc_build_intrinsic_lib_fndecls (void)
688 {
689   gfc_intrinsic_map_t *m;
690   tree quad_decls[END_BUILTINS + 1];
691 
692   if (gfc_real16_is_float128)
693   {
694     /* If we have soft-float types, we create the decls for their
695        C99-like library functions.  For now, we only handle _Float128
696        q-suffixed functions.  */
697 
698     tree type, complex_type, func_1, func_2, func_cabs, func_frexp;
699     tree func_iround, func_lround, func_llround, func_scalbn, func_cpow;
700 
701     memset (quad_decls, 0, sizeof(tree) * (END_BUILTINS + 1));
702 
703     type = gfc_float128_type_node;
704     complex_type = gfc_complex_float128_type_node;
705     /* type (*) (type) */
706     func_1 = build_function_type_list (type, type, NULL_TREE);
707     /* int (*) (type) */
708     func_iround = build_function_type_list (integer_type_node,
709 					    type, NULL_TREE);
710     /* long (*) (type) */
711     func_lround = build_function_type_list (long_integer_type_node,
712 					    type, NULL_TREE);
713     /* long long (*) (type) */
714     func_llround = build_function_type_list (long_long_integer_type_node,
715 					     type, NULL_TREE);
716     /* type (*) (type, type) */
717     func_2 = build_function_type_list (type, type, type, NULL_TREE);
718     /* type (*) (type, &int) */
719     func_frexp
720       = build_function_type_list (type,
721 				  type,
722 				  build_pointer_type (integer_type_node),
723 				  NULL_TREE);
724     /* type (*) (type, int) */
725     func_scalbn = build_function_type_list (type,
726 					    type, integer_type_node, NULL_TREE);
727     /* type (*) (complex type) */
728     func_cabs = build_function_type_list (type, complex_type, NULL_TREE);
729     /* complex type (*) (complex type, complex type) */
730     func_cpow
731       = build_function_type_list (complex_type,
732 				  complex_type, complex_type, NULL_TREE);
733 
734 #define DEFINE_MATH_BUILTIN(ID, NAME, ARGTYPE)
735 #define DEFINE_MATH_BUILTIN_C(ID, NAME, ARGTYPE)
736 #define LIB_FUNCTION(ID, NAME, HAVE_COMPLEX)
737 
738     /* Only these built-ins are actually needed here. These are used directly
739        from the code, when calling builtin_decl_for_precision() or
740        builtin_decl_for_float_type(). The others are all constructed by
741        gfc_get_intrinsic_lib_fndecl().  */
742 #define OTHER_BUILTIN(ID, NAME, TYPE, CONST) \
743   quad_decls[BUILT_IN_ ## ID] = define_quad_builtin (NAME "q", func_ ## TYPE, CONST);
744 
745 #include "mathbuiltins.def"
746 
747 #undef OTHER_BUILTIN
748 #undef LIB_FUNCTION
749 #undef DEFINE_MATH_BUILTIN
750 #undef DEFINE_MATH_BUILTIN_C
751 
752     /* There is one built-in we defined manually, because it gets called
753        with builtin_decl_for_precision() or builtin_decl_for_float_type()
754        even though it is not an OTHER_BUILTIN: it is SQRT.  */
755     quad_decls[BUILT_IN_SQRT] = define_quad_builtin ("sqrtq", func_1, true);
756 
757   }
758 
759   /* Add GCC builtin functions.  */
760   for (m = gfc_intrinsic_map;
761        m->id != GFC_ISYM_NONE || m->double_built_in != END_BUILTINS; m++)
762     {
763       if (m->float_built_in != END_BUILTINS)
764 	m->real4_decl = builtin_decl_explicit (m->float_built_in);
765       if (m->complex_float_built_in != END_BUILTINS)
766 	m->complex4_decl = builtin_decl_explicit (m->complex_float_built_in);
767       if (m->double_built_in != END_BUILTINS)
768 	m->real8_decl = builtin_decl_explicit (m->double_built_in);
769       if (m->complex_double_built_in != END_BUILTINS)
770 	m->complex8_decl = builtin_decl_explicit (m->complex_double_built_in);
771 
772       /* If real(kind=10) exists, it is always long double.  */
773       if (m->long_double_built_in != END_BUILTINS)
774 	m->real10_decl = builtin_decl_explicit (m->long_double_built_in);
775       if (m->complex_long_double_built_in != END_BUILTINS)
776 	m->complex10_decl
777 	  = builtin_decl_explicit (m->complex_long_double_built_in);
778 
779       if (!gfc_real16_is_float128)
780 	{
781 	  if (m->long_double_built_in != END_BUILTINS)
782 	    m->real16_decl = builtin_decl_explicit (m->long_double_built_in);
783 	  if (m->complex_long_double_built_in != END_BUILTINS)
784 	    m->complex16_decl
785 	      = builtin_decl_explicit (m->complex_long_double_built_in);
786 	}
787       else if (quad_decls[m->double_built_in] != NULL_TREE)
788         {
789 	  /* Quad-precision function calls are constructed when first
790 	     needed by builtin_decl_for_precision(), except for those
791 	     that will be used directly (define by OTHER_BUILTIN).  */
792 	  m->real16_decl = quad_decls[m->double_built_in];
793 	}
794       else if (quad_decls[m->complex_double_built_in] != NULL_TREE)
795         {
796 	  /* Same thing for the complex ones.  */
797 	  m->complex16_decl = quad_decls[m->double_built_in];
798 	}
799     }
800 }
801 
802 
803 /* Create a fndecl for a simple intrinsic library function.  */
804 
805 static tree
gfc_get_intrinsic_lib_fndecl(gfc_intrinsic_map_t * m,gfc_expr * expr)806 gfc_get_intrinsic_lib_fndecl (gfc_intrinsic_map_t * m, gfc_expr * expr)
807 {
808   tree type;
809   vec<tree, va_gc> *argtypes;
810   tree fndecl;
811   gfc_actual_arglist *actual;
812   tree *pdecl;
813   gfc_typespec *ts;
814   char name[GFC_MAX_SYMBOL_LEN + 3];
815 
816   ts = &expr->ts;
817   if (ts->type == BT_REAL)
818     {
819       switch (ts->kind)
820 	{
821 	case 4:
822 	  pdecl = &m->real4_decl;
823 	  break;
824 	case 8:
825 	  pdecl = &m->real8_decl;
826 	  break;
827 	case 10:
828 	  pdecl = &m->real10_decl;
829 	  break;
830 	case 16:
831 	  pdecl = &m->real16_decl;
832 	  break;
833 	default:
834 	  gcc_unreachable ();
835 	}
836     }
837   else if (ts->type == BT_COMPLEX)
838     {
839       gcc_assert (m->complex_available);
840 
841       switch (ts->kind)
842 	{
843 	case 4:
844 	  pdecl = &m->complex4_decl;
845 	  break;
846 	case 8:
847 	  pdecl = &m->complex8_decl;
848 	  break;
849 	case 10:
850 	  pdecl = &m->complex10_decl;
851 	  break;
852 	case 16:
853 	  pdecl = &m->complex16_decl;
854 	  break;
855 	default:
856 	  gcc_unreachable ();
857 	}
858     }
859   else
860     gcc_unreachable ();
861 
862   if (*pdecl)
863     return *pdecl;
864 
865   if (m->libm_name)
866     {
867       int n = gfc_validate_kind (BT_REAL, ts->kind, false);
868       if (gfc_real_kinds[n].c_float)
869 	snprintf (name, sizeof (name), "%s%s%s",
870 		  ts->type == BT_COMPLEX ? "c" : "", m->name, "f");
871       else if (gfc_real_kinds[n].c_double)
872 	snprintf (name, sizeof (name), "%s%s",
873 		  ts->type == BT_COMPLEX ? "c" : "", m->name);
874       else if (gfc_real_kinds[n].c_long_double)
875 	snprintf (name, sizeof (name), "%s%s%s",
876 		  ts->type == BT_COMPLEX ? "c" : "", m->name, "l");
877       else if (gfc_real_kinds[n].c_float128)
878 	snprintf (name, sizeof (name), "%s%s%s",
879 		  ts->type == BT_COMPLEX ? "c" : "", m->name, "q");
880       else
881 	gcc_unreachable ();
882     }
883   else
884     {
885       snprintf (name, sizeof (name), PREFIX ("%s_%c%d"), m->name,
886 		ts->type == BT_COMPLEX ? 'c' : 'r',
887 		gfc_type_abi_kind (ts));
888     }
889 
890   argtypes = NULL;
891   for (actual = expr->value.function.actual; actual; actual = actual->next)
892     {
893       type = gfc_typenode_for_spec (&actual->expr->ts);
894       vec_safe_push (argtypes, type);
895     }
896   type = build_function_type_vec (gfc_typenode_for_spec (ts), argtypes);
897   fndecl = build_decl (input_location,
898 		       FUNCTION_DECL, get_identifier (name), type);
899 
900   /* Mark the decl as external.  */
901   DECL_EXTERNAL (fndecl) = 1;
902   TREE_PUBLIC (fndecl) = 1;
903 
904   /* Mark it __attribute__((const)), if possible.  */
905   TREE_READONLY (fndecl) = m->is_constant;
906 
907   rest_of_decl_compilation (fndecl, 1, 0);
908 
909   (*pdecl) = fndecl;
910   return fndecl;
911 }
912 
913 
914 /* Convert an intrinsic function into an external or builtin call.  */
915 
916 static void
gfc_conv_intrinsic_lib_function(gfc_se * se,gfc_expr * expr)917 gfc_conv_intrinsic_lib_function (gfc_se * se, gfc_expr * expr)
918 {
919   gfc_intrinsic_map_t *m;
920   tree fndecl;
921   tree rettype;
922   tree *args;
923   unsigned int num_args;
924   gfc_isym_id id;
925 
926   id = expr->value.function.isym->id;
927   /* Find the entry for this function.  */
928   for (m = gfc_intrinsic_map;
929        m->id != GFC_ISYM_NONE || m->double_built_in != END_BUILTINS; m++)
930     {
931       if (id == m->id)
932 	break;
933     }
934 
935   if (m->id == GFC_ISYM_NONE)
936     {
937       gfc_internal_error ("Intrinsic function %qs (%d) not recognized",
938 			  expr->value.function.name, id);
939     }
940 
941   /* Get the decl and generate the call.  */
942   num_args = gfc_intrinsic_argument_list_length (expr);
943   args = XALLOCAVEC (tree, num_args);
944 
945   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
946   fndecl = gfc_get_intrinsic_lib_fndecl (m, expr);
947   rettype = TREE_TYPE (TREE_TYPE (fndecl));
948 
949   fndecl = build_addr (fndecl);
950   se->expr = build_call_array_loc (input_location, rettype, fndecl, num_args, args);
951 }
952 
953 
954 /* If bounds-checking is enabled, create code to verify at runtime that the
955    string lengths for both expressions are the same (needed for e.g. MERGE).
956    If bounds-checking is not enabled, does nothing.  */
957 
958 void
gfc_trans_same_strlen_check(const char * intr_name,locus * where,tree a,tree b,stmtblock_t * target)959 gfc_trans_same_strlen_check (const char* intr_name, locus* where,
960 			     tree a, tree b, stmtblock_t* target)
961 {
962   tree cond;
963   tree name;
964 
965   /* If bounds-checking is disabled, do nothing.  */
966   if (!(gfc_option.rtcheck & GFC_RTCHECK_BOUNDS))
967     return;
968 
969   /* Compare the two string lengths.  */
970   cond = fold_build2_loc (input_location, NE_EXPR, logical_type_node, a, b);
971 
972   /* Output the runtime-check.  */
973   name = gfc_build_cstring_const (intr_name);
974   name = gfc_build_addr_expr (pchar_type_node, name);
975   gfc_trans_runtime_check (true, false, cond, target, where,
976 			   "Unequal character lengths (%ld/%ld) in %s",
977 			   fold_convert (long_integer_type_node, a),
978 			   fold_convert (long_integer_type_node, b), name);
979 }
980 
981 
982 /* The EXPONENT(X) intrinsic function is translated into
983        int ret;
984        return isfinite(X) ? (frexp (X, &ret) , ret) : huge
985    so that if X is a NaN or infinity, the result is HUGE(0).
986  */
987 
988 static void
gfc_conv_intrinsic_exponent(gfc_se * se,gfc_expr * expr)989 gfc_conv_intrinsic_exponent (gfc_se *se, gfc_expr *expr)
990 {
991   tree arg, type, res, tmp, frexp, cond, huge;
992   int i;
993 
994   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP,
995 				       expr->value.function.actual->expr->ts.kind);
996 
997   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
998   arg = gfc_evaluate_now (arg, &se->pre);
999 
1000   i = gfc_validate_kind (BT_INTEGER, gfc_c_int_kind, false);
1001   huge = gfc_conv_mpz_to_tree (gfc_integer_kinds[i].huge, gfc_c_int_kind);
1002   cond = build_call_expr_loc (input_location,
1003 			      builtin_decl_explicit (BUILT_IN_ISFINITE),
1004 			      1, arg);
1005 
1006   res = gfc_create_var (integer_type_node, NULL);
1007   tmp = build_call_expr_loc (input_location, frexp, 2, arg,
1008 			     gfc_build_addr_expr (NULL_TREE, res));
1009   tmp = fold_build2_loc (input_location, COMPOUND_EXPR, integer_type_node,
1010 			 tmp, res);
1011   se->expr = fold_build3_loc (input_location, COND_EXPR, integer_type_node,
1012 			      cond, tmp, huge);
1013 
1014   type = gfc_typenode_for_spec (&expr->ts);
1015   se->expr = fold_convert (type, se->expr);
1016 }
1017 
1018 
1019 /* Fill in the following structure
1020      struct caf_vector_t {
1021        size_t nvec;  // size of the vector
1022        union {
1023          struct {
1024            void *vector;
1025            int kind;
1026          } v;
1027          struct {
1028            ptrdiff_t lower_bound;
1029            ptrdiff_t upper_bound;
1030            ptrdiff_t stride;
1031          } triplet;
1032        } u;
1033      }  */
1034 
1035 static void
conv_caf_vector_subscript_elem(stmtblock_t * block,int i,tree desc,tree lower,tree upper,tree stride,tree vector,int kind,tree nvec)1036 conv_caf_vector_subscript_elem (stmtblock_t *block, int i, tree desc,
1037 				tree lower, tree upper, tree stride,
1038 				tree vector, int kind, tree nvec)
1039 {
1040   tree field, type, tmp;
1041 
1042   desc = gfc_build_array_ref (desc, gfc_rank_cst[i], NULL_TREE);
1043   type = TREE_TYPE (desc);
1044 
1045   field = gfc_advance_chain (TYPE_FIELDS (type), 0);
1046   tmp = fold_build3_loc (input_location, COMPONENT_REF, TREE_TYPE (field),
1047 			 desc, field, NULL_TREE);
1048   gfc_add_modify (block, tmp, fold_convert (TREE_TYPE (field), nvec));
1049 
1050   /* Access union.  */
1051   field = gfc_advance_chain (TYPE_FIELDS (type), 1);
1052   desc = fold_build3_loc (input_location, COMPONENT_REF, TREE_TYPE (field),
1053 			  desc, field, NULL_TREE);
1054   type = TREE_TYPE (desc);
1055 
1056   /* Access the inner struct.  */
1057   field = gfc_advance_chain (TYPE_FIELDS (type), vector != NULL_TREE ? 0 : 1);
1058   desc = fold_build3_loc (input_location, COMPONENT_REF, TREE_TYPE (field),
1059 		      desc, field, NULL_TREE);
1060   type = TREE_TYPE (desc);
1061 
1062   if (vector != NULL_TREE)
1063     {
1064       /* Set vector and kind.  */
1065       field = gfc_advance_chain (TYPE_FIELDS (type), 0);
1066       tmp = fold_build3_loc (input_location, COMPONENT_REF, TREE_TYPE (field),
1067 			 desc, field, NULL_TREE);
1068       gfc_add_modify (block, tmp, fold_convert (TREE_TYPE (field), vector));
1069       field = gfc_advance_chain (TYPE_FIELDS (type), 1);
1070       tmp = fold_build3_loc (input_location, COMPONENT_REF, TREE_TYPE (field),
1071 			 desc, field, NULL_TREE);
1072       gfc_add_modify (block, tmp, build_int_cst (integer_type_node, kind));
1073     }
1074   else
1075     {
1076       /* Set dim.lower/upper/stride.  */
1077       field = gfc_advance_chain (TYPE_FIELDS (type), 0);
1078       tmp = fold_build3_loc (input_location, COMPONENT_REF, TREE_TYPE (field),
1079 			     desc, field, NULL_TREE);
1080       gfc_add_modify (block, tmp, fold_convert (TREE_TYPE (field), lower));
1081 
1082       field = gfc_advance_chain (TYPE_FIELDS (type), 1);
1083       tmp = fold_build3_loc (input_location, COMPONENT_REF, TREE_TYPE (field),
1084 			     desc, field, NULL_TREE);
1085       gfc_add_modify (block, tmp, fold_convert (TREE_TYPE (field), upper));
1086 
1087       field = gfc_advance_chain (TYPE_FIELDS (type), 2);
1088       tmp = fold_build3_loc (input_location, COMPONENT_REF, TREE_TYPE (field),
1089 			     desc, field, NULL_TREE);
1090       gfc_add_modify (block, tmp, fold_convert (TREE_TYPE (field), stride));
1091     }
1092 }
1093 
1094 
1095 static tree
conv_caf_vector_subscript(stmtblock_t * block,tree desc,gfc_array_ref * ar)1096 conv_caf_vector_subscript (stmtblock_t *block, tree desc, gfc_array_ref *ar)
1097 {
1098   gfc_se argse;
1099   tree var, lower, upper = NULL_TREE, stride = NULL_TREE, vector, nvec;
1100   tree lbound, ubound, tmp;
1101   int i;
1102 
1103   var = gfc_create_var (gfc_get_caf_vector_type (ar->dimen), "vector");
1104 
1105   for (i = 0; i < ar->dimen; i++)
1106     switch (ar->dimen_type[i])
1107       {
1108       case DIMEN_RANGE:
1109         if (ar->end[i])
1110 	  {
1111 	    gfc_init_se (&argse, NULL);
1112 	    gfc_conv_expr (&argse, ar->end[i]);
1113 	    gfc_add_block_to_block (block, &argse.pre);
1114 	    upper = gfc_evaluate_now (argse.expr, block);
1115 	  }
1116         else
1117 	  upper = gfc_conv_descriptor_ubound_get (desc, gfc_rank_cst[i]);
1118 	if (ar->stride[i])
1119 	  {
1120 	    gfc_init_se (&argse, NULL);
1121 	    gfc_conv_expr (&argse, ar->stride[i]);
1122 	    gfc_add_block_to_block (block, &argse.pre);
1123 	    stride = gfc_evaluate_now (argse.expr, block);
1124 	  }
1125 	else
1126 	  stride = gfc_index_one_node;
1127 
1128 	/* Fall through.  */
1129       case DIMEN_ELEMENT:
1130 	if (ar->start[i])
1131 	  {
1132 	    gfc_init_se (&argse, NULL);
1133 	    gfc_conv_expr (&argse, ar->start[i]);
1134 	    gfc_add_block_to_block (block, &argse.pre);
1135 	    lower = gfc_evaluate_now (argse.expr, block);
1136 	  }
1137 	else
1138 	  lower = gfc_conv_descriptor_lbound_get (desc, gfc_rank_cst[i]);
1139 	if (ar->dimen_type[i] == DIMEN_ELEMENT)
1140 	  {
1141 	    upper = lower;
1142 	    stride = gfc_index_one_node;
1143 	  }
1144 	vector = NULL_TREE;
1145 	nvec = size_zero_node;
1146 	conv_caf_vector_subscript_elem (block, i, var, lower, upper, stride,
1147 					vector, 0, nvec);
1148 	break;
1149 
1150       case DIMEN_VECTOR:
1151 	gfc_init_se (&argse, NULL);
1152 	argse.descriptor_only = 1;
1153 	gfc_conv_expr_descriptor (&argse, ar->start[i]);
1154 	gfc_add_block_to_block (block, &argse.pre);
1155 	vector = argse.expr;
1156 	lbound = gfc_conv_descriptor_lbound_get (vector, gfc_rank_cst[0]);
1157 	ubound = gfc_conv_descriptor_ubound_get (vector, gfc_rank_cst[0]);
1158 	nvec = gfc_conv_array_extent_dim (lbound, ubound, NULL);
1159         tmp = gfc_conv_descriptor_stride_get (vector, gfc_rank_cst[0]);
1160 	nvec = fold_build2_loc (input_location, TRUNC_DIV_EXPR,
1161 				TREE_TYPE (nvec), nvec, tmp);
1162 	lower = gfc_index_zero_node;
1163 	upper = gfc_index_zero_node;
1164 	stride = gfc_index_zero_node;
1165 	vector = gfc_conv_descriptor_data_get (vector);
1166 	conv_caf_vector_subscript_elem (block, i, var, lower, upper, stride,
1167 					vector, ar->start[i]->ts.kind, nvec);
1168 	break;
1169       default:
1170 	gcc_unreachable();
1171     }
1172   return gfc_build_addr_expr (NULL_TREE, var);
1173 }
1174 
1175 
1176 static tree
compute_component_offset(tree field,tree type)1177 compute_component_offset (tree field, tree type)
1178 {
1179   tree tmp;
1180   if (DECL_FIELD_BIT_OFFSET (field) != NULL_TREE
1181       && !integer_zerop (DECL_FIELD_BIT_OFFSET (field)))
1182     {
1183       tmp = fold_build2 (TRUNC_DIV_EXPR, type,
1184 			 DECL_FIELD_BIT_OFFSET (field),
1185 			 bitsize_unit_node);
1186       return fold_build2 (PLUS_EXPR, type, DECL_FIELD_OFFSET (field), tmp);
1187     }
1188   else
1189     return DECL_FIELD_OFFSET (field);
1190 }
1191 
1192 
1193 static tree
conv_expr_ref_to_caf_ref(stmtblock_t * block,gfc_expr * expr)1194 conv_expr_ref_to_caf_ref (stmtblock_t *block, gfc_expr *expr)
1195 {
1196   gfc_ref *ref = expr->ref, *last_comp_ref;
1197   tree caf_ref = NULL_TREE, prev_caf_ref = NULL_TREE, reference_type, tmp, tmp2,
1198       field, last_type, inner_struct, mode, mode_rhs, dim_array, dim, dim_type,
1199       start, end, stride, vector, nvec;
1200   gfc_se se;
1201   bool ref_static_array = false;
1202   tree last_component_ref_tree = NULL_TREE;
1203   int i, last_type_n;
1204 
1205   if (expr->symtree)
1206     {
1207       last_component_ref_tree = expr->symtree->n.sym->backend_decl;
1208       ref_static_array = !expr->symtree->n.sym->attr.allocatable
1209 	  && !expr->symtree->n.sym->attr.pointer;
1210     }
1211 
1212   /* Prevent uninit-warning.  */
1213   reference_type = NULL_TREE;
1214 
1215   /* Skip refs upto the first coarray-ref.  */
1216   last_comp_ref = NULL;
1217   while (ref && (ref->type != REF_ARRAY || ref->u.ar.codimen == 0))
1218     {
1219       /* Remember the type of components skipped.  */
1220       if (ref->type == REF_COMPONENT)
1221 	last_comp_ref = ref;
1222       ref = ref->next;
1223     }
1224   /* When a component was skipped, get the type information of the last
1225      component ref, else get the type from the symbol.  */
1226   if (last_comp_ref)
1227     {
1228       last_type = gfc_typenode_for_spec (&last_comp_ref->u.c.component->ts);
1229       last_type_n = last_comp_ref->u.c.component->ts.type;
1230     }
1231   else
1232     {
1233       last_type = gfc_typenode_for_spec (&expr->symtree->n.sym->ts);
1234       last_type_n = expr->symtree->n.sym->ts.type;
1235     }
1236 
1237   while (ref)
1238     {
1239       if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0
1240 	  && ref->u.ar.dimen == 0)
1241 	{
1242 	  /* Skip pure coindexes.  */
1243 	  ref = ref->next;
1244 	  continue;
1245 	}
1246       tmp = gfc_create_var (gfc_get_caf_reference_type (), "caf_ref");
1247       reference_type = TREE_TYPE (tmp);
1248 
1249       if (caf_ref == NULL_TREE)
1250 	caf_ref = tmp;
1251 
1252       /* Construct the chain of refs.  */
1253       if (prev_caf_ref != NULL_TREE)
1254 	{
1255 	  field = gfc_advance_chain (TYPE_FIELDS (reference_type), 0);
1256 	  tmp2 = fold_build3_loc (input_location, COMPONENT_REF,
1257 				  TREE_TYPE (field), prev_caf_ref, field,
1258 				  NULL_TREE);
1259 	  gfc_add_modify (block, tmp2, gfc_build_addr_expr (TREE_TYPE (field),
1260 							    tmp));
1261 	}
1262       prev_caf_ref = tmp;
1263 
1264       switch (ref->type)
1265 	{
1266 	case REF_COMPONENT:
1267 	  last_type = gfc_typenode_for_spec (&ref->u.c.component->ts);
1268 	  last_type_n = ref->u.c.component->ts.type;
1269 	  /* Set the type of the ref.  */
1270 	  field = gfc_advance_chain (TYPE_FIELDS (reference_type), 1);
1271 	  tmp = fold_build3_loc (input_location, COMPONENT_REF,
1272 				 TREE_TYPE (field), prev_caf_ref, field,
1273 				 NULL_TREE);
1274 	  gfc_add_modify (block, tmp, build_int_cst (integer_type_node,
1275 						     GFC_CAF_REF_COMPONENT));
1276 
1277 	  /* Ref the c in union u.  */
1278 	  field = gfc_advance_chain (TYPE_FIELDS (reference_type), 3);
1279 	  tmp = fold_build3_loc (input_location, COMPONENT_REF,
1280 				 TREE_TYPE (field), prev_caf_ref, field,
1281 				 NULL_TREE);
1282 	  field = gfc_advance_chain (TYPE_FIELDS (TREE_TYPE (field)), 0);
1283 	  inner_struct = fold_build3_loc (input_location, COMPONENT_REF,
1284 				       TREE_TYPE (field), tmp, field,
1285 				       NULL_TREE);
1286 
1287 	  /* Set the offset.  */
1288 	  field = gfc_advance_chain (TYPE_FIELDS (TREE_TYPE (inner_struct)), 0);
1289 	  tmp = fold_build3_loc (input_location, COMPONENT_REF,
1290 				 TREE_TYPE (field), inner_struct, field,
1291 				 NULL_TREE);
1292 	  /* Computing the offset is somewhat harder.  The bit_offset has to be
1293 	     taken into account.  When the bit_offset in the field_decl is non-
1294 	     null, divide it by the bitsize_unit and add it to the regular
1295 	     offset.  */
1296 	  tmp2 = compute_component_offset (ref->u.c.component->backend_decl,
1297 					   TREE_TYPE (tmp));
1298 	  gfc_add_modify (block, tmp, fold_convert (TREE_TYPE (tmp), tmp2));
1299 
1300 	  /* Set caf_token_offset.  */
1301 	  field = gfc_advance_chain (TYPE_FIELDS (TREE_TYPE (inner_struct)), 1);
1302 	  tmp = fold_build3_loc (input_location, COMPONENT_REF,
1303 				 TREE_TYPE (field), inner_struct, field,
1304 				 NULL_TREE);
1305 	  if ((ref->u.c.component->attr.allocatable
1306 	       || ref->u.c.component->attr.pointer)
1307 	      && ref->u.c.component->attr.dimension)
1308 	    {
1309 	      tree arr_desc_token_offset;
1310 	      /* Get the token field from the descriptor.  */
1311 	      arr_desc_token_offset = TREE_OPERAND (
1312 		    gfc_conv_descriptor_token (ref->u.c.component->backend_decl), 1);
1313 	      arr_desc_token_offset
1314 		  = compute_component_offset (arr_desc_token_offset,
1315 					      TREE_TYPE (tmp));
1316 	      tmp2 = fold_build2_loc (input_location, PLUS_EXPR,
1317 				      TREE_TYPE (tmp2), tmp2,
1318 				      arr_desc_token_offset);
1319 	    }
1320 	  else if (ref->u.c.component->caf_token)
1321 	    tmp2 = compute_component_offset (ref->u.c.component->caf_token,
1322 					     TREE_TYPE (tmp));
1323 	  else
1324 	    tmp2 = integer_zero_node;
1325 	  gfc_add_modify (block, tmp, fold_convert (TREE_TYPE (tmp), tmp2));
1326 
1327 	  /* Remember whether this ref was to a non-allocatable/non-pointer
1328 	     component so the next array ref can be tailored correctly.  */
1329 	  ref_static_array = !ref->u.c.component->attr.allocatable
1330 	      && !ref->u.c.component->attr.pointer;
1331 	  last_component_ref_tree = ref_static_array
1332 	      ? ref->u.c.component->backend_decl : NULL_TREE;
1333 	  break;
1334 	case REF_ARRAY:
1335 	  if (ref_static_array && ref->u.ar.as->type == AS_DEFERRED)
1336 	    ref_static_array = false;
1337 	  /* Set the type of the ref.  */
1338 	  field = gfc_advance_chain (TYPE_FIELDS (reference_type), 1);
1339 	  tmp = fold_build3_loc (input_location, COMPONENT_REF,
1340 				 TREE_TYPE (field), prev_caf_ref, field,
1341 				 NULL_TREE);
1342 	  gfc_add_modify (block, tmp, build_int_cst (integer_type_node,
1343 						     ref_static_array
1344 						     ? GFC_CAF_REF_STATIC_ARRAY
1345 						     : GFC_CAF_REF_ARRAY));
1346 
1347 	  /* Ref the a in union u.  */
1348 	  field = gfc_advance_chain (TYPE_FIELDS (reference_type), 3);
1349 	  tmp = fold_build3_loc (input_location, COMPONENT_REF,
1350 				 TREE_TYPE (field), prev_caf_ref, field,
1351 				 NULL_TREE);
1352 	  field = gfc_advance_chain (TYPE_FIELDS (TREE_TYPE (field)), 1);
1353 	  inner_struct = fold_build3_loc (input_location, COMPONENT_REF,
1354 				       TREE_TYPE (field), tmp, field,
1355 				       NULL_TREE);
1356 
1357 	  /* Set the static_array_type in a for static arrays.  */
1358 	  if (ref_static_array)
1359 	    {
1360 	      field = gfc_advance_chain (TYPE_FIELDS (TREE_TYPE (inner_struct)),
1361 					 1);
1362 	      tmp = fold_build3_loc (input_location, COMPONENT_REF,
1363 				     TREE_TYPE (field), inner_struct, field,
1364 				     NULL_TREE);
1365 	      gfc_add_modify (block, tmp, build_int_cst (TREE_TYPE (tmp),
1366 							 last_type_n));
1367 	    }
1368 	  /* Ref the mode in the inner_struct.  */
1369 	  field = gfc_advance_chain (TYPE_FIELDS (TREE_TYPE (inner_struct)), 0);
1370 	  mode = fold_build3_loc (input_location, COMPONENT_REF,
1371 				  TREE_TYPE (field), inner_struct, field,
1372 				  NULL_TREE);
1373 	  /* Ref the dim in the inner_struct.  */
1374 	  field = gfc_advance_chain (TYPE_FIELDS (TREE_TYPE (inner_struct)), 2);
1375 	  dim_array = fold_build3_loc (input_location, COMPONENT_REF,
1376 				       TREE_TYPE (field), inner_struct, field,
1377 				       NULL_TREE);
1378 	  for (i = 0; i < ref->u.ar.dimen; ++i)
1379 	    {
1380 	      /* Ref dim i.  */
1381 	      dim = gfc_build_array_ref (dim_array, gfc_rank_cst[i], NULL_TREE);
1382 	      dim_type = TREE_TYPE (dim);
1383 	      mode_rhs = start = end = stride = NULL_TREE;
1384 	      switch (ref->u.ar.dimen_type[i])
1385 		{
1386 		case DIMEN_RANGE:
1387 		  if (ref->u.ar.end[i])
1388 		    {
1389 		      gfc_init_se (&se, NULL);
1390 		      gfc_conv_expr (&se, ref->u.ar.end[i]);
1391 		      gfc_add_block_to_block (block, &se.pre);
1392 		      if (ref_static_array)
1393 			{
1394 			  /* Make the index zero-based, when reffing a static
1395 			     array.  */
1396 			  end = se.expr;
1397 			  gfc_init_se (&se, NULL);
1398 			  gfc_conv_expr (&se, ref->u.ar.as->lower[i]);
1399 			  gfc_add_block_to_block (block, &se.pre);
1400 			  se.expr = fold_build2 (MINUS_EXPR,
1401 						 gfc_array_index_type,
1402 						 end, fold_convert (
1403 						   gfc_array_index_type,
1404 						   se.expr));
1405 			}
1406 		      end = gfc_evaluate_now (fold_convert (
1407 						gfc_array_index_type,
1408 						se.expr),
1409 					      block);
1410 		    }
1411 		  else if (ref_static_array)
1412 		    end = fold_build2 (MINUS_EXPR,
1413 				       gfc_array_index_type,
1414 				       gfc_conv_array_ubound (
1415 					 last_component_ref_tree, i),
1416 				       gfc_conv_array_lbound (
1417 					 last_component_ref_tree, i));
1418 		  else
1419 		    {
1420 		      end = NULL_TREE;
1421 		      mode_rhs = build_int_cst (unsigned_char_type_node,
1422 						GFC_CAF_ARR_REF_OPEN_END);
1423 		    }
1424 		  if (ref->u.ar.stride[i])
1425 		    {
1426 		      gfc_init_se (&se, NULL);
1427 		      gfc_conv_expr (&se, ref->u.ar.stride[i]);
1428 		      gfc_add_block_to_block (block, &se.pre);
1429 		      stride = gfc_evaluate_now (fold_convert (
1430 						   gfc_array_index_type,
1431 						   se.expr),
1432 						 block);
1433 		      if (ref_static_array)
1434 			{
1435 			  /* Make the index zero-based, when reffing a static
1436 			     array.  */
1437 			  stride = fold_build2 (MULT_EXPR,
1438 						gfc_array_index_type,
1439 						gfc_conv_array_stride (
1440 						  last_component_ref_tree,
1441 						  i),
1442 						stride);
1443 			  gcc_assert (end != NULL_TREE);
1444 			  /* Multiply with the product of array's stride and
1445 			     the step of the ref to a virtual upper bound.
1446 			     We cannot compute the actual upper bound here or
1447 			     the caflib would compute the extend
1448 			     incorrectly.  */
1449 			  end = fold_build2 (MULT_EXPR, gfc_array_index_type,
1450 					     end, gfc_conv_array_stride (
1451 					       last_component_ref_tree,
1452 					       i));
1453 			  end = gfc_evaluate_now (end, block);
1454 			  stride = gfc_evaluate_now (stride, block);
1455 			}
1456 		    }
1457 		  else if (ref_static_array)
1458 		    {
1459 		      stride = gfc_conv_array_stride (last_component_ref_tree,
1460 						      i);
1461 		      end = fold_build2 (MULT_EXPR, gfc_array_index_type,
1462 					 end, stride);
1463 		      end = gfc_evaluate_now (end, block);
1464 		    }
1465 		  else
1466 		    /* Always set a ref stride of one to make caflib's
1467 		       handling easier.  */
1468 		    stride = gfc_index_one_node;
1469 
1470 		  /* Fall through.  */
1471 		case DIMEN_ELEMENT:
1472 		  if (ref->u.ar.start[i])
1473 		    {
1474 		      gfc_init_se (&se, NULL);
1475 		      gfc_conv_expr (&se, ref->u.ar.start[i]);
1476 		      gfc_add_block_to_block (block, &se.pre);
1477 		      if (ref_static_array)
1478 			{
1479 			  /* Make the index zero-based, when reffing a static
1480 			     array.  */
1481 			  start = fold_convert (gfc_array_index_type, se.expr);
1482 			  gfc_init_se (&se, NULL);
1483 			  gfc_conv_expr (&se, ref->u.ar.as->lower[i]);
1484 			  gfc_add_block_to_block (block, &se.pre);
1485 			  se.expr = fold_build2 (MINUS_EXPR,
1486 						 gfc_array_index_type,
1487 						 start, fold_convert (
1488 						   gfc_array_index_type,
1489 						   se.expr));
1490 			  /* Multiply with the stride.  */
1491 			  se.expr = fold_build2 (MULT_EXPR,
1492 						 gfc_array_index_type,
1493 						 se.expr,
1494 						 gfc_conv_array_stride (
1495 						   last_component_ref_tree,
1496 						   i));
1497 			}
1498 		      start = gfc_evaluate_now (fold_convert (
1499 						  gfc_array_index_type,
1500 						  se.expr),
1501 						block);
1502 		      if (mode_rhs == NULL_TREE)
1503 			mode_rhs = build_int_cst (unsigned_char_type_node,
1504 						  ref->u.ar.dimen_type[i]
1505 						  == DIMEN_ELEMENT
1506 						  ? GFC_CAF_ARR_REF_SINGLE
1507 						  : GFC_CAF_ARR_REF_RANGE);
1508 		    }
1509 		  else if (ref_static_array)
1510 		    {
1511 		      start = integer_zero_node;
1512 		      mode_rhs = build_int_cst (unsigned_char_type_node,
1513 						ref->u.ar.start[i] == NULL
1514 						? GFC_CAF_ARR_REF_FULL
1515 						: GFC_CAF_ARR_REF_RANGE);
1516 		    }
1517 		  else if (end == NULL_TREE)
1518 		    mode_rhs = build_int_cst (unsigned_char_type_node,
1519 					      GFC_CAF_ARR_REF_FULL);
1520 		  else
1521 		    mode_rhs = build_int_cst (unsigned_char_type_node,
1522 					      GFC_CAF_ARR_REF_OPEN_START);
1523 
1524 		  /* Ref the s in dim.  */
1525 		  field = gfc_advance_chain (TYPE_FIELDS (dim_type), 0);
1526 		  tmp = fold_build3_loc (input_location, COMPONENT_REF,
1527 					 TREE_TYPE (field), dim, field,
1528 					 NULL_TREE);
1529 
1530 		  /* Set start in s.  */
1531 		  if (start != NULL_TREE)
1532 		    {
1533 		      field = gfc_advance_chain (TYPE_FIELDS (TREE_TYPE (tmp)),
1534 						 0);
1535 		      tmp2 = fold_build3_loc (input_location, COMPONENT_REF,
1536 					      TREE_TYPE (field), tmp, field,
1537 					      NULL_TREE);
1538 		      gfc_add_modify (block, tmp2,
1539 				      fold_convert (TREE_TYPE (tmp2), start));
1540 		    }
1541 
1542 		  /* Set end in s.  */
1543 		  if (end != NULL_TREE)
1544 		    {
1545 		      field = gfc_advance_chain (TYPE_FIELDS (TREE_TYPE (tmp)),
1546 						 1);
1547 		      tmp2 = fold_build3_loc (input_location, COMPONENT_REF,
1548 					      TREE_TYPE (field), tmp, field,
1549 					      NULL_TREE);
1550 		      gfc_add_modify (block, tmp2,
1551 				      fold_convert (TREE_TYPE (tmp2), end));
1552 		    }
1553 
1554 		  /* Set end in s.  */
1555 		  if (stride != NULL_TREE)
1556 		    {
1557 		      field = gfc_advance_chain (TYPE_FIELDS (TREE_TYPE (tmp)),
1558 						 2);
1559 		      tmp2 = fold_build3_loc (input_location, COMPONENT_REF,
1560 					      TREE_TYPE (field), tmp, field,
1561 					      NULL_TREE);
1562 		      gfc_add_modify (block, tmp2,
1563 				      fold_convert (TREE_TYPE (tmp2), stride));
1564 		    }
1565 		  break;
1566 		case DIMEN_VECTOR:
1567 		  /* TODO: In case of static array.  */
1568 		  gcc_assert (!ref_static_array);
1569 		  mode_rhs = build_int_cst (unsigned_char_type_node,
1570 					    GFC_CAF_ARR_REF_VECTOR);
1571 		  gfc_init_se (&se, NULL);
1572 		  se.descriptor_only = 1;
1573 		  gfc_conv_expr_descriptor (&se, ref->u.ar.start[i]);
1574 		  gfc_add_block_to_block (block, &se.pre);
1575 		  vector = se.expr;
1576 		  tmp = gfc_conv_descriptor_lbound_get (vector,
1577 							gfc_rank_cst[0]);
1578 		  tmp2 = gfc_conv_descriptor_ubound_get (vector,
1579 							 gfc_rank_cst[0]);
1580 		  nvec = gfc_conv_array_extent_dim (tmp, tmp2, NULL);
1581 		  tmp = gfc_conv_descriptor_stride_get (vector,
1582 							gfc_rank_cst[0]);
1583 		  nvec = fold_build2_loc (input_location, TRUNC_DIV_EXPR,
1584 					  TREE_TYPE (nvec), nvec, tmp);
1585 		  vector = gfc_conv_descriptor_data_get (vector);
1586 
1587 		  /* Ref the v in dim.  */
1588 		  field = gfc_advance_chain (TYPE_FIELDS (dim_type), 1);
1589 		  tmp = fold_build3_loc (input_location, COMPONENT_REF,
1590 					 TREE_TYPE (field), dim, field,
1591 					 NULL_TREE);
1592 
1593 		  /* Set vector in v.  */
1594 		  field = gfc_advance_chain (TYPE_FIELDS (TREE_TYPE (tmp)), 0);
1595 		  tmp2 = fold_build3_loc (input_location, COMPONENT_REF,
1596 					  TREE_TYPE (field), tmp, field,
1597 					  NULL_TREE);
1598 		  gfc_add_modify (block, tmp2, fold_convert (TREE_TYPE (tmp2),
1599 							     vector));
1600 
1601 		  /* Set nvec in v.  */
1602 		  field = gfc_advance_chain (TYPE_FIELDS (TREE_TYPE (tmp)), 1);
1603 		  tmp2 = fold_build3_loc (input_location, COMPONENT_REF,
1604 					  TREE_TYPE (field), tmp, field,
1605 					  NULL_TREE);
1606 		  gfc_add_modify (block, tmp2, fold_convert (TREE_TYPE (tmp2),
1607 							     nvec));
1608 
1609 		  /* Set kind in v.  */
1610 		  field = gfc_advance_chain (TYPE_FIELDS (TREE_TYPE (tmp)), 2);
1611 		  tmp2 = fold_build3_loc (input_location, COMPONENT_REF,
1612 					  TREE_TYPE (field), tmp, field,
1613 					  NULL_TREE);
1614 		  gfc_add_modify (block, tmp2, build_int_cst (integer_type_node,
1615 						  ref->u.ar.start[i]->ts.kind));
1616 		  break;
1617 		default:
1618 		  gcc_unreachable ();
1619 		}
1620 	      /* Set the mode for dim i.  */
1621 	      tmp = gfc_build_array_ref (mode, gfc_rank_cst[i], NULL_TREE);
1622 	      gfc_add_modify (block, tmp, fold_convert (TREE_TYPE (tmp),
1623 							mode_rhs));
1624 	    }
1625 
1626 	  /* Set the mode for dim i+1 to GFC_ARR_REF_NONE.  */
1627 	  if (i < GFC_MAX_DIMENSIONS)
1628 	    {
1629 	      tmp = gfc_build_array_ref (mode, gfc_rank_cst[i], NULL_TREE);
1630 	      gfc_add_modify (block, tmp,
1631 			      build_int_cst (unsigned_char_type_node,
1632 					     GFC_CAF_ARR_REF_NONE));
1633 	    }
1634 	  break;
1635 	default:
1636 	  gcc_unreachable ();
1637 	}
1638 
1639       /* Set the size of the current type.  */
1640       field = gfc_advance_chain (TYPE_FIELDS (reference_type), 2);
1641       tmp = fold_build3_loc (input_location, COMPONENT_REF, TREE_TYPE (field),
1642 			     prev_caf_ref, field, NULL_TREE);
1643       gfc_add_modify (block, tmp, fold_convert (TREE_TYPE (field),
1644 						TYPE_SIZE_UNIT (last_type)));
1645 
1646       ref = ref->next;
1647     }
1648 
1649   if (prev_caf_ref != NULL_TREE)
1650     {
1651       field = gfc_advance_chain (TYPE_FIELDS (reference_type), 0);
1652       tmp = fold_build3_loc (input_location, COMPONENT_REF, TREE_TYPE (field),
1653 			     prev_caf_ref, field, NULL_TREE);
1654       gfc_add_modify (block, tmp, fold_convert (TREE_TYPE (field),
1655 						  null_pointer_node));
1656     }
1657   return caf_ref != NULL_TREE ? gfc_build_addr_expr (NULL_TREE, caf_ref)
1658 			      : NULL_TREE;
1659 }
1660 
1661 /* Get data from a remote coarray.  */
1662 
1663 static void
gfc_conv_intrinsic_caf_get(gfc_se * se,gfc_expr * expr,tree lhs,tree lhs_kind,tree may_require_tmp,bool may_realloc,symbol_attribute * caf_attr)1664 gfc_conv_intrinsic_caf_get (gfc_se *se, gfc_expr *expr, tree lhs, tree lhs_kind,
1665 			    tree may_require_tmp, bool may_realloc,
1666 			    symbol_attribute *caf_attr)
1667 {
1668   gfc_expr *array_expr, *tmp_stat;
1669   gfc_se argse;
1670   tree caf_decl, token, offset, image_index, tmp;
1671   tree res_var, dst_var, type, kind, vec, stat;
1672   tree caf_reference;
1673   symbol_attribute caf_attr_store;
1674 
1675   gcc_assert (flag_coarray == GFC_FCOARRAY_LIB);
1676 
1677   if (se->ss && se->ss->info->useflags)
1678     {
1679        /* Access the previously obtained result.  */
1680        gfc_conv_tmp_array_ref (se);
1681        return;
1682     }
1683 
1684   /* If lhs is set, the CAF_GET intrinsic has already been stripped.  */
1685   array_expr = (lhs == NULL_TREE) ? expr->value.function.actual->expr : expr;
1686   type = gfc_typenode_for_spec (&array_expr->ts);
1687 
1688   if (caf_attr == NULL)
1689     {
1690       caf_attr_store = gfc_caf_attr (array_expr);
1691       caf_attr = &caf_attr_store;
1692     }
1693 
1694   res_var = lhs;
1695   dst_var = lhs;
1696 
1697   vec = null_pointer_node;
1698   tmp_stat = gfc_find_stat_co (expr);
1699 
1700   if (tmp_stat)
1701     {
1702       gfc_se stat_se;
1703       gfc_init_se (&stat_se, NULL);
1704       gfc_conv_expr_reference (&stat_se, tmp_stat);
1705       stat = stat_se.expr;
1706       gfc_add_block_to_block (&se->pre, &stat_se.pre);
1707       gfc_add_block_to_block (&se->post, &stat_se.post);
1708     }
1709   else
1710     stat = null_pointer_node;
1711 
1712   /* Only use the new get_by_ref () where it is necessary.  I.e., when the lhs
1713      is reallocatable or the right-hand side has allocatable components.  */
1714   if (caf_attr->alloc_comp || caf_attr->pointer_comp || may_realloc)
1715     {
1716       /* Get using caf_get_by_ref.  */
1717       caf_reference = conv_expr_ref_to_caf_ref (&se->pre, array_expr);
1718 
1719       if (caf_reference != NULL_TREE)
1720 	{
1721 	  if (lhs == NULL_TREE)
1722 	    {
1723 	      if (array_expr->ts.type == BT_CHARACTER)
1724 		gfc_init_se (&argse, NULL);
1725 	      if (array_expr->rank == 0)
1726 		{
1727 		  symbol_attribute attr;
1728 		  gfc_clear_attr (&attr);
1729 		  if (array_expr->ts.type == BT_CHARACTER)
1730 		    {
1731 		      res_var = gfc_conv_string_tmp (se,
1732 						     build_pointer_type (type),
1733 					     array_expr->ts.u.cl->backend_decl);
1734 		      argse.string_length = array_expr->ts.u.cl->backend_decl;
1735 		    }
1736 		  else
1737 		    res_var = gfc_create_var (type, "caf_res");
1738 		  dst_var = gfc_conv_scalar_to_descriptor (se, res_var, attr);
1739 		  dst_var = gfc_build_addr_expr (NULL_TREE, dst_var);
1740 		}
1741 	      else
1742 		{
1743 		  /* Create temporary.  */
1744 		  if (array_expr->ts.type == BT_CHARACTER)
1745 		    gfc_conv_expr_descriptor (&argse, array_expr);
1746 		  may_realloc = gfc_trans_create_temp_array (&se->pre,
1747 							     &se->post,
1748 							     se->ss, type,
1749 							     NULL_TREE, false,
1750 							     false, false,
1751 							     &array_expr->where)
1752 		      == NULL_TREE;
1753 		  res_var = se->ss->info->data.array.descriptor;
1754 		  dst_var = gfc_build_addr_expr (NULL_TREE, res_var);
1755 		  if (may_realloc)
1756 		    {
1757 		      tmp = gfc_conv_descriptor_data_get (res_var);
1758 		      tmp = gfc_deallocate_with_status (tmp, NULL_TREE,
1759 							NULL_TREE, NULL_TREE,
1760 							NULL_TREE, true,
1761 							NULL,
1762 						     GFC_CAF_COARRAY_NOCOARRAY);
1763 		      gfc_add_expr_to_block (&se->post, tmp);
1764 		    }
1765 		}
1766 	    }
1767 
1768 	  kind = build_int_cst (integer_type_node, expr->ts.kind);
1769 	  if (lhs_kind == NULL_TREE)
1770 	    lhs_kind = kind;
1771 
1772 	  caf_decl = gfc_get_tree_for_caf_expr (array_expr);
1773 	  if (TREE_CODE (TREE_TYPE (caf_decl)) == REFERENCE_TYPE)
1774 	    caf_decl = build_fold_indirect_ref_loc (input_location, caf_decl);
1775 	  image_index = gfc_caf_get_image_index (&se->pre, array_expr,
1776 						 caf_decl);
1777 	  gfc_get_caf_token_offset (se, &token, NULL, caf_decl, NULL,
1778 				    array_expr);
1779 
1780 	  /* No overlap possible as we have generated a temporary.  */
1781 	  if (lhs == NULL_TREE)
1782 	    may_require_tmp = boolean_false_node;
1783 
1784 	  /* It guarantees memory consistency within the same segment.  */
1785 	  tmp = gfc_build_string_const (strlen ("memory") + 1, "memory");
1786 	  tmp = build5_loc (input_location, ASM_EXPR, void_type_node,
1787 			    gfc_build_string_const (1, ""), NULL_TREE,
1788 			    NULL_TREE, tree_cons (NULL_TREE, tmp, NULL_TREE),
1789 			    NULL_TREE);
1790 	  ASM_VOLATILE_P (tmp) = 1;
1791 	  gfc_add_expr_to_block (&se->pre, tmp);
1792 
1793 	  tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_get_by_ref,
1794 				     10, token, image_index, dst_var,
1795 				     caf_reference, lhs_kind, kind,
1796 				     may_require_tmp,
1797 				     may_realloc ? boolean_true_node :
1798 						   boolean_false_node,
1799 				     stat, build_int_cst (integer_type_node,
1800 							  array_expr->ts.type));
1801 
1802 	  gfc_add_expr_to_block (&se->pre, tmp);
1803 
1804 	  if (se->ss)
1805 	    gfc_advance_se_ss_chain (se);
1806 
1807 	  se->expr = res_var;
1808 	  if (array_expr->ts.type == BT_CHARACTER)
1809 	    se->string_length = argse.string_length;
1810 
1811 	  return;
1812 	}
1813     }
1814 
1815   gfc_init_se (&argse, NULL);
1816   if (array_expr->rank == 0)
1817     {
1818       symbol_attribute attr;
1819 
1820       gfc_clear_attr (&attr);
1821       gfc_conv_expr (&argse, array_expr);
1822 
1823       if (lhs == NULL_TREE)
1824 	{
1825 	  gfc_clear_attr (&attr);
1826 	  if (array_expr->ts.type == BT_CHARACTER)
1827 	    res_var = gfc_conv_string_tmp (se, build_pointer_type (type),
1828 					   argse.string_length);
1829 	  else
1830 	    res_var = gfc_create_var (type, "caf_res");
1831 	  dst_var = gfc_conv_scalar_to_descriptor (&argse, res_var, attr);
1832 	  dst_var = gfc_build_addr_expr (NULL_TREE, dst_var);
1833 	}
1834       argse.expr = gfc_conv_scalar_to_descriptor (&argse, argse.expr, attr);
1835       argse.expr = gfc_build_addr_expr (NULL_TREE, argse.expr);
1836     }
1837   else
1838     {
1839       /* If has_vector, pass descriptor for whole array and the
1840          vector bounds separately.  */
1841       gfc_array_ref *ar, ar2;
1842       bool has_vector = false;
1843 
1844       if (gfc_is_coindexed (expr) && gfc_has_vector_subscript (expr))
1845 	{
1846           has_vector = true;
1847           ar = gfc_find_array_ref (expr);
1848 	  ar2 = *ar;
1849 	  memset (ar, '\0', sizeof (*ar));
1850 	  ar->as = ar2.as;
1851 	  ar->type = AR_FULL;
1852 	}
1853       // TODO: Check whether argse.want_coarray = 1 can help with the below.
1854       gfc_conv_expr_descriptor (&argse, array_expr);
1855       /* Using gfc_conv_expr_descriptor, we only get the descriptor, but that
1856 	 has the wrong type if component references are done.  */
1857       gfc_add_modify (&argse.pre, gfc_conv_descriptor_dtype (argse.expr),
1858 		      gfc_get_dtype_rank_type (has_vector ? ar2.dimen
1859 							  : array_expr->rank,
1860 					       type));
1861       if (has_vector)
1862 	{
1863 	  vec = conv_caf_vector_subscript (&argse.pre, argse.expr, &ar2);
1864 	  *ar = ar2;
1865 	}
1866 
1867       if (lhs == NULL_TREE)
1868 	{
1869 	  /* Create temporary.  */
1870 	  for (int n = 0; n < se->ss->loop->dimen; n++)
1871 	    if (se->loop->to[n] == NULL_TREE)
1872 	      {
1873 		se->loop->from[n] = gfc_conv_descriptor_lbound_get (argse.expr,
1874 							       gfc_rank_cst[n]);
1875 		se->loop->to[n] = gfc_conv_descriptor_ubound_get (argse.expr,
1876 							       gfc_rank_cst[n]);
1877 	      }
1878 	  gfc_trans_create_temp_array (&argse.pre, &argse.post, se->ss, type,
1879 				       NULL_TREE, false, true, false,
1880 				       &array_expr->where);
1881 	  res_var = se->ss->info->data.array.descriptor;
1882 	  dst_var = gfc_build_addr_expr (NULL_TREE, res_var);
1883 	}
1884       argse.expr = gfc_build_addr_expr (NULL_TREE, argse.expr);
1885     }
1886 
1887   kind = build_int_cst (integer_type_node, expr->ts.kind);
1888   if (lhs_kind == NULL_TREE)
1889     lhs_kind = kind;
1890 
1891   gfc_add_block_to_block (&se->pre, &argse.pre);
1892   gfc_add_block_to_block (&se->post, &argse.post);
1893 
1894   caf_decl = gfc_get_tree_for_caf_expr (array_expr);
1895   if (TREE_CODE (TREE_TYPE (caf_decl)) == REFERENCE_TYPE)
1896     caf_decl = build_fold_indirect_ref_loc (input_location, caf_decl);
1897   image_index = gfc_caf_get_image_index (&se->pre, array_expr, caf_decl);
1898   gfc_get_caf_token_offset (se, &token, &offset, caf_decl, argse.expr,
1899 			    array_expr);
1900 
1901   /* No overlap possible as we have generated a temporary.  */
1902   if (lhs == NULL_TREE)
1903     may_require_tmp = boolean_false_node;
1904 
1905   /* It guarantees memory consistency within the same segment.  */
1906   tmp = gfc_build_string_const (strlen ("memory") + 1, "memory");
1907   tmp = build5_loc (input_location, ASM_EXPR, void_type_node,
1908 		    gfc_build_string_const (1, ""), NULL_TREE, NULL_TREE,
1909 		    tree_cons (NULL_TREE, tmp, NULL_TREE), NULL_TREE);
1910   ASM_VOLATILE_P (tmp) = 1;
1911   gfc_add_expr_to_block (&se->pre, tmp);
1912 
1913   tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_get, 10,
1914 			     token, offset, image_index, argse.expr, vec,
1915 			     dst_var, kind, lhs_kind, may_require_tmp, stat);
1916 
1917   gfc_add_expr_to_block (&se->pre, tmp);
1918 
1919   if (se->ss)
1920     gfc_advance_se_ss_chain (se);
1921 
1922   se->expr = res_var;
1923   if (array_expr->ts.type == BT_CHARACTER)
1924     se->string_length = argse.string_length;
1925 }
1926 
1927 
1928 /* Send data to a remote coarray.  */
1929 
1930 static tree
conv_caf_send(gfc_code * code)1931 conv_caf_send (gfc_code *code) {
1932   gfc_expr *lhs_expr, *rhs_expr, *tmp_stat, *tmp_team;
1933   gfc_se lhs_se, rhs_se;
1934   stmtblock_t block;
1935   tree caf_decl, token, offset, image_index, tmp, lhs_kind, rhs_kind;
1936   tree may_require_tmp, src_stat, dst_stat, dst_team;
1937   tree lhs_type = NULL_TREE;
1938   tree vec = null_pointer_node, rhs_vec = null_pointer_node;
1939   symbol_attribute lhs_caf_attr, rhs_caf_attr;
1940 
1941   gcc_assert (flag_coarray == GFC_FCOARRAY_LIB);
1942 
1943   lhs_expr = code->ext.actual->expr;
1944   rhs_expr = code->ext.actual->next->expr;
1945   may_require_tmp = gfc_check_dependency (lhs_expr, rhs_expr, true) == 0
1946 		    ? boolean_false_node : boolean_true_node;
1947   gfc_init_block (&block);
1948 
1949   lhs_caf_attr = gfc_caf_attr (lhs_expr);
1950   rhs_caf_attr = gfc_caf_attr (rhs_expr);
1951   src_stat = dst_stat = null_pointer_node;
1952   dst_team = null_pointer_node;
1953 
1954   /* LHS.  */
1955   gfc_init_se (&lhs_se, NULL);
1956   if (lhs_expr->rank == 0)
1957     {
1958       if (lhs_expr->ts.type == BT_CHARACTER && lhs_expr->ts.deferred)
1959 	{
1960 	  lhs_se.expr = gfc_get_tree_for_caf_expr (lhs_expr);
1961 	  lhs_se.expr = gfc_build_addr_expr (NULL_TREE, lhs_se.expr);
1962 	}
1963       else
1964 	{
1965 	  symbol_attribute attr;
1966 	  gfc_clear_attr (&attr);
1967 	  gfc_conv_expr (&lhs_se, lhs_expr);
1968 	  lhs_type = TREE_TYPE (lhs_se.expr);
1969 	  lhs_se.expr = gfc_conv_scalar_to_descriptor (&lhs_se, lhs_se.expr,
1970 						       attr);
1971 	  lhs_se.expr = gfc_build_addr_expr (NULL_TREE, lhs_se.expr);
1972 	}
1973     }
1974   else if ((lhs_caf_attr.alloc_comp || lhs_caf_attr.pointer_comp)
1975 	   && lhs_caf_attr.codimension)
1976     {
1977       lhs_se.want_pointer = 1;
1978       gfc_conv_expr_descriptor (&lhs_se, lhs_expr);
1979       /* Using gfc_conv_expr_descriptor, we only get the descriptor, but that
1980 	 has the wrong type if component references are done.  */
1981       lhs_type = gfc_typenode_for_spec (&lhs_expr->ts);
1982       tmp = build_fold_indirect_ref_loc (input_location, lhs_se.expr);
1983       gfc_add_modify (&lhs_se.pre, gfc_conv_descriptor_dtype (tmp),
1984 		      gfc_get_dtype_rank_type (
1985 			gfc_has_vector_subscript (lhs_expr)
1986 			? gfc_find_array_ref (lhs_expr)->dimen
1987 			: lhs_expr->rank,
1988 		      lhs_type));
1989     }
1990   else
1991     {
1992       bool has_vector = gfc_has_vector_subscript (lhs_expr);
1993 
1994       if (gfc_is_coindexed (lhs_expr) || !has_vector)
1995 	{
1996 	  /* If has_vector, pass descriptor for whole array and the
1997 	     vector bounds separately.  */
1998 	  gfc_array_ref *ar, ar2;
1999 	  bool has_tmp_lhs_array = false;
2000 	  if (has_vector)
2001 	    {
2002 	      has_tmp_lhs_array = true;
2003 	      ar = gfc_find_array_ref (lhs_expr);
2004 	      ar2 = *ar;
2005 	      memset (ar, '\0', sizeof (*ar));
2006 	      ar->as = ar2.as;
2007 	      ar->type = AR_FULL;
2008 	    }
2009 	  lhs_se.want_pointer = 1;
2010 	  gfc_conv_expr_descriptor (&lhs_se, lhs_expr);
2011 	  /* Using gfc_conv_expr_descriptor, we only get the descriptor, but
2012 	     that has the wrong type if component references are done.  */
2013 	  lhs_type = gfc_typenode_for_spec (&lhs_expr->ts);
2014 	  tmp = build_fold_indirect_ref_loc (input_location, lhs_se.expr);
2015 	  gfc_add_modify (&lhs_se.pre, gfc_conv_descriptor_dtype (tmp),
2016 			  gfc_get_dtype_rank_type (has_vector ? ar2.dimen
2017 							      : lhs_expr->rank,
2018 						   lhs_type));
2019 	  if (has_tmp_lhs_array)
2020 	    {
2021 	      vec = conv_caf_vector_subscript (&block, lhs_se.expr, &ar2);
2022 	      *ar = ar2;
2023 	    }
2024 	}
2025       else
2026 	{
2027 	  /* Special casing for arr1 ([...]) = arr2[...], i.e. caf_get to
2028 	     indexed array expression.  This is rewritten to:
2029 
2030 	     tmp_array = arr2[...]
2031 	     arr1 ([...]) = tmp_array
2032 
2033 	     because using the standard gfc_conv_expr (lhs_expr) did the
2034 	     assignment with lhs and rhs exchanged.  */
2035 
2036 	  gfc_ss *lss_for_tmparray, *lss_real;
2037 	  gfc_loopinfo loop;
2038 	  gfc_se se;
2039 	  stmtblock_t body;
2040 	  tree tmparr_desc, src;
2041 	  tree index = gfc_index_zero_node;
2042 	  tree stride = gfc_index_zero_node;
2043 	  int n;
2044 
2045 	  /* Walk both sides of the assignment, once to get the shape of the
2046 	     temporary array to create right.  */
2047 	  lss_for_tmparray = gfc_walk_expr (lhs_expr);
2048 	  /* And a second time to be able to create an assignment of the
2049 	     temporary to the lhs_expr.  gfc_trans_create_temp_array replaces
2050 	     the tree in the descriptor with the one for the temporary
2051 	     array.  */
2052 	  lss_real = gfc_walk_expr (lhs_expr);
2053 	  gfc_init_loopinfo (&loop);
2054 	  gfc_add_ss_to_loop (&loop, lss_for_tmparray);
2055 	  gfc_add_ss_to_loop (&loop, lss_real);
2056 	  gfc_conv_ss_startstride (&loop);
2057 	  gfc_conv_loop_setup (&loop, &lhs_expr->where);
2058 	  lhs_type = gfc_typenode_for_spec (&lhs_expr->ts);
2059 	  gfc_trans_create_temp_array (&lhs_se.pre, &lhs_se.post,
2060 				       lss_for_tmparray, lhs_type, NULL_TREE,
2061 				       false, true, false,
2062 				       &lhs_expr->where);
2063 	  tmparr_desc = lss_for_tmparray->info->data.array.descriptor;
2064 	  gfc_start_scalarized_body (&loop, &body);
2065 	  gfc_init_se (&se, NULL);
2066 	  gfc_copy_loopinfo_to_se (&se, &loop);
2067 	  se.ss = lss_real;
2068 	  gfc_conv_expr (&se, lhs_expr);
2069 	  gfc_add_block_to_block (&body, &se.pre);
2070 
2071 	  /* Walk over all indexes of the loop.  */
2072 	  for (n = loop.dimen - 1; n > 0; --n)
2073 	    {
2074 	      tmp = loop.loopvar[n];
2075 	      tmp = fold_build2_loc (input_location, MINUS_EXPR,
2076 				     gfc_array_index_type, tmp, loop.from[n]);
2077 	      tmp = fold_build2_loc (input_location, PLUS_EXPR,
2078 				     gfc_array_index_type, tmp, index);
2079 
2080 	      stride = fold_build2_loc (input_location, MINUS_EXPR,
2081 					gfc_array_index_type,
2082 					loop.to[n - 1], loop.from[n - 1]);
2083 	      stride = fold_build2_loc (input_location, PLUS_EXPR,
2084 					gfc_array_index_type,
2085 					stride, gfc_index_one_node);
2086 
2087 	      index = fold_build2_loc (input_location, MULT_EXPR,
2088 				       gfc_array_index_type, tmp, stride);
2089 	    }
2090 
2091 	  index = fold_build2_loc (input_location, MINUS_EXPR,
2092 				   gfc_array_index_type,
2093 				   index, loop.from[0]);
2094 
2095 	  index = fold_build2_loc (input_location, PLUS_EXPR,
2096 				   gfc_array_index_type,
2097 				   loop.loopvar[0], index);
2098 
2099 	  src = build_fold_indirect_ref (gfc_conv_array_data (tmparr_desc));
2100 	  src = gfc_build_array_ref (src, index, NULL);
2101 	  /* Now create the assignment of lhs_expr = tmp_array.  */
2102 	  gfc_add_modify (&body, se.expr, src);
2103 	  gfc_add_block_to_block (&body, &se.post);
2104 	  lhs_se.expr = gfc_build_addr_expr (NULL_TREE, tmparr_desc);
2105 	  gfc_trans_scalarizing_loops (&loop, &body);
2106 	  gfc_add_block_to_block (&loop.pre, &loop.post);
2107 	  gfc_add_expr_to_block (&lhs_se.post, gfc_finish_block (&loop.pre));
2108 	  gfc_free_ss (lss_for_tmparray);
2109 	  gfc_free_ss (lss_real);
2110 	}
2111     }
2112 
2113   lhs_kind = build_int_cst (integer_type_node, lhs_expr->ts.kind);
2114 
2115   /* Special case: RHS is a coarray but LHS is not; this code path avoids a
2116      temporary and a loop.  */
2117   if (!gfc_is_coindexed (lhs_expr)
2118       && (!lhs_caf_attr.codimension
2119 	  || !(lhs_expr->rank > 0
2120 	       && (lhs_caf_attr.allocatable || lhs_caf_attr.pointer))))
2121     {
2122       bool lhs_may_realloc = lhs_expr->rank > 0 && lhs_caf_attr.allocatable;
2123       gcc_assert (gfc_is_coindexed (rhs_expr));
2124       gfc_init_se (&rhs_se, NULL);
2125       if (lhs_expr->rank == 0 && lhs_caf_attr.allocatable)
2126 	{
2127 	  gfc_se scal_se;
2128 	  gfc_init_se (&scal_se, NULL);
2129 	  scal_se.want_pointer = 1;
2130 	  gfc_conv_expr (&scal_se, lhs_expr);
2131 	  /* Ensure scalar on lhs is allocated.  */
2132 	  gfc_add_block_to_block (&block, &scal_se.pre);
2133 
2134 	  gfc_allocate_using_malloc (&scal_se.pre, scal_se.expr,
2135 				    TYPE_SIZE_UNIT (
2136 				       gfc_typenode_for_spec (&lhs_expr->ts)),
2137 				    NULL_TREE);
2138 	  tmp = fold_build2 (EQ_EXPR, logical_type_node, scal_se.expr,
2139 			     null_pointer_node);
2140 	  tmp = fold_build3_loc (input_location, COND_EXPR, void_type_node,
2141 				 tmp, gfc_finish_block (&scal_se.pre),
2142 				 build_empty_stmt (input_location));
2143 	  gfc_add_expr_to_block (&block, tmp);
2144 	}
2145       else
2146 	lhs_may_realloc = lhs_may_realloc
2147 	    && gfc_full_array_ref_p (lhs_expr->ref, NULL);
2148       gfc_add_block_to_block (&block, &lhs_se.pre);
2149       gfc_conv_intrinsic_caf_get (&rhs_se, rhs_expr, lhs_se.expr, lhs_kind,
2150 				  may_require_tmp, lhs_may_realloc,
2151 				  &rhs_caf_attr);
2152       gfc_add_block_to_block (&block, &rhs_se.pre);
2153       gfc_add_block_to_block (&block, &rhs_se.post);
2154       gfc_add_block_to_block (&block, &lhs_se.post);
2155       return gfc_finish_block (&block);
2156     }
2157 
2158   gfc_add_block_to_block (&block, &lhs_se.pre);
2159 
2160   /* Obtain token, offset and image index for the LHS.  */
2161   caf_decl = gfc_get_tree_for_caf_expr (lhs_expr);
2162   if (TREE_CODE (TREE_TYPE (caf_decl)) == REFERENCE_TYPE)
2163     caf_decl = build_fold_indirect_ref_loc (input_location, caf_decl);
2164   image_index = gfc_caf_get_image_index (&block, lhs_expr, caf_decl);
2165   tmp = lhs_se.expr;
2166   if (lhs_caf_attr.alloc_comp)
2167     gfc_get_caf_token_offset (&lhs_se, &token, NULL, caf_decl, NULL_TREE,
2168 			      NULL);
2169   else
2170     gfc_get_caf_token_offset (&lhs_se, &token, &offset, caf_decl, tmp,
2171 			      lhs_expr);
2172   lhs_se.expr = tmp;
2173 
2174   /* RHS.  */
2175   gfc_init_se (&rhs_se, NULL);
2176   if (rhs_expr->expr_type == EXPR_FUNCTION && rhs_expr->value.function.isym
2177       && rhs_expr->value.function.isym->id == GFC_ISYM_CONVERSION)
2178     rhs_expr = rhs_expr->value.function.actual->expr;
2179   if (rhs_expr->rank == 0)
2180     {
2181       symbol_attribute attr;
2182       gfc_clear_attr (&attr);
2183       gfc_conv_expr (&rhs_se, rhs_expr);
2184       rhs_se.expr = gfc_conv_scalar_to_descriptor (&rhs_se, rhs_se.expr, attr);
2185       rhs_se.expr = gfc_build_addr_expr (NULL_TREE, rhs_se.expr);
2186     }
2187   else if ((rhs_caf_attr.alloc_comp || rhs_caf_attr.pointer_comp)
2188 	   && rhs_caf_attr.codimension)
2189     {
2190       tree tmp2;
2191       rhs_se.want_pointer = 1;
2192       gfc_conv_expr_descriptor (&rhs_se, rhs_expr);
2193       /* Using gfc_conv_expr_descriptor, we only get the descriptor, but that
2194 	 has the wrong type if component references are done.  */
2195       tmp2 = gfc_typenode_for_spec (&rhs_expr->ts);
2196       tmp = build_fold_indirect_ref_loc (input_location, rhs_se.expr);
2197       gfc_add_modify (&rhs_se.pre, gfc_conv_descriptor_dtype (tmp),
2198 		      gfc_get_dtype_rank_type (
2199 			gfc_has_vector_subscript (rhs_expr)
2200 			? gfc_find_array_ref (rhs_expr)->dimen
2201 			: rhs_expr->rank,
2202 		      tmp2));
2203     }
2204   else
2205     {
2206       /* If has_vector, pass descriptor for whole array and the
2207          vector bounds separately.  */
2208       gfc_array_ref *ar, ar2;
2209       bool has_vector = false;
2210       tree tmp2;
2211 
2212       if (gfc_is_coindexed (rhs_expr) && gfc_has_vector_subscript (rhs_expr))
2213 	{
2214           has_vector = true;
2215           ar = gfc_find_array_ref (rhs_expr);
2216 	  ar2 = *ar;
2217 	  memset (ar, '\0', sizeof (*ar));
2218 	  ar->as = ar2.as;
2219 	  ar->type = AR_FULL;
2220 	}
2221       rhs_se.want_pointer = 1;
2222       gfc_conv_expr_descriptor (&rhs_se, rhs_expr);
2223       /* Using gfc_conv_expr_descriptor, we only get the descriptor, but that
2224          has the wrong type if component references are done.  */
2225       tmp = build_fold_indirect_ref_loc (input_location, rhs_se.expr);
2226       tmp2 = gfc_typenode_for_spec (&rhs_expr->ts);
2227       gfc_add_modify (&rhs_se.pre, gfc_conv_descriptor_dtype (tmp),
2228                       gfc_get_dtype_rank_type (has_vector ? ar2.dimen
2229 							  : rhs_expr->rank,
2230 		      tmp2));
2231       if (has_vector)
2232 	{
2233 	  rhs_vec = conv_caf_vector_subscript (&block, rhs_se.expr, &ar2);
2234 	  *ar = ar2;
2235 	}
2236     }
2237 
2238   gfc_add_block_to_block (&block, &rhs_se.pre);
2239 
2240   rhs_kind = build_int_cst (integer_type_node, rhs_expr->ts.kind);
2241 
2242   tmp_stat = gfc_find_stat_co (lhs_expr);
2243 
2244   if (tmp_stat)
2245     {
2246       gfc_se stat_se;
2247       gfc_init_se (&stat_se, NULL);
2248       gfc_conv_expr_reference (&stat_se, tmp_stat);
2249       dst_stat = stat_se.expr;
2250       gfc_add_block_to_block (&block, &stat_se.pre);
2251       gfc_add_block_to_block (&block, &stat_se.post);
2252     }
2253 
2254   tmp_team = gfc_find_team_co (lhs_expr);
2255 
2256   if (tmp_team)
2257     {
2258       gfc_se team_se;
2259       gfc_init_se (&team_se, NULL);
2260       gfc_conv_expr_reference (&team_se, tmp_team);
2261       dst_team = team_se.expr;
2262       gfc_add_block_to_block (&block, &team_se.pre);
2263       gfc_add_block_to_block (&block, &team_se.post);
2264     }
2265 
2266   if (!gfc_is_coindexed (rhs_expr))
2267     {
2268       if (lhs_caf_attr.alloc_comp || lhs_caf_attr.pointer_comp)
2269 	{
2270 	  tree reference, dst_realloc;
2271 	  reference = conv_expr_ref_to_caf_ref (&block, lhs_expr);
2272 	  dst_realloc = lhs_caf_attr.allocatable ? boolean_true_node
2273 					     : boolean_false_node;
2274 	  tmp = build_call_expr_loc (input_location,
2275 				     gfor_fndecl_caf_send_by_ref,
2276 				     10, token, image_index, rhs_se.expr,
2277 				     reference, lhs_kind, rhs_kind,
2278 				     may_require_tmp, dst_realloc, src_stat,
2279 				     build_int_cst (integer_type_node,
2280 						    lhs_expr->ts.type));
2281 	  }
2282       else
2283 	tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_send, 11,
2284 				   token, offset, image_index, lhs_se.expr, vec,
2285 				   rhs_se.expr, lhs_kind, rhs_kind,
2286 				   may_require_tmp, src_stat, dst_team);
2287     }
2288   else
2289     {
2290       tree rhs_token, rhs_offset, rhs_image_index;
2291 
2292       /* It guarantees memory consistency within the same segment.  */
2293       tmp = gfc_build_string_const (strlen ("memory") + 1, "memory");
2294       tmp = build5_loc (input_location, ASM_EXPR, void_type_node,
2295 			  gfc_build_string_const (1, ""), NULL_TREE, NULL_TREE,
2296 			  tree_cons (NULL_TREE, tmp, NULL_TREE), NULL_TREE);
2297       ASM_VOLATILE_P (tmp) = 1;
2298       gfc_add_expr_to_block (&block, tmp);
2299 
2300       caf_decl = gfc_get_tree_for_caf_expr (rhs_expr);
2301       if (TREE_CODE (TREE_TYPE (caf_decl)) == REFERENCE_TYPE)
2302 	caf_decl = build_fold_indirect_ref_loc (input_location, caf_decl);
2303       rhs_image_index = gfc_caf_get_image_index (&block, rhs_expr, caf_decl);
2304       tmp = rhs_se.expr;
2305       if (rhs_caf_attr.alloc_comp || rhs_caf_attr.pointer_comp)
2306 	{
2307 	  tmp_stat = gfc_find_stat_co (lhs_expr);
2308 
2309 	  if (tmp_stat)
2310 	    {
2311 	      gfc_se stat_se;
2312 	      gfc_init_se (&stat_se, NULL);
2313 	      gfc_conv_expr_reference (&stat_se, tmp_stat);
2314 	      src_stat = stat_se.expr;
2315 	      gfc_add_block_to_block (&block, &stat_se.pre);
2316 	      gfc_add_block_to_block (&block, &stat_se.post);
2317 	    }
2318 
2319 	  gfc_get_caf_token_offset (&rhs_se, &rhs_token, NULL, caf_decl,
2320 				    NULL_TREE, NULL);
2321 	  tree lhs_reference, rhs_reference;
2322 	  lhs_reference = conv_expr_ref_to_caf_ref (&block, lhs_expr);
2323 	  rhs_reference = conv_expr_ref_to_caf_ref (&block, rhs_expr);
2324 	  tmp = build_call_expr_loc (input_location,
2325 				     gfor_fndecl_caf_sendget_by_ref, 13,
2326 				     token, image_index, lhs_reference,
2327 				     rhs_token, rhs_image_index, rhs_reference,
2328 				     lhs_kind, rhs_kind, may_require_tmp,
2329 				     dst_stat, src_stat,
2330 				     build_int_cst (integer_type_node,
2331 						    lhs_expr->ts.type),
2332 				     build_int_cst (integer_type_node,
2333 						    rhs_expr->ts.type));
2334 	}
2335       else
2336 	{
2337 	  gfc_get_caf_token_offset (&rhs_se, &rhs_token, &rhs_offset, caf_decl,
2338 				    tmp, rhs_expr);
2339 	  tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_sendget,
2340 				     14, token, offset, image_index,
2341 				     lhs_se.expr, vec, rhs_token, rhs_offset,
2342 				     rhs_image_index, tmp, rhs_vec, lhs_kind,
2343 				     rhs_kind, may_require_tmp, src_stat);
2344 	}
2345     }
2346   gfc_add_expr_to_block (&block, tmp);
2347   gfc_add_block_to_block (&block, &lhs_se.post);
2348   gfc_add_block_to_block (&block, &rhs_se.post);
2349 
2350   /* It guarantees memory consistency within the same segment.  */
2351   tmp = gfc_build_string_const (strlen ("memory") + 1, "memory");
2352   tmp = build5_loc (input_location, ASM_EXPR, void_type_node,
2353 		    gfc_build_string_const (1, ""), NULL_TREE, NULL_TREE,
2354 		    tree_cons (NULL_TREE, tmp, NULL_TREE), NULL_TREE);
2355   ASM_VOLATILE_P (tmp) = 1;
2356   gfc_add_expr_to_block (&block, tmp);
2357 
2358   return gfc_finish_block (&block);
2359 }
2360 
2361 
2362 static void
trans_this_image(gfc_se * se,gfc_expr * expr)2363 trans_this_image (gfc_se * se, gfc_expr *expr)
2364 {
2365   stmtblock_t loop;
2366   tree type, desc, dim_arg, cond, tmp, m, loop_var, exit_label, min_var,
2367        lbound, ubound, extent, ml;
2368   gfc_se argse;
2369   int rank, corank;
2370   gfc_expr *distance = expr->value.function.actual->next->next->expr;
2371 
2372   if (expr->value.function.actual->expr
2373       && !gfc_is_coarray (expr->value.function.actual->expr))
2374     distance = expr->value.function.actual->expr;
2375 
2376   /* The case -fcoarray=single is handled elsewhere.  */
2377   gcc_assert (flag_coarray != GFC_FCOARRAY_SINGLE);
2378 
2379   /* Argument-free version: THIS_IMAGE().  */
2380   if (distance || expr->value.function.actual->expr == NULL)
2381     {
2382       if (distance)
2383 	{
2384 	  gfc_init_se (&argse, NULL);
2385 	  gfc_conv_expr_val (&argse, distance);
2386 	  gfc_add_block_to_block (&se->pre, &argse.pre);
2387 	  gfc_add_block_to_block (&se->post, &argse.post);
2388 	  tmp = fold_convert (integer_type_node, argse.expr);
2389 	}
2390       else
2391 	tmp = integer_zero_node;
2392       tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_this_image, 1,
2393 				 tmp);
2394       se->expr = fold_convert (gfc_get_int_type (gfc_default_integer_kind),
2395 			       tmp);
2396       return;
2397     }
2398 
2399   /* Coarray-argument version: THIS_IMAGE(coarray [, dim]).  */
2400 
2401   type = gfc_get_int_type (gfc_default_integer_kind);
2402   corank = gfc_get_corank (expr->value.function.actual->expr);
2403   rank = expr->value.function.actual->expr->rank;
2404 
2405   /* Obtain the descriptor of the COARRAY.  */
2406   gfc_init_se (&argse, NULL);
2407   argse.want_coarray = 1;
2408   gfc_conv_expr_descriptor (&argse, expr->value.function.actual->expr);
2409   gfc_add_block_to_block (&se->pre, &argse.pre);
2410   gfc_add_block_to_block (&se->post, &argse.post);
2411   desc = argse.expr;
2412 
2413   if (se->ss)
2414     {
2415       /* Create an implicit second parameter from the loop variable.  */
2416       gcc_assert (!expr->value.function.actual->next->expr);
2417       gcc_assert (corank > 0);
2418       gcc_assert (se->loop->dimen == 1);
2419       gcc_assert (se->ss->info->expr == expr);
2420 
2421       dim_arg = se->loop->loopvar[0];
2422       dim_arg = fold_build2_loc (input_location, PLUS_EXPR,
2423 				 gfc_array_index_type, dim_arg,
2424 				 build_int_cst (TREE_TYPE (dim_arg), 1));
2425       gfc_advance_se_ss_chain (se);
2426     }
2427   else
2428     {
2429       /* Use the passed DIM= argument.  */
2430       gcc_assert (expr->value.function.actual->next->expr);
2431       gfc_init_se (&argse, NULL);
2432       gfc_conv_expr_type (&argse, expr->value.function.actual->next->expr,
2433 			  gfc_array_index_type);
2434       gfc_add_block_to_block (&se->pre, &argse.pre);
2435       dim_arg = argse.expr;
2436 
2437       if (INTEGER_CST_P (dim_arg))
2438 	{
2439 	  if (wi::ltu_p (wi::to_wide (dim_arg), 1)
2440 	      || wi::gtu_p (wi::to_wide (dim_arg),
2441 			    GFC_TYPE_ARRAY_CORANK (TREE_TYPE (desc))))
2442 	    gfc_error ("%<dim%> argument of %s intrinsic at %L is not a valid "
2443 		       "dimension index", expr->value.function.isym->name,
2444 		       &expr->where);
2445 	}
2446      else if (gfc_option.rtcheck & GFC_RTCHECK_BOUNDS)
2447 	{
2448 	  dim_arg = gfc_evaluate_now (dim_arg, &se->pre);
2449 	  cond = fold_build2_loc (input_location, LT_EXPR, logical_type_node,
2450 				  dim_arg,
2451 				  build_int_cst (TREE_TYPE (dim_arg), 1));
2452 	  tmp = gfc_rank_cst[GFC_TYPE_ARRAY_CORANK (TREE_TYPE (desc))];
2453 	  tmp = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
2454 				 dim_arg, tmp);
2455 	  cond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
2456 				  logical_type_node, cond, tmp);
2457 	  gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
2458 			           gfc_msg_fault);
2459 	}
2460     }
2461 
2462   /* Used algorithm; cf. Fortran 2008, C.10. Note, due to the scalarizer,
2463      one always has a dim_arg argument.
2464 
2465      m = this_image() - 1
2466      if (corank == 1)
2467        {
2468 	 sub(1) = m + lcobound(corank)
2469 	 return;
2470        }
2471      i = rank
2472      min_var = min (rank + corank - 2, rank + dim_arg - 1)
2473      for (;;)
2474        {
2475 	 extent = gfc_extent(i)
2476 	 ml = m
2477 	 m  = m/extent
2478 	 if (i >= min_var)
2479 	   goto exit_label
2480 	 i++
2481        }
2482      exit_label:
2483      sub(dim_arg) = (dim_arg < corank) ? ml - m*extent + lcobound(dim_arg)
2484 				       : m + lcobound(corank)
2485   */
2486 
2487   /* this_image () - 1.  */
2488   tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_this_image, 1,
2489 			     integer_zero_node);
2490   tmp = fold_build2_loc (input_location, MINUS_EXPR, type,
2491 			 fold_convert (type, tmp), build_int_cst (type, 1));
2492   if (corank == 1)
2493     {
2494       /* sub(1) = m + lcobound(corank).  */
2495       lbound = gfc_conv_descriptor_lbound_get (desc,
2496 			build_int_cst (TREE_TYPE (gfc_array_index_type),
2497 				       corank+rank-1));
2498       lbound = fold_convert (type, lbound);
2499       tmp = fold_build2_loc (input_location, PLUS_EXPR, type, tmp, lbound);
2500 
2501       se->expr = tmp;
2502       return;
2503     }
2504 
2505   m = gfc_create_var (type, NULL);
2506   ml = gfc_create_var (type, NULL);
2507   loop_var = gfc_create_var (integer_type_node, NULL);
2508   min_var = gfc_create_var (integer_type_node, NULL);
2509 
2510   /* m = this_image () - 1.  */
2511   gfc_add_modify (&se->pre, m, tmp);
2512 
2513   /* min_var = min (rank + corank-2, rank + dim_arg - 1).  */
2514   tmp = fold_build2_loc (input_location, PLUS_EXPR, integer_type_node,
2515 			 fold_convert (integer_type_node, dim_arg),
2516 			 build_int_cst (integer_type_node, rank - 1));
2517   tmp = fold_build2_loc (input_location, MIN_EXPR, integer_type_node,
2518 			 build_int_cst (integer_type_node, rank + corank - 2),
2519 			 tmp);
2520   gfc_add_modify (&se->pre, min_var, tmp);
2521 
2522   /* i = rank.  */
2523   tmp = build_int_cst (integer_type_node, rank);
2524   gfc_add_modify (&se->pre, loop_var, tmp);
2525 
2526   exit_label = gfc_build_label_decl (NULL_TREE);
2527   TREE_USED (exit_label) = 1;
2528 
2529   /* Loop body.  */
2530   gfc_init_block (&loop);
2531 
2532   /* ml = m.  */
2533   gfc_add_modify (&loop, ml, m);
2534 
2535   /* extent = ...  */
2536   lbound = gfc_conv_descriptor_lbound_get (desc, loop_var);
2537   ubound = gfc_conv_descriptor_ubound_get (desc, loop_var);
2538   extent = gfc_conv_array_extent_dim (lbound, ubound, NULL);
2539   extent = fold_convert (type, extent);
2540 
2541   /* m = m/extent.  */
2542   gfc_add_modify (&loop, m,
2543 		  fold_build2_loc (input_location, TRUNC_DIV_EXPR, type,
2544 			  m, extent));
2545 
2546   /* Exit condition:  if (i >= min_var) goto exit_label.  */
2547   cond = fold_build2_loc (input_location, GE_EXPR, logical_type_node, loop_var,
2548 		  min_var);
2549   tmp = build1_v (GOTO_EXPR, exit_label);
2550   tmp = fold_build3_loc (input_location, COND_EXPR, void_type_node, cond, tmp,
2551                          build_empty_stmt (input_location));
2552   gfc_add_expr_to_block (&loop, tmp);
2553 
2554   /* Increment loop variable: i++.  */
2555   gfc_add_modify (&loop, loop_var,
2556                   fold_build2_loc (input_location, PLUS_EXPR, integer_type_node,
2557 				   loop_var,
2558 				   build_int_cst (integer_type_node, 1)));
2559 
2560   /* Making the loop... actually loop!  */
2561   tmp = gfc_finish_block (&loop);
2562   tmp = build1_v (LOOP_EXPR, tmp);
2563   gfc_add_expr_to_block (&se->pre, tmp);
2564 
2565   /* The exit label.  */
2566   tmp = build1_v (LABEL_EXPR, exit_label);
2567   gfc_add_expr_to_block (&se->pre, tmp);
2568 
2569   /*  sub(co_dim) = (co_dim < corank) ? ml - m*extent + lcobound(dim_arg)
2570 				      : m + lcobound(corank) */
2571 
2572   cond = fold_build2_loc (input_location, LT_EXPR, logical_type_node, dim_arg,
2573 			  build_int_cst (TREE_TYPE (dim_arg), corank));
2574 
2575   lbound = gfc_conv_descriptor_lbound_get (desc,
2576 		fold_build2_loc (input_location, PLUS_EXPR,
2577 				 gfc_array_index_type, dim_arg,
2578 				 build_int_cst (TREE_TYPE (dim_arg), rank-1)));
2579   lbound = fold_convert (type, lbound);
2580 
2581   tmp = fold_build2_loc (input_location, MINUS_EXPR, type, ml,
2582 			 fold_build2_loc (input_location, MULT_EXPR, type,
2583 					  m, extent));
2584   tmp = fold_build2_loc (input_location, PLUS_EXPR, type, tmp, lbound);
2585 
2586   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond, tmp,
2587 			      fold_build2_loc (input_location, PLUS_EXPR, type,
2588 					       m, lbound));
2589 }
2590 
2591 
2592 /* Convert a call to image_status.  */
2593 
2594 static void
conv_intrinsic_image_status(gfc_se * se,gfc_expr * expr)2595 conv_intrinsic_image_status (gfc_se *se, gfc_expr *expr)
2596 {
2597   unsigned int num_args;
2598   tree *args, tmp;
2599 
2600   num_args = gfc_intrinsic_argument_list_length (expr);
2601   args = XALLOCAVEC (tree, num_args);
2602   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
2603   /* In args[0] the number of the image the status is desired for has to be
2604      given.  */
2605 
2606   if (flag_coarray == GFC_FCOARRAY_SINGLE)
2607     {
2608       tree arg;
2609       arg = gfc_evaluate_now (args[0], &se->pre);
2610       tmp = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
2611 			     fold_convert (integer_type_node, arg),
2612 			     integer_one_node);
2613       tmp = fold_build3_loc (input_location, COND_EXPR, integer_type_node,
2614 			     tmp, integer_zero_node,
2615 			     build_int_cst (integer_type_node,
2616 					    GFC_STAT_STOPPED_IMAGE));
2617     }
2618   else if (flag_coarray == GFC_FCOARRAY_LIB)
2619     tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_image_status, 2,
2620 			       args[0], build_int_cst (integer_type_node, -1));
2621   else
2622     gcc_unreachable ();
2623 
2624   se->expr = fold_convert (gfc_get_int_type (gfc_default_integer_kind), tmp);
2625 }
2626 
2627 static void
conv_intrinsic_team_number(gfc_se * se,gfc_expr * expr)2628 conv_intrinsic_team_number (gfc_se *se, gfc_expr *expr)
2629 {
2630   unsigned int num_args;
2631 
2632   tree *args, tmp;
2633 
2634   num_args = gfc_intrinsic_argument_list_length (expr);
2635   args = XALLOCAVEC (tree, num_args);
2636   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
2637 
2638   if (flag_coarray ==
2639       GFC_FCOARRAY_SINGLE && expr->value.function.actual->expr)
2640     {
2641       tree arg;
2642 
2643       arg = gfc_evaluate_now (args[0], &se->pre);
2644       tmp = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
2645       			     fold_convert (integer_type_node, arg),
2646       			     integer_one_node);
2647       tmp = fold_build3_loc (input_location, COND_EXPR, integer_type_node,
2648       			     tmp, integer_zero_node,
2649       			     build_int_cst (integer_type_node,
2650       					    GFC_STAT_STOPPED_IMAGE));
2651     }
2652   else if (flag_coarray == GFC_FCOARRAY_SINGLE)
2653     {
2654       // the value -1 represents that no team has been created yet
2655       tmp = build_int_cst (integer_type_node, -1);
2656     }
2657   else if (flag_coarray == GFC_FCOARRAY_LIB && expr->value.function.actual->expr)
2658     tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_team_number, 1,
2659 			       args[0], build_int_cst (integer_type_node, -1));
2660   else if (flag_coarray == GFC_FCOARRAY_LIB)
2661     tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_team_number, 1,
2662 		integer_zero_node, build_int_cst (integer_type_node, -1));
2663   else
2664     gcc_unreachable ();
2665 
2666   se->expr = fold_convert (gfc_get_int_type (gfc_default_integer_kind), tmp);
2667 }
2668 
2669 
2670 static void
trans_image_index(gfc_se * se,gfc_expr * expr)2671 trans_image_index (gfc_se * se, gfc_expr *expr)
2672 {
2673   tree num_images, cond, coindex, type, lbound, ubound, desc, subdesc,
2674        tmp, invalid_bound;
2675   gfc_se argse, subse;
2676   int rank, corank, codim;
2677 
2678   type = gfc_get_int_type (gfc_default_integer_kind);
2679   corank = gfc_get_corank (expr->value.function.actual->expr);
2680   rank = expr->value.function.actual->expr->rank;
2681 
2682   /* Obtain the descriptor of the COARRAY.  */
2683   gfc_init_se (&argse, NULL);
2684   argse.want_coarray = 1;
2685   gfc_conv_expr_descriptor (&argse, expr->value.function.actual->expr);
2686   gfc_add_block_to_block (&se->pre, &argse.pre);
2687   gfc_add_block_to_block (&se->post, &argse.post);
2688   desc = argse.expr;
2689 
2690   /* Obtain a handle to the SUB argument.  */
2691   gfc_init_se (&subse, NULL);
2692   gfc_conv_expr_descriptor (&subse, expr->value.function.actual->next->expr);
2693   gfc_add_block_to_block (&se->pre, &subse.pre);
2694   gfc_add_block_to_block (&se->post, &subse.post);
2695   subdesc = build_fold_indirect_ref_loc (input_location,
2696 			gfc_conv_descriptor_data_get (subse.expr));
2697 
2698   /* Fortran 2008 does not require that the values remain in the cobounds,
2699      thus we need explicitly check this - and return 0 if they are exceeded.  */
2700 
2701   lbound = gfc_conv_descriptor_lbound_get (desc, gfc_rank_cst[rank+corank-1]);
2702   tmp = gfc_build_array_ref (subdesc, gfc_rank_cst[corank-1], NULL);
2703   invalid_bound = fold_build2_loc (input_location, LT_EXPR, logical_type_node,
2704 				 fold_convert (gfc_array_index_type, tmp),
2705 				 lbound);
2706 
2707   for (codim = corank + rank - 2; codim >= rank; codim--)
2708     {
2709       lbound = gfc_conv_descriptor_lbound_get (desc, gfc_rank_cst[codim]);
2710       ubound = gfc_conv_descriptor_ubound_get (desc, gfc_rank_cst[codim]);
2711       tmp = gfc_build_array_ref (subdesc, gfc_rank_cst[codim-rank], NULL);
2712       cond = fold_build2_loc (input_location, LT_EXPR, logical_type_node,
2713 			      fold_convert (gfc_array_index_type, tmp),
2714 			      lbound);
2715       invalid_bound = fold_build2_loc (input_location, TRUTH_OR_EXPR,
2716 				       logical_type_node, invalid_bound, cond);
2717       cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
2718 			      fold_convert (gfc_array_index_type, tmp),
2719 			      ubound);
2720       invalid_bound = fold_build2_loc (input_location, TRUTH_OR_EXPR,
2721 				       logical_type_node, invalid_bound, cond);
2722     }
2723 
2724   invalid_bound = gfc_unlikely (invalid_bound, PRED_FORTRAN_INVALID_BOUND);
2725 
2726   /* See Fortran 2008, C.10 for the following algorithm.  */
2727 
2728   /* coindex = sub(corank) - lcobound(n).  */
2729   coindex = fold_convert (gfc_array_index_type,
2730 			  gfc_build_array_ref (subdesc, gfc_rank_cst[corank-1],
2731 					       NULL));
2732   lbound = gfc_conv_descriptor_lbound_get (desc, gfc_rank_cst[rank+corank-1]);
2733   coindex = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
2734 			     fold_convert (gfc_array_index_type, coindex),
2735 			     lbound);
2736 
2737   for (codim = corank + rank - 2; codim >= rank; codim--)
2738     {
2739       tree extent, ubound;
2740 
2741       /* coindex = coindex*extent(codim) + sub(codim) - lcobound(codim).  */
2742       lbound = gfc_conv_descriptor_lbound_get (desc, gfc_rank_cst[codim]);
2743       ubound = gfc_conv_descriptor_ubound_get (desc, gfc_rank_cst[codim]);
2744       extent = gfc_conv_array_extent_dim (lbound, ubound, NULL);
2745 
2746       /* coindex *= extent.  */
2747       coindex = fold_build2_loc (input_location, MULT_EXPR,
2748 				 gfc_array_index_type, coindex, extent);
2749 
2750       /* coindex += sub(codim).  */
2751       tmp = gfc_build_array_ref (subdesc, gfc_rank_cst[codim-rank], NULL);
2752       coindex = fold_build2_loc (input_location, PLUS_EXPR,
2753 				 gfc_array_index_type, coindex,
2754 				 fold_convert (gfc_array_index_type, tmp));
2755 
2756       /* coindex -= lbound(codim).  */
2757       lbound = gfc_conv_descriptor_lbound_get (desc, gfc_rank_cst[codim]);
2758       coindex = fold_build2_loc (input_location, MINUS_EXPR,
2759 				 gfc_array_index_type, coindex, lbound);
2760     }
2761 
2762   coindex = fold_build2_loc (input_location, PLUS_EXPR, type,
2763 			     fold_convert(type, coindex),
2764 			     build_int_cst (type, 1));
2765 
2766   /* Return 0 if "coindex" exceeds num_images().  */
2767 
2768   if (flag_coarray == GFC_FCOARRAY_SINGLE)
2769     num_images = build_int_cst (type, 1);
2770   else
2771     {
2772       tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_num_images, 2,
2773 				 integer_zero_node,
2774 				 build_int_cst (integer_type_node, -1));
2775       num_images = fold_convert (type, tmp);
2776     }
2777 
2778   tmp = gfc_create_var (type, NULL);
2779   gfc_add_modify (&se->pre, tmp, coindex);
2780 
2781   cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node, tmp,
2782 			  num_images);
2783   cond = fold_build2_loc (input_location, TRUTH_OR_EXPR, logical_type_node,
2784 			  cond,
2785 			  fold_convert (logical_type_node, invalid_bound));
2786   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond,
2787 			      build_int_cst (type, 0), tmp);
2788 }
2789 
2790 static void
trans_num_images(gfc_se * se,gfc_expr * expr)2791 trans_num_images (gfc_se * se, gfc_expr *expr)
2792 {
2793   tree tmp, distance, failed;
2794   gfc_se argse;
2795 
2796   if (expr->value.function.actual->expr)
2797     {
2798       gfc_init_se (&argse, NULL);
2799       gfc_conv_expr_val (&argse, expr->value.function.actual->expr);
2800       gfc_add_block_to_block (&se->pre, &argse.pre);
2801       gfc_add_block_to_block (&se->post, &argse.post);
2802       distance = fold_convert (integer_type_node, argse.expr);
2803     }
2804   else
2805     distance = integer_zero_node;
2806 
2807   if (expr->value.function.actual->next->expr)
2808     {
2809       gfc_init_se (&argse, NULL);
2810       gfc_conv_expr_val (&argse, expr->value.function.actual->next->expr);
2811       gfc_add_block_to_block (&se->pre, &argse.pre);
2812       gfc_add_block_to_block (&se->post, &argse.post);
2813       failed = fold_convert (integer_type_node, argse.expr);
2814     }
2815   else
2816     failed = build_int_cst (integer_type_node, -1);
2817   tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_num_images, 2,
2818 			     distance, failed);
2819   se->expr = fold_convert (gfc_get_int_type (gfc_default_integer_kind), tmp);
2820 }
2821 
2822 
2823 static void
gfc_conv_intrinsic_rank(gfc_se * se,gfc_expr * expr)2824 gfc_conv_intrinsic_rank (gfc_se *se, gfc_expr *expr)
2825 {
2826   gfc_se argse;
2827 
2828   gfc_init_se (&argse, NULL);
2829   argse.data_not_needed = 1;
2830   argse.descriptor_only = 1;
2831 
2832   gfc_conv_expr_descriptor (&argse, expr->value.function.actual->expr);
2833   gfc_add_block_to_block (&se->pre, &argse.pre);
2834   gfc_add_block_to_block (&se->post, &argse.post);
2835 
2836   se->expr = gfc_conv_descriptor_rank (argse.expr);
2837   se->expr = fold_convert (gfc_get_int_type (gfc_default_integer_kind),
2838 			   se->expr);
2839 }
2840 
2841 
2842 static void
gfc_conv_intrinsic_is_contiguous(gfc_se * se,gfc_expr * expr)2843 gfc_conv_intrinsic_is_contiguous (gfc_se * se, gfc_expr * expr)
2844 {
2845   gfc_expr *arg;
2846   arg = expr->value.function.actual->expr;
2847   gfc_conv_is_contiguous_expr (se, arg);
2848   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), se->expr);
2849 }
2850 
2851 /* This function does the work for gfc_conv_intrinsic_is_contiguous,
2852    plus it can be called directly.  */
2853 
2854 void
gfc_conv_is_contiguous_expr(gfc_se * se,gfc_expr * arg)2855 gfc_conv_is_contiguous_expr (gfc_se *se, gfc_expr *arg)
2856 {
2857   gfc_ss *ss;
2858   gfc_se argse;
2859   tree desc, tmp, stride, extent, cond;
2860   int i;
2861   tree fncall0;
2862   gfc_array_spec *as;
2863 
2864   if (arg->ts.type == BT_CLASS)
2865     gfc_add_class_array_ref (arg);
2866 
2867   ss = gfc_walk_expr (arg);
2868   gcc_assert (ss != gfc_ss_terminator);
2869   gfc_init_se (&argse, NULL);
2870   argse.data_not_needed = 1;
2871   gfc_conv_expr_descriptor (&argse, arg);
2872 
2873   as = gfc_get_full_arrayspec_from_expr (arg);
2874 
2875   /* Create:  stride[0] == 1 && stride[1] == extend[0]*stride[0] && ...
2876      Note in addition that zero-sized arrays don't count as contiguous.  */
2877 
2878   if (as && as->type == AS_ASSUMED_RANK)
2879     {
2880       /* Build the call to is_contiguous0.  */
2881       argse.want_pointer = 1;
2882       gfc_conv_expr_descriptor (&argse, arg);
2883       gfc_add_block_to_block (&se->pre, &argse.pre);
2884       gfc_add_block_to_block (&se->post, &argse.post);
2885       desc = gfc_evaluate_now (argse.expr, &se->pre);
2886       fncall0 = build_call_expr_loc (input_location,
2887 				     gfor_fndecl_is_contiguous0, 1, desc);
2888       se->expr = fncall0;
2889       se->expr = convert (logical_type_node, se->expr);
2890     }
2891   else
2892     {
2893       gfc_add_block_to_block (&se->pre, &argse.pre);
2894       gfc_add_block_to_block (&se->post, &argse.post);
2895       desc = gfc_evaluate_now (argse.expr, &se->pre);
2896 
2897       stride = gfc_conv_descriptor_stride_get (desc, gfc_rank_cst[0]);
2898       cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
2899 			      stride, build_int_cst (TREE_TYPE (stride), 1));
2900 
2901       for (i = 0; i < arg->rank - 1; i++)
2902 	{
2903 	  tmp = gfc_conv_descriptor_lbound_get (desc, gfc_rank_cst[i]);
2904 	  extent = gfc_conv_descriptor_ubound_get (desc, gfc_rank_cst[i]);
2905 	  extent = fold_build2_loc (input_location, MINUS_EXPR,
2906 				    gfc_array_index_type, extent, tmp);
2907 	  extent = fold_build2_loc (input_location, PLUS_EXPR,
2908 				    gfc_array_index_type, extent,
2909 				    gfc_index_one_node);
2910 	  tmp = gfc_conv_descriptor_stride_get (desc, gfc_rank_cst[i]);
2911 	  tmp = fold_build2_loc (input_location, MULT_EXPR, TREE_TYPE (tmp),
2912 				 tmp, extent);
2913 	  stride = gfc_conv_descriptor_stride_get (desc, gfc_rank_cst[i+1]);
2914 	  tmp = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
2915 				 stride, tmp);
2916 	  cond = fold_build2_loc (input_location, TRUTH_AND_EXPR,
2917 				  boolean_type_node, cond, tmp);
2918 	}
2919       se->expr = cond;
2920     }
2921 }
2922 
2923 
2924 /* Evaluate a single upper or lower bound.  */
2925 /* TODO: bound intrinsic generates way too much unnecessary code.  */
2926 
2927 static void
gfc_conv_intrinsic_bound(gfc_se * se,gfc_expr * expr,enum gfc_isym_id op)2928 gfc_conv_intrinsic_bound (gfc_se * se, gfc_expr * expr, enum gfc_isym_id op)
2929 {
2930   gfc_actual_arglist *arg;
2931   gfc_actual_arglist *arg2;
2932   tree desc;
2933   tree type;
2934   tree bound;
2935   tree tmp;
2936   tree cond, cond1;
2937   tree ubound;
2938   tree lbound;
2939   tree size;
2940   gfc_se argse;
2941   gfc_array_spec * as;
2942   bool assumed_rank_lb_one;
2943 
2944   arg = expr->value.function.actual;
2945   arg2 = arg->next;
2946 
2947   if (se->ss)
2948     {
2949       /* Create an implicit second parameter from the loop variable.  */
2950       gcc_assert (!arg2->expr || op == GFC_ISYM_SHAPE);
2951       gcc_assert (se->loop->dimen == 1);
2952       gcc_assert (se->ss->info->expr == expr);
2953       gfc_advance_se_ss_chain (se);
2954       bound = se->loop->loopvar[0];
2955       bound = fold_build2_loc (input_location, MINUS_EXPR,
2956 			       gfc_array_index_type, bound,
2957 			       se->loop->from[0]);
2958     }
2959   else
2960     {
2961       /* use the passed argument.  */
2962       gcc_assert (arg2->expr);
2963       gfc_init_se (&argse, NULL);
2964       gfc_conv_expr_type (&argse, arg2->expr, gfc_array_index_type);
2965       gfc_add_block_to_block (&se->pre, &argse.pre);
2966       bound = argse.expr;
2967       /* Convert from one based to zero based.  */
2968       bound = fold_build2_loc (input_location, MINUS_EXPR,
2969 			       gfc_array_index_type, bound,
2970 			       gfc_index_one_node);
2971     }
2972 
2973   /* TODO: don't re-evaluate the descriptor on each iteration.  */
2974   /* Get a descriptor for the first parameter.  */
2975   gfc_init_se (&argse, NULL);
2976   gfc_conv_expr_descriptor (&argse, arg->expr);
2977   gfc_add_block_to_block (&se->pre, &argse.pre);
2978   gfc_add_block_to_block (&se->post, &argse.post);
2979 
2980   desc = argse.expr;
2981 
2982   as = gfc_get_full_arrayspec_from_expr (arg->expr);
2983 
2984   if (INTEGER_CST_P (bound))
2985     {
2986       gcc_assert (op != GFC_ISYM_SHAPE);
2987       if (((!as || as->type != AS_ASSUMED_RANK)
2988 	   && wi::geu_p (wi::to_wide (bound),
2989 			 GFC_TYPE_ARRAY_RANK (TREE_TYPE (desc))))
2990 	  || wi::gtu_p (wi::to_wide (bound), GFC_MAX_DIMENSIONS))
2991 	gfc_error ("%<dim%> argument of %s intrinsic at %L is not a valid "
2992 		   "dimension index",
2993 		   (op == GFC_ISYM_UBOUND) ? "UBOUND" : "LBOUND",
2994 		   &expr->where);
2995     }
2996 
2997   if (!INTEGER_CST_P (bound) || (as && as->type == AS_ASSUMED_RANK))
2998     {
2999       if (gfc_option.rtcheck & GFC_RTCHECK_BOUNDS)
3000         {
3001           bound = gfc_evaluate_now (bound, &se->pre);
3002           cond = fold_build2_loc (input_location, LT_EXPR, logical_type_node,
3003 				  bound, build_int_cst (TREE_TYPE (bound), 0));
3004 	  if (as && as->type == AS_ASSUMED_RANK)
3005 	    tmp = gfc_conv_descriptor_rank (desc);
3006 	  else
3007 	    tmp = gfc_rank_cst[GFC_TYPE_ARRAY_RANK (TREE_TYPE (desc))];
3008           tmp = fold_build2_loc (input_location, GE_EXPR, logical_type_node,
3009 				 bound, fold_convert(TREE_TYPE (bound), tmp));
3010           cond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
3011 				  logical_type_node, cond, tmp);
3012           gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
3013 				   gfc_msg_fault);
3014         }
3015     }
3016 
3017   /* Take care of the lbound shift for assumed-rank arrays that are
3018      nonallocatable and nonpointers. Those have a lbound of 1.  */
3019   assumed_rank_lb_one = as && as->type == AS_ASSUMED_RANK
3020 			&& ((arg->expr->ts.type != BT_CLASS
3021 			     && !arg->expr->symtree->n.sym->attr.allocatable
3022 			     && !arg->expr->symtree->n.sym->attr.pointer)
3023 			    || (arg->expr->ts.type == BT_CLASS
3024 			     && !CLASS_DATA (arg->expr)->attr.allocatable
3025 			     && !CLASS_DATA (arg->expr)->attr.class_pointer));
3026 
3027   ubound = gfc_conv_descriptor_ubound_get (desc, bound);
3028   lbound = gfc_conv_descriptor_lbound_get (desc, bound);
3029   size = fold_build2_loc (input_location, MINUS_EXPR,
3030 			  gfc_array_index_type, ubound, lbound);
3031   size = fold_build2_loc (input_location, PLUS_EXPR,
3032 			  gfc_array_index_type, size, gfc_index_one_node);
3033 
3034   /* 13.14.53: Result value for LBOUND
3035 
3036      Case (i): For an array section or for an array expression other than a
3037                whole array or array structure component, LBOUND(ARRAY, DIM)
3038                has the value 1.  For a whole array or array structure
3039                component, LBOUND(ARRAY, DIM) has the value:
3040                  (a) equal to the lower bound for subscript DIM of ARRAY if
3041                      dimension DIM of ARRAY does not have extent zero
3042                      or if ARRAY is an assumed-size array of rank DIM,
3043               or (b) 1 otherwise.
3044 
3045      13.14.113: Result value for UBOUND
3046 
3047      Case (i): For an array section or for an array expression other than a
3048                whole array or array structure component, UBOUND(ARRAY, DIM)
3049                has the value equal to the number of elements in the given
3050                dimension; otherwise, it has a value equal to the upper bound
3051                for subscript DIM of ARRAY if dimension DIM of ARRAY does
3052                not have size zero and has value zero if dimension DIM has
3053                size zero.  */
3054 
3055   if (op == GFC_ISYM_LBOUND && assumed_rank_lb_one)
3056     se->expr = gfc_index_one_node;
3057   else if (as)
3058     {
3059       if (op == GFC_ISYM_UBOUND)
3060 	{
3061 	  cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
3062 				  size, gfc_index_zero_node);
3063 	  se->expr = fold_build3_loc (input_location, COND_EXPR,
3064 				      gfc_array_index_type, cond,
3065 				      (assumed_rank_lb_one ? size : ubound),
3066 				      gfc_index_zero_node);
3067 	}
3068       else if (op == GFC_ISYM_LBOUND)
3069 	{
3070 	  cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
3071 				  size, gfc_index_zero_node);
3072 	  if (as->type == AS_ASSUMED_SIZE)
3073 	    {
3074 	      cond1 = fold_build2_loc (input_location, EQ_EXPR,
3075 				       logical_type_node, bound,
3076 				       build_int_cst (TREE_TYPE (bound),
3077 						      arg->expr->rank - 1));
3078 	      cond = fold_build2_loc (input_location, TRUTH_OR_EXPR,
3079 				      logical_type_node, cond, cond1);
3080 	    }
3081 	  se->expr = fold_build3_loc (input_location, COND_EXPR,
3082 				      gfc_array_index_type, cond,
3083 				      lbound, gfc_index_one_node);
3084 	}
3085       else if (op == GFC_ISYM_SHAPE)
3086 	se->expr = fold_build2_loc (input_location, MAX_EXPR,
3087 				    gfc_array_index_type, size,
3088 				    gfc_index_zero_node);
3089       else
3090 	gcc_unreachable ();
3091 
3092       /* According to F2018 16.9.172, para 5, an assumed rank object,
3093 	 argument associated with and assumed size array, has the ubound
3094 	 of the final dimension set to -1 and UBOUND must return this.
3095 	 Similarly for the SHAPE intrinsic.  */
3096       if (op != GFC_ISYM_LBOUND && assumed_rank_lb_one)
3097 	{
3098 	  tree minus_one = build_int_cst (gfc_array_index_type, -1);
3099 	  tree rank = fold_convert (gfc_array_index_type,
3100 				    gfc_conv_descriptor_rank (desc));
3101 	  rank = fold_build2_loc (input_location, PLUS_EXPR,
3102 				  gfc_array_index_type, rank, minus_one);
3103 
3104 	  /* Fix the expression to stop it from becoming even more
3105 	     complicated.  */
3106 	  se->expr = gfc_evaluate_now (se->expr, &se->pre);
3107 
3108 	  /* Descriptors for assumed-size arrays have ubound = -1
3109 	     in the last dimension.  */
3110 	  cond1 = fold_build2_loc (input_location, EQ_EXPR,
3111 				   logical_type_node, ubound, minus_one);
3112 	  cond = fold_build2_loc (input_location, EQ_EXPR,
3113 				  logical_type_node, bound, rank);
3114 	  cond = fold_build2_loc (input_location, TRUTH_AND_EXPR,
3115 				  logical_type_node, cond, cond1);
3116 	  se->expr = fold_build3_loc (input_location, COND_EXPR,
3117 				      gfc_array_index_type, cond,
3118 				      minus_one, se->expr);
3119 	}
3120     }
3121   else   /* as is null; this is an old-fashioned 1-based array.  */
3122     {
3123       if (op != GFC_ISYM_LBOUND)
3124         {
3125 	  se->expr = fold_build2_loc (input_location, MAX_EXPR,
3126 				      gfc_array_index_type, size,
3127 				      gfc_index_zero_node);
3128 	}
3129       else
3130 	se->expr = gfc_index_one_node;
3131     }
3132 
3133 
3134   type = gfc_typenode_for_spec (&expr->ts);
3135   se->expr = convert (type, se->expr);
3136 }
3137 
3138 
3139 static void
conv_intrinsic_cobound(gfc_se * se,gfc_expr * expr)3140 conv_intrinsic_cobound (gfc_se * se, gfc_expr * expr)
3141 {
3142   gfc_actual_arglist *arg;
3143   gfc_actual_arglist *arg2;
3144   gfc_se argse;
3145   tree bound, resbound, resbound2, desc, cond, tmp;
3146   tree type;
3147   int corank;
3148 
3149   gcc_assert (expr->value.function.isym->id == GFC_ISYM_LCOBOUND
3150 	      || expr->value.function.isym->id == GFC_ISYM_UCOBOUND
3151 	      || expr->value.function.isym->id == GFC_ISYM_THIS_IMAGE);
3152 
3153   arg = expr->value.function.actual;
3154   arg2 = arg->next;
3155 
3156   gcc_assert (arg->expr->expr_type == EXPR_VARIABLE);
3157   corank = gfc_get_corank (arg->expr);
3158 
3159   gfc_init_se (&argse, NULL);
3160   argse.want_coarray = 1;
3161 
3162   gfc_conv_expr_descriptor (&argse, arg->expr);
3163   gfc_add_block_to_block (&se->pre, &argse.pre);
3164   gfc_add_block_to_block (&se->post, &argse.post);
3165   desc = argse.expr;
3166 
3167   if (se->ss)
3168     {
3169       /* Create an implicit second parameter from the loop variable.  */
3170       gcc_assert (!arg2->expr);
3171       gcc_assert (corank > 0);
3172       gcc_assert (se->loop->dimen == 1);
3173       gcc_assert (se->ss->info->expr == expr);
3174 
3175       bound = se->loop->loopvar[0];
3176       bound = fold_build2_loc (input_location, PLUS_EXPR, gfc_array_index_type,
3177 			       bound, gfc_rank_cst[arg->expr->rank]);
3178       gfc_advance_se_ss_chain (se);
3179     }
3180   else
3181     {
3182       /* use the passed argument.  */
3183       gcc_assert (arg2->expr);
3184       gfc_init_se (&argse, NULL);
3185       gfc_conv_expr_type (&argse, arg2->expr, gfc_array_index_type);
3186       gfc_add_block_to_block (&se->pre, &argse.pre);
3187       bound = argse.expr;
3188 
3189       if (INTEGER_CST_P (bound))
3190 	{
3191 	  if (wi::ltu_p (wi::to_wide (bound), 1)
3192 	      || wi::gtu_p (wi::to_wide (bound),
3193 			    GFC_TYPE_ARRAY_CORANK (TREE_TYPE (desc))))
3194 	    gfc_error ("%<dim%> argument of %s intrinsic at %L is not a valid "
3195 		       "dimension index", expr->value.function.isym->name,
3196 		       &expr->where);
3197 	}
3198       else if (gfc_option.rtcheck & GFC_RTCHECK_BOUNDS)
3199         {
3200 	  bound = gfc_evaluate_now (bound, &se->pre);
3201 	  cond = fold_build2_loc (input_location, LT_EXPR, logical_type_node,
3202 				  bound, build_int_cst (TREE_TYPE (bound), 1));
3203 	  tmp = gfc_rank_cst[GFC_TYPE_ARRAY_CORANK (TREE_TYPE (desc))];
3204 	  tmp = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
3205 				 bound, tmp);
3206 	  cond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
3207 				  logical_type_node, cond, tmp);
3208 	  gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
3209 				   gfc_msg_fault);
3210 	}
3211 
3212 
3213       /* Subtract 1 to get to zero based and add dimensions.  */
3214       switch (arg->expr->rank)
3215 	{
3216 	case 0:
3217 	  bound = fold_build2_loc (input_location, MINUS_EXPR,
3218 				   gfc_array_index_type, bound,
3219 				   gfc_index_one_node);
3220 	case 1:
3221 	  break;
3222 	default:
3223 	  bound = fold_build2_loc (input_location, PLUS_EXPR,
3224 				   gfc_array_index_type, bound,
3225 				   gfc_rank_cst[arg->expr->rank - 1]);
3226 	}
3227     }
3228 
3229   resbound = gfc_conv_descriptor_lbound_get (desc, bound);
3230 
3231   /* Handle UCOBOUND with special handling of the last codimension.  */
3232   if (expr->value.function.isym->id == GFC_ISYM_UCOBOUND)
3233     {
3234       /* Last codimension: For -fcoarray=single just return
3235 	 the lcobound - otherwise add
3236 	   ceiling (real (num_images ()) / real (size)) - 1
3237 	 = (num_images () + size - 1) / size - 1
3238 	 = (num_images - 1) / size(),
3239          where size is the product of the extent of all but the last
3240 	 codimension.  */
3241 
3242       if (flag_coarray != GFC_FCOARRAY_SINGLE && corank > 1)
3243 	{
3244           tree cosize;
3245 
3246 	  cosize = gfc_conv_descriptor_cosize (desc, arg->expr->rank, corank);
3247 	  tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_num_images,
3248 				     2, integer_zero_node,
3249 				     build_int_cst (integer_type_node, -1));
3250 	  tmp = fold_build2_loc (input_location, MINUS_EXPR,
3251 				 gfc_array_index_type,
3252 				 fold_convert (gfc_array_index_type, tmp),
3253 				 build_int_cst (gfc_array_index_type, 1));
3254 	  tmp = fold_build2_loc (input_location, TRUNC_DIV_EXPR,
3255 				 gfc_array_index_type, tmp,
3256 				 fold_convert (gfc_array_index_type, cosize));
3257 	  resbound = fold_build2_loc (input_location, PLUS_EXPR,
3258 				      gfc_array_index_type, resbound, tmp);
3259 	}
3260       else if (flag_coarray != GFC_FCOARRAY_SINGLE)
3261 	{
3262 	  /* ubound = lbound + num_images() - 1.  */
3263 	  tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_num_images,
3264 				     2, integer_zero_node,
3265 				     build_int_cst (integer_type_node, -1));
3266 	  tmp = fold_build2_loc (input_location, MINUS_EXPR,
3267 				 gfc_array_index_type,
3268 				 fold_convert (gfc_array_index_type, tmp),
3269 				 build_int_cst (gfc_array_index_type, 1));
3270 	  resbound = fold_build2_loc (input_location, PLUS_EXPR,
3271 				      gfc_array_index_type, resbound, tmp);
3272 	}
3273 
3274       if (corank > 1)
3275 	{
3276 	  cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
3277 				  bound,
3278 				  build_int_cst (TREE_TYPE (bound),
3279 						 arg->expr->rank + corank - 1));
3280 
3281 	  resbound2 = gfc_conv_descriptor_ubound_get (desc, bound);
3282 	  se->expr = fold_build3_loc (input_location, COND_EXPR,
3283 				      gfc_array_index_type, cond,
3284 				      resbound, resbound2);
3285 	}
3286       else
3287 	se->expr = resbound;
3288     }
3289   else
3290     se->expr = resbound;
3291 
3292   type = gfc_typenode_for_spec (&expr->ts);
3293   se->expr = convert (type, se->expr);
3294 }
3295 
3296 
3297 static void
conv_intrinsic_stride(gfc_se * se,gfc_expr * expr)3298 conv_intrinsic_stride (gfc_se * se, gfc_expr * expr)
3299 {
3300   gfc_actual_arglist *array_arg;
3301   gfc_actual_arglist *dim_arg;
3302   gfc_se argse;
3303   tree desc, tmp;
3304 
3305   array_arg = expr->value.function.actual;
3306   dim_arg = array_arg->next;
3307 
3308   gcc_assert (array_arg->expr->expr_type == EXPR_VARIABLE);
3309 
3310   gfc_init_se (&argse, NULL);
3311   gfc_conv_expr_descriptor (&argse, array_arg->expr);
3312   gfc_add_block_to_block (&se->pre, &argse.pre);
3313   gfc_add_block_to_block (&se->post, &argse.post);
3314   desc = argse.expr;
3315 
3316   gcc_assert (dim_arg->expr);
3317   gfc_init_se (&argse, NULL);
3318   gfc_conv_expr_type (&argse, dim_arg->expr, gfc_array_index_type);
3319   gfc_add_block_to_block (&se->pre, &argse.pre);
3320   tmp = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
3321 			 argse.expr, gfc_index_one_node);
3322   se->expr = gfc_conv_descriptor_stride_get (desc, tmp);
3323 }
3324 
3325 static void
gfc_conv_intrinsic_abs(gfc_se * se,gfc_expr * expr)3326 gfc_conv_intrinsic_abs (gfc_se * se, gfc_expr * expr)
3327 {
3328   tree arg, cabs;
3329 
3330   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
3331 
3332   switch (expr->value.function.actual->expr->ts.type)
3333     {
3334     case BT_INTEGER:
3335     case BT_REAL:
3336       se->expr = fold_build1_loc (input_location, ABS_EXPR, TREE_TYPE (arg),
3337 				  arg);
3338       break;
3339 
3340     case BT_COMPLEX:
3341       cabs = gfc_builtin_decl_for_float_kind (BUILT_IN_CABS, expr->ts.kind);
3342       se->expr = build_call_expr_loc (input_location, cabs, 1, arg);
3343       break;
3344 
3345     default:
3346       gcc_unreachable ();
3347     }
3348 }
3349 
3350 
3351 /* Create a complex value from one or two real components.  */
3352 
3353 static void
gfc_conv_intrinsic_cmplx(gfc_se * se,gfc_expr * expr,int both)3354 gfc_conv_intrinsic_cmplx (gfc_se * se, gfc_expr * expr, int both)
3355 {
3356   tree real;
3357   tree imag;
3358   tree type;
3359   tree *args;
3360   unsigned int num_args;
3361 
3362   num_args = gfc_intrinsic_argument_list_length (expr);
3363   args = XALLOCAVEC (tree, num_args);
3364 
3365   type = gfc_typenode_for_spec (&expr->ts);
3366   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
3367   real = convert (TREE_TYPE (type), args[0]);
3368   if (both)
3369     imag = convert (TREE_TYPE (type), args[1]);
3370   else if (TREE_CODE (TREE_TYPE (args[0])) == COMPLEX_TYPE)
3371     {
3372       imag = fold_build1_loc (input_location, IMAGPART_EXPR,
3373 			      TREE_TYPE (TREE_TYPE (args[0])), args[0]);
3374       imag = convert (TREE_TYPE (type), imag);
3375     }
3376   else
3377     imag = build_real_from_int_cst (TREE_TYPE (type), integer_zero_node);
3378 
3379   se->expr = fold_build2_loc (input_location, COMPLEX_EXPR, type, real, imag);
3380 }
3381 
3382 
3383 /* Remainder function MOD(A, P) = A - INT(A / P) * P
3384                       MODULO(A, P) = A - FLOOR (A / P) * P
3385 
3386    The obvious algorithms above are numerically instable for large
3387    arguments, hence these intrinsics are instead implemented via calls
3388    to the fmod family of functions.  It is the responsibility of the
3389    user to ensure that the second argument is non-zero.  */
3390 
3391 static void
gfc_conv_intrinsic_mod(gfc_se * se,gfc_expr * expr,int modulo)3392 gfc_conv_intrinsic_mod (gfc_se * se, gfc_expr * expr, int modulo)
3393 {
3394   tree type;
3395   tree tmp;
3396   tree test;
3397   tree test2;
3398   tree fmod;
3399   tree zero;
3400   tree args[2];
3401 
3402   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3403 
3404   switch (expr->ts.type)
3405     {
3406     case BT_INTEGER:
3407       /* Integer case is easy, we've got a builtin op.  */
3408       type = TREE_TYPE (args[0]);
3409 
3410       if (modulo)
3411        se->expr = fold_build2_loc (input_location, FLOOR_MOD_EXPR, type,
3412 				   args[0], args[1]);
3413       else
3414        se->expr = fold_build2_loc (input_location, TRUNC_MOD_EXPR, type,
3415 				   args[0], args[1]);
3416       break;
3417 
3418     case BT_REAL:
3419       fmod = NULL_TREE;
3420       /* Check if we have a builtin fmod.  */
3421       fmod = gfc_builtin_decl_for_float_kind (BUILT_IN_FMOD, expr->ts.kind);
3422 
3423       /* The builtin should always be available.  */
3424       gcc_assert (fmod != NULL_TREE);
3425 
3426       tmp = build_addr (fmod);
3427       se->expr = build_call_array_loc (input_location,
3428 				       TREE_TYPE (TREE_TYPE (fmod)),
3429                                        tmp, 2, args);
3430       if (modulo == 0)
3431 	return;
3432 
3433       type = TREE_TYPE (args[0]);
3434 
3435       args[0] = gfc_evaluate_now (args[0], &se->pre);
3436       args[1] = gfc_evaluate_now (args[1], &se->pre);
3437 
3438       /* Definition:
3439 	 modulo = arg - floor (arg/arg2) * arg2
3440 
3441 	 In order to calculate the result accurately, we use the fmod
3442 	 function as follows.
3443 
3444 	 res = fmod (arg, arg2);
3445 	 if (res)
3446 	   {
3447 	     if ((arg < 0) xor (arg2 < 0))
3448 	       res += arg2;
3449 	   }
3450 	 else
3451 	   res = copysign (0., arg2);
3452 
3453 	 => As two nested ternary exprs:
3454 
3455 	 res = res ? (((arg < 0) xor (arg2 < 0)) ? res + arg2 : res)
3456 	       : copysign (0., arg2);
3457 
3458       */
3459 
3460       zero = gfc_build_const (type, integer_zero_node);
3461       tmp = gfc_evaluate_now (se->expr, &se->pre);
3462       if (!flag_signed_zeros)
3463 	{
3464 	  test = fold_build2_loc (input_location, LT_EXPR, logical_type_node,
3465 				  args[0], zero);
3466 	  test2 = fold_build2_loc (input_location, LT_EXPR, logical_type_node,
3467 				   args[1], zero);
3468 	  test2 = fold_build2_loc (input_location, TRUTH_XOR_EXPR,
3469 				   logical_type_node, test, test2);
3470 	  test = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
3471 				  tmp, zero);
3472 	  test = fold_build2_loc (input_location, TRUTH_AND_EXPR,
3473 				  logical_type_node, test, test2);
3474 	  test = gfc_evaluate_now (test, &se->pre);
3475 	  se->expr = fold_build3_loc (input_location, COND_EXPR, type, test,
3476 				      fold_build2_loc (input_location,
3477 						       PLUS_EXPR,
3478 						       type, tmp, args[1]),
3479 				      tmp);
3480 	}
3481       else
3482 	{
3483 	  tree expr1, copysign, cscall;
3484 	  copysign = gfc_builtin_decl_for_float_kind (BUILT_IN_COPYSIGN,
3485 						      expr->ts.kind);
3486 	  test = fold_build2_loc (input_location, LT_EXPR, logical_type_node,
3487 				  args[0], zero);
3488 	  test2 = fold_build2_loc (input_location, LT_EXPR, logical_type_node,
3489 				   args[1], zero);
3490 	  test2 = fold_build2_loc (input_location, TRUTH_XOR_EXPR,
3491 				   logical_type_node, test, test2);
3492 	  expr1 = fold_build3_loc (input_location, COND_EXPR, type, test2,
3493 				   fold_build2_loc (input_location,
3494 						    PLUS_EXPR,
3495 						    type, tmp, args[1]),
3496 				   tmp);
3497 	  test = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
3498 				  tmp, zero);
3499 	  cscall = build_call_expr_loc (input_location, copysign, 2, zero,
3500 					args[1]);
3501 	  se->expr = fold_build3_loc (input_location, COND_EXPR, type, test,
3502 				      expr1, cscall);
3503 	}
3504       return;
3505 
3506     default:
3507       gcc_unreachable ();
3508     }
3509 }
3510 
3511 /* DSHIFTL(I,J,S) = (I << S) | (J >> (BITSIZE(J) - S))
3512    DSHIFTR(I,J,S) = (I << (BITSIZE(I) - S)) | (J >> S)
3513    where the right shifts are logical (i.e. 0's are shifted in).
3514    Because SHIFT_EXPR's want shifts strictly smaller than the integral
3515    type width, we have to special-case both S == 0 and S == BITSIZE(J):
3516      DSHIFTL(I,J,0) = I
3517      DSHIFTL(I,J,BITSIZE) = J
3518      DSHIFTR(I,J,0) = J
3519      DSHIFTR(I,J,BITSIZE) = I.  */
3520 
3521 static void
gfc_conv_intrinsic_dshift(gfc_se * se,gfc_expr * expr,bool dshiftl)3522 gfc_conv_intrinsic_dshift (gfc_se * se, gfc_expr * expr, bool dshiftl)
3523 {
3524   tree type, utype, stype, arg1, arg2, shift, res, left, right;
3525   tree args[3], cond, tmp;
3526   int bitsize;
3527 
3528   gfc_conv_intrinsic_function_args (se, expr, args, 3);
3529 
3530   gcc_assert (TREE_TYPE (args[0]) == TREE_TYPE (args[1]));
3531   type = TREE_TYPE (args[0]);
3532   bitsize = TYPE_PRECISION (type);
3533   utype = unsigned_type_for (type);
3534   stype = TREE_TYPE (args[2]);
3535 
3536   arg1 = gfc_evaluate_now (args[0], &se->pre);
3537   arg2 = gfc_evaluate_now (args[1], &se->pre);
3538   shift = gfc_evaluate_now (args[2], &se->pre);
3539 
3540   /* The generic case.  */
3541   tmp = fold_build2_loc (input_location, MINUS_EXPR, stype,
3542 			 build_int_cst (stype, bitsize), shift);
3543   left = fold_build2_loc (input_location, LSHIFT_EXPR, type,
3544 			  arg1, dshiftl ? shift : tmp);
3545 
3546   right = fold_build2_loc (input_location, RSHIFT_EXPR, utype,
3547 			   fold_convert (utype, arg2), dshiftl ? tmp : shift);
3548   right = fold_convert (type, right);
3549 
3550   res = fold_build2_loc (input_location, BIT_IOR_EXPR, type, left, right);
3551 
3552   /* Special cases.  */
3553   cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, shift,
3554 			  build_int_cst (stype, 0));
3555   res = fold_build3_loc (input_location, COND_EXPR, type, cond,
3556 			 dshiftl ? arg1 : arg2, res);
3557 
3558   cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, shift,
3559 			  build_int_cst (stype, bitsize));
3560   res = fold_build3_loc (input_location, COND_EXPR, type, cond,
3561 			 dshiftl ? arg2 : arg1, res);
3562 
3563   se->expr = res;
3564 }
3565 
3566 
3567 /* Positive difference DIM (x, y) = ((x - y) < 0) ? 0 : x - y.  */
3568 
3569 static void
gfc_conv_intrinsic_dim(gfc_se * se,gfc_expr * expr)3570 gfc_conv_intrinsic_dim (gfc_se * se, gfc_expr * expr)
3571 {
3572   tree val;
3573   tree tmp;
3574   tree type;
3575   tree zero;
3576   tree args[2];
3577 
3578   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3579   type = TREE_TYPE (args[0]);
3580 
3581   val = fold_build2_loc (input_location, MINUS_EXPR, type, args[0], args[1]);
3582   val = gfc_evaluate_now (val, &se->pre);
3583 
3584   zero = gfc_build_const (type, integer_zero_node);
3585   tmp = fold_build2_loc (input_location, LE_EXPR, logical_type_node, val, zero);
3586   se->expr = fold_build3_loc (input_location, COND_EXPR, type, tmp, zero, val);
3587 }
3588 
3589 
3590 /* SIGN(A, B) is absolute value of A times sign of B.
3591    The real value versions use library functions to ensure the correct
3592    handling of negative zero.  Integer case implemented as:
3593    SIGN(A, B) = { tmp = (A ^ B) >> C; (A + tmp) ^ tmp }
3594   */
3595 
3596 static void
gfc_conv_intrinsic_sign(gfc_se * se,gfc_expr * expr)3597 gfc_conv_intrinsic_sign (gfc_se * se, gfc_expr * expr)
3598 {
3599   tree tmp;
3600   tree type;
3601   tree args[2];
3602 
3603   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3604   if (expr->ts.type == BT_REAL)
3605     {
3606       tree abs;
3607 
3608       tmp = gfc_builtin_decl_for_float_kind (BUILT_IN_COPYSIGN, expr->ts.kind);
3609       abs = gfc_builtin_decl_for_float_kind (BUILT_IN_FABS, expr->ts.kind);
3610 
3611       /* We explicitly have to ignore the minus sign. We do so by using
3612 	 result = (arg1 == 0) ? abs(arg0) : copysign(arg0, arg1).  */
3613       if (!flag_sign_zero
3614 	  && MODE_HAS_SIGNED_ZEROS (TYPE_MODE (TREE_TYPE (args[1]))))
3615 	{
3616 	  tree cond, zero;
3617 	  zero = build_real_from_int_cst (TREE_TYPE (args[1]), integer_zero_node);
3618 	  cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
3619 				  args[1], zero);
3620 	  se->expr = fold_build3_loc (input_location, COND_EXPR,
3621 				  TREE_TYPE (args[0]), cond,
3622 				  build_call_expr_loc (input_location, abs, 1,
3623 						       args[0]),
3624 				  build_call_expr_loc (input_location, tmp, 2,
3625 						       args[0], args[1]));
3626 	}
3627       else
3628         se->expr = build_call_expr_loc (input_location, tmp, 2,
3629 					args[0], args[1]);
3630       return;
3631     }
3632 
3633   /* Having excluded floating point types, we know we are now dealing
3634      with signed integer types.  */
3635   type = TREE_TYPE (args[0]);
3636 
3637   /* Args[0] is used multiple times below.  */
3638   args[0] = gfc_evaluate_now (args[0], &se->pre);
3639 
3640   /* Construct (A ^ B) >> 31, which generates a bit mask of all zeros if
3641      the signs of A and B are the same, and of all ones if they differ.  */
3642   tmp = fold_build2_loc (input_location, BIT_XOR_EXPR, type, args[0], args[1]);
3643   tmp = fold_build2_loc (input_location, RSHIFT_EXPR, type, tmp,
3644 			 build_int_cst (type, TYPE_PRECISION (type) - 1));
3645   tmp = gfc_evaluate_now (tmp, &se->pre);
3646 
3647   /* Construct (A + tmp) ^ tmp, which is A if tmp is zero, and -A if tmp]
3648      is all ones (i.e. -1).  */
3649   se->expr = fold_build2_loc (input_location, BIT_XOR_EXPR, type,
3650 			      fold_build2_loc (input_location, PLUS_EXPR,
3651 					       type, args[0], tmp), tmp);
3652 }
3653 
3654 
3655 /* Test for the presence of an optional argument.  */
3656 
3657 static void
gfc_conv_intrinsic_present(gfc_se * se,gfc_expr * expr)3658 gfc_conv_intrinsic_present (gfc_se * se, gfc_expr * expr)
3659 {
3660   gfc_expr *arg;
3661 
3662   arg = expr->value.function.actual->expr;
3663   gcc_assert (arg->expr_type == EXPR_VARIABLE);
3664   se->expr = gfc_conv_expr_present (arg->symtree->n.sym);
3665   se->expr = convert (gfc_typenode_for_spec (&expr->ts), se->expr);
3666 }
3667 
3668 
3669 /* Calculate the double precision product of two single precision values.  */
3670 
3671 static void
gfc_conv_intrinsic_dprod(gfc_se * se,gfc_expr * expr)3672 gfc_conv_intrinsic_dprod (gfc_se * se, gfc_expr * expr)
3673 {
3674   tree type;
3675   tree args[2];
3676 
3677   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3678 
3679   /* Convert the args to double precision before multiplying.  */
3680   type = gfc_typenode_for_spec (&expr->ts);
3681   args[0] = convert (type, args[0]);
3682   args[1] = convert (type, args[1]);
3683   se->expr = fold_build2_loc (input_location, MULT_EXPR, type, args[0],
3684 			      args[1]);
3685 }
3686 
3687 
3688 /* Return a length one character string containing an ascii character.  */
3689 
3690 static void
gfc_conv_intrinsic_char(gfc_se * se,gfc_expr * expr)3691 gfc_conv_intrinsic_char (gfc_se * se, gfc_expr * expr)
3692 {
3693   tree arg[2];
3694   tree var;
3695   tree type;
3696   unsigned int num_args;
3697 
3698   num_args = gfc_intrinsic_argument_list_length (expr);
3699   gfc_conv_intrinsic_function_args (se, expr, arg, num_args);
3700 
3701   type = gfc_get_char_type (expr->ts.kind);
3702   var = gfc_create_var (type, "char");
3703 
3704   arg[0] = fold_build1_loc (input_location, NOP_EXPR, type, arg[0]);
3705   gfc_add_modify (&se->pre, var, arg[0]);
3706   se->expr = gfc_build_addr_expr (build_pointer_type (type), var);
3707   se->string_length = build_int_cst (gfc_charlen_type_node, 1);
3708 }
3709 
3710 
3711 static void
gfc_conv_intrinsic_ctime(gfc_se * se,gfc_expr * expr)3712 gfc_conv_intrinsic_ctime (gfc_se * se, gfc_expr * expr)
3713 {
3714   tree var;
3715   tree len;
3716   tree tmp;
3717   tree cond;
3718   tree fndecl;
3719   tree *args;
3720   unsigned int num_args;
3721 
3722   num_args = gfc_intrinsic_argument_list_length (expr) + 2;
3723   args = XALLOCAVEC (tree, num_args);
3724 
3725   var = gfc_create_var (pchar_type_node, "pstr");
3726   len = gfc_create_var (gfc_charlen_type_node, "len");
3727 
3728   gfc_conv_intrinsic_function_args (se, expr, &args[2], num_args - 2);
3729   args[0] = gfc_build_addr_expr (NULL_TREE, var);
3730   args[1] = gfc_build_addr_expr (NULL_TREE, len);
3731 
3732   fndecl = build_addr (gfor_fndecl_ctime);
3733   tmp = build_call_array_loc (input_location,
3734 			  TREE_TYPE (TREE_TYPE (gfor_fndecl_ctime)),
3735 			  fndecl, num_args, args);
3736   gfc_add_expr_to_block (&se->pre, tmp);
3737 
3738   /* Free the temporary afterwards, if necessary.  */
3739   cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
3740 			  len, build_int_cst (TREE_TYPE (len), 0));
3741   tmp = gfc_call_free (var);
3742   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
3743   gfc_add_expr_to_block (&se->post, tmp);
3744 
3745   se->expr = var;
3746   se->string_length = len;
3747 }
3748 
3749 
3750 static void
gfc_conv_intrinsic_fdate(gfc_se * se,gfc_expr * expr)3751 gfc_conv_intrinsic_fdate (gfc_se * se, gfc_expr * expr)
3752 {
3753   tree var;
3754   tree len;
3755   tree tmp;
3756   tree cond;
3757   tree fndecl;
3758   tree *args;
3759   unsigned int num_args;
3760 
3761   num_args = gfc_intrinsic_argument_list_length (expr) + 2;
3762   args = XALLOCAVEC (tree, num_args);
3763 
3764   var = gfc_create_var (pchar_type_node, "pstr");
3765   len = gfc_create_var (gfc_charlen_type_node, "len");
3766 
3767   gfc_conv_intrinsic_function_args (se, expr, &args[2], num_args - 2);
3768   args[0] = gfc_build_addr_expr (NULL_TREE, var);
3769   args[1] = gfc_build_addr_expr (NULL_TREE, len);
3770 
3771   fndecl = build_addr (gfor_fndecl_fdate);
3772   tmp = build_call_array_loc (input_location,
3773 			  TREE_TYPE (TREE_TYPE (gfor_fndecl_fdate)),
3774 			  fndecl, num_args, args);
3775   gfc_add_expr_to_block (&se->pre, tmp);
3776 
3777   /* Free the temporary afterwards, if necessary.  */
3778   cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
3779 			  len, build_int_cst (TREE_TYPE (len), 0));
3780   tmp = gfc_call_free (var);
3781   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
3782   gfc_add_expr_to_block (&se->post, tmp);
3783 
3784   se->expr = var;
3785   se->string_length = len;
3786 }
3787 
3788 
3789 /* Generate a direct call to free() for the FREE subroutine.  */
3790 
3791 static tree
conv_intrinsic_free(gfc_code * code)3792 conv_intrinsic_free (gfc_code *code)
3793 {
3794   stmtblock_t block;
3795   gfc_se argse;
3796   tree arg, call;
3797 
3798   gfc_init_se (&argse, NULL);
3799   gfc_conv_expr (&argse, code->ext.actual->expr);
3800   arg = fold_convert (ptr_type_node, argse.expr);
3801 
3802   gfc_init_block (&block);
3803   call = build_call_expr_loc (input_location,
3804 			      builtin_decl_explicit (BUILT_IN_FREE), 1, arg);
3805   gfc_add_expr_to_block (&block, call);
3806   return gfc_finish_block (&block);
3807 }
3808 
3809 
3810 /* Call the RANDOM_INIT library subroutine with a hidden argument for
3811    handling seeding on coarray images.  */
3812 
3813 static tree
conv_intrinsic_random_init(gfc_code * code)3814 conv_intrinsic_random_init (gfc_code *code)
3815 {
3816   stmtblock_t block;
3817   gfc_se se;
3818   tree arg1, arg2, tmp;
3819   /* On none coarray == lib compiles use LOGICAL(4) else regular LOGICAL.  */
3820   tree used_bool_type_node = flag_coarray == GFC_FCOARRAY_LIB
3821 			     ? logical_type_node
3822 			     : gfc_get_logical_type (4);
3823 
3824   /* Make the function call.  */
3825   gfc_init_block (&block);
3826   gfc_init_se (&se, NULL);
3827 
3828   /* Convert REPEATABLE to the desired LOGICAL entity.  */
3829   gfc_conv_expr (&se, code->ext.actual->expr);
3830   gfc_add_block_to_block (&block, &se.pre);
3831   arg1 = fold_convert (used_bool_type_node, gfc_evaluate_now (se.expr, &block));
3832   gfc_add_block_to_block (&block, &se.post);
3833 
3834   /* Convert IMAGE_DISTINCT to the desired LOGICAL entity.  */
3835   gfc_conv_expr (&se, code->ext.actual->next->expr);
3836   gfc_add_block_to_block (&block, &se.pre);
3837   arg2 = fold_convert (used_bool_type_node, gfc_evaluate_now (se.expr, &block));
3838   gfc_add_block_to_block (&block, &se.post);
3839 
3840   if (flag_coarray == GFC_FCOARRAY_LIB)
3841     {
3842       tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_random_init,
3843 				 2, arg1, arg2);
3844     }
3845   else
3846     {
3847       /* The ABI for libgfortran needs to be maintained, so a hidden
3848 	 argument must be include if code is compiled with -fcoarray=single
3849 	 or without the option.  Set to 0.  */
3850       tree arg3 = build_int_cst (gfc_get_int_type (4), 0);
3851       tmp = build_call_expr_loc (input_location, gfor_fndecl_random_init,
3852 				 3, arg1, arg2, arg3);
3853     }
3854 
3855   gfc_add_expr_to_block (&block, tmp);
3856 
3857   return gfc_finish_block (&block);
3858 }
3859 
3860 
3861 /* Call the SYSTEM_CLOCK library functions, handling the type and kind
3862    conversions.  */
3863 
3864 static tree
conv_intrinsic_system_clock(gfc_code * code)3865 conv_intrinsic_system_clock (gfc_code *code)
3866 {
3867   stmtblock_t block;
3868   gfc_se count_se, count_rate_se, count_max_se;
3869   tree arg1 = NULL_TREE, arg2 = NULL_TREE, arg3 = NULL_TREE;
3870   tree tmp;
3871   int least;
3872 
3873   gfc_expr *count = code->ext.actual->expr;
3874   gfc_expr *count_rate = code->ext.actual->next->expr;
3875   gfc_expr *count_max = code->ext.actual->next->next->expr;
3876 
3877   /* Evaluate our arguments.  */
3878   if (count)
3879     {
3880       gfc_init_se (&count_se, NULL);
3881       gfc_conv_expr (&count_se, count);
3882     }
3883 
3884   if (count_rate)
3885     {
3886       gfc_init_se (&count_rate_se, NULL);
3887       gfc_conv_expr (&count_rate_se, count_rate);
3888     }
3889 
3890   if (count_max)
3891     {
3892       gfc_init_se (&count_max_se, NULL);
3893       gfc_conv_expr (&count_max_se, count_max);
3894     }
3895 
3896   /* Find the smallest kind found of the arguments.  */
3897   least = 16;
3898   least = (count && count->ts.kind < least) ? count->ts.kind : least;
3899   least = (count_rate && count_rate->ts.kind < least) ? count_rate->ts.kind
3900 						      : least;
3901   least = (count_max && count_max->ts.kind < least) ? count_max->ts.kind
3902 						    : least;
3903 
3904   /* Prepare temporary variables.  */
3905 
3906   if (count)
3907     {
3908       if (least >= 8)
3909 	arg1 = gfc_create_var (gfc_get_int_type (8), "count");
3910       else if (least == 4)
3911 	arg1 = gfc_create_var (gfc_get_int_type (4), "count");
3912       else if (count->ts.kind == 1)
3913         arg1 = gfc_conv_mpz_to_tree (gfc_integer_kinds[0].pedantic_min_int,
3914 				     count->ts.kind);
3915       else
3916         arg1 = gfc_conv_mpz_to_tree (gfc_integer_kinds[1].pedantic_min_int,
3917 				     count->ts.kind);
3918     }
3919 
3920   if (count_rate)
3921     {
3922       if (least >= 8)
3923 	arg2 = gfc_create_var (gfc_get_int_type (8), "count_rate");
3924       else if (least == 4)
3925 	arg2 = gfc_create_var (gfc_get_int_type (4), "count_rate");
3926       else
3927         arg2 = integer_zero_node;
3928     }
3929 
3930   if (count_max)
3931     {
3932       if (least >= 8)
3933 	arg3 = gfc_create_var (gfc_get_int_type (8), "count_max");
3934       else if (least == 4)
3935 	arg3 = gfc_create_var (gfc_get_int_type (4), "count_max");
3936       else
3937         arg3 = integer_zero_node;
3938     }
3939 
3940   /* Make the function call.  */
3941   gfc_init_block (&block);
3942 
3943 if (least <= 2)
3944   {
3945     if (least == 1)
3946       {
3947 	arg1 ? gfc_build_addr_expr (NULL_TREE, arg1)
3948 	       : null_pointer_node;
3949 	arg2 ? gfc_build_addr_expr (NULL_TREE, arg2)
3950 	       : null_pointer_node;
3951 	arg3 ? gfc_build_addr_expr (NULL_TREE, arg3)
3952 	       : null_pointer_node;
3953       }
3954 
3955     if (least == 2)
3956       {
3957 	arg1 ? gfc_build_addr_expr (NULL_TREE, arg1)
3958 	       : null_pointer_node;
3959 	arg2 ? gfc_build_addr_expr (NULL_TREE, arg2)
3960 	       : null_pointer_node;
3961 	arg3 ? gfc_build_addr_expr (NULL_TREE, arg3)
3962 	       : null_pointer_node;
3963       }
3964   }
3965 else
3966   {
3967     if (least == 4)
3968       {
3969 	tmp = build_call_expr_loc (input_location,
3970 		gfor_fndecl_system_clock4, 3,
3971 		arg1 ? gfc_build_addr_expr (NULL_TREE, arg1)
3972 		       : null_pointer_node,
3973 		arg2 ? gfc_build_addr_expr (NULL_TREE, arg2)
3974 		       : null_pointer_node,
3975 		arg3 ? gfc_build_addr_expr (NULL_TREE, arg3)
3976 		       : null_pointer_node);
3977 	gfc_add_expr_to_block (&block, tmp);
3978       }
3979     /* Handle kind>=8, 10, or 16 arguments */
3980     if (least >= 8)
3981       {
3982 	tmp = build_call_expr_loc (input_location,
3983 		gfor_fndecl_system_clock8, 3,
3984 		arg1 ? gfc_build_addr_expr (NULL_TREE, arg1)
3985 		       : null_pointer_node,
3986 		arg2 ? gfc_build_addr_expr (NULL_TREE, arg2)
3987 		       : null_pointer_node,
3988 		arg3 ? gfc_build_addr_expr (NULL_TREE, arg3)
3989 		       : null_pointer_node);
3990 	gfc_add_expr_to_block (&block, tmp);
3991       }
3992   }
3993 
3994   /* And store values back if needed.  */
3995   if (arg1 && arg1 != count_se.expr)
3996     gfc_add_modify (&block, count_se.expr,
3997 		    fold_convert (TREE_TYPE (count_se.expr), arg1));
3998   if (arg2 && arg2 != count_rate_se.expr)
3999     gfc_add_modify (&block, count_rate_se.expr,
4000 		    fold_convert (TREE_TYPE (count_rate_se.expr), arg2));
4001   if (arg3 && arg3 != count_max_se.expr)
4002     gfc_add_modify (&block, count_max_se.expr,
4003 		    fold_convert (TREE_TYPE (count_max_se.expr), arg3));
4004 
4005   return gfc_finish_block (&block);
4006 }
4007 
4008 
4009 /* Return a character string containing the tty name.  */
4010 
4011 static void
gfc_conv_intrinsic_ttynam(gfc_se * se,gfc_expr * expr)4012 gfc_conv_intrinsic_ttynam (gfc_se * se, gfc_expr * expr)
4013 {
4014   tree var;
4015   tree len;
4016   tree tmp;
4017   tree cond;
4018   tree fndecl;
4019   tree *args;
4020   unsigned int num_args;
4021 
4022   num_args = gfc_intrinsic_argument_list_length (expr) + 2;
4023   args = XALLOCAVEC (tree, num_args);
4024 
4025   var = gfc_create_var (pchar_type_node, "pstr");
4026   len = gfc_create_var (gfc_charlen_type_node, "len");
4027 
4028   gfc_conv_intrinsic_function_args (se, expr, &args[2], num_args - 2);
4029   args[0] = gfc_build_addr_expr (NULL_TREE, var);
4030   args[1] = gfc_build_addr_expr (NULL_TREE, len);
4031 
4032   fndecl = build_addr (gfor_fndecl_ttynam);
4033   tmp = build_call_array_loc (input_location,
4034 			  TREE_TYPE (TREE_TYPE (gfor_fndecl_ttynam)),
4035 			  fndecl, num_args, args);
4036   gfc_add_expr_to_block (&se->pre, tmp);
4037 
4038   /* Free the temporary afterwards, if necessary.  */
4039   cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
4040 			  len, build_int_cst (TREE_TYPE (len), 0));
4041   tmp = gfc_call_free (var);
4042   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
4043   gfc_add_expr_to_block (&se->post, tmp);
4044 
4045   se->expr = var;
4046   se->string_length = len;
4047 }
4048 
4049 
4050 /* Get the minimum/maximum value of all the parameters.
4051     minmax (a1, a2, a3, ...)
4052     {
4053       mvar = a1;
4054       mvar = COMP (mvar, a2)
4055       mvar = COMP (mvar, a3)
4056       ...
4057       return mvar;
4058     }
4059     Where COMP is MIN/MAX_EXPR for integral types or when we don't
4060     care about NaNs, or IFN_FMIN/MAX when the target has support for
4061     fast NaN-honouring min/max.  When neither holds expand a sequence
4062     of explicit comparisons.  */
4063 
4064 /* TODO: Mismatching types can occur when specific names are used.
4065    These should be handled during resolution.  */
4066 static void
gfc_conv_intrinsic_minmax(gfc_se * se,gfc_expr * expr,enum tree_code op)4067 gfc_conv_intrinsic_minmax (gfc_se * se, gfc_expr * expr, enum tree_code op)
4068 {
4069   tree tmp;
4070   tree mvar;
4071   tree val;
4072   tree *args;
4073   tree type;
4074   tree argtype;
4075   gfc_actual_arglist *argexpr;
4076   unsigned int i, nargs;
4077 
4078   nargs = gfc_intrinsic_argument_list_length (expr);
4079   args = XALLOCAVEC (tree, nargs);
4080 
4081   gfc_conv_intrinsic_function_args (se, expr, args, nargs);
4082   type = gfc_typenode_for_spec (&expr->ts);
4083 
4084   /* Only evaluate the argument once.  */
4085   if (!VAR_P (args[0]) && !TREE_CONSTANT (args[0]))
4086     args[0] = gfc_evaluate_now (args[0], &se->pre);
4087 
4088   /* Determine suitable type of temporary, as a GNU extension allows
4089      different argument kinds.  */
4090   argtype = TREE_TYPE (args[0]);
4091   argexpr = expr->value.function.actual;
4092   for (i = 1, argexpr = argexpr->next; i < nargs; i++, argexpr = argexpr->next)
4093     {
4094       tree tmptype = TREE_TYPE (args[i]);
4095       if (TYPE_PRECISION (tmptype) > TYPE_PRECISION (argtype))
4096 	argtype = tmptype;
4097     }
4098   mvar = gfc_create_var (argtype, "M");
4099   gfc_add_modify (&se->pre, mvar, convert (argtype, args[0]));
4100 
4101   argexpr = expr->value.function.actual;
4102   for (i = 1, argexpr = argexpr->next; i < nargs; i++, argexpr = argexpr->next)
4103     {
4104       tree cond = NULL_TREE;
4105       val = args[i];
4106 
4107       /* Handle absent optional arguments by ignoring the comparison.  */
4108       if (argexpr->expr->expr_type == EXPR_VARIABLE
4109 	  && argexpr->expr->symtree->n.sym->attr.optional
4110 	  && TREE_CODE (val) == INDIRECT_REF)
4111 	{
4112 	  cond = fold_build2_loc (input_location,
4113 				NE_EXPR, logical_type_node,
4114 				TREE_OPERAND (val, 0),
4115 			build_int_cst (TREE_TYPE (TREE_OPERAND (val, 0)), 0));
4116 	}
4117       else if (!VAR_P (val) && !TREE_CONSTANT (val))
4118 	/* Only evaluate the argument once.  */
4119 	val = gfc_evaluate_now (val, &se->pre);
4120 
4121       tree calc;
4122       /* For floating point types, the question is what MAX(a, NaN) or
4123 	 MIN(a, NaN) should return (where "a" is a normal number).
4124 	 There are valid usecase for returning either one, but the
4125 	 Fortran standard doesn't specify which one should be chosen.
4126 	 Also, there is no consensus among other tested compilers.  In
4127 	 short, it's a mess.  So lets just do whatever is fastest.  */
4128       tree_code code = op == GT_EXPR ? MAX_EXPR : MIN_EXPR;
4129       calc = fold_build2_loc (input_location, code, argtype,
4130 			      convert (argtype, val), mvar);
4131       tmp = build2_v (MODIFY_EXPR, mvar, calc);
4132 
4133       if (cond != NULL_TREE)
4134 	tmp = build3_v (COND_EXPR, cond, tmp,
4135 			build_empty_stmt (input_location));
4136       gfc_add_expr_to_block (&se->pre, tmp);
4137     }
4138   se->expr = convert (type, mvar);
4139 }
4140 
4141 
4142 /* Generate library calls for MIN and MAX intrinsics for character
4143    variables.  */
4144 static void
gfc_conv_intrinsic_minmax_char(gfc_se * se,gfc_expr * expr,int op)4145 gfc_conv_intrinsic_minmax_char (gfc_se * se, gfc_expr * expr, int op)
4146 {
4147   tree *args;
4148   tree var, len, fndecl, tmp, cond, function;
4149   unsigned int nargs;
4150 
4151   nargs = gfc_intrinsic_argument_list_length (expr);
4152   args = XALLOCAVEC (tree, nargs + 4);
4153   gfc_conv_intrinsic_function_args (se, expr, &args[4], nargs);
4154 
4155   /* Create the result variables.  */
4156   len = gfc_create_var (gfc_charlen_type_node, "len");
4157   args[0] = gfc_build_addr_expr (NULL_TREE, len);
4158   var = gfc_create_var (gfc_get_pchar_type (expr->ts.kind), "pstr");
4159   args[1] = gfc_build_addr_expr (ppvoid_type_node, var);
4160   args[2] = build_int_cst (integer_type_node, op);
4161   args[3] = build_int_cst (integer_type_node, nargs / 2);
4162 
4163   if (expr->ts.kind == 1)
4164     function = gfor_fndecl_string_minmax;
4165   else if (expr->ts.kind == 4)
4166     function = gfor_fndecl_string_minmax_char4;
4167   else
4168     gcc_unreachable ();
4169 
4170   /* Make the function call.  */
4171   fndecl = build_addr (function);
4172   tmp = build_call_array_loc (input_location,
4173 			  TREE_TYPE (TREE_TYPE (function)), fndecl,
4174 			  nargs + 4, args);
4175   gfc_add_expr_to_block (&se->pre, tmp);
4176 
4177   /* Free the temporary afterwards, if necessary.  */
4178   cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
4179 			  len, build_int_cst (TREE_TYPE (len), 0));
4180   tmp = gfc_call_free (var);
4181   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
4182   gfc_add_expr_to_block (&se->post, tmp);
4183 
4184   se->expr = var;
4185   se->string_length = len;
4186 }
4187 
4188 
4189 /* Create a symbol node for this intrinsic.  The symbol from the frontend
4190    has the generic name.  */
4191 
4192 static gfc_symbol *
gfc_get_symbol_for_expr(gfc_expr * expr,bool ignore_optional)4193 gfc_get_symbol_for_expr (gfc_expr * expr, bool ignore_optional)
4194 {
4195   gfc_symbol *sym;
4196 
4197   /* TODO: Add symbols for intrinsic function to the global namespace.  */
4198   gcc_assert (strlen (expr->value.function.name) <= GFC_MAX_SYMBOL_LEN - 5);
4199   sym = gfc_new_symbol (expr->value.function.name, NULL);
4200 
4201   sym->ts = expr->ts;
4202   sym->attr.external = 1;
4203   sym->attr.function = 1;
4204   sym->attr.always_explicit = 1;
4205   sym->attr.proc = PROC_INTRINSIC;
4206   sym->attr.flavor = FL_PROCEDURE;
4207   sym->result = sym;
4208   if (expr->rank > 0)
4209     {
4210       sym->attr.dimension = 1;
4211       sym->as = gfc_get_array_spec ();
4212       sym->as->type = AS_ASSUMED_SHAPE;
4213       sym->as->rank = expr->rank;
4214     }
4215 
4216   gfc_copy_formal_args_intr (sym, expr->value.function.isym,
4217 			     ignore_optional ? expr->value.function.actual
4218 					     : NULL);
4219 
4220   return sym;
4221 }
4222 
4223 /* Remove empty actual arguments.  */
4224 
4225 static void
remove_empty_actual_arguments(gfc_actual_arglist ** ap)4226 remove_empty_actual_arguments (gfc_actual_arglist **ap)
4227 {
4228   while (*ap)
4229     {
4230       if ((*ap)->expr == NULL)
4231 	{
4232 	  gfc_actual_arglist *r = *ap;
4233 	  *ap = r->next;
4234 	  r->next = NULL;
4235 	  gfc_free_actual_arglist (r);
4236 	}
4237       else
4238 	ap = &((*ap)->next);
4239     }
4240 }
4241 
4242 #define MAX_SPEC_ARG 12
4243 
4244 /* Make up an fn spec that's right for intrinsic functions that we
4245    want to call.  */
4246 
4247 static char *
intrinsic_fnspec(gfc_expr * expr)4248 intrinsic_fnspec (gfc_expr *expr)
4249 {
4250   static char fnspec_buf[MAX_SPEC_ARG*2+1];
4251   char *fp;
4252   int i;
4253   int num_char_args;
4254 
4255 #define ADD_CHAR(c) do { *fp++ = c; *fp++ = ' '; } while(0)
4256 
4257   /* Set the fndecl.  */
4258   fp = fnspec_buf;
4259   /* Function return value.  FIXME: Check if the second letter could
4260      be something other than a space, for further optimization.  */
4261   ADD_CHAR ('.');
4262   if (expr->rank == 0)
4263     {
4264       if (expr->ts.type == BT_CHARACTER)
4265 	{
4266 	  ADD_CHAR ('w');  /* Address of character.  */
4267 	  ADD_CHAR ('.');  /* Length of character.  */
4268 	}
4269     }
4270   else
4271     ADD_CHAR ('w');  /* Return value is a descriptor.  */
4272 
4273   num_char_args = 0;
4274   for (gfc_actual_arglist *a = expr->value.function.actual; a; a = a->next)
4275     {
4276       if (a->expr == NULL)
4277 	continue;
4278 
4279       if (a->name && strcmp (a->name,"%VAL") == 0)
4280 	ADD_CHAR ('.');
4281       else
4282 	{
4283 	  if (a->expr->rank > 0)
4284 	    ADD_CHAR ('r');
4285 	  else
4286 	    ADD_CHAR ('R');
4287 	}
4288       num_char_args += a->expr->ts.type == BT_CHARACTER;
4289       gcc_assert (fp - fnspec_buf + num_char_args <= MAX_SPEC_ARG*2);
4290     }
4291 
4292   for (i = 0; i < num_char_args; i++)
4293     ADD_CHAR ('.');
4294 
4295   *fp = '\0';
4296   return fnspec_buf;
4297 }
4298 
4299 #undef MAX_SPEC_ARG
4300 #undef ADD_CHAR
4301 
4302 /* Generate the right symbol for the specific intrinsic function and
4303  modify the expr accordingly.  This assumes that absent optional
4304  arguments should be removed.  */
4305 
4306 gfc_symbol *
specific_intrinsic_symbol(gfc_expr * expr)4307 specific_intrinsic_symbol (gfc_expr *expr)
4308 {
4309   gfc_symbol *sym;
4310 
4311   sym = gfc_find_intrinsic_symbol (expr);
4312   if (sym == NULL)
4313     {
4314       sym = gfc_get_intrinsic_function_symbol (expr);
4315       sym->ts = expr->ts;
4316       if (sym->ts.type == BT_CHARACTER && sym->ts.u.cl)
4317 	sym->ts.u.cl = gfc_new_charlen (sym->ns, NULL);
4318 
4319       gfc_copy_formal_args_intr (sym, expr->value.function.isym,
4320 				 expr->value.function.actual, true);
4321       sym->backend_decl
4322 	= gfc_get_extern_function_decl (sym, expr->value.function.actual,
4323 					intrinsic_fnspec (expr));
4324     }
4325 
4326   remove_empty_actual_arguments (&(expr->value.function.actual));
4327 
4328   return sym;
4329 }
4330 
4331 /* Generate a call to an external intrinsic function.  FIXME: So far,
4332    this only works for functions which are called with well-defined
4333    types; CSHIFT and friends will come later.  */
4334 
4335 static void
gfc_conv_intrinsic_funcall(gfc_se * se,gfc_expr * expr)4336 gfc_conv_intrinsic_funcall (gfc_se * se, gfc_expr * expr)
4337 {
4338   gfc_symbol *sym;
4339   vec<tree, va_gc> *append_args;
4340   bool specific_symbol;
4341 
4342   gcc_assert (!se->ss || se->ss->info->expr == expr);
4343 
4344   if (se->ss)
4345     gcc_assert (expr->rank > 0);
4346   else
4347     gcc_assert (expr->rank == 0);
4348 
4349   switch (expr->value.function.isym->id)
4350     {
4351     case GFC_ISYM_ANY:
4352     case GFC_ISYM_ALL:
4353     case GFC_ISYM_FINDLOC:
4354     case GFC_ISYM_MAXLOC:
4355     case GFC_ISYM_MINLOC:
4356     case GFC_ISYM_MAXVAL:
4357     case GFC_ISYM_MINVAL:
4358     case GFC_ISYM_NORM2:
4359     case GFC_ISYM_PRODUCT:
4360     case GFC_ISYM_SUM:
4361       specific_symbol = true;
4362       break;
4363     default:
4364       specific_symbol = false;
4365     }
4366 
4367   if (specific_symbol)
4368     {
4369       /* Need to copy here because specific_intrinsic_symbol modifies
4370 	 expr to omit the absent optional arguments.  */
4371       expr = gfc_copy_expr (expr);
4372       sym = specific_intrinsic_symbol (expr);
4373     }
4374   else
4375     sym = gfc_get_symbol_for_expr (expr, se->ignore_optional);
4376 
4377   /* Calls to libgfortran_matmul need to be appended special arguments,
4378      to be able to call the BLAS ?gemm functions if required and possible.  */
4379   append_args = NULL;
4380   if (expr->value.function.isym->id == GFC_ISYM_MATMUL
4381       && !expr->external_blas
4382       && sym->ts.type != BT_LOGICAL)
4383     {
4384       tree cint = gfc_get_int_type (gfc_c_int_kind);
4385 
4386       if (flag_external_blas
4387 	  && (sym->ts.type == BT_REAL || sym->ts.type == BT_COMPLEX)
4388 	  && (sym->ts.kind == 4 || sym->ts.kind == 8))
4389 	{
4390 	  tree gemm_fndecl;
4391 
4392 	  if (sym->ts.type == BT_REAL)
4393 	    {
4394 	      if (sym->ts.kind == 4)
4395 		gemm_fndecl = gfor_fndecl_sgemm;
4396 	      else
4397 		gemm_fndecl = gfor_fndecl_dgemm;
4398 	    }
4399 	  else
4400 	    {
4401 	      if (sym->ts.kind == 4)
4402 		gemm_fndecl = gfor_fndecl_cgemm;
4403 	      else
4404 		gemm_fndecl = gfor_fndecl_zgemm;
4405 	    }
4406 
4407 	  vec_alloc (append_args, 3);
4408 	  append_args->quick_push (build_int_cst (cint, 1));
4409 	  append_args->quick_push (build_int_cst (cint,
4410 						  flag_blas_matmul_limit));
4411 	  append_args->quick_push (gfc_build_addr_expr (NULL_TREE,
4412 							gemm_fndecl));
4413 	}
4414       else
4415 	{
4416 	  vec_alloc (append_args, 3);
4417 	  append_args->quick_push (build_int_cst (cint, 0));
4418 	  append_args->quick_push (build_int_cst (cint, 0));
4419 	  append_args->quick_push (null_pointer_node);
4420 	}
4421     }
4422 
4423   gfc_conv_procedure_call (se, sym, expr->value.function.actual, expr,
4424 			  append_args);
4425 
4426   if (specific_symbol)
4427     gfc_free_expr (expr);
4428   else
4429     gfc_free_symbol (sym);
4430 }
4431 
4432 /* ANY and ALL intrinsics. ANY->op == NE_EXPR, ALL->op == EQ_EXPR.
4433    Implemented as
4434     any(a)
4435     {
4436       forall (i=...)
4437         if (a[i] != 0)
4438           return 1
4439       end forall
4440       return 0
4441     }
4442     all(a)
4443     {
4444       forall (i=...)
4445         if (a[i] == 0)
4446           return 0
4447       end forall
4448       return 1
4449     }
4450  */
4451 static void
gfc_conv_intrinsic_anyall(gfc_se * se,gfc_expr * expr,enum tree_code op)4452 gfc_conv_intrinsic_anyall (gfc_se * se, gfc_expr * expr, enum tree_code op)
4453 {
4454   tree resvar;
4455   stmtblock_t block;
4456   stmtblock_t body;
4457   tree type;
4458   tree tmp;
4459   tree found;
4460   gfc_loopinfo loop;
4461   gfc_actual_arglist *actual;
4462   gfc_ss *arrayss;
4463   gfc_se arrayse;
4464   tree exit_label;
4465 
4466   if (se->ss)
4467     {
4468       gfc_conv_intrinsic_funcall (se, expr);
4469       return;
4470     }
4471 
4472   actual = expr->value.function.actual;
4473   type = gfc_typenode_for_spec (&expr->ts);
4474   /* Initialize the result.  */
4475   resvar = gfc_create_var (type, "test");
4476   if (op == EQ_EXPR)
4477     tmp = convert (type, boolean_true_node);
4478   else
4479     tmp = convert (type, boolean_false_node);
4480   gfc_add_modify (&se->pre, resvar, tmp);
4481 
4482   /* Walk the arguments.  */
4483   arrayss = gfc_walk_expr (actual->expr);
4484   gcc_assert (arrayss != gfc_ss_terminator);
4485 
4486   /* Initialize the scalarizer.  */
4487   gfc_init_loopinfo (&loop);
4488   exit_label = gfc_build_label_decl (NULL_TREE);
4489   TREE_USED (exit_label) = 1;
4490   gfc_add_ss_to_loop (&loop, arrayss);
4491 
4492   /* Initialize the loop.  */
4493   gfc_conv_ss_startstride (&loop);
4494   gfc_conv_loop_setup (&loop, &expr->where);
4495 
4496   gfc_mark_ss_chain_used (arrayss, 1);
4497   /* Generate the loop body.  */
4498   gfc_start_scalarized_body (&loop, &body);
4499 
4500   /* If the condition matches then set the return value.  */
4501   gfc_start_block (&block);
4502   if (op == EQ_EXPR)
4503     tmp = convert (type, boolean_false_node);
4504   else
4505     tmp = convert (type, boolean_true_node);
4506   gfc_add_modify (&block, resvar, tmp);
4507 
4508   /* And break out of the loop.  */
4509   tmp = build1_v (GOTO_EXPR, exit_label);
4510   gfc_add_expr_to_block (&block, tmp);
4511 
4512   found = gfc_finish_block (&block);
4513 
4514   /* Check this element.  */
4515   gfc_init_se (&arrayse, NULL);
4516   gfc_copy_loopinfo_to_se (&arrayse, &loop);
4517   arrayse.ss = arrayss;
4518   gfc_conv_expr_val (&arrayse, actual->expr);
4519 
4520   gfc_add_block_to_block (&body, &arrayse.pre);
4521   tmp = fold_build2_loc (input_location, op, logical_type_node, arrayse.expr,
4522 			 build_int_cst (TREE_TYPE (arrayse.expr), 0));
4523   tmp = build3_v (COND_EXPR, tmp, found, build_empty_stmt (input_location));
4524   gfc_add_expr_to_block (&body, tmp);
4525   gfc_add_block_to_block (&body, &arrayse.post);
4526 
4527   gfc_trans_scalarizing_loops (&loop, &body);
4528 
4529   /* Add the exit label.  */
4530   tmp = build1_v (LABEL_EXPR, exit_label);
4531   gfc_add_expr_to_block (&loop.pre, tmp);
4532 
4533   gfc_add_block_to_block (&se->pre, &loop.pre);
4534   gfc_add_block_to_block (&se->pre, &loop.post);
4535   gfc_cleanup_loop (&loop);
4536 
4537   se->expr = resvar;
4538 }
4539 
4540 
4541 /* Generate the constant 180 / pi, which is used in the conversion
4542    of acosd(), asind(), atand(), atan2d().  */
4543 
4544 static tree
rad2deg(int kind)4545 rad2deg (int kind)
4546 {
4547   tree retval;
4548   mpfr_t pi, t0;
4549 
4550   gfc_set_model_kind (kind);
4551   mpfr_init (pi);
4552   mpfr_init (t0);
4553   mpfr_set_si (t0, 180, GFC_RND_MODE);
4554   mpfr_const_pi (pi, GFC_RND_MODE);
4555   mpfr_div (t0, t0, pi, GFC_RND_MODE);
4556   retval = gfc_conv_mpfr_to_tree (t0, kind, 0);
4557   mpfr_clear (t0);
4558   mpfr_clear (pi);
4559   return retval;
4560 }
4561 
4562 
4563 static gfc_intrinsic_map_t *
gfc_lookup_intrinsic(gfc_isym_id id)4564 gfc_lookup_intrinsic (gfc_isym_id id)
4565 {
4566   gfc_intrinsic_map_t *m = gfc_intrinsic_map;
4567   for (; m->id != GFC_ISYM_NONE || m->double_built_in != END_BUILTINS; m++)
4568     if (id == m->id)
4569       break;
4570   gcc_assert (id == m->id);
4571   return m;
4572 }
4573 
4574 
4575 /* ACOSD(x) is translated into ACOS(x) * 180 / pi.
4576    ASIND(x) is translated into ASIN(x) * 180 / pi.
4577    ATAND(x) is translated into ATAN(x) * 180 / pi.  */
4578 
4579 static void
gfc_conv_intrinsic_atrigd(gfc_se * se,gfc_expr * expr,gfc_isym_id id)4580 gfc_conv_intrinsic_atrigd (gfc_se * se, gfc_expr * expr, gfc_isym_id id)
4581 {
4582   tree arg;
4583   tree atrigd;
4584   tree type;
4585   gfc_intrinsic_map_t *m;
4586 
4587   type = gfc_typenode_for_spec (&expr->ts);
4588 
4589   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4590 
4591   switch (id)
4592     {
4593     case GFC_ISYM_ACOSD:
4594       m = gfc_lookup_intrinsic (GFC_ISYM_ACOS);
4595       break;
4596     case GFC_ISYM_ASIND:
4597       m = gfc_lookup_intrinsic (GFC_ISYM_ASIN);
4598       break;
4599     case GFC_ISYM_ATAND:
4600       m = gfc_lookup_intrinsic (GFC_ISYM_ATAN);
4601       break;
4602     default:
4603       gcc_unreachable ();
4604     }
4605   atrigd = gfc_get_intrinsic_lib_fndecl (m, expr);
4606   atrigd = build_call_expr_loc (input_location, atrigd, 1, arg);
4607 
4608   se->expr = fold_build2_loc (input_location, MULT_EXPR, type, atrigd,
4609 			      fold_convert (type, rad2deg (expr->ts.kind)));
4610 }
4611 
4612 
4613 /* COTAN(X) is translated into -TAN(X+PI/2) for REAL argument and
4614    COS(X) / SIN(X) for COMPLEX argument.  */
4615 
4616 static void
gfc_conv_intrinsic_cotan(gfc_se * se,gfc_expr * expr)4617 gfc_conv_intrinsic_cotan (gfc_se *se, gfc_expr *expr)
4618 {
4619   gfc_intrinsic_map_t *m;
4620   tree arg;
4621   tree type;
4622 
4623   type = gfc_typenode_for_spec (&expr->ts);
4624   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4625 
4626   if (expr->ts.type == BT_REAL)
4627     {
4628       tree tan;
4629       tree tmp;
4630       mpfr_t pio2;
4631 
4632       /* Create pi/2.  */
4633       gfc_set_model_kind (expr->ts.kind);
4634       mpfr_init (pio2);
4635       mpfr_const_pi (pio2, GFC_RND_MODE);
4636       mpfr_div_ui (pio2, pio2, 2, GFC_RND_MODE);
4637       tmp = gfc_conv_mpfr_to_tree (pio2, expr->ts.kind, 0);
4638       mpfr_clear (pio2);
4639 
4640       /* Find tan builtin function.  */
4641       m = gfc_lookup_intrinsic (GFC_ISYM_TAN);
4642       tan = gfc_get_intrinsic_lib_fndecl (m, expr);
4643       tmp = fold_build2_loc (input_location, PLUS_EXPR, type, arg, tmp);
4644       tan = build_call_expr_loc (input_location, tan, 1, tmp);
4645       se->expr = fold_build1_loc (input_location, NEGATE_EXPR, type, tan);
4646     }
4647   else
4648     {
4649       tree sin;
4650       tree cos;
4651 
4652       /* Find cos builtin function.  */
4653       m = gfc_lookup_intrinsic (GFC_ISYM_COS);
4654       cos = gfc_get_intrinsic_lib_fndecl (m, expr);
4655       cos = build_call_expr_loc (input_location, cos, 1, arg);
4656 
4657       /* Find sin builtin function.  */
4658       m = gfc_lookup_intrinsic (GFC_ISYM_SIN);
4659       sin = gfc_get_intrinsic_lib_fndecl (m, expr);
4660       sin = build_call_expr_loc (input_location, sin, 1, arg);
4661 
4662       /* Divide cos by sin. */
4663       se->expr = fold_build2_loc (input_location, RDIV_EXPR, type, cos, sin);
4664    }
4665 }
4666 
4667 
4668 /* COTAND(X) is translated into -TAND(X+90) for REAL argument.  */
4669 
4670 static void
gfc_conv_intrinsic_cotand(gfc_se * se,gfc_expr * expr)4671 gfc_conv_intrinsic_cotand (gfc_se *se, gfc_expr *expr)
4672 {
4673   tree arg;
4674   tree type;
4675   tree ninety_tree;
4676   mpfr_t ninety;
4677 
4678   type = gfc_typenode_for_spec (&expr->ts);
4679   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4680 
4681   gfc_set_model_kind (expr->ts.kind);
4682 
4683   /* Build the tree for x + 90.  */
4684   mpfr_init_set_ui (ninety, 90, GFC_RND_MODE);
4685   ninety_tree = gfc_conv_mpfr_to_tree (ninety, expr->ts.kind, 0);
4686   arg = fold_build2_loc (input_location, PLUS_EXPR, type, arg, ninety_tree);
4687   mpfr_clear (ninety);
4688 
4689   /* Find tand.  */
4690   gfc_intrinsic_map_t *m = gfc_lookup_intrinsic (GFC_ISYM_TAND);
4691   tree tand = gfc_get_intrinsic_lib_fndecl (m, expr);
4692   tand = build_call_expr_loc (input_location, tand, 1, arg);
4693 
4694   se->expr = fold_build1_loc (input_location, NEGATE_EXPR, type, tand);
4695 }
4696 
4697 
4698 /* ATAN2D(Y,X) is translated into ATAN2(Y,X) * 180 / PI. */
4699 
4700 static void
gfc_conv_intrinsic_atan2d(gfc_se * se,gfc_expr * expr)4701 gfc_conv_intrinsic_atan2d (gfc_se *se, gfc_expr *expr)
4702 {
4703   tree args[2];
4704   tree atan2d;
4705   tree type;
4706 
4707   gfc_conv_intrinsic_function_args (se, expr, args, 2);
4708   type = TREE_TYPE (args[0]);
4709 
4710   gfc_intrinsic_map_t *m = gfc_lookup_intrinsic (GFC_ISYM_ATAN2);
4711   atan2d = gfc_get_intrinsic_lib_fndecl (m, expr);
4712   atan2d = build_call_expr_loc (input_location, atan2d, 2, args[0], args[1]);
4713 
4714   se->expr = fold_build2_loc (input_location, MULT_EXPR, type, atan2d,
4715 			      rad2deg (expr->ts.kind));
4716 }
4717 
4718 
4719 /* COUNT(A) = Number of true elements in A.  */
4720 static void
gfc_conv_intrinsic_count(gfc_se * se,gfc_expr * expr)4721 gfc_conv_intrinsic_count (gfc_se * se, gfc_expr * expr)
4722 {
4723   tree resvar;
4724   tree type;
4725   stmtblock_t body;
4726   tree tmp;
4727   gfc_loopinfo loop;
4728   gfc_actual_arglist *actual;
4729   gfc_ss *arrayss;
4730   gfc_se arrayse;
4731 
4732   if (se->ss)
4733     {
4734       gfc_conv_intrinsic_funcall (se, expr);
4735       return;
4736     }
4737 
4738   actual = expr->value.function.actual;
4739 
4740   type = gfc_typenode_for_spec (&expr->ts);
4741   /* Initialize the result.  */
4742   resvar = gfc_create_var (type, "count");
4743   gfc_add_modify (&se->pre, resvar, build_int_cst (type, 0));
4744 
4745   /* Walk the arguments.  */
4746   arrayss = gfc_walk_expr (actual->expr);
4747   gcc_assert (arrayss != gfc_ss_terminator);
4748 
4749   /* Initialize the scalarizer.  */
4750   gfc_init_loopinfo (&loop);
4751   gfc_add_ss_to_loop (&loop, arrayss);
4752 
4753   /* Initialize the loop.  */
4754   gfc_conv_ss_startstride (&loop);
4755   gfc_conv_loop_setup (&loop, &expr->where);
4756 
4757   gfc_mark_ss_chain_used (arrayss, 1);
4758   /* Generate the loop body.  */
4759   gfc_start_scalarized_body (&loop, &body);
4760 
4761   tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (resvar),
4762 			 resvar, build_int_cst (TREE_TYPE (resvar), 1));
4763   tmp = build2_v (MODIFY_EXPR, resvar, tmp);
4764 
4765   gfc_init_se (&arrayse, NULL);
4766   gfc_copy_loopinfo_to_se (&arrayse, &loop);
4767   arrayse.ss = arrayss;
4768   gfc_conv_expr_val (&arrayse, actual->expr);
4769   tmp = build3_v (COND_EXPR, arrayse.expr, tmp,
4770 		  build_empty_stmt (input_location));
4771 
4772   gfc_add_block_to_block (&body, &arrayse.pre);
4773   gfc_add_expr_to_block (&body, tmp);
4774   gfc_add_block_to_block (&body, &arrayse.post);
4775 
4776   gfc_trans_scalarizing_loops (&loop, &body);
4777 
4778   gfc_add_block_to_block (&se->pre, &loop.pre);
4779   gfc_add_block_to_block (&se->pre, &loop.post);
4780   gfc_cleanup_loop (&loop);
4781 
4782   se->expr = resvar;
4783 }
4784 
4785 
4786 /* Update given gfc_se to have ss component pointing to the nested gfc_ss
4787    struct and return the corresponding loopinfo.  */
4788 
4789 static gfc_loopinfo *
enter_nested_loop(gfc_se * se)4790 enter_nested_loop (gfc_se *se)
4791 {
4792   se->ss = se->ss->nested_ss;
4793   gcc_assert (se->ss == se->ss->loop->ss);
4794 
4795   return se->ss->loop;
4796 }
4797 
4798 /* Build the condition for a mask, which may be optional.  */
4799 
4800 static tree
conv_mask_condition(gfc_se * maskse,gfc_expr * maskexpr,bool optional_mask)4801 conv_mask_condition (gfc_se *maskse, gfc_expr *maskexpr,
4802 			 bool optional_mask)
4803 {
4804   tree present;
4805   tree type;
4806 
4807   if (optional_mask)
4808     {
4809       type = TREE_TYPE (maskse->expr);
4810       present = gfc_conv_expr_present (maskexpr->symtree->n.sym);
4811       present = convert (type, present);
4812       present = fold_build1_loc (input_location, TRUTH_NOT_EXPR, type,
4813 				 present);
4814       return fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
4815 			      type, present, maskse->expr);
4816     }
4817   else
4818     return maskse->expr;
4819 }
4820 
4821 /* Inline implementation of the sum and product intrinsics.  */
4822 static void
gfc_conv_intrinsic_arith(gfc_se * se,gfc_expr * expr,enum tree_code op,bool norm2)4823 gfc_conv_intrinsic_arith (gfc_se * se, gfc_expr * expr, enum tree_code op,
4824 			  bool norm2)
4825 {
4826   tree resvar;
4827   tree scale = NULL_TREE;
4828   tree type;
4829   stmtblock_t body;
4830   stmtblock_t block;
4831   tree tmp;
4832   gfc_loopinfo loop, *ploop;
4833   gfc_actual_arglist *arg_array, *arg_mask;
4834   gfc_ss *arrayss = NULL;
4835   gfc_ss *maskss = NULL;
4836   gfc_se arrayse;
4837   gfc_se maskse;
4838   gfc_se *parent_se;
4839   gfc_expr *arrayexpr;
4840   gfc_expr *maskexpr;
4841   bool optional_mask;
4842 
4843   if (expr->rank > 0)
4844     {
4845       gcc_assert (gfc_inline_intrinsic_function_p (expr));
4846       parent_se = se;
4847     }
4848   else
4849     parent_se = NULL;
4850 
4851   type = gfc_typenode_for_spec (&expr->ts);
4852   /* Initialize the result.  */
4853   resvar = gfc_create_var (type, "val");
4854   if (norm2)
4855     {
4856       /* result = 0.0;
4857 	 scale = 1.0.  */
4858       scale = gfc_create_var (type, "scale");
4859       gfc_add_modify (&se->pre, scale,
4860 		      gfc_build_const (type, integer_one_node));
4861       tmp = gfc_build_const (type, integer_zero_node);
4862     }
4863   else if (op == PLUS_EXPR || op == BIT_IOR_EXPR || op == BIT_XOR_EXPR)
4864     tmp = gfc_build_const (type, integer_zero_node);
4865   else if (op == NE_EXPR)
4866     /* PARITY.  */
4867     tmp = convert (type, boolean_false_node);
4868   else if (op == BIT_AND_EXPR)
4869     tmp = gfc_build_const (type, fold_build1_loc (input_location, NEGATE_EXPR,
4870 						  type, integer_one_node));
4871   else
4872     tmp = gfc_build_const (type, integer_one_node);
4873 
4874   gfc_add_modify (&se->pre, resvar, tmp);
4875 
4876   arg_array = expr->value.function.actual;
4877 
4878   arrayexpr = arg_array->expr;
4879 
4880   if (op == NE_EXPR || norm2)
4881     {
4882       /* PARITY and NORM2.  */
4883       maskexpr = NULL;
4884       optional_mask = false;
4885     }
4886   else
4887     {
4888       arg_mask  = arg_array->next->next;
4889       gcc_assert (arg_mask != NULL);
4890       maskexpr = arg_mask->expr;
4891       optional_mask = maskexpr && maskexpr->expr_type == EXPR_VARIABLE
4892 	&& maskexpr->symtree->n.sym->attr.dummy
4893 	&& maskexpr->symtree->n.sym->attr.optional;
4894     }
4895 
4896   if (expr->rank == 0)
4897     {
4898       /* Walk the arguments.  */
4899       arrayss = gfc_walk_expr (arrayexpr);
4900       gcc_assert (arrayss != gfc_ss_terminator);
4901 
4902       if (maskexpr && maskexpr->rank > 0)
4903 	{
4904 	  maskss = gfc_walk_expr (maskexpr);
4905 	  gcc_assert (maskss != gfc_ss_terminator);
4906 	}
4907       else
4908 	maskss = NULL;
4909 
4910       /* Initialize the scalarizer.  */
4911       gfc_init_loopinfo (&loop);
4912 
4913       /* We add the mask first because the number of iterations is
4914 	 taken from the last ss, and this breaks if an absent
4915 	 optional argument is used for mask.  */
4916 
4917       if (maskexpr && maskexpr->rank > 0)
4918 	gfc_add_ss_to_loop (&loop, maskss);
4919       gfc_add_ss_to_loop (&loop, arrayss);
4920 
4921       /* Initialize the loop.  */
4922       gfc_conv_ss_startstride (&loop);
4923       gfc_conv_loop_setup (&loop, &expr->where);
4924 
4925       if (maskexpr && maskexpr->rank > 0)
4926 	gfc_mark_ss_chain_used (maskss, 1);
4927       gfc_mark_ss_chain_used (arrayss, 1);
4928 
4929       ploop = &loop;
4930     }
4931   else
4932     /* All the work has been done in the parent loops.  */
4933     ploop = enter_nested_loop (se);
4934 
4935   gcc_assert (ploop);
4936 
4937   /* Generate the loop body.  */
4938   gfc_start_scalarized_body (ploop, &body);
4939 
4940   /* If we have a mask, only add this element if the mask is set.  */
4941   if (maskexpr && maskexpr->rank > 0)
4942     {
4943       gfc_init_se (&maskse, parent_se);
4944       gfc_copy_loopinfo_to_se (&maskse, ploop);
4945       if (expr->rank == 0)
4946 	maskse.ss = maskss;
4947       gfc_conv_expr_val (&maskse, maskexpr);
4948       gfc_add_block_to_block (&body, &maskse.pre);
4949 
4950       gfc_start_block (&block);
4951     }
4952   else
4953     gfc_init_block (&block);
4954 
4955   /* Do the actual summation/product.  */
4956   gfc_init_se (&arrayse, parent_se);
4957   gfc_copy_loopinfo_to_se (&arrayse, ploop);
4958   if (expr->rank == 0)
4959     arrayse.ss = arrayss;
4960   gfc_conv_expr_val (&arrayse, arrayexpr);
4961   gfc_add_block_to_block (&block, &arrayse.pre);
4962 
4963   if (norm2)
4964     {
4965       /* if (x (i) != 0.0)
4966 	   {
4967 	     absX = abs(x(i))
4968 	     if (absX > scale)
4969 	       {
4970                  val = scale/absX;
4971 		 result = 1.0 + result * val * val;
4972 		 scale = absX;
4973 	       }
4974 	     else
4975 	       {
4976                  val = absX/scale;
4977 	         result += val * val;
4978 	       }
4979 	   }  */
4980       tree res1, res2, cond, absX, val;
4981       stmtblock_t ifblock1, ifblock2, ifblock3;
4982 
4983       gfc_init_block (&ifblock1);
4984 
4985       absX = gfc_create_var (type, "absX");
4986       gfc_add_modify (&ifblock1, absX,
4987 		      fold_build1_loc (input_location, ABS_EXPR, type,
4988 				       arrayse.expr));
4989       val = gfc_create_var (type, "val");
4990       gfc_add_expr_to_block (&ifblock1, val);
4991 
4992       gfc_init_block (&ifblock2);
4993       gfc_add_modify (&ifblock2, val,
4994 		      fold_build2_loc (input_location, RDIV_EXPR, type, scale,
4995 				       absX));
4996       res1 = fold_build2_loc (input_location, MULT_EXPR, type, val, val);
4997       res1 = fold_build2_loc (input_location, MULT_EXPR, type, resvar, res1);
4998       res1 = fold_build2_loc (input_location, PLUS_EXPR, type, res1,
4999 			      gfc_build_const (type, integer_one_node));
5000       gfc_add_modify (&ifblock2, resvar, res1);
5001       gfc_add_modify (&ifblock2, scale, absX);
5002       res1 = gfc_finish_block (&ifblock2);
5003 
5004       gfc_init_block (&ifblock3);
5005       gfc_add_modify (&ifblock3, val,
5006 		      fold_build2_loc (input_location, RDIV_EXPR, type, absX,
5007 				       scale));
5008       res2 = fold_build2_loc (input_location, MULT_EXPR, type, val, val);
5009       res2 = fold_build2_loc (input_location, PLUS_EXPR, type, resvar, res2);
5010       gfc_add_modify (&ifblock3, resvar, res2);
5011       res2 = gfc_finish_block (&ifblock3);
5012 
5013       cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
5014 			      absX, scale);
5015       tmp = build3_v (COND_EXPR, cond, res1, res2);
5016       gfc_add_expr_to_block (&ifblock1, tmp);
5017       tmp = gfc_finish_block (&ifblock1);
5018 
5019       cond = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
5020 			      arrayse.expr,
5021 			      gfc_build_const (type, integer_zero_node));
5022 
5023       tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
5024       gfc_add_expr_to_block (&block, tmp);
5025     }
5026   else
5027     {
5028       tmp = fold_build2_loc (input_location, op, type, resvar, arrayse.expr);
5029       gfc_add_modify (&block, resvar, tmp);
5030     }
5031 
5032   gfc_add_block_to_block (&block, &arrayse.post);
5033 
5034   if (maskexpr && maskexpr->rank > 0)
5035     {
5036       /* We enclose the above in if (mask) {...} .  If the mask is an
5037 	 optional argument, generate
5038 	 IF (.NOT. PRESENT(MASK) .OR. MASK(I)).  */
5039       tree ifmask;
5040       tmp = gfc_finish_block (&block);
5041       ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
5042       tmp = build3_v (COND_EXPR, ifmask, tmp,
5043 		      build_empty_stmt (input_location));
5044     }
5045   else
5046     tmp = gfc_finish_block (&block);
5047   gfc_add_expr_to_block (&body, tmp);
5048 
5049   gfc_trans_scalarizing_loops (ploop, &body);
5050 
5051   /* For a scalar mask, enclose the loop in an if statement.  */
5052   if (maskexpr && maskexpr->rank == 0)
5053     {
5054       gfc_init_block (&block);
5055       gfc_add_block_to_block (&block, &ploop->pre);
5056       gfc_add_block_to_block (&block, &ploop->post);
5057       tmp = gfc_finish_block (&block);
5058 
5059       if (expr->rank > 0)
5060 	{
5061 	  tmp = build3_v (COND_EXPR, se->ss->info->data.scalar.value, tmp,
5062 			  build_empty_stmt (input_location));
5063 	  gfc_advance_se_ss_chain (se);
5064 	}
5065       else
5066 	{
5067 	  tree ifmask;
5068 
5069 	  gcc_assert (expr->rank == 0);
5070 	  gfc_init_se (&maskse, NULL);
5071 	  gfc_conv_expr_val (&maskse, maskexpr);
5072 	  ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
5073 	  tmp = build3_v (COND_EXPR, ifmask, tmp,
5074 			  build_empty_stmt (input_location));
5075 	}
5076 
5077       gfc_add_expr_to_block (&block, tmp);
5078       gfc_add_block_to_block (&se->pre, &block);
5079       gcc_assert (se->post.head == NULL);
5080     }
5081   else
5082     {
5083       gfc_add_block_to_block (&se->pre, &ploop->pre);
5084       gfc_add_block_to_block (&se->pre, &ploop->post);
5085     }
5086 
5087   if (expr->rank == 0)
5088     gfc_cleanup_loop (ploop);
5089 
5090   if (norm2)
5091     {
5092       /* result = scale * sqrt(result).  */
5093       tree sqrt;
5094       sqrt = gfc_builtin_decl_for_float_kind (BUILT_IN_SQRT, expr->ts.kind);
5095       resvar = build_call_expr_loc (input_location,
5096 				    sqrt, 1, resvar);
5097       resvar = fold_build2_loc (input_location, MULT_EXPR, type, scale, resvar);
5098     }
5099 
5100   se->expr = resvar;
5101 }
5102 
5103 
5104 /* Inline implementation of the dot_product intrinsic. This function
5105    is based on gfc_conv_intrinsic_arith (the previous function).  */
5106 static void
gfc_conv_intrinsic_dot_product(gfc_se * se,gfc_expr * expr)5107 gfc_conv_intrinsic_dot_product (gfc_se * se, gfc_expr * expr)
5108 {
5109   tree resvar;
5110   tree type;
5111   stmtblock_t body;
5112   stmtblock_t block;
5113   tree tmp;
5114   gfc_loopinfo loop;
5115   gfc_actual_arglist *actual;
5116   gfc_ss *arrayss1, *arrayss2;
5117   gfc_se arrayse1, arrayse2;
5118   gfc_expr *arrayexpr1, *arrayexpr2;
5119 
5120   type = gfc_typenode_for_spec (&expr->ts);
5121 
5122   /* Initialize the result.  */
5123   resvar = gfc_create_var (type, "val");
5124   if (expr->ts.type == BT_LOGICAL)
5125     tmp = build_int_cst (type, 0);
5126   else
5127     tmp = gfc_build_const (type, integer_zero_node);
5128 
5129   gfc_add_modify (&se->pre, resvar, tmp);
5130 
5131   /* Walk argument #1.  */
5132   actual = expr->value.function.actual;
5133   arrayexpr1 = actual->expr;
5134   arrayss1 = gfc_walk_expr (arrayexpr1);
5135   gcc_assert (arrayss1 != gfc_ss_terminator);
5136 
5137   /* Walk argument #2.  */
5138   actual = actual->next;
5139   arrayexpr2 = actual->expr;
5140   arrayss2 = gfc_walk_expr (arrayexpr2);
5141   gcc_assert (arrayss2 != gfc_ss_terminator);
5142 
5143   /* Initialize the scalarizer.  */
5144   gfc_init_loopinfo (&loop);
5145   gfc_add_ss_to_loop (&loop, arrayss1);
5146   gfc_add_ss_to_loop (&loop, arrayss2);
5147 
5148   /* Initialize the loop.  */
5149   gfc_conv_ss_startstride (&loop);
5150   gfc_conv_loop_setup (&loop, &expr->where);
5151 
5152   gfc_mark_ss_chain_used (arrayss1, 1);
5153   gfc_mark_ss_chain_used (arrayss2, 1);
5154 
5155   /* Generate the loop body.  */
5156   gfc_start_scalarized_body (&loop, &body);
5157   gfc_init_block (&block);
5158 
5159   /* Make the tree expression for [conjg(]array1[)].  */
5160   gfc_init_se (&arrayse1, NULL);
5161   gfc_copy_loopinfo_to_se (&arrayse1, &loop);
5162   arrayse1.ss = arrayss1;
5163   gfc_conv_expr_val (&arrayse1, arrayexpr1);
5164   if (expr->ts.type == BT_COMPLEX)
5165     arrayse1.expr = fold_build1_loc (input_location, CONJ_EXPR, type,
5166 				     arrayse1.expr);
5167   gfc_add_block_to_block (&block, &arrayse1.pre);
5168 
5169   /* Make the tree expression for array2.  */
5170   gfc_init_se (&arrayse2, NULL);
5171   gfc_copy_loopinfo_to_se (&arrayse2, &loop);
5172   arrayse2.ss = arrayss2;
5173   gfc_conv_expr_val (&arrayse2, arrayexpr2);
5174   gfc_add_block_to_block (&block, &arrayse2.pre);
5175 
5176   /* Do the actual product and sum.  */
5177   if (expr->ts.type == BT_LOGICAL)
5178     {
5179       tmp = fold_build2_loc (input_location, TRUTH_AND_EXPR, type,
5180 			     arrayse1.expr, arrayse2.expr);
5181       tmp = fold_build2_loc (input_location, TRUTH_OR_EXPR, type, resvar, tmp);
5182     }
5183   else
5184     {
5185       tmp = fold_build2_loc (input_location, MULT_EXPR, type, arrayse1.expr,
5186 			     arrayse2.expr);
5187       tmp = fold_build2_loc (input_location, PLUS_EXPR, type, resvar, tmp);
5188     }
5189   gfc_add_modify (&block, resvar, tmp);
5190 
5191   /* Finish up the loop block and the loop.  */
5192   tmp = gfc_finish_block (&block);
5193   gfc_add_expr_to_block (&body, tmp);
5194 
5195   gfc_trans_scalarizing_loops (&loop, &body);
5196   gfc_add_block_to_block (&se->pre, &loop.pre);
5197   gfc_add_block_to_block (&se->pre, &loop.post);
5198   gfc_cleanup_loop (&loop);
5199 
5200   se->expr = resvar;
5201 }
5202 
5203 
5204 /* Remove unneeded kind= argument from actual argument list when the
5205    result conversion is dealt with in a different place.  */
5206 
5207 static void
strip_kind_from_actual(gfc_actual_arglist * actual)5208 strip_kind_from_actual (gfc_actual_arglist * actual)
5209 {
5210   for (gfc_actual_arglist *a = actual; a; a = a->next)
5211     {
5212       if (a && a->name && strcmp (a->name, "kind") == 0)
5213 	{
5214 	  gfc_free_expr (a->expr);
5215 	  a->expr = NULL;
5216 	}
5217     }
5218 }
5219 
5220 /* Emit code for minloc or maxloc intrinsic.  There are many different cases
5221    we need to handle.  For performance reasons we sometimes create two
5222    loops instead of one, where the second one is much simpler.
5223    Examples for minloc intrinsic:
5224    1) Result is an array, a call is generated
5225    2) Array mask is used and NaNs need to be supported:
5226       limit = Infinity;
5227       pos = 0;
5228       S = from;
5229       while (S <= to) {
5230 	if (mask[S]) {
5231 	  if (pos == 0) pos = S + (1 - from);
5232 	  if (a[S] <= limit) { limit = a[S]; pos = S + (1 - from); goto lab1; }
5233 	}
5234 	S++;
5235       }
5236       goto lab2;
5237       lab1:;
5238       while (S <= to) {
5239 	if (mask[S]) if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
5240 	S++;
5241       }
5242       lab2:;
5243    3) NaNs need to be supported, but it is known at compile time or cheaply
5244       at runtime whether array is nonempty or not:
5245       limit = Infinity;
5246       pos = 0;
5247       S = from;
5248       while (S <= to) {
5249 	if (a[S] <= limit) { limit = a[S]; pos = S + (1 - from); goto lab1; }
5250 	S++;
5251       }
5252       if (from <= to) pos = 1;
5253       goto lab2;
5254       lab1:;
5255       while (S <= to) {
5256 	if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
5257 	S++;
5258       }
5259       lab2:;
5260    4) NaNs aren't supported, array mask is used:
5261       limit = infinities_supported ? Infinity : huge (limit);
5262       pos = 0;
5263       S = from;
5264       while (S <= to) {
5265 	if (mask[S]) { limit = a[S]; pos = S + (1 - from); goto lab1; }
5266 	S++;
5267       }
5268       goto lab2;
5269       lab1:;
5270       while (S <= to) {
5271 	if (mask[S]) if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
5272 	S++;
5273       }
5274       lab2:;
5275    5) Same without array mask:
5276       limit = infinities_supported ? Infinity : huge (limit);
5277       pos = (from <= to) ? 1 : 0;
5278       S = from;
5279       while (S <= to) {
5280 	if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
5281 	S++;
5282       }
5283    For 3) and 5), if mask is scalar, this all goes into a conditional,
5284    setting pos = 0; in the else branch.
5285 
5286    Since we now also support the BACK argument, instead of using
5287    if (a[S] < limit), we now use
5288 
5289    if (back)
5290      cond = a[S] <= limit;
5291    else
5292      cond = a[S] < limit;
5293    if (cond) {
5294      ....
5295 
5296      The optimizer is smart enough to move the condition out of the loop.
5297      The are now marked as unlikely to for further speedup.  */
5298 
5299 static void
gfc_conv_intrinsic_minmaxloc(gfc_se * se,gfc_expr * expr,enum tree_code op)5300 gfc_conv_intrinsic_minmaxloc (gfc_se * se, gfc_expr * expr, enum tree_code op)
5301 {
5302   stmtblock_t body;
5303   stmtblock_t block;
5304   stmtblock_t ifblock;
5305   stmtblock_t elseblock;
5306   tree limit;
5307   tree type;
5308   tree tmp;
5309   tree cond;
5310   tree elsetmp;
5311   tree ifbody;
5312   tree offset;
5313   tree nonempty;
5314   tree lab1, lab2;
5315   tree b_if, b_else;
5316   gfc_loopinfo loop;
5317   gfc_actual_arglist *actual;
5318   gfc_ss *arrayss;
5319   gfc_ss *maskss;
5320   gfc_se arrayse;
5321   gfc_se maskse;
5322   gfc_expr *arrayexpr;
5323   gfc_expr *maskexpr;
5324   gfc_expr *backexpr;
5325   gfc_se backse;
5326   tree pos;
5327   int n;
5328   bool optional_mask;
5329 
5330   actual = expr->value.function.actual;
5331 
5332   /* The last argument, BACK, is passed by value. Ensure that
5333      by setting its name to %VAL. */
5334   for (gfc_actual_arglist *a = actual; a; a = a->next)
5335     {
5336       if (a->next == NULL)
5337 	a->name = "%VAL";
5338     }
5339 
5340   if (se->ss)
5341     {
5342       gfc_conv_intrinsic_funcall (se, expr);
5343       return;
5344     }
5345 
5346   arrayexpr = actual->expr;
5347 
5348   /* Special case for character maxloc.  Remove unneeded actual
5349      arguments, then call a library function.  */
5350 
5351   if (arrayexpr->ts.type == BT_CHARACTER)
5352     {
5353       gfc_actual_arglist *a;
5354       a = actual;
5355       strip_kind_from_actual (a);
5356       while (a)
5357 	{
5358 	  if (a->name && strcmp (a->name, "dim") == 0)
5359 	    {
5360 	      gfc_free_expr (a->expr);
5361 	      a->expr = NULL;
5362 	    }
5363 	  a = a->next;
5364 	}
5365       gfc_conv_intrinsic_funcall (se, expr);
5366       return;
5367     }
5368 
5369   /* Initialize the result.  */
5370   pos = gfc_create_var (gfc_array_index_type, "pos");
5371   offset = gfc_create_var (gfc_array_index_type, "offset");
5372   type = gfc_typenode_for_spec (&expr->ts);
5373 
5374   /* Walk the arguments.  */
5375   arrayss = gfc_walk_expr (arrayexpr);
5376   gcc_assert (arrayss != gfc_ss_terminator);
5377 
5378   actual = actual->next->next;
5379   gcc_assert (actual);
5380   maskexpr = actual->expr;
5381   optional_mask = maskexpr && maskexpr->expr_type == EXPR_VARIABLE
5382     && maskexpr->symtree->n.sym->attr.dummy
5383     && maskexpr->symtree->n.sym->attr.optional;
5384   backexpr = actual->next->next->expr;
5385   nonempty = NULL;
5386   if (maskexpr && maskexpr->rank != 0)
5387     {
5388       maskss = gfc_walk_expr (maskexpr);
5389       gcc_assert (maskss != gfc_ss_terminator);
5390     }
5391   else
5392     {
5393       mpz_t asize;
5394       if (gfc_array_size (arrayexpr, &asize))
5395 	{
5396 	  nonempty = gfc_conv_mpz_to_tree (asize, gfc_index_integer_kind);
5397 	  mpz_clear (asize);
5398 	  nonempty = fold_build2_loc (input_location, GT_EXPR,
5399 				      logical_type_node, nonempty,
5400 				      gfc_index_zero_node);
5401 	}
5402       maskss = NULL;
5403     }
5404 
5405   limit = gfc_create_var (gfc_typenode_for_spec (&arrayexpr->ts), "limit");
5406   switch (arrayexpr->ts.type)
5407     {
5408     case BT_REAL:
5409       tmp = gfc_build_inf_or_huge (TREE_TYPE (limit), arrayexpr->ts.kind);
5410       break;
5411 
5412     case BT_INTEGER:
5413       n = gfc_validate_kind (arrayexpr->ts.type, arrayexpr->ts.kind, false);
5414       tmp = gfc_conv_mpz_to_tree (gfc_integer_kinds[n].huge,
5415 				  arrayexpr->ts.kind);
5416       break;
5417 
5418     default:
5419       gcc_unreachable ();
5420     }
5421 
5422   /* We start with the most negative possible value for MAXLOC, and the most
5423      positive possible value for MINLOC. The most negative possible value is
5424      -HUGE for BT_REAL and (-HUGE - 1) for BT_INTEGER; the most positive
5425      possible value is HUGE in both cases.  */
5426   if (op == GT_EXPR)
5427     tmp = fold_build1_loc (input_location, NEGATE_EXPR, TREE_TYPE (tmp), tmp);
5428   if (op == GT_EXPR && arrayexpr->ts.type == BT_INTEGER)
5429     tmp = fold_build2_loc (input_location, MINUS_EXPR, TREE_TYPE (tmp), tmp,
5430 			   build_int_cst (TREE_TYPE (tmp), 1));
5431 
5432   gfc_add_modify (&se->pre, limit, tmp);
5433 
5434   /* Initialize the scalarizer.  */
5435   gfc_init_loopinfo (&loop);
5436 
5437   /* We add the mask first because the number of iterations is taken
5438      from the last ss, and this breaks if an absent optional argument
5439      is used for mask.  */
5440 
5441   if (maskss)
5442     gfc_add_ss_to_loop (&loop, maskss);
5443 
5444   gfc_add_ss_to_loop (&loop, arrayss);
5445 
5446   /* Initialize the loop.  */
5447   gfc_conv_ss_startstride (&loop);
5448 
5449   /* The code generated can have more than one loop in sequence (see the
5450      comment at the function header).  This doesn't work well with the
5451      scalarizer, which changes arrays' offset when the scalarization loops
5452      are generated (see gfc_trans_preloop_setup).  Fortunately, {min,max}loc
5453      are  currently inlined in the scalar case only (for which loop is of rank
5454      one).  As there is no dependency to care about in that case, there is no
5455      temporary, so that we can use the scalarizer temporary code to handle
5456      multiple loops.  Thus, we set temp_dim here, we call gfc_mark_ss_chain_used
5457      with flag=3 later, and we use gfc_trans_scalarized_loop_boundary even later
5458      to restore offset.
5459      TODO: this prevents inlining of rank > 0 minmaxloc calls, so this
5460      should eventually go away.  We could either create two loops properly,
5461      or find another way to save/restore the array offsets between the two
5462      loops (without conflicting with temporary management), or use a single
5463      loop minmaxloc implementation.  See PR 31067.  */
5464   loop.temp_dim = loop.dimen;
5465   gfc_conv_loop_setup (&loop, &expr->where);
5466 
5467   gcc_assert (loop.dimen == 1);
5468   if (nonempty == NULL && maskss == NULL && loop.from[0] && loop.to[0])
5469     nonempty = fold_build2_loc (input_location, LE_EXPR, logical_type_node,
5470 				loop.from[0], loop.to[0]);
5471 
5472   lab1 = NULL;
5473   lab2 = NULL;
5474   /* Initialize the position to zero, following Fortran 2003.  We are free
5475      to do this because Fortran 95 allows the result of an entirely false
5476      mask to be processor dependent.  If we know at compile time the array
5477      is non-empty and no MASK is used, we can initialize to 1 to simplify
5478      the inner loop.  */
5479   if (nonempty != NULL && !HONOR_NANS (DECL_MODE (limit)))
5480     gfc_add_modify (&loop.pre, pos,
5481 		    fold_build3_loc (input_location, COND_EXPR,
5482 				     gfc_array_index_type,
5483 				     nonempty, gfc_index_one_node,
5484 				     gfc_index_zero_node));
5485   else
5486     {
5487       gfc_add_modify (&loop.pre, pos, gfc_index_zero_node);
5488       lab1 = gfc_build_label_decl (NULL_TREE);
5489       TREE_USED (lab1) = 1;
5490       lab2 = gfc_build_label_decl (NULL_TREE);
5491       TREE_USED (lab2) = 1;
5492     }
5493 
5494   /* An offset must be added to the loop
5495      counter to obtain the required position.  */
5496   gcc_assert (loop.from[0]);
5497 
5498   tmp = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
5499 			 gfc_index_one_node, loop.from[0]);
5500   gfc_add_modify (&loop.pre, offset, tmp);
5501 
5502   gfc_mark_ss_chain_used (arrayss, lab1 ? 3 : 1);
5503   if (maskss)
5504     gfc_mark_ss_chain_used (maskss, lab1 ? 3 : 1);
5505   /* Generate the loop body.  */
5506   gfc_start_scalarized_body (&loop, &body);
5507 
5508   /* If we have a mask, only check this element if the mask is set.  */
5509   if (maskss)
5510     {
5511       gfc_init_se (&maskse, NULL);
5512       gfc_copy_loopinfo_to_se (&maskse, &loop);
5513       maskse.ss = maskss;
5514       gfc_conv_expr_val (&maskse, maskexpr);
5515       gfc_add_block_to_block (&body, &maskse.pre);
5516 
5517       gfc_start_block (&block);
5518     }
5519   else
5520     gfc_init_block (&block);
5521 
5522   /* Compare with the current limit.  */
5523   gfc_init_se (&arrayse, NULL);
5524   gfc_copy_loopinfo_to_se (&arrayse, &loop);
5525   arrayse.ss = arrayss;
5526   gfc_conv_expr_val (&arrayse, arrayexpr);
5527   gfc_add_block_to_block (&block, &arrayse.pre);
5528 
5529   gfc_init_se (&backse, NULL);
5530   gfc_conv_expr_val (&backse, backexpr);
5531   gfc_add_block_to_block (&block, &backse.pre);
5532 
5533   /* We do the following if this is a more extreme value.  */
5534   gfc_start_block (&ifblock);
5535 
5536   /* Assign the value to the limit...  */
5537   gfc_add_modify (&ifblock, limit, arrayse.expr);
5538 
5539   if (nonempty == NULL && HONOR_NANS (DECL_MODE (limit)))
5540     {
5541       stmtblock_t ifblock2;
5542       tree ifbody2;
5543 
5544       gfc_start_block (&ifblock2);
5545       tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (pos),
5546 			     loop.loopvar[0], offset);
5547       gfc_add_modify (&ifblock2, pos, tmp);
5548       ifbody2 = gfc_finish_block (&ifblock2);
5549       cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, pos,
5550 			      gfc_index_zero_node);
5551       tmp = build3_v (COND_EXPR, cond, ifbody2,
5552 		      build_empty_stmt (input_location));
5553       gfc_add_expr_to_block (&block, tmp);
5554     }
5555 
5556   tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (pos),
5557 			 loop.loopvar[0], offset);
5558   gfc_add_modify (&ifblock, pos, tmp);
5559 
5560   if (lab1)
5561     gfc_add_expr_to_block (&ifblock, build1_v (GOTO_EXPR, lab1));
5562 
5563   ifbody = gfc_finish_block (&ifblock);
5564 
5565   if (!lab1 || HONOR_NANS (DECL_MODE (limit)))
5566     {
5567       if (lab1)
5568 	cond = fold_build2_loc (input_location,
5569 				op == GT_EXPR ? GE_EXPR : LE_EXPR,
5570 				logical_type_node, arrayse.expr, limit);
5571       else
5572 	{
5573 	  tree ifbody2, elsebody2;
5574 
5575 	  /* We switch to > or >= depending on the value of the BACK argument. */
5576 	  cond = gfc_create_var (logical_type_node, "cond");
5577 
5578 	  gfc_start_block (&ifblock);
5579 	  b_if = fold_build2_loc (input_location, op == GT_EXPR ? GE_EXPR : LE_EXPR,
5580 				  logical_type_node, arrayse.expr, limit);
5581 
5582 	  gfc_add_modify (&ifblock, cond, b_if);
5583 	  ifbody2 = gfc_finish_block (&ifblock);
5584 
5585 	  gfc_start_block (&elseblock);
5586 	  b_else = fold_build2_loc (input_location, op, logical_type_node,
5587 				    arrayse.expr, limit);
5588 
5589 	  gfc_add_modify (&elseblock, cond, b_else);
5590 	  elsebody2 = gfc_finish_block (&elseblock);
5591 
5592 	  tmp = fold_build3_loc (input_location, COND_EXPR, logical_type_node,
5593 				 backse.expr, ifbody2, elsebody2);
5594 
5595 	  gfc_add_expr_to_block (&block, tmp);
5596 	}
5597 
5598       cond = gfc_unlikely (cond, PRED_BUILTIN_EXPECT);
5599       ifbody = build3_v (COND_EXPR, cond, ifbody,
5600 			 build_empty_stmt (input_location));
5601     }
5602   gfc_add_expr_to_block (&block, ifbody);
5603 
5604   if (maskss)
5605     {
5606       /* We enclose the above in if (mask) {...}.  If the mask is an
5607 	 optional argument, generate IF (.NOT. PRESENT(MASK)
5608 	 .OR. MASK(I)). */
5609 
5610       tree ifmask;
5611       ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
5612       tmp = gfc_finish_block (&block);
5613       tmp = build3_v (COND_EXPR, ifmask, tmp,
5614 		      build_empty_stmt (input_location));
5615     }
5616   else
5617     tmp = gfc_finish_block (&block);
5618   gfc_add_expr_to_block (&body, tmp);
5619 
5620   if (lab1)
5621     {
5622       gfc_trans_scalarized_loop_boundary (&loop, &body);
5623 
5624       if (HONOR_NANS (DECL_MODE (limit)))
5625 	{
5626 	  if (nonempty != NULL)
5627 	    {
5628 	      ifbody = build2_v (MODIFY_EXPR, pos, gfc_index_one_node);
5629 	      tmp = build3_v (COND_EXPR, nonempty, ifbody,
5630 			      build_empty_stmt (input_location));
5631 	      gfc_add_expr_to_block (&loop.code[0], tmp);
5632 	    }
5633 	}
5634 
5635       gfc_add_expr_to_block (&loop.code[0], build1_v (GOTO_EXPR, lab2));
5636       gfc_add_expr_to_block (&loop.code[0], build1_v (LABEL_EXPR, lab1));
5637 
5638       /* If we have a mask, only check this element if the mask is set.  */
5639       if (maskss)
5640 	{
5641 	  gfc_init_se (&maskse, NULL);
5642 	  gfc_copy_loopinfo_to_se (&maskse, &loop);
5643 	  maskse.ss = maskss;
5644 	  gfc_conv_expr_val (&maskse, maskexpr);
5645 	  gfc_add_block_to_block (&body, &maskse.pre);
5646 
5647 	  gfc_start_block (&block);
5648 	}
5649       else
5650 	gfc_init_block (&block);
5651 
5652       /* Compare with the current limit.  */
5653       gfc_init_se (&arrayse, NULL);
5654       gfc_copy_loopinfo_to_se (&arrayse, &loop);
5655       arrayse.ss = arrayss;
5656       gfc_conv_expr_val (&arrayse, arrayexpr);
5657       gfc_add_block_to_block (&block, &arrayse.pre);
5658 
5659       /* We do the following if this is a more extreme value.  */
5660       gfc_start_block (&ifblock);
5661 
5662       /* Assign the value to the limit...  */
5663       gfc_add_modify (&ifblock, limit, arrayse.expr);
5664 
5665       tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (pos),
5666 			     loop.loopvar[0], offset);
5667       gfc_add_modify (&ifblock, pos, tmp);
5668 
5669       ifbody = gfc_finish_block (&ifblock);
5670 
5671       /* We switch to > or >= depending on the value of the BACK argument. */
5672       {
5673 	tree ifbody2, elsebody2;
5674 
5675 	cond = gfc_create_var (logical_type_node, "cond");
5676 
5677 	gfc_start_block (&ifblock);
5678 	b_if = fold_build2_loc (input_location, op == GT_EXPR ? GE_EXPR : LE_EXPR,
5679 				logical_type_node, arrayse.expr, limit);
5680 
5681 	gfc_add_modify (&ifblock, cond, b_if);
5682 	ifbody2 = gfc_finish_block (&ifblock);
5683 
5684 	gfc_start_block (&elseblock);
5685 	b_else = fold_build2_loc (input_location, op, logical_type_node,
5686 				  arrayse.expr, limit);
5687 
5688 	gfc_add_modify (&elseblock, cond, b_else);
5689 	elsebody2 = gfc_finish_block (&elseblock);
5690 
5691 	tmp = fold_build3_loc (input_location, COND_EXPR, logical_type_node,
5692 			       backse.expr, ifbody2, elsebody2);
5693       }
5694 
5695       gfc_add_expr_to_block (&block, tmp);
5696       cond = gfc_unlikely (cond, PRED_BUILTIN_EXPECT);
5697       tmp = build3_v (COND_EXPR, cond, ifbody,
5698 		      build_empty_stmt (input_location));
5699 
5700       gfc_add_expr_to_block (&block, tmp);
5701 
5702       if (maskss)
5703 	{
5704 	  /* We enclose the above in if (mask) {...}.  If the mask is
5705 	 an optional argument, generate IF (.NOT. PRESENT(MASK)
5706 	 .OR. MASK(I)).*/
5707 
5708 	  tree ifmask;
5709 	  ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
5710 	  tmp = gfc_finish_block (&block);
5711 	  tmp = build3_v (COND_EXPR, ifmask, tmp,
5712 			  build_empty_stmt (input_location));
5713 	}
5714       else
5715 	tmp = gfc_finish_block (&block);
5716       gfc_add_expr_to_block (&body, tmp);
5717       /* Avoid initializing loopvar[0] again, it should be left where
5718 	 it finished by the first loop.  */
5719       loop.from[0] = loop.loopvar[0];
5720     }
5721 
5722   gfc_trans_scalarizing_loops (&loop, &body);
5723 
5724   if (lab2)
5725     gfc_add_expr_to_block (&loop.pre, build1_v (LABEL_EXPR, lab2));
5726 
5727   /* For a scalar mask, enclose the loop in an if statement.  */
5728   if (maskexpr && maskss == NULL)
5729     {
5730       tree ifmask;
5731 
5732       gfc_init_se (&maskse, NULL);
5733       gfc_conv_expr_val (&maskse, maskexpr);
5734       gfc_init_block (&block);
5735       gfc_add_block_to_block (&block, &loop.pre);
5736       gfc_add_block_to_block (&block, &loop.post);
5737       tmp = gfc_finish_block (&block);
5738 
5739       /* For the else part of the scalar mask, just initialize
5740 	 the pos variable the same way as above.  */
5741 
5742       gfc_init_block (&elseblock);
5743       gfc_add_modify (&elseblock, pos, gfc_index_zero_node);
5744       elsetmp = gfc_finish_block (&elseblock);
5745       ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
5746       tmp = build3_v (COND_EXPR, ifmask, tmp, elsetmp);
5747       gfc_add_expr_to_block (&block, tmp);
5748       gfc_add_block_to_block (&se->pre, &block);
5749     }
5750   else
5751     {
5752       gfc_add_block_to_block (&se->pre, &loop.pre);
5753       gfc_add_block_to_block (&se->pre, &loop.post);
5754     }
5755   gfc_cleanup_loop (&loop);
5756 
5757   se->expr = convert (type, pos);
5758 }
5759 
5760 /* Emit code for findloc.  */
5761 
5762 static void
gfc_conv_intrinsic_findloc(gfc_se * se,gfc_expr * expr)5763 gfc_conv_intrinsic_findloc (gfc_se *se, gfc_expr *expr)
5764 {
5765   gfc_actual_arglist *array_arg, *value_arg, *dim_arg, *mask_arg,
5766     *kind_arg, *back_arg;
5767   gfc_expr *value_expr;
5768   int ikind;
5769   tree resvar;
5770   stmtblock_t block;
5771   stmtblock_t body;
5772   stmtblock_t loopblock;
5773   tree type;
5774   tree tmp;
5775   tree found;
5776   tree forward_branch = NULL_TREE;
5777   tree back_branch;
5778   gfc_loopinfo loop;
5779   gfc_ss *arrayss;
5780   gfc_ss *maskss;
5781   gfc_se arrayse;
5782   gfc_se valuese;
5783   gfc_se maskse;
5784   gfc_se backse;
5785   tree exit_label;
5786   gfc_expr *maskexpr;
5787   tree offset;
5788   int i;
5789   bool optional_mask;
5790 
5791   array_arg = expr->value.function.actual;
5792   value_arg = array_arg->next;
5793   dim_arg   = value_arg->next;
5794   mask_arg  = dim_arg->next;
5795   kind_arg  = mask_arg->next;
5796   back_arg  = kind_arg->next;
5797 
5798   /* Remove kind and set ikind.  */
5799   if (kind_arg->expr)
5800     {
5801       ikind = mpz_get_si (kind_arg->expr->value.integer);
5802       gfc_free_expr (kind_arg->expr);
5803       kind_arg->expr = NULL;
5804     }
5805   else
5806     ikind = gfc_default_integer_kind;
5807 
5808   value_expr = value_arg->expr;
5809 
5810   /* Unless it's a string, pass VALUE by value.  */
5811   if (value_expr->ts.type != BT_CHARACTER)
5812     value_arg->name = "%VAL";
5813 
5814   /* Pass BACK argument by value.  */
5815   back_arg->name = "%VAL";
5816 
5817   /* Call the library if we have a character function or if
5818      rank > 0.  */
5819   if (se->ss || array_arg->expr->ts.type == BT_CHARACTER)
5820     {
5821       se->ignore_optional = 1;
5822       if (expr->rank == 0)
5823 	{
5824 	  /* Remove dim argument.  */
5825 	  gfc_free_expr (dim_arg->expr);
5826 	  dim_arg->expr = NULL;
5827 	}
5828       gfc_conv_intrinsic_funcall (se, expr);
5829       return;
5830     }
5831 
5832   type = gfc_get_int_type (ikind);
5833 
5834   /* Initialize the result.  */
5835   resvar = gfc_create_var (gfc_array_index_type, "pos");
5836   gfc_add_modify (&se->pre, resvar, build_int_cst (gfc_array_index_type, 0));
5837   offset = gfc_create_var (gfc_array_index_type, "offset");
5838 
5839   maskexpr = mask_arg->expr;
5840   optional_mask = maskexpr && maskexpr->expr_type == EXPR_VARIABLE
5841     && maskexpr->symtree->n.sym->attr.dummy
5842     && maskexpr->symtree->n.sym->attr.optional;
5843 
5844   /*  Generate two loops, one for BACK=.true. and one for BACK=.false.  */
5845 
5846   for (i = 0 ; i < 2; i++)
5847     {
5848       /* Walk the arguments.  */
5849       arrayss = gfc_walk_expr (array_arg->expr);
5850       gcc_assert (arrayss != gfc_ss_terminator);
5851 
5852       if (maskexpr && maskexpr->rank != 0)
5853 	{
5854 	  maskss = gfc_walk_expr (maskexpr);
5855 	  gcc_assert (maskss != gfc_ss_terminator);
5856 	}
5857       else
5858 	maskss = NULL;
5859 
5860       /* Initialize the scalarizer.  */
5861       gfc_init_loopinfo (&loop);
5862       exit_label = gfc_build_label_decl (NULL_TREE);
5863       TREE_USED (exit_label) = 1;
5864 
5865       /* We add the mask first because the number of iterations is
5866 	 taken from the last ss, and this breaks if an absent
5867 	 optional argument is used for mask.  */
5868 
5869       if (maskss)
5870 	gfc_add_ss_to_loop (&loop, maskss);
5871       gfc_add_ss_to_loop (&loop, arrayss);
5872 
5873       /* Initialize the loop.  */
5874       gfc_conv_ss_startstride (&loop);
5875       gfc_conv_loop_setup (&loop, &expr->where);
5876 
5877       /* Calculate the offset.  */
5878       tmp = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
5879 			     gfc_index_one_node, loop.from[0]);
5880       gfc_add_modify (&loop.pre, offset, tmp);
5881 
5882       gfc_mark_ss_chain_used (arrayss, 1);
5883       if (maskss)
5884 	gfc_mark_ss_chain_used (maskss, 1);
5885 
5886       /* The first loop is for BACK=.true.  */
5887       if (i == 0)
5888 	loop.reverse[0] = GFC_REVERSE_SET;
5889 
5890       /* Generate the loop body.  */
5891       gfc_start_scalarized_body (&loop, &body);
5892 
5893       /* If we have an array mask, only add the element if it is
5894 	 set.  */
5895       if (maskss)
5896 	{
5897 	  gfc_init_se (&maskse, NULL);
5898 	  gfc_copy_loopinfo_to_se (&maskse, &loop);
5899 	  maskse.ss = maskss;
5900 	  gfc_conv_expr_val (&maskse, maskexpr);
5901 	  gfc_add_block_to_block (&body, &maskse.pre);
5902 	}
5903 
5904       /* If the condition matches then set the return value.  */
5905       gfc_start_block (&block);
5906 
5907       /* Add the offset.  */
5908       tmp = fold_build2_loc (input_location, PLUS_EXPR,
5909 			     TREE_TYPE (resvar),
5910 			     loop.loopvar[0], offset);
5911       gfc_add_modify (&block, resvar, tmp);
5912       /* And break out of the loop.  */
5913       tmp = build1_v (GOTO_EXPR, exit_label);
5914       gfc_add_expr_to_block (&block, tmp);
5915 
5916       found = gfc_finish_block (&block);
5917 
5918       /* Check this element.  */
5919       gfc_init_se (&arrayse, NULL);
5920       gfc_copy_loopinfo_to_se (&arrayse, &loop);
5921       arrayse.ss = arrayss;
5922       gfc_conv_expr_val (&arrayse, array_arg->expr);
5923       gfc_add_block_to_block (&body, &arrayse.pre);
5924 
5925       gfc_init_se (&valuese, NULL);
5926       gfc_conv_expr_val (&valuese, value_arg->expr);
5927       gfc_add_block_to_block (&body, &valuese.pre);
5928 
5929       tmp = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
5930 			     arrayse.expr, valuese.expr);
5931 
5932       tmp = build3_v (COND_EXPR, tmp, found, build_empty_stmt (input_location));
5933       if (maskss)
5934 	{
5935 	  /* We enclose the above in if (mask) {...}.  If the mask is
5936 	     an optional argument, generate IF (.NOT. PRESENT(MASK)
5937 	     .OR. MASK(I)). */
5938 
5939 	  tree ifmask;
5940 	  ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
5941 	  tmp = build3_v (COND_EXPR, ifmask, tmp,
5942 			  build_empty_stmt (input_location));
5943 	}
5944 
5945       gfc_add_expr_to_block (&body, tmp);
5946       gfc_add_block_to_block (&body, &arrayse.post);
5947 
5948       gfc_trans_scalarizing_loops (&loop, &body);
5949 
5950       /* Add the exit label.  */
5951       tmp = build1_v (LABEL_EXPR, exit_label);
5952       gfc_add_expr_to_block (&loop.pre, tmp);
5953       gfc_start_block (&loopblock);
5954       gfc_add_block_to_block (&loopblock, &loop.pre);
5955       gfc_add_block_to_block (&loopblock, &loop.post);
5956       if (i == 0)
5957 	forward_branch = gfc_finish_block (&loopblock);
5958       else
5959 	back_branch = gfc_finish_block (&loopblock);
5960 
5961       gfc_cleanup_loop (&loop);
5962     }
5963 
5964   /* Enclose the two loops in an IF statement.  */
5965 
5966   gfc_init_se (&backse, NULL);
5967   gfc_conv_expr_val (&backse, back_arg->expr);
5968   gfc_add_block_to_block (&se->pre, &backse.pre);
5969   tmp = build3_v (COND_EXPR, backse.expr, forward_branch, back_branch);
5970 
5971   /* For a scalar mask, enclose the loop in an if statement.  */
5972   if (maskexpr && maskss == NULL)
5973     {
5974       tree ifmask;
5975       tree if_stmt;
5976 
5977       gfc_init_se (&maskse, NULL);
5978       gfc_conv_expr_val (&maskse, maskexpr);
5979       gfc_init_block (&block);
5980       gfc_add_expr_to_block (&block, maskse.expr);
5981       ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
5982       if_stmt = build3_v (COND_EXPR, ifmask, tmp,
5983 			  build_empty_stmt (input_location));
5984       gfc_add_expr_to_block (&block, if_stmt);
5985       tmp = gfc_finish_block (&block);
5986     }
5987 
5988   gfc_add_expr_to_block (&se->pre, tmp);
5989   se->expr = convert (type, resvar);
5990 
5991 }
5992 
5993 /* Emit code for minval or maxval intrinsic.  There are many different cases
5994    we need to handle.  For performance reasons we sometimes create two
5995    loops instead of one, where the second one is much simpler.
5996    Examples for minval intrinsic:
5997    1) Result is an array, a call is generated
5998    2) Array mask is used and NaNs need to be supported, rank 1:
5999       limit = Infinity;
6000       nonempty = false;
6001       S = from;
6002       while (S <= to) {
6003 	if (mask[S]) { nonempty = true; if (a[S] <= limit) goto lab; }
6004 	S++;
6005       }
6006       limit = nonempty ? NaN : huge (limit);
6007       lab:
6008       while (S <= to) { if(mask[S]) limit = min (a[S], limit); S++; }
6009    3) NaNs need to be supported, but it is known at compile time or cheaply
6010       at runtime whether array is nonempty or not, rank 1:
6011       limit = Infinity;
6012       S = from;
6013       while (S <= to) { if (a[S] <= limit) goto lab; S++; }
6014       limit = (from <= to) ? NaN : huge (limit);
6015       lab:
6016       while (S <= to) { limit = min (a[S], limit); S++; }
6017    4) Array mask is used and NaNs need to be supported, rank > 1:
6018       limit = Infinity;
6019       nonempty = false;
6020       fast = false;
6021       S1 = from1;
6022       while (S1 <= to1) {
6023 	S2 = from2;
6024 	while (S2 <= to2) {
6025 	  if (mask[S1][S2]) {
6026 	    if (fast) limit = min (a[S1][S2], limit);
6027 	    else {
6028 	      nonempty = true;
6029 	      if (a[S1][S2] <= limit) {
6030 		limit = a[S1][S2];
6031 		fast = true;
6032 	      }
6033 	    }
6034 	  }
6035 	  S2++;
6036 	}
6037 	S1++;
6038       }
6039       if (!fast)
6040 	limit = nonempty ? NaN : huge (limit);
6041    5) NaNs need to be supported, but it is known at compile time or cheaply
6042       at runtime whether array is nonempty or not, rank > 1:
6043       limit = Infinity;
6044       fast = false;
6045       S1 = from1;
6046       while (S1 <= to1) {
6047 	S2 = from2;
6048 	while (S2 <= to2) {
6049 	  if (fast) limit = min (a[S1][S2], limit);
6050 	  else {
6051 	    if (a[S1][S2] <= limit) {
6052 	      limit = a[S1][S2];
6053 	      fast = true;
6054 	    }
6055 	  }
6056 	  S2++;
6057 	}
6058 	S1++;
6059       }
6060       if (!fast)
6061 	limit = (nonempty_array) ? NaN : huge (limit);
6062    6) NaNs aren't supported, but infinities are.  Array mask is used:
6063       limit = Infinity;
6064       nonempty = false;
6065       S = from;
6066       while (S <= to) {
6067 	if (mask[S]) { nonempty = true; limit = min (a[S], limit); }
6068 	S++;
6069       }
6070       limit = nonempty ? limit : huge (limit);
6071    7) Same without array mask:
6072       limit = Infinity;
6073       S = from;
6074       while (S <= to) { limit = min (a[S], limit); S++; }
6075       limit = (from <= to) ? limit : huge (limit);
6076    8) Neither NaNs nor infinities are supported (-ffast-math or BT_INTEGER):
6077       limit = huge (limit);
6078       S = from;
6079       while (S <= to) { limit = min (a[S], limit); S++); }
6080       (or
6081       while (S <= to) { if (mask[S]) limit = min (a[S], limit); S++; }
6082       with array mask instead).
6083    For 3), 5), 7) and 8), if mask is scalar, this all goes into a conditional,
6084    setting limit = huge (limit); in the else branch.  */
6085 
6086 static void
gfc_conv_intrinsic_minmaxval(gfc_se * se,gfc_expr * expr,enum tree_code op)6087 gfc_conv_intrinsic_minmaxval (gfc_se * se, gfc_expr * expr, enum tree_code op)
6088 {
6089   tree limit;
6090   tree type;
6091   tree tmp;
6092   tree ifbody;
6093   tree nonempty;
6094   tree nonempty_var;
6095   tree lab;
6096   tree fast;
6097   tree huge_cst = NULL, nan_cst = NULL;
6098   stmtblock_t body;
6099   stmtblock_t block, block2;
6100   gfc_loopinfo loop;
6101   gfc_actual_arglist *actual;
6102   gfc_ss *arrayss;
6103   gfc_ss *maskss;
6104   gfc_se arrayse;
6105   gfc_se maskse;
6106   gfc_expr *arrayexpr;
6107   gfc_expr *maskexpr;
6108   int n;
6109   bool optional_mask;
6110 
6111   if (se->ss)
6112     {
6113       gfc_conv_intrinsic_funcall (se, expr);
6114       return;
6115     }
6116 
6117   actual = expr->value.function.actual;
6118   arrayexpr = actual->expr;
6119 
6120   if (arrayexpr->ts.type == BT_CHARACTER)
6121     {
6122       gfc_actual_arglist *dim = actual->next;
6123       if (expr->rank == 0 && dim->expr != 0)
6124 	{
6125 	  gfc_free_expr (dim->expr);
6126 	  dim->expr = NULL;
6127 	}
6128       gfc_conv_intrinsic_funcall (se, expr);
6129       return;
6130     }
6131 
6132   type = gfc_typenode_for_spec (&expr->ts);
6133   /* Initialize the result.  */
6134   limit = gfc_create_var (type, "limit");
6135   n = gfc_validate_kind (expr->ts.type, expr->ts.kind, false);
6136   switch (expr->ts.type)
6137     {
6138     case BT_REAL:
6139       huge_cst = gfc_conv_mpfr_to_tree (gfc_real_kinds[n].huge,
6140 					expr->ts.kind, 0);
6141       if (HONOR_INFINITIES (DECL_MODE (limit)))
6142 	{
6143 	  REAL_VALUE_TYPE real;
6144 	  real_inf (&real);
6145 	  tmp = build_real (type, real);
6146 	}
6147       else
6148 	tmp = huge_cst;
6149       if (HONOR_NANS (DECL_MODE (limit)))
6150 	nan_cst = gfc_build_nan (type, "");
6151       break;
6152 
6153     case BT_INTEGER:
6154       tmp = gfc_conv_mpz_to_tree (gfc_integer_kinds[n].huge, expr->ts.kind);
6155       break;
6156 
6157     default:
6158       gcc_unreachable ();
6159     }
6160 
6161   /* We start with the most negative possible value for MAXVAL, and the most
6162      positive possible value for MINVAL. The most negative possible value is
6163      -HUGE for BT_REAL and (-HUGE - 1) for BT_INTEGER; the most positive
6164      possible value is HUGE in both cases.  */
6165   if (op == GT_EXPR)
6166     {
6167       tmp = fold_build1_loc (input_location, NEGATE_EXPR, TREE_TYPE (tmp), tmp);
6168       if (huge_cst)
6169 	huge_cst = fold_build1_loc (input_location, NEGATE_EXPR,
6170 				    TREE_TYPE (huge_cst), huge_cst);
6171     }
6172 
6173   if (op == GT_EXPR && expr->ts.type == BT_INTEGER)
6174     tmp = fold_build2_loc (input_location, MINUS_EXPR, TREE_TYPE (tmp),
6175 			   tmp, build_int_cst (type, 1));
6176 
6177   gfc_add_modify (&se->pre, limit, tmp);
6178 
6179   /* Walk the arguments.  */
6180   arrayss = gfc_walk_expr (arrayexpr);
6181   gcc_assert (arrayss != gfc_ss_terminator);
6182 
6183   actual = actual->next->next;
6184   gcc_assert (actual);
6185   maskexpr = actual->expr;
6186   optional_mask = maskexpr && maskexpr->expr_type == EXPR_VARIABLE
6187     && maskexpr->symtree->n.sym->attr.dummy
6188     && maskexpr->symtree->n.sym->attr.optional;
6189   nonempty = NULL;
6190   if (maskexpr && maskexpr->rank != 0)
6191     {
6192       maskss = gfc_walk_expr (maskexpr);
6193       gcc_assert (maskss != gfc_ss_terminator);
6194     }
6195   else
6196     {
6197       mpz_t asize;
6198       if (gfc_array_size (arrayexpr, &asize))
6199 	{
6200 	  nonempty = gfc_conv_mpz_to_tree (asize, gfc_index_integer_kind);
6201 	  mpz_clear (asize);
6202 	  nonempty = fold_build2_loc (input_location, GT_EXPR,
6203 				      logical_type_node, nonempty,
6204 				      gfc_index_zero_node);
6205 	}
6206       maskss = NULL;
6207     }
6208 
6209   /* Initialize the scalarizer.  */
6210   gfc_init_loopinfo (&loop);
6211 
6212   /* We add the mask first because the number of iterations is taken
6213      from the last ss, and this breaks if an absent optional argument
6214      is used for mask.  */
6215 
6216   if (maskss)
6217     gfc_add_ss_to_loop (&loop, maskss);
6218   gfc_add_ss_to_loop (&loop, arrayss);
6219 
6220   /* Initialize the loop.  */
6221   gfc_conv_ss_startstride (&loop);
6222 
6223   /* The code generated can have more than one loop in sequence (see the
6224      comment at the function header).  This doesn't work well with the
6225      scalarizer, which changes arrays' offset when the scalarization loops
6226      are generated (see gfc_trans_preloop_setup).  Fortunately, {min,max}val
6227      are  currently inlined in the scalar case only.  As there is no dependency
6228      to care about in that case, there is no temporary, so that we can use the
6229      scalarizer temporary code to handle multiple loops.  Thus, we set temp_dim
6230      here, we call gfc_mark_ss_chain_used with flag=3 later, and we use
6231      gfc_trans_scalarized_loop_boundary even later to restore offset.
6232      TODO: this prevents inlining of rank > 0 minmaxval calls, so this
6233      should eventually go away.  We could either create two loops properly,
6234      or find another way to save/restore the array offsets between the two
6235      loops (without conflicting with temporary management), or use a single
6236      loop minmaxval implementation.  See PR 31067.  */
6237   loop.temp_dim = loop.dimen;
6238   gfc_conv_loop_setup (&loop, &expr->where);
6239 
6240   if (nonempty == NULL && maskss == NULL
6241       && loop.dimen == 1 && loop.from[0] && loop.to[0])
6242     nonempty = fold_build2_loc (input_location, LE_EXPR, logical_type_node,
6243 				loop.from[0], loop.to[0]);
6244   nonempty_var = NULL;
6245   if (nonempty == NULL
6246       && (HONOR_INFINITIES (DECL_MODE (limit))
6247 	  || HONOR_NANS (DECL_MODE (limit))))
6248     {
6249       nonempty_var = gfc_create_var (logical_type_node, "nonempty");
6250       gfc_add_modify (&se->pre, nonempty_var, logical_false_node);
6251       nonempty = nonempty_var;
6252     }
6253   lab = NULL;
6254   fast = NULL;
6255   if (HONOR_NANS (DECL_MODE (limit)))
6256     {
6257       if (loop.dimen == 1)
6258 	{
6259 	  lab = gfc_build_label_decl (NULL_TREE);
6260 	  TREE_USED (lab) = 1;
6261 	}
6262       else
6263 	{
6264 	  fast = gfc_create_var (logical_type_node, "fast");
6265 	  gfc_add_modify (&se->pre, fast, logical_false_node);
6266 	}
6267     }
6268 
6269   gfc_mark_ss_chain_used (arrayss, lab ? 3 : 1);
6270   if (maskss)
6271     gfc_mark_ss_chain_used (maskss, lab ? 3 : 1);
6272   /* Generate the loop body.  */
6273   gfc_start_scalarized_body (&loop, &body);
6274 
6275   /* If we have a mask, only add this element if the mask is set.  */
6276   if (maskss)
6277     {
6278       gfc_init_se (&maskse, NULL);
6279       gfc_copy_loopinfo_to_se (&maskse, &loop);
6280       maskse.ss = maskss;
6281       gfc_conv_expr_val (&maskse, maskexpr);
6282       gfc_add_block_to_block (&body, &maskse.pre);
6283 
6284       gfc_start_block (&block);
6285     }
6286   else
6287     gfc_init_block (&block);
6288 
6289   /* Compare with the current limit.  */
6290   gfc_init_se (&arrayse, NULL);
6291   gfc_copy_loopinfo_to_se (&arrayse, &loop);
6292   arrayse.ss = arrayss;
6293   gfc_conv_expr_val (&arrayse, arrayexpr);
6294   gfc_add_block_to_block (&block, &arrayse.pre);
6295 
6296   gfc_init_block (&block2);
6297 
6298   if (nonempty_var)
6299     gfc_add_modify (&block2, nonempty_var, logical_true_node);
6300 
6301   if (HONOR_NANS (DECL_MODE (limit)))
6302     {
6303       tmp = fold_build2_loc (input_location, op == GT_EXPR ? GE_EXPR : LE_EXPR,
6304 			     logical_type_node, arrayse.expr, limit);
6305       if (lab)
6306 	ifbody = build1_v (GOTO_EXPR, lab);
6307       else
6308 	{
6309 	  stmtblock_t ifblock;
6310 
6311 	  gfc_init_block (&ifblock);
6312 	  gfc_add_modify (&ifblock, limit, arrayse.expr);
6313 	  gfc_add_modify (&ifblock, fast, logical_true_node);
6314 	  ifbody = gfc_finish_block (&ifblock);
6315 	}
6316       tmp = build3_v (COND_EXPR, tmp, ifbody,
6317 		      build_empty_stmt (input_location));
6318       gfc_add_expr_to_block (&block2, tmp);
6319     }
6320   else
6321     {
6322       /* MIN_EXPR/MAX_EXPR has unspecified behavior with NaNs or
6323 	 signed zeros.  */
6324       tmp = fold_build2_loc (input_location,
6325 			     op == GT_EXPR ? MAX_EXPR : MIN_EXPR,
6326 			     type, arrayse.expr, limit);
6327       gfc_add_modify (&block2, limit, tmp);
6328     }
6329 
6330   if (fast)
6331     {
6332       tree elsebody = gfc_finish_block (&block2);
6333 
6334       /* MIN_EXPR/MAX_EXPR has unspecified behavior with NaNs or
6335 	 signed zeros.  */
6336       if (HONOR_NANS (DECL_MODE (limit)))
6337 	{
6338 	  tmp = fold_build2_loc (input_location, op, logical_type_node,
6339 				 arrayse.expr, limit);
6340 	  ifbody = build2_v (MODIFY_EXPR, limit, arrayse.expr);
6341 	  ifbody = build3_v (COND_EXPR, tmp, ifbody,
6342 			     build_empty_stmt (input_location));
6343 	}
6344       else
6345 	{
6346 	  tmp = fold_build2_loc (input_location,
6347 				 op == GT_EXPR ? MAX_EXPR : MIN_EXPR,
6348 				 type, arrayse.expr, limit);
6349 	  ifbody = build2_v (MODIFY_EXPR, limit, tmp);
6350 	}
6351       tmp = build3_v (COND_EXPR, fast, ifbody, elsebody);
6352       gfc_add_expr_to_block (&block, tmp);
6353     }
6354   else
6355     gfc_add_block_to_block (&block, &block2);
6356 
6357   gfc_add_block_to_block (&block, &arrayse.post);
6358 
6359   tmp = gfc_finish_block (&block);
6360   if (maskss)
6361     {
6362       /* We enclose the above in if (mask) {...}.  If the mask is an
6363 	 optional argument, generate IF (.NOT. PRESENT(MASK)
6364 	 .OR. MASK(I)).  */
6365       tree ifmask;
6366       ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
6367       tmp = build3_v (COND_EXPR, ifmask, tmp,
6368 		      build_empty_stmt (input_location));
6369     }
6370   gfc_add_expr_to_block (&body, tmp);
6371 
6372   if (lab)
6373     {
6374       gfc_trans_scalarized_loop_boundary (&loop, &body);
6375 
6376       tmp = fold_build3_loc (input_location, COND_EXPR, type, nonempty,
6377 			     nan_cst, huge_cst);
6378       gfc_add_modify (&loop.code[0], limit, tmp);
6379       gfc_add_expr_to_block (&loop.code[0], build1_v (LABEL_EXPR, lab));
6380 
6381       /* If we have a mask, only add this element if the mask is set.  */
6382       if (maskss)
6383 	{
6384 	  gfc_init_se (&maskse, NULL);
6385 	  gfc_copy_loopinfo_to_se (&maskse, &loop);
6386 	  maskse.ss = maskss;
6387 	  gfc_conv_expr_val (&maskse, maskexpr);
6388 	  gfc_add_block_to_block (&body, &maskse.pre);
6389 
6390 	  gfc_start_block (&block);
6391 	}
6392       else
6393 	gfc_init_block (&block);
6394 
6395       /* Compare with the current limit.  */
6396       gfc_init_se (&arrayse, NULL);
6397       gfc_copy_loopinfo_to_se (&arrayse, &loop);
6398       arrayse.ss = arrayss;
6399       gfc_conv_expr_val (&arrayse, arrayexpr);
6400       gfc_add_block_to_block (&block, &arrayse.pre);
6401 
6402       /* MIN_EXPR/MAX_EXPR has unspecified behavior with NaNs or
6403 	 signed zeros.  */
6404       if (HONOR_NANS (DECL_MODE (limit)))
6405 	{
6406 	  tmp = fold_build2_loc (input_location, op, logical_type_node,
6407 				 arrayse.expr, limit);
6408 	  ifbody = build2_v (MODIFY_EXPR, limit, arrayse.expr);
6409 	  tmp = build3_v (COND_EXPR, tmp, ifbody,
6410 			  build_empty_stmt (input_location));
6411 	  gfc_add_expr_to_block (&block, tmp);
6412 	}
6413       else
6414 	{
6415 	  tmp = fold_build2_loc (input_location,
6416 				 op == GT_EXPR ? MAX_EXPR : MIN_EXPR,
6417 				 type, arrayse.expr, limit);
6418 	  gfc_add_modify (&block, limit, tmp);
6419 	}
6420 
6421       gfc_add_block_to_block (&block, &arrayse.post);
6422 
6423       tmp = gfc_finish_block (&block);
6424       if (maskss)
6425 	/* We enclose the above in if (mask) {...}.  */
6426 	{
6427 	  tree ifmask;
6428 	  ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
6429 	  tmp = build3_v (COND_EXPR, ifmask, tmp,
6430 			  build_empty_stmt (input_location));
6431 	}
6432 
6433       gfc_add_expr_to_block (&body, tmp);
6434       /* Avoid initializing loopvar[0] again, it should be left where
6435 	 it finished by the first loop.  */
6436       loop.from[0] = loop.loopvar[0];
6437     }
6438   gfc_trans_scalarizing_loops (&loop, &body);
6439 
6440   if (fast)
6441     {
6442       tmp = fold_build3_loc (input_location, COND_EXPR, type, nonempty,
6443 			     nan_cst, huge_cst);
6444       ifbody = build2_v (MODIFY_EXPR, limit, tmp);
6445       tmp = build3_v (COND_EXPR, fast, build_empty_stmt (input_location),
6446 		      ifbody);
6447       gfc_add_expr_to_block (&loop.pre, tmp);
6448     }
6449   else if (HONOR_INFINITIES (DECL_MODE (limit)) && !lab)
6450     {
6451       tmp = fold_build3_loc (input_location, COND_EXPR, type, nonempty, limit,
6452 			     huge_cst);
6453       gfc_add_modify (&loop.pre, limit, tmp);
6454     }
6455 
6456   /* For a scalar mask, enclose the loop in an if statement.  */
6457   if (maskexpr && maskss == NULL)
6458     {
6459       tree else_stmt;
6460       tree ifmask;
6461 
6462       gfc_init_se (&maskse, NULL);
6463       gfc_conv_expr_val (&maskse, maskexpr);
6464       gfc_init_block (&block);
6465       gfc_add_block_to_block (&block, &loop.pre);
6466       gfc_add_block_to_block (&block, &loop.post);
6467       tmp = gfc_finish_block (&block);
6468 
6469       if (HONOR_INFINITIES (DECL_MODE (limit)))
6470 	else_stmt = build2_v (MODIFY_EXPR, limit, huge_cst);
6471       else
6472 	else_stmt = build_empty_stmt (input_location);
6473 
6474       ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
6475       tmp = build3_v (COND_EXPR, ifmask, tmp, else_stmt);
6476       gfc_add_expr_to_block (&block, tmp);
6477       gfc_add_block_to_block (&se->pre, &block);
6478     }
6479   else
6480     {
6481       gfc_add_block_to_block (&se->pre, &loop.pre);
6482       gfc_add_block_to_block (&se->pre, &loop.post);
6483     }
6484 
6485   gfc_cleanup_loop (&loop);
6486 
6487   se->expr = limit;
6488 }
6489 
6490 /* BTEST (i, pos) = (i & (1 << pos)) != 0.  */
6491 static void
gfc_conv_intrinsic_btest(gfc_se * se,gfc_expr * expr)6492 gfc_conv_intrinsic_btest (gfc_se * se, gfc_expr * expr)
6493 {
6494   tree args[2];
6495   tree type;
6496   tree tmp;
6497 
6498   gfc_conv_intrinsic_function_args (se, expr, args, 2);
6499   type = TREE_TYPE (args[0]);
6500 
6501   /* Optionally generate code for runtime argument check.  */
6502   if (gfc_option.rtcheck & GFC_RTCHECK_BITS)
6503     {
6504       tree below = fold_build2_loc (input_location, LT_EXPR,
6505 				    logical_type_node, args[1],
6506 				    build_int_cst (TREE_TYPE (args[1]), 0));
6507       tree nbits = build_int_cst (TREE_TYPE (args[1]), TYPE_PRECISION (type));
6508       tree above = fold_build2_loc (input_location, GE_EXPR,
6509 				    logical_type_node, args[1], nbits);
6510       tree scond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
6511 				    logical_type_node, below, above);
6512       gfc_trans_runtime_check (true, false, scond, &se->pre, &expr->where,
6513 			       "POS argument (%ld) out of range 0:%ld "
6514 			       "in intrinsic BTEST",
6515 			       fold_convert (long_integer_type_node, args[1]),
6516 			       fold_convert (long_integer_type_node, nbits));
6517     }
6518 
6519   tmp = fold_build2_loc (input_location, LSHIFT_EXPR, type,
6520 			 build_int_cst (type, 1), args[1]);
6521   tmp = fold_build2_loc (input_location, BIT_AND_EXPR, type, args[0], tmp);
6522   tmp = fold_build2_loc (input_location, NE_EXPR, logical_type_node, tmp,
6523 			 build_int_cst (type, 0));
6524   type = gfc_typenode_for_spec (&expr->ts);
6525   se->expr = convert (type, tmp);
6526 }
6527 
6528 
6529 /* Generate code for BGE, BGT, BLE and BLT intrinsics.  */
6530 static void
gfc_conv_intrinsic_bitcomp(gfc_se * se,gfc_expr * expr,enum tree_code op)6531 gfc_conv_intrinsic_bitcomp (gfc_se * se, gfc_expr * expr, enum tree_code op)
6532 {
6533   tree args[2];
6534 
6535   gfc_conv_intrinsic_function_args (se, expr, args, 2);
6536 
6537   /* Convert both arguments to the unsigned type of the same size.  */
6538   args[0] = fold_convert (unsigned_type_for (TREE_TYPE (args[0])), args[0]);
6539   args[1] = fold_convert (unsigned_type_for (TREE_TYPE (args[1])), args[1]);
6540 
6541   /* If they have unequal type size, convert to the larger one.  */
6542   if (TYPE_PRECISION (TREE_TYPE (args[0]))
6543       > TYPE_PRECISION (TREE_TYPE (args[1])))
6544     args[1] = fold_convert (TREE_TYPE (args[0]), args[1]);
6545   else if (TYPE_PRECISION (TREE_TYPE (args[1]))
6546 	   > TYPE_PRECISION (TREE_TYPE (args[0])))
6547     args[0] = fold_convert (TREE_TYPE (args[1]), args[0]);
6548 
6549   /* Now, we compare them.  */
6550   se->expr = fold_build2_loc (input_location, op, logical_type_node,
6551 			      args[0], args[1]);
6552 }
6553 
6554 
6555 /* Generate code to perform the specified operation.  */
6556 static void
gfc_conv_intrinsic_bitop(gfc_se * se,gfc_expr * expr,enum tree_code op)6557 gfc_conv_intrinsic_bitop (gfc_se * se, gfc_expr * expr, enum tree_code op)
6558 {
6559   tree args[2];
6560 
6561   gfc_conv_intrinsic_function_args (se, expr, args, 2);
6562   se->expr = fold_build2_loc (input_location, op, TREE_TYPE (args[0]),
6563 			      args[0], args[1]);
6564 }
6565 
6566 /* Bitwise not.  */
6567 static void
gfc_conv_intrinsic_not(gfc_se * se,gfc_expr * expr)6568 gfc_conv_intrinsic_not (gfc_se * se, gfc_expr * expr)
6569 {
6570   tree arg;
6571 
6572   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
6573   se->expr = fold_build1_loc (input_location, BIT_NOT_EXPR,
6574 			      TREE_TYPE (arg), arg);
6575 }
6576 
6577 /* Set or clear a single bit.  */
6578 static void
gfc_conv_intrinsic_singlebitop(gfc_se * se,gfc_expr * expr,int set)6579 gfc_conv_intrinsic_singlebitop (gfc_se * se, gfc_expr * expr, int set)
6580 {
6581   tree args[2];
6582   tree type;
6583   tree tmp;
6584   enum tree_code op;
6585 
6586   gfc_conv_intrinsic_function_args (se, expr, args, 2);
6587   type = TREE_TYPE (args[0]);
6588 
6589   /* Optionally generate code for runtime argument check.  */
6590   if (gfc_option.rtcheck & GFC_RTCHECK_BITS)
6591     {
6592       tree below = fold_build2_loc (input_location, LT_EXPR,
6593 				    logical_type_node, args[1],
6594 				    build_int_cst (TREE_TYPE (args[1]), 0));
6595       tree nbits = build_int_cst (TREE_TYPE (args[1]), TYPE_PRECISION (type));
6596       tree above = fold_build2_loc (input_location, GE_EXPR,
6597 				    logical_type_node, args[1], nbits);
6598       tree scond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
6599 				    logical_type_node, below, above);
6600       size_t len_name = strlen (expr->value.function.isym->name);
6601       char *name = XALLOCAVEC (char, len_name + 1);
6602       for (size_t i = 0; i < len_name; i++)
6603 	name[i] = TOUPPER (expr->value.function.isym->name[i]);
6604       name[len_name] = '\0';
6605       tree iname = gfc_build_addr_expr (pchar_type_node,
6606 					gfc_build_cstring_const (name));
6607       gfc_trans_runtime_check (true, false, scond, &se->pre, &expr->where,
6608 			       "POS argument (%ld) out of range 0:%ld "
6609 			       "in intrinsic %s",
6610 			       fold_convert (long_integer_type_node, args[1]),
6611 			       fold_convert (long_integer_type_node, nbits),
6612 			       iname);
6613     }
6614 
6615   tmp = fold_build2_loc (input_location, LSHIFT_EXPR, type,
6616 			 build_int_cst (type, 1), args[1]);
6617   if (set)
6618     op = BIT_IOR_EXPR;
6619   else
6620     {
6621       op = BIT_AND_EXPR;
6622       tmp = fold_build1_loc (input_location, BIT_NOT_EXPR, type, tmp);
6623     }
6624   se->expr = fold_build2_loc (input_location, op, type, args[0], tmp);
6625 }
6626 
6627 /* Extract a sequence of bits.
6628     IBITS(I, POS, LEN) = (I >> POS) & ~((~0) << LEN).  */
6629 static void
gfc_conv_intrinsic_ibits(gfc_se * se,gfc_expr * expr)6630 gfc_conv_intrinsic_ibits (gfc_se * se, gfc_expr * expr)
6631 {
6632   tree args[3];
6633   tree type;
6634   tree tmp;
6635   tree mask;
6636   tree num_bits, cond;
6637 
6638   gfc_conv_intrinsic_function_args (se, expr, args, 3);
6639   type = TREE_TYPE (args[0]);
6640 
6641   /* Optionally generate code for runtime argument check.  */
6642   if (gfc_option.rtcheck & GFC_RTCHECK_BITS)
6643     {
6644       tree tmp1 = fold_convert (long_integer_type_node, args[1]);
6645       tree tmp2 = fold_convert (long_integer_type_node, args[2]);
6646       tree nbits = build_int_cst (long_integer_type_node,
6647 				  TYPE_PRECISION (type));
6648       tree below = fold_build2_loc (input_location, LT_EXPR,
6649 				    logical_type_node, args[1],
6650 				    build_int_cst (TREE_TYPE (args[1]), 0));
6651       tree above = fold_build2_loc (input_location, GT_EXPR,
6652 				    logical_type_node, tmp1, nbits);
6653       tree scond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
6654 				    logical_type_node, below, above);
6655       gfc_trans_runtime_check (true, false, scond, &se->pre, &expr->where,
6656 			       "POS argument (%ld) out of range 0:%ld "
6657 			       "in intrinsic IBITS", tmp1, nbits);
6658       below = fold_build2_loc (input_location, LT_EXPR,
6659 			       logical_type_node, args[2],
6660 			       build_int_cst (TREE_TYPE (args[2]), 0));
6661       above = fold_build2_loc (input_location, GT_EXPR,
6662 			       logical_type_node, tmp2, nbits);
6663       scond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
6664 			       logical_type_node, below, above);
6665       gfc_trans_runtime_check (true, false, scond, &se->pre, &expr->where,
6666 			       "LEN argument (%ld) out of range 0:%ld "
6667 			       "in intrinsic IBITS", tmp2, nbits);
6668       above = fold_build2_loc (input_location, PLUS_EXPR,
6669 			       long_integer_type_node, tmp1, tmp2);
6670       scond = fold_build2_loc (input_location, GT_EXPR,
6671 			       logical_type_node, above, nbits);
6672       gfc_trans_runtime_check (true, false, scond, &se->pre, &expr->where,
6673 			       "POS(%ld)+LEN(%ld)>BIT_SIZE(%ld) "
6674 			       "in intrinsic IBITS", tmp1, tmp2, nbits);
6675     }
6676 
6677   /* The Fortran standard allows (shift width) LEN <= BIT_SIZE(I), whereas
6678      gcc requires a shift width < BIT_SIZE(I), so we have to catch this
6679      special case.  See also gfc_conv_intrinsic_ishft ().  */
6680   num_bits = build_int_cst (TREE_TYPE (args[2]), TYPE_PRECISION (type));
6681 
6682   mask = build_int_cst (type, -1);
6683   mask = fold_build2_loc (input_location, LSHIFT_EXPR, type, mask, args[2]);
6684   cond = fold_build2_loc (input_location, GE_EXPR, logical_type_node, args[2],
6685 			  num_bits);
6686   mask = fold_build3_loc (input_location, COND_EXPR, type, cond,
6687 			  build_int_cst (type, 0), mask);
6688   mask = fold_build1_loc (input_location, BIT_NOT_EXPR, type, mask);
6689 
6690   tmp = fold_build2_loc (input_location, RSHIFT_EXPR, type, args[0], args[1]);
6691 
6692   se->expr = fold_build2_loc (input_location, BIT_AND_EXPR, type, tmp, mask);
6693 }
6694 
6695 static void
gfc_conv_intrinsic_shift(gfc_se * se,gfc_expr * expr,bool right_shift,bool arithmetic)6696 gfc_conv_intrinsic_shift (gfc_se * se, gfc_expr * expr, bool right_shift,
6697 			  bool arithmetic)
6698 {
6699   tree args[2], type, num_bits, cond;
6700   tree bigshift;
6701 
6702   gfc_conv_intrinsic_function_args (se, expr, args, 2);
6703 
6704   args[0] = gfc_evaluate_now (args[0], &se->pre);
6705   args[1] = gfc_evaluate_now (args[1], &se->pre);
6706   type = TREE_TYPE (args[0]);
6707 
6708   if (!arithmetic)
6709     args[0] = fold_convert (unsigned_type_for (type), args[0]);
6710   else
6711     gcc_assert (right_shift);
6712 
6713   se->expr = fold_build2_loc (input_location,
6714 			      right_shift ? RSHIFT_EXPR : LSHIFT_EXPR,
6715 			      TREE_TYPE (args[0]), args[0], args[1]);
6716 
6717   if (!arithmetic)
6718     se->expr = fold_convert (type, se->expr);
6719 
6720   if (!arithmetic)
6721     bigshift = build_int_cst (type, 0);
6722   else
6723     {
6724       tree nonneg = fold_build2_loc (input_location, GE_EXPR,
6725 				     logical_type_node, args[0],
6726 				     build_int_cst (TREE_TYPE (args[0]), 0));
6727       bigshift = fold_build3_loc (input_location, COND_EXPR, type, nonneg,
6728 				  build_int_cst (type, 0),
6729 				  build_int_cst (type, -1));
6730     }
6731 
6732   /* The Fortran standard allows shift widths <= BIT_SIZE(I), whereas
6733      gcc requires a shift width < BIT_SIZE(I), so we have to catch this
6734      special case.  */
6735   num_bits = build_int_cst (TREE_TYPE (args[1]), TYPE_PRECISION (type));
6736 
6737   /* Optionally generate code for runtime argument check.  */
6738   if (gfc_option.rtcheck & GFC_RTCHECK_BITS)
6739     {
6740       tree below = fold_build2_loc (input_location, LT_EXPR,
6741 				    logical_type_node, args[1],
6742 				    build_int_cst (TREE_TYPE (args[1]), 0));
6743       tree above = fold_build2_loc (input_location, GT_EXPR,
6744 				    logical_type_node, args[1], num_bits);
6745       tree scond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
6746 				    logical_type_node, below, above);
6747       size_t len_name = strlen (expr->value.function.isym->name);
6748       char *name = XALLOCAVEC (char, len_name + 1);
6749       for (size_t i = 0; i < len_name; i++)
6750 	name[i] = TOUPPER (expr->value.function.isym->name[i]);
6751       name[len_name] = '\0';
6752       tree iname = gfc_build_addr_expr (pchar_type_node,
6753 					gfc_build_cstring_const (name));
6754       gfc_trans_runtime_check (true, false, scond, &se->pre, &expr->where,
6755 			       "SHIFT argument (%ld) out of range 0:%ld "
6756 			       "in intrinsic %s",
6757 			       fold_convert (long_integer_type_node, args[1]),
6758 			       fold_convert (long_integer_type_node, num_bits),
6759 			       iname);
6760     }
6761 
6762   cond = fold_build2_loc (input_location, GE_EXPR, logical_type_node,
6763 			  args[1], num_bits);
6764 
6765   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond,
6766 			      bigshift, se->expr);
6767 }
6768 
6769 /* ISHFT (I, SHIFT) = (abs (shift) >= BIT_SIZE (i))
6770                         ? 0
6771 	 	        : ((shift >= 0) ? i << shift : i >> -shift)
6772    where all shifts are logical shifts.  */
6773 static void
gfc_conv_intrinsic_ishft(gfc_se * se,gfc_expr * expr)6774 gfc_conv_intrinsic_ishft (gfc_se * se, gfc_expr * expr)
6775 {
6776   tree args[2];
6777   tree type;
6778   tree utype;
6779   tree tmp;
6780   tree width;
6781   tree num_bits;
6782   tree cond;
6783   tree lshift;
6784   tree rshift;
6785 
6786   gfc_conv_intrinsic_function_args (se, expr, args, 2);
6787 
6788   args[0] = gfc_evaluate_now (args[0], &se->pre);
6789   args[1] = gfc_evaluate_now (args[1], &se->pre);
6790 
6791   type = TREE_TYPE (args[0]);
6792   utype = unsigned_type_for (type);
6793 
6794   width = fold_build1_loc (input_location, ABS_EXPR, TREE_TYPE (args[1]),
6795 			   args[1]);
6796 
6797   /* Left shift if positive.  */
6798   lshift = fold_build2_loc (input_location, LSHIFT_EXPR, type, args[0], width);
6799 
6800   /* Right shift if negative.
6801      We convert to an unsigned type because we want a logical shift.
6802      The standard doesn't define the case of shifting negative
6803      numbers, and we try to be compatible with other compilers, most
6804      notably g77, here.  */
6805   rshift = fold_convert (type, fold_build2_loc (input_location, RSHIFT_EXPR,
6806 				    utype, convert (utype, args[0]), width));
6807 
6808   tmp = fold_build2_loc (input_location, GE_EXPR, logical_type_node, args[1],
6809 			 build_int_cst (TREE_TYPE (args[1]), 0));
6810   tmp = fold_build3_loc (input_location, COND_EXPR, type, tmp, lshift, rshift);
6811 
6812   /* The Fortran standard allows shift widths <= BIT_SIZE(I), whereas
6813      gcc requires a shift width < BIT_SIZE(I), so we have to catch this
6814      special case.  */
6815   num_bits = build_int_cst (TREE_TYPE (args[1]), TYPE_PRECISION (type));
6816 
6817   /* Optionally generate code for runtime argument check.  */
6818   if (gfc_option.rtcheck & GFC_RTCHECK_BITS)
6819     {
6820       tree outside = fold_build2_loc (input_location, GT_EXPR,
6821 				    logical_type_node, width, num_bits);
6822       gfc_trans_runtime_check (true, false, outside, &se->pre, &expr->where,
6823 			       "SHIFT argument (%ld) out of range -%ld:%ld "
6824 			       "in intrinsic ISHFT",
6825 			       fold_convert (long_integer_type_node, args[1]),
6826 			       fold_convert (long_integer_type_node, num_bits),
6827 			       fold_convert (long_integer_type_node, num_bits));
6828     }
6829 
6830   cond = fold_build2_loc (input_location, GE_EXPR, logical_type_node, width,
6831 			  num_bits);
6832   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond,
6833 			      build_int_cst (type, 0), tmp);
6834 }
6835 
6836 
6837 /* Circular shift.  AKA rotate or barrel shift.  */
6838 
6839 static void
gfc_conv_intrinsic_ishftc(gfc_se * se,gfc_expr * expr)6840 gfc_conv_intrinsic_ishftc (gfc_se * se, gfc_expr * expr)
6841 {
6842   tree *args;
6843   tree type;
6844   tree tmp;
6845   tree lrot;
6846   tree rrot;
6847   tree zero;
6848   tree nbits;
6849   unsigned int num_args;
6850 
6851   num_args = gfc_intrinsic_argument_list_length (expr);
6852   args = XALLOCAVEC (tree, num_args);
6853 
6854   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
6855 
6856   type = TREE_TYPE (args[0]);
6857   nbits = build_int_cst (long_integer_type_node, TYPE_PRECISION (type));
6858 
6859   if (num_args == 3)
6860     {
6861       /* Use a library function for the 3 parameter version.  */
6862       tree int4type = gfc_get_int_type (4);
6863 
6864       /* We convert the first argument to at least 4 bytes, and
6865 	 convert back afterwards.  This removes the need for library
6866 	 functions for all argument sizes, and function will be
6867 	 aligned to at least 32 bits, so there's no loss.  */
6868       if (expr->ts.kind < 4)
6869 	args[0] = convert (int4type, args[0]);
6870 
6871       /* Convert the SHIFT and SIZE args to INTEGER*4 otherwise we would
6872          need loads of library  functions.  They cannot have values >
6873 	 BIT_SIZE (I) so the conversion is safe.  */
6874       args[1] = convert (int4type, args[1]);
6875       args[2] = convert (int4type, args[2]);
6876 
6877       /* Optionally generate code for runtime argument check.  */
6878       if (gfc_option.rtcheck & GFC_RTCHECK_BITS)
6879 	{
6880 	  tree size = fold_convert (long_integer_type_node, args[2]);
6881 	  tree below = fold_build2_loc (input_location, LE_EXPR,
6882 					logical_type_node, size,
6883 					build_int_cst (TREE_TYPE (args[1]), 0));
6884 	  tree above = fold_build2_loc (input_location, GT_EXPR,
6885 					logical_type_node, size, nbits);
6886 	  tree scond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
6887 					logical_type_node, below, above);
6888 	  gfc_trans_runtime_check (true, false, scond, &se->pre, &expr->where,
6889 				   "SIZE argument (%ld) out of range 1:%ld "
6890 				   "in intrinsic ISHFTC", size, nbits);
6891 	  tree width = fold_convert (long_integer_type_node, args[1]);
6892 	  width = fold_build1_loc (input_location, ABS_EXPR,
6893 				   long_integer_type_node, width);
6894 	  scond = fold_build2_loc (input_location, GT_EXPR,
6895 				   logical_type_node, width, size);
6896 	  gfc_trans_runtime_check (true, false, scond, &se->pre, &expr->where,
6897 				   "SHIFT argument (%ld) out of range -%ld:%ld "
6898 				   "in intrinsic ISHFTC",
6899 				   fold_convert (long_integer_type_node, args[1]),
6900 				   size, size);
6901 	}
6902 
6903       switch (expr->ts.kind)
6904 	{
6905 	case 1:
6906 	case 2:
6907 	case 4:
6908 	  tmp = gfor_fndecl_math_ishftc4;
6909 	  break;
6910 	case 8:
6911 	  tmp = gfor_fndecl_math_ishftc8;
6912 	  break;
6913 	case 16:
6914 	  tmp = gfor_fndecl_math_ishftc16;
6915 	  break;
6916 	default:
6917 	  gcc_unreachable ();
6918 	}
6919       se->expr = build_call_expr_loc (input_location,
6920 				      tmp, 3, args[0], args[1], args[2]);
6921       /* Convert the result back to the original type, if we extended
6922 	 the first argument's width above.  */
6923       if (expr->ts.kind < 4)
6924 	se->expr = convert (type, se->expr);
6925 
6926       return;
6927     }
6928 
6929   /* Evaluate arguments only once.  */
6930   args[0] = gfc_evaluate_now (args[0], &se->pre);
6931   args[1] = gfc_evaluate_now (args[1], &se->pre);
6932 
6933   /* Optionally generate code for runtime argument check.  */
6934   if (gfc_option.rtcheck & GFC_RTCHECK_BITS)
6935     {
6936       tree width = fold_convert (long_integer_type_node, args[1]);
6937       width = fold_build1_loc (input_location, ABS_EXPR,
6938 			       long_integer_type_node, width);
6939       tree outside = fold_build2_loc (input_location, GT_EXPR,
6940 				      logical_type_node, width, nbits);
6941       gfc_trans_runtime_check (true, false, outside, &se->pre, &expr->where,
6942 			       "SHIFT argument (%ld) out of range -%ld:%ld "
6943 			       "in intrinsic ISHFTC",
6944 			       fold_convert (long_integer_type_node, args[1]),
6945 			       nbits, nbits);
6946     }
6947 
6948   /* Rotate left if positive.  */
6949   lrot = fold_build2_loc (input_location, LROTATE_EXPR, type, args[0], args[1]);
6950 
6951   /* Rotate right if negative.  */
6952   tmp = fold_build1_loc (input_location, NEGATE_EXPR, TREE_TYPE (args[1]),
6953 			 args[1]);
6954   rrot = fold_build2_loc (input_location,RROTATE_EXPR, type, args[0], tmp);
6955 
6956   zero = build_int_cst (TREE_TYPE (args[1]), 0);
6957   tmp = fold_build2_loc (input_location, GT_EXPR, logical_type_node, args[1],
6958 			 zero);
6959   rrot = fold_build3_loc (input_location, COND_EXPR, type, tmp, lrot, rrot);
6960 
6961   /* Do nothing if shift == 0.  */
6962   tmp = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, args[1],
6963 			 zero);
6964   se->expr = fold_build3_loc (input_location, COND_EXPR, type, tmp, args[0],
6965 			      rrot);
6966 }
6967 
6968 
6969 /* LEADZ (i) = (i == 0) ? BIT_SIZE (i)
6970 			: __builtin_clz(i) - (BIT_SIZE('int') - BIT_SIZE(i))
6971 
6972    The conditional expression is necessary because the result of LEADZ(0)
6973    is defined, but the result of __builtin_clz(0) is undefined for most
6974    targets.
6975 
6976    For INTEGER kinds smaller than the C 'int' type, we have to subtract the
6977    difference in bit size between the argument of LEADZ and the C int.  */
6978 
6979 static void
gfc_conv_intrinsic_leadz(gfc_se * se,gfc_expr * expr)6980 gfc_conv_intrinsic_leadz (gfc_se * se, gfc_expr * expr)
6981 {
6982   tree arg;
6983   tree arg_type;
6984   tree cond;
6985   tree result_type;
6986   tree leadz;
6987   tree bit_size;
6988   tree tmp;
6989   tree func;
6990   int s, argsize;
6991 
6992   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
6993   argsize = TYPE_PRECISION (TREE_TYPE (arg));
6994 
6995   /* Which variant of __builtin_clz* should we call?  */
6996   if (argsize <= INT_TYPE_SIZE)
6997     {
6998       arg_type = unsigned_type_node;
6999       func = builtin_decl_explicit (BUILT_IN_CLZ);
7000     }
7001   else if (argsize <= LONG_TYPE_SIZE)
7002     {
7003       arg_type = long_unsigned_type_node;
7004       func = builtin_decl_explicit (BUILT_IN_CLZL);
7005     }
7006   else if (argsize <= LONG_LONG_TYPE_SIZE)
7007     {
7008       arg_type = long_long_unsigned_type_node;
7009       func = builtin_decl_explicit (BUILT_IN_CLZLL);
7010     }
7011   else
7012     {
7013       gcc_assert (argsize == 2 * LONG_LONG_TYPE_SIZE);
7014       arg_type = gfc_build_uint_type (argsize);
7015       func = NULL_TREE;
7016     }
7017 
7018   /* Convert the actual argument twice: first, to the unsigned type of the
7019      same size; then, to the proper argument type for the built-in
7020      function.  But the return type is of the default INTEGER kind.  */
7021   arg = fold_convert (gfc_build_uint_type (argsize), arg);
7022   arg = fold_convert (arg_type, arg);
7023   arg = gfc_evaluate_now (arg, &se->pre);
7024   result_type = gfc_get_int_type (gfc_default_integer_kind);
7025 
7026   /* Compute LEADZ for the case i .ne. 0.  */
7027   if (func)
7028     {
7029       s = TYPE_PRECISION (arg_type) - argsize;
7030       tmp = fold_convert (result_type,
7031 			  build_call_expr_loc (input_location, func,
7032 					       1, arg));
7033       leadz = fold_build2_loc (input_location, MINUS_EXPR, result_type,
7034 			       tmp, build_int_cst (result_type, s));
7035     }
7036   else
7037     {
7038       /* We end up here if the argument type is larger than 'long long'.
7039 	 We generate this code:
7040 
7041 	    if (x & (ULL_MAX << ULL_SIZE) != 0)
7042 	      return clzll ((unsigned long long) (x >> ULLSIZE));
7043 	    else
7044 	      return ULL_SIZE + clzll ((unsigned long long) x);
7045 	 where ULL_MAX is the largest value that a ULL_MAX can hold
7046 	 (0xFFFFFFFFFFFFFFFF for a 64-bit long long type), and ULLSIZE
7047 	 is the bit-size of the long long type (64 in this example).  */
7048       tree ullsize, ullmax, tmp1, tmp2, btmp;
7049 
7050       ullsize = build_int_cst (result_type, LONG_LONG_TYPE_SIZE);
7051       ullmax = fold_build1_loc (input_location, BIT_NOT_EXPR,
7052 				long_long_unsigned_type_node,
7053 				build_int_cst (long_long_unsigned_type_node,
7054 					       0));
7055 
7056       cond = fold_build2_loc (input_location, LSHIFT_EXPR, arg_type,
7057 			      fold_convert (arg_type, ullmax), ullsize);
7058       cond = fold_build2_loc (input_location, BIT_AND_EXPR, arg_type,
7059 			      arg, cond);
7060       cond = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
7061 			      cond, build_int_cst (arg_type, 0));
7062 
7063       tmp1 = fold_build2_loc (input_location, RSHIFT_EXPR, arg_type,
7064 			      arg, ullsize);
7065       tmp1 = fold_convert (long_long_unsigned_type_node, tmp1);
7066       btmp = builtin_decl_explicit (BUILT_IN_CLZLL);
7067       tmp1 = fold_convert (result_type,
7068 			   build_call_expr_loc (input_location, btmp, 1, tmp1));
7069 
7070       tmp2 = fold_convert (long_long_unsigned_type_node, arg);
7071       btmp = builtin_decl_explicit (BUILT_IN_CLZLL);
7072       tmp2 = fold_convert (result_type,
7073 			   build_call_expr_loc (input_location, btmp, 1, tmp2));
7074       tmp2 = fold_build2_loc (input_location, PLUS_EXPR, result_type,
7075 			      tmp2, ullsize);
7076 
7077       leadz = fold_build3_loc (input_location, COND_EXPR, result_type,
7078 			       cond, tmp1, tmp2);
7079     }
7080 
7081   /* Build BIT_SIZE.  */
7082   bit_size = build_int_cst (result_type, argsize);
7083 
7084   cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
7085 			  arg, build_int_cst (arg_type, 0));
7086   se->expr = fold_build3_loc (input_location, COND_EXPR, result_type, cond,
7087 			      bit_size, leadz);
7088 }
7089 
7090 
7091 /* TRAILZ(i) = (i == 0) ? BIT_SIZE (i) : __builtin_ctz(i)
7092 
7093    The conditional expression is necessary because the result of TRAILZ(0)
7094    is defined, but the result of __builtin_ctz(0) is undefined for most
7095    targets.  */
7096 
7097 static void
gfc_conv_intrinsic_trailz(gfc_se * se,gfc_expr * expr)7098 gfc_conv_intrinsic_trailz (gfc_se * se, gfc_expr *expr)
7099 {
7100   tree arg;
7101   tree arg_type;
7102   tree cond;
7103   tree result_type;
7104   tree trailz;
7105   tree bit_size;
7106   tree func;
7107   int argsize;
7108 
7109   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
7110   argsize = TYPE_PRECISION (TREE_TYPE (arg));
7111 
7112   /* Which variant of __builtin_ctz* should we call?  */
7113   if (argsize <= INT_TYPE_SIZE)
7114     {
7115       arg_type = unsigned_type_node;
7116       func = builtin_decl_explicit (BUILT_IN_CTZ);
7117     }
7118   else if (argsize <= LONG_TYPE_SIZE)
7119     {
7120       arg_type = long_unsigned_type_node;
7121       func = builtin_decl_explicit (BUILT_IN_CTZL);
7122     }
7123   else if (argsize <= LONG_LONG_TYPE_SIZE)
7124     {
7125       arg_type = long_long_unsigned_type_node;
7126       func = builtin_decl_explicit (BUILT_IN_CTZLL);
7127     }
7128   else
7129     {
7130       gcc_assert (argsize == 2 * LONG_LONG_TYPE_SIZE);
7131       arg_type = gfc_build_uint_type (argsize);
7132       func = NULL_TREE;
7133     }
7134 
7135   /* Convert the actual argument twice: first, to the unsigned type of the
7136      same size; then, to the proper argument type for the built-in
7137      function.  But the return type is of the default INTEGER kind.  */
7138   arg = fold_convert (gfc_build_uint_type (argsize), arg);
7139   arg = fold_convert (arg_type, arg);
7140   arg = gfc_evaluate_now (arg, &se->pre);
7141   result_type = gfc_get_int_type (gfc_default_integer_kind);
7142 
7143   /* Compute TRAILZ for the case i .ne. 0.  */
7144   if (func)
7145     trailz = fold_convert (result_type, build_call_expr_loc (input_location,
7146 							     func, 1, arg));
7147   else
7148     {
7149       /* We end up here if the argument type is larger than 'long long'.
7150 	 We generate this code:
7151 
7152 	    if ((x & ULL_MAX) == 0)
7153 	      return ULL_SIZE + ctzll ((unsigned long long) (x >> ULLSIZE));
7154 	    else
7155 	      return ctzll ((unsigned long long) x);
7156 
7157 	 where ULL_MAX is the largest value that a ULL_MAX can hold
7158 	 (0xFFFFFFFFFFFFFFFF for a 64-bit long long type), and ULLSIZE
7159 	 is the bit-size of the long long type (64 in this example).  */
7160       tree ullsize, ullmax, tmp1, tmp2, btmp;
7161 
7162       ullsize = build_int_cst (result_type, LONG_LONG_TYPE_SIZE);
7163       ullmax = fold_build1_loc (input_location, BIT_NOT_EXPR,
7164 				long_long_unsigned_type_node,
7165 				build_int_cst (long_long_unsigned_type_node, 0));
7166 
7167       cond = fold_build2_loc (input_location, BIT_AND_EXPR, arg_type, arg,
7168 			      fold_convert (arg_type, ullmax));
7169       cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, cond,
7170 			      build_int_cst (arg_type, 0));
7171 
7172       tmp1 = fold_build2_loc (input_location, RSHIFT_EXPR, arg_type,
7173 			      arg, ullsize);
7174       tmp1 = fold_convert (long_long_unsigned_type_node, tmp1);
7175       btmp = builtin_decl_explicit (BUILT_IN_CTZLL);
7176       tmp1 = fold_convert (result_type,
7177 			   build_call_expr_loc (input_location, btmp, 1, tmp1));
7178       tmp1 = fold_build2_loc (input_location, PLUS_EXPR, result_type,
7179 			      tmp1, ullsize);
7180 
7181       tmp2 = fold_convert (long_long_unsigned_type_node, arg);
7182       btmp = builtin_decl_explicit (BUILT_IN_CTZLL);
7183       tmp2 = fold_convert (result_type,
7184 			   build_call_expr_loc (input_location, btmp, 1, tmp2));
7185 
7186       trailz = fold_build3_loc (input_location, COND_EXPR, result_type,
7187 				cond, tmp1, tmp2);
7188     }
7189 
7190   /* Build BIT_SIZE.  */
7191   bit_size = build_int_cst (result_type, argsize);
7192 
7193   cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
7194 			  arg, build_int_cst (arg_type, 0));
7195   se->expr = fold_build3_loc (input_location, COND_EXPR, result_type, cond,
7196 			      bit_size, trailz);
7197 }
7198 
7199 /* Using __builtin_popcount for POPCNT and __builtin_parity for POPPAR;
7200    for types larger than "long long", we call the long long built-in for
7201    the lower and higher bits and combine the result.  */
7202 
7203 static void
gfc_conv_intrinsic_popcnt_poppar(gfc_se * se,gfc_expr * expr,int parity)7204 gfc_conv_intrinsic_popcnt_poppar (gfc_se * se, gfc_expr *expr, int parity)
7205 {
7206   tree arg;
7207   tree arg_type;
7208   tree result_type;
7209   tree func;
7210   int argsize;
7211 
7212   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
7213   argsize = TYPE_PRECISION (TREE_TYPE (arg));
7214   result_type = gfc_get_int_type (gfc_default_integer_kind);
7215 
7216   /* Which variant of the builtin should we call?  */
7217   if (argsize <= INT_TYPE_SIZE)
7218     {
7219       arg_type = unsigned_type_node;
7220       func = builtin_decl_explicit (parity
7221 				    ? BUILT_IN_PARITY
7222 				    : BUILT_IN_POPCOUNT);
7223     }
7224   else if (argsize <= LONG_TYPE_SIZE)
7225     {
7226       arg_type = long_unsigned_type_node;
7227       func = builtin_decl_explicit (parity
7228 				    ? BUILT_IN_PARITYL
7229 				    : BUILT_IN_POPCOUNTL);
7230     }
7231   else if (argsize <= LONG_LONG_TYPE_SIZE)
7232     {
7233       arg_type = long_long_unsigned_type_node;
7234       func = builtin_decl_explicit (parity
7235 				    ? BUILT_IN_PARITYLL
7236 				    : BUILT_IN_POPCOUNTLL);
7237     }
7238   else
7239     {
7240       /* Our argument type is larger than 'long long', which mean none
7241 	 of the POPCOUNT builtins covers it.  We thus call the 'long long'
7242 	 variant multiple times, and add the results.  */
7243       tree utype, arg2, call1, call2;
7244 
7245       /* For now, we only cover the case where argsize is twice as large
7246 	 as 'long long'.  */
7247       gcc_assert (argsize == 2 * LONG_LONG_TYPE_SIZE);
7248 
7249       func = builtin_decl_explicit (parity
7250 				    ? BUILT_IN_PARITYLL
7251 				    : BUILT_IN_POPCOUNTLL);
7252 
7253       /* Convert it to an integer, and store into a variable.  */
7254       utype = gfc_build_uint_type (argsize);
7255       arg = fold_convert (utype, arg);
7256       arg = gfc_evaluate_now (arg, &se->pre);
7257 
7258       /* Call the builtin twice.  */
7259       call1 = build_call_expr_loc (input_location, func, 1,
7260 				   fold_convert (long_long_unsigned_type_node,
7261 						 arg));
7262 
7263       arg2 = fold_build2_loc (input_location, RSHIFT_EXPR, utype, arg,
7264 			      build_int_cst (utype, LONG_LONG_TYPE_SIZE));
7265       call2 = build_call_expr_loc (input_location, func, 1,
7266 				   fold_convert (long_long_unsigned_type_node,
7267 						 arg2));
7268 
7269       /* Combine the results.  */
7270       if (parity)
7271 	se->expr = fold_build2_loc (input_location, BIT_XOR_EXPR,
7272 				    integer_type_node, call1, call2);
7273       else
7274 	se->expr = fold_build2_loc (input_location, PLUS_EXPR,
7275 				    integer_type_node, call1, call2);
7276 
7277       se->expr = convert (result_type, se->expr);
7278       return;
7279     }
7280 
7281   /* Convert the actual argument twice: first, to the unsigned type of the
7282      same size; then, to the proper argument type for the built-in
7283      function.  */
7284   arg = fold_convert (gfc_build_uint_type (argsize), arg);
7285   arg = fold_convert (arg_type, arg);
7286 
7287   se->expr = fold_convert (result_type,
7288 			   build_call_expr_loc (input_location, func, 1, arg));
7289 }
7290 
7291 
7292 /* Process an intrinsic with unspecified argument-types that has an optional
7293    argument (which could be of type character), e.g. EOSHIFT.  For those, we
7294    need to append the string length of the optional argument if it is not
7295    present and the type is really character.
7296    primary specifies the position (starting at 1) of the non-optional argument
7297    specifying the type and optional gives the position of the optional
7298    argument in the arglist.  */
7299 
7300 static void
conv_generic_with_optional_char_arg(gfc_se * se,gfc_expr * expr,unsigned primary,unsigned optional)7301 conv_generic_with_optional_char_arg (gfc_se* se, gfc_expr* expr,
7302 				     unsigned primary, unsigned optional)
7303 {
7304   gfc_actual_arglist* prim_arg;
7305   gfc_actual_arglist* opt_arg;
7306   unsigned cur_pos;
7307   gfc_actual_arglist* arg;
7308   gfc_symbol* sym;
7309   vec<tree, va_gc> *append_args;
7310 
7311   /* Find the two arguments given as position.  */
7312   cur_pos = 0;
7313   prim_arg = NULL;
7314   opt_arg = NULL;
7315   for (arg = expr->value.function.actual; arg; arg = arg->next)
7316     {
7317       ++cur_pos;
7318 
7319       if (cur_pos == primary)
7320 	prim_arg = arg;
7321       if (cur_pos == optional)
7322 	opt_arg = arg;
7323 
7324       if (cur_pos >= primary && cur_pos >= optional)
7325 	break;
7326     }
7327   gcc_assert (prim_arg);
7328   gcc_assert (prim_arg->expr);
7329   gcc_assert (opt_arg);
7330 
7331   /* If we do have type CHARACTER and the optional argument is really absent,
7332      append a dummy 0 as string length.  */
7333   append_args = NULL;
7334   if (prim_arg->expr->ts.type == BT_CHARACTER && !opt_arg->expr)
7335     {
7336       tree dummy;
7337 
7338       dummy = build_int_cst (gfc_charlen_type_node, 0);
7339       vec_alloc (append_args, 1);
7340       append_args->quick_push (dummy);
7341     }
7342 
7343   /* Build the call itself.  */
7344   gcc_assert (!se->ignore_optional);
7345   sym = gfc_get_symbol_for_expr (expr, false);
7346   gfc_conv_procedure_call (se, sym, expr->value.function.actual, expr,
7347 			  append_args);
7348   gfc_free_symbol (sym);
7349 }
7350 
7351 /* The length of a character string.  */
7352 static void
gfc_conv_intrinsic_len(gfc_se * se,gfc_expr * expr)7353 gfc_conv_intrinsic_len (gfc_se * se, gfc_expr * expr)
7354 {
7355   tree len;
7356   tree type;
7357   tree decl;
7358   gfc_symbol *sym;
7359   gfc_se argse;
7360   gfc_expr *arg;
7361 
7362   gcc_assert (!se->ss);
7363 
7364   arg = expr->value.function.actual->expr;
7365 
7366   type = gfc_typenode_for_spec (&expr->ts);
7367   switch (arg->expr_type)
7368     {
7369     case EXPR_CONSTANT:
7370       len = build_int_cst (gfc_charlen_type_node, arg->value.character.length);
7371       break;
7372 
7373     case EXPR_ARRAY:
7374       /* Obtain the string length from the function used by
7375          trans-array.cc(gfc_trans_array_constructor).  */
7376       len = NULL_TREE;
7377       get_array_ctor_strlen (&se->pre, arg->value.constructor, &len);
7378       break;
7379 
7380     case EXPR_VARIABLE:
7381       if (arg->ref == NULL
7382 	    || (arg->ref->next == NULL && arg->ref->type == REF_ARRAY))
7383 	{
7384 	  /* This doesn't catch all cases.
7385 	     See http://gcc.gnu.org/ml/fortran/2004-06/msg00165.html
7386 	     and the surrounding thread.  */
7387 	  sym = arg->symtree->n.sym;
7388 	  decl = gfc_get_symbol_decl (sym);
7389 	  if (decl == current_function_decl && sym->attr.function
7390 		&& (sym->result == sym))
7391 	    decl = gfc_get_fake_result_decl (sym, 0);
7392 
7393 	  len = sym->ts.u.cl->backend_decl;
7394 	  gcc_assert (len);
7395 	  break;
7396 	}
7397 
7398       /* Fall through.  */
7399 
7400     default:
7401       gfc_init_se (&argse, se);
7402       if (arg->rank == 0)
7403 	gfc_conv_expr (&argse, arg);
7404       else
7405 	gfc_conv_expr_descriptor (&argse, arg);
7406       gfc_add_block_to_block (&se->pre, &argse.pre);
7407       gfc_add_block_to_block (&se->post, &argse.post);
7408       len = argse.string_length;
7409       break;
7410     }
7411   se->expr = convert (type, len);
7412 }
7413 
7414 /* The length of a character string not including trailing blanks.  */
7415 static void
gfc_conv_intrinsic_len_trim(gfc_se * se,gfc_expr * expr)7416 gfc_conv_intrinsic_len_trim (gfc_se * se, gfc_expr * expr)
7417 {
7418   int kind = expr->value.function.actual->expr->ts.kind;
7419   tree args[2], type, fndecl;
7420 
7421   gfc_conv_intrinsic_function_args (se, expr, args, 2);
7422   type = gfc_typenode_for_spec (&expr->ts);
7423 
7424   if (kind == 1)
7425     fndecl = gfor_fndecl_string_len_trim;
7426   else if (kind == 4)
7427     fndecl = gfor_fndecl_string_len_trim_char4;
7428   else
7429     gcc_unreachable ();
7430 
7431   se->expr = build_call_expr_loc (input_location,
7432 			      fndecl, 2, args[0], args[1]);
7433   se->expr = convert (type, se->expr);
7434 }
7435 
7436 
7437 /* Returns the starting position of a substring within a string.  */
7438 
7439 static void
gfc_conv_intrinsic_index_scan_verify(gfc_se * se,gfc_expr * expr,tree function)7440 gfc_conv_intrinsic_index_scan_verify (gfc_se * se, gfc_expr * expr,
7441 				      tree function)
7442 {
7443   tree logical4_type_node = gfc_get_logical_type (4);
7444   tree type;
7445   tree fndecl;
7446   tree *args;
7447   unsigned int num_args;
7448 
7449   args = XALLOCAVEC (tree, 5);
7450 
7451   /* Get number of arguments; characters count double due to the
7452      string length argument. Kind= is not passed to the library
7453      and thus ignored.  */
7454   if (expr->value.function.actual->next->next->expr == NULL)
7455     num_args = 4;
7456   else
7457     num_args = 5;
7458 
7459   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
7460   type = gfc_typenode_for_spec (&expr->ts);
7461 
7462   if (num_args == 4)
7463     args[4] = build_int_cst (logical4_type_node, 0);
7464   else
7465     args[4] = convert (logical4_type_node, args[4]);
7466 
7467   fndecl = build_addr (function);
7468   se->expr = build_call_array_loc (input_location,
7469 			       TREE_TYPE (TREE_TYPE (function)), fndecl,
7470 			       5, args);
7471   se->expr = convert (type, se->expr);
7472 
7473 }
7474 
7475 /* The ascii value for a single character.  */
7476 static void
gfc_conv_intrinsic_ichar(gfc_se * se,gfc_expr * expr)7477 gfc_conv_intrinsic_ichar (gfc_se * se, gfc_expr * expr)
7478 {
7479   tree args[3], type, pchartype;
7480   int nargs;
7481 
7482   nargs = gfc_intrinsic_argument_list_length (expr);
7483   gfc_conv_intrinsic_function_args (se, expr, args, nargs);
7484   gcc_assert (POINTER_TYPE_P (TREE_TYPE (args[1])));
7485   pchartype = gfc_get_pchar_type (expr->value.function.actual->expr->ts.kind);
7486   args[1] = fold_build1_loc (input_location, NOP_EXPR, pchartype, args[1]);
7487   type = gfc_typenode_for_spec (&expr->ts);
7488 
7489   se->expr = build_fold_indirect_ref_loc (input_location,
7490 				      args[1]);
7491   se->expr = convert (type, se->expr);
7492 }
7493 
7494 
7495 /* Intrinsic ISNAN calls __builtin_isnan.  */
7496 
7497 static void
gfc_conv_intrinsic_isnan(gfc_se * se,gfc_expr * expr)7498 gfc_conv_intrinsic_isnan (gfc_se * se, gfc_expr * expr)
7499 {
7500   tree arg;
7501 
7502   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
7503   se->expr = build_call_expr_loc (input_location,
7504 				  builtin_decl_explicit (BUILT_IN_ISNAN),
7505 				  1, arg);
7506   STRIP_TYPE_NOPS (se->expr);
7507   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), se->expr);
7508 }
7509 
7510 
7511 /* Intrinsics IS_IOSTAT_END and IS_IOSTAT_EOR just need to compare
7512    their argument against a constant integer value.  */
7513 
7514 static void
gfc_conv_has_intvalue(gfc_se * se,gfc_expr * expr,const int value)7515 gfc_conv_has_intvalue (gfc_se * se, gfc_expr * expr, const int value)
7516 {
7517   tree arg;
7518 
7519   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
7520   se->expr = fold_build2_loc (input_location, EQ_EXPR,
7521 			      gfc_typenode_for_spec (&expr->ts),
7522 			      arg, build_int_cst (TREE_TYPE (arg), value));
7523 }
7524 
7525 
7526 
7527 /* MERGE (tsource, fsource, mask) = mask ? tsource : fsource.  */
7528 
7529 static void
gfc_conv_intrinsic_merge(gfc_se * se,gfc_expr * expr)7530 gfc_conv_intrinsic_merge (gfc_se * se, gfc_expr * expr)
7531 {
7532   tree tsource;
7533   tree fsource;
7534   tree mask;
7535   tree type;
7536   tree len, len2;
7537   tree *args;
7538   unsigned int num_args;
7539 
7540   num_args = gfc_intrinsic_argument_list_length (expr);
7541   args = XALLOCAVEC (tree, num_args);
7542 
7543   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
7544   if (expr->ts.type != BT_CHARACTER)
7545     {
7546       tsource = args[0];
7547       fsource = args[1];
7548       mask = args[2];
7549     }
7550   else
7551     {
7552       /* We do the same as in the non-character case, but the argument
7553 	 list is different because of the string length arguments. We
7554 	 also have to set the string length for the result.  */
7555       len = args[0];
7556       tsource = args[1];
7557       len2 = args[2];
7558       fsource = args[3];
7559       mask = args[4];
7560 
7561       gfc_trans_same_strlen_check ("MERGE intrinsic", &expr->where, len, len2,
7562 				   &se->pre);
7563       se->string_length = len;
7564     }
7565   type = TREE_TYPE (tsource);
7566   se->expr = fold_build3_loc (input_location, COND_EXPR, type, mask, tsource,
7567 			      fold_convert (type, fsource));
7568 }
7569 
7570 
7571 /* MERGE_BITS (I, J, MASK) = (I & MASK) | (I & (~MASK)).  */
7572 
7573 static void
gfc_conv_intrinsic_merge_bits(gfc_se * se,gfc_expr * expr)7574 gfc_conv_intrinsic_merge_bits (gfc_se * se, gfc_expr * expr)
7575 {
7576   tree args[3], mask, type;
7577 
7578   gfc_conv_intrinsic_function_args (se, expr, args, 3);
7579   mask = gfc_evaluate_now (args[2], &se->pre);
7580 
7581   type = TREE_TYPE (args[0]);
7582   gcc_assert (TREE_TYPE (args[1]) == type);
7583   gcc_assert (TREE_TYPE (mask) == type);
7584 
7585   args[0] = fold_build2_loc (input_location, BIT_AND_EXPR, type, args[0], mask);
7586   args[1] = fold_build2_loc (input_location, BIT_AND_EXPR, type, args[1],
7587 			     fold_build1_loc (input_location, BIT_NOT_EXPR,
7588 					      type, mask));
7589   se->expr = fold_build2_loc (input_location, BIT_IOR_EXPR, type,
7590 			      args[0], args[1]);
7591 }
7592 
7593 
7594 /* MASKL(n)  =  n == 0 ? 0 : (~0) << (BIT_SIZE - n)
7595    MASKR(n)  =  n == BIT_SIZE ? ~0 : ~((~0) << n)  */
7596 
7597 static void
gfc_conv_intrinsic_mask(gfc_se * se,gfc_expr * expr,int left)7598 gfc_conv_intrinsic_mask (gfc_se * se, gfc_expr * expr, int left)
7599 {
7600   tree arg, allones, type, utype, res, cond, bitsize;
7601   int i;
7602 
7603   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
7604   arg = gfc_evaluate_now (arg, &se->pre);
7605 
7606   type = gfc_get_int_type (expr->ts.kind);
7607   utype = unsigned_type_for (type);
7608 
7609   i = gfc_validate_kind (BT_INTEGER, expr->ts.kind, false);
7610   bitsize = build_int_cst (TREE_TYPE (arg), gfc_integer_kinds[i].bit_size);
7611 
7612   allones = fold_build1_loc (input_location, BIT_NOT_EXPR, utype,
7613 			     build_int_cst (utype, 0));
7614 
7615   if (left)
7616     {
7617       /* Left-justified mask.  */
7618       res = fold_build2_loc (input_location, MINUS_EXPR, TREE_TYPE (arg),
7619 			     bitsize, arg);
7620       res = fold_build2_loc (input_location, LSHIFT_EXPR, utype, allones,
7621 			     fold_convert (utype, res));
7622 
7623       /* Special case arg == 0, because SHIFT_EXPR wants a shift strictly
7624 	 smaller than type width.  */
7625       cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, arg,
7626 			      build_int_cst (TREE_TYPE (arg), 0));
7627       res = fold_build3_loc (input_location, COND_EXPR, utype, cond,
7628 			     build_int_cst (utype, 0), res);
7629     }
7630   else
7631     {
7632       /* Right-justified mask.  */
7633       res = fold_build2_loc (input_location, LSHIFT_EXPR, utype, allones,
7634 			     fold_convert (utype, arg));
7635       res = fold_build1_loc (input_location, BIT_NOT_EXPR, utype, res);
7636 
7637       /* Special case agr == bit_size, because SHIFT_EXPR wants a shift
7638 	 strictly smaller than type width.  */
7639       cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
7640 			      arg, bitsize);
7641       res = fold_build3_loc (input_location, COND_EXPR, utype,
7642 			     cond, allones, res);
7643     }
7644 
7645   se->expr = fold_convert (type, res);
7646 }
7647 
7648 
7649 /* FRACTION (s) is translated into:
7650      isfinite (s) ? frexp (s, &dummy_int) : NaN  */
7651 static void
gfc_conv_intrinsic_fraction(gfc_se * se,gfc_expr * expr)7652 gfc_conv_intrinsic_fraction (gfc_se * se, gfc_expr * expr)
7653 {
7654   tree arg, type, tmp, res, frexp, cond;
7655 
7656   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
7657 
7658   type = gfc_typenode_for_spec (&expr->ts);
7659   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
7660   arg = gfc_evaluate_now (arg, &se->pre);
7661 
7662   cond = build_call_expr_loc (input_location,
7663 			      builtin_decl_explicit (BUILT_IN_ISFINITE),
7664 			      1, arg);
7665 
7666   tmp = gfc_create_var (integer_type_node, NULL);
7667   res = build_call_expr_loc (input_location, frexp, 2,
7668 			     fold_convert (type, arg),
7669 			     gfc_build_addr_expr (NULL_TREE, tmp));
7670   res = fold_convert (type, res);
7671 
7672   se->expr = fold_build3_loc (input_location, COND_EXPR, type,
7673 			      cond, res, gfc_build_nan (type, ""));
7674 }
7675 
7676 
7677 /* NEAREST (s, dir) is translated into
7678      tmp = copysign (HUGE_VAL, dir);
7679      return nextafter (s, tmp);
7680  */
7681 static void
gfc_conv_intrinsic_nearest(gfc_se * se,gfc_expr * expr)7682 gfc_conv_intrinsic_nearest (gfc_se * se, gfc_expr * expr)
7683 {
7684   tree args[2], type, tmp, nextafter, copysign, huge_val;
7685 
7686   nextafter = gfc_builtin_decl_for_float_kind (BUILT_IN_NEXTAFTER, expr->ts.kind);
7687   copysign = gfc_builtin_decl_for_float_kind (BUILT_IN_COPYSIGN, expr->ts.kind);
7688 
7689   type = gfc_typenode_for_spec (&expr->ts);
7690   gfc_conv_intrinsic_function_args (se, expr, args, 2);
7691 
7692   huge_val = gfc_build_inf_or_huge (type, expr->ts.kind);
7693   tmp = build_call_expr_loc (input_location, copysign, 2, huge_val,
7694 			     fold_convert (type, args[1]));
7695   se->expr = build_call_expr_loc (input_location, nextafter, 2,
7696 				  fold_convert (type, args[0]), tmp);
7697   se->expr = fold_convert (type, se->expr);
7698 }
7699 
7700 
7701 /* SPACING (s) is translated into
7702     int e;
7703     if (!isfinite (s))
7704       res = NaN;
7705     else if (s == 0)
7706       res = tiny;
7707     else
7708     {
7709       frexp (s, &e);
7710       e = e - prec;
7711       e = MAX_EXPR (e, emin);
7712       res = scalbn (1., e);
7713     }
7714     return res;
7715 
7716  where prec is the precision of s, gfc_real_kinds[k].digits,
7717        emin is min_exponent - 1, gfc_real_kinds[k].min_exponent - 1,
7718    and tiny is tiny(s), gfc_real_kinds[k].tiny.  */
7719 
7720 static void
gfc_conv_intrinsic_spacing(gfc_se * se,gfc_expr * expr)7721 gfc_conv_intrinsic_spacing (gfc_se * se, gfc_expr * expr)
7722 {
7723   tree arg, type, prec, emin, tiny, res, e;
7724   tree cond, nan, tmp, frexp, scalbn;
7725   int k;
7726   stmtblock_t block;
7727 
7728   k = gfc_validate_kind (BT_REAL, expr->ts.kind, false);
7729   prec = build_int_cst (integer_type_node, gfc_real_kinds[k].digits);
7730   emin = build_int_cst (integer_type_node, gfc_real_kinds[k].min_exponent - 1);
7731   tiny = gfc_conv_mpfr_to_tree (gfc_real_kinds[k].tiny, expr->ts.kind, 0);
7732 
7733   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
7734   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
7735 
7736   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
7737   arg = gfc_evaluate_now (arg, &se->pre);
7738 
7739   type = gfc_typenode_for_spec (&expr->ts);
7740   e = gfc_create_var (integer_type_node, NULL);
7741   res = gfc_create_var (type, NULL);
7742 
7743 
7744   /* Build the block for s /= 0.  */
7745   gfc_start_block (&block);
7746   tmp = build_call_expr_loc (input_location, frexp, 2, arg,
7747 			     gfc_build_addr_expr (NULL_TREE, e));
7748   gfc_add_expr_to_block (&block, tmp);
7749 
7750   tmp = fold_build2_loc (input_location, MINUS_EXPR, integer_type_node, e,
7751 			 prec);
7752   gfc_add_modify (&block, e, fold_build2_loc (input_location, MAX_EXPR,
7753 					      integer_type_node, tmp, emin));
7754 
7755   tmp = build_call_expr_loc (input_location, scalbn, 2,
7756 			 build_real_from_int_cst (type, integer_one_node), e);
7757   gfc_add_modify (&block, res, tmp);
7758 
7759   /* Finish by building the IF statement for value zero.  */
7760   cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, arg,
7761 			  build_real_from_int_cst (type, integer_zero_node));
7762   tmp = build3_v (COND_EXPR, cond, build2_v (MODIFY_EXPR, res, tiny),
7763 		  gfc_finish_block (&block));
7764 
7765   /* And deal with infinities and NaNs.  */
7766   cond = build_call_expr_loc (input_location,
7767 			      builtin_decl_explicit (BUILT_IN_ISFINITE),
7768 			      1, arg);
7769   nan = gfc_build_nan (type, "");
7770   tmp = build3_v (COND_EXPR, cond, tmp, build2_v (MODIFY_EXPR, res, nan));
7771 
7772   gfc_add_expr_to_block (&se->pre, tmp);
7773   se->expr = res;
7774 }
7775 
7776 
7777 /* RRSPACING (s) is translated into
7778       int e;
7779       real x;
7780       x = fabs (s);
7781       if (isfinite (x))
7782       {
7783 	if (x != 0)
7784 	{
7785 	  frexp (s, &e);
7786 	  x = scalbn (x, precision - e);
7787 	}
7788       }
7789       else
7790         x = NaN;
7791       return x;
7792 
7793  where precision is gfc_real_kinds[k].digits.  */
7794 
7795 static void
gfc_conv_intrinsic_rrspacing(gfc_se * se,gfc_expr * expr)7796 gfc_conv_intrinsic_rrspacing (gfc_se * se, gfc_expr * expr)
7797 {
7798   tree arg, type, e, x, cond, nan, stmt, tmp, frexp, scalbn, fabs;
7799   int prec, k;
7800   stmtblock_t block;
7801 
7802   k = gfc_validate_kind (BT_REAL, expr->ts.kind, false);
7803   prec = gfc_real_kinds[k].digits;
7804 
7805   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
7806   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
7807   fabs = gfc_builtin_decl_for_float_kind (BUILT_IN_FABS, expr->ts.kind);
7808 
7809   type = gfc_typenode_for_spec (&expr->ts);
7810   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
7811   arg = gfc_evaluate_now (arg, &se->pre);
7812 
7813   e = gfc_create_var (integer_type_node, NULL);
7814   x = gfc_create_var (type, NULL);
7815   gfc_add_modify (&se->pre, x,
7816 		  build_call_expr_loc (input_location, fabs, 1, arg));
7817 
7818 
7819   gfc_start_block (&block);
7820   tmp = build_call_expr_loc (input_location, frexp, 2, arg,
7821 			     gfc_build_addr_expr (NULL_TREE, e));
7822   gfc_add_expr_to_block (&block, tmp);
7823 
7824   tmp = fold_build2_loc (input_location, MINUS_EXPR, integer_type_node,
7825 			 build_int_cst (integer_type_node, prec), e);
7826   tmp = build_call_expr_loc (input_location, scalbn, 2, x, tmp);
7827   gfc_add_modify (&block, x, tmp);
7828   stmt = gfc_finish_block (&block);
7829 
7830   /* if (x != 0) */
7831   cond = fold_build2_loc (input_location, NE_EXPR, logical_type_node, x,
7832 			  build_real_from_int_cst (type, integer_zero_node));
7833   tmp = build3_v (COND_EXPR, cond, stmt, build_empty_stmt (input_location));
7834 
7835   /* And deal with infinities and NaNs.  */
7836   cond = build_call_expr_loc (input_location,
7837 			      builtin_decl_explicit (BUILT_IN_ISFINITE),
7838 			      1, x);
7839   nan = gfc_build_nan (type, "");
7840   tmp = build3_v (COND_EXPR, cond, tmp, build2_v (MODIFY_EXPR, x, nan));
7841 
7842   gfc_add_expr_to_block (&se->pre, tmp);
7843   se->expr = fold_convert (type, x);
7844 }
7845 
7846 
7847 /* SCALE (s, i) is translated into scalbn (s, i).  */
7848 static void
gfc_conv_intrinsic_scale(gfc_se * se,gfc_expr * expr)7849 gfc_conv_intrinsic_scale (gfc_se * se, gfc_expr * expr)
7850 {
7851   tree args[2], type, scalbn;
7852 
7853   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
7854 
7855   type = gfc_typenode_for_spec (&expr->ts);
7856   gfc_conv_intrinsic_function_args (se, expr, args, 2);
7857   se->expr = build_call_expr_loc (input_location, scalbn, 2,
7858 				  fold_convert (type, args[0]),
7859 				  fold_convert (integer_type_node, args[1]));
7860   se->expr = fold_convert (type, se->expr);
7861 }
7862 
7863 
7864 /* SET_EXPONENT (s, i) is translated into
7865    isfinite(s) ? scalbn (frexp (s, &dummy_int), i) : NaN  */
7866 static void
gfc_conv_intrinsic_set_exponent(gfc_se * se,gfc_expr * expr)7867 gfc_conv_intrinsic_set_exponent (gfc_se * se, gfc_expr * expr)
7868 {
7869   tree args[2], type, tmp, frexp, scalbn, cond, nan, res;
7870 
7871   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
7872   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
7873 
7874   type = gfc_typenode_for_spec (&expr->ts);
7875   gfc_conv_intrinsic_function_args (se, expr, args, 2);
7876   args[0] = gfc_evaluate_now (args[0], &se->pre);
7877 
7878   tmp = gfc_create_var (integer_type_node, NULL);
7879   tmp = build_call_expr_loc (input_location, frexp, 2,
7880 			     fold_convert (type, args[0]),
7881 			     gfc_build_addr_expr (NULL_TREE, tmp));
7882   res = build_call_expr_loc (input_location, scalbn, 2, tmp,
7883 			     fold_convert (integer_type_node, args[1]));
7884   res = fold_convert (type, res);
7885 
7886   /* Call to isfinite */
7887   cond = build_call_expr_loc (input_location,
7888 			      builtin_decl_explicit (BUILT_IN_ISFINITE),
7889 			      1, args[0]);
7890   nan = gfc_build_nan (type, "");
7891 
7892   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond,
7893 			      res, nan);
7894 }
7895 
7896 
7897 static void
gfc_conv_intrinsic_size(gfc_se * se,gfc_expr * expr)7898 gfc_conv_intrinsic_size (gfc_se * se, gfc_expr * expr)
7899 {
7900   gfc_actual_arglist *actual;
7901   tree arg1;
7902   tree type;
7903   tree size;
7904   gfc_se argse;
7905   gfc_expr *e;
7906   gfc_symbol *sym = NULL;
7907 
7908   gfc_init_se (&argse, NULL);
7909   actual = expr->value.function.actual;
7910 
7911   if (actual->expr->ts.type == BT_CLASS)
7912     gfc_add_class_array_ref (actual->expr);
7913 
7914   e = actual->expr;
7915 
7916   /* These are emerging from the interface mapping, when a class valued
7917      function appears as the rhs in a realloc on assign statement, where
7918      the size of the result is that of one of the actual arguments.  */
7919   if (e->expr_type == EXPR_VARIABLE
7920       && e->symtree->n.sym->ns == NULL /* This is distinctive!  */
7921       && e->symtree->n.sym->ts.type == BT_CLASS
7922       && e->ref && e->ref->type == REF_COMPONENT
7923       && strcmp (e->ref->u.c.component->name, "_data") == 0)
7924     sym = e->symtree->n.sym;
7925 
7926   if ((gfc_option.rtcheck & GFC_RTCHECK_POINTER)
7927       && e
7928       && (e->expr_type == EXPR_VARIABLE || e->expr_type == EXPR_FUNCTION))
7929     {
7930       symbol_attribute attr;
7931       char *msg;
7932       tree temp;
7933       tree cond;
7934 
7935       if (e->symtree->n.sym && IS_CLASS_ARRAY (e->symtree->n.sym))
7936 	{
7937 	  attr = CLASS_DATA (e->symtree->n.sym)->attr;
7938 	  attr.pointer = attr.class_pointer;
7939 	}
7940       else
7941 	attr = gfc_expr_attr (e);
7942 
7943       if (attr.allocatable)
7944 	msg = xasprintf ("Allocatable argument '%s' is not allocated",
7945 			 e->symtree->n.sym->name);
7946       else if (attr.pointer)
7947 	msg = xasprintf ("Pointer argument '%s' is not associated",
7948 			 e->symtree->n.sym->name);
7949       else
7950 	goto end_arg_check;
7951 
7952       if (sym)
7953 	{
7954 	  temp = gfc_class_data_get (sym->backend_decl);
7955 	  temp = gfc_conv_descriptor_data_get (temp);
7956 	}
7957       else
7958 	{
7959 	  argse.descriptor_only = 1;
7960 	  gfc_conv_expr_descriptor (&argse, actual->expr);
7961 	  temp = gfc_conv_descriptor_data_get (argse.expr);
7962 	}
7963 
7964       cond = fold_build2_loc (input_location, EQ_EXPR,
7965 			      logical_type_node, temp,
7966 			      fold_convert (TREE_TYPE (temp),
7967 					    null_pointer_node));
7968       gfc_trans_runtime_check (true, false, cond, &argse.pre, &e->where, msg);
7969 
7970       free (msg);
7971     }
7972  end_arg_check:
7973 
7974   argse.data_not_needed = 1;
7975   if (gfc_is_class_array_function (e))
7976     {
7977       /* For functions that return a class array conv_expr_descriptor is not
7978 	 able to get the descriptor right.  Therefore this special case.  */
7979       gfc_conv_expr_reference (&argse, e);
7980       argse.expr = gfc_class_data_get (argse.expr);
7981     }
7982   else if (sym && sym->backend_decl)
7983     {
7984       gcc_assert (GFC_CLASS_TYPE_P (TREE_TYPE (sym->backend_decl)));
7985       argse.expr = gfc_class_data_get (sym->backend_decl);
7986     }
7987   else
7988     gfc_conv_expr_descriptor (&argse, actual->expr);
7989   gfc_add_block_to_block (&se->pre, &argse.pre);
7990   gfc_add_block_to_block (&se->post, &argse.post);
7991   arg1 = argse.expr;
7992 
7993   actual = actual->next;
7994   if (actual->expr)
7995     {
7996       stmtblock_t block;
7997       gfc_init_block (&block);
7998       gfc_init_se (&argse, NULL);
7999       gfc_conv_expr_type (&argse, actual->expr,
8000 			  gfc_array_index_type);
8001       gfc_add_block_to_block (&block, &argse.pre);
8002       tree tmp = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
8003 			     argse.expr, gfc_index_one_node);
8004       size = gfc_tree_array_size (&block, arg1, e, tmp);
8005 
8006       /* Unusually, for an intrinsic, size does not exclude
8007 	 an optional arg2, so we must test for it.  */
8008       if (actual->expr->expr_type == EXPR_VARIABLE
8009 	    && actual->expr->symtree->n.sym->attr.dummy
8010 	    && actual->expr->symtree->n.sym->attr.optional)
8011 	{
8012 	  tree cond;
8013 	  stmtblock_t block2;
8014 	  gfc_init_block (&block2);
8015 	  gfc_init_se (&argse, NULL);
8016 	  argse.want_pointer = 1;
8017 	  argse.data_not_needed = 1;
8018 	  gfc_conv_expr (&argse, actual->expr);
8019 	  gfc_add_block_to_block (&se->pre, &argse.pre);
8020 	  cond = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
8021 				  argse.expr, null_pointer_node);
8022 	  cond = gfc_evaluate_now (cond, &se->pre);
8023 	  /* 'block2' contains the arg2 absent case, 'block' the arg2 present
8024 	      case; size_var can be used in both blocks. */
8025 	  tree size_var = gfc_create_var (TREE_TYPE (size), "size");
8026 	  tmp = fold_build2_loc (input_location, MODIFY_EXPR,
8027 				 TREE_TYPE (size_var), size_var, size);
8028 	  gfc_add_expr_to_block (&block, tmp);
8029 	  size = gfc_tree_array_size (&block2, arg1, e, NULL_TREE);
8030 	  tmp = fold_build2_loc (input_location, MODIFY_EXPR,
8031 				 TREE_TYPE (size_var), size_var, size);
8032 	  gfc_add_expr_to_block (&block2, tmp);
8033 	  tmp = build3_v (COND_EXPR, cond, gfc_finish_block (&block),
8034 			  gfc_finish_block (&block2));
8035 	  gfc_add_expr_to_block (&se->pre, tmp);
8036 	  size = size_var;
8037 	}
8038       else
8039 	gfc_add_block_to_block (&se->pre, &block);
8040     }
8041   else
8042     size = gfc_tree_array_size (&se->pre, arg1, e, NULL_TREE);
8043   type = gfc_typenode_for_spec (&expr->ts);
8044   se->expr = convert (type, size);
8045 }
8046 
8047 
8048 /* Helper function to compute the size of a character variable,
8049    excluding the terminating null characters.  The result has
8050    gfc_array_index_type type.  */
8051 
8052 tree
size_of_string_in_bytes(int kind,tree string_length)8053 size_of_string_in_bytes (int kind, tree string_length)
8054 {
8055   tree bytesize;
8056   int i = gfc_validate_kind (BT_CHARACTER, kind, false);
8057 
8058   bytesize = build_int_cst (gfc_array_index_type,
8059 			    gfc_character_kinds[i].bit_size / 8);
8060 
8061   return fold_build2_loc (input_location, MULT_EXPR, gfc_array_index_type,
8062 			  bytesize,
8063 			  fold_convert (gfc_array_index_type, string_length));
8064 }
8065 
8066 
8067 static void
gfc_conv_intrinsic_sizeof(gfc_se * se,gfc_expr * expr)8068 gfc_conv_intrinsic_sizeof (gfc_se *se, gfc_expr *expr)
8069 {
8070   gfc_expr *arg;
8071   gfc_se argse;
8072   tree source_bytes;
8073   tree tmp;
8074   tree lower;
8075   tree upper;
8076   tree byte_size;
8077   tree field;
8078   int n;
8079 
8080   gfc_init_se (&argse, NULL);
8081   arg = expr->value.function.actual->expr;
8082 
8083   if (arg->rank || arg->ts.type == BT_ASSUMED)
8084     gfc_conv_expr_descriptor (&argse, arg);
8085   else
8086     gfc_conv_expr_reference (&argse, arg);
8087 
8088   if (arg->ts.type == BT_ASSUMED)
8089     {
8090       /* This only works if an array descriptor has been passed; thus, extract
8091 	 the size from the descriptor.  */
8092       gcc_assert (TYPE_PRECISION (gfc_array_index_type)
8093 		  == TYPE_PRECISION (size_type_node));
8094       tmp = arg->symtree->n.sym->backend_decl;
8095       tmp = DECL_LANG_SPECIFIC (tmp)
8096 	    && GFC_DECL_SAVED_DESCRIPTOR (tmp) != NULL_TREE
8097 	    ? GFC_DECL_SAVED_DESCRIPTOR (tmp) : tmp;
8098       if (POINTER_TYPE_P (TREE_TYPE (tmp)))
8099 	tmp = build_fold_indirect_ref_loc (input_location, tmp);
8100 
8101       tmp = gfc_conv_descriptor_dtype (tmp);
8102       field = gfc_advance_chain (TYPE_FIELDS (get_dtype_type_node ()),
8103 				 GFC_DTYPE_ELEM_LEN);
8104       tmp = fold_build3_loc (input_location, COMPONENT_REF, TREE_TYPE (field),
8105 			     tmp, field, NULL_TREE);
8106 
8107       byte_size = fold_convert (gfc_array_index_type, tmp);
8108     }
8109   else if (arg->ts.type == BT_CLASS)
8110     {
8111       /* Conv_expr_descriptor returns a component_ref to _data component of the
8112 	 class object.  The class object may be a non-pointer object, e.g.
8113 	 located on the stack, or a memory location pointed to, e.g. a
8114 	 parameter, i.e., an indirect_ref.  */
8115       if (POINTER_TYPE_P (TREE_TYPE (argse.expr))
8116 	  && GFC_CLASS_TYPE_P (TREE_TYPE (TREE_TYPE (argse.expr))))
8117 	byte_size
8118 	  = gfc_class_vtab_size_get (build_fold_indirect_ref (argse.expr));
8119       else if (GFC_CLASS_TYPE_P (TREE_TYPE (argse.expr)))
8120 	byte_size = gfc_class_vtab_size_get (argse.expr);
8121       else if (GFC_DESCRIPTOR_TYPE_P (TREE_TYPE (argse.expr))
8122 	       && TREE_CODE (argse.expr) == COMPONENT_REF)
8123 	byte_size = gfc_class_vtab_size_get (TREE_OPERAND (argse.expr, 0));
8124       else if (arg->rank > 0
8125 	       || (arg->rank == 0
8126 		   && arg->ref && arg->ref->type == REF_COMPONENT))
8127 	/* The scalarizer added an additional temp.  To get the class' vptr
8128 	   one has to look at the original backend_decl.  */
8129 	byte_size = gfc_class_vtab_size_get (
8130 	      GFC_DECL_SAVED_DESCRIPTOR (arg->symtree->n.sym->backend_decl));
8131       else
8132 	gcc_unreachable ();
8133     }
8134   else
8135     {
8136       if (arg->ts.type == BT_CHARACTER)
8137 	byte_size = size_of_string_in_bytes (arg->ts.kind, argse.string_length);
8138       else
8139 	{
8140 	  if (arg->rank == 0)
8141 	    byte_size = TREE_TYPE (build_fold_indirect_ref_loc (input_location,
8142 								argse.expr));
8143 	  else
8144 	    byte_size = gfc_get_element_type (TREE_TYPE (argse.expr));
8145 	  byte_size = fold_convert (gfc_array_index_type,
8146 				    size_in_bytes (byte_size));
8147 	}
8148     }
8149 
8150   if (arg->rank == 0)
8151     se->expr = byte_size;
8152   else
8153     {
8154       source_bytes = gfc_create_var (gfc_array_index_type, "bytes");
8155       gfc_add_modify (&argse.pre, source_bytes, byte_size);
8156 
8157       if (arg->rank == -1)
8158 	{
8159 	  tree cond, loop_var, exit_label;
8160           stmtblock_t body;
8161 
8162 	  tmp = fold_convert (gfc_array_index_type,
8163 			      gfc_conv_descriptor_rank (argse.expr));
8164 	  loop_var = gfc_create_var (gfc_array_index_type, "i");
8165 	  gfc_add_modify (&argse.pre, loop_var, gfc_index_zero_node);
8166           exit_label = gfc_build_label_decl (NULL_TREE);
8167 
8168 	  /* Create loop:
8169 	     for (;;)
8170 		{
8171 		  if (i >= rank)
8172 		    goto exit;
8173 		  source_bytes = source_bytes * array.dim[i].extent;
8174 		  i = i + 1;
8175 		}
8176 	      exit:  */
8177 	  gfc_start_block (&body);
8178 	  cond = fold_build2_loc (input_location, GE_EXPR, logical_type_node,
8179 				  loop_var, tmp);
8180 	  tmp = build1_v (GOTO_EXPR, exit_label);
8181 	  tmp = fold_build3_loc (input_location, COND_EXPR, void_type_node,
8182 				 cond, tmp, build_empty_stmt (input_location));
8183 	  gfc_add_expr_to_block (&body, tmp);
8184 
8185 	  lower = gfc_conv_descriptor_lbound_get (argse.expr, loop_var);
8186 	  upper = gfc_conv_descriptor_ubound_get (argse.expr, loop_var);
8187 	  tmp = gfc_conv_array_extent_dim (lower, upper, NULL);
8188 	  tmp = fold_build2_loc (input_location, MULT_EXPR,
8189 				 gfc_array_index_type, tmp, source_bytes);
8190 	  gfc_add_modify (&body, source_bytes, tmp);
8191 
8192 	  tmp = fold_build2_loc (input_location, PLUS_EXPR,
8193 				 gfc_array_index_type, loop_var,
8194 				 gfc_index_one_node);
8195 	  gfc_add_modify_loc (input_location, &body, loop_var, tmp);
8196 
8197 	  tmp = gfc_finish_block (&body);
8198 
8199 	  tmp = fold_build1_loc (input_location, LOOP_EXPR, void_type_node,
8200 				 tmp);
8201 	  gfc_add_expr_to_block (&argse.pre, tmp);
8202 
8203 	  tmp = build1_v (LABEL_EXPR, exit_label);
8204 	  gfc_add_expr_to_block (&argse.pre, tmp);
8205 	}
8206       else
8207 	{
8208 	  /* Obtain the size of the array in bytes.  */
8209 	  for (n = 0; n < arg->rank; n++)
8210 	    {
8211 	      tree idx;
8212 	      idx = gfc_rank_cst[n];
8213 	      lower = gfc_conv_descriptor_lbound_get (argse.expr, idx);
8214 	      upper = gfc_conv_descriptor_ubound_get (argse.expr, idx);
8215 	      tmp = gfc_conv_array_extent_dim (lower, upper, NULL);
8216 	      tmp = fold_build2_loc (input_location, MULT_EXPR,
8217 				     gfc_array_index_type, tmp, source_bytes);
8218 	      gfc_add_modify (&argse.pre, source_bytes, tmp);
8219 	    }
8220 	}
8221       se->expr = source_bytes;
8222     }
8223 
8224   gfc_add_block_to_block (&se->pre, &argse.pre);
8225 }
8226 
8227 
8228 static void
gfc_conv_intrinsic_storage_size(gfc_se * se,gfc_expr * expr)8229 gfc_conv_intrinsic_storage_size (gfc_se *se, gfc_expr *expr)
8230 {
8231   gfc_expr *arg;
8232   gfc_se argse;
8233   tree type, result_type, tmp;
8234 
8235   arg = expr->value.function.actual->expr;
8236 
8237   gfc_init_se (&argse, NULL);
8238   result_type = gfc_get_int_type (expr->ts.kind);
8239 
8240   if (arg->rank == 0)
8241     {
8242       if (arg->ts.type == BT_CLASS)
8243 	{
8244 	  gfc_add_vptr_component (arg);
8245 	  gfc_add_size_component (arg);
8246 	  gfc_conv_expr (&argse, arg);
8247 	  tmp = fold_convert (result_type, argse.expr);
8248 	  goto done;
8249 	}
8250 
8251       gfc_conv_expr_reference (&argse, arg);
8252       type = TREE_TYPE (build_fold_indirect_ref_loc (input_location,
8253 						     argse.expr));
8254     }
8255   else
8256     {
8257       argse.want_pointer = 0;
8258       gfc_conv_expr_descriptor (&argse, arg);
8259       if (arg->ts.type == BT_CLASS)
8260 	{
8261 	  if (arg->rank > 0)
8262 	    tmp = gfc_class_vtab_size_get (
8263 		 GFC_DECL_SAVED_DESCRIPTOR (arg->symtree->n.sym->backend_decl));
8264 	  else
8265 	    tmp = gfc_class_vtab_size_get (TREE_OPERAND (argse.expr, 0));
8266 	  tmp = fold_convert (result_type, tmp);
8267 	  goto done;
8268 	}
8269       type = gfc_get_element_type (TREE_TYPE (argse.expr));
8270     }
8271 
8272   /* Obtain the argument's word length.  */
8273   if (arg->ts.type == BT_CHARACTER)
8274     tmp = size_of_string_in_bytes (arg->ts.kind, argse.string_length);
8275   else
8276     tmp = size_in_bytes (type);
8277   tmp = fold_convert (result_type, tmp);
8278 
8279 done:
8280   se->expr = fold_build2_loc (input_location, MULT_EXPR, result_type, tmp,
8281 			      build_int_cst (result_type, BITS_PER_UNIT));
8282   gfc_add_block_to_block (&se->pre, &argse.pre);
8283 }
8284 
8285 
8286 /* Intrinsic string comparison functions.  */
8287 
8288 static void
gfc_conv_intrinsic_strcmp(gfc_se * se,gfc_expr * expr,enum tree_code op)8289 gfc_conv_intrinsic_strcmp (gfc_se * se, gfc_expr * expr, enum tree_code op)
8290 {
8291   tree args[4];
8292 
8293   gfc_conv_intrinsic_function_args (se, expr, args, 4);
8294 
8295   se->expr
8296     = gfc_build_compare_string (args[0], args[1], args[2], args[3],
8297 				expr->value.function.actual->expr->ts.kind,
8298 				op);
8299   se->expr = fold_build2_loc (input_location, op,
8300 			      gfc_typenode_for_spec (&expr->ts), se->expr,
8301 			      build_int_cst (TREE_TYPE (se->expr), 0));
8302 }
8303 
8304 /* Generate a call to the adjustl/adjustr library function.  */
8305 static void
gfc_conv_intrinsic_adjust(gfc_se * se,gfc_expr * expr,tree fndecl)8306 gfc_conv_intrinsic_adjust (gfc_se * se, gfc_expr * expr, tree fndecl)
8307 {
8308   tree args[3];
8309   tree len;
8310   tree type;
8311   tree var;
8312   tree tmp;
8313 
8314   gfc_conv_intrinsic_function_args (se, expr, &args[1], 2);
8315   len = args[1];
8316 
8317   type = TREE_TYPE (args[2]);
8318   var = gfc_conv_string_tmp (se, type, len);
8319   args[0] = var;
8320 
8321   tmp = build_call_expr_loc (input_location,
8322 			 fndecl, 3, args[0], args[1], args[2]);
8323   gfc_add_expr_to_block (&se->pre, tmp);
8324   se->expr = var;
8325   se->string_length = len;
8326 }
8327 
8328 
8329 /* Generate code for the TRANSFER intrinsic:
8330 	For scalar results:
8331 	  DEST = TRANSFER (SOURCE, MOLD)
8332 	where:
8333 	  typeof<DEST> = typeof<MOLD>
8334 	and:
8335 	  MOLD is scalar.
8336 
8337 	For array results:
8338 	  DEST(1:N) = TRANSFER (SOURCE, MOLD[, SIZE])
8339 	where:
8340 	  typeof<DEST> = typeof<MOLD>
8341 	and:
8342 	  N = min (sizeof (SOURCE(:)), sizeof (DEST(:)),
8343 	      sizeof (DEST(0) * SIZE).  */
8344 static void
gfc_conv_intrinsic_transfer(gfc_se * se,gfc_expr * expr)8345 gfc_conv_intrinsic_transfer (gfc_se * se, gfc_expr * expr)
8346 {
8347   tree tmp;
8348   tree tmpdecl;
8349   tree ptr;
8350   tree extent;
8351   tree source;
8352   tree source_type;
8353   tree source_bytes;
8354   tree mold_type;
8355   tree dest_word_len;
8356   tree size_words;
8357   tree size_bytes;
8358   tree upper;
8359   tree lower;
8360   tree stmt;
8361   tree class_ref = NULL_TREE;
8362   gfc_actual_arglist *arg;
8363   gfc_se argse;
8364   gfc_array_info *info;
8365   stmtblock_t block;
8366   int n;
8367   bool scalar_mold;
8368   gfc_expr *source_expr, *mold_expr, *class_expr;
8369 
8370   info = NULL;
8371   if (se->loop)
8372     info = &se->ss->info->data.array;
8373 
8374   /* Convert SOURCE.  The output from this stage is:-
8375 	source_bytes = length of the source in bytes
8376 	source = pointer to the source data.  */
8377   arg = expr->value.function.actual;
8378   source_expr = arg->expr;
8379 
8380   /* Ensure double transfer through LOGICAL preserves all
8381      the needed bits.  */
8382   if (arg->expr->expr_type == EXPR_FUNCTION
8383 	&& arg->expr->value.function.esym == NULL
8384 	&& arg->expr->value.function.isym != NULL
8385 	&& arg->expr->value.function.isym->id == GFC_ISYM_TRANSFER
8386 	&& arg->expr->ts.type == BT_LOGICAL
8387 	&& expr->ts.type != arg->expr->ts.type)
8388     arg->expr->value.function.name = "__transfer_in_transfer";
8389 
8390   gfc_init_se (&argse, NULL);
8391 
8392   source_bytes = gfc_create_var (gfc_array_index_type, NULL);
8393 
8394   /* Obtain the pointer to source and the length of source in bytes.  */
8395   if (arg->expr->rank == 0)
8396     {
8397       gfc_conv_expr_reference (&argse, arg->expr);
8398       if (arg->expr->ts.type == BT_CLASS)
8399 	{
8400 	  tmp = build_fold_indirect_ref_loc (input_location, argse.expr);
8401 	  if (GFC_CLASS_TYPE_P (TREE_TYPE (tmp)))
8402 	    source = gfc_class_data_get (tmp);
8403 	  else
8404 	    {
8405 	      /* Array elements are evaluated as a reference to the data.
8406 		 To obtain the vptr for the element size, the argument
8407 		 expression must be stripped to the class reference and
8408 		 re-evaluated. The pre and post blocks are not needed.  */
8409 	      gcc_assert (arg->expr->expr_type == EXPR_VARIABLE);
8410 	      source = argse.expr;
8411 	      class_expr = gfc_find_and_cut_at_last_class_ref (arg->expr);
8412 	      gfc_init_se (&argse, NULL);
8413 	      gfc_conv_expr (&argse, class_expr);
8414 	      class_ref = argse.expr;
8415 	    }
8416 	}
8417       else
8418 	source = argse.expr;
8419 
8420       /* Obtain the source word length.  */
8421       switch (arg->expr->ts.type)
8422 	{
8423 	case BT_CHARACTER:
8424 	  tmp = size_of_string_in_bytes (arg->expr->ts.kind,
8425 					 argse.string_length);
8426 	  break;
8427 	case BT_CLASS:
8428 	  if (class_ref != NULL_TREE)
8429 	    tmp = gfc_class_vtab_size_get (class_ref);
8430 	  else
8431 	    tmp = gfc_class_vtab_size_get (argse.expr);
8432 	  break;
8433 	default:
8434 	  source_type = TREE_TYPE (build_fold_indirect_ref_loc (input_location,
8435 								source));
8436 	  tmp = fold_convert (gfc_array_index_type,
8437 			      size_in_bytes (source_type));
8438 	  break;
8439 	}
8440     }
8441   else
8442     {
8443       argse.want_pointer = 0;
8444       gfc_conv_expr_descriptor (&argse, arg->expr);
8445       source = gfc_conv_descriptor_data_get (argse.expr);
8446       source_type = gfc_get_element_type (TREE_TYPE (argse.expr));
8447 
8448       /* Repack the source if not simply contiguous.  */
8449       if (!gfc_is_simply_contiguous (arg->expr, false, true))
8450 	{
8451 	  tmp = gfc_build_addr_expr (NULL_TREE, argse.expr);
8452 
8453 	  if (warn_array_temporaries)
8454 	    gfc_warning (OPT_Warray_temporaries,
8455 			 "Creating array temporary at %L", &expr->where);
8456 
8457 	  source = build_call_expr_loc (input_location,
8458 				    gfor_fndecl_in_pack, 1, tmp);
8459 	  source = gfc_evaluate_now (source, &argse.pre);
8460 
8461 	  /* Free the temporary.  */
8462 	  gfc_start_block (&block);
8463 	  tmp = gfc_call_free (source);
8464 	  gfc_add_expr_to_block (&block, tmp);
8465 	  stmt = gfc_finish_block (&block);
8466 
8467 	  /* Clean up if it was repacked.  */
8468 	  gfc_init_block (&block);
8469 	  tmp = gfc_conv_array_data (argse.expr);
8470 	  tmp = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
8471 				 source, tmp);
8472 	  tmp = build3_v (COND_EXPR, tmp, stmt,
8473 			  build_empty_stmt (input_location));
8474 	  gfc_add_expr_to_block (&block, tmp);
8475 	  gfc_add_block_to_block (&block, &se->post);
8476 	  gfc_init_block (&se->post);
8477 	  gfc_add_block_to_block (&se->post, &block);
8478 	}
8479 
8480       /* Obtain the source word length.  */
8481       if (arg->expr->ts.type == BT_CHARACTER)
8482 	tmp = size_of_string_in_bytes (arg->expr->ts.kind,
8483 				       argse.string_length);
8484       else
8485 	tmp = fold_convert (gfc_array_index_type,
8486 			    size_in_bytes (source_type));
8487 
8488       /* Obtain the size of the array in bytes.  */
8489       extent = gfc_create_var (gfc_array_index_type, NULL);
8490       for (n = 0; n < arg->expr->rank; n++)
8491 	{
8492 	  tree idx;
8493 	  idx = gfc_rank_cst[n];
8494 	  gfc_add_modify (&argse.pre, source_bytes, tmp);
8495 	  lower = gfc_conv_descriptor_lbound_get (argse.expr, idx);
8496 	  upper = gfc_conv_descriptor_ubound_get (argse.expr, idx);
8497 	  tmp = fold_build2_loc (input_location, MINUS_EXPR,
8498 				 gfc_array_index_type, upper, lower);
8499 	  gfc_add_modify (&argse.pre, extent, tmp);
8500 	  tmp = fold_build2_loc (input_location, PLUS_EXPR,
8501 				 gfc_array_index_type, extent,
8502 				 gfc_index_one_node);
8503 	  tmp = fold_build2_loc (input_location, MULT_EXPR,
8504 				 gfc_array_index_type, tmp, source_bytes);
8505 	}
8506     }
8507 
8508   gfc_add_modify (&argse.pre, source_bytes, tmp);
8509   gfc_add_block_to_block (&se->pre, &argse.pre);
8510   gfc_add_block_to_block (&se->post, &argse.post);
8511 
8512   /* Now convert MOLD.  The outputs are:
8513 	mold_type = the TREE type of MOLD
8514 	dest_word_len = destination word length in bytes.  */
8515   arg = arg->next;
8516   mold_expr = arg->expr;
8517 
8518   gfc_init_se (&argse, NULL);
8519 
8520   scalar_mold = arg->expr->rank == 0;
8521 
8522   if (arg->expr->rank == 0)
8523     {
8524       gfc_conv_expr_reference (&argse, arg->expr);
8525       mold_type = TREE_TYPE (build_fold_indirect_ref_loc (input_location,
8526 							  argse.expr));
8527     }
8528   else
8529     {
8530       gfc_init_se (&argse, NULL);
8531       argse.want_pointer = 0;
8532       gfc_conv_expr_descriptor (&argse, arg->expr);
8533       mold_type = gfc_get_element_type (TREE_TYPE (argse.expr));
8534     }
8535 
8536   gfc_add_block_to_block (&se->pre, &argse.pre);
8537   gfc_add_block_to_block (&se->post, &argse.post);
8538 
8539   if (strcmp (expr->value.function.name, "__transfer_in_transfer") == 0)
8540     {
8541       /* If this TRANSFER is nested in another TRANSFER, use a type
8542 	 that preserves all bits.  */
8543       if (arg->expr->ts.type == BT_LOGICAL)
8544 	mold_type = gfc_get_int_type (arg->expr->ts.kind);
8545     }
8546 
8547   /* Obtain the destination word length.  */
8548   switch (arg->expr->ts.type)
8549     {
8550     case BT_CHARACTER:
8551       tmp = size_of_string_in_bytes (arg->expr->ts.kind, argse.string_length);
8552       mold_type = gfc_get_character_type_len (arg->expr->ts.kind,
8553 					      argse.string_length);
8554       break;
8555     case BT_CLASS:
8556       tmp = gfc_class_vtab_size_get (argse.expr);
8557       break;
8558     default:
8559       tmp = fold_convert (gfc_array_index_type, size_in_bytes (mold_type));
8560       break;
8561     }
8562   dest_word_len = gfc_create_var (gfc_array_index_type, NULL);
8563   gfc_add_modify (&se->pre, dest_word_len, tmp);
8564 
8565   /* Finally convert SIZE, if it is present.  */
8566   arg = arg->next;
8567   size_words = gfc_create_var (gfc_array_index_type, NULL);
8568 
8569   if (arg->expr)
8570     {
8571       gfc_init_se (&argse, NULL);
8572       gfc_conv_expr_reference (&argse, arg->expr);
8573       tmp = convert (gfc_array_index_type,
8574 		     build_fold_indirect_ref_loc (input_location,
8575 					      argse.expr));
8576       gfc_add_block_to_block (&se->pre, &argse.pre);
8577       gfc_add_block_to_block (&se->post, &argse.post);
8578     }
8579   else
8580     tmp = NULL_TREE;
8581 
8582   /* Separate array and scalar results.  */
8583   if (scalar_mold && tmp == NULL_TREE)
8584     goto scalar_transfer;
8585 
8586   size_bytes = gfc_create_var (gfc_array_index_type, NULL);
8587   if (tmp != NULL_TREE)
8588     tmp = fold_build2_loc (input_location, MULT_EXPR, gfc_array_index_type,
8589 			   tmp, dest_word_len);
8590   else
8591     tmp = source_bytes;
8592 
8593   gfc_add_modify (&se->pre, size_bytes, tmp);
8594   gfc_add_modify (&se->pre, size_words,
8595 		       fold_build2_loc (input_location, CEIL_DIV_EXPR,
8596 					gfc_array_index_type,
8597 					size_bytes, dest_word_len));
8598 
8599   /* Evaluate the bounds of the result.  If the loop range exists, we have
8600      to check if it is too large.  If so, we modify loop->to be consistent
8601      with min(size, size(source)).  Otherwise, size is made consistent with
8602      the loop range, so that the right number of bytes is transferred.*/
8603   n = se->loop->order[0];
8604   if (se->loop->to[n] != NULL_TREE)
8605     {
8606       tmp = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
8607 			     se->loop->to[n], se->loop->from[n]);
8608       tmp = fold_build2_loc (input_location, PLUS_EXPR, gfc_array_index_type,
8609 			     tmp, gfc_index_one_node);
8610       tmp = fold_build2_loc (input_location, MIN_EXPR, gfc_array_index_type,
8611 			 tmp, size_words);
8612       gfc_add_modify (&se->pre, size_words, tmp);
8613       gfc_add_modify (&se->pre, size_bytes,
8614 			   fold_build2_loc (input_location, MULT_EXPR,
8615 					    gfc_array_index_type,
8616 					    size_words, dest_word_len));
8617       upper = fold_build2_loc (input_location, PLUS_EXPR, gfc_array_index_type,
8618 			       size_words, se->loop->from[n]);
8619       upper = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
8620 			       upper, gfc_index_one_node);
8621     }
8622   else
8623     {
8624       upper = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
8625 			       size_words, gfc_index_one_node);
8626       se->loop->from[n] = gfc_index_zero_node;
8627     }
8628 
8629   se->loop->to[n] = upper;
8630 
8631   /* Build a destination descriptor, using the pointer, source, as the
8632      data field.  */
8633   gfc_trans_create_temp_array (&se->pre, &se->post, se->ss, mold_type,
8634 			       NULL_TREE, false, true, false, &expr->where);
8635 
8636   /* Cast the pointer to the result.  */
8637   tmp = gfc_conv_descriptor_data_get (info->descriptor);
8638   tmp = fold_convert (pvoid_type_node, tmp);
8639 
8640   /* Use memcpy to do the transfer.  */
8641   tmp
8642     = build_call_expr_loc (input_location,
8643 			   builtin_decl_explicit (BUILT_IN_MEMCPY), 3, tmp,
8644 			   fold_convert (pvoid_type_node, source),
8645 			   fold_convert (size_type_node,
8646 					 fold_build2_loc (input_location,
8647 							  MIN_EXPR,
8648 							  gfc_array_index_type,
8649 							  size_bytes,
8650 							  source_bytes)));
8651   gfc_add_expr_to_block (&se->pre, tmp);
8652 
8653   se->expr = info->descriptor;
8654   if (expr->ts.type == BT_CHARACTER)
8655     {
8656       tmp = fold_convert (gfc_charlen_type_node,
8657 			  TYPE_SIZE_UNIT (gfc_get_char_type (expr->ts.kind)));
8658       se->string_length = fold_build2_loc (input_location, TRUNC_DIV_EXPR,
8659 					   gfc_charlen_type_node,
8660 					   dest_word_len, tmp);
8661     }
8662 
8663   return;
8664 
8665 /* Deal with scalar results.  */
8666 scalar_transfer:
8667   extent = fold_build2_loc (input_location, MIN_EXPR, gfc_array_index_type,
8668 			    dest_word_len, source_bytes);
8669   extent = fold_build2_loc (input_location, MAX_EXPR, gfc_array_index_type,
8670 			    extent, gfc_index_zero_node);
8671 
8672   if (expr->ts.type == BT_CHARACTER)
8673     {
8674       tree direct, indirect, free;
8675 
8676       ptr = convert (gfc_get_pchar_type (expr->ts.kind), source);
8677       tmpdecl = gfc_create_var (gfc_get_pchar_type (expr->ts.kind),
8678 				"transfer");
8679 
8680       /* If source is longer than the destination, use a pointer to
8681 	 the source directly.  */
8682       gfc_init_block (&block);
8683       gfc_add_modify (&block, tmpdecl, ptr);
8684       direct = gfc_finish_block (&block);
8685 
8686       /* Otherwise, allocate a string with the length of the destination
8687 	 and copy the source into it.  */
8688       gfc_init_block (&block);
8689       tmp = gfc_get_pchar_type (expr->ts.kind);
8690       tmp = gfc_call_malloc (&block, tmp, dest_word_len);
8691       gfc_add_modify (&block, tmpdecl,
8692 		      fold_convert (TREE_TYPE (ptr), tmp));
8693       tmp = build_call_expr_loc (input_location,
8694 			     builtin_decl_explicit (BUILT_IN_MEMCPY), 3,
8695 			     fold_convert (pvoid_type_node, tmpdecl),
8696 			     fold_convert (pvoid_type_node, ptr),
8697 			     fold_convert (size_type_node, extent));
8698       gfc_add_expr_to_block (&block, tmp);
8699       indirect = gfc_finish_block (&block);
8700 
8701       /* Wrap it up with the condition.  */
8702       tmp = fold_build2_loc (input_location, LE_EXPR, logical_type_node,
8703 			     dest_word_len, source_bytes);
8704       tmp = build3_v (COND_EXPR, tmp, direct, indirect);
8705       gfc_add_expr_to_block (&se->pre, tmp);
8706 
8707       /* Free the temporary string, if necessary.  */
8708       free = gfc_call_free (tmpdecl);
8709       tmp = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
8710 			     dest_word_len, source_bytes);
8711       tmp = build3_v (COND_EXPR, tmp, free, build_empty_stmt (input_location));
8712       gfc_add_expr_to_block (&se->post, tmp);
8713 
8714       se->expr = tmpdecl;
8715       tmp = fold_convert (gfc_charlen_type_node,
8716 			  TYPE_SIZE_UNIT (gfc_get_char_type (expr->ts.kind)));
8717       se->string_length = fold_build2_loc (input_location, TRUNC_DIV_EXPR,
8718 					   gfc_charlen_type_node,
8719 					   dest_word_len, tmp);
8720     }
8721   else
8722     {
8723       tmpdecl = gfc_create_var (mold_type, "transfer");
8724 
8725       ptr = convert (build_pointer_type (mold_type), source);
8726 
8727       /* For CLASS results, allocate the needed memory first.  */
8728       if (mold_expr->ts.type == BT_CLASS)
8729 	{
8730 	  tree cdata;
8731 	  cdata = gfc_class_data_get (tmpdecl);
8732 	  tmp = gfc_call_malloc (&se->pre, TREE_TYPE (cdata), dest_word_len);
8733 	  gfc_add_modify (&se->pre, cdata, tmp);
8734 	}
8735 
8736       /* Use memcpy to do the transfer.  */
8737       if (mold_expr->ts.type == BT_CLASS)
8738 	tmp = gfc_class_data_get (tmpdecl);
8739       else
8740 	tmp = gfc_build_addr_expr (NULL_TREE, tmpdecl);
8741 
8742       tmp = build_call_expr_loc (input_location,
8743 			     builtin_decl_explicit (BUILT_IN_MEMCPY), 3,
8744 			     fold_convert (pvoid_type_node, tmp),
8745 			     fold_convert (pvoid_type_node, ptr),
8746 			     fold_convert (size_type_node, extent));
8747       gfc_add_expr_to_block (&se->pre, tmp);
8748 
8749       /* For CLASS results, set the _vptr.  */
8750       if (mold_expr->ts.type == BT_CLASS)
8751 	{
8752 	  tree vptr;
8753 	  gfc_symbol *vtab;
8754 	  vptr = gfc_class_vptr_get (tmpdecl);
8755 	  vtab = gfc_find_derived_vtab (source_expr->ts.u.derived);
8756 	  gcc_assert (vtab);
8757 	  tmp = gfc_build_addr_expr (NULL_TREE, gfc_get_symbol_decl (vtab));
8758 	  gfc_add_modify (&se->pre, vptr, fold_convert (TREE_TYPE (vptr), tmp));
8759 	}
8760 
8761       se->expr = tmpdecl;
8762     }
8763 }
8764 
8765 
8766 /* Generate a call to caf_is_present.  */
8767 
8768 static tree
trans_caf_is_present(gfc_se * se,gfc_expr * expr)8769 trans_caf_is_present (gfc_se *se, gfc_expr *expr)
8770 {
8771   tree caf_reference, caf_decl, token, image_index;
8772 
8773   /* Compile the reference chain.  */
8774   caf_reference = conv_expr_ref_to_caf_ref (&se->pre, expr);
8775   gcc_assert (caf_reference != NULL_TREE);
8776 
8777   caf_decl = gfc_get_tree_for_caf_expr (expr);
8778   if (TREE_CODE (TREE_TYPE (caf_decl)) == REFERENCE_TYPE)
8779     caf_decl = build_fold_indirect_ref_loc (input_location, caf_decl);
8780   image_index = gfc_caf_get_image_index (&se->pre, expr, caf_decl);
8781   gfc_get_caf_token_offset (se, &token, NULL, caf_decl, NULL,
8782 			    expr);
8783 
8784   return build_call_expr_loc (input_location, gfor_fndecl_caf_is_present,
8785 			      3, token, image_index, caf_reference);
8786 }
8787 
8788 
8789 /* Test whether this ref-chain refs this image only.  */
8790 
8791 static bool
caf_this_image_ref(gfc_ref * ref)8792 caf_this_image_ref (gfc_ref *ref)
8793 {
8794   for ( ; ref; ref = ref->next)
8795     if (ref->type == REF_ARRAY && ref->u.ar.codimen)
8796       return ref->u.ar.dimen_type[ref->u.ar.dimen] == DIMEN_THIS_IMAGE;
8797 
8798   return false;
8799 }
8800 
8801 
8802 /* Generate code for the ALLOCATED intrinsic.
8803    Generate inline code that directly check the address of the argument.  */
8804 
8805 static void
gfc_conv_allocated(gfc_se * se,gfc_expr * expr)8806 gfc_conv_allocated (gfc_se *se, gfc_expr *expr)
8807 {
8808   gfc_se arg1se;
8809   tree tmp;
8810   bool coindexed_caf_comp = false;
8811   gfc_expr *e = expr->value.function.actual->expr;
8812 
8813   gfc_init_se (&arg1se, NULL);
8814   if (e->ts.type == BT_CLASS)
8815     {
8816       /* Make sure that class array expressions have both a _data
8817 	 component reference and an array reference....  */
8818       if (CLASS_DATA (e)->attr.dimension)
8819 	gfc_add_class_array_ref (e);
8820       /* .... whilst scalars only need the _data component.  */
8821       else
8822 	gfc_add_data_component (e);
8823     }
8824 
8825   /* When 'e' references an allocatable component in a coarray, then call
8826      the caf-library function caf_is_present ().  */
8827   if (flag_coarray == GFC_FCOARRAY_LIB && e->expr_type == EXPR_FUNCTION
8828       && e->value.function.isym
8829       && e->value.function.isym->id == GFC_ISYM_CAF_GET)
8830     {
8831       e = e->value.function.actual->expr;
8832       if (gfc_expr_attr (e).codimension)
8833 	{
8834 	  /* Last partref is the coindexed coarray. As coarrays are collectively
8835 	     (de)allocated, the allocation status must be the same as the one of
8836 	     the local allocation.  Convert to local access. */
8837 	  for (gfc_ref *ref = e->ref; ref; ref = ref->next)
8838 	    if (ref->type == REF_ARRAY && ref->u.ar.codimen)
8839 	      {
8840 		for (int i = ref->u.ar.dimen;
8841 		     i < ref->u.ar.dimen + ref->u.ar.codimen; ++i)
8842 		ref->u.ar.dimen_type[i] = DIMEN_THIS_IMAGE;
8843 		break;
8844 	      }
8845 	}
8846       else if (!caf_this_image_ref (e->ref))
8847 	coindexed_caf_comp = true;
8848     }
8849   if (coindexed_caf_comp)
8850     tmp = trans_caf_is_present (se, e);
8851   else
8852     {
8853       if (e->rank == 0)
8854 	{
8855 	  /* Allocatable scalar.  */
8856 	  arg1se.want_pointer = 1;
8857 	  gfc_conv_expr (&arg1se, e);
8858 	  tmp = arg1se.expr;
8859 	}
8860       else
8861 	{
8862 	  /* Allocatable array.  */
8863 	  arg1se.descriptor_only = 1;
8864 	  gfc_conv_expr_descriptor (&arg1se, e);
8865 	  tmp = gfc_conv_descriptor_data_get (arg1se.expr);
8866 	}
8867 
8868       tmp = fold_build2_loc (input_location, NE_EXPR, logical_type_node, tmp,
8869 			     fold_convert (TREE_TYPE (tmp), null_pointer_node));
8870     }
8871 
8872   /* Components of pointer array references sometimes come back with a pre block.  */
8873   if (arg1se.pre.head)
8874     gfc_add_block_to_block (&se->pre, &arg1se.pre);
8875 
8876   se->expr = convert (gfc_typenode_for_spec (&expr->ts), tmp);
8877 }
8878 
8879 
8880 /* Generate code for the ASSOCIATED intrinsic.
8881    If both POINTER and TARGET are arrays, generate a call to library function
8882    _gfor_associated, and pass descriptors of POINTER and TARGET to it.
8883    In other cases, generate inline code that directly compare the address of
8884    POINTER with the address of TARGET.  */
8885 
8886 static void
gfc_conv_associated(gfc_se * se,gfc_expr * expr)8887 gfc_conv_associated (gfc_se *se, gfc_expr *expr)
8888 {
8889   gfc_actual_arglist *arg1;
8890   gfc_actual_arglist *arg2;
8891   gfc_se arg1se;
8892   gfc_se arg2se;
8893   tree tmp2;
8894   tree tmp;
8895   tree nonzero_arraylen = NULL_TREE;
8896   gfc_ss *ss;
8897   bool scalar;
8898 
8899   gfc_init_se (&arg1se, NULL);
8900   gfc_init_se (&arg2se, NULL);
8901   arg1 = expr->value.function.actual;
8902   arg2 = arg1->next;
8903 
8904   /* Check whether the expression is a scalar or not; we cannot use
8905      arg1->expr->rank as it can be nonzero for proc pointers.  */
8906   ss = gfc_walk_expr (arg1->expr);
8907   scalar = ss == gfc_ss_terminator;
8908   if (!scalar)
8909     gfc_free_ss_chain (ss);
8910 
8911   if (!arg2->expr)
8912     {
8913       /* No optional target.  */
8914       if (scalar)
8915         {
8916 	  /* A pointer to a scalar.  */
8917 	  arg1se.want_pointer = 1;
8918 	  gfc_conv_expr (&arg1se, arg1->expr);
8919 	  if (arg1->expr->symtree->n.sym->attr.proc_pointer
8920 	      && arg1->expr->symtree->n.sym->attr.dummy)
8921 	    arg1se.expr = build_fold_indirect_ref_loc (input_location,
8922 						       arg1se.expr);
8923   	  if (arg1->expr->ts.type == BT_CLASS)
8924 	    {
8925 	      tmp2 = gfc_class_data_get (arg1se.expr);
8926 	      if (GFC_DESCRIPTOR_TYPE_P (TREE_TYPE (tmp2)))
8927 		tmp2 = gfc_conv_descriptor_data_get (tmp2);
8928 	    }
8929 	  else
8930 	    tmp2 = arg1se.expr;
8931         }
8932       else
8933         {
8934           /* A pointer to an array.  */
8935           gfc_conv_expr_descriptor (&arg1se, arg1->expr);
8936           tmp2 = gfc_conv_descriptor_data_get (arg1se.expr);
8937         }
8938       gfc_add_block_to_block (&se->pre, &arg1se.pre);
8939       gfc_add_block_to_block (&se->post, &arg1se.post);
8940       tmp = fold_build2_loc (input_location, NE_EXPR, logical_type_node, tmp2,
8941 			     fold_convert (TREE_TYPE (tmp2), null_pointer_node));
8942       se->expr = tmp;
8943     }
8944   else
8945     {
8946       /* An optional target.  */
8947       if (arg2->expr->ts.type == BT_CLASS
8948 	  && arg2->expr->expr_type != EXPR_FUNCTION)
8949 	gfc_add_data_component (arg2->expr);
8950 
8951       if (scalar)
8952         {
8953 	  /* A pointer to a scalar.  */
8954 	  arg1se.want_pointer = 1;
8955 	  gfc_conv_expr (&arg1se, arg1->expr);
8956 	  if (arg1->expr->symtree->n.sym->attr.proc_pointer
8957 	      && arg1->expr->symtree->n.sym->attr.dummy)
8958 	    arg1se.expr = build_fold_indirect_ref_loc (input_location,
8959 						       arg1se.expr);
8960 	  if (arg1->expr->ts.type == BT_CLASS)
8961 	    arg1se.expr = gfc_class_data_get (arg1se.expr);
8962 
8963 	  arg2se.want_pointer = 1;
8964 	  gfc_conv_expr (&arg2se, arg2->expr);
8965 	  if (arg2->expr->symtree->n.sym->attr.proc_pointer
8966 	      && arg2->expr->symtree->n.sym->attr.dummy)
8967 	    arg2se.expr = build_fold_indirect_ref_loc (input_location,
8968 						       arg2se.expr);
8969 	  if (arg2->expr->ts.type == BT_CLASS)
8970 	    {
8971 	      arg2se.expr = gfc_evaluate_now (arg2se.expr, &arg2se.pre);
8972 	      arg2se.expr = gfc_class_data_get (arg2se.expr);
8973 	    }
8974 	  gfc_add_block_to_block (&se->pre, &arg1se.pre);
8975 	  gfc_add_block_to_block (&se->post, &arg1se.post);
8976 	  gfc_add_block_to_block (&se->pre, &arg2se.pre);
8977 	  gfc_add_block_to_block (&se->post, &arg2se.post);
8978           tmp = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
8979 				 arg1se.expr, arg2se.expr);
8980           tmp2 = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
8981 				  arg1se.expr, null_pointer_node);
8982           se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
8983 				      logical_type_node, tmp, tmp2);
8984         }
8985       else
8986         {
8987 	  /* An array pointer of zero length is not associated if target is
8988 	     present.  */
8989 	  arg1se.descriptor_only = 1;
8990 	  gfc_conv_expr_lhs (&arg1se, arg1->expr);
8991 	  if (arg1->expr->rank == -1)
8992 	    {
8993 	      tmp = gfc_conv_descriptor_rank (arg1se.expr);
8994 	      tmp = fold_build2_loc (input_location, MINUS_EXPR,
8995 				     TREE_TYPE (tmp), tmp,
8996 				     build_int_cst (TREE_TYPE (tmp), 1));
8997 	    }
8998 	  else
8999 	    tmp = gfc_rank_cst[arg1->expr->rank - 1];
9000 	  tmp = gfc_conv_descriptor_stride_get (arg1se.expr, tmp);
9001 	  if (arg2->expr->rank != 0)
9002 	    nonzero_arraylen = fold_build2_loc (input_location, NE_EXPR,
9003 						logical_type_node, tmp,
9004 						build_int_cst (TREE_TYPE (tmp), 0));
9005 
9006 	  /* A pointer to an array, call library function _gfor_associated.  */
9007 	  arg1se.want_pointer = 1;
9008 	  gfc_conv_expr_descriptor (&arg1se, arg1->expr);
9009 	  gfc_add_block_to_block (&se->pre, &arg1se.pre);
9010 	  gfc_add_block_to_block (&se->post, &arg1se.post);
9011 
9012 	  arg2se.want_pointer = 1;
9013 	  arg2se.force_no_tmp = 1;
9014 	  if (arg2->expr->rank != 0)
9015 	    gfc_conv_expr_descriptor (&arg2se, arg2->expr);
9016 	  else
9017 	    {
9018 	      gfc_conv_expr (&arg2se, arg2->expr);
9019 	      arg2se.expr
9020 		= gfc_conv_scalar_to_descriptor (&arg2se, arg2se.expr,
9021 						 gfc_expr_attr (arg2->expr));
9022 	      arg2se.expr = gfc_build_addr_expr (NULL_TREE, arg2se.expr);
9023 	    }
9024 	  gfc_add_block_to_block (&se->pre, &arg2se.pre);
9025 	  gfc_add_block_to_block (&se->post, &arg2se.post);
9026 	  se->expr = build_call_expr_loc (input_location,
9027 				      gfor_fndecl_associated, 2,
9028 				      arg1se.expr, arg2se.expr);
9029 	  se->expr = convert (logical_type_node, se->expr);
9030 	  if (arg2->expr->rank != 0)
9031 	    se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
9032 					logical_type_node, se->expr,
9033 					nonzero_arraylen);
9034         }
9035 
9036       /* If target is present zero character length pointers cannot
9037 	 be associated.  */
9038       if (arg1->expr->ts.type == BT_CHARACTER)
9039 	{
9040 	  tmp = arg1se.string_length;
9041 	  tmp = fold_build2_loc (input_location, NE_EXPR,
9042 				 logical_type_node, tmp,
9043 				 build_zero_cst (TREE_TYPE (tmp)));
9044 	  se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
9045 				      logical_type_node, se->expr, tmp);
9046 	}
9047     }
9048 
9049   se->expr = convert (gfc_typenode_for_spec (&expr->ts), se->expr);
9050 }
9051 
9052 
9053 /* Generate code for the SAME_TYPE_AS intrinsic.
9054    Generate inline code that directly checks the vindices.  */
9055 
9056 static void
gfc_conv_same_type_as(gfc_se * se,gfc_expr * expr)9057 gfc_conv_same_type_as (gfc_se *se, gfc_expr *expr)
9058 {
9059   gfc_expr *a, *b;
9060   gfc_se se1, se2;
9061   tree tmp;
9062   tree conda = NULL_TREE, condb = NULL_TREE;
9063 
9064   gfc_init_se (&se1, NULL);
9065   gfc_init_se (&se2, NULL);
9066 
9067   a = expr->value.function.actual->expr;
9068   b = expr->value.function.actual->next->expr;
9069 
9070   bool unlimited_poly_a = UNLIMITED_POLY (a);
9071   bool unlimited_poly_b = UNLIMITED_POLY (b);
9072   if (unlimited_poly_a)
9073     {
9074       se1.want_pointer = 1;
9075       gfc_add_vptr_component (a);
9076     }
9077   else if (a->ts.type == BT_CLASS)
9078     {
9079       gfc_add_vptr_component (a);
9080       gfc_add_hash_component (a);
9081     }
9082   else if (a->ts.type == BT_DERIVED)
9083     a = gfc_get_int_expr (gfc_default_integer_kind, NULL,
9084 			  a->ts.u.derived->hash_value);
9085 
9086   if (unlimited_poly_b)
9087     {
9088       se2.want_pointer = 1;
9089       gfc_add_vptr_component (b);
9090     }
9091   else if (b->ts.type == BT_CLASS)
9092     {
9093       gfc_add_vptr_component (b);
9094       gfc_add_hash_component (b);
9095     }
9096   else if (b->ts.type == BT_DERIVED)
9097     b = gfc_get_int_expr (gfc_default_integer_kind, NULL,
9098 			  b->ts.u.derived->hash_value);
9099 
9100   gfc_conv_expr (&se1, a);
9101   gfc_conv_expr (&se2, b);
9102 
9103   if (unlimited_poly_a)
9104     {
9105       conda = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
9106 			       se1.expr,
9107 			       build_int_cst (TREE_TYPE (se1.expr), 0));
9108       se1.expr = gfc_vptr_hash_get (se1.expr);
9109     }
9110 
9111   if (unlimited_poly_b)
9112     {
9113       condb = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
9114 			       se2.expr,
9115 			       build_int_cst (TREE_TYPE (se2.expr), 0));
9116       se2.expr = gfc_vptr_hash_get (se2.expr);
9117     }
9118 
9119   tmp = fold_build2_loc (input_location, EQ_EXPR,
9120 			 logical_type_node, se1.expr,
9121 			 fold_convert (TREE_TYPE (se1.expr), se2.expr));
9122 
9123   if (conda)
9124     tmp = fold_build2_loc (input_location, TRUTH_ANDIF_EXPR,
9125 			   logical_type_node, conda, tmp);
9126 
9127   if (condb)
9128     tmp = fold_build2_loc (input_location, TRUTH_ANDIF_EXPR,
9129 			   logical_type_node, condb, tmp);
9130 
9131   se->expr = convert (gfc_typenode_for_spec (&expr->ts), tmp);
9132 }
9133 
9134 
9135 /* Generate code for SELECTED_CHAR_KIND (NAME) intrinsic function.  */
9136 
9137 static void
gfc_conv_intrinsic_sc_kind(gfc_se * se,gfc_expr * expr)9138 gfc_conv_intrinsic_sc_kind (gfc_se *se, gfc_expr *expr)
9139 {
9140   tree args[2];
9141 
9142   gfc_conv_intrinsic_function_args (se, expr, args, 2);
9143   se->expr = build_call_expr_loc (input_location,
9144 			      gfor_fndecl_sc_kind, 2, args[0], args[1]);
9145   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), se->expr);
9146 }
9147 
9148 
9149 /* Generate code for SELECTED_INT_KIND (R) intrinsic function.  */
9150 
9151 static void
gfc_conv_intrinsic_si_kind(gfc_se * se,gfc_expr * expr)9152 gfc_conv_intrinsic_si_kind (gfc_se *se, gfc_expr *expr)
9153 {
9154   tree arg, type;
9155 
9156   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
9157 
9158   /* The argument to SELECTED_INT_KIND is INTEGER(4).  */
9159   type = gfc_get_int_type (4);
9160   arg = gfc_build_addr_expr (NULL_TREE, fold_convert (type, arg));
9161 
9162   /* Convert it to the required type.  */
9163   type = gfc_typenode_for_spec (&expr->ts);
9164   se->expr = build_call_expr_loc (input_location,
9165 			      gfor_fndecl_si_kind, 1, arg);
9166   se->expr = fold_convert (type, se->expr);
9167 }
9168 
9169 
9170 /* Generate code for SELECTED_REAL_KIND (P, R, RADIX) intrinsic function.  */
9171 
9172 static void
gfc_conv_intrinsic_sr_kind(gfc_se * se,gfc_expr * expr)9173 gfc_conv_intrinsic_sr_kind (gfc_se *se, gfc_expr *expr)
9174 {
9175   gfc_actual_arglist *actual;
9176   tree type;
9177   gfc_se argse;
9178   vec<tree, va_gc> *args = NULL;
9179 
9180   for (actual = expr->value.function.actual; actual; actual = actual->next)
9181     {
9182       gfc_init_se (&argse, se);
9183 
9184       /* Pass a NULL pointer for an absent arg.  */
9185       if (actual->expr == NULL)
9186         argse.expr = null_pointer_node;
9187       else
9188 	{
9189 	  gfc_typespec ts;
9190           gfc_clear_ts (&ts);
9191 
9192 	  if (actual->expr->ts.kind != gfc_c_int_kind)
9193 	    {
9194   	      /* The arguments to SELECTED_REAL_KIND are INTEGER(4).  */
9195 	      ts.type = BT_INTEGER;
9196 	      ts.kind = gfc_c_int_kind;
9197 	      gfc_convert_type (actual->expr, &ts, 2);
9198 	    }
9199 	  gfc_conv_expr_reference (&argse, actual->expr);
9200 	}
9201 
9202       gfc_add_block_to_block (&se->pre, &argse.pre);
9203       gfc_add_block_to_block (&se->post, &argse.post);
9204       vec_safe_push (args, argse.expr);
9205     }
9206 
9207   /* Convert it to the required type.  */
9208   type = gfc_typenode_for_spec (&expr->ts);
9209   se->expr = build_call_expr_loc_vec (input_location,
9210 				      gfor_fndecl_sr_kind, args);
9211   se->expr = fold_convert (type, se->expr);
9212 }
9213 
9214 
9215 /* Generate code for TRIM (A) intrinsic function.  */
9216 
9217 static void
gfc_conv_intrinsic_trim(gfc_se * se,gfc_expr * expr)9218 gfc_conv_intrinsic_trim (gfc_se * se, gfc_expr * expr)
9219 {
9220   tree var;
9221   tree len;
9222   tree addr;
9223   tree tmp;
9224   tree cond;
9225   tree fndecl;
9226   tree function;
9227   tree *args;
9228   unsigned int num_args;
9229 
9230   num_args = gfc_intrinsic_argument_list_length (expr) + 2;
9231   args = XALLOCAVEC (tree, num_args);
9232 
9233   var = gfc_create_var (gfc_get_pchar_type (expr->ts.kind), "pstr");
9234   addr = gfc_build_addr_expr (ppvoid_type_node, var);
9235   len = gfc_create_var (gfc_charlen_type_node, "len");
9236 
9237   gfc_conv_intrinsic_function_args (se, expr, &args[2], num_args - 2);
9238   args[0] = gfc_build_addr_expr (NULL_TREE, len);
9239   args[1] = addr;
9240 
9241   if (expr->ts.kind == 1)
9242     function = gfor_fndecl_string_trim;
9243   else if (expr->ts.kind == 4)
9244     function = gfor_fndecl_string_trim_char4;
9245   else
9246     gcc_unreachable ();
9247 
9248   fndecl = build_addr (function);
9249   tmp = build_call_array_loc (input_location,
9250 			  TREE_TYPE (TREE_TYPE (function)), fndecl,
9251 			  num_args, args);
9252   gfc_add_expr_to_block (&se->pre, tmp);
9253 
9254   /* Free the temporary afterwards, if necessary.  */
9255   cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
9256 			  len, build_int_cst (TREE_TYPE (len), 0));
9257   tmp = gfc_call_free (var);
9258   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
9259   gfc_add_expr_to_block (&se->post, tmp);
9260 
9261   se->expr = var;
9262   se->string_length = len;
9263 }
9264 
9265 
9266 /* Generate code for REPEAT (STRING, NCOPIES) intrinsic function.  */
9267 
9268 static void
gfc_conv_intrinsic_repeat(gfc_se * se,gfc_expr * expr)9269 gfc_conv_intrinsic_repeat (gfc_se * se, gfc_expr * expr)
9270 {
9271   tree args[3], ncopies, dest, dlen, src, slen, ncopies_type;
9272   tree type, cond, tmp, count, exit_label, n, max, largest;
9273   tree size;
9274   stmtblock_t block, body;
9275   int i;
9276 
9277   /* We store in charsize the size of a character.  */
9278   i = gfc_validate_kind (BT_CHARACTER, expr->ts.kind, false);
9279   size = build_int_cst (sizetype, gfc_character_kinds[i].bit_size / 8);
9280 
9281   /* Get the arguments.  */
9282   gfc_conv_intrinsic_function_args (se, expr, args, 3);
9283   slen = fold_convert (sizetype, gfc_evaluate_now (args[0], &se->pre));
9284   src = args[1];
9285   ncopies = gfc_evaluate_now (args[2], &se->pre);
9286   ncopies_type = TREE_TYPE (ncopies);
9287 
9288   /* Check that NCOPIES is not negative.  */
9289   cond = fold_build2_loc (input_location, LT_EXPR, logical_type_node, ncopies,
9290 			  build_int_cst (ncopies_type, 0));
9291   gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
9292 			   "Argument NCOPIES of REPEAT intrinsic is negative "
9293 			   "(its value is %ld)",
9294 			   fold_convert (long_integer_type_node, ncopies));
9295 
9296   /* If the source length is zero, any non negative value of NCOPIES
9297      is valid, and nothing happens.  */
9298   n = gfc_create_var (ncopies_type, "ncopies");
9299   cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, slen,
9300 			  size_zero_node);
9301   tmp = fold_build3_loc (input_location, COND_EXPR, ncopies_type, cond,
9302 			 build_int_cst (ncopies_type, 0), ncopies);
9303   gfc_add_modify (&se->pre, n, tmp);
9304   ncopies = n;
9305 
9306   /* Check that ncopies is not too large: ncopies should be less than
9307      (or equal to) MAX / slen, where MAX is the maximal integer of
9308      the gfc_charlen_type_node type.  If slen == 0, we need a special
9309      case to avoid the division by zero.  */
9310   max = fold_build2_loc (input_location, TRUNC_DIV_EXPR, sizetype,
9311 			 fold_convert (sizetype,
9312 				       TYPE_MAX_VALUE (gfc_charlen_type_node)),
9313 			 slen);
9314   largest = TYPE_PRECISION (sizetype) > TYPE_PRECISION (ncopies_type)
9315 	      ? sizetype : ncopies_type;
9316   cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
9317 			  fold_convert (largest, ncopies),
9318 			  fold_convert (largest, max));
9319   tmp = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, slen,
9320 			 size_zero_node);
9321   cond = fold_build3_loc (input_location, COND_EXPR, logical_type_node, tmp,
9322 			  logical_false_node, cond);
9323   gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
9324 			   "Argument NCOPIES of REPEAT intrinsic is too large");
9325 
9326   /* Compute the destination length.  */
9327   dlen = fold_build2_loc (input_location, MULT_EXPR, gfc_charlen_type_node,
9328 			  fold_convert (gfc_charlen_type_node, slen),
9329 			  fold_convert (gfc_charlen_type_node, ncopies));
9330   type = gfc_get_character_type (expr->ts.kind, expr->ts.u.cl);
9331   dest = gfc_conv_string_tmp (se, build_pointer_type (type), dlen);
9332 
9333   /* Generate the code to do the repeat operation:
9334        for (i = 0; i < ncopies; i++)
9335          memmove (dest + (i * slen * size), src, slen*size);  */
9336   gfc_start_block (&block);
9337   count = gfc_create_var (sizetype, "count");
9338   gfc_add_modify (&block, count, size_zero_node);
9339   exit_label = gfc_build_label_decl (NULL_TREE);
9340 
9341   /* Start the loop body.  */
9342   gfc_start_block (&body);
9343 
9344   /* Exit the loop if count >= ncopies.  */
9345   cond = fold_build2_loc (input_location, GE_EXPR, logical_type_node, count,
9346 			  fold_convert (sizetype, ncopies));
9347   tmp = build1_v (GOTO_EXPR, exit_label);
9348   TREE_USED (exit_label) = 1;
9349   tmp = fold_build3_loc (input_location, COND_EXPR, void_type_node, cond, tmp,
9350 			 build_empty_stmt (input_location));
9351   gfc_add_expr_to_block (&body, tmp);
9352 
9353   /* Call memmove (dest + (i*slen*size), src, slen*size).  */
9354   tmp = fold_build2_loc (input_location, MULT_EXPR, sizetype, slen,
9355 			 count);
9356   tmp = fold_build2_loc (input_location, MULT_EXPR, sizetype, tmp,
9357 			 size);
9358   tmp = fold_build_pointer_plus_loc (input_location,
9359 				     fold_convert (pvoid_type_node, dest), tmp);
9360   tmp = build_call_expr_loc (input_location,
9361 			     builtin_decl_explicit (BUILT_IN_MEMMOVE),
9362 			     3, tmp, src,
9363 			     fold_build2_loc (input_location, MULT_EXPR,
9364 					      size_type_node, slen, size));
9365   gfc_add_expr_to_block (&body, tmp);
9366 
9367   /* Increment count.  */
9368   tmp = fold_build2_loc (input_location, PLUS_EXPR, sizetype,
9369 			 count, size_one_node);
9370   gfc_add_modify (&body, count, tmp);
9371 
9372   /* Build the loop.  */
9373   tmp = build1_v (LOOP_EXPR, gfc_finish_block (&body));
9374   gfc_add_expr_to_block (&block, tmp);
9375 
9376   /* Add the exit label.  */
9377   tmp = build1_v (LABEL_EXPR, exit_label);
9378   gfc_add_expr_to_block (&block, tmp);
9379 
9380   /* Finish the block.  */
9381   tmp = gfc_finish_block (&block);
9382   gfc_add_expr_to_block (&se->pre, tmp);
9383 
9384   /* Set the result value.  */
9385   se->expr = dest;
9386   se->string_length = dlen;
9387 }
9388 
9389 
9390 /* Generate code for the IARGC intrinsic.  */
9391 
9392 static void
gfc_conv_intrinsic_iargc(gfc_se * se,gfc_expr * expr)9393 gfc_conv_intrinsic_iargc (gfc_se * se, gfc_expr * expr)
9394 {
9395   tree tmp;
9396   tree fndecl;
9397   tree type;
9398 
9399   /* Call the library function.  This always returns an INTEGER(4).  */
9400   fndecl = gfor_fndecl_iargc;
9401   tmp = build_call_expr_loc (input_location,
9402 			 fndecl, 0);
9403 
9404   /* Convert it to the required type.  */
9405   type = gfc_typenode_for_spec (&expr->ts);
9406   tmp = fold_convert (type, tmp);
9407 
9408   se->expr = tmp;
9409 }
9410 
9411 
9412 /* Generate code for the KILL intrinsic.  */
9413 
9414 static void
conv_intrinsic_kill(gfc_se * se,gfc_expr * expr)9415 conv_intrinsic_kill (gfc_se *se, gfc_expr *expr)
9416 {
9417   tree *args;
9418   tree int4_type_node = gfc_get_int_type (4);
9419   tree pid;
9420   tree sig;
9421   tree tmp;
9422   unsigned int num_args;
9423 
9424   num_args = gfc_intrinsic_argument_list_length (expr);
9425   args = XALLOCAVEC (tree, num_args);
9426   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
9427 
9428   /* Convert PID to a INTEGER(4) entity.  */
9429   pid = convert (int4_type_node, args[0]);
9430 
9431   /* Convert SIG to a INTEGER(4) entity.  */
9432   sig = convert (int4_type_node, args[1]);
9433 
9434   tmp = build_call_expr_loc (input_location, gfor_fndecl_kill, 2, pid, sig);
9435 
9436   se->expr = fold_convert (TREE_TYPE (args[0]), tmp);
9437 }
9438 
9439 
9440 static tree
conv_intrinsic_kill_sub(gfc_code * code)9441 conv_intrinsic_kill_sub (gfc_code *code)
9442 {
9443   stmtblock_t block;
9444   gfc_se se, se_stat;
9445   tree int4_type_node = gfc_get_int_type (4);
9446   tree pid;
9447   tree sig;
9448   tree statp;
9449   tree tmp;
9450 
9451   /* Make the function call.  */
9452   gfc_init_block (&block);
9453   gfc_init_se (&se, NULL);
9454 
9455   /* Convert PID to a INTEGER(4) entity.  */
9456   gfc_conv_expr (&se, code->ext.actual->expr);
9457   gfc_add_block_to_block (&block, &se.pre);
9458   pid = fold_convert (int4_type_node, gfc_evaluate_now (se.expr, &block));
9459   gfc_add_block_to_block (&block, &se.post);
9460 
9461   /* Convert SIG to a INTEGER(4) entity.  */
9462   gfc_conv_expr (&se, code->ext.actual->next->expr);
9463   gfc_add_block_to_block (&block, &se.pre);
9464   sig = fold_convert (int4_type_node, gfc_evaluate_now (se.expr, &block));
9465   gfc_add_block_to_block (&block, &se.post);
9466 
9467   /* Deal with an optional STATUS.  */
9468   if (code->ext.actual->next->next->expr)
9469     {
9470       gfc_init_se (&se_stat, NULL);
9471       gfc_conv_expr (&se_stat, code->ext.actual->next->next->expr);
9472       statp = gfc_create_var (gfc_get_int_type (4), "_statp");
9473     }
9474   else
9475     statp = NULL_TREE;
9476 
9477   tmp = build_call_expr_loc (input_location, gfor_fndecl_kill_sub, 3, pid, sig,
9478 	statp ? gfc_build_addr_expr (NULL_TREE, statp) : null_pointer_node);
9479 
9480   gfc_add_expr_to_block (&block, tmp);
9481 
9482   if (statp && statp != se_stat.expr)
9483     gfc_add_modify (&block, se_stat.expr,
9484 		    fold_convert (TREE_TYPE (se_stat.expr), statp));
9485 
9486   return gfc_finish_block (&block);
9487 }
9488 
9489 
9490 
9491 /* The loc intrinsic returns the address of its argument as
9492    gfc_index_integer_kind integer.  */
9493 
9494 static void
gfc_conv_intrinsic_loc(gfc_se * se,gfc_expr * expr)9495 gfc_conv_intrinsic_loc (gfc_se * se, gfc_expr * expr)
9496 {
9497   tree temp_var;
9498   gfc_expr *arg_expr;
9499 
9500   gcc_assert (!se->ss);
9501 
9502   arg_expr = expr->value.function.actual->expr;
9503   if (arg_expr->rank == 0)
9504     {
9505       if (arg_expr->ts.type == BT_CLASS)
9506 	gfc_add_data_component (arg_expr);
9507       gfc_conv_expr_reference (se, arg_expr);
9508     }
9509   else
9510     gfc_conv_array_parameter (se, arg_expr, true, NULL, NULL, NULL);
9511   se->expr = convert (gfc_get_int_type (gfc_index_integer_kind), se->expr);
9512 
9513   /* Create a temporary variable for loc return value.  Without this,
9514      we get an error an ICE in gcc/expr.cc(expand_expr_addr_expr_1).  */
9515   temp_var = gfc_create_var (gfc_get_int_type (gfc_index_integer_kind), NULL);
9516   gfc_add_modify (&se->pre, temp_var, se->expr);
9517   se->expr = temp_var;
9518 }
9519 
9520 
9521 /* The following routine generates code for the intrinsic
9522    functions from the ISO_C_BINDING module:
9523     * C_LOC
9524     * C_FUNLOC
9525     * C_ASSOCIATED  */
9526 
9527 static void
conv_isocbinding_function(gfc_se * se,gfc_expr * expr)9528 conv_isocbinding_function (gfc_se *se, gfc_expr *expr)
9529 {
9530   gfc_actual_arglist *arg = expr->value.function.actual;
9531 
9532   if (expr->value.function.isym->id == GFC_ISYM_C_LOC)
9533     {
9534       if (arg->expr->rank == 0)
9535 	gfc_conv_expr_reference (se, arg->expr);
9536       else if (gfc_is_simply_contiguous (arg->expr, false, false))
9537 	gfc_conv_array_parameter (se, arg->expr, true, NULL, NULL, NULL);
9538       else
9539 	{
9540 	  gfc_conv_expr_descriptor (se, arg->expr);
9541 	  se->expr = gfc_conv_descriptor_data_get (se->expr);
9542 	}
9543 
9544       /* TODO -- the following two lines shouldn't be necessary, but if
9545 	 they're removed, a bug is exposed later in the code path.
9546 	 This workaround was thus introduced, but will have to be
9547 	 removed; please see PR 35150 for details about the issue.  */
9548       se->expr = convert (pvoid_type_node, se->expr);
9549       se->expr = gfc_evaluate_now (se->expr, &se->pre);
9550     }
9551   else if (expr->value.function.isym->id == GFC_ISYM_C_FUNLOC)
9552     gfc_conv_expr_reference (se, arg->expr);
9553   else if (expr->value.function.isym->id == GFC_ISYM_C_ASSOCIATED)
9554     {
9555       gfc_se arg1se;
9556       gfc_se arg2se;
9557 
9558       /* Build the addr_expr for the first argument.  The argument is
9559 	 already an *address* so we don't need to set want_pointer in
9560 	 the gfc_se.  */
9561       gfc_init_se (&arg1se, NULL);
9562       gfc_conv_expr (&arg1se, arg->expr);
9563       gfc_add_block_to_block (&se->pre, &arg1se.pre);
9564       gfc_add_block_to_block (&se->post, &arg1se.post);
9565 
9566       /* See if we were given two arguments.  */
9567       if (arg->next->expr == NULL)
9568 	/* Only given one arg so generate a null and do a
9569 	   not-equal comparison against the first arg.  */
9570 	se->expr = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
9571 				    arg1se.expr,
9572 				    fold_convert (TREE_TYPE (arg1se.expr),
9573 						  null_pointer_node));
9574       else
9575 	{
9576 	  tree eq_expr;
9577 	  tree not_null_expr;
9578 
9579 	  /* Given two arguments so build the arg2se from second arg.  */
9580 	  gfc_init_se (&arg2se, NULL);
9581 	  gfc_conv_expr (&arg2se, arg->next->expr);
9582 	  gfc_add_block_to_block (&se->pre, &arg2se.pre);
9583 	  gfc_add_block_to_block (&se->post, &arg2se.post);
9584 
9585 	  /* Generate test to compare that the two args are equal.  */
9586 	  eq_expr = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
9587 				     arg1se.expr, arg2se.expr);
9588 	  /* Generate test to ensure that the first arg is not null.  */
9589 	  not_null_expr = fold_build2_loc (input_location, NE_EXPR,
9590 					   logical_type_node,
9591 					   arg1se.expr, null_pointer_node);
9592 
9593 	  /* Finally, the generated test must check that both arg1 is not
9594 	     NULL and that it is equal to the second arg.  */
9595 	  se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
9596 				      logical_type_node,
9597 				      not_null_expr, eq_expr);
9598 	}
9599     }
9600   else
9601     gcc_unreachable ();
9602 }
9603 
9604 
9605 /* The following routine generates code for the intrinsic
9606    subroutines from the ISO_C_BINDING module:
9607     * C_F_POINTER
9608     * C_F_PROCPOINTER.  */
9609 
9610 static tree
conv_isocbinding_subroutine(gfc_code * code)9611 conv_isocbinding_subroutine (gfc_code *code)
9612 {
9613   gfc_se se;
9614   gfc_se cptrse;
9615   gfc_se fptrse;
9616   gfc_se shapese;
9617   gfc_ss *shape_ss;
9618   tree desc, dim, tmp, stride, offset;
9619   stmtblock_t body, block;
9620   gfc_loopinfo loop;
9621   gfc_actual_arglist *arg = code->ext.actual;
9622 
9623   gfc_init_se (&se, NULL);
9624   gfc_init_se (&cptrse, NULL);
9625   gfc_conv_expr (&cptrse, arg->expr);
9626   gfc_add_block_to_block (&se.pre, &cptrse.pre);
9627   gfc_add_block_to_block (&se.post, &cptrse.post);
9628 
9629   gfc_init_se (&fptrse, NULL);
9630   if (arg->next->expr->rank == 0)
9631     {
9632       fptrse.want_pointer = 1;
9633       gfc_conv_expr (&fptrse, arg->next->expr);
9634       gfc_add_block_to_block (&se.pre, &fptrse.pre);
9635       gfc_add_block_to_block (&se.post, &fptrse.post);
9636       if (arg->next->expr->symtree->n.sym->attr.proc_pointer
9637 	  && arg->next->expr->symtree->n.sym->attr.dummy)
9638 	fptrse.expr = build_fold_indirect_ref_loc (input_location,
9639 						       fptrse.expr);
9640       se.expr = fold_build2_loc (input_location, MODIFY_EXPR,
9641 				 TREE_TYPE (fptrse.expr),
9642 				 fptrse.expr,
9643 				 fold_convert (TREE_TYPE (fptrse.expr),
9644 					       cptrse.expr));
9645       gfc_add_expr_to_block (&se.pre, se.expr);
9646       gfc_add_block_to_block (&se.pre, &se.post);
9647       return gfc_finish_block (&se.pre);
9648     }
9649 
9650   gfc_start_block (&block);
9651 
9652   /* Get the descriptor of the Fortran pointer.  */
9653   fptrse.descriptor_only = 1;
9654   gfc_conv_expr_descriptor (&fptrse, arg->next->expr);
9655   gfc_add_block_to_block (&block, &fptrse.pre);
9656   desc = fptrse.expr;
9657 
9658   /* Set the span field.  */
9659   tmp = TYPE_SIZE_UNIT (gfc_get_element_type (TREE_TYPE (desc)));
9660   tmp = fold_convert (gfc_array_index_type, tmp);
9661   gfc_conv_descriptor_span_set (&block, desc, tmp);
9662 
9663   /* Set data value, dtype, and offset.  */
9664   tmp = GFC_TYPE_ARRAY_DATAPTR_TYPE (TREE_TYPE (desc));
9665   gfc_conv_descriptor_data_set (&block, desc, fold_convert (tmp, cptrse.expr));
9666   gfc_add_modify (&block, gfc_conv_descriptor_dtype (desc),
9667 		  gfc_get_dtype (TREE_TYPE (desc)));
9668 
9669   /* Start scalarization of the bounds, using the shape argument.  */
9670 
9671   shape_ss = gfc_walk_expr (arg->next->next->expr);
9672   gcc_assert (shape_ss != gfc_ss_terminator);
9673   gfc_init_se (&shapese, NULL);
9674 
9675   gfc_init_loopinfo (&loop);
9676   gfc_add_ss_to_loop (&loop, shape_ss);
9677   gfc_conv_ss_startstride (&loop);
9678   gfc_conv_loop_setup (&loop, &arg->next->expr->where);
9679   gfc_mark_ss_chain_used (shape_ss, 1);
9680 
9681   gfc_copy_loopinfo_to_se (&shapese, &loop);
9682   shapese.ss = shape_ss;
9683 
9684   stride = gfc_create_var (gfc_array_index_type, "stride");
9685   offset = gfc_create_var (gfc_array_index_type, "offset");
9686   gfc_add_modify (&block, stride, gfc_index_one_node);
9687   gfc_add_modify (&block, offset, gfc_index_zero_node);
9688 
9689   /* Loop body.  */
9690   gfc_start_scalarized_body (&loop, &body);
9691 
9692   dim = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
9693 			     loop.loopvar[0], loop.from[0]);
9694 
9695   /* Set bounds and stride.  */
9696   gfc_conv_descriptor_lbound_set (&body, desc, dim, gfc_index_one_node);
9697   gfc_conv_descriptor_stride_set (&body, desc, dim, stride);
9698 
9699   gfc_conv_expr (&shapese, arg->next->next->expr);
9700   gfc_add_block_to_block (&body, &shapese.pre);
9701   gfc_conv_descriptor_ubound_set (&body, desc, dim, shapese.expr);
9702   gfc_add_block_to_block (&body, &shapese.post);
9703 
9704   /* Calculate offset.  */
9705   gfc_add_modify (&body, offset,
9706 		  fold_build2_loc (input_location, PLUS_EXPR,
9707 				   gfc_array_index_type, offset, stride));
9708   /* Update stride.  */
9709   gfc_add_modify (&body, stride,
9710 		  fold_build2_loc (input_location, MULT_EXPR,
9711 				   gfc_array_index_type, stride,
9712 				   fold_convert (gfc_array_index_type,
9713 						 shapese.expr)));
9714   /* Finish scalarization loop.  */
9715   gfc_trans_scalarizing_loops (&loop, &body);
9716   gfc_add_block_to_block (&block, &loop.pre);
9717   gfc_add_block_to_block (&block, &loop.post);
9718   gfc_add_block_to_block (&block, &fptrse.post);
9719   gfc_cleanup_loop (&loop);
9720 
9721   gfc_add_modify (&block, offset,
9722 		  fold_build1_loc (input_location, NEGATE_EXPR,
9723 				   gfc_array_index_type, offset));
9724   gfc_conv_descriptor_offset_set (&block, desc, offset);
9725 
9726   gfc_add_expr_to_block (&se.pre, gfc_finish_block (&block));
9727   gfc_add_block_to_block (&se.pre, &se.post);
9728   return gfc_finish_block (&se.pre);
9729 }
9730 
9731 
9732 /* Save and restore floating-point state.  */
9733 
9734 tree
gfc_save_fp_state(stmtblock_t * block)9735 gfc_save_fp_state (stmtblock_t *block)
9736 {
9737   tree type, fpstate, tmp;
9738 
9739   type = build_array_type (char_type_node,
9740 	                   build_range_type (size_type_node, size_zero_node,
9741 					     size_int (GFC_FPE_STATE_BUFFER_SIZE)));
9742   fpstate = gfc_create_var (type, "fpstate");
9743   fpstate = gfc_build_addr_expr (pvoid_type_node, fpstate);
9744 
9745   tmp = build_call_expr_loc (input_location, gfor_fndecl_ieee_procedure_entry,
9746 			     1, fpstate);
9747   gfc_add_expr_to_block (block, tmp);
9748 
9749   return fpstate;
9750 }
9751 
9752 
9753 void
gfc_restore_fp_state(stmtblock_t * block,tree fpstate)9754 gfc_restore_fp_state (stmtblock_t *block, tree fpstate)
9755 {
9756   tree tmp;
9757 
9758   tmp = build_call_expr_loc (input_location, gfor_fndecl_ieee_procedure_exit,
9759 			     1, fpstate);
9760   gfc_add_expr_to_block (block, tmp);
9761 }
9762 
9763 
9764 /* Generate code for arguments of IEEE functions.  */
9765 
9766 static void
conv_ieee_function_args(gfc_se * se,gfc_expr * expr,tree * argarray,int nargs)9767 conv_ieee_function_args (gfc_se *se, gfc_expr *expr, tree *argarray,
9768 			 int nargs)
9769 {
9770   gfc_actual_arglist *actual;
9771   gfc_expr *e;
9772   gfc_se argse;
9773   int arg;
9774 
9775   actual = expr->value.function.actual;
9776   for (arg = 0; arg < nargs; arg++, actual = actual->next)
9777     {
9778       gcc_assert (actual);
9779       e = actual->expr;
9780 
9781       gfc_init_se (&argse, se);
9782       gfc_conv_expr_val (&argse, e);
9783 
9784       gfc_add_block_to_block (&se->pre, &argse.pre);
9785       gfc_add_block_to_block (&se->post, &argse.post);
9786       argarray[arg] = argse.expr;
9787     }
9788 }
9789 
9790 
9791 /* Generate code for intrinsics IEEE_IS_NAN, IEEE_IS_FINITE,
9792    and IEEE_UNORDERED, which translate directly to GCC type-generic
9793    built-ins.  */
9794 
9795 static void
conv_intrinsic_ieee_builtin(gfc_se * se,gfc_expr * expr,enum built_in_function code,int nargs)9796 conv_intrinsic_ieee_builtin (gfc_se * se, gfc_expr * expr,
9797 			     enum built_in_function code, int nargs)
9798 {
9799   tree args[2];
9800   gcc_assert ((unsigned) nargs <= sizeof(args)/sizeof(args[0]));
9801 
9802   conv_ieee_function_args (se, expr, args, nargs);
9803   se->expr = build_call_expr_loc_array (input_location,
9804 					builtin_decl_explicit (code),
9805 					nargs, args);
9806   STRIP_TYPE_NOPS (se->expr);
9807   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), se->expr);
9808 }
9809 
9810 
9811 /* Generate code for IEEE_IS_NORMAL intrinsic:
9812      IEEE_IS_NORMAL(x) --> (__builtin_isnormal(x) || x == 0)  */
9813 
9814 static void
conv_intrinsic_ieee_is_normal(gfc_se * se,gfc_expr * expr)9815 conv_intrinsic_ieee_is_normal (gfc_se * se, gfc_expr * expr)
9816 {
9817   tree arg, isnormal, iszero;
9818 
9819   /* Convert arg, evaluate it only once.  */
9820   conv_ieee_function_args (se, expr, &arg, 1);
9821   arg = gfc_evaluate_now (arg, &se->pre);
9822 
9823   isnormal = build_call_expr_loc (input_location,
9824 				  builtin_decl_explicit (BUILT_IN_ISNORMAL),
9825 				  1, arg);
9826   iszero = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, arg,
9827 			    build_real_from_int_cst (TREE_TYPE (arg),
9828 						     integer_zero_node));
9829   se->expr = fold_build2_loc (input_location, TRUTH_OR_EXPR,
9830 			      logical_type_node, isnormal, iszero);
9831   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), se->expr);
9832 }
9833 
9834 
9835 /* Generate code for IEEE_IS_NEGATIVE intrinsic:
9836      IEEE_IS_NEGATIVE(x) --> (__builtin_signbit(x) && !__builtin_isnan(x))  */
9837 
9838 static void
conv_intrinsic_ieee_is_negative(gfc_se * se,gfc_expr * expr)9839 conv_intrinsic_ieee_is_negative (gfc_se * se, gfc_expr * expr)
9840 {
9841   tree arg, signbit, isnan;
9842 
9843   /* Convert arg, evaluate it only once.  */
9844   conv_ieee_function_args (se, expr, &arg, 1);
9845   arg = gfc_evaluate_now (arg, &se->pre);
9846 
9847   isnan = build_call_expr_loc (input_location,
9848 			       builtin_decl_explicit (BUILT_IN_ISNAN),
9849 			       1, arg);
9850   STRIP_TYPE_NOPS (isnan);
9851 
9852   signbit = build_call_expr_loc (input_location,
9853 				 builtin_decl_explicit (BUILT_IN_SIGNBIT),
9854 				 1, arg);
9855   signbit = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
9856 			     signbit, integer_zero_node);
9857 
9858   se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
9859 			      logical_type_node, signbit,
9860 			      fold_build1_loc (input_location, TRUTH_NOT_EXPR,
9861 					       TREE_TYPE(isnan), isnan));
9862 
9863   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), se->expr);
9864 }
9865 
9866 
9867 /* Generate code for IEEE_LOGB and IEEE_RINT.  */
9868 
9869 static void
conv_intrinsic_ieee_logb_rint(gfc_se * se,gfc_expr * expr,enum built_in_function code)9870 conv_intrinsic_ieee_logb_rint (gfc_se * se, gfc_expr * expr,
9871 			       enum built_in_function code)
9872 {
9873   tree arg, decl, call, fpstate;
9874   int argprec;
9875 
9876   conv_ieee_function_args (se, expr, &arg, 1);
9877   argprec = TYPE_PRECISION (TREE_TYPE (arg));
9878   decl = builtin_decl_for_precision (code, argprec);
9879 
9880   /* Save floating-point state.  */
9881   fpstate = gfc_save_fp_state (&se->pre);
9882 
9883   /* Make the function call.  */
9884   call = build_call_expr_loc (input_location, decl, 1, arg);
9885   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), call);
9886 
9887   /* Restore floating-point state.  */
9888   gfc_restore_fp_state (&se->post, fpstate);
9889 }
9890 
9891 
9892 /* Generate code for IEEE_REM.  */
9893 
9894 static void
conv_intrinsic_ieee_rem(gfc_se * se,gfc_expr * expr)9895 conv_intrinsic_ieee_rem (gfc_se * se, gfc_expr * expr)
9896 {
9897   tree args[2], decl, call, fpstate;
9898   int argprec;
9899 
9900   conv_ieee_function_args (se, expr, args, 2);
9901 
9902   /* If arguments have unequal size, convert them to the larger.  */
9903   if (TYPE_PRECISION (TREE_TYPE (args[0]))
9904       > TYPE_PRECISION (TREE_TYPE (args[1])))
9905     args[1] = fold_convert (TREE_TYPE (args[0]), args[1]);
9906   else if (TYPE_PRECISION (TREE_TYPE (args[1]))
9907 	   > TYPE_PRECISION (TREE_TYPE (args[0])))
9908     args[0] = fold_convert (TREE_TYPE (args[1]), args[0]);
9909 
9910   argprec = TYPE_PRECISION (TREE_TYPE (args[0]));
9911   decl = builtin_decl_for_precision (BUILT_IN_REMAINDER, argprec);
9912 
9913   /* Save floating-point state.  */
9914   fpstate = gfc_save_fp_state (&se->pre);
9915 
9916   /* Make the function call.  */
9917   call = build_call_expr_loc_array (input_location, decl, 2, args);
9918   se->expr = fold_convert (TREE_TYPE (args[0]), call);
9919 
9920   /* Restore floating-point state.  */
9921   gfc_restore_fp_state (&se->post, fpstate);
9922 }
9923 
9924 
9925 /* Generate code for IEEE_NEXT_AFTER.  */
9926 
9927 static void
conv_intrinsic_ieee_next_after(gfc_se * se,gfc_expr * expr)9928 conv_intrinsic_ieee_next_after (gfc_se * se, gfc_expr * expr)
9929 {
9930   tree args[2], decl, call, fpstate;
9931   int argprec;
9932 
9933   conv_ieee_function_args (se, expr, args, 2);
9934 
9935   /* Result has the characteristics of first argument.  */
9936   args[1] = fold_convert (TREE_TYPE (args[0]), args[1]);
9937   argprec = TYPE_PRECISION (TREE_TYPE (args[0]));
9938   decl = builtin_decl_for_precision (BUILT_IN_NEXTAFTER, argprec);
9939 
9940   /* Save floating-point state.  */
9941   fpstate = gfc_save_fp_state (&se->pre);
9942 
9943   /* Make the function call.  */
9944   call = build_call_expr_loc_array (input_location, decl, 2, args);
9945   se->expr = fold_convert (TREE_TYPE (args[0]), call);
9946 
9947   /* Restore floating-point state.  */
9948   gfc_restore_fp_state (&se->post, fpstate);
9949 }
9950 
9951 
9952 /* Generate code for IEEE_SCALB.  */
9953 
9954 static void
conv_intrinsic_ieee_scalb(gfc_se * se,gfc_expr * expr)9955 conv_intrinsic_ieee_scalb (gfc_se * se, gfc_expr * expr)
9956 {
9957   tree args[2], decl, call, huge, type;
9958   int argprec, n;
9959 
9960   conv_ieee_function_args (se, expr, args, 2);
9961 
9962   /* Result has the characteristics of first argument.  */
9963   argprec = TYPE_PRECISION (TREE_TYPE (args[0]));
9964   decl = builtin_decl_for_precision (BUILT_IN_SCALBN, argprec);
9965 
9966   if (TYPE_PRECISION (TREE_TYPE (args[1])) > TYPE_PRECISION (integer_type_node))
9967     {
9968       /* We need to fold the integer into the range of a C int.  */
9969       args[1] = gfc_evaluate_now (args[1], &se->pre);
9970       type = TREE_TYPE (args[1]);
9971 
9972       n = gfc_validate_kind (BT_INTEGER, gfc_c_int_kind, false);
9973       huge = gfc_conv_mpz_to_tree (gfc_integer_kinds[n].huge,
9974 				   gfc_c_int_kind);
9975       huge = fold_convert (type, huge);
9976       args[1] = fold_build2_loc (input_location, MIN_EXPR, type, args[1],
9977 				 huge);
9978       args[1] = fold_build2_loc (input_location, MAX_EXPR, type, args[1],
9979 				 fold_build1_loc (input_location, NEGATE_EXPR,
9980 						  type, huge));
9981     }
9982 
9983   args[1] = fold_convert (integer_type_node, args[1]);
9984 
9985   /* Make the function call.  */
9986   call = build_call_expr_loc_array (input_location, decl, 2, args);
9987   se->expr = fold_convert (TREE_TYPE (args[0]), call);
9988 }
9989 
9990 
9991 /* Generate code for IEEE_COPY_SIGN.  */
9992 
9993 static void
conv_intrinsic_ieee_copy_sign(gfc_se * se,gfc_expr * expr)9994 conv_intrinsic_ieee_copy_sign (gfc_se * se, gfc_expr * expr)
9995 {
9996   tree args[2], decl, sign;
9997   int argprec;
9998 
9999   conv_ieee_function_args (se, expr, args, 2);
10000 
10001   /* Get the sign of the second argument.  */
10002   sign = build_call_expr_loc (input_location,
10003 			      builtin_decl_explicit (BUILT_IN_SIGNBIT),
10004 			      1, args[1]);
10005   sign = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
10006 			  sign, integer_zero_node);
10007 
10008   /* Create a value of one, with the right sign.  */
10009   sign = fold_build3_loc (input_location, COND_EXPR, integer_type_node,
10010 			  sign,
10011 			  fold_build1_loc (input_location, NEGATE_EXPR,
10012 					   integer_type_node,
10013 					   integer_one_node),
10014 			  integer_one_node);
10015   args[1] = fold_convert (TREE_TYPE (args[0]), sign);
10016 
10017   argprec = TYPE_PRECISION (TREE_TYPE (args[0]));
10018   decl = builtin_decl_for_precision (BUILT_IN_COPYSIGN, argprec);
10019 
10020   se->expr = build_call_expr_loc_array (input_location, decl, 2, args);
10021 }
10022 
10023 
10024 /* Generate code for IEEE_CLASS.  */
10025 
10026 static bool
conv_intrinsic_ieee_class(gfc_se * se,gfc_expr * expr)10027 conv_intrinsic_ieee_class (gfc_se *se, gfc_expr *expr)
10028 {
10029   tree arg, c, t1, t2, t3, t4;
10030 
10031   /* In GCC 12, handle inline only the powerpc64le-linux IEEE quad
10032      real(kind=16) and nothing else.  */
10033   if (gfc_type_abi_kind (&expr->value.function.actual->expr->ts) != 17)
10034     return false;
10035 
10036   /* Convert arg, evaluate it only once.  */
10037   conv_ieee_function_args (se, expr, &arg, 1);
10038   arg = gfc_evaluate_now (arg, &se->pre);
10039 
10040   c = build_call_expr_loc (input_location,
10041 			   builtin_decl_explicit (BUILT_IN_FPCLASSIFY), 6,
10042 			   build_int_cst (integer_type_node, IEEE_QUIET_NAN),
10043 			   build_int_cst (integer_type_node,
10044 					  IEEE_POSITIVE_INF),
10045 			   build_int_cst (integer_type_node,
10046 					  IEEE_POSITIVE_NORMAL),
10047 			   build_int_cst (integer_type_node,
10048 					  IEEE_POSITIVE_DENORMAL),
10049 			   build_int_cst (integer_type_node,
10050 					  IEEE_POSITIVE_ZERO),
10051 			   arg);
10052   c = gfc_evaluate_now (c, &se->pre);
10053   t1 = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
10054 			c, build_int_cst (integer_type_node,
10055 					  IEEE_QUIET_NAN));
10056   /* In GCC 12, we don't have __builtin_issignaling but above we made
10057      sure arg is powerpc64le-linux IEEE quad real(kind=16).
10058      When we check it is some kind of NaN by fpclassify, all we need
10059      is check the ((__int128) 1) << 111 bit, if it is zero, it is a sNaN,
10060      if it is set, it is a qNaN.  */
10061   t2 = fold_build1_loc (input_location, VIEW_CONVERT_EXPR,
10062 			build_nonstandard_integer_type (128, 1), arg);
10063   t2 = fold_build2_loc (input_location, RSHIFT_EXPR, TREE_TYPE (t2), t2,
10064 			build_int_cst (integer_type_node, 111));
10065   t2 = fold_convert (integer_type_node, t2);
10066   t2 = fold_build2_loc (input_location, BIT_AND_EXPR, integer_type_node,
10067 			t2, integer_one_node);
10068   t2 = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
10069 			t2, build_zero_cst (TREE_TYPE (t2)));
10070   t1 = fold_build2_loc (input_location, TRUTH_AND_EXPR,
10071 			logical_type_node, t1, t2);
10072   t3 = fold_build2_loc (input_location, GE_EXPR, logical_type_node,
10073 			c, build_int_cst (integer_type_node,
10074 					  IEEE_POSITIVE_ZERO));
10075   t4 = build_call_expr_loc (input_location,
10076 			    builtin_decl_explicit (BUILT_IN_SIGNBIT), 1,
10077 			    arg);
10078   t4 = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
10079 			t4, build_zero_cst (TREE_TYPE (t4)));
10080   t3 = fold_build2_loc (input_location, TRUTH_AND_EXPR,
10081 			logical_type_node, t3, t4);
10082   int s = IEEE_NEGATIVE_ZERO + IEEE_POSITIVE_ZERO;
10083   gcc_assert (IEEE_NEGATIVE_INF == s - IEEE_POSITIVE_INF);
10084   gcc_assert (IEEE_NEGATIVE_NORMAL == s - IEEE_POSITIVE_NORMAL);
10085   gcc_assert (IEEE_NEGATIVE_DENORMAL == s - IEEE_POSITIVE_DENORMAL);
10086   gcc_assert (IEEE_NEGATIVE_SUBNORMAL == s - IEEE_POSITIVE_SUBNORMAL);
10087   gcc_assert (IEEE_NEGATIVE_ZERO == s - IEEE_POSITIVE_ZERO);
10088   t4 = fold_build2_loc (input_location, MINUS_EXPR, TREE_TYPE (c),
10089 			build_int_cst (TREE_TYPE (c), s), c);
10090   t3 = fold_build3_loc (input_location, COND_EXPR, TREE_TYPE (c),
10091 			t3, t4, c);
10092   t1 = fold_build3_loc (input_location, COND_EXPR, TREE_TYPE (c), t1,
10093 			build_int_cst (TREE_TYPE (c), IEEE_SIGNALING_NAN),
10094 			t3);
10095   tree type = gfc_typenode_for_spec (&expr->ts);
10096   /* Perform a quick sanity check that the return type is
10097      IEEE_CLASS_TYPE derived type defined in
10098      libgfortran/ieee/ieee_arithmetic.F90
10099      Primarily check that it is a derived type with a single
10100      member in it.  */
10101   gcc_assert (TREE_CODE (type) == RECORD_TYPE);
10102   tree field = NULL_TREE;
10103   for (tree f = TYPE_FIELDS (type); f != NULL_TREE; f = DECL_CHAIN (f))
10104     if (TREE_CODE (f) == FIELD_DECL)
10105       {
10106 	gcc_assert (field == NULL_TREE);
10107 	field = f;
10108       }
10109   gcc_assert (field);
10110   t1 = fold_convert (TREE_TYPE (field), t1);
10111   se->expr = build_constructor_single (type, field, t1);
10112   return true;
10113 }
10114 
10115 
10116 /* Generate code for IEEE_VALUE.  */
10117 
10118 static bool
conv_intrinsic_ieee_value(gfc_se * se,gfc_expr * expr)10119 conv_intrinsic_ieee_value (gfc_se *se, gfc_expr *expr)
10120 {
10121   tree args[2], arg, ret, tmp;
10122   stmtblock_t body;
10123 
10124   /* In GCC 12, handle inline only the powerpc64le-linux IEEE quad
10125      real(kind=16) and nothing else.  */
10126   if (gfc_type_abi_kind (&expr->ts) != 17)
10127     return false;
10128 
10129   /* Convert args, evaluate the second one only once.  */
10130   conv_ieee_function_args (se, expr, args, 2);
10131   arg = gfc_evaluate_now (args[1], &se->pre);
10132 
10133   tree type = TREE_TYPE (arg);
10134   /* Perform a quick sanity check that the second argument's type is
10135      IEEE_CLASS_TYPE derived type defined in
10136      libgfortran/ieee/ieee_arithmetic.F90
10137      Primarily check that it is a derived type with a single
10138      member in it.  */
10139   gcc_assert (TREE_CODE (type) == RECORD_TYPE);
10140   tree field = NULL_TREE;
10141   for (tree f = TYPE_FIELDS (type); f != NULL_TREE; f = DECL_CHAIN (f))
10142     if (TREE_CODE (f) == FIELD_DECL)
10143       {
10144 	gcc_assert (field == NULL_TREE);
10145 	field = f;
10146       }
10147   gcc_assert (field);
10148   arg = fold_build3_loc (input_location, COMPONENT_REF, TREE_TYPE (field),
10149 			 arg, field, NULL_TREE);
10150   arg = gfc_evaluate_now (arg, &se->pre);
10151 
10152   type = gfc_typenode_for_spec (&expr->ts);
10153   gcc_assert (TREE_CODE (type) == REAL_TYPE);
10154   ret = gfc_create_var (type, NULL);
10155 
10156   gfc_init_block (&body);
10157 
10158   tree end_label = gfc_build_label_decl (NULL_TREE);
10159   for (int c = IEEE_SIGNALING_NAN; c <= IEEE_POSITIVE_INF; ++c)
10160     {
10161       tree label = gfc_build_label_decl (NULL_TREE);
10162       tree low = build_int_cst (TREE_TYPE (arg), c);
10163       tmp = build_case_label (low, low, label);
10164       gfc_add_expr_to_block (&body, tmp);
10165 
10166       REAL_VALUE_TYPE real;
10167       int k;
10168       switch (c)
10169 	{
10170 	case IEEE_SIGNALING_NAN:
10171 	  real_nan (&real, "", 0, TYPE_MODE (type));
10172 	  break;
10173 	case IEEE_QUIET_NAN:
10174 	  real_nan (&real, "", 1, TYPE_MODE (type));
10175 	  break;
10176 	case IEEE_NEGATIVE_INF:
10177 	  real_inf (&real);
10178 	  real = real_value_negate (&real);
10179 	  break;
10180 	case IEEE_NEGATIVE_NORMAL:
10181 	  real_from_integer (&real, TYPE_MODE (type), -42, SIGNED);
10182 	  break;
10183 	case IEEE_NEGATIVE_DENORMAL:
10184 	  k = gfc_validate_kind (BT_REAL, expr->ts.kind, false);
10185 	  real_from_mpfr (&real, gfc_real_kinds[k].tiny,
10186 			  type, GFC_RND_MODE);
10187 	  real_arithmetic (&real, RDIV_EXPR, &real, &dconst2);
10188 	  real = real_value_negate (&real);
10189 	  break;
10190 	case IEEE_NEGATIVE_ZERO:
10191 	  real_from_integer (&real, TYPE_MODE (type), 0, SIGNED);
10192 	  real = real_value_negate (&real);
10193 	  break;
10194 	case IEEE_POSITIVE_ZERO:
10195 	  /* Make this also the default: label.  The other possibility
10196 	     would be to add a separate default: label followed by
10197 	     __builtin_unreachable ().  */
10198 	  label = gfc_build_label_decl (NULL_TREE);
10199 	  tmp = build_case_label (NULL_TREE, NULL_TREE, label);
10200 	  gfc_add_expr_to_block (&body, tmp);
10201 	  real_from_integer (&real, TYPE_MODE (type), 0, SIGNED);
10202 	  break;
10203 	case IEEE_POSITIVE_DENORMAL:
10204 	  k = gfc_validate_kind (BT_REAL, expr->ts.kind, false);
10205 	  real_from_mpfr (&real, gfc_real_kinds[k].tiny,
10206 			  type, GFC_RND_MODE);
10207 	  real_arithmetic (&real, RDIV_EXPR, &real, &dconst2);
10208 	  break;
10209 	case IEEE_POSITIVE_NORMAL:
10210 	  real_from_integer (&real, TYPE_MODE (type), 42, SIGNED);
10211 	  break;
10212 	case IEEE_POSITIVE_INF:
10213 	  real_inf (&real);
10214 	  break;
10215 	default:
10216 	  gcc_unreachable ();
10217 	}
10218 
10219       tree val = build_real (type, real);
10220       gfc_add_modify (&body, ret, val);
10221 
10222       tmp = build1_v (GOTO_EXPR, end_label);
10223       gfc_add_expr_to_block (&body, tmp);
10224     }
10225 
10226   tmp = gfc_finish_block (&body);
10227   tmp = fold_build2_loc (input_location, SWITCH_EXPR, NULL_TREE, arg, tmp);
10228   gfc_add_expr_to_block (&se->pre, tmp);
10229 
10230   tmp = build1_v (LABEL_EXPR, end_label);
10231   gfc_add_expr_to_block (&se->pre, tmp);
10232 
10233   se->expr = ret;
10234   return true;
10235 }
10236 
10237 
10238 /* Generate code for an intrinsic function from the IEEE_ARITHMETIC
10239    module.  */
10240 
10241 bool
gfc_conv_ieee_arithmetic_function(gfc_se * se,gfc_expr * expr)10242 gfc_conv_ieee_arithmetic_function (gfc_se * se, gfc_expr * expr)
10243 {
10244   const char *name = expr->value.function.name;
10245 
10246   if (startswith (name, "_gfortran_ieee_is_nan"))
10247     conv_intrinsic_ieee_builtin (se, expr, BUILT_IN_ISNAN, 1);
10248   else if (startswith (name, "_gfortran_ieee_is_finite"))
10249     conv_intrinsic_ieee_builtin (se, expr, BUILT_IN_ISFINITE, 1);
10250   else if (startswith (name, "_gfortran_ieee_unordered"))
10251     conv_intrinsic_ieee_builtin (se, expr, BUILT_IN_ISUNORDERED, 2);
10252   else if (startswith (name, "_gfortran_ieee_is_normal"))
10253     conv_intrinsic_ieee_is_normal (se, expr);
10254   else if (startswith (name, "_gfortran_ieee_is_negative"))
10255     conv_intrinsic_ieee_is_negative (se, expr);
10256   else if (startswith (name, "_gfortran_ieee_copy_sign"))
10257     conv_intrinsic_ieee_copy_sign (se, expr);
10258   else if (startswith (name, "_gfortran_ieee_scalb"))
10259     conv_intrinsic_ieee_scalb (se, expr);
10260   else if (startswith (name, "_gfortran_ieee_next_after"))
10261     conv_intrinsic_ieee_next_after (se, expr);
10262   else if (startswith (name, "_gfortran_ieee_rem"))
10263     conv_intrinsic_ieee_rem (se, expr);
10264   else if (startswith (name, "_gfortran_ieee_logb"))
10265     conv_intrinsic_ieee_logb_rint (se, expr, BUILT_IN_LOGB);
10266   else if (startswith (name, "_gfortran_ieee_rint"))
10267     conv_intrinsic_ieee_logb_rint (se, expr, BUILT_IN_RINT);
10268   else if (startswith (name, "ieee_class_") && ISDIGIT (name[11]))
10269     return conv_intrinsic_ieee_class (se, expr);
10270   else if (startswith (name, "ieee_value_") && ISDIGIT (name[11]))
10271     return conv_intrinsic_ieee_value (se, expr);
10272   else
10273     /* It is not among the functions we translate directly.  We return
10274        false, so a library function call is emitted.  */
10275     return false;
10276 
10277   return true;
10278 }
10279 
10280 
10281 /* Generate a direct call to malloc() for the MALLOC intrinsic.  */
10282 
10283 static void
gfc_conv_intrinsic_malloc(gfc_se * se,gfc_expr * expr)10284 gfc_conv_intrinsic_malloc (gfc_se * se, gfc_expr * expr)
10285 {
10286   tree arg, res, restype;
10287 
10288   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
10289   arg = fold_convert (size_type_node, arg);
10290   res = build_call_expr_loc (input_location,
10291 			     builtin_decl_explicit (BUILT_IN_MALLOC), 1, arg);
10292   restype = gfc_typenode_for_spec (&expr->ts);
10293   se->expr = fold_convert (restype, res);
10294 }
10295 
10296 
10297 /* Generate code for an intrinsic function.  Some map directly to library
10298    calls, others get special handling.  In some cases the name of the function
10299    used depends on the type specifiers.  */
10300 
10301 void
gfc_conv_intrinsic_function(gfc_se * se,gfc_expr * expr)10302 gfc_conv_intrinsic_function (gfc_se * se, gfc_expr * expr)
10303 {
10304   const char *name;
10305   int lib, kind;
10306   tree fndecl;
10307 
10308   name = &expr->value.function.name[2];
10309 
10310   if (expr->rank > 0)
10311     {
10312       lib = gfc_is_intrinsic_libcall (expr);
10313       if (lib != 0)
10314 	{
10315 	  if (lib == 1)
10316 	    se->ignore_optional = 1;
10317 
10318 	  switch (expr->value.function.isym->id)
10319 	    {
10320 	    case GFC_ISYM_EOSHIFT:
10321 	    case GFC_ISYM_PACK:
10322 	    case GFC_ISYM_RESHAPE:
10323 	      /* For all of those the first argument specifies the type and the
10324 		 third is optional.  */
10325 	      conv_generic_with_optional_char_arg (se, expr, 1, 3);
10326 	      break;
10327 
10328 	    case GFC_ISYM_FINDLOC:
10329 	      gfc_conv_intrinsic_findloc (se, expr);
10330 	      break;
10331 
10332 	    case GFC_ISYM_MINLOC:
10333 	      gfc_conv_intrinsic_minmaxloc (se, expr, LT_EXPR);
10334 	      break;
10335 
10336 	    case GFC_ISYM_MAXLOC:
10337 	      gfc_conv_intrinsic_minmaxloc (se, expr, GT_EXPR);
10338 	      break;
10339 
10340 	    default:
10341 	      gfc_conv_intrinsic_funcall (se, expr);
10342 	      break;
10343 	    }
10344 
10345 	  return;
10346 	}
10347     }
10348 
10349   switch (expr->value.function.isym->id)
10350     {
10351     case GFC_ISYM_NONE:
10352       gcc_unreachable ();
10353 
10354     case GFC_ISYM_REPEAT:
10355       gfc_conv_intrinsic_repeat (se, expr);
10356       break;
10357 
10358     case GFC_ISYM_TRIM:
10359       gfc_conv_intrinsic_trim (se, expr);
10360       break;
10361 
10362     case GFC_ISYM_SC_KIND:
10363       gfc_conv_intrinsic_sc_kind (se, expr);
10364       break;
10365 
10366     case GFC_ISYM_SI_KIND:
10367       gfc_conv_intrinsic_si_kind (se, expr);
10368       break;
10369 
10370     case GFC_ISYM_SR_KIND:
10371       gfc_conv_intrinsic_sr_kind (se, expr);
10372       break;
10373 
10374     case GFC_ISYM_EXPONENT:
10375       gfc_conv_intrinsic_exponent (se, expr);
10376       break;
10377 
10378     case GFC_ISYM_SCAN:
10379       kind = expr->value.function.actual->expr->ts.kind;
10380       if (kind == 1)
10381        fndecl = gfor_fndecl_string_scan;
10382       else if (kind == 4)
10383        fndecl = gfor_fndecl_string_scan_char4;
10384       else
10385        gcc_unreachable ();
10386 
10387       gfc_conv_intrinsic_index_scan_verify (se, expr, fndecl);
10388       break;
10389 
10390     case GFC_ISYM_VERIFY:
10391       kind = expr->value.function.actual->expr->ts.kind;
10392       if (kind == 1)
10393        fndecl = gfor_fndecl_string_verify;
10394       else if (kind == 4)
10395        fndecl = gfor_fndecl_string_verify_char4;
10396       else
10397        gcc_unreachable ();
10398 
10399       gfc_conv_intrinsic_index_scan_verify (se, expr, fndecl);
10400       break;
10401 
10402     case GFC_ISYM_ALLOCATED:
10403       gfc_conv_allocated (se, expr);
10404       break;
10405 
10406     case GFC_ISYM_ASSOCIATED:
10407       gfc_conv_associated(se, expr);
10408       break;
10409 
10410     case GFC_ISYM_SAME_TYPE_AS:
10411       gfc_conv_same_type_as (se, expr);
10412       break;
10413 
10414     case GFC_ISYM_ABS:
10415       gfc_conv_intrinsic_abs (se, expr);
10416       break;
10417 
10418     case GFC_ISYM_ADJUSTL:
10419       if (expr->ts.kind == 1)
10420        fndecl = gfor_fndecl_adjustl;
10421       else if (expr->ts.kind == 4)
10422        fndecl = gfor_fndecl_adjustl_char4;
10423       else
10424        gcc_unreachable ();
10425 
10426       gfc_conv_intrinsic_adjust (se, expr, fndecl);
10427       break;
10428 
10429     case GFC_ISYM_ADJUSTR:
10430       if (expr->ts.kind == 1)
10431        fndecl = gfor_fndecl_adjustr;
10432       else if (expr->ts.kind == 4)
10433        fndecl = gfor_fndecl_adjustr_char4;
10434       else
10435        gcc_unreachable ();
10436 
10437       gfc_conv_intrinsic_adjust (se, expr, fndecl);
10438       break;
10439 
10440     case GFC_ISYM_AIMAG:
10441       gfc_conv_intrinsic_imagpart (se, expr);
10442       break;
10443 
10444     case GFC_ISYM_AINT:
10445       gfc_conv_intrinsic_aint (se, expr, RND_TRUNC);
10446       break;
10447 
10448     case GFC_ISYM_ALL:
10449       gfc_conv_intrinsic_anyall (se, expr, EQ_EXPR);
10450       break;
10451 
10452     case GFC_ISYM_ANINT:
10453       gfc_conv_intrinsic_aint (se, expr, RND_ROUND);
10454       break;
10455 
10456     case GFC_ISYM_AND:
10457       gfc_conv_intrinsic_bitop (se, expr, BIT_AND_EXPR);
10458       break;
10459 
10460     case GFC_ISYM_ANY:
10461       gfc_conv_intrinsic_anyall (se, expr, NE_EXPR);
10462       break;
10463 
10464     case GFC_ISYM_ACOSD:
10465     case GFC_ISYM_ASIND:
10466     case GFC_ISYM_ATAND:
10467       gfc_conv_intrinsic_atrigd (se, expr, expr->value.function.isym->id);
10468       break;
10469 
10470     case GFC_ISYM_COTAN:
10471       gfc_conv_intrinsic_cotan (se, expr);
10472       break;
10473 
10474     case GFC_ISYM_COTAND:
10475       gfc_conv_intrinsic_cotand (se, expr);
10476       break;
10477 
10478     case GFC_ISYM_ATAN2D:
10479       gfc_conv_intrinsic_atan2d (se, expr);
10480       break;
10481 
10482     case GFC_ISYM_BTEST:
10483       gfc_conv_intrinsic_btest (se, expr);
10484       break;
10485 
10486     case GFC_ISYM_BGE:
10487       gfc_conv_intrinsic_bitcomp (se, expr, GE_EXPR);
10488       break;
10489 
10490     case GFC_ISYM_BGT:
10491       gfc_conv_intrinsic_bitcomp (se, expr, GT_EXPR);
10492       break;
10493 
10494     case GFC_ISYM_BLE:
10495       gfc_conv_intrinsic_bitcomp (se, expr, LE_EXPR);
10496       break;
10497 
10498     case GFC_ISYM_BLT:
10499       gfc_conv_intrinsic_bitcomp (se, expr, LT_EXPR);
10500       break;
10501 
10502     case GFC_ISYM_C_ASSOCIATED:
10503     case GFC_ISYM_C_FUNLOC:
10504     case GFC_ISYM_C_LOC:
10505       conv_isocbinding_function (se, expr);
10506       break;
10507 
10508     case GFC_ISYM_ACHAR:
10509     case GFC_ISYM_CHAR:
10510       gfc_conv_intrinsic_char (se, expr);
10511       break;
10512 
10513     case GFC_ISYM_CONVERSION:
10514     case GFC_ISYM_DBLE:
10515     case GFC_ISYM_DFLOAT:
10516     case GFC_ISYM_FLOAT:
10517     case GFC_ISYM_LOGICAL:
10518     case GFC_ISYM_REAL:
10519     case GFC_ISYM_REALPART:
10520     case GFC_ISYM_SNGL:
10521       gfc_conv_intrinsic_conversion (se, expr);
10522       break;
10523 
10524       /* Integer conversions are handled separately to make sure we get the
10525          correct rounding mode.  */
10526     case GFC_ISYM_INT:
10527     case GFC_ISYM_INT2:
10528     case GFC_ISYM_INT8:
10529     case GFC_ISYM_LONG:
10530       gfc_conv_intrinsic_int (se, expr, RND_TRUNC);
10531       break;
10532 
10533     case GFC_ISYM_NINT:
10534       gfc_conv_intrinsic_int (se, expr, RND_ROUND);
10535       break;
10536 
10537     case GFC_ISYM_CEILING:
10538       gfc_conv_intrinsic_int (se, expr, RND_CEIL);
10539       break;
10540 
10541     case GFC_ISYM_FLOOR:
10542       gfc_conv_intrinsic_int (se, expr, RND_FLOOR);
10543       break;
10544 
10545     case GFC_ISYM_MOD:
10546       gfc_conv_intrinsic_mod (se, expr, 0);
10547       break;
10548 
10549     case GFC_ISYM_MODULO:
10550       gfc_conv_intrinsic_mod (se, expr, 1);
10551       break;
10552 
10553     case GFC_ISYM_CAF_GET:
10554       gfc_conv_intrinsic_caf_get (se, expr, NULL_TREE, NULL_TREE, NULL_TREE,
10555 				  false, NULL);
10556       break;
10557 
10558     case GFC_ISYM_CMPLX:
10559       gfc_conv_intrinsic_cmplx (se, expr, name[5] == '1');
10560       break;
10561 
10562     case GFC_ISYM_COMMAND_ARGUMENT_COUNT:
10563       gfc_conv_intrinsic_iargc (se, expr);
10564       break;
10565 
10566     case GFC_ISYM_COMPLEX:
10567       gfc_conv_intrinsic_cmplx (se, expr, 1);
10568       break;
10569 
10570     case GFC_ISYM_CONJG:
10571       gfc_conv_intrinsic_conjg (se, expr);
10572       break;
10573 
10574     case GFC_ISYM_COUNT:
10575       gfc_conv_intrinsic_count (se, expr);
10576       break;
10577 
10578     case GFC_ISYM_CTIME:
10579       gfc_conv_intrinsic_ctime (se, expr);
10580       break;
10581 
10582     case GFC_ISYM_DIM:
10583       gfc_conv_intrinsic_dim (se, expr);
10584       break;
10585 
10586     case GFC_ISYM_DOT_PRODUCT:
10587       gfc_conv_intrinsic_dot_product (se, expr);
10588       break;
10589 
10590     case GFC_ISYM_DPROD:
10591       gfc_conv_intrinsic_dprod (se, expr);
10592       break;
10593 
10594     case GFC_ISYM_DSHIFTL:
10595       gfc_conv_intrinsic_dshift (se, expr, true);
10596       break;
10597 
10598     case GFC_ISYM_DSHIFTR:
10599       gfc_conv_intrinsic_dshift (se, expr, false);
10600       break;
10601 
10602     case GFC_ISYM_FDATE:
10603       gfc_conv_intrinsic_fdate (se, expr);
10604       break;
10605 
10606     case GFC_ISYM_FRACTION:
10607       gfc_conv_intrinsic_fraction (se, expr);
10608       break;
10609 
10610     case GFC_ISYM_IALL:
10611       gfc_conv_intrinsic_arith (se, expr, BIT_AND_EXPR, false);
10612       break;
10613 
10614     case GFC_ISYM_IAND:
10615       gfc_conv_intrinsic_bitop (se, expr, BIT_AND_EXPR);
10616       break;
10617 
10618     case GFC_ISYM_IANY:
10619       gfc_conv_intrinsic_arith (se, expr, BIT_IOR_EXPR, false);
10620       break;
10621 
10622     case GFC_ISYM_IBCLR:
10623       gfc_conv_intrinsic_singlebitop (se, expr, 0);
10624       break;
10625 
10626     case GFC_ISYM_IBITS:
10627       gfc_conv_intrinsic_ibits (se, expr);
10628       break;
10629 
10630     case GFC_ISYM_IBSET:
10631       gfc_conv_intrinsic_singlebitop (se, expr, 1);
10632       break;
10633 
10634     case GFC_ISYM_IACHAR:
10635     case GFC_ISYM_ICHAR:
10636       /* We assume ASCII character sequence.  */
10637       gfc_conv_intrinsic_ichar (se, expr);
10638       break;
10639 
10640     case GFC_ISYM_IARGC:
10641       gfc_conv_intrinsic_iargc (se, expr);
10642       break;
10643 
10644     case GFC_ISYM_IEOR:
10645       gfc_conv_intrinsic_bitop (se, expr, BIT_XOR_EXPR);
10646       break;
10647 
10648     case GFC_ISYM_INDEX:
10649       kind = expr->value.function.actual->expr->ts.kind;
10650       if (kind == 1)
10651        fndecl = gfor_fndecl_string_index;
10652       else if (kind == 4)
10653        fndecl = gfor_fndecl_string_index_char4;
10654       else
10655        gcc_unreachable ();
10656 
10657       gfc_conv_intrinsic_index_scan_verify (se, expr, fndecl);
10658       break;
10659 
10660     case GFC_ISYM_IOR:
10661       gfc_conv_intrinsic_bitop (se, expr, BIT_IOR_EXPR);
10662       break;
10663 
10664     case GFC_ISYM_IPARITY:
10665       gfc_conv_intrinsic_arith (se, expr, BIT_XOR_EXPR, false);
10666       break;
10667 
10668     case GFC_ISYM_IS_IOSTAT_END:
10669       gfc_conv_has_intvalue (se, expr, LIBERROR_END);
10670       break;
10671 
10672     case GFC_ISYM_IS_IOSTAT_EOR:
10673       gfc_conv_has_intvalue (se, expr, LIBERROR_EOR);
10674       break;
10675 
10676     case GFC_ISYM_IS_CONTIGUOUS:
10677       gfc_conv_intrinsic_is_contiguous (se, expr);
10678       break;
10679 
10680     case GFC_ISYM_ISNAN:
10681       gfc_conv_intrinsic_isnan (se, expr);
10682       break;
10683 
10684     case GFC_ISYM_KILL:
10685       conv_intrinsic_kill (se, expr);
10686       break;
10687 
10688     case GFC_ISYM_LSHIFT:
10689       gfc_conv_intrinsic_shift (se, expr, false, false);
10690       break;
10691 
10692     case GFC_ISYM_RSHIFT:
10693       gfc_conv_intrinsic_shift (se, expr, true, true);
10694       break;
10695 
10696     case GFC_ISYM_SHIFTA:
10697       gfc_conv_intrinsic_shift (se, expr, true, true);
10698       break;
10699 
10700     case GFC_ISYM_SHIFTL:
10701       gfc_conv_intrinsic_shift (se, expr, false, false);
10702       break;
10703 
10704     case GFC_ISYM_SHIFTR:
10705       gfc_conv_intrinsic_shift (se, expr, true, false);
10706       break;
10707 
10708     case GFC_ISYM_ISHFT:
10709       gfc_conv_intrinsic_ishft (se, expr);
10710       break;
10711 
10712     case GFC_ISYM_ISHFTC:
10713       gfc_conv_intrinsic_ishftc (se, expr);
10714       break;
10715 
10716     case GFC_ISYM_LEADZ:
10717       gfc_conv_intrinsic_leadz (se, expr);
10718       break;
10719 
10720     case GFC_ISYM_TRAILZ:
10721       gfc_conv_intrinsic_trailz (se, expr);
10722       break;
10723 
10724     case GFC_ISYM_POPCNT:
10725       gfc_conv_intrinsic_popcnt_poppar (se, expr, 0);
10726       break;
10727 
10728     case GFC_ISYM_POPPAR:
10729       gfc_conv_intrinsic_popcnt_poppar (se, expr, 1);
10730       break;
10731 
10732     case GFC_ISYM_LBOUND:
10733       gfc_conv_intrinsic_bound (se, expr, GFC_ISYM_LBOUND);
10734       break;
10735 
10736     case GFC_ISYM_LCOBOUND:
10737       conv_intrinsic_cobound (se, expr);
10738       break;
10739 
10740     case GFC_ISYM_TRANSPOSE:
10741       /* The scalarizer has already been set up for reversed dimension access
10742 	 order ; now we just get the argument value normally.  */
10743       gfc_conv_expr (se, expr->value.function.actual->expr);
10744       break;
10745 
10746     case GFC_ISYM_LEN:
10747       gfc_conv_intrinsic_len (se, expr);
10748       break;
10749 
10750     case GFC_ISYM_LEN_TRIM:
10751       gfc_conv_intrinsic_len_trim (se, expr);
10752       break;
10753 
10754     case GFC_ISYM_LGE:
10755       gfc_conv_intrinsic_strcmp (se, expr, GE_EXPR);
10756       break;
10757 
10758     case GFC_ISYM_LGT:
10759       gfc_conv_intrinsic_strcmp (se, expr, GT_EXPR);
10760       break;
10761 
10762     case GFC_ISYM_LLE:
10763       gfc_conv_intrinsic_strcmp (se, expr, LE_EXPR);
10764       break;
10765 
10766     case GFC_ISYM_LLT:
10767       gfc_conv_intrinsic_strcmp (se, expr, LT_EXPR);
10768       break;
10769 
10770     case GFC_ISYM_MALLOC:
10771       gfc_conv_intrinsic_malloc (se, expr);
10772       break;
10773 
10774     case GFC_ISYM_MASKL:
10775       gfc_conv_intrinsic_mask (se, expr, 1);
10776       break;
10777 
10778     case GFC_ISYM_MASKR:
10779       gfc_conv_intrinsic_mask (se, expr, 0);
10780       break;
10781 
10782     case GFC_ISYM_MAX:
10783       if (expr->ts.type == BT_CHARACTER)
10784 	gfc_conv_intrinsic_minmax_char (se, expr, 1);
10785       else
10786 	gfc_conv_intrinsic_minmax (se, expr, GT_EXPR);
10787       break;
10788 
10789     case GFC_ISYM_MAXLOC:
10790       gfc_conv_intrinsic_minmaxloc (se, expr, GT_EXPR);
10791       break;
10792 
10793     case GFC_ISYM_FINDLOC:
10794       gfc_conv_intrinsic_findloc (se, expr);
10795       break;
10796 
10797     case GFC_ISYM_MAXVAL:
10798       gfc_conv_intrinsic_minmaxval (se, expr, GT_EXPR);
10799       break;
10800 
10801     case GFC_ISYM_MERGE:
10802       gfc_conv_intrinsic_merge (se, expr);
10803       break;
10804 
10805     case GFC_ISYM_MERGE_BITS:
10806       gfc_conv_intrinsic_merge_bits (se, expr);
10807       break;
10808 
10809     case GFC_ISYM_MIN:
10810       if (expr->ts.type == BT_CHARACTER)
10811 	gfc_conv_intrinsic_minmax_char (se, expr, -1);
10812       else
10813 	gfc_conv_intrinsic_minmax (se, expr, LT_EXPR);
10814       break;
10815 
10816     case GFC_ISYM_MINLOC:
10817       gfc_conv_intrinsic_minmaxloc (se, expr, LT_EXPR);
10818       break;
10819 
10820     case GFC_ISYM_MINVAL:
10821       gfc_conv_intrinsic_minmaxval (se, expr, LT_EXPR);
10822       break;
10823 
10824     case GFC_ISYM_NEAREST:
10825       gfc_conv_intrinsic_nearest (se, expr);
10826       break;
10827 
10828     case GFC_ISYM_NORM2:
10829       gfc_conv_intrinsic_arith (se, expr, PLUS_EXPR, true);
10830       break;
10831 
10832     case GFC_ISYM_NOT:
10833       gfc_conv_intrinsic_not (se, expr);
10834       break;
10835 
10836     case GFC_ISYM_OR:
10837       gfc_conv_intrinsic_bitop (se, expr, BIT_IOR_EXPR);
10838       break;
10839 
10840     case GFC_ISYM_PARITY:
10841       gfc_conv_intrinsic_arith (se, expr, NE_EXPR, false);
10842       break;
10843 
10844     case GFC_ISYM_PRESENT:
10845       gfc_conv_intrinsic_present (se, expr);
10846       break;
10847 
10848     case GFC_ISYM_PRODUCT:
10849       gfc_conv_intrinsic_arith (se, expr, MULT_EXPR, false);
10850       break;
10851 
10852     case GFC_ISYM_RANK:
10853       gfc_conv_intrinsic_rank (se, expr);
10854       break;
10855 
10856     case GFC_ISYM_RRSPACING:
10857       gfc_conv_intrinsic_rrspacing (se, expr);
10858       break;
10859 
10860     case GFC_ISYM_SET_EXPONENT:
10861       gfc_conv_intrinsic_set_exponent (se, expr);
10862       break;
10863 
10864     case GFC_ISYM_SCALE:
10865       gfc_conv_intrinsic_scale (se, expr);
10866       break;
10867 
10868     case GFC_ISYM_SHAPE:
10869       gfc_conv_intrinsic_bound (se, expr, GFC_ISYM_SHAPE);
10870       break;
10871 
10872     case GFC_ISYM_SIGN:
10873       gfc_conv_intrinsic_sign (se, expr);
10874       break;
10875 
10876     case GFC_ISYM_SIZE:
10877       gfc_conv_intrinsic_size (se, expr);
10878       break;
10879 
10880     case GFC_ISYM_SIZEOF:
10881     case GFC_ISYM_C_SIZEOF:
10882       gfc_conv_intrinsic_sizeof (se, expr);
10883       break;
10884 
10885     case GFC_ISYM_STORAGE_SIZE:
10886       gfc_conv_intrinsic_storage_size (se, expr);
10887       break;
10888 
10889     case GFC_ISYM_SPACING:
10890       gfc_conv_intrinsic_spacing (se, expr);
10891       break;
10892 
10893     case GFC_ISYM_STRIDE:
10894       conv_intrinsic_stride (se, expr);
10895       break;
10896 
10897     case GFC_ISYM_SUM:
10898       gfc_conv_intrinsic_arith (se, expr, PLUS_EXPR, false);
10899       break;
10900 
10901     case GFC_ISYM_TEAM_NUMBER:
10902       conv_intrinsic_team_number (se, expr);
10903       break;
10904 
10905     case GFC_ISYM_TRANSFER:
10906       if (se->ss && se->ss->info->useflags)
10907 	/* Access the previously obtained result.  */
10908 	gfc_conv_tmp_array_ref (se);
10909       else
10910 	gfc_conv_intrinsic_transfer (se, expr);
10911       break;
10912 
10913     case GFC_ISYM_TTYNAM:
10914       gfc_conv_intrinsic_ttynam (se, expr);
10915       break;
10916 
10917     case GFC_ISYM_UBOUND:
10918       gfc_conv_intrinsic_bound (se, expr, GFC_ISYM_UBOUND);
10919       break;
10920 
10921     case GFC_ISYM_UCOBOUND:
10922       conv_intrinsic_cobound (se, expr);
10923       break;
10924 
10925     case GFC_ISYM_XOR:
10926       gfc_conv_intrinsic_bitop (se, expr, BIT_XOR_EXPR);
10927       break;
10928 
10929     case GFC_ISYM_LOC:
10930       gfc_conv_intrinsic_loc (se, expr);
10931       break;
10932 
10933     case GFC_ISYM_THIS_IMAGE:
10934       /* For num_images() == 1, handle as LCOBOUND.  */
10935       if (expr->value.function.actual->expr
10936 	  && flag_coarray == GFC_FCOARRAY_SINGLE)
10937 	conv_intrinsic_cobound (se, expr);
10938       else
10939 	trans_this_image (se, expr);
10940       break;
10941 
10942     case GFC_ISYM_IMAGE_INDEX:
10943       trans_image_index (se, expr);
10944       break;
10945 
10946     case GFC_ISYM_IMAGE_STATUS:
10947       conv_intrinsic_image_status (se, expr);
10948       break;
10949 
10950     case GFC_ISYM_NUM_IMAGES:
10951       trans_num_images (se, expr);
10952       break;
10953 
10954     case GFC_ISYM_ACCESS:
10955     case GFC_ISYM_CHDIR:
10956     case GFC_ISYM_CHMOD:
10957     case GFC_ISYM_DTIME:
10958     case GFC_ISYM_ETIME:
10959     case GFC_ISYM_EXTENDS_TYPE_OF:
10960     case GFC_ISYM_FGET:
10961     case GFC_ISYM_FGETC:
10962     case GFC_ISYM_FNUM:
10963     case GFC_ISYM_FPUT:
10964     case GFC_ISYM_FPUTC:
10965     case GFC_ISYM_FSTAT:
10966     case GFC_ISYM_FTELL:
10967     case GFC_ISYM_GETCWD:
10968     case GFC_ISYM_GETGID:
10969     case GFC_ISYM_GETPID:
10970     case GFC_ISYM_GETUID:
10971     case GFC_ISYM_HOSTNM:
10972     case GFC_ISYM_IERRNO:
10973     case GFC_ISYM_IRAND:
10974     case GFC_ISYM_ISATTY:
10975     case GFC_ISYM_JN2:
10976     case GFC_ISYM_LINK:
10977     case GFC_ISYM_LSTAT:
10978     case GFC_ISYM_MATMUL:
10979     case GFC_ISYM_MCLOCK:
10980     case GFC_ISYM_MCLOCK8:
10981     case GFC_ISYM_RAND:
10982     case GFC_ISYM_RENAME:
10983     case GFC_ISYM_SECOND:
10984     case GFC_ISYM_SECNDS:
10985     case GFC_ISYM_SIGNAL:
10986     case GFC_ISYM_STAT:
10987     case GFC_ISYM_SYMLNK:
10988     case GFC_ISYM_SYSTEM:
10989     case GFC_ISYM_TIME:
10990     case GFC_ISYM_TIME8:
10991     case GFC_ISYM_UMASK:
10992     case GFC_ISYM_UNLINK:
10993     case GFC_ISYM_YN2:
10994       gfc_conv_intrinsic_funcall (se, expr);
10995       break;
10996 
10997     case GFC_ISYM_EOSHIFT:
10998     case GFC_ISYM_PACK:
10999     case GFC_ISYM_RESHAPE:
11000       /* For those, expr->rank should always be >0 and thus the if above the
11001 	 switch should have matched.  */
11002       gcc_unreachable ();
11003       break;
11004 
11005     default:
11006       gfc_conv_intrinsic_lib_function (se, expr);
11007       break;
11008     }
11009 }
11010 
11011 
11012 static gfc_ss *
walk_inline_intrinsic_transpose(gfc_ss * ss,gfc_expr * expr)11013 walk_inline_intrinsic_transpose (gfc_ss *ss, gfc_expr *expr)
11014 {
11015   gfc_ss *arg_ss, *tmp_ss;
11016   gfc_actual_arglist *arg;
11017 
11018   arg = expr->value.function.actual;
11019 
11020   gcc_assert (arg->expr);
11021 
11022   arg_ss = gfc_walk_subexpr (gfc_ss_terminator, arg->expr);
11023   gcc_assert (arg_ss != gfc_ss_terminator);
11024 
11025   for (tmp_ss = arg_ss; ; tmp_ss = tmp_ss->next)
11026     {
11027       if (tmp_ss->info->type != GFC_SS_SCALAR
11028 	  && tmp_ss->info->type != GFC_SS_REFERENCE)
11029 	{
11030 	  gcc_assert (tmp_ss->dimen == 2);
11031 
11032 	  /* We just invert dimensions.  */
11033 	  std::swap (tmp_ss->dim[0], tmp_ss->dim[1]);
11034 	}
11035 
11036       /* Stop when tmp_ss points to the last valid element of the chain...  */
11037       if (tmp_ss->next == gfc_ss_terminator)
11038 	break;
11039     }
11040 
11041   /* ... so that we can attach the rest of the chain to it.  */
11042   tmp_ss->next = ss;
11043 
11044   return arg_ss;
11045 }
11046 
11047 
11048 /* Move the given dimension of the given gfc_ss list to a nested gfc_ss list.
11049    This has the side effect of reversing the nested list, so there is no
11050    need to call gfc_reverse_ss on it (the given list is assumed not to be
11051    reversed yet).   */
11052 
11053 static gfc_ss *
nest_loop_dimension(gfc_ss * ss,int dim)11054 nest_loop_dimension (gfc_ss *ss, int dim)
11055 {
11056   int ss_dim, i;
11057   gfc_ss *new_ss, *prev_ss = gfc_ss_terminator;
11058   gfc_loopinfo *new_loop;
11059 
11060   gcc_assert (ss != gfc_ss_terminator);
11061 
11062   for (; ss != gfc_ss_terminator; ss = ss->next)
11063     {
11064       new_ss = gfc_get_ss ();
11065       new_ss->next = prev_ss;
11066       new_ss->parent = ss;
11067       new_ss->info = ss->info;
11068       new_ss->info->refcount++;
11069       if (ss->dimen != 0)
11070 	{
11071 	  gcc_assert (ss->info->type != GFC_SS_SCALAR
11072 		      && ss->info->type != GFC_SS_REFERENCE);
11073 
11074 	  new_ss->dimen = 1;
11075 	  new_ss->dim[0] = ss->dim[dim];
11076 
11077 	  gcc_assert (dim < ss->dimen);
11078 
11079 	  ss_dim = --ss->dimen;
11080 	  for (i = dim; i < ss_dim; i++)
11081 	    ss->dim[i] = ss->dim[i + 1];
11082 
11083 	  ss->dim[ss_dim] = 0;
11084 	}
11085       prev_ss = new_ss;
11086 
11087       if (ss->nested_ss)
11088 	{
11089 	  ss->nested_ss->parent = new_ss;
11090 	  new_ss->nested_ss = ss->nested_ss;
11091 	}
11092       ss->nested_ss = new_ss;
11093     }
11094 
11095   new_loop = gfc_get_loopinfo ();
11096   gfc_init_loopinfo (new_loop);
11097 
11098   gcc_assert (prev_ss != NULL);
11099   gcc_assert (prev_ss != gfc_ss_terminator);
11100   gfc_add_ss_to_loop (new_loop, prev_ss);
11101   return new_ss->parent;
11102 }
11103 
11104 
11105 /* Create the gfc_ss list for the SUM/PRODUCT arguments when the function
11106    is to be inlined.  */
11107 
11108 static gfc_ss *
walk_inline_intrinsic_arith(gfc_ss * ss,gfc_expr * expr)11109 walk_inline_intrinsic_arith (gfc_ss *ss, gfc_expr *expr)
11110 {
11111   gfc_ss *tmp_ss, *tail, *array_ss;
11112   gfc_actual_arglist *arg1, *arg2, *arg3;
11113   int sum_dim;
11114   bool scalar_mask = false;
11115 
11116   /* The rank of the result will be determined later.  */
11117   arg1 = expr->value.function.actual;
11118   arg2 = arg1->next;
11119   arg3 = arg2->next;
11120   gcc_assert (arg3 != NULL);
11121 
11122   if (expr->rank == 0)
11123     return ss;
11124 
11125   tmp_ss = gfc_ss_terminator;
11126 
11127   if (arg3->expr)
11128     {
11129       gfc_ss *mask_ss;
11130 
11131       mask_ss = gfc_walk_subexpr (tmp_ss, arg3->expr);
11132       if (mask_ss == tmp_ss)
11133 	scalar_mask = 1;
11134 
11135       tmp_ss = mask_ss;
11136     }
11137 
11138   array_ss = gfc_walk_subexpr (tmp_ss, arg1->expr);
11139   gcc_assert (array_ss != tmp_ss);
11140 
11141   /* Odd thing: If the mask is scalar, it is used by the frontend after
11142      the array (to make an if around the nested loop). Thus it shall
11143      be after array_ss once the gfc_ss list is reversed.  */
11144   if (scalar_mask)
11145     tmp_ss = gfc_get_scalar_ss (array_ss, arg3->expr);
11146   else
11147     tmp_ss = array_ss;
11148 
11149   /* "Hide" the dimension on which we will sum in the first arg's scalarization
11150      chain.  */
11151   sum_dim = mpz_get_si (arg2->expr->value.integer) - 1;
11152   tail = nest_loop_dimension (tmp_ss, sum_dim);
11153   tail->next = ss;
11154 
11155   return tmp_ss;
11156 }
11157 
11158 
11159 static gfc_ss *
walk_inline_intrinsic_function(gfc_ss * ss,gfc_expr * expr)11160 walk_inline_intrinsic_function (gfc_ss * ss, gfc_expr * expr)
11161 {
11162 
11163   switch (expr->value.function.isym->id)
11164     {
11165       case GFC_ISYM_PRODUCT:
11166       case GFC_ISYM_SUM:
11167 	return walk_inline_intrinsic_arith (ss, expr);
11168 
11169       case GFC_ISYM_TRANSPOSE:
11170 	return walk_inline_intrinsic_transpose (ss, expr);
11171 
11172       default:
11173 	gcc_unreachable ();
11174     }
11175   gcc_unreachable ();
11176 }
11177 
11178 
11179 /* This generates code to execute before entering the scalarization loop.
11180    Currently does nothing.  */
11181 
11182 void
gfc_add_intrinsic_ss_code(gfc_loopinfo * loop ATTRIBUTE_UNUSED,gfc_ss * ss)11183 gfc_add_intrinsic_ss_code (gfc_loopinfo * loop ATTRIBUTE_UNUSED, gfc_ss * ss)
11184 {
11185   switch (ss->info->expr->value.function.isym->id)
11186     {
11187     case GFC_ISYM_UBOUND:
11188     case GFC_ISYM_LBOUND:
11189     case GFC_ISYM_UCOBOUND:
11190     case GFC_ISYM_LCOBOUND:
11191     case GFC_ISYM_THIS_IMAGE:
11192     case GFC_ISYM_SHAPE:
11193       break;
11194 
11195     default:
11196       gcc_unreachable ();
11197     }
11198 }
11199 
11200 
11201 /* The LBOUND, LCOBOUND, UBOUND, UCOBOUND, and SHAPE intrinsics with
11202    one parameter are expanded into code inside the scalarization loop.  */
11203 
11204 static gfc_ss *
gfc_walk_intrinsic_bound(gfc_ss * ss,gfc_expr * expr)11205 gfc_walk_intrinsic_bound (gfc_ss * ss, gfc_expr * expr)
11206 {
11207   if (expr->value.function.actual->expr->ts.type == BT_CLASS)
11208     gfc_add_class_array_ref (expr->value.function.actual->expr);
11209 
11210   /* The two argument version returns a scalar.  */
11211   if (expr->value.function.isym->id != GFC_ISYM_SHAPE
11212       && expr->value.function.actual->next->expr)
11213     return ss;
11214 
11215   return gfc_get_array_ss (ss, expr, 1, GFC_SS_INTRINSIC);
11216 }
11217 
11218 
11219 /* Walk an intrinsic array libcall.  */
11220 
11221 static gfc_ss *
gfc_walk_intrinsic_libfunc(gfc_ss * ss,gfc_expr * expr)11222 gfc_walk_intrinsic_libfunc (gfc_ss * ss, gfc_expr * expr)
11223 {
11224   gcc_assert (expr->rank > 0);
11225   return gfc_get_array_ss (ss, expr, expr->rank, GFC_SS_FUNCTION);
11226 }
11227 
11228 
11229 /* Return whether the function call expression EXPR will be expanded
11230    inline by gfc_conv_intrinsic_function.  */
11231 
11232 bool
gfc_inline_intrinsic_function_p(gfc_expr * expr)11233 gfc_inline_intrinsic_function_p (gfc_expr *expr)
11234 {
11235   gfc_actual_arglist *args, *dim_arg, *mask_arg;
11236   gfc_expr *maskexpr;
11237 
11238   if (!expr->value.function.isym)
11239     return false;
11240 
11241   switch (expr->value.function.isym->id)
11242     {
11243     case GFC_ISYM_PRODUCT:
11244     case GFC_ISYM_SUM:
11245       /* Disable inline expansion if code size matters.  */
11246       if (optimize_size)
11247 	return false;
11248 
11249       args = expr->value.function.actual;
11250       dim_arg = args->next;
11251 
11252       /* We need to be able to subset the SUM argument at compile-time.  */
11253       if (dim_arg->expr && dim_arg->expr->expr_type != EXPR_CONSTANT)
11254 	return false;
11255 
11256       /* FIXME: If MASK is optional for a more than two-dimensional
11257 	 argument, the scalarizer gets confused if the mask is
11258 	 absent.  See PR 82995.  For now, fall back to the library
11259 	 function.  */
11260 
11261       mask_arg = dim_arg->next;
11262       maskexpr = mask_arg->expr;
11263 
11264       if (expr->rank > 0 && maskexpr && maskexpr->expr_type == EXPR_VARIABLE
11265 	  && maskexpr->symtree->n.sym->attr.dummy
11266 	  && maskexpr->symtree->n.sym->attr.optional)
11267 	return false;
11268 
11269       return true;
11270 
11271     case GFC_ISYM_TRANSPOSE:
11272       return true;
11273 
11274     default:
11275       return false;
11276     }
11277 }
11278 
11279 
11280 /* Returns nonzero if the specified intrinsic function call maps directly to
11281    an external library call.  Should only be used for functions that return
11282    arrays.  */
11283 
11284 int
gfc_is_intrinsic_libcall(gfc_expr * expr)11285 gfc_is_intrinsic_libcall (gfc_expr * expr)
11286 {
11287   gcc_assert (expr->expr_type == EXPR_FUNCTION && expr->value.function.isym);
11288   gcc_assert (expr->rank > 0);
11289 
11290   if (gfc_inline_intrinsic_function_p (expr))
11291     return 0;
11292 
11293   switch (expr->value.function.isym->id)
11294     {
11295     case GFC_ISYM_ALL:
11296     case GFC_ISYM_ANY:
11297     case GFC_ISYM_COUNT:
11298     case GFC_ISYM_FINDLOC:
11299     case GFC_ISYM_JN2:
11300     case GFC_ISYM_IANY:
11301     case GFC_ISYM_IALL:
11302     case GFC_ISYM_IPARITY:
11303     case GFC_ISYM_MATMUL:
11304     case GFC_ISYM_MAXLOC:
11305     case GFC_ISYM_MAXVAL:
11306     case GFC_ISYM_MINLOC:
11307     case GFC_ISYM_MINVAL:
11308     case GFC_ISYM_NORM2:
11309     case GFC_ISYM_PARITY:
11310     case GFC_ISYM_PRODUCT:
11311     case GFC_ISYM_SUM:
11312     case GFC_ISYM_SPREAD:
11313     case GFC_ISYM_YN2:
11314       /* Ignore absent optional parameters.  */
11315       return 1;
11316 
11317     case GFC_ISYM_CSHIFT:
11318     case GFC_ISYM_EOSHIFT:
11319     case GFC_ISYM_GET_TEAM:
11320     case GFC_ISYM_FAILED_IMAGES:
11321     case GFC_ISYM_STOPPED_IMAGES:
11322     case GFC_ISYM_PACK:
11323     case GFC_ISYM_RESHAPE:
11324     case GFC_ISYM_UNPACK:
11325       /* Pass absent optional parameters.  */
11326       return 2;
11327 
11328     default:
11329       return 0;
11330     }
11331 }
11332 
11333 /* Walk an intrinsic function.  */
11334 gfc_ss *
gfc_walk_intrinsic_function(gfc_ss * ss,gfc_expr * expr,gfc_intrinsic_sym * isym)11335 gfc_walk_intrinsic_function (gfc_ss * ss, gfc_expr * expr,
11336 			     gfc_intrinsic_sym * isym)
11337 {
11338   gcc_assert (isym);
11339 
11340   if (isym->elemental)
11341     return gfc_walk_elemental_function_args (ss, expr->value.function.actual,
11342 					     expr->value.function.isym,
11343 					     GFC_SS_SCALAR);
11344 
11345   if (expr->rank == 0)
11346     return ss;
11347 
11348   if (gfc_inline_intrinsic_function_p (expr))
11349     return walk_inline_intrinsic_function (ss, expr);
11350 
11351   if (gfc_is_intrinsic_libcall (expr))
11352     return gfc_walk_intrinsic_libfunc (ss, expr);
11353 
11354   /* Special cases.  */
11355   switch (isym->id)
11356     {
11357     case GFC_ISYM_LBOUND:
11358     case GFC_ISYM_LCOBOUND:
11359     case GFC_ISYM_UBOUND:
11360     case GFC_ISYM_UCOBOUND:
11361     case GFC_ISYM_THIS_IMAGE:
11362     case GFC_ISYM_SHAPE:
11363       return gfc_walk_intrinsic_bound (ss, expr);
11364 
11365     case GFC_ISYM_TRANSFER:
11366     case GFC_ISYM_CAF_GET:
11367       return gfc_walk_intrinsic_libfunc (ss, expr);
11368 
11369     default:
11370       /* This probably meant someone forgot to add an intrinsic to the above
11371          list(s) when they implemented it, or something's gone horribly
11372 	 wrong.  */
11373       gcc_unreachable ();
11374     }
11375 }
11376 
11377 static tree
conv_co_collective(gfc_code * code)11378 conv_co_collective (gfc_code *code)
11379 {
11380   gfc_se argse;
11381   stmtblock_t block, post_block;
11382   tree fndecl, array = NULL_TREE, strlen, image_index, stat, errmsg, errmsg_len;
11383   gfc_expr *image_idx_expr, *stat_expr, *errmsg_expr, *opr_expr;
11384 
11385   gfc_start_block (&block);
11386   gfc_init_block (&post_block);
11387 
11388   if (code->resolved_isym->id == GFC_ISYM_CO_REDUCE)
11389     {
11390       opr_expr = code->ext.actual->next->expr;
11391       image_idx_expr = code->ext.actual->next->next->expr;
11392       stat_expr = code->ext.actual->next->next->next->expr;
11393       errmsg_expr = code->ext.actual->next->next->next->next->expr;
11394     }
11395   else
11396     {
11397       opr_expr = NULL;
11398       image_idx_expr = code->ext.actual->next->expr;
11399       stat_expr = code->ext.actual->next->next->expr;
11400       errmsg_expr = code->ext.actual->next->next->next->expr;
11401     }
11402 
11403   /* stat.  */
11404   if (stat_expr)
11405     {
11406       gfc_init_se (&argse, NULL);
11407       gfc_conv_expr (&argse, stat_expr);
11408       gfc_add_block_to_block (&block, &argse.pre);
11409       gfc_add_block_to_block (&post_block, &argse.post);
11410       stat = argse.expr;
11411       if (flag_coarray != GFC_FCOARRAY_SINGLE)
11412 	stat = gfc_build_addr_expr (NULL_TREE, stat);
11413     }
11414   else if (flag_coarray == GFC_FCOARRAY_SINGLE)
11415     stat = NULL_TREE;
11416   else
11417     stat = null_pointer_node;
11418 
11419   /* Early exit for GFC_FCOARRAY_SINGLE.  */
11420   if (flag_coarray == GFC_FCOARRAY_SINGLE)
11421     {
11422       if (stat != NULL_TREE)
11423 	{
11424 	  /* For optional stats, check the pointer is valid before zero'ing.  */
11425 	  if (gfc_expr_attr (stat_expr).optional)
11426 	    {
11427 	      tree tmp;
11428 	      stmtblock_t ass_block;
11429 	      gfc_start_block (&ass_block);
11430 	      gfc_add_modify (&ass_block, stat,
11431 			      fold_convert (TREE_TYPE (stat),
11432 					    integer_zero_node));
11433 	      tmp = fold_build2 (NE_EXPR, logical_type_node,
11434 				 gfc_build_addr_expr (NULL_TREE, stat),
11435 				 null_pointer_node);
11436 	      tmp = fold_build3 (COND_EXPR, void_type_node, tmp,
11437 				 gfc_finish_block (&ass_block),
11438 				 build_empty_stmt (input_location));
11439 	      gfc_add_expr_to_block (&block, tmp);
11440 	    }
11441 	  else
11442 	    gfc_add_modify (&block, stat,
11443 			    fold_convert (TREE_TYPE (stat), integer_zero_node));
11444 	}
11445       return gfc_finish_block (&block);
11446     }
11447 
11448   gfc_symbol *derived = code->ext.actual->expr->ts.type == BT_DERIVED
11449     ? code->ext.actual->expr->ts.u.derived : NULL;
11450 
11451   /* Handle the array.  */
11452   gfc_init_se (&argse, NULL);
11453   if (!derived || !derived->attr.alloc_comp
11454       || code->resolved_isym->id != GFC_ISYM_CO_BROADCAST)
11455     {
11456       if (code->ext.actual->expr->rank == 0)
11457 	{
11458 	  symbol_attribute attr;
11459 	  gfc_clear_attr (&attr);
11460 	  gfc_init_se (&argse, NULL);
11461 	  gfc_conv_expr (&argse, code->ext.actual->expr);
11462 	  gfc_add_block_to_block (&block, &argse.pre);
11463 	  gfc_add_block_to_block (&post_block, &argse.post);
11464 	  array = gfc_conv_scalar_to_descriptor (&argse, argse.expr, attr);
11465 	  array = gfc_build_addr_expr (NULL_TREE, array);
11466 	}
11467       else
11468 	{
11469 	  argse.want_pointer = 1;
11470 	  gfc_conv_expr_descriptor (&argse, code->ext.actual->expr);
11471 	  array = argse.expr;
11472 	}
11473     }
11474 
11475   gfc_add_block_to_block (&block, &argse.pre);
11476   gfc_add_block_to_block (&post_block, &argse.post);
11477 
11478   if (code->ext.actual->expr->ts.type == BT_CHARACTER)
11479     strlen = argse.string_length;
11480   else
11481     strlen = integer_zero_node;
11482 
11483   /* image_index.  */
11484   if (image_idx_expr)
11485     {
11486       gfc_init_se (&argse, NULL);
11487       gfc_conv_expr (&argse, image_idx_expr);
11488       gfc_add_block_to_block (&block, &argse.pre);
11489       gfc_add_block_to_block (&post_block, &argse.post);
11490       image_index = fold_convert (integer_type_node, argse.expr);
11491     }
11492   else
11493     image_index = integer_zero_node;
11494 
11495   /* errmsg.  */
11496   if (errmsg_expr)
11497     {
11498       gfc_init_se (&argse, NULL);
11499       gfc_conv_expr (&argse, errmsg_expr);
11500       gfc_add_block_to_block (&block, &argse.pre);
11501       gfc_add_block_to_block (&post_block, &argse.post);
11502       errmsg = argse.expr;
11503       errmsg_len = fold_convert (size_type_node, argse.string_length);
11504     }
11505   else
11506     {
11507       errmsg = null_pointer_node;
11508       errmsg_len = build_zero_cst (size_type_node);
11509     }
11510 
11511   /* Generate the function call.  */
11512   switch (code->resolved_isym->id)
11513     {
11514     case GFC_ISYM_CO_BROADCAST:
11515       fndecl = gfor_fndecl_co_broadcast;
11516       break;
11517     case GFC_ISYM_CO_MAX:
11518       fndecl = gfor_fndecl_co_max;
11519       break;
11520     case GFC_ISYM_CO_MIN:
11521       fndecl = gfor_fndecl_co_min;
11522       break;
11523     case GFC_ISYM_CO_REDUCE:
11524       fndecl = gfor_fndecl_co_reduce;
11525       break;
11526     case GFC_ISYM_CO_SUM:
11527       fndecl = gfor_fndecl_co_sum;
11528       break;
11529     default:
11530       gcc_unreachable ();
11531     }
11532 
11533   if (derived && derived->attr.alloc_comp
11534       && code->resolved_isym->id == GFC_ISYM_CO_BROADCAST)
11535     /* The derived type has the attribute 'alloc_comp'.  */
11536     {
11537       tree tmp = gfc_bcast_alloc_comp (derived, code->ext.actual->expr,
11538 				       code->ext.actual->expr->rank,
11539 				       image_index, stat, errmsg, errmsg_len);
11540       gfc_add_expr_to_block (&block, tmp);
11541     }
11542   else
11543     {
11544       if (code->resolved_isym->id == GFC_ISYM_CO_SUM
11545 	  || code->resolved_isym->id == GFC_ISYM_CO_BROADCAST)
11546 	fndecl = build_call_expr_loc (input_location, fndecl, 5, array,
11547 				      image_index, stat, errmsg, errmsg_len);
11548       else if (code->resolved_isym->id != GFC_ISYM_CO_REDUCE)
11549 	fndecl = build_call_expr_loc (input_location, fndecl, 6, array,
11550 				      image_index, stat, errmsg,
11551 				      strlen, errmsg_len);
11552       else
11553 	{
11554 	  tree opr, opr_flags;
11555 
11556 	  // FIXME: Handle TS29113's bind(C) strings with descriptor.
11557 	  int opr_flag_int;
11558 	  if (gfc_is_proc_ptr_comp (opr_expr))
11559 	    {
11560 	      gfc_symbol *sym = gfc_get_proc_ptr_comp (opr_expr)->ts.interface;
11561 	      opr_flag_int = sym->attr.dimension
11562 		|| (sym->ts.type == BT_CHARACTER
11563 		    && !sym->attr.is_bind_c)
11564 		? GFC_CAF_BYREF : 0;
11565 	      opr_flag_int |= opr_expr->ts.type == BT_CHARACTER
11566 		&& !sym->attr.is_bind_c
11567 		? GFC_CAF_HIDDENLEN : 0;
11568 	      opr_flag_int |= sym->formal->sym->attr.value
11569 		? GFC_CAF_ARG_VALUE : 0;
11570 	    }
11571 	  else
11572 	    {
11573 	      opr_flag_int = gfc_return_by_reference (opr_expr->symtree->n.sym)
11574 		? GFC_CAF_BYREF : 0;
11575 	      opr_flag_int |= opr_expr->ts.type == BT_CHARACTER
11576 		&& !opr_expr->symtree->n.sym->attr.is_bind_c
11577 		? GFC_CAF_HIDDENLEN : 0;
11578 	      opr_flag_int |= opr_expr->symtree->n.sym->formal->sym->attr.value
11579 		? GFC_CAF_ARG_VALUE : 0;
11580 	    }
11581 	  opr_flags = build_int_cst (integer_type_node, opr_flag_int);
11582 	  gfc_conv_expr (&argse, opr_expr);
11583 	  opr = argse.expr;
11584 	  fndecl = build_call_expr_loc (input_location, fndecl, 8, array, opr,
11585 					opr_flags, image_index, stat, errmsg,
11586 					strlen, errmsg_len);
11587 	}
11588     }
11589 
11590   gfc_add_expr_to_block (&block, fndecl);
11591   gfc_add_block_to_block (&block, &post_block);
11592 
11593   return gfc_finish_block (&block);
11594 }
11595 
11596 
11597 static tree
conv_intrinsic_atomic_op(gfc_code * code)11598 conv_intrinsic_atomic_op (gfc_code *code)
11599 {
11600   gfc_se argse;
11601   tree tmp, atom, value, old = NULL_TREE, stat = NULL_TREE;
11602   stmtblock_t block, post_block;
11603   gfc_expr *atom_expr = code->ext.actual->expr;
11604   gfc_expr *stat_expr;
11605   built_in_function fn;
11606 
11607   if (atom_expr->expr_type == EXPR_FUNCTION
11608       && atom_expr->value.function.isym
11609       && atom_expr->value.function.isym->id == GFC_ISYM_CAF_GET)
11610     atom_expr = atom_expr->value.function.actual->expr;
11611 
11612   gfc_start_block (&block);
11613   gfc_init_block (&post_block);
11614 
11615   gfc_init_se (&argse, NULL);
11616   argse.want_pointer = 1;
11617   gfc_conv_expr (&argse, atom_expr);
11618   gfc_add_block_to_block (&block, &argse.pre);
11619   gfc_add_block_to_block (&post_block, &argse.post);
11620   atom = argse.expr;
11621 
11622   gfc_init_se (&argse, NULL);
11623   if (flag_coarray == GFC_FCOARRAY_LIB
11624       && code->ext.actual->next->expr->ts.kind == atom_expr->ts.kind)
11625     argse.want_pointer = 1;
11626   gfc_conv_expr (&argse, code->ext.actual->next->expr);
11627   gfc_add_block_to_block (&block, &argse.pre);
11628   gfc_add_block_to_block (&post_block, &argse.post);
11629   value = argse.expr;
11630 
11631   switch (code->resolved_isym->id)
11632     {
11633     case GFC_ISYM_ATOMIC_ADD:
11634     case GFC_ISYM_ATOMIC_AND:
11635     case GFC_ISYM_ATOMIC_DEF:
11636     case GFC_ISYM_ATOMIC_OR:
11637     case GFC_ISYM_ATOMIC_XOR:
11638       stat_expr = code->ext.actual->next->next->expr;
11639       if (flag_coarray == GFC_FCOARRAY_LIB)
11640 	old = null_pointer_node;
11641       break;
11642     default:
11643       gfc_init_se (&argse, NULL);
11644       if (flag_coarray == GFC_FCOARRAY_LIB)
11645 	argse.want_pointer = 1;
11646       gfc_conv_expr (&argse, code->ext.actual->next->next->expr);
11647       gfc_add_block_to_block (&block, &argse.pre);
11648       gfc_add_block_to_block (&post_block, &argse.post);
11649       old = argse.expr;
11650       stat_expr = code->ext.actual->next->next->next->expr;
11651     }
11652 
11653   /* STAT=  */
11654   if (stat_expr != NULL)
11655     {
11656       gcc_assert (stat_expr->expr_type == EXPR_VARIABLE);
11657       gfc_init_se (&argse, NULL);
11658       if (flag_coarray == GFC_FCOARRAY_LIB)
11659 	argse.want_pointer = 1;
11660       gfc_conv_expr_val (&argse, stat_expr);
11661       gfc_add_block_to_block (&block, &argse.pre);
11662       gfc_add_block_to_block (&post_block, &argse.post);
11663       stat = argse.expr;
11664     }
11665   else if (flag_coarray == GFC_FCOARRAY_LIB)
11666     stat = null_pointer_node;
11667 
11668   if (flag_coarray == GFC_FCOARRAY_LIB)
11669     {
11670       tree image_index, caf_decl, offset, token;
11671       int op;
11672 
11673       switch (code->resolved_isym->id)
11674 	{
11675 	case GFC_ISYM_ATOMIC_ADD:
11676 	case GFC_ISYM_ATOMIC_FETCH_ADD:
11677 	  op = (int) GFC_CAF_ATOMIC_ADD;
11678 	  break;
11679 	case GFC_ISYM_ATOMIC_AND:
11680 	case GFC_ISYM_ATOMIC_FETCH_AND:
11681 	  op = (int) GFC_CAF_ATOMIC_AND;
11682 	  break;
11683 	case GFC_ISYM_ATOMIC_OR:
11684 	case GFC_ISYM_ATOMIC_FETCH_OR:
11685 	  op = (int) GFC_CAF_ATOMIC_OR;
11686 	  break;
11687 	case GFC_ISYM_ATOMIC_XOR:
11688 	case GFC_ISYM_ATOMIC_FETCH_XOR:
11689 	  op = (int) GFC_CAF_ATOMIC_XOR;
11690 	  break;
11691 	case GFC_ISYM_ATOMIC_DEF:
11692 	  op = 0;  /* Unused.  */
11693 	  break;
11694 	default:
11695 	  gcc_unreachable ();
11696 	}
11697 
11698       caf_decl = gfc_get_tree_for_caf_expr (atom_expr);
11699       if (TREE_CODE (TREE_TYPE (caf_decl)) == REFERENCE_TYPE)
11700 	caf_decl = build_fold_indirect_ref_loc (input_location, caf_decl);
11701 
11702       if (gfc_is_coindexed (atom_expr))
11703 	image_index = gfc_caf_get_image_index (&block, atom_expr, caf_decl);
11704       else
11705 	image_index = integer_zero_node;
11706 
11707       if (!POINTER_TYPE_P (TREE_TYPE (value)))
11708 	{
11709 	  tmp = gfc_create_var (TREE_TYPE (TREE_TYPE (atom)), "value");
11710 	  gfc_add_modify (&block, tmp, fold_convert (TREE_TYPE (tmp), value));
11711           value = gfc_build_addr_expr (NULL_TREE, tmp);
11712 	}
11713 
11714       gfc_init_se (&argse, NULL);
11715       gfc_get_caf_token_offset (&argse, &token, &offset, caf_decl, atom,
11716 				atom_expr);
11717 
11718       gfc_add_block_to_block (&block, &argse.pre);
11719       if (code->resolved_isym->id == GFC_ISYM_ATOMIC_DEF)
11720 	tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_atomic_def, 7,
11721 				   token, offset, image_index, value, stat,
11722 				   build_int_cst (integer_type_node,
11723 						  (int) atom_expr->ts.type),
11724 				   build_int_cst (integer_type_node,
11725 						  (int) atom_expr->ts.kind));
11726       else
11727 	tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_atomic_op, 9,
11728 				   build_int_cst (integer_type_node, op),
11729 				   token, offset, image_index, value, old, stat,
11730 				   build_int_cst (integer_type_node,
11731 						  (int) atom_expr->ts.type),
11732 				   build_int_cst (integer_type_node,
11733 						  (int) atom_expr->ts.kind));
11734 
11735       gfc_add_expr_to_block (&block, tmp);
11736       gfc_add_block_to_block (&block, &argse.post);
11737       gfc_add_block_to_block (&block, &post_block);
11738       return gfc_finish_block (&block);
11739     }
11740 
11741 
11742   switch (code->resolved_isym->id)
11743     {
11744     case GFC_ISYM_ATOMIC_ADD:
11745     case GFC_ISYM_ATOMIC_FETCH_ADD:
11746       fn = BUILT_IN_ATOMIC_FETCH_ADD_N;
11747       break;
11748     case GFC_ISYM_ATOMIC_AND:
11749     case GFC_ISYM_ATOMIC_FETCH_AND:
11750       fn = BUILT_IN_ATOMIC_FETCH_AND_N;
11751       break;
11752     case GFC_ISYM_ATOMIC_DEF:
11753       fn = BUILT_IN_ATOMIC_STORE_N;
11754       break;
11755     case GFC_ISYM_ATOMIC_OR:
11756     case GFC_ISYM_ATOMIC_FETCH_OR:
11757       fn = BUILT_IN_ATOMIC_FETCH_OR_N;
11758       break;
11759     case GFC_ISYM_ATOMIC_XOR:
11760     case GFC_ISYM_ATOMIC_FETCH_XOR:
11761       fn = BUILT_IN_ATOMIC_FETCH_XOR_N;
11762       break;
11763     default:
11764       gcc_unreachable ();
11765     }
11766 
11767   tmp = TREE_TYPE (TREE_TYPE (atom));
11768   fn = (built_in_function) ((int) fn
11769 			    + exact_log2 (tree_to_uhwi (TYPE_SIZE_UNIT (tmp)))
11770 			    + 1);
11771   tree itype = TREE_TYPE (TREE_TYPE (atom));
11772   tmp = builtin_decl_explicit (fn);
11773 
11774   switch (code->resolved_isym->id)
11775     {
11776     case GFC_ISYM_ATOMIC_ADD:
11777     case GFC_ISYM_ATOMIC_AND:
11778     case GFC_ISYM_ATOMIC_DEF:
11779     case GFC_ISYM_ATOMIC_OR:
11780     case GFC_ISYM_ATOMIC_XOR:
11781       tmp = build_call_expr_loc (input_location, tmp, 3, atom,
11782 				 fold_convert (itype, value),
11783 				 build_int_cst (NULL, MEMMODEL_RELAXED));
11784       gfc_add_expr_to_block (&block, tmp);
11785       break;
11786     default:
11787       tmp = build_call_expr_loc (input_location, tmp, 3, atom,
11788 				 fold_convert (itype, value),
11789 				 build_int_cst (NULL, MEMMODEL_RELAXED));
11790       gfc_add_modify (&block, old, fold_convert (TREE_TYPE (old), tmp));
11791       break;
11792     }
11793 
11794   if (stat != NULL_TREE)
11795     gfc_add_modify (&block, stat, build_int_cst (TREE_TYPE (stat), 0));
11796   gfc_add_block_to_block (&block, &post_block);
11797   return gfc_finish_block (&block);
11798 }
11799 
11800 
11801 static tree
conv_intrinsic_atomic_ref(gfc_code * code)11802 conv_intrinsic_atomic_ref (gfc_code *code)
11803 {
11804   gfc_se argse;
11805   tree tmp, atom, value, stat = NULL_TREE;
11806   stmtblock_t block, post_block;
11807   built_in_function fn;
11808   gfc_expr *atom_expr = code->ext.actual->next->expr;
11809 
11810   if (atom_expr->expr_type == EXPR_FUNCTION
11811       && atom_expr->value.function.isym
11812       && atom_expr->value.function.isym->id == GFC_ISYM_CAF_GET)
11813     atom_expr = atom_expr->value.function.actual->expr;
11814 
11815   gfc_start_block (&block);
11816   gfc_init_block (&post_block);
11817   gfc_init_se (&argse, NULL);
11818   argse.want_pointer = 1;
11819   gfc_conv_expr (&argse, atom_expr);
11820   gfc_add_block_to_block (&block, &argse.pre);
11821   gfc_add_block_to_block (&post_block, &argse.post);
11822   atom = argse.expr;
11823 
11824   gfc_init_se (&argse, NULL);
11825   if (flag_coarray == GFC_FCOARRAY_LIB
11826       && code->ext.actual->expr->ts.kind == atom_expr->ts.kind)
11827     argse.want_pointer = 1;
11828   gfc_conv_expr (&argse, code->ext.actual->expr);
11829   gfc_add_block_to_block (&block, &argse.pre);
11830   gfc_add_block_to_block (&post_block, &argse.post);
11831   value = argse.expr;
11832 
11833   /* STAT=  */
11834   if (code->ext.actual->next->next->expr != NULL)
11835     {
11836       gcc_assert (code->ext.actual->next->next->expr->expr_type
11837 		  == EXPR_VARIABLE);
11838       gfc_init_se (&argse, NULL);
11839       if (flag_coarray == GFC_FCOARRAY_LIB)
11840 	argse.want_pointer = 1;
11841       gfc_conv_expr_val (&argse, code->ext.actual->next->next->expr);
11842       gfc_add_block_to_block (&block, &argse.pre);
11843       gfc_add_block_to_block (&post_block, &argse.post);
11844       stat = argse.expr;
11845     }
11846   else if (flag_coarray == GFC_FCOARRAY_LIB)
11847     stat = null_pointer_node;
11848 
11849   if (flag_coarray == GFC_FCOARRAY_LIB)
11850     {
11851       tree image_index, caf_decl, offset, token;
11852       tree orig_value = NULL_TREE, vardecl = NULL_TREE;
11853 
11854       caf_decl = gfc_get_tree_for_caf_expr (atom_expr);
11855       if (TREE_CODE (TREE_TYPE (caf_decl)) == REFERENCE_TYPE)
11856 	caf_decl = build_fold_indirect_ref_loc (input_location, caf_decl);
11857 
11858       if (gfc_is_coindexed (atom_expr))
11859 	image_index = gfc_caf_get_image_index (&block, atom_expr, caf_decl);
11860       else
11861 	image_index = integer_zero_node;
11862 
11863       gfc_init_se (&argse, NULL);
11864       gfc_get_caf_token_offset (&argse, &token, &offset, caf_decl, atom,
11865 				atom_expr);
11866       gfc_add_block_to_block (&block, &argse.pre);
11867 
11868       /* Different type, need type conversion.  */
11869       if (!POINTER_TYPE_P (TREE_TYPE (value)))
11870 	{
11871 	  vardecl = gfc_create_var (TREE_TYPE (TREE_TYPE (atom)), "value");
11872           orig_value = value;
11873           value = gfc_build_addr_expr (NULL_TREE, vardecl);
11874 	}
11875 
11876       tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_atomic_ref, 7,
11877 				 token, offset, image_index, value, stat,
11878 				 build_int_cst (integer_type_node,
11879 						(int) atom_expr->ts.type),
11880 				 build_int_cst (integer_type_node,
11881 						(int) atom_expr->ts.kind));
11882       gfc_add_expr_to_block (&block, tmp);
11883       if (vardecl != NULL_TREE)
11884 	gfc_add_modify (&block, orig_value,
11885 			fold_convert (TREE_TYPE (orig_value), vardecl));
11886       gfc_add_block_to_block (&block, &argse.post);
11887       gfc_add_block_to_block (&block, &post_block);
11888       return gfc_finish_block (&block);
11889     }
11890 
11891   tmp = TREE_TYPE (TREE_TYPE (atom));
11892   fn = (built_in_function) ((int) BUILT_IN_ATOMIC_LOAD_N
11893 			    + exact_log2 (tree_to_uhwi (TYPE_SIZE_UNIT (tmp)))
11894 			    + 1);
11895   tmp = builtin_decl_explicit (fn);
11896   tmp = build_call_expr_loc (input_location, tmp, 2, atom,
11897 			     build_int_cst (integer_type_node,
11898 					    MEMMODEL_RELAXED));
11899   gfc_add_modify (&block, value, fold_convert (TREE_TYPE (value), tmp));
11900 
11901   if (stat != NULL_TREE)
11902     gfc_add_modify (&block, stat, build_int_cst (TREE_TYPE (stat), 0));
11903   gfc_add_block_to_block (&block, &post_block);
11904   return gfc_finish_block (&block);
11905 }
11906 
11907 
11908 static tree
conv_intrinsic_atomic_cas(gfc_code * code)11909 conv_intrinsic_atomic_cas (gfc_code *code)
11910 {
11911   gfc_se argse;
11912   tree tmp, atom, old, new_val, comp, stat = NULL_TREE;
11913   stmtblock_t block, post_block;
11914   built_in_function fn;
11915   gfc_expr *atom_expr = code->ext.actual->expr;
11916 
11917   if (atom_expr->expr_type == EXPR_FUNCTION
11918       && atom_expr->value.function.isym
11919       && atom_expr->value.function.isym->id == GFC_ISYM_CAF_GET)
11920     atom_expr = atom_expr->value.function.actual->expr;
11921 
11922   gfc_init_block (&block);
11923   gfc_init_block (&post_block);
11924   gfc_init_se (&argse, NULL);
11925   argse.want_pointer = 1;
11926   gfc_conv_expr (&argse, atom_expr);
11927   atom = argse.expr;
11928 
11929   gfc_init_se (&argse, NULL);
11930   if (flag_coarray == GFC_FCOARRAY_LIB)
11931     argse.want_pointer = 1;
11932   gfc_conv_expr (&argse, code->ext.actual->next->expr);
11933   gfc_add_block_to_block (&block, &argse.pre);
11934   gfc_add_block_to_block (&post_block, &argse.post);
11935   old = argse.expr;
11936 
11937   gfc_init_se (&argse, NULL);
11938   if (flag_coarray == GFC_FCOARRAY_LIB)
11939     argse.want_pointer = 1;
11940   gfc_conv_expr (&argse, code->ext.actual->next->next->expr);
11941   gfc_add_block_to_block (&block, &argse.pre);
11942   gfc_add_block_to_block (&post_block, &argse.post);
11943   comp = argse.expr;
11944 
11945   gfc_init_se (&argse, NULL);
11946   if (flag_coarray == GFC_FCOARRAY_LIB
11947       && code->ext.actual->next->next->next->expr->ts.kind
11948 	 == atom_expr->ts.kind)
11949     argse.want_pointer = 1;
11950   gfc_conv_expr (&argse, code->ext.actual->next->next->next->expr);
11951   gfc_add_block_to_block (&block, &argse.pre);
11952   gfc_add_block_to_block (&post_block, &argse.post);
11953   new_val = argse.expr;
11954 
11955   /* STAT=  */
11956   if (code->ext.actual->next->next->next->next->expr != NULL)
11957     {
11958       gcc_assert (code->ext.actual->next->next->next->next->expr->expr_type
11959 		  == EXPR_VARIABLE);
11960       gfc_init_se (&argse, NULL);
11961       if (flag_coarray == GFC_FCOARRAY_LIB)
11962 	argse.want_pointer = 1;
11963       gfc_conv_expr_val (&argse,
11964 			 code->ext.actual->next->next->next->next->expr);
11965       gfc_add_block_to_block (&block, &argse.pre);
11966       gfc_add_block_to_block (&post_block, &argse.post);
11967       stat = argse.expr;
11968     }
11969   else if (flag_coarray == GFC_FCOARRAY_LIB)
11970     stat = null_pointer_node;
11971 
11972   if (flag_coarray == GFC_FCOARRAY_LIB)
11973     {
11974       tree image_index, caf_decl, offset, token;
11975 
11976       caf_decl = gfc_get_tree_for_caf_expr (atom_expr);
11977       if (TREE_CODE (TREE_TYPE (caf_decl)) == REFERENCE_TYPE)
11978 	caf_decl = build_fold_indirect_ref_loc (input_location, caf_decl);
11979 
11980       if (gfc_is_coindexed (atom_expr))
11981 	image_index = gfc_caf_get_image_index (&block, atom_expr, caf_decl);
11982       else
11983 	image_index = integer_zero_node;
11984 
11985       if (TREE_TYPE (TREE_TYPE (new_val)) != TREE_TYPE (TREE_TYPE (old)))
11986 	{
11987 	  tmp = gfc_create_var (TREE_TYPE (TREE_TYPE (old)), "new");
11988 	  gfc_add_modify (&block, tmp, fold_convert (TREE_TYPE (tmp), new_val));
11989           new_val = gfc_build_addr_expr (NULL_TREE, tmp);
11990 	}
11991 
11992       /* Convert a constant to a pointer.  */
11993       if (!POINTER_TYPE_P (TREE_TYPE (comp)))
11994 	{
11995 	  tmp = gfc_create_var (TREE_TYPE (TREE_TYPE (old)), "comp");
11996 	  gfc_add_modify (&block, tmp, fold_convert (TREE_TYPE (tmp), comp));
11997           comp = gfc_build_addr_expr (NULL_TREE, tmp);
11998 	}
11999 
12000       gfc_init_se (&argse, NULL);
12001       gfc_get_caf_token_offset (&argse, &token, &offset, caf_decl, atom,
12002 				atom_expr);
12003       gfc_add_block_to_block (&block, &argse.pre);
12004 
12005       tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_atomic_cas, 9,
12006 				 token, offset, image_index, old, comp, new_val,
12007 				 stat, build_int_cst (integer_type_node,
12008 						      (int) atom_expr->ts.type),
12009 				 build_int_cst (integer_type_node,
12010 						(int) atom_expr->ts.kind));
12011       gfc_add_expr_to_block (&block, tmp);
12012       gfc_add_block_to_block (&block, &argse.post);
12013       gfc_add_block_to_block (&block, &post_block);
12014       return gfc_finish_block (&block);
12015     }
12016 
12017   tmp = TREE_TYPE (TREE_TYPE (atom));
12018   fn = (built_in_function) ((int) BUILT_IN_ATOMIC_COMPARE_EXCHANGE_N
12019 			    + exact_log2 (tree_to_uhwi (TYPE_SIZE_UNIT (tmp)))
12020 			    + 1);
12021   tmp = builtin_decl_explicit (fn);
12022 
12023   gfc_add_modify (&block, old, comp);
12024   tmp = build_call_expr_loc (input_location, tmp, 6, atom,
12025 			     gfc_build_addr_expr (NULL, old),
12026 			     fold_convert (TREE_TYPE (old), new_val),
12027 			     boolean_false_node,
12028 			     build_int_cst (NULL, MEMMODEL_RELAXED),
12029 			     build_int_cst (NULL, MEMMODEL_RELAXED));
12030   gfc_add_expr_to_block (&block, tmp);
12031 
12032   if (stat != NULL_TREE)
12033     gfc_add_modify (&block, stat, build_int_cst (TREE_TYPE (stat), 0));
12034   gfc_add_block_to_block (&block, &post_block);
12035   return gfc_finish_block (&block);
12036 }
12037 
12038 static tree
conv_intrinsic_event_query(gfc_code * code)12039 conv_intrinsic_event_query (gfc_code *code)
12040 {
12041   gfc_se se, argse;
12042   tree stat = NULL_TREE, stat2 = NULL_TREE;
12043   tree count = NULL_TREE, count2 = NULL_TREE;
12044 
12045   gfc_expr *event_expr = code->ext.actual->expr;
12046 
12047   if (code->ext.actual->next->next->expr)
12048     {
12049       gcc_assert (code->ext.actual->next->next->expr->expr_type
12050 		  == EXPR_VARIABLE);
12051       gfc_init_se (&argse, NULL);
12052       gfc_conv_expr_val (&argse, code->ext.actual->next->next->expr);
12053       stat = argse.expr;
12054     }
12055   else if (flag_coarray == GFC_FCOARRAY_LIB)
12056     stat = null_pointer_node;
12057 
12058   if (code->ext.actual->next->expr)
12059     {
12060       gcc_assert (code->ext.actual->next->expr->expr_type == EXPR_VARIABLE);
12061       gfc_init_se (&argse, NULL);
12062       gfc_conv_expr_val (&argse, code->ext.actual->next->expr);
12063       count = argse.expr;
12064     }
12065 
12066   gfc_start_block (&se.pre);
12067   if (flag_coarray == GFC_FCOARRAY_LIB)
12068     {
12069       tree tmp, token, image_index;
12070       tree index = build_zero_cst (gfc_array_index_type);
12071 
12072       if (event_expr->expr_type == EXPR_FUNCTION
12073 	  && event_expr->value.function.isym
12074 	  && event_expr->value.function.isym->id == GFC_ISYM_CAF_GET)
12075 	event_expr = event_expr->value.function.actual->expr;
12076 
12077       tree caf_decl = gfc_get_tree_for_caf_expr (event_expr);
12078 
12079       if (event_expr->symtree->n.sym->ts.type != BT_DERIVED
12080 	  || event_expr->symtree->n.sym->ts.u.derived->from_intmod
12081 	     != INTMOD_ISO_FORTRAN_ENV
12082 	  || event_expr->symtree->n.sym->ts.u.derived->intmod_sym_id
12083 	     != ISOFORTRAN_EVENT_TYPE)
12084 	{
12085 	  gfc_error ("Sorry, the event component of derived type at %L is not "
12086 		     "yet supported", &event_expr->where);
12087 	  return NULL_TREE;
12088 	}
12089 
12090       if (gfc_is_coindexed (event_expr))
12091 	{
12092 	  gfc_error ("The event variable at %L shall not be coindexed",
12093 		     &event_expr->where);
12094           return NULL_TREE;
12095 	}
12096 
12097       image_index = integer_zero_node;
12098 
12099       gfc_get_caf_token_offset (&se, &token, NULL, caf_decl, NULL_TREE,
12100 				event_expr);
12101 
12102       /* For arrays, obtain the array index.  */
12103       if (gfc_expr_attr (event_expr).dimension)
12104 	{
12105 	  tree desc, tmp, extent, lbound, ubound;
12106           gfc_array_ref *ar, ar2;
12107           int i;
12108 
12109 	  /* TODO: Extend this, once DT components are supported.  */
12110 	  ar = &event_expr->ref->u.ar;
12111 	  ar2 = *ar;
12112 	  memset (ar, '\0', sizeof (*ar));
12113 	  ar->as = ar2.as;
12114 	  ar->type = AR_FULL;
12115 
12116 	  gfc_init_se (&argse, NULL);
12117 	  argse.descriptor_only = 1;
12118 	  gfc_conv_expr_descriptor (&argse, event_expr);
12119 	  gfc_add_block_to_block (&se.pre, &argse.pre);
12120 	  desc = argse.expr;
12121 	  *ar = ar2;
12122 
12123 	  extent = build_one_cst (gfc_array_index_type);
12124 	  for (i = 0; i < ar->dimen; i++)
12125 	    {
12126 	      gfc_init_se (&argse, NULL);
12127 	      gfc_conv_expr_type (&argse, ar->start[i], gfc_array_index_type);
12128 	      gfc_add_block_to_block (&argse.pre, &argse.pre);
12129 	      lbound = gfc_conv_descriptor_lbound_get (desc, gfc_rank_cst[i]);
12130 	      tmp = fold_build2_loc (input_location, MINUS_EXPR,
12131 				     TREE_TYPE (lbound), argse.expr, lbound);
12132 	      tmp = fold_build2_loc (input_location, MULT_EXPR,
12133 				     TREE_TYPE (tmp), extent, tmp);
12134 	      index = fold_build2_loc (input_location, PLUS_EXPR,
12135 				       TREE_TYPE (tmp), index, tmp);
12136 	      if (i < ar->dimen - 1)
12137 		{
12138 		  ubound = gfc_conv_descriptor_ubound_get (desc, gfc_rank_cst[i]);
12139 		  tmp = gfc_conv_array_extent_dim (lbound, ubound, NULL);
12140 		  extent = fold_build2_loc (input_location, MULT_EXPR,
12141 					    TREE_TYPE (tmp), extent, tmp);
12142 		}
12143 	    }
12144 	}
12145 
12146       if (count != null_pointer_node && TREE_TYPE (count) != integer_type_node)
12147 	{
12148 	  count2 = count;
12149 	  count = gfc_create_var (integer_type_node, "count");
12150 	}
12151 
12152       if (stat != null_pointer_node && TREE_TYPE (stat) != integer_type_node)
12153 	{
12154 	  stat2 = stat;
12155 	  stat = gfc_create_var (integer_type_node, "stat");
12156 	}
12157 
12158       index = fold_convert (size_type_node, index);
12159       tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_event_query, 5,
12160                                    token, index, image_index, count
12161 				   ? gfc_build_addr_expr (NULL, count) : count,
12162 				   stat != null_pointer_node
12163 				   ? gfc_build_addr_expr (NULL, stat) : stat);
12164       gfc_add_expr_to_block (&se.pre, tmp);
12165 
12166       if (count2 != NULL_TREE)
12167 	gfc_add_modify (&se.pre, count2,
12168 			fold_convert (TREE_TYPE (count2), count));
12169 
12170       if (stat2 != NULL_TREE)
12171 	gfc_add_modify (&se.pre, stat2,
12172 			fold_convert (TREE_TYPE (stat2), stat));
12173 
12174       return gfc_finish_block (&se.pre);
12175     }
12176 
12177   gfc_init_se (&argse, NULL);
12178   gfc_conv_expr_val (&argse, code->ext.actual->expr);
12179   gfc_add_modify (&se.pre, count, fold_convert (TREE_TYPE (count), argse.expr));
12180 
12181   if (stat != NULL_TREE)
12182     gfc_add_modify (&se.pre, stat, build_int_cst (TREE_TYPE (stat), 0));
12183 
12184   return gfc_finish_block (&se.pre);
12185 }
12186 
12187 
12188 /* This is a peculiar case because of the need to do dependency checking.
12189    It is called via trans-stmt.cc(gfc_trans_call), where it is picked out as
12190    a special case and this function called instead of
12191    gfc_conv_procedure_call.  */
12192 void
gfc_conv_intrinsic_mvbits(gfc_se * se,gfc_actual_arglist * actual_args,gfc_loopinfo * loop)12193 gfc_conv_intrinsic_mvbits (gfc_se *se, gfc_actual_arglist *actual_args,
12194 			   gfc_loopinfo *loop)
12195 {
12196   gfc_actual_arglist *actual;
12197   gfc_se argse[5];
12198   gfc_expr *arg[5];
12199   gfc_ss *lss;
12200   int n;
12201 
12202   tree from, frompos, len, to, topos;
12203   tree lenmask, oldbits, newbits, bitsize;
12204   tree type, utype, above, mask1, mask2;
12205 
12206   if (loop)
12207     lss = loop->ss;
12208   else
12209     lss = gfc_ss_terminator;
12210 
12211   actual = actual_args;
12212   for (n = 0; n < 5; n++, actual = actual->next)
12213     {
12214       arg[n] = actual->expr;
12215       gfc_init_se (&argse[n], NULL);
12216 
12217       if (lss != gfc_ss_terminator)
12218 	{
12219 	  gfc_copy_loopinfo_to_se (&argse[n], loop);
12220 	  /* Find the ss for the expression if it is there.  */
12221 	  argse[n].ss = lss;
12222 	  gfc_mark_ss_chain_used (lss, 1);
12223 	}
12224 
12225       gfc_conv_expr (&argse[n], arg[n]);
12226 
12227       if (loop)
12228 	lss = argse[n].ss;
12229     }
12230 
12231   from    = argse[0].expr;
12232   frompos = argse[1].expr;
12233   len     = argse[2].expr;
12234   to      = argse[3].expr;
12235   topos   = argse[4].expr;
12236 
12237   /* The type of the result (TO).  */
12238   type    = TREE_TYPE (to);
12239   bitsize = build_int_cst (integer_type_node, TYPE_PRECISION (type));
12240 
12241   /* Optionally generate code for runtime argument check.  */
12242   if (gfc_option.rtcheck & GFC_RTCHECK_BITS)
12243     {
12244       tree nbits, below, ccond;
12245       tree fp = fold_convert (long_integer_type_node, frompos);
12246       tree ln = fold_convert (long_integer_type_node, len);
12247       tree tp = fold_convert (long_integer_type_node, topos);
12248       below = fold_build2_loc (input_location, LT_EXPR,
12249 			       logical_type_node, frompos,
12250 			       build_int_cst (TREE_TYPE (frompos), 0));
12251       above = fold_build2_loc (input_location, GT_EXPR,
12252 			       logical_type_node, frompos,
12253 			       fold_convert (TREE_TYPE (frompos), bitsize));
12254       ccond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
12255 			       logical_type_node, below, above);
12256       gfc_trans_runtime_check (true, false, ccond, &argse[1].pre,
12257 			       &arg[1]->where,
12258 			       "FROMPOS argument (%ld) out of range 0:%d "
12259 			       "in intrinsic MVBITS", fp, bitsize);
12260       below = fold_build2_loc (input_location, LT_EXPR,
12261 			       logical_type_node, len,
12262 			       build_int_cst (TREE_TYPE (len), 0));
12263       above = fold_build2_loc (input_location, GT_EXPR,
12264 			       logical_type_node, len,
12265 			       fold_convert (TREE_TYPE (len), bitsize));
12266       ccond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
12267 			       logical_type_node, below, above);
12268       gfc_trans_runtime_check (true, false, ccond, &argse[2].pre,
12269 			       &arg[2]->where,
12270 			       "LEN argument (%ld) out of range 0:%d "
12271 			       "in intrinsic MVBITS", ln, bitsize);
12272       below = fold_build2_loc (input_location, LT_EXPR,
12273 			       logical_type_node, topos,
12274 			       build_int_cst (TREE_TYPE (topos), 0));
12275       above = fold_build2_loc (input_location, GT_EXPR,
12276 			       logical_type_node, topos,
12277 			       fold_convert (TREE_TYPE (topos), bitsize));
12278       ccond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
12279 			       logical_type_node, below, above);
12280       gfc_trans_runtime_check (true, false, ccond, &argse[4].pre,
12281 			       &arg[4]->where,
12282 			       "TOPOS argument (%ld) out of range 0:%d "
12283 			       "in intrinsic MVBITS", tp, bitsize);
12284 
12285       /* The tests above ensure that FROMPOS, LEN and TOPOS fit into short
12286 	 integers.  Additions below cannot overflow.  */
12287       nbits = fold_convert (long_integer_type_node, bitsize);
12288       above = fold_build2_loc (input_location, PLUS_EXPR,
12289 			       long_integer_type_node, fp, ln);
12290       ccond = fold_build2_loc (input_location, GT_EXPR,
12291 			       logical_type_node, above, nbits);
12292       gfc_trans_runtime_check (true, false, ccond, &argse[1].pre,
12293 			       &arg[1]->where,
12294 			       "FROMPOS(%ld)+LEN(%ld)>BIT_SIZE(%d) "
12295 			       "in intrinsic MVBITS", fp, ln, bitsize);
12296       above = fold_build2_loc (input_location, PLUS_EXPR,
12297 			       long_integer_type_node, tp, ln);
12298       ccond = fold_build2_loc (input_location, GT_EXPR,
12299 			       logical_type_node, above, nbits);
12300       gfc_trans_runtime_check (true, false, ccond, &argse[4].pre,
12301 			       &arg[4]->where,
12302 			       "TOPOS(%ld)+LEN(%ld)>BIT_SIZE(%d) "
12303 			       "in intrinsic MVBITS", tp, ln, bitsize);
12304     }
12305 
12306   for (n = 0; n < 5; n++)
12307     {
12308       gfc_add_block_to_block (&se->pre, &argse[n].pre);
12309       gfc_add_block_to_block (&se->post, &argse[n].post);
12310     }
12311 
12312   /* lenmask = (LEN >= bit_size (TYPE)) ? ~(TYPE)0 : ((TYPE)1 << LEN) - 1  */
12313   above = fold_build2_loc (input_location, GE_EXPR, logical_type_node,
12314 			   len, fold_convert (TREE_TYPE (len), bitsize));
12315   mask1 = build_int_cst (type, -1);
12316   mask2 = fold_build2_loc (input_location, LSHIFT_EXPR, type,
12317 			   build_int_cst (type, 1), len);
12318   mask2 = fold_build2_loc (input_location, MINUS_EXPR, type,
12319 			   mask2, build_int_cst (type, 1));
12320   lenmask = fold_build3_loc (input_location, COND_EXPR, type,
12321 			     above, mask1, mask2);
12322 
12323   /* newbits = (((UTYPE)(FROM) >> FROMPOS) & lenmask) << TOPOS.
12324    * For valid frompos+len <= bit_size(FROM) the conversion to unsigned is
12325    * not strictly necessary; artificial bits from rshift will be masked.  */
12326   utype = unsigned_type_for (type);
12327   newbits = fold_build2_loc (input_location, RSHIFT_EXPR, utype,
12328 			     fold_convert (utype, from), frompos);
12329   newbits = fold_build2_loc (input_location, BIT_AND_EXPR, type,
12330 			     fold_convert (type, newbits), lenmask);
12331   newbits = fold_build2_loc (input_location, LSHIFT_EXPR, type,
12332 			     newbits, topos);
12333 
12334   /* oldbits = TO & (~(lenmask << TOPOS)).  */
12335   oldbits = fold_build2_loc (input_location, LSHIFT_EXPR, type,
12336 			     lenmask, topos);
12337   oldbits = fold_build1_loc (input_location, BIT_NOT_EXPR, type, oldbits);
12338   oldbits = fold_build2_loc (input_location, BIT_AND_EXPR, type, oldbits, to);
12339 
12340   /* TO = newbits | oldbits.  */
12341   se->expr = fold_build2_loc (input_location, BIT_IOR_EXPR, type,
12342 			      oldbits, newbits);
12343 
12344   /* Return the assignment.  */
12345   se->expr = fold_build2_loc (input_location, MODIFY_EXPR,
12346 			      void_type_node, to, se->expr);
12347 }
12348 
12349 
12350 static tree
conv_intrinsic_move_alloc(gfc_code * code)12351 conv_intrinsic_move_alloc (gfc_code *code)
12352 {
12353   stmtblock_t block;
12354   gfc_expr *from_expr, *to_expr;
12355   gfc_expr *to_expr2, *from_expr2 = NULL;
12356   gfc_se from_se, to_se;
12357   tree tmp;
12358   bool coarray;
12359 
12360   gfc_start_block (&block);
12361 
12362   from_expr = code->ext.actual->expr;
12363   to_expr = code->ext.actual->next->expr;
12364 
12365   gfc_init_se (&from_se, NULL);
12366   gfc_init_se (&to_se, NULL);
12367 
12368   gcc_assert (from_expr->ts.type != BT_CLASS
12369 	      || to_expr->ts.type == BT_CLASS);
12370   coarray = gfc_get_corank (from_expr) != 0;
12371 
12372   if (from_expr->rank == 0 && !coarray)
12373     {
12374       if (from_expr->ts.type != BT_CLASS)
12375 	from_expr2 = from_expr;
12376       else
12377 	{
12378 	  from_expr2 = gfc_copy_expr (from_expr);
12379 	  gfc_add_data_component (from_expr2);
12380 	}
12381 
12382       if (to_expr->ts.type != BT_CLASS)
12383 	to_expr2 = to_expr;
12384       else
12385 	{
12386 	  to_expr2 = gfc_copy_expr (to_expr);
12387 	  gfc_add_data_component (to_expr2);
12388 	}
12389 
12390       from_se.want_pointer = 1;
12391       to_se.want_pointer = 1;
12392       gfc_conv_expr (&from_se, from_expr2);
12393       gfc_conv_expr (&to_se, to_expr2);
12394       gfc_add_block_to_block (&block, &from_se.pre);
12395       gfc_add_block_to_block (&block, &to_se.pre);
12396 
12397       /* Deallocate "to".  */
12398       tmp = gfc_deallocate_scalar_with_status (to_se.expr, NULL_TREE, NULL_TREE,
12399 					       true, to_expr, to_expr->ts);
12400       gfc_add_expr_to_block (&block, tmp);
12401 
12402       /* Assign (_data) pointers.  */
12403       gfc_add_modify_loc (input_location, &block, to_se.expr,
12404 			  fold_convert (TREE_TYPE (to_se.expr), from_se.expr));
12405 
12406       /* Set "from" to NULL.  */
12407       gfc_add_modify_loc (input_location, &block, from_se.expr,
12408 			  fold_convert (TREE_TYPE (from_se.expr), null_pointer_node));
12409 
12410       gfc_add_block_to_block (&block, &from_se.post);
12411       gfc_add_block_to_block (&block, &to_se.post);
12412 
12413       /* Set _vptr.  */
12414       if (to_expr->ts.type == BT_CLASS)
12415 	{
12416 	  gfc_symbol *vtab;
12417 
12418 	  gfc_free_expr (to_expr2);
12419 	  gfc_init_se (&to_se, NULL);
12420 	  to_se.want_pointer = 1;
12421 	  gfc_add_vptr_component (to_expr);
12422 	  gfc_conv_expr (&to_se, to_expr);
12423 
12424 	  if (from_expr->ts.type == BT_CLASS)
12425 	    {
12426 	      if (UNLIMITED_POLY (from_expr))
12427 		vtab = NULL;
12428 	      else
12429 		{
12430 		  vtab = gfc_find_derived_vtab (from_expr->ts.u.derived);
12431 		  gcc_assert (vtab);
12432 		}
12433 
12434 	      gfc_free_expr (from_expr2);
12435 	      gfc_init_se (&from_se, NULL);
12436 	      from_se.want_pointer = 1;
12437 	      gfc_add_vptr_component (from_expr);
12438 	      gfc_conv_expr (&from_se, from_expr);
12439 	      gfc_add_modify_loc (input_location, &block, to_se.expr,
12440 				  fold_convert (TREE_TYPE (to_se.expr),
12441 				  from_se.expr));
12442 
12443               /* Reset _vptr component to declared type.  */
12444 	      if (vtab == NULL)
12445 		/* Unlimited polymorphic.  */
12446 		gfc_add_modify_loc (input_location, &block, from_se.expr,
12447 				    fold_convert (TREE_TYPE (from_se.expr),
12448 						  null_pointer_node));
12449 	      else
12450 		{
12451 		  tmp = gfc_build_addr_expr (NULL_TREE, gfc_get_symbol_decl (vtab));
12452 		  gfc_add_modify_loc (input_location, &block, from_se.expr,
12453 				      fold_convert (TREE_TYPE (from_se.expr), tmp));
12454 		}
12455 	    }
12456 	  else
12457 	    {
12458 	      vtab = gfc_find_vtab (&from_expr->ts);
12459 	      gcc_assert (vtab);
12460 	      tmp = gfc_build_addr_expr (NULL_TREE, gfc_get_symbol_decl (vtab));
12461 	      gfc_add_modify_loc (input_location, &block, to_se.expr,
12462 				  fold_convert (TREE_TYPE (to_se.expr), tmp));
12463 	    }
12464 	}
12465 
12466       if (to_expr->ts.type == BT_CHARACTER && to_expr->ts.deferred)
12467 	{
12468 	  gfc_add_modify_loc (input_location, &block, to_se.string_length,
12469 			      fold_convert (TREE_TYPE (to_se.string_length),
12470 					    from_se.string_length));
12471 	  if (from_expr->ts.deferred)
12472 	    gfc_add_modify_loc (input_location, &block, from_se.string_length,
12473 			build_int_cst (TREE_TYPE (from_se.string_length), 0));
12474 	}
12475 
12476       return gfc_finish_block (&block);
12477     }
12478 
12479   /* Update _vptr component.  */
12480   if (to_expr->ts.type == BT_CLASS)
12481     {
12482       gfc_symbol *vtab;
12483 
12484       to_se.want_pointer = 1;
12485       to_expr2 = gfc_copy_expr (to_expr);
12486       gfc_add_vptr_component (to_expr2);
12487       gfc_conv_expr (&to_se, to_expr2);
12488 
12489       if (from_expr->ts.type == BT_CLASS)
12490 	{
12491 	  if (UNLIMITED_POLY (from_expr))
12492 	    vtab = NULL;
12493 	  else
12494 	    {
12495 	      vtab = gfc_find_derived_vtab (from_expr->ts.u.derived);
12496 	      gcc_assert (vtab);
12497 	    }
12498 
12499 	  from_se.want_pointer = 1;
12500 	  from_expr2 = gfc_copy_expr (from_expr);
12501 	  gfc_add_vptr_component (from_expr2);
12502 	  gfc_conv_expr (&from_se, from_expr2);
12503 	  gfc_add_modify_loc (input_location, &block, to_se.expr,
12504 			      fold_convert (TREE_TYPE (to_se.expr),
12505 			      from_se.expr));
12506 
12507 	  /* Reset _vptr component to declared type.  */
12508 	  if (vtab == NULL)
12509 	    /* Unlimited polymorphic.  */
12510 	    gfc_add_modify_loc (input_location, &block, from_se.expr,
12511 				fold_convert (TREE_TYPE (from_se.expr),
12512 					      null_pointer_node));
12513 	  else
12514 	    {
12515 	      tmp = gfc_build_addr_expr (NULL_TREE, gfc_get_symbol_decl (vtab));
12516 	      gfc_add_modify_loc (input_location, &block, from_se.expr,
12517 				  fold_convert (TREE_TYPE (from_se.expr), tmp));
12518 	    }
12519 	}
12520       else
12521 	{
12522 	  vtab = gfc_find_vtab (&from_expr->ts);
12523 	  gcc_assert (vtab);
12524 	  tmp = gfc_build_addr_expr (NULL_TREE, gfc_get_symbol_decl (vtab));
12525 	  gfc_add_modify_loc (input_location, &block, to_se.expr,
12526 			      fold_convert (TREE_TYPE (to_se.expr), tmp));
12527 	}
12528 
12529       gfc_free_expr (to_expr2);
12530       gfc_init_se (&to_se, NULL);
12531 
12532       if (from_expr->ts.type == BT_CLASS)
12533 	{
12534 	  gfc_free_expr (from_expr2);
12535 	  gfc_init_se (&from_se, NULL);
12536 	}
12537     }
12538 
12539 
12540   /* Deallocate "to".  */
12541   if (from_expr->rank == 0)
12542     {
12543       to_se.want_coarray = 1;
12544       from_se.want_coarray = 1;
12545     }
12546   gfc_conv_expr_descriptor (&to_se, to_expr);
12547   gfc_conv_expr_descriptor (&from_se, from_expr);
12548 
12549   /* For coarrays, call SYNC ALL if TO is already deallocated as MOVE_ALLOC
12550      is an image control "statement", cf. IR F08/0040 in 12-006A.  */
12551   if (coarray && flag_coarray == GFC_FCOARRAY_LIB)
12552     {
12553       tree cond;
12554 
12555       tmp = gfc_deallocate_with_status (to_se.expr, NULL_TREE, NULL_TREE,
12556 					NULL_TREE, NULL_TREE, true, to_expr,
12557 					GFC_CAF_COARRAY_DEALLOCATE_ONLY);
12558       gfc_add_expr_to_block (&block, tmp);
12559 
12560       tmp = gfc_conv_descriptor_data_get (to_se.expr);
12561       cond = fold_build2_loc (input_location, EQ_EXPR,
12562 			      logical_type_node, tmp,
12563 			      fold_convert (TREE_TYPE (tmp),
12564 					    null_pointer_node));
12565       tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_sync_all,
12566 				 3, null_pointer_node, null_pointer_node,
12567 				 build_int_cst (integer_type_node, 0));
12568 
12569       tmp = fold_build3_loc (input_location, COND_EXPR, void_type_node, cond,
12570 			     tmp, build_empty_stmt (input_location));
12571       gfc_add_expr_to_block (&block, tmp);
12572     }
12573   else
12574     {
12575       if (to_expr->ts.type == BT_DERIVED
12576 	  && to_expr->ts.u.derived->attr.alloc_comp)
12577 	{
12578 	  tmp = gfc_deallocate_alloc_comp (to_expr->ts.u.derived,
12579 					   to_se.expr, to_expr->rank);
12580 	  gfc_add_expr_to_block (&block, tmp);
12581 	}
12582 
12583       tmp = gfc_conv_descriptor_data_get (to_se.expr);
12584       tmp = gfc_deallocate_with_status (tmp, NULL_TREE, NULL_TREE, NULL_TREE,
12585 					NULL_TREE, true, to_expr,
12586 					GFC_CAF_COARRAY_NOCOARRAY);
12587       gfc_add_expr_to_block (&block, tmp);
12588     }
12589 
12590   /* Move the pointer and update the array descriptor data.  */
12591   gfc_add_modify_loc (input_location, &block, to_se.expr, from_se.expr);
12592 
12593   /* Set "from" to NULL.  */
12594   tmp = gfc_conv_descriptor_data_get (from_se.expr);
12595   gfc_add_modify_loc (input_location, &block, tmp,
12596 		      fold_convert (TREE_TYPE (tmp), null_pointer_node));
12597 
12598 
12599   if (to_expr->ts.type == BT_CHARACTER && to_expr->ts.deferred)
12600     {
12601       gfc_add_modify_loc (input_location, &block, to_se.string_length,
12602 			  fold_convert (TREE_TYPE (to_se.string_length),
12603 					from_se.string_length));
12604       if (from_expr->ts.deferred)
12605         gfc_add_modify_loc (input_location, &block, from_se.string_length,
12606 			build_int_cst (TREE_TYPE (from_se.string_length), 0));
12607     }
12608 
12609   return gfc_finish_block (&block);
12610 }
12611 
12612 
12613 tree
gfc_conv_intrinsic_subroutine(gfc_code * code)12614 gfc_conv_intrinsic_subroutine (gfc_code *code)
12615 {
12616   tree res;
12617 
12618   gcc_assert (code->resolved_isym);
12619 
12620   switch (code->resolved_isym->id)
12621     {
12622     case GFC_ISYM_MOVE_ALLOC:
12623       res = conv_intrinsic_move_alloc (code);
12624       break;
12625 
12626     case GFC_ISYM_ATOMIC_CAS:
12627       res = conv_intrinsic_atomic_cas (code);
12628       break;
12629 
12630     case GFC_ISYM_ATOMIC_ADD:
12631     case GFC_ISYM_ATOMIC_AND:
12632     case GFC_ISYM_ATOMIC_DEF:
12633     case GFC_ISYM_ATOMIC_OR:
12634     case GFC_ISYM_ATOMIC_XOR:
12635     case GFC_ISYM_ATOMIC_FETCH_ADD:
12636     case GFC_ISYM_ATOMIC_FETCH_AND:
12637     case GFC_ISYM_ATOMIC_FETCH_OR:
12638     case GFC_ISYM_ATOMIC_FETCH_XOR:
12639       res = conv_intrinsic_atomic_op (code);
12640       break;
12641 
12642     case GFC_ISYM_ATOMIC_REF:
12643       res = conv_intrinsic_atomic_ref (code);
12644       break;
12645 
12646     case GFC_ISYM_EVENT_QUERY:
12647       res = conv_intrinsic_event_query (code);
12648       break;
12649 
12650     case GFC_ISYM_C_F_POINTER:
12651     case GFC_ISYM_C_F_PROCPOINTER:
12652       res = conv_isocbinding_subroutine (code);
12653       break;
12654 
12655     case GFC_ISYM_CAF_SEND:
12656       res = conv_caf_send (code);
12657       break;
12658 
12659     case GFC_ISYM_CO_BROADCAST:
12660     case GFC_ISYM_CO_MIN:
12661     case GFC_ISYM_CO_MAX:
12662     case GFC_ISYM_CO_REDUCE:
12663     case GFC_ISYM_CO_SUM:
12664       res = conv_co_collective (code);
12665       break;
12666 
12667     case GFC_ISYM_FREE:
12668       res = conv_intrinsic_free (code);
12669       break;
12670 
12671     case GFC_ISYM_RANDOM_INIT:
12672       res = conv_intrinsic_random_init (code);
12673       break;
12674 
12675     case GFC_ISYM_KILL:
12676       res = conv_intrinsic_kill_sub (code);
12677       break;
12678 
12679     case GFC_ISYM_MVBITS:
12680       res = NULL_TREE;
12681       break;
12682 
12683     case GFC_ISYM_SYSTEM_CLOCK:
12684       res = conv_intrinsic_system_clock (code);
12685       break;
12686 
12687     default:
12688       res = NULL_TREE;
12689       break;
12690     }
12691 
12692   return res;
12693 }
12694 
12695 #include "gt-fortran-trans-intrinsic.h"
12696