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 = size;
3087       else
3088 	gcc_unreachable ();
3089 
3090       /* According to F2018 16.9.172, para 5, an assumed rank object,
3091 	 argument associated with and assumed size array, has the ubound
3092 	 of the final dimension set to -1 and UBOUND must return this.
3093 	 Similarly for the SHAPE intrinsic.  */
3094       if (op != GFC_ISYM_LBOUND && assumed_rank_lb_one)
3095 	{
3096 	  tree minus_one = build_int_cst (gfc_array_index_type, -1);
3097 	  tree rank = fold_convert (gfc_array_index_type,
3098 				    gfc_conv_descriptor_rank (desc));
3099 	  rank = fold_build2_loc (input_location, PLUS_EXPR,
3100 				  gfc_array_index_type, rank, minus_one);
3101 
3102 	  /* Fix the expression to stop it from becoming even more
3103 	     complicated.  */
3104 	  se->expr = gfc_evaluate_now (se->expr, &se->pre);
3105 
3106 	  /* Descriptors for assumed-size arrays have ubound = -1
3107 	     in the last dimension.  */
3108 	  cond1 = fold_build2_loc (input_location, EQ_EXPR,
3109 				   logical_type_node, ubound, minus_one);
3110 	  cond = fold_build2_loc (input_location, EQ_EXPR,
3111 				  logical_type_node, bound, rank);
3112 	  cond = fold_build2_loc (input_location, TRUTH_AND_EXPR,
3113 				  logical_type_node, cond, cond1);
3114 	  se->expr = fold_build3_loc (input_location, COND_EXPR,
3115 				      gfc_array_index_type, cond,
3116 				      minus_one, se->expr);
3117 	}
3118     }
3119   else   /* as is null; this is an old-fashioned 1-based array.  */
3120     {
3121       if (op != GFC_ISYM_LBOUND)
3122         {
3123 	  se->expr = fold_build2_loc (input_location, MAX_EXPR,
3124 				      gfc_array_index_type, size,
3125 				      gfc_index_zero_node);
3126 	}
3127       else
3128 	se->expr = gfc_index_one_node;
3129     }
3130 
3131 
3132   type = gfc_typenode_for_spec (&expr->ts);
3133   se->expr = convert (type, se->expr);
3134 }
3135 
3136 
3137 static void
conv_intrinsic_cobound(gfc_se * se,gfc_expr * expr)3138 conv_intrinsic_cobound (gfc_se * se, gfc_expr * expr)
3139 {
3140   gfc_actual_arglist *arg;
3141   gfc_actual_arglist *arg2;
3142   gfc_se argse;
3143   tree bound, resbound, resbound2, desc, cond, tmp;
3144   tree type;
3145   int corank;
3146 
3147   gcc_assert (expr->value.function.isym->id == GFC_ISYM_LCOBOUND
3148 	      || expr->value.function.isym->id == GFC_ISYM_UCOBOUND
3149 	      || expr->value.function.isym->id == GFC_ISYM_THIS_IMAGE);
3150 
3151   arg = expr->value.function.actual;
3152   arg2 = arg->next;
3153 
3154   gcc_assert (arg->expr->expr_type == EXPR_VARIABLE);
3155   corank = gfc_get_corank (arg->expr);
3156 
3157   gfc_init_se (&argse, NULL);
3158   argse.want_coarray = 1;
3159 
3160   gfc_conv_expr_descriptor (&argse, arg->expr);
3161   gfc_add_block_to_block (&se->pre, &argse.pre);
3162   gfc_add_block_to_block (&se->post, &argse.post);
3163   desc = argse.expr;
3164 
3165   if (se->ss)
3166     {
3167       /* Create an implicit second parameter from the loop variable.  */
3168       gcc_assert (!arg2->expr);
3169       gcc_assert (corank > 0);
3170       gcc_assert (se->loop->dimen == 1);
3171       gcc_assert (se->ss->info->expr == expr);
3172 
3173       bound = se->loop->loopvar[0];
3174       bound = fold_build2_loc (input_location, PLUS_EXPR, gfc_array_index_type,
3175 			       bound, gfc_rank_cst[arg->expr->rank]);
3176       gfc_advance_se_ss_chain (se);
3177     }
3178   else
3179     {
3180       /* use the passed argument.  */
3181       gcc_assert (arg2->expr);
3182       gfc_init_se (&argse, NULL);
3183       gfc_conv_expr_type (&argse, arg2->expr, gfc_array_index_type);
3184       gfc_add_block_to_block (&se->pre, &argse.pre);
3185       bound = argse.expr;
3186 
3187       if (INTEGER_CST_P (bound))
3188 	{
3189 	  if (wi::ltu_p (wi::to_wide (bound), 1)
3190 	      || wi::gtu_p (wi::to_wide (bound),
3191 			    GFC_TYPE_ARRAY_CORANK (TREE_TYPE (desc))))
3192 	    gfc_error ("%<dim%> argument of %s intrinsic at %L is not a valid "
3193 		       "dimension index", expr->value.function.isym->name,
3194 		       &expr->where);
3195 	}
3196       else if (gfc_option.rtcheck & GFC_RTCHECK_BOUNDS)
3197         {
3198 	  bound = gfc_evaluate_now (bound, &se->pre);
3199 	  cond = fold_build2_loc (input_location, LT_EXPR, logical_type_node,
3200 				  bound, build_int_cst (TREE_TYPE (bound), 1));
3201 	  tmp = gfc_rank_cst[GFC_TYPE_ARRAY_CORANK (TREE_TYPE (desc))];
3202 	  tmp = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
3203 				 bound, tmp);
3204 	  cond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
3205 				  logical_type_node, cond, tmp);
3206 	  gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
3207 				   gfc_msg_fault);
3208 	}
3209 
3210 
3211       /* Subtract 1 to get to zero based and add dimensions.  */
3212       switch (arg->expr->rank)
3213 	{
3214 	case 0:
3215 	  bound = fold_build2_loc (input_location, MINUS_EXPR,
3216 				   gfc_array_index_type, bound,
3217 				   gfc_index_one_node);
3218 	case 1:
3219 	  break;
3220 	default:
3221 	  bound = fold_build2_loc (input_location, PLUS_EXPR,
3222 				   gfc_array_index_type, bound,
3223 				   gfc_rank_cst[arg->expr->rank - 1]);
3224 	}
3225     }
3226 
3227   resbound = gfc_conv_descriptor_lbound_get (desc, bound);
3228 
3229   /* Handle UCOBOUND with special handling of the last codimension.  */
3230   if (expr->value.function.isym->id == GFC_ISYM_UCOBOUND)
3231     {
3232       /* Last codimension: For -fcoarray=single just return
3233 	 the lcobound - otherwise add
3234 	   ceiling (real (num_images ()) / real (size)) - 1
3235 	 = (num_images () + size - 1) / size - 1
3236 	 = (num_images - 1) / size(),
3237          where size is the product of the extent of all but the last
3238 	 codimension.  */
3239 
3240       if (flag_coarray != GFC_FCOARRAY_SINGLE && corank > 1)
3241 	{
3242           tree cosize;
3243 
3244 	  cosize = gfc_conv_descriptor_cosize (desc, arg->expr->rank, corank);
3245 	  tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_num_images,
3246 				     2, integer_zero_node,
3247 				     build_int_cst (integer_type_node, -1));
3248 	  tmp = fold_build2_loc (input_location, MINUS_EXPR,
3249 				 gfc_array_index_type,
3250 				 fold_convert (gfc_array_index_type, tmp),
3251 				 build_int_cst (gfc_array_index_type, 1));
3252 	  tmp = fold_build2_loc (input_location, TRUNC_DIV_EXPR,
3253 				 gfc_array_index_type, tmp,
3254 				 fold_convert (gfc_array_index_type, cosize));
3255 	  resbound = fold_build2_loc (input_location, PLUS_EXPR,
3256 				      gfc_array_index_type, resbound, tmp);
3257 	}
3258       else if (flag_coarray != GFC_FCOARRAY_SINGLE)
3259 	{
3260 	  /* ubound = lbound + num_images() - 1.  */
3261 	  tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_num_images,
3262 				     2, integer_zero_node,
3263 				     build_int_cst (integer_type_node, -1));
3264 	  tmp = fold_build2_loc (input_location, MINUS_EXPR,
3265 				 gfc_array_index_type,
3266 				 fold_convert (gfc_array_index_type, tmp),
3267 				 build_int_cst (gfc_array_index_type, 1));
3268 	  resbound = fold_build2_loc (input_location, PLUS_EXPR,
3269 				      gfc_array_index_type, resbound, tmp);
3270 	}
3271 
3272       if (corank > 1)
3273 	{
3274 	  cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
3275 				  bound,
3276 				  build_int_cst (TREE_TYPE (bound),
3277 						 arg->expr->rank + corank - 1));
3278 
3279 	  resbound2 = gfc_conv_descriptor_ubound_get (desc, bound);
3280 	  se->expr = fold_build3_loc (input_location, COND_EXPR,
3281 				      gfc_array_index_type, cond,
3282 				      resbound, resbound2);
3283 	}
3284       else
3285 	se->expr = resbound;
3286     }
3287   else
3288     se->expr = resbound;
3289 
3290   type = gfc_typenode_for_spec (&expr->ts);
3291   se->expr = convert (type, se->expr);
3292 }
3293 
3294 
3295 static void
conv_intrinsic_stride(gfc_se * se,gfc_expr * expr)3296 conv_intrinsic_stride (gfc_se * se, gfc_expr * expr)
3297 {
3298   gfc_actual_arglist *array_arg;
3299   gfc_actual_arglist *dim_arg;
3300   gfc_se argse;
3301   tree desc, tmp;
3302 
3303   array_arg = expr->value.function.actual;
3304   dim_arg = array_arg->next;
3305 
3306   gcc_assert (array_arg->expr->expr_type == EXPR_VARIABLE);
3307 
3308   gfc_init_se (&argse, NULL);
3309   gfc_conv_expr_descriptor (&argse, array_arg->expr);
3310   gfc_add_block_to_block (&se->pre, &argse.pre);
3311   gfc_add_block_to_block (&se->post, &argse.post);
3312   desc = argse.expr;
3313 
3314   gcc_assert (dim_arg->expr);
3315   gfc_init_se (&argse, NULL);
3316   gfc_conv_expr_type (&argse, dim_arg->expr, gfc_array_index_type);
3317   gfc_add_block_to_block (&se->pre, &argse.pre);
3318   tmp = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
3319 			 argse.expr, gfc_index_one_node);
3320   se->expr = gfc_conv_descriptor_stride_get (desc, tmp);
3321 }
3322 
3323 static void
gfc_conv_intrinsic_abs(gfc_se * se,gfc_expr * expr)3324 gfc_conv_intrinsic_abs (gfc_se * se, gfc_expr * expr)
3325 {
3326   tree arg, cabs;
3327 
3328   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
3329 
3330   switch (expr->value.function.actual->expr->ts.type)
3331     {
3332     case BT_INTEGER:
3333     case BT_REAL:
3334       se->expr = fold_build1_loc (input_location, ABS_EXPR, TREE_TYPE (arg),
3335 				  arg);
3336       break;
3337 
3338     case BT_COMPLEX:
3339       cabs = gfc_builtin_decl_for_float_kind (BUILT_IN_CABS, expr->ts.kind);
3340       se->expr = build_call_expr_loc (input_location, cabs, 1, arg);
3341       break;
3342 
3343     default:
3344       gcc_unreachable ();
3345     }
3346 }
3347 
3348 
3349 /* Create a complex value from one or two real components.  */
3350 
3351 static void
gfc_conv_intrinsic_cmplx(gfc_se * se,gfc_expr * expr,int both)3352 gfc_conv_intrinsic_cmplx (gfc_se * se, gfc_expr * expr, int both)
3353 {
3354   tree real;
3355   tree imag;
3356   tree type;
3357   tree *args;
3358   unsigned int num_args;
3359 
3360   num_args = gfc_intrinsic_argument_list_length (expr);
3361   args = XALLOCAVEC (tree, num_args);
3362 
3363   type = gfc_typenode_for_spec (&expr->ts);
3364   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
3365   real = convert (TREE_TYPE (type), args[0]);
3366   if (both)
3367     imag = convert (TREE_TYPE (type), args[1]);
3368   else if (TREE_CODE (TREE_TYPE (args[0])) == COMPLEX_TYPE)
3369     {
3370       imag = fold_build1_loc (input_location, IMAGPART_EXPR,
3371 			      TREE_TYPE (TREE_TYPE (args[0])), args[0]);
3372       imag = convert (TREE_TYPE (type), imag);
3373     }
3374   else
3375     imag = build_real_from_int_cst (TREE_TYPE (type), integer_zero_node);
3376 
3377   se->expr = fold_build2_loc (input_location, COMPLEX_EXPR, type, real, imag);
3378 }
3379 
3380 
3381 /* Remainder function MOD(A, P) = A - INT(A / P) * P
3382                       MODULO(A, P) = A - FLOOR (A / P) * P
3383 
3384    The obvious algorithms above are numerically instable for large
3385    arguments, hence these intrinsics are instead implemented via calls
3386    to the fmod family of functions.  It is the responsibility of the
3387    user to ensure that the second argument is non-zero.  */
3388 
3389 static void
gfc_conv_intrinsic_mod(gfc_se * se,gfc_expr * expr,int modulo)3390 gfc_conv_intrinsic_mod (gfc_se * se, gfc_expr * expr, int modulo)
3391 {
3392   tree type;
3393   tree tmp;
3394   tree test;
3395   tree test2;
3396   tree fmod;
3397   tree zero;
3398   tree args[2];
3399 
3400   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3401 
3402   switch (expr->ts.type)
3403     {
3404     case BT_INTEGER:
3405       /* Integer case is easy, we've got a builtin op.  */
3406       type = TREE_TYPE (args[0]);
3407 
3408       if (modulo)
3409        se->expr = fold_build2_loc (input_location, FLOOR_MOD_EXPR, type,
3410 				   args[0], args[1]);
3411       else
3412        se->expr = fold_build2_loc (input_location, TRUNC_MOD_EXPR, type,
3413 				   args[0], args[1]);
3414       break;
3415 
3416     case BT_REAL:
3417       fmod = NULL_TREE;
3418       /* Check if we have a builtin fmod.  */
3419       fmod = gfc_builtin_decl_for_float_kind (BUILT_IN_FMOD, expr->ts.kind);
3420 
3421       /* The builtin should always be available.  */
3422       gcc_assert (fmod != NULL_TREE);
3423 
3424       tmp = build_addr (fmod);
3425       se->expr = build_call_array_loc (input_location,
3426 				       TREE_TYPE (TREE_TYPE (fmod)),
3427                                        tmp, 2, args);
3428       if (modulo == 0)
3429 	return;
3430 
3431       type = TREE_TYPE (args[0]);
3432 
3433       args[0] = gfc_evaluate_now (args[0], &se->pre);
3434       args[1] = gfc_evaluate_now (args[1], &se->pre);
3435 
3436       /* Definition:
3437 	 modulo = arg - floor (arg/arg2) * arg2
3438 
3439 	 In order to calculate the result accurately, we use the fmod
3440 	 function as follows.
3441 
3442 	 res = fmod (arg, arg2);
3443 	 if (res)
3444 	   {
3445 	     if ((arg < 0) xor (arg2 < 0))
3446 	       res += arg2;
3447 	   }
3448 	 else
3449 	   res = copysign (0., arg2);
3450 
3451 	 => As two nested ternary exprs:
3452 
3453 	 res = res ? (((arg < 0) xor (arg2 < 0)) ? res + arg2 : res)
3454 	       : copysign (0., arg2);
3455 
3456       */
3457 
3458       zero = gfc_build_const (type, integer_zero_node);
3459       tmp = gfc_evaluate_now (se->expr, &se->pre);
3460       if (!flag_signed_zeros)
3461 	{
3462 	  test = fold_build2_loc (input_location, LT_EXPR, logical_type_node,
3463 				  args[0], zero);
3464 	  test2 = fold_build2_loc (input_location, LT_EXPR, logical_type_node,
3465 				   args[1], zero);
3466 	  test2 = fold_build2_loc (input_location, TRUTH_XOR_EXPR,
3467 				   logical_type_node, test, test2);
3468 	  test = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
3469 				  tmp, zero);
3470 	  test = fold_build2_loc (input_location, TRUTH_AND_EXPR,
3471 				  logical_type_node, test, test2);
3472 	  test = gfc_evaluate_now (test, &se->pre);
3473 	  se->expr = fold_build3_loc (input_location, COND_EXPR, type, test,
3474 				      fold_build2_loc (input_location,
3475 						       PLUS_EXPR,
3476 						       type, tmp, args[1]),
3477 				      tmp);
3478 	}
3479       else
3480 	{
3481 	  tree expr1, copysign, cscall;
3482 	  copysign = gfc_builtin_decl_for_float_kind (BUILT_IN_COPYSIGN,
3483 						      expr->ts.kind);
3484 	  test = fold_build2_loc (input_location, LT_EXPR, logical_type_node,
3485 				  args[0], zero);
3486 	  test2 = fold_build2_loc (input_location, LT_EXPR, logical_type_node,
3487 				   args[1], zero);
3488 	  test2 = fold_build2_loc (input_location, TRUTH_XOR_EXPR,
3489 				   logical_type_node, test, test2);
3490 	  expr1 = fold_build3_loc (input_location, COND_EXPR, type, test2,
3491 				   fold_build2_loc (input_location,
3492 						    PLUS_EXPR,
3493 						    type, tmp, args[1]),
3494 				   tmp);
3495 	  test = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
3496 				  tmp, zero);
3497 	  cscall = build_call_expr_loc (input_location, copysign, 2, zero,
3498 					args[1]);
3499 	  se->expr = fold_build3_loc (input_location, COND_EXPR, type, test,
3500 				      expr1, cscall);
3501 	}
3502       return;
3503 
3504     default:
3505       gcc_unreachable ();
3506     }
3507 }
3508 
3509 /* DSHIFTL(I,J,S) = (I << S) | (J >> (BITSIZE(J) - S))
3510    DSHIFTR(I,J,S) = (I << (BITSIZE(I) - S)) | (J >> S)
3511    where the right shifts are logical (i.e. 0's are shifted in).
3512    Because SHIFT_EXPR's want shifts strictly smaller than the integral
3513    type width, we have to special-case both S == 0 and S == BITSIZE(J):
3514      DSHIFTL(I,J,0) = I
3515      DSHIFTL(I,J,BITSIZE) = J
3516      DSHIFTR(I,J,0) = J
3517      DSHIFTR(I,J,BITSIZE) = I.  */
3518 
3519 static void
gfc_conv_intrinsic_dshift(gfc_se * se,gfc_expr * expr,bool dshiftl)3520 gfc_conv_intrinsic_dshift (gfc_se * se, gfc_expr * expr, bool dshiftl)
3521 {
3522   tree type, utype, stype, arg1, arg2, shift, res, left, right;
3523   tree args[3], cond, tmp;
3524   int bitsize;
3525 
3526   gfc_conv_intrinsic_function_args (se, expr, args, 3);
3527 
3528   gcc_assert (TREE_TYPE (args[0]) == TREE_TYPE (args[1]));
3529   type = TREE_TYPE (args[0]);
3530   bitsize = TYPE_PRECISION (type);
3531   utype = unsigned_type_for (type);
3532   stype = TREE_TYPE (args[2]);
3533 
3534   arg1 = gfc_evaluate_now (args[0], &se->pre);
3535   arg2 = gfc_evaluate_now (args[1], &se->pre);
3536   shift = gfc_evaluate_now (args[2], &se->pre);
3537 
3538   /* The generic case.  */
3539   tmp = fold_build2_loc (input_location, MINUS_EXPR, stype,
3540 			 build_int_cst (stype, bitsize), shift);
3541   left = fold_build2_loc (input_location, LSHIFT_EXPR, type,
3542 			  arg1, dshiftl ? shift : tmp);
3543 
3544   right = fold_build2_loc (input_location, RSHIFT_EXPR, utype,
3545 			   fold_convert (utype, arg2), dshiftl ? tmp : shift);
3546   right = fold_convert (type, right);
3547 
3548   res = fold_build2_loc (input_location, BIT_IOR_EXPR, type, left, right);
3549 
3550   /* Special cases.  */
3551   cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, shift,
3552 			  build_int_cst (stype, 0));
3553   res = fold_build3_loc (input_location, COND_EXPR, type, cond,
3554 			 dshiftl ? arg1 : arg2, res);
3555 
3556   cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, shift,
3557 			  build_int_cst (stype, bitsize));
3558   res = fold_build3_loc (input_location, COND_EXPR, type, cond,
3559 			 dshiftl ? arg2 : arg1, res);
3560 
3561   se->expr = res;
3562 }
3563 
3564 
3565 /* Positive difference DIM (x, y) = ((x - y) < 0) ? 0 : x - y.  */
3566 
3567 static void
gfc_conv_intrinsic_dim(gfc_se * se,gfc_expr * expr)3568 gfc_conv_intrinsic_dim (gfc_se * se, gfc_expr * expr)
3569 {
3570   tree val;
3571   tree tmp;
3572   tree type;
3573   tree zero;
3574   tree args[2];
3575 
3576   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3577   type = TREE_TYPE (args[0]);
3578 
3579   val = fold_build2_loc (input_location, MINUS_EXPR, type, args[0], args[1]);
3580   val = gfc_evaluate_now (val, &se->pre);
3581 
3582   zero = gfc_build_const (type, integer_zero_node);
3583   tmp = fold_build2_loc (input_location, LE_EXPR, logical_type_node, val, zero);
3584   se->expr = fold_build3_loc (input_location, COND_EXPR, type, tmp, zero, val);
3585 }
3586 
3587 
3588 /* SIGN(A, B) is absolute value of A times sign of B.
3589    The real value versions use library functions to ensure the correct
3590    handling of negative zero.  Integer case implemented as:
3591    SIGN(A, B) = { tmp = (A ^ B) >> C; (A + tmp) ^ tmp }
3592   */
3593 
3594 static void
gfc_conv_intrinsic_sign(gfc_se * se,gfc_expr * expr)3595 gfc_conv_intrinsic_sign (gfc_se * se, gfc_expr * expr)
3596 {
3597   tree tmp;
3598   tree type;
3599   tree args[2];
3600 
3601   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3602   if (expr->ts.type == BT_REAL)
3603     {
3604       tree abs;
3605 
3606       tmp = gfc_builtin_decl_for_float_kind (BUILT_IN_COPYSIGN, expr->ts.kind);
3607       abs = gfc_builtin_decl_for_float_kind (BUILT_IN_FABS, expr->ts.kind);
3608 
3609       /* We explicitly have to ignore the minus sign. We do so by using
3610 	 result = (arg1 == 0) ? abs(arg0) : copysign(arg0, arg1).  */
3611       if (!flag_sign_zero
3612 	  && MODE_HAS_SIGNED_ZEROS (TYPE_MODE (TREE_TYPE (args[1]))))
3613 	{
3614 	  tree cond, zero;
3615 	  zero = build_real_from_int_cst (TREE_TYPE (args[1]), integer_zero_node);
3616 	  cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
3617 				  args[1], zero);
3618 	  se->expr = fold_build3_loc (input_location, COND_EXPR,
3619 				  TREE_TYPE (args[0]), cond,
3620 				  build_call_expr_loc (input_location, abs, 1,
3621 						       args[0]),
3622 				  build_call_expr_loc (input_location, tmp, 2,
3623 						       args[0], args[1]));
3624 	}
3625       else
3626         se->expr = build_call_expr_loc (input_location, tmp, 2,
3627 					args[0], args[1]);
3628       return;
3629     }
3630 
3631   /* Having excluded floating point types, we know we are now dealing
3632      with signed integer types.  */
3633   type = TREE_TYPE (args[0]);
3634 
3635   /* Args[0] is used multiple times below.  */
3636   args[0] = gfc_evaluate_now (args[0], &se->pre);
3637 
3638   /* Construct (A ^ B) >> 31, which generates a bit mask of all zeros if
3639      the signs of A and B are the same, and of all ones if they differ.  */
3640   tmp = fold_build2_loc (input_location, BIT_XOR_EXPR, type, args[0], args[1]);
3641   tmp = fold_build2_loc (input_location, RSHIFT_EXPR, type, tmp,
3642 			 build_int_cst (type, TYPE_PRECISION (type) - 1));
3643   tmp = gfc_evaluate_now (tmp, &se->pre);
3644 
3645   /* Construct (A + tmp) ^ tmp, which is A if tmp is zero, and -A if tmp]
3646      is all ones (i.e. -1).  */
3647   se->expr = fold_build2_loc (input_location, BIT_XOR_EXPR, type,
3648 			      fold_build2_loc (input_location, PLUS_EXPR,
3649 					       type, args[0], tmp), tmp);
3650 }
3651 
3652 
3653 /* Test for the presence of an optional argument.  */
3654 
3655 static void
gfc_conv_intrinsic_present(gfc_se * se,gfc_expr * expr)3656 gfc_conv_intrinsic_present (gfc_se * se, gfc_expr * expr)
3657 {
3658   gfc_expr *arg;
3659 
3660   arg = expr->value.function.actual->expr;
3661   gcc_assert (arg->expr_type == EXPR_VARIABLE);
3662   se->expr = gfc_conv_expr_present (arg->symtree->n.sym);
3663   se->expr = convert (gfc_typenode_for_spec (&expr->ts), se->expr);
3664 }
3665 
3666 
3667 /* Calculate the double precision product of two single precision values.  */
3668 
3669 static void
gfc_conv_intrinsic_dprod(gfc_se * se,gfc_expr * expr)3670 gfc_conv_intrinsic_dprod (gfc_se * se, gfc_expr * expr)
3671 {
3672   tree type;
3673   tree args[2];
3674 
3675   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3676 
3677   /* Convert the args to double precision before multiplying.  */
3678   type = gfc_typenode_for_spec (&expr->ts);
3679   args[0] = convert (type, args[0]);
3680   args[1] = convert (type, args[1]);
3681   se->expr = fold_build2_loc (input_location, MULT_EXPR, type, args[0],
3682 			      args[1]);
3683 }
3684 
3685 
3686 /* Return a length one character string containing an ascii character.  */
3687 
3688 static void
gfc_conv_intrinsic_char(gfc_se * se,gfc_expr * expr)3689 gfc_conv_intrinsic_char (gfc_se * se, gfc_expr * expr)
3690 {
3691   tree arg[2];
3692   tree var;
3693   tree type;
3694   unsigned int num_args;
3695 
3696   num_args = gfc_intrinsic_argument_list_length (expr);
3697   gfc_conv_intrinsic_function_args (se, expr, arg, num_args);
3698 
3699   type = gfc_get_char_type (expr->ts.kind);
3700   var = gfc_create_var (type, "char");
3701 
3702   arg[0] = fold_build1_loc (input_location, NOP_EXPR, type, arg[0]);
3703   gfc_add_modify (&se->pre, var, arg[0]);
3704   se->expr = gfc_build_addr_expr (build_pointer_type (type), var);
3705   se->string_length = build_int_cst (gfc_charlen_type_node, 1);
3706 }
3707 
3708 
3709 static void
gfc_conv_intrinsic_ctime(gfc_se * se,gfc_expr * expr)3710 gfc_conv_intrinsic_ctime (gfc_se * se, gfc_expr * expr)
3711 {
3712   tree var;
3713   tree len;
3714   tree tmp;
3715   tree cond;
3716   tree fndecl;
3717   tree *args;
3718   unsigned int num_args;
3719 
3720   num_args = gfc_intrinsic_argument_list_length (expr) + 2;
3721   args = XALLOCAVEC (tree, num_args);
3722 
3723   var = gfc_create_var (pchar_type_node, "pstr");
3724   len = gfc_create_var (gfc_charlen_type_node, "len");
3725 
3726   gfc_conv_intrinsic_function_args (se, expr, &args[2], num_args - 2);
3727   args[0] = gfc_build_addr_expr (NULL_TREE, var);
3728   args[1] = gfc_build_addr_expr (NULL_TREE, len);
3729 
3730   fndecl = build_addr (gfor_fndecl_ctime);
3731   tmp = build_call_array_loc (input_location,
3732 			  TREE_TYPE (TREE_TYPE (gfor_fndecl_ctime)),
3733 			  fndecl, num_args, args);
3734   gfc_add_expr_to_block (&se->pre, tmp);
3735 
3736   /* Free the temporary afterwards, if necessary.  */
3737   cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
3738 			  len, build_int_cst (TREE_TYPE (len), 0));
3739   tmp = gfc_call_free (var);
3740   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
3741   gfc_add_expr_to_block (&se->post, tmp);
3742 
3743   se->expr = var;
3744   se->string_length = len;
3745 }
3746 
3747 
3748 static void
gfc_conv_intrinsic_fdate(gfc_se * se,gfc_expr * expr)3749 gfc_conv_intrinsic_fdate (gfc_se * se, gfc_expr * expr)
3750 {
3751   tree var;
3752   tree len;
3753   tree tmp;
3754   tree cond;
3755   tree fndecl;
3756   tree *args;
3757   unsigned int num_args;
3758 
3759   num_args = gfc_intrinsic_argument_list_length (expr) + 2;
3760   args = XALLOCAVEC (tree, num_args);
3761 
3762   var = gfc_create_var (pchar_type_node, "pstr");
3763   len = gfc_create_var (gfc_charlen_type_node, "len");
3764 
3765   gfc_conv_intrinsic_function_args (se, expr, &args[2], num_args - 2);
3766   args[0] = gfc_build_addr_expr (NULL_TREE, var);
3767   args[1] = gfc_build_addr_expr (NULL_TREE, len);
3768 
3769   fndecl = build_addr (gfor_fndecl_fdate);
3770   tmp = build_call_array_loc (input_location,
3771 			  TREE_TYPE (TREE_TYPE (gfor_fndecl_fdate)),
3772 			  fndecl, num_args, args);
3773   gfc_add_expr_to_block (&se->pre, tmp);
3774 
3775   /* Free the temporary afterwards, if necessary.  */
3776   cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
3777 			  len, build_int_cst (TREE_TYPE (len), 0));
3778   tmp = gfc_call_free (var);
3779   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
3780   gfc_add_expr_to_block (&se->post, tmp);
3781 
3782   se->expr = var;
3783   se->string_length = len;
3784 }
3785 
3786 
3787 /* Generate a direct call to free() for the FREE subroutine.  */
3788 
3789 static tree
conv_intrinsic_free(gfc_code * code)3790 conv_intrinsic_free (gfc_code *code)
3791 {
3792   stmtblock_t block;
3793   gfc_se argse;
3794   tree arg, call;
3795 
3796   gfc_init_se (&argse, NULL);
3797   gfc_conv_expr (&argse, code->ext.actual->expr);
3798   arg = fold_convert (ptr_type_node, argse.expr);
3799 
3800   gfc_init_block (&block);
3801   call = build_call_expr_loc (input_location,
3802 			      builtin_decl_explicit (BUILT_IN_FREE), 1, arg);
3803   gfc_add_expr_to_block (&block, call);
3804   return gfc_finish_block (&block);
3805 }
3806 
3807 
3808 /* Call the RANDOM_INIT library subroutine with a hidden argument for
3809    handling seeding on coarray images.  */
3810 
3811 static tree
conv_intrinsic_random_init(gfc_code * code)3812 conv_intrinsic_random_init (gfc_code *code)
3813 {
3814   stmtblock_t block;
3815   gfc_se se;
3816   tree arg1, arg2, tmp;
3817   /* On none coarray == lib compiles use LOGICAL(4) else regular LOGICAL.  */
3818   tree used_bool_type_node = flag_coarray == GFC_FCOARRAY_LIB
3819 			     ? logical_type_node
3820 			     : gfc_get_logical_type (4);
3821 
3822   /* Make the function call.  */
3823   gfc_init_block (&block);
3824   gfc_init_se (&se, NULL);
3825 
3826   /* Convert REPEATABLE to the desired LOGICAL entity.  */
3827   gfc_conv_expr (&se, code->ext.actual->expr);
3828   gfc_add_block_to_block (&block, &se.pre);
3829   arg1 = fold_convert (used_bool_type_node, gfc_evaluate_now (se.expr, &block));
3830   gfc_add_block_to_block (&block, &se.post);
3831 
3832   /* Convert IMAGE_DISTINCT to the desired LOGICAL entity.  */
3833   gfc_conv_expr (&se, code->ext.actual->next->expr);
3834   gfc_add_block_to_block (&block, &se.pre);
3835   arg2 = fold_convert (used_bool_type_node, gfc_evaluate_now (se.expr, &block));
3836   gfc_add_block_to_block (&block, &se.post);
3837 
3838   if (flag_coarray == GFC_FCOARRAY_LIB)
3839     {
3840       tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_random_init,
3841 				 2, arg1, arg2);
3842     }
3843   else
3844     {
3845       /* The ABI for libgfortran needs to be maintained, so a hidden
3846 	 argument must be include if code is compiled with -fcoarray=single
3847 	 or without the option.  Set to 0.  */
3848       tree arg3 = build_int_cst (gfc_get_int_type (4), 0);
3849       tmp = build_call_expr_loc (input_location, gfor_fndecl_random_init,
3850 				 3, arg1, arg2, arg3);
3851     }
3852 
3853   gfc_add_expr_to_block (&block, tmp);
3854 
3855   return gfc_finish_block (&block);
3856 }
3857 
3858 
3859 /* Call the SYSTEM_CLOCK library functions, handling the type and kind
3860    conversions.  */
3861 
3862 static tree
conv_intrinsic_system_clock(gfc_code * code)3863 conv_intrinsic_system_clock (gfc_code *code)
3864 {
3865   stmtblock_t block;
3866   gfc_se count_se, count_rate_se, count_max_se;
3867   tree arg1 = NULL_TREE, arg2 = NULL_TREE, arg3 = NULL_TREE;
3868   tree tmp;
3869   int least;
3870 
3871   gfc_expr *count = code->ext.actual->expr;
3872   gfc_expr *count_rate = code->ext.actual->next->expr;
3873   gfc_expr *count_max = code->ext.actual->next->next->expr;
3874 
3875   /* Evaluate our arguments.  */
3876   if (count)
3877     {
3878       gfc_init_se (&count_se, NULL);
3879       gfc_conv_expr (&count_se, count);
3880     }
3881 
3882   if (count_rate)
3883     {
3884       gfc_init_se (&count_rate_se, NULL);
3885       gfc_conv_expr (&count_rate_se, count_rate);
3886     }
3887 
3888   if (count_max)
3889     {
3890       gfc_init_se (&count_max_se, NULL);
3891       gfc_conv_expr (&count_max_se, count_max);
3892     }
3893 
3894   /* Find the smallest kind found of the arguments.  */
3895   least = 16;
3896   least = (count && count->ts.kind < least) ? count->ts.kind : least;
3897   least = (count_rate && count_rate->ts.kind < least) ? count_rate->ts.kind
3898 						      : least;
3899   least = (count_max && count_max->ts.kind < least) ? count_max->ts.kind
3900 						    : least;
3901 
3902   /* Prepare temporary variables.  */
3903 
3904   if (count)
3905     {
3906       if (least >= 8)
3907 	arg1 = gfc_create_var (gfc_get_int_type (8), "count");
3908       else if (least == 4)
3909 	arg1 = gfc_create_var (gfc_get_int_type (4), "count");
3910       else if (count->ts.kind == 1)
3911         arg1 = gfc_conv_mpz_to_tree (gfc_integer_kinds[0].pedantic_min_int,
3912 				     count->ts.kind);
3913       else
3914         arg1 = gfc_conv_mpz_to_tree (gfc_integer_kinds[1].pedantic_min_int,
3915 				     count->ts.kind);
3916     }
3917 
3918   if (count_rate)
3919     {
3920       if (least >= 8)
3921 	arg2 = gfc_create_var (gfc_get_int_type (8), "count_rate");
3922       else if (least == 4)
3923 	arg2 = gfc_create_var (gfc_get_int_type (4), "count_rate");
3924       else
3925         arg2 = integer_zero_node;
3926     }
3927 
3928   if (count_max)
3929     {
3930       if (least >= 8)
3931 	arg3 = gfc_create_var (gfc_get_int_type (8), "count_max");
3932       else if (least == 4)
3933 	arg3 = gfc_create_var (gfc_get_int_type (4), "count_max");
3934       else
3935         arg3 = integer_zero_node;
3936     }
3937 
3938   /* Make the function call.  */
3939   gfc_init_block (&block);
3940 
3941 if (least <= 2)
3942   {
3943     if (least == 1)
3944       {
3945 	arg1 ? gfc_build_addr_expr (NULL_TREE, arg1)
3946 	       : null_pointer_node;
3947 	arg2 ? gfc_build_addr_expr (NULL_TREE, arg2)
3948 	       : null_pointer_node;
3949 	arg3 ? gfc_build_addr_expr (NULL_TREE, arg3)
3950 	       : null_pointer_node;
3951       }
3952 
3953     if (least == 2)
3954       {
3955 	arg1 ? gfc_build_addr_expr (NULL_TREE, arg1)
3956 	       : null_pointer_node;
3957 	arg2 ? gfc_build_addr_expr (NULL_TREE, arg2)
3958 	       : null_pointer_node;
3959 	arg3 ? gfc_build_addr_expr (NULL_TREE, arg3)
3960 	       : null_pointer_node;
3961       }
3962   }
3963 else
3964   {
3965     if (least == 4)
3966       {
3967 	tmp = build_call_expr_loc (input_location,
3968 		gfor_fndecl_system_clock4, 3,
3969 		arg1 ? gfc_build_addr_expr (NULL_TREE, arg1)
3970 		       : null_pointer_node,
3971 		arg2 ? gfc_build_addr_expr (NULL_TREE, arg2)
3972 		       : null_pointer_node,
3973 		arg3 ? gfc_build_addr_expr (NULL_TREE, arg3)
3974 		       : null_pointer_node);
3975 	gfc_add_expr_to_block (&block, tmp);
3976       }
3977     /* Handle kind>=8, 10, or 16 arguments */
3978     if (least >= 8)
3979       {
3980 	tmp = build_call_expr_loc (input_location,
3981 		gfor_fndecl_system_clock8, 3,
3982 		arg1 ? gfc_build_addr_expr (NULL_TREE, arg1)
3983 		       : null_pointer_node,
3984 		arg2 ? gfc_build_addr_expr (NULL_TREE, arg2)
3985 		       : null_pointer_node,
3986 		arg3 ? gfc_build_addr_expr (NULL_TREE, arg3)
3987 		       : null_pointer_node);
3988 	gfc_add_expr_to_block (&block, tmp);
3989       }
3990   }
3991 
3992   /* And store values back if needed.  */
3993   if (arg1 && arg1 != count_se.expr)
3994     gfc_add_modify (&block, count_se.expr,
3995 		    fold_convert (TREE_TYPE (count_se.expr), arg1));
3996   if (arg2 && arg2 != count_rate_se.expr)
3997     gfc_add_modify (&block, count_rate_se.expr,
3998 		    fold_convert (TREE_TYPE (count_rate_se.expr), arg2));
3999   if (arg3 && arg3 != count_max_se.expr)
4000     gfc_add_modify (&block, count_max_se.expr,
4001 		    fold_convert (TREE_TYPE (count_max_se.expr), arg3));
4002 
4003   return gfc_finish_block (&block);
4004 }
4005 
4006 
4007 /* Return a character string containing the tty name.  */
4008 
4009 static void
gfc_conv_intrinsic_ttynam(gfc_se * se,gfc_expr * expr)4010 gfc_conv_intrinsic_ttynam (gfc_se * se, gfc_expr * expr)
4011 {
4012   tree var;
4013   tree len;
4014   tree tmp;
4015   tree cond;
4016   tree fndecl;
4017   tree *args;
4018   unsigned int num_args;
4019 
4020   num_args = gfc_intrinsic_argument_list_length (expr) + 2;
4021   args = XALLOCAVEC (tree, num_args);
4022 
4023   var = gfc_create_var (pchar_type_node, "pstr");
4024   len = gfc_create_var (gfc_charlen_type_node, "len");
4025 
4026   gfc_conv_intrinsic_function_args (se, expr, &args[2], num_args - 2);
4027   args[0] = gfc_build_addr_expr (NULL_TREE, var);
4028   args[1] = gfc_build_addr_expr (NULL_TREE, len);
4029 
4030   fndecl = build_addr (gfor_fndecl_ttynam);
4031   tmp = build_call_array_loc (input_location,
4032 			  TREE_TYPE (TREE_TYPE (gfor_fndecl_ttynam)),
4033 			  fndecl, num_args, args);
4034   gfc_add_expr_to_block (&se->pre, tmp);
4035 
4036   /* Free the temporary afterwards, if necessary.  */
4037   cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
4038 			  len, build_int_cst (TREE_TYPE (len), 0));
4039   tmp = gfc_call_free (var);
4040   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
4041   gfc_add_expr_to_block (&se->post, tmp);
4042 
4043   se->expr = var;
4044   se->string_length = len;
4045 }
4046 
4047 
4048 /* Get the minimum/maximum value of all the parameters.
4049     minmax (a1, a2, a3, ...)
4050     {
4051       mvar = a1;
4052       mvar = COMP (mvar, a2)
4053       mvar = COMP (mvar, a3)
4054       ...
4055       return mvar;
4056     }
4057     Where COMP is MIN/MAX_EXPR for integral types or when we don't
4058     care about NaNs, or IFN_FMIN/MAX when the target has support for
4059     fast NaN-honouring min/max.  When neither holds expand a sequence
4060     of explicit comparisons.  */
4061 
4062 /* TODO: Mismatching types can occur when specific names are used.
4063    These should be handled during resolution.  */
4064 static void
gfc_conv_intrinsic_minmax(gfc_se * se,gfc_expr * expr,enum tree_code op)4065 gfc_conv_intrinsic_minmax (gfc_se * se, gfc_expr * expr, enum tree_code op)
4066 {
4067   tree tmp;
4068   tree mvar;
4069   tree val;
4070   tree *args;
4071   tree type;
4072   tree argtype;
4073   gfc_actual_arglist *argexpr;
4074   unsigned int i, nargs;
4075 
4076   nargs = gfc_intrinsic_argument_list_length (expr);
4077   args = XALLOCAVEC (tree, nargs);
4078 
4079   gfc_conv_intrinsic_function_args (se, expr, args, nargs);
4080   type = gfc_typenode_for_spec (&expr->ts);
4081 
4082   /* Only evaluate the argument once.  */
4083   if (!VAR_P (args[0]) && !TREE_CONSTANT (args[0]))
4084     args[0] = gfc_evaluate_now (args[0], &se->pre);
4085 
4086   /* Determine suitable type of temporary, as a GNU extension allows
4087      different argument kinds.  */
4088   argtype = TREE_TYPE (args[0]);
4089   argexpr = expr->value.function.actual;
4090   for (i = 1, argexpr = argexpr->next; i < nargs; i++, argexpr = argexpr->next)
4091     {
4092       tree tmptype = TREE_TYPE (args[i]);
4093       if (TYPE_PRECISION (tmptype) > TYPE_PRECISION (argtype))
4094 	argtype = tmptype;
4095     }
4096   mvar = gfc_create_var (argtype, "M");
4097   gfc_add_modify (&se->pre, mvar, convert (argtype, args[0]));
4098 
4099   argexpr = expr->value.function.actual;
4100   for (i = 1, argexpr = argexpr->next; i < nargs; i++, argexpr = argexpr->next)
4101     {
4102       tree cond = NULL_TREE;
4103       val = args[i];
4104 
4105       /* Handle absent optional arguments by ignoring the comparison.  */
4106       if (argexpr->expr->expr_type == EXPR_VARIABLE
4107 	  && argexpr->expr->symtree->n.sym->attr.optional
4108 	  && TREE_CODE (val) == INDIRECT_REF)
4109 	{
4110 	  cond = fold_build2_loc (input_location,
4111 				NE_EXPR, logical_type_node,
4112 				TREE_OPERAND (val, 0),
4113 			build_int_cst (TREE_TYPE (TREE_OPERAND (val, 0)), 0));
4114 	}
4115       else if (!VAR_P (val) && !TREE_CONSTANT (val))
4116 	/* Only evaluate the argument once.  */
4117 	val = gfc_evaluate_now (val, &se->pre);
4118 
4119       tree calc;
4120       /* For floating point types, the question is what MAX(a, NaN) or
4121 	 MIN(a, NaN) should return (where "a" is a normal number).
4122 	 There are valid usecase for returning either one, but the
4123 	 Fortran standard doesn't specify which one should be chosen.
4124 	 Also, there is no consensus among other tested compilers.  In
4125 	 short, it's a mess.  So lets just do whatever is fastest.  */
4126       tree_code code = op == GT_EXPR ? MAX_EXPR : MIN_EXPR;
4127       calc = fold_build2_loc (input_location, code, argtype,
4128 			      convert (argtype, val), mvar);
4129       tmp = build2_v (MODIFY_EXPR, mvar, calc);
4130 
4131       if (cond != NULL_TREE)
4132 	tmp = build3_v (COND_EXPR, cond, tmp,
4133 			build_empty_stmt (input_location));
4134       gfc_add_expr_to_block (&se->pre, tmp);
4135     }
4136   se->expr = convert (type, mvar);
4137 }
4138 
4139 
4140 /* Generate library calls for MIN and MAX intrinsics for character
4141    variables.  */
4142 static void
gfc_conv_intrinsic_minmax_char(gfc_se * se,gfc_expr * expr,int op)4143 gfc_conv_intrinsic_minmax_char (gfc_se * se, gfc_expr * expr, int op)
4144 {
4145   tree *args;
4146   tree var, len, fndecl, tmp, cond, function;
4147   unsigned int nargs;
4148 
4149   nargs = gfc_intrinsic_argument_list_length (expr);
4150   args = XALLOCAVEC (tree, nargs + 4);
4151   gfc_conv_intrinsic_function_args (se, expr, &args[4], nargs);
4152 
4153   /* Create the result variables.  */
4154   len = gfc_create_var (gfc_charlen_type_node, "len");
4155   args[0] = gfc_build_addr_expr (NULL_TREE, len);
4156   var = gfc_create_var (gfc_get_pchar_type (expr->ts.kind), "pstr");
4157   args[1] = gfc_build_addr_expr (ppvoid_type_node, var);
4158   args[2] = build_int_cst (integer_type_node, op);
4159   args[3] = build_int_cst (integer_type_node, nargs / 2);
4160 
4161   if (expr->ts.kind == 1)
4162     function = gfor_fndecl_string_minmax;
4163   else if (expr->ts.kind == 4)
4164     function = gfor_fndecl_string_minmax_char4;
4165   else
4166     gcc_unreachable ();
4167 
4168   /* Make the function call.  */
4169   fndecl = build_addr (function);
4170   tmp = build_call_array_loc (input_location,
4171 			  TREE_TYPE (TREE_TYPE (function)), fndecl,
4172 			  nargs + 4, args);
4173   gfc_add_expr_to_block (&se->pre, tmp);
4174 
4175   /* Free the temporary afterwards, if necessary.  */
4176   cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
4177 			  len, build_int_cst (TREE_TYPE (len), 0));
4178   tmp = gfc_call_free (var);
4179   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
4180   gfc_add_expr_to_block (&se->post, tmp);
4181 
4182   se->expr = var;
4183   se->string_length = len;
4184 }
4185 
4186 
4187 /* Create a symbol node for this intrinsic.  The symbol from the frontend
4188    has the generic name.  */
4189 
4190 static gfc_symbol *
gfc_get_symbol_for_expr(gfc_expr * expr,bool ignore_optional)4191 gfc_get_symbol_for_expr (gfc_expr * expr, bool ignore_optional)
4192 {
4193   gfc_symbol *sym;
4194 
4195   /* TODO: Add symbols for intrinsic function to the global namespace.  */
4196   gcc_assert (strlen (expr->value.function.name) <= GFC_MAX_SYMBOL_LEN - 5);
4197   sym = gfc_new_symbol (expr->value.function.name, NULL);
4198 
4199   sym->ts = expr->ts;
4200   sym->attr.external = 1;
4201   sym->attr.function = 1;
4202   sym->attr.always_explicit = 1;
4203   sym->attr.proc = PROC_INTRINSIC;
4204   sym->attr.flavor = FL_PROCEDURE;
4205   sym->result = sym;
4206   if (expr->rank > 0)
4207     {
4208       sym->attr.dimension = 1;
4209       sym->as = gfc_get_array_spec ();
4210       sym->as->type = AS_ASSUMED_SHAPE;
4211       sym->as->rank = expr->rank;
4212     }
4213 
4214   gfc_copy_formal_args_intr (sym, expr->value.function.isym,
4215 			     ignore_optional ? expr->value.function.actual
4216 					     : NULL);
4217 
4218   return sym;
4219 }
4220 
4221 /* Remove empty actual arguments.  */
4222 
4223 static void
remove_empty_actual_arguments(gfc_actual_arglist ** ap)4224 remove_empty_actual_arguments (gfc_actual_arglist **ap)
4225 {
4226   while (*ap)
4227     {
4228       if ((*ap)->expr == NULL)
4229 	{
4230 	  gfc_actual_arglist *r = *ap;
4231 	  *ap = r->next;
4232 	  r->next = NULL;
4233 	  gfc_free_actual_arglist (r);
4234 	}
4235       else
4236 	ap = &((*ap)->next);
4237     }
4238 }
4239 
4240 #define MAX_SPEC_ARG 12
4241 
4242 /* Make up an fn spec that's right for intrinsic functions that we
4243    want to call.  */
4244 
4245 static char *
intrinsic_fnspec(gfc_expr * expr)4246 intrinsic_fnspec (gfc_expr *expr)
4247 {
4248   static char fnspec_buf[MAX_SPEC_ARG*2+1];
4249   char *fp;
4250   int i;
4251   int num_char_args;
4252 
4253 #define ADD_CHAR(c) do { *fp++ = c; *fp++ = ' '; } while(0)
4254 
4255   /* Set the fndecl.  */
4256   fp = fnspec_buf;
4257   /* Function return value.  FIXME: Check if the second letter could
4258      be something other than a space, for further optimization.  */
4259   ADD_CHAR ('.');
4260   if (expr->rank == 0)
4261     {
4262       if (expr->ts.type == BT_CHARACTER)
4263 	{
4264 	  ADD_CHAR ('w');  /* Address of character.  */
4265 	  ADD_CHAR ('.');  /* Length of character.  */
4266 	}
4267     }
4268   else
4269     ADD_CHAR ('w');  /* Return value is a descriptor.  */
4270 
4271   num_char_args = 0;
4272   for (gfc_actual_arglist *a = expr->value.function.actual; a; a = a->next)
4273     {
4274       if (a->expr == NULL)
4275 	continue;
4276 
4277       if (a->name && strcmp (a->name,"%VAL") == 0)
4278 	ADD_CHAR ('.');
4279       else
4280 	{
4281 	  if (a->expr->rank > 0)
4282 	    ADD_CHAR ('r');
4283 	  else
4284 	    ADD_CHAR ('R');
4285 	}
4286       num_char_args += a->expr->ts.type == BT_CHARACTER;
4287       gcc_assert (fp - fnspec_buf + num_char_args <= MAX_SPEC_ARG*2);
4288     }
4289 
4290   for (i = 0; i < num_char_args; i++)
4291     ADD_CHAR ('.');
4292 
4293   *fp = '\0';
4294   return fnspec_buf;
4295 }
4296 
4297 #undef MAX_SPEC_ARG
4298 #undef ADD_CHAR
4299 
4300 /* Generate the right symbol for the specific intrinsic function and
4301  modify the expr accordingly.  This assumes that absent optional
4302  arguments should be removed.  */
4303 
4304 gfc_symbol *
specific_intrinsic_symbol(gfc_expr * expr)4305 specific_intrinsic_symbol (gfc_expr *expr)
4306 {
4307   gfc_symbol *sym;
4308 
4309   sym = gfc_find_intrinsic_symbol (expr);
4310   if (sym == NULL)
4311     {
4312       sym = gfc_get_intrinsic_function_symbol (expr);
4313       sym->ts = expr->ts;
4314       if (sym->ts.type == BT_CHARACTER && sym->ts.u.cl)
4315 	sym->ts.u.cl = gfc_new_charlen (sym->ns, NULL);
4316 
4317       gfc_copy_formal_args_intr (sym, expr->value.function.isym,
4318 				 expr->value.function.actual, true);
4319       sym->backend_decl
4320 	= gfc_get_extern_function_decl (sym, expr->value.function.actual,
4321 					intrinsic_fnspec (expr));
4322     }
4323 
4324   remove_empty_actual_arguments (&(expr->value.function.actual));
4325 
4326   return sym;
4327 }
4328 
4329 /* Generate a call to an external intrinsic function.  FIXME: So far,
4330    this only works for functions which are called with well-defined
4331    types; CSHIFT and friends will come later.  */
4332 
4333 static void
gfc_conv_intrinsic_funcall(gfc_se * se,gfc_expr * expr)4334 gfc_conv_intrinsic_funcall (gfc_se * se, gfc_expr * expr)
4335 {
4336   gfc_symbol *sym;
4337   vec<tree, va_gc> *append_args;
4338   bool specific_symbol;
4339 
4340   gcc_assert (!se->ss || se->ss->info->expr == expr);
4341 
4342   if (se->ss)
4343     gcc_assert (expr->rank > 0);
4344   else
4345     gcc_assert (expr->rank == 0);
4346 
4347   switch (expr->value.function.isym->id)
4348     {
4349     case GFC_ISYM_ANY:
4350     case GFC_ISYM_ALL:
4351     case GFC_ISYM_FINDLOC:
4352     case GFC_ISYM_MAXLOC:
4353     case GFC_ISYM_MINLOC:
4354     case GFC_ISYM_MAXVAL:
4355     case GFC_ISYM_MINVAL:
4356     case GFC_ISYM_NORM2:
4357     case GFC_ISYM_PRODUCT:
4358     case GFC_ISYM_SUM:
4359       specific_symbol = true;
4360       break;
4361     default:
4362       specific_symbol = false;
4363     }
4364 
4365   if (specific_symbol)
4366     {
4367       /* Need to copy here because specific_intrinsic_symbol modifies
4368 	 expr to omit the absent optional arguments.  */
4369       expr = gfc_copy_expr (expr);
4370       sym = specific_intrinsic_symbol (expr);
4371     }
4372   else
4373     sym = gfc_get_symbol_for_expr (expr, se->ignore_optional);
4374 
4375   /* Calls to libgfortran_matmul need to be appended special arguments,
4376      to be able to call the BLAS ?gemm functions if required and possible.  */
4377   append_args = NULL;
4378   if (expr->value.function.isym->id == GFC_ISYM_MATMUL
4379       && !expr->external_blas
4380       && sym->ts.type != BT_LOGICAL)
4381     {
4382       tree cint = gfc_get_int_type (gfc_c_int_kind);
4383 
4384       if (flag_external_blas
4385 	  && (sym->ts.type == BT_REAL || sym->ts.type == BT_COMPLEX)
4386 	  && (sym->ts.kind == 4 || sym->ts.kind == 8))
4387 	{
4388 	  tree gemm_fndecl;
4389 
4390 	  if (sym->ts.type == BT_REAL)
4391 	    {
4392 	      if (sym->ts.kind == 4)
4393 		gemm_fndecl = gfor_fndecl_sgemm;
4394 	      else
4395 		gemm_fndecl = gfor_fndecl_dgemm;
4396 	    }
4397 	  else
4398 	    {
4399 	      if (sym->ts.kind == 4)
4400 		gemm_fndecl = gfor_fndecl_cgemm;
4401 	      else
4402 		gemm_fndecl = gfor_fndecl_zgemm;
4403 	    }
4404 
4405 	  vec_alloc (append_args, 3);
4406 	  append_args->quick_push (build_int_cst (cint, 1));
4407 	  append_args->quick_push (build_int_cst (cint,
4408 						  flag_blas_matmul_limit));
4409 	  append_args->quick_push (gfc_build_addr_expr (NULL_TREE,
4410 							gemm_fndecl));
4411 	}
4412       else
4413 	{
4414 	  vec_alloc (append_args, 3);
4415 	  append_args->quick_push (build_int_cst (cint, 0));
4416 	  append_args->quick_push (build_int_cst (cint, 0));
4417 	  append_args->quick_push (null_pointer_node);
4418 	}
4419     }
4420 
4421   gfc_conv_procedure_call (se, sym, expr->value.function.actual, expr,
4422 			  append_args);
4423 
4424   if (specific_symbol)
4425     gfc_free_expr (expr);
4426   else
4427     gfc_free_symbol (sym);
4428 }
4429 
4430 /* ANY and ALL intrinsics. ANY->op == NE_EXPR, ALL->op == EQ_EXPR.
4431    Implemented as
4432     any(a)
4433     {
4434       forall (i=...)
4435         if (a[i] != 0)
4436           return 1
4437       end forall
4438       return 0
4439     }
4440     all(a)
4441     {
4442       forall (i=...)
4443         if (a[i] == 0)
4444           return 0
4445       end forall
4446       return 1
4447     }
4448  */
4449 static void
gfc_conv_intrinsic_anyall(gfc_se * se,gfc_expr * expr,enum tree_code op)4450 gfc_conv_intrinsic_anyall (gfc_se * se, gfc_expr * expr, enum tree_code op)
4451 {
4452   tree resvar;
4453   stmtblock_t block;
4454   stmtblock_t body;
4455   tree type;
4456   tree tmp;
4457   tree found;
4458   gfc_loopinfo loop;
4459   gfc_actual_arglist *actual;
4460   gfc_ss *arrayss;
4461   gfc_se arrayse;
4462   tree exit_label;
4463 
4464   if (se->ss)
4465     {
4466       gfc_conv_intrinsic_funcall (se, expr);
4467       return;
4468     }
4469 
4470   actual = expr->value.function.actual;
4471   type = gfc_typenode_for_spec (&expr->ts);
4472   /* Initialize the result.  */
4473   resvar = gfc_create_var (type, "test");
4474   if (op == EQ_EXPR)
4475     tmp = convert (type, boolean_true_node);
4476   else
4477     tmp = convert (type, boolean_false_node);
4478   gfc_add_modify (&se->pre, resvar, tmp);
4479 
4480   /* Walk the arguments.  */
4481   arrayss = gfc_walk_expr (actual->expr);
4482   gcc_assert (arrayss != gfc_ss_terminator);
4483 
4484   /* Initialize the scalarizer.  */
4485   gfc_init_loopinfo (&loop);
4486   exit_label = gfc_build_label_decl (NULL_TREE);
4487   TREE_USED (exit_label) = 1;
4488   gfc_add_ss_to_loop (&loop, arrayss);
4489 
4490   /* Initialize the loop.  */
4491   gfc_conv_ss_startstride (&loop);
4492   gfc_conv_loop_setup (&loop, &expr->where);
4493 
4494   gfc_mark_ss_chain_used (arrayss, 1);
4495   /* Generate the loop body.  */
4496   gfc_start_scalarized_body (&loop, &body);
4497 
4498   /* If the condition matches then set the return value.  */
4499   gfc_start_block (&block);
4500   if (op == EQ_EXPR)
4501     tmp = convert (type, boolean_false_node);
4502   else
4503     tmp = convert (type, boolean_true_node);
4504   gfc_add_modify (&block, resvar, tmp);
4505 
4506   /* And break out of the loop.  */
4507   tmp = build1_v (GOTO_EXPR, exit_label);
4508   gfc_add_expr_to_block (&block, tmp);
4509 
4510   found = gfc_finish_block (&block);
4511 
4512   /* Check this element.  */
4513   gfc_init_se (&arrayse, NULL);
4514   gfc_copy_loopinfo_to_se (&arrayse, &loop);
4515   arrayse.ss = arrayss;
4516   gfc_conv_expr_val (&arrayse, actual->expr);
4517 
4518   gfc_add_block_to_block (&body, &arrayse.pre);
4519   tmp = fold_build2_loc (input_location, op, logical_type_node, arrayse.expr,
4520 			 build_int_cst (TREE_TYPE (arrayse.expr), 0));
4521   tmp = build3_v (COND_EXPR, tmp, found, build_empty_stmt (input_location));
4522   gfc_add_expr_to_block (&body, tmp);
4523   gfc_add_block_to_block (&body, &arrayse.post);
4524 
4525   gfc_trans_scalarizing_loops (&loop, &body);
4526 
4527   /* Add the exit label.  */
4528   tmp = build1_v (LABEL_EXPR, exit_label);
4529   gfc_add_expr_to_block (&loop.pre, tmp);
4530 
4531   gfc_add_block_to_block (&se->pre, &loop.pre);
4532   gfc_add_block_to_block (&se->pre, &loop.post);
4533   gfc_cleanup_loop (&loop);
4534 
4535   se->expr = resvar;
4536 }
4537 
4538 
4539 /* Generate the constant 180 / pi, which is used in the conversion
4540    of acosd(), asind(), atand(), atan2d().  */
4541 
4542 static tree
rad2deg(int kind)4543 rad2deg (int kind)
4544 {
4545   tree retval;
4546   mpfr_t pi, t0;
4547 
4548   gfc_set_model_kind (kind);
4549   mpfr_init (pi);
4550   mpfr_init (t0);
4551   mpfr_set_si (t0, 180, GFC_RND_MODE);
4552   mpfr_const_pi (pi, GFC_RND_MODE);
4553   mpfr_div (t0, t0, pi, GFC_RND_MODE);
4554   retval = gfc_conv_mpfr_to_tree (t0, kind, 0);
4555   mpfr_clear (t0);
4556   mpfr_clear (pi);
4557   return retval;
4558 }
4559 
4560 
4561 static gfc_intrinsic_map_t *
gfc_lookup_intrinsic(gfc_isym_id id)4562 gfc_lookup_intrinsic (gfc_isym_id id)
4563 {
4564   gfc_intrinsic_map_t *m = gfc_intrinsic_map;
4565   for (; m->id != GFC_ISYM_NONE || m->double_built_in != END_BUILTINS; m++)
4566     if (id == m->id)
4567       break;
4568   gcc_assert (id == m->id);
4569   return m;
4570 }
4571 
4572 
4573 /* ACOSD(x) is translated into ACOS(x) * 180 / pi.
4574    ASIND(x) is translated into ASIN(x) * 180 / pi.
4575    ATAND(x) is translated into ATAN(x) * 180 / pi.  */
4576 
4577 static void
gfc_conv_intrinsic_atrigd(gfc_se * se,gfc_expr * expr,gfc_isym_id id)4578 gfc_conv_intrinsic_atrigd (gfc_se * se, gfc_expr * expr, gfc_isym_id id)
4579 {
4580   tree arg;
4581   tree atrigd;
4582   tree type;
4583   gfc_intrinsic_map_t *m;
4584 
4585   type = gfc_typenode_for_spec (&expr->ts);
4586 
4587   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4588 
4589   switch (id)
4590     {
4591     case GFC_ISYM_ACOSD:
4592       m = gfc_lookup_intrinsic (GFC_ISYM_ACOS);
4593       break;
4594     case GFC_ISYM_ASIND:
4595       m = gfc_lookup_intrinsic (GFC_ISYM_ASIN);
4596       break;
4597     case GFC_ISYM_ATAND:
4598       m = gfc_lookup_intrinsic (GFC_ISYM_ATAN);
4599       break;
4600     default:
4601       gcc_unreachable ();
4602     }
4603   atrigd = gfc_get_intrinsic_lib_fndecl (m, expr);
4604   atrigd = build_call_expr_loc (input_location, atrigd, 1, arg);
4605 
4606   se->expr = fold_build2_loc (input_location, MULT_EXPR, type, atrigd,
4607 			      fold_convert (type, rad2deg (expr->ts.kind)));
4608 }
4609 
4610 
4611 /* COTAN(X) is translated into -TAN(X+PI/2) for REAL argument and
4612    COS(X) / SIN(X) for COMPLEX argument.  */
4613 
4614 static void
gfc_conv_intrinsic_cotan(gfc_se * se,gfc_expr * expr)4615 gfc_conv_intrinsic_cotan (gfc_se *se, gfc_expr *expr)
4616 {
4617   gfc_intrinsic_map_t *m;
4618   tree arg;
4619   tree type;
4620 
4621   type = gfc_typenode_for_spec (&expr->ts);
4622   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4623 
4624   if (expr->ts.type == BT_REAL)
4625     {
4626       tree tan;
4627       tree tmp;
4628       mpfr_t pio2;
4629 
4630       /* Create pi/2.  */
4631       gfc_set_model_kind (expr->ts.kind);
4632       mpfr_init (pio2);
4633       mpfr_const_pi (pio2, GFC_RND_MODE);
4634       mpfr_div_ui (pio2, pio2, 2, GFC_RND_MODE);
4635       tmp = gfc_conv_mpfr_to_tree (pio2, expr->ts.kind, 0);
4636       mpfr_clear (pio2);
4637 
4638       /* Find tan builtin function.  */
4639       m = gfc_lookup_intrinsic (GFC_ISYM_TAN);
4640       tan = gfc_get_intrinsic_lib_fndecl (m, expr);
4641       tmp = fold_build2_loc (input_location, PLUS_EXPR, type, arg, tmp);
4642       tan = build_call_expr_loc (input_location, tan, 1, tmp);
4643       se->expr = fold_build1_loc (input_location, NEGATE_EXPR, type, tan);
4644     }
4645   else
4646     {
4647       tree sin;
4648       tree cos;
4649 
4650       /* Find cos builtin function.  */
4651       m = gfc_lookup_intrinsic (GFC_ISYM_COS);
4652       cos = gfc_get_intrinsic_lib_fndecl (m, expr);
4653       cos = build_call_expr_loc (input_location, cos, 1, arg);
4654 
4655       /* Find sin builtin function.  */
4656       m = gfc_lookup_intrinsic (GFC_ISYM_SIN);
4657       sin = gfc_get_intrinsic_lib_fndecl (m, expr);
4658       sin = build_call_expr_loc (input_location, sin, 1, arg);
4659 
4660       /* Divide cos by sin. */
4661       se->expr = fold_build2_loc (input_location, RDIV_EXPR, type, cos, sin);
4662    }
4663 }
4664 
4665 
4666 /* COTAND(X) is translated into -TAND(X+90) for REAL argument.  */
4667 
4668 static void
gfc_conv_intrinsic_cotand(gfc_se * se,gfc_expr * expr)4669 gfc_conv_intrinsic_cotand (gfc_se *se, gfc_expr *expr)
4670 {
4671   tree arg;
4672   tree type;
4673   tree ninety_tree;
4674   mpfr_t ninety;
4675 
4676   type = gfc_typenode_for_spec (&expr->ts);
4677   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4678 
4679   gfc_set_model_kind (expr->ts.kind);
4680 
4681   /* Build the tree for x + 90.  */
4682   mpfr_init_set_ui (ninety, 90, GFC_RND_MODE);
4683   ninety_tree = gfc_conv_mpfr_to_tree (ninety, expr->ts.kind, 0);
4684   arg = fold_build2_loc (input_location, PLUS_EXPR, type, arg, ninety_tree);
4685   mpfr_clear (ninety);
4686 
4687   /* Find tand.  */
4688   gfc_intrinsic_map_t *m = gfc_lookup_intrinsic (GFC_ISYM_TAND);
4689   tree tand = gfc_get_intrinsic_lib_fndecl (m, expr);
4690   tand = build_call_expr_loc (input_location, tand, 1, arg);
4691 
4692   se->expr = fold_build1_loc (input_location, NEGATE_EXPR, type, tand);
4693 }
4694 
4695 
4696 /* ATAN2D(Y,X) is translated into ATAN2(Y,X) * 180 / PI. */
4697 
4698 static void
gfc_conv_intrinsic_atan2d(gfc_se * se,gfc_expr * expr)4699 gfc_conv_intrinsic_atan2d (gfc_se *se, gfc_expr *expr)
4700 {
4701   tree args[2];
4702   tree atan2d;
4703   tree type;
4704 
4705   gfc_conv_intrinsic_function_args (se, expr, args, 2);
4706   type = TREE_TYPE (args[0]);
4707 
4708   gfc_intrinsic_map_t *m = gfc_lookup_intrinsic (GFC_ISYM_ATAN2);
4709   atan2d = gfc_get_intrinsic_lib_fndecl (m, expr);
4710   atan2d = build_call_expr_loc (input_location, atan2d, 2, args[0], args[1]);
4711 
4712   se->expr = fold_build2_loc (input_location, MULT_EXPR, type, atan2d,
4713 			      rad2deg (expr->ts.kind));
4714 }
4715 
4716 
4717 /* COUNT(A) = Number of true elements in A.  */
4718 static void
gfc_conv_intrinsic_count(gfc_se * se,gfc_expr * expr)4719 gfc_conv_intrinsic_count (gfc_se * se, gfc_expr * expr)
4720 {
4721   tree resvar;
4722   tree type;
4723   stmtblock_t body;
4724   tree tmp;
4725   gfc_loopinfo loop;
4726   gfc_actual_arglist *actual;
4727   gfc_ss *arrayss;
4728   gfc_se arrayse;
4729 
4730   if (se->ss)
4731     {
4732       gfc_conv_intrinsic_funcall (se, expr);
4733       return;
4734     }
4735 
4736   actual = expr->value.function.actual;
4737 
4738   type = gfc_typenode_for_spec (&expr->ts);
4739   /* Initialize the result.  */
4740   resvar = gfc_create_var (type, "count");
4741   gfc_add_modify (&se->pre, resvar, build_int_cst (type, 0));
4742 
4743   /* Walk the arguments.  */
4744   arrayss = gfc_walk_expr (actual->expr);
4745   gcc_assert (arrayss != gfc_ss_terminator);
4746 
4747   /* Initialize the scalarizer.  */
4748   gfc_init_loopinfo (&loop);
4749   gfc_add_ss_to_loop (&loop, arrayss);
4750 
4751   /* Initialize the loop.  */
4752   gfc_conv_ss_startstride (&loop);
4753   gfc_conv_loop_setup (&loop, &expr->where);
4754 
4755   gfc_mark_ss_chain_used (arrayss, 1);
4756   /* Generate the loop body.  */
4757   gfc_start_scalarized_body (&loop, &body);
4758 
4759   tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (resvar),
4760 			 resvar, build_int_cst (TREE_TYPE (resvar), 1));
4761   tmp = build2_v (MODIFY_EXPR, resvar, tmp);
4762 
4763   gfc_init_se (&arrayse, NULL);
4764   gfc_copy_loopinfo_to_se (&arrayse, &loop);
4765   arrayse.ss = arrayss;
4766   gfc_conv_expr_val (&arrayse, actual->expr);
4767   tmp = build3_v (COND_EXPR, arrayse.expr, tmp,
4768 		  build_empty_stmt (input_location));
4769 
4770   gfc_add_block_to_block (&body, &arrayse.pre);
4771   gfc_add_expr_to_block (&body, tmp);
4772   gfc_add_block_to_block (&body, &arrayse.post);
4773 
4774   gfc_trans_scalarizing_loops (&loop, &body);
4775 
4776   gfc_add_block_to_block (&se->pre, &loop.pre);
4777   gfc_add_block_to_block (&se->pre, &loop.post);
4778   gfc_cleanup_loop (&loop);
4779 
4780   se->expr = resvar;
4781 }
4782 
4783 
4784 /* Update given gfc_se to have ss component pointing to the nested gfc_ss
4785    struct and return the corresponding loopinfo.  */
4786 
4787 static gfc_loopinfo *
enter_nested_loop(gfc_se * se)4788 enter_nested_loop (gfc_se *se)
4789 {
4790   se->ss = se->ss->nested_ss;
4791   gcc_assert (se->ss == se->ss->loop->ss);
4792 
4793   return se->ss->loop;
4794 }
4795 
4796 /* Build the condition for a mask, which may be optional.  */
4797 
4798 static tree
conv_mask_condition(gfc_se * maskse,gfc_expr * maskexpr,bool optional_mask)4799 conv_mask_condition (gfc_se *maskse, gfc_expr *maskexpr,
4800 			 bool optional_mask)
4801 {
4802   tree present;
4803   tree type;
4804 
4805   if (optional_mask)
4806     {
4807       type = TREE_TYPE (maskse->expr);
4808       present = gfc_conv_expr_present (maskexpr->symtree->n.sym);
4809       present = convert (type, present);
4810       present = fold_build1_loc (input_location, TRUTH_NOT_EXPR, type,
4811 				 present);
4812       return fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
4813 			      type, present, maskse->expr);
4814     }
4815   else
4816     return maskse->expr;
4817 }
4818 
4819 /* Inline implementation of the sum and product intrinsics.  */
4820 static void
gfc_conv_intrinsic_arith(gfc_se * se,gfc_expr * expr,enum tree_code op,bool norm2)4821 gfc_conv_intrinsic_arith (gfc_se * se, gfc_expr * expr, enum tree_code op,
4822 			  bool norm2)
4823 {
4824   tree resvar;
4825   tree scale = NULL_TREE;
4826   tree type;
4827   stmtblock_t body;
4828   stmtblock_t block;
4829   tree tmp;
4830   gfc_loopinfo loop, *ploop;
4831   gfc_actual_arglist *arg_array, *arg_mask;
4832   gfc_ss *arrayss = NULL;
4833   gfc_ss *maskss = NULL;
4834   gfc_se arrayse;
4835   gfc_se maskse;
4836   gfc_se *parent_se;
4837   gfc_expr *arrayexpr;
4838   gfc_expr *maskexpr;
4839   bool optional_mask;
4840 
4841   if (expr->rank > 0)
4842     {
4843       gcc_assert (gfc_inline_intrinsic_function_p (expr));
4844       parent_se = se;
4845     }
4846   else
4847     parent_se = NULL;
4848 
4849   type = gfc_typenode_for_spec (&expr->ts);
4850   /* Initialize the result.  */
4851   resvar = gfc_create_var (type, "val");
4852   if (norm2)
4853     {
4854       /* result = 0.0;
4855 	 scale = 1.0.  */
4856       scale = gfc_create_var (type, "scale");
4857       gfc_add_modify (&se->pre, scale,
4858 		      gfc_build_const (type, integer_one_node));
4859       tmp = gfc_build_const (type, integer_zero_node);
4860     }
4861   else if (op == PLUS_EXPR || op == BIT_IOR_EXPR || op == BIT_XOR_EXPR)
4862     tmp = gfc_build_const (type, integer_zero_node);
4863   else if (op == NE_EXPR)
4864     /* PARITY.  */
4865     tmp = convert (type, boolean_false_node);
4866   else if (op == BIT_AND_EXPR)
4867     tmp = gfc_build_const (type, fold_build1_loc (input_location, NEGATE_EXPR,
4868 						  type, integer_one_node));
4869   else
4870     tmp = gfc_build_const (type, integer_one_node);
4871 
4872   gfc_add_modify (&se->pre, resvar, tmp);
4873 
4874   arg_array = expr->value.function.actual;
4875 
4876   arrayexpr = arg_array->expr;
4877 
4878   if (op == NE_EXPR || norm2)
4879     {
4880       /* PARITY and NORM2.  */
4881       maskexpr = NULL;
4882       optional_mask = false;
4883     }
4884   else
4885     {
4886       arg_mask  = arg_array->next->next;
4887       gcc_assert (arg_mask != NULL);
4888       maskexpr = arg_mask->expr;
4889       optional_mask = maskexpr && maskexpr->expr_type == EXPR_VARIABLE
4890 	&& maskexpr->symtree->n.sym->attr.dummy
4891 	&& maskexpr->symtree->n.sym->attr.optional;
4892     }
4893 
4894   if (expr->rank == 0)
4895     {
4896       /* Walk the arguments.  */
4897       arrayss = gfc_walk_expr (arrayexpr);
4898       gcc_assert (arrayss != gfc_ss_terminator);
4899 
4900       if (maskexpr && maskexpr->rank > 0)
4901 	{
4902 	  maskss = gfc_walk_expr (maskexpr);
4903 	  gcc_assert (maskss != gfc_ss_terminator);
4904 	}
4905       else
4906 	maskss = NULL;
4907 
4908       /* Initialize the scalarizer.  */
4909       gfc_init_loopinfo (&loop);
4910 
4911       /* We add the mask first because the number of iterations is
4912 	 taken from the last ss, and this breaks if an absent
4913 	 optional argument is used for mask.  */
4914 
4915       if (maskexpr && maskexpr->rank > 0)
4916 	gfc_add_ss_to_loop (&loop, maskss);
4917       gfc_add_ss_to_loop (&loop, arrayss);
4918 
4919       /* Initialize the loop.  */
4920       gfc_conv_ss_startstride (&loop);
4921       gfc_conv_loop_setup (&loop, &expr->where);
4922 
4923       if (maskexpr && maskexpr->rank > 0)
4924 	gfc_mark_ss_chain_used (maskss, 1);
4925       gfc_mark_ss_chain_used (arrayss, 1);
4926 
4927       ploop = &loop;
4928     }
4929   else
4930     /* All the work has been done in the parent loops.  */
4931     ploop = enter_nested_loop (se);
4932 
4933   gcc_assert (ploop);
4934 
4935   /* Generate the loop body.  */
4936   gfc_start_scalarized_body (ploop, &body);
4937 
4938   /* If we have a mask, only add this element if the mask is set.  */
4939   if (maskexpr && maskexpr->rank > 0)
4940     {
4941       gfc_init_se (&maskse, parent_se);
4942       gfc_copy_loopinfo_to_se (&maskse, ploop);
4943       if (expr->rank == 0)
4944 	maskse.ss = maskss;
4945       gfc_conv_expr_val (&maskse, maskexpr);
4946       gfc_add_block_to_block (&body, &maskse.pre);
4947 
4948       gfc_start_block (&block);
4949     }
4950   else
4951     gfc_init_block (&block);
4952 
4953   /* Do the actual summation/product.  */
4954   gfc_init_se (&arrayse, parent_se);
4955   gfc_copy_loopinfo_to_se (&arrayse, ploop);
4956   if (expr->rank == 0)
4957     arrayse.ss = arrayss;
4958   gfc_conv_expr_val (&arrayse, arrayexpr);
4959   gfc_add_block_to_block (&block, &arrayse.pre);
4960 
4961   if (norm2)
4962     {
4963       /* if (x (i) != 0.0)
4964 	   {
4965 	     absX = abs(x(i))
4966 	     if (absX > scale)
4967 	       {
4968                  val = scale/absX;
4969 		 result = 1.0 + result * val * val;
4970 		 scale = absX;
4971 	       }
4972 	     else
4973 	       {
4974                  val = absX/scale;
4975 	         result += val * val;
4976 	       }
4977 	   }  */
4978       tree res1, res2, cond, absX, val;
4979       stmtblock_t ifblock1, ifblock2, ifblock3;
4980 
4981       gfc_init_block (&ifblock1);
4982 
4983       absX = gfc_create_var (type, "absX");
4984       gfc_add_modify (&ifblock1, absX,
4985 		      fold_build1_loc (input_location, ABS_EXPR, type,
4986 				       arrayse.expr));
4987       val = gfc_create_var (type, "val");
4988       gfc_add_expr_to_block (&ifblock1, val);
4989 
4990       gfc_init_block (&ifblock2);
4991       gfc_add_modify (&ifblock2, val,
4992 		      fold_build2_loc (input_location, RDIV_EXPR, type, scale,
4993 				       absX));
4994       res1 = fold_build2_loc (input_location, MULT_EXPR, type, val, val);
4995       res1 = fold_build2_loc (input_location, MULT_EXPR, type, resvar, res1);
4996       res1 = fold_build2_loc (input_location, PLUS_EXPR, type, res1,
4997 			      gfc_build_const (type, integer_one_node));
4998       gfc_add_modify (&ifblock2, resvar, res1);
4999       gfc_add_modify (&ifblock2, scale, absX);
5000       res1 = gfc_finish_block (&ifblock2);
5001 
5002       gfc_init_block (&ifblock3);
5003       gfc_add_modify (&ifblock3, val,
5004 		      fold_build2_loc (input_location, RDIV_EXPR, type, absX,
5005 				       scale));
5006       res2 = fold_build2_loc (input_location, MULT_EXPR, type, val, val);
5007       res2 = fold_build2_loc (input_location, PLUS_EXPR, type, resvar, res2);
5008       gfc_add_modify (&ifblock3, resvar, res2);
5009       res2 = gfc_finish_block (&ifblock3);
5010 
5011       cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
5012 			      absX, scale);
5013       tmp = build3_v (COND_EXPR, cond, res1, res2);
5014       gfc_add_expr_to_block (&ifblock1, tmp);
5015       tmp = gfc_finish_block (&ifblock1);
5016 
5017       cond = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
5018 			      arrayse.expr,
5019 			      gfc_build_const (type, integer_zero_node));
5020 
5021       tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
5022       gfc_add_expr_to_block (&block, tmp);
5023     }
5024   else
5025     {
5026       tmp = fold_build2_loc (input_location, op, type, resvar, arrayse.expr);
5027       gfc_add_modify (&block, resvar, tmp);
5028     }
5029 
5030   gfc_add_block_to_block (&block, &arrayse.post);
5031 
5032   if (maskexpr && maskexpr->rank > 0)
5033     {
5034       /* We enclose the above in if (mask) {...} .  If the mask is an
5035 	 optional argument, generate
5036 	 IF (.NOT. PRESENT(MASK) .OR. MASK(I)).  */
5037       tree ifmask;
5038       tmp = gfc_finish_block (&block);
5039       ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
5040       tmp = build3_v (COND_EXPR, ifmask, tmp,
5041 		      build_empty_stmt (input_location));
5042     }
5043   else
5044     tmp = gfc_finish_block (&block);
5045   gfc_add_expr_to_block (&body, tmp);
5046 
5047   gfc_trans_scalarizing_loops (ploop, &body);
5048 
5049   /* For a scalar mask, enclose the loop in an if statement.  */
5050   if (maskexpr && maskexpr->rank == 0)
5051     {
5052       gfc_init_block (&block);
5053       gfc_add_block_to_block (&block, &ploop->pre);
5054       gfc_add_block_to_block (&block, &ploop->post);
5055       tmp = gfc_finish_block (&block);
5056 
5057       if (expr->rank > 0)
5058 	{
5059 	  tmp = build3_v (COND_EXPR, se->ss->info->data.scalar.value, tmp,
5060 			  build_empty_stmt (input_location));
5061 	  gfc_advance_se_ss_chain (se);
5062 	}
5063       else
5064 	{
5065 	  tree ifmask;
5066 
5067 	  gcc_assert (expr->rank == 0);
5068 	  gfc_init_se (&maskse, NULL);
5069 	  gfc_conv_expr_val (&maskse, maskexpr);
5070 	  ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
5071 	  tmp = build3_v (COND_EXPR, ifmask, tmp,
5072 			  build_empty_stmt (input_location));
5073 	}
5074 
5075       gfc_add_expr_to_block (&block, tmp);
5076       gfc_add_block_to_block (&se->pre, &block);
5077       gcc_assert (se->post.head == NULL);
5078     }
5079   else
5080     {
5081       gfc_add_block_to_block (&se->pre, &ploop->pre);
5082       gfc_add_block_to_block (&se->pre, &ploop->post);
5083     }
5084 
5085   if (expr->rank == 0)
5086     gfc_cleanup_loop (ploop);
5087 
5088   if (norm2)
5089     {
5090       /* result = scale * sqrt(result).  */
5091       tree sqrt;
5092       sqrt = gfc_builtin_decl_for_float_kind (BUILT_IN_SQRT, expr->ts.kind);
5093       resvar = build_call_expr_loc (input_location,
5094 				    sqrt, 1, resvar);
5095       resvar = fold_build2_loc (input_location, MULT_EXPR, type, scale, resvar);
5096     }
5097 
5098   se->expr = resvar;
5099 }
5100 
5101 
5102 /* Inline implementation of the dot_product intrinsic. This function
5103    is based on gfc_conv_intrinsic_arith (the previous function).  */
5104 static void
gfc_conv_intrinsic_dot_product(gfc_se * se,gfc_expr * expr)5105 gfc_conv_intrinsic_dot_product (gfc_se * se, gfc_expr * expr)
5106 {
5107   tree resvar;
5108   tree type;
5109   stmtblock_t body;
5110   stmtblock_t block;
5111   tree tmp;
5112   gfc_loopinfo loop;
5113   gfc_actual_arglist *actual;
5114   gfc_ss *arrayss1, *arrayss2;
5115   gfc_se arrayse1, arrayse2;
5116   gfc_expr *arrayexpr1, *arrayexpr2;
5117 
5118   type = gfc_typenode_for_spec (&expr->ts);
5119 
5120   /* Initialize the result.  */
5121   resvar = gfc_create_var (type, "val");
5122   if (expr->ts.type == BT_LOGICAL)
5123     tmp = build_int_cst (type, 0);
5124   else
5125     tmp = gfc_build_const (type, integer_zero_node);
5126 
5127   gfc_add_modify (&se->pre, resvar, tmp);
5128 
5129   /* Walk argument #1.  */
5130   actual = expr->value.function.actual;
5131   arrayexpr1 = actual->expr;
5132   arrayss1 = gfc_walk_expr (arrayexpr1);
5133   gcc_assert (arrayss1 != gfc_ss_terminator);
5134 
5135   /* Walk argument #2.  */
5136   actual = actual->next;
5137   arrayexpr2 = actual->expr;
5138   arrayss2 = gfc_walk_expr (arrayexpr2);
5139   gcc_assert (arrayss2 != gfc_ss_terminator);
5140 
5141   /* Initialize the scalarizer.  */
5142   gfc_init_loopinfo (&loop);
5143   gfc_add_ss_to_loop (&loop, arrayss1);
5144   gfc_add_ss_to_loop (&loop, arrayss2);
5145 
5146   /* Initialize the loop.  */
5147   gfc_conv_ss_startstride (&loop);
5148   gfc_conv_loop_setup (&loop, &expr->where);
5149 
5150   gfc_mark_ss_chain_used (arrayss1, 1);
5151   gfc_mark_ss_chain_used (arrayss2, 1);
5152 
5153   /* Generate the loop body.  */
5154   gfc_start_scalarized_body (&loop, &body);
5155   gfc_init_block (&block);
5156 
5157   /* Make the tree expression for [conjg(]array1[)].  */
5158   gfc_init_se (&arrayse1, NULL);
5159   gfc_copy_loopinfo_to_se (&arrayse1, &loop);
5160   arrayse1.ss = arrayss1;
5161   gfc_conv_expr_val (&arrayse1, arrayexpr1);
5162   if (expr->ts.type == BT_COMPLEX)
5163     arrayse1.expr = fold_build1_loc (input_location, CONJ_EXPR, type,
5164 				     arrayse1.expr);
5165   gfc_add_block_to_block (&block, &arrayse1.pre);
5166 
5167   /* Make the tree expression for array2.  */
5168   gfc_init_se (&arrayse2, NULL);
5169   gfc_copy_loopinfo_to_se (&arrayse2, &loop);
5170   arrayse2.ss = arrayss2;
5171   gfc_conv_expr_val (&arrayse2, arrayexpr2);
5172   gfc_add_block_to_block (&block, &arrayse2.pre);
5173 
5174   /* Do the actual product and sum.  */
5175   if (expr->ts.type == BT_LOGICAL)
5176     {
5177       tmp = fold_build2_loc (input_location, TRUTH_AND_EXPR, type,
5178 			     arrayse1.expr, arrayse2.expr);
5179       tmp = fold_build2_loc (input_location, TRUTH_OR_EXPR, type, resvar, tmp);
5180     }
5181   else
5182     {
5183       tmp = fold_build2_loc (input_location, MULT_EXPR, type, arrayse1.expr,
5184 			     arrayse2.expr);
5185       tmp = fold_build2_loc (input_location, PLUS_EXPR, type, resvar, tmp);
5186     }
5187   gfc_add_modify (&block, resvar, tmp);
5188 
5189   /* Finish up the loop block and the loop.  */
5190   tmp = gfc_finish_block (&block);
5191   gfc_add_expr_to_block (&body, tmp);
5192 
5193   gfc_trans_scalarizing_loops (&loop, &body);
5194   gfc_add_block_to_block (&se->pre, &loop.pre);
5195   gfc_add_block_to_block (&se->pre, &loop.post);
5196   gfc_cleanup_loop (&loop);
5197 
5198   se->expr = resvar;
5199 }
5200 
5201 
5202 /* Remove unneeded kind= argument from actual argument list when the
5203    result conversion is dealt with in a different place.  */
5204 
5205 static void
strip_kind_from_actual(gfc_actual_arglist * actual)5206 strip_kind_from_actual (gfc_actual_arglist * actual)
5207 {
5208   for (gfc_actual_arglist *a = actual; a; a = a->next)
5209     {
5210       if (a && a->name && strcmp (a->name, "kind") == 0)
5211 	{
5212 	  gfc_free_expr (a->expr);
5213 	  a->expr = NULL;
5214 	}
5215     }
5216 }
5217 
5218 /* Emit code for minloc or maxloc intrinsic.  There are many different cases
5219    we need to handle.  For performance reasons we sometimes create two
5220    loops instead of one, where the second one is much simpler.
5221    Examples for minloc intrinsic:
5222    1) Result is an array, a call is generated
5223    2) Array mask is used and NaNs need to be supported:
5224       limit = Infinity;
5225       pos = 0;
5226       S = from;
5227       while (S <= to) {
5228 	if (mask[S]) {
5229 	  if (pos == 0) pos = S + (1 - from);
5230 	  if (a[S] <= limit) { limit = a[S]; pos = S + (1 - from); goto lab1; }
5231 	}
5232 	S++;
5233       }
5234       goto lab2;
5235       lab1:;
5236       while (S <= to) {
5237 	if (mask[S]) if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
5238 	S++;
5239       }
5240       lab2:;
5241    3) NaNs need to be supported, but it is known at compile time or cheaply
5242       at runtime whether array is nonempty or not:
5243       limit = Infinity;
5244       pos = 0;
5245       S = from;
5246       while (S <= to) {
5247 	if (a[S] <= limit) { limit = a[S]; pos = S + (1 - from); goto lab1; }
5248 	S++;
5249       }
5250       if (from <= to) pos = 1;
5251       goto lab2;
5252       lab1:;
5253       while (S <= to) {
5254 	if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
5255 	S++;
5256       }
5257       lab2:;
5258    4) NaNs aren't supported, array mask is used:
5259       limit = infinities_supported ? Infinity : huge (limit);
5260       pos = 0;
5261       S = from;
5262       while (S <= to) {
5263 	if (mask[S]) { limit = a[S]; pos = S + (1 - from); goto lab1; }
5264 	S++;
5265       }
5266       goto lab2;
5267       lab1:;
5268       while (S <= to) {
5269 	if (mask[S]) if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
5270 	S++;
5271       }
5272       lab2:;
5273    5) Same without array mask:
5274       limit = infinities_supported ? Infinity : huge (limit);
5275       pos = (from <= to) ? 1 : 0;
5276       S = from;
5277       while (S <= to) {
5278 	if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
5279 	S++;
5280       }
5281    For 3) and 5), if mask is scalar, this all goes into a conditional,
5282    setting pos = 0; in the else branch.
5283 
5284    Since we now also support the BACK argument, instead of using
5285    if (a[S] < limit), we now use
5286 
5287    if (back)
5288      cond = a[S] <= limit;
5289    else
5290      cond = a[S] < limit;
5291    if (cond) {
5292      ....
5293 
5294      The optimizer is smart enough to move the condition out of the loop.
5295      The are now marked as unlikely to for further speedup.  */
5296 
5297 static void
gfc_conv_intrinsic_minmaxloc(gfc_se * se,gfc_expr * expr,enum tree_code op)5298 gfc_conv_intrinsic_minmaxloc (gfc_se * se, gfc_expr * expr, enum tree_code op)
5299 {
5300   stmtblock_t body;
5301   stmtblock_t block;
5302   stmtblock_t ifblock;
5303   stmtblock_t elseblock;
5304   tree limit;
5305   tree type;
5306   tree tmp;
5307   tree cond;
5308   tree elsetmp;
5309   tree ifbody;
5310   tree offset;
5311   tree nonempty;
5312   tree lab1, lab2;
5313   tree b_if, b_else;
5314   gfc_loopinfo loop;
5315   gfc_actual_arglist *actual;
5316   gfc_ss *arrayss;
5317   gfc_ss *maskss;
5318   gfc_se arrayse;
5319   gfc_se maskse;
5320   gfc_expr *arrayexpr;
5321   gfc_expr *maskexpr;
5322   gfc_expr *backexpr;
5323   gfc_se backse;
5324   tree pos;
5325   int n;
5326   bool optional_mask;
5327 
5328   actual = expr->value.function.actual;
5329 
5330   /* The last argument, BACK, is passed by value. Ensure that
5331      by setting its name to %VAL. */
5332   for (gfc_actual_arglist *a = actual; a; a = a->next)
5333     {
5334       if (a->next == NULL)
5335 	a->name = "%VAL";
5336     }
5337 
5338   if (se->ss)
5339     {
5340       gfc_conv_intrinsic_funcall (se, expr);
5341       return;
5342     }
5343 
5344   arrayexpr = actual->expr;
5345 
5346   /* Special case for character maxloc.  Remove unneeded actual
5347      arguments, then call a library function.  */
5348 
5349   if (arrayexpr->ts.type == BT_CHARACTER)
5350     {
5351       gfc_actual_arglist *a;
5352       a = actual;
5353       strip_kind_from_actual (a);
5354       while (a)
5355 	{
5356 	  if (a->name && strcmp (a->name, "dim") == 0)
5357 	    {
5358 	      gfc_free_expr (a->expr);
5359 	      a->expr = NULL;
5360 	    }
5361 	  a = a->next;
5362 	}
5363       gfc_conv_intrinsic_funcall (se, expr);
5364       return;
5365     }
5366 
5367   /* Initialize the result.  */
5368   pos = gfc_create_var (gfc_array_index_type, "pos");
5369   offset = gfc_create_var (gfc_array_index_type, "offset");
5370   type = gfc_typenode_for_spec (&expr->ts);
5371 
5372   /* Walk the arguments.  */
5373   arrayss = gfc_walk_expr (arrayexpr);
5374   gcc_assert (arrayss != gfc_ss_terminator);
5375 
5376   actual = actual->next->next;
5377   gcc_assert (actual);
5378   maskexpr = actual->expr;
5379   optional_mask = maskexpr && maskexpr->expr_type == EXPR_VARIABLE
5380     && maskexpr->symtree->n.sym->attr.dummy
5381     && maskexpr->symtree->n.sym->attr.optional;
5382   backexpr = actual->next->next->expr;
5383   nonempty = NULL;
5384   if (maskexpr && maskexpr->rank != 0)
5385     {
5386       maskss = gfc_walk_expr (maskexpr);
5387       gcc_assert (maskss != gfc_ss_terminator);
5388     }
5389   else
5390     {
5391       mpz_t asize;
5392       if (gfc_array_size (arrayexpr, &asize))
5393 	{
5394 	  nonempty = gfc_conv_mpz_to_tree (asize, gfc_index_integer_kind);
5395 	  mpz_clear (asize);
5396 	  nonempty = fold_build2_loc (input_location, GT_EXPR,
5397 				      logical_type_node, nonempty,
5398 				      gfc_index_zero_node);
5399 	}
5400       maskss = NULL;
5401     }
5402 
5403   limit = gfc_create_var (gfc_typenode_for_spec (&arrayexpr->ts), "limit");
5404   switch (arrayexpr->ts.type)
5405     {
5406     case BT_REAL:
5407       tmp = gfc_build_inf_or_huge (TREE_TYPE (limit), arrayexpr->ts.kind);
5408       break;
5409 
5410     case BT_INTEGER:
5411       n = gfc_validate_kind (arrayexpr->ts.type, arrayexpr->ts.kind, false);
5412       tmp = gfc_conv_mpz_to_tree (gfc_integer_kinds[n].huge,
5413 				  arrayexpr->ts.kind);
5414       break;
5415 
5416     default:
5417       gcc_unreachable ();
5418     }
5419 
5420   /* We start with the most negative possible value for MAXLOC, and the most
5421      positive possible value for MINLOC. The most negative possible value is
5422      -HUGE for BT_REAL and (-HUGE - 1) for BT_INTEGER; the most positive
5423      possible value is HUGE in both cases.  */
5424   if (op == GT_EXPR)
5425     tmp = fold_build1_loc (input_location, NEGATE_EXPR, TREE_TYPE (tmp), tmp);
5426   if (op == GT_EXPR && arrayexpr->ts.type == BT_INTEGER)
5427     tmp = fold_build2_loc (input_location, MINUS_EXPR, TREE_TYPE (tmp), tmp,
5428 			   build_int_cst (TREE_TYPE (tmp), 1));
5429 
5430   gfc_add_modify (&se->pre, limit, tmp);
5431 
5432   /* Initialize the scalarizer.  */
5433   gfc_init_loopinfo (&loop);
5434 
5435   /* We add the mask first because the number of iterations is taken
5436      from the last ss, and this breaks if an absent optional argument
5437      is used for mask.  */
5438 
5439   if (maskss)
5440     gfc_add_ss_to_loop (&loop, maskss);
5441 
5442   gfc_add_ss_to_loop (&loop, arrayss);
5443 
5444   /* Initialize the loop.  */
5445   gfc_conv_ss_startstride (&loop);
5446 
5447   /* The code generated can have more than one loop in sequence (see the
5448      comment at the function header).  This doesn't work well with the
5449      scalarizer, which changes arrays' offset when the scalarization loops
5450      are generated (see gfc_trans_preloop_setup).  Fortunately, {min,max}loc
5451      are  currently inlined in the scalar case only (for which loop is of rank
5452      one).  As there is no dependency to care about in that case, there is no
5453      temporary, so that we can use the scalarizer temporary code to handle
5454      multiple loops.  Thus, we set temp_dim here, we call gfc_mark_ss_chain_used
5455      with flag=3 later, and we use gfc_trans_scalarized_loop_boundary even later
5456      to restore offset.
5457      TODO: this prevents inlining of rank > 0 minmaxloc calls, so this
5458      should eventually go away.  We could either create two loops properly,
5459      or find another way to save/restore the array offsets between the two
5460      loops (without conflicting with temporary management), or use a single
5461      loop minmaxloc implementation.  See PR 31067.  */
5462   loop.temp_dim = loop.dimen;
5463   gfc_conv_loop_setup (&loop, &expr->where);
5464 
5465   gcc_assert (loop.dimen == 1);
5466   if (nonempty == NULL && maskss == NULL && loop.from[0] && loop.to[0])
5467     nonempty = fold_build2_loc (input_location, LE_EXPR, logical_type_node,
5468 				loop.from[0], loop.to[0]);
5469 
5470   lab1 = NULL;
5471   lab2 = NULL;
5472   /* Initialize the position to zero, following Fortran 2003.  We are free
5473      to do this because Fortran 95 allows the result of an entirely false
5474      mask to be processor dependent.  If we know at compile time the array
5475      is non-empty and no MASK is used, we can initialize to 1 to simplify
5476      the inner loop.  */
5477   if (nonempty != NULL && !HONOR_NANS (DECL_MODE (limit)))
5478     gfc_add_modify (&loop.pre, pos,
5479 		    fold_build3_loc (input_location, COND_EXPR,
5480 				     gfc_array_index_type,
5481 				     nonempty, gfc_index_one_node,
5482 				     gfc_index_zero_node));
5483   else
5484     {
5485       gfc_add_modify (&loop.pre, pos, gfc_index_zero_node);
5486       lab1 = gfc_build_label_decl (NULL_TREE);
5487       TREE_USED (lab1) = 1;
5488       lab2 = gfc_build_label_decl (NULL_TREE);
5489       TREE_USED (lab2) = 1;
5490     }
5491 
5492   /* An offset must be added to the loop
5493      counter to obtain the required position.  */
5494   gcc_assert (loop.from[0]);
5495 
5496   tmp = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
5497 			 gfc_index_one_node, loop.from[0]);
5498   gfc_add_modify (&loop.pre, offset, tmp);
5499 
5500   gfc_mark_ss_chain_used (arrayss, lab1 ? 3 : 1);
5501   if (maskss)
5502     gfc_mark_ss_chain_used (maskss, lab1 ? 3 : 1);
5503   /* Generate the loop body.  */
5504   gfc_start_scalarized_body (&loop, &body);
5505 
5506   /* If we have a mask, only check this element if the mask is set.  */
5507   if (maskss)
5508     {
5509       gfc_init_se (&maskse, NULL);
5510       gfc_copy_loopinfo_to_se (&maskse, &loop);
5511       maskse.ss = maskss;
5512       gfc_conv_expr_val (&maskse, maskexpr);
5513       gfc_add_block_to_block (&body, &maskse.pre);
5514 
5515       gfc_start_block (&block);
5516     }
5517   else
5518     gfc_init_block (&block);
5519 
5520   /* Compare with the current limit.  */
5521   gfc_init_se (&arrayse, NULL);
5522   gfc_copy_loopinfo_to_se (&arrayse, &loop);
5523   arrayse.ss = arrayss;
5524   gfc_conv_expr_val (&arrayse, arrayexpr);
5525   gfc_add_block_to_block (&block, &arrayse.pre);
5526 
5527   gfc_init_se (&backse, NULL);
5528   gfc_conv_expr_val (&backse, backexpr);
5529   gfc_add_block_to_block (&block, &backse.pre);
5530 
5531   /* We do the following if this is a more extreme value.  */
5532   gfc_start_block (&ifblock);
5533 
5534   /* Assign the value to the limit...  */
5535   gfc_add_modify (&ifblock, limit, arrayse.expr);
5536 
5537   if (nonempty == NULL && HONOR_NANS (DECL_MODE (limit)))
5538     {
5539       stmtblock_t ifblock2;
5540       tree ifbody2;
5541 
5542       gfc_start_block (&ifblock2);
5543       tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (pos),
5544 			     loop.loopvar[0], offset);
5545       gfc_add_modify (&ifblock2, pos, tmp);
5546       ifbody2 = gfc_finish_block (&ifblock2);
5547       cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, pos,
5548 			      gfc_index_zero_node);
5549       tmp = build3_v (COND_EXPR, cond, ifbody2,
5550 		      build_empty_stmt (input_location));
5551       gfc_add_expr_to_block (&block, tmp);
5552     }
5553 
5554   tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (pos),
5555 			 loop.loopvar[0], offset);
5556   gfc_add_modify (&ifblock, pos, tmp);
5557 
5558   if (lab1)
5559     gfc_add_expr_to_block (&ifblock, build1_v (GOTO_EXPR, lab1));
5560 
5561   ifbody = gfc_finish_block (&ifblock);
5562 
5563   if (!lab1 || HONOR_NANS (DECL_MODE (limit)))
5564     {
5565       if (lab1)
5566 	cond = fold_build2_loc (input_location,
5567 				op == GT_EXPR ? GE_EXPR : LE_EXPR,
5568 				logical_type_node, arrayse.expr, limit);
5569       else
5570 	{
5571 	  tree ifbody2, elsebody2;
5572 
5573 	  /* We switch to > or >= depending on the value of the BACK argument. */
5574 	  cond = gfc_create_var (logical_type_node, "cond");
5575 
5576 	  gfc_start_block (&ifblock);
5577 	  b_if = fold_build2_loc (input_location, op == GT_EXPR ? GE_EXPR : LE_EXPR,
5578 				  logical_type_node, arrayse.expr, limit);
5579 
5580 	  gfc_add_modify (&ifblock, cond, b_if);
5581 	  ifbody2 = gfc_finish_block (&ifblock);
5582 
5583 	  gfc_start_block (&elseblock);
5584 	  b_else = fold_build2_loc (input_location, op, logical_type_node,
5585 				    arrayse.expr, limit);
5586 
5587 	  gfc_add_modify (&elseblock, cond, b_else);
5588 	  elsebody2 = gfc_finish_block (&elseblock);
5589 
5590 	  tmp = fold_build3_loc (input_location, COND_EXPR, logical_type_node,
5591 				 backse.expr, ifbody2, elsebody2);
5592 
5593 	  gfc_add_expr_to_block (&block, tmp);
5594 	}
5595 
5596       cond = gfc_unlikely (cond, PRED_BUILTIN_EXPECT);
5597       ifbody = build3_v (COND_EXPR, cond, ifbody,
5598 			 build_empty_stmt (input_location));
5599     }
5600   gfc_add_expr_to_block (&block, ifbody);
5601 
5602   if (maskss)
5603     {
5604       /* We enclose the above in if (mask) {...}.  If the mask is an
5605 	 optional argument, generate IF (.NOT. PRESENT(MASK)
5606 	 .OR. MASK(I)). */
5607 
5608       tree ifmask;
5609       ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
5610       tmp = gfc_finish_block (&block);
5611       tmp = build3_v (COND_EXPR, ifmask, tmp,
5612 		      build_empty_stmt (input_location));
5613     }
5614   else
5615     tmp = gfc_finish_block (&block);
5616   gfc_add_expr_to_block (&body, tmp);
5617 
5618   if (lab1)
5619     {
5620       gfc_trans_scalarized_loop_boundary (&loop, &body);
5621 
5622       if (HONOR_NANS (DECL_MODE (limit)))
5623 	{
5624 	  if (nonempty != NULL)
5625 	    {
5626 	      ifbody = build2_v (MODIFY_EXPR, pos, gfc_index_one_node);
5627 	      tmp = build3_v (COND_EXPR, nonempty, ifbody,
5628 			      build_empty_stmt (input_location));
5629 	      gfc_add_expr_to_block (&loop.code[0], tmp);
5630 	    }
5631 	}
5632 
5633       gfc_add_expr_to_block (&loop.code[0], build1_v (GOTO_EXPR, lab2));
5634       gfc_add_expr_to_block (&loop.code[0], build1_v (LABEL_EXPR, lab1));
5635 
5636       /* If we have a mask, only check this element if the mask is set.  */
5637       if (maskss)
5638 	{
5639 	  gfc_init_se (&maskse, NULL);
5640 	  gfc_copy_loopinfo_to_se (&maskse, &loop);
5641 	  maskse.ss = maskss;
5642 	  gfc_conv_expr_val (&maskse, maskexpr);
5643 	  gfc_add_block_to_block (&body, &maskse.pre);
5644 
5645 	  gfc_start_block (&block);
5646 	}
5647       else
5648 	gfc_init_block (&block);
5649 
5650       /* Compare with the current limit.  */
5651       gfc_init_se (&arrayse, NULL);
5652       gfc_copy_loopinfo_to_se (&arrayse, &loop);
5653       arrayse.ss = arrayss;
5654       gfc_conv_expr_val (&arrayse, arrayexpr);
5655       gfc_add_block_to_block (&block, &arrayse.pre);
5656 
5657       /* We do the following if this is a more extreme value.  */
5658       gfc_start_block (&ifblock);
5659 
5660       /* Assign the value to the limit...  */
5661       gfc_add_modify (&ifblock, limit, arrayse.expr);
5662 
5663       tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (pos),
5664 			     loop.loopvar[0], offset);
5665       gfc_add_modify (&ifblock, pos, tmp);
5666 
5667       ifbody = gfc_finish_block (&ifblock);
5668 
5669       /* We switch to > or >= depending on the value of the BACK argument. */
5670       {
5671 	tree ifbody2, elsebody2;
5672 
5673 	cond = gfc_create_var (logical_type_node, "cond");
5674 
5675 	gfc_start_block (&ifblock);
5676 	b_if = fold_build2_loc (input_location, op == GT_EXPR ? GE_EXPR : LE_EXPR,
5677 				logical_type_node, arrayse.expr, limit);
5678 
5679 	gfc_add_modify (&ifblock, cond, b_if);
5680 	ifbody2 = gfc_finish_block (&ifblock);
5681 
5682 	gfc_start_block (&elseblock);
5683 	b_else = fold_build2_loc (input_location, op, logical_type_node,
5684 				  arrayse.expr, limit);
5685 
5686 	gfc_add_modify (&elseblock, cond, b_else);
5687 	elsebody2 = gfc_finish_block (&elseblock);
5688 
5689 	tmp = fold_build3_loc (input_location, COND_EXPR, logical_type_node,
5690 			       backse.expr, ifbody2, elsebody2);
5691       }
5692 
5693       gfc_add_expr_to_block (&block, tmp);
5694       cond = gfc_unlikely (cond, PRED_BUILTIN_EXPECT);
5695       tmp = build3_v (COND_EXPR, cond, ifbody,
5696 		      build_empty_stmt (input_location));
5697 
5698       gfc_add_expr_to_block (&block, tmp);
5699 
5700       if (maskss)
5701 	{
5702 	  /* We enclose the above in if (mask) {...}.  If the mask is
5703 	 an optional argument, generate IF (.NOT. PRESENT(MASK)
5704 	 .OR. MASK(I)).*/
5705 
5706 	  tree ifmask;
5707 	  ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
5708 	  tmp = gfc_finish_block (&block);
5709 	  tmp = build3_v (COND_EXPR, ifmask, tmp,
5710 			  build_empty_stmt (input_location));
5711 	}
5712       else
5713 	tmp = gfc_finish_block (&block);
5714       gfc_add_expr_to_block (&body, tmp);
5715       /* Avoid initializing loopvar[0] again, it should be left where
5716 	 it finished by the first loop.  */
5717       loop.from[0] = loop.loopvar[0];
5718     }
5719 
5720   gfc_trans_scalarizing_loops (&loop, &body);
5721 
5722   if (lab2)
5723     gfc_add_expr_to_block (&loop.pre, build1_v (LABEL_EXPR, lab2));
5724 
5725   /* For a scalar mask, enclose the loop in an if statement.  */
5726   if (maskexpr && maskss == NULL)
5727     {
5728       tree ifmask;
5729 
5730       gfc_init_se (&maskse, NULL);
5731       gfc_conv_expr_val (&maskse, maskexpr);
5732       gfc_init_block (&block);
5733       gfc_add_block_to_block (&block, &loop.pre);
5734       gfc_add_block_to_block (&block, &loop.post);
5735       tmp = gfc_finish_block (&block);
5736 
5737       /* For the else part of the scalar mask, just initialize
5738 	 the pos variable the same way as above.  */
5739 
5740       gfc_init_block (&elseblock);
5741       gfc_add_modify (&elseblock, pos, gfc_index_zero_node);
5742       elsetmp = gfc_finish_block (&elseblock);
5743       ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
5744       tmp = build3_v (COND_EXPR, ifmask, tmp, elsetmp);
5745       gfc_add_expr_to_block (&block, tmp);
5746       gfc_add_block_to_block (&se->pre, &block);
5747     }
5748   else
5749     {
5750       gfc_add_block_to_block (&se->pre, &loop.pre);
5751       gfc_add_block_to_block (&se->pre, &loop.post);
5752     }
5753   gfc_cleanup_loop (&loop);
5754 
5755   se->expr = convert (type, pos);
5756 }
5757 
5758 /* Emit code for findloc.  */
5759 
5760 static void
gfc_conv_intrinsic_findloc(gfc_se * se,gfc_expr * expr)5761 gfc_conv_intrinsic_findloc (gfc_se *se, gfc_expr *expr)
5762 {
5763   gfc_actual_arglist *array_arg, *value_arg, *dim_arg, *mask_arg,
5764     *kind_arg, *back_arg;
5765   gfc_expr *value_expr;
5766   int ikind;
5767   tree resvar;
5768   stmtblock_t block;
5769   stmtblock_t body;
5770   stmtblock_t loopblock;
5771   tree type;
5772   tree tmp;
5773   tree found;
5774   tree forward_branch = NULL_TREE;
5775   tree back_branch;
5776   gfc_loopinfo loop;
5777   gfc_ss *arrayss;
5778   gfc_ss *maskss;
5779   gfc_se arrayse;
5780   gfc_se valuese;
5781   gfc_se maskse;
5782   gfc_se backse;
5783   tree exit_label;
5784   gfc_expr *maskexpr;
5785   tree offset;
5786   int i;
5787   bool optional_mask;
5788 
5789   array_arg = expr->value.function.actual;
5790   value_arg = array_arg->next;
5791   dim_arg   = value_arg->next;
5792   mask_arg  = dim_arg->next;
5793   kind_arg  = mask_arg->next;
5794   back_arg  = kind_arg->next;
5795 
5796   /* Remove kind and set ikind.  */
5797   if (kind_arg->expr)
5798     {
5799       ikind = mpz_get_si (kind_arg->expr->value.integer);
5800       gfc_free_expr (kind_arg->expr);
5801       kind_arg->expr = NULL;
5802     }
5803   else
5804     ikind = gfc_default_integer_kind;
5805 
5806   value_expr = value_arg->expr;
5807 
5808   /* Unless it's a string, pass VALUE by value.  */
5809   if (value_expr->ts.type != BT_CHARACTER)
5810     value_arg->name = "%VAL";
5811 
5812   /* Pass BACK argument by value.  */
5813   back_arg->name = "%VAL";
5814 
5815   /* Call the library if we have a character function or if
5816      rank > 0.  */
5817   if (se->ss || array_arg->expr->ts.type == BT_CHARACTER)
5818     {
5819       se->ignore_optional = 1;
5820       if (expr->rank == 0)
5821 	{
5822 	  /* Remove dim argument.  */
5823 	  gfc_free_expr (dim_arg->expr);
5824 	  dim_arg->expr = NULL;
5825 	}
5826       gfc_conv_intrinsic_funcall (se, expr);
5827       return;
5828     }
5829 
5830   type = gfc_get_int_type (ikind);
5831 
5832   /* Initialize the result.  */
5833   resvar = gfc_create_var (gfc_array_index_type, "pos");
5834   gfc_add_modify (&se->pre, resvar, build_int_cst (gfc_array_index_type, 0));
5835   offset = gfc_create_var (gfc_array_index_type, "offset");
5836 
5837   maskexpr = mask_arg->expr;
5838   optional_mask = maskexpr && maskexpr->expr_type == EXPR_VARIABLE
5839     && maskexpr->symtree->n.sym->attr.dummy
5840     && maskexpr->symtree->n.sym->attr.optional;
5841 
5842   /*  Generate two loops, one for BACK=.true. and one for BACK=.false.  */
5843 
5844   for (i = 0 ; i < 2; i++)
5845     {
5846       /* Walk the arguments.  */
5847       arrayss = gfc_walk_expr (array_arg->expr);
5848       gcc_assert (arrayss != gfc_ss_terminator);
5849 
5850       if (maskexpr && maskexpr->rank != 0)
5851 	{
5852 	  maskss = gfc_walk_expr (maskexpr);
5853 	  gcc_assert (maskss != gfc_ss_terminator);
5854 	}
5855       else
5856 	maskss = NULL;
5857 
5858       /* Initialize the scalarizer.  */
5859       gfc_init_loopinfo (&loop);
5860       exit_label = gfc_build_label_decl (NULL_TREE);
5861       TREE_USED (exit_label) = 1;
5862 
5863       /* We add the mask first because the number of iterations is
5864 	 taken from the last ss, and this breaks if an absent
5865 	 optional argument is used for mask.  */
5866 
5867       if (maskss)
5868 	gfc_add_ss_to_loop (&loop, maskss);
5869       gfc_add_ss_to_loop (&loop, arrayss);
5870 
5871       /* Initialize the loop.  */
5872       gfc_conv_ss_startstride (&loop);
5873       gfc_conv_loop_setup (&loop, &expr->where);
5874 
5875       /* Calculate the offset.  */
5876       tmp = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
5877 			     gfc_index_one_node, loop.from[0]);
5878       gfc_add_modify (&loop.pre, offset, tmp);
5879 
5880       gfc_mark_ss_chain_used (arrayss, 1);
5881       if (maskss)
5882 	gfc_mark_ss_chain_used (maskss, 1);
5883 
5884       /* The first loop is for BACK=.true.  */
5885       if (i == 0)
5886 	loop.reverse[0] = GFC_REVERSE_SET;
5887 
5888       /* Generate the loop body.  */
5889       gfc_start_scalarized_body (&loop, &body);
5890 
5891       /* If we have an array mask, only add the element if it is
5892 	 set.  */
5893       if (maskss)
5894 	{
5895 	  gfc_init_se (&maskse, NULL);
5896 	  gfc_copy_loopinfo_to_se (&maskse, &loop);
5897 	  maskse.ss = maskss;
5898 	  gfc_conv_expr_val (&maskse, maskexpr);
5899 	  gfc_add_block_to_block (&body, &maskse.pre);
5900 	}
5901 
5902       /* If the condition matches then set the return value.  */
5903       gfc_start_block (&block);
5904 
5905       /* Add the offset.  */
5906       tmp = fold_build2_loc (input_location, PLUS_EXPR,
5907 			     TREE_TYPE (resvar),
5908 			     loop.loopvar[0], offset);
5909       gfc_add_modify (&block, resvar, tmp);
5910       /* And break out of the loop.  */
5911       tmp = build1_v (GOTO_EXPR, exit_label);
5912       gfc_add_expr_to_block (&block, tmp);
5913 
5914       found = gfc_finish_block (&block);
5915 
5916       /* Check this element.  */
5917       gfc_init_se (&arrayse, NULL);
5918       gfc_copy_loopinfo_to_se (&arrayse, &loop);
5919       arrayse.ss = arrayss;
5920       gfc_conv_expr_val (&arrayse, array_arg->expr);
5921       gfc_add_block_to_block (&body, &arrayse.pre);
5922 
5923       gfc_init_se (&valuese, NULL);
5924       gfc_conv_expr_val (&valuese, value_arg->expr);
5925       gfc_add_block_to_block (&body, &valuese.pre);
5926 
5927       tmp = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
5928 			     arrayse.expr, valuese.expr);
5929 
5930       tmp = build3_v (COND_EXPR, tmp, found, build_empty_stmt (input_location));
5931       if (maskss)
5932 	{
5933 	  /* We enclose the above in if (mask) {...}.  If the mask is
5934 	     an optional argument, generate IF (.NOT. PRESENT(MASK)
5935 	     .OR. MASK(I)). */
5936 
5937 	  tree ifmask;
5938 	  ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
5939 	  tmp = build3_v (COND_EXPR, ifmask, tmp,
5940 			  build_empty_stmt (input_location));
5941 	}
5942 
5943       gfc_add_expr_to_block (&body, tmp);
5944       gfc_add_block_to_block (&body, &arrayse.post);
5945 
5946       gfc_trans_scalarizing_loops (&loop, &body);
5947 
5948       /* Add the exit label.  */
5949       tmp = build1_v (LABEL_EXPR, exit_label);
5950       gfc_add_expr_to_block (&loop.pre, tmp);
5951       gfc_start_block (&loopblock);
5952       gfc_add_block_to_block (&loopblock, &loop.pre);
5953       gfc_add_block_to_block (&loopblock, &loop.post);
5954       if (i == 0)
5955 	forward_branch = gfc_finish_block (&loopblock);
5956       else
5957 	back_branch = gfc_finish_block (&loopblock);
5958 
5959       gfc_cleanup_loop (&loop);
5960     }
5961 
5962   /* Enclose the two loops in an IF statement.  */
5963 
5964   gfc_init_se (&backse, NULL);
5965   gfc_conv_expr_val (&backse, back_arg->expr);
5966   gfc_add_block_to_block (&se->pre, &backse.pre);
5967   tmp = build3_v (COND_EXPR, backse.expr, forward_branch, back_branch);
5968 
5969   /* For a scalar mask, enclose the loop in an if statement.  */
5970   if (maskexpr && maskss == NULL)
5971     {
5972       tree ifmask;
5973       tree if_stmt;
5974 
5975       gfc_init_se (&maskse, NULL);
5976       gfc_conv_expr_val (&maskse, maskexpr);
5977       gfc_init_block (&block);
5978       gfc_add_expr_to_block (&block, maskse.expr);
5979       ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
5980       if_stmt = build3_v (COND_EXPR, ifmask, tmp,
5981 			  build_empty_stmt (input_location));
5982       gfc_add_expr_to_block (&block, if_stmt);
5983       tmp = gfc_finish_block (&block);
5984     }
5985 
5986   gfc_add_expr_to_block (&se->pre, tmp);
5987   se->expr = convert (type, resvar);
5988 
5989 }
5990 
5991 /* Emit code for minval or maxval intrinsic.  There are many different cases
5992    we need to handle.  For performance reasons we sometimes create two
5993    loops instead of one, where the second one is much simpler.
5994    Examples for minval intrinsic:
5995    1) Result is an array, a call is generated
5996    2) Array mask is used and NaNs need to be supported, rank 1:
5997       limit = Infinity;
5998       nonempty = false;
5999       S = from;
6000       while (S <= to) {
6001 	if (mask[S]) { nonempty = true; if (a[S] <= limit) goto lab; }
6002 	S++;
6003       }
6004       limit = nonempty ? NaN : huge (limit);
6005       lab:
6006       while (S <= to) { if(mask[S]) limit = min (a[S], limit); S++; }
6007    3) NaNs need to be supported, but it is known at compile time or cheaply
6008       at runtime whether array is nonempty or not, rank 1:
6009       limit = Infinity;
6010       S = from;
6011       while (S <= to) { if (a[S] <= limit) goto lab; S++; }
6012       limit = (from <= to) ? NaN : huge (limit);
6013       lab:
6014       while (S <= to) { limit = min (a[S], limit); S++; }
6015    4) Array mask is used and NaNs need to be supported, rank > 1:
6016       limit = Infinity;
6017       nonempty = false;
6018       fast = false;
6019       S1 = from1;
6020       while (S1 <= to1) {
6021 	S2 = from2;
6022 	while (S2 <= to2) {
6023 	  if (mask[S1][S2]) {
6024 	    if (fast) limit = min (a[S1][S2], limit);
6025 	    else {
6026 	      nonempty = true;
6027 	      if (a[S1][S2] <= limit) {
6028 		limit = a[S1][S2];
6029 		fast = true;
6030 	      }
6031 	    }
6032 	  }
6033 	  S2++;
6034 	}
6035 	S1++;
6036       }
6037       if (!fast)
6038 	limit = nonempty ? NaN : huge (limit);
6039    5) NaNs need to be supported, but it is known at compile time or cheaply
6040       at runtime whether array is nonempty or not, rank > 1:
6041       limit = Infinity;
6042       fast = false;
6043       S1 = from1;
6044       while (S1 <= to1) {
6045 	S2 = from2;
6046 	while (S2 <= to2) {
6047 	  if (fast) limit = min (a[S1][S2], limit);
6048 	  else {
6049 	    if (a[S1][S2] <= limit) {
6050 	      limit = a[S1][S2];
6051 	      fast = true;
6052 	    }
6053 	  }
6054 	  S2++;
6055 	}
6056 	S1++;
6057       }
6058       if (!fast)
6059 	limit = (nonempty_array) ? NaN : huge (limit);
6060    6) NaNs aren't supported, but infinities are.  Array mask is used:
6061       limit = Infinity;
6062       nonempty = false;
6063       S = from;
6064       while (S <= to) {
6065 	if (mask[S]) { nonempty = true; limit = min (a[S], limit); }
6066 	S++;
6067       }
6068       limit = nonempty ? limit : huge (limit);
6069    7) Same without array mask:
6070       limit = Infinity;
6071       S = from;
6072       while (S <= to) { limit = min (a[S], limit); S++; }
6073       limit = (from <= to) ? limit : huge (limit);
6074    8) Neither NaNs nor infinities are supported (-ffast-math or BT_INTEGER):
6075       limit = huge (limit);
6076       S = from;
6077       while (S <= to) { limit = min (a[S], limit); S++); }
6078       (or
6079       while (S <= to) { if (mask[S]) limit = min (a[S], limit); S++; }
6080       with array mask instead).
6081    For 3), 5), 7) and 8), if mask is scalar, this all goes into a conditional,
6082    setting limit = huge (limit); in the else branch.  */
6083 
6084 static void
gfc_conv_intrinsic_minmaxval(gfc_se * se,gfc_expr * expr,enum tree_code op)6085 gfc_conv_intrinsic_minmaxval (gfc_se * se, gfc_expr * expr, enum tree_code op)
6086 {
6087   tree limit;
6088   tree type;
6089   tree tmp;
6090   tree ifbody;
6091   tree nonempty;
6092   tree nonempty_var;
6093   tree lab;
6094   tree fast;
6095   tree huge_cst = NULL, nan_cst = NULL;
6096   stmtblock_t body;
6097   stmtblock_t block, block2;
6098   gfc_loopinfo loop;
6099   gfc_actual_arglist *actual;
6100   gfc_ss *arrayss;
6101   gfc_ss *maskss;
6102   gfc_se arrayse;
6103   gfc_se maskse;
6104   gfc_expr *arrayexpr;
6105   gfc_expr *maskexpr;
6106   int n;
6107   bool optional_mask;
6108 
6109   if (se->ss)
6110     {
6111       gfc_conv_intrinsic_funcall (se, expr);
6112       return;
6113     }
6114 
6115   actual = expr->value.function.actual;
6116   arrayexpr = actual->expr;
6117 
6118   if (arrayexpr->ts.type == BT_CHARACTER)
6119     {
6120       gfc_actual_arglist *dim = actual->next;
6121       if (expr->rank == 0 && dim->expr != 0)
6122 	{
6123 	  gfc_free_expr (dim->expr);
6124 	  dim->expr = NULL;
6125 	}
6126       gfc_conv_intrinsic_funcall (se, expr);
6127       return;
6128     }
6129 
6130   type = gfc_typenode_for_spec (&expr->ts);
6131   /* Initialize the result.  */
6132   limit = gfc_create_var (type, "limit");
6133   n = gfc_validate_kind (expr->ts.type, expr->ts.kind, false);
6134   switch (expr->ts.type)
6135     {
6136     case BT_REAL:
6137       huge_cst = gfc_conv_mpfr_to_tree (gfc_real_kinds[n].huge,
6138 					expr->ts.kind, 0);
6139       if (HONOR_INFINITIES (DECL_MODE (limit)))
6140 	{
6141 	  REAL_VALUE_TYPE real;
6142 	  real_inf (&real);
6143 	  tmp = build_real (type, real);
6144 	}
6145       else
6146 	tmp = huge_cst;
6147       if (HONOR_NANS (DECL_MODE (limit)))
6148 	nan_cst = gfc_build_nan (type, "");
6149       break;
6150 
6151     case BT_INTEGER:
6152       tmp = gfc_conv_mpz_to_tree (gfc_integer_kinds[n].huge, expr->ts.kind);
6153       break;
6154 
6155     default:
6156       gcc_unreachable ();
6157     }
6158 
6159   /* We start with the most negative possible value for MAXVAL, and the most
6160      positive possible value for MINVAL. The most negative possible value is
6161      -HUGE for BT_REAL and (-HUGE - 1) for BT_INTEGER; the most positive
6162      possible value is HUGE in both cases.  */
6163   if (op == GT_EXPR)
6164     {
6165       tmp = fold_build1_loc (input_location, NEGATE_EXPR, TREE_TYPE (tmp), tmp);
6166       if (huge_cst)
6167 	huge_cst = fold_build1_loc (input_location, NEGATE_EXPR,
6168 				    TREE_TYPE (huge_cst), huge_cst);
6169     }
6170 
6171   if (op == GT_EXPR && expr->ts.type == BT_INTEGER)
6172     tmp = fold_build2_loc (input_location, MINUS_EXPR, TREE_TYPE (tmp),
6173 			   tmp, build_int_cst (type, 1));
6174 
6175   gfc_add_modify (&se->pre, limit, tmp);
6176 
6177   /* Walk the arguments.  */
6178   arrayss = gfc_walk_expr (arrayexpr);
6179   gcc_assert (arrayss != gfc_ss_terminator);
6180 
6181   actual = actual->next->next;
6182   gcc_assert (actual);
6183   maskexpr = actual->expr;
6184   optional_mask = maskexpr && maskexpr->expr_type == EXPR_VARIABLE
6185     && maskexpr->symtree->n.sym->attr.dummy
6186     && maskexpr->symtree->n.sym->attr.optional;
6187   nonempty = NULL;
6188   if (maskexpr && maskexpr->rank != 0)
6189     {
6190       maskss = gfc_walk_expr (maskexpr);
6191       gcc_assert (maskss != gfc_ss_terminator);
6192     }
6193   else
6194     {
6195       mpz_t asize;
6196       if (gfc_array_size (arrayexpr, &asize))
6197 	{
6198 	  nonempty = gfc_conv_mpz_to_tree (asize, gfc_index_integer_kind);
6199 	  mpz_clear (asize);
6200 	  nonempty = fold_build2_loc (input_location, GT_EXPR,
6201 				      logical_type_node, nonempty,
6202 				      gfc_index_zero_node);
6203 	}
6204       maskss = NULL;
6205     }
6206 
6207   /* Initialize the scalarizer.  */
6208   gfc_init_loopinfo (&loop);
6209 
6210   /* We add the mask first because the number of iterations is taken
6211      from the last ss, and this breaks if an absent optional argument
6212      is used for mask.  */
6213 
6214   if (maskss)
6215     gfc_add_ss_to_loop (&loop, maskss);
6216   gfc_add_ss_to_loop (&loop, arrayss);
6217 
6218   /* Initialize the loop.  */
6219   gfc_conv_ss_startstride (&loop);
6220 
6221   /* The code generated can have more than one loop in sequence (see the
6222      comment at the function header).  This doesn't work well with the
6223      scalarizer, which changes arrays' offset when the scalarization loops
6224      are generated (see gfc_trans_preloop_setup).  Fortunately, {min,max}val
6225      are  currently inlined in the scalar case only.  As there is no dependency
6226      to care about in that case, there is no temporary, so that we can use the
6227      scalarizer temporary code to handle multiple loops.  Thus, we set temp_dim
6228      here, we call gfc_mark_ss_chain_used with flag=3 later, and we use
6229      gfc_trans_scalarized_loop_boundary even later to restore offset.
6230      TODO: this prevents inlining of rank > 0 minmaxval calls, so this
6231      should eventually go away.  We could either create two loops properly,
6232      or find another way to save/restore the array offsets between the two
6233      loops (without conflicting with temporary management), or use a single
6234      loop minmaxval implementation.  See PR 31067.  */
6235   loop.temp_dim = loop.dimen;
6236   gfc_conv_loop_setup (&loop, &expr->where);
6237 
6238   if (nonempty == NULL && maskss == NULL
6239       && loop.dimen == 1 && loop.from[0] && loop.to[0])
6240     nonempty = fold_build2_loc (input_location, LE_EXPR, logical_type_node,
6241 				loop.from[0], loop.to[0]);
6242   nonempty_var = NULL;
6243   if (nonempty == NULL
6244       && (HONOR_INFINITIES (DECL_MODE (limit))
6245 	  || HONOR_NANS (DECL_MODE (limit))))
6246     {
6247       nonempty_var = gfc_create_var (logical_type_node, "nonempty");
6248       gfc_add_modify (&se->pre, nonempty_var, logical_false_node);
6249       nonempty = nonempty_var;
6250     }
6251   lab = NULL;
6252   fast = NULL;
6253   if (HONOR_NANS (DECL_MODE (limit)))
6254     {
6255       if (loop.dimen == 1)
6256 	{
6257 	  lab = gfc_build_label_decl (NULL_TREE);
6258 	  TREE_USED (lab) = 1;
6259 	}
6260       else
6261 	{
6262 	  fast = gfc_create_var (logical_type_node, "fast");
6263 	  gfc_add_modify (&se->pre, fast, logical_false_node);
6264 	}
6265     }
6266 
6267   gfc_mark_ss_chain_used (arrayss, lab ? 3 : 1);
6268   if (maskss)
6269     gfc_mark_ss_chain_used (maskss, lab ? 3 : 1);
6270   /* Generate the loop body.  */
6271   gfc_start_scalarized_body (&loop, &body);
6272 
6273   /* If we have a mask, only add this element if the mask is set.  */
6274   if (maskss)
6275     {
6276       gfc_init_se (&maskse, NULL);
6277       gfc_copy_loopinfo_to_se (&maskse, &loop);
6278       maskse.ss = maskss;
6279       gfc_conv_expr_val (&maskse, maskexpr);
6280       gfc_add_block_to_block (&body, &maskse.pre);
6281 
6282       gfc_start_block (&block);
6283     }
6284   else
6285     gfc_init_block (&block);
6286 
6287   /* Compare with the current limit.  */
6288   gfc_init_se (&arrayse, NULL);
6289   gfc_copy_loopinfo_to_se (&arrayse, &loop);
6290   arrayse.ss = arrayss;
6291   gfc_conv_expr_val (&arrayse, arrayexpr);
6292   gfc_add_block_to_block (&block, &arrayse.pre);
6293 
6294   gfc_init_block (&block2);
6295 
6296   if (nonempty_var)
6297     gfc_add_modify (&block2, nonempty_var, logical_true_node);
6298 
6299   if (HONOR_NANS (DECL_MODE (limit)))
6300     {
6301       tmp = fold_build2_loc (input_location, op == GT_EXPR ? GE_EXPR : LE_EXPR,
6302 			     logical_type_node, arrayse.expr, limit);
6303       if (lab)
6304 	ifbody = build1_v (GOTO_EXPR, lab);
6305       else
6306 	{
6307 	  stmtblock_t ifblock;
6308 
6309 	  gfc_init_block (&ifblock);
6310 	  gfc_add_modify (&ifblock, limit, arrayse.expr);
6311 	  gfc_add_modify (&ifblock, fast, logical_true_node);
6312 	  ifbody = gfc_finish_block (&ifblock);
6313 	}
6314       tmp = build3_v (COND_EXPR, tmp, ifbody,
6315 		      build_empty_stmt (input_location));
6316       gfc_add_expr_to_block (&block2, tmp);
6317     }
6318   else
6319     {
6320       /* MIN_EXPR/MAX_EXPR has unspecified behavior with NaNs or
6321 	 signed zeros.  */
6322       tmp = fold_build2_loc (input_location,
6323 			     op == GT_EXPR ? MAX_EXPR : MIN_EXPR,
6324 			     type, arrayse.expr, limit);
6325       gfc_add_modify (&block2, limit, tmp);
6326     }
6327 
6328   if (fast)
6329     {
6330       tree elsebody = gfc_finish_block (&block2);
6331 
6332       /* MIN_EXPR/MAX_EXPR has unspecified behavior with NaNs or
6333 	 signed zeros.  */
6334       if (HONOR_NANS (DECL_MODE (limit)))
6335 	{
6336 	  tmp = fold_build2_loc (input_location, op, logical_type_node,
6337 				 arrayse.expr, limit);
6338 	  ifbody = build2_v (MODIFY_EXPR, limit, arrayse.expr);
6339 	  ifbody = build3_v (COND_EXPR, tmp, ifbody,
6340 			     build_empty_stmt (input_location));
6341 	}
6342       else
6343 	{
6344 	  tmp = fold_build2_loc (input_location,
6345 				 op == GT_EXPR ? MAX_EXPR : MIN_EXPR,
6346 				 type, arrayse.expr, limit);
6347 	  ifbody = build2_v (MODIFY_EXPR, limit, tmp);
6348 	}
6349       tmp = build3_v (COND_EXPR, fast, ifbody, elsebody);
6350       gfc_add_expr_to_block (&block, tmp);
6351     }
6352   else
6353     gfc_add_block_to_block (&block, &block2);
6354 
6355   gfc_add_block_to_block (&block, &arrayse.post);
6356 
6357   tmp = gfc_finish_block (&block);
6358   if (maskss)
6359     {
6360       /* We enclose the above in if (mask) {...}.  If the mask is an
6361 	 optional argument, generate IF (.NOT. PRESENT(MASK)
6362 	 .OR. MASK(I)).  */
6363       tree ifmask;
6364       ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
6365       tmp = build3_v (COND_EXPR, ifmask, tmp,
6366 		      build_empty_stmt (input_location));
6367     }
6368   gfc_add_expr_to_block (&body, tmp);
6369 
6370   if (lab)
6371     {
6372       gfc_trans_scalarized_loop_boundary (&loop, &body);
6373 
6374       tmp = fold_build3_loc (input_location, COND_EXPR, type, nonempty,
6375 			     nan_cst, huge_cst);
6376       gfc_add_modify (&loop.code[0], limit, tmp);
6377       gfc_add_expr_to_block (&loop.code[0], build1_v (LABEL_EXPR, lab));
6378 
6379       /* If we have a mask, only add this element if the mask is set.  */
6380       if (maskss)
6381 	{
6382 	  gfc_init_se (&maskse, NULL);
6383 	  gfc_copy_loopinfo_to_se (&maskse, &loop);
6384 	  maskse.ss = maskss;
6385 	  gfc_conv_expr_val (&maskse, maskexpr);
6386 	  gfc_add_block_to_block (&body, &maskse.pre);
6387 
6388 	  gfc_start_block (&block);
6389 	}
6390       else
6391 	gfc_init_block (&block);
6392 
6393       /* Compare with the current limit.  */
6394       gfc_init_se (&arrayse, NULL);
6395       gfc_copy_loopinfo_to_se (&arrayse, &loop);
6396       arrayse.ss = arrayss;
6397       gfc_conv_expr_val (&arrayse, arrayexpr);
6398       gfc_add_block_to_block (&block, &arrayse.pre);
6399 
6400       /* MIN_EXPR/MAX_EXPR has unspecified behavior with NaNs or
6401 	 signed zeros.  */
6402       if (HONOR_NANS (DECL_MODE (limit)))
6403 	{
6404 	  tmp = fold_build2_loc (input_location, op, logical_type_node,
6405 				 arrayse.expr, limit);
6406 	  ifbody = build2_v (MODIFY_EXPR, limit, arrayse.expr);
6407 	  tmp = build3_v (COND_EXPR, tmp, ifbody,
6408 			  build_empty_stmt (input_location));
6409 	  gfc_add_expr_to_block (&block, tmp);
6410 	}
6411       else
6412 	{
6413 	  tmp = fold_build2_loc (input_location,
6414 				 op == GT_EXPR ? MAX_EXPR : MIN_EXPR,
6415 				 type, arrayse.expr, limit);
6416 	  gfc_add_modify (&block, limit, tmp);
6417 	}
6418 
6419       gfc_add_block_to_block (&block, &arrayse.post);
6420 
6421       tmp = gfc_finish_block (&block);
6422       if (maskss)
6423 	/* We enclose the above in if (mask) {...}.  */
6424 	{
6425 	  tree ifmask;
6426 	  ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
6427 	  tmp = build3_v (COND_EXPR, ifmask, tmp,
6428 			  build_empty_stmt (input_location));
6429 	}
6430 
6431       gfc_add_expr_to_block (&body, tmp);
6432       /* Avoid initializing loopvar[0] again, it should be left where
6433 	 it finished by the first loop.  */
6434       loop.from[0] = loop.loopvar[0];
6435     }
6436   gfc_trans_scalarizing_loops (&loop, &body);
6437 
6438   if (fast)
6439     {
6440       tmp = fold_build3_loc (input_location, COND_EXPR, type, nonempty,
6441 			     nan_cst, huge_cst);
6442       ifbody = build2_v (MODIFY_EXPR, limit, tmp);
6443       tmp = build3_v (COND_EXPR, fast, build_empty_stmt (input_location),
6444 		      ifbody);
6445       gfc_add_expr_to_block (&loop.pre, tmp);
6446     }
6447   else if (HONOR_INFINITIES (DECL_MODE (limit)) && !lab)
6448     {
6449       tmp = fold_build3_loc (input_location, COND_EXPR, type, nonempty, limit,
6450 			     huge_cst);
6451       gfc_add_modify (&loop.pre, limit, tmp);
6452     }
6453 
6454   /* For a scalar mask, enclose the loop in an if statement.  */
6455   if (maskexpr && maskss == NULL)
6456     {
6457       tree else_stmt;
6458       tree ifmask;
6459 
6460       gfc_init_se (&maskse, NULL);
6461       gfc_conv_expr_val (&maskse, maskexpr);
6462       gfc_init_block (&block);
6463       gfc_add_block_to_block (&block, &loop.pre);
6464       gfc_add_block_to_block (&block, &loop.post);
6465       tmp = gfc_finish_block (&block);
6466 
6467       if (HONOR_INFINITIES (DECL_MODE (limit)))
6468 	else_stmt = build2_v (MODIFY_EXPR, limit, huge_cst);
6469       else
6470 	else_stmt = build_empty_stmt (input_location);
6471 
6472       ifmask = conv_mask_condition (&maskse, maskexpr, optional_mask);
6473       tmp = build3_v (COND_EXPR, ifmask, tmp, else_stmt);
6474       gfc_add_expr_to_block (&block, tmp);
6475       gfc_add_block_to_block (&se->pre, &block);
6476     }
6477   else
6478     {
6479       gfc_add_block_to_block (&se->pre, &loop.pre);
6480       gfc_add_block_to_block (&se->pre, &loop.post);
6481     }
6482 
6483   gfc_cleanup_loop (&loop);
6484 
6485   se->expr = limit;
6486 }
6487 
6488 /* BTEST (i, pos) = (i & (1 << pos)) != 0.  */
6489 static void
gfc_conv_intrinsic_btest(gfc_se * se,gfc_expr * expr)6490 gfc_conv_intrinsic_btest (gfc_se * se, gfc_expr * expr)
6491 {
6492   tree args[2];
6493   tree type;
6494   tree tmp;
6495 
6496   gfc_conv_intrinsic_function_args (se, expr, args, 2);
6497   type = TREE_TYPE (args[0]);
6498 
6499   /* Optionally generate code for runtime argument check.  */
6500   if (gfc_option.rtcheck & GFC_RTCHECK_BITS)
6501     {
6502       tree below = fold_build2_loc (input_location, LT_EXPR,
6503 				    logical_type_node, args[1],
6504 				    build_int_cst (TREE_TYPE (args[1]), 0));
6505       tree nbits = build_int_cst (TREE_TYPE (args[1]), TYPE_PRECISION (type));
6506       tree above = fold_build2_loc (input_location, GE_EXPR,
6507 				    logical_type_node, args[1], nbits);
6508       tree scond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
6509 				    logical_type_node, below, above);
6510       gfc_trans_runtime_check (true, false, scond, &se->pre, &expr->where,
6511 			       "POS argument (%ld) out of range 0:%ld "
6512 			       "in intrinsic BTEST",
6513 			       fold_convert (long_integer_type_node, args[1]),
6514 			       fold_convert (long_integer_type_node, nbits));
6515     }
6516 
6517   tmp = fold_build2_loc (input_location, LSHIFT_EXPR, type,
6518 			 build_int_cst (type, 1), args[1]);
6519   tmp = fold_build2_loc (input_location, BIT_AND_EXPR, type, args[0], tmp);
6520   tmp = fold_build2_loc (input_location, NE_EXPR, logical_type_node, tmp,
6521 			 build_int_cst (type, 0));
6522   type = gfc_typenode_for_spec (&expr->ts);
6523   se->expr = convert (type, tmp);
6524 }
6525 
6526 
6527 /* Generate code for BGE, BGT, BLE and BLT intrinsics.  */
6528 static void
gfc_conv_intrinsic_bitcomp(gfc_se * se,gfc_expr * expr,enum tree_code op)6529 gfc_conv_intrinsic_bitcomp (gfc_se * se, gfc_expr * expr, enum tree_code op)
6530 {
6531   tree args[2];
6532 
6533   gfc_conv_intrinsic_function_args (se, expr, args, 2);
6534 
6535   /* Convert both arguments to the unsigned type of the same size.  */
6536   args[0] = fold_convert (unsigned_type_for (TREE_TYPE (args[0])), args[0]);
6537   args[1] = fold_convert (unsigned_type_for (TREE_TYPE (args[1])), args[1]);
6538 
6539   /* If they have unequal type size, convert to the larger one.  */
6540   if (TYPE_PRECISION (TREE_TYPE (args[0]))
6541       > TYPE_PRECISION (TREE_TYPE (args[1])))
6542     args[1] = fold_convert (TREE_TYPE (args[0]), args[1]);
6543   else if (TYPE_PRECISION (TREE_TYPE (args[1]))
6544 	   > TYPE_PRECISION (TREE_TYPE (args[0])))
6545     args[0] = fold_convert (TREE_TYPE (args[1]), args[0]);
6546 
6547   /* Now, we compare them.  */
6548   se->expr = fold_build2_loc (input_location, op, logical_type_node,
6549 			      args[0], args[1]);
6550 }
6551 
6552 
6553 /* Generate code to perform the specified operation.  */
6554 static void
gfc_conv_intrinsic_bitop(gfc_se * se,gfc_expr * expr,enum tree_code op)6555 gfc_conv_intrinsic_bitop (gfc_se * se, gfc_expr * expr, enum tree_code op)
6556 {
6557   tree args[2];
6558 
6559   gfc_conv_intrinsic_function_args (se, expr, args, 2);
6560   se->expr = fold_build2_loc (input_location, op, TREE_TYPE (args[0]),
6561 			      args[0], args[1]);
6562 }
6563 
6564 /* Bitwise not.  */
6565 static void
gfc_conv_intrinsic_not(gfc_se * se,gfc_expr * expr)6566 gfc_conv_intrinsic_not (gfc_se * se, gfc_expr * expr)
6567 {
6568   tree arg;
6569 
6570   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
6571   se->expr = fold_build1_loc (input_location, BIT_NOT_EXPR,
6572 			      TREE_TYPE (arg), arg);
6573 }
6574 
6575 /* Set or clear a single bit.  */
6576 static void
gfc_conv_intrinsic_singlebitop(gfc_se * se,gfc_expr * expr,int set)6577 gfc_conv_intrinsic_singlebitop (gfc_se * se, gfc_expr * expr, int set)
6578 {
6579   tree args[2];
6580   tree type;
6581   tree tmp;
6582   enum tree_code op;
6583 
6584   gfc_conv_intrinsic_function_args (se, expr, args, 2);
6585   type = TREE_TYPE (args[0]);
6586 
6587   /* Optionally generate code for runtime argument check.  */
6588   if (gfc_option.rtcheck & GFC_RTCHECK_BITS)
6589     {
6590       tree below = fold_build2_loc (input_location, LT_EXPR,
6591 				    logical_type_node, args[1],
6592 				    build_int_cst (TREE_TYPE (args[1]), 0));
6593       tree nbits = build_int_cst (TREE_TYPE (args[1]), TYPE_PRECISION (type));
6594       tree above = fold_build2_loc (input_location, GE_EXPR,
6595 				    logical_type_node, args[1], nbits);
6596       tree scond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
6597 				    logical_type_node, below, above);
6598       size_t len_name = strlen (expr->value.function.isym->name);
6599       char *name = XALLOCAVEC (char, len_name + 1);
6600       for (size_t i = 0; i < len_name; i++)
6601 	name[i] = TOUPPER (expr->value.function.isym->name[i]);
6602       name[len_name] = '\0';
6603       tree iname = gfc_build_addr_expr (pchar_type_node,
6604 					gfc_build_cstring_const (name));
6605       gfc_trans_runtime_check (true, false, scond, &se->pre, &expr->where,
6606 			       "POS argument (%ld) out of range 0:%ld "
6607 			       "in intrinsic %s",
6608 			       fold_convert (long_integer_type_node, args[1]),
6609 			       fold_convert (long_integer_type_node, nbits),
6610 			       iname);
6611     }
6612 
6613   tmp = fold_build2_loc (input_location, LSHIFT_EXPR, type,
6614 			 build_int_cst (type, 1), args[1]);
6615   if (set)
6616     op = BIT_IOR_EXPR;
6617   else
6618     {
6619       op = BIT_AND_EXPR;
6620       tmp = fold_build1_loc (input_location, BIT_NOT_EXPR, type, tmp);
6621     }
6622   se->expr = fold_build2_loc (input_location, op, type, args[0], tmp);
6623 }
6624 
6625 /* Extract a sequence of bits.
6626     IBITS(I, POS, LEN) = (I >> POS) & ~((~0) << LEN).  */
6627 static void
gfc_conv_intrinsic_ibits(gfc_se * se,gfc_expr * expr)6628 gfc_conv_intrinsic_ibits (gfc_se * se, gfc_expr * expr)
6629 {
6630   tree args[3];
6631   tree type;
6632   tree tmp;
6633   tree mask;
6634   tree num_bits, cond;
6635 
6636   gfc_conv_intrinsic_function_args (se, expr, args, 3);
6637   type = TREE_TYPE (args[0]);
6638 
6639   /* Optionally generate code for runtime argument check.  */
6640   if (gfc_option.rtcheck & GFC_RTCHECK_BITS)
6641     {
6642       tree tmp1 = fold_convert (long_integer_type_node, args[1]);
6643       tree tmp2 = fold_convert (long_integer_type_node, args[2]);
6644       tree nbits = build_int_cst (long_integer_type_node,
6645 				  TYPE_PRECISION (type));
6646       tree below = fold_build2_loc (input_location, LT_EXPR,
6647 				    logical_type_node, args[1],
6648 				    build_int_cst (TREE_TYPE (args[1]), 0));
6649       tree above = fold_build2_loc (input_location, GT_EXPR,
6650 				    logical_type_node, tmp1, nbits);
6651       tree scond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
6652 				    logical_type_node, below, above);
6653       gfc_trans_runtime_check (true, false, scond, &se->pre, &expr->where,
6654 			       "POS argument (%ld) out of range 0:%ld "
6655 			       "in intrinsic IBITS", tmp1, nbits);
6656       below = fold_build2_loc (input_location, LT_EXPR,
6657 			       logical_type_node, args[2],
6658 			       build_int_cst (TREE_TYPE (args[2]), 0));
6659       above = fold_build2_loc (input_location, GT_EXPR,
6660 			       logical_type_node, tmp2, nbits);
6661       scond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
6662 			       logical_type_node, below, above);
6663       gfc_trans_runtime_check (true, false, scond, &se->pre, &expr->where,
6664 			       "LEN argument (%ld) out of range 0:%ld "
6665 			       "in intrinsic IBITS", tmp2, nbits);
6666       above = fold_build2_loc (input_location, PLUS_EXPR,
6667 			       long_integer_type_node, tmp1, tmp2);
6668       scond = fold_build2_loc (input_location, GT_EXPR,
6669 			       logical_type_node, above, nbits);
6670       gfc_trans_runtime_check (true, false, scond, &se->pre, &expr->where,
6671 			       "POS(%ld)+LEN(%ld)>BIT_SIZE(%ld) "
6672 			       "in intrinsic IBITS", tmp1, tmp2, nbits);
6673     }
6674 
6675   /* The Fortran standard allows (shift width) LEN <= BIT_SIZE(I), whereas
6676      gcc requires a shift width < BIT_SIZE(I), so we have to catch this
6677      special case.  See also gfc_conv_intrinsic_ishft ().  */
6678   num_bits = build_int_cst (TREE_TYPE (args[2]), TYPE_PRECISION (type));
6679 
6680   mask = build_int_cst (type, -1);
6681   mask = fold_build2_loc (input_location, LSHIFT_EXPR, type, mask, args[2]);
6682   cond = fold_build2_loc (input_location, GE_EXPR, logical_type_node, args[2],
6683 			  num_bits);
6684   mask = fold_build3_loc (input_location, COND_EXPR, type, cond,
6685 			  build_int_cst (type, 0), mask);
6686   mask = fold_build1_loc (input_location, BIT_NOT_EXPR, type, mask);
6687 
6688   tmp = fold_build2_loc (input_location, RSHIFT_EXPR, type, args[0], args[1]);
6689 
6690   se->expr = fold_build2_loc (input_location, BIT_AND_EXPR, type, tmp, mask);
6691 }
6692 
6693 static void
gfc_conv_intrinsic_shift(gfc_se * se,gfc_expr * expr,bool right_shift,bool arithmetic)6694 gfc_conv_intrinsic_shift (gfc_se * se, gfc_expr * expr, bool right_shift,
6695 			  bool arithmetic)
6696 {
6697   tree args[2], type, num_bits, cond;
6698   tree bigshift;
6699 
6700   gfc_conv_intrinsic_function_args (se, expr, args, 2);
6701 
6702   args[0] = gfc_evaluate_now (args[0], &se->pre);
6703   args[1] = gfc_evaluate_now (args[1], &se->pre);
6704   type = TREE_TYPE (args[0]);
6705 
6706   if (!arithmetic)
6707     args[0] = fold_convert (unsigned_type_for (type), args[0]);
6708   else
6709     gcc_assert (right_shift);
6710 
6711   se->expr = fold_build2_loc (input_location,
6712 			      right_shift ? RSHIFT_EXPR : LSHIFT_EXPR,
6713 			      TREE_TYPE (args[0]), args[0], args[1]);
6714 
6715   if (!arithmetic)
6716     se->expr = fold_convert (type, se->expr);
6717 
6718   if (!arithmetic)
6719     bigshift = build_int_cst (type, 0);
6720   else
6721     {
6722       tree nonneg = fold_build2_loc (input_location, GE_EXPR,
6723 				     logical_type_node, args[0],
6724 				     build_int_cst (TREE_TYPE (args[0]), 0));
6725       bigshift = fold_build3_loc (input_location, COND_EXPR, type, nonneg,
6726 				  build_int_cst (type, 0),
6727 				  build_int_cst (type, -1));
6728     }
6729 
6730   /* The Fortran standard allows shift widths <= BIT_SIZE(I), whereas
6731      gcc requires a shift width < BIT_SIZE(I), so we have to catch this
6732      special case.  */
6733   num_bits = build_int_cst (TREE_TYPE (args[1]), TYPE_PRECISION (type));
6734 
6735   /* Optionally generate code for runtime argument check.  */
6736   if (gfc_option.rtcheck & GFC_RTCHECK_BITS)
6737     {
6738       tree below = fold_build2_loc (input_location, LT_EXPR,
6739 				    logical_type_node, args[1],
6740 				    build_int_cst (TREE_TYPE (args[1]), 0));
6741       tree above = fold_build2_loc (input_location, GT_EXPR,
6742 				    logical_type_node, args[1], num_bits);
6743       tree scond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
6744 				    logical_type_node, below, above);
6745       size_t len_name = strlen (expr->value.function.isym->name);
6746       char *name = XALLOCAVEC (char, len_name + 1);
6747       for (size_t i = 0; i < len_name; i++)
6748 	name[i] = TOUPPER (expr->value.function.isym->name[i]);
6749       name[len_name] = '\0';
6750       tree iname = gfc_build_addr_expr (pchar_type_node,
6751 					gfc_build_cstring_const (name));
6752       gfc_trans_runtime_check (true, false, scond, &se->pre, &expr->where,
6753 			       "SHIFT argument (%ld) out of range 0:%ld "
6754 			       "in intrinsic %s",
6755 			       fold_convert (long_integer_type_node, args[1]),
6756 			       fold_convert (long_integer_type_node, num_bits),
6757 			       iname);
6758     }
6759 
6760   cond = fold_build2_loc (input_location, GE_EXPR, logical_type_node,
6761 			  args[1], num_bits);
6762 
6763   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond,
6764 			      bigshift, se->expr);
6765 }
6766 
6767 /* ISHFT (I, SHIFT) = (abs (shift) >= BIT_SIZE (i))
6768                         ? 0
6769 	 	        : ((shift >= 0) ? i << shift : i >> -shift)
6770    where all shifts are logical shifts.  */
6771 static void
gfc_conv_intrinsic_ishft(gfc_se * se,gfc_expr * expr)6772 gfc_conv_intrinsic_ishft (gfc_se * se, gfc_expr * expr)
6773 {
6774   tree args[2];
6775   tree type;
6776   tree utype;
6777   tree tmp;
6778   tree width;
6779   tree num_bits;
6780   tree cond;
6781   tree lshift;
6782   tree rshift;
6783 
6784   gfc_conv_intrinsic_function_args (se, expr, args, 2);
6785 
6786   args[0] = gfc_evaluate_now (args[0], &se->pre);
6787   args[1] = gfc_evaluate_now (args[1], &se->pre);
6788 
6789   type = TREE_TYPE (args[0]);
6790   utype = unsigned_type_for (type);
6791 
6792   width = fold_build1_loc (input_location, ABS_EXPR, TREE_TYPE (args[1]),
6793 			   args[1]);
6794 
6795   /* Left shift if positive.  */
6796   lshift = fold_build2_loc (input_location, LSHIFT_EXPR, type, args[0], width);
6797 
6798   /* Right shift if negative.
6799      We convert to an unsigned type because we want a logical shift.
6800      The standard doesn't define the case of shifting negative
6801      numbers, and we try to be compatible with other compilers, most
6802      notably g77, here.  */
6803   rshift = fold_convert (type, fold_build2_loc (input_location, RSHIFT_EXPR,
6804 				    utype, convert (utype, args[0]), width));
6805 
6806   tmp = fold_build2_loc (input_location, GE_EXPR, logical_type_node, args[1],
6807 			 build_int_cst (TREE_TYPE (args[1]), 0));
6808   tmp = fold_build3_loc (input_location, COND_EXPR, type, tmp, lshift, rshift);
6809 
6810   /* The Fortran standard allows shift widths <= BIT_SIZE(I), whereas
6811      gcc requires a shift width < BIT_SIZE(I), so we have to catch this
6812      special case.  */
6813   num_bits = build_int_cst (TREE_TYPE (args[1]), TYPE_PRECISION (type));
6814 
6815   /* Optionally generate code for runtime argument check.  */
6816   if (gfc_option.rtcheck & GFC_RTCHECK_BITS)
6817     {
6818       tree outside = fold_build2_loc (input_location, GT_EXPR,
6819 				    logical_type_node, width, num_bits);
6820       gfc_trans_runtime_check (true, false, outside, &se->pre, &expr->where,
6821 			       "SHIFT argument (%ld) out of range -%ld:%ld "
6822 			       "in intrinsic ISHFT",
6823 			       fold_convert (long_integer_type_node, args[1]),
6824 			       fold_convert (long_integer_type_node, num_bits),
6825 			       fold_convert (long_integer_type_node, num_bits));
6826     }
6827 
6828   cond = fold_build2_loc (input_location, GE_EXPR, logical_type_node, width,
6829 			  num_bits);
6830   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond,
6831 			      build_int_cst (type, 0), tmp);
6832 }
6833 
6834 
6835 /* Circular shift.  AKA rotate or barrel shift.  */
6836 
6837 static void
gfc_conv_intrinsic_ishftc(gfc_se * se,gfc_expr * expr)6838 gfc_conv_intrinsic_ishftc (gfc_se * se, gfc_expr * expr)
6839 {
6840   tree *args;
6841   tree type;
6842   tree tmp;
6843   tree lrot;
6844   tree rrot;
6845   tree zero;
6846   tree nbits;
6847   unsigned int num_args;
6848 
6849   num_args = gfc_intrinsic_argument_list_length (expr);
6850   args = XALLOCAVEC (tree, num_args);
6851 
6852   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
6853 
6854   type = TREE_TYPE (args[0]);
6855   nbits = build_int_cst (long_integer_type_node, TYPE_PRECISION (type));
6856 
6857   if (num_args == 3)
6858     {
6859       /* Use a library function for the 3 parameter version.  */
6860       tree int4type = gfc_get_int_type (4);
6861 
6862       /* We convert the first argument to at least 4 bytes, and
6863 	 convert back afterwards.  This removes the need for library
6864 	 functions for all argument sizes, and function will be
6865 	 aligned to at least 32 bits, so there's no loss.  */
6866       if (expr->ts.kind < 4)
6867 	args[0] = convert (int4type, args[0]);
6868 
6869       /* Convert the SHIFT and SIZE args to INTEGER*4 otherwise we would
6870          need loads of library  functions.  They cannot have values >
6871 	 BIT_SIZE (I) so the conversion is safe.  */
6872       args[1] = convert (int4type, args[1]);
6873       args[2] = convert (int4type, args[2]);
6874 
6875       /* Optionally generate code for runtime argument check.  */
6876       if (gfc_option.rtcheck & GFC_RTCHECK_BITS)
6877 	{
6878 	  tree size = fold_convert (long_integer_type_node, args[2]);
6879 	  tree below = fold_build2_loc (input_location, LE_EXPR,
6880 					logical_type_node, size,
6881 					build_int_cst (TREE_TYPE (args[1]), 0));
6882 	  tree above = fold_build2_loc (input_location, GT_EXPR,
6883 					logical_type_node, size, nbits);
6884 	  tree scond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
6885 					logical_type_node, below, above);
6886 	  gfc_trans_runtime_check (true, false, scond, &se->pre, &expr->where,
6887 				   "SIZE argument (%ld) out of range 1:%ld "
6888 				   "in intrinsic ISHFTC", size, nbits);
6889 	  tree width = fold_convert (long_integer_type_node, args[1]);
6890 	  width = fold_build1_loc (input_location, ABS_EXPR,
6891 				   long_integer_type_node, width);
6892 	  scond = fold_build2_loc (input_location, GT_EXPR,
6893 				   logical_type_node, width, size);
6894 	  gfc_trans_runtime_check (true, false, scond, &se->pre, &expr->where,
6895 				   "SHIFT argument (%ld) out of range -%ld:%ld "
6896 				   "in intrinsic ISHFTC",
6897 				   fold_convert (long_integer_type_node, args[1]),
6898 				   size, size);
6899 	}
6900 
6901       switch (expr->ts.kind)
6902 	{
6903 	case 1:
6904 	case 2:
6905 	case 4:
6906 	  tmp = gfor_fndecl_math_ishftc4;
6907 	  break;
6908 	case 8:
6909 	  tmp = gfor_fndecl_math_ishftc8;
6910 	  break;
6911 	case 16:
6912 	  tmp = gfor_fndecl_math_ishftc16;
6913 	  break;
6914 	default:
6915 	  gcc_unreachable ();
6916 	}
6917       se->expr = build_call_expr_loc (input_location,
6918 				      tmp, 3, args[0], args[1], args[2]);
6919       /* Convert the result back to the original type, if we extended
6920 	 the first argument's width above.  */
6921       if (expr->ts.kind < 4)
6922 	se->expr = convert (type, se->expr);
6923 
6924       return;
6925     }
6926 
6927   /* Evaluate arguments only once.  */
6928   args[0] = gfc_evaluate_now (args[0], &se->pre);
6929   args[1] = gfc_evaluate_now (args[1], &se->pre);
6930 
6931   /* Optionally generate code for runtime argument check.  */
6932   if (gfc_option.rtcheck & GFC_RTCHECK_BITS)
6933     {
6934       tree width = fold_convert (long_integer_type_node, args[1]);
6935       width = fold_build1_loc (input_location, ABS_EXPR,
6936 			       long_integer_type_node, width);
6937       tree outside = fold_build2_loc (input_location, GT_EXPR,
6938 				      logical_type_node, width, nbits);
6939       gfc_trans_runtime_check (true, false, outside, &se->pre, &expr->where,
6940 			       "SHIFT argument (%ld) out of range -%ld:%ld "
6941 			       "in intrinsic ISHFTC",
6942 			       fold_convert (long_integer_type_node, args[1]),
6943 			       nbits, nbits);
6944     }
6945 
6946   /* Rotate left if positive.  */
6947   lrot = fold_build2_loc (input_location, LROTATE_EXPR, type, args[0], args[1]);
6948 
6949   /* Rotate right if negative.  */
6950   tmp = fold_build1_loc (input_location, NEGATE_EXPR, TREE_TYPE (args[1]),
6951 			 args[1]);
6952   rrot = fold_build2_loc (input_location,RROTATE_EXPR, type, args[0], tmp);
6953 
6954   zero = build_int_cst (TREE_TYPE (args[1]), 0);
6955   tmp = fold_build2_loc (input_location, GT_EXPR, logical_type_node, args[1],
6956 			 zero);
6957   rrot = fold_build3_loc (input_location, COND_EXPR, type, tmp, lrot, rrot);
6958 
6959   /* Do nothing if shift == 0.  */
6960   tmp = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, args[1],
6961 			 zero);
6962   se->expr = fold_build3_loc (input_location, COND_EXPR, type, tmp, args[0],
6963 			      rrot);
6964 }
6965 
6966 
6967 /* LEADZ (i) = (i == 0) ? BIT_SIZE (i)
6968 			: __builtin_clz(i) - (BIT_SIZE('int') - BIT_SIZE(i))
6969 
6970    The conditional expression is necessary because the result of LEADZ(0)
6971    is defined, but the result of __builtin_clz(0) is undefined for most
6972    targets.
6973 
6974    For INTEGER kinds smaller than the C 'int' type, we have to subtract the
6975    difference in bit size between the argument of LEADZ and the C int.  */
6976 
6977 static void
gfc_conv_intrinsic_leadz(gfc_se * se,gfc_expr * expr)6978 gfc_conv_intrinsic_leadz (gfc_se * se, gfc_expr * expr)
6979 {
6980   tree arg;
6981   tree arg_type;
6982   tree cond;
6983   tree result_type;
6984   tree leadz;
6985   tree bit_size;
6986   tree tmp;
6987   tree func;
6988   int s, argsize;
6989 
6990   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
6991   argsize = TYPE_PRECISION (TREE_TYPE (arg));
6992 
6993   /* Which variant of __builtin_clz* should we call?  */
6994   if (argsize <= INT_TYPE_SIZE)
6995     {
6996       arg_type = unsigned_type_node;
6997       func = builtin_decl_explicit (BUILT_IN_CLZ);
6998     }
6999   else if (argsize <= LONG_TYPE_SIZE)
7000     {
7001       arg_type = long_unsigned_type_node;
7002       func = builtin_decl_explicit (BUILT_IN_CLZL);
7003     }
7004   else if (argsize <= LONG_LONG_TYPE_SIZE)
7005     {
7006       arg_type = long_long_unsigned_type_node;
7007       func = builtin_decl_explicit (BUILT_IN_CLZLL);
7008     }
7009   else
7010     {
7011       gcc_assert (argsize == 2 * LONG_LONG_TYPE_SIZE);
7012       arg_type = gfc_build_uint_type (argsize);
7013       func = NULL_TREE;
7014     }
7015 
7016   /* Convert the actual argument twice: first, to the unsigned type of the
7017      same size; then, to the proper argument type for the built-in
7018      function.  But the return type is of the default INTEGER kind.  */
7019   arg = fold_convert (gfc_build_uint_type (argsize), arg);
7020   arg = fold_convert (arg_type, arg);
7021   arg = gfc_evaluate_now (arg, &se->pre);
7022   result_type = gfc_get_int_type (gfc_default_integer_kind);
7023 
7024   /* Compute LEADZ for the case i .ne. 0.  */
7025   if (func)
7026     {
7027       s = TYPE_PRECISION (arg_type) - argsize;
7028       tmp = fold_convert (result_type,
7029 			  build_call_expr_loc (input_location, func,
7030 					       1, arg));
7031       leadz = fold_build2_loc (input_location, MINUS_EXPR, result_type,
7032 			       tmp, build_int_cst (result_type, s));
7033     }
7034   else
7035     {
7036       /* We end up here if the argument type is larger than 'long long'.
7037 	 We generate this code:
7038 
7039 	    if (x & (ULL_MAX << ULL_SIZE) != 0)
7040 	      return clzll ((unsigned long long) (x >> ULLSIZE));
7041 	    else
7042 	      return ULL_SIZE + clzll ((unsigned long long) x);
7043 	 where ULL_MAX is the largest value that a ULL_MAX can hold
7044 	 (0xFFFFFFFFFFFFFFFF for a 64-bit long long type), and ULLSIZE
7045 	 is the bit-size of the long long type (64 in this example).  */
7046       tree ullsize, ullmax, tmp1, tmp2, btmp;
7047 
7048       ullsize = build_int_cst (result_type, LONG_LONG_TYPE_SIZE);
7049       ullmax = fold_build1_loc (input_location, BIT_NOT_EXPR,
7050 				long_long_unsigned_type_node,
7051 				build_int_cst (long_long_unsigned_type_node,
7052 					       0));
7053 
7054       cond = fold_build2_loc (input_location, LSHIFT_EXPR, arg_type,
7055 			      fold_convert (arg_type, ullmax), ullsize);
7056       cond = fold_build2_loc (input_location, BIT_AND_EXPR, arg_type,
7057 			      arg, cond);
7058       cond = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
7059 			      cond, build_int_cst (arg_type, 0));
7060 
7061       tmp1 = fold_build2_loc (input_location, RSHIFT_EXPR, arg_type,
7062 			      arg, ullsize);
7063       tmp1 = fold_convert (long_long_unsigned_type_node, tmp1);
7064       btmp = builtin_decl_explicit (BUILT_IN_CLZLL);
7065       tmp1 = fold_convert (result_type,
7066 			   build_call_expr_loc (input_location, btmp, 1, tmp1));
7067 
7068       tmp2 = fold_convert (long_long_unsigned_type_node, arg);
7069       btmp = builtin_decl_explicit (BUILT_IN_CLZLL);
7070       tmp2 = fold_convert (result_type,
7071 			   build_call_expr_loc (input_location, btmp, 1, tmp2));
7072       tmp2 = fold_build2_loc (input_location, PLUS_EXPR, result_type,
7073 			      tmp2, ullsize);
7074 
7075       leadz = fold_build3_loc (input_location, COND_EXPR, result_type,
7076 			       cond, tmp1, tmp2);
7077     }
7078 
7079   /* Build BIT_SIZE.  */
7080   bit_size = build_int_cst (result_type, argsize);
7081 
7082   cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
7083 			  arg, build_int_cst (arg_type, 0));
7084   se->expr = fold_build3_loc (input_location, COND_EXPR, result_type, cond,
7085 			      bit_size, leadz);
7086 }
7087 
7088 
7089 /* TRAILZ(i) = (i == 0) ? BIT_SIZE (i) : __builtin_ctz(i)
7090 
7091    The conditional expression is necessary because the result of TRAILZ(0)
7092    is defined, but the result of __builtin_ctz(0) is undefined for most
7093    targets.  */
7094 
7095 static void
gfc_conv_intrinsic_trailz(gfc_se * se,gfc_expr * expr)7096 gfc_conv_intrinsic_trailz (gfc_se * se, gfc_expr *expr)
7097 {
7098   tree arg;
7099   tree arg_type;
7100   tree cond;
7101   tree result_type;
7102   tree trailz;
7103   tree bit_size;
7104   tree func;
7105   int argsize;
7106 
7107   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
7108   argsize = TYPE_PRECISION (TREE_TYPE (arg));
7109 
7110   /* Which variant of __builtin_ctz* should we call?  */
7111   if (argsize <= INT_TYPE_SIZE)
7112     {
7113       arg_type = unsigned_type_node;
7114       func = builtin_decl_explicit (BUILT_IN_CTZ);
7115     }
7116   else if (argsize <= LONG_TYPE_SIZE)
7117     {
7118       arg_type = long_unsigned_type_node;
7119       func = builtin_decl_explicit (BUILT_IN_CTZL);
7120     }
7121   else if (argsize <= LONG_LONG_TYPE_SIZE)
7122     {
7123       arg_type = long_long_unsigned_type_node;
7124       func = builtin_decl_explicit (BUILT_IN_CTZLL);
7125     }
7126   else
7127     {
7128       gcc_assert (argsize == 2 * LONG_LONG_TYPE_SIZE);
7129       arg_type = gfc_build_uint_type (argsize);
7130       func = NULL_TREE;
7131     }
7132 
7133   /* Convert the actual argument twice: first, to the unsigned type of the
7134      same size; then, to the proper argument type for the built-in
7135      function.  But the return type is of the default INTEGER kind.  */
7136   arg = fold_convert (gfc_build_uint_type (argsize), arg);
7137   arg = fold_convert (arg_type, arg);
7138   arg = gfc_evaluate_now (arg, &se->pre);
7139   result_type = gfc_get_int_type (gfc_default_integer_kind);
7140 
7141   /* Compute TRAILZ for the case i .ne. 0.  */
7142   if (func)
7143     trailz = fold_convert (result_type, build_call_expr_loc (input_location,
7144 							     func, 1, arg));
7145   else
7146     {
7147       /* We end up here if the argument type is larger than 'long long'.
7148 	 We generate this code:
7149 
7150 	    if ((x & ULL_MAX) == 0)
7151 	      return ULL_SIZE + ctzll ((unsigned long long) (x >> ULLSIZE));
7152 	    else
7153 	      return ctzll ((unsigned long long) x);
7154 
7155 	 where ULL_MAX is the largest value that a ULL_MAX can hold
7156 	 (0xFFFFFFFFFFFFFFFF for a 64-bit long long type), and ULLSIZE
7157 	 is the bit-size of the long long type (64 in this example).  */
7158       tree ullsize, ullmax, tmp1, tmp2, btmp;
7159 
7160       ullsize = build_int_cst (result_type, LONG_LONG_TYPE_SIZE);
7161       ullmax = fold_build1_loc (input_location, BIT_NOT_EXPR,
7162 				long_long_unsigned_type_node,
7163 				build_int_cst (long_long_unsigned_type_node, 0));
7164 
7165       cond = fold_build2_loc (input_location, BIT_AND_EXPR, arg_type, arg,
7166 			      fold_convert (arg_type, ullmax));
7167       cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, cond,
7168 			      build_int_cst (arg_type, 0));
7169 
7170       tmp1 = fold_build2_loc (input_location, RSHIFT_EXPR, arg_type,
7171 			      arg, ullsize);
7172       tmp1 = fold_convert (long_long_unsigned_type_node, tmp1);
7173       btmp = builtin_decl_explicit (BUILT_IN_CTZLL);
7174       tmp1 = fold_convert (result_type,
7175 			   build_call_expr_loc (input_location, btmp, 1, tmp1));
7176       tmp1 = fold_build2_loc (input_location, PLUS_EXPR, result_type,
7177 			      tmp1, ullsize);
7178 
7179       tmp2 = fold_convert (long_long_unsigned_type_node, arg);
7180       btmp = builtin_decl_explicit (BUILT_IN_CTZLL);
7181       tmp2 = fold_convert (result_type,
7182 			   build_call_expr_loc (input_location, btmp, 1, tmp2));
7183 
7184       trailz = fold_build3_loc (input_location, COND_EXPR, result_type,
7185 				cond, tmp1, tmp2);
7186     }
7187 
7188   /* Build BIT_SIZE.  */
7189   bit_size = build_int_cst (result_type, argsize);
7190 
7191   cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
7192 			  arg, build_int_cst (arg_type, 0));
7193   se->expr = fold_build3_loc (input_location, COND_EXPR, result_type, cond,
7194 			      bit_size, trailz);
7195 }
7196 
7197 /* Using __builtin_popcount for POPCNT and __builtin_parity for POPPAR;
7198    for types larger than "long long", we call the long long built-in for
7199    the lower and higher bits and combine the result.  */
7200 
7201 static void
gfc_conv_intrinsic_popcnt_poppar(gfc_se * se,gfc_expr * expr,int parity)7202 gfc_conv_intrinsic_popcnt_poppar (gfc_se * se, gfc_expr *expr, int parity)
7203 {
7204   tree arg;
7205   tree arg_type;
7206   tree result_type;
7207   tree func;
7208   int argsize;
7209 
7210   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
7211   argsize = TYPE_PRECISION (TREE_TYPE (arg));
7212   result_type = gfc_get_int_type (gfc_default_integer_kind);
7213 
7214   /* Which variant of the builtin should we call?  */
7215   if (argsize <= INT_TYPE_SIZE)
7216     {
7217       arg_type = unsigned_type_node;
7218       func = builtin_decl_explicit (parity
7219 				    ? BUILT_IN_PARITY
7220 				    : BUILT_IN_POPCOUNT);
7221     }
7222   else if (argsize <= LONG_TYPE_SIZE)
7223     {
7224       arg_type = long_unsigned_type_node;
7225       func = builtin_decl_explicit (parity
7226 				    ? BUILT_IN_PARITYL
7227 				    : BUILT_IN_POPCOUNTL);
7228     }
7229   else if (argsize <= LONG_LONG_TYPE_SIZE)
7230     {
7231       arg_type = long_long_unsigned_type_node;
7232       func = builtin_decl_explicit (parity
7233 				    ? BUILT_IN_PARITYLL
7234 				    : BUILT_IN_POPCOUNTLL);
7235     }
7236   else
7237     {
7238       /* Our argument type is larger than 'long long', which mean none
7239 	 of the POPCOUNT builtins covers it.  We thus call the 'long long'
7240 	 variant multiple times, and add the results.  */
7241       tree utype, arg2, call1, call2;
7242 
7243       /* For now, we only cover the case where argsize is twice as large
7244 	 as 'long long'.  */
7245       gcc_assert (argsize == 2 * LONG_LONG_TYPE_SIZE);
7246 
7247       func = builtin_decl_explicit (parity
7248 				    ? BUILT_IN_PARITYLL
7249 				    : BUILT_IN_POPCOUNTLL);
7250 
7251       /* Convert it to an integer, and store into a variable.  */
7252       utype = gfc_build_uint_type (argsize);
7253       arg = fold_convert (utype, arg);
7254       arg = gfc_evaluate_now (arg, &se->pre);
7255 
7256       /* Call the builtin twice.  */
7257       call1 = build_call_expr_loc (input_location, func, 1,
7258 				   fold_convert (long_long_unsigned_type_node,
7259 						 arg));
7260 
7261       arg2 = fold_build2_loc (input_location, RSHIFT_EXPR, utype, arg,
7262 			      build_int_cst (utype, LONG_LONG_TYPE_SIZE));
7263       call2 = build_call_expr_loc (input_location, func, 1,
7264 				   fold_convert (long_long_unsigned_type_node,
7265 						 arg2));
7266 
7267       /* Combine the results.  */
7268       if (parity)
7269 	se->expr = fold_build2_loc (input_location, BIT_XOR_EXPR,
7270 				    integer_type_node, call1, call2);
7271       else
7272 	se->expr = fold_build2_loc (input_location, PLUS_EXPR,
7273 				    integer_type_node, call1, call2);
7274 
7275       se->expr = convert (result_type, se->expr);
7276       return;
7277     }
7278 
7279   /* Convert the actual argument twice: first, to the unsigned type of the
7280      same size; then, to the proper argument type for the built-in
7281      function.  */
7282   arg = fold_convert (gfc_build_uint_type (argsize), arg);
7283   arg = fold_convert (arg_type, arg);
7284 
7285   se->expr = fold_convert (result_type,
7286 			   build_call_expr_loc (input_location, func, 1, arg));
7287 }
7288 
7289 
7290 /* Process an intrinsic with unspecified argument-types that has an optional
7291    argument (which could be of type character), e.g. EOSHIFT.  For those, we
7292    need to append the string length of the optional argument if it is not
7293    present and the type is really character.
7294    primary specifies the position (starting at 1) of the non-optional argument
7295    specifying the type and optional gives the position of the optional
7296    argument in the arglist.  */
7297 
7298 static void
conv_generic_with_optional_char_arg(gfc_se * se,gfc_expr * expr,unsigned primary,unsigned optional)7299 conv_generic_with_optional_char_arg (gfc_se* se, gfc_expr* expr,
7300 				     unsigned primary, unsigned optional)
7301 {
7302   gfc_actual_arglist* prim_arg;
7303   gfc_actual_arglist* opt_arg;
7304   unsigned cur_pos;
7305   gfc_actual_arglist* arg;
7306   gfc_symbol* sym;
7307   vec<tree, va_gc> *append_args;
7308 
7309   /* Find the two arguments given as position.  */
7310   cur_pos = 0;
7311   prim_arg = NULL;
7312   opt_arg = NULL;
7313   for (arg = expr->value.function.actual; arg; arg = arg->next)
7314     {
7315       ++cur_pos;
7316 
7317       if (cur_pos == primary)
7318 	prim_arg = arg;
7319       if (cur_pos == optional)
7320 	opt_arg = arg;
7321 
7322       if (cur_pos >= primary && cur_pos >= optional)
7323 	break;
7324     }
7325   gcc_assert (prim_arg);
7326   gcc_assert (prim_arg->expr);
7327   gcc_assert (opt_arg);
7328 
7329   /* If we do have type CHARACTER and the optional argument is really absent,
7330      append a dummy 0 as string length.  */
7331   append_args = NULL;
7332   if (prim_arg->expr->ts.type == BT_CHARACTER && !opt_arg->expr)
7333     {
7334       tree dummy;
7335 
7336       dummy = build_int_cst (gfc_charlen_type_node, 0);
7337       vec_alloc (append_args, 1);
7338       append_args->quick_push (dummy);
7339     }
7340 
7341   /* Build the call itself.  */
7342   gcc_assert (!se->ignore_optional);
7343   sym = gfc_get_symbol_for_expr (expr, false);
7344   gfc_conv_procedure_call (se, sym, expr->value.function.actual, expr,
7345 			  append_args);
7346   gfc_free_symbol (sym);
7347 }
7348 
7349 /* The length of a character string.  */
7350 static void
gfc_conv_intrinsic_len(gfc_se * se,gfc_expr * expr)7351 gfc_conv_intrinsic_len (gfc_se * se, gfc_expr * expr)
7352 {
7353   tree len;
7354   tree type;
7355   tree decl;
7356   gfc_symbol *sym;
7357   gfc_se argse;
7358   gfc_expr *arg;
7359 
7360   gcc_assert (!se->ss);
7361 
7362   arg = expr->value.function.actual->expr;
7363 
7364   type = gfc_typenode_for_spec (&expr->ts);
7365   switch (arg->expr_type)
7366     {
7367     case EXPR_CONSTANT:
7368       len = build_int_cst (gfc_charlen_type_node, arg->value.character.length);
7369       break;
7370 
7371     case EXPR_ARRAY:
7372       /* Obtain the string length from the function used by
7373          trans-array.cc(gfc_trans_array_constructor).  */
7374       len = NULL_TREE;
7375       get_array_ctor_strlen (&se->pre, arg->value.constructor, &len);
7376       break;
7377 
7378     case EXPR_VARIABLE:
7379       if (arg->ref == NULL
7380 	    || (arg->ref->next == NULL && arg->ref->type == REF_ARRAY))
7381 	{
7382 	  /* This doesn't catch all cases.
7383 	     See http://gcc.gnu.org/ml/fortran/2004-06/msg00165.html
7384 	     and the surrounding thread.  */
7385 	  sym = arg->symtree->n.sym;
7386 	  decl = gfc_get_symbol_decl (sym);
7387 	  if (decl == current_function_decl && sym->attr.function
7388 		&& (sym->result == sym))
7389 	    decl = gfc_get_fake_result_decl (sym, 0);
7390 
7391 	  len = sym->ts.u.cl->backend_decl;
7392 	  gcc_assert (len);
7393 	  break;
7394 	}
7395 
7396       /* Fall through.  */
7397 
7398     default:
7399       gfc_init_se (&argse, se);
7400       if (arg->rank == 0)
7401 	gfc_conv_expr (&argse, arg);
7402       else
7403 	gfc_conv_expr_descriptor (&argse, arg);
7404       gfc_add_block_to_block (&se->pre, &argse.pre);
7405       gfc_add_block_to_block (&se->post, &argse.post);
7406       len = argse.string_length;
7407       break;
7408     }
7409   se->expr = convert (type, len);
7410 }
7411 
7412 /* The length of a character string not including trailing blanks.  */
7413 static void
gfc_conv_intrinsic_len_trim(gfc_se * se,gfc_expr * expr)7414 gfc_conv_intrinsic_len_trim (gfc_se * se, gfc_expr * expr)
7415 {
7416   int kind = expr->value.function.actual->expr->ts.kind;
7417   tree args[2], type, fndecl;
7418 
7419   gfc_conv_intrinsic_function_args (se, expr, args, 2);
7420   type = gfc_typenode_for_spec (&expr->ts);
7421 
7422   if (kind == 1)
7423     fndecl = gfor_fndecl_string_len_trim;
7424   else if (kind == 4)
7425     fndecl = gfor_fndecl_string_len_trim_char4;
7426   else
7427     gcc_unreachable ();
7428 
7429   se->expr = build_call_expr_loc (input_location,
7430 			      fndecl, 2, args[0], args[1]);
7431   se->expr = convert (type, se->expr);
7432 }
7433 
7434 
7435 /* Returns the starting position of a substring within a string.  */
7436 
7437 static void
gfc_conv_intrinsic_index_scan_verify(gfc_se * se,gfc_expr * expr,tree function)7438 gfc_conv_intrinsic_index_scan_verify (gfc_se * se, gfc_expr * expr,
7439 				      tree function)
7440 {
7441   tree logical4_type_node = gfc_get_logical_type (4);
7442   tree type;
7443   tree fndecl;
7444   tree *args;
7445   unsigned int num_args;
7446 
7447   args = XALLOCAVEC (tree, 5);
7448 
7449   /* Get number of arguments; characters count double due to the
7450      string length argument. Kind= is not passed to the library
7451      and thus ignored.  */
7452   if (expr->value.function.actual->next->next->expr == NULL)
7453     num_args = 4;
7454   else
7455     num_args = 5;
7456 
7457   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
7458   type = gfc_typenode_for_spec (&expr->ts);
7459 
7460   if (num_args == 4)
7461     args[4] = build_int_cst (logical4_type_node, 0);
7462   else
7463     args[4] = convert (logical4_type_node, args[4]);
7464 
7465   fndecl = build_addr (function);
7466   se->expr = build_call_array_loc (input_location,
7467 			       TREE_TYPE (TREE_TYPE (function)), fndecl,
7468 			       5, args);
7469   se->expr = convert (type, se->expr);
7470 
7471 }
7472 
7473 /* The ascii value for a single character.  */
7474 static void
gfc_conv_intrinsic_ichar(gfc_se * se,gfc_expr * expr)7475 gfc_conv_intrinsic_ichar (gfc_se * se, gfc_expr * expr)
7476 {
7477   tree args[3], type, pchartype;
7478   int nargs;
7479 
7480   nargs = gfc_intrinsic_argument_list_length (expr);
7481   gfc_conv_intrinsic_function_args (se, expr, args, nargs);
7482   gcc_assert (POINTER_TYPE_P (TREE_TYPE (args[1])));
7483   pchartype = gfc_get_pchar_type (expr->value.function.actual->expr->ts.kind);
7484   args[1] = fold_build1_loc (input_location, NOP_EXPR, pchartype, args[1]);
7485   type = gfc_typenode_for_spec (&expr->ts);
7486 
7487   se->expr = build_fold_indirect_ref_loc (input_location,
7488 				      args[1]);
7489   se->expr = convert (type, se->expr);
7490 }
7491 
7492 
7493 /* Intrinsic ISNAN calls __builtin_isnan.  */
7494 
7495 static void
gfc_conv_intrinsic_isnan(gfc_se * se,gfc_expr * expr)7496 gfc_conv_intrinsic_isnan (gfc_se * se, gfc_expr * expr)
7497 {
7498   tree arg;
7499 
7500   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
7501   se->expr = build_call_expr_loc (input_location,
7502 				  builtin_decl_explicit (BUILT_IN_ISNAN),
7503 				  1, arg);
7504   STRIP_TYPE_NOPS (se->expr);
7505   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), se->expr);
7506 }
7507 
7508 
7509 /* Intrinsics IS_IOSTAT_END and IS_IOSTAT_EOR just need to compare
7510    their argument against a constant integer value.  */
7511 
7512 static void
gfc_conv_has_intvalue(gfc_se * se,gfc_expr * expr,const int value)7513 gfc_conv_has_intvalue (gfc_se * se, gfc_expr * expr, const int value)
7514 {
7515   tree arg;
7516 
7517   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
7518   se->expr = fold_build2_loc (input_location, EQ_EXPR,
7519 			      gfc_typenode_for_spec (&expr->ts),
7520 			      arg, build_int_cst (TREE_TYPE (arg), value));
7521 }
7522 
7523 
7524 
7525 /* MERGE (tsource, fsource, mask) = mask ? tsource : fsource.  */
7526 
7527 static void
gfc_conv_intrinsic_merge(gfc_se * se,gfc_expr * expr)7528 gfc_conv_intrinsic_merge (gfc_se * se, gfc_expr * expr)
7529 {
7530   tree tsource;
7531   tree fsource;
7532   tree mask;
7533   tree type;
7534   tree len, len2;
7535   tree *args;
7536   unsigned int num_args;
7537 
7538   num_args = gfc_intrinsic_argument_list_length (expr);
7539   args = XALLOCAVEC (tree, num_args);
7540 
7541   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
7542   if (expr->ts.type != BT_CHARACTER)
7543     {
7544       tsource = args[0];
7545       fsource = args[1];
7546       mask = args[2];
7547     }
7548   else
7549     {
7550       /* We do the same as in the non-character case, but the argument
7551 	 list is different because of the string length arguments. We
7552 	 also have to set the string length for the result.  */
7553       len = args[0];
7554       tsource = args[1];
7555       len2 = args[2];
7556       fsource = args[3];
7557       mask = args[4];
7558 
7559       gfc_trans_same_strlen_check ("MERGE intrinsic", &expr->where, len, len2,
7560 				   &se->pre);
7561       se->string_length = len;
7562     }
7563   type = TREE_TYPE (tsource);
7564   se->expr = fold_build3_loc (input_location, COND_EXPR, type, mask, tsource,
7565 			      fold_convert (type, fsource));
7566 }
7567 
7568 
7569 /* MERGE_BITS (I, J, MASK) = (I & MASK) | (I & (~MASK)).  */
7570 
7571 static void
gfc_conv_intrinsic_merge_bits(gfc_se * se,gfc_expr * expr)7572 gfc_conv_intrinsic_merge_bits (gfc_se * se, gfc_expr * expr)
7573 {
7574   tree args[3], mask, type;
7575 
7576   gfc_conv_intrinsic_function_args (se, expr, args, 3);
7577   mask = gfc_evaluate_now (args[2], &se->pre);
7578 
7579   type = TREE_TYPE (args[0]);
7580   gcc_assert (TREE_TYPE (args[1]) == type);
7581   gcc_assert (TREE_TYPE (mask) == type);
7582 
7583   args[0] = fold_build2_loc (input_location, BIT_AND_EXPR, type, args[0], mask);
7584   args[1] = fold_build2_loc (input_location, BIT_AND_EXPR, type, args[1],
7585 			     fold_build1_loc (input_location, BIT_NOT_EXPR,
7586 					      type, mask));
7587   se->expr = fold_build2_loc (input_location, BIT_IOR_EXPR, type,
7588 			      args[0], args[1]);
7589 }
7590 
7591 
7592 /* MASKL(n)  =  n == 0 ? 0 : (~0) << (BIT_SIZE - n)
7593    MASKR(n)  =  n == BIT_SIZE ? ~0 : ~((~0) << n)  */
7594 
7595 static void
gfc_conv_intrinsic_mask(gfc_se * se,gfc_expr * expr,int left)7596 gfc_conv_intrinsic_mask (gfc_se * se, gfc_expr * expr, int left)
7597 {
7598   tree arg, allones, type, utype, res, cond, bitsize;
7599   int i;
7600 
7601   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
7602   arg = gfc_evaluate_now (arg, &se->pre);
7603 
7604   type = gfc_get_int_type (expr->ts.kind);
7605   utype = unsigned_type_for (type);
7606 
7607   i = gfc_validate_kind (BT_INTEGER, expr->ts.kind, false);
7608   bitsize = build_int_cst (TREE_TYPE (arg), gfc_integer_kinds[i].bit_size);
7609 
7610   allones = fold_build1_loc (input_location, BIT_NOT_EXPR, utype,
7611 			     build_int_cst (utype, 0));
7612 
7613   if (left)
7614     {
7615       /* Left-justified mask.  */
7616       res = fold_build2_loc (input_location, MINUS_EXPR, TREE_TYPE (arg),
7617 			     bitsize, arg);
7618       res = fold_build2_loc (input_location, LSHIFT_EXPR, utype, allones,
7619 			     fold_convert (utype, res));
7620 
7621       /* Special case arg == 0, because SHIFT_EXPR wants a shift strictly
7622 	 smaller than type width.  */
7623       cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, arg,
7624 			      build_int_cst (TREE_TYPE (arg), 0));
7625       res = fold_build3_loc (input_location, COND_EXPR, utype, cond,
7626 			     build_int_cst (utype, 0), res);
7627     }
7628   else
7629     {
7630       /* Right-justified mask.  */
7631       res = fold_build2_loc (input_location, LSHIFT_EXPR, utype, allones,
7632 			     fold_convert (utype, arg));
7633       res = fold_build1_loc (input_location, BIT_NOT_EXPR, utype, res);
7634 
7635       /* Special case agr == bit_size, because SHIFT_EXPR wants a shift
7636 	 strictly smaller than type width.  */
7637       cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
7638 			      arg, bitsize);
7639       res = fold_build3_loc (input_location, COND_EXPR, utype,
7640 			     cond, allones, res);
7641     }
7642 
7643   se->expr = fold_convert (type, res);
7644 }
7645 
7646 
7647 /* FRACTION (s) is translated into:
7648      isfinite (s) ? frexp (s, &dummy_int) : NaN  */
7649 static void
gfc_conv_intrinsic_fraction(gfc_se * se,gfc_expr * expr)7650 gfc_conv_intrinsic_fraction (gfc_se * se, gfc_expr * expr)
7651 {
7652   tree arg, type, tmp, res, frexp, cond;
7653 
7654   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
7655 
7656   type = gfc_typenode_for_spec (&expr->ts);
7657   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
7658   arg = gfc_evaluate_now (arg, &se->pre);
7659 
7660   cond = build_call_expr_loc (input_location,
7661 			      builtin_decl_explicit (BUILT_IN_ISFINITE),
7662 			      1, arg);
7663 
7664   tmp = gfc_create_var (integer_type_node, NULL);
7665   res = build_call_expr_loc (input_location, frexp, 2,
7666 			     fold_convert (type, arg),
7667 			     gfc_build_addr_expr (NULL_TREE, tmp));
7668   res = fold_convert (type, res);
7669 
7670   se->expr = fold_build3_loc (input_location, COND_EXPR, type,
7671 			      cond, res, gfc_build_nan (type, ""));
7672 }
7673 
7674 
7675 /* NEAREST (s, dir) is translated into
7676      tmp = copysign (HUGE_VAL, dir);
7677      return nextafter (s, tmp);
7678  */
7679 static void
gfc_conv_intrinsic_nearest(gfc_se * se,gfc_expr * expr)7680 gfc_conv_intrinsic_nearest (gfc_se * se, gfc_expr * expr)
7681 {
7682   tree args[2], type, tmp, nextafter, copysign, huge_val;
7683 
7684   nextafter = gfc_builtin_decl_for_float_kind (BUILT_IN_NEXTAFTER, expr->ts.kind);
7685   copysign = gfc_builtin_decl_for_float_kind (BUILT_IN_COPYSIGN, expr->ts.kind);
7686 
7687   type = gfc_typenode_for_spec (&expr->ts);
7688   gfc_conv_intrinsic_function_args (se, expr, args, 2);
7689 
7690   huge_val = gfc_build_inf_or_huge (type, expr->ts.kind);
7691   tmp = build_call_expr_loc (input_location, copysign, 2, huge_val,
7692 			     fold_convert (type, args[1]));
7693   se->expr = build_call_expr_loc (input_location, nextafter, 2,
7694 				  fold_convert (type, args[0]), tmp);
7695   se->expr = fold_convert (type, se->expr);
7696 }
7697 
7698 
7699 /* SPACING (s) is translated into
7700     int e;
7701     if (!isfinite (s))
7702       res = NaN;
7703     else if (s == 0)
7704       res = tiny;
7705     else
7706     {
7707       frexp (s, &e);
7708       e = e - prec;
7709       e = MAX_EXPR (e, emin);
7710       res = scalbn (1., e);
7711     }
7712     return res;
7713 
7714  where prec is the precision of s, gfc_real_kinds[k].digits,
7715        emin is min_exponent - 1, gfc_real_kinds[k].min_exponent - 1,
7716    and tiny is tiny(s), gfc_real_kinds[k].tiny.  */
7717 
7718 static void
gfc_conv_intrinsic_spacing(gfc_se * se,gfc_expr * expr)7719 gfc_conv_intrinsic_spacing (gfc_se * se, gfc_expr * expr)
7720 {
7721   tree arg, type, prec, emin, tiny, res, e;
7722   tree cond, nan, tmp, frexp, scalbn;
7723   int k;
7724   stmtblock_t block;
7725 
7726   k = gfc_validate_kind (BT_REAL, expr->ts.kind, false);
7727   prec = build_int_cst (integer_type_node, gfc_real_kinds[k].digits);
7728   emin = build_int_cst (integer_type_node, gfc_real_kinds[k].min_exponent - 1);
7729   tiny = gfc_conv_mpfr_to_tree (gfc_real_kinds[k].tiny, expr->ts.kind, 0);
7730 
7731   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
7732   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
7733 
7734   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
7735   arg = gfc_evaluate_now (arg, &se->pre);
7736 
7737   type = gfc_typenode_for_spec (&expr->ts);
7738   e = gfc_create_var (integer_type_node, NULL);
7739   res = gfc_create_var (type, NULL);
7740 
7741 
7742   /* Build the block for s /= 0.  */
7743   gfc_start_block (&block);
7744   tmp = build_call_expr_loc (input_location, frexp, 2, arg,
7745 			     gfc_build_addr_expr (NULL_TREE, e));
7746   gfc_add_expr_to_block (&block, tmp);
7747 
7748   tmp = fold_build2_loc (input_location, MINUS_EXPR, integer_type_node, e,
7749 			 prec);
7750   gfc_add_modify (&block, e, fold_build2_loc (input_location, MAX_EXPR,
7751 					      integer_type_node, tmp, emin));
7752 
7753   tmp = build_call_expr_loc (input_location, scalbn, 2,
7754 			 build_real_from_int_cst (type, integer_one_node), e);
7755   gfc_add_modify (&block, res, tmp);
7756 
7757   /* Finish by building the IF statement for value zero.  */
7758   cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, arg,
7759 			  build_real_from_int_cst (type, integer_zero_node));
7760   tmp = build3_v (COND_EXPR, cond, build2_v (MODIFY_EXPR, res, tiny),
7761 		  gfc_finish_block (&block));
7762 
7763   /* And deal with infinities and NaNs.  */
7764   cond = build_call_expr_loc (input_location,
7765 			      builtin_decl_explicit (BUILT_IN_ISFINITE),
7766 			      1, arg);
7767   nan = gfc_build_nan (type, "");
7768   tmp = build3_v (COND_EXPR, cond, tmp, build2_v (MODIFY_EXPR, res, nan));
7769 
7770   gfc_add_expr_to_block (&se->pre, tmp);
7771   se->expr = res;
7772 }
7773 
7774 
7775 /* RRSPACING (s) is translated into
7776       int e;
7777       real x;
7778       x = fabs (s);
7779       if (isfinite (x))
7780       {
7781 	if (x != 0)
7782 	{
7783 	  frexp (s, &e);
7784 	  x = scalbn (x, precision - e);
7785 	}
7786       }
7787       else
7788         x = NaN;
7789       return x;
7790 
7791  where precision is gfc_real_kinds[k].digits.  */
7792 
7793 static void
gfc_conv_intrinsic_rrspacing(gfc_se * se,gfc_expr * expr)7794 gfc_conv_intrinsic_rrspacing (gfc_se * se, gfc_expr * expr)
7795 {
7796   tree arg, type, e, x, cond, nan, stmt, tmp, frexp, scalbn, fabs;
7797   int prec, k;
7798   stmtblock_t block;
7799 
7800   k = gfc_validate_kind (BT_REAL, expr->ts.kind, false);
7801   prec = gfc_real_kinds[k].digits;
7802 
7803   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
7804   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
7805   fabs = gfc_builtin_decl_for_float_kind (BUILT_IN_FABS, expr->ts.kind);
7806 
7807   type = gfc_typenode_for_spec (&expr->ts);
7808   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
7809   arg = gfc_evaluate_now (arg, &se->pre);
7810 
7811   e = gfc_create_var (integer_type_node, NULL);
7812   x = gfc_create_var (type, NULL);
7813   gfc_add_modify (&se->pre, x,
7814 		  build_call_expr_loc (input_location, fabs, 1, arg));
7815 
7816 
7817   gfc_start_block (&block);
7818   tmp = build_call_expr_loc (input_location, frexp, 2, arg,
7819 			     gfc_build_addr_expr (NULL_TREE, e));
7820   gfc_add_expr_to_block (&block, tmp);
7821 
7822   tmp = fold_build2_loc (input_location, MINUS_EXPR, integer_type_node,
7823 			 build_int_cst (integer_type_node, prec), e);
7824   tmp = build_call_expr_loc (input_location, scalbn, 2, x, tmp);
7825   gfc_add_modify (&block, x, tmp);
7826   stmt = gfc_finish_block (&block);
7827 
7828   /* if (x != 0) */
7829   cond = fold_build2_loc (input_location, NE_EXPR, logical_type_node, x,
7830 			  build_real_from_int_cst (type, integer_zero_node));
7831   tmp = build3_v (COND_EXPR, cond, stmt, build_empty_stmt (input_location));
7832 
7833   /* And deal with infinities and NaNs.  */
7834   cond = build_call_expr_loc (input_location,
7835 			      builtin_decl_explicit (BUILT_IN_ISFINITE),
7836 			      1, x);
7837   nan = gfc_build_nan (type, "");
7838   tmp = build3_v (COND_EXPR, cond, tmp, build2_v (MODIFY_EXPR, x, nan));
7839 
7840   gfc_add_expr_to_block (&se->pre, tmp);
7841   se->expr = fold_convert (type, x);
7842 }
7843 
7844 
7845 /* SCALE (s, i) is translated into scalbn (s, i).  */
7846 static void
gfc_conv_intrinsic_scale(gfc_se * se,gfc_expr * expr)7847 gfc_conv_intrinsic_scale (gfc_se * se, gfc_expr * expr)
7848 {
7849   tree args[2], type, scalbn;
7850 
7851   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
7852 
7853   type = gfc_typenode_for_spec (&expr->ts);
7854   gfc_conv_intrinsic_function_args (se, expr, args, 2);
7855   se->expr = build_call_expr_loc (input_location, scalbn, 2,
7856 				  fold_convert (type, args[0]),
7857 				  fold_convert (integer_type_node, args[1]));
7858   se->expr = fold_convert (type, se->expr);
7859 }
7860 
7861 
7862 /* SET_EXPONENT (s, i) is translated into
7863    isfinite(s) ? scalbn (frexp (s, &dummy_int), i) : NaN  */
7864 static void
gfc_conv_intrinsic_set_exponent(gfc_se * se,gfc_expr * expr)7865 gfc_conv_intrinsic_set_exponent (gfc_se * se, gfc_expr * expr)
7866 {
7867   tree args[2], type, tmp, frexp, scalbn, cond, nan, res;
7868 
7869   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
7870   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
7871 
7872   type = gfc_typenode_for_spec (&expr->ts);
7873   gfc_conv_intrinsic_function_args (se, expr, args, 2);
7874   args[0] = gfc_evaluate_now (args[0], &se->pre);
7875 
7876   tmp = gfc_create_var (integer_type_node, NULL);
7877   tmp = build_call_expr_loc (input_location, frexp, 2,
7878 			     fold_convert (type, args[0]),
7879 			     gfc_build_addr_expr (NULL_TREE, tmp));
7880   res = build_call_expr_loc (input_location, scalbn, 2, tmp,
7881 			     fold_convert (integer_type_node, args[1]));
7882   res = fold_convert (type, res);
7883 
7884   /* Call to isfinite */
7885   cond = build_call_expr_loc (input_location,
7886 			      builtin_decl_explicit (BUILT_IN_ISFINITE),
7887 			      1, args[0]);
7888   nan = gfc_build_nan (type, "");
7889 
7890   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond,
7891 			      res, nan);
7892 }
7893 
7894 
7895 static void
gfc_conv_intrinsic_size(gfc_se * se,gfc_expr * expr)7896 gfc_conv_intrinsic_size (gfc_se * se, gfc_expr * expr)
7897 {
7898   gfc_actual_arglist *actual;
7899   tree arg1;
7900   tree type;
7901   tree size;
7902   gfc_se argse;
7903   gfc_expr *e;
7904   gfc_symbol *sym = NULL;
7905 
7906   gfc_init_se (&argse, NULL);
7907   actual = expr->value.function.actual;
7908 
7909   if (actual->expr->ts.type == BT_CLASS)
7910     gfc_add_class_array_ref (actual->expr);
7911 
7912   e = actual->expr;
7913 
7914   /* These are emerging from the interface mapping, when a class valued
7915      function appears as the rhs in a realloc on assign statement, where
7916      the size of the result is that of one of the actual arguments.  */
7917   if (e->expr_type == EXPR_VARIABLE
7918       && e->symtree->n.sym->ns == NULL /* This is distinctive!  */
7919       && e->symtree->n.sym->ts.type == BT_CLASS
7920       && e->ref && e->ref->type == REF_COMPONENT
7921       && strcmp (e->ref->u.c.component->name, "_data") == 0)
7922     sym = e->symtree->n.sym;
7923 
7924   if ((gfc_option.rtcheck & GFC_RTCHECK_POINTER)
7925       && e
7926       && (e->expr_type == EXPR_VARIABLE || e->expr_type == EXPR_FUNCTION))
7927     {
7928       symbol_attribute attr;
7929       char *msg;
7930       tree temp;
7931       tree cond;
7932 
7933       if (e->symtree->n.sym && IS_CLASS_ARRAY (e->symtree->n.sym))
7934 	{
7935 	  attr = CLASS_DATA (e->symtree->n.sym)->attr;
7936 	  attr.pointer = attr.class_pointer;
7937 	}
7938       else
7939 	attr = gfc_expr_attr (e);
7940 
7941       if (attr.allocatable)
7942 	msg = xasprintf ("Allocatable argument '%s' is not allocated",
7943 			 e->symtree->n.sym->name);
7944       else if (attr.pointer)
7945 	msg = xasprintf ("Pointer argument '%s' is not associated",
7946 			 e->symtree->n.sym->name);
7947       else
7948 	goto end_arg_check;
7949 
7950       if (sym)
7951 	{
7952 	  temp = gfc_class_data_get (sym->backend_decl);
7953 	  temp = gfc_conv_descriptor_data_get (temp);
7954 	}
7955       else
7956 	{
7957 	  argse.descriptor_only = 1;
7958 	  gfc_conv_expr_descriptor (&argse, actual->expr);
7959 	  temp = gfc_conv_descriptor_data_get (argse.expr);
7960 	}
7961 
7962       cond = fold_build2_loc (input_location, EQ_EXPR,
7963 			      logical_type_node, temp,
7964 			      fold_convert (TREE_TYPE (temp),
7965 					    null_pointer_node));
7966       gfc_trans_runtime_check (true, false, cond, &argse.pre, &e->where, msg);
7967 
7968       free (msg);
7969     }
7970  end_arg_check:
7971 
7972   argse.data_not_needed = 1;
7973   if (gfc_is_class_array_function (e))
7974     {
7975       /* For functions that return a class array conv_expr_descriptor is not
7976 	 able to get the descriptor right.  Therefore this special case.  */
7977       gfc_conv_expr_reference (&argse, e);
7978       argse.expr = gfc_class_data_get (argse.expr);
7979     }
7980   else if (sym && sym->backend_decl)
7981     {
7982       gcc_assert (GFC_CLASS_TYPE_P (TREE_TYPE (sym->backend_decl)));
7983       argse.expr = gfc_class_data_get (sym->backend_decl);
7984     }
7985   else
7986     gfc_conv_expr_descriptor (&argse, actual->expr);
7987   gfc_add_block_to_block (&se->pre, &argse.pre);
7988   gfc_add_block_to_block (&se->post, &argse.post);
7989   arg1 = argse.expr;
7990 
7991   actual = actual->next;
7992   if (actual->expr)
7993     {
7994       stmtblock_t block;
7995       gfc_init_block (&block);
7996       gfc_init_se (&argse, NULL);
7997       gfc_conv_expr_type (&argse, actual->expr,
7998 			  gfc_array_index_type);
7999       gfc_add_block_to_block (&block, &argse.pre);
8000       tree tmp = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
8001 			     argse.expr, gfc_index_one_node);
8002       size = gfc_tree_array_size (&block, arg1, e, tmp);
8003 
8004       /* Unusually, for an intrinsic, size does not exclude
8005 	 an optional arg2, so we must test for it.  */
8006       if (actual->expr->expr_type == EXPR_VARIABLE
8007 	    && actual->expr->symtree->n.sym->attr.dummy
8008 	    && actual->expr->symtree->n.sym->attr.optional)
8009 	{
8010 	  tree cond;
8011 	  stmtblock_t block2;
8012 	  gfc_init_block (&block2);
8013 	  gfc_init_se (&argse, NULL);
8014 	  argse.want_pointer = 1;
8015 	  argse.data_not_needed = 1;
8016 	  gfc_conv_expr (&argse, actual->expr);
8017 	  gfc_add_block_to_block (&se->pre, &argse.pre);
8018 	  cond = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
8019 				  argse.expr, null_pointer_node);
8020 	  cond = gfc_evaluate_now (cond, &se->pre);
8021 	  /* 'block2' contains the arg2 absent case, 'block' the arg2 present
8022 	      case; size_var can be used in both blocks. */
8023 	  tree size_var = gfc_create_var (TREE_TYPE (size), "size");
8024 	  tmp = fold_build2_loc (input_location, MODIFY_EXPR,
8025 				 TREE_TYPE (size_var), size_var, size);
8026 	  gfc_add_expr_to_block (&block, tmp);
8027 	  size = gfc_tree_array_size (&block2, arg1, e, NULL_TREE);
8028 	  tmp = fold_build2_loc (input_location, MODIFY_EXPR,
8029 				 TREE_TYPE (size_var), size_var, size);
8030 	  gfc_add_expr_to_block (&block2, tmp);
8031 	  tmp = build3_v (COND_EXPR, cond, gfc_finish_block (&block),
8032 			  gfc_finish_block (&block2));
8033 	  gfc_add_expr_to_block (&se->pre, tmp);
8034 	  size = size_var;
8035 	}
8036       else
8037 	gfc_add_block_to_block (&se->pre, &block);
8038     }
8039   else
8040     size = gfc_tree_array_size (&se->pre, arg1, e, NULL_TREE);
8041   type = gfc_typenode_for_spec (&expr->ts);
8042   se->expr = convert (type, size);
8043 }
8044 
8045 
8046 /* Helper function to compute the size of a character variable,
8047    excluding the terminating null characters.  The result has
8048    gfc_array_index_type type.  */
8049 
8050 tree
size_of_string_in_bytes(int kind,tree string_length)8051 size_of_string_in_bytes (int kind, tree string_length)
8052 {
8053   tree bytesize;
8054   int i = gfc_validate_kind (BT_CHARACTER, kind, false);
8055 
8056   bytesize = build_int_cst (gfc_array_index_type,
8057 			    gfc_character_kinds[i].bit_size / 8);
8058 
8059   return fold_build2_loc (input_location, MULT_EXPR, gfc_array_index_type,
8060 			  bytesize,
8061 			  fold_convert (gfc_array_index_type, string_length));
8062 }
8063 
8064 
8065 static void
gfc_conv_intrinsic_sizeof(gfc_se * se,gfc_expr * expr)8066 gfc_conv_intrinsic_sizeof (gfc_se *se, gfc_expr *expr)
8067 {
8068   gfc_expr *arg;
8069   gfc_se argse;
8070   tree source_bytes;
8071   tree tmp;
8072   tree lower;
8073   tree upper;
8074   tree byte_size;
8075   tree field;
8076   int n;
8077 
8078   gfc_init_se (&argse, NULL);
8079   arg = expr->value.function.actual->expr;
8080 
8081   if (arg->rank || arg->ts.type == BT_ASSUMED)
8082     gfc_conv_expr_descriptor (&argse, arg);
8083   else
8084     gfc_conv_expr_reference (&argse, arg);
8085 
8086   if (arg->ts.type == BT_ASSUMED)
8087     {
8088       /* This only works if an array descriptor has been passed; thus, extract
8089 	 the size from the descriptor.  */
8090       gcc_assert (TYPE_PRECISION (gfc_array_index_type)
8091 		  == TYPE_PRECISION (size_type_node));
8092       tmp = arg->symtree->n.sym->backend_decl;
8093       tmp = DECL_LANG_SPECIFIC (tmp)
8094 	    && GFC_DECL_SAVED_DESCRIPTOR (tmp) != NULL_TREE
8095 	    ? GFC_DECL_SAVED_DESCRIPTOR (tmp) : tmp;
8096       if (POINTER_TYPE_P (TREE_TYPE (tmp)))
8097 	tmp = build_fold_indirect_ref_loc (input_location, tmp);
8098 
8099       tmp = gfc_conv_descriptor_dtype (tmp);
8100       field = gfc_advance_chain (TYPE_FIELDS (get_dtype_type_node ()),
8101 				 GFC_DTYPE_ELEM_LEN);
8102       tmp = fold_build3_loc (input_location, COMPONENT_REF, TREE_TYPE (field),
8103 			     tmp, field, NULL_TREE);
8104 
8105       byte_size = fold_convert (gfc_array_index_type, tmp);
8106     }
8107   else if (arg->ts.type == BT_CLASS)
8108     {
8109       /* Conv_expr_descriptor returns a component_ref to _data component of the
8110 	 class object.  The class object may be a non-pointer object, e.g.
8111 	 located on the stack, or a memory location pointed to, e.g. a
8112 	 parameter, i.e., an indirect_ref.  */
8113       if (POINTER_TYPE_P (TREE_TYPE (argse.expr))
8114 	  && GFC_CLASS_TYPE_P (TREE_TYPE (TREE_TYPE (argse.expr))))
8115 	byte_size
8116 	  = gfc_class_vtab_size_get (build_fold_indirect_ref (argse.expr));
8117       else if (GFC_CLASS_TYPE_P (TREE_TYPE (argse.expr)))
8118 	byte_size = gfc_class_vtab_size_get (argse.expr);
8119       else if (GFC_DESCRIPTOR_TYPE_P (TREE_TYPE (argse.expr))
8120 	       && TREE_CODE (argse.expr) == COMPONENT_REF)
8121 	byte_size = gfc_class_vtab_size_get (TREE_OPERAND (argse.expr, 0));
8122       else if (arg->rank > 0
8123 	       || (arg->rank == 0
8124 		   && arg->ref && arg->ref->type == REF_COMPONENT))
8125 	/* The scalarizer added an additional temp.  To get the class' vptr
8126 	   one has to look at the original backend_decl.  */
8127 	byte_size = gfc_class_vtab_size_get (
8128 	      GFC_DECL_SAVED_DESCRIPTOR (arg->symtree->n.sym->backend_decl));
8129       else
8130 	gcc_unreachable ();
8131     }
8132   else
8133     {
8134       if (arg->ts.type == BT_CHARACTER)
8135 	byte_size = size_of_string_in_bytes (arg->ts.kind, argse.string_length);
8136       else
8137 	{
8138 	  if (arg->rank == 0)
8139 	    byte_size = TREE_TYPE (build_fold_indirect_ref_loc (input_location,
8140 								argse.expr));
8141 	  else
8142 	    byte_size = gfc_get_element_type (TREE_TYPE (argse.expr));
8143 	  byte_size = fold_convert (gfc_array_index_type,
8144 				    size_in_bytes (byte_size));
8145 	}
8146     }
8147 
8148   if (arg->rank == 0)
8149     se->expr = byte_size;
8150   else
8151     {
8152       source_bytes = gfc_create_var (gfc_array_index_type, "bytes");
8153       gfc_add_modify (&argse.pre, source_bytes, byte_size);
8154 
8155       if (arg->rank == -1)
8156 	{
8157 	  tree cond, loop_var, exit_label;
8158           stmtblock_t body;
8159 
8160 	  tmp = fold_convert (gfc_array_index_type,
8161 			      gfc_conv_descriptor_rank (argse.expr));
8162 	  loop_var = gfc_create_var (gfc_array_index_type, "i");
8163 	  gfc_add_modify (&argse.pre, loop_var, gfc_index_zero_node);
8164           exit_label = gfc_build_label_decl (NULL_TREE);
8165 
8166 	  /* Create loop:
8167 	     for (;;)
8168 		{
8169 		  if (i >= rank)
8170 		    goto exit;
8171 		  source_bytes = source_bytes * array.dim[i].extent;
8172 		  i = i + 1;
8173 		}
8174 	      exit:  */
8175 	  gfc_start_block (&body);
8176 	  cond = fold_build2_loc (input_location, GE_EXPR, logical_type_node,
8177 				  loop_var, tmp);
8178 	  tmp = build1_v (GOTO_EXPR, exit_label);
8179 	  tmp = fold_build3_loc (input_location, COND_EXPR, void_type_node,
8180 				 cond, tmp, build_empty_stmt (input_location));
8181 	  gfc_add_expr_to_block (&body, tmp);
8182 
8183 	  lower = gfc_conv_descriptor_lbound_get (argse.expr, loop_var);
8184 	  upper = gfc_conv_descriptor_ubound_get (argse.expr, loop_var);
8185 	  tmp = gfc_conv_array_extent_dim (lower, upper, NULL);
8186 	  tmp = fold_build2_loc (input_location, MULT_EXPR,
8187 				 gfc_array_index_type, tmp, source_bytes);
8188 	  gfc_add_modify (&body, source_bytes, tmp);
8189 
8190 	  tmp = fold_build2_loc (input_location, PLUS_EXPR,
8191 				 gfc_array_index_type, loop_var,
8192 				 gfc_index_one_node);
8193 	  gfc_add_modify_loc (input_location, &body, loop_var, tmp);
8194 
8195 	  tmp = gfc_finish_block (&body);
8196 
8197 	  tmp = fold_build1_loc (input_location, LOOP_EXPR, void_type_node,
8198 				 tmp);
8199 	  gfc_add_expr_to_block (&argse.pre, tmp);
8200 
8201 	  tmp = build1_v (LABEL_EXPR, exit_label);
8202 	  gfc_add_expr_to_block (&argse.pre, tmp);
8203 	}
8204       else
8205 	{
8206 	  /* Obtain the size of the array in bytes.  */
8207 	  for (n = 0; n < arg->rank; n++)
8208 	    {
8209 	      tree idx;
8210 	      idx = gfc_rank_cst[n];
8211 	      lower = gfc_conv_descriptor_lbound_get (argse.expr, idx);
8212 	      upper = gfc_conv_descriptor_ubound_get (argse.expr, idx);
8213 	      tmp = gfc_conv_array_extent_dim (lower, upper, NULL);
8214 	      tmp = fold_build2_loc (input_location, MULT_EXPR,
8215 				     gfc_array_index_type, tmp, source_bytes);
8216 	      gfc_add_modify (&argse.pre, source_bytes, tmp);
8217 	    }
8218 	}
8219       se->expr = source_bytes;
8220     }
8221 
8222   gfc_add_block_to_block (&se->pre, &argse.pre);
8223 }
8224 
8225 
8226 static void
gfc_conv_intrinsic_storage_size(gfc_se * se,gfc_expr * expr)8227 gfc_conv_intrinsic_storage_size (gfc_se *se, gfc_expr *expr)
8228 {
8229   gfc_expr *arg;
8230   gfc_se argse;
8231   tree type, result_type, tmp;
8232 
8233   arg = expr->value.function.actual->expr;
8234 
8235   gfc_init_se (&argse, NULL);
8236   result_type = gfc_get_int_type (expr->ts.kind);
8237 
8238   if (arg->rank == 0)
8239     {
8240       if (arg->ts.type == BT_CLASS)
8241 	{
8242 	  gfc_add_vptr_component (arg);
8243 	  gfc_add_size_component (arg);
8244 	  gfc_conv_expr (&argse, arg);
8245 	  tmp = fold_convert (result_type, argse.expr);
8246 	  goto done;
8247 	}
8248 
8249       gfc_conv_expr_reference (&argse, arg);
8250       type = TREE_TYPE (build_fold_indirect_ref_loc (input_location,
8251 						     argse.expr));
8252     }
8253   else
8254     {
8255       argse.want_pointer = 0;
8256       gfc_conv_expr_descriptor (&argse, arg);
8257       if (arg->ts.type == BT_CLASS)
8258 	{
8259 	  if (arg->rank > 0)
8260 	    tmp = gfc_class_vtab_size_get (
8261 		 GFC_DECL_SAVED_DESCRIPTOR (arg->symtree->n.sym->backend_decl));
8262 	  else
8263 	    tmp = gfc_class_vtab_size_get (TREE_OPERAND (argse.expr, 0));
8264 	  tmp = fold_convert (result_type, tmp);
8265 	  goto done;
8266 	}
8267       type = gfc_get_element_type (TREE_TYPE (argse.expr));
8268     }
8269 
8270   /* Obtain the argument's word length.  */
8271   if (arg->ts.type == BT_CHARACTER)
8272     tmp = size_of_string_in_bytes (arg->ts.kind, argse.string_length);
8273   else
8274     tmp = size_in_bytes (type);
8275   tmp = fold_convert (result_type, tmp);
8276 
8277 done:
8278   se->expr = fold_build2_loc (input_location, MULT_EXPR, result_type, tmp,
8279 			      build_int_cst (result_type, BITS_PER_UNIT));
8280   gfc_add_block_to_block (&se->pre, &argse.pre);
8281 }
8282 
8283 
8284 /* Intrinsic string comparison functions.  */
8285 
8286 static void
gfc_conv_intrinsic_strcmp(gfc_se * se,gfc_expr * expr,enum tree_code op)8287 gfc_conv_intrinsic_strcmp (gfc_se * se, gfc_expr * expr, enum tree_code op)
8288 {
8289   tree args[4];
8290 
8291   gfc_conv_intrinsic_function_args (se, expr, args, 4);
8292 
8293   se->expr
8294     = gfc_build_compare_string (args[0], args[1], args[2], args[3],
8295 				expr->value.function.actual->expr->ts.kind,
8296 				op);
8297   se->expr = fold_build2_loc (input_location, op,
8298 			      gfc_typenode_for_spec (&expr->ts), se->expr,
8299 			      build_int_cst (TREE_TYPE (se->expr), 0));
8300 }
8301 
8302 /* Generate a call to the adjustl/adjustr library function.  */
8303 static void
gfc_conv_intrinsic_adjust(gfc_se * se,gfc_expr * expr,tree fndecl)8304 gfc_conv_intrinsic_adjust (gfc_se * se, gfc_expr * expr, tree fndecl)
8305 {
8306   tree args[3];
8307   tree len;
8308   tree type;
8309   tree var;
8310   tree tmp;
8311 
8312   gfc_conv_intrinsic_function_args (se, expr, &args[1], 2);
8313   len = args[1];
8314 
8315   type = TREE_TYPE (args[2]);
8316   var = gfc_conv_string_tmp (se, type, len);
8317   args[0] = var;
8318 
8319   tmp = build_call_expr_loc (input_location,
8320 			 fndecl, 3, args[0], args[1], args[2]);
8321   gfc_add_expr_to_block (&se->pre, tmp);
8322   se->expr = var;
8323   se->string_length = len;
8324 }
8325 
8326 
8327 /* Generate code for the TRANSFER intrinsic:
8328 	For scalar results:
8329 	  DEST = TRANSFER (SOURCE, MOLD)
8330 	where:
8331 	  typeof<DEST> = typeof<MOLD>
8332 	and:
8333 	  MOLD is scalar.
8334 
8335 	For array results:
8336 	  DEST(1:N) = TRANSFER (SOURCE, MOLD[, SIZE])
8337 	where:
8338 	  typeof<DEST> = typeof<MOLD>
8339 	and:
8340 	  N = min (sizeof (SOURCE(:)), sizeof (DEST(:)),
8341 	      sizeof (DEST(0) * SIZE).  */
8342 static void
gfc_conv_intrinsic_transfer(gfc_se * se,gfc_expr * expr)8343 gfc_conv_intrinsic_transfer (gfc_se * se, gfc_expr * expr)
8344 {
8345   tree tmp;
8346   tree tmpdecl;
8347   tree ptr;
8348   tree extent;
8349   tree source;
8350   tree source_type;
8351   tree source_bytes;
8352   tree mold_type;
8353   tree dest_word_len;
8354   tree size_words;
8355   tree size_bytes;
8356   tree upper;
8357   tree lower;
8358   tree stmt;
8359   tree class_ref = NULL_TREE;
8360   gfc_actual_arglist *arg;
8361   gfc_se argse;
8362   gfc_array_info *info;
8363   stmtblock_t block;
8364   int n;
8365   bool scalar_mold;
8366   gfc_expr *source_expr, *mold_expr, *class_expr;
8367 
8368   info = NULL;
8369   if (se->loop)
8370     info = &se->ss->info->data.array;
8371 
8372   /* Convert SOURCE.  The output from this stage is:-
8373 	source_bytes = length of the source in bytes
8374 	source = pointer to the source data.  */
8375   arg = expr->value.function.actual;
8376   source_expr = arg->expr;
8377 
8378   /* Ensure double transfer through LOGICAL preserves all
8379      the needed bits.  */
8380   if (arg->expr->expr_type == EXPR_FUNCTION
8381 	&& arg->expr->value.function.esym == NULL
8382 	&& arg->expr->value.function.isym != NULL
8383 	&& arg->expr->value.function.isym->id == GFC_ISYM_TRANSFER
8384 	&& arg->expr->ts.type == BT_LOGICAL
8385 	&& expr->ts.type != arg->expr->ts.type)
8386     arg->expr->value.function.name = "__transfer_in_transfer";
8387 
8388   gfc_init_se (&argse, NULL);
8389 
8390   source_bytes = gfc_create_var (gfc_array_index_type, NULL);
8391 
8392   /* Obtain the pointer to source and the length of source in bytes.  */
8393   if (arg->expr->rank == 0)
8394     {
8395       gfc_conv_expr_reference (&argse, arg->expr);
8396       if (arg->expr->ts.type == BT_CLASS)
8397 	{
8398 	  tmp = build_fold_indirect_ref_loc (input_location, argse.expr);
8399 	  if (GFC_CLASS_TYPE_P (TREE_TYPE (tmp)))
8400 	    source = gfc_class_data_get (tmp);
8401 	  else
8402 	    {
8403 	      /* Array elements are evaluated as a reference to the data.
8404 		 To obtain the vptr for the element size, the argument
8405 		 expression must be stripped to the class reference and
8406 		 re-evaluated. The pre and post blocks are not needed.  */
8407 	      gcc_assert (arg->expr->expr_type == EXPR_VARIABLE);
8408 	      source = argse.expr;
8409 	      class_expr = gfc_find_and_cut_at_last_class_ref (arg->expr);
8410 	      gfc_init_se (&argse, NULL);
8411 	      gfc_conv_expr (&argse, class_expr);
8412 	      class_ref = argse.expr;
8413 	    }
8414 	}
8415       else
8416 	source = argse.expr;
8417 
8418       /* Obtain the source word length.  */
8419       switch (arg->expr->ts.type)
8420 	{
8421 	case BT_CHARACTER:
8422 	  tmp = size_of_string_in_bytes (arg->expr->ts.kind,
8423 					 argse.string_length);
8424 	  break;
8425 	case BT_CLASS:
8426 	  if (class_ref != NULL_TREE)
8427 	    tmp = gfc_class_vtab_size_get (class_ref);
8428 	  else
8429 	    tmp = gfc_class_vtab_size_get (argse.expr);
8430 	  break;
8431 	default:
8432 	  source_type = TREE_TYPE (build_fold_indirect_ref_loc (input_location,
8433 								source));
8434 	  tmp = fold_convert (gfc_array_index_type,
8435 			      size_in_bytes (source_type));
8436 	  break;
8437 	}
8438     }
8439   else
8440     {
8441       argse.want_pointer = 0;
8442       gfc_conv_expr_descriptor (&argse, arg->expr);
8443       source = gfc_conv_descriptor_data_get (argse.expr);
8444       source_type = gfc_get_element_type (TREE_TYPE (argse.expr));
8445 
8446       /* Repack the source if not simply contiguous.  */
8447       if (!gfc_is_simply_contiguous (arg->expr, false, true))
8448 	{
8449 	  tmp = gfc_build_addr_expr (NULL_TREE, argse.expr);
8450 
8451 	  if (warn_array_temporaries)
8452 	    gfc_warning (OPT_Warray_temporaries,
8453 			 "Creating array temporary at %L", &expr->where);
8454 
8455 	  source = build_call_expr_loc (input_location,
8456 				    gfor_fndecl_in_pack, 1, tmp);
8457 	  source = gfc_evaluate_now (source, &argse.pre);
8458 
8459 	  /* Free the temporary.  */
8460 	  gfc_start_block (&block);
8461 	  tmp = gfc_call_free (source);
8462 	  gfc_add_expr_to_block (&block, tmp);
8463 	  stmt = gfc_finish_block (&block);
8464 
8465 	  /* Clean up if it was repacked.  */
8466 	  gfc_init_block (&block);
8467 	  tmp = gfc_conv_array_data (argse.expr);
8468 	  tmp = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
8469 				 source, tmp);
8470 	  tmp = build3_v (COND_EXPR, tmp, stmt,
8471 			  build_empty_stmt (input_location));
8472 	  gfc_add_expr_to_block (&block, tmp);
8473 	  gfc_add_block_to_block (&block, &se->post);
8474 	  gfc_init_block (&se->post);
8475 	  gfc_add_block_to_block (&se->post, &block);
8476 	}
8477 
8478       /* Obtain the source word length.  */
8479       if (arg->expr->ts.type == BT_CHARACTER)
8480 	tmp = size_of_string_in_bytes (arg->expr->ts.kind,
8481 				       argse.string_length);
8482       else
8483 	tmp = fold_convert (gfc_array_index_type,
8484 			    size_in_bytes (source_type));
8485 
8486       /* Obtain the size of the array in bytes.  */
8487       extent = gfc_create_var (gfc_array_index_type, NULL);
8488       for (n = 0; n < arg->expr->rank; n++)
8489 	{
8490 	  tree idx;
8491 	  idx = gfc_rank_cst[n];
8492 	  gfc_add_modify (&argse.pre, source_bytes, tmp);
8493 	  lower = gfc_conv_descriptor_lbound_get (argse.expr, idx);
8494 	  upper = gfc_conv_descriptor_ubound_get (argse.expr, idx);
8495 	  tmp = fold_build2_loc (input_location, MINUS_EXPR,
8496 				 gfc_array_index_type, upper, lower);
8497 	  gfc_add_modify (&argse.pre, extent, tmp);
8498 	  tmp = fold_build2_loc (input_location, PLUS_EXPR,
8499 				 gfc_array_index_type, extent,
8500 				 gfc_index_one_node);
8501 	  tmp = fold_build2_loc (input_location, MULT_EXPR,
8502 				 gfc_array_index_type, tmp, source_bytes);
8503 	}
8504     }
8505 
8506   gfc_add_modify (&argse.pre, source_bytes, tmp);
8507   gfc_add_block_to_block (&se->pre, &argse.pre);
8508   gfc_add_block_to_block (&se->post, &argse.post);
8509 
8510   /* Now convert MOLD.  The outputs are:
8511 	mold_type = the TREE type of MOLD
8512 	dest_word_len = destination word length in bytes.  */
8513   arg = arg->next;
8514   mold_expr = arg->expr;
8515 
8516   gfc_init_se (&argse, NULL);
8517 
8518   scalar_mold = arg->expr->rank == 0;
8519 
8520   if (arg->expr->rank == 0)
8521     {
8522       gfc_conv_expr_reference (&argse, arg->expr);
8523       mold_type = TREE_TYPE (build_fold_indirect_ref_loc (input_location,
8524 							  argse.expr));
8525     }
8526   else
8527     {
8528       gfc_init_se (&argse, NULL);
8529       argse.want_pointer = 0;
8530       gfc_conv_expr_descriptor (&argse, arg->expr);
8531       mold_type = gfc_get_element_type (TREE_TYPE (argse.expr));
8532     }
8533 
8534   gfc_add_block_to_block (&se->pre, &argse.pre);
8535   gfc_add_block_to_block (&se->post, &argse.post);
8536 
8537   if (strcmp (expr->value.function.name, "__transfer_in_transfer") == 0)
8538     {
8539       /* If this TRANSFER is nested in another TRANSFER, use a type
8540 	 that preserves all bits.  */
8541       if (arg->expr->ts.type == BT_LOGICAL)
8542 	mold_type = gfc_get_int_type (arg->expr->ts.kind);
8543     }
8544 
8545   /* Obtain the destination word length.  */
8546   switch (arg->expr->ts.type)
8547     {
8548     case BT_CHARACTER:
8549       tmp = size_of_string_in_bytes (arg->expr->ts.kind, argse.string_length);
8550       mold_type = gfc_get_character_type_len (arg->expr->ts.kind,
8551 					      argse.string_length);
8552       break;
8553     case BT_CLASS:
8554       tmp = gfc_class_vtab_size_get (argse.expr);
8555       break;
8556     default:
8557       tmp = fold_convert (gfc_array_index_type, size_in_bytes (mold_type));
8558       break;
8559     }
8560   dest_word_len = gfc_create_var (gfc_array_index_type, NULL);
8561   gfc_add_modify (&se->pre, dest_word_len, tmp);
8562 
8563   /* Finally convert SIZE, if it is present.  */
8564   arg = arg->next;
8565   size_words = gfc_create_var (gfc_array_index_type, NULL);
8566 
8567   if (arg->expr)
8568     {
8569       gfc_init_se (&argse, NULL);
8570       gfc_conv_expr_reference (&argse, arg->expr);
8571       tmp = convert (gfc_array_index_type,
8572 		     build_fold_indirect_ref_loc (input_location,
8573 					      argse.expr));
8574       gfc_add_block_to_block (&se->pre, &argse.pre);
8575       gfc_add_block_to_block (&se->post, &argse.post);
8576     }
8577   else
8578     tmp = NULL_TREE;
8579 
8580   /* Separate array and scalar results.  */
8581   if (scalar_mold && tmp == NULL_TREE)
8582     goto scalar_transfer;
8583 
8584   size_bytes = gfc_create_var (gfc_array_index_type, NULL);
8585   if (tmp != NULL_TREE)
8586     tmp = fold_build2_loc (input_location, MULT_EXPR, gfc_array_index_type,
8587 			   tmp, dest_word_len);
8588   else
8589     tmp = source_bytes;
8590 
8591   gfc_add_modify (&se->pre, size_bytes, tmp);
8592   gfc_add_modify (&se->pre, size_words,
8593 		       fold_build2_loc (input_location, CEIL_DIV_EXPR,
8594 					gfc_array_index_type,
8595 					size_bytes, dest_word_len));
8596 
8597   /* Evaluate the bounds of the result.  If the loop range exists, we have
8598      to check if it is too large.  If so, we modify loop->to be consistent
8599      with min(size, size(source)).  Otherwise, size is made consistent with
8600      the loop range, so that the right number of bytes is transferred.*/
8601   n = se->loop->order[0];
8602   if (se->loop->to[n] != NULL_TREE)
8603     {
8604       tmp = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
8605 			     se->loop->to[n], se->loop->from[n]);
8606       tmp = fold_build2_loc (input_location, PLUS_EXPR, gfc_array_index_type,
8607 			     tmp, gfc_index_one_node);
8608       tmp = fold_build2_loc (input_location, MIN_EXPR, gfc_array_index_type,
8609 			 tmp, size_words);
8610       gfc_add_modify (&se->pre, size_words, tmp);
8611       gfc_add_modify (&se->pre, size_bytes,
8612 			   fold_build2_loc (input_location, MULT_EXPR,
8613 					    gfc_array_index_type,
8614 					    size_words, dest_word_len));
8615       upper = fold_build2_loc (input_location, PLUS_EXPR, gfc_array_index_type,
8616 			       size_words, se->loop->from[n]);
8617       upper = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
8618 			       upper, gfc_index_one_node);
8619     }
8620   else
8621     {
8622       upper = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
8623 			       size_words, gfc_index_one_node);
8624       se->loop->from[n] = gfc_index_zero_node;
8625     }
8626 
8627   se->loop->to[n] = upper;
8628 
8629   /* Build a destination descriptor, using the pointer, source, as the
8630      data field.  */
8631   gfc_trans_create_temp_array (&se->pre, &se->post, se->ss, mold_type,
8632 			       NULL_TREE, false, true, false, &expr->where);
8633 
8634   /* Cast the pointer to the result.  */
8635   tmp = gfc_conv_descriptor_data_get (info->descriptor);
8636   tmp = fold_convert (pvoid_type_node, tmp);
8637 
8638   /* Use memcpy to do the transfer.  */
8639   tmp
8640     = build_call_expr_loc (input_location,
8641 			   builtin_decl_explicit (BUILT_IN_MEMCPY), 3, tmp,
8642 			   fold_convert (pvoid_type_node, source),
8643 			   fold_convert (size_type_node,
8644 					 fold_build2_loc (input_location,
8645 							  MIN_EXPR,
8646 							  gfc_array_index_type,
8647 							  size_bytes,
8648 							  source_bytes)));
8649   gfc_add_expr_to_block (&se->pre, tmp);
8650 
8651   se->expr = info->descriptor;
8652   if (expr->ts.type == BT_CHARACTER)
8653     {
8654       tmp = fold_convert (gfc_charlen_type_node,
8655 			  TYPE_SIZE_UNIT (gfc_get_char_type (expr->ts.kind)));
8656       se->string_length = fold_build2_loc (input_location, TRUNC_DIV_EXPR,
8657 					   gfc_charlen_type_node,
8658 					   dest_word_len, tmp);
8659     }
8660 
8661   return;
8662 
8663 /* Deal with scalar results.  */
8664 scalar_transfer:
8665   extent = fold_build2_loc (input_location, MIN_EXPR, gfc_array_index_type,
8666 			    dest_word_len, source_bytes);
8667   extent = fold_build2_loc (input_location, MAX_EXPR, gfc_array_index_type,
8668 			    extent, gfc_index_zero_node);
8669 
8670   if (expr->ts.type == BT_CHARACTER)
8671     {
8672       tree direct, indirect, free;
8673 
8674       ptr = convert (gfc_get_pchar_type (expr->ts.kind), source);
8675       tmpdecl = gfc_create_var (gfc_get_pchar_type (expr->ts.kind),
8676 				"transfer");
8677 
8678       /* If source is longer than the destination, use a pointer to
8679 	 the source directly.  */
8680       gfc_init_block (&block);
8681       gfc_add_modify (&block, tmpdecl, ptr);
8682       direct = gfc_finish_block (&block);
8683 
8684       /* Otherwise, allocate a string with the length of the destination
8685 	 and copy the source into it.  */
8686       gfc_init_block (&block);
8687       tmp = gfc_get_pchar_type (expr->ts.kind);
8688       tmp = gfc_call_malloc (&block, tmp, dest_word_len);
8689       gfc_add_modify (&block, tmpdecl,
8690 		      fold_convert (TREE_TYPE (ptr), tmp));
8691       tmp = build_call_expr_loc (input_location,
8692 			     builtin_decl_explicit (BUILT_IN_MEMCPY), 3,
8693 			     fold_convert (pvoid_type_node, tmpdecl),
8694 			     fold_convert (pvoid_type_node, ptr),
8695 			     fold_convert (size_type_node, extent));
8696       gfc_add_expr_to_block (&block, tmp);
8697       indirect = gfc_finish_block (&block);
8698 
8699       /* Wrap it up with the condition.  */
8700       tmp = fold_build2_loc (input_location, LE_EXPR, logical_type_node,
8701 			     dest_word_len, source_bytes);
8702       tmp = build3_v (COND_EXPR, tmp, direct, indirect);
8703       gfc_add_expr_to_block (&se->pre, tmp);
8704 
8705       /* Free the temporary string, if necessary.  */
8706       free = gfc_call_free (tmpdecl);
8707       tmp = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
8708 			     dest_word_len, source_bytes);
8709       tmp = build3_v (COND_EXPR, tmp, free, build_empty_stmt (input_location));
8710       gfc_add_expr_to_block (&se->post, tmp);
8711 
8712       se->expr = tmpdecl;
8713       tmp = fold_convert (gfc_charlen_type_node,
8714 			  TYPE_SIZE_UNIT (gfc_get_char_type (expr->ts.kind)));
8715       se->string_length = fold_build2_loc (input_location, TRUNC_DIV_EXPR,
8716 					   gfc_charlen_type_node,
8717 					   dest_word_len, tmp);
8718     }
8719   else
8720     {
8721       tmpdecl = gfc_create_var (mold_type, "transfer");
8722 
8723       ptr = convert (build_pointer_type (mold_type), source);
8724 
8725       /* For CLASS results, allocate the needed memory first.  */
8726       if (mold_expr->ts.type == BT_CLASS)
8727 	{
8728 	  tree cdata;
8729 	  cdata = gfc_class_data_get (tmpdecl);
8730 	  tmp = gfc_call_malloc (&se->pre, TREE_TYPE (cdata), dest_word_len);
8731 	  gfc_add_modify (&se->pre, cdata, tmp);
8732 	}
8733 
8734       /* Use memcpy to do the transfer.  */
8735       if (mold_expr->ts.type == BT_CLASS)
8736 	tmp = gfc_class_data_get (tmpdecl);
8737       else
8738 	tmp = gfc_build_addr_expr (NULL_TREE, tmpdecl);
8739 
8740       tmp = build_call_expr_loc (input_location,
8741 			     builtin_decl_explicit (BUILT_IN_MEMCPY), 3,
8742 			     fold_convert (pvoid_type_node, tmp),
8743 			     fold_convert (pvoid_type_node, ptr),
8744 			     fold_convert (size_type_node, extent));
8745       gfc_add_expr_to_block (&se->pre, tmp);
8746 
8747       /* For CLASS results, set the _vptr.  */
8748       if (mold_expr->ts.type == BT_CLASS)
8749 	{
8750 	  tree vptr;
8751 	  gfc_symbol *vtab;
8752 	  vptr = gfc_class_vptr_get (tmpdecl);
8753 	  vtab = gfc_find_derived_vtab (source_expr->ts.u.derived);
8754 	  gcc_assert (vtab);
8755 	  tmp = gfc_build_addr_expr (NULL_TREE, gfc_get_symbol_decl (vtab));
8756 	  gfc_add_modify (&se->pre, vptr, fold_convert (TREE_TYPE (vptr), tmp));
8757 	}
8758 
8759       se->expr = tmpdecl;
8760     }
8761 }
8762 
8763 
8764 /* Generate a call to caf_is_present.  */
8765 
8766 static tree
trans_caf_is_present(gfc_se * se,gfc_expr * expr)8767 trans_caf_is_present (gfc_se *se, gfc_expr *expr)
8768 {
8769   tree caf_reference, caf_decl, token, image_index;
8770 
8771   /* Compile the reference chain.  */
8772   caf_reference = conv_expr_ref_to_caf_ref (&se->pre, expr);
8773   gcc_assert (caf_reference != NULL_TREE);
8774 
8775   caf_decl = gfc_get_tree_for_caf_expr (expr);
8776   if (TREE_CODE (TREE_TYPE (caf_decl)) == REFERENCE_TYPE)
8777     caf_decl = build_fold_indirect_ref_loc (input_location, caf_decl);
8778   image_index = gfc_caf_get_image_index (&se->pre, expr, caf_decl);
8779   gfc_get_caf_token_offset (se, &token, NULL, caf_decl, NULL,
8780 			    expr);
8781 
8782   return build_call_expr_loc (input_location, gfor_fndecl_caf_is_present,
8783 			      3, token, image_index, caf_reference);
8784 }
8785 
8786 
8787 /* Test whether this ref-chain refs this image only.  */
8788 
8789 static bool
caf_this_image_ref(gfc_ref * ref)8790 caf_this_image_ref (gfc_ref *ref)
8791 {
8792   for ( ; ref; ref = ref->next)
8793     if (ref->type == REF_ARRAY && ref->u.ar.codimen)
8794       return ref->u.ar.dimen_type[ref->u.ar.dimen] == DIMEN_THIS_IMAGE;
8795 
8796   return false;
8797 }
8798 
8799 
8800 /* Generate code for the ALLOCATED intrinsic.
8801    Generate inline code that directly check the address of the argument.  */
8802 
8803 static void
gfc_conv_allocated(gfc_se * se,gfc_expr * expr)8804 gfc_conv_allocated (gfc_se *se, gfc_expr *expr)
8805 {
8806   gfc_se arg1se;
8807   tree tmp;
8808   bool coindexed_caf_comp = false;
8809   gfc_expr *e = expr->value.function.actual->expr;
8810 
8811   gfc_init_se (&arg1se, NULL);
8812   if (e->ts.type == BT_CLASS)
8813     {
8814       /* Make sure that class array expressions have both a _data
8815 	 component reference and an array reference....  */
8816       if (CLASS_DATA (e)->attr.dimension)
8817 	gfc_add_class_array_ref (e);
8818       /* .... whilst scalars only need the _data component.  */
8819       else
8820 	gfc_add_data_component (e);
8821     }
8822 
8823   /* When 'e' references an allocatable component in a coarray, then call
8824      the caf-library function caf_is_present ().  */
8825   if (flag_coarray == GFC_FCOARRAY_LIB && e->expr_type == EXPR_FUNCTION
8826       && e->value.function.isym
8827       && e->value.function.isym->id == GFC_ISYM_CAF_GET)
8828     {
8829       e = e->value.function.actual->expr;
8830       if (gfc_expr_attr (e).codimension)
8831 	{
8832 	  /* Last partref is the coindexed coarray. As coarrays are collectively
8833 	     (de)allocated, the allocation status must be the same as the one of
8834 	     the local allocation.  Convert to local access. */
8835 	  for (gfc_ref *ref = e->ref; ref; ref = ref->next)
8836 	    if (ref->type == REF_ARRAY && ref->u.ar.codimen)
8837 	      {
8838 		for (int i = ref->u.ar.dimen;
8839 		     i < ref->u.ar.dimen + ref->u.ar.codimen; ++i)
8840 		ref->u.ar.dimen_type[i] = DIMEN_THIS_IMAGE;
8841 		break;
8842 	      }
8843 	}
8844       else if (!caf_this_image_ref (e->ref))
8845 	coindexed_caf_comp = true;
8846     }
8847   if (coindexed_caf_comp)
8848     tmp = trans_caf_is_present (se, e);
8849   else
8850     {
8851       if (e->rank == 0)
8852 	{
8853 	  /* Allocatable scalar.  */
8854 	  arg1se.want_pointer = 1;
8855 	  gfc_conv_expr (&arg1se, e);
8856 	  tmp = arg1se.expr;
8857 	}
8858       else
8859 	{
8860 	  /* Allocatable array.  */
8861 	  arg1se.descriptor_only = 1;
8862 	  gfc_conv_expr_descriptor (&arg1se, e);
8863 	  tmp = gfc_conv_descriptor_data_get (arg1se.expr);
8864 	}
8865 
8866       tmp = fold_build2_loc (input_location, NE_EXPR, logical_type_node, tmp,
8867 			     fold_convert (TREE_TYPE (tmp), null_pointer_node));
8868     }
8869 
8870   /* Components of pointer array references sometimes come back with a pre block.  */
8871   if (arg1se.pre.head)
8872     gfc_add_block_to_block (&se->pre, &arg1se.pre);
8873 
8874   se->expr = convert (gfc_typenode_for_spec (&expr->ts), tmp);
8875 }
8876 
8877 
8878 /* Generate code for the ASSOCIATED intrinsic.
8879    If both POINTER and TARGET are arrays, generate a call to library function
8880    _gfor_associated, and pass descriptors of POINTER and TARGET to it.
8881    In other cases, generate inline code that directly compare the address of
8882    POINTER with the address of TARGET.  */
8883 
8884 static void
gfc_conv_associated(gfc_se * se,gfc_expr * expr)8885 gfc_conv_associated (gfc_se *se, gfc_expr *expr)
8886 {
8887   gfc_actual_arglist *arg1;
8888   gfc_actual_arglist *arg2;
8889   gfc_se arg1se;
8890   gfc_se arg2se;
8891   tree tmp2;
8892   tree tmp;
8893   tree nonzero_arraylen = NULL_TREE;
8894   gfc_ss *ss;
8895   bool scalar;
8896 
8897   gfc_init_se (&arg1se, NULL);
8898   gfc_init_se (&arg2se, NULL);
8899   arg1 = expr->value.function.actual;
8900   arg2 = arg1->next;
8901 
8902   /* Check whether the expression is a scalar or not; we cannot use
8903      arg1->expr->rank as it can be nonzero for proc pointers.  */
8904   ss = gfc_walk_expr (arg1->expr);
8905   scalar = ss == gfc_ss_terminator;
8906   if (!scalar)
8907     gfc_free_ss_chain (ss);
8908 
8909   if (!arg2->expr)
8910     {
8911       /* No optional target.  */
8912       if (scalar)
8913         {
8914 	  /* A pointer to a scalar.  */
8915 	  arg1se.want_pointer = 1;
8916 	  gfc_conv_expr (&arg1se, arg1->expr);
8917 	  if (arg1->expr->symtree->n.sym->attr.proc_pointer
8918 	      && arg1->expr->symtree->n.sym->attr.dummy)
8919 	    arg1se.expr = build_fold_indirect_ref_loc (input_location,
8920 						       arg1se.expr);
8921   	  if (arg1->expr->ts.type == BT_CLASS)
8922 	    {
8923 	      tmp2 = gfc_class_data_get (arg1se.expr);
8924 	      if (GFC_DESCRIPTOR_TYPE_P (TREE_TYPE (tmp2)))
8925 		tmp2 = gfc_conv_descriptor_data_get (tmp2);
8926 	    }
8927 	  else
8928 	    tmp2 = arg1se.expr;
8929         }
8930       else
8931         {
8932           /* A pointer to an array.  */
8933           gfc_conv_expr_descriptor (&arg1se, arg1->expr);
8934           tmp2 = gfc_conv_descriptor_data_get (arg1se.expr);
8935         }
8936       gfc_add_block_to_block (&se->pre, &arg1se.pre);
8937       gfc_add_block_to_block (&se->post, &arg1se.post);
8938       tmp = fold_build2_loc (input_location, NE_EXPR, logical_type_node, tmp2,
8939 			     fold_convert (TREE_TYPE (tmp2), null_pointer_node));
8940       se->expr = tmp;
8941     }
8942   else
8943     {
8944       /* An optional target.  */
8945       if (arg2->expr->ts.type == BT_CLASS
8946 	  && arg2->expr->expr_type != EXPR_FUNCTION)
8947 	gfc_add_data_component (arg2->expr);
8948 
8949       if (scalar)
8950         {
8951 	  /* A pointer to a scalar.  */
8952 	  arg1se.want_pointer = 1;
8953 	  gfc_conv_expr (&arg1se, arg1->expr);
8954 	  if (arg1->expr->symtree->n.sym->attr.proc_pointer
8955 	      && arg1->expr->symtree->n.sym->attr.dummy)
8956 	    arg1se.expr = build_fold_indirect_ref_loc (input_location,
8957 						       arg1se.expr);
8958 	  if (arg1->expr->ts.type == BT_CLASS)
8959 	    arg1se.expr = gfc_class_data_get (arg1se.expr);
8960 
8961 	  arg2se.want_pointer = 1;
8962 	  gfc_conv_expr (&arg2se, arg2->expr);
8963 	  if (arg2->expr->symtree->n.sym->attr.proc_pointer
8964 	      && arg2->expr->symtree->n.sym->attr.dummy)
8965 	    arg2se.expr = build_fold_indirect_ref_loc (input_location,
8966 						       arg2se.expr);
8967 	  if (arg2->expr->ts.type == BT_CLASS)
8968 	    {
8969 	      arg2se.expr = gfc_evaluate_now (arg2se.expr, &arg2se.pre);
8970 	      arg2se.expr = gfc_class_data_get (arg2se.expr);
8971 	    }
8972 	  gfc_add_block_to_block (&se->pre, &arg1se.pre);
8973 	  gfc_add_block_to_block (&se->post, &arg1se.post);
8974 	  gfc_add_block_to_block (&se->pre, &arg2se.pre);
8975 	  gfc_add_block_to_block (&se->post, &arg2se.post);
8976           tmp = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
8977 				 arg1se.expr, arg2se.expr);
8978           tmp2 = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
8979 				  arg1se.expr, null_pointer_node);
8980           se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
8981 				      logical_type_node, tmp, tmp2);
8982         }
8983       else
8984         {
8985 	  /* An array pointer of zero length is not associated if target is
8986 	     present.  */
8987 	  arg1se.descriptor_only = 1;
8988 	  gfc_conv_expr_lhs (&arg1se, arg1->expr);
8989 	  if (arg1->expr->rank == -1)
8990 	    {
8991 	      tmp = gfc_conv_descriptor_rank (arg1se.expr);
8992 	      tmp = fold_build2_loc (input_location, MINUS_EXPR,
8993 				     TREE_TYPE (tmp), tmp,
8994 				     build_int_cst (TREE_TYPE (tmp), 1));
8995 	    }
8996 	  else
8997 	    tmp = gfc_rank_cst[arg1->expr->rank - 1];
8998 	  tmp = gfc_conv_descriptor_stride_get (arg1se.expr, tmp);
8999 	  if (arg2->expr->rank != 0)
9000 	    nonzero_arraylen = fold_build2_loc (input_location, NE_EXPR,
9001 						logical_type_node, tmp,
9002 						build_int_cst (TREE_TYPE (tmp), 0));
9003 
9004 	  /* A pointer to an array, call library function _gfor_associated.  */
9005 	  arg1se.want_pointer = 1;
9006 	  gfc_conv_expr_descriptor (&arg1se, arg1->expr);
9007 	  gfc_add_block_to_block (&se->pre, &arg1se.pre);
9008 	  gfc_add_block_to_block (&se->post, &arg1se.post);
9009 
9010 	  arg2se.want_pointer = 1;
9011 	  arg2se.force_no_tmp = 1;
9012 	  if (arg2->expr->rank != 0)
9013 	    gfc_conv_expr_descriptor (&arg2se, arg2->expr);
9014 	  else
9015 	    {
9016 	      gfc_conv_expr (&arg2se, arg2->expr);
9017 	      arg2se.expr
9018 		= gfc_conv_scalar_to_descriptor (&arg2se, arg2se.expr,
9019 						 gfc_expr_attr (arg2->expr));
9020 	      arg2se.expr = gfc_build_addr_expr (NULL_TREE, arg2se.expr);
9021 	    }
9022 	  gfc_add_block_to_block (&se->pre, &arg2se.pre);
9023 	  gfc_add_block_to_block (&se->post, &arg2se.post);
9024 	  se->expr = build_call_expr_loc (input_location,
9025 				      gfor_fndecl_associated, 2,
9026 				      arg1se.expr, arg2se.expr);
9027 	  se->expr = convert (logical_type_node, se->expr);
9028 	  if (arg2->expr->rank != 0)
9029 	    se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
9030 					logical_type_node, se->expr,
9031 					nonzero_arraylen);
9032         }
9033 
9034       /* If target is present zero character length pointers cannot
9035 	 be associated.  */
9036       if (arg1->expr->ts.type == BT_CHARACTER)
9037 	{
9038 	  tmp = arg1se.string_length;
9039 	  tmp = fold_build2_loc (input_location, NE_EXPR,
9040 				 logical_type_node, tmp,
9041 				 build_zero_cst (TREE_TYPE (tmp)));
9042 	  se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
9043 				      logical_type_node, se->expr, tmp);
9044 	}
9045     }
9046 
9047   se->expr = convert (gfc_typenode_for_spec (&expr->ts), se->expr);
9048 }
9049 
9050 
9051 /* Generate code for the SAME_TYPE_AS intrinsic.
9052    Generate inline code that directly checks the vindices.  */
9053 
9054 static void
gfc_conv_same_type_as(gfc_se * se,gfc_expr * expr)9055 gfc_conv_same_type_as (gfc_se *se, gfc_expr *expr)
9056 {
9057   gfc_expr *a, *b;
9058   gfc_se se1, se2;
9059   tree tmp;
9060   tree conda = NULL_TREE, condb = NULL_TREE;
9061 
9062   gfc_init_se (&se1, NULL);
9063   gfc_init_se (&se2, NULL);
9064 
9065   a = expr->value.function.actual->expr;
9066   b = expr->value.function.actual->next->expr;
9067 
9068   bool unlimited_poly_a = UNLIMITED_POLY (a);
9069   bool unlimited_poly_b = UNLIMITED_POLY (b);
9070   if (unlimited_poly_a)
9071     {
9072       se1.want_pointer = 1;
9073       gfc_add_vptr_component (a);
9074     }
9075   else if (a->ts.type == BT_CLASS)
9076     {
9077       gfc_add_vptr_component (a);
9078       gfc_add_hash_component (a);
9079     }
9080   else if (a->ts.type == BT_DERIVED)
9081     a = gfc_get_int_expr (gfc_default_integer_kind, NULL,
9082 			  a->ts.u.derived->hash_value);
9083 
9084   if (unlimited_poly_b)
9085     {
9086       se2.want_pointer = 1;
9087       gfc_add_vptr_component (b);
9088     }
9089   else if (b->ts.type == BT_CLASS)
9090     {
9091       gfc_add_vptr_component (b);
9092       gfc_add_hash_component (b);
9093     }
9094   else if (b->ts.type == BT_DERIVED)
9095     b = gfc_get_int_expr (gfc_default_integer_kind, NULL,
9096 			  b->ts.u.derived->hash_value);
9097 
9098   gfc_conv_expr (&se1, a);
9099   gfc_conv_expr (&se2, b);
9100 
9101   if (unlimited_poly_a)
9102     {
9103       conda = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
9104 			       se1.expr,
9105 			       build_int_cst (TREE_TYPE (se1.expr), 0));
9106       se1.expr = gfc_vptr_hash_get (se1.expr);
9107     }
9108 
9109   if (unlimited_poly_b)
9110     {
9111       condb = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
9112 			       se2.expr,
9113 			       build_int_cst (TREE_TYPE (se2.expr), 0));
9114       se2.expr = gfc_vptr_hash_get (se2.expr);
9115     }
9116 
9117   tmp = fold_build2_loc (input_location, EQ_EXPR,
9118 			 logical_type_node, se1.expr,
9119 			 fold_convert (TREE_TYPE (se1.expr), se2.expr));
9120 
9121   if (conda)
9122     tmp = fold_build2_loc (input_location, TRUTH_ANDIF_EXPR,
9123 			   logical_type_node, conda, tmp);
9124 
9125   if (condb)
9126     tmp = fold_build2_loc (input_location, TRUTH_ANDIF_EXPR,
9127 			   logical_type_node, condb, tmp);
9128 
9129   se->expr = convert (gfc_typenode_for_spec (&expr->ts), tmp);
9130 }
9131 
9132 
9133 /* Generate code for SELECTED_CHAR_KIND (NAME) intrinsic function.  */
9134 
9135 static void
gfc_conv_intrinsic_sc_kind(gfc_se * se,gfc_expr * expr)9136 gfc_conv_intrinsic_sc_kind (gfc_se *se, gfc_expr *expr)
9137 {
9138   tree args[2];
9139 
9140   gfc_conv_intrinsic_function_args (se, expr, args, 2);
9141   se->expr = build_call_expr_loc (input_location,
9142 			      gfor_fndecl_sc_kind, 2, args[0], args[1]);
9143   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), se->expr);
9144 }
9145 
9146 
9147 /* Generate code for SELECTED_INT_KIND (R) intrinsic function.  */
9148 
9149 static void
gfc_conv_intrinsic_si_kind(gfc_se * se,gfc_expr * expr)9150 gfc_conv_intrinsic_si_kind (gfc_se *se, gfc_expr *expr)
9151 {
9152   tree arg, type;
9153 
9154   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
9155 
9156   /* The argument to SELECTED_INT_KIND is INTEGER(4).  */
9157   type = gfc_get_int_type (4);
9158   arg = gfc_build_addr_expr (NULL_TREE, fold_convert (type, arg));
9159 
9160   /* Convert it to the required type.  */
9161   type = gfc_typenode_for_spec (&expr->ts);
9162   se->expr = build_call_expr_loc (input_location,
9163 			      gfor_fndecl_si_kind, 1, arg);
9164   se->expr = fold_convert (type, se->expr);
9165 }
9166 
9167 
9168 /* Generate code for SELECTED_REAL_KIND (P, R, RADIX) intrinsic function.  */
9169 
9170 static void
gfc_conv_intrinsic_sr_kind(gfc_se * se,gfc_expr * expr)9171 gfc_conv_intrinsic_sr_kind (gfc_se *se, gfc_expr *expr)
9172 {
9173   gfc_actual_arglist *actual;
9174   tree type;
9175   gfc_se argse;
9176   vec<tree, va_gc> *args = NULL;
9177 
9178   for (actual = expr->value.function.actual; actual; actual = actual->next)
9179     {
9180       gfc_init_se (&argse, se);
9181 
9182       /* Pass a NULL pointer for an absent arg.  */
9183       if (actual->expr == NULL)
9184         argse.expr = null_pointer_node;
9185       else
9186 	{
9187 	  gfc_typespec ts;
9188           gfc_clear_ts (&ts);
9189 
9190 	  if (actual->expr->ts.kind != gfc_c_int_kind)
9191 	    {
9192   	      /* The arguments to SELECTED_REAL_KIND are INTEGER(4).  */
9193 	      ts.type = BT_INTEGER;
9194 	      ts.kind = gfc_c_int_kind;
9195 	      gfc_convert_type (actual->expr, &ts, 2);
9196 	    }
9197 	  gfc_conv_expr_reference (&argse, actual->expr);
9198 	}
9199 
9200       gfc_add_block_to_block (&se->pre, &argse.pre);
9201       gfc_add_block_to_block (&se->post, &argse.post);
9202       vec_safe_push (args, argse.expr);
9203     }
9204 
9205   /* Convert it to the required type.  */
9206   type = gfc_typenode_for_spec (&expr->ts);
9207   se->expr = build_call_expr_loc_vec (input_location,
9208 				      gfor_fndecl_sr_kind, args);
9209   se->expr = fold_convert (type, se->expr);
9210 }
9211 
9212 
9213 /* Generate code for TRIM (A) intrinsic function.  */
9214 
9215 static void
gfc_conv_intrinsic_trim(gfc_se * se,gfc_expr * expr)9216 gfc_conv_intrinsic_trim (gfc_se * se, gfc_expr * expr)
9217 {
9218   tree var;
9219   tree len;
9220   tree addr;
9221   tree tmp;
9222   tree cond;
9223   tree fndecl;
9224   tree function;
9225   tree *args;
9226   unsigned int num_args;
9227 
9228   num_args = gfc_intrinsic_argument_list_length (expr) + 2;
9229   args = XALLOCAVEC (tree, num_args);
9230 
9231   var = gfc_create_var (gfc_get_pchar_type (expr->ts.kind), "pstr");
9232   addr = gfc_build_addr_expr (ppvoid_type_node, var);
9233   len = gfc_create_var (gfc_charlen_type_node, "len");
9234 
9235   gfc_conv_intrinsic_function_args (se, expr, &args[2], num_args - 2);
9236   args[0] = gfc_build_addr_expr (NULL_TREE, len);
9237   args[1] = addr;
9238 
9239   if (expr->ts.kind == 1)
9240     function = gfor_fndecl_string_trim;
9241   else if (expr->ts.kind == 4)
9242     function = gfor_fndecl_string_trim_char4;
9243   else
9244     gcc_unreachable ();
9245 
9246   fndecl = build_addr (function);
9247   tmp = build_call_array_loc (input_location,
9248 			  TREE_TYPE (TREE_TYPE (function)), fndecl,
9249 			  num_args, args);
9250   gfc_add_expr_to_block (&se->pre, tmp);
9251 
9252   /* Free the temporary afterwards, if necessary.  */
9253   cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
9254 			  len, build_int_cst (TREE_TYPE (len), 0));
9255   tmp = gfc_call_free (var);
9256   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
9257   gfc_add_expr_to_block (&se->post, tmp);
9258 
9259   se->expr = var;
9260   se->string_length = len;
9261 }
9262 
9263 
9264 /* Generate code for REPEAT (STRING, NCOPIES) intrinsic function.  */
9265 
9266 static void
gfc_conv_intrinsic_repeat(gfc_se * se,gfc_expr * expr)9267 gfc_conv_intrinsic_repeat (gfc_se * se, gfc_expr * expr)
9268 {
9269   tree args[3], ncopies, dest, dlen, src, slen, ncopies_type;
9270   tree type, cond, tmp, count, exit_label, n, max, largest;
9271   tree size;
9272   stmtblock_t block, body;
9273   int i;
9274 
9275   /* We store in charsize the size of a character.  */
9276   i = gfc_validate_kind (BT_CHARACTER, expr->ts.kind, false);
9277   size = build_int_cst (sizetype, gfc_character_kinds[i].bit_size / 8);
9278 
9279   /* Get the arguments.  */
9280   gfc_conv_intrinsic_function_args (se, expr, args, 3);
9281   slen = fold_convert (sizetype, gfc_evaluate_now (args[0], &se->pre));
9282   src = args[1];
9283   ncopies = gfc_evaluate_now (args[2], &se->pre);
9284   ncopies_type = TREE_TYPE (ncopies);
9285 
9286   /* Check that NCOPIES is not negative.  */
9287   cond = fold_build2_loc (input_location, LT_EXPR, logical_type_node, ncopies,
9288 			  build_int_cst (ncopies_type, 0));
9289   gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
9290 			   "Argument NCOPIES of REPEAT intrinsic is negative "
9291 			   "(its value is %ld)",
9292 			   fold_convert (long_integer_type_node, ncopies));
9293 
9294   /* If the source length is zero, any non negative value of NCOPIES
9295      is valid, and nothing happens.  */
9296   n = gfc_create_var (ncopies_type, "ncopies");
9297   cond = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, slen,
9298 			  size_zero_node);
9299   tmp = fold_build3_loc (input_location, COND_EXPR, ncopies_type, cond,
9300 			 build_int_cst (ncopies_type, 0), ncopies);
9301   gfc_add_modify (&se->pre, n, tmp);
9302   ncopies = n;
9303 
9304   /* Check that ncopies is not too large: ncopies should be less than
9305      (or equal to) MAX / slen, where MAX is the maximal integer of
9306      the gfc_charlen_type_node type.  If slen == 0, we need a special
9307      case to avoid the division by zero.  */
9308   max = fold_build2_loc (input_location, TRUNC_DIV_EXPR, sizetype,
9309 			 fold_convert (sizetype,
9310 				       TYPE_MAX_VALUE (gfc_charlen_type_node)),
9311 			 slen);
9312   largest = TYPE_PRECISION (sizetype) > TYPE_PRECISION (ncopies_type)
9313 	      ? sizetype : ncopies_type;
9314   cond = fold_build2_loc (input_location, GT_EXPR, logical_type_node,
9315 			  fold_convert (largest, ncopies),
9316 			  fold_convert (largest, max));
9317   tmp = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, slen,
9318 			 size_zero_node);
9319   cond = fold_build3_loc (input_location, COND_EXPR, logical_type_node, tmp,
9320 			  logical_false_node, cond);
9321   gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
9322 			   "Argument NCOPIES of REPEAT intrinsic is too large");
9323 
9324   /* Compute the destination length.  */
9325   dlen = fold_build2_loc (input_location, MULT_EXPR, gfc_charlen_type_node,
9326 			  fold_convert (gfc_charlen_type_node, slen),
9327 			  fold_convert (gfc_charlen_type_node, ncopies));
9328   type = gfc_get_character_type (expr->ts.kind, expr->ts.u.cl);
9329   dest = gfc_conv_string_tmp (se, build_pointer_type (type), dlen);
9330 
9331   /* Generate the code to do the repeat operation:
9332        for (i = 0; i < ncopies; i++)
9333          memmove (dest + (i * slen * size), src, slen*size);  */
9334   gfc_start_block (&block);
9335   count = gfc_create_var (sizetype, "count");
9336   gfc_add_modify (&block, count, size_zero_node);
9337   exit_label = gfc_build_label_decl (NULL_TREE);
9338 
9339   /* Start the loop body.  */
9340   gfc_start_block (&body);
9341 
9342   /* Exit the loop if count >= ncopies.  */
9343   cond = fold_build2_loc (input_location, GE_EXPR, logical_type_node, count,
9344 			  fold_convert (sizetype, ncopies));
9345   tmp = build1_v (GOTO_EXPR, exit_label);
9346   TREE_USED (exit_label) = 1;
9347   tmp = fold_build3_loc (input_location, COND_EXPR, void_type_node, cond, tmp,
9348 			 build_empty_stmt (input_location));
9349   gfc_add_expr_to_block (&body, tmp);
9350 
9351   /* Call memmove (dest + (i*slen*size), src, slen*size).  */
9352   tmp = fold_build2_loc (input_location, MULT_EXPR, sizetype, slen,
9353 			 count);
9354   tmp = fold_build2_loc (input_location, MULT_EXPR, sizetype, tmp,
9355 			 size);
9356   tmp = fold_build_pointer_plus_loc (input_location,
9357 				     fold_convert (pvoid_type_node, dest), tmp);
9358   tmp = build_call_expr_loc (input_location,
9359 			     builtin_decl_explicit (BUILT_IN_MEMMOVE),
9360 			     3, tmp, src,
9361 			     fold_build2_loc (input_location, MULT_EXPR,
9362 					      size_type_node, slen, size));
9363   gfc_add_expr_to_block (&body, tmp);
9364 
9365   /* Increment count.  */
9366   tmp = fold_build2_loc (input_location, PLUS_EXPR, sizetype,
9367 			 count, size_one_node);
9368   gfc_add_modify (&body, count, tmp);
9369 
9370   /* Build the loop.  */
9371   tmp = build1_v (LOOP_EXPR, gfc_finish_block (&body));
9372   gfc_add_expr_to_block (&block, tmp);
9373 
9374   /* Add the exit label.  */
9375   tmp = build1_v (LABEL_EXPR, exit_label);
9376   gfc_add_expr_to_block (&block, tmp);
9377 
9378   /* Finish the block.  */
9379   tmp = gfc_finish_block (&block);
9380   gfc_add_expr_to_block (&se->pre, tmp);
9381 
9382   /* Set the result value.  */
9383   se->expr = dest;
9384   se->string_length = dlen;
9385 }
9386 
9387 
9388 /* Generate code for the IARGC intrinsic.  */
9389 
9390 static void
gfc_conv_intrinsic_iargc(gfc_se * se,gfc_expr * expr)9391 gfc_conv_intrinsic_iargc (gfc_se * se, gfc_expr * expr)
9392 {
9393   tree tmp;
9394   tree fndecl;
9395   tree type;
9396 
9397   /* Call the library function.  This always returns an INTEGER(4).  */
9398   fndecl = gfor_fndecl_iargc;
9399   tmp = build_call_expr_loc (input_location,
9400 			 fndecl, 0);
9401 
9402   /* Convert it to the required type.  */
9403   type = gfc_typenode_for_spec (&expr->ts);
9404   tmp = fold_convert (type, tmp);
9405 
9406   se->expr = tmp;
9407 }
9408 
9409 
9410 /* Generate code for the KILL intrinsic.  */
9411 
9412 static void
conv_intrinsic_kill(gfc_se * se,gfc_expr * expr)9413 conv_intrinsic_kill (gfc_se *se, gfc_expr *expr)
9414 {
9415   tree *args;
9416   tree int4_type_node = gfc_get_int_type (4);
9417   tree pid;
9418   tree sig;
9419   tree tmp;
9420   unsigned int num_args;
9421 
9422   num_args = gfc_intrinsic_argument_list_length (expr);
9423   args = XALLOCAVEC (tree, num_args);
9424   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
9425 
9426   /* Convert PID to a INTEGER(4) entity.  */
9427   pid = convert (int4_type_node, args[0]);
9428 
9429   /* Convert SIG to a INTEGER(4) entity.  */
9430   sig = convert (int4_type_node, args[1]);
9431 
9432   tmp = build_call_expr_loc (input_location, gfor_fndecl_kill, 2, pid, sig);
9433 
9434   se->expr = fold_convert (TREE_TYPE (args[0]), tmp);
9435 }
9436 
9437 
9438 static tree
conv_intrinsic_kill_sub(gfc_code * code)9439 conv_intrinsic_kill_sub (gfc_code *code)
9440 {
9441   stmtblock_t block;
9442   gfc_se se, se_stat;
9443   tree int4_type_node = gfc_get_int_type (4);
9444   tree pid;
9445   tree sig;
9446   tree statp;
9447   tree tmp;
9448 
9449   /* Make the function call.  */
9450   gfc_init_block (&block);
9451   gfc_init_se (&se, NULL);
9452 
9453   /* Convert PID to a INTEGER(4) entity.  */
9454   gfc_conv_expr (&se, code->ext.actual->expr);
9455   gfc_add_block_to_block (&block, &se.pre);
9456   pid = fold_convert (int4_type_node, gfc_evaluate_now (se.expr, &block));
9457   gfc_add_block_to_block (&block, &se.post);
9458 
9459   /* Convert SIG to a INTEGER(4) entity.  */
9460   gfc_conv_expr (&se, code->ext.actual->next->expr);
9461   gfc_add_block_to_block (&block, &se.pre);
9462   sig = fold_convert (int4_type_node, gfc_evaluate_now (se.expr, &block));
9463   gfc_add_block_to_block (&block, &se.post);
9464 
9465   /* Deal with an optional STATUS.  */
9466   if (code->ext.actual->next->next->expr)
9467     {
9468       gfc_init_se (&se_stat, NULL);
9469       gfc_conv_expr (&se_stat, code->ext.actual->next->next->expr);
9470       statp = gfc_create_var (gfc_get_int_type (4), "_statp");
9471     }
9472   else
9473     statp = NULL_TREE;
9474 
9475   tmp = build_call_expr_loc (input_location, gfor_fndecl_kill_sub, 3, pid, sig,
9476 	statp ? gfc_build_addr_expr (NULL_TREE, statp) : null_pointer_node);
9477 
9478   gfc_add_expr_to_block (&block, tmp);
9479 
9480   if (statp && statp != se_stat.expr)
9481     gfc_add_modify (&block, se_stat.expr,
9482 		    fold_convert (TREE_TYPE (se_stat.expr), statp));
9483 
9484   return gfc_finish_block (&block);
9485 }
9486 
9487 
9488 
9489 /* The loc intrinsic returns the address of its argument as
9490    gfc_index_integer_kind integer.  */
9491 
9492 static void
gfc_conv_intrinsic_loc(gfc_se * se,gfc_expr * expr)9493 gfc_conv_intrinsic_loc (gfc_se * se, gfc_expr * expr)
9494 {
9495   tree temp_var;
9496   gfc_expr *arg_expr;
9497 
9498   gcc_assert (!se->ss);
9499 
9500   arg_expr = expr->value.function.actual->expr;
9501   if (arg_expr->rank == 0)
9502     {
9503       if (arg_expr->ts.type == BT_CLASS)
9504 	gfc_add_data_component (arg_expr);
9505       gfc_conv_expr_reference (se, arg_expr);
9506     }
9507   else
9508     gfc_conv_array_parameter (se, arg_expr, true, NULL, NULL, NULL);
9509   se->expr = convert (gfc_get_int_type (gfc_index_integer_kind), se->expr);
9510 
9511   /* Create a temporary variable for loc return value.  Without this,
9512      we get an error an ICE in gcc/expr.cc(expand_expr_addr_expr_1).  */
9513   temp_var = gfc_create_var (gfc_get_int_type (gfc_index_integer_kind), NULL);
9514   gfc_add_modify (&se->pre, temp_var, se->expr);
9515   se->expr = temp_var;
9516 }
9517 
9518 
9519 /* The following routine generates code for the intrinsic
9520    functions from the ISO_C_BINDING module:
9521     * C_LOC
9522     * C_FUNLOC
9523     * C_ASSOCIATED  */
9524 
9525 static void
conv_isocbinding_function(gfc_se * se,gfc_expr * expr)9526 conv_isocbinding_function (gfc_se *se, gfc_expr *expr)
9527 {
9528   gfc_actual_arglist *arg = expr->value.function.actual;
9529 
9530   if (expr->value.function.isym->id == GFC_ISYM_C_LOC)
9531     {
9532       if (arg->expr->rank == 0)
9533 	gfc_conv_expr_reference (se, arg->expr);
9534       else if (gfc_is_simply_contiguous (arg->expr, false, false))
9535 	gfc_conv_array_parameter (se, arg->expr, true, NULL, NULL, NULL);
9536       else
9537 	{
9538 	  gfc_conv_expr_descriptor (se, arg->expr);
9539 	  se->expr = gfc_conv_descriptor_data_get (se->expr);
9540 	}
9541 
9542       /* TODO -- the following two lines shouldn't be necessary, but if
9543 	 they're removed, a bug is exposed later in the code path.
9544 	 This workaround was thus introduced, but will have to be
9545 	 removed; please see PR 35150 for details about the issue.  */
9546       se->expr = convert (pvoid_type_node, se->expr);
9547       se->expr = gfc_evaluate_now (se->expr, &se->pre);
9548     }
9549   else if (expr->value.function.isym->id == GFC_ISYM_C_FUNLOC)
9550     gfc_conv_expr_reference (se, arg->expr);
9551   else if (expr->value.function.isym->id == GFC_ISYM_C_ASSOCIATED)
9552     {
9553       gfc_se arg1se;
9554       gfc_se arg2se;
9555 
9556       /* Build the addr_expr for the first argument.  The argument is
9557 	 already an *address* so we don't need to set want_pointer in
9558 	 the gfc_se.  */
9559       gfc_init_se (&arg1se, NULL);
9560       gfc_conv_expr (&arg1se, arg->expr);
9561       gfc_add_block_to_block (&se->pre, &arg1se.pre);
9562       gfc_add_block_to_block (&se->post, &arg1se.post);
9563 
9564       /* See if we were given two arguments.  */
9565       if (arg->next->expr == NULL)
9566 	/* Only given one arg so generate a null and do a
9567 	   not-equal comparison against the first arg.  */
9568 	se->expr = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
9569 				    arg1se.expr,
9570 				    fold_convert (TREE_TYPE (arg1se.expr),
9571 						  null_pointer_node));
9572       else
9573 	{
9574 	  tree eq_expr;
9575 	  tree not_null_expr;
9576 
9577 	  /* Given two arguments so build the arg2se from second arg.  */
9578 	  gfc_init_se (&arg2se, NULL);
9579 	  gfc_conv_expr (&arg2se, arg->next->expr);
9580 	  gfc_add_block_to_block (&se->pre, &arg2se.pre);
9581 	  gfc_add_block_to_block (&se->post, &arg2se.post);
9582 
9583 	  /* Generate test to compare that the two args are equal.  */
9584 	  eq_expr = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
9585 				     arg1se.expr, arg2se.expr);
9586 	  /* Generate test to ensure that the first arg is not null.  */
9587 	  not_null_expr = fold_build2_loc (input_location, NE_EXPR,
9588 					   logical_type_node,
9589 					   arg1se.expr, null_pointer_node);
9590 
9591 	  /* Finally, the generated test must check that both arg1 is not
9592 	     NULL and that it is equal to the second arg.  */
9593 	  se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
9594 				      logical_type_node,
9595 				      not_null_expr, eq_expr);
9596 	}
9597     }
9598   else
9599     gcc_unreachable ();
9600 }
9601 
9602 
9603 /* The following routine generates code for the intrinsic
9604    subroutines from the ISO_C_BINDING module:
9605     * C_F_POINTER
9606     * C_F_PROCPOINTER.  */
9607 
9608 static tree
conv_isocbinding_subroutine(gfc_code * code)9609 conv_isocbinding_subroutine (gfc_code *code)
9610 {
9611   gfc_se se;
9612   gfc_se cptrse;
9613   gfc_se fptrse;
9614   gfc_se shapese;
9615   gfc_ss *shape_ss;
9616   tree desc, dim, tmp, stride, offset;
9617   stmtblock_t body, block;
9618   gfc_loopinfo loop;
9619   gfc_actual_arglist *arg = code->ext.actual;
9620 
9621   gfc_init_se (&se, NULL);
9622   gfc_init_se (&cptrse, NULL);
9623   gfc_conv_expr (&cptrse, arg->expr);
9624   gfc_add_block_to_block (&se.pre, &cptrse.pre);
9625   gfc_add_block_to_block (&se.post, &cptrse.post);
9626 
9627   gfc_init_se (&fptrse, NULL);
9628   if (arg->next->expr->rank == 0)
9629     {
9630       fptrse.want_pointer = 1;
9631       gfc_conv_expr (&fptrse, arg->next->expr);
9632       gfc_add_block_to_block (&se.pre, &fptrse.pre);
9633       gfc_add_block_to_block (&se.post, &fptrse.post);
9634       if (arg->next->expr->symtree->n.sym->attr.proc_pointer
9635 	  && arg->next->expr->symtree->n.sym->attr.dummy)
9636 	fptrse.expr = build_fold_indirect_ref_loc (input_location,
9637 						       fptrse.expr);
9638       se.expr = fold_build2_loc (input_location, MODIFY_EXPR,
9639 				 TREE_TYPE (fptrse.expr),
9640 				 fptrse.expr,
9641 				 fold_convert (TREE_TYPE (fptrse.expr),
9642 					       cptrse.expr));
9643       gfc_add_expr_to_block (&se.pre, se.expr);
9644       gfc_add_block_to_block (&se.pre, &se.post);
9645       return gfc_finish_block (&se.pre);
9646     }
9647 
9648   gfc_start_block (&block);
9649 
9650   /* Get the descriptor of the Fortran pointer.  */
9651   fptrse.descriptor_only = 1;
9652   gfc_conv_expr_descriptor (&fptrse, arg->next->expr);
9653   gfc_add_block_to_block (&block, &fptrse.pre);
9654   desc = fptrse.expr;
9655 
9656   /* Set the span field.  */
9657   tmp = TYPE_SIZE_UNIT (gfc_get_element_type (TREE_TYPE (desc)));
9658   tmp = fold_convert (gfc_array_index_type, tmp);
9659   gfc_conv_descriptor_span_set (&block, desc, tmp);
9660 
9661   /* Set data value, dtype, and offset.  */
9662   tmp = GFC_TYPE_ARRAY_DATAPTR_TYPE (TREE_TYPE (desc));
9663   gfc_conv_descriptor_data_set (&block, desc, fold_convert (tmp, cptrse.expr));
9664   gfc_add_modify (&block, gfc_conv_descriptor_dtype (desc),
9665 		  gfc_get_dtype (TREE_TYPE (desc)));
9666 
9667   /* Start scalarization of the bounds, using the shape argument.  */
9668 
9669   shape_ss = gfc_walk_expr (arg->next->next->expr);
9670   gcc_assert (shape_ss != gfc_ss_terminator);
9671   gfc_init_se (&shapese, NULL);
9672 
9673   gfc_init_loopinfo (&loop);
9674   gfc_add_ss_to_loop (&loop, shape_ss);
9675   gfc_conv_ss_startstride (&loop);
9676   gfc_conv_loop_setup (&loop, &arg->next->expr->where);
9677   gfc_mark_ss_chain_used (shape_ss, 1);
9678 
9679   gfc_copy_loopinfo_to_se (&shapese, &loop);
9680   shapese.ss = shape_ss;
9681 
9682   stride = gfc_create_var (gfc_array_index_type, "stride");
9683   offset = gfc_create_var (gfc_array_index_type, "offset");
9684   gfc_add_modify (&block, stride, gfc_index_one_node);
9685   gfc_add_modify (&block, offset, gfc_index_zero_node);
9686 
9687   /* Loop body.  */
9688   gfc_start_scalarized_body (&loop, &body);
9689 
9690   dim = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
9691 			     loop.loopvar[0], loop.from[0]);
9692 
9693   /* Set bounds and stride.  */
9694   gfc_conv_descriptor_lbound_set (&body, desc, dim, gfc_index_one_node);
9695   gfc_conv_descriptor_stride_set (&body, desc, dim, stride);
9696 
9697   gfc_conv_expr (&shapese, arg->next->next->expr);
9698   gfc_add_block_to_block (&body, &shapese.pre);
9699   gfc_conv_descriptor_ubound_set (&body, desc, dim, shapese.expr);
9700   gfc_add_block_to_block (&body, &shapese.post);
9701 
9702   /* Calculate offset.  */
9703   gfc_add_modify (&body, offset,
9704 		  fold_build2_loc (input_location, PLUS_EXPR,
9705 				   gfc_array_index_type, offset, stride));
9706   /* Update stride.  */
9707   gfc_add_modify (&body, stride,
9708 		  fold_build2_loc (input_location, MULT_EXPR,
9709 				   gfc_array_index_type, stride,
9710 				   fold_convert (gfc_array_index_type,
9711 						 shapese.expr)));
9712   /* Finish scalarization loop.  */
9713   gfc_trans_scalarizing_loops (&loop, &body);
9714   gfc_add_block_to_block (&block, &loop.pre);
9715   gfc_add_block_to_block (&block, &loop.post);
9716   gfc_add_block_to_block (&block, &fptrse.post);
9717   gfc_cleanup_loop (&loop);
9718 
9719   gfc_add_modify (&block, offset,
9720 		  fold_build1_loc (input_location, NEGATE_EXPR,
9721 				   gfc_array_index_type, offset));
9722   gfc_conv_descriptor_offset_set (&block, desc, offset);
9723 
9724   gfc_add_expr_to_block (&se.pre, gfc_finish_block (&block));
9725   gfc_add_block_to_block (&se.pre, &se.post);
9726   return gfc_finish_block (&se.pre);
9727 }
9728 
9729 
9730 /* Save and restore floating-point state.  */
9731 
9732 tree
gfc_save_fp_state(stmtblock_t * block)9733 gfc_save_fp_state (stmtblock_t *block)
9734 {
9735   tree type, fpstate, tmp;
9736 
9737   type = build_array_type (char_type_node,
9738 	                   build_range_type (size_type_node, size_zero_node,
9739 					     size_int (GFC_FPE_STATE_BUFFER_SIZE)));
9740   fpstate = gfc_create_var (type, "fpstate");
9741   fpstate = gfc_build_addr_expr (pvoid_type_node, fpstate);
9742 
9743   tmp = build_call_expr_loc (input_location, gfor_fndecl_ieee_procedure_entry,
9744 			     1, fpstate);
9745   gfc_add_expr_to_block (block, tmp);
9746 
9747   return fpstate;
9748 }
9749 
9750 
9751 void
gfc_restore_fp_state(stmtblock_t * block,tree fpstate)9752 gfc_restore_fp_state (stmtblock_t *block, tree fpstate)
9753 {
9754   tree tmp;
9755 
9756   tmp = build_call_expr_loc (input_location, gfor_fndecl_ieee_procedure_exit,
9757 			     1, fpstate);
9758   gfc_add_expr_to_block (block, tmp);
9759 }
9760 
9761 
9762 /* Generate code for arguments of IEEE functions.  */
9763 
9764 static void
conv_ieee_function_args(gfc_se * se,gfc_expr * expr,tree * argarray,int nargs)9765 conv_ieee_function_args (gfc_se *se, gfc_expr *expr, tree *argarray,
9766 			 int nargs)
9767 {
9768   gfc_actual_arglist *actual;
9769   gfc_expr *e;
9770   gfc_se argse;
9771   int arg;
9772 
9773   actual = expr->value.function.actual;
9774   for (arg = 0; arg < nargs; arg++, actual = actual->next)
9775     {
9776       gcc_assert (actual);
9777       e = actual->expr;
9778 
9779       gfc_init_se (&argse, se);
9780       gfc_conv_expr_val (&argse, e);
9781 
9782       gfc_add_block_to_block (&se->pre, &argse.pre);
9783       gfc_add_block_to_block (&se->post, &argse.post);
9784       argarray[arg] = argse.expr;
9785     }
9786 }
9787 
9788 
9789 /* Generate code for intrinsics IEEE_IS_NAN, IEEE_IS_FINITE,
9790    and IEEE_UNORDERED, which translate directly to GCC type-generic
9791    built-ins.  */
9792 
9793 static void
conv_intrinsic_ieee_builtin(gfc_se * se,gfc_expr * expr,enum built_in_function code,int nargs)9794 conv_intrinsic_ieee_builtin (gfc_se * se, gfc_expr * expr,
9795 			     enum built_in_function code, int nargs)
9796 {
9797   tree args[2];
9798   gcc_assert ((unsigned) nargs <= sizeof(args)/sizeof(args[0]));
9799 
9800   conv_ieee_function_args (se, expr, args, nargs);
9801   se->expr = build_call_expr_loc_array (input_location,
9802 					builtin_decl_explicit (code),
9803 					nargs, args);
9804   STRIP_TYPE_NOPS (se->expr);
9805   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), se->expr);
9806 }
9807 
9808 
9809 /* Generate code for IEEE_IS_NORMAL intrinsic:
9810      IEEE_IS_NORMAL(x) --> (__builtin_isnormal(x) || x == 0)  */
9811 
9812 static void
conv_intrinsic_ieee_is_normal(gfc_se * se,gfc_expr * expr)9813 conv_intrinsic_ieee_is_normal (gfc_se * se, gfc_expr * expr)
9814 {
9815   tree arg, isnormal, iszero;
9816 
9817   /* Convert arg, evaluate it only once.  */
9818   conv_ieee_function_args (se, expr, &arg, 1);
9819   arg = gfc_evaluate_now (arg, &se->pre);
9820 
9821   isnormal = build_call_expr_loc (input_location,
9822 				  builtin_decl_explicit (BUILT_IN_ISNORMAL),
9823 				  1, arg);
9824   iszero = fold_build2_loc (input_location, EQ_EXPR, logical_type_node, arg,
9825 			    build_real_from_int_cst (TREE_TYPE (arg),
9826 						     integer_zero_node));
9827   se->expr = fold_build2_loc (input_location, TRUTH_OR_EXPR,
9828 			      logical_type_node, isnormal, iszero);
9829   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), se->expr);
9830 }
9831 
9832 
9833 /* Generate code for IEEE_IS_NEGATIVE intrinsic:
9834      IEEE_IS_NEGATIVE(x) --> (__builtin_signbit(x) && !__builtin_isnan(x))  */
9835 
9836 static void
conv_intrinsic_ieee_is_negative(gfc_se * se,gfc_expr * expr)9837 conv_intrinsic_ieee_is_negative (gfc_se * se, gfc_expr * expr)
9838 {
9839   tree arg, signbit, isnan;
9840 
9841   /* Convert arg, evaluate it only once.  */
9842   conv_ieee_function_args (se, expr, &arg, 1);
9843   arg = gfc_evaluate_now (arg, &se->pre);
9844 
9845   isnan = build_call_expr_loc (input_location,
9846 			       builtin_decl_explicit (BUILT_IN_ISNAN),
9847 			       1, arg);
9848   STRIP_TYPE_NOPS (isnan);
9849 
9850   signbit = build_call_expr_loc (input_location,
9851 				 builtin_decl_explicit (BUILT_IN_SIGNBIT),
9852 				 1, arg);
9853   signbit = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
9854 			     signbit, integer_zero_node);
9855 
9856   se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
9857 			      logical_type_node, signbit,
9858 			      fold_build1_loc (input_location, TRUTH_NOT_EXPR,
9859 					       TREE_TYPE(isnan), isnan));
9860 
9861   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), se->expr);
9862 }
9863 
9864 
9865 /* Generate code for IEEE_LOGB and IEEE_RINT.  */
9866 
9867 static void
conv_intrinsic_ieee_logb_rint(gfc_se * se,gfc_expr * expr,enum built_in_function code)9868 conv_intrinsic_ieee_logb_rint (gfc_se * se, gfc_expr * expr,
9869 			       enum built_in_function code)
9870 {
9871   tree arg, decl, call, fpstate;
9872   int argprec;
9873 
9874   conv_ieee_function_args (se, expr, &arg, 1);
9875   argprec = TYPE_PRECISION (TREE_TYPE (arg));
9876   decl = builtin_decl_for_precision (code, argprec);
9877 
9878   /* Save floating-point state.  */
9879   fpstate = gfc_save_fp_state (&se->pre);
9880 
9881   /* Make the function call.  */
9882   call = build_call_expr_loc (input_location, decl, 1, arg);
9883   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), call);
9884 
9885   /* Restore floating-point state.  */
9886   gfc_restore_fp_state (&se->post, fpstate);
9887 }
9888 
9889 
9890 /* Generate code for IEEE_REM.  */
9891 
9892 static void
conv_intrinsic_ieee_rem(gfc_se * se,gfc_expr * expr)9893 conv_intrinsic_ieee_rem (gfc_se * se, gfc_expr * expr)
9894 {
9895   tree args[2], decl, call, fpstate;
9896   int argprec;
9897 
9898   conv_ieee_function_args (se, expr, args, 2);
9899 
9900   /* If arguments have unequal size, convert them to the larger.  */
9901   if (TYPE_PRECISION (TREE_TYPE (args[0]))
9902       > TYPE_PRECISION (TREE_TYPE (args[1])))
9903     args[1] = fold_convert (TREE_TYPE (args[0]), args[1]);
9904   else if (TYPE_PRECISION (TREE_TYPE (args[1]))
9905 	   > TYPE_PRECISION (TREE_TYPE (args[0])))
9906     args[0] = fold_convert (TREE_TYPE (args[1]), args[0]);
9907 
9908   argprec = TYPE_PRECISION (TREE_TYPE (args[0]));
9909   decl = builtin_decl_for_precision (BUILT_IN_REMAINDER, argprec);
9910 
9911   /* Save floating-point state.  */
9912   fpstate = gfc_save_fp_state (&se->pre);
9913 
9914   /* Make the function call.  */
9915   call = build_call_expr_loc_array (input_location, decl, 2, args);
9916   se->expr = fold_convert (TREE_TYPE (args[0]), call);
9917 
9918   /* Restore floating-point state.  */
9919   gfc_restore_fp_state (&se->post, fpstate);
9920 }
9921 
9922 
9923 /* Generate code for IEEE_NEXT_AFTER.  */
9924 
9925 static void
conv_intrinsic_ieee_next_after(gfc_se * se,gfc_expr * expr)9926 conv_intrinsic_ieee_next_after (gfc_se * se, gfc_expr * expr)
9927 {
9928   tree args[2], decl, call, fpstate;
9929   int argprec;
9930 
9931   conv_ieee_function_args (se, expr, args, 2);
9932 
9933   /* Result has the characteristics of first argument.  */
9934   args[1] = fold_convert (TREE_TYPE (args[0]), args[1]);
9935   argprec = TYPE_PRECISION (TREE_TYPE (args[0]));
9936   decl = builtin_decl_for_precision (BUILT_IN_NEXTAFTER, argprec);
9937 
9938   /* Save floating-point state.  */
9939   fpstate = gfc_save_fp_state (&se->pre);
9940 
9941   /* Make the function call.  */
9942   call = build_call_expr_loc_array (input_location, decl, 2, args);
9943   se->expr = fold_convert (TREE_TYPE (args[0]), call);
9944 
9945   /* Restore floating-point state.  */
9946   gfc_restore_fp_state (&se->post, fpstate);
9947 }
9948 
9949 
9950 /* Generate code for IEEE_SCALB.  */
9951 
9952 static void
conv_intrinsic_ieee_scalb(gfc_se * se,gfc_expr * expr)9953 conv_intrinsic_ieee_scalb (gfc_se * se, gfc_expr * expr)
9954 {
9955   tree args[2], decl, call, huge, type;
9956   int argprec, n;
9957 
9958   conv_ieee_function_args (se, expr, args, 2);
9959 
9960   /* Result has the characteristics of first argument.  */
9961   argprec = TYPE_PRECISION (TREE_TYPE (args[0]));
9962   decl = builtin_decl_for_precision (BUILT_IN_SCALBN, argprec);
9963 
9964   if (TYPE_PRECISION (TREE_TYPE (args[1])) > TYPE_PRECISION (integer_type_node))
9965     {
9966       /* We need to fold the integer into the range of a C int.  */
9967       args[1] = gfc_evaluate_now (args[1], &se->pre);
9968       type = TREE_TYPE (args[1]);
9969 
9970       n = gfc_validate_kind (BT_INTEGER, gfc_c_int_kind, false);
9971       huge = gfc_conv_mpz_to_tree (gfc_integer_kinds[n].huge,
9972 				   gfc_c_int_kind);
9973       huge = fold_convert (type, huge);
9974       args[1] = fold_build2_loc (input_location, MIN_EXPR, type, args[1],
9975 				 huge);
9976       args[1] = fold_build2_loc (input_location, MAX_EXPR, type, args[1],
9977 				 fold_build1_loc (input_location, NEGATE_EXPR,
9978 						  type, huge));
9979     }
9980 
9981   args[1] = fold_convert (integer_type_node, args[1]);
9982 
9983   /* Make the function call.  */
9984   call = build_call_expr_loc_array (input_location, decl, 2, args);
9985   se->expr = fold_convert (TREE_TYPE (args[0]), call);
9986 }
9987 
9988 
9989 /* Generate code for IEEE_COPY_SIGN.  */
9990 
9991 static void
conv_intrinsic_ieee_copy_sign(gfc_se * se,gfc_expr * expr)9992 conv_intrinsic_ieee_copy_sign (gfc_se * se, gfc_expr * expr)
9993 {
9994   tree args[2], decl, sign;
9995   int argprec;
9996 
9997   conv_ieee_function_args (se, expr, args, 2);
9998 
9999   /* Get the sign of the second argument.  */
10000   sign = build_call_expr_loc (input_location,
10001 			      builtin_decl_explicit (BUILT_IN_SIGNBIT),
10002 			      1, args[1]);
10003   sign = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
10004 			  sign, integer_zero_node);
10005 
10006   /* Create a value of one, with the right sign.  */
10007   sign = fold_build3_loc (input_location, COND_EXPR, integer_type_node,
10008 			  sign,
10009 			  fold_build1_loc (input_location, NEGATE_EXPR,
10010 					   integer_type_node,
10011 					   integer_one_node),
10012 			  integer_one_node);
10013   args[1] = fold_convert (TREE_TYPE (args[0]), sign);
10014 
10015   argprec = TYPE_PRECISION (TREE_TYPE (args[0]));
10016   decl = builtin_decl_for_precision (BUILT_IN_COPYSIGN, argprec);
10017 
10018   se->expr = build_call_expr_loc_array (input_location, decl, 2, args);
10019 }
10020 
10021 
10022 /* Generate code for IEEE_CLASS.  */
10023 
10024 static bool
conv_intrinsic_ieee_class(gfc_se * se,gfc_expr * expr)10025 conv_intrinsic_ieee_class (gfc_se *se, gfc_expr *expr)
10026 {
10027   tree arg, c, t1, t2, t3, t4;
10028 
10029   /* In GCC 12, handle inline only the powerpc64le-linux IEEE quad
10030      real(kind=16) and nothing else.  */
10031   if (gfc_type_abi_kind (&expr->value.function.actual->expr->ts) != 17)
10032     return false;
10033 
10034   /* Convert arg, evaluate it only once.  */
10035   conv_ieee_function_args (se, expr, &arg, 1);
10036   arg = gfc_evaluate_now (arg, &se->pre);
10037 
10038   c = build_call_expr_loc (input_location,
10039 			   builtin_decl_explicit (BUILT_IN_FPCLASSIFY), 6,
10040 			   build_int_cst (integer_type_node, IEEE_QUIET_NAN),
10041 			   build_int_cst (integer_type_node,
10042 					  IEEE_POSITIVE_INF),
10043 			   build_int_cst (integer_type_node,
10044 					  IEEE_POSITIVE_NORMAL),
10045 			   build_int_cst (integer_type_node,
10046 					  IEEE_POSITIVE_DENORMAL),
10047 			   build_int_cst (integer_type_node,
10048 					  IEEE_POSITIVE_ZERO),
10049 			   arg);
10050   c = gfc_evaluate_now (c, &se->pre);
10051   t1 = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
10052 			c, build_int_cst (integer_type_node,
10053 					  IEEE_QUIET_NAN));
10054   /* In GCC 12, we don't have __builtin_issignaling but above we made
10055      sure arg is powerpc64le-linux IEEE quad real(kind=16).
10056      When we check it is some kind of NaN by fpclassify, all we need
10057      is check the ((__int128) 1) << 111 bit, if it is zero, it is a sNaN,
10058      if it is set, it is a qNaN.  */
10059   t2 = fold_build1_loc (input_location, VIEW_CONVERT_EXPR,
10060 			build_nonstandard_integer_type (128, 1), arg);
10061   t2 = fold_build2_loc (input_location, RSHIFT_EXPR, TREE_TYPE (t2), t2,
10062 			build_int_cst (integer_type_node, 111));
10063   t2 = fold_convert (integer_type_node, t2);
10064   t2 = fold_build2_loc (input_location, BIT_AND_EXPR, integer_type_node,
10065 			t2, integer_one_node);
10066   t2 = fold_build2_loc (input_location, EQ_EXPR, logical_type_node,
10067 			t2, build_zero_cst (TREE_TYPE (t2)));
10068   t1 = fold_build2_loc (input_location, TRUTH_AND_EXPR,
10069 			logical_type_node, t1, t2);
10070   t3 = fold_build2_loc (input_location, GE_EXPR, logical_type_node,
10071 			c, build_int_cst (integer_type_node,
10072 					  IEEE_POSITIVE_ZERO));
10073   t4 = build_call_expr_loc (input_location,
10074 			    builtin_decl_explicit (BUILT_IN_SIGNBIT), 1,
10075 			    arg);
10076   t4 = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
10077 			t4, build_zero_cst (TREE_TYPE (t4)));
10078   t3 = fold_build2_loc (input_location, TRUTH_AND_EXPR,
10079 			logical_type_node, t3, t4);
10080   int s = IEEE_NEGATIVE_ZERO + IEEE_POSITIVE_ZERO;
10081   gcc_assert (IEEE_NEGATIVE_INF == s - IEEE_POSITIVE_INF);
10082   gcc_assert (IEEE_NEGATIVE_NORMAL == s - IEEE_POSITIVE_NORMAL);
10083   gcc_assert (IEEE_NEGATIVE_DENORMAL == s - IEEE_POSITIVE_DENORMAL);
10084   gcc_assert (IEEE_NEGATIVE_SUBNORMAL == s - IEEE_POSITIVE_SUBNORMAL);
10085   gcc_assert (IEEE_NEGATIVE_ZERO == s - IEEE_POSITIVE_ZERO);
10086   t4 = fold_build2_loc (input_location, MINUS_EXPR, TREE_TYPE (c),
10087 			build_int_cst (TREE_TYPE (c), s), c);
10088   t3 = fold_build3_loc (input_location, COND_EXPR, TREE_TYPE (c),
10089 			t3, t4, c);
10090   t1 = fold_build3_loc (input_location, COND_EXPR, TREE_TYPE (c), t1,
10091 			build_int_cst (TREE_TYPE (c), IEEE_SIGNALING_NAN),
10092 			t3);
10093   tree type = gfc_typenode_for_spec (&expr->ts);
10094   /* Perform a quick sanity check that the return type is
10095      IEEE_CLASS_TYPE derived type defined in
10096      libgfortran/ieee/ieee_arithmetic.F90
10097      Primarily check that it is a derived type with a single
10098      member in it.  */
10099   gcc_assert (TREE_CODE (type) == RECORD_TYPE);
10100   tree field = NULL_TREE;
10101   for (tree f = TYPE_FIELDS (type); f != NULL_TREE; f = DECL_CHAIN (f))
10102     if (TREE_CODE (f) == FIELD_DECL)
10103       {
10104 	gcc_assert (field == NULL_TREE);
10105 	field = f;
10106       }
10107   gcc_assert (field);
10108   t1 = fold_convert (TREE_TYPE (field), t1);
10109   se->expr = build_constructor_single (type, field, t1);
10110   return true;
10111 }
10112 
10113 
10114 /* Generate code for IEEE_VALUE.  */
10115 
10116 static bool
conv_intrinsic_ieee_value(gfc_se * se,gfc_expr * expr)10117 conv_intrinsic_ieee_value (gfc_se *se, gfc_expr *expr)
10118 {
10119   tree args[2], arg, ret, tmp;
10120   stmtblock_t body;
10121 
10122   /* In GCC 12, handle inline only the powerpc64le-linux IEEE quad
10123      real(kind=16) and nothing else.  */
10124   if (gfc_type_abi_kind (&expr->ts) != 17)
10125     return false;
10126 
10127   /* Convert args, evaluate the second one only once.  */
10128   conv_ieee_function_args (se, expr, args, 2);
10129   arg = gfc_evaluate_now (args[1], &se->pre);
10130 
10131   tree type = TREE_TYPE (arg);
10132   /* Perform a quick sanity check that the second argument's type is
10133      IEEE_CLASS_TYPE derived type defined in
10134      libgfortran/ieee/ieee_arithmetic.F90
10135      Primarily check that it is a derived type with a single
10136      member in it.  */
10137   gcc_assert (TREE_CODE (type) == RECORD_TYPE);
10138   tree field = NULL_TREE;
10139   for (tree f = TYPE_FIELDS (type); f != NULL_TREE; f = DECL_CHAIN (f))
10140     if (TREE_CODE (f) == FIELD_DECL)
10141       {
10142 	gcc_assert (field == NULL_TREE);
10143 	field = f;
10144       }
10145   gcc_assert (field);
10146   arg = fold_build3_loc (input_location, COMPONENT_REF, TREE_TYPE (field),
10147 			 arg, field, NULL_TREE);
10148   arg = gfc_evaluate_now (arg, &se->pre);
10149 
10150   type = gfc_typenode_for_spec (&expr->ts);
10151   gcc_assert (TREE_CODE (type) == REAL_TYPE);
10152   ret = gfc_create_var (type, NULL);
10153 
10154   gfc_init_block (&body);
10155 
10156   tree end_label = gfc_build_label_decl (NULL_TREE);
10157   for (int c = IEEE_SIGNALING_NAN; c <= IEEE_POSITIVE_INF; ++c)
10158     {
10159       tree label = gfc_build_label_decl (NULL_TREE);
10160       tree low = build_int_cst (TREE_TYPE (arg), c);
10161       tmp = build_case_label (low, low, label);
10162       gfc_add_expr_to_block (&body, tmp);
10163 
10164       REAL_VALUE_TYPE real;
10165       int k;
10166       switch (c)
10167 	{
10168 	case IEEE_SIGNALING_NAN:
10169 	  real_nan (&real, "", 0, TYPE_MODE (type));
10170 	  break;
10171 	case IEEE_QUIET_NAN:
10172 	  real_nan (&real, "", 1, TYPE_MODE (type));
10173 	  break;
10174 	case IEEE_NEGATIVE_INF:
10175 	  real_inf (&real);
10176 	  real = real_value_negate (&real);
10177 	  break;
10178 	case IEEE_NEGATIVE_NORMAL:
10179 	  real_from_integer (&real, TYPE_MODE (type), -42, SIGNED);
10180 	  break;
10181 	case IEEE_NEGATIVE_DENORMAL:
10182 	  k = gfc_validate_kind (BT_REAL, expr->ts.kind, false);
10183 	  real_from_mpfr (&real, gfc_real_kinds[k].tiny,
10184 			  type, GFC_RND_MODE);
10185 	  real_arithmetic (&real, RDIV_EXPR, &real, &dconst2);
10186 	  real = real_value_negate (&real);
10187 	  break;
10188 	case IEEE_NEGATIVE_ZERO:
10189 	  real_from_integer (&real, TYPE_MODE (type), 0, SIGNED);
10190 	  real = real_value_negate (&real);
10191 	  break;
10192 	case IEEE_POSITIVE_ZERO:
10193 	  /* Make this also the default: label.  The other possibility
10194 	     would be to add a separate default: label followed by
10195 	     __builtin_unreachable ().  */
10196 	  label = gfc_build_label_decl (NULL_TREE);
10197 	  tmp = build_case_label (NULL_TREE, NULL_TREE, label);
10198 	  gfc_add_expr_to_block (&body, tmp);
10199 	  real_from_integer (&real, TYPE_MODE (type), 0, SIGNED);
10200 	  break;
10201 	case IEEE_POSITIVE_DENORMAL:
10202 	  k = gfc_validate_kind (BT_REAL, expr->ts.kind, false);
10203 	  real_from_mpfr (&real, gfc_real_kinds[k].tiny,
10204 			  type, GFC_RND_MODE);
10205 	  real_arithmetic (&real, RDIV_EXPR, &real, &dconst2);
10206 	  break;
10207 	case IEEE_POSITIVE_NORMAL:
10208 	  real_from_integer (&real, TYPE_MODE (type), 42, SIGNED);
10209 	  break;
10210 	case IEEE_POSITIVE_INF:
10211 	  real_inf (&real);
10212 	  break;
10213 	default:
10214 	  gcc_unreachable ();
10215 	}
10216 
10217       tree val = build_real (type, real);
10218       gfc_add_modify (&body, ret, val);
10219 
10220       tmp = build1_v (GOTO_EXPR, end_label);
10221       gfc_add_expr_to_block (&body, tmp);
10222     }
10223 
10224   tmp = gfc_finish_block (&body);
10225   tmp = fold_build2_loc (input_location, SWITCH_EXPR, NULL_TREE, arg, tmp);
10226   gfc_add_expr_to_block (&se->pre, tmp);
10227 
10228   tmp = build1_v (LABEL_EXPR, end_label);
10229   gfc_add_expr_to_block (&se->pre, tmp);
10230 
10231   se->expr = ret;
10232   return true;
10233 }
10234 
10235 
10236 /* Generate code for an intrinsic function from the IEEE_ARITHMETIC
10237    module.  */
10238 
10239 bool
gfc_conv_ieee_arithmetic_function(gfc_se * se,gfc_expr * expr)10240 gfc_conv_ieee_arithmetic_function (gfc_se * se, gfc_expr * expr)
10241 {
10242   const char *name = expr->value.function.name;
10243 
10244   if (startswith (name, "_gfortran_ieee_is_nan"))
10245     conv_intrinsic_ieee_builtin (se, expr, BUILT_IN_ISNAN, 1);
10246   else if (startswith (name, "_gfortran_ieee_is_finite"))
10247     conv_intrinsic_ieee_builtin (se, expr, BUILT_IN_ISFINITE, 1);
10248   else if (startswith (name, "_gfortran_ieee_unordered"))
10249     conv_intrinsic_ieee_builtin (se, expr, BUILT_IN_ISUNORDERED, 2);
10250   else if (startswith (name, "_gfortran_ieee_is_normal"))
10251     conv_intrinsic_ieee_is_normal (se, expr);
10252   else if (startswith (name, "_gfortran_ieee_is_negative"))
10253     conv_intrinsic_ieee_is_negative (se, expr);
10254   else if (startswith (name, "_gfortran_ieee_copy_sign"))
10255     conv_intrinsic_ieee_copy_sign (se, expr);
10256   else if (startswith (name, "_gfortran_ieee_scalb"))
10257     conv_intrinsic_ieee_scalb (se, expr);
10258   else if (startswith (name, "_gfortran_ieee_next_after"))
10259     conv_intrinsic_ieee_next_after (se, expr);
10260   else if (startswith (name, "_gfortran_ieee_rem"))
10261     conv_intrinsic_ieee_rem (se, expr);
10262   else if (startswith (name, "_gfortran_ieee_logb"))
10263     conv_intrinsic_ieee_logb_rint (se, expr, BUILT_IN_LOGB);
10264   else if (startswith (name, "_gfortran_ieee_rint"))
10265     conv_intrinsic_ieee_logb_rint (se, expr, BUILT_IN_RINT);
10266   else if (startswith (name, "ieee_class_") && ISDIGIT (name[11]))
10267     return conv_intrinsic_ieee_class (se, expr);
10268   else if (startswith (name, "ieee_value_") && ISDIGIT (name[11]))
10269     return conv_intrinsic_ieee_value (se, expr);
10270   else
10271     /* It is not among the functions we translate directly.  We return
10272        false, so a library function call is emitted.  */
10273     return false;
10274 
10275   return true;
10276 }
10277 
10278 
10279 /* Generate a direct call to malloc() for the MALLOC intrinsic.  */
10280 
10281 static void
gfc_conv_intrinsic_malloc(gfc_se * se,gfc_expr * expr)10282 gfc_conv_intrinsic_malloc (gfc_se * se, gfc_expr * expr)
10283 {
10284   tree arg, res, restype;
10285 
10286   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
10287   arg = fold_convert (size_type_node, arg);
10288   res = build_call_expr_loc (input_location,
10289 			     builtin_decl_explicit (BUILT_IN_MALLOC), 1, arg);
10290   restype = gfc_typenode_for_spec (&expr->ts);
10291   se->expr = fold_convert (restype, res);
10292 }
10293 
10294 
10295 /* Generate code for an intrinsic function.  Some map directly to library
10296    calls, others get special handling.  In some cases the name of the function
10297    used depends on the type specifiers.  */
10298 
10299 void
gfc_conv_intrinsic_function(gfc_se * se,gfc_expr * expr)10300 gfc_conv_intrinsic_function (gfc_se * se, gfc_expr * expr)
10301 {
10302   const char *name;
10303   int lib, kind;
10304   tree fndecl;
10305 
10306   name = &expr->value.function.name[2];
10307 
10308   if (expr->rank > 0)
10309     {
10310       lib = gfc_is_intrinsic_libcall (expr);
10311       if (lib != 0)
10312 	{
10313 	  if (lib == 1)
10314 	    se->ignore_optional = 1;
10315 
10316 	  switch (expr->value.function.isym->id)
10317 	    {
10318 	    case GFC_ISYM_EOSHIFT:
10319 	    case GFC_ISYM_PACK:
10320 	    case GFC_ISYM_RESHAPE:
10321 	      /* For all of those the first argument specifies the type and the
10322 		 third is optional.  */
10323 	      conv_generic_with_optional_char_arg (se, expr, 1, 3);
10324 	      break;
10325 
10326 	    case GFC_ISYM_FINDLOC:
10327 	      gfc_conv_intrinsic_findloc (se, expr);
10328 	      break;
10329 
10330 	    case GFC_ISYM_MINLOC:
10331 	      gfc_conv_intrinsic_minmaxloc (se, expr, LT_EXPR);
10332 	      break;
10333 
10334 	    case GFC_ISYM_MAXLOC:
10335 	      gfc_conv_intrinsic_minmaxloc (se, expr, GT_EXPR);
10336 	      break;
10337 
10338 	    default:
10339 	      gfc_conv_intrinsic_funcall (se, expr);
10340 	      break;
10341 	    }
10342 
10343 	  return;
10344 	}
10345     }
10346 
10347   switch (expr->value.function.isym->id)
10348     {
10349     case GFC_ISYM_NONE:
10350       gcc_unreachable ();
10351 
10352     case GFC_ISYM_REPEAT:
10353       gfc_conv_intrinsic_repeat (se, expr);
10354       break;
10355 
10356     case GFC_ISYM_TRIM:
10357       gfc_conv_intrinsic_trim (se, expr);
10358       break;
10359 
10360     case GFC_ISYM_SC_KIND:
10361       gfc_conv_intrinsic_sc_kind (se, expr);
10362       break;
10363 
10364     case GFC_ISYM_SI_KIND:
10365       gfc_conv_intrinsic_si_kind (se, expr);
10366       break;
10367 
10368     case GFC_ISYM_SR_KIND:
10369       gfc_conv_intrinsic_sr_kind (se, expr);
10370       break;
10371 
10372     case GFC_ISYM_EXPONENT:
10373       gfc_conv_intrinsic_exponent (se, expr);
10374       break;
10375 
10376     case GFC_ISYM_SCAN:
10377       kind = expr->value.function.actual->expr->ts.kind;
10378       if (kind == 1)
10379        fndecl = gfor_fndecl_string_scan;
10380       else if (kind == 4)
10381        fndecl = gfor_fndecl_string_scan_char4;
10382       else
10383        gcc_unreachable ();
10384 
10385       gfc_conv_intrinsic_index_scan_verify (se, expr, fndecl);
10386       break;
10387 
10388     case GFC_ISYM_VERIFY:
10389       kind = expr->value.function.actual->expr->ts.kind;
10390       if (kind == 1)
10391        fndecl = gfor_fndecl_string_verify;
10392       else if (kind == 4)
10393        fndecl = gfor_fndecl_string_verify_char4;
10394       else
10395        gcc_unreachable ();
10396 
10397       gfc_conv_intrinsic_index_scan_verify (se, expr, fndecl);
10398       break;
10399 
10400     case GFC_ISYM_ALLOCATED:
10401       gfc_conv_allocated (se, expr);
10402       break;
10403 
10404     case GFC_ISYM_ASSOCIATED:
10405       gfc_conv_associated(se, expr);
10406       break;
10407 
10408     case GFC_ISYM_SAME_TYPE_AS:
10409       gfc_conv_same_type_as (se, expr);
10410       break;
10411 
10412     case GFC_ISYM_ABS:
10413       gfc_conv_intrinsic_abs (se, expr);
10414       break;
10415 
10416     case GFC_ISYM_ADJUSTL:
10417       if (expr->ts.kind == 1)
10418        fndecl = gfor_fndecl_adjustl;
10419       else if (expr->ts.kind == 4)
10420        fndecl = gfor_fndecl_adjustl_char4;
10421       else
10422        gcc_unreachable ();
10423 
10424       gfc_conv_intrinsic_adjust (se, expr, fndecl);
10425       break;
10426 
10427     case GFC_ISYM_ADJUSTR:
10428       if (expr->ts.kind == 1)
10429        fndecl = gfor_fndecl_adjustr;
10430       else if (expr->ts.kind == 4)
10431        fndecl = gfor_fndecl_adjustr_char4;
10432       else
10433        gcc_unreachable ();
10434 
10435       gfc_conv_intrinsic_adjust (se, expr, fndecl);
10436       break;
10437 
10438     case GFC_ISYM_AIMAG:
10439       gfc_conv_intrinsic_imagpart (se, expr);
10440       break;
10441 
10442     case GFC_ISYM_AINT:
10443       gfc_conv_intrinsic_aint (se, expr, RND_TRUNC);
10444       break;
10445 
10446     case GFC_ISYM_ALL:
10447       gfc_conv_intrinsic_anyall (se, expr, EQ_EXPR);
10448       break;
10449 
10450     case GFC_ISYM_ANINT:
10451       gfc_conv_intrinsic_aint (se, expr, RND_ROUND);
10452       break;
10453 
10454     case GFC_ISYM_AND:
10455       gfc_conv_intrinsic_bitop (se, expr, BIT_AND_EXPR);
10456       break;
10457 
10458     case GFC_ISYM_ANY:
10459       gfc_conv_intrinsic_anyall (se, expr, NE_EXPR);
10460       break;
10461 
10462     case GFC_ISYM_ACOSD:
10463     case GFC_ISYM_ASIND:
10464     case GFC_ISYM_ATAND:
10465       gfc_conv_intrinsic_atrigd (se, expr, expr->value.function.isym->id);
10466       break;
10467 
10468     case GFC_ISYM_COTAN:
10469       gfc_conv_intrinsic_cotan (se, expr);
10470       break;
10471 
10472     case GFC_ISYM_COTAND:
10473       gfc_conv_intrinsic_cotand (se, expr);
10474       break;
10475 
10476     case GFC_ISYM_ATAN2D:
10477       gfc_conv_intrinsic_atan2d (se, expr);
10478       break;
10479 
10480     case GFC_ISYM_BTEST:
10481       gfc_conv_intrinsic_btest (se, expr);
10482       break;
10483 
10484     case GFC_ISYM_BGE:
10485       gfc_conv_intrinsic_bitcomp (se, expr, GE_EXPR);
10486       break;
10487 
10488     case GFC_ISYM_BGT:
10489       gfc_conv_intrinsic_bitcomp (se, expr, GT_EXPR);
10490       break;
10491 
10492     case GFC_ISYM_BLE:
10493       gfc_conv_intrinsic_bitcomp (se, expr, LE_EXPR);
10494       break;
10495 
10496     case GFC_ISYM_BLT:
10497       gfc_conv_intrinsic_bitcomp (se, expr, LT_EXPR);
10498       break;
10499 
10500     case GFC_ISYM_C_ASSOCIATED:
10501     case GFC_ISYM_C_FUNLOC:
10502     case GFC_ISYM_C_LOC:
10503       conv_isocbinding_function (se, expr);
10504       break;
10505 
10506     case GFC_ISYM_ACHAR:
10507     case GFC_ISYM_CHAR:
10508       gfc_conv_intrinsic_char (se, expr);
10509       break;
10510 
10511     case GFC_ISYM_CONVERSION:
10512     case GFC_ISYM_DBLE:
10513     case GFC_ISYM_DFLOAT:
10514     case GFC_ISYM_FLOAT:
10515     case GFC_ISYM_LOGICAL:
10516     case GFC_ISYM_REAL:
10517     case GFC_ISYM_REALPART:
10518     case GFC_ISYM_SNGL:
10519       gfc_conv_intrinsic_conversion (se, expr);
10520       break;
10521 
10522       /* Integer conversions are handled separately to make sure we get the
10523          correct rounding mode.  */
10524     case GFC_ISYM_INT:
10525     case GFC_ISYM_INT2:
10526     case GFC_ISYM_INT8:
10527     case GFC_ISYM_LONG:
10528       gfc_conv_intrinsic_int (se, expr, RND_TRUNC);
10529       break;
10530 
10531     case GFC_ISYM_NINT:
10532       gfc_conv_intrinsic_int (se, expr, RND_ROUND);
10533       break;
10534 
10535     case GFC_ISYM_CEILING:
10536       gfc_conv_intrinsic_int (se, expr, RND_CEIL);
10537       break;
10538 
10539     case GFC_ISYM_FLOOR:
10540       gfc_conv_intrinsic_int (se, expr, RND_FLOOR);
10541       break;
10542 
10543     case GFC_ISYM_MOD:
10544       gfc_conv_intrinsic_mod (se, expr, 0);
10545       break;
10546 
10547     case GFC_ISYM_MODULO:
10548       gfc_conv_intrinsic_mod (se, expr, 1);
10549       break;
10550 
10551     case GFC_ISYM_CAF_GET:
10552       gfc_conv_intrinsic_caf_get (se, expr, NULL_TREE, NULL_TREE, NULL_TREE,
10553 				  false, NULL);
10554       break;
10555 
10556     case GFC_ISYM_CMPLX:
10557       gfc_conv_intrinsic_cmplx (se, expr, name[5] == '1');
10558       break;
10559 
10560     case GFC_ISYM_COMMAND_ARGUMENT_COUNT:
10561       gfc_conv_intrinsic_iargc (se, expr);
10562       break;
10563 
10564     case GFC_ISYM_COMPLEX:
10565       gfc_conv_intrinsic_cmplx (se, expr, 1);
10566       break;
10567 
10568     case GFC_ISYM_CONJG:
10569       gfc_conv_intrinsic_conjg (se, expr);
10570       break;
10571 
10572     case GFC_ISYM_COUNT:
10573       gfc_conv_intrinsic_count (se, expr);
10574       break;
10575 
10576     case GFC_ISYM_CTIME:
10577       gfc_conv_intrinsic_ctime (se, expr);
10578       break;
10579 
10580     case GFC_ISYM_DIM:
10581       gfc_conv_intrinsic_dim (se, expr);
10582       break;
10583 
10584     case GFC_ISYM_DOT_PRODUCT:
10585       gfc_conv_intrinsic_dot_product (se, expr);
10586       break;
10587 
10588     case GFC_ISYM_DPROD:
10589       gfc_conv_intrinsic_dprod (se, expr);
10590       break;
10591 
10592     case GFC_ISYM_DSHIFTL:
10593       gfc_conv_intrinsic_dshift (se, expr, true);
10594       break;
10595 
10596     case GFC_ISYM_DSHIFTR:
10597       gfc_conv_intrinsic_dshift (se, expr, false);
10598       break;
10599 
10600     case GFC_ISYM_FDATE:
10601       gfc_conv_intrinsic_fdate (se, expr);
10602       break;
10603 
10604     case GFC_ISYM_FRACTION:
10605       gfc_conv_intrinsic_fraction (se, expr);
10606       break;
10607 
10608     case GFC_ISYM_IALL:
10609       gfc_conv_intrinsic_arith (se, expr, BIT_AND_EXPR, false);
10610       break;
10611 
10612     case GFC_ISYM_IAND:
10613       gfc_conv_intrinsic_bitop (se, expr, BIT_AND_EXPR);
10614       break;
10615 
10616     case GFC_ISYM_IANY:
10617       gfc_conv_intrinsic_arith (se, expr, BIT_IOR_EXPR, false);
10618       break;
10619 
10620     case GFC_ISYM_IBCLR:
10621       gfc_conv_intrinsic_singlebitop (se, expr, 0);
10622       break;
10623 
10624     case GFC_ISYM_IBITS:
10625       gfc_conv_intrinsic_ibits (se, expr);
10626       break;
10627 
10628     case GFC_ISYM_IBSET:
10629       gfc_conv_intrinsic_singlebitop (se, expr, 1);
10630       break;
10631 
10632     case GFC_ISYM_IACHAR:
10633     case GFC_ISYM_ICHAR:
10634       /* We assume ASCII character sequence.  */
10635       gfc_conv_intrinsic_ichar (se, expr);
10636       break;
10637 
10638     case GFC_ISYM_IARGC:
10639       gfc_conv_intrinsic_iargc (se, expr);
10640       break;
10641 
10642     case GFC_ISYM_IEOR:
10643       gfc_conv_intrinsic_bitop (se, expr, BIT_XOR_EXPR);
10644       break;
10645 
10646     case GFC_ISYM_INDEX:
10647       kind = expr->value.function.actual->expr->ts.kind;
10648       if (kind == 1)
10649        fndecl = gfor_fndecl_string_index;
10650       else if (kind == 4)
10651        fndecl = gfor_fndecl_string_index_char4;
10652       else
10653        gcc_unreachable ();
10654 
10655       gfc_conv_intrinsic_index_scan_verify (se, expr, fndecl);
10656       break;
10657 
10658     case GFC_ISYM_IOR:
10659       gfc_conv_intrinsic_bitop (se, expr, BIT_IOR_EXPR);
10660       break;
10661 
10662     case GFC_ISYM_IPARITY:
10663       gfc_conv_intrinsic_arith (se, expr, BIT_XOR_EXPR, false);
10664       break;
10665 
10666     case GFC_ISYM_IS_IOSTAT_END:
10667       gfc_conv_has_intvalue (se, expr, LIBERROR_END);
10668       break;
10669 
10670     case GFC_ISYM_IS_IOSTAT_EOR:
10671       gfc_conv_has_intvalue (se, expr, LIBERROR_EOR);
10672       break;
10673 
10674     case GFC_ISYM_IS_CONTIGUOUS:
10675       gfc_conv_intrinsic_is_contiguous (se, expr);
10676       break;
10677 
10678     case GFC_ISYM_ISNAN:
10679       gfc_conv_intrinsic_isnan (se, expr);
10680       break;
10681 
10682     case GFC_ISYM_KILL:
10683       conv_intrinsic_kill (se, expr);
10684       break;
10685 
10686     case GFC_ISYM_LSHIFT:
10687       gfc_conv_intrinsic_shift (se, expr, false, false);
10688       break;
10689 
10690     case GFC_ISYM_RSHIFT:
10691       gfc_conv_intrinsic_shift (se, expr, true, true);
10692       break;
10693 
10694     case GFC_ISYM_SHIFTA:
10695       gfc_conv_intrinsic_shift (se, expr, true, true);
10696       break;
10697 
10698     case GFC_ISYM_SHIFTL:
10699       gfc_conv_intrinsic_shift (se, expr, false, false);
10700       break;
10701 
10702     case GFC_ISYM_SHIFTR:
10703       gfc_conv_intrinsic_shift (se, expr, true, false);
10704       break;
10705 
10706     case GFC_ISYM_ISHFT:
10707       gfc_conv_intrinsic_ishft (se, expr);
10708       break;
10709 
10710     case GFC_ISYM_ISHFTC:
10711       gfc_conv_intrinsic_ishftc (se, expr);
10712       break;
10713 
10714     case GFC_ISYM_LEADZ:
10715       gfc_conv_intrinsic_leadz (se, expr);
10716       break;
10717 
10718     case GFC_ISYM_TRAILZ:
10719       gfc_conv_intrinsic_trailz (se, expr);
10720       break;
10721 
10722     case GFC_ISYM_POPCNT:
10723       gfc_conv_intrinsic_popcnt_poppar (se, expr, 0);
10724       break;
10725 
10726     case GFC_ISYM_POPPAR:
10727       gfc_conv_intrinsic_popcnt_poppar (se, expr, 1);
10728       break;
10729 
10730     case GFC_ISYM_LBOUND:
10731       gfc_conv_intrinsic_bound (se, expr, GFC_ISYM_LBOUND);
10732       break;
10733 
10734     case GFC_ISYM_LCOBOUND:
10735       conv_intrinsic_cobound (se, expr);
10736       break;
10737 
10738     case GFC_ISYM_TRANSPOSE:
10739       /* The scalarizer has already been set up for reversed dimension access
10740 	 order ; now we just get the argument value normally.  */
10741       gfc_conv_expr (se, expr->value.function.actual->expr);
10742       break;
10743 
10744     case GFC_ISYM_LEN:
10745       gfc_conv_intrinsic_len (se, expr);
10746       break;
10747 
10748     case GFC_ISYM_LEN_TRIM:
10749       gfc_conv_intrinsic_len_trim (se, expr);
10750       break;
10751 
10752     case GFC_ISYM_LGE:
10753       gfc_conv_intrinsic_strcmp (se, expr, GE_EXPR);
10754       break;
10755 
10756     case GFC_ISYM_LGT:
10757       gfc_conv_intrinsic_strcmp (se, expr, GT_EXPR);
10758       break;
10759 
10760     case GFC_ISYM_LLE:
10761       gfc_conv_intrinsic_strcmp (se, expr, LE_EXPR);
10762       break;
10763 
10764     case GFC_ISYM_LLT:
10765       gfc_conv_intrinsic_strcmp (se, expr, LT_EXPR);
10766       break;
10767 
10768     case GFC_ISYM_MALLOC:
10769       gfc_conv_intrinsic_malloc (se, expr);
10770       break;
10771 
10772     case GFC_ISYM_MASKL:
10773       gfc_conv_intrinsic_mask (se, expr, 1);
10774       break;
10775 
10776     case GFC_ISYM_MASKR:
10777       gfc_conv_intrinsic_mask (se, expr, 0);
10778       break;
10779 
10780     case GFC_ISYM_MAX:
10781       if (expr->ts.type == BT_CHARACTER)
10782 	gfc_conv_intrinsic_minmax_char (se, expr, 1);
10783       else
10784 	gfc_conv_intrinsic_minmax (se, expr, GT_EXPR);
10785       break;
10786 
10787     case GFC_ISYM_MAXLOC:
10788       gfc_conv_intrinsic_minmaxloc (se, expr, GT_EXPR);
10789       break;
10790 
10791     case GFC_ISYM_FINDLOC:
10792       gfc_conv_intrinsic_findloc (se, expr);
10793       break;
10794 
10795     case GFC_ISYM_MAXVAL:
10796       gfc_conv_intrinsic_minmaxval (se, expr, GT_EXPR);
10797       break;
10798 
10799     case GFC_ISYM_MERGE:
10800       gfc_conv_intrinsic_merge (se, expr);
10801       break;
10802 
10803     case GFC_ISYM_MERGE_BITS:
10804       gfc_conv_intrinsic_merge_bits (se, expr);
10805       break;
10806 
10807     case GFC_ISYM_MIN:
10808       if (expr->ts.type == BT_CHARACTER)
10809 	gfc_conv_intrinsic_minmax_char (se, expr, -1);
10810       else
10811 	gfc_conv_intrinsic_minmax (se, expr, LT_EXPR);
10812       break;
10813 
10814     case GFC_ISYM_MINLOC:
10815       gfc_conv_intrinsic_minmaxloc (se, expr, LT_EXPR);
10816       break;
10817 
10818     case GFC_ISYM_MINVAL:
10819       gfc_conv_intrinsic_minmaxval (se, expr, LT_EXPR);
10820       break;
10821 
10822     case GFC_ISYM_NEAREST:
10823       gfc_conv_intrinsic_nearest (se, expr);
10824       break;
10825 
10826     case GFC_ISYM_NORM2:
10827       gfc_conv_intrinsic_arith (se, expr, PLUS_EXPR, true);
10828       break;
10829 
10830     case GFC_ISYM_NOT:
10831       gfc_conv_intrinsic_not (se, expr);
10832       break;
10833 
10834     case GFC_ISYM_OR:
10835       gfc_conv_intrinsic_bitop (se, expr, BIT_IOR_EXPR);
10836       break;
10837 
10838     case GFC_ISYM_PARITY:
10839       gfc_conv_intrinsic_arith (se, expr, NE_EXPR, false);
10840       break;
10841 
10842     case GFC_ISYM_PRESENT:
10843       gfc_conv_intrinsic_present (se, expr);
10844       break;
10845 
10846     case GFC_ISYM_PRODUCT:
10847       gfc_conv_intrinsic_arith (se, expr, MULT_EXPR, false);
10848       break;
10849 
10850     case GFC_ISYM_RANK:
10851       gfc_conv_intrinsic_rank (se, expr);
10852       break;
10853 
10854     case GFC_ISYM_RRSPACING:
10855       gfc_conv_intrinsic_rrspacing (se, expr);
10856       break;
10857 
10858     case GFC_ISYM_SET_EXPONENT:
10859       gfc_conv_intrinsic_set_exponent (se, expr);
10860       break;
10861 
10862     case GFC_ISYM_SCALE:
10863       gfc_conv_intrinsic_scale (se, expr);
10864       break;
10865 
10866     case GFC_ISYM_SHAPE:
10867       gfc_conv_intrinsic_bound (se, expr, GFC_ISYM_SHAPE);
10868       break;
10869 
10870     case GFC_ISYM_SIGN:
10871       gfc_conv_intrinsic_sign (se, expr);
10872       break;
10873 
10874     case GFC_ISYM_SIZE:
10875       gfc_conv_intrinsic_size (se, expr);
10876       break;
10877 
10878     case GFC_ISYM_SIZEOF:
10879     case GFC_ISYM_C_SIZEOF:
10880       gfc_conv_intrinsic_sizeof (se, expr);
10881       break;
10882 
10883     case GFC_ISYM_STORAGE_SIZE:
10884       gfc_conv_intrinsic_storage_size (se, expr);
10885       break;
10886 
10887     case GFC_ISYM_SPACING:
10888       gfc_conv_intrinsic_spacing (se, expr);
10889       break;
10890 
10891     case GFC_ISYM_STRIDE:
10892       conv_intrinsic_stride (se, expr);
10893       break;
10894 
10895     case GFC_ISYM_SUM:
10896       gfc_conv_intrinsic_arith (se, expr, PLUS_EXPR, false);
10897       break;
10898 
10899     case GFC_ISYM_TEAM_NUMBER:
10900       conv_intrinsic_team_number (se, expr);
10901       break;
10902 
10903     case GFC_ISYM_TRANSFER:
10904       if (se->ss && se->ss->info->useflags)
10905 	/* Access the previously obtained result.  */
10906 	gfc_conv_tmp_array_ref (se);
10907       else
10908 	gfc_conv_intrinsic_transfer (se, expr);
10909       break;
10910 
10911     case GFC_ISYM_TTYNAM:
10912       gfc_conv_intrinsic_ttynam (se, expr);
10913       break;
10914 
10915     case GFC_ISYM_UBOUND:
10916       gfc_conv_intrinsic_bound (se, expr, GFC_ISYM_UBOUND);
10917       break;
10918 
10919     case GFC_ISYM_UCOBOUND:
10920       conv_intrinsic_cobound (se, expr);
10921       break;
10922 
10923     case GFC_ISYM_XOR:
10924       gfc_conv_intrinsic_bitop (se, expr, BIT_XOR_EXPR);
10925       break;
10926 
10927     case GFC_ISYM_LOC:
10928       gfc_conv_intrinsic_loc (se, expr);
10929       break;
10930 
10931     case GFC_ISYM_THIS_IMAGE:
10932       /* For num_images() == 1, handle as LCOBOUND.  */
10933       if (expr->value.function.actual->expr
10934 	  && flag_coarray == GFC_FCOARRAY_SINGLE)
10935 	conv_intrinsic_cobound (se, expr);
10936       else
10937 	trans_this_image (se, expr);
10938       break;
10939 
10940     case GFC_ISYM_IMAGE_INDEX:
10941       trans_image_index (se, expr);
10942       break;
10943 
10944     case GFC_ISYM_IMAGE_STATUS:
10945       conv_intrinsic_image_status (se, expr);
10946       break;
10947 
10948     case GFC_ISYM_NUM_IMAGES:
10949       trans_num_images (se, expr);
10950       break;
10951 
10952     case GFC_ISYM_ACCESS:
10953     case GFC_ISYM_CHDIR:
10954     case GFC_ISYM_CHMOD:
10955     case GFC_ISYM_DTIME:
10956     case GFC_ISYM_ETIME:
10957     case GFC_ISYM_EXTENDS_TYPE_OF:
10958     case GFC_ISYM_FGET:
10959     case GFC_ISYM_FGETC:
10960     case GFC_ISYM_FNUM:
10961     case GFC_ISYM_FPUT:
10962     case GFC_ISYM_FPUTC:
10963     case GFC_ISYM_FSTAT:
10964     case GFC_ISYM_FTELL:
10965     case GFC_ISYM_GETCWD:
10966     case GFC_ISYM_GETGID:
10967     case GFC_ISYM_GETPID:
10968     case GFC_ISYM_GETUID:
10969     case GFC_ISYM_HOSTNM:
10970     case GFC_ISYM_IERRNO:
10971     case GFC_ISYM_IRAND:
10972     case GFC_ISYM_ISATTY:
10973     case GFC_ISYM_JN2:
10974     case GFC_ISYM_LINK:
10975     case GFC_ISYM_LSTAT:
10976     case GFC_ISYM_MATMUL:
10977     case GFC_ISYM_MCLOCK:
10978     case GFC_ISYM_MCLOCK8:
10979     case GFC_ISYM_RAND:
10980     case GFC_ISYM_RENAME:
10981     case GFC_ISYM_SECOND:
10982     case GFC_ISYM_SECNDS:
10983     case GFC_ISYM_SIGNAL:
10984     case GFC_ISYM_STAT:
10985     case GFC_ISYM_SYMLNK:
10986     case GFC_ISYM_SYSTEM:
10987     case GFC_ISYM_TIME:
10988     case GFC_ISYM_TIME8:
10989     case GFC_ISYM_UMASK:
10990     case GFC_ISYM_UNLINK:
10991     case GFC_ISYM_YN2:
10992       gfc_conv_intrinsic_funcall (se, expr);
10993       break;
10994 
10995     case GFC_ISYM_EOSHIFT:
10996     case GFC_ISYM_PACK:
10997     case GFC_ISYM_RESHAPE:
10998       /* For those, expr->rank should always be >0 and thus the if above the
10999 	 switch should have matched.  */
11000       gcc_unreachable ();
11001       break;
11002 
11003     default:
11004       gfc_conv_intrinsic_lib_function (se, expr);
11005       break;
11006     }
11007 }
11008 
11009 
11010 static gfc_ss *
walk_inline_intrinsic_transpose(gfc_ss * ss,gfc_expr * expr)11011 walk_inline_intrinsic_transpose (gfc_ss *ss, gfc_expr *expr)
11012 {
11013   gfc_ss *arg_ss, *tmp_ss;
11014   gfc_actual_arglist *arg;
11015 
11016   arg = expr->value.function.actual;
11017 
11018   gcc_assert (arg->expr);
11019 
11020   arg_ss = gfc_walk_subexpr (gfc_ss_terminator, arg->expr);
11021   gcc_assert (arg_ss != gfc_ss_terminator);
11022 
11023   for (tmp_ss = arg_ss; ; tmp_ss = tmp_ss->next)
11024     {
11025       if (tmp_ss->info->type != GFC_SS_SCALAR
11026 	  && tmp_ss->info->type != GFC_SS_REFERENCE)
11027 	{
11028 	  gcc_assert (tmp_ss->dimen == 2);
11029 
11030 	  /* We just invert dimensions.  */
11031 	  std::swap (tmp_ss->dim[0], tmp_ss->dim[1]);
11032 	}
11033 
11034       /* Stop when tmp_ss points to the last valid element of the chain...  */
11035       if (tmp_ss->next == gfc_ss_terminator)
11036 	break;
11037     }
11038 
11039   /* ... so that we can attach the rest of the chain to it.  */
11040   tmp_ss->next = ss;
11041 
11042   return arg_ss;
11043 }
11044 
11045 
11046 /* Move the given dimension of the given gfc_ss list to a nested gfc_ss list.
11047    This has the side effect of reversing the nested list, so there is no
11048    need to call gfc_reverse_ss on it (the given list is assumed not to be
11049    reversed yet).   */
11050 
11051 static gfc_ss *
nest_loop_dimension(gfc_ss * ss,int dim)11052 nest_loop_dimension (gfc_ss *ss, int dim)
11053 {
11054   int ss_dim, i;
11055   gfc_ss *new_ss, *prev_ss = gfc_ss_terminator;
11056   gfc_loopinfo *new_loop;
11057 
11058   gcc_assert (ss != gfc_ss_terminator);
11059 
11060   for (; ss != gfc_ss_terminator; ss = ss->next)
11061     {
11062       new_ss = gfc_get_ss ();
11063       new_ss->next = prev_ss;
11064       new_ss->parent = ss;
11065       new_ss->info = ss->info;
11066       new_ss->info->refcount++;
11067       if (ss->dimen != 0)
11068 	{
11069 	  gcc_assert (ss->info->type != GFC_SS_SCALAR
11070 		      && ss->info->type != GFC_SS_REFERENCE);
11071 
11072 	  new_ss->dimen = 1;
11073 	  new_ss->dim[0] = ss->dim[dim];
11074 
11075 	  gcc_assert (dim < ss->dimen);
11076 
11077 	  ss_dim = --ss->dimen;
11078 	  for (i = dim; i < ss_dim; i++)
11079 	    ss->dim[i] = ss->dim[i + 1];
11080 
11081 	  ss->dim[ss_dim] = 0;
11082 	}
11083       prev_ss = new_ss;
11084 
11085       if (ss->nested_ss)
11086 	{
11087 	  ss->nested_ss->parent = new_ss;
11088 	  new_ss->nested_ss = ss->nested_ss;
11089 	}
11090       ss->nested_ss = new_ss;
11091     }
11092 
11093   new_loop = gfc_get_loopinfo ();
11094   gfc_init_loopinfo (new_loop);
11095 
11096   gcc_assert (prev_ss != NULL);
11097   gcc_assert (prev_ss != gfc_ss_terminator);
11098   gfc_add_ss_to_loop (new_loop, prev_ss);
11099   return new_ss->parent;
11100 }
11101 
11102 
11103 /* Create the gfc_ss list for the SUM/PRODUCT arguments when the function
11104    is to be inlined.  */
11105 
11106 static gfc_ss *
walk_inline_intrinsic_arith(gfc_ss * ss,gfc_expr * expr)11107 walk_inline_intrinsic_arith (gfc_ss *ss, gfc_expr *expr)
11108 {
11109   gfc_ss *tmp_ss, *tail, *array_ss;
11110   gfc_actual_arglist *arg1, *arg2, *arg3;
11111   int sum_dim;
11112   bool scalar_mask = false;
11113 
11114   /* The rank of the result will be determined later.  */
11115   arg1 = expr->value.function.actual;
11116   arg2 = arg1->next;
11117   arg3 = arg2->next;
11118   gcc_assert (arg3 != NULL);
11119 
11120   if (expr->rank == 0)
11121     return ss;
11122 
11123   tmp_ss = gfc_ss_terminator;
11124 
11125   if (arg3->expr)
11126     {
11127       gfc_ss *mask_ss;
11128 
11129       mask_ss = gfc_walk_subexpr (tmp_ss, arg3->expr);
11130       if (mask_ss == tmp_ss)
11131 	scalar_mask = 1;
11132 
11133       tmp_ss = mask_ss;
11134     }
11135 
11136   array_ss = gfc_walk_subexpr (tmp_ss, arg1->expr);
11137   gcc_assert (array_ss != tmp_ss);
11138 
11139   /* Odd thing: If the mask is scalar, it is used by the frontend after
11140      the array (to make an if around the nested loop). Thus it shall
11141      be after array_ss once the gfc_ss list is reversed.  */
11142   if (scalar_mask)
11143     tmp_ss = gfc_get_scalar_ss (array_ss, arg3->expr);
11144   else
11145     tmp_ss = array_ss;
11146 
11147   /* "Hide" the dimension on which we will sum in the first arg's scalarization
11148      chain.  */
11149   sum_dim = mpz_get_si (arg2->expr->value.integer) - 1;
11150   tail = nest_loop_dimension (tmp_ss, sum_dim);
11151   tail->next = ss;
11152 
11153   return tmp_ss;
11154 }
11155 
11156 
11157 static gfc_ss *
walk_inline_intrinsic_function(gfc_ss * ss,gfc_expr * expr)11158 walk_inline_intrinsic_function (gfc_ss * ss, gfc_expr * expr)
11159 {
11160 
11161   switch (expr->value.function.isym->id)
11162     {
11163       case GFC_ISYM_PRODUCT:
11164       case GFC_ISYM_SUM:
11165 	return walk_inline_intrinsic_arith (ss, expr);
11166 
11167       case GFC_ISYM_TRANSPOSE:
11168 	return walk_inline_intrinsic_transpose (ss, expr);
11169 
11170       default:
11171 	gcc_unreachable ();
11172     }
11173   gcc_unreachable ();
11174 }
11175 
11176 
11177 /* This generates code to execute before entering the scalarization loop.
11178    Currently does nothing.  */
11179 
11180 void
gfc_add_intrinsic_ss_code(gfc_loopinfo * loop ATTRIBUTE_UNUSED,gfc_ss * ss)11181 gfc_add_intrinsic_ss_code (gfc_loopinfo * loop ATTRIBUTE_UNUSED, gfc_ss * ss)
11182 {
11183   switch (ss->info->expr->value.function.isym->id)
11184     {
11185     case GFC_ISYM_UBOUND:
11186     case GFC_ISYM_LBOUND:
11187     case GFC_ISYM_UCOBOUND:
11188     case GFC_ISYM_LCOBOUND:
11189     case GFC_ISYM_THIS_IMAGE:
11190     case GFC_ISYM_SHAPE:
11191       break;
11192 
11193     default:
11194       gcc_unreachable ();
11195     }
11196 }
11197 
11198 
11199 /* The LBOUND, LCOBOUND, UBOUND, UCOBOUND, and SHAPE intrinsics with
11200    one parameter are expanded into code inside the scalarization loop.  */
11201 
11202 static gfc_ss *
gfc_walk_intrinsic_bound(gfc_ss * ss,gfc_expr * expr)11203 gfc_walk_intrinsic_bound (gfc_ss * ss, gfc_expr * expr)
11204 {
11205   if (expr->value.function.actual->expr->ts.type == BT_CLASS)
11206     gfc_add_class_array_ref (expr->value.function.actual->expr);
11207 
11208   /* The two argument version returns a scalar.  */
11209   if (expr->value.function.isym->id != GFC_ISYM_SHAPE
11210       && expr->value.function.actual->next->expr)
11211     return ss;
11212 
11213   return gfc_get_array_ss (ss, expr, 1, GFC_SS_INTRINSIC);
11214 }
11215 
11216 
11217 /* Walk an intrinsic array libcall.  */
11218 
11219 static gfc_ss *
gfc_walk_intrinsic_libfunc(gfc_ss * ss,gfc_expr * expr)11220 gfc_walk_intrinsic_libfunc (gfc_ss * ss, gfc_expr * expr)
11221 {
11222   gcc_assert (expr->rank > 0);
11223   return gfc_get_array_ss (ss, expr, expr->rank, GFC_SS_FUNCTION);
11224 }
11225 
11226 
11227 /* Return whether the function call expression EXPR will be expanded
11228    inline by gfc_conv_intrinsic_function.  */
11229 
11230 bool
gfc_inline_intrinsic_function_p(gfc_expr * expr)11231 gfc_inline_intrinsic_function_p (gfc_expr *expr)
11232 {
11233   gfc_actual_arglist *args, *dim_arg, *mask_arg;
11234   gfc_expr *maskexpr;
11235 
11236   if (!expr->value.function.isym)
11237     return false;
11238 
11239   switch (expr->value.function.isym->id)
11240     {
11241     case GFC_ISYM_PRODUCT:
11242     case GFC_ISYM_SUM:
11243       /* Disable inline expansion if code size matters.  */
11244       if (optimize_size)
11245 	return false;
11246 
11247       args = expr->value.function.actual;
11248       dim_arg = args->next;
11249 
11250       /* We need to be able to subset the SUM argument at compile-time.  */
11251       if (dim_arg->expr && dim_arg->expr->expr_type != EXPR_CONSTANT)
11252 	return false;
11253 
11254       /* FIXME: If MASK is optional for a more than two-dimensional
11255 	 argument, the scalarizer gets confused if the mask is
11256 	 absent.  See PR 82995.  For now, fall back to the library
11257 	 function.  */
11258 
11259       mask_arg = dim_arg->next;
11260       maskexpr = mask_arg->expr;
11261 
11262       if (expr->rank > 0 && maskexpr && maskexpr->expr_type == EXPR_VARIABLE
11263 	  && maskexpr->symtree->n.sym->attr.dummy
11264 	  && maskexpr->symtree->n.sym->attr.optional)
11265 	return false;
11266 
11267       return true;
11268 
11269     case GFC_ISYM_TRANSPOSE:
11270       return true;
11271 
11272     default:
11273       return false;
11274     }
11275 }
11276 
11277 
11278 /* Returns nonzero if the specified intrinsic function call maps directly to
11279    an external library call.  Should only be used for functions that return
11280    arrays.  */
11281 
11282 int
gfc_is_intrinsic_libcall(gfc_expr * expr)11283 gfc_is_intrinsic_libcall (gfc_expr * expr)
11284 {
11285   gcc_assert (expr->expr_type == EXPR_FUNCTION && expr->value.function.isym);
11286   gcc_assert (expr->rank > 0);
11287 
11288   if (gfc_inline_intrinsic_function_p (expr))
11289     return 0;
11290 
11291   switch (expr->value.function.isym->id)
11292     {
11293     case GFC_ISYM_ALL:
11294     case GFC_ISYM_ANY:
11295     case GFC_ISYM_COUNT:
11296     case GFC_ISYM_FINDLOC:
11297     case GFC_ISYM_JN2:
11298     case GFC_ISYM_IANY:
11299     case GFC_ISYM_IALL:
11300     case GFC_ISYM_IPARITY:
11301     case GFC_ISYM_MATMUL:
11302     case GFC_ISYM_MAXLOC:
11303     case GFC_ISYM_MAXVAL:
11304     case GFC_ISYM_MINLOC:
11305     case GFC_ISYM_MINVAL:
11306     case GFC_ISYM_NORM2:
11307     case GFC_ISYM_PARITY:
11308     case GFC_ISYM_PRODUCT:
11309     case GFC_ISYM_SUM:
11310     case GFC_ISYM_SPREAD:
11311     case GFC_ISYM_YN2:
11312       /* Ignore absent optional parameters.  */
11313       return 1;
11314 
11315     case GFC_ISYM_CSHIFT:
11316     case GFC_ISYM_EOSHIFT:
11317     case GFC_ISYM_GET_TEAM:
11318     case GFC_ISYM_FAILED_IMAGES:
11319     case GFC_ISYM_STOPPED_IMAGES:
11320     case GFC_ISYM_PACK:
11321     case GFC_ISYM_RESHAPE:
11322     case GFC_ISYM_UNPACK:
11323       /* Pass absent optional parameters.  */
11324       return 2;
11325 
11326     default:
11327       return 0;
11328     }
11329 }
11330 
11331 /* Walk an intrinsic function.  */
11332 gfc_ss *
gfc_walk_intrinsic_function(gfc_ss * ss,gfc_expr * expr,gfc_intrinsic_sym * isym)11333 gfc_walk_intrinsic_function (gfc_ss * ss, gfc_expr * expr,
11334 			     gfc_intrinsic_sym * isym)
11335 {
11336   gcc_assert (isym);
11337 
11338   if (isym->elemental)
11339     return gfc_walk_elemental_function_args (ss, expr->value.function.actual,
11340 					     expr->value.function.isym,
11341 					     GFC_SS_SCALAR);
11342 
11343   if (expr->rank == 0)
11344     return ss;
11345 
11346   if (gfc_inline_intrinsic_function_p (expr))
11347     return walk_inline_intrinsic_function (ss, expr);
11348 
11349   if (gfc_is_intrinsic_libcall (expr))
11350     return gfc_walk_intrinsic_libfunc (ss, expr);
11351 
11352   /* Special cases.  */
11353   switch (isym->id)
11354     {
11355     case GFC_ISYM_LBOUND:
11356     case GFC_ISYM_LCOBOUND:
11357     case GFC_ISYM_UBOUND:
11358     case GFC_ISYM_UCOBOUND:
11359     case GFC_ISYM_THIS_IMAGE:
11360     case GFC_ISYM_SHAPE:
11361       return gfc_walk_intrinsic_bound (ss, expr);
11362 
11363     case GFC_ISYM_TRANSFER:
11364     case GFC_ISYM_CAF_GET:
11365       return gfc_walk_intrinsic_libfunc (ss, expr);
11366 
11367     default:
11368       /* This probably meant someone forgot to add an intrinsic to the above
11369          list(s) when they implemented it, or something's gone horribly
11370 	 wrong.  */
11371       gcc_unreachable ();
11372     }
11373 }
11374 
11375 static tree
conv_co_collective(gfc_code * code)11376 conv_co_collective (gfc_code *code)
11377 {
11378   gfc_se argse;
11379   stmtblock_t block, post_block;
11380   tree fndecl, array = NULL_TREE, strlen, image_index, stat, errmsg, errmsg_len;
11381   gfc_expr *image_idx_expr, *stat_expr, *errmsg_expr, *opr_expr;
11382 
11383   gfc_start_block (&block);
11384   gfc_init_block (&post_block);
11385 
11386   if (code->resolved_isym->id == GFC_ISYM_CO_REDUCE)
11387     {
11388       opr_expr = code->ext.actual->next->expr;
11389       image_idx_expr = code->ext.actual->next->next->expr;
11390       stat_expr = code->ext.actual->next->next->next->expr;
11391       errmsg_expr = code->ext.actual->next->next->next->next->expr;
11392     }
11393   else
11394     {
11395       opr_expr = NULL;
11396       image_idx_expr = code->ext.actual->next->expr;
11397       stat_expr = code->ext.actual->next->next->expr;
11398       errmsg_expr = code->ext.actual->next->next->next->expr;
11399     }
11400 
11401   /* stat.  */
11402   if (stat_expr)
11403     {
11404       gfc_init_se (&argse, NULL);
11405       gfc_conv_expr (&argse, stat_expr);
11406       gfc_add_block_to_block (&block, &argse.pre);
11407       gfc_add_block_to_block (&post_block, &argse.post);
11408       stat = argse.expr;
11409       if (flag_coarray != GFC_FCOARRAY_SINGLE)
11410 	stat = gfc_build_addr_expr (NULL_TREE, stat);
11411     }
11412   else if (flag_coarray == GFC_FCOARRAY_SINGLE)
11413     stat = NULL_TREE;
11414   else
11415     stat = null_pointer_node;
11416 
11417   /* Early exit for GFC_FCOARRAY_SINGLE.  */
11418   if (flag_coarray == GFC_FCOARRAY_SINGLE)
11419     {
11420       if (stat != NULL_TREE)
11421 	{
11422 	  /* For optional stats, check the pointer is valid before zero'ing.  */
11423 	  if (gfc_expr_attr (stat_expr).optional)
11424 	    {
11425 	      tree tmp;
11426 	      stmtblock_t ass_block;
11427 	      gfc_start_block (&ass_block);
11428 	      gfc_add_modify (&ass_block, stat,
11429 			      fold_convert (TREE_TYPE (stat),
11430 					    integer_zero_node));
11431 	      tmp = fold_build2 (NE_EXPR, logical_type_node,
11432 				 gfc_build_addr_expr (NULL_TREE, stat),
11433 				 null_pointer_node);
11434 	      tmp = fold_build3 (COND_EXPR, void_type_node, tmp,
11435 				 gfc_finish_block (&ass_block),
11436 				 build_empty_stmt (input_location));
11437 	      gfc_add_expr_to_block (&block, tmp);
11438 	    }
11439 	  else
11440 	    gfc_add_modify (&block, stat,
11441 			    fold_convert (TREE_TYPE (stat), integer_zero_node));
11442 	}
11443       return gfc_finish_block (&block);
11444     }
11445 
11446   gfc_symbol *derived = code->ext.actual->expr->ts.type == BT_DERIVED
11447     ? code->ext.actual->expr->ts.u.derived : NULL;
11448 
11449   /* Handle the array.  */
11450   gfc_init_se (&argse, NULL);
11451   if (!derived || !derived->attr.alloc_comp
11452       || code->resolved_isym->id != GFC_ISYM_CO_BROADCAST)
11453     {
11454       if (code->ext.actual->expr->rank == 0)
11455 	{
11456 	  symbol_attribute attr;
11457 	  gfc_clear_attr (&attr);
11458 	  gfc_init_se (&argse, NULL);
11459 	  gfc_conv_expr (&argse, code->ext.actual->expr);
11460 	  gfc_add_block_to_block (&block, &argse.pre);
11461 	  gfc_add_block_to_block (&post_block, &argse.post);
11462 	  array = gfc_conv_scalar_to_descriptor (&argse, argse.expr, attr);
11463 	  array = gfc_build_addr_expr (NULL_TREE, array);
11464 	}
11465       else
11466 	{
11467 	  argse.want_pointer = 1;
11468 	  gfc_conv_expr_descriptor (&argse, code->ext.actual->expr);
11469 	  array = argse.expr;
11470 	}
11471     }
11472 
11473   gfc_add_block_to_block (&block, &argse.pre);
11474   gfc_add_block_to_block (&post_block, &argse.post);
11475 
11476   if (code->ext.actual->expr->ts.type == BT_CHARACTER)
11477     strlen = argse.string_length;
11478   else
11479     strlen = integer_zero_node;
11480 
11481   /* image_index.  */
11482   if (image_idx_expr)
11483     {
11484       gfc_init_se (&argse, NULL);
11485       gfc_conv_expr (&argse, image_idx_expr);
11486       gfc_add_block_to_block (&block, &argse.pre);
11487       gfc_add_block_to_block (&post_block, &argse.post);
11488       image_index = fold_convert (integer_type_node, argse.expr);
11489     }
11490   else
11491     image_index = integer_zero_node;
11492 
11493   /* errmsg.  */
11494   if (errmsg_expr)
11495     {
11496       gfc_init_se (&argse, NULL);
11497       gfc_conv_expr (&argse, errmsg_expr);
11498       gfc_add_block_to_block (&block, &argse.pre);
11499       gfc_add_block_to_block (&post_block, &argse.post);
11500       errmsg = argse.expr;
11501       errmsg_len = fold_convert (size_type_node, argse.string_length);
11502     }
11503   else
11504     {
11505       errmsg = null_pointer_node;
11506       errmsg_len = build_zero_cst (size_type_node);
11507     }
11508 
11509   /* Generate the function call.  */
11510   switch (code->resolved_isym->id)
11511     {
11512     case GFC_ISYM_CO_BROADCAST:
11513       fndecl = gfor_fndecl_co_broadcast;
11514       break;
11515     case GFC_ISYM_CO_MAX:
11516       fndecl = gfor_fndecl_co_max;
11517       break;
11518     case GFC_ISYM_CO_MIN:
11519       fndecl = gfor_fndecl_co_min;
11520       break;
11521     case GFC_ISYM_CO_REDUCE:
11522       fndecl = gfor_fndecl_co_reduce;
11523       break;
11524     case GFC_ISYM_CO_SUM:
11525       fndecl = gfor_fndecl_co_sum;
11526       break;
11527     default:
11528       gcc_unreachable ();
11529     }
11530 
11531   if (derived && derived->attr.alloc_comp
11532       && code->resolved_isym->id == GFC_ISYM_CO_BROADCAST)
11533     /* The derived type has the attribute 'alloc_comp'.  */
11534     {
11535       tree tmp = gfc_bcast_alloc_comp (derived, code->ext.actual->expr,
11536 				       code->ext.actual->expr->rank,
11537 				       image_index, stat, errmsg, errmsg_len);
11538       gfc_add_expr_to_block (&block, tmp);
11539     }
11540   else
11541     {
11542       if (code->resolved_isym->id == GFC_ISYM_CO_SUM
11543 	  || code->resolved_isym->id == GFC_ISYM_CO_BROADCAST)
11544 	fndecl = build_call_expr_loc (input_location, fndecl, 5, array,
11545 				      image_index, stat, errmsg, errmsg_len);
11546       else if (code->resolved_isym->id != GFC_ISYM_CO_REDUCE)
11547 	fndecl = build_call_expr_loc (input_location, fndecl, 6, array,
11548 				      image_index, stat, errmsg,
11549 				      strlen, errmsg_len);
11550       else
11551 	{
11552 	  tree opr, opr_flags;
11553 
11554 	  // FIXME: Handle TS29113's bind(C) strings with descriptor.
11555 	  int opr_flag_int;
11556 	  if (gfc_is_proc_ptr_comp (opr_expr))
11557 	    {
11558 	      gfc_symbol *sym = gfc_get_proc_ptr_comp (opr_expr)->ts.interface;
11559 	      opr_flag_int = sym->attr.dimension
11560 		|| (sym->ts.type == BT_CHARACTER
11561 		    && !sym->attr.is_bind_c)
11562 		? GFC_CAF_BYREF : 0;
11563 	      opr_flag_int |= opr_expr->ts.type == BT_CHARACTER
11564 		&& !sym->attr.is_bind_c
11565 		? GFC_CAF_HIDDENLEN : 0;
11566 	      opr_flag_int |= sym->formal->sym->attr.value
11567 		? GFC_CAF_ARG_VALUE : 0;
11568 	    }
11569 	  else
11570 	    {
11571 	      opr_flag_int = gfc_return_by_reference (opr_expr->symtree->n.sym)
11572 		? GFC_CAF_BYREF : 0;
11573 	      opr_flag_int |= opr_expr->ts.type == BT_CHARACTER
11574 		&& !opr_expr->symtree->n.sym->attr.is_bind_c
11575 		? GFC_CAF_HIDDENLEN : 0;
11576 	      opr_flag_int |= opr_expr->symtree->n.sym->formal->sym->attr.value
11577 		? GFC_CAF_ARG_VALUE : 0;
11578 	    }
11579 	  opr_flags = build_int_cst (integer_type_node, opr_flag_int);
11580 	  gfc_conv_expr (&argse, opr_expr);
11581 	  opr = argse.expr;
11582 	  fndecl = build_call_expr_loc (input_location, fndecl, 8, array, opr,
11583 					opr_flags, image_index, stat, errmsg,
11584 					strlen, errmsg_len);
11585 	}
11586     }
11587 
11588   gfc_add_expr_to_block (&block, fndecl);
11589   gfc_add_block_to_block (&block, &post_block);
11590 
11591   return gfc_finish_block (&block);
11592 }
11593 
11594 
11595 static tree
conv_intrinsic_atomic_op(gfc_code * code)11596 conv_intrinsic_atomic_op (gfc_code *code)
11597 {
11598   gfc_se argse;
11599   tree tmp, atom, value, old = NULL_TREE, stat = NULL_TREE;
11600   stmtblock_t block, post_block;
11601   gfc_expr *atom_expr = code->ext.actual->expr;
11602   gfc_expr *stat_expr;
11603   built_in_function fn;
11604 
11605   if (atom_expr->expr_type == EXPR_FUNCTION
11606       && atom_expr->value.function.isym
11607       && atom_expr->value.function.isym->id == GFC_ISYM_CAF_GET)
11608     atom_expr = atom_expr->value.function.actual->expr;
11609 
11610   gfc_start_block (&block);
11611   gfc_init_block (&post_block);
11612 
11613   gfc_init_se (&argse, NULL);
11614   argse.want_pointer = 1;
11615   gfc_conv_expr (&argse, atom_expr);
11616   gfc_add_block_to_block (&block, &argse.pre);
11617   gfc_add_block_to_block (&post_block, &argse.post);
11618   atom = argse.expr;
11619 
11620   gfc_init_se (&argse, NULL);
11621   if (flag_coarray == GFC_FCOARRAY_LIB
11622       && code->ext.actual->next->expr->ts.kind == atom_expr->ts.kind)
11623     argse.want_pointer = 1;
11624   gfc_conv_expr (&argse, code->ext.actual->next->expr);
11625   gfc_add_block_to_block (&block, &argse.pre);
11626   gfc_add_block_to_block (&post_block, &argse.post);
11627   value = argse.expr;
11628 
11629   switch (code->resolved_isym->id)
11630     {
11631     case GFC_ISYM_ATOMIC_ADD:
11632     case GFC_ISYM_ATOMIC_AND:
11633     case GFC_ISYM_ATOMIC_DEF:
11634     case GFC_ISYM_ATOMIC_OR:
11635     case GFC_ISYM_ATOMIC_XOR:
11636       stat_expr = code->ext.actual->next->next->expr;
11637       if (flag_coarray == GFC_FCOARRAY_LIB)
11638 	old = null_pointer_node;
11639       break;
11640     default:
11641       gfc_init_se (&argse, NULL);
11642       if (flag_coarray == GFC_FCOARRAY_LIB)
11643 	argse.want_pointer = 1;
11644       gfc_conv_expr (&argse, code->ext.actual->next->next->expr);
11645       gfc_add_block_to_block (&block, &argse.pre);
11646       gfc_add_block_to_block (&post_block, &argse.post);
11647       old = argse.expr;
11648       stat_expr = code->ext.actual->next->next->next->expr;
11649     }
11650 
11651   /* STAT=  */
11652   if (stat_expr != NULL)
11653     {
11654       gcc_assert (stat_expr->expr_type == EXPR_VARIABLE);
11655       gfc_init_se (&argse, NULL);
11656       if (flag_coarray == GFC_FCOARRAY_LIB)
11657 	argse.want_pointer = 1;
11658       gfc_conv_expr_val (&argse, stat_expr);
11659       gfc_add_block_to_block (&block, &argse.pre);
11660       gfc_add_block_to_block (&post_block, &argse.post);
11661       stat = argse.expr;
11662     }
11663   else if (flag_coarray == GFC_FCOARRAY_LIB)
11664     stat = null_pointer_node;
11665 
11666   if (flag_coarray == GFC_FCOARRAY_LIB)
11667     {
11668       tree image_index, caf_decl, offset, token;
11669       int op;
11670 
11671       switch (code->resolved_isym->id)
11672 	{
11673 	case GFC_ISYM_ATOMIC_ADD:
11674 	case GFC_ISYM_ATOMIC_FETCH_ADD:
11675 	  op = (int) GFC_CAF_ATOMIC_ADD;
11676 	  break;
11677 	case GFC_ISYM_ATOMIC_AND:
11678 	case GFC_ISYM_ATOMIC_FETCH_AND:
11679 	  op = (int) GFC_CAF_ATOMIC_AND;
11680 	  break;
11681 	case GFC_ISYM_ATOMIC_OR:
11682 	case GFC_ISYM_ATOMIC_FETCH_OR:
11683 	  op = (int) GFC_CAF_ATOMIC_OR;
11684 	  break;
11685 	case GFC_ISYM_ATOMIC_XOR:
11686 	case GFC_ISYM_ATOMIC_FETCH_XOR:
11687 	  op = (int) GFC_CAF_ATOMIC_XOR;
11688 	  break;
11689 	case GFC_ISYM_ATOMIC_DEF:
11690 	  op = 0;  /* Unused.  */
11691 	  break;
11692 	default:
11693 	  gcc_unreachable ();
11694 	}
11695 
11696       caf_decl = gfc_get_tree_for_caf_expr (atom_expr);
11697       if (TREE_CODE (TREE_TYPE (caf_decl)) == REFERENCE_TYPE)
11698 	caf_decl = build_fold_indirect_ref_loc (input_location, caf_decl);
11699 
11700       if (gfc_is_coindexed (atom_expr))
11701 	image_index = gfc_caf_get_image_index (&block, atom_expr, caf_decl);
11702       else
11703 	image_index = integer_zero_node;
11704 
11705       if (!POINTER_TYPE_P (TREE_TYPE (value)))
11706 	{
11707 	  tmp = gfc_create_var (TREE_TYPE (TREE_TYPE (atom)), "value");
11708 	  gfc_add_modify (&block, tmp, fold_convert (TREE_TYPE (tmp), value));
11709           value = gfc_build_addr_expr (NULL_TREE, tmp);
11710 	}
11711 
11712       gfc_init_se (&argse, NULL);
11713       gfc_get_caf_token_offset (&argse, &token, &offset, caf_decl, atom,
11714 				atom_expr);
11715 
11716       gfc_add_block_to_block (&block, &argse.pre);
11717       if (code->resolved_isym->id == GFC_ISYM_ATOMIC_DEF)
11718 	tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_atomic_def, 7,
11719 				   token, offset, image_index, value, stat,
11720 				   build_int_cst (integer_type_node,
11721 						  (int) atom_expr->ts.type),
11722 				   build_int_cst (integer_type_node,
11723 						  (int) atom_expr->ts.kind));
11724       else
11725 	tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_atomic_op, 9,
11726 				   build_int_cst (integer_type_node, op),
11727 				   token, offset, image_index, value, old, stat,
11728 				   build_int_cst (integer_type_node,
11729 						  (int) atom_expr->ts.type),
11730 				   build_int_cst (integer_type_node,
11731 						  (int) atom_expr->ts.kind));
11732 
11733       gfc_add_expr_to_block (&block, tmp);
11734       gfc_add_block_to_block (&block, &argse.post);
11735       gfc_add_block_to_block (&block, &post_block);
11736       return gfc_finish_block (&block);
11737     }
11738 
11739 
11740   switch (code->resolved_isym->id)
11741     {
11742     case GFC_ISYM_ATOMIC_ADD:
11743     case GFC_ISYM_ATOMIC_FETCH_ADD:
11744       fn = BUILT_IN_ATOMIC_FETCH_ADD_N;
11745       break;
11746     case GFC_ISYM_ATOMIC_AND:
11747     case GFC_ISYM_ATOMIC_FETCH_AND:
11748       fn = BUILT_IN_ATOMIC_FETCH_AND_N;
11749       break;
11750     case GFC_ISYM_ATOMIC_DEF:
11751       fn = BUILT_IN_ATOMIC_STORE_N;
11752       break;
11753     case GFC_ISYM_ATOMIC_OR:
11754     case GFC_ISYM_ATOMIC_FETCH_OR:
11755       fn = BUILT_IN_ATOMIC_FETCH_OR_N;
11756       break;
11757     case GFC_ISYM_ATOMIC_XOR:
11758     case GFC_ISYM_ATOMIC_FETCH_XOR:
11759       fn = BUILT_IN_ATOMIC_FETCH_XOR_N;
11760       break;
11761     default:
11762       gcc_unreachable ();
11763     }
11764 
11765   tmp = TREE_TYPE (TREE_TYPE (atom));
11766   fn = (built_in_function) ((int) fn
11767 			    + exact_log2 (tree_to_uhwi (TYPE_SIZE_UNIT (tmp)))
11768 			    + 1);
11769   tree itype = TREE_TYPE (TREE_TYPE (atom));
11770   tmp = builtin_decl_explicit (fn);
11771 
11772   switch (code->resolved_isym->id)
11773     {
11774     case GFC_ISYM_ATOMIC_ADD:
11775     case GFC_ISYM_ATOMIC_AND:
11776     case GFC_ISYM_ATOMIC_DEF:
11777     case GFC_ISYM_ATOMIC_OR:
11778     case GFC_ISYM_ATOMIC_XOR:
11779       tmp = build_call_expr_loc (input_location, tmp, 3, atom,
11780 				 fold_convert (itype, value),
11781 				 build_int_cst (NULL, MEMMODEL_RELAXED));
11782       gfc_add_expr_to_block (&block, tmp);
11783       break;
11784     default:
11785       tmp = build_call_expr_loc (input_location, tmp, 3, atom,
11786 				 fold_convert (itype, value),
11787 				 build_int_cst (NULL, MEMMODEL_RELAXED));
11788       gfc_add_modify (&block, old, fold_convert (TREE_TYPE (old), tmp));
11789       break;
11790     }
11791 
11792   if (stat != NULL_TREE)
11793     gfc_add_modify (&block, stat, build_int_cst (TREE_TYPE (stat), 0));
11794   gfc_add_block_to_block (&block, &post_block);
11795   return gfc_finish_block (&block);
11796 }
11797 
11798 
11799 static tree
conv_intrinsic_atomic_ref(gfc_code * code)11800 conv_intrinsic_atomic_ref (gfc_code *code)
11801 {
11802   gfc_se argse;
11803   tree tmp, atom, value, stat = NULL_TREE;
11804   stmtblock_t block, post_block;
11805   built_in_function fn;
11806   gfc_expr *atom_expr = code->ext.actual->next->expr;
11807 
11808   if (atom_expr->expr_type == EXPR_FUNCTION
11809       && atom_expr->value.function.isym
11810       && atom_expr->value.function.isym->id == GFC_ISYM_CAF_GET)
11811     atom_expr = atom_expr->value.function.actual->expr;
11812 
11813   gfc_start_block (&block);
11814   gfc_init_block (&post_block);
11815   gfc_init_se (&argse, NULL);
11816   argse.want_pointer = 1;
11817   gfc_conv_expr (&argse, atom_expr);
11818   gfc_add_block_to_block (&block, &argse.pre);
11819   gfc_add_block_to_block (&post_block, &argse.post);
11820   atom = argse.expr;
11821 
11822   gfc_init_se (&argse, NULL);
11823   if (flag_coarray == GFC_FCOARRAY_LIB
11824       && code->ext.actual->expr->ts.kind == atom_expr->ts.kind)
11825     argse.want_pointer = 1;
11826   gfc_conv_expr (&argse, code->ext.actual->expr);
11827   gfc_add_block_to_block (&block, &argse.pre);
11828   gfc_add_block_to_block (&post_block, &argse.post);
11829   value = argse.expr;
11830 
11831   /* STAT=  */
11832   if (code->ext.actual->next->next->expr != NULL)
11833     {
11834       gcc_assert (code->ext.actual->next->next->expr->expr_type
11835 		  == EXPR_VARIABLE);
11836       gfc_init_se (&argse, NULL);
11837       if (flag_coarray == GFC_FCOARRAY_LIB)
11838 	argse.want_pointer = 1;
11839       gfc_conv_expr_val (&argse, code->ext.actual->next->next->expr);
11840       gfc_add_block_to_block (&block, &argse.pre);
11841       gfc_add_block_to_block (&post_block, &argse.post);
11842       stat = argse.expr;
11843     }
11844   else if (flag_coarray == GFC_FCOARRAY_LIB)
11845     stat = null_pointer_node;
11846 
11847   if (flag_coarray == GFC_FCOARRAY_LIB)
11848     {
11849       tree image_index, caf_decl, offset, token;
11850       tree orig_value = NULL_TREE, vardecl = NULL_TREE;
11851 
11852       caf_decl = gfc_get_tree_for_caf_expr (atom_expr);
11853       if (TREE_CODE (TREE_TYPE (caf_decl)) == REFERENCE_TYPE)
11854 	caf_decl = build_fold_indirect_ref_loc (input_location, caf_decl);
11855 
11856       if (gfc_is_coindexed (atom_expr))
11857 	image_index = gfc_caf_get_image_index (&block, atom_expr, caf_decl);
11858       else
11859 	image_index = integer_zero_node;
11860 
11861       gfc_init_se (&argse, NULL);
11862       gfc_get_caf_token_offset (&argse, &token, &offset, caf_decl, atom,
11863 				atom_expr);
11864       gfc_add_block_to_block (&block, &argse.pre);
11865 
11866       /* Different type, need type conversion.  */
11867       if (!POINTER_TYPE_P (TREE_TYPE (value)))
11868 	{
11869 	  vardecl = gfc_create_var (TREE_TYPE (TREE_TYPE (atom)), "value");
11870           orig_value = value;
11871           value = gfc_build_addr_expr (NULL_TREE, vardecl);
11872 	}
11873 
11874       tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_atomic_ref, 7,
11875 				 token, offset, image_index, value, stat,
11876 				 build_int_cst (integer_type_node,
11877 						(int) atom_expr->ts.type),
11878 				 build_int_cst (integer_type_node,
11879 						(int) atom_expr->ts.kind));
11880       gfc_add_expr_to_block (&block, tmp);
11881       if (vardecl != NULL_TREE)
11882 	gfc_add_modify (&block, orig_value,
11883 			fold_convert (TREE_TYPE (orig_value), vardecl));
11884       gfc_add_block_to_block (&block, &argse.post);
11885       gfc_add_block_to_block (&block, &post_block);
11886       return gfc_finish_block (&block);
11887     }
11888 
11889   tmp = TREE_TYPE (TREE_TYPE (atom));
11890   fn = (built_in_function) ((int) BUILT_IN_ATOMIC_LOAD_N
11891 			    + exact_log2 (tree_to_uhwi (TYPE_SIZE_UNIT (tmp)))
11892 			    + 1);
11893   tmp = builtin_decl_explicit (fn);
11894   tmp = build_call_expr_loc (input_location, tmp, 2, atom,
11895 			     build_int_cst (integer_type_node,
11896 					    MEMMODEL_RELAXED));
11897   gfc_add_modify (&block, value, fold_convert (TREE_TYPE (value), tmp));
11898 
11899   if (stat != NULL_TREE)
11900     gfc_add_modify (&block, stat, build_int_cst (TREE_TYPE (stat), 0));
11901   gfc_add_block_to_block (&block, &post_block);
11902   return gfc_finish_block (&block);
11903 }
11904 
11905 
11906 static tree
conv_intrinsic_atomic_cas(gfc_code * code)11907 conv_intrinsic_atomic_cas (gfc_code *code)
11908 {
11909   gfc_se argse;
11910   tree tmp, atom, old, new_val, comp, stat = NULL_TREE;
11911   stmtblock_t block, post_block;
11912   built_in_function fn;
11913   gfc_expr *atom_expr = code->ext.actual->expr;
11914 
11915   if (atom_expr->expr_type == EXPR_FUNCTION
11916       && atom_expr->value.function.isym
11917       && atom_expr->value.function.isym->id == GFC_ISYM_CAF_GET)
11918     atom_expr = atom_expr->value.function.actual->expr;
11919 
11920   gfc_init_block (&block);
11921   gfc_init_block (&post_block);
11922   gfc_init_se (&argse, NULL);
11923   argse.want_pointer = 1;
11924   gfc_conv_expr (&argse, atom_expr);
11925   atom = argse.expr;
11926 
11927   gfc_init_se (&argse, NULL);
11928   if (flag_coarray == GFC_FCOARRAY_LIB)
11929     argse.want_pointer = 1;
11930   gfc_conv_expr (&argse, code->ext.actual->next->expr);
11931   gfc_add_block_to_block (&block, &argse.pre);
11932   gfc_add_block_to_block (&post_block, &argse.post);
11933   old = argse.expr;
11934 
11935   gfc_init_se (&argse, NULL);
11936   if (flag_coarray == GFC_FCOARRAY_LIB)
11937     argse.want_pointer = 1;
11938   gfc_conv_expr (&argse, code->ext.actual->next->next->expr);
11939   gfc_add_block_to_block (&block, &argse.pre);
11940   gfc_add_block_to_block (&post_block, &argse.post);
11941   comp = argse.expr;
11942 
11943   gfc_init_se (&argse, NULL);
11944   if (flag_coarray == GFC_FCOARRAY_LIB
11945       && code->ext.actual->next->next->next->expr->ts.kind
11946 	 == atom_expr->ts.kind)
11947     argse.want_pointer = 1;
11948   gfc_conv_expr (&argse, code->ext.actual->next->next->next->expr);
11949   gfc_add_block_to_block (&block, &argse.pre);
11950   gfc_add_block_to_block (&post_block, &argse.post);
11951   new_val = argse.expr;
11952 
11953   /* STAT=  */
11954   if (code->ext.actual->next->next->next->next->expr != NULL)
11955     {
11956       gcc_assert (code->ext.actual->next->next->next->next->expr->expr_type
11957 		  == EXPR_VARIABLE);
11958       gfc_init_se (&argse, NULL);
11959       if (flag_coarray == GFC_FCOARRAY_LIB)
11960 	argse.want_pointer = 1;
11961       gfc_conv_expr_val (&argse,
11962 			 code->ext.actual->next->next->next->next->expr);
11963       gfc_add_block_to_block (&block, &argse.pre);
11964       gfc_add_block_to_block (&post_block, &argse.post);
11965       stat = argse.expr;
11966     }
11967   else if (flag_coarray == GFC_FCOARRAY_LIB)
11968     stat = null_pointer_node;
11969 
11970   if (flag_coarray == GFC_FCOARRAY_LIB)
11971     {
11972       tree image_index, caf_decl, offset, token;
11973 
11974       caf_decl = gfc_get_tree_for_caf_expr (atom_expr);
11975       if (TREE_CODE (TREE_TYPE (caf_decl)) == REFERENCE_TYPE)
11976 	caf_decl = build_fold_indirect_ref_loc (input_location, caf_decl);
11977 
11978       if (gfc_is_coindexed (atom_expr))
11979 	image_index = gfc_caf_get_image_index (&block, atom_expr, caf_decl);
11980       else
11981 	image_index = integer_zero_node;
11982 
11983       if (TREE_TYPE (TREE_TYPE (new_val)) != TREE_TYPE (TREE_TYPE (old)))
11984 	{
11985 	  tmp = gfc_create_var (TREE_TYPE (TREE_TYPE (old)), "new");
11986 	  gfc_add_modify (&block, tmp, fold_convert (TREE_TYPE (tmp), new_val));
11987           new_val = gfc_build_addr_expr (NULL_TREE, tmp);
11988 	}
11989 
11990       /* Convert a constant to a pointer.  */
11991       if (!POINTER_TYPE_P (TREE_TYPE (comp)))
11992 	{
11993 	  tmp = gfc_create_var (TREE_TYPE (TREE_TYPE (old)), "comp");
11994 	  gfc_add_modify (&block, tmp, fold_convert (TREE_TYPE (tmp), comp));
11995           comp = gfc_build_addr_expr (NULL_TREE, tmp);
11996 	}
11997 
11998       gfc_init_se (&argse, NULL);
11999       gfc_get_caf_token_offset (&argse, &token, &offset, caf_decl, atom,
12000 				atom_expr);
12001       gfc_add_block_to_block (&block, &argse.pre);
12002 
12003       tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_atomic_cas, 9,
12004 				 token, offset, image_index, old, comp, new_val,
12005 				 stat, build_int_cst (integer_type_node,
12006 						      (int) atom_expr->ts.type),
12007 				 build_int_cst (integer_type_node,
12008 						(int) atom_expr->ts.kind));
12009       gfc_add_expr_to_block (&block, tmp);
12010       gfc_add_block_to_block (&block, &argse.post);
12011       gfc_add_block_to_block (&block, &post_block);
12012       return gfc_finish_block (&block);
12013     }
12014 
12015   tmp = TREE_TYPE (TREE_TYPE (atom));
12016   fn = (built_in_function) ((int) BUILT_IN_ATOMIC_COMPARE_EXCHANGE_N
12017 			    + exact_log2 (tree_to_uhwi (TYPE_SIZE_UNIT (tmp)))
12018 			    + 1);
12019   tmp = builtin_decl_explicit (fn);
12020 
12021   gfc_add_modify (&block, old, comp);
12022   tmp = build_call_expr_loc (input_location, tmp, 6, atom,
12023 			     gfc_build_addr_expr (NULL, old),
12024 			     fold_convert (TREE_TYPE (old), new_val),
12025 			     boolean_false_node,
12026 			     build_int_cst (NULL, MEMMODEL_RELAXED),
12027 			     build_int_cst (NULL, MEMMODEL_RELAXED));
12028   gfc_add_expr_to_block (&block, tmp);
12029 
12030   if (stat != NULL_TREE)
12031     gfc_add_modify (&block, stat, build_int_cst (TREE_TYPE (stat), 0));
12032   gfc_add_block_to_block (&block, &post_block);
12033   return gfc_finish_block (&block);
12034 }
12035 
12036 static tree
conv_intrinsic_event_query(gfc_code * code)12037 conv_intrinsic_event_query (gfc_code *code)
12038 {
12039   gfc_se se, argse;
12040   tree stat = NULL_TREE, stat2 = NULL_TREE;
12041   tree count = NULL_TREE, count2 = NULL_TREE;
12042 
12043   gfc_expr *event_expr = code->ext.actual->expr;
12044 
12045   if (code->ext.actual->next->next->expr)
12046     {
12047       gcc_assert (code->ext.actual->next->next->expr->expr_type
12048 		  == EXPR_VARIABLE);
12049       gfc_init_se (&argse, NULL);
12050       gfc_conv_expr_val (&argse, code->ext.actual->next->next->expr);
12051       stat = argse.expr;
12052     }
12053   else if (flag_coarray == GFC_FCOARRAY_LIB)
12054     stat = null_pointer_node;
12055 
12056   if (code->ext.actual->next->expr)
12057     {
12058       gcc_assert (code->ext.actual->next->expr->expr_type == EXPR_VARIABLE);
12059       gfc_init_se (&argse, NULL);
12060       gfc_conv_expr_val (&argse, code->ext.actual->next->expr);
12061       count = argse.expr;
12062     }
12063 
12064   gfc_start_block (&se.pre);
12065   if (flag_coarray == GFC_FCOARRAY_LIB)
12066     {
12067       tree tmp, token, image_index;
12068       tree index = build_zero_cst (gfc_array_index_type);
12069 
12070       if (event_expr->expr_type == EXPR_FUNCTION
12071 	  && event_expr->value.function.isym
12072 	  && event_expr->value.function.isym->id == GFC_ISYM_CAF_GET)
12073 	event_expr = event_expr->value.function.actual->expr;
12074 
12075       tree caf_decl = gfc_get_tree_for_caf_expr (event_expr);
12076 
12077       if (event_expr->symtree->n.sym->ts.type != BT_DERIVED
12078 	  || event_expr->symtree->n.sym->ts.u.derived->from_intmod
12079 	     != INTMOD_ISO_FORTRAN_ENV
12080 	  || event_expr->symtree->n.sym->ts.u.derived->intmod_sym_id
12081 	     != ISOFORTRAN_EVENT_TYPE)
12082 	{
12083 	  gfc_error ("Sorry, the event component of derived type at %L is not "
12084 		     "yet supported", &event_expr->where);
12085 	  return NULL_TREE;
12086 	}
12087 
12088       if (gfc_is_coindexed (event_expr))
12089 	{
12090 	  gfc_error ("The event variable at %L shall not be coindexed",
12091 		     &event_expr->where);
12092           return NULL_TREE;
12093 	}
12094 
12095       image_index = integer_zero_node;
12096 
12097       gfc_get_caf_token_offset (&se, &token, NULL, caf_decl, NULL_TREE,
12098 				event_expr);
12099 
12100       /* For arrays, obtain the array index.  */
12101       if (gfc_expr_attr (event_expr).dimension)
12102 	{
12103 	  tree desc, tmp, extent, lbound, ubound;
12104           gfc_array_ref *ar, ar2;
12105           int i;
12106 
12107 	  /* TODO: Extend this, once DT components are supported.  */
12108 	  ar = &event_expr->ref->u.ar;
12109 	  ar2 = *ar;
12110 	  memset (ar, '\0', sizeof (*ar));
12111 	  ar->as = ar2.as;
12112 	  ar->type = AR_FULL;
12113 
12114 	  gfc_init_se (&argse, NULL);
12115 	  argse.descriptor_only = 1;
12116 	  gfc_conv_expr_descriptor (&argse, event_expr);
12117 	  gfc_add_block_to_block (&se.pre, &argse.pre);
12118 	  desc = argse.expr;
12119 	  *ar = ar2;
12120 
12121 	  extent = build_one_cst (gfc_array_index_type);
12122 	  for (i = 0; i < ar->dimen; i++)
12123 	    {
12124 	      gfc_init_se (&argse, NULL);
12125 	      gfc_conv_expr_type (&argse, ar->start[i], gfc_array_index_type);
12126 	      gfc_add_block_to_block (&argse.pre, &argse.pre);
12127 	      lbound = gfc_conv_descriptor_lbound_get (desc, gfc_rank_cst[i]);
12128 	      tmp = fold_build2_loc (input_location, MINUS_EXPR,
12129 				     TREE_TYPE (lbound), argse.expr, lbound);
12130 	      tmp = fold_build2_loc (input_location, MULT_EXPR,
12131 				     TREE_TYPE (tmp), extent, tmp);
12132 	      index = fold_build2_loc (input_location, PLUS_EXPR,
12133 				       TREE_TYPE (tmp), index, tmp);
12134 	      if (i < ar->dimen - 1)
12135 		{
12136 		  ubound = gfc_conv_descriptor_ubound_get (desc, gfc_rank_cst[i]);
12137 		  tmp = gfc_conv_array_extent_dim (lbound, ubound, NULL);
12138 		  extent = fold_build2_loc (input_location, MULT_EXPR,
12139 					    TREE_TYPE (tmp), extent, tmp);
12140 		}
12141 	    }
12142 	}
12143 
12144       if (count != null_pointer_node && TREE_TYPE (count) != integer_type_node)
12145 	{
12146 	  count2 = count;
12147 	  count = gfc_create_var (integer_type_node, "count");
12148 	}
12149 
12150       if (stat != null_pointer_node && TREE_TYPE (stat) != integer_type_node)
12151 	{
12152 	  stat2 = stat;
12153 	  stat = gfc_create_var (integer_type_node, "stat");
12154 	}
12155 
12156       index = fold_convert (size_type_node, index);
12157       tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_event_query, 5,
12158                                    token, index, image_index, count
12159 				   ? gfc_build_addr_expr (NULL, count) : count,
12160 				   stat != null_pointer_node
12161 				   ? gfc_build_addr_expr (NULL, stat) : stat);
12162       gfc_add_expr_to_block (&se.pre, tmp);
12163 
12164       if (count2 != NULL_TREE)
12165 	gfc_add_modify (&se.pre, count2,
12166 			fold_convert (TREE_TYPE (count2), count));
12167 
12168       if (stat2 != NULL_TREE)
12169 	gfc_add_modify (&se.pre, stat2,
12170 			fold_convert (TREE_TYPE (stat2), stat));
12171 
12172       return gfc_finish_block (&se.pre);
12173     }
12174 
12175   gfc_init_se (&argse, NULL);
12176   gfc_conv_expr_val (&argse, code->ext.actual->expr);
12177   gfc_add_modify (&se.pre, count, fold_convert (TREE_TYPE (count), argse.expr));
12178 
12179   if (stat != NULL_TREE)
12180     gfc_add_modify (&se.pre, stat, build_int_cst (TREE_TYPE (stat), 0));
12181 
12182   return gfc_finish_block (&se.pre);
12183 }
12184 
12185 
12186 /* This is a peculiar case because of the need to do dependency checking.
12187    It is called via trans-stmt.cc(gfc_trans_call), where it is picked out as
12188    a special case and this function called instead of
12189    gfc_conv_procedure_call.  */
12190 void
gfc_conv_intrinsic_mvbits(gfc_se * se,gfc_actual_arglist * actual_args,gfc_loopinfo * loop)12191 gfc_conv_intrinsic_mvbits (gfc_se *se, gfc_actual_arglist *actual_args,
12192 			   gfc_loopinfo *loop)
12193 {
12194   gfc_actual_arglist *actual;
12195   gfc_se argse[5];
12196   gfc_expr *arg[5];
12197   gfc_ss *lss;
12198   int n;
12199 
12200   tree from, frompos, len, to, topos;
12201   tree lenmask, oldbits, newbits, bitsize;
12202   tree type, utype, above, mask1, mask2;
12203 
12204   if (loop)
12205     lss = loop->ss;
12206   else
12207     lss = gfc_ss_terminator;
12208 
12209   actual = actual_args;
12210   for (n = 0; n < 5; n++, actual = actual->next)
12211     {
12212       arg[n] = actual->expr;
12213       gfc_init_se (&argse[n], NULL);
12214 
12215       if (lss != gfc_ss_terminator)
12216 	{
12217 	  gfc_copy_loopinfo_to_se (&argse[n], loop);
12218 	  /* Find the ss for the expression if it is there.  */
12219 	  argse[n].ss = lss;
12220 	  gfc_mark_ss_chain_used (lss, 1);
12221 	}
12222 
12223       gfc_conv_expr (&argse[n], arg[n]);
12224 
12225       if (loop)
12226 	lss = argse[n].ss;
12227     }
12228 
12229   from    = argse[0].expr;
12230   frompos = argse[1].expr;
12231   len     = argse[2].expr;
12232   to      = argse[3].expr;
12233   topos   = argse[4].expr;
12234 
12235   /* The type of the result (TO).  */
12236   type    = TREE_TYPE (to);
12237   bitsize = build_int_cst (integer_type_node, TYPE_PRECISION (type));
12238 
12239   /* Optionally generate code for runtime argument check.  */
12240   if (gfc_option.rtcheck & GFC_RTCHECK_BITS)
12241     {
12242       tree nbits, below, ccond;
12243       tree fp = fold_convert (long_integer_type_node, frompos);
12244       tree ln = fold_convert (long_integer_type_node, len);
12245       tree tp = fold_convert (long_integer_type_node, topos);
12246       below = fold_build2_loc (input_location, LT_EXPR,
12247 			       logical_type_node, frompos,
12248 			       build_int_cst (TREE_TYPE (frompos), 0));
12249       above = fold_build2_loc (input_location, GT_EXPR,
12250 			       logical_type_node, frompos,
12251 			       fold_convert (TREE_TYPE (frompos), bitsize));
12252       ccond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
12253 			       logical_type_node, below, above);
12254       gfc_trans_runtime_check (true, false, ccond, &argse[1].pre,
12255 			       &arg[1]->where,
12256 			       "FROMPOS argument (%ld) out of range 0:%d "
12257 			       "in intrinsic MVBITS", fp, bitsize);
12258       below = fold_build2_loc (input_location, LT_EXPR,
12259 			       logical_type_node, len,
12260 			       build_int_cst (TREE_TYPE (len), 0));
12261       above = fold_build2_loc (input_location, GT_EXPR,
12262 			       logical_type_node, len,
12263 			       fold_convert (TREE_TYPE (len), bitsize));
12264       ccond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
12265 			       logical_type_node, below, above);
12266       gfc_trans_runtime_check (true, false, ccond, &argse[2].pre,
12267 			       &arg[2]->where,
12268 			       "LEN argument (%ld) out of range 0:%d "
12269 			       "in intrinsic MVBITS", ln, bitsize);
12270       below = fold_build2_loc (input_location, LT_EXPR,
12271 			       logical_type_node, topos,
12272 			       build_int_cst (TREE_TYPE (topos), 0));
12273       above = fold_build2_loc (input_location, GT_EXPR,
12274 			       logical_type_node, topos,
12275 			       fold_convert (TREE_TYPE (topos), bitsize));
12276       ccond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
12277 			       logical_type_node, below, above);
12278       gfc_trans_runtime_check (true, false, ccond, &argse[4].pre,
12279 			       &arg[4]->where,
12280 			       "TOPOS argument (%ld) out of range 0:%d "
12281 			       "in intrinsic MVBITS", tp, bitsize);
12282 
12283       /* The tests above ensure that FROMPOS, LEN and TOPOS fit into short
12284 	 integers.  Additions below cannot overflow.  */
12285       nbits = fold_convert (long_integer_type_node, bitsize);
12286       above = fold_build2_loc (input_location, PLUS_EXPR,
12287 			       long_integer_type_node, fp, ln);
12288       ccond = fold_build2_loc (input_location, GT_EXPR,
12289 			       logical_type_node, above, nbits);
12290       gfc_trans_runtime_check (true, false, ccond, &argse[1].pre,
12291 			       &arg[1]->where,
12292 			       "FROMPOS(%ld)+LEN(%ld)>BIT_SIZE(%d) "
12293 			       "in intrinsic MVBITS", fp, ln, bitsize);
12294       above = fold_build2_loc (input_location, PLUS_EXPR,
12295 			       long_integer_type_node, tp, ln);
12296       ccond = fold_build2_loc (input_location, GT_EXPR,
12297 			       logical_type_node, above, nbits);
12298       gfc_trans_runtime_check (true, false, ccond, &argse[4].pre,
12299 			       &arg[4]->where,
12300 			       "TOPOS(%ld)+LEN(%ld)>BIT_SIZE(%d) "
12301 			       "in intrinsic MVBITS", tp, ln, bitsize);
12302     }
12303 
12304   for (n = 0; n < 5; n++)
12305     {
12306       gfc_add_block_to_block (&se->pre, &argse[n].pre);
12307       gfc_add_block_to_block (&se->post, &argse[n].post);
12308     }
12309 
12310   /* lenmask = (LEN >= bit_size (TYPE)) ? ~(TYPE)0 : ((TYPE)1 << LEN) - 1  */
12311   above = fold_build2_loc (input_location, GE_EXPR, logical_type_node,
12312 			   len, fold_convert (TREE_TYPE (len), bitsize));
12313   mask1 = build_int_cst (type, -1);
12314   mask2 = fold_build2_loc (input_location, LSHIFT_EXPR, type,
12315 			   build_int_cst (type, 1), len);
12316   mask2 = fold_build2_loc (input_location, MINUS_EXPR, type,
12317 			   mask2, build_int_cst (type, 1));
12318   lenmask = fold_build3_loc (input_location, COND_EXPR, type,
12319 			     above, mask1, mask2);
12320 
12321   /* newbits = (((UTYPE)(FROM) >> FROMPOS) & lenmask) << TOPOS.
12322    * For valid frompos+len <= bit_size(FROM) the conversion to unsigned is
12323    * not strictly necessary; artificial bits from rshift will be masked.  */
12324   utype = unsigned_type_for (type);
12325   newbits = fold_build2_loc (input_location, RSHIFT_EXPR, utype,
12326 			     fold_convert (utype, from), frompos);
12327   newbits = fold_build2_loc (input_location, BIT_AND_EXPR, type,
12328 			     fold_convert (type, newbits), lenmask);
12329   newbits = fold_build2_loc (input_location, LSHIFT_EXPR, type,
12330 			     newbits, topos);
12331 
12332   /* oldbits = TO & (~(lenmask << TOPOS)).  */
12333   oldbits = fold_build2_loc (input_location, LSHIFT_EXPR, type,
12334 			     lenmask, topos);
12335   oldbits = fold_build1_loc (input_location, BIT_NOT_EXPR, type, oldbits);
12336   oldbits = fold_build2_loc (input_location, BIT_AND_EXPR, type, oldbits, to);
12337 
12338   /* TO = newbits | oldbits.  */
12339   se->expr = fold_build2_loc (input_location, BIT_IOR_EXPR, type,
12340 			      oldbits, newbits);
12341 
12342   /* Return the assignment.  */
12343   se->expr = fold_build2_loc (input_location, MODIFY_EXPR,
12344 			      void_type_node, to, se->expr);
12345 }
12346 
12347 
12348 static tree
conv_intrinsic_move_alloc(gfc_code * code)12349 conv_intrinsic_move_alloc (gfc_code *code)
12350 {
12351   stmtblock_t block;
12352   gfc_expr *from_expr, *to_expr;
12353   gfc_expr *to_expr2, *from_expr2 = NULL;
12354   gfc_se from_se, to_se;
12355   tree tmp;
12356   bool coarray;
12357 
12358   gfc_start_block (&block);
12359 
12360   from_expr = code->ext.actual->expr;
12361   to_expr = code->ext.actual->next->expr;
12362 
12363   gfc_init_se (&from_se, NULL);
12364   gfc_init_se (&to_se, NULL);
12365 
12366   gcc_assert (from_expr->ts.type != BT_CLASS
12367 	      || to_expr->ts.type == BT_CLASS);
12368   coarray = gfc_get_corank (from_expr) != 0;
12369 
12370   if (from_expr->rank == 0 && !coarray)
12371     {
12372       if (from_expr->ts.type != BT_CLASS)
12373 	from_expr2 = from_expr;
12374       else
12375 	{
12376 	  from_expr2 = gfc_copy_expr (from_expr);
12377 	  gfc_add_data_component (from_expr2);
12378 	}
12379 
12380       if (to_expr->ts.type != BT_CLASS)
12381 	to_expr2 = to_expr;
12382       else
12383 	{
12384 	  to_expr2 = gfc_copy_expr (to_expr);
12385 	  gfc_add_data_component (to_expr2);
12386 	}
12387 
12388       from_se.want_pointer = 1;
12389       to_se.want_pointer = 1;
12390       gfc_conv_expr (&from_se, from_expr2);
12391       gfc_conv_expr (&to_se, to_expr2);
12392       gfc_add_block_to_block (&block, &from_se.pre);
12393       gfc_add_block_to_block (&block, &to_se.pre);
12394 
12395       /* Deallocate "to".  */
12396       tmp = gfc_deallocate_scalar_with_status (to_se.expr, NULL_TREE, NULL_TREE,
12397 					       true, to_expr, to_expr->ts);
12398       gfc_add_expr_to_block (&block, tmp);
12399 
12400       /* Assign (_data) pointers.  */
12401       gfc_add_modify_loc (input_location, &block, to_se.expr,
12402 			  fold_convert (TREE_TYPE (to_se.expr), from_se.expr));
12403 
12404       /* Set "from" to NULL.  */
12405       gfc_add_modify_loc (input_location, &block, from_se.expr,
12406 			  fold_convert (TREE_TYPE (from_se.expr), null_pointer_node));
12407 
12408       gfc_add_block_to_block (&block, &from_se.post);
12409       gfc_add_block_to_block (&block, &to_se.post);
12410 
12411       /* Set _vptr.  */
12412       if (to_expr->ts.type == BT_CLASS)
12413 	{
12414 	  gfc_symbol *vtab;
12415 
12416 	  gfc_free_expr (to_expr2);
12417 	  gfc_init_se (&to_se, NULL);
12418 	  to_se.want_pointer = 1;
12419 	  gfc_add_vptr_component (to_expr);
12420 	  gfc_conv_expr (&to_se, to_expr);
12421 
12422 	  if (from_expr->ts.type == BT_CLASS)
12423 	    {
12424 	      if (UNLIMITED_POLY (from_expr))
12425 		vtab = NULL;
12426 	      else
12427 		{
12428 		  vtab = gfc_find_derived_vtab (from_expr->ts.u.derived);
12429 		  gcc_assert (vtab);
12430 		}
12431 
12432 	      gfc_free_expr (from_expr2);
12433 	      gfc_init_se (&from_se, NULL);
12434 	      from_se.want_pointer = 1;
12435 	      gfc_add_vptr_component (from_expr);
12436 	      gfc_conv_expr (&from_se, from_expr);
12437 	      gfc_add_modify_loc (input_location, &block, to_se.expr,
12438 				  fold_convert (TREE_TYPE (to_se.expr),
12439 				  from_se.expr));
12440 
12441               /* Reset _vptr component to declared type.  */
12442 	      if (vtab == NULL)
12443 		/* Unlimited polymorphic.  */
12444 		gfc_add_modify_loc (input_location, &block, from_se.expr,
12445 				    fold_convert (TREE_TYPE (from_se.expr),
12446 						  null_pointer_node));
12447 	      else
12448 		{
12449 		  tmp = gfc_build_addr_expr (NULL_TREE, gfc_get_symbol_decl (vtab));
12450 		  gfc_add_modify_loc (input_location, &block, from_se.expr,
12451 				      fold_convert (TREE_TYPE (from_se.expr), tmp));
12452 		}
12453 	    }
12454 	  else
12455 	    {
12456 	      vtab = gfc_find_vtab (&from_expr->ts);
12457 	      gcc_assert (vtab);
12458 	      tmp = gfc_build_addr_expr (NULL_TREE, gfc_get_symbol_decl (vtab));
12459 	      gfc_add_modify_loc (input_location, &block, to_se.expr,
12460 				  fold_convert (TREE_TYPE (to_se.expr), tmp));
12461 	    }
12462 	}
12463 
12464       if (to_expr->ts.type == BT_CHARACTER && to_expr->ts.deferred)
12465 	{
12466 	  gfc_add_modify_loc (input_location, &block, to_se.string_length,
12467 			      fold_convert (TREE_TYPE (to_se.string_length),
12468 					    from_se.string_length));
12469 	  if (from_expr->ts.deferred)
12470 	    gfc_add_modify_loc (input_location, &block, from_se.string_length,
12471 			build_int_cst (TREE_TYPE (from_se.string_length), 0));
12472 	}
12473 
12474       return gfc_finish_block (&block);
12475     }
12476 
12477   /* Update _vptr component.  */
12478   if (to_expr->ts.type == BT_CLASS)
12479     {
12480       gfc_symbol *vtab;
12481 
12482       to_se.want_pointer = 1;
12483       to_expr2 = gfc_copy_expr (to_expr);
12484       gfc_add_vptr_component (to_expr2);
12485       gfc_conv_expr (&to_se, to_expr2);
12486 
12487       if (from_expr->ts.type == BT_CLASS)
12488 	{
12489 	  if (UNLIMITED_POLY (from_expr))
12490 	    vtab = NULL;
12491 	  else
12492 	    {
12493 	      vtab = gfc_find_derived_vtab (from_expr->ts.u.derived);
12494 	      gcc_assert (vtab);
12495 	    }
12496 
12497 	  from_se.want_pointer = 1;
12498 	  from_expr2 = gfc_copy_expr (from_expr);
12499 	  gfc_add_vptr_component (from_expr2);
12500 	  gfc_conv_expr (&from_se, from_expr2);
12501 	  gfc_add_modify_loc (input_location, &block, to_se.expr,
12502 			      fold_convert (TREE_TYPE (to_se.expr),
12503 			      from_se.expr));
12504 
12505 	  /* Reset _vptr component to declared type.  */
12506 	  if (vtab == NULL)
12507 	    /* Unlimited polymorphic.  */
12508 	    gfc_add_modify_loc (input_location, &block, from_se.expr,
12509 				fold_convert (TREE_TYPE (from_se.expr),
12510 					      null_pointer_node));
12511 	  else
12512 	    {
12513 	      tmp = gfc_build_addr_expr (NULL_TREE, gfc_get_symbol_decl (vtab));
12514 	      gfc_add_modify_loc (input_location, &block, from_se.expr,
12515 				  fold_convert (TREE_TYPE (from_se.expr), tmp));
12516 	    }
12517 	}
12518       else
12519 	{
12520 	  vtab = gfc_find_vtab (&from_expr->ts);
12521 	  gcc_assert (vtab);
12522 	  tmp = gfc_build_addr_expr (NULL_TREE, gfc_get_symbol_decl (vtab));
12523 	  gfc_add_modify_loc (input_location, &block, to_se.expr,
12524 			      fold_convert (TREE_TYPE (to_se.expr), tmp));
12525 	}
12526 
12527       gfc_free_expr (to_expr2);
12528       gfc_init_se (&to_se, NULL);
12529 
12530       if (from_expr->ts.type == BT_CLASS)
12531 	{
12532 	  gfc_free_expr (from_expr2);
12533 	  gfc_init_se (&from_se, NULL);
12534 	}
12535     }
12536 
12537 
12538   /* Deallocate "to".  */
12539   if (from_expr->rank == 0)
12540     {
12541       to_se.want_coarray = 1;
12542       from_se.want_coarray = 1;
12543     }
12544   gfc_conv_expr_descriptor (&to_se, to_expr);
12545   gfc_conv_expr_descriptor (&from_se, from_expr);
12546 
12547   /* For coarrays, call SYNC ALL if TO is already deallocated as MOVE_ALLOC
12548      is an image control "statement", cf. IR F08/0040 in 12-006A.  */
12549   if (coarray && flag_coarray == GFC_FCOARRAY_LIB)
12550     {
12551       tree cond;
12552 
12553       tmp = gfc_deallocate_with_status (to_se.expr, NULL_TREE, NULL_TREE,
12554 					NULL_TREE, NULL_TREE, true, to_expr,
12555 					GFC_CAF_COARRAY_DEALLOCATE_ONLY);
12556       gfc_add_expr_to_block (&block, tmp);
12557 
12558       tmp = gfc_conv_descriptor_data_get (to_se.expr);
12559       cond = fold_build2_loc (input_location, EQ_EXPR,
12560 			      logical_type_node, tmp,
12561 			      fold_convert (TREE_TYPE (tmp),
12562 					    null_pointer_node));
12563       tmp = build_call_expr_loc (input_location, gfor_fndecl_caf_sync_all,
12564 				 3, null_pointer_node, null_pointer_node,
12565 				 build_int_cst (integer_type_node, 0));
12566 
12567       tmp = fold_build3_loc (input_location, COND_EXPR, void_type_node, cond,
12568 			     tmp, build_empty_stmt (input_location));
12569       gfc_add_expr_to_block (&block, tmp);
12570     }
12571   else
12572     {
12573       if (to_expr->ts.type == BT_DERIVED
12574 	  && to_expr->ts.u.derived->attr.alloc_comp)
12575 	{
12576 	  tmp = gfc_deallocate_alloc_comp (to_expr->ts.u.derived,
12577 					   to_se.expr, to_expr->rank);
12578 	  gfc_add_expr_to_block (&block, tmp);
12579 	}
12580 
12581       tmp = gfc_conv_descriptor_data_get (to_se.expr);
12582       tmp = gfc_deallocate_with_status (tmp, NULL_TREE, NULL_TREE, NULL_TREE,
12583 					NULL_TREE, true, to_expr,
12584 					GFC_CAF_COARRAY_NOCOARRAY);
12585       gfc_add_expr_to_block (&block, tmp);
12586     }
12587 
12588   /* Move the pointer and update the array descriptor data.  */
12589   gfc_add_modify_loc (input_location, &block, to_se.expr, from_se.expr);
12590 
12591   /* Set "from" to NULL.  */
12592   tmp = gfc_conv_descriptor_data_get (from_se.expr);
12593   gfc_add_modify_loc (input_location, &block, tmp,
12594 		      fold_convert (TREE_TYPE (tmp), null_pointer_node));
12595 
12596 
12597   if (to_expr->ts.type == BT_CHARACTER && to_expr->ts.deferred)
12598     {
12599       gfc_add_modify_loc (input_location, &block, to_se.string_length,
12600 			  fold_convert (TREE_TYPE (to_se.string_length),
12601 					from_se.string_length));
12602       if (from_expr->ts.deferred)
12603         gfc_add_modify_loc (input_location, &block, from_se.string_length,
12604 			build_int_cst (TREE_TYPE (from_se.string_length), 0));
12605     }
12606 
12607   return gfc_finish_block (&block);
12608 }
12609 
12610 
12611 tree
gfc_conv_intrinsic_subroutine(gfc_code * code)12612 gfc_conv_intrinsic_subroutine (gfc_code *code)
12613 {
12614   tree res;
12615 
12616   gcc_assert (code->resolved_isym);
12617 
12618   switch (code->resolved_isym->id)
12619     {
12620     case GFC_ISYM_MOVE_ALLOC:
12621       res = conv_intrinsic_move_alloc (code);
12622       break;
12623 
12624     case GFC_ISYM_ATOMIC_CAS:
12625       res = conv_intrinsic_atomic_cas (code);
12626       break;
12627 
12628     case GFC_ISYM_ATOMIC_ADD:
12629     case GFC_ISYM_ATOMIC_AND:
12630     case GFC_ISYM_ATOMIC_DEF:
12631     case GFC_ISYM_ATOMIC_OR:
12632     case GFC_ISYM_ATOMIC_XOR:
12633     case GFC_ISYM_ATOMIC_FETCH_ADD:
12634     case GFC_ISYM_ATOMIC_FETCH_AND:
12635     case GFC_ISYM_ATOMIC_FETCH_OR:
12636     case GFC_ISYM_ATOMIC_FETCH_XOR:
12637       res = conv_intrinsic_atomic_op (code);
12638       break;
12639 
12640     case GFC_ISYM_ATOMIC_REF:
12641       res = conv_intrinsic_atomic_ref (code);
12642       break;
12643 
12644     case GFC_ISYM_EVENT_QUERY:
12645       res = conv_intrinsic_event_query (code);
12646       break;
12647 
12648     case GFC_ISYM_C_F_POINTER:
12649     case GFC_ISYM_C_F_PROCPOINTER:
12650       res = conv_isocbinding_subroutine (code);
12651       break;
12652 
12653     case GFC_ISYM_CAF_SEND:
12654       res = conv_caf_send (code);
12655       break;
12656 
12657     case GFC_ISYM_CO_BROADCAST:
12658     case GFC_ISYM_CO_MIN:
12659     case GFC_ISYM_CO_MAX:
12660     case GFC_ISYM_CO_REDUCE:
12661     case GFC_ISYM_CO_SUM:
12662       res = conv_co_collective (code);
12663       break;
12664 
12665     case GFC_ISYM_FREE:
12666       res = conv_intrinsic_free (code);
12667       break;
12668 
12669     case GFC_ISYM_RANDOM_INIT:
12670       res = conv_intrinsic_random_init (code);
12671       break;
12672 
12673     case GFC_ISYM_KILL:
12674       res = conv_intrinsic_kill_sub (code);
12675       break;
12676 
12677     case GFC_ISYM_MVBITS:
12678       res = NULL_TREE;
12679       break;
12680 
12681     case GFC_ISYM_SYSTEM_CLOCK:
12682       res = conv_intrinsic_system_clock (code);
12683       break;
12684 
12685     default:
12686       res = NULL_TREE;
12687       break;
12688     }
12689 
12690   return res;
12691 }
12692 
12693 #include "gt-fortran-trans-intrinsic.h"
12694