OSDN Git Service

5a0a43ee033f07781b84882e9418f97b49602dcc
[pf3gnuchains/gcc-fork.git] / gcc / fortran / trans-intrinsic.c
1 /* Intrinsic translation
2    Copyright (C) 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010
3    Free Software Foundation, Inc.
4    Contributed by Paul Brook <paul@nowt.org>
5    and Steven Bosscher <s.bosscher@student.tudelft.nl>
6
7 This file is part of GCC.
8
9 GCC is free software; you can redistribute it and/or modify it under
10 the terms of the GNU General Public License as published by the Free
11 Software Foundation; either version 3, or (at your option) any later
12 version.
13
14 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
15 WARRANTY; without even the implied warranty of MERCHANTABILITY or
16 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
17 for more details.
18
19 You should have received a copy of the GNU General Public License
20 along with GCC; see the file COPYING3.  If not see
21 <http://www.gnu.org/licenses/>.  */
22
23 /* trans-intrinsic.c-- generate GENERIC trees for calls to intrinsics.  */
24
25 #include "config.h"
26 #include "system.h"
27 #include "coretypes.h"
28 #include "tm.h"         /* For UNITS_PER_WORD.  */
29 #include "tree.h"
30 #include "ggc.h"
31 #include "diagnostic-core.h"    /* For internal_error.  */
32 #include "toplev.h"     /* For rest_of_decl_compilation.  */
33 #include "flags.h"
34 #include "gfortran.h"
35 #include "arith.h"
36 #include "intrinsic.h"
37 #include "trans.h"
38 #include "trans-const.h"
39 #include "trans-types.h"
40 #include "trans-array.h"
41 #include "defaults.h"
42 /* Only for gfc_trans_assign and gfc_trans_pointer_assign.  */
43 #include "trans-stmt.h"
44
45 /* This maps fortran intrinsic math functions to external library or GCC
46    builtin functions.  */
47 typedef struct GTY(()) gfc_intrinsic_map_t {
48   /* The explicit enum is required to work around inadequacies in the
49      garbage collection/gengtype parsing mechanism.  */
50   enum gfc_isym_id id;
51
52   /* Enum value from the "language-independent", aka C-centric, part
53      of gcc, or END_BUILTINS of no such value set.  */
54   enum built_in_function float_built_in;
55   enum built_in_function double_built_in;
56   enum built_in_function long_double_built_in;
57   enum built_in_function complex_float_built_in;
58   enum built_in_function complex_double_built_in;
59   enum built_in_function complex_long_double_built_in;
60
61   /* True if the naming pattern is to prepend "c" for complex and
62      append "f" for kind=4.  False if the naming pattern is to
63      prepend "_gfortran_" and append "[rc](4|8|10|16)".  */
64   bool libm_name;
65
66   /* True if a complex version of the function exists.  */
67   bool complex_available;
68
69   /* True if the function should be marked const.  */
70   bool is_constant;
71
72   /* The base library name of this function.  */
73   const char *name;
74
75   /* Cache decls created for the various operand types.  */
76   tree real4_decl;
77   tree real8_decl;
78   tree real10_decl;
79   tree real16_decl;
80   tree complex4_decl;
81   tree complex8_decl;
82   tree complex10_decl;
83   tree complex16_decl;
84 }
85 gfc_intrinsic_map_t;
86
87 /* ??? The NARGS==1 hack here is based on the fact that (c99 at least)
88    defines complex variants of all of the entries in mathbuiltins.def
89    except for atan2.  */
90 #define DEFINE_MATH_BUILTIN(ID, NAME, ARGTYPE) \
91   { GFC_ISYM_ ## ID, BUILT_IN_ ## ID ## F, BUILT_IN_ ## ID, \
92     BUILT_IN_ ## ID ## L, END_BUILTINS, END_BUILTINS, END_BUILTINS, \
93     true, false, true, NAME, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, \
94     NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE},
95
96 #define DEFINE_MATH_BUILTIN_C(ID, NAME, ARGTYPE) \
97   { GFC_ISYM_ ## ID, BUILT_IN_ ## ID ## F, BUILT_IN_ ## ID, \
98     BUILT_IN_ ## ID ## L, BUILT_IN_C ## ID ## F, BUILT_IN_C ## ID, \
99     BUILT_IN_C ## ID ## L, true, true, true, NAME, NULL_TREE, NULL_TREE, \
100     NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE},
101
102 #define LIB_FUNCTION(ID, NAME, HAVE_COMPLEX) \
103   { GFC_ISYM_ ## ID, END_BUILTINS, END_BUILTINS, END_BUILTINS, \
104     END_BUILTINS, END_BUILTINS, END_BUILTINS, \
105     false, HAVE_COMPLEX, true, NAME, NULL_TREE, NULL_TREE, NULL_TREE, \
106     NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE }
107
108 #define OTHER_BUILTIN(ID, NAME, TYPE, CONST) \
109   { GFC_ISYM_NONE, BUILT_IN_ ## ID ## F, BUILT_IN_ ## ID, \
110     BUILT_IN_ ## ID ## L, END_BUILTINS, END_BUILTINS, END_BUILTINS, \
111     true, false, CONST, NAME, NULL_TREE, NULL_TREE, \
112     NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE},
113
114 static GTY(()) gfc_intrinsic_map_t gfc_intrinsic_map[] =
115 {
116   /* Functions built into gcc itself (DEFINE_MATH_BUILTIN and
117      DEFINE_MATH_BUILTIN_C), then the built-ins that don't correspond
118      to any GFC_ISYM id directly, which use the OTHER_BUILTIN macro.  */
119 #include "mathbuiltins.def"
120
121   /* Functions in libgfortran.  */
122   LIB_FUNCTION (ERFC_SCALED, "erfc_scaled", false),
123
124   /* End the list.  */
125   LIB_FUNCTION (NONE, NULL, false)
126
127 };
128 #undef OTHER_BUILTIN
129 #undef LIB_FUNCTION
130 #undef DEFINE_MATH_BUILTIN
131 #undef DEFINE_MATH_BUILTIN_C
132
133
134 enum rounding_mode { RND_ROUND, RND_TRUNC, RND_CEIL, RND_FLOOR };
135
136
137 /* Find the correct variant of a given builtin from its argument.  */
138 static tree
139 builtin_decl_for_precision (enum built_in_function base_built_in,
140                             int precision)
141 {
142   int i = END_BUILTINS;
143
144   gfc_intrinsic_map_t *m;
145   for (m = gfc_intrinsic_map; m->double_built_in != base_built_in ; m++)
146     ;
147
148   if (precision == TYPE_PRECISION (float_type_node))
149     i = m->float_built_in;
150   else if (precision == TYPE_PRECISION (double_type_node))
151     i = m->double_built_in;
152   else if (precision == TYPE_PRECISION (long_double_type_node))
153     i = m->long_double_built_in;
154   else if (precision == TYPE_PRECISION (float128_type_node))
155     {
156       /* Special treatment, because it is not exactly a built-in, but
157          a library function.  */
158       return m->real16_decl;
159     }
160
161   return (i == END_BUILTINS ? NULL_TREE : built_in_decls[i]);
162 }
163
164
165 tree
166 gfc_builtin_decl_for_float_kind (enum built_in_function double_built_in,
167                                  int kind)
168 {
169   int i = gfc_validate_kind (BT_REAL, kind, false);
170
171   if (gfc_real_kinds[i].c_float128)
172     {
173       /* For __float128, the story is a bit different, because we return
174          a decl to a library function rather than a built-in.  */
175       gfc_intrinsic_map_t *m; 
176       for (m = gfc_intrinsic_map; m->double_built_in != double_built_in ; m++)
177         ;
178
179       return m->real16_decl;
180     }
181
182   return builtin_decl_for_precision (double_built_in,
183                                      gfc_real_kinds[i].mode_precision);
184 }
185
186
187 /* Evaluate the arguments to an intrinsic function.  The value
188    of NARGS may be less than the actual number of arguments in EXPR
189    to allow optional "KIND" arguments that are not included in the
190    generated code to be ignored.  */
191
192 static void
193 gfc_conv_intrinsic_function_args (gfc_se *se, gfc_expr *expr,
194                                   tree *argarray, int nargs)
195 {
196   gfc_actual_arglist *actual;
197   gfc_expr *e;
198   gfc_intrinsic_arg  *formal;
199   gfc_se argse;
200   int curr_arg;
201
202   formal = expr->value.function.isym->formal;
203   actual = expr->value.function.actual;
204
205    for (curr_arg = 0; curr_arg < nargs; curr_arg++,
206         actual = actual->next,
207         formal = formal ? formal->next : NULL)
208     {
209       gcc_assert (actual);
210       e = actual->expr;
211       /* Skip omitted optional arguments.  */
212       if (!e)
213         {
214           --curr_arg;
215           continue;
216         }
217
218       /* Evaluate the parameter.  This will substitute scalarized
219          references automatically.  */
220       gfc_init_se (&argse, se);
221
222       if (e->ts.type == BT_CHARACTER)
223         {
224           gfc_conv_expr (&argse, e);
225           gfc_conv_string_parameter (&argse);
226           argarray[curr_arg++] = argse.string_length;
227           gcc_assert (curr_arg < nargs);
228         }
229       else
230         gfc_conv_expr_val (&argse, e);
231
232       /* If an optional argument is itself an optional dummy argument,
233          check its presence and substitute a null if absent.  */
234       if (e->expr_type == EXPR_VARIABLE
235             && e->symtree->n.sym->attr.optional
236             && formal
237             && formal->optional)
238         gfc_conv_missing_dummy (&argse, e, formal->ts, 0);
239
240       gfc_add_block_to_block (&se->pre, &argse.pre);
241       gfc_add_block_to_block (&se->post, &argse.post);
242       argarray[curr_arg] = argse.expr;
243     }
244 }
245
246 /* Count the number of actual arguments to the intrinsic function EXPR
247    including any "hidden" string length arguments.  */
248
249 static unsigned int
250 gfc_intrinsic_argument_list_length (gfc_expr *expr)
251 {
252   int n = 0;
253   gfc_actual_arglist *actual;
254
255   for (actual = expr->value.function.actual; actual; actual = actual->next)
256     {
257       if (!actual->expr)
258         continue;
259
260       if (actual->expr->ts.type == BT_CHARACTER)
261         n += 2;
262       else
263         n++;
264     }
265
266   return n;
267 }
268
269
270 /* Conversions between different types are output by the frontend as
271    intrinsic functions.  We implement these directly with inline code.  */
272
273 static void
274 gfc_conv_intrinsic_conversion (gfc_se * se, gfc_expr * expr)
275 {
276   tree type;
277   tree *args;
278   int nargs;
279
280   nargs = gfc_intrinsic_argument_list_length (expr);
281   args = XALLOCAVEC (tree, nargs);
282
283   /* Evaluate all the arguments passed. Whilst we're only interested in the 
284      first one here, there are other parts of the front-end that assume this 
285      and will trigger an ICE if it's not the case.  */
286   type = gfc_typenode_for_spec (&expr->ts);
287   gcc_assert (expr->value.function.actual->expr);
288   gfc_conv_intrinsic_function_args (se, expr, args, nargs);
289
290   /* Conversion between character kinds involves a call to a library
291      function.  */
292   if (expr->ts.type == BT_CHARACTER)
293     {
294       tree fndecl, var, addr, tmp;
295
296       if (expr->ts.kind == 1
297           && expr->value.function.actual->expr->ts.kind == 4)
298         fndecl = gfor_fndecl_convert_char4_to_char1;
299       else if (expr->ts.kind == 4
300                && expr->value.function.actual->expr->ts.kind == 1)
301         fndecl = gfor_fndecl_convert_char1_to_char4;
302       else
303         gcc_unreachable ();
304
305       /* Create the variable storing the converted value.  */
306       type = gfc_get_pchar_type (expr->ts.kind);
307       var = gfc_create_var (type, "str");
308       addr = gfc_build_addr_expr (build_pointer_type (type), var);
309
310       /* Call the library function that will perform the conversion.  */
311       gcc_assert (nargs >= 2);
312       tmp = build_call_expr_loc (input_location,
313                              fndecl, 3, addr, args[0], args[1]);
314       gfc_add_expr_to_block (&se->pre, tmp);
315
316       /* Free the temporary afterwards.  */
317       tmp = gfc_call_free (var);
318       gfc_add_expr_to_block (&se->post, tmp);
319
320       se->expr = var;
321       se->string_length = args[0];
322
323       return;
324     }
325
326   /* Conversion from complex to non-complex involves taking the real
327      component of the value.  */
328   if (TREE_CODE (TREE_TYPE (args[0])) == COMPLEX_TYPE
329       && expr->ts.type != BT_COMPLEX)
330     {
331       tree artype;
332
333       artype = TREE_TYPE (TREE_TYPE (args[0]));
334       args[0] = fold_build1_loc (input_location, REALPART_EXPR, artype,
335                                  args[0]);
336     }
337
338   se->expr = convert (type, args[0]);
339 }
340
341 /* This is needed because the gcc backend only implements
342    FIX_TRUNC_EXPR, which is the same as INT() in Fortran.
343    FLOOR(x) = INT(x) <= x ? INT(x) : INT(x) - 1
344    Similarly for CEILING.  */
345
346 static tree
347 build_fixbound_expr (stmtblock_t * pblock, tree arg, tree type, int up)
348 {
349   tree tmp;
350   tree cond;
351   tree argtype;
352   tree intval;
353
354   argtype = TREE_TYPE (arg);
355   arg = gfc_evaluate_now (arg, pblock);
356
357   intval = convert (type, arg);
358   intval = gfc_evaluate_now (intval, pblock);
359
360   tmp = convert (argtype, intval);
361   cond = fold_build2_loc (input_location, up ? GE_EXPR : LE_EXPR,
362                           boolean_type_node, tmp, arg);
363
364   tmp = fold_build2_loc (input_location, up ? PLUS_EXPR : MINUS_EXPR, type,
365                          intval, build_int_cst (type, 1));
366   tmp = fold_build3_loc (input_location, COND_EXPR, type, cond, intval, tmp);
367   return tmp;
368 }
369
370
371 /* Round to nearest integer, away from zero.  */
372
373 static tree
374 build_round_expr (tree arg, tree restype)
375 {
376   tree argtype;
377   tree fn;
378   bool longlong;
379   int argprec, resprec;
380
381   argtype = TREE_TYPE (arg);
382   argprec = TYPE_PRECISION (argtype);
383   resprec = TYPE_PRECISION (restype);
384
385   /* Depending on the type of the result, choose the long int intrinsic
386      (lround family) or long long intrinsic (llround).  We might also
387      need to convert the result afterwards.  */
388   if (resprec <= LONG_TYPE_SIZE)
389     longlong = false;
390   else if (resprec <= LONG_LONG_TYPE_SIZE)
391     longlong = true;
392   else
393     gcc_unreachable ();
394
395   /* Now, depending on the argument type, we choose between intrinsics.  */
396   if (longlong)
397     fn = builtin_decl_for_precision (BUILT_IN_LLROUND, argprec);
398   else
399     fn = builtin_decl_for_precision (BUILT_IN_LROUND, argprec);
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
410 static tree
411 build_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       break;
419
420     case RND_CEIL:
421       return build_fixbound_expr (pblock, arg, type, 1);
422       break;
423
424     case RND_ROUND:
425       return build_round_expr (arg, type);
426       break;
427
428     case RND_TRUNC:
429       return fold_build1_loc (input_location, FIX_TRUNC_EXPR, type, arg);
430       break;
431
432     default:
433       gcc_unreachable ();
434     }
435 }
436
437
438 /* Round a real value using the specified rounding mode.
439    We use a temporary integer of that same kind size as the result.
440    Values larger than those that can be represented by this kind are
441    unchanged, as they will not be accurate enough to represent the
442    rounding.
443     huge = HUGE (KIND (a))
444     aint (a) = ((a > huge) || (a < -huge)) ? a : (real)(int)a
445    */
446
447 static void
448 gfc_conv_intrinsic_aint (gfc_se * se, gfc_expr * expr, enum rounding_mode op)
449 {
450   tree type;
451   tree itype;
452   tree arg[2];
453   tree tmp;
454   tree cond;
455   tree decl;
456   mpfr_t huge;
457   int n, nargs;
458   int kind;
459
460   kind = expr->ts.kind;
461   nargs = gfc_intrinsic_argument_list_length (expr);
462
463   decl = NULL_TREE;
464   /* We have builtin functions for some cases.  */
465   switch (op)
466     {
467     case RND_ROUND:
468       decl = gfc_builtin_decl_for_float_kind (BUILT_IN_ROUND, kind);
469       break;
470
471     case RND_TRUNC:
472       decl = gfc_builtin_decl_for_float_kind (BUILT_IN_TRUNC, kind);
473       break;
474
475     default:
476       gcc_unreachable ();
477     }
478
479   /* Evaluate the argument.  */
480   gcc_assert (expr->value.function.actual->expr);
481   gfc_conv_intrinsic_function_args (se, expr, arg, nargs);
482
483   /* Use a builtin function if one exists.  */
484   if (decl != NULL_TREE)
485     {
486       se->expr = build_call_expr_loc (input_location, decl, 1, arg[0]);
487       return;
488     }
489
490   /* This code is probably redundant, but we'll keep it lying around just
491      in case.  */
492   type = gfc_typenode_for_spec (&expr->ts);
493   arg[0] = gfc_evaluate_now (arg[0], &se->pre);
494
495   /* Test if the value is too large to handle sensibly.  */
496   gfc_set_model_kind (kind);
497   mpfr_init (huge);
498   n = gfc_validate_kind (BT_INTEGER, kind, false);
499   mpfr_set_z (huge, gfc_integer_kinds[n].huge, GFC_RND_MODE);
500   tmp = gfc_conv_mpfr_to_tree (huge, kind, 0);
501   cond = fold_build2_loc (input_location, LT_EXPR, boolean_type_node, arg[0],
502                           tmp);
503
504   mpfr_neg (huge, huge, GFC_RND_MODE);
505   tmp = gfc_conv_mpfr_to_tree (huge, kind, 0);
506   tmp = fold_build2_loc (input_location, GT_EXPR, boolean_type_node, arg[0],
507                          tmp);
508   cond = fold_build2_loc (input_location, TRUTH_AND_EXPR, boolean_type_node,
509                           cond, tmp);
510   itype = gfc_get_int_type (kind);
511
512   tmp = build_fix_expr (&se->pre, arg[0], itype, op);
513   tmp = convert (type, tmp);
514   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond, tmp,
515                               arg[0]);
516   mpfr_clear (huge);
517 }
518
519
520 /* Convert to an integer using the specified rounding mode.  */
521
522 static void
523 gfc_conv_intrinsic_int (gfc_se * se, gfc_expr * expr, enum rounding_mode op)
524 {
525   tree type;
526   tree *args;
527   int nargs;
528
529   nargs = gfc_intrinsic_argument_list_length (expr);
530   args = XALLOCAVEC (tree, nargs);
531
532   /* Evaluate the argument, we process all arguments even though we only 
533      use the first one for code generation purposes.  */
534   type = gfc_typenode_for_spec (&expr->ts);
535   gcc_assert (expr->value.function.actual->expr);
536   gfc_conv_intrinsic_function_args (se, expr, args, nargs);
537
538   if (TREE_CODE (TREE_TYPE (args[0])) == INTEGER_TYPE)
539     {
540       /* Conversion to a different integer kind.  */
541       se->expr = convert (type, args[0]);
542     }
543   else
544     {
545       /* Conversion from complex to non-complex involves taking the real
546          component of the value.  */
547       if (TREE_CODE (TREE_TYPE (args[0])) == COMPLEX_TYPE
548           && expr->ts.type != BT_COMPLEX)
549         {
550           tree artype;
551
552           artype = TREE_TYPE (TREE_TYPE (args[0]));
553           args[0] = fold_build1_loc (input_location, REALPART_EXPR, artype,
554                                      args[0]);
555         }
556
557       se->expr = build_fix_expr (&se->pre, args[0], type, op);
558     }
559 }
560
561
562 /* Get the imaginary component of a value.  */
563
564 static void
565 gfc_conv_intrinsic_imagpart (gfc_se * se, gfc_expr * expr)
566 {
567   tree arg;
568
569   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
570   se->expr = fold_build1_loc (input_location, IMAGPART_EXPR,
571                               TREE_TYPE (TREE_TYPE (arg)), arg);
572 }
573
574
575 /* Get the complex conjugate of a value.  */
576
577 static void
578 gfc_conv_intrinsic_conjg (gfc_se * se, gfc_expr * expr)
579 {
580   tree arg;
581
582   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
583   se->expr = fold_build1_loc (input_location, CONJ_EXPR, TREE_TYPE (arg), arg);
584 }
585
586
587
588 static tree
589 define_quad_builtin (const char *name, tree type, bool is_const)
590 {
591   tree fndecl;
592   fndecl = build_decl (input_location, FUNCTION_DECL, get_identifier (name),
593                        type);
594
595   /* Mark the decl as external.  */
596   DECL_EXTERNAL (fndecl) = 1;
597   TREE_PUBLIC (fndecl) = 1;
598
599   /* Mark it __attribute__((const)).  */
600   TREE_READONLY (fndecl) = is_const;
601
602   rest_of_decl_compilation (fndecl, 1, 0);
603
604   return fndecl;
605 }
606
607
608
609 /* Initialize function decls for library functions.  The external functions
610    are created as required.  Builtin functions are added here.  */
611
612 void
613 gfc_build_intrinsic_lib_fndecls (void)
614 {
615   gfc_intrinsic_map_t *m;
616   tree quad_decls[END_BUILTINS + 1];
617
618   if (gfc_real16_is_float128)
619   {
620     /* If we have soft-float types, we create the decls for their
621        C99-like library functions.  For now, we only handle __float128
622        q-suffixed functions.  */
623
624     tree tmp, func_1, func_2, func_cabs, func_frexp;
625     tree func_lround, func_llround, func_scalbn, func_cpow;
626
627     memset (quad_decls, 0, sizeof(tree) * (END_BUILTINS + 1));
628
629     /* type (*) (type) */
630     tmp = tree_cons (NULL_TREE, float128_type_node, void_list_node);
631     func_1 = build_function_type (float128_type_node, tmp);
632     /* long (*) (type) */
633     func_lround = build_function_type (long_integer_type_node, tmp);
634     /* long long (*) (type) */
635     func_llround = build_function_type (long_long_integer_type_node, tmp);
636     /* type (*) (type, type) */
637     tmp = tree_cons (NULL_TREE, float128_type_node, tmp);
638     func_2 = build_function_type (float128_type_node, tmp);
639     /* type (*) (type, &int) */
640     tmp = tree_cons (NULL_TREE, float128_type_node, void_list_node);
641     tmp = tree_cons (NULL_TREE, build_pointer_type (integer_type_node), tmp);
642     func_frexp = build_function_type (float128_type_node, tmp);
643     /* type (*) (type, int) */
644     tmp = tree_cons (NULL_TREE, float128_type_node, void_list_node);
645     tmp = tree_cons (NULL_TREE, integer_type_node, tmp);
646     func_scalbn = build_function_type (float128_type_node, tmp);
647     /* type (*) (complex type) */
648     tmp = tree_cons (NULL_TREE, complex_float128_type_node, void_list_node);
649     func_cabs = build_function_type (float128_type_node, tmp);
650     /* complex type (*) (complex type, complex type) */
651     tmp = tree_cons (NULL_TREE, complex_float128_type_node, tmp);
652     func_cpow = build_function_type (complex_float128_type_node, tmp);
653
654 #define DEFINE_MATH_BUILTIN(ID, NAME, ARGTYPE)
655 #define DEFINE_MATH_BUILTIN_C(ID, NAME, ARGTYPE)
656 #define LIB_FUNCTION(ID, NAME, HAVE_COMPLEX)
657
658     /* Only these built-ins are actually needed here. These are used directly
659        from the code, when calling builtin_decl_for_precision() or
660        builtin_decl_for_float_type(). The others are all constructed by
661        gfc_get_intrinsic_lib_fndecl().  */
662 #define OTHER_BUILTIN(ID, NAME, TYPE, CONST) \
663   quad_decls[BUILT_IN_ ## ID] = define_quad_builtin (NAME "q", func_ ## TYPE, CONST);
664
665 #include "mathbuiltins.def"
666
667 #undef OTHER_BUILTIN
668 #undef LIB_FUNCTION
669 #undef DEFINE_MATH_BUILTIN
670 #undef DEFINE_MATH_BUILTIN_C
671
672   }
673
674   /* Add GCC builtin functions.  */
675   for (m = gfc_intrinsic_map;
676        m->id != GFC_ISYM_NONE || m->double_built_in != END_BUILTINS; m++)
677     {
678       if (m->float_built_in != END_BUILTINS)
679         m->real4_decl = built_in_decls[m->float_built_in];
680       if (m->complex_float_built_in != END_BUILTINS)
681         m->complex4_decl = built_in_decls[m->complex_float_built_in];
682       if (m->double_built_in != END_BUILTINS)
683         m->real8_decl = built_in_decls[m->double_built_in];
684       if (m->complex_double_built_in != END_BUILTINS)
685         m->complex8_decl = built_in_decls[m->complex_double_built_in];
686
687       /* If real(kind=10) exists, it is always long double.  */
688       if (m->long_double_built_in != END_BUILTINS)
689         m->real10_decl = built_in_decls[m->long_double_built_in];
690       if (m->complex_long_double_built_in != END_BUILTINS)
691         m->complex10_decl = built_in_decls[m->complex_long_double_built_in];
692
693       if (!gfc_real16_is_float128)
694         {
695           if (m->long_double_built_in != END_BUILTINS)
696             m->real16_decl = built_in_decls[m->long_double_built_in];
697           if (m->complex_long_double_built_in != END_BUILTINS)
698             m->complex16_decl = built_in_decls[m->complex_long_double_built_in];
699         }
700       else if (quad_decls[m->double_built_in] != NULL_TREE)
701         {
702           /* Quad-precision function calls are constructed when first
703              needed by builtin_decl_for_precision(), except for those
704              that will be used directly (define by OTHER_BUILTIN).  */
705           m->real16_decl = quad_decls[m->double_built_in];
706         }
707       else if (quad_decls[m->complex_double_built_in] != NULL_TREE)
708         {
709           /* Same thing for the complex ones.  */
710           m->complex16_decl = quad_decls[m->double_built_in];
711         }
712     }
713 }
714
715
716 /* Create a fndecl for a simple intrinsic library function.  */
717
718 static tree
719 gfc_get_intrinsic_lib_fndecl (gfc_intrinsic_map_t * m, gfc_expr * expr)
720 {
721   tree type;
722   tree argtypes;
723   tree fndecl;
724   gfc_actual_arglist *actual;
725   tree *pdecl;
726   gfc_typespec *ts;
727   char name[GFC_MAX_SYMBOL_LEN + 3];
728
729   ts = &expr->ts;
730   if (ts->type == BT_REAL)
731     {
732       switch (ts->kind)
733         {
734         case 4:
735           pdecl = &m->real4_decl;
736           break;
737         case 8:
738           pdecl = &m->real8_decl;
739           break;
740         case 10:
741           pdecl = &m->real10_decl;
742           break;
743         case 16:
744           pdecl = &m->real16_decl;
745           break;
746         default:
747           gcc_unreachable ();
748         }
749     }
750   else if (ts->type == BT_COMPLEX)
751     {
752       gcc_assert (m->complex_available);
753
754       switch (ts->kind)
755         {
756         case 4:
757           pdecl = &m->complex4_decl;
758           break;
759         case 8:
760           pdecl = &m->complex8_decl;
761           break;
762         case 10:
763           pdecl = &m->complex10_decl;
764           break;
765         case 16:
766           pdecl = &m->complex16_decl;
767           break;
768         default:
769           gcc_unreachable ();
770         }
771     }
772   else
773     gcc_unreachable ();
774
775   if (*pdecl)
776     return *pdecl;
777
778   if (m->libm_name)
779     {
780       int n = gfc_validate_kind (BT_REAL, ts->kind, false);
781       if (gfc_real_kinds[n].c_float)
782         snprintf (name, sizeof (name), "%s%s%s",
783                   ts->type == BT_COMPLEX ? "c" : "", m->name, "f");
784       else if (gfc_real_kinds[n].c_double)
785         snprintf (name, sizeof (name), "%s%s",
786                   ts->type == BT_COMPLEX ? "c" : "", m->name);
787       else if (gfc_real_kinds[n].c_long_double)
788         snprintf (name, sizeof (name), "%s%s%s",
789                   ts->type == BT_COMPLEX ? "c" : "", m->name, "l");
790       else if (gfc_real_kinds[n].c_float128)
791         snprintf (name, sizeof (name), "%s%s%s",
792                   ts->type == BT_COMPLEX ? "c" : "", m->name, "q");
793       else
794         gcc_unreachable ();
795     }
796   else
797     {
798       snprintf (name, sizeof (name), PREFIX ("%s_%c%d"), m->name,
799                 ts->type == BT_COMPLEX ? 'c' : 'r',
800                 ts->kind);
801     }
802
803   argtypes = NULL_TREE;
804   for (actual = expr->value.function.actual; actual; actual = actual->next)
805     {
806       type = gfc_typenode_for_spec (&actual->expr->ts);
807       argtypes = gfc_chainon_list (argtypes, type);
808     }
809   argtypes = chainon (argtypes, void_list_node);
810   type = build_function_type (gfc_typenode_for_spec (ts), argtypes);
811   fndecl = build_decl (input_location,
812                        FUNCTION_DECL, get_identifier (name), type);
813
814   /* Mark the decl as external.  */
815   DECL_EXTERNAL (fndecl) = 1;
816   TREE_PUBLIC (fndecl) = 1;
817
818   /* Mark it __attribute__((const)), if possible.  */
819   TREE_READONLY (fndecl) = m->is_constant;
820
821   rest_of_decl_compilation (fndecl, 1, 0);
822
823   (*pdecl) = fndecl;
824   return fndecl;
825 }
826
827
828 /* Convert an intrinsic function into an external or builtin call.  */
829
830 static void
831 gfc_conv_intrinsic_lib_function (gfc_se * se, gfc_expr * expr)
832 {
833   gfc_intrinsic_map_t *m;
834   tree fndecl;
835   tree rettype;
836   tree *args;
837   unsigned int num_args;
838   gfc_isym_id id;
839
840   id = expr->value.function.isym->id;
841   /* Find the entry for this function.  */
842   for (m = gfc_intrinsic_map;
843        m->id != GFC_ISYM_NONE || m->double_built_in != END_BUILTINS; m++)
844     {
845       if (id == m->id)
846         break;
847     }
848
849   if (m->id == GFC_ISYM_NONE)
850     {
851       internal_error ("Intrinsic function %s(%d) not recognized",
852                       expr->value.function.name, id);
853     }
854
855   /* Get the decl and generate the call.  */
856   num_args = gfc_intrinsic_argument_list_length (expr);
857   args = XALLOCAVEC (tree, num_args);
858
859   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
860   fndecl = gfc_get_intrinsic_lib_fndecl (m, expr);
861   rettype = TREE_TYPE (TREE_TYPE (fndecl));
862
863   fndecl = build_addr (fndecl, current_function_decl);
864   se->expr = build_call_array_loc (input_location, rettype, fndecl, num_args, args);
865 }
866
867
868 /* If bounds-checking is enabled, create code to verify at runtime that the
869    string lengths for both expressions are the same (needed for e.g. MERGE).
870    If bounds-checking is not enabled, does nothing.  */
871
872 void
873 gfc_trans_same_strlen_check (const char* intr_name, locus* where,
874                              tree a, tree b, stmtblock_t* target)
875 {
876   tree cond;
877   tree name;
878
879   /* If bounds-checking is disabled, do nothing.  */
880   if (!(gfc_option.rtcheck & GFC_RTCHECK_BOUNDS))
881     return;
882
883   /* Compare the two string lengths.  */
884   cond = fold_build2_loc (input_location, NE_EXPR, boolean_type_node, a, b);
885
886   /* Output the runtime-check.  */
887   name = gfc_build_cstring_const (intr_name);
888   name = gfc_build_addr_expr (pchar_type_node, name);
889   gfc_trans_runtime_check (true, false, cond, target, where,
890                            "Unequal character lengths (%ld/%ld) in %s",
891                            fold_convert (long_integer_type_node, a),
892                            fold_convert (long_integer_type_node, b), name);
893 }
894
895
896 /* The EXPONENT(s) intrinsic function is translated into
897        int ret;
898        frexp (s, &ret);
899        return ret;
900  */
901
902 static void
903 gfc_conv_intrinsic_exponent (gfc_se *se, gfc_expr *expr)
904 {
905   tree arg, type, res, tmp, frexp;
906
907   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP,
908                                        expr->value.function.actual->expr->ts.kind);
909
910   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
911
912   res = gfc_create_var (integer_type_node, NULL);
913   tmp = build_call_expr_loc (input_location, frexp, 2, arg,
914                              gfc_build_addr_expr (NULL_TREE, res));
915   gfc_add_expr_to_block (&se->pre, tmp);
916
917   type = gfc_typenode_for_spec (&expr->ts);
918   se->expr = fold_convert (type, res);
919 }
920
921 /* Evaluate a single upper or lower bound.  */
922 /* TODO: bound intrinsic generates way too much unnecessary code.  */
923
924 static void
925 gfc_conv_intrinsic_bound (gfc_se * se, gfc_expr * expr, int upper)
926 {
927   gfc_actual_arglist *arg;
928   gfc_actual_arglist *arg2;
929   tree desc;
930   tree type;
931   tree bound;
932   tree tmp;
933   tree cond, cond1, cond3, cond4, size;
934   tree ubound;
935   tree lbound;
936   gfc_se argse;
937   gfc_ss *ss;
938   gfc_array_spec * as;
939
940   arg = expr->value.function.actual;
941   arg2 = arg->next;
942
943   if (se->ss)
944     {
945       /* Create an implicit second parameter from the loop variable.  */
946       gcc_assert (!arg2->expr);
947       gcc_assert (se->loop->dimen == 1);
948       gcc_assert (se->ss->expr == expr);
949       gfc_advance_se_ss_chain (se);
950       bound = se->loop->loopvar[0];
951       bound = fold_build2_loc (input_location, MINUS_EXPR,
952                                gfc_array_index_type, bound,
953                                se->loop->from[0]);
954     }
955   else
956     {
957       /* use the passed argument.  */
958       gcc_assert (arg->next->expr);
959       gfc_init_se (&argse, NULL);
960       gfc_conv_expr_type (&argse, arg->next->expr, gfc_array_index_type);
961       gfc_add_block_to_block (&se->pre, &argse.pre);
962       bound = argse.expr;
963       /* Convert from one based to zero based.  */
964       bound = fold_build2_loc (input_location, MINUS_EXPR,
965                                gfc_array_index_type, bound,
966                                gfc_index_one_node);
967     }
968
969   /* TODO: don't re-evaluate the descriptor on each iteration.  */
970   /* Get a descriptor for the first parameter.  */
971   ss = gfc_walk_expr (arg->expr);
972   gcc_assert (ss != gfc_ss_terminator);
973   gfc_init_se (&argse, NULL);
974   gfc_conv_expr_descriptor (&argse, arg->expr, ss);
975   gfc_add_block_to_block (&se->pre, &argse.pre);
976   gfc_add_block_to_block (&se->post, &argse.post);
977
978   desc = argse.expr;
979
980   if (INTEGER_CST_P (bound))
981     {
982       int hi, low;
983
984       hi = TREE_INT_CST_HIGH (bound);
985       low = TREE_INT_CST_LOW (bound);
986       if (hi || low < 0 || low >= GFC_TYPE_ARRAY_RANK (TREE_TYPE (desc)))
987         gfc_error ("'dim' argument of %s intrinsic at %L is not a valid "
988                    "dimension index", upper ? "UBOUND" : "LBOUND",
989                    &expr->where);
990     }
991   else
992     {
993       if (gfc_option.rtcheck & GFC_RTCHECK_BOUNDS)
994         {
995           bound = gfc_evaluate_now (bound, &se->pre);
996           cond = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
997                                   bound, build_int_cst (TREE_TYPE (bound), 0));
998           tmp = gfc_rank_cst[GFC_TYPE_ARRAY_RANK (TREE_TYPE (desc))];
999           tmp = fold_build2_loc (input_location, GE_EXPR, boolean_type_node,
1000                                  bound, tmp);
1001           cond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
1002                                   boolean_type_node, cond, tmp);
1003           gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
1004                                    gfc_msg_fault);
1005         }
1006     }
1007
1008   ubound = gfc_conv_descriptor_ubound_get (desc, bound);
1009   lbound = gfc_conv_descriptor_lbound_get (desc, bound);
1010   
1011   as = gfc_get_full_arrayspec_from_expr (arg->expr);
1012
1013   /* 13.14.53: Result value for LBOUND
1014
1015      Case (i): For an array section or for an array expression other than a
1016                whole array or array structure component, LBOUND(ARRAY, DIM)
1017                has the value 1.  For a whole array or array structure
1018                component, LBOUND(ARRAY, DIM) has the value:
1019                  (a) equal to the lower bound for subscript DIM of ARRAY if
1020                      dimension DIM of ARRAY does not have extent zero
1021                      or if ARRAY is an assumed-size array of rank DIM,
1022               or (b) 1 otherwise.
1023
1024      13.14.113: Result value for UBOUND
1025
1026      Case (i): For an array section or for an array expression other than a
1027                whole array or array structure component, UBOUND(ARRAY, DIM)
1028                has the value equal to the number of elements in the given
1029                dimension; otherwise, it has a value equal to the upper bound
1030                for subscript DIM of ARRAY if dimension DIM of ARRAY does
1031                not have size zero and has value zero if dimension DIM has
1032                size zero.  */
1033
1034   if (as)
1035     {
1036       tree stride = gfc_conv_descriptor_stride_get (desc, bound);
1037
1038       cond1 = fold_build2_loc (input_location, GE_EXPR, boolean_type_node,
1039                                ubound, lbound);
1040       cond3 = fold_build2_loc (input_location, GE_EXPR, boolean_type_node,
1041                                stride, gfc_index_zero_node);
1042       cond3 = fold_build2_loc (input_location, TRUTH_AND_EXPR,
1043                                boolean_type_node, cond3, cond1);
1044       cond4 = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
1045                                stride, gfc_index_zero_node);
1046
1047       if (upper)
1048         {
1049           tree cond5;
1050           cond = fold_build2_loc (input_location, TRUTH_OR_EXPR,
1051                                   boolean_type_node, cond3, cond4);
1052           cond5 = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
1053                                    gfc_index_one_node, lbound);
1054           cond5 = fold_build2_loc (input_location, TRUTH_AND_EXPR,
1055                                    boolean_type_node, cond4, cond5);
1056
1057           cond = fold_build2_loc (input_location, TRUTH_OR_EXPR,
1058                                   boolean_type_node, cond, cond5);
1059
1060           se->expr = fold_build3_loc (input_location, COND_EXPR,
1061                                       gfc_array_index_type, cond,
1062                                       ubound, gfc_index_zero_node);
1063         }
1064       else
1065         {
1066           if (as->type == AS_ASSUMED_SIZE)
1067             cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
1068                                     bound, build_int_cst (TREE_TYPE (bound),
1069                                                           arg->expr->rank - 1));
1070           else
1071             cond = boolean_false_node;
1072
1073           cond1 = fold_build2_loc (input_location, TRUTH_OR_EXPR,
1074                                    boolean_type_node, cond3, cond4);
1075           cond = fold_build2_loc (input_location, TRUTH_OR_EXPR,
1076                                   boolean_type_node, cond, cond1);
1077
1078           se->expr = fold_build3_loc (input_location, COND_EXPR,
1079                                       gfc_array_index_type, cond,
1080                                       lbound, gfc_index_one_node);
1081         }
1082     }
1083   else
1084     {
1085       if (upper)
1086         {
1087           size = fold_build2_loc (input_location, MINUS_EXPR,
1088                                   gfc_array_index_type, ubound, lbound);
1089           se->expr = fold_build2_loc (input_location, PLUS_EXPR,
1090                                       gfc_array_index_type, size,
1091                                   gfc_index_one_node);
1092           se->expr = fold_build2_loc (input_location, MAX_EXPR,
1093                                       gfc_array_index_type, se->expr,
1094                                       gfc_index_zero_node);
1095         }
1096       else
1097         se->expr = gfc_index_one_node;
1098     }
1099
1100   type = gfc_typenode_for_spec (&expr->ts);
1101   se->expr = convert (type, se->expr);
1102 }
1103
1104
1105 static void
1106 gfc_conv_intrinsic_abs (gfc_se * se, gfc_expr * expr)
1107 {
1108   tree arg, cabs;
1109
1110   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
1111
1112   switch (expr->value.function.actual->expr->ts.type)
1113     {
1114     case BT_INTEGER:
1115     case BT_REAL:
1116       se->expr = fold_build1_loc (input_location, ABS_EXPR, TREE_TYPE (arg),
1117                                   arg);
1118       break;
1119
1120     case BT_COMPLEX:
1121       cabs = gfc_builtin_decl_for_float_kind (BUILT_IN_CABS, expr->ts.kind);
1122       se->expr = build_call_expr_loc (input_location, cabs, 1, arg);
1123       break;
1124
1125     default:
1126       gcc_unreachable ();
1127     }
1128 }
1129
1130
1131 /* Create a complex value from one or two real components.  */
1132
1133 static void
1134 gfc_conv_intrinsic_cmplx (gfc_se * se, gfc_expr * expr, int both)
1135 {
1136   tree real;
1137   tree imag;
1138   tree type;
1139   tree *args;
1140   unsigned int num_args;
1141
1142   num_args = gfc_intrinsic_argument_list_length (expr);
1143   args = XALLOCAVEC (tree, num_args);
1144
1145   type = gfc_typenode_for_spec (&expr->ts);
1146   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
1147   real = convert (TREE_TYPE (type), args[0]);
1148   if (both)
1149     imag = convert (TREE_TYPE (type), args[1]);
1150   else if (TREE_CODE (TREE_TYPE (args[0])) == COMPLEX_TYPE)
1151     {
1152       imag = fold_build1_loc (input_location, IMAGPART_EXPR,
1153                               TREE_TYPE (TREE_TYPE (args[0])), args[0]);
1154       imag = convert (TREE_TYPE (type), imag);
1155     }
1156   else
1157     imag = build_real_from_int_cst (TREE_TYPE (type), integer_zero_node);
1158
1159   se->expr = fold_build2_loc (input_location, COMPLEX_EXPR, type, real, imag);
1160 }
1161
1162 /* Remainder function MOD(A, P) = A - INT(A / P) * P
1163                       MODULO(A, P) = A - FLOOR (A / P) * P  */
1164 /* TODO: MOD(x, 0)  */
1165
1166 static void
1167 gfc_conv_intrinsic_mod (gfc_se * se, gfc_expr * expr, int modulo)
1168 {
1169   tree type;
1170   tree itype;
1171   tree tmp;
1172   tree test;
1173   tree test2;
1174   tree fmod;
1175   mpfr_t huge;
1176   int n, ikind;
1177   tree args[2];
1178
1179   gfc_conv_intrinsic_function_args (se, expr, args, 2);
1180
1181   switch (expr->ts.type)
1182     {
1183     case BT_INTEGER:
1184       /* Integer case is easy, we've got a builtin op.  */
1185       type = TREE_TYPE (args[0]);
1186
1187       if (modulo)
1188        se->expr = fold_build2_loc (input_location, FLOOR_MOD_EXPR, type,
1189                                    args[0], args[1]);
1190       else
1191        se->expr = fold_build2_loc (input_location, TRUNC_MOD_EXPR, type,
1192                                    args[0], args[1]);
1193       break;
1194
1195     case BT_REAL:
1196       fmod = NULL_TREE;
1197       /* Check if we have a builtin fmod.  */
1198       fmod = gfc_builtin_decl_for_float_kind (BUILT_IN_FMOD, expr->ts.kind);
1199
1200       /* Use it if it exists.  */
1201       if (fmod != NULL_TREE)
1202         {
1203           tmp = build_addr (fmod, current_function_decl);
1204           se->expr = build_call_array_loc (input_location,
1205                                        TREE_TYPE (TREE_TYPE (fmod)),
1206                                        tmp, 2, args);
1207           if (modulo == 0)
1208             return;
1209         }
1210
1211       type = TREE_TYPE (args[0]);
1212
1213       args[0] = gfc_evaluate_now (args[0], &se->pre);
1214       args[1] = gfc_evaluate_now (args[1], &se->pre);
1215
1216       /* Definition:
1217          modulo = arg - floor (arg/arg2) * arg2, so
1218                 = test ? fmod (arg, arg2) : fmod (arg, arg2) + arg2, 
1219          where
1220           test  = (fmod (arg, arg2) != 0) && ((arg < 0) xor (arg2 < 0))
1221          thereby avoiding another division and retaining the accuracy
1222          of the builtin function.  */
1223       if (fmod != NULL_TREE && modulo)
1224         {
1225           tree zero = gfc_build_const (type, integer_zero_node);
1226           tmp = gfc_evaluate_now (se->expr, &se->pre);
1227           test = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
1228                                   args[0], zero);
1229           test2 = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
1230                                    args[1], zero);
1231           test2 = fold_build2_loc (input_location, TRUTH_XOR_EXPR,
1232                                    boolean_type_node, test, test2);
1233           test = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
1234                                   tmp, zero);
1235           test = fold_build2_loc (input_location, TRUTH_AND_EXPR,
1236                                   boolean_type_node, test, test2);
1237           test = gfc_evaluate_now (test, &se->pre);
1238           se->expr = fold_build3_loc (input_location, COND_EXPR, type, test,
1239                                   fold_build2_loc (input_location, PLUS_EXPR,
1240                                                    type, tmp, args[1]), tmp);
1241           return;
1242         }
1243
1244       /* If we do not have a built_in fmod, the calculation is going to
1245          have to be done longhand.  */
1246       tmp = fold_build2_loc (input_location, RDIV_EXPR, type, args[0], args[1]);
1247
1248       /* Test if the value is too large to handle sensibly.  */
1249       gfc_set_model_kind (expr->ts.kind);
1250       mpfr_init (huge);
1251       n = gfc_validate_kind (BT_INTEGER, expr->ts.kind, true);
1252       ikind = expr->ts.kind;
1253       if (n < 0)
1254         {
1255           n = gfc_validate_kind (BT_INTEGER, gfc_max_integer_kind, false);
1256           ikind = gfc_max_integer_kind;
1257         }
1258       mpfr_set_z (huge, gfc_integer_kinds[n].huge, GFC_RND_MODE);
1259       test = gfc_conv_mpfr_to_tree (huge, expr->ts.kind, 0);
1260       test2 = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
1261                                tmp, test);
1262
1263       mpfr_neg (huge, huge, GFC_RND_MODE);
1264       test = gfc_conv_mpfr_to_tree (huge, expr->ts.kind, 0);
1265       test = fold_build2_loc (input_location, GT_EXPR, boolean_type_node, tmp,
1266                               test);
1267       test2 = fold_build2_loc (input_location, TRUTH_AND_EXPR,
1268                                boolean_type_node, test, test2);
1269
1270       itype = gfc_get_int_type (ikind);
1271       if (modulo)
1272        tmp = build_fix_expr (&se->pre, tmp, itype, RND_FLOOR);
1273       else
1274        tmp = build_fix_expr (&se->pre, tmp, itype, RND_TRUNC);
1275       tmp = convert (type, tmp);
1276       tmp = fold_build3_loc (input_location, COND_EXPR, type, test2, tmp,
1277                              args[0]);
1278       tmp = fold_build2_loc (input_location, MULT_EXPR, type, tmp, args[1]);
1279       se->expr = fold_build2_loc (input_location, MINUS_EXPR, type, args[0],
1280                                   tmp);
1281       mpfr_clear (huge);
1282       break;
1283
1284     default:
1285       gcc_unreachable ();
1286     }
1287 }
1288
1289 /* DSHIFTL(I,J,S) = (I << S) | (J >> (BITSIZE(J) - S))
1290    DSHIFTR(I,J,S) = (I << (BITSIZE(I) - S)) | (J >> S)
1291    where the right shifts are logical (i.e. 0's are shifted in).
1292    Because SHIFT_EXPR's want shifts strictly smaller than the integral
1293    type width, we have to special-case both S == 0 and S == BITSIZE(J):
1294      DSHIFTL(I,J,0) = I
1295      DSHIFTL(I,J,BITSIZE) = J
1296      DSHIFTR(I,J,0) = J
1297      DSHIFTR(I,J,BITSIZE) = I.  */
1298
1299 static void
1300 gfc_conv_intrinsic_dshift (gfc_se * se, gfc_expr * expr, bool dshiftl)
1301 {
1302   tree type, utype, stype, arg1, arg2, shift, res, left, right;
1303   tree args[3], cond, tmp;
1304   int bitsize;
1305
1306   gfc_conv_intrinsic_function_args (se, expr, args, 3);
1307
1308   gcc_assert (TREE_TYPE (args[0]) == TREE_TYPE (args[1]));
1309   type = TREE_TYPE (args[0]);
1310   bitsize = TYPE_PRECISION (type);
1311   utype = unsigned_type_for (type);
1312   stype = TREE_TYPE (args[2]);
1313
1314   arg1 = gfc_evaluate_now (args[0], &se->pre);
1315   arg2 = gfc_evaluate_now (args[1], &se->pre);
1316   shift = gfc_evaluate_now (args[2], &se->pre);
1317
1318   /* The generic case.  */
1319   tmp = fold_build2_loc (input_location, MINUS_EXPR, stype,
1320                          build_int_cst (stype, bitsize), shift);
1321   left = fold_build2_loc (input_location, LSHIFT_EXPR, type,
1322                           arg1, dshiftl ? shift : tmp);
1323
1324   right = fold_build2_loc (input_location, RSHIFT_EXPR, utype,
1325                            fold_convert (utype, arg2), dshiftl ? tmp : shift);
1326   right = fold_convert (type, right);
1327
1328   res = fold_build2_loc (input_location, BIT_IOR_EXPR, type, left, right);
1329
1330   /* Special cases.  */
1331   cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, shift,
1332                           build_int_cst (stype, 0));
1333   res = fold_build3_loc (input_location, COND_EXPR, type, cond,
1334                          dshiftl ? arg1 : arg2, res);
1335
1336   cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, shift,
1337                           build_int_cst (stype, bitsize));
1338   res = fold_build3_loc (input_location, COND_EXPR, type, cond,
1339                          dshiftl ? arg2 : arg1, res);
1340
1341   se->expr = res;
1342 }
1343
1344
1345 /* Positive difference DIM (x, y) = ((x - y) < 0) ? 0 : x - y.  */
1346
1347 static void
1348 gfc_conv_intrinsic_dim (gfc_se * se, gfc_expr * expr)
1349 {
1350   tree val;
1351   tree tmp;
1352   tree type;
1353   tree zero;
1354   tree args[2];
1355
1356   gfc_conv_intrinsic_function_args (se, expr, args, 2);
1357   type = TREE_TYPE (args[0]);
1358
1359   val = fold_build2_loc (input_location, MINUS_EXPR, type, args[0], args[1]);
1360   val = gfc_evaluate_now (val, &se->pre);
1361
1362   zero = gfc_build_const (type, integer_zero_node);
1363   tmp = fold_build2_loc (input_location, LE_EXPR, boolean_type_node, val, zero);
1364   se->expr = fold_build3_loc (input_location, COND_EXPR, type, tmp, zero, val);
1365 }
1366
1367
1368 /* SIGN(A, B) is absolute value of A times sign of B.
1369    The real value versions use library functions to ensure the correct
1370    handling of negative zero.  Integer case implemented as:
1371    SIGN(A, B) = { tmp = (A ^ B) >> C; (A + tmp) ^ tmp }
1372   */
1373
1374 static void
1375 gfc_conv_intrinsic_sign (gfc_se * se, gfc_expr * expr)
1376 {
1377   tree tmp;
1378   tree type;
1379   tree args[2];
1380
1381   gfc_conv_intrinsic_function_args (se, expr, args, 2);
1382   if (expr->ts.type == BT_REAL)
1383     {
1384       tree abs;
1385
1386       tmp = gfc_builtin_decl_for_float_kind (BUILT_IN_COPYSIGN, expr->ts.kind);
1387       abs = gfc_builtin_decl_for_float_kind (BUILT_IN_FABS, expr->ts.kind);
1388
1389       /* We explicitly have to ignore the minus sign. We do so by using
1390          result = (arg1 == 0) ? abs(arg0) : copysign(arg0, arg1).  */
1391       if (!gfc_option.flag_sign_zero
1392           && MODE_HAS_SIGNED_ZEROS (TYPE_MODE (TREE_TYPE (args[1]))))
1393         {
1394           tree cond, zero;
1395           zero = build_real_from_int_cst (TREE_TYPE (args[1]), integer_zero_node);
1396           cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
1397                                   args[1], zero);
1398           se->expr = fold_build3_loc (input_location, COND_EXPR,
1399                                   TREE_TYPE (args[0]), cond,
1400                                   build_call_expr_loc (input_location, abs, 1,
1401                                                        args[0]),
1402                                   build_call_expr_loc (input_location, tmp, 2,
1403                                                        args[0], args[1]));
1404         }
1405       else
1406         se->expr = build_call_expr_loc (input_location, tmp, 2,
1407                                         args[0], args[1]);
1408       return;
1409     }
1410
1411   /* Having excluded floating point types, we know we are now dealing
1412      with signed integer types.  */
1413   type = TREE_TYPE (args[0]);
1414
1415   /* Args[0] is used multiple times below.  */
1416   args[0] = gfc_evaluate_now (args[0], &se->pre);
1417
1418   /* Construct (A ^ B) >> 31, which generates a bit mask of all zeros if
1419      the signs of A and B are the same, and of all ones if they differ.  */
1420   tmp = fold_build2_loc (input_location, BIT_XOR_EXPR, type, args[0], args[1]);
1421   tmp = fold_build2_loc (input_location, RSHIFT_EXPR, type, tmp,
1422                          build_int_cst (type, TYPE_PRECISION (type) - 1));
1423   tmp = gfc_evaluate_now (tmp, &se->pre);
1424
1425   /* Construct (A + tmp) ^ tmp, which is A if tmp is zero, and -A if tmp]
1426      is all ones (i.e. -1).  */
1427   se->expr = fold_build2_loc (input_location, BIT_XOR_EXPR, type,
1428                               fold_build2_loc (input_location, PLUS_EXPR,
1429                                                type, args[0], tmp), tmp);
1430 }
1431
1432
1433 /* Test for the presence of an optional argument.  */
1434
1435 static void
1436 gfc_conv_intrinsic_present (gfc_se * se, gfc_expr * expr)
1437 {
1438   gfc_expr *arg;
1439
1440   arg = expr->value.function.actual->expr;
1441   gcc_assert (arg->expr_type == EXPR_VARIABLE);
1442   se->expr = gfc_conv_expr_present (arg->symtree->n.sym);
1443   se->expr = convert (gfc_typenode_for_spec (&expr->ts), se->expr);
1444 }
1445
1446
1447 /* Calculate the double precision product of two single precision values.  */
1448
1449 static void
1450 gfc_conv_intrinsic_dprod (gfc_se * se, gfc_expr * expr)
1451 {
1452   tree type;
1453   tree args[2];
1454
1455   gfc_conv_intrinsic_function_args (se, expr, args, 2);
1456
1457   /* Convert the args to double precision before multiplying.  */
1458   type = gfc_typenode_for_spec (&expr->ts);
1459   args[0] = convert (type, args[0]);
1460   args[1] = convert (type, args[1]);
1461   se->expr = fold_build2_loc (input_location, MULT_EXPR, type, args[0],
1462                               args[1]);
1463 }
1464
1465
1466 /* Return a length one character string containing an ascii character.  */
1467
1468 static void
1469 gfc_conv_intrinsic_char (gfc_se * se, gfc_expr * expr)
1470 {
1471   tree arg[2];
1472   tree var;
1473   tree type;
1474   unsigned int num_args;
1475
1476   num_args = gfc_intrinsic_argument_list_length (expr);
1477   gfc_conv_intrinsic_function_args (se, expr, arg, num_args);
1478
1479   type = gfc_get_char_type (expr->ts.kind);
1480   var = gfc_create_var (type, "char");
1481
1482   arg[0] = fold_build1_loc (input_location, NOP_EXPR, type, arg[0]);
1483   gfc_add_modify (&se->pre, var, arg[0]);
1484   se->expr = gfc_build_addr_expr (build_pointer_type (type), var);
1485   se->string_length = build_int_cst (gfc_charlen_type_node, 1);
1486 }
1487
1488
1489 static void
1490 gfc_conv_intrinsic_ctime (gfc_se * se, gfc_expr * expr)
1491 {
1492   tree var;
1493   tree len;
1494   tree tmp;
1495   tree cond;
1496   tree fndecl;
1497   tree *args;
1498   unsigned int num_args;
1499
1500   num_args = gfc_intrinsic_argument_list_length (expr) + 2;
1501   args = XALLOCAVEC (tree, num_args);
1502
1503   var = gfc_create_var (pchar_type_node, "pstr");
1504   len = gfc_create_var (gfc_get_int_type (8), "len");
1505
1506   gfc_conv_intrinsic_function_args (se, expr, &args[2], num_args - 2);
1507   args[0] = gfc_build_addr_expr (NULL_TREE, var);
1508   args[1] = gfc_build_addr_expr (NULL_TREE, len);
1509
1510   fndecl = build_addr (gfor_fndecl_ctime, current_function_decl);
1511   tmp = build_call_array_loc (input_location,
1512                           TREE_TYPE (TREE_TYPE (gfor_fndecl_ctime)),
1513                           fndecl, num_args, args);
1514   gfc_add_expr_to_block (&se->pre, tmp);
1515
1516   /* Free the temporary afterwards, if necessary.  */
1517   cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
1518                           len, build_int_cst (TREE_TYPE (len), 0));
1519   tmp = gfc_call_free (var);
1520   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
1521   gfc_add_expr_to_block (&se->post, tmp);
1522
1523   se->expr = var;
1524   se->string_length = len;
1525 }
1526
1527
1528 static void
1529 gfc_conv_intrinsic_fdate (gfc_se * se, gfc_expr * expr)
1530 {
1531   tree var;
1532   tree len;
1533   tree tmp;
1534   tree cond;
1535   tree fndecl;
1536   tree *args;
1537   unsigned int num_args;
1538
1539   num_args = gfc_intrinsic_argument_list_length (expr) + 2;
1540   args = XALLOCAVEC (tree, num_args);
1541
1542   var = gfc_create_var (pchar_type_node, "pstr");
1543   len = gfc_create_var (gfc_charlen_type_node, "len");
1544
1545   gfc_conv_intrinsic_function_args (se, expr, &args[2], num_args - 2);
1546   args[0] = gfc_build_addr_expr (NULL_TREE, var);
1547   args[1] = gfc_build_addr_expr (NULL_TREE, len);
1548
1549   fndecl = build_addr (gfor_fndecl_fdate, current_function_decl);
1550   tmp = build_call_array_loc (input_location,
1551                           TREE_TYPE (TREE_TYPE (gfor_fndecl_fdate)),
1552                           fndecl, num_args, args);
1553   gfc_add_expr_to_block (&se->pre, tmp);
1554
1555   /* Free the temporary afterwards, if necessary.  */
1556   cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
1557                           len, build_int_cst (TREE_TYPE (len), 0));
1558   tmp = gfc_call_free (var);
1559   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
1560   gfc_add_expr_to_block (&se->post, tmp);
1561
1562   se->expr = var;
1563   se->string_length = len;
1564 }
1565
1566
1567 /* Return a character string containing the tty name.  */
1568
1569 static void
1570 gfc_conv_intrinsic_ttynam (gfc_se * se, gfc_expr * expr)
1571 {
1572   tree var;
1573   tree len;
1574   tree tmp;
1575   tree cond;
1576   tree fndecl;
1577   tree *args;
1578   unsigned int num_args;
1579
1580   num_args = gfc_intrinsic_argument_list_length (expr) + 2;
1581   args = XALLOCAVEC (tree, num_args);
1582
1583   var = gfc_create_var (pchar_type_node, "pstr");
1584   len = gfc_create_var (gfc_charlen_type_node, "len");
1585
1586   gfc_conv_intrinsic_function_args (se, expr, &args[2], num_args - 2);
1587   args[0] = gfc_build_addr_expr (NULL_TREE, var);
1588   args[1] = gfc_build_addr_expr (NULL_TREE, len);
1589
1590   fndecl = build_addr (gfor_fndecl_ttynam, current_function_decl);
1591   tmp = build_call_array_loc (input_location,
1592                           TREE_TYPE (TREE_TYPE (gfor_fndecl_ttynam)),
1593                           fndecl, num_args, args);
1594   gfc_add_expr_to_block (&se->pre, tmp);
1595
1596   /* Free the temporary afterwards, if necessary.  */
1597   cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
1598                           len, build_int_cst (TREE_TYPE (len), 0));
1599   tmp = gfc_call_free (var);
1600   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
1601   gfc_add_expr_to_block (&se->post, tmp);
1602
1603   se->expr = var;
1604   se->string_length = len;
1605 }
1606
1607
1608 /* Get the minimum/maximum value of all the parameters.
1609     minmax (a1, a2, a3, ...)
1610     {
1611       mvar = a1;
1612       if (a2 .op. mvar || isnan(mvar))
1613         mvar = a2;
1614       if (a3 .op. mvar || isnan(mvar))
1615         mvar = a3;
1616       ...
1617       return mvar
1618     }
1619  */
1620
1621 /* TODO: Mismatching types can occur when specific names are used.
1622    These should be handled during resolution.  */
1623 static void
1624 gfc_conv_intrinsic_minmax (gfc_se * se, gfc_expr * expr, enum tree_code op)
1625 {
1626   tree tmp;
1627   tree mvar;
1628   tree val;
1629   tree thencase;
1630   tree *args;
1631   tree type;
1632   gfc_actual_arglist *argexpr;
1633   unsigned int i, nargs;
1634
1635   nargs = gfc_intrinsic_argument_list_length (expr);
1636   args = XALLOCAVEC (tree, nargs);
1637
1638   gfc_conv_intrinsic_function_args (se, expr, args, nargs);
1639   type = gfc_typenode_for_spec (&expr->ts);
1640
1641   argexpr = expr->value.function.actual;
1642   if (TREE_TYPE (args[0]) != type)
1643     args[0] = convert (type, args[0]);
1644   /* Only evaluate the argument once.  */
1645   if (TREE_CODE (args[0]) != VAR_DECL && !TREE_CONSTANT (args[0]))
1646     args[0] = gfc_evaluate_now (args[0], &se->pre);
1647
1648   mvar = gfc_create_var (type, "M");
1649   gfc_add_modify (&se->pre, mvar, args[0]);
1650   for (i = 1, argexpr = argexpr->next; i < nargs; i++)
1651     {
1652       tree cond, isnan;
1653
1654       val = args[i]; 
1655
1656       /* Handle absent optional arguments by ignoring the comparison.  */
1657       if (argexpr->expr->expr_type == EXPR_VARIABLE
1658           && argexpr->expr->symtree->n.sym->attr.optional
1659           && TREE_CODE (val) == INDIRECT_REF)
1660         cond = fold_build2_loc (input_location,
1661                                 NE_EXPR, boolean_type_node,
1662                                 TREE_OPERAND (val, 0), 
1663                         build_int_cst (TREE_TYPE (TREE_OPERAND (val, 0)), 0));
1664       else
1665       {
1666         cond = NULL_TREE;
1667
1668         /* Only evaluate the argument once.  */
1669         if (TREE_CODE (val) != VAR_DECL && !TREE_CONSTANT (val))
1670           val = gfc_evaluate_now (val, &se->pre);
1671       }
1672
1673       thencase = build2_v (MODIFY_EXPR, mvar, convert (type, val));
1674
1675       tmp = fold_build2_loc (input_location, op, boolean_type_node,
1676                              convert (type, val), mvar);
1677
1678       /* FIXME: When the IEEE_ARITHMETIC module is implemented, the call to
1679          __builtin_isnan might be made dependent on that module being loaded,
1680          to help performance of programs that don't rely on IEEE semantics.  */
1681       if (FLOAT_TYPE_P (TREE_TYPE (mvar)))
1682         {
1683           isnan = build_call_expr_loc (input_location,
1684                                    built_in_decls[BUILT_IN_ISNAN], 1, mvar);
1685           tmp = fold_build2_loc (input_location, TRUTH_OR_EXPR,
1686                                  boolean_type_node, tmp,
1687                                  fold_convert (boolean_type_node, isnan));
1688         }
1689       tmp = build3_v (COND_EXPR, tmp, thencase,
1690                       build_empty_stmt (input_location));
1691
1692       if (cond != NULL_TREE)
1693         tmp = build3_v (COND_EXPR, cond, tmp,
1694                         build_empty_stmt (input_location));
1695
1696       gfc_add_expr_to_block (&se->pre, tmp);
1697       argexpr = argexpr->next;
1698     }
1699   se->expr = mvar;
1700 }
1701
1702
1703 /* Generate library calls for MIN and MAX intrinsics for character
1704    variables.  */
1705 static void
1706 gfc_conv_intrinsic_minmax_char (gfc_se * se, gfc_expr * expr, int op)
1707 {
1708   tree *args;
1709   tree var, len, fndecl, tmp, cond, function;
1710   unsigned int nargs;
1711
1712   nargs = gfc_intrinsic_argument_list_length (expr);
1713   args = XALLOCAVEC (tree, nargs + 4);
1714   gfc_conv_intrinsic_function_args (se, expr, &args[4], nargs);
1715
1716   /* Create the result variables.  */
1717   len = gfc_create_var (gfc_charlen_type_node, "len");
1718   args[0] = gfc_build_addr_expr (NULL_TREE, len);
1719   var = gfc_create_var (gfc_get_pchar_type (expr->ts.kind), "pstr");
1720   args[1] = gfc_build_addr_expr (ppvoid_type_node, var);
1721   args[2] = build_int_cst (NULL_TREE, op);
1722   args[3] = build_int_cst (NULL_TREE, nargs / 2);
1723
1724   if (expr->ts.kind == 1)
1725     function = gfor_fndecl_string_minmax;
1726   else if (expr->ts.kind == 4)
1727     function = gfor_fndecl_string_minmax_char4;
1728   else
1729     gcc_unreachable ();
1730
1731   /* Make the function call.  */
1732   fndecl = build_addr (function, current_function_decl);
1733   tmp = build_call_array_loc (input_location,
1734                           TREE_TYPE (TREE_TYPE (function)), fndecl,
1735                           nargs + 4, args);
1736   gfc_add_expr_to_block (&se->pre, tmp);
1737
1738   /* Free the temporary afterwards, if necessary.  */
1739   cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
1740                           len, build_int_cst (TREE_TYPE (len), 0));
1741   tmp = gfc_call_free (var);
1742   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
1743   gfc_add_expr_to_block (&se->post, tmp);
1744
1745   se->expr = var;
1746   se->string_length = len;
1747 }
1748
1749
1750 /* Create a symbol node for this intrinsic.  The symbol from the frontend
1751    has the generic name.  */
1752
1753 static gfc_symbol *
1754 gfc_get_symbol_for_expr (gfc_expr * expr)
1755 {
1756   gfc_symbol *sym;
1757
1758   /* TODO: Add symbols for intrinsic function to the global namespace.  */
1759   gcc_assert (strlen (expr->value.function.name) <= GFC_MAX_SYMBOL_LEN - 5);
1760   sym = gfc_new_symbol (expr->value.function.name, NULL);
1761
1762   sym->ts = expr->ts;
1763   sym->attr.external = 1;
1764   sym->attr.function = 1;
1765   sym->attr.always_explicit = 1;
1766   sym->attr.proc = PROC_INTRINSIC;
1767   sym->attr.flavor = FL_PROCEDURE;
1768   sym->result = sym;
1769   if (expr->rank > 0)
1770     {
1771       sym->attr.dimension = 1;
1772       sym->as = gfc_get_array_spec ();
1773       sym->as->type = AS_ASSUMED_SHAPE;
1774       sym->as->rank = expr->rank;
1775     }
1776
1777   gfc_copy_formal_args_intr (sym, expr->value.function.isym);
1778
1779   return sym;
1780 }
1781
1782 /* Generate a call to an external intrinsic function.  */
1783 static void
1784 gfc_conv_intrinsic_funcall (gfc_se * se, gfc_expr * expr)
1785 {
1786   gfc_symbol *sym;
1787   VEC(tree,gc) *append_args;
1788
1789   gcc_assert (!se->ss || se->ss->expr == expr);
1790
1791   if (se->ss)
1792     gcc_assert (expr->rank > 0);
1793   else
1794     gcc_assert (expr->rank == 0);
1795
1796   sym = gfc_get_symbol_for_expr (expr);
1797
1798   /* Calls to libgfortran_matmul need to be appended special arguments,
1799      to be able to call the BLAS ?gemm functions if required and possible.  */
1800   append_args = NULL;
1801   if (expr->value.function.isym->id == GFC_ISYM_MATMUL
1802       && sym->ts.type != BT_LOGICAL)
1803     {
1804       tree cint = gfc_get_int_type (gfc_c_int_kind);
1805
1806       if (gfc_option.flag_external_blas
1807           && (sym->ts.type == BT_REAL || sym->ts.type == BT_COMPLEX)
1808           && (sym->ts.kind == gfc_default_real_kind
1809               || sym->ts.kind == gfc_default_double_kind))
1810         {
1811           tree gemm_fndecl;
1812
1813           if (sym->ts.type == BT_REAL)
1814             {
1815               if (sym->ts.kind == gfc_default_real_kind)
1816                 gemm_fndecl = gfor_fndecl_sgemm;
1817               else
1818                 gemm_fndecl = gfor_fndecl_dgemm;
1819             }
1820           else
1821             {
1822               if (sym->ts.kind == gfc_default_real_kind)
1823                 gemm_fndecl = gfor_fndecl_cgemm;
1824               else
1825                 gemm_fndecl = gfor_fndecl_zgemm;
1826             }
1827
1828           append_args = VEC_alloc (tree, gc, 3);
1829           VEC_quick_push (tree, append_args, build_int_cst (cint, 1));
1830           VEC_quick_push (tree, append_args,
1831                           build_int_cst (cint, gfc_option.blas_matmul_limit));
1832           VEC_quick_push (tree, append_args,
1833                           gfc_build_addr_expr (NULL_TREE, gemm_fndecl));
1834         }
1835       else
1836         {
1837           append_args = VEC_alloc (tree, gc, 3);
1838           VEC_quick_push (tree, append_args, build_int_cst (cint, 0));
1839           VEC_quick_push (tree, append_args, build_int_cst (cint, 0));
1840           VEC_quick_push (tree, append_args, null_pointer_node);
1841         }
1842     }
1843
1844   gfc_conv_procedure_call (se, sym, expr->value.function.actual, expr,
1845                           append_args);
1846   gfc_free_symbol (sym);
1847 }
1848
1849 /* ANY and ALL intrinsics. ANY->op == NE_EXPR, ALL->op == EQ_EXPR.
1850    Implemented as
1851     any(a)
1852     {
1853       forall (i=...)
1854         if (a[i] != 0)
1855           return 1
1856       end forall
1857       return 0
1858     }
1859     all(a)
1860     {
1861       forall (i=...)
1862         if (a[i] == 0)
1863           return 0
1864       end forall
1865       return 1
1866     }
1867  */
1868 static void
1869 gfc_conv_intrinsic_anyall (gfc_se * se, gfc_expr * expr, enum tree_code op)
1870 {
1871   tree resvar;
1872   stmtblock_t block;
1873   stmtblock_t body;
1874   tree type;
1875   tree tmp;
1876   tree found;
1877   gfc_loopinfo loop;
1878   gfc_actual_arglist *actual;
1879   gfc_ss *arrayss;
1880   gfc_se arrayse;
1881   tree exit_label;
1882
1883   if (se->ss)
1884     {
1885       gfc_conv_intrinsic_funcall (se, expr);
1886       return;
1887     }
1888
1889   actual = expr->value.function.actual;
1890   type = gfc_typenode_for_spec (&expr->ts);
1891   /* Initialize the result.  */
1892   resvar = gfc_create_var (type, "test");
1893   if (op == EQ_EXPR)
1894     tmp = convert (type, boolean_true_node);
1895   else
1896     tmp = convert (type, boolean_false_node);
1897   gfc_add_modify (&se->pre, resvar, tmp);
1898
1899   /* Walk the arguments.  */
1900   arrayss = gfc_walk_expr (actual->expr);
1901   gcc_assert (arrayss != gfc_ss_terminator);
1902
1903   /* Initialize the scalarizer.  */
1904   gfc_init_loopinfo (&loop);
1905   exit_label = gfc_build_label_decl (NULL_TREE);
1906   TREE_USED (exit_label) = 1;
1907   gfc_add_ss_to_loop (&loop, arrayss);
1908
1909   /* Initialize the loop.  */
1910   gfc_conv_ss_startstride (&loop);
1911   gfc_conv_loop_setup (&loop, &expr->where);
1912
1913   gfc_mark_ss_chain_used (arrayss, 1);
1914   /* Generate the loop body.  */
1915   gfc_start_scalarized_body (&loop, &body);
1916
1917   /* If the condition matches then set the return value.  */
1918   gfc_start_block (&block);
1919   if (op == EQ_EXPR)
1920     tmp = convert (type, boolean_false_node);
1921   else
1922     tmp = convert (type, boolean_true_node);
1923   gfc_add_modify (&block, resvar, tmp);
1924
1925   /* And break out of the loop.  */
1926   tmp = build1_v (GOTO_EXPR, exit_label);
1927   gfc_add_expr_to_block (&block, tmp);
1928
1929   found = gfc_finish_block (&block);
1930
1931   /* Check this element.  */
1932   gfc_init_se (&arrayse, NULL);
1933   gfc_copy_loopinfo_to_se (&arrayse, &loop);
1934   arrayse.ss = arrayss;
1935   gfc_conv_expr_val (&arrayse, actual->expr);
1936
1937   gfc_add_block_to_block (&body, &arrayse.pre);
1938   tmp = fold_build2_loc (input_location, op, boolean_type_node, arrayse.expr,
1939                          build_int_cst (TREE_TYPE (arrayse.expr), 0));
1940   tmp = build3_v (COND_EXPR, tmp, found, build_empty_stmt (input_location));
1941   gfc_add_expr_to_block (&body, tmp);
1942   gfc_add_block_to_block (&body, &arrayse.post);
1943
1944   gfc_trans_scalarizing_loops (&loop, &body);
1945
1946   /* Add the exit label.  */
1947   tmp = build1_v (LABEL_EXPR, exit_label);
1948   gfc_add_expr_to_block (&loop.pre, tmp);
1949
1950   gfc_add_block_to_block (&se->pre, &loop.pre);
1951   gfc_add_block_to_block (&se->pre, &loop.post);
1952   gfc_cleanup_loop (&loop);
1953
1954   se->expr = resvar;
1955 }
1956
1957 /* COUNT(A) = Number of true elements in A.  */
1958 static void
1959 gfc_conv_intrinsic_count (gfc_se * se, gfc_expr * expr)
1960 {
1961   tree resvar;
1962   tree type;
1963   stmtblock_t body;
1964   tree tmp;
1965   gfc_loopinfo loop;
1966   gfc_actual_arglist *actual;
1967   gfc_ss *arrayss;
1968   gfc_se arrayse;
1969
1970   if (se->ss)
1971     {
1972       gfc_conv_intrinsic_funcall (se, expr);
1973       return;
1974     }
1975
1976   actual = expr->value.function.actual;
1977
1978   type = gfc_typenode_for_spec (&expr->ts);
1979   /* Initialize the result.  */
1980   resvar = gfc_create_var (type, "count");
1981   gfc_add_modify (&se->pre, resvar, build_int_cst (type, 0));
1982
1983   /* Walk the arguments.  */
1984   arrayss = gfc_walk_expr (actual->expr);
1985   gcc_assert (arrayss != gfc_ss_terminator);
1986
1987   /* Initialize the scalarizer.  */
1988   gfc_init_loopinfo (&loop);
1989   gfc_add_ss_to_loop (&loop, arrayss);
1990
1991   /* Initialize the loop.  */
1992   gfc_conv_ss_startstride (&loop);
1993   gfc_conv_loop_setup (&loop, &expr->where);
1994
1995   gfc_mark_ss_chain_used (arrayss, 1);
1996   /* Generate the loop body.  */
1997   gfc_start_scalarized_body (&loop, &body);
1998
1999   tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (resvar),
2000                          resvar, build_int_cst (TREE_TYPE (resvar), 1));
2001   tmp = build2_v (MODIFY_EXPR, resvar, tmp);
2002
2003   gfc_init_se (&arrayse, NULL);
2004   gfc_copy_loopinfo_to_se (&arrayse, &loop);
2005   arrayse.ss = arrayss;
2006   gfc_conv_expr_val (&arrayse, actual->expr);
2007   tmp = build3_v (COND_EXPR, arrayse.expr, tmp,
2008                   build_empty_stmt (input_location));
2009
2010   gfc_add_block_to_block (&body, &arrayse.pre);
2011   gfc_add_expr_to_block (&body, tmp);
2012   gfc_add_block_to_block (&body, &arrayse.post);
2013
2014   gfc_trans_scalarizing_loops (&loop, &body);
2015
2016   gfc_add_block_to_block (&se->pre, &loop.pre);
2017   gfc_add_block_to_block (&se->pre, &loop.post);
2018   gfc_cleanup_loop (&loop);
2019
2020   se->expr = resvar;
2021 }
2022
2023 /* Inline implementation of the sum and product intrinsics.  */
2024 static void
2025 gfc_conv_intrinsic_arith (gfc_se * se, gfc_expr * expr, enum tree_code op,
2026                           bool norm2)
2027 {
2028   tree resvar;
2029   tree scale = NULL_TREE;
2030   tree type;
2031   stmtblock_t body;
2032   stmtblock_t block;
2033   tree tmp;
2034   gfc_loopinfo loop;
2035   gfc_actual_arglist *actual;
2036   gfc_ss *arrayss;
2037   gfc_ss *maskss;
2038   gfc_se arrayse;
2039   gfc_se maskse;
2040   gfc_expr *arrayexpr;
2041   gfc_expr *maskexpr;
2042
2043   if (se->ss)
2044     {
2045       gfc_conv_intrinsic_funcall (se, expr);
2046       return;
2047     }
2048
2049   type = gfc_typenode_for_spec (&expr->ts);
2050   /* Initialize the result.  */
2051   resvar = gfc_create_var (type, "val");
2052   if (norm2)
2053     {
2054       /* result = 0.0;
2055          scale = 1.0.  */
2056       scale = gfc_create_var (type, "scale");
2057       gfc_add_modify (&se->pre, scale,
2058                       gfc_build_const (type, integer_one_node));
2059       tmp = gfc_build_const (type, integer_zero_node);
2060     }
2061   else if (op == PLUS_EXPR || op == BIT_IOR_EXPR || op == BIT_XOR_EXPR)
2062     tmp = gfc_build_const (type, integer_zero_node);
2063   else if (op == NE_EXPR)
2064     /* PARITY.  */
2065     tmp = convert (type, boolean_false_node);
2066   else if (op == BIT_AND_EXPR)
2067     tmp = gfc_build_const (type, fold_build1_loc (input_location, NEGATE_EXPR,
2068                                                   type, integer_one_node));
2069   else
2070     tmp = gfc_build_const (type, integer_one_node);
2071
2072   gfc_add_modify (&se->pre, resvar, tmp);
2073
2074   /* Walk the arguments.  */
2075   actual = expr->value.function.actual;
2076   arrayexpr = actual->expr;
2077   arrayss = gfc_walk_expr (arrayexpr);
2078   gcc_assert (arrayss != gfc_ss_terminator);
2079
2080   if (op == NE_EXPR || norm2)
2081     /* PARITY and NORM2.  */
2082     maskexpr = NULL;
2083   else
2084     {
2085       actual = actual->next->next;
2086       gcc_assert (actual);
2087       maskexpr = actual->expr;
2088     }
2089
2090   if (maskexpr && maskexpr->rank != 0)
2091     {
2092       maskss = gfc_walk_expr (maskexpr);
2093       gcc_assert (maskss != gfc_ss_terminator);
2094     }
2095   else
2096     maskss = NULL;
2097
2098   /* Initialize the scalarizer.  */
2099   gfc_init_loopinfo (&loop);
2100   gfc_add_ss_to_loop (&loop, arrayss);
2101   if (maskss)
2102     gfc_add_ss_to_loop (&loop, maskss);
2103
2104   /* Initialize the loop.  */
2105   gfc_conv_ss_startstride (&loop);
2106   gfc_conv_loop_setup (&loop, &expr->where);
2107
2108   gfc_mark_ss_chain_used (arrayss, 1);
2109   if (maskss)
2110     gfc_mark_ss_chain_used (maskss, 1);
2111   /* Generate the loop body.  */
2112   gfc_start_scalarized_body (&loop, &body);
2113
2114   /* If we have a mask, only add this element if the mask is set.  */
2115   if (maskss)
2116     {
2117       gfc_init_se (&maskse, NULL);
2118       gfc_copy_loopinfo_to_se (&maskse, &loop);
2119       maskse.ss = maskss;
2120       gfc_conv_expr_val (&maskse, maskexpr);
2121       gfc_add_block_to_block (&body, &maskse.pre);
2122
2123       gfc_start_block (&block);
2124     }
2125   else
2126     gfc_init_block (&block);
2127
2128   /* Do the actual summation/product.  */
2129   gfc_init_se (&arrayse, NULL);
2130   gfc_copy_loopinfo_to_se (&arrayse, &loop);
2131   arrayse.ss = arrayss;
2132   gfc_conv_expr_val (&arrayse, arrayexpr);
2133   gfc_add_block_to_block (&block, &arrayse.pre);
2134
2135   if (norm2)
2136     {
2137       /* if (x(i) != 0.0)
2138            {
2139              absX = abs(x(i))
2140              if (absX > scale)
2141                {
2142                  val = scale/absX;
2143                  result = 1.0 + result * val * val;
2144                  scale = absX;
2145                }
2146              else
2147                {
2148                  val = absX/scale;
2149                  result += val * val;
2150                }
2151            }  */
2152       tree res1, res2, cond, absX, val;
2153       stmtblock_t ifblock1, ifblock2, ifblock3;
2154
2155       gfc_init_block (&ifblock1);
2156
2157       absX = gfc_create_var (type, "absX");
2158       gfc_add_modify (&ifblock1, absX,
2159                       fold_build1_loc (input_location, ABS_EXPR, type,
2160                                        arrayse.expr));
2161       val = gfc_create_var (type, "val");
2162       gfc_add_expr_to_block (&ifblock1, val);
2163
2164       gfc_init_block (&ifblock2);
2165       gfc_add_modify (&ifblock2, val,
2166                       fold_build2_loc (input_location, RDIV_EXPR, type, scale,
2167                                        absX));
2168       res1 = fold_build2_loc (input_location, MULT_EXPR, type, val, val); 
2169       res1 = fold_build2_loc (input_location, MULT_EXPR, type, resvar, res1);
2170       res1 = fold_build2_loc (input_location, PLUS_EXPR, type, res1,
2171                               gfc_build_const (type, integer_one_node));
2172       gfc_add_modify (&ifblock2, resvar, res1);
2173       gfc_add_modify (&ifblock2, scale, absX);
2174       res1 = gfc_finish_block (&ifblock2); 
2175
2176       gfc_init_block (&ifblock3);
2177       gfc_add_modify (&ifblock3, val,
2178                       fold_build2_loc (input_location, RDIV_EXPR, type, absX,
2179                                        scale));
2180       res2 = fold_build2_loc (input_location, MULT_EXPR, type, val, val); 
2181       res2 = fold_build2_loc (input_location, PLUS_EXPR, type, resvar, res2);
2182       gfc_add_modify (&ifblock3, resvar, res2);
2183       res2 = gfc_finish_block (&ifblock3);
2184
2185       cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
2186                               absX, scale);
2187       tmp = build3_v (COND_EXPR, cond, res1, res2);
2188       gfc_add_expr_to_block (&ifblock1, tmp);  
2189       tmp = gfc_finish_block (&ifblock1);
2190
2191       cond = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
2192                               arrayse.expr,
2193                               gfc_build_const (type, integer_zero_node));
2194
2195       tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
2196       gfc_add_expr_to_block (&block, tmp);  
2197     }
2198   else
2199     {
2200       tmp = fold_build2_loc (input_location, op, type, resvar, arrayse.expr);
2201       gfc_add_modify (&block, resvar, tmp);
2202     }
2203
2204   gfc_add_block_to_block (&block, &arrayse.post);
2205
2206   if (maskss)
2207     {
2208       /* We enclose the above in if (mask) {...} .  */
2209
2210       tmp = gfc_finish_block (&block);
2211       tmp = build3_v (COND_EXPR, maskse.expr, tmp,
2212                       build_empty_stmt (input_location));
2213     }
2214   else
2215     tmp = gfc_finish_block (&block);
2216   gfc_add_expr_to_block (&body, tmp);
2217
2218   gfc_trans_scalarizing_loops (&loop, &body);
2219
2220   /* For a scalar mask, enclose the loop in an if statement.  */
2221   if (maskexpr && maskss == NULL)
2222     {
2223       gfc_init_se (&maskse, NULL);
2224       gfc_conv_expr_val (&maskse, maskexpr);
2225       gfc_init_block (&block);
2226       gfc_add_block_to_block (&block, &loop.pre);
2227       gfc_add_block_to_block (&block, &loop.post);
2228       tmp = gfc_finish_block (&block);
2229
2230       tmp = build3_v (COND_EXPR, maskse.expr, tmp,
2231                       build_empty_stmt (input_location));
2232       gfc_add_expr_to_block (&block, tmp);
2233       gfc_add_block_to_block (&se->pre, &block);
2234     }
2235   else
2236     {
2237       gfc_add_block_to_block (&se->pre, &loop.pre);
2238       gfc_add_block_to_block (&se->pre, &loop.post);
2239     }
2240
2241   gfc_cleanup_loop (&loop);
2242
2243   if (norm2)
2244     {
2245       /* result = scale * sqrt(result).  */
2246       tree sqrt;
2247       sqrt = gfc_builtin_decl_for_float_kind (BUILT_IN_SQRT, expr->ts.kind);
2248       resvar = build_call_expr_loc (input_location,
2249                                     sqrt, 1, resvar);
2250       resvar = fold_build2_loc (input_location, MULT_EXPR, type, scale, resvar);
2251     }
2252
2253   se->expr = resvar;
2254 }
2255
2256
2257 /* Inline implementation of the dot_product intrinsic. This function
2258    is based on gfc_conv_intrinsic_arith (the previous function).  */
2259 static void
2260 gfc_conv_intrinsic_dot_product (gfc_se * se, gfc_expr * expr)
2261 {
2262   tree resvar;
2263   tree type;
2264   stmtblock_t body;
2265   stmtblock_t block;
2266   tree tmp;
2267   gfc_loopinfo loop;
2268   gfc_actual_arglist *actual;
2269   gfc_ss *arrayss1, *arrayss2;
2270   gfc_se arrayse1, arrayse2;
2271   gfc_expr *arrayexpr1, *arrayexpr2;
2272
2273   type = gfc_typenode_for_spec (&expr->ts);
2274
2275   /* Initialize the result.  */
2276   resvar = gfc_create_var (type, "val");
2277   if (expr->ts.type == BT_LOGICAL)
2278     tmp = build_int_cst (type, 0);
2279   else
2280     tmp = gfc_build_const (type, integer_zero_node);
2281
2282   gfc_add_modify (&se->pre, resvar, tmp);
2283
2284   /* Walk argument #1.  */
2285   actual = expr->value.function.actual;
2286   arrayexpr1 = actual->expr;
2287   arrayss1 = gfc_walk_expr (arrayexpr1);
2288   gcc_assert (arrayss1 != gfc_ss_terminator);
2289
2290   /* Walk argument #2.  */
2291   actual = actual->next;
2292   arrayexpr2 = actual->expr;
2293   arrayss2 = gfc_walk_expr (arrayexpr2);
2294   gcc_assert (arrayss2 != gfc_ss_terminator);
2295
2296   /* Initialize the scalarizer.  */
2297   gfc_init_loopinfo (&loop);
2298   gfc_add_ss_to_loop (&loop, arrayss1);
2299   gfc_add_ss_to_loop (&loop, arrayss2);
2300
2301   /* Initialize the loop.  */
2302   gfc_conv_ss_startstride (&loop);
2303   gfc_conv_loop_setup (&loop, &expr->where);
2304
2305   gfc_mark_ss_chain_used (arrayss1, 1);
2306   gfc_mark_ss_chain_used (arrayss2, 1);
2307
2308   /* Generate the loop body.  */
2309   gfc_start_scalarized_body (&loop, &body);
2310   gfc_init_block (&block);
2311
2312   /* Make the tree expression for [conjg(]array1[)].  */
2313   gfc_init_se (&arrayse1, NULL);
2314   gfc_copy_loopinfo_to_se (&arrayse1, &loop);
2315   arrayse1.ss = arrayss1;
2316   gfc_conv_expr_val (&arrayse1, arrayexpr1);
2317   if (expr->ts.type == BT_COMPLEX)
2318     arrayse1.expr = fold_build1_loc (input_location, CONJ_EXPR, type,
2319                                      arrayse1.expr);
2320   gfc_add_block_to_block (&block, &arrayse1.pre);
2321
2322   /* Make the tree expression for array2.  */
2323   gfc_init_se (&arrayse2, NULL);
2324   gfc_copy_loopinfo_to_se (&arrayse2, &loop);
2325   arrayse2.ss = arrayss2;
2326   gfc_conv_expr_val (&arrayse2, arrayexpr2);
2327   gfc_add_block_to_block (&block, &arrayse2.pre);
2328
2329   /* Do the actual product and sum.  */
2330   if (expr->ts.type == BT_LOGICAL)
2331     {
2332       tmp = fold_build2_loc (input_location, TRUTH_AND_EXPR, type,
2333                              arrayse1.expr, arrayse2.expr);
2334       tmp = fold_build2_loc (input_location, TRUTH_OR_EXPR, type, resvar, tmp);
2335     }
2336   else
2337     {
2338       tmp = fold_build2_loc (input_location, MULT_EXPR, type, arrayse1.expr,
2339                              arrayse2.expr);
2340       tmp = fold_build2_loc (input_location, PLUS_EXPR, type, resvar, tmp);
2341     }
2342   gfc_add_modify (&block, resvar, tmp);
2343
2344   /* Finish up the loop block and the loop.  */
2345   tmp = gfc_finish_block (&block);
2346   gfc_add_expr_to_block (&body, tmp);
2347
2348   gfc_trans_scalarizing_loops (&loop, &body);
2349   gfc_add_block_to_block (&se->pre, &loop.pre);
2350   gfc_add_block_to_block (&se->pre, &loop.post);
2351   gfc_cleanup_loop (&loop);
2352
2353   se->expr = resvar;
2354 }
2355
2356
2357 /* Emit code for minloc or maxloc intrinsic.  There are many different cases
2358    we need to handle.  For performance reasons we sometimes create two
2359    loops instead of one, where the second one is much simpler.
2360    Examples for minloc intrinsic:
2361    1) Result is an array, a call is generated
2362    2) Array mask is used and NaNs need to be supported:
2363       limit = Infinity;
2364       pos = 0;
2365       S = from;
2366       while (S <= to) {
2367         if (mask[S]) {
2368           if (pos == 0) pos = S + (1 - from);
2369           if (a[S] <= limit) { limit = a[S]; pos = S + (1 - from); goto lab1; }
2370         }
2371         S++;
2372       }
2373       goto lab2;
2374       lab1:;
2375       while (S <= to) {
2376         if (mask[S]) if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
2377         S++;
2378       }
2379       lab2:;
2380    3) NaNs need to be supported, but it is known at compile time or cheaply
2381       at runtime whether array is nonempty or not:
2382       limit = Infinity;
2383       pos = 0;
2384       S = from;
2385       while (S <= to) {
2386         if (a[S] <= limit) { limit = a[S]; pos = S + (1 - from); goto lab1; }
2387         S++;
2388       }
2389       if (from <= to) pos = 1;
2390       goto lab2;
2391       lab1:;
2392       while (S <= to) {
2393         if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
2394         S++;
2395       }
2396       lab2:;
2397    4) NaNs aren't supported, array mask is used:
2398       limit = infinities_supported ? Infinity : huge (limit);
2399       pos = 0;
2400       S = from;
2401       while (S <= to) {
2402         if (mask[S]) { limit = a[S]; pos = S + (1 - from); goto lab1; }
2403         S++;
2404       }
2405       goto lab2;
2406       lab1:;
2407       while (S <= to) {
2408         if (mask[S]) if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
2409         S++;
2410       }
2411       lab2:;
2412    5) Same without array mask:
2413       limit = infinities_supported ? Infinity : huge (limit);
2414       pos = (from <= to) ? 1 : 0;
2415       S = from;
2416       while (S <= to) {
2417         if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
2418         S++;
2419       }
2420    For 3) and 5), if mask is scalar, this all goes into a conditional,
2421    setting pos = 0; in the else branch.  */
2422
2423 static void
2424 gfc_conv_intrinsic_minmaxloc (gfc_se * se, gfc_expr * expr, enum tree_code op)
2425 {
2426   stmtblock_t body;
2427   stmtblock_t block;
2428   stmtblock_t ifblock;
2429   stmtblock_t elseblock;
2430   tree limit;
2431   tree type;
2432   tree tmp;
2433   tree cond;
2434   tree elsetmp;
2435   tree ifbody;
2436   tree offset;
2437   tree nonempty;
2438   tree lab1, lab2;
2439   gfc_loopinfo loop;
2440   gfc_actual_arglist *actual;
2441   gfc_ss *arrayss;
2442   gfc_ss *maskss;
2443   gfc_se arrayse;
2444   gfc_se maskse;
2445   gfc_expr *arrayexpr;
2446   gfc_expr *maskexpr;
2447   tree pos;
2448   int n;
2449
2450   if (se->ss)
2451     {
2452       gfc_conv_intrinsic_funcall (se, expr);
2453       return;
2454     }
2455
2456   /* Initialize the result.  */
2457   pos = gfc_create_var (gfc_array_index_type, "pos");
2458   offset = gfc_create_var (gfc_array_index_type, "offset");
2459   type = gfc_typenode_for_spec (&expr->ts);
2460
2461   /* Walk the arguments.  */
2462   actual = expr->value.function.actual;
2463   arrayexpr = actual->expr;
2464   arrayss = gfc_walk_expr (arrayexpr);
2465   gcc_assert (arrayss != gfc_ss_terminator);
2466
2467   actual = actual->next->next;
2468   gcc_assert (actual);
2469   maskexpr = actual->expr;
2470   nonempty = NULL;
2471   if (maskexpr && maskexpr->rank != 0)
2472     {
2473       maskss = gfc_walk_expr (maskexpr);
2474       gcc_assert (maskss != gfc_ss_terminator);
2475     }
2476   else
2477     {
2478       mpz_t asize;
2479       if (gfc_array_size (arrayexpr, &asize) == SUCCESS)
2480         {
2481           nonempty = gfc_conv_mpz_to_tree (asize, gfc_index_integer_kind);
2482           mpz_clear (asize);
2483           nonempty = fold_build2_loc (input_location, GT_EXPR,
2484                                       boolean_type_node, nonempty,
2485                                       gfc_index_zero_node);
2486         }
2487       maskss = NULL;
2488     }
2489
2490   limit = gfc_create_var (gfc_typenode_for_spec (&arrayexpr->ts), "limit");
2491   switch (arrayexpr->ts.type)
2492     {
2493     case BT_REAL:
2494       tmp = gfc_build_inf_or_huge (TREE_TYPE (limit), arrayexpr->ts.kind);
2495       break;
2496
2497     case BT_INTEGER:
2498       n = gfc_validate_kind (arrayexpr->ts.type, arrayexpr->ts.kind, false);
2499       tmp = gfc_conv_mpz_to_tree (gfc_integer_kinds[n].huge,
2500                                   arrayexpr->ts.kind);
2501       break;
2502
2503     default:
2504       gcc_unreachable ();
2505     }
2506
2507   /* We start with the most negative possible value for MAXLOC, and the most
2508      positive possible value for MINLOC. The most negative possible value is
2509      -HUGE for BT_REAL and (-HUGE - 1) for BT_INTEGER; the most positive
2510      possible value is HUGE in both cases.  */
2511   if (op == GT_EXPR)
2512     tmp = fold_build1_loc (input_location, NEGATE_EXPR, TREE_TYPE (tmp), tmp);
2513   if (op == GT_EXPR && expr->ts.type == BT_INTEGER)
2514     tmp = fold_build2_loc (input_location, MINUS_EXPR, TREE_TYPE (tmp), tmp,
2515                            build_int_cst (type, 1));
2516
2517   gfc_add_modify (&se->pre, limit, tmp);
2518
2519   /* Initialize the scalarizer.  */
2520   gfc_init_loopinfo (&loop);
2521   gfc_add_ss_to_loop (&loop, arrayss);
2522   if (maskss)
2523     gfc_add_ss_to_loop (&loop, maskss);
2524
2525   /* Initialize the loop.  */
2526   gfc_conv_ss_startstride (&loop);
2527   gfc_conv_loop_setup (&loop, &expr->where);
2528
2529   gcc_assert (loop.dimen == 1);
2530   if (nonempty == NULL && maskss == NULL && loop.from[0] && loop.to[0])
2531     nonempty = fold_build2_loc (input_location, LE_EXPR, boolean_type_node,
2532                                 loop.from[0], loop.to[0]);
2533
2534   lab1 = NULL;
2535   lab2 = NULL;
2536   /* Initialize the position to zero, following Fortran 2003.  We are free
2537      to do this because Fortran 95 allows the result of an entirely false
2538      mask to be processor dependent.  If we know at compile time the array
2539      is non-empty and no MASK is used, we can initialize to 1 to simplify
2540      the inner loop.  */
2541   if (nonempty != NULL && !HONOR_NANS (DECL_MODE (limit)))
2542     gfc_add_modify (&loop.pre, pos,
2543                     fold_build3_loc (input_location, COND_EXPR,
2544                                      gfc_array_index_type,
2545                                      nonempty, gfc_index_one_node,
2546                                      gfc_index_zero_node));
2547   else
2548     {
2549       gfc_add_modify (&loop.pre, pos, gfc_index_zero_node);
2550       lab1 = gfc_build_label_decl (NULL_TREE);
2551       TREE_USED (lab1) = 1;
2552       lab2 = gfc_build_label_decl (NULL_TREE);
2553       TREE_USED (lab2) = 1;
2554     }
2555
2556   gfc_mark_ss_chain_used (arrayss, 1);
2557   if (maskss)
2558     gfc_mark_ss_chain_used (maskss, 1);
2559   /* Generate the loop body.  */
2560   gfc_start_scalarized_body (&loop, &body);
2561
2562   /* If we have a mask, only check this element if the mask is set.  */
2563   if (maskss)
2564     {
2565       gfc_init_se (&maskse, NULL);
2566       gfc_copy_loopinfo_to_se (&maskse, &loop);
2567       maskse.ss = maskss;
2568       gfc_conv_expr_val (&maskse, maskexpr);
2569       gfc_add_block_to_block (&body, &maskse.pre);
2570
2571       gfc_start_block (&block);
2572     }
2573   else
2574     gfc_init_block (&block);
2575
2576   /* Compare with the current limit.  */
2577   gfc_init_se (&arrayse, NULL);
2578   gfc_copy_loopinfo_to_se (&arrayse, &loop);
2579   arrayse.ss = arrayss;
2580   gfc_conv_expr_val (&arrayse, arrayexpr);
2581   gfc_add_block_to_block (&block, &arrayse.pre);
2582
2583   /* We do the following if this is a more extreme value.  */
2584   gfc_start_block (&ifblock);
2585
2586   /* Assign the value to the limit...  */
2587   gfc_add_modify (&ifblock, limit, arrayse.expr);
2588
2589   /* Remember where we are.  An offset must be added to the loop
2590      counter to obtain the required position.  */
2591   if (loop.from[0])
2592     tmp = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
2593                            gfc_index_one_node, loop.from[0]);
2594   else
2595     tmp = gfc_index_one_node;
2596
2597   gfc_add_modify (&block, offset, tmp);
2598
2599   if (nonempty == NULL && HONOR_NANS (DECL_MODE (limit)))
2600     {
2601       stmtblock_t ifblock2;
2602       tree ifbody2;
2603
2604       gfc_start_block (&ifblock2);
2605       tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (pos),
2606                              loop.loopvar[0], offset);
2607       gfc_add_modify (&ifblock2, pos, tmp);
2608       ifbody2 = gfc_finish_block (&ifblock2);
2609       cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, pos,
2610                               gfc_index_zero_node);
2611       tmp = build3_v (COND_EXPR, cond, ifbody2,
2612                       build_empty_stmt (input_location));
2613       gfc_add_expr_to_block (&block, tmp);
2614     }
2615
2616   tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (pos),
2617                          loop.loopvar[0], offset);
2618   gfc_add_modify (&ifblock, pos, tmp);
2619
2620   if (lab1)
2621     gfc_add_expr_to_block (&ifblock, build1_v (GOTO_EXPR, lab1));
2622
2623   ifbody = gfc_finish_block (&ifblock);
2624
2625   if (!lab1 || HONOR_NANS (DECL_MODE (limit)))
2626     {
2627       if (lab1)
2628         cond = fold_build2_loc (input_location,
2629                                 op == GT_EXPR ? GE_EXPR : LE_EXPR,
2630                                 boolean_type_node, arrayse.expr, limit);
2631       else
2632         cond = fold_build2_loc (input_location, op, boolean_type_node,
2633                                 arrayse.expr, limit);
2634
2635       ifbody = build3_v (COND_EXPR, cond, ifbody,
2636                          build_empty_stmt (input_location));
2637     }
2638   gfc_add_expr_to_block (&block, ifbody);
2639
2640   if (maskss)
2641     {
2642       /* We enclose the above in if (mask) {...}.  */
2643       tmp = gfc_finish_block (&block);
2644
2645       tmp = build3_v (COND_EXPR, maskse.expr, tmp,
2646                       build_empty_stmt (input_location));
2647     }
2648   else
2649     tmp = gfc_finish_block (&block);
2650   gfc_add_expr_to_block (&body, tmp);
2651
2652   if (lab1)
2653     {
2654       gfc_trans_scalarized_loop_end (&loop, 0, &body);
2655
2656       if (HONOR_NANS (DECL_MODE (limit)))
2657         {
2658           if (nonempty != NULL)
2659             {
2660               ifbody = build2_v (MODIFY_EXPR, pos, gfc_index_one_node);
2661               tmp = build3_v (COND_EXPR, nonempty, ifbody,
2662                               build_empty_stmt (input_location));
2663               gfc_add_expr_to_block (&loop.code[0], tmp);
2664             }
2665         }
2666
2667       gfc_add_expr_to_block (&loop.code[0], build1_v (GOTO_EXPR, lab2));
2668       gfc_add_expr_to_block (&loop.code[0], build1_v (LABEL_EXPR, lab1));
2669       gfc_start_block (&body);
2670
2671       /* If we have a mask, only check this element if the mask is set.  */
2672       if (maskss)
2673         {
2674           gfc_init_se (&maskse, NULL);
2675           gfc_copy_loopinfo_to_se (&maskse, &loop);
2676           maskse.ss = maskss;
2677           gfc_conv_expr_val (&maskse, maskexpr);
2678           gfc_add_block_to_block (&body, &maskse.pre);
2679
2680           gfc_start_block (&block);
2681         }
2682       else
2683         gfc_init_block (&block);
2684
2685       /* Compare with the current limit.  */
2686       gfc_init_se (&arrayse, NULL);
2687       gfc_copy_loopinfo_to_se (&arrayse, &loop);
2688       arrayse.ss = arrayss;
2689       gfc_conv_expr_val (&arrayse, arrayexpr);
2690       gfc_add_block_to_block (&block, &arrayse.pre);
2691
2692       /* We do the following if this is a more extreme value.  */
2693       gfc_start_block (&ifblock);
2694
2695       /* Assign the value to the limit...  */
2696       gfc_add_modify (&ifblock, limit, arrayse.expr);
2697
2698       /* Remember where we are.  An offset must be added to the loop
2699          counter to obtain the required position.  */
2700       if (loop.from[0])
2701         tmp = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
2702                                gfc_index_one_node, loop.from[0]);
2703       else
2704         tmp = gfc_index_one_node;
2705
2706       gfc_add_modify (&block, offset, tmp);
2707
2708       tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (pos),
2709                              loop.loopvar[0], offset);
2710       gfc_add_modify (&ifblock, pos, tmp);
2711
2712       ifbody = gfc_finish_block (&ifblock);
2713
2714       cond = fold_build2_loc (input_location, op, boolean_type_node,
2715                               arrayse.expr, limit);
2716
2717       tmp = build3_v (COND_EXPR, cond, ifbody,
2718                       build_empty_stmt (input_location));
2719       gfc_add_expr_to_block (&block, tmp);
2720
2721       if (maskss)
2722         {
2723           /* We enclose the above in if (mask) {...}.  */
2724           tmp = gfc_finish_block (&block);
2725
2726           tmp = build3_v (COND_EXPR, maskse.expr, tmp,
2727                           build_empty_stmt (input_location));
2728         }
2729       else
2730         tmp = gfc_finish_block (&block);
2731       gfc_add_expr_to_block (&body, tmp);
2732       /* Avoid initializing loopvar[0] again, it should be left where
2733          it finished by the first loop.  */
2734       loop.from[0] = loop.loopvar[0];
2735     }
2736
2737   gfc_trans_scalarizing_loops (&loop, &body);
2738
2739   if (lab2)
2740     gfc_add_expr_to_block (&loop.pre, build1_v (LABEL_EXPR, lab2));
2741
2742   /* For a scalar mask, enclose the loop in an if statement.  */
2743   if (maskexpr && maskss == NULL)
2744     {
2745       gfc_init_se (&maskse, NULL);
2746       gfc_conv_expr_val (&maskse, maskexpr);
2747       gfc_init_block (&block);
2748       gfc_add_block_to_block (&block, &loop.pre);
2749       gfc_add_block_to_block (&block, &loop.post);
2750       tmp = gfc_finish_block (&block);
2751
2752       /* For the else part of the scalar mask, just initialize
2753          the pos variable the same way as above.  */
2754
2755       gfc_init_block (&elseblock);
2756       gfc_add_modify (&elseblock, pos, gfc_index_zero_node);
2757       elsetmp = gfc_finish_block (&elseblock);
2758
2759       tmp = build3_v (COND_EXPR, maskse.expr, tmp, elsetmp);
2760       gfc_add_expr_to_block (&block, tmp);
2761       gfc_add_block_to_block (&se->pre, &block);
2762     }
2763   else
2764     {
2765       gfc_add_block_to_block (&se->pre, &loop.pre);
2766       gfc_add_block_to_block (&se->pre, &loop.post);
2767     }
2768   gfc_cleanup_loop (&loop);
2769
2770   se->expr = convert (type, pos);
2771 }
2772
2773 /* Emit code for minval or maxval intrinsic.  There are many different cases
2774    we need to handle.  For performance reasons we sometimes create two
2775    loops instead of one, where the second one is much simpler.
2776    Examples for minval intrinsic:
2777    1) Result is an array, a call is generated
2778    2) Array mask is used and NaNs need to be supported, rank 1:
2779       limit = Infinity;
2780       nonempty = false;
2781       S = from;
2782       while (S <= to) {
2783         if (mask[S]) { nonempty = true; if (a[S] <= limit) goto lab; }
2784         S++;
2785       }
2786       limit = nonempty ? NaN : huge (limit);
2787       lab:
2788       while (S <= to) { if(mask[S]) limit = min (a[S], limit); S++; }
2789    3) NaNs need to be supported, but it is known at compile time or cheaply
2790       at runtime whether array is nonempty or not, rank 1:
2791       limit = Infinity;
2792       S = from;
2793       while (S <= to) { if (a[S] <= limit) goto lab; S++; }
2794       limit = (from <= to) ? NaN : huge (limit);
2795       lab:
2796       while (S <= to) { limit = min (a[S], limit); S++; }
2797    4) Array mask is used and NaNs need to be supported, rank > 1:
2798       limit = Infinity;
2799       nonempty = false;
2800       fast = false;
2801       S1 = from1;
2802       while (S1 <= to1) {
2803         S2 = from2;
2804         while (S2 <= to2) {
2805           if (mask[S1][S2]) {
2806             if (fast) limit = min (a[S1][S2], limit);
2807             else {
2808               nonempty = true;
2809               if (a[S1][S2] <= limit) {
2810                 limit = a[S1][S2];
2811                 fast = true;
2812               }
2813             }
2814           }
2815           S2++;
2816         }
2817         S1++;
2818       }
2819       if (!fast)
2820         limit = nonempty ? NaN : huge (limit);
2821    5) NaNs need to be supported, but it is known at compile time or cheaply
2822       at runtime whether array is nonempty or not, rank > 1:
2823       limit = Infinity;
2824       fast = false;
2825       S1 = from1;
2826       while (S1 <= to1) {
2827         S2 = from2;
2828         while (S2 <= to2) {
2829           if (fast) limit = min (a[S1][S2], limit);
2830           else {
2831             if (a[S1][S2] <= limit) {
2832               limit = a[S1][S2];
2833               fast = true;
2834             }
2835           }
2836           S2++;
2837         }
2838         S1++;
2839       }
2840       if (!fast)
2841         limit = (nonempty_array) ? NaN : huge (limit);
2842    6) NaNs aren't supported, but infinities are.  Array mask is used:
2843       limit = Infinity;
2844       nonempty = false;
2845       S = from;
2846       while (S <= to) {
2847         if (mask[S]) { nonempty = true; limit = min (a[S], limit); }
2848         S++;
2849       }
2850       limit = nonempty ? limit : huge (limit);
2851    7) Same without array mask:
2852       limit = Infinity;
2853       S = from;
2854       while (S <= to) { limit = min (a[S], limit); S++; }
2855       limit = (from <= to) ? limit : huge (limit);
2856    8) Neither NaNs nor infinities are supported (-ffast-math or BT_INTEGER):
2857       limit = huge (limit);
2858       S = from;
2859       while (S <= to) { limit = min (a[S], limit); S++); }
2860       (or
2861       while (S <= to) { if (mask[S]) limit = min (a[S], limit); S++; }
2862       with array mask instead).
2863    For 3), 5), 7) and 8), if mask is scalar, this all goes into a conditional,
2864    setting limit = huge (limit); in the else branch.  */
2865
2866 static void
2867 gfc_conv_intrinsic_minmaxval (gfc_se * se, gfc_expr * expr, enum tree_code op)
2868 {
2869   tree limit;
2870   tree type;
2871   tree tmp;
2872   tree ifbody;
2873   tree nonempty;
2874   tree nonempty_var;
2875   tree lab;
2876   tree fast;
2877   tree huge_cst = NULL, nan_cst = NULL;
2878   stmtblock_t body;
2879   stmtblock_t block, block2;
2880   gfc_loopinfo loop;
2881   gfc_actual_arglist *actual;
2882   gfc_ss *arrayss;
2883   gfc_ss *maskss;
2884   gfc_se arrayse;
2885   gfc_se maskse;
2886   gfc_expr *arrayexpr;
2887   gfc_expr *maskexpr;
2888   int n;
2889
2890   if (se->ss)
2891     {
2892       gfc_conv_intrinsic_funcall (se, expr);
2893       return;
2894     }
2895
2896   type = gfc_typenode_for_spec (&expr->ts);
2897   /* Initialize the result.  */
2898   limit = gfc_create_var (type, "limit");
2899   n = gfc_validate_kind (expr->ts.type, expr->ts.kind, false);
2900   switch (expr->ts.type)
2901     {
2902     case BT_REAL:
2903       huge_cst = gfc_conv_mpfr_to_tree (gfc_real_kinds[n].huge,
2904                                         expr->ts.kind, 0);
2905       if (HONOR_INFINITIES (DECL_MODE (limit)))
2906         {
2907           REAL_VALUE_TYPE real;
2908           real_inf (&real);
2909           tmp = build_real (type, real);
2910         }
2911       else
2912         tmp = huge_cst;
2913       if (HONOR_NANS (DECL_MODE (limit)))
2914         {
2915           REAL_VALUE_TYPE real;
2916           real_nan (&real, "", 1, DECL_MODE (limit));
2917           nan_cst = build_real (type, real);
2918         }
2919       break;
2920
2921     case BT_INTEGER:
2922       tmp = gfc_conv_mpz_to_tree (gfc_integer_kinds[n].huge, expr->ts.kind);
2923       break;
2924
2925     default:
2926       gcc_unreachable ();
2927     }
2928
2929   /* We start with the most negative possible value for MAXVAL, and the most
2930      positive possible value for MINVAL. The most negative possible value is
2931      -HUGE for BT_REAL and (-HUGE - 1) for BT_INTEGER; the most positive
2932      possible value is HUGE in both cases.  */
2933   if (op == GT_EXPR)
2934     {
2935       tmp = fold_build1_loc (input_location, NEGATE_EXPR, TREE_TYPE (tmp), tmp);
2936       if (huge_cst)
2937         huge_cst = fold_build1_loc (input_location, NEGATE_EXPR,
2938                                     TREE_TYPE (huge_cst), huge_cst);
2939     }
2940
2941   if (op == GT_EXPR && expr->ts.type == BT_INTEGER)
2942     tmp = fold_build2_loc (input_location, MINUS_EXPR, TREE_TYPE (tmp),
2943                            tmp, build_int_cst (type, 1));
2944
2945   gfc_add_modify (&se->pre, limit, tmp);
2946
2947   /* Walk the arguments.  */
2948   actual = expr->value.function.actual;
2949   arrayexpr = actual->expr;
2950   arrayss = gfc_walk_expr (arrayexpr);
2951   gcc_assert (arrayss != gfc_ss_terminator);
2952
2953   actual = actual->next->next;
2954   gcc_assert (actual);
2955   maskexpr = actual->expr;
2956   nonempty = NULL;
2957   if (maskexpr && maskexpr->rank != 0)
2958     {
2959       maskss = gfc_walk_expr (maskexpr);
2960       gcc_assert (maskss != gfc_ss_terminator);
2961     }
2962   else
2963     {
2964       mpz_t asize;
2965       if (gfc_array_size (arrayexpr, &asize) == SUCCESS)
2966         {
2967           nonempty = gfc_conv_mpz_to_tree (asize, gfc_index_integer_kind);
2968           mpz_clear (asize);
2969           nonempty = fold_build2_loc (input_location, GT_EXPR,
2970                                       boolean_type_node, nonempty,
2971                                       gfc_index_zero_node);
2972         }
2973       maskss = NULL;
2974     }
2975
2976   /* Initialize the scalarizer.  */
2977   gfc_init_loopinfo (&loop);
2978   gfc_add_ss_to_loop (&loop, arrayss);
2979   if (maskss)
2980     gfc_add_ss_to_loop (&loop, maskss);
2981
2982   /* Initialize the loop.  */
2983   gfc_conv_ss_startstride (&loop);
2984   gfc_conv_loop_setup (&loop, &expr->where);
2985
2986   if (nonempty == NULL && maskss == NULL
2987       && loop.dimen == 1 && loop.from[0] && loop.to[0])
2988     nonempty = fold_build2_loc (input_location, LE_EXPR, boolean_type_node,
2989                                 loop.from[0], loop.to[0]);
2990   nonempty_var = NULL;
2991   if (nonempty == NULL
2992       && (HONOR_INFINITIES (DECL_MODE (limit))
2993           || HONOR_NANS (DECL_MODE (limit))))
2994     {
2995       nonempty_var = gfc_create_var (boolean_type_node, "nonempty");
2996       gfc_add_modify (&se->pre, nonempty_var, boolean_false_node);
2997       nonempty = nonempty_var;
2998     }
2999   lab = NULL;
3000   fast = NULL;
3001   if (HONOR_NANS (DECL_MODE (limit)))
3002     {
3003       if (loop.dimen == 1)
3004         {
3005           lab = gfc_build_label_decl (NULL_TREE);
3006           TREE_USED (lab) = 1;
3007         }
3008       else
3009         {
3010           fast = gfc_create_var (boolean_type_node, "fast");
3011           gfc_add_modify (&se->pre, fast, boolean_false_node);
3012         }
3013     }
3014
3015   gfc_mark_ss_chain_used (arrayss, 1);
3016   if (maskss)
3017     gfc_mark_ss_chain_used (maskss, 1);
3018   /* Generate the loop body.  */
3019   gfc_start_scalarized_body (&loop, &body);
3020
3021   /* If we have a mask, only add this element if the mask is set.  */
3022   if (maskss)
3023     {
3024       gfc_init_se (&maskse, NULL);
3025       gfc_copy_loopinfo_to_se (&maskse, &loop);
3026       maskse.ss = maskss;
3027       gfc_conv_expr_val (&maskse, maskexpr);
3028       gfc_add_block_to_block (&body, &maskse.pre);
3029
3030       gfc_start_block (&block);
3031     }
3032   else
3033     gfc_init_block (&block);
3034
3035   /* Compare with the current limit.  */
3036   gfc_init_se (&arrayse, NULL);
3037   gfc_copy_loopinfo_to_se (&arrayse, &loop);
3038   arrayse.ss = arrayss;
3039   gfc_conv_expr_val (&arrayse, arrayexpr);
3040   gfc_add_block_to_block (&block, &arrayse.pre);
3041
3042   gfc_init_block (&block2);
3043
3044   if (nonempty_var)
3045     gfc_add_modify (&block2, nonempty_var, boolean_true_node);
3046
3047   if (HONOR_NANS (DECL_MODE (limit)))
3048     {
3049       tmp = fold_build2_loc (input_location, op == GT_EXPR ? GE_EXPR : LE_EXPR,
3050                              boolean_type_node, arrayse.expr, limit);
3051       if (lab)
3052         ifbody = build1_v (GOTO_EXPR, lab);
3053       else
3054         {
3055           stmtblock_t ifblock;
3056
3057           gfc_init_block (&ifblock);
3058           gfc_add_modify (&ifblock, limit, arrayse.expr);
3059           gfc_add_modify (&ifblock, fast, boolean_true_node);
3060           ifbody = gfc_finish_block (&ifblock);
3061         }
3062       tmp = build3_v (COND_EXPR, tmp, ifbody,
3063                       build_empty_stmt (input_location));
3064       gfc_add_expr_to_block (&block2, tmp);
3065     }
3066   else
3067     {
3068       /* MIN_EXPR/MAX_EXPR has unspecified behavior with NaNs or
3069          signed zeros.  */
3070       if (HONOR_SIGNED_ZEROS (DECL_MODE (limit)))
3071         {
3072           tmp = fold_build2_loc (input_location, op, boolean_type_node,
3073                                  arrayse.expr, limit);
3074           ifbody = build2_v (MODIFY_EXPR, limit, arrayse.expr);
3075           tmp = build3_v (COND_EXPR, tmp, ifbody,
3076                           build_empty_stmt (input_location));
3077           gfc_add_expr_to_block (&block2, tmp);
3078         }
3079       else
3080         {
3081           tmp = fold_build2_loc (input_location,
3082                                  op == GT_EXPR ? MAX_EXPR : MIN_EXPR,
3083                                  type, arrayse.expr, limit);
3084           gfc_add_modify (&block2, limit, tmp);
3085         }
3086     }
3087
3088   if (fast)
3089     {
3090       tree elsebody = gfc_finish_block (&block2);
3091
3092       /* MIN_EXPR/MAX_EXPR has unspecified behavior with NaNs or
3093          signed zeros.  */
3094       if (HONOR_NANS (DECL_MODE (limit))
3095           || HONOR_SIGNED_ZEROS (DECL_MODE (limit)))
3096         {
3097           tmp = fold_build2_loc (input_location, op, boolean_type_node,
3098                                  arrayse.expr, limit);
3099           ifbody = build2_v (MODIFY_EXPR, limit, arrayse.expr);
3100           ifbody = build3_v (COND_EXPR, tmp, ifbody,
3101                              build_empty_stmt (input_location));
3102         }
3103       else
3104         {
3105           tmp = fold_build2_loc (input_location,
3106                                  op == GT_EXPR ? MAX_EXPR : MIN_EXPR,
3107                                  type, arrayse.expr, limit);
3108           ifbody = build2_v (MODIFY_EXPR, limit, tmp);
3109         }
3110       tmp = build3_v (COND_EXPR, fast, ifbody, elsebody);
3111       gfc_add_expr_to_block (&block, tmp);
3112     }
3113   else
3114     gfc_add_block_to_block (&block, &block2);
3115
3116   gfc_add_block_to_block (&block, &arrayse.post);
3117
3118   tmp = gfc_finish_block (&block);
3119   if (maskss)
3120     /* We enclose the above in if (mask) {...}.  */
3121     tmp = build3_v (COND_EXPR, maskse.expr, tmp,
3122                     build_empty_stmt (input_location));
3123   gfc_add_expr_to_block (&body, tmp);
3124
3125   if (lab)
3126     {
3127       gfc_trans_scalarized_loop_end (&loop, 0, &body);
3128
3129       tmp = fold_build3_loc (input_location, COND_EXPR, type, nonempty,
3130                              nan_cst, huge_cst);
3131       gfc_add_modify (&loop.code[0], limit, tmp);
3132       gfc_add_expr_to_block (&loop.code[0], build1_v (LABEL_EXPR, lab));
3133
3134       gfc_start_block (&body);
3135
3136       /* If we have a mask, only add this element if the mask is set.  */
3137       if (maskss)
3138         {
3139           gfc_init_se (&maskse, NULL);
3140           gfc_copy_loopinfo_to_se (&maskse, &loop);
3141           maskse.ss = maskss;
3142           gfc_conv_expr_val (&maskse, maskexpr);
3143           gfc_add_block_to_block (&body, &maskse.pre);
3144
3145           gfc_start_block (&block);
3146         }
3147       else
3148         gfc_init_block (&block);
3149
3150       /* Compare with the current limit.  */
3151       gfc_init_se (&arrayse, NULL);
3152       gfc_copy_loopinfo_to_se (&arrayse, &loop);
3153       arrayse.ss = arrayss;
3154       gfc_conv_expr_val (&arrayse, arrayexpr);
3155       gfc_add_block_to_block (&block, &arrayse.pre);
3156
3157       /* MIN_EXPR/MAX_EXPR has unspecified behavior with NaNs or
3158          signed zeros.  */
3159       if (HONOR_NANS (DECL_MODE (limit))
3160           || HONOR_SIGNED_ZEROS (DECL_MODE (limit)))
3161         {
3162           tmp = fold_build2_loc (input_location, op, boolean_type_node,
3163                                  arrayse.expr, limit);
3164           ifbody = build2_v (MODIFY_EXPR, limit, arrayse.expr);
3165           tmp = build3_v (COND_EXPR, tmp, ifbody,
3166                           build_empty_stmt (input_location));
3167           gfc_add_expr_to_block (&block, tmp);
3168         }
3169       else
3170         {
3171           tmp = fold_build2_loc (input_location,
3172                                  op == GT_EXPR ? MAX_EXPR : MIN_EXPR,
3173                                  type, arrayse.expr, limit);
3174           gfc_add_modify (&block, limit, tmp);
3175         }
3176
3177       gfc_add_block_to_block (&block, &arrayse.post);
3178
3179       tmp = gfc_finish_block (&block);
3180       if (maskss)
3181         /* We enclose the above in if (mask) {...}.  */
3182         tmp = build3_v (COND_EXPR, maskse.expr, tmp,
3183                         build_empty_stmt (input_location));
3184       gfc_add_expr_to_block (&body, tmp);
3185       /* Avoid initializing loopvar[0] again, it should be left where
3186          it finished by the first loop.  */
3187       loop.from[0] = loop.loopvar[0];
3188     }
3189   gfc_trans_scalarizing_loops (&loop, &body);
3190
3191   if (fast)
3192     {
3193       tmp = fold_build3_loc (input_location, COND_EXPR, type, nonempty,
3194                              nan_cst, huge_cst);
3195       ifbody = build2_v (MODIFY_EXPR, limit, tmp);
3196       tmp = build3_v (COND_EXPR, fast, build_empty_stmt (input_location),
3197                       ifbody);
3198       gfc_add_expr_to_block (&loop.pre, tmp);
3199     }
3200   else if (HONOR_INFINITIES (DECL_MODE (limit)) && !lab)
3201     {
3202       tmp = fold_build3_loc (input_location, COND_EXPR, type, nonempty, limit,
3203                              huge_cst);
3204       gfc_add_modify (&loop.pre, limit, tmp);
3205     }
3206
3207   /* For a scalar mask, enclose the loop in an if statement.  */
3208   if (maskexpr && maskss == NULL)
3209     {
3210       tree else_stmt;
3211
3212       gfc_init_se (&maskse, NULL);
3213       gfc_conv_expr_val (&maskse, maskexpr);
3214       gfc_init_block (&block);
3215       gfc_add_block_to_block (&block, &loop.pre);
3216       gfc_add_block_to_block (&block, &loop.post);
3217       tmp = gfc_finish_block (&block);
3218
3219       if (HONOR_INFINITIES (DECL_MODE (limit)))
3220         else_stmt = build2_v (MODIFY_EXPR, limit, huge_cst);
3221       else
3222         else_stmt = build_empty_stmt (input_location);
3223       tmp = build3_v (COND_EXPR, maskse.expr, tmp, else_stmt);
3224       gfc_add_expr_to_block (&block, tmp);
3225       gfc_add_block_to_block (&se->pre, &block);
3226     }
3227   else
3228     {
3229       gfc_add_block_to_block (&se->pre, &loop.pre);
3230       gfc_add_block_to_block (&se->pre, &loop.post);
3231     }
3232
3233   gfc_cleanup_loop (&loop);
3234
3235   se->expr = limit;
3236 }
3237
3238 /* BTEST (i, pos) = (i & (1 << pos)) != 0.  */
3239 static void
3240 gfc_conv_intrinsic_btest (gfc_se * se, gfc_expr * expr)
3241 {
3242   tree args[2];
3243   tree type;
3244   tree tmp;
3245
3246   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3247   type = TREE_TYPE (args[0]);
3248
3249   tmp = fold_build2_loc (input_location, LSHIFT_EXPR, type,
3250                          build_int_cst (type, 1), args[1]);
3251   tmp = fold_build2_loc (input_location, BIT_AND_EXPR, type, args[0], tmp);
3252   tmp = fold_build2_loc (input_location, NE_EXPR, boolean_type_node, tmp,
3253                          build_int_cst (type, 0));
3254   type = gfc_typenode_for_spec (&expr->ts);
3255   se->expr = convert (type, tmp);
3256 }
3257
3258
3259 /* Generate code for BGE, BGT, BLE and BLT intrinsics.  */
3260 static void
3261 gfc_conv_intrinsic_bitcomp (gfc_se * se, gfc_expr * expr, enum tree_code op)
3262 {
3263   tree args[2];
3264
3265   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3266
3267   /* Convert both arguments to the unsigned type of the same size.  */
3268   args[0] = fold_convert (unsigned_type_for (TREE_TYPE (args[0])), args[0]);
3269   args[1] = fold_convert (unsigned_type_for (TREE_TYPE (args[1])), args[1]);
3270
3271   /* If they have unequal type size, convert to the larger one.  */
3272   if (TYPE_PRECISION (TREE_TYPE (args[0]))
3273       > TYPE_PRECISION (TREE_TYPE (args[1])))
3274     args[1] = fold_convert (TREE_TYPE (args[0]), args[1]);
3275   else if (TYPE_PRECISION (TREE_TYPE (args[1]))
3276            > TYPE_PRECISION (TREE_TYPE (args[0])))
3277     args[0] = fold_convert (TREE_TYPE (args[1]), args[0]);
3278
3279   /* Now, we compare them.  */
3280   se->expr = fold_build2_loc (input_location, op, boolean_type_node,
3281                               args[0], args[1]);
3282 }
3283
3284
3285 /* Generate code to perform the specified operation.  */
3286 static void
3287 gfc_conv_intrinsic_bitop (gfc_se * se, gfc_expr * expr, enum tree_code op)
3288 {
3289   tree args[2];
3290
3291   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3292   se->expr = fold_build2_loc (input_location, op, TREE_TYPE (args[0]),
3293                               args[0], args[1]);
3294 }
3295
3296 /* Bitwise not.  */
3297 static void
3298 gfc_conv_intrinsic_not (gfc_se * se, gfc_expr * expr)
3299 {
3300   tree arg;
3301
3302   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
3303   se->expr = fold_build1_loc (input_location, BIT_NOT_EXPR,
3304                               TREE_TYPE (arg), arg);
3305 }
3306
3307 /* Set or clear a single bit.  */
3308 static void
3309 gfc_conv_intrinsic_singlebitop (gfc_se * se, gfc_expr * expr, int set)
3310 {
3311   tree args[2];
3312   tree type;
3313   tree tmp;
3314   enum tree_code op;
3315
3316   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3317   type = TREE_TYPE (args[0]);
3318
3319   tmp = fold_build2_loc (input_location, LSHIFT_EXPR, type,
3320                          build_int_cst (type, 1), args[1]);
3321   if (set)
3322     op = BIT_IOR_EXPR;
3323   else
3324     {
3325       op = BIT_AND_EXPR;
3326       tmp = fold_build1_loc (input_location, BIT_NOT_EXPR, type, tmp);
3327     }
3328   se->expr = fold_build2_loc (input_location, op, type, args[0], tmp);
3329 }
3330
3331 /* Extract a sequence of bits.
3332     IBITS(I, POS, LEN) = (I >> POS) & ~((~0) << LEN).  */
3333 static void
3334 gfc_conv_intrinsic_ibits (gfc_se * se, gfc_expr * expr)
3335 {
3336   tree args[3];
3337   tree type;
3338   tree tmp;
3339   tree mask;
3340
3341   gfc_conv_intrinsic_function_args (se, expr, args, 3);
3342   type = TREE_TYPE (args[0]);
3343
3344   mask = build_int_cst (type, -1);
3345   mask = fold_build2_loc (input_location, LSHIFT_EXPR, type, mask, args[2]);
3346   mask = fold_build1_loc (input_location, BIT_NOT_EXPR, type, mask);
3347
3348   tmp = fold_build2_loc (input_location, RSHIFT_EXPR, type, args[0], args[1]);
3349
3350   se->expr = fold_build2_loc (input_location, BIT_AND_EXPR, type, tmp, mask);
3351 }
3352
3353 static void
3354 gfc_conv_intrinsic_shift (gfc_se * se, gfc_expr * expr, bool right_shift,
3355                           bool arithmetic)
3356 {
3357   tree args[2], type, num_bits, cond;
3358
3359   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3360
3361   args[0] = gfc_evaluate_now (args[0], &se->pre);
3362   args[1] = gfc_evaluate_now (args[1], &se->pre);
3363   type = TREE_TYPE (args[0]);
3364
3365   if (!arithmetic)
3366     args[0] = fold_convert (unsigned_type_for (type), args[0]);
3367   else
3368     gcc_assert (right_shift);
3369
3370   se->expr = fold_build2_loc (input_location,
3371                               right_shift ? RSHIFT_EXPR : LSHIFT_EXPR,
3372                               TREE_TYPE (args[0]), args[0], args[1]);
3373
3374   if (!arithmetic)
3375     se->expr = fold_convert (type, se->expr);
3376
3377   /* The Fortran standard allows shift widths <= BIT_SIZE(I), whereas
3378      gcc requires a shift width < BIT_SIZE(I), so we have to catch this
3379      special case.  */
3380   num_bits = build_int_cst (TREE_TYPE (args[1]), TYPE_PRECISION (type));
3381   cond = fold_build2_loc (input_location, GE_EXPR, boolean_type_node,
3382                           args[1], num_bits);
3383
3384   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond,
3385                               build_int_cst (type, 0), se->expr);
3386 }
3387
3388 /* ISHFT (I, SHIFT) = (abs (shift) >= BIT_SIZE (i))
3389                         ? 0
3390                         : ((shift >= 0) ? i << shift : i >> -shift)
3391    where all shifts are logical shifts.  */
3392 static void
3393 gfc_conv_intrinsic_ishft (gfc_se * se, gfc_expr * expr)
3394 {
3395   tree args[2];
3396   tree type;
3397   tree utype;
3398   tree tmp;
3399   tree width;
3400   tree num_bits;
3401   tree cond;
3402   tree lshift;
3403   tree rshift;
3404
3405   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3406
3407   args[0] = gfc_evaluate_now (args[0], &se->pre);
3408   args[1] = gfc_evaluate_now (args[1], &se->pre);
3409
3410   type = TREE_TYPE (args[0]);
3411   utype = unsigned_type_for (type);
3412
3413   width = fold_build1_loc (input_location, ABS_EXPR, TREE_TYPE (args[1]),
3414                            args[1]);
3415
3416   /* Left shift if positive.  */
3417   lshift = fold_build2_loc (input_location, LSHIFT_EXPR, type, args[0], width);
3418
3419   /* Right shift if negative.
3420      We convert to an unsigned type because we want a logical shift.
3421      The standard doesn't define the case of shifting negative
3422      numbers, and we try to be compatible with other compilers, most
3423      notably g77, here.  */
3424   rshift = fold_convert (type, fold_build2_loc (input_location, RSHIFT_EXPR,
3425                                     utype, convert (utype, args[0]), width));
3426
3427   tmp = fold_build2_loc (input_location, GE_EXPR, boolean_type_node, args[1],
3428                          build_int_cst (TREE_TYPE (args[1]), 0));
3429   tmp = fold_build3_loc (input_location, COND_EXPR, type, tmp, lshift, rshift);
3430
3431   /* The Fortran standard allows shift widths <= BIT_SIZE(I), whereas
3432      gcc requires a shift width < BIT_SIZE(I), so we have to catch this
3433      special case.  */
3434   num_bits = build_int_cst (TREE_TYPE (args[1]), TYPE_PRECISION (type));
3435   cond = fold_build2_loc (input_location, GE_EXPR, boolean_type_node, width,
3436                           num_bits);
3437   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond,
3438                               build_int_cst (type, 0), tmp);
3439 }
3440
3441
3442 /* Circular shift.  AKA rotate or barrel shift.  */
3443
3444 static void
3445 gfc_conv_intrinsic_ishftc (gfc_se * se, gfc_expr * expr)
3446 {
3447   tree *args;
3448   tree type;
3449   tree tmp;
3450   tree lrot;
3451   tree rrot;
3452   tree zero;
3453   unsigned int num_args;
3454
3455   num_args = gfc_intrinsic_argument_list_length (expr);
3456   args = XALLOCAVEC (tree, num_args);
3457
3458   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
3459
3460   if (num_args == 3)
3461     {
3462       /* Use a library function for the 3 parameter version.  */
3463       tree int4type = gfc_get_int_type (4);
3464
3465       type = TREE_TYPE (args[0]);
3466       /* We convert the first argument to at least 4 bytes, and
3467          convert back afterwards.  This removes the need for library
3468          functions for all argument sizes, and function will be
3469          aligned to at least 32 bits, so there's no loss.  */
3470       if (expr->ts.kind < 4)
3471         args[0] = convert (int4type, args[0]);
3472
3473       /* Convert the SHIFT and SIZE args to INTEGER*4 otherwise we would
3474          need loads of library  functions.  They cannot have values >
3475          BIT_SIZE (I) so the conversion is safe.  */
3476       args[1] = convert (int4type, args[1]);
3477       args[2] = convert (int4type, args[2]);
3478
3479       switch (expr->ts.kind)
3480         {
3481         case 1:
3482         case 2:
3483         case 4:
3484           tmp = gfor_fndecl_math_ishftc4;
3485           break;
3486         case 8:
3487           tmp = gfor_fndecl_math_ishftc8;
3488           break;
3489         case 16:
3490           tmp = gfor_fndecl_math_ishftc16;
3491           break;
3492         default:
3493           gcc_unreachable ();
3494         }
3495       se->expr = build_call_expr_loc (input_location,
3496                                       tmp, 3, args[0], args[1], args[2]);
3497       /* Convert the result back to the original type, if we extended
3498          the first argument's width above.  */
3499       if (expr->ts.kind < 4)
3500         se->expr = convert (type, se->expr);
3501
3502       return;
3503     }
3504   type = TREE_TYPE (args[0]);
3505
3506   /* Evaluate arguments only once.  */
3507   args[0] = gfc_evaluate_now (args[0], &se->pre);
3508   args[1] = gfc_evaluate_now (args[1], &se->pre);
3509
3510   /* Rotate left if positive.  */
3511   lrot = fold_build2_loc (input_location, LROTATE_EXPR, type, args[0], args[1]);
3512
3513   /* Rotate right if negative.  */
3514   tmp = fold_build1_loc (input_location, NEGATE_EXPR, TREE_TYPE (args[1]),
3515                          args[1]);
3516   rrot = fold_build2_loc (input_location,RROTATE_EXPR, type, args[0], tmp);
3517
3518   zero = build_int_cst (TREE_TYPE (args[1]), 0);
3519   tmp = fold_build2_loc (input_location, GT_EXPR, boolean_type_node, args[1],
3520                          zero);
3521   rrot = fold_build3_loc (input_location, COND_EXPR, type, tmp, lrot, rrot);
3522
3523   /* Do nothing if shift == 0.  */
3524   tmp = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, args[1],
3525                          zero);
3526   se->expr = fold_build3_loc (input_location, COND_EXPR, type, tmp, args[0],
3527                               rrot);
3528 }
3529
3530
3531 /* LEADZ (i) = (i == 0) ? BIT_SIZE (i)
3532                         : __builtin_clz(i) - (BIT_SIZE('int') - BIT_SIZE(i))
3533
3534    The conditional expression is necessary because the result of LEADZ(0)
3535    is defined, but the result of __builtin_clz(0) is undefined for most
3536    targets.
3537
3538    For INTEGER kinds smaller than the C 'int' type, we have to subtract the
3539    difference in bit size between the argument of LEADZ and the C int.  */
3540  
3541 static void
3542 gfc_conv_intrinsic_leadz (gfc_se * se, gfc_expr * expr)
3543 {
3544   tree arg;
3545   tree arg_type;
3546   tree cond;
3547   tree result_type;
3548   tree leadz;
3549   tree bit_size;
3550   tree tmp;
3551   tree func;
3552   int s, argsize;
3553
3554   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
3555   argsize = TYPE_PRECISION (TREE_TYPE (arg));
3556
3557   /* Which variant of __builtin_clz* should we call?  */
3558   if (argsize <= INT_TYPE_SIZE)
3559     {
3560       arg_type = unsigned_type_node;
3561       func = built_in_decls[BUILT_IN_CLZ];
3562     }
3563   else if (argsize <= LONG_TYPE_SIZE)
3564     {
3565       arg_type = long_unsigned_type_node;
3566       func = built_in_decls[BUILT_IN_CLZL];
3567     }
3568   else if (argsize <= LONG_LONG_TYPE_SIZE)
3569     {
3570       arg_type = long_long_unsigned_type_node;
3571       func = built_in_decls[BUILT_IN_CLZLL];
3572     }
3573   else
3574     {
3575       gcc_assert (argsize == 2 * LONG_LONG_TYPE_SIZE);
3576       arg_type = gfc_build_uint_type (argsize);
3577       func = NULL_TREE;
3578     }
3579
3580   /* Convert the actual argument twice: first, to the unsigned type of the
3581      same size; then, to the proper argument type for the built-in
3582      function.  But the return type is of the default INTEGER kind.  */
3583   arg = fold_convert (gfc_build_uint_type (argsize), arg);
3584   arg = fold_convert (arg_type, arg);
3585   arg = gfc_evaluate_now (arg, &se->pre);
3586   result_type = gfc_get_int_type (gfc_default_integer_kind);
3587
3588   /* Compute LEADZ for the case i .ne. 0.  */
3589   if (func)
3590     {
3591       s = TYPE_PRECISION (arg_type) - argsize;
3592       tmp = fold_convert (result_type,
3593                           build_call_expr_loc (input_location, func,
3594                                                1, arg));
3595       leadz = fold_build2_loc (input_location, MINUS_EXPR, result_type,
3596                                tmp, build_int_cst (result_type, s));
3597     }
3598   else
3599     {
3600       /* We end up here if the argument type is larger than 'long long'.
3601          We generate this code:
3602   
3603             if (x & (ULL_MAX << ULL_SIZE) != 0)
3604               return clzll ((unsigned long long) (x >> ULLSIZE));
3605             else
3606               return ULL_SIZE + clzll ((unsigned long long) x);
3607          where ULL_MAX is the largest value that a ULL_MAX can hold
3608          (0xFFFFFFFFFFFFFFFF for a 64-bit long long type), and ULLSIZE
3609          is the bit-size of the long long type (64 in this example).  */
3610       tree ullsize, ullmax, tmp1, tmp2;
3611
3612       ullsize = build_int_cst (result_type, LONG_LONG_TYPE_SIZE);
3613       ullmax = fold_build1_loc (input_location, BIT_NOT_EXPR,
3614                                 long_long_unsigned_type_node,
3615                                 build_int_cst (long_long_unsigned_type_node,
3616                                                0));
3617
3618       cond = fold_build2_loc (input_location, LSHIFT_EXPR, arg_type,
3619                               fold_convert (arg_type, ullmax), ullsize);
3620       cond = fold_build2_loc (input_location, BIT_AND_EXPR, arg_type,
3621                               arg, cond);
3622       cond = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
3623                               cond, build_int_cst (arg_type, 0));
3624
3625       tmp1 = fold_build2_loc (input_location, RSHIFT_EXPR, arg_type,
3626                               arg, ullsize);
3627       tmp1 = fold_convert (long_long_unsigned_type_node, tmp1);
3628       tmp1 = fold_convert (result_type,
3629                            build_call_expr_loc (input_location, 
3630                                                 built_in_decls[BUILT_IN_CLZLL],
3631                                                 1, tmp1));
3632
3633       tmp2 = fold_convert (long_long_unsigned_type_node, arg);
3634       tmp2 = fold_convert (result_type,
3635                            build_call_expr_loc (input_location,
3636                                                 built_in_decls[BUILT_IN_CLZLL],
3637                                                 1, tmp2));
3638       tmp2 = fold_build2_loc (input_location, PLUS_EXPR, result_type,
3639                               tmp2, ullsize);
3640
3641       leadz = fold_build3_loc (input_location, COND_EXPR, result_type,
3642                                cond, tmp1, tmp2);
3643     }
3644
3645   /* Build BIT_SIZE.  */
3646   bit_size = build_int_cst (result_type, argsize);
3647
3648   cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
3649                           arg, build_int_cst (arg_type, 0));
3650   se->expr = fold_build3_loc (input_location, COND_EXPR, result_type, cond,
3651                               bit_size, leadz);
3652 }
3653
3654
3655 /* TRAILZ(i) = (i == 0) ? BIT_SIZE (i) : __builtin_ctz(i)
3656
3657    The conditional expression is necessary because the result of TRAILZ(0)
3658    is defined, but the result of __builtin_ctz(0) is undefined for most
3659    targets.  */
3660  
3661 static void
3662 gfc_conv_intrinsic_trailz (gfc_se * se, gfc_expr *expr)
3663 {
3664   tree arg;
3665   tree arg_type;
3666   tree cond;
3667   tree result_type;
3668   tree trailz;
3669   tree bit_size;
3670   tree func;
3671   int argsize;
3672
3673   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
3674   argsize = TYPE_PRECISION (TREE_TYPE (arg));
3675
3676   /* Which variant of __builtin_ctz* should we call?  */
3677   if (argsize <= INT_TYPE_SIZE)
3678     {
3679       arg_type = unsigned_type_node;
3680       func = built_in_decls[BUILT_IN_CTZ];
3681     }
3682   else if (argsize <= LONG_TYPE_SIZE)
3683     {
3684       arg_type = long_unsigned_type_node;
3685       func = built_in_decls[BUILT_IN_CTZL];
3686     }
3687   else if (argsize <= LONG_LONG_TYPE_SIZE)
3688     {
3689       arg_type = long_long_unsigned_type_node;
3690       func = built_in_decls[BUILT_IN_CTZLL];
3691     }
3692   else
3693     {
3694       gcc_assert (argsize == 2 * LONG_LONG_TYPE_SIZE);
3695       arg_type = gfc_build_uint_type (argsize);
3696       func = NULL_TREE;
3697     }
3698
3699   /* Convert the actual argument twice: first, to the unsigned type of the
3700      same size; then, to the proper argument type for the built-in
3701      function.  But the return type is of the default INTEGER kind.  */
3702   arg = fold_convert (gfc_build_uint_type (argsize), arg);
3703   arg = fold_convert (arg_type, arg);
3704   arg = gfc_evaluate_now (arg, &se->pre);
3705   result_type = gfc_get_int_type (gfc_default_integer_kind);
3706
3707   /* Compute TRAILZ for the case i .ne. 0.  */
3708   if (func)
3709     trailz = fold_convert (result_type, build_call_expr_loc (input_location,
3710                                                              func, 1, arg));
3711   else
3712     {
3713       /* We end up here if the argument type is larger than 'long long'.
3714          We generate this code:
3715   
3716             if ((x & ULL_MAX) == 0)
3717               return ULL_SIZE + ctzll ((unsigned long long) (x >> ULLSIZE));
3718             else
3719               return ctzll ((unsigned long long) x);
3720
3721          where ULL_MAX is the largest value that a ULL_MAX can hold
3722          (0xFFFFFFFFFFFFFFFF for a 64-bit long long type), and ULLSIZE
3723          is the bit-size of the long long type (64 in this example).  */
3724       tree ullsize, ullmax, tmp1, tmp2;
3725
3726       ullsize = build_int_cst (result_type, LONG_LONG_TYPE_SIZE);
3727       ullmax = fold_build1_loc (input_location, BIT_NOT_EXPR,
3728                                 long_long_unsigned_type_node,
3729                                 build_int_cst (long_long_unsigned_type_node, 0));
3730
3731       cond = fold_build2_loc (input_location, BIT_AND_EXPR, arg_type, arg,
3732                               fold_convert (arg_type, ullmax));
3733       cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, cond,
3734                               build_int_cst (arg_type, 0));
3735
3736       tmp1 = fold_build2_loc (input_location, RSHIFT_EXPR, arg_type,
3737                               arg, ullsize);
3738       tmp1 = fold_convert (long_long_unsigned_type_node, tmp1);
3739       tmp1 = fold_convert (result_type,
3740                            build_call_expr_loc (input_location, 
3741                                                 built_in_decls[BUILT_IN_CTZLL],
3742                                                 1, tmp1));
3743       tmp1 = fold_build2_loc (input_location, PLUS_EXPR, result_type,
3744                               tmp1, ullsize);
3745
3746       tmp2 = fold_convert (long_long_unsigned_type_node, arg);
3747       tmp2 = fold_convert (result_type,
3748                            build_call_expr_loc (input_location,
3749                                                 built_in_decls[BUILT_IN_CTZLL],
3750                                                 1, tmp2));
3751
3752       trailz = fold_build3_loc (input_location, COND_EXPR, result_type,
3753                                 cond, tmp1, tmp2);
3754     }
3755
3756   /* Build BIT_SIZE.  */
3757   bit_size = build_int_cst (result_type, argsize);
3758
3759   cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
3760                           arg, build_int_cst (arg_type, 0));
3761   se->expr = fold_build3_loc (input_location, COND_EXPR, result_type, cond,
3762                               bit_size, trailz);
3763 }
3764
3765 /* Using __builtin_popcount for POPCNT and __builtin_parity for POPPAR;
3766    for types larger than "long long", we call the long long built-in for
3767    the lower and higher bits and combine the result.  */
3768  
3769 static void
3770 gfc_conv_intrinsic_popcnt_poppar (gfc_se * se, gfc_expr *expr, int parity)
3771 {
3772   tree arg;
3773   tree arg_type;
3774   tree result_type;
3775   tree func;
3776   int argsize;
3777
3778   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
3779   argsize = TYPE_PRECISION (TREE_TYPE (arg));
3780   result_type = gfc_get_int_type (gfc_default_integer_kind);
3781
3782   /* Which variant of the builtin should we call?  */
3783   if (argsize <= INT_TYPE_SIZE)
3784     {
3785       arg_type = unsigned_type_node;
3786       func = built_in_decls[parity ? BUILT_IN_PARITY : BUILT_IN_POPCOUNT];
3787     }
3788   else if (argsize <= LONG_TYPE_SIZE)
3789     {
3790       arg_type = long_unsigned_type_node;
3791       func = built_in_decls[parity ? BUILT_IN_PARITYL : BUILT_IN_POPCOUNTL];
3792     }
3793   else if (argsize <= LONG_LONG_TYPE_SIZE)
3794     {
3795       arg_type = long_long_unsigned_type_node;
3796       func = built_in_decls[parity ? BUILT_IN_PARITYLL : BUILT_IN_POPCOUNTLL];
3797     }
3798   else
3799     {
3800       /* Our argument type is larger than 'long long', which mean none
3801          of the POPCOUNT builtins covers it.  We thus call the 'long long'
3802          variant multiple times, and add the results.  */
3803       tree utype, arg2, call1, call2;
3804
3805       /* For now, we only cover the case where argsize is twice as large
3806          as 'long long'.  */
3807       gcc_assert (argsize == 2 * LONG_LONG_TYPE_SIZE);
3808
3809       func = built_in_decls[parity ? BUILT_IN_PARITYLL : BUILT_IN_POPCOUNTLL];
3810
3811       /* Convert it to an integer, and store into a variable.  */
3812       utype = gfc_build_uint_type (argsize);
3813       arg = fold_convert (utype, arg);
3814       arg = gfc_evaluate_now (arg, &se->pre);
3815
3816       /* Call the builtin twice.  */
3817       call1 = build_call_expr_loc (input_location, func, 1,
3818                                    fold_convert (long_long_unsigned_type_node,
3819                                                  arg));
3820
3821       arg2 = fold_build2_loc (input_location, RSHIFT_EXPR, utype, arg,
3822                               build_int_cst (utype, LONG_LONG_TYPE_SIZE));
3823       call2 = build_call_expr_loc (input_location, func, 1,
3824                                    fold_convert (long_long_unsigned_type_node,
3825                                                  arg2));
3826                           
3827       /* Combine the results.  */
3828       if (parity)
3829         se->expr = fold_build2_loc (input_location, BIT_XOR_EXPR, result_type,
3830                                     call1, call2);
3831       else
3832         se->expr = fold_build2_loc (input_location, PLUS_EXPR, result_type,
3833                                     call1, call2);
3834
3835       return;
3836     }
3837
3838   /* Convert the actual argument twice: first, to the unsigned type of the
3839      same size; then, to the proper argument type for the built-in
3840      function.  */
3841   arg = fold_convert (gfc_build_uint_type (argsize), arg);
3842   arg = fold_convert (arg_type, arg);
3843
3844   se->expr = fold_convert (result_type,
3845                            build_call_expr_loc (input_location, func, 1, arg));
3846 }
3847
3848
3849 /* Process an intrinsic with unspecified argument-types that has an optional
3850    argument (which could be of type character), e.g. EOSHIFT.  For those, we
3851    need to append the string length of the optional argument if it is not
3852    present and the type is really character.
3853    primary specifies the position (starting at 1) of the non-optional argument
3854    specifying the type and optional gives the position of the optional
3855    argument in the arglist.  */
3856
3857 static void
3858 conv_generic_with_optional_char_arg (gfc_se* se, gfc_expr* expr,
3859                                      unsigned primary, unsigned optional)
3860 {
3861   gfc_actual_arglist* prim_arg;
3862   gfc_actual_arglist* opt_arg;
3863   unsigned cur_pos;
3864   gfc_actual_arglist* arg;
3865   gfc_symbol* sym;
3866   VEC(tree,gc) *append_args;
3867
3868   /* Find the two arguments given as position.  */
3869   cur_pos = 0;
3870   prim_arg = NULL;
3871   opt_arg = NULL;
3872   for (arg = expr->value.function.actual; arg; arg = arg->next)
3873     {
3874       ++cur_pos;
3875
3876       if (cur_pos == primary)
3877         prim_arg = arg;
3878       if (cur_pos == optional)
3879         opt_arg = arg;
3880
3881       if (cur_pos >= primary && cur_pos >= optional)
3882         break;
3883     }
3884   gcc_assert (prim_arg);
3885   gcc_assert (prim_arg->expr);
3886   gcc_assert (opt_arg);
3887
3888   /* If we do have type CHARACTER and the optional argument is really absent,
3889      append a dummy 0 as string length.  */
3890   append_args = NULL;
3891   if (prim_arg->expr->ts.type == BT_CHARACTER && !opt_arg->expr)
3892     {
3893       tree dummy;
3894
3895       dummy = build_int_cst (gfc_charlen_type_node, 0);
3896       append_args = VEC_alloc (tree, gc, 1);
3897       VEC_quick_push (tree, append_args, dummy);
3898     }
3899
3900   /* Build the call itself.  */
3901   sym = gfc_get_symbol_for_expr (expr);
3902   gfc_conv_procedure_call (se, sym, expr->value.function.actual, expr,
3903                           append_args);
3904   gfc_free (sym);
3905 }
3906
3907
3908 /* The length of a character string.  */
3909 static void
3910 gfc_conv_intrinsic_len (gfc_se * se, gfc_expr * expr)
3911 {
3912   tree len;
3913   tree type;
3914   tree decl;
3915   gfc_symbol *sym;
3916   gfc_se argse;
3917   gfc_expr *arg;
3918   gfc_ss *ss;
3919
3920   gcc_assert (!se->ss);
3921
3922   arg = expr->value.function.actual->expr;
3923
3924   type = gfc_typenode_for_spec (&expr->ts);
3925   switch (arg->expr_type)
3926     {
3927     case EXPR_CONSTANT:
3928       len = build_int_cst (NULL_TREE, arg->value.character.length);
3929       break;
3930
3931     case EXPR_ARRAY:
3932       /* Obtain the string length from the function used by
3933          trans-array.c(gfc_trans_array_constructor).  */
3934       len = NULL_TREE;
3935       get_array_ctor_strlen (&se->pre, arg->value.constructor, &len);
3936       break;
3937
3938     case EXPR_VARIABLE:
3939       if (arg->ref == NULL
3940             || (arg->ref->next == NULL && arg->ref->type == REF_ARRAY))
3941         {
3942           /* This doesn't catch all cases.
3943              See http://gcc.gnu.org/ml/fortran/2004-06/msg00165.html
3944              and the surrounding thread.  */
3945           sym = arg->symtree->n.sym;
3946           decl = gfc_get_symbol_decl (sym);
3947           if (decl == current_function_decl && sym->attr.function
3948                 && (sym->result == sym))
3949             decl = gfc_get_fake_result_decl (sym, 0);
3950
3951           len = sym->ts.u.cl->backend_decl;
3952           gcc_assert (len);
3953           break;
3954         }
3955
3956       /* Otherwise fall through.  */
3957
3958     default:
3959       /* Anybody stupid enough to do this deserves inefficient code.  */
3960       ss = gfc_walk_expr (arg);
3961       gfc_init_se (&argse, se);
3962       if (ss == gfc_ss_terminator)
3963         gfc_conv_expr (&argse, arg);
3964       else
3965         gfc_conv_expr_descriptor (&argse, arg, ss);
3966       gfc_add_block_to_block (&se->pre, &argse.pre);
3967       gfc_add_block_to_block (&se->post, &argse.post);
3968       len = argse.string_length;
3969       break;
3970     }
3971   se->expr = convert (type, len);
3972 }
3973
3974 /* The length of a character string not including trailing blanks.  */
3975 static void
3976 gfc_conv_intrinsic_len_trim (gfc_se * se, gfc_expr * expr)
3977 {
3978   int kind = expr->value.function.actual->expr->ts.kind;
3979   tree args[2], type, fndecl;
3980
3981   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3982   type = gfc_typenode_for_spec (&expr->ts);
3983
3984   if (kind == 1)
3985     fndecl = gfor_fndecl_string_len_trim;
3986   else if (kind == 4)
3987     fndecl = gfor_fndecl_string_len_trim_char4;
3988   else
3989     gcc_unreachable ();
3990
3991   se->expr = build_call_expr_loc (input_location,
3992                               fndecl, 2, args[0], args[1]);
3993   se->expr = convert (type, se->expr);
3994 }
3995
3996
3997 /* Returns the starting position of a substring within a string.  */
3998
3999 static void
4000 gfc_conv_intrinsic_index_scan_verify (gfc_se * se, gfc_expr * expr,
4001                                       tree function)
4002 {
4003   tree logical4_type_node = gfc_get_logical_type (4);
4004   tree type;
4005   tree fndecl;
4006   tree *args;
4007   unsigned int num_args;
4008
4009   args = XALLOCAVEC (tree, 5);
4010
4011   /* Get number of arguments; characters count double due to the
4012      string length argument. Kind= is not passed to the library
4013      and thus ignored.  */
4014   if (expr->value.function.actual->next->next->expr == NULL)
4015     num_args = 4;
4016   else
4017     num_args = 5;
4018
4019   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
4020   type = gfc_typenode_for_spec (&expr->ts);
4021
4022   if (num_args == 4)
4023     args[4] = build_int_cst (logical4_type_node, 0);
4024   else
4025     args[4] = convert (logical4_type_node, args[4]);
4026
4027   fndecl = build_addr (function, current_function_decl);
4028   se->expr = build_call_array_loc (input_location,
4029                                TREE_TYPE (TREE_TYPE (function)), fndecl,
4030                                5, args);
4031   se->expr = convert (type, se->expr);
4032
4033 }
4034
4035 /* The ascii value for a single character.  */
4036 static void
4037 gfc_conv_intrinsic_ichar (gfc_se * se, gfc_expr * expr)
4038 {
4039   tree args[2], type, pchartype;
4040
4041   gfc_conv_intrinsic_function_args (se, expr, args, 2);
4042   gcc_assert (POINTER_TYPE_P (TREE_TYPE (args[1])));
4043   pchartype = gfc_get_pchar_type (expr->value.function.actual->expr->ts.kind);
4044   args[1] = fold_build1_loc (input_location, NOP_EXPR, pchartype, args[1]);
4045   type = gfc_typenode_for_spec (&expr->ts);
4046
4047   se->expr = build_fold_indirect_ref_loc (input_location,
4048                                       args[1]);
4049   se->expr = convert (type, se->expr);
4050 }
4051
4052
4053 /* Intrinsic ISNAN calls __builtin_isnan.  */
4054
4055 static void
4056 gfc_conv_intrinsic_isnan (gfc_se * se, gfc_expr * expr)
4057 {
4058   tree arg;
4059
4060   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4061   se->expr = build_call_expr_loc (input_location,
4062                               built_in_decls[BUILT_IN_ISNAN], 1, arg);
4063   STRIP_TYPE_NOPS (se->expr);
4064   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), se->expr);
4065 }
4066
4067
4068 /* Intrinsics IS_IOSTAT_END and IS_IOSTAT_EOR just need to compare
4069    their argument against a constant integer value.  */
4070
4071 static void
4072 gfc_conv_has_intvalue (gfc_se * se, gfc_expr * expr, const int value)
4073 {
4074   tree arg;
4075
4076   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4077   se->expr = fold_build2_loc (input_location, EQ_EXPR,
4078                               gfc_typenode_for_spec (&expr->ts),
4079                               arg, build_int_cst (TREE_TYPE (arg), value));
4080 }
4081
4082
4083
4084 /* MERGE (tsource, fsource, mask) = mask ? tsource : fsource.  */
4085
4086 static void
4087 gfc_conv_intrinsic_merge (gfc_se * se, gfc_expr * expr)
4088 {
4089   tree tsource;
4090   tree fsource;
4091   tree mask;
4092   tree type;
4093   tree len, len2;
4094   tree *args;
4095   unsigned int num_args;
4096
4097   num_args = gfc_intrinsic_argument_list_length (expr);
4098   args = XALLOCAVEC (tree, num_args);
4099
4100   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
4101   if (expr->ts.type != BT_CHARACTER)
4102     {
4103       tsource = args[0];
4104       fsource = args[1];
4105       mask = args[2];
4106     }
4107   else
4108     {
4109       /* We do the same as in the non-character case, but the argument
4110          list is different because of the string length arguments. We
4111          also have to set the string length for the result.  */
4112       len = args[0];
4113       tsource = args[1];
4114       len2 = args[2];
4115       fsource = args[3];
4116       mask = args[4];
4117
4118       gfc_trans_same_strlen_check ("MERGE intrinsic", &expr->where, len, len2,
4119                                    &se->pre);
4120       se->string_length = len;
4121     }
4122   type = TREE_TYPE (tsource);
4123   se->expr = fold_build3_loc (input_location, COND_EXPR, type, mask, tsource,
4124                               fold_convert (type, fsource));
4125 }
4126
4127
4128 /* MERGE_BITS (I, J, MASK) = (I & MASK) | (I & (~MASK)).  */
4129
4130 static void
4131 gfc_conv_intrinsic_merge_bits (gfc_se * se, gfc_expr * expr)
4132 {
4133   tree args[3], mask, type;
4134
4135   gfc_conv_intrinsic_function_args (se, expr, args, 3);
4136   mask = gfc_evaluate_now (args[2], &se->pre);
4137
4138   type = TREE_TYPE (args[0]);
4139   gcc_assert (TREE_TYPE (args[1]) == type);
4140   gcc_assert (TREE_TYPE (mask) == type);
4141
4142   args[0] = fold_build2_loc (input_location, BIT_AND_EXPR, type, args[0], mask);
4143   args[1] = fold_build2_loc (input_location, BIT_AND_EXPR, type, args[1],
4144                              fold_build1_loc (input_location, BIT_NOT_EXPR,
4145                                               type, mask));
4146   se->expr = fold_build2_loc (input_location, BIT_IOR_EXPR, type,
4147                               args[0], args[1]);
4148 }
4149
4150
4151 /* MASKL(n)  =  n == 0 ? 0 : (~0) << (BIT_SIZE - n)
4152    MASKR(n)  =  n == BIT_SIZE ? ~0 : ~((~0) << n)  */
4153
4154 static void
4155 gfc_conv_intrinsic_mask (gfc_se * se, gfc_expr * expr, int left)
4156 {
4157   tree arg, allones, type, utype, res, cond, bitsize;
4158   int i;
4159  
4160   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4161   arg = gfc_evaluate_now (arg, &se->pre);
4162
4163   type = gfc_get_int_type (expr->ts.kind);
4164   utype = unsigned_type_for (type);
4165
4166   i = gfc_validate_kind (BT_INTEGER, expr->ts.kind, false);
4167   bitsize = build_int_cst (TREE_TYPE (arg), gfc_integer_kinds[i].bit_size);
4168
4169   allones = fold_build1_loc (input_location, BIT_NOT_EXPR, utype,
4170                              build_int_cst (utype, 0));
4171
4172   if (left)
4173     {
4174       /* Left-justified mask.  */
4175       res = fold_build2_loc (input_location, MINUS_EXPR, TREE_TYPE (arg),
4176                              bitsize, arg);
4177       res = fold_build2_loc (input_location, LSHIFT_EXPR, utype, allones,
4178                              fold_convert (utype, res));
4179
4180       /* Special case arg == 0, because SHIFT_EXPR wants a shift strictly
4181          smaller than type width.  */
4182       cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, arg,
4183                               build_int_cst (TREE_TYPE (arg), 0));
4184       res = fold_build3_loc (input_location, COND_EXPR, utype, cond,
4185                              build_int_cst (utype, 0), res);
4186     }
4187   else
4188     {
4189       /* Right-justified mask.  */
4190       res = fold_build2_loc (input_location, LSHIFT_EXPR, utype, allones,
4191                              fold_convert (utype, arg));
4192       res = fold_build1_loc (input_location, BIT_NOT_EXPR, utype, res);
4193
4194       /* Special case agr == bit_size, because SHIFT_EXPR wants a shift
4195          strictly smaller than type width.  */
4196       cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
4197                               arg, bitsize);
4198       res = fold_build3_loc (input_location, COND_EXPR, utype,
4199                              cond, allones, res);
4200     }
4201
4202   se->expr = fold_convert (type, res);
4203 }
4204
4205
4206 /* FRACTION (s) is translated into frexp (s, &dummy_int).  */
4207 static void
4208 gfc_conv_intrinsic_fraction (gfc_se * se, gfc_expr * expr)
4209 {
4210   tree arg, type, tmp, frexp;
4211
4212   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
4213
4214   type = gfc_typenode_for_spec (&expr->ts);
4215   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4216   tmp = gfc_create_var (integer_type_node, NULL);
4217   se->expr = build_call_expr_loc (input_location, frexp, 2,
4218                                   fold_convert (type, arg),
4219                                   gfc_build_addr_expr (NULL_TREE, tmp));
4220   se->expr = fold_convert (type, se->expr);
4221 }
4222
4223
4224 /* NEAREST (s, dir) is translated into
4225      tmp = copysign (HUGE_VAL, dir);
4226      return nextafter (s, tmp);
4227  */
4228 static void
4229 gfc_conv_intrinsic_nearest (gfc_se * se, gfc_expr * expr)
4230 {
4231   tree args[2], type, tmp, nextafter, copysign, huge_val;
4232
4233   nextafter = gfc_builtin_decl_for_float_kind (BUILT_IN_NEXTAFTER, expr->ts.kind);
4234   copysign = gfc_builtin_decl_for_float_kind (BUILT_IN_COPYSIGN, expr->ts.kind);
4235
4236   type = gfc_typenode_for_spec (&expr->ts);
4237   gfc_conv_intrinsic_function_args (se, expr, args, 2);
4238
4239   huge_val = gfc_build_inf_or_huge (type, expr->ts.kind);
4240   tmp = build_call_expr_loc (input_location, copysign, 2, huge_val,
4241                              fold_convert (type, args[1]));
4242   se->expr = build_call_expr_loc (input_location, nextafter, 2,
4243                                   fold_convert (type, args[0]), tmp);
4244   se->expr = fold_convert (type, se->expr);
4245 }
4246
4247
4248 /* SPACING (s) is translated into
4249     int e;
4250     if (s == 0)
4251       res = tiny;
4252     else
4253     {
4254       frexp (s, &e);
4255       e = e - prec;
4256       e = MAX_EXPR (e, emin);
4257       res = scalbn (1., e);
4258     }
4259     return res;
4260
4261  where prec is the precision of s, gfc_real_kinds[k].digits,
4262        emin is min_exponent - 1, gfc_real_kinds[k].min_exponent - 1,
4263    and tiny is tiny(s), gfc_real_kinds[k].tiny.  */
4264
4265 static void
4266 gfc_conv_intrinsic_spacing (gfc_se * se, gfc_expr * expr)
4267 {
4268   tree arg, type, prec, emin, tiny, res, e;
4269   tree cond, tmp, frexp, scalbn;
4270   int k;
4271   stmtblock_t block;
4272
4273   k = gfc_validate_kind (BT_REAL, expr->ts.kind, false);
4274   prec = build_int_cst (NULL_TREE, gfc_real_kinds[k].digits);
4275   emin = build_int_cst (NULL_TREE, gfc_real_kinds[k].min_exponent - 1);
4276   tiny = gfc_conv_mpfr_to_tree (gfc_real_kinds[k].tiny, expr->ts.kind, 0);
4277
4278   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
4279   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
4280
4281   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4282   arg = gfc_evaluate_now (arg, &se->pre);
4283
4284   type = gfc_typenode_for_spec (&expr->ts);
4285   e = gfc_create_var (integer_type_node, NULL);
4286   res = gfc_create_var (type, NULL);
4287
4288
4289   /* Build the block for s /= 0.  */
4290   gfc_start_block (&block);
4291   tmp = build_call_expr_loc (input_location, frexp, 2, arg,
4292                              gfc_build_addr_expr (NULL_TREE, e));
4293   gfc_add_expr_to_block (&block, tmp);
4294
4295   tmp = fold_build2_loc (input_location, MINUS_EXPR, integer_type_node, e,
4296                          prec);
4297   gfc_add_modify (&block, e, fold_build2_loc (input_location, MAX_EXPR,
4298                                               integer_type_node, tmp, emin));
4299
4300   tmp = build_call_expr_loc (input_location, scalbn, 2,
4301                          build_real_from_int_cst (type, integer_one_node), e);
4302   gfc_add_modify (&block, res, tmp);
4303
4304   /* Finish by building the IF statement.  */
4305   cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, arg,
4306                           build_real_from_int_cst (type, integer_zero_node));
4307   tmp = build3_v (COND_EXPR, cond, build2_v (MODIFY_EXPR, res, tiny),
4308                   gfc_finish_block (&block));
4309
4310   gfc_add_expr_to_block (&se->pre, tmp);
4311   se->expr = res;
4312 }
4313
4314
4315 /* RRSPACING (s) is translated into
4316       int e;
4317       real x;
4318       x = fabs (s);
4319       if (x != 0)
4320       {
4321         frexp (s, &e);
4322         x = scalbn (x, precision - e);
4323       }
4324       return x;
4325
4326  where precision is gfc_real_kinds[k].digits.  */
4327
4328 static void
4329 gfc_conv_intrinsic_rrspacing (gfc_se * se, gfc_expr * expr)
4330 {
4331   tree arg, type, e, x, cond, stmt, tmp, frexp, scalbn, fabs;
4332   int prec, k;
4333   stmtblock_t block;
4334
4335   k = gfc_validate_kind (BT_REAL, expr->ts.kind, false);
4336   prec = gfc_real_kinds[k].digits;
4337
4338   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
4339   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
4340   fabs = gfc_builtin_decl_for_float_kind (BUILT_IN_FABS, expr->ts.kind);
4341
4342   type = gfc_typenode_for_spec (&expr->ts);
4343   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4344   arg = gfc_evaluate_now (arg, &se->pre);
4345
4346   e = gfc_create_var (integer_type_node, NULL);
4347   x = gfc_create_var (type, NULL);
4348   gfc_add_modify (&se->pre, x,
4349                   build_call_expr_loc (input_location, fabs, 1, arg));
4350
4351
4352   gfc_start_block (&block);
4353   tmp = build_call_expr_loc (input_location, frexp, 2, arg,
4354                              gfc_build_addr_expr (NULL_TREE, e));
4355   gfc_add_expr_to_block (&block, tmp);
4356
4357   tmp = fold_build2_loc (input_location, MINUS_EXPR, integer_type_node,
4358                          build_int_cst (NULL_TREE, prec), e);
4359   tmp = build_call_expr_loc (input_location, scalbn, 2, x, tmp);
4360   gfc_add_modify (&block, x, tmp);
4361   stmt = gfc_finish_block (&block);
4362
4363   cond = fold_build2_loc (input_location, NE_EXPR, boolean_type_node, x,
4364                           build_real_from_int_cst (type, integer_zero_node));
4365   tmp = build3_v (COND_EXPR, cond, stmt, build_empty_stmt (input_location));
4366   gfc_add_expr_to_block (&se->pre, tmp);
4367
4368   se->expr = fold_convert (type, x);
4369 }
4370
4371
4372 /* SCALE (s, i) is translated into scalbn (s, i).  */
4373 static void
4374 gfc_conv_intrinsic_scale (gfc_se * se, gfc_expr * expr)
4375 {
4376   tree args[2], type, scalbn;
4377
4378   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
4379
4380   type = gfc_typenode_for_spec (&expr->ts);
4381   gfc_conv_intrinsic_function_args (se, expr, args, 2);
4382   se->expr = build_call_expr_loc (input_location, scalbn, 2,
4383                                   fold_convert (type, args[0]),
4384                                   fold_convert (integer_type_node, args[1]));
4385   se->expr = fold_convert (type, se->expr);
4386 }
4387
4388
4389 /* SET_EXPONENT (s, i) is translated into
4390    scalbn (frexp (s, &dummy_int), i).  */
4391 static void
4392 gfc_conv_intrinsic_set_exponent (gfc_se * se, gfc_expr * expr)
4393 {
4394   tree args[2], type, tmp, frexp, scalbn;
4395
4396   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
4397   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
4398
4399   type = gfc_typenode_for_spec (&expr->ts);
4400   gfc_conv_intrinsic_function_args (se, expr, args, 2);
4401
4402   tmp = gfc_create_var (integer_type_node, NULL);
4403   tmp = build_call_expr_loc (input_location, frexp, 2,
4404                              fold_convert (type, args[0]),
4405                              gfc_build_addr_expr (NULL_TREE, tmp));
4406   se->expr = build_call_expr_loc (input_location, scalbn, 2, tmp,
4407                                   fold_convert (integer_type_node, args[1]));
4408   se->expr = fold_convert (type, se->expr);
4409 }
4410
4411
4412 static void
4413 gfc_conv_intrinsic_size (gfc_se * se, gfc_expr * expr)
4414 {
4415   gfc_actual_arglist *actual;
4416   tree arg1;
4417   tree type;
4418   tree fncall0;
4419   tree fncall1;
4420   gfc_se argse;
4421   gfc_ss *ss;
4422
4423   gfc_init_se (&argse, NULL);
4424   actual = expr->value.function.actual;
4425
4426   ss = gfc_walk_expr (actual->expr);
4427   gcc_assert (ss != gfc_ss_terminator);
4428   argse.want_pointer = 1;
4429   argse.data_not_needed = 1;
4430   gfc_conv_expr_descriptor (&argse, actual->expr, ss);
4431   gfc_add_block_to_block (&se->pre, &argse.pre);
4432   gfc_add_block_to_block (&se->post, &argse.post);
4433   arg1 = gfc_evaluate_now (argse.expr, &se->pre);
4434
4435   /* Build the call to size0.  */
4436   fncall0 = build_call_expr_loc (input_location,
4437                              gfor_fndecl_size0, 1, arg1);
4438
4439   actual = actual->next;
4440
4441   if (actual->expr)
4442     {
4443       gfc_init_se (&argse, NULL);
4444       gfc_conv_expr_type (&argse, actual->expr,
4445                           gfc_array_index_type);
4446       gfc_add_block_to_block (&se->pre, &argse.pre);
4447
4448       /* Unusually, for an intrinsic, size does not exclude
4449          an optional arg2, so we must test for it.  */  
4450       if (actual->expr->expr_type == EXPR_VARIABLE
4451             && actual->expr->symtree->n.sym->attr.dummy
4452             && actual->expr->symtree->n.sym->attr.optional)
4453         {
4454           tree tmp;
4455           /* Build the call to size1.  */
4456           fncall1 = build_call_expr_loc (input_location,
4457                                      gfor_fndecl_size1, 2,
4458                                      arg1, argse.expr);
4459
4460           gfc_init_se (&argse, NULL);
4461           argse.want_pointer = 1;
4462           argse.data_not_needed = 1;
4463           gfc_conv_expr (&argse, actual->expr);
4464           gfc_add_block_to_block (&se->pre, &argse.pre);
4465           tmp = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
4466                                  argse.expr, null_pointer_node);
4467           tmp = gfc_evaluate_now (tmp, &se->pre);
4468           se->expr = fold_build3_loc (input_location, COND_EXPR,
4469                                       pvoid_type_node, tmp, fncall1, fncall0);
4470         }
4471       else
4472         {
4473           se->expr = NULL_TREE;
4474           argse.expr = fold_build2_loc (input_location, MINUS_EXPR,
4475                                         gfc_array_index_type,
4476                                         argse.expr, gfc_index_one_node);
4477         }
4478     }
4479   else if (expr->value.function.actual->expr->rank == 1)
4480     {
4481       argse.expr = gfc_index_zero_node;
4482       se->expr = NULL_TREE;
4483     }
4484   else
4485     se->expr = fncall0;
4486
4487   if (se->expr == NULL_TREE)
4488     {
4489       tree ubound, lbound;
4490
4491       arg1 = build_fold_indirect_ref_loc (input_location,
4492                                       arg1);
4493       ubound = gfc_conv_descriptor_ubound_get (arg1, argse.expr);
4494       lbound = gfc_conv_descriptor_lbound_get (arg1, argse.expr);
4495       se->expr = fold_build2_loc (input_location, MINUS_EXPR,
4496                                   gfc_array_index_type, ubound, lbound);
4497       se->expr = fold_build2_loc (input_location, PLUS_EXPR,
4498                                   gfc_array_index_type,
4499                                   se->expr, gfc_index_one_node);
4500       se->expr = fold_build2_loc (input_location, MAX_EXPR,
4501                                   gfc_array_index_type, se->expr,
4502                                   gfc_index_zero_node);
4503     }
4504
4505   type = gfc_typenode_for_spec (&expr->ts);
4506   se->expr = convert (type, se->expr);
4507 }
4508
4509
4510 /* Helper function to compute the size of a character variable,
4511    excluding the terminating null characters.  The result has
4512    gfc_array_index_type type.  */
4513
4514 static tree
4515 size_of_string_in_bytes (int kind, tree string_length)
4516 {
4517   tree bytesize;
4518   int i = gfc_validate_kind (BT_CHARACTER, kind, false);
4519  
4520   bytesize = build_int_cst (gfc_array_index_type,
4521                             gfc_character_kinds[i].bit_size / 8);
4522
4523   return fold_build2_loc (input_location, MULT_EXPR, gfc_array_index_type,
4524                           bytesize,
4525                           fold_convert (gfc_array_index_type, string_length));
4526 }
4527
4528
4529 static void
4530 gfc_conv_intrinsic_sizeof (gfc_se *se, gfc_expr *expr)
4531 {
4532   gfc_expr *arg;
4533   gfc_ss *ss;
4534   gfc_se argse;
4535   tree source_bytes;
4536   tree type;
4537   tree tmp;
4538   tree lower;
4539   tree upper;
4540   int n;
4541
4542   arg = expr->value.function.actual->expr;
4543
4544   gfc_init_se (&argse, NULL);
4545   ss = gfc_walk_expr (arg);
4546
4547   if (ss == gfc_ss_terminator)
4548     {
4549       if (arg->ts.type == BT_CLASS)
4550         gfc_add_component_ref (arg, "$data");
4551
4552       gfc_conv_expr_reference (&argse, arg);
4553
4554       type = TREE_TYPE (build_fold_indirect_ref_loc (input_location,
4555                                                  argse.expr));
4556
4557       /* Obtain the source word length.  */
4558       if (arg->ts.type == BT_CHARACTER)
4559         se->expr = size_of_string_in_bytes (arg->ts.kind,
4560                                             argse.string_length);
4561       else
4562         se->expr = fold_convert (gfc_array_index_type, size_in_bytes (type)); 
4563     }
4564   else
4565     {
4566       source_bytes = gfc_create_var (gfc_array_index_type, "bytes");
4567       argse.want_pointer = 0;
4568       gfc_conv_expr_descriptor (&argse, arg, ss);
4569       type = gfc_get_element_type (TREE_TYPE (argse.expr));
4570
4571       /* Obtain the argument's word length.  */
4572       if (arg->ts.type == BT_CHARACTER)
4573         tmp = size_of_string_in_bytes (arg->ts.kind, argse.string_length);
4574       else
4575         tmp = fold_convert (gfc_array_index_type,
4576                             size_in_bytes (type)); 
4577       gfc_add_modify (&argse.pre, source_bytes, tmp);
4578
4579       /* Obtain the size of the array in bytes.  */
4580       for (n = 0; n < arg->rank; n++)
4581         {
4582           tree idx;
4583           idx = gfc_rank_cst[n];
4584           lower = gfc_conv_descriptor_lbound_get (argse.expr, idx);
4585           upper = gfc_conv_descriptor_ubound_get (argse.expr, idx);
4586           tmp = fold_build2_loc (input_location, MINUS_EXPR,
4587                                  gfc_array_index_type, upper, lower);
4588           tmp = fold_build2_loc (input_location, PLUS_EXPR,
4589                                  gfc_array_index_type, tmp, gfc_index_one_node);
4590           tmp = fold_build2_loc (input_location, MULT_EXPR,
4591                                  gfc_array_index_type, tmp, source_bytes);
4592           gfc_add_modify (&argse.pre, source_bytes, tmp);
4593         }
4594       se->expr = source_bytes;
4595     }
4596
4597   gfc_add_block_to_block (&se->pre, &argse.pre);
4598 }
4599
4600
4601 static void
4602 gfc_conv_intrinsic_storage_size (gfc_se *se, gfc_expr *expr)
4603 {
4604   gfc_expr *arg;
4605   gfc_ss *ss;
4606   gfc_se argse,eight;
4607   tree type, result_type, tmp;
4608
4609   arg = expr->value.function.actual->expr;
4610   gfc_init_se (&eight, NULL);
4611   gfc_conv_expr (&eight, gfc_get_int_expr (expr->ts.kind, NULL, 8));
4612   
4613   gfc_init_se (&argse, NULL);
4614   ss = gfc_walk_expr (arg);
4615   result_type = gfc_get_int_type (expr->ts.kind);
4616
4617   if (ss == gfc_ss_terminator)
4618     {
4619       if (arg->ts.type == BT_CLASS)
4620       {
4621         gfc_add_component_ref (arg, "$vptr");
4622         gfc_add_component_ref (arg, "$size");
4623         gfc_conv_expr (&argse, arg);
4624         tmp = fold_convert (result_type, argse.expr);
4625         goto done;
4626       }
4627
4628       gfc_conv_expr_reference (&argse, arg);
4629       type = TREE_TYPE (build_fold_indirect_ref_loc (input_location, 
4630                                                      argse.expr));
4631     }
4632   else
4633     {
4634       argse.want_pointer = 0;
4635       gfc_conv_expr_descriptor (&argse, arg, ss);
4636       type = gfc_get_element_type (TREE_TYPE (argse.expr));
4637     }
4638     
4639   /* Obtain the argument's word length.  */
4640   if (arg->ts.type == BT_CHARACTER)
4641     tmp = size_of_string_in_bytes (arg->ts.kind, argse.string_length);
4642   else
4643     tmp = fold_convert (result_type, size_in_bytes (type)); 
4644
4645 done:
4646   se->expr = fold_build2_loc (input_location, MULT_EXPR, result_type, tmp,
4647                               eight.expr);
4648   gfc_add_block_to_block (&se->pre, &argse.pre);
4649 }
4650
4651
4652 /* Intrinsic string comparison functions.  */
4653
4654 static void
4655 gfc_conv_intrinsic_strcmp (gfc_se * se, gfc_expr * expr, enum tree_code op)
4656 {
4657   tree args[4];
4658
4659   gfc_conv_intrinsic_function_args (se, expr, args, 4);
4660
4661   se->expr
4662     = gfc_build_compare_string (args[0], args[1], args[2], args[3],
4663                                 expr->value.function.actual->expr->ts.kind,
4664                                 op);
4665   se->expr = fold_build2_loc (input_location, op,
4666                               gfc_typenode_for_spec (&expr->ts), se->expr,
4667                               build_int_cst (TREE_TYPE (se->expr), 0));
4668 }
4669
4670 /* Generate a call to the adjustl/adjustr library function.  */
4671 static void
4672 gfc_conv_intrinsic_adjust (gfc_se * se, gfc_expr * expr, tree fndecl)
4673 {
4674   tree args[3];
4675   tree len;
4676   tree type;
4677   tree var;
4678   tree tmp;
4679
4680   gfc_conv_intrinsic_function_args (se, expr, &args[1], 2);
4681   len = args[1];
4682
4683   type = TREE_TYPE (args[2]);
4684   var = gfc_conv_string_tmp (se, type, len);
4685   args[0] = var;
4686
4687   tmp = build_call_expr_loc (input_location,
4688                          fndecl, 3, args[0], args[1], args[2]);
4689   gfc_add_expr_to_block (&se->pre, tmp);
4690   se->expr = var;
4691   se->string_length = len;
4692 }
4693
4694
4695 /* Generate code for the TRANSFER intrinsic:
4696         For scalar results:
4697           DEST = TRANSFER (SOURCE, MOLD)
4698         where:
4699           typeof<DEST> = typeof<MOLD>
4700         and:
4701           MOLD is scalar.
4702
4703         For array results:
4704           DEST(1:N) = TRANSFER (SOURCE, MOLD[, SIZE])
4705         where:
4706           typeof<DEST> = typeof<MOLD>
4707         and:
4708           N = min (sizeof (SOURCE(:)), sizeof (DEST(:)),
4709               sizeof (DEST(0) * SIZE).  */
4710 static void
4711 gfc_conv_intrinsic_transfer (gfc_se * se, gfc_expr * expr)
4712 {
4713   tree tmp;
4714   tree tmpdecl;
4715   tree ptr;
4716   tree extent;
4717   tree source;
4718   tree source_type;
4719   tree source_bytes;
4720   tree mold_type;
4721   tree dest_word_len;
4722   tree size_words;
4723   tree size_bytes;
4724   tree upper;
4725   tree lower;
4726   tree stmt;
4727   gfc_actual_arglist *arg;
4728   gfc_se argse;
4729   gfc_ss *ss;
4730   gfc_ss_info *info;
4731   stmtblock_t block;
4732   int n;
4733   bool scalar_mold;
4734
4735   info = NULL;
4736   if (se->loop)
4737     info = &se->ss->data.info;
4738
4739   /* Convert SOURCE.  The output from this stage is:-
4740         source_bytes = length of the source in bytes
4741         source = pointer to the source data.  */
4742   arg = expr->value.function.actual;
4743
4744   /* Ensure double transfer through LOGICAL preserves all
4745      the needed bits.  */
4746   if (arg->expr->expr_type == EXPR_FUNCTION
4747         && arg->expr->value.function.esym == NULL
4748         && arg->expr->value.function.isym != NULL
4749         && arg->expr->value.function.isym->id == GFC_ISYM_TRANSFER
4750         && arg->expr->ts.type == BT_LOGICAL
4751         && expr->ts.type != arg->expr->ts.type)
4752     arg->expr->value.function.name = "__transfer_in_transfer";
4753
4754   gfc_init_se (&argse, NULL);
4755   ss = gfc_walk_expr (arg->expr);
4756
4757   source_bytes = gfc_create_var (gfc_array_index_type, NULL);
4758
4759   /* Obtain the pointer to source and the length of source in bytes.  */
4760   if (ss == gfc_ss_terminator)
4761     {
4762       gfc_conv_expr_reference (&argse, arg->expr);
4763       source = argse.expr;
4764
4765       source_type = TREE_TYPE (build_fold_indirect_ref_loc (input_location,
4766                                                         argse.expr));
4767
4768       /* Obtain the source word length.  */
4769       if (arg->expr->ts.type == BT_CHARACTER)
4770         tmp = size_of_string_in_bytes (arg->expr->ts.kind,
4771                                        argse.string_length);
4772       else
4773         tmp = fold_convert (gfc_array_index_type,
4774                             size_in_bytes (source_type)); 
4775     }
4776   else
4777     {
4778       argse.want_pointer = 0;
4779       gfc_conv_expr_descriptor (&argse, arg->expr, ss);
4780       source = gfc_conv_descriptor_data_get (argse.expr);
4781       source_type = gfc_get_element_type (TREE_TYPE (argse.expr));
4782
4783       /* Repack the source if not a full variable array.  */
4784       if (arg->expr->expr_type == EXPR_VARIABLE
4785               && arg->expr->ref->u.ar.type != AR_FULL)
4786         {
4787           tmp = gfc_build_addr_expr (NULL_TREE, argse.expr);
4788
4789           if (gfc_option.warn_array_temp)
4790             gfc_warning ("Creating array temporary at %L", &expr->where);
4791
4792           source = build_call_expr_loc (input_location,
4793                                     gfor_fndecl_in_pack, 1, tmp);
4794           source = gfc_evaluate_now (source, &argse.pre);
4795
4796           /* Free the temporary.  */
4797           gfc_start_block (&block);
4798           tmp = gfc_call_free (convert (pvoid_type_node, source));
4799           gfc_add_expr_to_block (&block, tmp);
4800           stmt = gfc_finish_block (&block);
4801
4802           /* Clean up if it was repacked.  */
4803           gfc_init_block (&block);
4804           tmp = gfc_conv_array_data (argse.expr);
4805           tmp = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
4806                                  source, tmp);
4807           tmp = build3_v (COND_EXPR, tmp, stmt,
4808                           build_empty_stmt (input_location));
4809           gfc_add_expr_to_block (&block, tmp);
4810           gfc_add_block_to_block (&block, &se->post);
4811           gfc_init_block (&se->post);
4812           gfc_add_block_to_block (&se->post, &block);
4813         }
4814
4815       /* Obtain the source word length.  */
4816       if (arg->expr->ts.type == BT_CHARACTER)
4817         tmp = size_of_string_in_bytes (arg->expr->ts.kind,
4818                                        argse.string_length);
4819       else
4820         tmp = fold_convert (gfc_array_index_type,
4821                             size_in_bytes (source_type)); 
4822
4823       /* Obtain the size of the array in bytes.  */
4824       extent = gfc_create_var (gfc_array_index_type, NULL);
4825       for (n = 0; n < arg->expr->rank; n++)
4826         {
4827           tree idx;
4828           idx = gfc_rank_cst[n];
4829           gfc_add_modify (&argse.pre, source_bytes, tmp);
4830           lower = gfc_conv_descriptor_lbound_get (argse.expr, idx);
4831           upper = gfc_conv_descriptor_ubound_get (argse.expr, idx);
4832           tmp = fold_build2_loc (input_location, MINUS_EXPR,
4833                                  gfc_array_index_type, upper, lower);
4834           gfc_add_modify (&argse.pre, extent, tmp);
4835           tmp = fold_build2_loc (input_location, PLUS_EXPR,
4836                                  gfc_array_index_type, extent,
4837                                  gfc_index_one_node);
4838           tmp = fold_build2_loc (input_location, MULT_EXPR,
4839                                  gfc_array_index_type, tmp, source_bytes);
4840         }
4841     }
4842
4843   gfc_add_modify (&argse.pre, source_bytes, tmp);
4844   gfc_add_block_to_block (&se->pre, &argse.pre);
4845   gfc_add_block_to_block (&se->post, &argse.post);
4846
4847   /* Now convert MOLD.  The outputs are:
4848         mold_type = the TREE type of MOLD
4849         dest_word_len = destination word length in bytes.  */
4850   arg = arg->next;
4851
4852   gfc_init_se (&argse, NULL);
4853   ss = gfc_walk_expr (arg->expr);
4854
4855   scalar_mold = arg->expr->rank == 0;
4856
4857   if (ss == gfc_ss_terminator)
4858     {
4859       gfc_conv_expr_reference (&argse, arg->expr);
4860       mold_type = TREE_TYPE (build_fold_indirect_ref_loc (input_location,
4861                                                       argse.expr));
4862     }
4863   else
4864     {
4865       gfc_init_se (&argse, NULL);
4866       argse.want_pointer = 0;
4867       gfc_conv_expr_descriptor (&argse, arg->expr, ss);
4868       mold_type = gfc_get_element_type (TREE_TYPE (argse.expr));
4869     }
4870
4871   gfc_add_block_to_block (&se->pre, &argse.pre);
4872   gfc_add_block_to_block (&se->post, &argse.post);
4873
4874   if (strcmp (expr->value.function.name, "__transfer_in_transfer") == 0)
4875     {
4876       /* If this TRANSFER is nested in another TRANSFER, use a type
4877          that preserves all bits.  */
4878       if (arg->expr->ts.type == BT_LOGICAL)
4879         mold_type = gfc_get_int_type (arg->expr->ts.kind);
4880     }
4881
4882   if (arg->expr->ts.type == BT_CHARACTER)
4883     {
4884       tmp = size_of_string_in_bytes (arg->expr->ts.kind, argse.string_length);
4885       mold_type = gfc_get_character_type_len (arg->expr->ts.kind, tmp);
4886     }
4887   else
4888     tmp = fold_convert (gfc_array_index_type,
4889                         size_in_bytes (mold_type)); 
4890  
4891   dest_word_len = gfc_create_var (gfc_array_index_type, NULL);
4892   gfc_add_modify (&se->pre, dest_word_len, tmp);
4893
4894   /* Finally convert SIZE, if it is present.  */
4895   arg = arg->next;
4896   size_words = gfc_create_var (gfc_array_index_type, NULL);
4897
4898   if (arg->expr)
4899     {
4900       gfc_init_se (&argse, NULL);
4901       gfc_conv_expr_reference (&argse, arg->expr);
4902       tmp = convert (gfc_array_index_type,
4903                      build_fold_indirect_ref_loc (input_location,
4904                                               argse.expr));
4905       gfc_add_block_to_block (&se->pre, &argse.pre);
4906       gfc_add_block_to_block (&se->post, &argse.post);
4907     }
4908   else
4909     tmp = NULL_TREE;
4910
4911   /* Separate array and scalar results.  */
4912   if (scalar_mold && tmp == NULL_TREE)
4913     goto scalar_transfer;
4914
4915   size_bytes = gfc_create_var (gfc_array_index_type, NULL);
4916   if (tmp != NULL_TREE)
4917     tmp = fold_build2_loc (input_location, MULT_EXPR, gfc_array_index_type,
4918                            tmp, dest_word_len);
4919   else
4920     tmp = source_bytes;
4921
4922   gfc_add_modify (&se->pre, size_bytes, tmp);
4923   gfc_add_modify (&se->pre, size_words,
4924                        fold_build2_loc (input_location, CEIL_DIV_EXPR,
4925                                         gfc_array_index_type,
4926                                         size_bytes, dest_word_len));
4927
4928   /* Evaluate the bounds of the result.  If the loop range exists, we have
4929      to check if it is too large.  If so, we modify loop->to be consistent
4930      with min(size, size(source)).  Otherwise, size is made consistent with
4931      the loop range, so that the right number of bytes is transferred.*/
4932   n = se->loop->order[0];
4933   if (se->loop->to[n] != NULL_TREE)
4934     {
4935       tmp = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
4936                              se->loop->to[n], se->loop->from[n]);
4937       tmp = fold_build2_loc (input_location, PLUS_EXPR, gfc_array_index_type,
4938                              tmp, gfc_index_one_node);
4939       tmp = fold_build2_loc (input_location, MIN_EXPR, gfc_array_index_type,
4940                          tmp, size_words);
4941       gfc_add_modify (&se->pre, size_words, tmp);
4942       gfc_add_modify (&se->pre, size_bytes,
4943                            fold_build2_loc (input_location, MULT_EXPR,
4944                                             gfc_array_index_type,
4945                                             size_words, dest_word_len));
4946       upper = fold_build2_loc (input_location, PLUS_EXPR, gfc_array_index_type,
4947                                size_words, se->loop->from[n]);
4948       upper = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
4949                                upper, gfc_index_one_node);
4950     }
4951   else
4952     {
4953       upper = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
4954                                size_words, gfc_index_one_node);
4955       se->loop->from[n] = gfc_index_zero_node;
4956     }
4957
4958   se->loop->to[n] = upper;
4959
4960   /* Build a destination descriptor, using the pointer, source, as the
4961      data field.  */
4962   gfc_trans_create_temp_array (&se->pre, &se->post, se->loop,
4963                                info, mold_type, NULL_TREE, false, true, false,
4964                                &expr->where);
4965
4966   /* Cast the pointer to the result.  */
4967   tmp = gfc_conv_descriptor_data_get (info->descriptor);
4968   tmp = fold_convert (pvoid_type_node, tmp);
4969
4970   /* Use memcpy to do the transfer.  */
4971   tmp = build_call_expr_loc (input_location,
4972                          built_in_decls[BUILT_IN_MEMCPY],
4973                          3,
4974                          tmp,
4975                          fold_convert (pvoid_type_node, source),
4976                          fold_build2_loc (input_location, MIN_EXPR,
4977                                           gfc_array_index_type,
4978                                           size_bytes, source_bytes));
4979   gfc_add_expr_to_block (&se->pre, tmp);
4980
4981   se->expr = info->descriptor;
4982   if (expr->ts.type == BT_CHARACTER)
4983     se->string_length = fold_convert (gfc_charlen_type_node, dest_word_len);
4984
4985   return;
4986
4987 /* Deal with scalar results.  */
4988 scalar_transfer:
4989   extent = fold_build2_loc (input_location, MIN_EXPR, gfc_array_index_type,
4990                             dest_word_len, source_bytes);
4991   extent = fold_build2_loc (input_location, MAX_EXPR, gfc_array_index_type,
4992                             extent, gfc_index_zero_node);
4993
4994   if (expr->ts.type == BT_CHARACTER)
4995     {
4996       tree direct;
4997       tree indirect;
4998
4999       ptr = convert (gfc_get_pchar_type (expr->ts.kind), source);
5000       tmpdecl = gfc_create_var (gfc_get_pchar_type (expr->ts.kind),
5001                                 "transfer");
5002
5003       /* If source is longer than the destination, use a pointer to
5004          the source directly.  */
5005       gfc_init_block (&block);
5006       gfc_add_modify (&block, tmpdecl, ptr);
5007       direct = gfc_finish_block (&block);
5008
5009       /* Otherwise, allocate a string with the length of the destination
5010          and copy the source into it.  */
5011       gfc_init_block (&block);
5012       tmp = gfc_get_pchar_type (expr->ts.kind);
5013       tmp = gfc_call_malloc (&block, tmp, dest_word_len);
5014       gfc_add_modify (&block, tmpdecl,
5015                       fold_convert (TREE_TYPE (ptr), tmp));
5016       tmp = build_call_expr_loc (input_location,
5017                              built_in_decls[BUILT_IN_MEMCPY], 3,
5018                              fold_convert (pvoid_type_node, tmpdecl),
5019                              fold_convert (pvoid_type_node, ptr),
5020                              extent);
5021       gfc_add_expr_to_block (&block, tmp);
5022       indirect = gfc_finish_block (&block);
5023
5024       /* Wrap it up with the condition.  */
5025       tmp = fold_build2_loc (input_location, LE_EXPR, boolean_type_node,
5026                              dest_word_len, source_bytes);
5027       tmp = build3_v (COND_EXPR, tmp, direct, indirect);
5028       gfc_add_expr_to_block (&se->pre, tmp);
5029
5030       se->expr = tmpdecl;
5031       se->string_length = dest_word_len;
5032     }
5033   else
5034     {
5035       tmpdecl = gfc_create_var (mold_type, "transfer");
5036
5037       ptr = convert (build_pointer_type (mold_type), source);
5038
5039       /* Use memcpy to do the transfer.  */
5040       tmp = gfc_build_addr_expr (NULL_TREE, tmpdecl);
5041       tmp = build_call_expr_loc (input_location,
5042                              built_in_decls[BUILT_IN_MEMCPY], 3,
5043                              fold_convert (pvoid_type_node, tmp),
5044                              fold_convert (pvoid_type_node, ptr),
5045                              extent);
5046       gfc_add_expr_to_block (&se->pre, tmp);
5047
5048       se->expr = tmpdecl;
5049     }
5050 }
5051
5052
5053 /* Generate code for the ALLOCATED intrinsic.
5054    Generate inline code that directly check the address of the argument.  */
5055
5056 static void
5057 gfc_conv_allocated (gfc_se *se, gfc_expr *expr)
5058 {
5059   gfc_actual_arglist *arg1;
5060   gfc_se arg1se;
5061   gfc_ss *ss1;
5062   tree tmp;
5063
5064   gfc_init_se (&arg1se, NULL);
5065   arg1 = expr->value.function.actual;
5066   ss1 = gfc_walk_expr (arg1->expr);
5067
5068   if (ss1 == gfc_ss_terminator)
5069     {
5070       /* Allocatable scalar.  */
5071       arg1se.want_pointer = 1;
5072       if (arg1->expr->ts.type == BT_CLASS)
5073         gfc_add_component_ref (arg1->expr, "$data");
5074       gfc_conv_expr (&arg1se, arg1->expr);
5075       tmp = arg1se.expr;
5076     }
5077   else
5078     {
5079       /* Allocatable array.  */
5080       arg1se.descriptor_only = 1;
5081       gfc_conv_expr_descriptor (&arg1se, arg1->expr, ss1);
5082       tmp = gfc_conv_descriptor_data_get (arg1se.expr);
5083     }
5084
5085   tmp = fold_build2_loc (input_location, NE_EXPR, boolean_type_node, tmp,
5086                          fold_convert (TREE_TYPE (tmp), null_pointer_node));
5087   se->expr = convert (gfc_typenode_for_spec (&expr->ts), tmp);
5088 }
5089
5090
5091 /* Generate code for the ASSOCIATED intrinsic.
5092    If both POINTER and TARGET are arrays, generate a call to library function
5093    _gfor_associated, and pass descriptors of POINTER and TARGET to it.
5094    In other cases, generate inline code that directly compare the address of
5095    POINTER with the address of TARGET.  */
5096
5097 static void
5098 gfc_conv_associated (gfc_se *se, gfc_expr *expr)
5099 {
5100   gfc_actual_arglist *arg1;
5101   gfc_actual_arglist *arg2;
5102   gfc_se arg1se;
5103   gfc_se arg2se;
5104   tree tmp2;
5105   tree tmp;
5106   tree nonzero_charlen;
5107   tree nonzero_arraylen;
5108   gfc_ss *ss1, *ss2;
5109
5110   gfc_init_se (&arg1se, NULL);
5111   gfc_init_se (&arg2se, NULL);
5112   arg1 = expr->value.function.actual;
5113   if (arg1->expr->ts.type == BT_CLASS)
5114     gfc_add_component_ref (arg1->expr, "$data");
5115   arg2 = arg1->next;
5116   ss1 = gfc_walk_expr (arg1->expr);
5117
5118   if (!arg2->expr)
5119     {
5120       /* No optional target.  */
5121       if (ss1 == gfc_ss_terminator)
5122         {
5123           /* A pointer to a scalar.  */
5124           arg1se.want_pointer = 1;
5125           gfc_conv_expr (&arg1se, arg1->expr);
5126           tmp2 = arg1se.expr;
5127         }
5128       else
5129         {
5130           /* A pointer to an array.  */
5131           gfc_conv_expr_descriptor (&arg1se, arg1->expr, ss1);
5132           tmp2 = gfc_conv_descriptor_data_get (arg1se.expr);
5133         }
5134       gfc_add_block_to_block (&se->pre, &arg1se.pre);
5135       gfc_add_block_to_block (&se->post, &arg1se.post);
5136       tmp = fold_build2_loc (input_location, NE_EXPR, boolean_type_node, tmp2,
5137                              fold_convert (TREE_TYPE (tmp2), null_pointer_node));
5138       se->expr = tmp;
5139     }
5140   else
5141     {
5142       /* An optional target.  */
5143       if (arg2->expr->ts.type == BT_CLASS)
5144         gfc_add_component_ref (arg2->expr, "$data");
5145       ss2 = gfc_walk_expr (arg2->expr);
5146
5147       nonzero_charlen = NULL_TREE;
5148       if (arg1->expr->ts.type == BT_CHARACTER)
5149         nonzero_charlen = fold_build2_loc (input_location, NE_EXPR,
5150                                            boolean_type_node,
5151                                            arg1->expr->ts.u.cl->backend_decl,
5152                                            integer_zero_node);
5153
5154       if (ss1 == gfc_ss_terminator)
5155         {
5156           /* A pointer to a scalar.  */
5157           gcc_assert (ss2 == gfc_ss_terminator);
5158           arg1se.want_pointer = 1;
5159           gfc_conv_expr (&arg1se, arg1->expr);
5160           arg2se.want_pointer = 1;
5161           gfc_conv_expr (&arg2se, arg2->expr);
5162           gfc_add_block_to_block (&se->pre, &arg1se.pre);
5163           gfc_add_block_to_block (&se->post, &arg1se.post);
5164           tmp = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
5165                                  arg1se.expr, arg2se.expr);
5166           tmp2 = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
5167                                   arg1se.expr, null_pointer_node);
5168           se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
5169                                       boolean_type_node, tmp, tmp2);
5170         }
5171       else
5172         {
5173           /* An array pointer of zero length is not associated if target is
5174              present.  */
5175           arg1se.descriptor_only = 1;
5176           gfc_conv_expr_lhs (&arg1se, arg1->expr);
5177           tmp = gfc_conv_descriptor_stride_get (arg1se.expr,
5178                                             gfc_rank_cst[arg1->expr->rank - 1]);
5179           nonzero_arraylen = fold_build2_loc (input_location, NE_EXPR,
5180                                               boolean_type_node, tmp,
5181                                               build_int_cst (TREE_TYPE (tmp), 0));
5182
5183           /* A pointer to an array, call library function _gfor_associated.  */
5184           gcc_assert (ss2 != gfc_ss_terminator);
5185           arg1se.want_pointer = 1;
5186           gfc_conv_expr_descriptor (&arg1se, arg1->expr, ss1);
5187
5188           arg2se.want_pointer = 1;
5189           gfc_conv_expr_descriptor (&arg2se, arg2->expr, ss2);
5190           gfc_add_block_to_block (&se->pre, &arg2se.pre);
5191           gfc_add_block_to_block (&se->post, &arg2se.post);
5192           se->expr = build_call_expr_loc (input_location,
5193                                       gfor_fndecl_associated, 2,
5194                                       arg1se.expr, arg2se.expr);
5195           se->expr = convert (boolean_type_node, se->expr);
5196           se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
5197                                       boolean_type_node, se->expr,
5198                                       nonzero_arraylen);
5199         }
5200
5201       /* If target is present zero character length pointers cannot
5202          be associated.  */
5203       if (nonzero_charlen != NULL_TREE)
5204         se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
5205                                     boolean_type_node,
5206                                     se->expr, nonzero_charlen);
5207     }
5208
5209   se->expr = convert (gfc_typenode_for_spec (&expr->ts), se->expr);
5210 }
5211
5212
5213 /* Generate code for the SAME_TYPE_AS intrinsic.
5214    Generate inline code that directly checks the vindices.  */
5215
5216 static void
5217 gfc_conv_same_type_as (gfc_se *se, gfc_expr *expr)
5218 {
5219   gfc_expr *a, *b;
5220   gfc_se se1, se2;
5221   tree tmp;
5222
5223   gfc_init_se (&se1, NULL);
5224   gfc_init_se (&se2, NULL);
5225
5226   a = expr->value.function.actual->expr;
5227   b = expr->value.function.actual->next->expr;
5228
5229   if (a->ts.type == BT_CLASS)
5230     {
5231       gfc_add_component_ref (a, "$vptr");
5232       gfc_add_component_ref (a, "$hash");
5233     }
5234   else if (a->ts.type == BT_DERIVED)
5235     a = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5236                           a->ts.u.derived->hash_value);
5237
5238   if (b->ts.type == BT_CLASS)
5239     {
5240       gfc_add_component_ref (b, "$vptr");
5241       gfc_add_component_ref (b, "$hash");
5242     }
5243   else if (b->ts.type == BT_DERIVED)
5244     b = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5245                           b->ts.u.derived->hash_value);
5246
5247   gfc_conv_expr (&se1, a);
5248   gfc_conv_expr (&se2, b);
5249
5250   tmp = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
5251                          se1.expr, fold_convert (TREE_TYPE (se1.expr), se2.expr));
5252   se->expr = convert (gfc_typenode_for_spec (&expr->ts), tmp);
5253 }
5254
5255
5256 /* Generate code for SELECTED_CHAR_KIND (NAME) intrinsic function.  */
5257
5258 static void
5259 gfc_conv_intrinsic_sc_kind (gfc_se *se, gfc_expr *expr)
5260 {
5261   tree args[2];
5262
5263   gfc_conv_intrinsic_function_args (se, expr, args, 2);
5264   se->expr = build_call_expr_loc (input_location,
5265                               gfor_fndecl_sc_kind, 2, args[0], args[1]);
5266   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), se->expr);
5267 }
5268
5269
5270 /* Generate code for SELECTED_INT_KIND (R) intrinsic function.  */
5271
5272 static void
5273 gfc_conv_intrinsic_si_kind (gfc_se *se, gfc_expr *expr)
5274 {
5275   tree arg, type;
5276
5277   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
5278
5279   /* The argument to SELECTED_INT_KIND is INTEGER(4).  */
5280   type = gfc_get_int_type (4); 
5281   arg = gfc_build_addr_expr (NULL_TREE, fold_convert (type, arg));
5282
5283   /* Convert it to the required type.  */
5284   type = gfc_typenode_for_spec (&expr->ts);
5285   se->expr = build_call_expr_loc (input_location,
5286                               gfor_fndecl_si_kind, 1, arg);
5287   se->expr = fold_convert (type, se->expr);
5288 }
5289
5290
5291 /* Generate code for SELECTED_REAL_KIND (P, R) intrinsic function.  */
5292
5293 static void
5294 gfc_conv_intrinsic_sr_kind (gfc_se *se, gfc_expr *expr)
5295 {
5296   gfc_actual_arglist *actual;
5297   tree type;
5298   gfc_se argse;
5299   VEC(tree,gc) *args = NULL;
5300
5301   for (actual = expr->value.function.actual; actual; actual = actual->next)
5302     {
5303       gfc_init_se (&argse, se);
5304
5305       /* Pass a NULL pointer for an absent arg.  */
5306       if (actual->expr == NULL)
5307         argse.expr = null_pointer_node;
5308       else
5309         {
5310           gfc_typespec ts;
5311           gfc_clear_ts (&ts);
5312
5313           if (actual->expr->ts.kind != gfc_c_int_kind)
5314             {
5315               /* The arguments to SELECTED_REAL_KIND are INTEGER(4).  */
5316               ts.type = BT_INTEGER;
5317               ts.kind = gfc_c_int_kind;
5318               gfc_convert_type (actual->expr, &ts, 2);
5319             }
5320           gfc_conv_expr_reference (&argse, actual->expr);
5321         } 
5322
5323       gfc_add_block_to_block (&se->pre, &argse.pre);
5324       gfc_add_block_to_block (&se->post, &argse.post);
5325       VEC_safe_push (tree, gc, args, argse.expr);
5326     }
5327
5328   /* Convert it to the required type.  */
5329   type = gfc_typenode_for_spec (&expr->ts);
5330   se->expr = build_call_expr_loc_vec (input_location,
5331                                       gfor_fndecl_sr_kind, args);
5332   se->expr = fold_convert (type, se->expr);
5333 }
5334
5335
5336 /* Generate code for TRIM (A) intrinsic function.  */
5337
5338 static void
5339 gfc_conv_intrinsic_trim (gfc_se * se, gfc_expr * expr)
5340 {
5341   tree var;
5342   tree len;
5343   tree addr;
5344   tree tmp;
5345   tree cond;
5346   tree fndecl;
5347   tree function;
5348   tree *args;
5349   unsigned int num_args;
5350
5351   num_args = gfc_intrinsic_argument_list_length (expr) + 2;
5352   args = XALLOCAVEC (tree, num_args);
5353
5354   var = gfc_create_var (gfc_get_pchar_type (expr->ts.kind), "pstr");
5355   addr = gfc_build_addr_expr (ppvoid_type_node, var);
5356   len = gfc_create_var (gfc_charlen_type_node, "len");
5357
5358   gfc_conv_intrinsic_function_args (se, expr, &args[2], num_args - 2);
5359   args[0] = gfc_build_addr_expr (NULL_TREE, len);
5360   args[1] = addr;
5361
5362   if (expr->ts.kind == 1)
5363     function = gfor_fndecl_string_trim;
5364   else if (expr->ts.kind == 4)
5365     function = gfor_fndecl_string_trim_char4;
5366   else
5367     gcc_unreachable ();
5368
5369   fndecl = build_addr (function, current_function_decl);
5370   tmp = build_call_array_loc (input_location,
5371                           TREE_TYPE (TREE_TYPE (function)), fndecl,
5372                           num_args, args);
5373   gfc_add_expr_to_block (&se->pre, tmp);
5374
5375   /* Free the temporary afterwards, if necessary.  */
5376   cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
5377                           len, build_int_cst (TREE_TYPE (len), 0));
5378   tmp = gfc_call_free (var);
5379   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
5380   gfc_add_expr_to_block (&se->post, tmp);
5381
5382   se->expr = var;
5383   se->string_length = len;
5384 }
5385
5386
5387 /* Generate code for REPEAT (STRING, NCOPIES) intrinsic function.  */
5388
5389 static void
5390 gfc_conv_intrinsic_repeat (gfc_se * se, gfc_expr * expr)
5391 {
5392   tree args[3], ncopies, dest, dlen, src, slen, ncopies_type;
5393   tree type, cond, tmp, count, exit_label, n, max, largest;
5394   tree size;
5395   stmtblock_t block, body;
5396   int i;
5397
5398   /* We store in charsize the size of a character.  */
5399   i = gfc_validate_kind (BT_CHARACTER, expr->ts.kind, false);
5400   size = build_int_cst (size_type_node, gfc_character_kinds[i].bit_size / 8);
5401
5402   /* Get the arguments.  */
5403   gfc_conv_intrinsic_function_args (se, expr, args, 3);
5404   slen = fold_convert (size_type_node, gfc_evaluate_now (args[0], &se->pre));
5405   src = args[1];
5406   ncopies = gfc_evaluate_now (args[2], &se->pre);
5407   ncopies_type = TREE_TYPE (ncopies);
5408
5409   /* Check that NCOPIES is not negative.  */
5410   cond = fold_build2_loc (input_location, LT_EXPR, boolean_type_node, ncopies,
5411                           build_int_cst (ncopies_type, 0));
5412   gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
5413                            "Argument NCOPIES of REPEAT intrinsic is negative "
5414                            "(its value is %lld)",
5415                            fold_convert (long_integer_type_node, ncopies));
5416
5417   /* If the source length is zero, any non negative value of NCOPIES
5418      is valid, and nothing happens.  */
5419   n = gfc_create_var (ncopies_type, "ncopies");
5420   cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, slen,
5421                           build_int_cst (size_type_node, 0));
5422   tmp = fold_build3_loc (input_location, COND_EXPR, ncopies_type, cond,
5423                          build_int_cst (ncopies_type, 0), ncopies);
5424   gfc_add_modify (&se->pre, n, tmp);
5425   ncopies = n;
5426
5427   /* Check that ncopies is not too large: ncopies should be less than
5428      (or equal to) MAX / slen, where MAX is the maximal integer of
5429      the gfc_charlen_type_node type.  If slen == 0, we need a special
5430      case to avoid the division by zero.  */
5431   i = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
5432   max = gfc_conv_mpz_to_tree (gfc_integer_kinds[i].huge, gfc_charlen_int_kind);
5433   max = fold_build2_loc (input_location, TRUNC_DIV_EXPR, size_type_node,
5434                           fold_convert (size_type_node, max), slen);
5435   largest = TYPE_PRECISION (size_type_node) > TYPE_PRECISION (ncopies_type)
5436               ? size_type_node : ncopies_type;
5437   cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
5438                           fold_convert (largest, ncopies),
5439                           fold_convert (largest, max));
5440   tmp = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, slen,
5441                          build_int_cst (size_type_node, 0));
5442   cond = fold_build3_loc (input_location, COND_EXPR, boolean_type_node, tmp,
5443                           boolean_false_node, cond);
5444   gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
5445                            "Argument NCOPIES of REPEAT intrinsic is too large");
5446
5447   /* Compute the destination length.  */
5448   dlen = fold_build2_loc (input_location, MULT_EXPR, gfc_charlen_type_node,
5449                           fold_convert (gfc_charlen_type_node, slen),
5450                           fold_convert (gfc_charlen_type_node, ncopies));
5451   type = gfc_get_character_type (expr->ts.kind, expr->ts.u.cl);
5452   dest = gfc_conv_string_tmp (se, build_pointer_type (type), dlen);
5453
5454   /* Generate the code to do the repeat operation:
5455        for (i = 0; i < ncopies; i++)
5456          memmove (dest + (i * slen * size), src, slen*size);  */
5457   gfc_start_block (&block);
5458   count = gfc_create_var (ncopies_type, "count");
5459   gfc_add_modify (&block, count, build_int_cst (ncopies_type, 0));
5460   exit_label = gfc_build_label_decl (NULL_TREE);
5461
5462   /* Start the loop body.  */
5463   gfc_start_block (&body);
5464
5465   /* Exit the loop if count >= ncopies.  */
5466   cond = fold_build2_loc (input_location, GE_EXPR, boolean_type_node, count,
5467                           ncopies);
5468   tmp = build1_v (GOTO_EXPR, exit_label);
5469   TREE_USED (exit_label) = 1;
5470   tmp = fold_build3_loc (input_location, COND_EXPR, void_type_node, cond, tmp,
5471                          build_empty_stmt (input_location));
5472   gfc_add_expr_to_block (&body, tmp);
5473
5474   /* Call memmove (dest + (i*slen*size), src, slen*size).  */
5475   tmp = fold_build2_loc (input_location, MULT_EXPR, gfc_charlen_type_node,
5476                          fold_convert (gfc_charlen_type_node, slen),
5477                          fold_convert (gfc_charlen_type_node, count));
5478   tmp = fold_build2_loc (input_location, MULT_EXPR, gfc_charlen_type_node,
5479                          tmp, fold_convert (gfc_charlen_type_node, size));
5480   tmp = fold_build2_loc (input_location, POINTER_PLUS_EXPR, pvoid_type_node,
5481                          fold_convert (pvoid_type_node, dest),
5482                          fold_convert (sizetype, tmp));
5483   tmp = build_call_expr_loc (input_location,
5484                              built_in_decls[BUILT_IN_MEMMOVE], 3, tmp, src,
5485                              fold_build2_loc (input_location, MULT_EXPR,
5486                                               size_type_node, slen,
5487                                               fold_convert (size_type_node,
5488                                                             size)));
5489   gfc_add_expr_to_block (&body, tmp);
5490
5491   /* Increment count.  */
5492   tmp = fold_build2_loc (input_location, PLUS_EXPR, ncopies_type,
5493                          count, build_int_cst (TREE_TYPE (count), 1));
5494   gfc_add_modify (&body, count, tmp);
5495
5496   /* Build the loop.  */
5497   tmp = build1_v (LOOP_EXPR, gfc_finish_block (&body));
5498   gfc_add_expr_to_block (&block, tmp);
5499
5500   /* Add the exit label.  */
5501   tmp = build1_v (LABEL_EXPR, exit_label);
5502   gfc_add_expr_to_block (&block, tmp);
5503
5504   /* Finish the block.  */
5505   tmp = gfc_finish_block (&block);
5506   gfc_add_expr_to_block (&se->pre, tmp);
5507
5508   /* Set the result value.  */
5509   se->expr = dest;
5510   se->string_length = dlen;
5511 }
5512
5513
5514 /* Generate code for the IARGC intrinsic.  */
5515
5516 static void
5517 gfc_conv_intrinsic_iargc (gfc_se * se, gfc_expr * expr)
5518 {
5519   tree tmp;
5520   tree fndecl;
5521   tree type;
5522
5523   /* Call the library function.  This always returns an INTEGER(4).  */
5524   fndecl = gfor_fndecl_iargc;
5525   tmp = build_call_expr_loc (input_location,
5526                          fndecl, 0);
5527
5528   /* Convert it to the required type.  */
5529   type = gfc_typenode_for_spec (&expr->ts);
5530   tmp = fold_convert (type, tmp);
5531
5532   se->expr = tmp;
5533 }
5534
5535
5536 /* The loc intrinsic returns the address of its argument as
5537    gfc_index_integer_kind integer.  */
5538
5539 static void
5540 gfc_conv_intrinsic_loc (gfc_se * se, gfc_expr * expr)
5541 {
5542   tree temp_var;
5543   gfc_expr *arg_expr;
5544   gfc_ss *ss;
5545
5546   gcc_assert (!se->ss);
5547
5548   arg_expr = expr->value.function.actual->expr;
5549   ss = gfc_walk_expr (arg_expr);
5550   if (ss == gfc_ss_terminator)
5551     gfc_conv_expr_reference (se, arg_expr);
5552   else
5553     gfc_conv_array_parameter (se, arg_expr, ss, true, NULL, NULL, NULL);
5554   se->expr= convert (gfc_get_int_type (gfc_index_integer_kind), se->expr);
5555    
5556   /* Create a temporary variable for loc return value.  Without this, 
5557      we get an error an ICE in gcc/expr.c(expand_expr_addr_expr_1).  */
5558   temp_var = gfc_create_var (gfc_get_int_type (gfc_index_integer_kind), NULL);
5559   gfc_add_modify (&se->pre, temp_var, se->expr);
5560   se->expr = temp_var;
5561 }
5562
5563 /* Generate code for an intrinsic function.  Some map directly to library
5564    calls, others get special handling.  In some cases the name of the function
5565    used depends on the type specifiers.  */
5566
5567 void
5568 gfc_conv_intrinsic_function (gfc_se * se, gfc_expr * expr)
5569 {
5570   const char *name;
5571   int lib, kind;
5572   tree fndecl;
5573
5574   name = &expr->value.function.name[2];
5575
5576   if (expr->rank > 0)
5577     {
5578       lib = gfc_is_intrinsic_libcall (expr);
5579       if (lib != 0)
5580         {
5581           if (lib == 1)
5582             se->ignore_optional = 1;
5583
5584           switch (expr->value.function.isym->id)
5585             {
5586             case GFC_ISYM_EOSHIFT:
5587             case GFC_ISYM_PACK:
5588             case GFC_ISYM_RESHAPE:
5589               /* For all of those the first argument specifies the type and the
5590                  third is optional.  */
5591               conv_generic_with_optional_char_arg (se, expr, 1, 3);
5592               break;
5593
5594             default:
5595               gfc_conv_intrinsic_funcall (se, expr);
5596               break;
5597             }
5598
5599           return;
5600         }
5601     }
5602
5603   switch (expr->value.function.isym->id)
5604     {
5605     case GFC_ISYM_NONE:
5606       gcc_unreachable ();
5607
5608     case GFC_ISYM_REPEAT:
5609       gfc_conv_intrinsic_repeat (se, expr);
5610       break;
5611
5612     case GFC_ISYM_TRIM:
5613       gfc_conv_intrinsic_trim (se, expr);
5614       break;
5615
5616     case GFC_ISYM_SC_KIND:
5617       gfc_conv_intrinsic_sc_kind (se, expr);
5618       break;
5619
5620     case GFC_ISYM_SI_KIND:
5621       gfc_conv_intrinsic_si_kind (se, expr);
5622       break;
5623
5624     case GFC_ISYM_SR_KIND:
5625       gfc_conv_intrinsic_sr_kind (se, expr);
5626       break;
5627
5628     case GFC_ISYM_EXPONENT:
5629       gfc_conv_intrinsic_exponent (se, expr);
5630       break;
5631
5632     case GFC_ISYM_SCAN:
5633       kind = expr->value.function.actual->expr->ts.kind;
5634       if (kind == 1)
5635        fndecl = gfor_fndecl_string_scan;
5636       else if (kind == 4)
5637        fndecl = gfor_fndecl_string_scan_char4;
5638       else
5639        gcc_unreachable ();
5640
5641       gfc_conv_intrinsic_index_scan_verify (se, expr, fndecl);
5642       break;
5643
5644     case GFC_ISYM_VERIFY:
5645       kind = expr->value.function.actual->expr->ts.kind;
5646       if (kind == 1)
5647        fndecl = gfor_fndecl_string_verify;
5648       else if (kind == 4)
5649        fndecl = gfor_fndecl_string_verify_char4;
5650       else
5651        gcc_unreachable ();
5652
5653       gfc_conv_intrinsic_index_scan_verify (se, expr, fndecl);
5654       break;
5655
5656     case GFC_ISYM_ALLOCATED:
5657       gfc_conv_allocated (se, expr);
5658       break;
5659
5660     case GFC_ISYM_ASSOCIATED:
5661       gfc_conv_associated(se, expr);
5662       break;
5663
5664     case GFC_ISYM_SAME_TYPE_AS:
5665       gfc_conv_same_type_as (se, expr);
5666       break;
5667
5668     case GFC_ISYM_ABS:
5669       gfc_conv_intrinsic_abs (se, expr);
5670       break;
5671
5672     case GFC_ISYM_ADJUSTL:
5673       if (expr->ts.kind == 1)
5674        fndecl = gfor_fndecl_adjustl;
5675       else if (expr->ts.kind == 4)
5676        fndecl = gfor_fndecl_adjustl_char4;
5677       else
5678        gcc_unreachable ();
5679
5680       gfc_conv_intrinsic_adjust (se, expr, fndecl);
5681       break;
5682
5683     case GFC_ISYM_ADJUSTR:
5684       if (expr->ts.kind == 1)
5685        fndecl = gfor_fndecl_adjustr;
5686       else if (expr->ts.kind == 4)
5687        fndecl = gfor_fndecl_adjustr_char4;
5688       else
5689        gcc_unreachable ();
5690
5691       gfc_conv_intrinsic_adjust (se, expr, fndecl);
5692       break;
5693
5694     case GFC_ISYM_AIMAG:
5695       gfc_conv_intrinsic_imagpart (se, expr);
5696       break;
5697
5698     case GFC_ISYM_AINT:
5699       gfc_conv_intrinsic_aint (se, expr, RND_TRUNC);
5700       break;
5701
5702     case GFC_ISYM_ALL:
5703       gfc_conv_intrinsic_anyall (se, expr, EQ_EXPR);
5704       break;
5705
5706     case GFC_ISYM_ANINT:
5707       gfc_conv_intrinsic_aint (se, expr, RND_ROUND);
5708       break;
5709
5710     case GFC_ISYM_AND:
5711       gfc_conv_intrinsic_bitop (se, expr, BIT_AND_EXPR);
5712       break;
5713
5714     case GFC_ISYM_ANY:
5715       gfc_conv_intrinsic_anyall (se, expr, NE_EXPR);
5716       break;
5717
5718     case GFC_ISYM_BTEST:
5719       gfc_conv_intrinsic_btest (se, expr);
5720       break;
5721
5722     case GFC_ISYM_BGE:
5723       gfc_conv_intrinsic_bitcomp (se, expr, GE_EXPR);
5724       break;
5725
5726     case GFC_ISYM_BGT:
5727       gfc_conv_intrinsic_bitcomp (se, expr, GT_EXPR);
5728       break;
5729
5730     case GFC_ISYM_BLE:
5731       gfc_conv_intrinsic_bitcomp (se, expr, LE_EXPR);
5732       break;
5733
5734     case GFC_ISYM_BLT:
5735       gfc_conv_intrinsic_bitcomp (se, expr, LT_EXPR);
5736       break;
5737
5738     case GFC_ISYM_ACHAR:
5739     case GFC_ISYM_CHAR:
5740       gfc_conv_intrinsic_char (se, expr);
5741       break;
5742
5743     case GFC_ISYM_CONVERSION:
5744     case GFC_ISYM_REAL:
5745     case GFC_ISYM_LOGICAL:
5746     case GFC_ISYM_DBLE:
5747       gfc_conv_intrinsic_conversion (se, expr);
5748       break;
5749
5750       /* Integer conversions are handled separately to make sure we get the
5751          correct rounding mode.  */
5752     case GFC_ISYM_INT:
5753     case GFC_ISYM_INT2:
5754     case GFC_ISYM_INT8:
5755     case GFC_ISYM_LONG:
5756       gfc_conv_intrinsic_int (se, expr, RND_TRUNC);
5757       break;
5758
5759     case GFC_ISYM_NINT:
5760       gfc_conv_intrinsic_int (se, expr, RND_ROUND);
5761       break;
5762
5763     case GFC_ISYM_CEILING:
5764       gfc_conv_intrinsic_int (se, expr, RND_CEIL);
5765       break;
5766
5767     case GFC_ISYM_FLOOR:
5768       gfc_conv_intrinsic_int (se, expr, RND_FLOOR);
5769       break;
5770
5771     case GFC_ISYM_MOD:
5772       gfc_conv_intrinsic_mod (se, expr, 0);
5773       break;
5774
5775     case GFC_ISYM_MODULO:
5776       gfc_conv_intrinsic_mod (se, expr, 1);
5777       break;
5778
5779     case GFC_ISYM_CMPLX:
5780       gfc_conv_intrinsic_cmplx (se, expr, name[5] == '1');
5781       break;
5782
5783     case GFC_ISYM_COMMAND_ARGUMENT_COUNT:
5784       gfc_conv_intrinsic_iargc (se, expr);
5785       break;
5786
5787     case GFC_ISYM_COMPLEX:
5788       gfc_conv_intrinsic_cmplx (se, expr, 1);
5789       break;
5790
5791     case GFC_ISYM_CONJG:
5792       gfc_conv_intrinsic_conjg (se, expr);
5793       break;
5794
5795     case GFC_ISYM_COUNT:
5796       gfc_conv_intrinsic_count (se, expr);
5797       break;
5798
5799     case GFC_ISYM_CTIME:
5800       gfc_conv_intrinsic_ctime (se, expr);
5801       break;
5802
5803     case GFC_ISYM_DIM:
5804       gfc_conv_intrinsic_dim (se, expr);
5805       break;
5806
5807     case GFC_ISYM_DOT_PRODUCT:
5808       gfc_conv_intrinsic_dot_product (se, expr);
5809       break;
5810
5811     case GFC_ISYM_DPROD:
5812       gfc_conv_intrinsic_dprod (se, expr);
5813       break;
5814
5815     case GFC_ISYM_DSHIFTL:
5816       gfc_conv_intrinsic_dshift (se, expr, true);
5817       break;
5818
5819     case GFC_ISYM_DSHIFTR:
5820       gfc_conv_intrinsic_dshift (se, expr, false);
5821       break;
5822
5823     case GFC_ISYM_FDATE:
5824       gfc_conv_intrinsic_fdate (se, expr);
5825       break;
5826
5827     case GFC_ISYM_FRACTION:
5828       gfc_conv_intrinsic_fraction (se, expr);
5829       break;
5830
5831     case GFC_ISYM_IALL:
5832       gfc_conv_intrinsic_arith (se, expr, BIT_AND_EXPR, false);
5833       break;
5834
5835     case GFC_ISYM_IAND:
5836       gfc_conv_intrinsic_bitop (se, expr, BIT_AND_EXPR);
5837       break;
5838
5839     case GFC_ISYM_IANY:
5840       gfc_conv_intrinsic_arith (se, expr, BIT_IOR_EXPR, false);
5841       break;
5842
5843     case GFC_ISYM_IBCLR:
5844       gfc_conv_intrinsic_singlebitop (se, expr, 0);
5845       break;
5846
5847     case GFC_ISYM_IBITS:
5848       gfc_conv_intrinsic_ibits (se, expr);
5849       break;
5850
5851     case GFC_ISYM_IBSET:
5852       gfc_conv_intrinsic_singlebitop (se, expr, 1);
5853       break;
5854
5855     case GFC_ISYM_IACHAR:
5856     case GFC_ISYM_ICHAR:
5857       /* We assume ASCII character sequence.  */
5858       gfc_conv_intrinsic_ichar (se, expr);
5859       break;
5860
5861     case GFC_ISYM_IARGC:
5862       gfc_conv_intrinsic_iargc (se, expr);
5863       break;
5864
5865     case GFC_ISYM_IEOR:
5866       gfc_conv_intrinsic_bitop (se, expr, BIT_XOR_EXPR);
5867       break;
5868
5869     case GFC_ISYM_INDEX:
5870       kind = expr->value.function.actual->expr->ts.kind;
5871       if (kind == 1)
5872        fndecl = gfor_fndecl_string_index;
5873       else if (kind == 4)
5874        fndecl = gfor_fndecl_string_index_char4;
5875       else
5876        gcc_unreachable ();
5877
5878       gfc_conv_intrinsic_index_scan_verify (se, expr, fndecl);
5879       break;
5880
5881     case GFC_ISYM_IOR:
5882       gfc_conv_intrinsic_bitop (se, expr, BIT_IOR_EXPR);
5883       break;
5884
5885     case GFC_ISYM_IPARITY:
5886       gfc_conv_intrinsic_arith (se, expr, BIT_XOR_EXPR, false);
5887       break;
5888
5889     case GFC_ISYM_IS_IOSTAT_END:
5890       gfc_conv_has_intvalue (se, expr, LIBERROR_END);
5891       break;
5892
5893     case GFC_ISYM_IS_IOSTAT_EOR:
5894       gfc_conv_has_intvalue (se, expr, LIBERROR_EOR);
5895       break;
5896
5897     case GFC_ISYM_ISNAN:
5898       gfc_conv_intrinsic_isnan (se, expr);
5899       break;
5900
5901     case GFC_ISYM_LSHIFT:
5902       gfc_conv_intrinsic_shift (se, expr, false, false);
5903       break;
5904
5905     case GFC_ISYM_RSHIFT:
5906       gfc_conv_intrinsic_shift (se, expr, true, true);
5907       break;
5908
5909     case GFC_ISYM_SHIFTA:
5910       gfc_conv_intrinsic_shift (se, expr, true, true);
5911       break;
5912
5913     case GFC_ISYM_SHIFTL:
5914       gfc_conv_intrinsic_shift (se, expr, false, false);
5915       break;
5916
5917     case GFC_ISYM_SHIFTR:
5918       gfc_conv_intrinsic_shift (se, expr, true, false);
5919       break;
5920
5921     case GFC_ISYM_ISHFT:
5922       gfc_conv_intrinsic_ishft (se, expr);
5923       break;
5924
5925     case GFC_ISYM_ISHFTC:
5926       gfc_conv_intrinsic_ishftc (se, expr);
5927       break;
5928
5929     case GFC_ISYM_LEADZ:
5930       gfc_conv_intrinsic_leadz (se, expr);
5931       break;
5932
5933     case GFC_ISYM_TRAILZ:
5934       gfc_conv_intrinsic_trailz (se, expr);
5935       break;
5936
5937     case GFC_ISYM_POPCNT:
5938       gfc_conv_intrinsic_popcnt_poppar (se, expr, 0);
5939       break;
5940
5941     case GFC_ISYM_POPPAR:
5942       gfc_conv_intrinsic_popcnt_poppar (se, expr, 1);
5943       break;
5944
5945     case GFC_ISYM_LBOUND:
5946       gfc_conv_intrinsic_bound (se, expr, 0);
5947       break;
5948
5949     case GFC_ISYM_TRANSPOSE:
5950       /* The scalarizer has already been set up for reversed dimension access
5951          order ; now we just get the argument value normally.  */
5952       gfc_conv_expr (se, expr->value.function.actual->expr);
5953       break;
5954
5955     case GFC_ISYM_LEN:
5956       gfc_conv_intrinsic_len (se, expr);
5957       break;
5958
5959     case GFC_ISYM_LEN_TRIM:
5960       gfc_conv_intrinsic_len_trim (se, expr);
5961       break;
5962
5963     case GFC_ISYM_LGE:
5964       gfc_conv_intrinsic_strcmp (se, expr, GE_EXPR);
5965       break;
5966
5967     case GFC_ISYM_LGT:
5968       gfc_conv_intrinsic_strcmp (se, expr, GT_EXPR);
5969       break;
5970
5971     case GFC_ISYM_LLE:
5972       gfc_conv_intrinsic_strcmp (se, expr, LE_EXPR);
5973       break;
5974
5975     case GFC_ISYM_LLT:
5976       gfc_conv_intrinsic_strcmp (se, expr, LT_EXPR);
5977       break;
5978
5979     case GFC_ISYM_MASKL:
5980       gfc_conv_intrinsic_mask (se, expr, 1);
5981       break;
5982
5983     case GFC_ISYM_MASKR:
5984       gfc_conv_intrinsic_mask (se, expr, 0);
5985       break;
5986
5987     case GFC_ISYM_MAX:
5988       if (expr->ts.type == BT_CHARACTER)
5989         gfc_conv_intrinsic_minmax_char (se, expr, 1);
5990       else
5991         gfc_conv_intrinsic_minmax (se, expr, GT_EXPR);
5992       break;
5993
5994     case GFC_ISYM_MAXLOC:
5995       gfc_conv_intrinsic_minmaxloc (se, expr, GT_EXPR);
5996       break;
5997
5998     case GFC_ISYM_MAXVAL:
5999       gfc_conv_intrinsic_minmaxval (se, expr, GT_EXPR);
6000       break;
6001
6002     case GFC_ISYM_MERGE:
6003       gfc_conv_intrinsic_merge (se, expr);
6004       break;
6005
6006     case GFC_ISYM_MERGE_BITS:
6007       gfc_conv_intrinsic_merge_bits (se, expr);
6008       break;
6009
6010     case GFC_ISYM_MIN:
6011       if (expr->ts.type == BT_CHARACTER)
6012         gfc_conv_intrinsic_minmax_char (se, expr, -1);
6013       else
6014         gfc_conv_intrinsic_minmax (se, expr, LT_EXPR);
6015       break;
6016
6017     case GFC_ISYM_MINLOC:
6018       gfc_conv_intrinsic_minmaxloc (se, expr, LT_EXPR);
6019       break;
6020
6021     case GFC_ISYM_MINVAL:
6022       gfc_conv_intrinsic_minmaxval (se, expr, LT_EXPR);
6023       break;
6024
6025     case GFC_ISYM_NEAREST:
6026       gfc_conv_intrinsic_nearest (se, expr);
6027       break;
6028
6029     case GFC_ISYM_NORM2:
6030       gfc_conv_intrinsic_arith (se, expr, PLUS_EXPR, true);
6031       break;
6032
6033     case GFC_ISYM_NOT:
6034       gfc_conv_intrinsic_not (se, expr);
6035       break;
6036
6037     case GFC_ISYM_OR:
6038       gfc_conv_intrinsic_bitop (se, expr, BIT_IOR_EXPR);
6039       break;
6040
6041     case GFC_ISYM_PARITY:
6042       gfc_conv_intrinsic_arith (se, expr, NE_EXPR, false);
6043       break;
6044
6045     case GFC_ISYM_PRESENT:
6046       gfc_conv_intrinsic_present (se, expr);
6047       break;
6048
6049     case GFC_ISYM_PRODUCT:
6050       gfc_conv_intrinsic_arith (se, expr, MULT_EXPR, false);
6051       break;
6052
6053     case GFC_ISYM_RRSPACING:
6054       gfc_conv_intrinsic_rrspacing (se, expr);
6055       break;
6056
6057     case GFC_ISYM_SET_EXPONENT:
6058       gfc_conv_intrinsic_set_exponent (se, expr);
6059       break;
6060
6061     case GFC_ISYM_SCALE:
6062       gfc_conv_intrinsic_scale (se, expr);
6063       break;
6064
6065     case GFC_ISYM_SIGN:
6066       gfc_conv_intrinsic_sign (se, expr);
6067       break;
6068
6069     case GFC_ISYM_SIZE:
6070       gfc_conv_intrinsic_size (se, expr);
6071       break;
6072
6073     case GFC_ISYM_SIZEOF:
6074     case GFC_ISYM_C_SIZEOF:
6075       gfc_conv_intrinsic_sizeof (se, expr);
6076       break;
6077
6078     case GFC_ISYM_STORAGE_SIZE:
6079       gfc_conv_intrinsic_storage_size (se, expr);
6080       break;
6081
6082     case GFC_ISYM_SPACING:
6083       gfc_conv_intrinsic_spacing (se, expr);
6084       break;
6085
6086     case GFC_ISYM_SUM:
6087       gfc_conv_intrinsic_arith (se, expr, PLUS_EXPR, false);
6088       break;
6089
6090     case GFC_ISYM_TRANSFER:
6091       if (se->ss && se->ss->useflags)
6092         /* Access the previously obtained result.  */
6093         gfc_conv_tmp_array_ref (se);
6094       else
6095         gfc_conv_intrinsic_transfer (se, expr);
6096       break;
6097
6098     case GFC_ISYM_TTYNAM:
6099       gfc_conv_intrinsic_ttynam (se, expr);
6100       break;
6101
6102     case GFC_ISYM_UBOUND:
6103       gfc_conv_intrinsic_bound (se, expr, 1);
6104       break;
6105
6106     case GFC_ISYM_XOR:
6107       gfc_conv_intrinsic_bitop (se, expr, BIT_XOR_EXPR);
6108       break;
6109
6110     case GFC_ISYM_LOC:
6111       gfc_conv_intrinsic_loc (se, expr);
6112       break;
6113
6114     case GFC_ISYM_ACCESS:
6115     case GFC_ISYM_CHDIR:
6116     case GFC_ISYM_CHMOD:
6117     case GFC_ISYM_DTIME:
6118     case GFC_ISYM_ETIME:
6119     case GFC_ISYM_EXTENDS_TYPE_OF:
6120     case GFC_ISYM_FGET:
6121     case GFC_ISYM_FGETC:
6122     case GFC_ISYM_FNUM:
6123     case GFC_ISYM_FPUT:
6124     case GFC_ISYM_FPUTC:
6125     case GFC_ISYM_FSTAT:
6126     case GFC_ISYM_FTELL:
6127     case GFC_ISYM_GETCWD:
6128     case GFC_ISYM_GETGID:
6129     case GFC_ISYM_GETPID:
6130     case GFC_ISYM_GETUID:
6131     case GFC_ISYM_HOSTNM:
6132     case GFC_ISYM_KILL:
6133     case GFC_ISYM_IERRNO:
6134     case GFC_ISYM_IRAND:
6135     case GFC_ISYM_ISATTY:
6136     case GFC_ISYM_JN2:
6137     case GFC_ISYM_LINK:
6138     case GFC_ISYM_LSTAT:
6139     case GFC_ISYM_MALLOC:
6140     case GFC_ISYM_MATMUL:
6141     case GFC_ISYM_MCLOCK:
6142     case GFC_ISYM_MCLOCK8:
6143     case GFC_ISYM_RAND:
6144     case GFC_ISYM_RENAME:
6145     case GFC_ISYM_SECOND:
6146     case GFC_ISYM_SECNDS:
6147     case GFC_ISYM_SIGNAL:
6148     case GFC_ISYM_STAT:
6149     case GFC_ISYM_SYMLNK:
6150     case GFC_ISYM_SYSTEM:
6151     case GFC_ISYM_TIME:
6152     case GFC_ISYM_TIME8:
6153     case GFC_ISYM_UMASK:
6154     case GFC_ISYM_UNLINK:
6155     case GFC_ISYM_YN2:
6156       gfc_conv_intrinsic_funcall (se, expr);
6157       break;
6158
6159     case GFC_ISYM_EOSHIFT:
6160     case GFC_ISYM_PACK:
6161     case GFC_ISYM_RESHAPE:
6162       /* For those, expr->rank should always be >0 and thus the if above the
6163          switch should have matched.  */
6164       gcc_unreachable ();
6165       break;
6166
6167     default:
6168       gfc_conv_intrinsic_lib_function (se, expr);
6169       break;
6170     }
6171 }
6172
6173
6174 static gfc_ss *
6175 walk_inline_intrinsic_transpose (gfc_ss *ss, gfc_expr *expr)
6176 {
6177   gfc_ss *arg_ss, *tmp_ss;
6178   gfc_actual_arglist *arg;
6179
6180   arg = expr->value.function.actual;
6181
6182   gcc_assert (arg->expr);
6183
6184   arg_ss = gfc_walk_subexpr (gfc_ss_terminator, arg->expr);
6185   gcc_assert (arg_ss != gfc_ss_terminator);
6186
6187   for (tmp_ss = arg_ss; ; tmp_ss = tmp_ss->next)
6188     {
6189       if (tmp_ss->type != GFC_SS_SCALAR
6190           && tmp_ss->type != GFC_SS_REFERENCE)
6191         {
6192           int tmp_dim;
6193           gfc_ss_info *info;
6194
6195           info = &tmp_ss->data.info;
6196           gcc_assert (info->dimen == 2);
6197
6198           /* We just invert dimensions.  */
6199           tmp_dim = info->dim[0];
6200           info->dim[0] = info->dim[1];
6201           info->dim[1] = tmp_dim;
6202         }
6203
6204       /* Stop when tmp_ss points to the last valid element of the chain...  */
6205       if (tmp_ss->next == gfc_ss_terminator)
6206         break;
6207     }
6208
6209   /* ... so that we can attach the rest of the chain to it.  */
6210   tmp_ss->next = ss;
6211
6212   return arg_ss;
6213 }
6214
6215
6216 static gfc_ss *
6217 walk_inline_intrinsic_function (gfc_ss * ss, gfc_expr * expr)
6218 {
6219
6220   switch (expr->value.function.isym->id)
6221     {
6222       case GFC_ISYM_TRANSPOSE:
6223         return walk_inline_intrinsic_transpose (ss, expr);
6224
6225       default:
6226         gcc_unreachable ();
6227     }
6228   gcc_unreachable ();
6229 }
6230
6231
6232 /* This generates code to execute before entering the scalarization loop.
6233    Currently does nothing.  */
6234
6235 void
6236 gfc_add_intrinsic_ss_code (gfc_loopinfo * loop ATTRIBUTE_UNUSED, gfc_ss * ss)
6237 {
6238   switch (ss->expr->value.function.isym->id)
6239     {
6240     case GFC_ISYM_UBOUND:
6241     case GFC_ISYM_LBOUND:
6242       break;
6243
6244     default:
6245       gcc_unreachable ();
6246     }
6247 }
6248
6249
6250 /* UBOUND and LBOUND intrinsics with one parameter are expanded into code
6251    inside the scalarization loop.  */
6252
6253 static gfc_ss *
6254 gfc_walk_intrinsic_bound (gfc_ss * ss, gfc_expr * expr)
6255 {
6256   gfc_ss *newss;
6257
6258   /* The two argument version returns a scalar.  */
6259   if (expr->value.function.actual->next->expr)
6260     return ss;
6261
6262   newss = gfc_get_ss ();
6263   newss->type = GFC_SS_INTRINSIC;
6264   newss->expr = expr;
6265   newss->next = ss;
6266   newss->data.info.dimen = 1;
6267
6268   return newss;
6269 }
6270
6271
6272 /* Walk an intrinsic array libcall.  */
6273
6274 static gfc_ss *
6275 gfc_walk_intrinsic_libfunc (gfc_ss * ss, gfc_expr * expr)
6276 {
6277   gfc_ss *newss;
6278   int n;
6279
6280   gcc_assert (expr->rank > 0);
6281
6282   newss = gfc_get_ss ();
6283   newss->type = GFC_SS_FUNCTION;
6284   newss->expr = expr;
6285   newss->next = ss;
6286   newss->data.info.dimen = expr->rank;
6287   for (n = 0; n < newss->data.info.dimen; n++)
6288     newss->data.info.dim[n] = n;
6289
6290   return newss;
6291 }
6292
6293
6294 /* Return whether the function call expression EXPR will be expanded
6295    inline by gfc_conv_intrinsic_function.  */
6296
6297 bool
6298 gfc_inline_intrinsic_function_p (gfc_expr *expr)
6299 {
6300   if (!expr->value.function.isym)
6301     return false;
6302
6303   switch (expr->value.function.isym->id)
6304     {
6305     case GFC_ISYM_TRANSPOSE:
6306       return true;
6307
6308     default:
6309       return false;
6310     }
6311 }
6312
6313
6314 /* Returns nonzero if the specified intrinsic function call maps directly to
6315    an external library call.  Should only be used for functions that return
6316    arrays.  */
6317
6318 int
6319 gfc_is_intrinsic_libcall (gfc_expr * expr)
6320 {
6321   gcc_assert (expr->expr_type == EXPR_FUNCTION && expr->value.function.isym);
6322   gcc_assert (expr->rank > 0);
6323
6324   if (gfc_inline_intrinsic_function_p (expr))
6325     return 0;
6326
6327   switch (expr->value.function.isym->id)
6328     {
6329     case GFC_ISYM_ALL:
6330     case GFC_ISYM_ANY:
6331     case GFC_ISYM_COUNT:
6332     case GFC_ISYM_JN2:
6333     case GFC_ISYM_IANY:
6334     case GFC_ISYM_IALL:
6335     case GFC_ISYM_IPARITY:
6336     case GFC_ISYM_MATMUL:
6337     case GFC_ISYM_MAXLOC:
6338     case GFC_ISYM_MAXVAL:
6339     case GFC_ISYM_MINLOC:
6340     case GFC_ISYM_MINVAL:
6341     case GFC_ISYM_NORM2:
6342     case GFC_ISYM_PARITY:
6343     case GFC_ISYM_PRODUCT:
6344     case GFC_ISYM_SUM:
6345     case GFC_ISYM_SHAPE:
6346     case GFC_ISYM_SPREAD:
6347     case GFC_ISYM_YN2:
6348       /* Ignore absent optional parameters.  */
6349       return 1;
6350
6351     case GFC_ISYM_RESHAPE:
6352     case GFC_ISYM_CSHIFT:
6353     case GFC_ISYM_EOSHIFT:
6354     case GFC_ISYM_PACK:
6355     case GFC_ISYM_UNPACK:
6356       /* Pass absent optional parameters.  */
6357       return 2;
6358
6359     default:
6360       return 0;
6361     }
6362 }
6363
6364 /* Walk an intrinsic function.  */
6365 gfc_ss *
6366 gfc_walk_intrinsic_function (gfc_ss * ss, gfc_expr * expr,
6367                              gfc_intrinsic_sym * isym)
6368 {
6369   gcc_assert (isym);
6370
6371   if (isym->elemental)
6372     return gfc_walk_elemental_function_args (ss, expr->value.function.actual,
6373                                              GFC_SS_SCALAR);
6374
6375   if (expr->rank == 0)
6376     return ss;
6377
6378   if (gfc_inline_intrinsic_function_p (expr))
6379     return walk_inline_intrinsic_function (ss, expr);
6380
6381   if (gfc_is_intrinsic_libcall (expr))
6382     return gfc_walk_intrinsic_libfunc (ss, expr);
6383
6384   /* Special cases.  */
6385   switch (isym->id)
6386     {
6387     case GFC_ISYM_LBOUND:
6388     case GFC_ISYM_UBOUND:
6389       return gfc_walk_intrinsic_bound (ss, expr);
6390
6391     case GFC_ISYM_TRANSFER:
6392       return gfc_walk_intrinsic_libfunc (ss, expr);
6393
6394     default:
6395       /* This probably meant someone forgot to add an intrinsic to the above
6396          list(s) when they implemented it, or something's gone horribly
6397          wrong.  */
6398       gcc_unreachable ();
6399     }
6400 }
6401
6402
6403 tree
6404 gfc_conv_intrinsic_move_alloc (gfc_code *code)
6405 {
6406   if (code->ext.actual->expr->rank == 0)
6407     {
6408       /* Scalar arguments: Generate pointer assignments.  */
6409       gfc_expr *from, *to;
6410       stmtblock_t block;
6411       tree tmp;
6412
6413       from = code->ext.actual->expr;
6414       to = code->ext.actual->next->expr;
6415
6416       gfc_start_block (&block);
6417
6418       if (to->ts.type == BT_CLASS)
6419         tmp = gfc_trans_class_assign (to, from, EXEC_POINTER_ASSIGN);
6420       else
6421         tmp = gfc_trans_pointer_assignment (to, from);
6422       gfc_add_expr_to_block (&block, tmp);
6423
6424       if (from->ts.type == BT_CLASS)
6425         tmp = gfc_trans_class_assign (from, gfc_get_null_expr (NULL),
6426                                       EXEC_POINTER_ASSIGN);
6427       else
6428         tmp = gfc_trans_pointer_assignment (from,
6429                                             gfc_get_null_expr (NULL));
6430       gfc_add_expr_to_block (&block, tmp);
6431
6432       return gfc_finish_block (&block);
6433     }
6434   else
6435     /* Array arguments: Generate library code.  */
6436     return gfc_trans_call (code, false, NULL_TREE, NULL_TREE, false);
6437 }
6438
6439
6440 #include "gt-fortran-trans-intrinsic.h"