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