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