source: patches/gcc-4.8.2-branch_update-1.patch@ c88e5fc

clfs-3.0.0-systemd systemd
Last change on this file since c88e5fc was 88af5df, checked in by William Harrington <kb0iic@…>, 12 years ago

Fix gcc 4.8.2 branch update 1 patch.

  • Property mode set to 100644
File size: 251.5 KB
  • ChangeLog

    Submitted By: Jim Gifford (jim at cross-lfs dot org)
    Date: 11-01-2013
    Initial Package Version: 4.8.2
    Origin: Upstream
    Upstream Status: Applied
    Description: This is a branch update for gcc-4.8.2, and should be
                 rechecked periodically.
    
    Includes PR tree-optimization/54094
    
    This patch was made from Revision # 204292.
    
    diff -Naur gcc-4.8.2.orig/ChangeLog gcc-4.8.2/ChangeLog
    old new  
    77        * configure.ac: Also allow ISL 0.12.
    88        * configure: Regenerated.
    99
     10        PR tree-optimization/54094
     11        * graphite-clast-to-gimple.c (translate_clast_for_loop): Derive the
     12          scheduling dimension for the parallelism check from the polyhedral
     13          information in the AST.
     14        * graphite-dependences.c (carries_deps): Do not assume the schedule is
     15          in 2D + 1 form.
     16
    10172013-05-31  Release Manager
    1118
    1219        * GCC 4.8.1 released.
  • contrib/gcc_update

    diff -Naur gcc-4.8.2.orig/contrib/gcc_update gcc-4.8.2/contrib/gcc_update
    old new  
    382382        fi
    383383
    384384        revision=`$GCC_SVN info | awk '/Revision:/ { print $2 }'`
    385         branch=`$GCC_SVN info | sed -ne "/URL:/ {
     385        branch=`$GCC_SVN info | sed -ne "/^URL:/ {
    386386            s,.*/trunk,trunk,
    387387            s,.*/branches/,,
    388388            s,.*/tags/,,
  • gcc/DATESTAMP

    diff -Naur gcc-4.8.2.orig/gcc/DATESTAMP gcc-4.8.2/gcc/DATESTAMP
    old new  
    1 20131016
     120131101
  • gcc/ada/gcc-interface/utils.c

    diff -Naur gcc-4.8.2.orig/gcc/ada/gcc-interface/utils.c gcc-4.8.2/gcc/ada/gcc-interface/utils.c
    old new  
    232232static tree split_plus (tree, tree *);
    233233static tree float_type_for_precision (int, enum machine_mode);
    234234static tree convert_to_fat_pointer (tree, tree);
     235static unsigned int scale_by_factor_of (tree, unsigned int);
    235236static bool potential_alignment_gap (tree, tree, tree);
    236237static void process_attributes (tree, struct attrib *);
    237238
  • gcc/alias.c

    @@ -532,6 +533,22 @@
       free_binding_level = level;
     }
     
    
    +/* Set the context of TYPE and its parallel types (if any) to CONTEXT.  */
    +
    +static void
    +gnat_set_type_context (tree type, tree context)
    +{
    +  tree decl = TYPE_STUB_DECL (type);
    +
    +  TYPE_CONTEXT (type) = context;
    +
    +  while (decl && DECL_PARALLEL_TYPE (decl))
    +    {
    +      TYPE_CONTEXT (DECL_PARALLEL_TYPE (decl)) = context;
    +      decl = TYPE_STUB_DECL (DECL_PARALLEL_TYPE (decl));
    +    }
    +}
    +
     /* Record DECL as belonging to the current lexical scope and use GNAT_NODE
        for location information and flag propagation.  */
     
    @@ -613,7 +630,7 @@
     	      if (TREE_CODE (t) == POINTER_TYPE)
     		TYPE_NEXT_PTR_TO (t) = tt;
     	      TYPE_NAME (tt) = DECL_NAME (decl);
    -	      TYPE_CONTEXT (tt) = DECL_CONTEXT (decl);
    +	      gnat_set_type_context (tt, DECL_CONTEXT (decl));
     	      TYPE_STUB_DECL (tt) = TYPE_STUB_DECL (t);
     	      DECL_ORIGINAL_TYPE (decl) = tt;
     	    }
    @@ -623,7 +640,7 @@
     	  /* We need a variant for the placeholder machinery to work.  */
     	  tree tt = build_variant_type_copy (t);
     	  TYPE_NAME (tt) = decl;
    -	  TYPE_CONTEXT (tt) = DECL_CONTEXT (decl);
    +	  gnat_set_type_context (tt, DECL_CONTEXT (decl));
     	  TREE_USED (tt) = TREE_USED (t);
     	  TREE_TYPE (decl) = tt;
     	  if (DECL_ORIGINAL_TYPE (TYPE_NAME (t)))
    @@ -645,7 +662,7 @@
     	  if (!(TYPE_NAME (t) && TREE_CODE (TYPE_NAME (t)) == TYPE_DECL))
     	    {
     	      TYPE_NAME (t) = decl;
    -	      TYPE_CONTEXT (t) = DECL_CONTEXT (decl);
    +	      gnat_set_type_context (t, DECL_CONTEXT (decl));
     	    }
         }
     }
    @@ -1692,93 +1709,74 @@
           TYPE_SIZE_UNIT (new_record_type)
     	= size_int (TYPE_ALIGN (record_type) / BITS_PER_UNIT);
     
    -      /* Now scan all the fields, replacing each field with a new
    -	 field corresponding to the new encoding.  */
    +      /* Now scan all the fields, replacing each field with a new field
    +	 corresponding to the new encoding.  */
           for (old_field = TYPE_FIELDS (record_type); old_field;
     	   old_field = DECL_CHAIN (old_field))
     	{
     	  tree field_type = TREE_TYPE (old_field);
     	  tree field_name = DECL_NAME (old_field);
    -	  tree new_field;
     	  tree curpos = bit_position (old_field);
    +	  tree pos, new_field;
     	  bool var = false;
     	  unsigned int align = 0;
    -	  tree pos;
    -
    -	  /* See how the position was modified from the last position.
     
    -	  There are two basic cases we support: a value was added
    -	  to the last position or the last position was rounded to
    -	  a boundary and they something was added.  Check for the
    -	  first case first.  If not, see if there is any evidence
    -	  of rounding.  If so, round the last position and try
    -	  again.
    +	  /* We're going to do some pattern matching below so remove as many
    +	     conversions as possible.  */
    +	  curpos = remove_conversions (curpos, true);
     
    -	  If this is a union, the position can be taken as zero. */
    +	  /* See how the position was modified from the last position.
     
    -	  /* Some computations depend on the shape of the position expression,
    -	     so strip conversions to make sure it's exposed.  */
    -	  curpos = remove_conversions (curpos, true);
    +	     There are two basic cases we support: a value was added
    +	     to the last position or the last position was rounded to
    +	     a boundary and they something was added.  Check for the
    +	     first case first.  If not, see if there is any evidence
    +	     of rounding.  If so, round the last position and retry.
     
    +	     If this is a union, the position can be taken as zero.  */
     	  if (TREE_CODE (new_record_type) == UNION_TYPE)
    -	    pos = bitsize_zero_node, align = 0;
    +	    pos = bitsize_zero_node;
     	  else
     	    pos = compute_related_constant (curpos, last_pos);
     
    -	  if (!pos && TREE_CODE (curpos) == MULT_EXPR
    +	  if (!pos
    +	      && TREE_CODE (curpos) == MULT_EXPR
     	      && host_integerp (TREE_OPERAND (curpos, 1), 1))
     	    {
     	      tree offset = TREE_OPERAND (curpos, 0);
     	      align = tree_low_cst (TREE_OPERAND (curpos, 1), 1);
    -
    -	      /* An offset which is a bitwise AND with a mask increases the
    -		 alignment according to the number of trailing zeros.  */
    -	      offset = remove_conversions (offset, true);
    -	      if (TREE_CODE (offset) == BIT_AND_EXPR
    -		  && TREE_CODE (TREE_OPERAND (offset, 1)) == INTEGER_CST)
    -		{
    -		  unsigned HOST_WIDE_INT mask
    -		    = TREE_INT_CST_LOW (TREE_OPERAND (offset, 1));
    -		  unsigned int i;
    -
    -		  for (i = 0; i < HOST_BITS_PER_WIDE_INT; i++)
    -		    {
    -		      if (mask & 1)
    -			break;
    -		      mask >>= 1;
    -		      align *= 2;
    -		    }
    -		}
    -
    -	      pos = compute_related_constant (curpos,
    -					      round_up (last_pos, align));
    +	      align = scale_by_factor_of (offset, align);
    +	      last_pos = round_up (last_pos, align);
    +	      pos = compute_related_constant (curpos, last_pos);
     	    }
    -	  else if (!pos && TREE_CODE (curpos) == PLUS_EXPR
    -		   && TREE_CODE (TREE_OPERAND (curpos, 1)) == INTEGER_CST
    +	  else if (!pos
    +		   && TREE_CODE (curpos) == PLUS_EXPR
    +		   && host_integerp (TREE_OPERAND (curpos, 1), 1)
     		   && TREE_CODE (TREE_OPERAND (curpos, 0)) == MULT_EXPR
    -		   && host_integerp (TREE_OPERAND
    -				     (TREE_OPERAND (curpos, 0), 1),
    -				     1))
    +		   && host_integerp
    +		      (TREE_OPERAND (TREE_OPERAND (curpos, 0), 1), 1))
     	    {
    +	      tree offset = TREE_OPERAND (TREE_OPERAND (curpos, 0), 0);
    +	      unsigned HOST_WIDE_INT addend
    +	        = tree_low_cst (TREE_OPERAND (curpos, 1), 1);
     	      align
    -		= tree_low_cst
    -		(TREE_OPERAND (TREE_OPERAND (curpos, 0), 1), 1);
    -	      pos = compute_related_constant (curpos,
    -					      round_up (last_pos, align));
    +		= tree_low_cst (TREE_OPERAND (TREE_OPERAND (curpos, 0), 1), 1);
    +	      align = scale_by_factor_of (offset, align);
    +	      align = MIN (align, addend & -addend);
    +	      last_pos = round_up (last_pos, align);
    +	      pos = compute_related_constant (curpos, last_pos);
     	    }
    -	  else if (potential_alignment_gap (prev_old_field, old_field,
    -					    pos))
    +	  else if (potential_alignment_gap (prev_old_field, old_field, pos))
     	    {
     	      align = TYPE_ALIGN (field_type);
    -	      pos = compute_related_constant (curpos,
    -					      round_up (last_pos, align));
    +	      last_pos = round_up (last_pos, align);
    +	      pos = compute_related_constant (curpos, last_pos);
     	    }
     
     	  /* If we can't compute a position, set it to zero.
     
    -	  ??? We really should abort here, but it's too much work
    -	  to get this correct for all cases.  */
    -
    +	     ??? We really should abort here, but it's too much work
    +	     to get this correct for all cases.  */
     	  if (!pos)
     	    pos = bitsize_zero_node;
     
    @@ -2553,6 +2551,32 @@
       return false;
     }
     
    +/* Return VALUE scaled by the biggest power-of-2 factor of EXPR.  */
    +
    +static unsigned int
    +scale_by_factor_of (tree expr, unsigned int value)
    +{
    +  expr = remove_conversions (expr, true);
    +
    +  /* An expression which is a bitwise AND with a mask has a power-of-2 factor
    +     corresponding to the number of trailing zeros of the mask.  */
    +  if (TREE_CODE (expr) == BIT_AND_EXPR
    +      && TREE_CODE (TREE_OPERAND (expr, 1)) == INTEGER_CST)
    +    {
    +      unsigned HOST_WIDE_INT mask = TREE_INT_CST_LOW (TREE_OPERAND (expr, 1));
    +      unsigned int i = 0;
    +
    +      while ((mask & 1) == 0 && i < HOST_BITS_PER_WIDE_INT)
    +	{
    +	  mask >>= 1;
    +	  value *= 2;
    +	  i++;
    +	}
    +    }
    +
    +  return value;
    +}
    +
     /* Given two consecutive field decls PREV_FIELD and CURR_FIELD, return true
        unless we can prove these 2 fields are laid out in such a way that no gap
        exist between the end of PREV_FIELD and the beginning of CURR_FIELD.  OFFSET
    diff -Naur gcc-4.8.2.orig/gcc/alias.c gcc-4.8.2/gcc/alias.c
    old new  
    28712871      /* Wipe the reg_seen array clean.  */
    28722872      bitmap_clear (reg_seen);
    28732873
    2874       /* Mark all hard registers which may contain an address.
    2875          The stack, frame and argument pointers may contain an address.
    2876          An argument register which can hold a Pmode value may contain
    2877          an address even if it is not in BASE_REGS.
    2878 
    2879          The address expression is VOIDmode for an argument and
    2880          Pmode for other registers.  */
    2881 
    2882       memcpy (new_reg_base_value, static_reg_base_value,
    2883               FIRST_PSEUDO_REGISTER * sizeof (rtx));
     2874      /* Initialize the alias information for this pass.  */
     2875      for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
     2876        if (static_reg_base_value[i])
     2877          {
     2878            new_reg_base_value[i] = static_reg_base_value[i];
     2879            bitmap_set_bit (reg_seen, i);
     2880          }
    28842881
    28852882      /* Walk the insns adding values to the new_reg_base_value array.  */
    28862883      for (i = 0; i < rpo_cnt; i++)
  • gcc/cfgexpand.c

    diff -Naur gcc-4.8.2.orig/gcc/cfgexpand.c gcc-4.8.2/gcc/cfgexpand.c
    old new  
    47074707          if (e->insns.r)
    47084708            {
    47094709              rebuild_jump_labels_chain (e->insns.r);
    4710               /* Avoid putting insns before parm_birth_insn.  */
     4710              /* Put insns after parm birth, but before
     4711                 NOTE_INSNS_FUNCTION_BEG.  */
    47114712              if (e->src == ENTRY_BLOCK_PTR
    4712                   && single_succ_p (ENTRY_BLOCK_PTR)
    4713                   && parm_birth_insn)
     4713                  && single_succ_p (ENTRY_BLOCK_PTR))
    47144714                {
    47154715                  rtx insns = e->insns.r;
    47164716                  e->insns.r = NULL_RTX;
    4717                   emit_insn_after_noloc (insns, parm_birth_insn, e->dest);
     4717                  if (NOTE_P (parm_birth_insn)
     4718                      && NOTE_KIND (parm_birth_insn) == NOTE_INSN_FUNCTION_BEG)
     4719                    emit_insn_before_noloc (insns, parm_birth_insn, e->dest);
     4720                  else
     4721                    emit_insn_after_noloc (insns, parm_birth_insn, e->dest);
    47184722                }
    47194723              else
    47204724                commit_one_edge_insertion (e);
  • gcc/cgraph.c

    diff -Naur gcc-4.8.2.orig/gcc/cgraph.c gcc-4.8.2/gcc/cgraph.c
    old new  
    25962596  FOR_EACH_FUNCTION (node)
    25972597    verify_cgraph_node (node);
    25982598}
     2599
     2600/* Create external decl node for DECL.
     2601   The difference i nbetween cgraph_get_create_node and
     2602   cgraph_get_create_real_symbol_node is that cgraph_get_create_node
     2603   may return inline clone, while cgraph_get_create_real_symbol_node
     2604   will create a new node in this case.
     2605   FIXME: This function should be removed once clones are put out of decl
     2606   hash.  */
     2607
     2608struct cgraph_node *
     2609cgraph_get_create_real_symbol_node (tree decl)
     2610{
     2611  struct cgraph_node *first_clone = cgraph_get_node (decl);
     2612  struct cgraph_node *node;
     2613  /* create symbol table node.  even if inline clone exists, we can not take
     2614     it as a target of non-inlined call.  */
     2615  node = cgraph_get_node (decl);
     2616  if (node && !node->global.inlined_to)
     2617    return node;
     2618
     2619  node = cgraph_create_node (decl);
     2620
     2621  /* ok, we previously inlined the function, then removed the offline copy and
     2622     now we want it back for external call.  this can happen when devirtualizing
     2623     while inlining function called once that happens after extern inlined and
     2624     virtuals are already removed.  in this case introduce the external node
     2625     and make it available for call.  */
     2626  if (first_clone)
     2627    {
     2628      first_clone->clone_of = node;
     2629      node->clones = first_clone;
     2630      symtab_prevail_in_asm_name_hash ((symtab_node) node);
     2631      symtab_insert_node_to_hashtable ((symtab_node) node);
     2632      if (dump_file)
     2633        fprintf (dump_file, "Introduced new external node "
     2634                 "(%s/%i) and turned into root of the clone tree.\n",
     2635                 xstrdup (cgraph_node_name (node)), node->uid);
     2636    }
     2637  else if (dump_file)
     2638    fprintf (dump_file, "Introduced new external node "
     2639             "(%s/%i).\n", xstrdup (cgraph_node_name (node)), node->uid);
     2640  return node;
     2641}
    25992642#include "gt-cgraph.h"
  • gcc/cgraph.h

    diff -Naur gcc-4.8.2.orig/gcc/cgraph.h gcc-4.8.2/gcc/cgraph.h
    old new  
    575575struct cgraph_node * cgraph_create_node (tree);
    576576struct cgraph_node * cgraph_create_empty_node (void);
    577577struct cgraph_node * cgraph_get_create_node (tree);
     578struct cgraph_node * cgraph_get_create_real_symbol_node (tree);
    578579struct cgraph_node * cgraph_same_body_alias (struct cgraph_node *, tree, tree);
    579580struct cgraph_node * cgraph_add_thunk (struct cgraph_node *, tree, tree, bool, HOST_WIDE_INT,
    580581                                       HOST_WIDE_INT, tree, tree);
  • gcc/cgraphbuild.c

    diff -Naur gcc-4.8.2.orig/gcc/cgraphbuild.c gcc-4.8.2/gcc/cgraphbuild.c
    old new  
    7373      decl = get_base_var (*tp);
    7474      if (TREE_CODE (decl) == FUNCTION_DECL)
    7575        {
    76           struct cgraph_node *node = cgraph_get_create_node (decl);
     76          struct cgraph_node *node = cgraph_get_create_real_symbol_node (decl);
    7777          if (!ctx->only_vars)
    7878            cgraph_mark_address_taken_node (node);
    7979          ipa_record_reference ((symtab_node)ctx->varpool_node,
     
    143143    {
    144144      struct cgraph_node *per_node;
    145145
    146       per_node = cgraph_get_create_node (DECL_FUNCTION_PERSONALITY (node->symbol.decl));
     146      per_node = cgraph_get_create_real_symbol_node (DECL_FUNCTION_PERSONALITY (node->symbol.decl));
    147147      ipa_record_reference ((symtab_node)node, (symtab_node)per_node, IPA_REF_ADDR, NULL);
    148148      cgraph_mark_address_taken_node (per_node);
    149149    }
     
    223223  addr = get_base_address (addr);
    224224  if (TREE_CODE (addr) == FUNCTION_DECL)
    225225    {
    226       struct cgraph_node *node = cgraph_get_create_node (addr);
     226      struct cgraph_node *node = cgraph_get_create_real_symbol_node (addr);
    227227      cgraph_mark_address_taken_node (node);
    228228      ipa_record_reference ((symtab_node)data,
    229229                            (symtab_node)node,
     
    252252    {
    253253      /* ??? This can happen on platforms with descriptors when these are
    254254         directly manipulated in the code.  Pretend that it's an address.  */
    255       struct cgraph_node *node = cgraph_get_create_node (t);
     255      struct cgraph_node *node = cgraph_get_create_real_symbol_node (t);
    256256      cgraph_mark_address_taken_node (node);
    257257      ipa_record_reference ((symtab_node)data,
    258258                            (symtab_node)node,
     
    330330            {
    331331              tree fn = gimple_omp_parallel_child_fn (stmt);
    332332              ipa_record_reference ((symtab_node)node,
    333                                     (symtab_node)cgraph_get_create_node (fn),
     333                                    (symtab_node)cgraph_get_create_real_symbol_node (fn),
    334334                                    IPA_REF_ADDR, stmt);
    335335            }
    336336          if (gimple_code (stmt) == GIMPLE_OMP_TASK)
     
    338338              tree fn = gimple_omp_task_child_fn (stmt);
    339339              if (fn)
    340340                ipa_record_reference ((symtab_node)node,
    341                                       (symtab_node) cgraph_get_create_node (fn),
     341                                      (symtab_node) cgraph_get_create_real_symbol_node (fn),
    342342                                      IPA_REF_ADDR, stmt);
    343343              fn = gimple_omp_task_copy_fn (stmt);
    344344              if (fn)
    345345                ipa_record_reference ((symtab_node)node,
    346                                       (symtab_node)cgraph_get_create_node (fn),
     346                                      (symtab_node)cgraph_get_create_real_symbol_node (fn),
    347347                                      IPA_REF_ADDR, stmt);
    348348            }
    349349        }
  • gcc/combine.c

    diff -Naur gcc-4.8.2.orig/gcc/combine.c gcc-4.8.2/gcc/combine.c
    old new  
    57985798                return x;
    57995799            }
    58005800
    5801           /* If the code changed, return a whole new comparison.  */
    5802           if (new_code != code)
     5801          /* If the code changed, return a whole new comparison.
     5802             We also need to avoid using SUBST in cases where
     5803             simplify_comparison has widened a comparison with a CONST_INT,
     5804             since in that case the wider CONST_INT may fail the sanity
     5805             checks in do_SUBST.  */
     5806          if (new_code != code
     5807              || (CONST_INT_P (op1)
     5808                  && GET_MODE (op0) != GET_MODE (XEXP (x, 0))
     5809                  && GET_MODE (op0) != GET_MODE (XEXP (x, 1))))
    58035810            return gen_rtx_fmt_ee (new_code, mode, op0, op1);
    58045811
    58055812          /* Otherwise, keep this operation, but maybe change its operands.
  • gcc/config/i386/i386.c

    diff -Naur gcc-4.8.2.orig/gcc/config/i386/i386.c gcc-4.8.2/gcc/config/i386/i386.c
    old new  
    29832983      {"bdver3", PROCESSOR_BDVER3, CPU_BDVER3,
    29842984        PTA_64BIT | PTA_MMX | PTA_SSE | PTA_SSE2 | PTA_SSE3
    29852985        | PTA_SSE4A | PTA_CX16 | PTA_ABM | PTA_SSSE3 | PTA_SSE4_1
    2986         | PTA_SSE4_2 | PTA_AES | PTA_PCLMUL | PTA_AVX
     2986        | PTA_SSE4_2 | PTA_AES | PTA_PCLMUL | PTA_AVX | PTA_FMA4
    29872987        | PTA_XOP | PTA_LWP | PTA_BMI | PTA_TBM | PTA_F16C
    29882988        | PTA_FMA | PTA_PRFCHW | PTA_FXSR | PTA_XSAVE
    29892989        | PTA_XSAVEOPT},
     
    72357235  switch (regno)
    72367236    {
    72377237    case AX_REG:
     7238    case DX_REG:
    72387239      return true;
    7239 
    7240     case FIRST_FLOAT_REG:
     7240    case DI_REG:
     7241    case SI_REG:
     7242      return TARGET_64BIT && ix86_abi != MS_ABI;
     7243
     7244      /* Complex values are returned in %st(0)/%st(1) pair.  */
     7245    case ST0_REG:
     7246    case ST1_REG:
    72417247      /* TODO: The function should depend on current function ABI but
    72427248       builtins.c would need updating then. Therefore we use the
    72437249       default ABI.  */
     
    72457251        return false;
    72467252      return TARGET_FLOAT_RETURNS_IN_80387;
    72477253
    7248     case FIRST_SSE_REG:
     7254      /* Complex values are returned in %xmm0/%xmm1 pair.  */
     7255    case XMM0_REG:
     7256    case XMM1_REG:
    72497257      return TARGET_SSE;
    72507258
    7251     case FIRST_MMX_REG:
     7259    case MM0_REG:
    72527260      if (TARGET_MACHO || TARGET_64BIT)
    72537261        return false;
    72547262      return TARGET_MMX;
     
    1381713825         Those same assemblers have the same but opposite lossage on cmov.  */
    1381813826      if (mode == CCmode)
    1381913827        suffix = fp ? "nbe" : "a";
    13820       else if (mode == CCCmode)
    13821         suffix = "b";
    1382213828      else
    1382313829        gcc_unreachable ();
    1382413830      break;
     
    1384013846        }
    1384113847      break;
    1384213848    case LTU:
    13843       gcc_assert (mode == CCmode || mode == CCCmode);
    13844       suffix = "b";
     13849      if (mode == CCmode)
     13850        suffix = "b";
     13851      else if (mode == CCCmode)
     13852        suffix = "c";
     13853      else
     13854        gcc_unreachable ();
    1384513855      break;
    1384613856    case GE:
    1384713857      switch (mode)
     
    1386113871        }
    1386213872      break;
    1386313873    case GEU:
    13864       /* ??? As above.  */
    13865       gcc_assert (mode == CCmode || mode == CCCmode);
    13866       suffix = fp ? "nb" : "ae";
     13874      if (mode == CCmode)
     13875        suffix = fp ? "nb" : "ae";
     13876      else if (mode == CCCmode)
     13877        suffix = "nc";
     13878      else
     13879        gcc_unreachable ();
    1386713880      break;
    1386813881    case LE:
    1386913882      gcc_assert (mode == CCmode || mode == CCGCmode || mode == CCNOmode);
    1387013883      suffix = "le";
    1387113884      break;
    1387213885    case LEU:
    13873       /* ??? As above.  */
    1387413886      if (mode == CCmode)
    1387513887        suffix = "be";
    13876       else if (mode == CCCmode)
    13877         suffix = fp ? "nb" : "ae";
    1387813888      else
    1387913889        gcc_unreachable ();
    1388013890      break;
     
    1848618496        return CCmode;
    1848718497    case GTU:                   /* CF=0 & ZF=0 */
    1848818498    case LEU:                   /* CF=1 | ZF=1 */
    18489       /* Detect overflow checks.  They need just the carry flag.  */
    18490       if (GET_CODE (op0) == MINUS
    18491           && rtx_equal_p (op1, XEXP (op0, 0)))
    18492         return CCCmode;
    18493       else
    18494         return CCmode;
     18499      return CCmode;
    1849518500      /* Codes possibly doable only with sign flag when
    1849618501         comparing against zero.  */
    1849718502    case GE:                    /* SF=OF   or   SF=0 */
  • gcc/config/i386/i386.md

    diff -Naur gcc-4.8.2.orig/gcc/config/i386/i386.md gcc-4.8.2/gcc/config/i386/i386.md
    old new  
    65896589   (set_attr "use_carry" "1")
    65906590   (set_attr "mode" "<MODE>")])
    65916591
    65926592
    6593 ;; Overflow setting add and subtract instructions
     6593;; Overflow setting add instructions
    65946594
    65956595(define_insn "*add<mode>3_cconly_overflow"
  • gcc/config/rs6000/rs6000.md

       [(set (reg:CCC FLAGS_REG)
    @@ -6604,43 +6604,31 @@
       [(set_attr "type" "alu")
        (set_attr "mode" "<MODE>")])
     
    -(define_insn "*sub<mode>3_cconly_overflow"
    +(define_insn "*add<mode>3_cc_overflow"
       [(set (reg:CCC FLAGS_REG)
     	(compare:CCC
    -	  (minus:SWI
    -	    (match_operand:SWI 0 "nonimmediate_operand" "<r>m,<r>")
    -	    (match_operand:SWI 1 "<general_operand>" "<r><i>,<r>m"))
    -	  (match_dup 0)))]
    -  ""
    -  "cmp{<imodesuffix>}\t{%1, %0|%0, %1}"
    -  [(set_attr "type" "icmp")
    -   (set_attr "mode" "<MODE>")])
    -
    -(define_insn "*<plusminus_insn><mode>3_cc_overflow"
    -  [(set (reg:CCC FLAGS_REG)
    -	(compare:CCC
    -	    (plusminus:SWI
    -		(match_operand:SWI 1 "nonimmediate_operand" "<comm>0,0")
    +	    (plus:SWI
    +		(match_operand:SWI 1 "nonimmediate_operand" "%0,0")
     		(match_operand:SWI 2 "<general_operand>" "<r><i>,<r>m"))
     	    (match_dup 1)))
        (set (match_operand:SWI 0 "nonimmediate_operand" "=<r>m,<r>")
    -	(plusminus:SWI (match_dup 1) (match_dup 2)))]
    -  "ix86_binary_operator_ok (<CODE>, <MODE>mode, operands)"
    -  "<plusminus_mnemonic>{<imodesuffix>}\t{%2, %0|%0, %2}"
    +	(plus:SWI (match_dup 1) (match_dup 2)))]
    +  "ix86_binary_operator_ok (PLUS, <MODE>mode, operands)"
    +  "add{<imodesuffix>}\t{%2, %0|%0, %2}"
       [(set_attr "type" "alu")
        (set_attr "mode" "<MODE>")])
     
    -(define_insn "*<plusminus_insn>si3_zext_cc_overflow"
    +(define_insn "*addsi3_zext_cc_overflow"
       [(set (reg:CCC FLAGS_REG)
     	(compare:CCC
    -	  (plusminus:SI
    -	    (match_operand:SI 1 "nonimmediate_operand" "<comm>0")
    +	  (plus:SI
    +	    (match_operand:SI 1 "nonimmediate_operand" "%0")
     	    (match_operand:SI 2 "x86_64_general_operand" "rme"))
     	  (match_dup 1)))
        (set (match_operand:DI 0 "register_operand" "=r")
    -	(zero_extend:DI (plusminus:SI (match_dup 1) (match_dup 2))))]
    -  "TARGET_64BIT && ix86_binary_operator_ok (<CODE>, SImode, operands)"
    -  "<plusminus_mnemonic>{l}\t{%2, %k0|%k0, %2}"
    +	(zero_extend:DI (plus:SI (match_dup 1) (match_dup 2))))]
    +  "TARGET_64BIT && ix86_binary_operator_ok (PLUS, SImode, operands)"
    +  "add{l}\t{%2, %k0|%k0, %2}"
       [(set_attr "type" "alu")
        (set_attr "mode" "SI")])
     
    diff -Naur gcc-4.8.2.orig/gcc/config/rs6000/rs6000.md gcc-4.8.2/gcc/config/rs6000/rs6000.md
    old new  
    24122412                             (match_operand:SI 2 "gpc_reg_operand" "r,r"))
    24132413                    (const_int 0)))
    24142414   (clobber (match_scratch:SI 3 "=r,r"))]
    2415   ""
     2415  "TARGET_32BIT"
    24162416  "@
    24172417   mullw. %3,%1,%2
    24182418   #"
     
    24252425                             (match_operand:SI 2 "gpc_reg_operand" ""))
    24262426                    (const_int 0)))
    24272427   (clobber (match_scratch:SI 3 ""))]
    2428   "reload_completed"
     2428  "TARGET_32BIT && reload_completed"
    24292429  [(set (match_dup 3)
    24302430        (mult:SI (match_dup 1) (match_dup 2)))
    24312431   (set (match_dup 0)
     
    24402440                    (const_int 0)))
    24412441   (set (match_operand:SI 0 "gpc_reg_operand" "=r,r")
    24422442        (mult:SI (match_dup 1) (match_dup 2)))]
    2443   ""
     2443  "TARGET_32BIT"
    24442444  "@
    24452445   mullw. %0,%1,%2
    24462446   #"
     
    24542454                    (const_int 0)))
    24552455   (set (match_operand:SI 0 "gpc_reg_operand" "")
    24562456        (mult:SI (match_dup 1) (match_dup 2)))]
    2457   "reload_completed"
     2457  "TARGET_32BIT && reload_completed"
    24582458  [(set (match_dup 0)
    24592459        (mult:SI (match_dup 1) (match_dup 2)))
    24602460   (set (match_dup 3)
  • gcc/config/sh/sh.opt

    diff -Naur gcc-4.8.2.orig/gcc/config/sh/sh.opt gcc-4.8.2/gcc/config/sh/sh.opt
    old new  
    2121;; Used for various architecture options.
    2222Mask(SH_E)
    2323
    24 ;; Set if the default precision of th FPU is single.
     24;; Set if the default precision of the FPU is single.
    2525Mask(FPU_SINGLE)
    2626
    2727;; Set if the a double-precision FPU is present but is restricted to
  • gcc/cp/decl2.c

    diff -Naur gcc-4.8.2.orig/gcc/cp/decl2.c gcc-4.8.2/gcc/cp/decl2.c
    old new  
    39603960  expand_or_defer_fn (finish_function (0));
    39613961}
    39623962
     3963/* The entire file is now complete.  If requested, dump everything
     3964   to a file.  */
     3965
     3966static void
     3967dump_tu (void)
     3968{
     3969  int flags;
     3970  FILE *stream = dump_begin (TDI_tu, &flags);
     3971
     3972  if (stream)
     3973    {
     3974      dump_node (global_namespace, flags & ~TDF_SLIM, stream);
     3975      dump_end (TDI_tu, stream);
     3976    }
     3977}
     3978
    39633979/* This routine is called at the end of compilation.
    39643980   Its job is to create all the code needed to initialize and
    39653981   destroy the global aggregates.  We do the destruction
     
    39904006  if (pch_file)
    39914007    {
    39924008      c_common_write_pch ();
     4009      dump_tu ();
    39934010      return;
    39944011    }
    39954012
     
    43594376
    43604377  /* The entire file is now complete.  If requested, dump everything
    43614378     to a file.  */
    4362   {
    4363     int flags;
    4364     FILE *stream = dump_begin (TDI_tu, &flags);
    4365 
    4366     if (stream)
    4367       {
    4368         dump_node (global_namespace, flags & ~TDF_SLIM, stream);
    4369         dump_end (TDI_tu, stream);
    4370       }
    4371   }
     4379  dump_tu ();
    43724380
    43734381  if (flag_detailed_statistics)
    43744382    {
  • gcc/cp/except.c

    diff -Naur gcc-4.8.2.orig/gcc/cp/except.c gcc-4.8.2/gcc/cp/except.c
    old new  
    380380{
    381381  tree type = body ? TREE_TYPE (body) : void_type_node;
    382382
     383  if (!flag_exceptions)
     384    return body;
     385
    383386  if (cond && !value_dependent_expression_p (cond))
    384387    {
    385388      cond = cxx_constant_value (cond);
  • gcc/cp/parser.c

    diff -Naur gcc-4.8.2.orig/gcc/cp/parser.c gcc-4.8.2/gcc/cp/parser.c
    old new  
    64216421  /* Look for the `~'.  */
    64226422  cp_parser_require (parser, CPP_COMPL, RT_COMPL);
    64236423
    6424   /* Once we see the ~, this has to be a pseudo-destructor.  */
    6425   if (!processing_template_decl && !cp_parser_error_occurred (parser))
    6426     cp_parser_commit_to_tentative_parse (parser);
    6427 
    64286424  /* Look for the type-name again.  We are not responsible for
    64296425     checking that it matches the first type-name.  */
    64306426  *type = cp_parser_nonclass_name (parser);
  • gcc/cp/semantics.c

    diff -Naur gcc-4.8.2.orig/gcc/cp/semantics.c gcc-4.8.2/gcc/cp/semantics.c
    old new  
    94819481  /* In unevaluated context this isn't an odr-use, so just return the
    94829482     nearest 'this'.  */
    94839483  if (cp_unevaluated_operand)
    9484     return lookup_name (this_identifier);
     9484    {
     9485      /* In an NSDMI the fake 'this' pointer that we're using for
     9486         parsing is in scope_chain.  */
     9487      if (LAMBDA_EXPR_EXTRA_SCOPE (lambda)
     9488          && TREE_CODE (LAMBDA_EXPR_EXTRA_SCOPE (lambda)) == FIELD_DECL)
     9489        return scope_chain->x_current_class_ptr;
     9490      return lookup_name (this_identifier);
     9491    }
    94859492
    94869493  /* Try to default capture 'this' if we can.  */
    94879494  if (!this_capture
  • gcc/gimple-fold.c

    diff -Naur gcc-4.8.2.orig/gcc/gimple-fold.c gcc-4.8.2/gcc/gimple-fold.c
    old new  
    178178          /* Make sure we create a cgraph node for functions we'll reference.
    179179             They can be non-existent if the reference comes from an entry
    180180             of an external vtable for example.  */
    181           cgraph_get_create_node (base);
     181          cgraph_get_create_real_symbol_node (base);
    182182        }
    183183      /* Fixup types in global initializers.  */
    184184      if (TREE_TYPE (TREE_TYPE (cval)) != TREE_TYPE (TREE_OPERAND (cval, 0)))
  • gcc/go/go-gcc.cc

    diff -Naur gcc-4.8.2.orig/gcc/go/go-gcc.cc gcc-4.8.2/gcc/go/go-gcc.cc
    old new  
    232232  Bexpression*
    233233  convert_expression(Btype* type, Bexpression* expr, Location);
    234234
     235  Bexpression*
     236  function_code_expression(Bfunction*, Location);
     237
    235238  // Statements.
    236239
    237240  Bstatement*
     
    334337  Bexpression*
    335338  label_address(Blabel*, Location);
    336339
     340  // Functions.
     341
     342  Bfunction*
     343  error_function()
     344  { return this->make_function(error_mark_node); }
     345
     346  Bfunction*
     347  function(Btype* fntype, const std::string& name, const std::string& asm_name,
     348           bool is_visible, bool is_declaration, bool is_inlinable,
     349           bool disable_split_stack, bool in_unique_section, Location);
     350
    337351 private:
    338352  // Make a Bexpression from a tree.
    339353  Bexpression*
     
    350364  make_type(tree t)
    351365  { return new Btype(t); }
    352366
     367  Bfunction*
     368  make_function(tree t)
     369  { return new Bfunction(t); }
     370
    353371  Btype*
    354372  fill_in_struct(Btype*, const std::vector<Btyped_identifier>&);
    355373
     
    966984  return tree_to_expr(ret);
    967985}
    968986
     987// Get the address of a function.
     988
     989Bexpression*
     990Gcc_backend::function_code_expression(Bfunction* bfunc, Location location)
     991{
     992  tree func = bfunc->get_tree();
     993  if (func == error_mark_node)
     994    return this->error_expression();
     995
     996  tree ret = build_fold_addr_expr_loc(location.gcc_location(), func);
     997  return this->make_expression(ret);
     998}
     999
    9691000// An expression as a statement.
    9701001
    9711002Bstatement*
     
    17241755  return this->make_expression(ret);
    17251756}
    17261757
     1758// Declare or define a new function.
     1759
     1760Bfunction*
     1761Gcc_backend::function(Btype* fntype, const std::string& name,
     1762                      const std::string& asm_name, bool is_visible,
     1763                      bool is_declaration, bool is_inlinable,
     1764                      bool disable_split_stack, bool in_unique_section,
     1765                      Location location)
     1766{
     1767  tree functype = fntype->get_tree();
     1768  if (functype != error_mark_node)
     1769    {
     1770      gcc_assert(FUNCTION_POINTER_TYPE_P(functype));
     1771      functype = TREE_TYPE(functype);
     1772    }
     1773  tree id = get_identifier_from_string(name);
     1774  if (functype == error_mark_node || id == error_mark_node)
     1775    return this->error_function();
     1776
     1777  tree decl = build_decl(location.gcc_location(), FUNCTION_DECL, id, functype);
     1778  if (!asm_name.empty())
     1779    SET_DECL_ASSEMBLER_NAME(decl, get_identifier_from_string(asm_name));
     1780  if (is_visible)
     1781    TREE_PUBLIC(decl) = 1;
     1782  if (is_declaration)
     1783    DECL_EXTERNAL(decl) = 1;
     1784  else
     1785    {
     1786      tree restype = TREE_TYPE(functype);
     1787      tree resdecl =
     1788          build_decl(location.gcc_location(), RESULT_DECL, NULL_TREE, restype);
     1789      DECL_ARTIFICIAL(resdecl) = 1;
     1790      DECL_IGNORED_P(resdecl) = 1;
     1791      DECL_CONTEXT(resdecl) = decl;
     1792      DECL_RESULT(decl) = resdecl;
     1793    }
     1794  if (!is_inlinable)
     1795    DECL_UNINLINABLE(decl) = 1;
     1796  if (disable_split_stack)
     1797    {
     1798      tree attr = get_identifier("__no_split_stack__");
     1799      DECL_ATTRIBUTES(decl) = tree_cons(attr, NULL_TREE, NULL_TREE);
     1800    }
     1801  if (in_unique_section)
     1802    resolve_unique_section(decl, 0, 1);
     1803
     1804  go_preserve_from_gc(decl);
     1805  return new Bfunction(decl);
     1806}
     1807
    17271808// The single backend.
    17281809
    17291810static Gcc_backend gcc_backend;
     
    17991880{
    18001881  return bv->get_tree();
    18011882}
     1883
     1884tree
     1885function_to_tree(Bfunction* bf)
     1886{
     1887  return bf->get_tree();
     1888}
  • gcc/go/gofrontend/backend.h

    diff -Naur gcc-4.8.2.orig/gcc/go/gofrontend/backend.h gcc-4.8.2/gcc/go/gofrontend/backend.h
    old new  
    2323// The backend representation of a statement.
    2424class Bstatement;
    2525
    26 // The backend representation of a function definition.
     26// The backend representation of a function definition or declaration.
    2727class Bfunction;
    2828
    2929// The backend representation of a block.
     
    266266  virtual Bexpression*
    267267  convert_expression(Btype* type, Bexpression* expr, Location) = 0;
    268268
     269  // Create an expression for the address of a function.  This is used to
     270  // get the address of the code for a function.
     271  virtual Bexpression*
     272  function_code_expression(Bfunction*, Location) = 0;
     273
    269274  // Statements.
    270275
    271276  // Create an error statement.  This is used for cases which should
     
    498503  // recover.
    499504  virtual Bexpression*
    500505  label_address(Blabel*, Location) = 0;
     506
     507  // Functions.
     508
     509  // Create an error function.  This is used for cases which should
     510  // not occur in a correct program, in order to keep the compilation
     511  // going without crashing.
     512  virtual Bfunction*
     513  error_function() = 0;
     514
     515  // Declare or define a function of FNTYPE.
     516  // NAME is the Go name of the function. ASM_NAME, if not the empty string, is
     517  // the name that should be used in the symbol table; this will be non-empty if
     518  // a magic extern comment is used.
     519  // IS_VISIBLE is true if this function should be visible outside of the
     520  // current compilation unit. IS_DECLARATION is true if this is a function
     521  // declaration rather than a definition; the function definition will be in
     522  // another compilation unit.
     523  // IS_INLINABLE is true if the function can be inlined.
     524  // DISABLE_SPLIT_STACK is true if this function may not split the stack; this
     525  // is used for the implementation of recover.
     526  // IN_UNIQUE_SECTION is true if this function should be put into a unique
     527  // location if possible; this is used for field tracking.
     528  virtual Bfunction*
     529  function(Btype* fntype, const std::string& name, const std::string& asm_name,
     530           bool is_visible, bool is_declaration, bool is_inlinable,
     531           bool disable_split_stack, bool in_unique_section, Location) = 0;
    501532};
    502533
    503534// The backend interface has to define this function.
     
    517548extern tree stat_to_tree(Bstatement*);
    518549extern tree block_to_tree(Bblock*);
    519550extern tree var_to_tree(Bvariable*);
     551extern tree function_to_tree(Bfunction*);
    520552
    521553#endif // !defined(GO_BACKEND_H)
  • gcc/go/gofrontend/expressions.cc

    diff -Naur gcc-4.8.2.orig/gcc/go/gofrontend/expressions.cc gcc-4.8.2/gcc/go/gofrontend/expressions.cc
    old new  
    12191219
    12201220// Get the tree for the code of a function expression.
    12211221
    1222 tree
     1222Bexpression*
    12231223Func_expression::get_code_pointer(Gogo* gogo, Named_object* no, Location loc)
    12241224{
    12251225  Function_type* fntype;
     
    12371237      error_at(loc,
    12381238               "invalid use of special builtin function %qs; must be called",
    12391239               no->message_name().c_str());
    1240       return error_mark_node;
     1240      return gogo->backend()->error_expression();
    12411241    }
    12421242
    1243   tree id = no->get_id(gogo);
    1244   if (id == error_mark_node)
    1245     return error_mark_node;
    1246 
    1247   tree fndecl;
     1243  Bfunction* fndecl;
    12481244  if (no->is_function())
    1249     fndecl = no->func_value()->get_or_make_decl(gogo, no, id);
     1245    fndecl = no->func_value()->get_or_make_decl(gogo, no);
    12501246  else if (no->is_function_declaration())
    1251     fndecl = no->func_declaration_value()->get_or_make_decl(gogo, no, id);
     1247    fndecl = no->func_declaration_value()->get_or_make_decl(gogo, no);
    12521248  else
    12531249    go_unreachable();
    12541250
    1255   if (fndecl == error_mark_node)
    1256     return error_mark_node;
    1257 
    1258   return build_fold_addr_expr_loc(loc.gcc_location(), fndecl);
     1251  return gogo->backend()->function_code_expression(fndecl, loc);
    12591252}
    12601253
    12611254// Get the tree for a function expression.  This is used when we take
     
    14921485tree
    14931486Func_code_reference_expression::do_get_tree(Translate_context* context)
    14941487{
    1495   return Func_expression::get_code_pointer(context->gogo(), this->function_,
    1496                                            this->location());
     1488  Bexpression* ret =
     1489      Func_expression::get_code_pointer(context->gogo(), this->function_,
     1490                                        this->location());
     1491  return expr_to_tree(ret);
    14971492}
    14981493
    14991494// Make a reference to the code of a function.
     
    30553050  do_lower(Gogo*, Named_object*, Statement_inserter*, int);
    30563051
    30573052  bool
    3058   do_is_constant() const
    3059   { return this->expr_->is_constant(); }
     3053  do_is_constant() const;
    30603054
    30613055  bool
    30623056  do_numeric_constant_value(Numeric_constant*) const;
     
    31983192  return this;
    31993193}
    32003194
     3195// Return whether a type conversion is a constant.
     3196
     3197bool
     3198Type_conversion_expression::do_is_constant() const
     3199{
     3200  if (!this->expr_->is_constant())
     3201    return false;
     3202
     3203  // A conversion to a type that may not be used as a constant is not
     3204  // a constant.  For example, []byte(nil).
     3205  Type* type = this->type_;
     3206  if (type->integer_type() == NULL
     3207      && type->float_type() == NULL
     3208      && type->complex_type() == NULL
     3209      && !type->is_boolean_type()
     3210      && !type->is_string_type())
     3211    return false;
     3212
     3213  return true;
     3214}
     3215
    32013216// Return the constant numeric value if there is one.
    32023217
    32033218bool
     
    55865601      subcontext.type = NULL;
    55875602    }
    55885603
     5604  if (this->op_ == OPERATOR_ANDAND || this->op_ == OPERATOR_OROR)
     5605    {
     5606      // For a logical operation, the context does not determine the
     5607      // types of the operands.  The operands must be some boolean
     5608      // type but if the context has a boolean type they do not
     5609      // inherit it.  See http://golang.org/issue/3924.
     5610      subcontext.type = NULL;
     5611    }
     5612
    55895613  // Set the context for the left hand operand.
    55905614  if (is_shift_op)
    55915615    {
     
    59675991                                right);
    59685992    }
    59695993
     5994  // For complex division Go wants slightly different results than the
     5995  // GCC library provides, so we have our own runtime routine.
     5996  if (this->op_ == OPERATOR_DIV && this->left_->type()->complex_type() != NULL)
     5997    {
     5998      const char *name;
     5999      tree *pdecl;
     6000      Type* ctype;
     6001      static tree complex64_div_decl;
     6002      static tree complex128_div_decl;
     6003      switch (this->left_->type()->complex_type()->bits())
     6004        {
     6005        case 64:
     6006          name = "__go_complex64_div";
     6007          pdecl = &complex64_div_decl;
     6008          ctype = Type::lookup_complex_type("complex64");
     6009          break;
     6010        case 128:
     6011          name = "__go_complex128_div";
     6012          pdecl = &complex128_div_decl;
     6013          ctype = Type::lookup_complex_type("complex128");
     6014          break;
     6015        default:
     6016          go_unreachable();
     6017        }
     6018      Btype* cbtype = ctype->get_backend(gogo);
     6019      tree ctype_tree = type_to_tree(cbtype);
     6020      return Gogo::call_builtin(pdecl,
     6021                                this->location(),
     6022                                name,
     6023                                2,
     6024                                ctype_tree,
     6025                                ctype_tree,
     6026                                fold_convert_loc(gccloc, ctype_tree, left),
     6027                                type,
     6028                                fold_convert_loc(gccloc, ctype_tree, right));
     6029    }
     6030
    59706031  tree compute_type = excess_precision_type(type);
    59716032  if (compute_type != NULL_TREE)
    59726033    {
     
    71917252  if (this->code_ == BUILTIN_OFFSETOF)
    71927253    {
    71937254      Expression* arg = this->one_arg();
     7255
     7256      if (arg->bound_method_expression() != NULL
     7257          || arg->interface_field_reference_expression() != NULL)
     7258        {
     7259          this->report_error(_("invalid use of method value as argument "
     7260                               "of Offsetof"));
     7261          return this;
     7262        }
     7263
    71947264      Field_reference_expression* farg = arg->field_reference_expression();
    71957265      while (farg != NULL)
    71967266        {
     
    72007270          // it must not be reached through pointer indirections.
    72017271          if (farg->expr()->deref() != farg->expr())
    72027272            {
    7203               this->report_error(_("argument of Offsetof implies indirection of an embedded field"));
     7273              this->report_error(_("argument of Offsetof implies "
     7274                                   "indirection of an embedded field"));
    72047275              return this;
    72057276            }
    72067277          // Go up until we reach the original base.
     
    74767547      switch (nc.to_unsigned_long(&v))
    74777548        {
    74787549        case Numeric_constant::NC_UL_VALID:
    7479           return true;
     7550          break;
    74807551        case Numeric_constant::NC_UL_NOTINT:
    74817552          error_at(e->location(), "non-integer %s argument to make",
    74827553                   is_length ? "len" : "cap");
     
    74887559        case Numeric_constant::NC_UL_BIG:
    74897560          // We don't want to give a compile-time error for a 64-bit
    74907561          // value on a 32-bit target.
    7491           return true;
     7562          break;
    74927563        }
     7564
     7565      mpz_t val;
     7566      if (!nc.to_int(&val))
     7567        go_unreachable();
     7568      int bits = mpz_sizeinbase(val, 2);
     7569      mpz_clear(val);
     7570      Type* int_type = Type::lookup_integer_type("int");
     7571      if (bits >= int_type->integer_type()->bits())
     7572        {
     7573          error_at(e->location(), "%s argument too large for make",
     7574                   is_length ? "len" : "cap");
     7575          return false;
     7576        }
     7577
     7578      return true;
    74937579    }
    74947580
    74957581  if (e->type()->integer_type() != NULL)
     
    75957681bool
    75967682Builtin_call_expression::do_is_constant() const
    75977683{
     7684  if (this->is_error_expression())
     7685    return true;
    75987686  switch (this->code_)
    75997687    {
    76007688    case BUILTIN_LEN:
     
    97449832    }
    97459833
    97469834  tree fntype_tree = type_to_tree(fntype->get_backend(gogo));
    9747   if (fntype_tree == error_mark_node)
    9748     return error_mark_node;
    9749   go_assert(POINTER_TYPE_P(fntype_tree));
    9750   if (TREE_TYPE(fntype_tree) == error_mark_node)
    9751     return error_mark_node;
    9752   go_assert(TREE_CODE(TREE_TYPE(fntype_tree)) == RECORD_TYPE);
    9753   tree fnfield_type = TREE_TYPE(TYPE_FIELDS(TREE_TYPE(fntype_tree)));
    9754   if (fnfield_type == error_mark_node)
     9835  tree fnfield_type = type_to_tree(fntype->get_backend_fntype(gogo));
     9836  if (fntype_tree == error_mark_node || fnfield_type == error_mark_node)
    97559837    return error_mark_node;
    97569838  go_assert(FUNCTION_POINTER_TYPE_P(fnfield_type));
    97579839  tree rettype = TREE_TYPE(TREE_TYPE(fnfield_type));
     
    97639845  if (func != NULL)
    97649846    {
    97659847      Named_object* no = func->named_object();
    9766       fn = Func_expression::get_code_pointer(gogo, no, location);
     9848      fn = expr_to_tree(Func_expression::get_code_pointer(gogo, no, location));
    97679849      if (!has_closure)
    97689850        closure_tree = NULL_TREE;
    97699851      else
     
    1081710899void
    1081810900String_index_expression::do_check_types(Gogo*)
    1081910901{
    10820   if (this->start_->type()->integer_type() == NULL)
     10902  Numeric_constant nc;
     10903  unsigned long v;
     10904  if (this->start_->type()->integer_type() == NULL
     10905      && !this->start_->type()->is_error()
     10906      && (!this->start_->numeric_constant_value(&nc)
     10907          || nc.to_unsigned_long(&v) == Numeric_constant::NC_UL_NOTINT))
    1082110908    this->report_error(_("index must be integer"));
    1082210909  if (this->end_ != NULL
    1082310910      && this->end_->type()->integer_type() == NULL
    10824       && !this->end_->is_nil_expression())
     10911      && !this->end_->type()->is_error()
     10912      && !this->end_->is_nil_expression()
     10913      && !this->end_->is_error_expression()
     10914      && (!this->end_->numeric_constant_value(&nc)
     10915          || nc.to_unsigned_long(&v) == Numeric_constant::NC_UL_NOTINT))
    1082510916    this->report_error(_("slice end must be integer"));
    1082610917
    1082710918  std::string sval;
  • gcc/go/gofrontend/expressions.h

    diff -Naur gcc-4.8.2.orig/gcc/go/gofrontend/expressions.h gcc-4.8.2/gcc/go/gofrontend/expressions.h
    old new  
    15141514  closure()
    15151515  { return this->closure_; }
    15161516
    1517   // Return a tree for the code for a function.
    1518   static tree
     1517  // Return a backend expression for the code of a function.
     1518  static Bexpression*
    15191519  get_code_pointer(Gogo*, Named_object* function, Location loc);
    15201520
    15211521 protected:
  • gcc/go/gofrontend/gogo-tree.cc

    diff -Naur gcc-4.8.2.orig/gcc/go/gofrontend/gogo-tree.cc gcc-4.8.2/gcc/go/gofrontend/gogo-tree.cc
    old new  
    985985  delete[] vec;
    986986}
    987987
    988 // Get a tree for the identifier for a named object.
    989 
    990 tree
    991 Named_object::get_id(Gogo* gogo)
    992 {
    993   go_assert(!this->is_variable() && !this->is_result_variable());
    994   std::string decl_name;
    995   if (this->is_function_declaration()
    996       && !this->func_declaration_value()->asm_name().empty())
    997     decl_name = this->func_declaration_value()->asm_name();
    998   else if (this->is_type()
    999            && Linemap::is_predeclared_location(this->type_value()->location()))
    1000     {
    1001       // We don't need the package name for builtin types.
    1002       decl_name = Gogo::unpack_hidden_name(this->name_);
    1003     }
    1004   else
    1005     {
    1006       std::string package_name;
    1007       if (this->package_ == NULL)
    1008         package_name = gogo->package_name();
    1009       else
    1010         package_name = this->package_->package_name();
    1011 
    1012       // Note that this will be misleading if this is an unexported
    1013       // method generated for an embedded imported type.  In that case
    1014       // the unexported method should have the package name of the
    1015       // package from which it is imported, but we are going to give
    1016       // it our package name.  Fixing this would require knowing the
    1017       // package name, but we only know the package path.  It might be
    1018       // better to use package paths here anyhow.  This doesn't affect
    1019       // the assembler code, because we always set that name in
    1020       // Function::get_or_make_decl anyhow.  FIXME.
    1021 
    1022       decl_name = package_name + '.' + Gogo::unpack_hidden_name(this->name_);
    1023 
    1024       Function_type* fntype;
    1025       if (this->is_function())
    1026         fntype = this->func_value()->type();
    1027       else if (this->is_function_declaration())
    1028         fntype = this->func_declaration_value()->type();
    1029       else
    1030         fntype = NULL;
    1031       if (fntype != NULL && fntype->is_method())
    1032         {
    1033           decl_name.push_back('.');
    1034           decl_name.append(fntype->receiver()->type()->mangled_name(gogo));
    1035         }
    1036     }
    1037   if (this->is_type())
    1038     {
    1039       unsigned int index;
    1040       const Named_object* in_function = this->type_value()->in_function(&index);
    1041       if (in_function != NULL)
    1042         {
    1043           decl_name += '$' + Gogo::unpack_hidden_name(in_function->name());
    1044           if (index > 0)
    1045             {
    1046               char buf[30];
    1047               snprintf(buf, sizeof buf, "%u", index);
    1048               decl_name += '$';
    1049               decl_name += buf;
    1050             }
    1051         }
    1052     }
    1053   return get_identifier_from_string(decl_name);
    1054 }
    1055 
    1056988// Get a tree for a named object.
    1057989
    1058990tree
     
    1067999      return error_mark_node;
    10681000    }
    10691001
    1070   tree name;
    1071   if (this->classification_ == NAMED_OBJECT_TYPE)
    1072     name = NULL_TREE;
    1073   else
    1074     name = this->get_id(gogo);
    10751002  tree decl;
    10761003  switch (this->classification_)
    10771004    {
     
    10991026              decl = error_mark_node;
    11001027            else if (INTEGRAL_TYPE_P(TREE_TYPE(expr_tree)))
    11011028              {
     1029                tree name = get_identifier_from_string(this->get_id(gogo));
    11021030                decl = build_decl(named_constant->location().gcc_location(),
    11031031                                  CONST_DECL, name, TREE_TYPE(expr_tree));
    11041032                DECL_INITIAL(decl) = expr_tree;
     
    11611089    case NAMED_OBJECT_FUNC:
    11621090      {
    11631091        Function* func = this->u_.func_value;
    1164         decl = func->get_or_make_decl(gogo, this, name);
     1092        decl = function_to_tree(func->get_or_make_decl(gogo, this));
    11651093        if (decl != error_mark_node)
    11661094          {
    11671095            if (func->block() != NULL)
     
    12861214  return block_tree;
    12871215}
    12881216
    1289 // Get a tree for a function decl.
     1217// Get the backend representation.
    12901218
    1291 tree
    1292 Function::get_or_make_decl(Gogo* gogo, Named_object* no, tree id)
     1219Bfunction*
     1220Function_declaration::get_or_make_decl(Gogo* gogo, Named_object* no)
    12931221{
    1294   if (this->fndecl_ == NULL_TREE)
    1295     {
    1296       tree functype = type_to_tree(this->type_->get_backend(gogo));
    1297 
    1298       if (functype != error_mark_node)
    1299         {
    1300           // The type of a function comes back as a pointer to a
    1301           // struct whose first field is the function, but we want the
    1302           // real function type for a function declaration.
    1303           go_assert(POINTER_TYPE_P(functype)
    1304                     && TREE_CODE(TREE_TYPE(functype)) == RECORD_TYPE);
    1305           functype = TREE_TYPE(TYPE_FIELDS(TREE_TYPE(functype)));
    1306           go_assert(FUNCTION_POINTER_TYPE_P(functype));
    1307           functype = TREE_TYPE(functype);
    1308         }
    1309 
    1310       if (functype == error_mark_node)
    1311         this->fndecl_ = error_mark_node;
    1312       else
    1313         {
    1314           tree decl = build_decl(this->location().gcc_location(), FUNCTION_DECL,
    1315                                  id, functype);
    1316 
    1317           this->fndecl_ = decl;
    1318 
    1319           if (no->package() != NULL)
    1320             ;
    1321           else if (this->enclosing_ != NULL || Gogo::is_thunk(no))
    1322             ;
    1323           else if (Gogo::unpack_hidden_name(no->name()) == "init"
    1324                    && !this->type_->is_method())
    1325             ;
    1326           else if (Gogo::unpack_hidden_name(no->name()) == "main"
    1327                    && gogo->is_main_package())
    1328             TREE_PUBLIC(decl) = 1;
    1329           // Methods have to be public even if they are hidden because
    1330           // they can be pulled into type descriptors when using
    1331           // anonymous fields.
    1332           else if (!Gogo::is_hidden_name(no->name())
    1333                    || this->type_->is_method())
    1334             {
    1335               TREE_PUBLIC(decl) = 1;
    1336               std::string pkgpath = gogo->pkgpath_symbol();
    1337               if (this->type_->is_method()
    1338                   && Gogo::is_hidden_name(no->name())
    1339                   && Gogo::hidden_name_pkgpath(no->name()) != gogo->pkgpath())
    1340                 {
    1341                   // This is a method we created for an unexported
    1342                   // method of an imported embedded type.  We need to
    1343                   // use the pkgpath of the imported package to avoid
    1344                   // a possible name collision.  See bug478 for a test
    1345                   // case.
    1346                   pkgpath = Gogo::hidden_name_pkgpath(no->name());
    1347                   pkgpath = Gogo::pkgpath_for_symbol(pkgpath);
    1348                 }
    1349 
    1350               std::string asm_name = pkgpath;
    1351               asm_name.append(1, '.');
    1352               asm_name.append(Gogo::unpack_hidden_name(no->name()));
    1353               if (this->type_->is_method())
    1354                 {
    1355                   asm_name.append(1, '.');
    1356                   Type* rtype = this->type_->receiver()->type();
    1357                   asm_name.append(rtype->mangled_name(gogo));
    1358                 }
    1359               SET_DECL_ASSEMBLER_NAME(decl,
    1360                                       get_identifier_from_string(asm_name));
    1361             }
    1362 
    1363           // Why do we have to do this in the frontend?
    1364           tree restype = TREE_TYPE(functype);
    1365           tree resdecl =
    1366             build_decl(this->location().gcc_location(), RESULT_DECL, NULL_TREE,
    1367                        restype);
    1368           DECL_ARTIFICIAL(resdecl) = 1;
    1369           DECL_IGNORED_P(resdecl) = 1;
    1370           DECL_CONTEXT(resdecl) = decl;
    1371           DECL_RESULT(decl) = resdecl;
    1372 
    1373           // If a function calls the predeclared recover function, we
    1374           // can't inline it, because recover behaves differently in a
    1375           // function passed directly to defer.  If this is a recover
    1376           // thunk that we built to test whether a function can be
    1377           // recovered, we can't inline it, because that will mess up
    1378           // our return address comparison.
    1379           if (this->calls_recover_ || this->is_recover_thunk_)
    1380             DECL_UNINLINABLE(decl) = 1;
    1381 
    1382           // If this is a thunk created to call a function which calls
    1383           // the predeclared recover function, we need to disable
    1384           // stack splitting for the thunk.
    1385           if (this->is_recover_thunk_)
    1386             {
    1387               tree attr = get_identifier("__no_split_stack__");
    1388               DECL_ATTRIBUTES(decl) = tree_cons(attr, NULL_TREE, NULL_TREE);
    1389             }
    1390 
    1391           if (this->in_unique_section_)
    1392             resolve_unique_section (decl, 0, 1);
    1393 
    1394           go_preserve_from_gc(decl);
    1395         }
    1396     }
    1397   return this->fndecl_;
    1398 }
    1399 
    1400 // Get a tree for a function declaration.
    1401 
    1402 tree
    1403 Function_declaration::get_or_make_decl(Gogo* gogo, Named_object* no, tree id)
    1404 {
    1405   if (this->fndecl_ == NULL_TREE)
     1222  if (this->fndecl_ == NULL)
    14061223    {
    14071224      // Let Go code use an asm declaration to pick up a builtin
    14081225      // function.
     
    14121229            builtin_functions.find(this->asm_name_);
    14131230          if (p != builtin_functions.end())
    14141231            {
    1415               this->fndecl_ = p->second;
     1232              this->fndecl_ = tree_to_function(p->second);
    14161233              return this->fndecl_;
    14171234            }
    14181235        }
    14191236
    1420       tree functype = type_to_tree(this->fntype_->get_backend(gogo));
     1237      std::string asm_name;
     1238      if (this->asm_name_.empty())
     1239        {
     1240          asm_name = (no->package() == NULL
     1241                                  ? gogo->pkgpath_symbol()
     1242                                  : no->package()->pkgpath_symbol());
     1243          asm_name.append(1, '.');
     1244          asm_name.append(Gogo::unpack_hidden_name(no->name()));
     1245          if (this->fntype_->is_method())
     1246            {
     1247              asm_name.append(1, '.');
     1248              Type* rtype = this->fntype_->receiver()->type();
     1249              asm_name.append(rtype->mangled_name(gogo));
     1250            }
     1251        }
     1252
     1253      Btype* functype = this->fntype_->get_backend_fntype(gogo);
     1254      this->fndecl_ =
     1255          gogo->backend()->function(functype, no->get_id(gogo), asm_name,
     1256                                    true, true, true, false, false,
     1257                                    this->location());
     1258    }
    14211259
    1422       if (functype != error_mark_node)
    1423         {
    1424           // The type of a function comes back as a pointer to a
    1425           // struct whose first field is the function, but we want the
    1426           // real function type for a function declaration.
    1427           go_assert(POINTER_TYPE_P(functype)
    1428                     && TREE_CODE(TREE_TYPE(functype)) == RECORD_TYPE);
    1429           functype = TREE_TYPE(TYPE_FIELDS(TREE_TYPE(functype)));
    1430           go_assert(FUNCTION_POINTER_TYPE_P(functype));
    1431           functype = TREE_TYPE(functype);
    1432         }
     1260  return this->fndecl_;
     1261}
    14331262
    1434       tree decl;
    1435       if (functype == error_mark_node)
    1436         decl = error_mark_node;
    1437       else
    1438         {
    1439           decl = build_decl(this->location().gcc_location(), FUNCTION_DECL, id,
    1440                             functype);
    1441           TREE_PUBLIC(decl) = 1;
    1442           DECL_EXTERNAL(decl) = 1;
     1263// Return the function's decl after it has been built.
    14431264
    1444           if (this->asm_name_.empty())
    1445             {
    1446               std::string asm_name = (no->package() == NULL
    1447                                       ? gogo->pkgpath_symbol()
    1448                                       : no->package()->pkgpath_symbol());
    1449               asm_name.append(1, '.');
    1450               asm_name.append(Gogo::unpack_hidden_name(no->name()));
    1451               if (this->fntype_->is_method())
    1452                 {
    1453                   asm_name.append(1, '.');
    1454                   Type* rtype = this->fntype_->receiver()->type();
    1455                   asm_name.append(rtype->mangled_name(gogo));
    1456                 }
    1457               SET_DECL_ASSEMBLER_NAME(decl,
    1458                                       get_identifier_from_string(asm_name));
    1459             }
    1460         }
    1461       this->fndecl_ = decl;
    1462       go_preserve_from_gc(decl);
    1463     }
    1464   return this->fndecl_;
     1265tree
     1266Function::get_decl() const
     1267{
     1268  go_assert(this->fndecl_ != NULL);
     1269  return function_to_tree(this->fndecl_);
    14651270}
    14661271
    14671272// We always pass the receiver to a method as a pointer.  If the
     
    15581363void
    15591364Function::build_tree(Gogo* gogo, Named_object* named_function)
    15601365{
    1561   tree fndecl = this->fndecl_;
     1366  tree fndecl = this->get_decl();
    15621367  go_assert(fndecl != NULL_TREE);
    15631368
    15641369  tree params = NULL_TREE;
     
    17961601    set = NULL_TREE;
    17971602  else
    17981603    set = fold_build2_loc(end_loc.gcc_location(), MODIFY_EXPR, void_type_node,
    1799                           DECL_RESULT(this->fndecl_), retval);
     1604                          DECL_RESULT(this->get_decl()), retval);
    18001605  tree ret_stmt = fold_build1_loc(end_loc.gcc_location(), RETURN_EXPR,
    18011606                                  void_type_node, set);
    18021607  append_to_statement_list(ret_stmt, &stmt_list);
     
    18511656      retval = this->return_value(gogo, named_function, end_loc,
    18521657                                  &stmt_list);
    18531658      set = fold_build2_loc(end_loc.gcc_location(), MODIFY_EXPR, void_type_node,
    1854                             DECL_RESULT(this->fndecl_), retval);
     1659                            DECL_RESULT(this->get_decl()), retval);
    18551660      ret_stmt = fold_build1_loc(end_loc.gcc_location(), RETURN_EXPR,
    18561661                                 void_type_node, set);
    18571662
     
    18691674  *fini = stmt_list;
    18701675}
    18711676
    1872 // Return the value to assign to DECL_RESULT(this->fndecl_).  This may
     1677// Return the value to assign to DECL_RESULT(this->get_decl()).  This may
    18731678// also add statements to STMT_LIST, which need to be executed before
    18741679// the assignment.  This is used for a return statement with no
    18751680// explicit values.
     
    19021707    }
    19031708  else
    19041709    {
    1905       tree rettype = TREE_TYPE(DECL_RESULT(this->fndecl_));
     1710      tree rettype = TREE_TYPE(DECL_RESULT(this->get_decl()));
    19061711      retval = create_tmp_var(rettype, "RESULT");
    19071712      tree field = TYPE_FIELDS(rettype);
    19081713      int index = 0;
     
    23232128      go_assert(m != NULL);
    23242129
    23252130      Named_object* no = m->named_object();
    2326 
    2327       tree fnid = no->get_id(this);
    2328 
    2329       tree fndecl;
     2131      Bfunction* bf;
    23302132      if (no->is_function())
    2331         fndecl = no->func_value()->get_or_make_decl(this, no, fnid);
     2133        bf = no->func_value()->get_or_make_decl(this, no);
    23322134      else if (no->is_function_declaration())
    2333         fndecl = no->func_declaration_value()->get_or_make_decl(this, no,
    2334                                                                 fnid);
     2135        bf = no->func_declaration_value()->get_or_make_decl(this, no);
    23352136      else
    23362137        go_unreachable();
    2337       fndecl = build_fold_addr_expr(fndecl);
     2138      tree fndecl = build_fold_addr_expr(function_to_tree(bf));
    23382139
    23392140      elt = pointers->quick_push(empty);
    23402141      elt->index = size_int(i);
     
    23532154  TREE_CONSTANT(decl) = 1;
    23542155  DECL_INITIAL(decl) = constructor;
    23552156
    2356   // If the interface type has hidden methods, then this is the only
    2357   // definition of the table.  Otherwise it is a comdat table which
    2358   // may be defined in multiple packages.
    2359   if (has_hidden_methods)
     2157  // If the interface type has hidden methods, and the table is for a
     2158  // named type, then this is the only definition of the table.
     2159  // Otherwise it is a comdat table which may be defined in multiple
     2160  // packages.
     2161  if (has_hidden_methods && type->named_type() != NULL)
    23602162    TREE_PUBLIC(decl) = 1;
    23612163  else
    23622164    {
  • gcc/go/gofrontend/gogo.cc

    diff -Naur gcc-4.8.2.orig/gcc/go/gofrontend/gogo.cc gcc-4.8.2/gcc/go/gofrontend/gogo.cc
    old new  
    33203320    closure_var_(NULL), block_(block), location_(location), labels_(),
    33213321    local_type_count_(0), descriptor_(NULL), fndecl_(NULL), defer_stack_(NULL),
    33223322    is_sink_(false), results_are_named_(false), nointerface_(false),
    3323     calls_recover_(false), is_recover_thunk_(false), has_recover_thunk_(false),
     3323    is_unnamed_type_stub_method_(false), calls_recover_(false),
     3324    is_recover_thunk_(false), has_recover_thunk_(false),
    33243325    in_unique_section_(false)
    33253326{
    33263327}
     
    38193820  *presults = results;
    38203821}
    38213822
     3823// Get the backend representation.
     3824
     3825Bfunction*
     3826Function::get_or_make_decl(Gogo* gogo, Named_object* no)
     3827{
     3828  if (this->fndecl_ == NULL)
     3829    {
     3830      std::string asm_name;
     3831      bool is_visible = false;
     3832      if (no->package() != NULL)
     3833        ;
     3834      else if (this->enclosing_ != NULL || Gogo::is_thunk(no))
     3835        ;
     3836      else if (Gogo::unpack_hidden_name(no->name()) == "init"
     3837               && !this->type_->is_method())
     3838        ;
     3839      else if (Gogo::unpack_hidden_name(no->name()) == "main"
     3840               && gogo->is_main_package())
     3841        is_visible = true;
     3842      // Methods have to be public even if they are hidden because
     3843      // they can be pulled into type descriptors when using
     3844      // anonymous fields.
     3845      else if (!Gogo::is_hidden_name(no->name())
     3846               || this->type_->is_method())
     3847        {
     3848          if (!this->is_unnamed_type_stub_method_)
     3849            is_visible = true;
     3850          std::string pkgpath = gogo->pkgpath_symbol();
     3851          if (this->type_->is_method()
     3852              && Gogo::is_hidden_name(no->name())
     3853              && Gogo::hidden_name_pkgpath(no->name()) != gogo->pkgpath())
     3854            {
     3855              // This is a method we created for an unexported
     3856              // method of an imported embedded type.  We need to
     3857              // use the pkgpath of the imported package to avoid
     3858              // a possible name collision.  See bug478 for a test
     3859              // case.
     3860              pkgpath = Gogo::hidden_name_pkgpath(no->name());
     3861              pkgpath = Gogo::pkgpath_for_symbol(pkgpath);
     3862            }
     3863
     3864          asm_name = pkgpath;
     3865          asm_name.append(1, '.');
     3866          asm_name.append(Gogo::unpack_hidden_name(no->name()));
     3867          if (this->type_->is_method())
     3868            {
     3869              asm_name.append(1, '.');
     3870              Type* rtype = this->type_->receiver()->type();
     3871              asm_name.append(rtype->mangled_name(gogo));
     3872            }
     3873        }
     3874
     3875      // If a function calls the predeclared recover function, we
     3876      // can't inline it, because recover behaves differently in a
     3877      // function passed directly to defer.  If this is a recover
     3878      // thunk that we built to test whether a function can be
     3879      // recovered, we can't inline it, because that will mess up
     3880      // our return address comparison.
     3881      bool is_inlinable = !(this->calls_recover_ || this->is_recover_thunk_);
     3882
     3883      // If this is a thunk created to call a function which calls
     3884      // the predeclared recover function, we need to disable
     3885      // stack splitting for the thunk.
     3886      bool disable_split_stack = this->is_recover_thunk_;
     3887
     3888      Btype* functype = this->type_->get_backend_fntype(gogo);
     3889      this->fndecl_ =
     3890          gogo->backend()->function(functype, no->get_id(gogo), asm_name,
     3891                                    is_visible, false, is_inlinable,
     3892                                    disable_split_stack,
     3893                                    this->in_unique_section_, this->location());
     3894    }
     3895  return this->fndecl_;
     3896}
     3897
    38223898// Class Block.
    38233899
    38243900Block::Block(Block* enclosing, Location location)
     
    51105186    go_unreachable();
    51115187}
    51125188
     5189
     5190// Return the external identifier for this object.
     5191
     5192std::string
     5193Named_object::get_id(Gogo* gogo)
     5194{
     5195  go_assert(!this->is_variable() && !this->is_result_variable());
     5196  std::string decl_name;
     5197  if (this->is_function_declaration()
     5198      && !this->func_declaration_value()->asm_name().empty())
     5199    decl_name = this->func_declaration_value()->asm_name();
     5200  else if (this->is_type()
     5201           && Linemap::is_predeclared_location(this->type_value()->location()))
     5202    {
     5203      // We don't need the package name for builtin types.
     5204      decl_name = Gogo::unpack_hidden_name(this->name_);
     5205    }
     5206  else
     5207    {
     5208      std::string package_name;
     5209      if (this->package_ == NULL)
     5210        package_name = gogo->package_name();
     5211      else
     5212        package_name = this->package_->package_name();
     5213
     5214      // Note that this will be misleading if this is an unexported
     5215      // method generated for an embedded imported type.  In that case
     5216      // the unexported method should have the package name of the
     5217      // package from which it is imported, but we are going to give
     5218      // it our package name.  Fixing this would require knowing the
     5219      // package name, but we only know the package path.  It might be
     5220      // better to use package paths here anyhow.  This doesn't affect
     5221      // the assembler code, because we always set that name in
     5222      // Function::get_or_make_decl anyhow.  FIXME.
     5223
     5224      decl_name = package_name + '.' + Gogo::unpack_hidden_name(this->name_);
     5225
     5226      Function_type* fntype;
     5227      if (this->is_function())
     5228        fntype = this->func_value()->type();
     5229      else if (this->is_function_declaration())
     5230        fntype = this->func_declaration_value()->type();
     5231      else
     5232        fntype = NULL;
     5233      if (fntype != NULL && fntype->is_method())
     5234        {
     5235          decl_name.push_back('.');
     5236          decl_name.append(fntype->receiver()->type()->mangled_name(gogo));
     5237        }
     5238    }
     5239  if (this->is_type())
     5240    {
     5241      unsigned int index;
     5242      const Named_object* in_function = this->type_value()->in_function(&index);
     5243      if (in_function != NULL)
     5244        {
     5245          decl_name += '$' + Gogo::unpack_hidden_name(in_function->name());
     5246          if (index > 0)
     5247            {
     5248              char buf[30];
     5249              snprintf(buf, sizeof buf, "%u", index);
     5250              decl_name += '$';
     5251              decl_name += buf;
     5252            }
     5253        }
     5254    }
     5255  return decl_name;
     5256}
     5257
    51135258// Class Bindings.
    51145259
    51155260Bindings::Bindings(Bindings* enclosing)
  • gcc/go/gofrontend/gogo.h

    diff -Naur gcc-4.8.2.orig/gcc/go/gofrontend/gogo.h gcc-4.8.2/gcc/go/gofrontend/gogo.h
    old new  
    4848class Bblock;
    4949class Bvariable;
    5050class Blabel;
     51class Bfunction;
    5152
    5253// This file declares the basic classes used to hold the internal
    5354// representation of Go which is built by the parser.
     
    952953    this->nointerface_ = true;
    953954  }
    954955
     956  // Record that this function is a stub method created for an unnamed
     957  // type.
     958  void
     959  set_is_unnamed_type_stub_method()
     960  {
     961    go_assert(this->is_method());
     962    this->is_unnamed_type_stub_method_ = true;
     963  }
     964
    955965  // Add a new field to the closure variable.
    956966  void
    957967  add_closure_field(Named_object* var, Location loc)
     
    10891099    this->descriptor_ = descriptor;
    10901100  }
    10911101
    1092   // Return the function's decl given an identifier.
    1093   tree
    1094   get_or_make_decl(Gogo*, Named_object*, tree id);
     1102  // Return the backend representation.
     1103  Bfunction*
     1104  get_or_make_decl(Gogo*, Named_object*);
    10951105
    10961106  // Return the function's decl after it has been built.
    10971107  tree
    1098   get_decl() const
    1099   {
    1100     go_assert(this->fndecl_ != NULL);
    1101     return this->fndecl_;
    1102   }
     1108  get_decl() const;
    11031109
    11041110  // Set the function decl to hold a tree of the function code.
    11051111  void
     
    11701176  // The function descriptor, if any.
    11711177  Expression* descriptor_;
    11721178  // The function decl.
    1173   tree fndecl_;
     1179  Bfunction* fndecl_;
    11741180  // The defer stack variable.  A pointer to this variable is used to
    11751181  // distinguish the defer stack for one function from another.  This
    11761182  // is NULL unless we actually need a defer stack.
     
    11811187  bool results_are_named_ : 1;
    11821188  // True if this method should not be included in the type descriptor.
    11831189  bool nointerface_ : 1;
     1190  // True if this function is a stub method created for an unnamed
     1191  // type.
     1192  bool is_unnamed_type_stub_method_ : 1;
    11841193  // True if this function calls the predeclared recover function.
    11851194  bool calls_recover_ : 1;
    11861195  // True if this a thunk built for a function which calls recover.
     
    12651274  has_descriptor() const
    12661275  { return this->descriptor_ != NULL; }
    12671276
    1268   // Return a decl for the function given an identifier.
    1269   tree
    1270   get_or_make_decl(Gogo*, Named_object*, tree id);
     1277  // Return a backend representation.
     1278  Bfunction*
     1279  get_or_make_decl(Gogo*, Named_object*);
    12711280
    12721281  // If there is a descriptor, build it into the backend
    12731282  // representation.
     
    12901299  // The function descriptor, if any.
    12911300  Expression* descriptor_;
    12921301  // The function decl if needed.
    1293   tree fndecl_;
     1302  Bfunction* fndecl_;
    12941303};
    12951304
    12961305// A variable.
     
    21812190  Bvariable*
    21822191  get_backend_variable(Gogo*, Named_object* function);
    21832192
    2184   // Return a tree for the external identifier for this object.
    2185   tree
     2193  // Return the external identifier for this object.
     2194  std::string
    21862195  get_id(Gogo*);
    21872196
    21882197  // Return a tree representing this object.
  • gcc/go/gofrontend/import.h

    diff -Naur gcc-4.8.2.orig/gcc/go/gofrontend/import.h gcc-4.8.2/gcc/go/gofrontend/import.h
    old new  
    149149  location() const
    150150  { return this->location_; }
    151151
     152  // Return the package we are importing.
     153  Package*
     154  package() const
     155  { return this->package_; }
     156
    152157  // Return the next character.
    153158  int
    154159  peek_char()
  • gcc/go/gofrontend/lex.cc

    diff -Naur gcc-4.8.2.orig/gcc/go/gofrontend/lex.cc gcc-4.8.2/gcc/go/gofrontend/lex.cc
    old new  
    873873              && (cc < 'a' || cc > 'z')
    874874              && cc != '_'
    875875              && (cc < '0' || cc > '9'))
    876             break;
     876            {
     877              // Check for an invalid character here, as we get better
     878              // error behaviour if we swallow them as part of the
     879              // identifier we are building.
     880              if ((cc >= ' ' && cc < 0x7f)
     881                  || cc == '\t'
     882                  || cc == '\r'
     883                  || cc == '\n')
     884                break;
     885
     886              this->lineoff_ = p - this->linebuf_;
     887              error_at(this->location(),
     888                       "invalid character 0x%x in identifier",
     889                       cc);
     890              if (!has_non_ascii_char)
     891                {
     892                  buf.assign(pstart, p - pstart);
     893                  has_non_ascii_char = true;
     894                }
     895              if (!Lex::is_invalid_identifier(buf))
     896                buf.append("$INVALID$");
     897            }
    877898          ++p;
    878899          if (is_first)
    879900            {
  • gcc/go/gofrontend/parse.cc

    diff -Naur gcc-4.8.2.orig/gcc/go/gofrontend/parse.cc gcc-4.8.2/gcc/go/gofrontend/parse.cc
    old new  
    744744    return NULL;
    745745
    746746  Parse::Names names;
     747  if (receiver != NULL)
     748    names[receiver->name()] = receiver;
    747749  if (params != NULL)
    748750    this->check_signature_names(params, &names);
    749751  if (results != NULL)
  • gcc/go/gofrontend/runtime.cc

    diff -Naur gcc-4.8.2.orig/gcc/go/gofrontend/runtime.cc gcc-4.8.2/gcc/go/gofrontend/runtime.cc
    old new  
    4242  RFT_RUNE,
    4343  // Go type float64, C type double.
    4444  RFT_FLOAT64,
     45  // Go type complex64, C type __complex float.
     46  RFT_COMPLEX64,
    4547  // Go type complex128, C type __complex double.
    4648  RFT_COMPLEX128,
    4749  // Go type string, C type struct __go_string.
     
    126128          t = Type::lookup_float_type("float64");
    127129          break;
    128130
     131        case RFT_COMPLEX64:
     132          t = Type::lookup_complex_type("complex64");
     133          break;
     134
    129135        case RFT_COMPLEX128:
    130136          t = Type::lookup_complex_type("complex128");
    131137          break;
     
    216222    case RFT_UINTPTR:
    217223    case RFT_RUNE:
    218224    case RFT_FLOAT64:
     225    case RFT_COMPLEX64:
    219226    case RFT_COMPLEX128:
    220227    case RFT_STRING:
    221228    case RFT_POINTER:
  • gcc/go/gofrontend/runtime.def

    diff -Naur gcc-4.8.2.orig/gcc/go/gofrontend/runtime.def gcc-4.8.2/gcc/go/gofrontend/runtime.def
    old new  
    6868               P1(STRING), R1(SLICE))
    6969
    7070
     71// Complex division.
     72DEF_GO_RUNTIME(COMPLEX64_DIV, "__go_complex64_div",
     73               P2(COMPLEX64, COMPLEX64), R1(COMPLEX64))
     74DEF_GO_RUNTIME(COMPLEX128_DIV, "__go_complex128_div",
     75               P2(COMPLEX128, COMPLEX128), R1(COMPLEX128))
     76
    7177// Make a slice.
    7278DEF_GO_RUNTIME(MAKESLICE1, "__go_make_slice1", P2(TYPE, UINTPTR), R1(SLICE))
    7379DEF_GO_RUNTIME(MAKESLICE2, "__go_make_slice2", P3(TYPE, UINTPTR, UINTPTR),
  • gcc/go/gofrontend/types.cc

    diff -Naur gcc-4.8.2.orig/gcc/go/gofrontend/types.cc gcc-4.8.2/gcc/go/gofrontend/types.cc
    old new  
    33833383// Get the backend representation for a function type.
    33843384
    33853385Btype*
     3386Function_type::get_backend_fntype(Gogo* gogo)
     3387{
     3388  if (this->fnbtype_ == NULL)
     3389    {
     3390      Backend::Btyped_identifier breceiver;
     3391      if (this->receiver_ != NULL)
     3392        {
     3393          breceiver.name = Gogo::unpack_hidden_name(this->receiver_->name());
     3394
     3395          // We always pass the address of the receiver parameter, in
     3396          // order to make interface calls work with unknown types.
     3397          Type* rtype = this->receiver_->type();
     3398          if (rtype->points_to() == NULL)
     3399            rtype = Type::make_pointer_type(rtype);
     3400          breceiver.btype = rtype->get_backend(gogo);
     3401          breceiver.location = this->receiver_->location();
     3402        }
     3403
     3404      std::vector<Backend::Btyped_identifier> bparameters;
     3405      if (this->parameters_ != NULL)
     3406        {
     3407          bparameters.resize(this->parameters_->size());
     3408          size_t i = 0;
     3409          for (Typed_identifier_list::const_iterator p =
     3410                   this->parameters_->begin(); p != this->parameters_->end();
     3411               ++p, ++i)
     3412            {
     3413              bparameters[i].name = Gogo::unpack_hidden_name(p->name());
     3414              bparameters[i].btype = p->type()->get_backend(gogo);
     3415              bparameters[i].location = p->location();
     3416            }
     3417          go_assert(i == bparameters.size());
     3418        }
     3419
     3420      std::vector<Backend::Btyped_identifier> bresults;
     3421      if (this->results_ != NULL)
     3422        {
     3423          bresults.resize(this->results_->size());
     3424          size_t i = 0;
     3425          for (Typed_identifier_list::const_iterator p =
     3426                   this->results_->begin(); p != this->results_->end();
     3427               ++p, ++i)
     3428            {
     3429              bresults[i].name = Gogo::unpack_hidden_name(p->name());
     3430              bresults[i].btype = p->type()->get_backend(gogo);
     3431              bresults[i].location = p->location();
     3432            }
     3433          go_assert(i == bresults.size());
     3434        }
     3435
     3436      this->fnbtype_ = gogo->backend()->function_type(breceiver, bparameters,
     3437                                                      bresults,
     3438                                                      this->location());
     3439
     3440    }
     3441
     3442  return this->fnbtype_;
     3443}
     3444
     3445// Get the backend representation for a Go function type.
     3446
     3447Btype*
    33863448Function_type::do_get_backend(Gogo* gogo)
    33873449{
    33883450  // When we do anything with a function value other than call it, it
     
    33953457    gogo->backend()->placeholder_struct_type("__go_descriptor", loc);
    33963458  Btype* ptr_struct_type = gogo->backend()->pointer_type(struct_type);
    33973459
    3398   Backend::Btyped_identifier breceiver;
    3399   if (this->receiver_ != NULL)
    3400     {
    3401       breceiver.name = Gogo::unpack_hidden_name(this->receiver_->name());
    3402 
    3403       // We always pass the address of the receiver parameter, in
    3404       // order to make interface calls work with unknown types.
    3405       Type* rtype = this->receiver_->type();
    3406       if (rtype->points_to() == NULL)
    3407         rtype = Type::make_pointer_type(rtype);
    3408       breceiver.btype = rtype->get_backend(gogo);
    3409       breceiver.location = this->receiver_->location();
    3410     }
    3411 
    3412   std::vector<Backend::Btyped_identifier> bparameters;
    3413   if (this->parameters_ != NULL)
    3414     {
    3415       bparameters.resize(this->parameters_->size());
    3416       size_t i = 0;
    3417       for (Typed_identifier_list::const_iterator p = this->parameters_->begin();
    3418            p != this->parameters_->end();
    3419            ++p, ++i)
    3420         {
    3421           bparameters[i].name = Gogo::unpack_hidden_name(p->name());
    3422           bparameters[i].btype = p->type()->get_backend(gogo);
    3423           bparameters[i].location = p->location();
    3424         }
    3425       go_assert(i == bparameters.size());
    3426     }
    3427 
    3428   std::vector<Backend::Btyped_identifier> bresults;
    3429   if (this->results_ != NULL)
    3430     {
    3431       bresults.resize(this->results_->size());
    3432       size_t i = 0;
    3433       for (Typed_identifier_list::const_iterator p = this->results_->begin();
    3434            p != this->results_->end();
    3435            ++p, ++i)
    3436         {
    3437           bresults[i].name = Gogo::unpack_hidden_name(p->name());
    3438           bresults[i].btype = p->type()->get_backend(gogo);
    3439           bresults[i].location = p->location();
    3440         }
    3441       go_assert(i == bresults.size());
    3442     }
    3443 
    3444   Btype* fntype = gogo->backend()->function_type(breceiver, bparameters,
    3445                                                  bresults, loc);
    34463460  std::vector<Backend::Btyped_identifier> fields(1);
    34473461  fields[0].name = "code";
    3448   fields[0].btype = fntype;
     3462  fields[0].btype = this->get_backend_fntype(gogo);
    34493463  fields[0].location = loc;
    34503464  if (!gogo->backend()->set_placeholder_struct_type(struct_type, fields))
    34513465    return gogo->backend()->error_type();
     
    41954209
    41964210      // This is a horrible hack caused by the fact that we don't pack
    41974211      // the names of builtin types.  FIXME.
    4198       if (nt != NULL
     4212      if (!this->is_imported_
     4213          && nt != NULL
    41994214          && nt->is_builtin()
    42004215          && nt->name() == Gogo::unpack_hidden_name(name))
    42014216        return true;
     
    42044219    }
    42054220}
    42064221
     4222// Return whether this field is an unexported field named NAME.
     4223
     4224bool
     4225Struct_field::is_unexported_field_name(Gogo* gogo,
     4226                                       const std::string& name) const
     4227{
     4228  const std::string& field_name(this->field_name());
     4229  if (Gogo::is_hidden_name(field_name)
     4230      && name == Gogo::unpack_hidden_name(field_name)
     4231      && gogo->pack_hidden_name(name, false) != field_name)
     4232    return true;
     4233
     4234  // Check for the name of a builtin type.  This is like the test in
     4235  // is_field_name, only there we return false if this->is_imported_,
     4236  // and here we return true.
     4237  if (this->is_imported_ && this->is_anonymous())
     4238    {
     4239      Type* t = this->typed_identifier_.type();
     4240      if (t->points_to() != NULL)
     4241        t = t->points_to();
     4242      Named_type* nt = t->named_type();
     4243      if (nt != NULL
     4244          && nt->is_builtin()
     4245          && nt->name() == Gogo::unpack_hidden_name(name))
     4246        return true;
     4247    }
     4248
     4249  return false;
     4250}
     4251
    42074252// Return whether this field is an embedded built-in type.
    42084253
    42094254bool
     
    42644309       ++p)
    42654310    {
    42664311      Type* t = p->type();
    4267       if (t->is_undefined())
    4268         {
    4269           error_at(p->location(), "struct field type is incomplete");
    4270           p->set_type(Type::make_error_type());
    4271         }
    4272       else if (p->is_anonymous())
     4312      if (p->is_anonymous())
    42734313        {
    42744314          if (t->named_type() != NULL && t->points_to() != NULL)
    42754315            {
     
    46414681      for (Struct_field_list::const_iterator pf = fields->begin();
    46424682           pf != fields->end();
    46434683           ++pf)
    4644         {
    4645           const std::string& field_name(pf->field_name());
    4646           if (Gogo::is_hidden_name(field_name)
    4647               && name == Gogo::unpack_hidden_name(field_name)
    4648               && gogo->pack_hidden_name(name, false) != field_name)
    4649             return true;
    4650         }
     4684        if (pf->is_unexported_field_name(gogo, name))
     4685          return true;
    46514686    }
    46524687  return false;
    46534688}
     
    52505285          Type* ftype = imp->read_type();
    52515286
    52525287          Struct_field sf(Typed_identifier(name, ftype, imp->location()));
     5288          sf.set_is_imported();
    52535289
    52545290          if (imp->peek_char() == ' ')
    52555291            {
     
    90229058                                      fntype->is_varargs(), location);
    90239059          gogo->finish_function(fntype->location());
    90249060
     9061          if (type->named_type() == NULL && stub->is_function())
     9062            stub->func_value()->set_is_unnamed_type_stub_method();
    90259063          if (m->nointerface() && stub->is_function())
    90269064            stub->func_value()->set_nointerface();
    90279065        }
     
    92899327      else
    92909328        {
    92919329          bool is_unexported;
    9292           if (!Gogo::is_hidden_name(name))
     9330          // The test for 'a' and 'z' is to handle builtin names,
     9331          // which are not hidden.
     9332          if (!Gogo::is_hidden_name(name) && (name[0] < 'a' || name[0] > 'z'))
    92939333            is_unexported = false;
    92949334          else
    92959335            {
  • gcc/go/gofrontend/types.h

    diff -Naur gcc-4.8.2.orig/gcc/go/gofrontend/types.h gcc-4.8.2/gcc/go/gofrontend/types.h
    old new  
    17171717                Typed_identifier_list* results, Location location)
    17181718    : Type(TYPE_FUNCTION),
    17191719      receiver_(receiver), parameters_(parameters), results_(results),
    1720       location_(location), is_varargs_(false), is_builtin_(false)
     1720      location_(location), is_varargs_(false), is_builtin_(false),
     1721      fnbtype_(NULL)
    17211722  { }
    17221723
    17231724  // Get the receiver.
     
    17981799  static Type*
    17991800  make_function_type_descriptor_type();
    18001801
     1802  // Return the backend representation of this function type. This is used
     1803  // as the real type of a backend function declaration or defintion.
     1804  Btype*
     1805  get_backend_fntype(Gogo*);
     1806
    18011807 protected:
    18021808  int
    18031809  do_traverse(Traverse*);
     
    18511857  // Whether this is a special builtin function which can not simply
    18521858  // be called.  This is used for len, cap, etc.
    18531859  bool is_builtin_;
     1860  // The backend representation of this type for backend function
     1861  // declarations and definitions.
     1862  Btype* fnbtype_;
    18541863};
    18551864
    18561865// The type of a pointer.
     
    19151924{
    19161925 public:
    19171926  explicit Struct_field(const Typed_identifier& typed_identifier)
    1918     : typed_identifier_(typed_identifier), tag_(NULL)
     1927    : typed_identifier_(typed_identifier), tag_(NULL), is_imported_(false)
    19191928  { }
    19201929
    19211930  // The field name.
     
    19261935  bool
    19271936  is_field_name(const std::string& name) const;
    19281937
     1938  // Return whether this struct field is an unexported field named NAME.
     1939  bool
     1940  is_unexported_field_name(Gogo*, const std::string& name) const;
     1941
    19291942  // Return whether this struct field is an embedded built-in type.
    19301943  bool
    19311944  is_embedded_builtin(Gogo*) const;
     
    19631976  set_tag(const std::string& tag)
    19641977  { this->tag_ = new std::string(tag); }
    19651978
     1979  // Record that this field is defined in an imported struct.
     1980  void
     1981  set_is_imported()
     1982  { this->is_imported_ = true; }
     1983
    19661984  // Set the type.  This is only used in error cases.
    19671985  void
    19681986  set_type(Type* type)
     
    19731991  Typed_identifier typed_identifier_;
    19741992  // The field tag.  This is NULL if the field has no tag.
    19751993  std::string* tag_;
     1994  // Whether this field is defined in an imported struct.
     1995  bool is_imported_;
    19761996};
    19771997
    19781998// A list of struct fields.
  • gcc/graphite-clast-to-gimple.c

    diff -Naur gcc-4.8.2.orig/gcc/graphite-clast-to-gimple.c gcc-4.8.2/gcc/graphite-clast-to-gimple.c
    old new  
    11701170  redirect_edge_succ_nodup (next_e, after);
    11711171  set_immediate_dominator (CDI_DOMINATORS, next_e->dest, next_e->src);
    11721172
     1173  isl_set *domain = isl_set_from_cloog_domain (stmt->domain);
     1174  int scheduling_dim = isl_set_n_dim (domain);
     1175
    11731176  if (flag_loop_parallelize_all
    1174       && loop_is_parallel_p (loop, bb_pbb_mapping, level))
     1177      && loop_is_parallel_p (loop, bb_pbb_mapping, scheduling_dim))
    11751178    loop->can_be_parallel = true;
    11761179
    11771180  return last_e;
  • gcc/graphite-dependences.c

    diff -Naur gcc-4.8.2.orig/gcc/graphite-dependences.c gcc-4.8.2/gcc/graphite-dependences.c
    old new  
    297297              int depth)
    298298{
    299299  bool res;
    300   int idx, i;
     300  int i;
    301301  isl_space *space;
    302302  isl_map *lex, *x;
    303303  isl_constraint *ineq;
     
    312312  space = isl_map_get_space (x);
    313313  ineq = isl_inequality_alloc (isl_local_space_from_space (space));
    314314
    315   idx = 2 * depth + 1;
    316   for (i = 0; i < idx; i++)
     315  for (i = 0; i < depth - 1; i++)
    317316    lex = isl_map_equate (lex, isl_dim_in, i, isl_dim_out, i);
    318317
    319318  /* in + 1 <= out  */
    320   ineq = isl_constraint_set_coefficient_si (ineq, isl_dim_out, idx, 1);
    321   ineq = isl_constraint_set_coefficient_si (ineq, isl_dim_in, idx, -1);
     319  ineq = isl_constraint_set_coefficient_si (ineq, isl_dim_out, depth - 1, 1);
     320  ineq = isl_constraint_set_coefficient_si (ineq, isl_dim_in, depth - 1, -1);
    322321  ineq = isl_constraint_set_constant_si (ineq, -1);
    323322  lex = isl_map_add_constraint (lex, ineq);
    324323  x = isl_map_intersect (x, lex);
  • gcc/ipa-prop.c

    diff -Naur gcc-4.8.2.orig/gcc/ipa-prop.c gcc-4.8.2/gcc/ipa-prop.c
    old new  
    21262126     we may create the first reference to the object in the unit.  */
    21272127  if (!callee || callee->global.inlined_to)
    21282128    {
    2129       struct cgraph_node *first_clone = callee;
    21302129
    21312130      /* We are better to ensure we can refer to it.
    21322131         In the case of static functions we are out of luck, since we already   
     
    21422141                     xstrdup (cgraph_node_name (ie->callee)), ie->callee->uid);
    21432142          return NULL;
    21442143        }
    2145 
    2146       /* Create symbol table node.  Even if inline clone exists, we can not take
    2147          it as a target of non-inlined call.  */
    2148       callee = cgraph_create_node (target);
    2149 
    2150       /* OK, we previously inlined the function, then removed the offline copy and
    2151          now we want it back for external call.  This can happen when devirtualizing
    2152          while inlining function called once that happens after extern inlined and
    2153          virtuals are already removed.  In this case introduce the external node
    2154          and make it available for call.  */
    2155       if (first_clone)
    2156         {
    2157           first_clone->clone_of = callee;
    2158           callee->clones = first_clone;
    2159           symtab_prevail_in_asm_name_hash ((symtab_node)callee);
    2160           symtab_insert_node_to_hashtable ((symtab_node)callee);
    2161           if (dump_file)
    2162             fprintf (dump_file, "ipa-prop: Introduced new external node "
    2163                      "(%s/%i) and turned into root of the clone tree.\n",
    2164                      xstrdup (cgraph_node_name (callee)), callee->uid);
    2165         }
    2166       else if (dump_file)
    2167         fprintf (dump_file, "ipa-prop: Introduced new external node "
    2168                  "(%s/%i).\n",
    2169                  xstrdup (cgraph_node_name (callee)), callee->uid);
     2144      callee = cgraph_get_create_real_symbol_node (target);
    21702145    }
    21712146  ipa_check_create_node_params ();
    21722147
  • gcc/optabs.c

    diff -Naur gcc-4.8.2.orig/gcc/optabs.c gcc-4.8.2/gcc/optabs.c
    old new  
    70357035
    70367036      create_output_operand (&ops[0], target, mode);
    70377037      create_fixed_operand (&ops[1], mem);
    7038       /* VAL may have been promoted to a wider mode.  Shrink it if so.  */
    7039       create_convert_operand_to (&ops[2], val, mode, true);
     7038      create_input_operand (&ops[2], val, mode);
    70407039      create_integer_operand (&ops[3], model);
    70417040      if (maybe_expand_insn (icode, 4, ops))
    70427041        return ops[0].value;
     
    70757074      struct expand_operand ops[3];
    70767075      create_output_operand (&ops[0], target, mode);
    70777076      create_fixed_operand (&ops[1], mem);
    7078       /* VAL may have been promoted to a wider mode.  Shrink it if so.  */
    7079       create_convert_operand_to (&ops[2], val, mode, true);
     7077      create_input_operand (&ops[2], val, mode);
    70807078      if (maybe_expand_insn (icode, 3, ops))
    70817079        return ops[0].value;
    70827080    }
     
    71187116    {
    71197117      if (!target || !register_operand (target, mode))
    71207118        target = gen_reg_rtx (mode);
    7121       if (GET_MODE (val) != VOIDmode && GET_MODE (val) != mode)
    7122         val = convert_modes (mode, GET_MODE (val), val, 1);
    71237119      if (expand_compare_and_swap_loop (mem, target, val, NULL_RTX))
    71247120        return target;
    71257121    }
     
    73317327      create_output_operand (&ops[0], target_bool, bool_mode);
    73327328      create_output_operand (&ops[1], target_oval, mode);
    73337329      create_fixed_operand (&ops[2], mem);
    7334       create_convert_operand_to (&ops[3], expected, mode, true);
    7335       create_convert_operand_to (&ops[4], desired, mode, true);
     7330      create_input_operand (&ops[3], expected, mode);
     7331      create_input_operand (&ops[4], desired, mode);
    73367332      create_integer_operand (&ops[5], is_weak);
    73377333      create_integer_operand (&ops[6], succ_model);
    73387334      create_integer_operand (&ops[7], fail_model);
     
    73537349
    73547350      create_output_operand (&ops[0], target_oval, mode);
    73557351      create_fixed_operand (&ops[1], mem);
    7356       create_convert_operand_to (&ops[2], expected, mode, true);
    7357       create_convert_operand_to (&ops[3], desired, mode, true);
     7352      create_input_operand (&ops[2], expected, mode);
     7353      create_input_operand (&ops[3], desired, mode);
    73587354      if (!maybe_expand_insn (icode, 4, ops))
    73597355        return false;
    73607356
  • gcc/recog.c

    diff -Naur gcc-4.8.2.orig/gcc/recog.c gcc-4.8.2/gcc/recog.c
    old new  
    30613061  return 1;
    30623062}
    30633063
     3064/* Regno offset to be used in the register search.  */
     3065static int search_ofs;
     3066
    30643067/* Try to find a hard register of mode MODE, matching the register class in
    30653068   CLASS_STR, which is available at the beginning of insn CURRENT_INSN and
    30663069   remains available until the end of LAST_INSN.  LAST_INSN may be NULL_RTX,
     
    30763079peep2_find_free_register (int from, int to, const char *class_str,
    30773080                          enum machine_mode mode, HARD_REG_SET *reg_set)
    30783081{
    3079   static int search_ofs;
    30803082  enum reg_class cl;
    30813083  HARD_REG_SET live;
    30823084  df_ref *def_rec;
     
    35413543  /* Initialize the regsets we're going to use.  */
    35423544  for (i = 0; i < MAX_INSNS_PER_PEEP2 + 1; ++i)
    35433545    peep2_insn_data[i].live_before = BITMAP_ALLOC (&reg_obstack);
     3546  search_ofs = 0;
    35443547  live = BITMAP_ALLOC (&reg_obstack);
    35453548
    35463549  FOR_EACH_BB_REVERSE (bb)
  • gcc/testsuite/g++.dg/cpp0x/decltype57.C

    diff -Naur gcc-4.8.2.orig/gcc/testsuite/g++.dg/cpp0x/decltype57.C gcc-4.8.2/gcc/testsuite/g++.dg/cpp0x/decltype57.C
    old new  
     1// PR c++/58633
     2// { dg-do compile { target c++11 } }
     3
     4void foo(int i)
     5{
     6  typedef int I;
     7  decltype(i.I::~I())* p;
     8}
  • gcc/testsuite/g++.dg/cpp0x/enum18.C

    diff -Naur gcc-4.8.2.orig/gcc/testsuite/g++.dg/cpp0x/enum18.C gcc-4.8.2/gcc/testsuite/g++.dg/cpp0x/enum18.C
    old new  
    44int main(void) {
    55  enum e {};
    66  e ev;
    7   ev.e::~e_u(); // { dg-error "e_u. has not been declared" }
     7  ev.e::~e_u(); // { dg-error "" }
    88}
  • gcc/testsuite/g++.dg/cpp0x/lambda/lambda-nsdmi5.C

    diff -Naur gcc-4.8.2.orig/gcc/testsuite/g++.dg/cpp0x/lambda/lambda-nsdmi5.C gcc-4.8.2/gcc/testsuite/g++.dg/cpp0x/lambda/lambda-nsdmi5.C
    old new  
     1// PR c++/58596
     2// { dg-do compile { target c++11 } }
     3
     4struct A
     5{
     6  int i = [] { return decltype(i)(); }();
     7};
  • gcc/testsuite/g++.dg/tm/noexcept-6.C

    diff -Naur gcc-4.8.2.orig/gcc/testsuite/g++.dg/tm/noexcept-6.C gcc-4.8.2/gcc/testsuite/g++.dg/tm/noexcept-6.C
    old new  
     1// { dg-do compile }
     2// { dg-options "-fno-exceptions -fgnu-tm -O -std=c++0x -fdump-tree-tmlower" }
     3
     4struct TrueFalse
     5{
     6  static constexpr bool v() { return true; }
     7};
     8
     9int global;
     10
     11template<typename T> int foo()
     12{
     13  return __transaction_atomic noexcept(T::v()) (global + 1);
     14}
     15
     16int f1()
     17{
     18  return foo<TrueFalse>();
     19}
     20
     21/* { dg-final { scan-tree-dump-times "eh_must_not_throw" 0 "tmlower" } } */
     22/* { dg-final { scan-tree-dump-times "__transaction_atomic" 1 "tmlower" } } */
     23/* { dg-final { cleanup-tree-dump "tmlower" } } */
  • gcc/testsuite/gcc.c-torture/execute/pr58831.c

    diff -Naur gcc-4.8.2.orig/gcc/testsuite/gcc.c-torture/execute/pr58831.c gcc-4.8.2/gcc/testsuite/gcc.c-torture/execute/pr58831.c
    old new  
     1#include <assert.h>
     2
     3int a, *b, c, d, f, **i, p, q, *r;
     4short o, j;
     5
     6static int __attribute__((noinline, noclone))
     7fn1 (int *p1, int **p2)
     8{
     9  int **e = &b;
     10  for (; p; p++)
     11    *p1 = 1;
     12  *e = *p2 = &d;
     13
     14  assert (r);
     15
     16  return c;
     17}
     18
     19static int ** __attribute__((noinline, noclone))
     20fn2 (void)
     21{
     22  for (f = 0; f != 42; f++)
     23    {
     24      int *g[3] = {0, 0, 0};
     25      for (o = 0; o; o--)
     26        for (; a > 1;)
     27          {
     28            int **h[1] = { &g[2] };
     29          }
     30    }
     31  return &r;
     32}
     33
     34int
     35main (void)
     36{
     37  i = fn2 ();
     38  fn1 (b, i);
     39  return 0;
     40}
  • gcc/testsuite/gcc.dg/atomic-store-6.c

    diff -Naur gcc-4.8.2.orig/gcc/testsuite/gcc.dg/atomic-store-6.c gcc-4.8.2/gcc/testsuite/gcc.dg/atomic-store-6.c
    old new  
     1/* { dg-do run } */
     2/* { dg-require-effective-target sync_int_128_runtime } */
     3/* { dg-options "-mcx16" { target { i?86-*-* x86_64-*-* } } } */
     4
     5__int128_t i;
     6
     7int main()
     8{
     9  __atomic_store_16(&i, -1, 0);
     10  if (i != -1)
     11    __builtin_abort();
     12  return 0;
     13}
  • gcc/testsuite/gcc.dg/graphite/pr54094.c

    diff -Naur gcc-4.8.2.orig/gcc/testsuite/gcc.dg/graphite/pr54094.c gcc-4.8.2/gcc/testsuite/gcc.dg/graphite/pr54094.c
    old new  
     1/* { dg-options "-O2 -floop-parallelize-all -floop-nest-optimize" } */
     2void dwt_deinterleave_h(int *a, int *b, int dn, int sn, int cas)
     3{
     4  int i;
     5  for (i=0; i<sn; i++)
     6    b[i]=a[2*i+cas];
     7  for (i=0; i<dn; i++)
     8    b[sn+i]=a[(2*i+1-cas)];
     9}
     10
  • gcc/testsuite/gcc.dg/pr58805.c

    diff -Naur gcc-4.8.2.orig/gcc/testsuite/gcc.dg/pr58805.c gcc-4.8.2/gcc/testsuite/gcc.dg/pr58805.c
    old new  
     1/* { dg-do compile } */
     2/* { dg-options "-O2 -ftree-tail-merge -fdump-tree-pre" } */
     3
     4/* Type that matches the 'p' constraint.  */
     5#define TYPE void *
     6
     7static inline
     8void bar (TYPE *r)
     9{
     10  TYPE t;
     11  __asm__ ("" : "=&p" (t), "=p" (*r));
     12}
     13
     14void
     15foo (int n, TYPE *x, TYPE *y)
     16{
     17  if (n == 0)
     18    bar (x);
     19  else
     20    bar (y);
     21}
     22
     23/* { dg-final { scan-tree-dump-times "__asm__" 2 "pre"} } */
     24/* { dg-final { cleanup-tree-dump "pre" } } */
  • gcc/testsuite/gcc.dg/torture/pr57488.c

    diff -Naur gcc-4.8.2.orig/gcc/testsuite/gcc.dg/torture/pr57488.c gcc-4.8.2/gcc/testsuite/gcc.dg/torture/pr57488.c
    old new  
     1/* { dg-do run } */
     2
     3extern void abort (void);
     4
     5int i, j, *pj = &j, **ppj = &pj;
     6int x, *px = &x;
     7
     8short s, *ps = &s, k;
     9
     10unsigned short u, *pu = &u, **ppu = &pu;
     11
     12char c, *pc = &c;
     13
     14unsigned char v = 48;
     15
     16static int
     17bar (int p)
     18{
     19  p = k;
     20  *px = **ppu = i;
     21  *ppj = &p;
     22  if (**ppj)
     23    *pj = p;
     24  return p;
     25}
     26
     27void __attribute__((noinline))
     28foo ()
     29{
     30  for (; i <= 3; i++)
     31    for (; j; j--);
     32
     33  u ^= bar (*pj);
     34
     35  for (k = 1; k >= 0; k--)
     36    {
     37      int l;
     38      bar (0);
     39      for (l = 1; l < 5; l++)
     40        {
     41          int m;
     42          for (m = 6; m; m--)
     43            {
     44              v--;
     45              *ps = *pc;
     46            }
     47        }
     48    }
     49}
     50
     51int
     52main ()
     53{
     54  foo ();
     55  if (v != 0)
     56    abort ();
     57  return 0;
     58}
  • gcc/testsuite/gcc.dg/torture/pr58079.c

    diff -Naur gcc-4.8.2.orig/gcc/testsuite/gcc.dg/torture/pr58079.c gcc-4.8.2/gcc/testsuite/gcc.dg/torture/pr58079.c
    old new  
     1/* { dg-options "-mlong-calls" { target mips*-*-* } } */
     2
     3typedef unsigned char u8;
     4typedef unsigned short u16;
     5typedef unsigned int __kernel_size_t;
     6typedef __kernel_size_t size_t;
     7struct list_head {
     8 struct list_head *next;
     9};
     10
     11struct dmx_ts_feed {
     12 int is_filtering;
     13};
     14struct dmx_section_feed {
     15 u16 secbufp;
     16 u16 seclen;
     17 u16 tsfeedp;
     18};
     19
     20typedef int (*dmx_ts_cb) (
     21        const u8 * buffer1,
     22      size_t buffer1_length,
     23      const u8 * buffer2,
     24      size_t buffer2_length
     25);
     26
     27struct dvb_demux_feed {
     28 union {
     29  struct dmx_ts_feed ts;
     30  struct dmx_section_feed sec;
     31 } feed;
     32 union {
     33  dmx_ts_cb ts;
     34 } cb;
     35 int type;
     36 u16 pid;
     37 int ts_type;
     38 struct list_head list_head;
     39};
     40
     41struct dvb_demux {
     42 int (*stop_feed)(struct dvb_demux_feed *feed);
     43 struct list_head feed_list;
     44};
     45
     46
     47static
     48inline
     49__attribute__((always_inline))
     50u8
     51payload(const u8 *tsp)
     52{
     53 if (tsp[3] & 0x20) {
     54   return 184 - 1 - tsp[4];
     55 }
     56 return 184;
     57}
     58
     59static
     60inline
     61__attribute__((always_inline))
     62int
     63dvb_dmx_swfilter_payload(struct dvb_demux_feed *feed, const u8 *buf)
     64{
     65 int count = payload(buf);
     66 int p;
     67 if (count == 0)
     68  return -1;
     69 return feed->cb.ts(&buf[p], count, ((void *)0), 0);
     70}
     71
     72static
     73inline
     74__attribute__((always_inline))
     75void
     76dvb_dmx_swfilter_packet_type(struct dvb_demux_feed *feed, const u8 *buf)
     77{
     78 switch (feed->type) {
     79 case 0:
     80  if (feed->ts_type & 1) {
     81    dvb_dmx_swfilter_payload(feed, buf);
     82  }
     83  if (dvb_dmx_swfilter_section_packet(feed, buf) < 0)
     84   feed->feed.sec.seclen = feed->feed.sec.secbufp = 0;
     85 }
     86}
     87
     88static
     89void
     90dvb_dmx_swfilter_packet(struct dvb_demux *demux, const u8 *buf)
     91{
     92 struct dvb_demux_feed *feed;
     93 int dvr_done = 0;
     94
     95 for (feed = ({ const typeof( ((typeof(*feed) *)0)->list_head ) *__mptr = ((&demux->feed_list)->next); (typeof(*feed) *)( (char *)__mptr - __builtin_offsetof(typeof(*feed),list_head) );}); __builtin_prefetch(feed->list_head.next), &feed->list_head != (&demux->feed_list); feed = ({ const typeof( ((typeof(*feed) *)0)->list_head ) *__mptr = (feed->list_head.next); (typeof(*feed) *)( (char *)__mptr - __builtin_offsetof(typeof(*feed),list_head) );})) {
     96  if (((((feed)->type == 0) && ((feed)->feed.ts.is_filtering) && (((feed)->ts_type & (1 | 8)) == 1))) && (dvr_done++))
     97   dvb_dmx_swfilter_packet_type(feed, buf);
     98  else if (feed->pid == 0x2000)
     99   feed->cb.ts(buf, 188, ((void *)0), 0);
     100 }
     101}
     102void dvb_dmx_swfilter_packets(struct dvb_demux *demux, const u8 *buf, size_t count)
     103{
     104 while (count--) {
     105   dvb_dmx_swfilter_packet(demux, buf);
     106 }
     107}
  • gcc/testsuite/gcc.dg/torture/pr58779.c

    diff -Naur gcc-4.8.2.orig/gcc/testsuite/gcc.dg/torture/pr58779.c gcc-4.8.2/gcc/testsuite/gcc.dg/torture/pr58779.c
    old new  
     1/* { dg-do run } */
     2
     3int a, c;
     4
     5int main ()
     6{
     7  int e = -1;
     8  short d = (c <= 0) ^ e;
     9  if ((unsigned int) a - (a || d) <= (unsigned int) a)
     10    __builtin_abort ();
     11  return 0;
     12}
  • gcc/testsuite/gcc.dg/torture/pr58830.c

    diff -Naur gcc-4.8.2.orig/gcc/testsuite/gcc.dg/torture/pr58830.c gcc-4.8.2/gcc/testsuite/gcc.dg/torture/pr58830.c
    old new  
     1/* { dg-do run } */
     2/* { dg-additional-options "-ftree-pre -ftree-partial-pre" } */
     3
     4extern void abort (void);
     5
     6int b, c, d, f, g, h, i, j[6], *l = &b, *m, n, *o, r;
     7char k;
     8
     9static int
     10foo ()
     11{
     12  char *p = &k;
     13
     14  for (; d; d++)
     15    if (i)
     16      h = 0;
     17    else
     18      h = c || (r = 0);
     19
     20  for (f = 0; f < 2; f++)
     21    {
     22      unsigned int q;
     23      *l = 0;
     24      if (n)
     25        *m = g;
     26      if (g)
     27        o = 0;
     28      for (q = -8; q >= 5; q++)
     29        (*p)--;
     30    }
     31
     32  return 0;
     33}
     34
     35int
     36main ()
     37{
     38  foo ();
     39  if (j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[j[0]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]] ^ (k & 15)] != 0)
     40    abort ();
     41  return 0;
     42}
  • gcc/testsuite/gcc.target/arm/require-pic-register-loc.c

    diff -Naur gcc-4.8.2.orig/gcc/testsuite/gcc.target/arm/require-pic-register-loc.c gcc-4.8.2/gcc/testsuite/gcc.target/arm/require-pic-register-loc.c
    old new  
     1/* { dg-do compile } */
     2/* { dg-options "-g -fPIC" } */
     3
     4void *v;
     5void a (void *x) { }
     6void b (void) { }
     7                       /* line 7.  */
     8int                    /* line 8.  */
     9main (int argc)        /* line 9.  */
     10{                      /* line 10.  */
     11  if (argc == 12345)   /* line 11.  */
     12    {
     13      a (v);
     14      return 1;
     15    }
     16  b ();
     17
     18  return 0;
     19}
     20
     21/* { dg-final { scan-assembler-not "\.loc 1 7 0" } } */
     22/* { dg-final { scan-assembler-not "\.loc 1 8 0" } } */
     23/* { dg-final { scan-assembler-not "\.loc 1 9 0" } } */
     24
     25/* The loc at the start of the prologue.  */
     26/* { dg-final { scan-assembler-times "\.loc 1 10 0" 1 } } */
     27
     28/* The loc at the end of the prologue, with the first user line.  */
     29/* { dg-final { scan-assembler-times "\.loc 1 11 0" 1 } } */
  • gcc/testsuite/gcc.target/i386/pr30315.c

    diff -Naur gcc-4.8.2.orig/gcc/testsuite/gcc.target/i386/pr30315.c gcc-4.8.2/gcc/testsuite/gcc.target/i386/pr30315.c
    old new  
    11/* { dg-do compile } */
    22/* { dg-options "-O2" } */
    3 /* { dg-final { scan-assembler-times "cmp" 4 } } */
     3/* { dg-final { scan-assembler-not "cmp" } } */
    44
    55extern void abort (void);
    66int c;
     
    3434}
    3535#define PLUSCCONLY(T, t) PLUSCCONLY1(T, t, a) PLUSCCONLY1(T, t, b)
    3636
    37 #define MINUSCC(T, t)   \
    38 T minuscc##t (T a, T b) \
    39 {       \
    40   T difference = a - b; \
    41   if (difference > a)   \
    42     abort ();           \
    43   return difference;    \
    44 }
    45 
    46 #define DECCC(T, t)     \
    47 T deccc##t (T a, T b)   \
    48 {       \
    49   T difference = a - b; \
    50   if (difference > a)   \
    51     c --;               \
    52   return difference;    \
    53 }
    54 
    55 #define MINUSCCONLY(T, t)       \
    56 void minuscconly##t (T a, T b)  \
    57 {       \
    58   T difference = a - b; \
    59   if (difference > a)   \
    60     abort ();           \
    61 }
    62 
    6337#define TEST(T, t)      \
    6438  PLUSCC(T, t)          \
    6539  PLUSCCONLY(T, t)      \
    66   INCCC(T, t)           \
    67   MINUSCC(T, t)         \
    68   MINUSCCONLY(T, t)     \
    69   DECCC(T, t)
     40  INCCC(T, t)
    7041
    7142TEST (unsigned long,  l)
    7243TEST (unsigned int,   i)
     
    8455
    8556PLUSCCZEXT(a)
    8657PLUSCCZEXT(b)
    87 
    88 #define MINUSCCZEXT     \
    89 unsigned long minuscczext (unsigned int a, unsigned int b)      \
    90 {       \
    91   unsigned int difference = a - b;      \
    92   if (difference > a)           \
    93     abort ();                   \
    94   return difference;            \
    95 }
    96 
    97 MINUSCCZEXT
  • gcc/testsuite/gcc.target/sh/pr54089-3.c

    diff -Naur gcc-4.8.2.orig/gcc/testsuite/gcc.target/sh/pr54089-3.c gcc-4.8.2/gcc/testsuite/gcc.target/sh/pr54089-3.c
    old new  
    55/* { dg-options "-O1" } */
    66/* { dg-skip-if "" { "sh*-*-*" } { "*" } { "-m1*" "-m2" "-m2e*" } } */
    77/* { dg-final { scan-assembler-not "and" } } */
    8 /* { dg-final { scan-assembler-not "31" } } */
     8/* { dg-final { scan-assembler-not "#31" } } */
    99
    1010int
    1111test00 (unsigned int a, int* b, int c, int* d, unsigned int e)
  • gcc/tree-ssa-pre.c

    diff -Naur gcc-4.8.2.orig/gcc/tree-ssa-pre.c gcc-4.8.2/gcc/tree-ssa-pre.c
    old new  
    36643664      if (dump_file && dump_flags & TDF_DETAILS)
    36653665        fprintf (dump_file, "Starting insert iteration %d\n", num_iterations);
    36663666      new_stuff = insert_aux (ENTRY_BLOCK_PTR);
     3667
     3668      /* Clear the NEW sets before the next iteration.  We have already
     3669         fully propagated its contents.  */
     3670      if (new_stuff)
     3671        FOR_ALL_BB (bb)
     3672          bitmap_set_free (NEW_SETS (bb));
    36673673    }
    36683674  statistics_histogram_event (cfun, "insert iterations", num_iterations);
    36693675}
  • gcc/tree-ssa-tail-merge.c

    diff -Naur gcc-4.8.2.orig/gcc/tree-ssa-tail-merge.c gcc-4.8.2/gcc/tree-ssa-tail-merge.c
    old new  
    297297  tree val;
    298298  def_operand_p def_p;
    299299
    300   if (gimple_has_side_effects (stmt))
     300  if (gimple_has_side_effects (stmt)
     301      || gimple_vdef (stmt) != NULL_TREE)
    301302    return false;
    302303
    303304  def_p = SINGLE_SSA_DEF_OPERAND (stmt, SSA_OP_DEF);
  • gcc/version.c

    diff -Naur gcc-4.8.2.orig/gcc/version.c gcc-4.8.2/gcc/version.c
    old new  
    3232   Makefile.  */
    3333
    3434const char version_string[] = BASEVER DATESTAMP DEVPHASE REVISION;
    35 const char pkgversion_string[] = PKGVERSION;
     35const char pkgversion_string[] = "(GCC for Cross-LFS 4.8.2.20131101) ";
  • libffi/doc/libffi.info

    diff -Naur gcc-4.8.2.orig/libffi/doc/libffi.info gcc-4.8.2/libffi/doc/libffi.info
    old new  
    1 This is libffi.info, produced by makeinfo version 5.1 from libffi.texi.
    2 
    3 This manual is for Libffi, a portable foreign-function interface
    4 library.
    5 
    6    Copyright (C) 2008, 2010, 2011 Red Hat, Inc.
    7 
    8      Permission is granted to copy, distribute and/or modify this
    9      document under the terms of the GNU General Public License as
    10      published by the Free Software Foundation; either version 2, or (at
    11      your option) any later version.  A copy of the license is included
    12      in the section entitled "GNU General Public License".
    13 
    14 INFO-DIR-SECTION Development
    15 START-INFO-DIR-ENTRY
    16 * libffi: (libffi).             Portable foreign-function interface library.
    17 END-INFO-DIR-ENTRY
    18 
    19 
    20 File: libffi.info,  Node: Top,  Next: Introduction,  Up: (dir)
    21 
    22 libffi
    23 ******
    24 
    25 This manual is for Libffi, a portable foreign-function interface
    26 library.
    27 
    28    Copyright (C) 2008, 2010, 2011 Red Hat, Inc.
    29 
    30      Permission is granted to copy, distribute and/or modify this
    31      document under the terms of the GNU General Public License as
    32      published by the Free Software Foundation; either version 2, or (at
    33      your option) any later version.  A copy of the license is included
    34      in the section entitled "GNU General Public License".
    35 
    36 * Menu:
    37 
    38 * Introduction::                What is libffi?
    39 * Using libffi::                How to use libffi.
    40 * Missing Features::            Things libffi can't do.
    41 * Index::                       Index.
    42 
    43 
    44 File: libffi.info,  Node: Introduction,  Next: Using libffi,  Prev: Top,  Up: Top
    45 
    46 1 What is libffi?
    47 *****************
    48 
    49 Compilers for high level languages generate code that follow certain
    50 conventions.  These conventions are necessary, in part, for separate
    51 compilation to work.  One such convention is the "calling convention".
    52 The calling convention is a set of assumptions made by the compiler
    53 about where function arguments will be found on entry to a function.  A
    54 calling convention also specifies where the return value for a function
    55 is found.  The calling convention is also sometimes called the "ABI" or
    56 "Application Binary Interface".
    57 
    58    Some programs may not know at the time of compilation what arguments
    59 are to be passed to a function.  For instance, an interpreter may be
    60 told at run-time about the number and types of arguments used to call a
    61 given function.  'Libffi' can be used in such programs to provide a
    62 bridge from the interpreter program to compiled code.
    63 
    64    The 'libffi' library provides a portable, high level programming
    65 interface to various calling conventions.  This allows a programmer to
    66 call any function specified by a call interface description at run time.
    67 
    68    FFI stands for Foreign Function Interface.  A foreign function
    69 interface is the popular name for the interface that allows code written
    70 in one language to call code written in another language.  The 'libffi'
    71 library really only provides the lowest, machine dependent layer of a
    72 fully featured foreign function interface.  A layer must exist above
    73 'libffi' that handles type conversions for values passed between the two
    74 languages.
    75 
    76 
    77 File: libffi.info,  Node: Using libffi,  Next: Missing Features,  Prev: Introduction,  Up: Top
    78 
    79 2 Using libffi
    80 **************
    81 
    82 * Menu:
    83 
    84 * The Basics::                  The basic libffi API.
    85 * Simple Example::              A simple example.
    86 * Types::                       libffi type descriptions.
    87 * Multiple ABIs::               Different passing styles on one platform.
    88 * The Closure API::             Writing a generic function.
    89 * Closure Example::             A closure example.
    90 
    91 
    92 File: libffi.info,  Node: The Basics,  Next: Simple Example,  Up: Using libffi
    93 
    94 2.1 The Basics
    95 ==============
    96 
    97 'Libffi' assumes that you have a pointer to the function you wish to
    98 call and that you know the number and types of arguments to pass it, as
    99 well as the return type of the function.
    100 
    101    The first thing you must do is create an 'ffi_cif' object that
    102 matches the signature of the function you wish to call.  This is a
    103 separate step because it is common to make multiple calls using a single
    104 'ffi_cif'.  The "cif" in 'ffi_cif' stands for Call InterFace.  To
    105 prepare a call interface object, use the function 'ffi_prep_cif'.
    106 
    107  -- Function: ffi_status ffi_prep_cif (ffi_cif *CIF, ffi_abi ABI,
    108           unsigned int NARGS, ffi_type *RTYPE, ffi_type **ARGTYPES)
    109      This initializes CIF according to the given parameters.
    110 
    111      ABI is the ABI to use; normally 'FFI_DEFAULT_ABI' is what you want.
    112      *note Multiple ABIs:: for more information.
    113 
    114      NARGS is the number of arguments that this function accepts.
    115 
    116      RTYPE is a pointer to an 'ffi_type' structure that describes the
    117      return type of the function.  *Note Types::.
    118 
    119      ARGTYPES is a vector of 'ffi_type' pointers.  ARGTYPES must have
    120      NARGS elements.  If NARGS is 0, this argument is ignored.
    121 
    122      'ffi_prep_cif' returns a 'libffi' status code, of type
    123      'ffi_status'.  This will be either 'FFI_OK' if everything worked
    124      properly; 'FFI_BAD_TYPEDEF' if one of the 'ffi_type' objects is
    125      incorrect; or 'FFI_BAD_ABI' if the ABI parameter is invalid.
    126 
    127    If the function being called is variadic (varargs) then
    128 'ffi_prep_cif_var' must be used instead of 'ffi_prep_cif'.
    129 
    130  -- Function: ffi_status ffi_prep_cif_var (ffi_cif *CIF, ffi_abi varabi,
    131           unsigned int NFIXEDARGS, unsigned int varntotalargs, ffi_type
    132           *RTYPE, ffi_type **ARGTYPES)
    133      This initializes CIF according to the given parameters for a call
    134      to a variadic function.  In general it's operation is the same as
    135      for 'ffi_prep_cif' except that:
    136 
    137      NFIXEDARGS is the number of fixed arguments, prior to any variadic
    138      arguments.  It must be greater than zero.
    139 
    140      NTOTALARGS the total number of arguments, including variadic and
    141      fixed arguments.
    142 
    143      Note that, different cif's must be prepped for calls to the same
    144      function when different numbers of arguments are passed.
    145 
    146      Also note that a call to 'ffi_prep_cif_var' with
    147      NFIXEDARGS=NOTOTALARGS is NOT equivalent to a call to
    148      'ffi_prep_cif'.
    149 
    150    To call a function using an initialized 'ffi_cif', use the 'ffi_call'
    151 function:
    152 
    153  -- Function: void ffi_call (ffi_cif *CIF, void *FN, void *RVALUE, void
    154           **AVALUES)
    155      This calls the function FN according to the description given in
    156      CIF.  CIF must have already been prepared using 'ffi_prep_cif'.
    157 
    158      RVALUE is a pointer to a chunk of memory that will hold the result
    159      of the function call.  This must be large enough to hold the result
    160      and must be suitably aligned; it is the caller's responsibility to
    161      ensure this.  If CIF declares that the function returns 'void'
    162      (using 'ffi_type_void'), then RVALUE is ignored.  If RVALUE is
    163      'NULL', then the return value is discarded.
    164 
    165      AVALUES is a vector of 'void *' pointers that point to the memory
    166      locations holding the argument values for a call.  If CIF declares
    167      that the function has no arguments (i.e., NARGS was 0), then
    168      AVALUES is ignored.  Note that argument values may be modified by
    169      the callee (for instance, structs passed by value); the burden of
    170      copying pass-by-value arguments is placed on the caller.
    171 
    172 
    173 File: libffi.info,  Node: Simple Example,  Next: Types,  Prev: The Basics,  Up: Using libffi
    174 
    175 2.2 Simple Example
    176 ==================
    177 
    178 Here is a trivial example that calls 'puts' a few times.
    179 
    180      #include <stdio.h>
    181      #include <ffi.h>
    182 
    183      int main()
    184      {
    185        ffi_cif cif;
    186        ffi_type *args[1];
    187        void *values[1];
    188        char *s;
    189        int rc;
    190 
    191        /* Initialize the argument info vectors */
    192        args[0] = &ffi_type_pointer;
    193        values[0] = &s;
    194 
    195        /* Initialize the cif */
    196        if (ffi_prep_cif(&cif, FFI_DEFAULT_ABI, 1,
    197                        &ffi_type_uint, args) == FFI_OK)
    198          {
    199            s = "Hello World!";
    200            ffi_call(&cif, puts, &rc, values);
    201            /* rc now holds the result of the call to puts */
    202 
    203            /* values holds a pointer to the function's arg, so to
    204               call puts() again all we need to do is change the
    205               value of s */
    206            s = "This is cool!";
    207            ffi_call(&cif, puts, &rc, values);
    208          }
    209 
    210        return 0;
    211      }
    212 
    213 
    214 File: libffi.info,  Node: Types,  Next: Multiple ABIs,  Prev: Simple Example,  Up: Using libffi
    215 
    216 2.3 Types
    217 =========
    218 
    219 * Menu:
    220 
    221 * Primitive Types::             Built-in types.
    222 * Structures::                  Structure types.
    223 * Type Example::                Structure type example.
    224 
    225 
    226 File: libffi.info,  Node: Primitive Types,  Next: Structures,  Up: Types
    227 
    228 2.3.1 Primitive Types
    229 ---------------------
    230 
    231 'Libffi' provides a number of built-in type descriptors that can be used
    232 to describe argument and return types:
    233 
    234 'ffi_type_void'
    235      The type 'void'.  This cannot be used for argument types, only for
    236      return values.
    237 
    238 'ffi_type_uint8'
    239      An unsigned, 8-bit integer type.
    240 
    241 'ffi_type_sint8'
    242      A signed, 8-bit integer type.
    243 
    244 'ffi_type_uint16'
    245      An unsigned, 16-bit integer type.
    246 
    247 'ffi_type_sint16'
    248      A signed, 16-bit integer type.
    249 
    250 'ffi_type_uint32'
    251      An unsigned, 32-bit integer type.
    252 
    253 'ffi_type_sint32'
    254      A signed, 32-bit integer type.
    255 
    256 'ffi_type_uint64'
    257      An unsigned, 64-bit integer type.
    258 
    259 'ffi_type_sint64'
    260      A signed, 64-bit integer type.
    261 
    262 'ffi_type_float'
    263      The C 'float' type.
    264 
    265 'ffi_type_double'
    266      The C 'double' type.
    267 
    268 'ffi_type_uchar'
    269      The C 'unsigned char' type.
    270 
    271 'ffi_type_schar'
    272      The C 'signed char' type.  (Note that there is not an exact
    273      equivalent to the C 'char' type in 'libffi'; ordinarily you should
    274      either use 'ffi_type_schar' or 'ffi_type_uchar' depending on
    275      whether 'char' is signed.)
    276 
    277 'ffi_type_ushort'
    278      The C 'unsigned short' type.
    279 
    280 'ffi_type_sshort'
    281      The C 'short' type.
    282 
    283 'ffi_type_uint'
    284      The C 'unsigned int' type.
    285 
    286 'ffi_type_sint'
    287      The C 'int' type.
    288 
    289 'ffi_type_ulong'
    290      The C 'unsigned long' type.
    291 
    292 'ffi_type_slong'
    293      The C 'long' type.
    294 
    295 'ffi_type_longdouble'
    296      On platforms that have a C 'long double' type, this is defined.  On
    297      other platforms, it is not.
    298 
    299 'ffi_type_pointer'
    300      A generic 'void *' pointer.  You should use this for all pointers,
    301      regardless of their real type.
    302 
    303    Each of these is of type 'ffi_type', so you must take the address
    304 when passing to 'ffi_prep_cif'.
    305 
    306 
    307 File: libffi.info,  Node: Structures,  Next: Type Example,  Prev: Primitive Types,  Up: Types
    308 
    309 2.3.2 Structures
    310 ----------------
    311 
    312 Although 'libffi' has no special support for unions or bit-fields, it is
    313 perfectly happy passing structures back and forth.  You must first
    314 describe the structure to 'libffi' by creating a new 'ffi_type' object
    315 for it.
    316 
    317  -- ffi_type:
    318      The 'ffi_type' has the following members:
    319      'size_t size'
    320           This is set by 'libffi'; you should initialize it to zero.
    321 
    322      'unsigned short alignment'
    323           This is set by 'libffi'; you should initialize it to zero.
    324 
    325      'unsigned short type'
    326           For a structure, this should be set to 'FFI_TYPE_STRUCT'.
    327 
    328      'ffi_type **elements'
    329           This is a 'NULL'-terminated array of pointers to 'ffi_type'
    330           objects.  There is one element per field of the struct.
    331 
    332 
    333 File: libffi.info,  Node: Type Example,  Prev: Structures,  Up: Types
    334 
    335 2.3.3 Type Example
    336 ------------------
    337 
    338 The following example initializes a 'ffi_type' object representing the
    339 'tm' struct from Linux's 'time.h'.
    340 
    341    Here is how the struct is defined:
    342 
    343      struct tm {
    344          int tm_sec;
    345          int tm_min;
    346          int tm_hour;
    347          int tm_mday;
    348          int tm_mon;
    349          int tm_year;
    350          int tm_wday;
    351          int tm_yday;
    352          int tm_isdst;
    353          /* Those are for future use. */
    354          long int __tm_gmtoff__;
    355          __const char *__tm_zone__;
    356      };
    357 
    358    Here is the corresponding code to describe this struct to 'libffi':
    359 
    360          {
    361            ffi_type tm_type;
    362            ffi_type *tm_type_elements[12];
    363            int i;
    364 
    365            tm_type.size = tm_type.alignment = 0;
    366            tm_type.elements = &tm_type_elements;
    367 
    368            for (i = 0; i < 9; i++)
    369                tm_type_elements[i] = &ffi_type_sint;
    370 
    371            tm_type_elements[9] = &ffi_type_slong;
    372            tm_type_elements[10] = &ffi_type_pointer;
    373            tm_type_elements[11] = NULL;
    374 
    375            /* tm_type can now be used to represent tm argument types and
    376          return types for ffi_prep_cif() */
    377          }
    378 
    379 
    380 File: libffi.info,  Node: Multiple ABIs,  Next: The Closure API,  Prev: Types,  Up: Using libffi
    381 
    382 2.4 Multiple ABIs
    383 =================
    384 
    385 A given platform may provide multiple different ABIs at once.  For
    386 instance, the x86 platform has both 'stdcall' and 'fastcall' functions.
    387 
    388    'libffi' provides some support for this.  However, this is
    389 necessarily platform-specific.
    390 
    391 
    392 File: libffi.info,  Node: The Closure API,  Next: Closure Example,  Prev: Multiple ABIs,  Up: Using libffi
    393 
    394 2.5 The Closure API
    395 ===================
    396 
    397 'libffi' also provides a way to write a generic function - a function
    398 that can accept and decode any combination of arguments.  This can be
    399 useful when writing an interpreter, or to provide wrappers for arbitrary
    400 functions.
    401 
    402    This facility is called the "closure API". Closures are not supported
    403 on all platforms; you can check the 'FFI_CLOSURES' define to determine
    404 whether they are supported on the current platform.
    405 
    406    Because closures work by assembling a tiny function at runtime, they
    407 require special allocation on platforms that have a non-executable heap.
    408 Memory management for closures is handled by a pair of functions:
    409 
    410  -- Function: void *ffi_closure_alloc (size_t SIZE, void **CODE)
    411      Allocate a chunk of memory holding SIZE bytes.  This returns a
    412      pointer to the writable address, and sets *CODE to the
    413      corresponding executable address.
    414 
    415      SIZE should be sufficient to hold a 'ffi_closure' object.
    416 
    417  -- Function: void ffi_closure_free (void *WRITABLE)
    418      Free memory allocated using 'ffi_closure_alloc'.  The argument is
    419      the writable address that was returned.
    420 
    421    Once you have allocated the memory for a closure, you must construct
    422 a 'ffi_cif' describing the function call.  Finally you can prepare the
    423 closure function:
    424 
    425  -- Function: ffi_status ffi_prep_closure_loc (ffi_closure *CLOSURE,
    426           ffi_cif *CIF, void (*FUN) (ffi_cif *CIF, void *RET, void
    427           **ARGS, void *USER_DATA), void *USER_DATA, void *CODELOC)
    428      Prepare a closure function.
    429 
    430      CLOSURE is the address of a 'ffi_closure' object; this is the
    431      writable address returned by 'ffi_closure_alloc'.
    432 
    433      CIF is the 'ffi_cif' describing the function parameters.
    434 
    435      USER_DATA is an arbitrary datum that is passed, uninterpreted, to
    436      your closure function.
    437 
    438      CODELOC is the executable address returned by 'ffi_closure_alloc'.
    439 
    440      FUN is the function which will be called when the closure is
    441      invoked.  It is called with the arguments:
    442      CIF
    443           The 'ffi_cif' passed to 'ffi_prep_closure_loc'.
    444 
    445      RET
    446           A pointer to the memory used for the function's return value.
    447           FUN must fill this, unless the function is declared as
    448           returning 'void'.
    449 
    450      ARGS
    451           A vector of pointers to memory holding the arguments to the
    452           function.
    453 
    454      USER_DATA
    455           The same USER_DATA that was passed to 'ffi_prep_closure_loc'.
    456 
    457      'ffi_prep_closure_loc' will return 'FFI_OK' if everything went ok,
    458      and something else on error.
    459 
    460      After calling 'ffi_prep_closure_loc', you can cast CODELOC to the
    461      appropriate pointer-to-function type.
    462 
    463    You may see old code referring to 'ffi_prep_closure'.  This function
    464 is deprecated, as it cannot handle the need for separate writable and
    465 executable addresses.
    466 
    467 
    468 File: libffi.info,  Node: Closure Example,  Prev: The Closure API,  Up: Using libffi
    469 
    470 2.6 Closure Example
    471 ===================
    472 
    473 A trivial example that creates a new 'puts' by binding 'fputs' with
    474 'stdin'.
    475 
    476      #include <stdio.h>
    477      #include <ffi.h>
    478 
    479      /* Acts like puts with the file given at time of enclosure. */
    480      void puts_binding(ffi_cif *cif, unsigned int *ret, void* args[],
    481                        FILE *stream)
    482      {
    483        *ret = fputs(*(char **)args[0], stream);
    484      }
    485 
    486      int main()
    487      {
    488        ffi_cif cif;
    489        ffi_type *args[1];
    490        ffi_closure *closure;
    491 
    492        int (*bound_puts)(char *);
    493        int rc;
    494 
    495        /* Allocate closure and bound_puts */
    496        closure = ffi_closure_alloc(sizeof(ffi_closure), &bound_puts);
    497 
    498        if (closure)
    499          {
    500            /* Initialize the argument info vectors */
    501            args[0] = &ffi_type_pointer;
    502 
    503            /* Initialize the cif */
    504            if (ffi_prep_cif(&cif, FFI_DEFAULT_ABI, 1,
    505                             &ffi_type_uint, args) == FFI_OK)
    506              {
    507                /* Initialize the closure, setting stream to stdout */
    508                if (ffi_prep_closure_loc(closure, &cif, puts_binding,
    509                                         stdout, bound_puts) == FFI_OK)
    510                  {
    511                    rc = bound_puts("Hello World!");
    512                    /* rc now holds the result of the call to fputs */
    513                  }
    514              }
    515          }
    516 
    517        /* Deallocate both closure, and bound_puts */
    518        ffi_closure_free(closure);
    519 
    520        return 0;
    521      }
    522 
    523 
    524 File: libffi.info,  Node: Missing Features,  Next: Index,  Prev: Using libffi,  Up: Top
    525 
    526 3 Missing Features
    527 ******************
    528 
    529 'libffi' is missing a few features.  We welcome patches to add support
    530 for these.
    531 
    532    * Variadic closures.
    533 
    534    * There is no support for bit fields in structures.
    535 
    536    * The closure API is
    537 
    538    * The "raw" API is undocumented.
    539 
    540    Note that variadic support is very new and tested on a relatively
    541 small number of platforms.
    542 
    543 
    544 File: libffi.info,  Node: Index,  Prev: Missing Features,  Up: Top
    545 
    546 Index
    547 *****
    548 
    549 [index]
    550 * Menu:
    551 
    552 * ABI:                                   Introduction.         (line 13)
    553 * Application Binary Interface:          Introduction.         (line 13)
    554 * calling convention:                    Introduction.         (line 13)
    555 * cif:                                   The Basics.           (line 14)
    556 * closure API:                           The Closure API.      (line 13)
    557 * closures:                              The Closure API.      (line 13)
    558 * FFI:                                   Introduction.         (line 31)
    559 * ffi_call:                              The Basics.           (line 62)
    560 * FFI_CLOSURES:                          The Closure API.      (line 13)
    561 * ffi_closure_alloc:                     The Closure API.      (line 19)
    562 * ffi_closure_free:                      The Closure API.      (line 26)
    563 * ffi_prep_cif:                          The Basics.           (line 16)
    564 * ffi_prep_cif_var:                      The Basics.           (line 39)
    565 * ffi_prep_closure_loc:                  The Closure API.      (line 34)
    566 * ffi_status:                            The Basics.           (line 16)
    567 * ffi_status <1>:                        The Basics.           (line 39)
    568 * ffi_status <2>:                        The Closure API.      (line 34)
    569 * ffi_type:                              Structures.           (line 11)
    570 * ffi_type_double:                       Primitive Types.      (line 41)
    571 * ffi_type_float:                        Primitive Types.      (line 38)
    572 * ffi_type_longdouble:                   Primitive Types.      (line 71)
    573 * ffi_type_pointer:                      Primitive Types.      (line 75)
    574 * ffi_type_schar:                        Primitive Types.      (line 47)
    575 * ffi_type_sint:                         Primitive Types.      (line 62)
    576 * ffi_type_sint16:                       Primitive Types.      (line 23)
    577 * ffi_type_sint32:                       Primitive Types.      (line 29)
    578 * ffi_type_sint64:                       Primitive Types.      (line 35)
    579 * ffi_type_sint8:                        Primitive Types.      (line 17)
    580 * ffi_type_slong:                        Primitive Types.      (line 68)
    581 * ffi_type_sshort:                       Primitive Types.      (line 56)
    582 * ffi_type_uchar:                        Primitive Types.      (line 44)
    583 * ffi_type_uint:                         Primitive Types.      (line 59)
    584 * ffi_type_uint16:                       Primitive Types.      (line 20)
    585 * ffi_type_uint32:                       Primitive Types.      (line 26)
    586 * ffi_type_uint64:                       Primitive Types.      (line 32)
    587 * ffi_type_uint8:                        Primitive Types.      (line 14)
    588 * ffi_type_ulong:                        Primitive Types.      (line 65)
    589 * ffi_type_ushort:                       Primitive Types.      (line 53)
    590 * ffi_type_void:                         Primitive Types.      (line 10)
    591 * Foreign Function Interface:            Introduction.         (line 31)
    592 * void:                                  The Basics.           (line 62)
    593 * void <1>:                              The Closure API.      (line 19)
    594 * void <2>:                              The Closure API.      (line 26)
    595 
    596 
    597 
    598 Tag Table:
    599 Node: Top682
    600 Node: Introduction1429
    601 Node: Using libffi3061
    602 Node: The Basics3547
    603 Node: Simple Example7187
    604 Node: Types8214
    605 Node: Primitive Types8497
    606 Node: Structures10318
    607 Node: Type Example11182
    608 Node: Multiple ABIs12405
    609 Node: The Closure API12776
    610 Node: Closure Example15720
    611 Node: Missing Features17279
    612 Node: Index17732
    613 
    614 End Tag Table
  • libgo/Makefile.am

    diff -Naur gcc-4.8.2.orig/libgo/Makefile.am gcc-4.8.2/libgo/Makefile.am
    old new  
    424424        runtime/go-caller.c \
    425425        runtime/go-callers.c \
    426426        runtime/go-can-convert-interface.c \
     427        runtime/go-cdiv.c \
    427428        runtime/go-cgo.c \
    428429        runtime/go-check-interface.c \
    429430        runtime/go-construct-map.c \
  • libgo/Makefile.in

    diff -Naur gcc-4.8.2.orig/libgo/Makefile.in gcc-4.8.2/libgo/Makefile.in
    old new  
    195195@LIBGO_IS_LINUX_TRUE@am__objects_5 = getncpu-linux.lo
    196196am__objects_6 = go-append.lo go-assert.lo go-assert-interface.lo \
    197197        go-byte-array-to-string.lo go-breakpoint.lo go-caller.lo \
    198         go-callers.lo go-can-convert-interface.lo go-cgo.lo \
     198        go-callers.lo go-can-convert-interface.lo go-cdiv.lo go-cgo.lo \
    199199        go-check-interface.lo go-construct-map.lo \
    200200        go-convert-interface.lo go-copy.lo go-defer.lo \
    201201        go-deferred-recover.lo go-eface-compare.lo \
     
    757757        runtime/go-caller.c \
    758758        runtime/go-callers.c \
    759759        runtime/go-can-convert-interface.c \
     760        runtime/go-cdiv.c \
    760761        runtime/go-cgo.c \
    761762        runtime/go-check-interface.c \
    762763        runtime/go-construct-map.c \
     
    23682369@AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/go-caller.Plo@am__quote@
    23692370@AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/go-callers.Plo@am__quote@
    23702371@AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/go-can-convert-interface.Plo@am__quote@
     2372@AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/go-cdiv.Plo@am__quote@
    23712373@AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/go-cgo.Plo@am__quote@
    23722374@AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/go-check-interface.Plo@am__quote@
    23732375@AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/go-construct-map.Plo@am__quote@
     
    25542556@AMDEP_TRUE@@am__fastdepCC_FALSE@       DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@
    25552557@am__fastdepCC_FALSE@   $(LIBTOOL)  --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) -c -o go-can-convert-interface.lo `test -f 'runtime/go-can-convert-interface.c' || echo '$(srcdir)/'`runtime/go-can-convert-interface.c
    25562558
     2559go-cdiv.lo: runtime/go-cdiv.c
     2560@am__fastdepCC_TRUE@    $(LIBTOOL)  --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) -MT go-cdiv.lo -MD -MP -MF $(DEPDIR)/go-cdiv.Tpo -c -o go-cdiv.lo `test -f 'runtime/go-cdiv.c' || echo '$(srcdir)/'`runtime/go-cdiv.c
     2561@am__fastdepCC_TRUE@    $(am__mv) $(DEPDIR)/go-cdiv.Tpo $(DEPDIR)/go-cdiv.Plo
     2562@AMDEP_TRUE@@am__fastdepCC_FALSE@       source='runtime/go-cdiv.c' object='go-cdiv.lo' libtool=yes @AMDEPBACKSLASH@
     2563@AMDEP_TRUE@@am__fastdepCC_FALSE@       DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@
     2564@am__fastdepCC_FALSE@   $(LIBTOOL)  --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) -c -o go-cdiv.lo `test -f 'runtime/go-cdiv.c' || echo '$(srcdir)/'`runtime/go-cdiv.c
     2565
    25572566go-cgo.lo: runtime/go-cgo.c
    25582567@am__fastdepCC_TRUE@    $(LIBTOOL)  --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) -MT go-cgo.lo -MD -MP -MF $(DEPDIR)/go-cgo.Tpo -c -o go-cgo.lo `test -f 'runtime/go-cgo.c' || echo '$(srcdir)/'`runtime/go-cgo.c
    25592568@am__fastdepCC_TRUE@    $(am__mv) $(DEPDIR)/go-cgo.Tpo $(DEPDIR)/go-cgo.Plo
  • libgo/config.h.in

    diff -Naur gcc-4.8.2.orig/libgo/config.h.in gcc-4.8.2/libgo/config.h.in
    old new  
    3939/* Define to 1 if you have the `dl_iterate_phdr' function. */
    4040#undef HAVE_DL_ITERATE_PHDR
    4141
     42/* Define to 1 if you have the `dup3' function. */
     43#undef HAVE_DUP3
     44
    4245/* Define to 1 if you have the `epoll_create1' function. */
    4346#undef HAVE_EPOLL_CREATE1
    4447
     
    6669/* Define if _Unwind_GetIPInfo is available. */
    6770#undef HAVE_GETIPINFO
    6871
     72/* Define to 1 if you have the `getxattr' function. */
     73#undef HAVE_GETXATTR
     74
    6975/* Define to 1 if you have the `inotify_add_watch' function. */
    7076#undef HAVE_INOTIFY_ADD_WATCH
    7177
     
    111117/* Define to 1 if you have the <linux/rtnetlink.h> header file. */
    112118#undef HAVE_LINUX_RTNETLINK_H
    113119
     120/* Define to 1 if you have the `listxattr' function. */
     121#undef HAVE_LISTXATTR
     122
    114123/* Define to 1 if the system has the type `loff_t'. */
    115124#undef HAVE_LOFF_T
    116125
     
    171180/* Define to 1 if you have the `pipe2' function. */
    172181#undef HAVE_PIPE2
    173182
     183/* Define to 1 if you have the `removexattr' function. */
     184#undef HAVE_REMOVEXATTR
     185
    174186/* Define to 1 if you have the `renameat' function. */
    175187#undef HAVE_RENAMEAT
    176188
     
    180192/* Define to 1 if you have the `setenv' function. */
    181193#undef HAVE_SETENV
    182194
     195/* Define to 1 if you have the `setxattr' function. */
     196#undef HAVE_SETXATTR
     197
    183198/* Define to 1 if you have the `sinl' function. */
    184199#undef HAVE_SINL
    185200
  • libgo/configure

    diff -Naur gcc-4.8.2.orig/libgo/configure gcc-4.8.2/libgo/configure
    old new  
    1470014700fi
    1470114701
    1470214702
    14703 for ac_func in accept4 epoll_create1 faccessat fallocate fchmodat fchownat futimesat inotify_add_watch inotify_init inotify_init1 inotify_rm_watch mkdirat mknodat openat pipe2 renameat sync_file_range splice tee unlinkat unshare utimensat
     14703for ac_func in accept4 dup3 epoll_create1 faccessat fallocate fchmodat fchownat futimesat getxattr inotify_add_watch inotify_init inotify_init1 inotify_rm_watch listxattr mkdirat mknodat openat pipe2 removexattr renameat setxattr sync_file_range splice tee unlinkat unshare utimensat
    1470414704do :
    1470514705  as_ac_var=`$as_echo "ac_cv_func_$ac_func" | $as_tr_sh`
    1470614706ac_fn_c_check_func "$LINENO" "$ac_func" "$as_ac_var"
  • libgo/configure.ac

    diff -Naur gcc-4.8.2.orig/libgo/configure.ac gcc-4.8.2/libgo/configure.ac
    old new  
    503503AM_CONDITIONAL(HAVE_STRERROR_R, test "$ac_cv_func_strerror_r" = yes)
    504504AM_CONDITIONAL(HAVE_WAIT4, test "$ac_cv_func_wait4" = yes)
    505505
    506 AC_CHECK_FUNCS(accept4 epoll_create1 faccessat fallocate fchmodat fchownat futimesat inotify_add_watch inotify_init inotify_init1 inotify_rm_watch mkdirat mknodat openat pipe2 renameat sync_file_range splice tee unlinkat unshare utimensat)
     506AC_CHECK_FUNCS(accept4 dup3 epoll_create1 faccessat fallocate fchmodat fchownat futimesat getxattr inotify_add_watch inotify_init inotify_init1 inotify_rm_watch listxattr mkdirat mknodat openat pipe2 removexattr renameat setxattr sync_file_range splice tee unlinkat unshare utimensat)
    507507AC_TYPE_OFF_T
    508508AC_CHECK_TYPES([loff_t])
    509509
  • libgo/go/syscall/libcall_linux.go

    diff -Naur gcc-4.8.2.orig/libgo/go/syscall/libcall_linux.go gcc-4.8.2/libgo/go/syscall/libcall_linux.go
    old new  
    190190//sys   Adjtimex(buf *Timex) (state int, err error)
    191191//adjtimex(buf *Timex) _C_int
    192192
     193//sysnb Dup3(oldfd int, newfd int, flags int) (err error)
     194//dup3(oldfd _C_int, newfd _C_int, flags _C_int) _C_int
     195
    193196//sys   Faccessat(dirfd int, path string, mode uint32, flags int) (err error)
    194197//faccessat(dirfd _C_int, pathname *byte, mode _C_int, flags _C_int) _C_int
    195198
     
    268271        return origlen - len(buf), count, names
    269272}
    270273
     274//sys   Getxattr(path string, attr string, dest []byte) (sz int, err error)
     275//getxattr(path *byte, attr *byte, buf *byte, count Size_t) Ssize_t
     276
    271277//sys   InotifyAddWatch(fd int, pathname string, mask uint32) (watchdesc int, err error)
    272278//inotify_add_watch(fd _C_int, pathname *byte, mask uint32) _C_int
    273279
     
    283289//sys   Klogctl(typ int, buf []byte) (n int, err error)
    284290//klogctl(typ _C_int, bufp *byte, len _C_int) _C_int
    285291
     292//sys   Listxattr(path string, dest []byte) (sz int, err error)
     293//listxattr(path *byte, list *byte, size Size_t) Ssize_t
     294
    286295//sys   Mkdirat(dirfd int, path string, mode uint32) (err error)
    287296//mkdirat(dirfd _C_int, path *byte, mode Mode_t) _C_int
    288297
     
    305314//sys   PivotRoot(newroot string, putold string) (err error)
    306315//pivot_root(newroot *byte, putold *byte) _C_int
    307316
     317//sys   Removexattr(path string, attr string) (err error)
     318//removexattr(path *byte, name *byte) _C_int
     319
    308320//sys   Renameat(olddirfd int, oldpath string, newdirfd int, newpath string) (err error)
    309321//renameat(olddirfd _C_int, oldpath *byte, newdirfd _C_int, newpath *byte) _C_int
    310322
     
    338350//sysnb Setresuid(ruid int, eguid int, suid int) (err error)
    339351//setresuid(ruid Uid_t, euid Uid_t, suid Uid_t) _C_int
    340352
     353//sys   Setxattr(path string, attr string, data []byte, flags int) (err error)
     354//setxattr(path *byte, name *byte, value *byte, size Size_t, flags _C_int) _C_int
     355
    341356//sys   splice(rfd int, roff *_loff_t, wfd int, woff *_loff_t, len int, flags int) (n int64, err error)
    342357//splice(rfd _C_int, roff *_loff_t, wfd _C_int, woff *_loff_t, len Size_t, flags _C_uint) Ssize_t
    343358func Splice(rfd int, roff *int64, wfd int, woff *int64, len int, flags int) (n int64, err error) {
  • libgo/go/syscall/libcall_posix.go

    diff -Naur gcc-4.8.2.orig/libgo/go/syscall/libcall_posix.go gcc-4.8.2/libgo/go/syscall/libcall_posix.go
    old new  
    238238//sysnb Getppid() (ppid int)
    239239//getppid() Pid_t
    240240
     241//sys Getpriority(which int, who int) (prio int, err error)
     242//getpriority(which _C_int, who _C_int) _C_int
     243
    241244//sysnb Getrlimit(resource int, rlim *Rlimit) (err error)
    242245//getrlimit(resource _C_int, rlim *Rlimit) _C_int
    243246
     
    307310//sysnb Setpgid(pid int, pgid int) (err error)
    308311//setpgid(pid Pid_t, pgid Pid_t) _C_int
    309312
     313//sys Setpriority(which int, who int, prio int) (err error)
     314//setpriority(which _C_int, who _C_int, prio _C_int) _C_int
     315
    310316//sysnb Setreuid(ruid int, euid int) (err error)
    311317//setreuid(ruid Uid_t, euid Uid_t) _C_int
    312318
  • libgo/mksysinfo.sh

    diff -Naur gcc-4.8.2.orig/libgo/mksysinfo.sh gcc-4.8.2/libgo/mksysinfo.sh
    old new  
    10351035grep '^const _LOCK_' gen-sysinfo.go |
    10361036    sed -e 's/^\(const \)_\(LOCK_[^= ]*\)\(.*\)$/\1\2 = _\2/' >> ${OUT}
    10371037
     1038# The PRIO constants.
     1039grep '^const _PRIO_' gen-sysinfo.go | \
     1040  sed -e 's/^\(const \)_\(PRIO_[^= ]*\)\(.*\)$/\1\2 = _\2/' >> ${OUT}
     1041
    10381042# The GNU/Linux LINUX_REBOOT flags.
    10391043grep '^const _LINUX_REBOOT_' gen-sysinfo.go |
    10401044    sed -e 's/^\(const \)_\(LINUX_REBOOT_[^= ]*\)\(.*\)$/\1\2 = _\2/' >> ${OUT}
  • libgo/runtime/go-cdiv.c

    diff -Naur gcc-4.8.2.orig/libgo/runtime/go-cdiv.c gcc-4.8.2/libgo/runtime/go-cdiv.c
    old new  
     1/* go-cdiv.c -- complex division routines
     2
     3   Copyright 2013 The Go Authors. All rights reserved.
     4   Use of this source code is governed by a BSD-style
     5   license that can be found in the LICENSE file.  */
     6
     7/* Calls to these functions are generated by the Go frontend for
     8   division of complex64 or complex128.  We use these because Go's
     9   complex division expects slightly different results from the GCC
     10   default.  When dividing NaN+1.0i / 0+0i, Go expects NaN+NaNi but
     11   GCC generates NaN+Infi.  NaN+Infi seems wrong seems the rules of
     12   C99 Annex G specify that if either side of a complex number is Inf,
     13   the the whole number is Inf, but an operation involving NaN ought
     14   to result in NaN, not Inf.  */
     15
     16__complex float
     17__go_complex64_div (__complex float a, __complex float b)
     18{
     19  if (__builtin_expect (b == 0+0i, 0))
     20    {
     21      if (!__builtin_isinff (__real__ a)
     22          && !__builtin_isinff (__imag__ a)
     23          && (__builtin_isnanf (__real__ a) || __builtin_isnanf (__imag__ a)))
     24        {
     25          /* Pass "1" to nanf to match math/bits.go.  */
     26          return __builtin_nanf("1") + __builtin_nanf("1")*1i;
     27        }
     28    }
     29  return a / b;
     30}
     31
     32__complex double
     33__go_complex128_div (__complex double a, __complex double b)
     34{
     35  if (__builtin_expect (b == 0+0i, 0))
     36    {
     37      if (!__builtin_isinf (__real__ a)
     38          && !__builtin_isinf (__imag__ a)
     39          && (__builtin_isnan (__real__ a) || __builtin_isnan (__imag__ a)))
     40        {
     41          /* Pass "1" to nan to match math/bits.go.  */
     42          return __builtin_nan("1") + __builtin_nan("1")*1i;
     43        }
     44    }
     45  return a / b;
     46}
  • libgo/runtime/go-make-slice.c

    diff -Naur gcc-4.8.2.orig/libgo/runtime/go-make-slice.c gcc-4.8.2/libgo/runtime/go-make-slice.c
    old new  
    3434  std = (const struct __go_slice_type *) td;
    3535
    3636  ilen = (intgo) len;
    37   if (ilen < 0 || (uintptr_t) ilen != len)
     37  if (ilen < 0
     38      || (uintptr_t) ilen != len
     39      || (std->__element_type->__size > 0
     40          && len > MaxMem / std->__element_type->__size))
    3841    runtime_panicstring ("makeslice: len out of range");
    3942
    4043  icap = (intgo) cap;
  • libgo/runtime/go-nosys.c

    diff -Naur gcc-4.8.2.orig/libgo/runtime/go-nosys.c gcc-4.8.2/libgo/runtime/go-nosys.c
    old new  
    4343}
    4444#endif
    4545
     46#ifndef HAVE_DUP3
     47int
     48dup3 (int oldfd __attribute__ ((unused)),
     49      int newfd __attribute__ ((unused)),
     50      int flags __attribute__ ((unused)))
     51{
     52  errno = ENOSYS;
     53  return -1;
     54}
     55#endif
     56
    4657#ifndef HAVE_EPOLL_CREATE1
    4758int
    4859epoll_create1 (int flags __attribute__ ((unused)))
     
    112123}
    113124#endif
    114125
     126#ifndef HAVE_GETXATTR
     127ssize_t
     128getxattr (const char *path __attribute__ ((unused)),
     129          const char *name __attribute__ ((unused)),
     130          void *value __attribute__ ((unused)),
     131          size_t size __attribute__ ((unused)))
     132{
     133  errno = ENOSYS;
     134  return -1;
     135}
     136#endif
     137
    115138#ifndef HAVE_INOTIFY_ADD_WATCH
    116139int
    117140inotify_add_watch (int fd __attribute__ ((unused)),
     
    151174}
    152175#endif
    153176
     177#ifndef HAVE_LISTXATTR
     178ssize_t
     179listxattr (const char *path __attribute__ ((unused)),
     180           char *list __attribute__ ((unused)),
     181           size_t size __attribute__ ((unused)))
     182{
     183  errno = ENOSYS;
     184  return -1;
     185}
     186#endif
     187
    154188#ifndef HAVE_MKDIRAT
    155189int
    156190mkdirat (int dirfd __attribute__ ((unused)),
     
    196230}
    197231#endif
    198232
     233#ifndef HAVE_REMOVEXATTR
     234int
     235removexattr (const char *path __attribute__ ((unused)),
     236             const char *name __attribute__ ((unused)))
     237{
     238  errno = ENOSYS;
     239  return -1;
     240}
     241#endif
     242
    199243#ifndef HAVE_RENAMEAT
    200244int
    201245renameat (int olddirfd __attribute__ ((unused)),
     
    205249{
    206250  errno = ENOSYS;
    207251  return -1;
     252}
     253#endif
     254
     255#ifndef HAVE_SETXATTR
     256int
     257setxattr (const char *path __attribute__ ((unused)),
     258          const char *name __attribute__ ((unused)),
     259          const void *value __attribute__ ((unused)),
     260          size_t size __attribute__ ((unused)),
     261          int flags __attribute__ ((unused)))
     262{
     263  errno = ENOSYS;
     264  return -1;
    208265}
    209266#endif
    210267
  • libgo/runtime/go-signal.c

    diff -Naur gcc-4.8.2.orig/libgo/runtime/go-signal.c gcc-4.8.2/libgo/runtime/go-signal.c
    old new  
    399399{
    400400  G *gp;
    401401  M *mp;
     402#ifdef USING_SPLIT_STACK
     403  void *stack_context[10];
     404#endif
    402405
    403406  /* We are now running on the stack registered via sigaltstack.
    404407     (Actually there is a small span of time between runtime_siginit
     
    409412  if (gp != NULL)
    410413    {
    411414#ifdef USING_SPLIT_STACK
    412       __splitstack_getcontext (&gp->stack_context[0]);
     415      __splitstack_getcontext (&stack_context[0]);
    413416#endif
    414417    }
    415418
     
    432435  if (gp != NULL)
    433436    {
    434437#ifdef USING_SPLIT_STACK
    435       __splitstack_setcontext (&gp->stack_context[0]);
     438      __splitstack_setcontext (&stack_context[0]);
    436439#endif
    437440    }
    438441}
  • libitm/libitm.info

    diff -Naur gcc-4.8.2.orig/libitm/libitm.info gcc-4.8.2/libitm/libitm.info
    old new  
    1 This is libitm.info, produced by makeinfo version 5.1 from libitm.texi.
    2 
    3 Copyright (C) 2011-2013 Free Software Foundation, Inc.
    4 
    5    Permission is granted to copy, distribute and/or modify this document
    6 under the terms of the GNU Free Documentation License, Version 1.2 or
    7 any later version published by the Free Software Foundation; with no
    8 Invariant Sections, no Front-Cover Texts, and no Back-Cover Texts.  A
    9 copy of the license is included in the section entitled "GNU Free
    10 Documentation License".
    11 INFO-DIR-SECTION GNU Libraries
    12 START-INFO-DIR-ENTRY
    13 * libitm: (libitm).                    GNU Transactional Memory Library
    14 END-INFO-DIR-ENTRY
    15 
    16    This manual documents the GNU Transactional Memory Library.
    17 
    18    Copyright (C) 2011-2013 Free Software Foundation, Inc.
    19 
    20    Permission is granted to copy, distribute and/or modify this document
    21 under the terms of the GNU Free Documentation License, Version 1.2 or
    22 any later version published by the Free Software Foundation; with no
    23 Invariant Sections, no Front-Cover Texts, and no Back-Cover Texts.  A
    24 copy of the license is included in the section entitled "GNU Free
    25 Documentation License".
    26 
    27 
    28 File: libitm.info,  Node: Top,  Next: Enabling libitm,  Up: (dir)
    29 
    30 Introduction
    31 ************
    32 
    33 This manual documents the usage and internals of libitm, the GNU
    34 Transactional Memory Library.  It provides transaction support for
    35 accesses to a process' memory, enabling easy-to-use synchronization of
    36 accesses to shared memory by several threads.
    37 
    38 * Menu:
    39 
    40 * Enabling libitm::            How to enable libitm for your applications.
    41 * C/C++ Language Constructs for TM::
    42                                Notes on the language-level interface supported
    43                                by gcc.
    44 * The libitm ABI::             Notes on the external ABI provided by libitm.
    45 * Internals::                  Notes on libitm's internal synchronization.
    46 * GNU Free Documentation License::
    47                                How you can copy and share this manual.
    48 * Index::                      Index of this documentation.
    49 
    50 
    51 File: libitm.info,  Node: Enabling libitm,  Next: C/C++ Language Constructs for TM,  Prev: Top,  Up: Top
    52 
    53 1 Enabling libitm
    54 *****************
    55 
    56 To activate support for TM in C/C++, the compile-time flag '-fgnu-tm'
    57 must be specified.  This enables TM language-level constructs such as
    58 transaction statements (e.g., '__transaction_atomic', *note C/C++
    59 Language Constructs for TM:: for details).
    60 
    61 
    62 File: libitm.info,  Node: C/C++ Language Constructs for TM,  Next: The libitm ABI,  Prev: Enabling libitm,  Up: Top
    63 
    64 2 C/C++ Language Constructs for TM
    65 **********************************
    66 
    67 Transactions are supported in C++ and C in the form of transaction
    68 statements, transaction expressions, and function transactions.  In the
    69 following example, both 'a' and 'b' will be read and the difference will
    70 be written to 'c', all atomically and isolated from other transactions:
    71 
    72      __transaction_atomic { c = a - b; }
    73 
    74    Therefore, another thread can use the following code to concurrently
    75 update 'b' without ever causing 'c' to hold a negative value (and
    76 without having to use other synchronization constructs such as locks or
    77 C++11 atomics):
    78 
    79      __transaction_atomic { if (a > b) b++; }
    80 
    81    GCC follows the Draft Specification of Transactional Language
    82 Constructs for C++ (v1.1)
    83 (https://sites.google.com/site/tmforcplusplus/) in its implementation of
    84 transactions.
    85 
    86    The precise semantics of transactions are defined in terms of the
    87 C++11/C11 memory model (see the specification).  Roughly, transactions
    88 provide synchronization guarantees that are similar to what would be
    89 guaranteed when using a single global lock as a guard for all
    90 transactions.  Note that like other synchronization constructs in C/C++,
    91 transactions rely on a data-race-free program (e.g., a nontransactional
    92 write that is concurrent with a transactional read to the same memory
    93 location is a data race).
    94 
    95 
    96 File: libitm.info,  Node: The libitm ABI,  Next: Internals,  Prev: C/C++ Language Constructs for TM,  Up: Top
    97 
    98 3 The libitm ABI
    99 ****************
    100 
    101 The ABI provided by libitm is basically equal to the Linux variant of
    102 Intel's current TM ABI specification document (Revision 1.1, May 6 2009)
    103 but with the differences listed in this chapter.  It would be good if
    104 these changes would eventually be merged into a future version of this
    105 specification.  To ease look-up, the following subsections mirror the
    106 structure of this specification.
    107 
    108 3.1 [No changes] Objectives
    109 ===========================
    110 
    111 3.2 [No changes] Non-objectives
    112 ===============================
    113 
    114 3.3 Library design principles
    115 =============================
    116 
    117 3.3.1 [No changes] Calling conventions
    118 --------------------------------------
    119 
    120 3.3.2 [No changes] TM library algorithms
    121 ----------------------------------------
    122 
    123 3.3.3 [No changes] Optimized load and store routines
    124 ----------------------------------------------------
    125 
    126 3.3.4 [No changes] Aligned load and store routines
    127 --------------------------------------------------
    128 
    129 3.3.5 Data logging functions
    130 ----------------------------
    131 
    132 The memory locations accessed with transactional loads and stores and
    133 the memory locations whose values are logged must not overlap.  This
    134 required separation only extends to the scope of the execution of one
    135 transaction including all the executions of all nested transactions.
    136 
    137    The compiler must be consistent (within the scope of a single
    138 transaction) about which memory locations are shared and which are not
    139 shared with other threads (i.e., data must be accessed either
    140 transactionally or nontransactionally).  Otherwise, non-write-through TM
    141 algorithms would not work.
    142 
    143    For memory locations on the stack, this requirement extends to only
    144 the lifetime of the stack frame that the memory location belongs to (or
    145 the lifetime of the transaction, whichever is shorter).  Thus, memory
    146 that is reused for several stack frames could be target of both data
    147 logging and transactional accesses; however, this is harmless because
    148 these stack frames' lifetimes will end before the transaction finishes.
    149 
    150 3.3.6 [No changes] Scatter/gather calls
    151 ---------------------------------------
    152 
    153 3.3.7 [No changes] Serial and irrevocable mode
    154 ----------------------------------------------
    155 
    156 3.3.8 [No changes] Transaction descriptor
    157 -----------------------------------------
    158 
    159 3.3.9 Store allocation
    160 ----------------------
    161 
    162 There is no 'getTransaction' function.
    163 
    164 3.3.10 [No changes] Naming conventions
    165 --------------------------------------
    166 
    167 3.3.11 Function pointer encryption
    168 ----------------------------------
    169 
    170 Currently, this is not implemented.
    171 
    172 3.4 Types and macros list
    173 =========================
    174 
    175 '_ITM_codeProperties' has changed, *note Starting a transaction:
    176 txn-code-properties.  '_ITM_srcLocation' is not used.
    177 
    178 3.5 Function list
    179 =================
    180 
    181 3.5.1 Initialization and finalization functions
    182 -----------------------------------------------
    183 
    184 These functions are not part of the ABI.
    185 
    186 3.5.2 [No changes] Version checking
    187 -----------------------------------
    188 
    189 3.5.3 [No changes] Error reporting
    190 ----------------------------------
    191 
    192 3.5.4 [No changes] inTransaction call
    193 -------------------------------------
    194 
    195 3.5.5 State manipulation functions
    196 ----------------------------------
    197 
    198 There is no 'getTransaction' function.  Transaction identifiers for
    199 nested transactions will be ordered but not necessarily sequential
    200 (i.e., for a nested transaction's identifier IN and its enclosing
    201 transaction's identifier IE, it is guaranteed that IN >= IE).
    202 
    203 3.5.6 [No changes] Source locations
    204 -----------------------------------
    205 
    206 3.5.7 Starting a transaction
    207 ----------------------------
    208 
    209 3.5.7.1 Transaction code properties
    210 ...................................
    211 
    212 The bit 'hasNoXMMUpdate' is instead called 'hasNoVectorUpdate'.  Iff it
    213 is set, vector register save/restore is not necessary for any target
    214 machine.
    215 
    216    The 'hasNoFloatUpdate' bit ('0x0010') is new.  Iff it is set,
    217 floating point register save/restore is not necessary for any target
    218 machine.
    219 
    220    'undoLogCode' is not supported and a fatal runtime error will be
    221 raised if this bit is set.  It is not properly defined in the ABI why
    222 barriers other than undo logging are not present; Are they not necessary
    223 (e.g., a transaction operating purely on thread-local data) or have they
    224 been omitted by the compiler because it thinks that some kind of global
    225 synchronization (e.g., serial mode) might perform better?  The
    226 specification suggests that the latter might be the case, but the former
    227 seems to be more useful.
    228 
    229    The 'readOnly' bit ('0x4000') is new.  *TODO* Lexical or dynamic
    230 scope?
    231 
    232    'hasNoRetry' is not supported.  If this bit is not set, but
    233 'hasNoAbort' is set, the library can assume that transaction rollback
    234 will not be requested.
    235 
    236    It would be useful if the absence of externally-triggered rollbacks
    237 would be reported for the dynamic scope as well, not just for the
    238 lexical scope ('hasNoAbort').  Without this, a library cannot exploit
    239 this together with flat nesting.
    240 
    241    'exceptionBlock' is not supported because exception blocks are not
    242 used.
    243 
    244 3.5.7.2 [No changes] Windows exception state
    245 ............................................
    246 
    247 3.5.7.3 [No changes] Other machine state
    248 ........................................
    249 
    250 3.5.7.4 [No changes] Results from beginTransaction
    251 ..................................................
    252 
    253 3.5.8 Aborting a transaction
    254 ----------------------------
    255 
    256 '_ITM_rollbackTransaction' is not supported.  '_ITM_abortTransaction' is
    257 supported but the abort reasons 'exceptionBlockAbort', 'TMConflict', and
    258 'userRetry' are not supported.  There are no exception blocks in
    259 general, so the related cases also do not have to be considered.  To
    260 encode '__transaction_cancel [[outer]]', compilers must set the new
    261 'outerAbort' bit ('0x10') additionally to the 'userAbort' bit in the
    262 abort reason.
    263 
    264 3.5.9 Committing a transaction
    265 ------------------------------
    266 
    267 The exception handling (EH) scheme is different.  The Intel ABI requires
    268 the '_ITM_tryCommitTransaction' function that will return even when the
    269 commit failed and will have to be matched with calls to either
    270 '_ITM_abortTransaction' or '_ITM_commitTransaction'.  In contrast, gcc
    271 relies on transactional wrappers for the functions of the Exception
    272 Handling ABI and on one additional commit function (shown below).  This
    273 allows the TM to keep track of EH internally and thus it does not have
    274 to embed the cleanup of EH state into the existing EH code in the
    275 program.  '_ITM_tryCommitTransaction' is not supported.
    276 '_ITM_commitTransactionToId' is also not supported because the
    277 propagation of thrown exceptions will not bypass commits of nested
    278 transactions.
    279 
    280      void _ITM_commitTransactionEH(void *exc_ptr) ITM_REGPARM;
    281      void *_ITM_cxa_allocate_exception (size_t);
    282      void _ITM_cxa_throw (void *obj, void *tinfo, void *dest);
    283      void *_ITM_cxa_begin_catch (void *exc_ptr);
    284      void _ITM_cxa_end_catch (void);
    285 
    286    '_ITM_commitTransactionEH' must be called to commit a transaction if
    287 an exception could be in flight at this position in the code.  'exc_ptr'
    288 is the current exception or zero if there is no current exception.  The
    289 '_ITM_cxa...' functions are transactional wrappers for the respective
    290 '__cxa...' functions and must be called instead of these in
    291 transactional code.
    292 
    293    To support this EH scheme, libstdc++ needs to provide one additional
    294 function ('_cxa_tm_cleanup'), which is used by the TM to clean up the
    295 exception handling state while rolling back a transaction:
    296 
    297      void __cxa_tm_cleanup (void *unthrown_obj, void *cleanup_exc,
    298                             unsigned int caught_count);
    299 
    300    'unthrown_obj' is non-null if the program called
    301 '__cxa_allocate_exception' for this exception but did not yet called
    302 '__cxa_throw' for it.  'cleanup_exc' is non-null if the program is
    303 currently processing a cleanup along an exception path but has not
    304 caught this exception yet.  'caught_count' is the nesting depth of
    305 '__cxa_begin_catch' within the transaction (which can be counted by the
    306 TM using '_ITM_cxa_begin_catch' and '_ITM_cxa_end_catch');
    307 '__cxa_tm_cleanup' then performs rollback by essentially performing
    308 '__cxa_end_catch' that many times.
    309 
    310 3.5.10 Exception handling support
    311 ---------------------------------
    312 
    313 Currently, there is no support for functionality like
    314 '__transaction_cancel throw' as described in the C++ TM specification.
    315 Supporting this should be possible with the EH scheme explained
    316 previously because via the transactional wrappers for the EH ABI, the TM
    317 is able to observe and intercept EH.
    318 
    319 3.5.11 [No changes] Transition to serial-irrevocable mode
    320 ---------------------------------------------------------
    321 
    322 3.5.12 [No changes] Data transfer functions
    323 -------------------------------------------
    324 
    325 3.5.13 [No changes] Transactional memory copies
    326 -----------------------------------------------
    327 
    328 3.5.14 Transactional versions of memmove
    329 ----------------------------------------
    330 
    331 If either the source or destination memory region is to be accessed
    332 nontransactionally, then source and destination regions must not be
    333 overlapping.  The respective '_ITM_memmove' functions are still
    334 available but a fatal runtime error will be raised if such regions do
    335 overlap.  To support this functionality, the ABI would have to specify
    336 how the intersection of the regions has to be accessed (i.e.,
    337 transactionally or nontransactionally).
    338 
    339 3.5.15 [No changes] Transactional versions of memset
    340 ----------------------------------------------------
    341 
    342 3.5.16 [No changes] Logging functions
    343 -------------------------------------
    344 
    345 3.5.17 User-registered commit and undo actions
    346 ----------------------------------------------
    347 
    348 Commit actions will get executed in the same order in which the
    349 respective calls to '_ITM_addUserCommitAction' happened.  Only
    350 '_ITM_noTransactionId' is allowed as value for the
    351 'resumingTransactionId' argument.  Commit actions get executed after
    352 privatization safety has been ensured.
    353 
    354    Undo actions will get executed in reverse order compared to the order
    355 in which the respective calls to '_ITM_addUserUndoAction' happened.  The
    356 ordering of undo actions w.r.t.  the roll-back of other actions (e.g.,
    357 data transfers or memory allocations) is undefined.
    358 
    359    '_ITM_getThreadnum' is not supported currently because its only
    360 purpose is to provide a thread ID that matches some assumed performance
    361 tuning output, but this output is not part of the ABI nor further
    362 defined by it.
    363 
    364    '_ITM_dropReferences' is not supported currently because its
    365 semantics and the intention behind it is not entirely clear.  The
    366 specification suggests that this function is necessary because of
    367 certain orderings of data transfer undos and the releasing of memory
    368 regions (i.e., privatization).  However, this ordering is never defined,
    369 nor is the ordering of dropping references w.r.t.  other events.
    370 
    371 3.5.18 [New] Transactional indirect calls
    372 -----------------------------------------
    373 
    374 Indirect calls (i.e., calls through a function pointer) within
    375 transactions should execute the transactional clone of the original
    376 function (i.e., a clone of the original that has been fully instrumented
    377 to use the TM runtime), if such a clone is available.  The runtime
    378 provides two functions to register/deregister clone tables:
    379 
    380      struct clone_entry
    381      {
    382        void *orig, *clone;
    383      };
    384 
    385      void _ITM_registerTMCloneTable (clone_entry *table, size_t entries);
    386      void _ITM_deregisterTMCloneTable (clone_entry *table);
    387 
    388    Registered tables must be writable by the TM runtime, and must be
    389 live throughout the life-time of the TM runtime.
    390 
    391    *TODO* The intention was always to drop the registration functions
    392 entirely, and create a new ELF Phdr describing the linker-sorted table.
    393 Much like what currently happens for 'PT_GNU_EH_FRAME'.  This work kept
    394 getting bogged down in how to represent the N different code generation
    395 variants.  We clearly needed at least two--SW and HW transactional
    396 clones--but there was always a suggestion of more variants for different
    397 TM assumptions/invariants.
    398 
    399    The compiler can then use two TM runtime functions to perform
    400 indirect calls in transactions:
    401      void *_ITM_getTMCloneOrIrrevocable (void *function) ITM_REGPARM;
    402      void *_ITM_getTMCloneSafe (void *function) ITM_REGPARM;
    403 
    404    If there is a registered clone for supplied function, both will
    405 return a pointer to the clone.  If not, the first runtime function will
    406 attempt to switch to serial-irrevocable mode and return the original
    407 pointer, whereas the second will raise a fatal runtime error.
    408 
    409 3.5.19 [New] Transactional dynamic memory management
    410 ----------------------------------------------------
    411 
    412      void *_ITM_malloc (size_t)
    413             __attribute__((__malloc__)) ITM_PURE;
    414      void *_ITM_calloc (size_t, size_t)
    415             __attribute__((__malloc__)) ITM_PURE;
    416      void _ITM_free (void *) ITM_PURE;
    417 
    418    These functions are essentially transactional wrappers for 'malloc',
    419 'calloc', and 'free'.  Within transactions, the compiler should replace
    420 calls to the original functions with calls to the wrapper functions.
    421 
    422 3.6 [No changes] Future Enhancements to the ABI
    423 ===============================================
    424 
    425 3.7 Sample code
    426 ===============
    427 
    428 The code examples might not be correct w.r.t.  the current version of
    429 the ABI, especially everything related to exception handling.
    430 
    431 3.8 [New] Memory model
    432 ======================
    433 
    434 The ABI should define a memory model and the ordering that is guaranteed
    435 for data transfers and commit/undo actions, or at least refer to another
    436 memory model that needs to be preserved.  Without that, the compiler
    437 cannot ensure the memory model specified on the level of the programming
    438 language (e.g., by the C++ TM specification).
    439 
    440    For example, if a transactional load is ordered before another
    441 load/store, then the TM runtime must also ensure this ordering when
    442 accessing shared state.  If not, this might break the kind of
    443 publication safety used in the C++ TM specification.  Likewise, the TM
    444 runtime must ensure privatization safety.
    445 
    446 
    447 File: libitm.info,  Node: Internals,  Next: GNU Free Documentation License,  Prev: The libitm ABI,  Up: Top
    448 
    449 4 Internals
    450 ***********
    451 
    452 4.1 TM methods and method groups
    453 ================================
    454 
    455 libitm supports several ways of synchronizing transactions with each
    456 other.  These TM methods (or TM algorithms) are implemented in the form
    457 of subclasses of 'abi_dispatch', which provide methods for transactional
    458 loads and stores as well as callbacks for rollback and commit.  All
    459 methods that are compatible with each other (i.e., that let concurrently
    460 running transactions still synchronize correctly even if different
    461 methods are used) belong to the same TM method group.  Pointers to TM
    462 methods can be obtained using the factory methods prefixed with
    463 'dispatch_' in 'libitm_i.h'.  There are two special methods,
    464 'dispatch_serial' and 'dispatch_serialirr', that are compatible with all
    465 methods because they run transactions completely in serial mode.
    466 
    467 4.1.1 TM method life cycle
    468 --------------------------
    469 
    470 The state of TM methods does not change after construction, but they do
    471 alter the state of transactions that use this method.  However, because
    472 per-transaction data gets used by several methods, 'gtm_thread' is
    473 responsible for setting an initial state that is useful for all methods.
    474 After that, methods are responsible for resetting/clearing this state on
    475 each rollback or commit (of outermost transactions), so that the
    476 transaction executed next is not affected by the previous transaction.
    477 
    478    There is also global state associated with each method group, which
    479 is initialized and shut down ('method_group::init()' and 'fini()') when
    480 switching between method groups (see 'retry.cc').
    481 
    482 4.1.2 Selecting the default method
    483 ----------------------------------
    484 
    485 The default method that libitm uses for freshly started transactions
    486 (but not necessarily for restarted transactions) can be set via an
    487 environment variable ('ITM_DEFAULT_METHOD'), whose value should be equal
    488 to the name of one of the factory methods returning abi_dispatch
    489 subclasses but without the "dispatch_" prefix (e.g., "serialirr" instead
    490 of 'GTM::dispatch_serialirr()').
    491 
    492    Note that this environment variable is only a hint for libitm and
    493 might not be supported in the future.
    494 
    495 4.2 Nesting: flat vs. closed
    496 ============================
    497 
    498 We support two different kinds of nesting of transactions.  In the case
    499 of _flat nesting_, the nesting structure is flattened and all nested
    500 transactions are subsumed by the enclosing transaction.  In contrast,
    501 with _closed nesting_, nested transactions that have not yet committed
    502 can be rolled back separately from the enclosing transactions; when they
    503 commit, they are subsumed by the enclosing transaction, and their
    504 effects will be finally committed when the outermost transaction
    505 commits.  _Open nesting_ (where nested transactions can commit
    506 independently of the enclosing transactions) are not supported.
    507 
    508    Flat nesting is the default nesting mode, but closed nesting is
    509 supported and used when transactions contain user-controlled aborts
    510 ('__transaction_cancel' statements).  We assume that user-controlled
    511 aborts are rare in typical code and used mostly in exceptional
    512 situations.  Thus, it makes more sense to use flat nesting by default to
    513 avoid the performance overhead of the additional checkpoints required
    514 for closed nesting.  User-controlled aborts will correctly abort the
    515 innermost enclosing transaction, whereas the whole (i.e., outermost)
    516 transaction will be restarted otherwise (e.g., when a transaction
    517 encounters data conflicts during optimistic execution).
    518 
    519 4.3 Locking conventions
    520 =======================
    521 
    522 This section documents the locking scheme and rules for all uses of
    523 locking in libitm.  We have to support serial(-irrevocable) mode, which
    524 is implemented using a global lock as explained next (called the _serial
    525 lock_).  To simplify the overall design, we use the same lock as
    526 catch-all locking mechanism for other infrequent tasks such as
    527 (de)registering clone tables or threads.  Besides the serial lock, there
    528 are _per-method-group locks_ that are managed by specific method groups
    529 (i.e., groups of similar TM concurrency control algorithms), and
    530 lock-like constructs for quiescence-based operations such as ensuring
    531 privatization safety.
    532 
    533    Thus, the actions that participate in the libitm-internal locking are
    534 either _active transactions_ that do not run in serial mode, _serial
    535 transactions_ (which (are about to) run in serial mode), and management
    536 tasks that do not execute within a transaction but have acquired the
    537 serial mode like a serial transaction would do (e.g., to be able to
    538 register threads with libitm).  Transactions become active as soon as
    539 they have successfully used the serial lock to announce this globally
    540 (*note Serial lock implementation: serial-lock-impl.).  Likewise,
    541 transactions become serial transactions as soon as they have acquired
    542 the exclusive rights provided by the serial lock (i.e., serial mode,
    543 which also means that there are no other concurrent active or serial
    544 transactions).  Note that active transactions can become serial
    545 transactions when they enter serial mode during the runtime of the
    546 transaction.
    547 
    548 4.3.1 State-to-lock mapping
    549 ---------------------------
    550 
    551 Application data is protected by the serial lock if there is a serial
    552 transaction and no concurrently running active transaction (i.e.,
    553 non-serial).  Otherwise, application data is protected by the currently
    554 selected method group, which might use per-method-group locks or other
    555 mechanisms.  Also note that application data that is about to be
    556 privatized might not be allowed to be accessed by nontransactional code
    557 until privatization safety has been ensured; the details of this are
    558 handled by the current method group.
    559 
    560    libitm-internal state is either protected by the serial lock or
    561 accessed through custom concurrent code.  The latter applies to the
    562 public/shared part of a transaction object and most typical
    563 method-group-specific state.
    564 
    565    The former category (protected by the serial lock) includes:
    566    * The list of active threads that have used transactions.
    567    * The tables that map functions to their transactional clones.
    568    * The current selection of which method group to use.
    569    * Some method-group-specific data, or invariants of this data.  For
    570      example, resetting a method group to its initial state is handled
    571      by switching to the same method group, so the serial lock protects
    572      such resetting as well.
    573    In general, such state is immutable whenever there exists an active
    574 (non-serial) transaction.  If there is no active transaction, a serial
    575 transaction (or a thread that is not currently executing a transaction
    576 but has acquired the serial lock) is allowed to modify this state (but
    577 must of course be careful to not surprise the current method group's
    578 implementation with such modifications).
    579 
    580 4.3.2 Lock acquisition order
    581 ----------------------------
    582 
    583 To prevent deadlocks, locks acquisition must happen in a globally
    584 agreed-upon order.  Note that this applies to other forms of blocking
    585 too, but does not necessarily apply to lock acquisitions that do not
    586 block (e.g., trylock() calls that do not get retried forever).  Note
    587 that serial transactions are never return back to active transactions
    588 until the transaction has committed.  Likewise, active transactions stay
    589 active until they have committed.  Per-method-group locks are typically
    590 also not released before commit.
    591 
    592    Lock acquisition / blocking rules:
    593 
    594    * Transactions must become active or serial before they are allowed
    595      to use method-group-specific locks or blocking (i.e., the serial
    596      lock must be acquired before those other locks, either in serial or
    597      nonserial mode).
    598 
    599    * Any number of threads that do not currently run active transactions
    600      can block while trying to get the serial lock in exclusive mode.
    601      Note that active transactions must not block when trying to upgrade
    602      to serial mode unless there is no other transaction that is trying
    603      that (the latter is ensured by the serial lock implementation.
    604 
    605    * Method groups must prevent deadlocks on their locks.  In
    606      particular, they must also be prepared for another active
    607      transaction that has acquired method-group-specific locks but is
    608      blocked during an attempt to upgrade to being a serial transaction.
    609      See below for details.
    610 
    611    * Serial transactions can acquire method-group-specific locks because
    612      there will be no other active nor serial transaction.
    613 
    614    There is no single rule for per-method-group blocking because this
    615 depends on when a TM method might acquire locks.  If no active
    616 transaction can upgrade to being a serial transaction after it has
    617 acquired per-method-group locks (e.g., when those locks are only
    618 acquired during an attempt to commit), then the TM method does not need
    619 to consider a potential deadlock due to serial mode.
    620 
    621    If there can be upgrades to serial mode after the acquisition of
    622 per-method-group locks, then TM methods need to avoid those deadlocks:
    623    * When upgrading to a serial transaction, after acquiring exclusive
    624      rights to the serial lock but before waiting for concurrent active
    625      transactions to finish (*note Serial lock implementation:
    626      serial-lock-impl. for details), we have to wake up all active
    627      transactions waiting on the upgrader's per-method-group locks.
    628    * Active transactions blocking on per-method-group locks need to
    629      check the serial lock and abort if there is a pending serial
    630      transaction.
    631    * Lost wake-ups have to be prevented (e.g., by changing a bit in each
    632      per-method-group lock before doing the wake-up, and only blocking
    633      on this lock using a futex if this bit is not group).
    634 
    635    *TODO*: Can reuse serial lock for gl-*?  And if we can, does it make
    636 sense to introduce further complexity in the serial lock?  For gl-*, we
    637 can really only avoid an abort if we do -wb and -vbv.
    638 
    639 4.3.3 Serial lock implementation
    640 --------------------------------
    641 
    642 The serial lock implementation is optimized towards assuming that serial
    643 transactions are infrequent and not the common case.  However, the
    644 performance of entering serial mode can matter because when only few
    645 transactions are run concurrently or if there are few threads, then it
    646 can be efficient to run transactions serially.
    647 
    648    The serial lock is similar to a multi-reader-single-writer lock in
    649 that there can be several active transactions but only one serial
    650 transaction.  However, we do want to avoid contention (in the lock
    651 implementation) between active transactions, so we split up the reader
    652 side of the lock into per-transaction flags that are true iff the
    653 transaction is active.  The exclusive writer side remains a shared
    654 single flag, which is acquired using a CAS, for example.  On the
    655 fast-path, the serial lock then works similar to Dekker's algorithm but
    656 with several reader flags that a serial transaction would have to check.
    657 A serial transaction thus requires a list of all threads with
    658 potentially active transactions; we can use the serial lock itself to
    659 protect this list (i.e., only threads that have acquired the serial lock
    660 can modify this list).
    661 
    662    We want starvation-freedom for the serial lock to allow for using it
    663 to ensure progress for potentially starved transactions (*note Progress
    664 Guarantees: progress-guarantees. for details).  However, this is
    665 currently not enforced by the implementation of the serial lock.
    666 
    667    Here is pseudo-code for the read/write fast paths of acquiring the
    668 serial lock (read-to-write upgrade is similar to write_lock:
    669      // read_lock:
    670      tx->shared_state |= active;
    671      __sync_synchronize(); // or STLD membar, or C++0x seq-cst fence
    672      while (!serial_lock.exclusive)
    673        if (spinning_for_too_long) goto slowpath;
    674 
    675      // write_lock:
    676      if (CAS(&serial_lock.exclusive, 0, this) != 0)
    677        goto slowpath; // writer-writer contention
    678      // need a membar here, but CAS already has full membar semantics
    679      bool need_blocking = false;
    680      for (t: all txns)
    681        {
    682          for (;t->shared_state & active;)
    683            if (spinning_for_too_long) { need_blocking = true; break; }
    684        }
    685      if (need_blocking) goto slowpath;
    686 
    687    Releasing a lock in this spin-lock version then just consists of
    688 resetting 'tx->shared_state' to inactive or clearing
    689 'serial_lock.exclusive'.
    690 
    691    However, we can't rely on a pure spinlock because we need to get the
    692 OS involved at some time (e.g., when there are more threads than CPUs to
    693 run on).  Therefore, the real implementation falls back to a blocking
    694 slow path, either based on pthread mutexes or Linux futexes.
    695 
    696 4.3.4 Reentrancy
    697 ----------------
    698 
    699 libitm has to consider the following cases of reentrancy:
    700 
    701    * Transaction calls unsafe code that starts a new transaction: The
    702      outer transaction will become a serial transaction before executing
    703      unsafe code.  Therefore, nesting within serial transactions must
    704      work, even if the nested transaction is called from within
    705      uninstrumented code.
    706 
    707    * Transaction calls either a transactional wrapper or safe code,
    708      which in turn starts a new transaction: It is not yet defined in
    709      the specification whether this is allowed.  Thus, it is undefined
    710      whether libitm supports this.
    711 
    712    * Code that starts new transactions might be called from within any
    713      part of libitm: This kind of reentrancy would likely be rather
    714      complex and can probably be avoided.  Therefore, it is not
    715      supported.
    716 
    717 4.3.5 Privatization safety
    718 --------------------------
    719 
    720 Privatization safety is ensured by libitm using a quiescence-based
    721 approach.  Basically, a privatizing transaction waits until all
    722 concurrent active transactions will either have finished (are not active
    723 anymore) or operate on a sufficiently recent snapshot to not access the
    724 privatized data anymore.  This happens after the privatizing transaction
    725 has stopped being an active transaction, so waiting for quiescence does
    726 not contribute to deadlocks.
    727 
    728    In method groups that need to ensure publication safety explicitly,
    729 active transactions maintain a flag or timestamp in the public/shared
    730 part of the transaction descriptor.  Before blocking, privatizers need
    731 to let the other transactions know that they should wake up the
    732 privatizer.
    733 
    734    *TODO* Ho to implement the waiters?  Should those flags be
    735 per-transaction or at a central place?  We want to avoid one wake/wait
    736 call per active transactions, so we might want to use either a tree or
    737 combining to reduce the syscall overhead, or rather spin for a long
    738 amount of time instead of doing blocking.  Also, it would be good if
    739 only the last transaction that the privatizer waits for would do the
    740 wake-up.
    741 
    742 4.3.6 Progress guarantees
    743 -------------------------
    744 
    745 Transactions that do not make progress when using the current TM method
    746 will eventually try to execute in serial mode.  Thus, the serial lock's
    747 progress guarantees determine the progress guarantees of the whole TM.
    748 Obviously, we at least need deadlock-freedom for the serial lock, but it
    749 would also be good to provide starvation-freedom (informally, all
    750 threads will finish executing a transaction eventually iff they get
    751 enough cycles).
    752 
    753    However, the scheduling of transactions (e.g., thread scheduling by
    754 the OS) also affects the handling of progress guarantees by the TM.
    755 First, the TM can only guarantee deadlock-freedom if threads do not get
    756 stopped.  Likewise, low-priority threads can starve if they do not get
    757 scheduled when other high-priority threads get those cycles instead.
    758 
    759    If all threads get scheduled eventually, correct lock implementations
    760 will provide deadlock-freedom, but might not provide starvation-freedom.
    761 We can either enforce the latter in the TM's lock implementation, or
    762 assume that the scheduling is sufficiently random to yield a
    763 probabilistic guarantee that no thread will starve (because eventually,
    764 a transaction will encounter a scheduling that will allow it to run).
    765 This can indeed work well in practice but is not necessarily guaranteed
    766 to work (e.g., simple spin locks can be pretty efficient).
    767 
    768    Because enforcing stronger progress guarantees in the TM has a higher
    769 runtime overhead, we focus on deadlock-freedom right now and assume that
    770 the threads will get scheduled eventually by the OS (but don't consider
    771 threads with different priorities).  We should support
    772 starvation-freedom for serial transactions in the future.  Everything
    773 beyond that is highly related to proper contention management across all
    774 of the TM (including with TM method to choose), and is future work.
    775 
    776    *TODO* Handling thread priorities: We want to avoid priority
    777 inversion but it's unclear how often that actually matters in practice.
    778 Workloads that have threads with different priorities will likely also
    779 require lower latency or higher throughput for high-priority threads.
    780 Therefore, it probably makes not that much sense (except for eventual
    781 progress guarantees) to use priority inheritance until the TM has
    782 priority-aware contention management.
    783 
    784 
    785 File: libitm.info,  Node: GNU Free Documentation License,  Next: Index,  Prev: Internals,  Up: Top
    786 
    787 GNU Free Documentation License
    788 ******************************
    789 
    790                      Version 1.3, 3 November 2008
    791 
    792      Copyright (C) 2000, 2001, 2002, 2007, 2008 Free Software Foundation, Inc.
    793      <http://fsf.org/>
    794 
    795      Everyone is permitted to copy and distribute verbatim copies
    796      of this license document, but changing it is not allowed.
    797 
    798   0. PREAMBLE
    799 
    800      The purpose of this License is to make a manual, textbook, or other
    801      functional and useful document "free" in the sense of freedom: to
    802      assure everyone the effective freedom to copy and redistribute it,
    803      with or without modifying it, either commercially or
    804      noncommercially.  Secondarily, this License preserves for the
    805      author and publisher a way to get credit for their work, while not
    806      being considered responsible for modifications made by others.
    807 
    808      This License is a kind of "copyleft", which means that derivative
    809      works of the document must themselves be free in the same sense.
    810      It complements the GNU General Public License, which is a copyleft
    811      license designed for free software.
    812 
    813      We have designed this License in order to use it for manuals for
    814      free software, because free software needs free documentation: a
    815      free program should come with manuals providing the same freedoms
    816      that the software does.  But this License is not limited to
    817      software manuals; it can be used for any textual work, regardless
    818      of subject matter or whether it is published as a printed book.  We
    819      recommend this License principally for works whose purpose is
    820      instruction or reference.
    821 
    822   1. APPLICABILITY AND DEFINITIONS
    823 
    824      This License applies to any manual or other work, in any medium,
    825      that contains a notice placed by the copyright holder saying it can
    826      be distributed under the terms of this License.  Such a notice
    827      grants a world-wide, royalty-free license, unlimited in duration,
    828      to use that work under the conditions stated herein.  The
    829      "Document", below, refers to any such manual or work.  Any member
    830      of the public is a licensee, and is addressed as "you".  You accept
    831      the license if you copy, modify or distribute the work in a way
    832      requiring permission under copyright law.
    833 
    834      A "Modified Version" of the Document means any work containing the
    835      Document or a portion of it, either copied verbatim, or with
    836      modifications and/or translated into another language.
    837 
    838      A "Secondary Section" is a named appendix or a front-matter section
    839      of the Document that deals exclusively with the relationship of the
    840      publishers or authors of the Document to the Document's overall
    841      subject (or to related matters) and contains nothing that could
    842      fall directly within that overall subject.  (Thus, if the Document
    843      is in part a textbook of mathematics, a Secondary Section may not
    844      explain any mathematics.)  The relationship could be a matter of
    845      historical connection with the subject or with related matters, or
    846      of legal, commercial, philosophical, ethical or political position
    847      regarding them.
    848 
    849      The "Invariant Sections" are certain Secondary Sections whose
    850      titles are designated, as being those of Invariant Sections, in the
    851      notice that says that the Document is released under this License.
    852      If a section does not fit the above definition of Secondary then it
    853      is not allowed to be designated as Invariant.  The Document may
    854      contain zero Invariant Sections.  If the Document does not identify
    855      any Invariant Sections then there are none.
    856 
    857      The "Cover Texts" are certain short passages of text that are
    858      listed, as Front-Cover Texts or Back-Cover Texts, in the notice
    859      that says that the Document is released under this License.  A
    860      Front-Cover Text may be at most 5 words, and a Back-Cover Text may
    861      be at most 25 words.
    862 
    863      A "Transparent" copy of the Document means a machine-readable copy,
    864      represented in a format whose specification is available to the
    865      general public, that is suitable for revising the document
    866      straightforwardly with generic text editors or (for images composed
    867      of pixels) generic paint programs or (for drawings) some widely
    868      available drawing editor, and that is suitable for input to text
    869      formatters or for automatic translation to a variety of formats
    870      suitable for input to text formatters.  A copy made in an otherwise
    871      Transparent file format whose markup, or absence of markup, has
    872      been arranged to thwart or discourage subsequent modification by
    873      readers is not Transparent.  An image format is not Transparent if
    874      used for any substantial amount of text.  A copy that is not
    875      "Transparent" is called "Opaque".
    876 
    877      Examples of suitable formats for Transparent copies include plain
    878      ASCII without markup, Texinfo input format, LaTeX input format,
    879      SGML or XML using a publicly available DTD, and standard-conforming
    880      simple HTML, PostScript or PDF designed for human modification.
    881      Examples of transparent image formats include PNG, XCF and JPG.
    882      Opaque formats include proprietary formats that can be read and
    883      edited only by proprietary word processors, SGML or XML for which
    884      the DTD and/or processing tools are not generally available, and
    885      the machine-generated HTML, PostScript or PDF produced by some word
    886      processors for output purposes only.
    887 
    888      The "Title Page" means, for a printed book, the title page itself,
    889      plus such following pages as are needed to hold, legibly, the
    890      material this License requires to appear in the title page.  For
    891      works in formats which do not have any title page as such, "Title
    892      Page" means the text near the most prominent appearance of the
    893      work's title, preceding the beginning of the body of the text.
    894 
    895      The "publisher" means any person or entity that distributes copies
    896      of the Document to the public.
    897 
    898      A section "Entitled XYZ" means a named subunit of the Document
    899      whose title either is precisely XYZ or contains XYZ in parentheses
    900      following text that translates XYZ in another language.  (Here XYZ
    901      stands for a specific section name mentioned below, such as
    902      "Acknowledgements", "Dedications", "Endorsements", or "History".)
    903      To "Preserve the Title" of such a section when you modify the
    904      Document means that it remains a section "Entitled XYZ" according
    905      to this definition.
    906 
    907      The Document may include Warranty Disclaimers next to the notice
    908      which states that this License applies to the Document.  These
    909      Warranty Disclaimers are considered to be included by reference in
    910      this License, but only as regards disclaiming warranties: any other
    911      implication that these Warranty Disclaimers may have is void and
    912      has no effect on the meaning of this License.
    913 
    914   2. VERBATIM COPYING
    915 
    916      You may copy and distribute the Document in any medium, either
    917      commercially or noncommercially, provided that this License, the
    918      copyright notices, and the license notice saying this License
    919      applies to the Document are reproduced in all copies, and that you
    920      add no other conditions whatsoever to those of this License.  You
    921      may not use technical measures to obstruct or control the reading
    922      or further copying of the copies you make or distribute.  However,
    923      you may accept compensation in exchange for copies.  If you
    924      distribute a large enough number of copies you must also follow the
    925      conditions in section 3.
    926 
    927      You may also lend copies, under the same conditions stated above,
    928      and you may publicly display copies.
    929 
    930   3. COPYING IN QUANTITY
    931 
    932      If you publish printed copies (or copies in media that commonly
    933      have printed covers) of the Document, numbering more than 100, and
    934      the Document's license notice requires Cover Texts, you must
    935      enclose the copies in covers that carry, clearly and legibly, all
    936      these Cover Texts: Front-Cover Texts on the front cover, and
    937      Back-Cover Texts on the back cover.  Both covers must also clearly
    938      and legibly identify you as the publisher of these copies.  The
    939      front cover must present the full title with all words of the title
    940      equally prominent and visible.  You may add other material on the
    941      covers in addition.  Copying with changes limited to the covers, as
    942      long as they preserve the title of the Document and satisfy these
    943      conditions, can be treated as verbatim copying in other respects.
    944 
    945      If the required texts for either cover are too voluminous to fit
    946      legibly, you should put the first ones listed (as many as fit
    947      reasonably) on the actual cover, and continue the rest onto
    948      adjacent pages.
    949 
    950      If you publish or distribute Opaque copies of the Document
    951      numbering more than 100, you must either include a machine-readable
    952      Transparent copy along with each Opaque copy, or state in or with
    953      each Opaque copy a computer-network location from which the general
    954      network-using public has access to download using public-standard
    955      network protocols a complete Transparent copy of the Document, free
    956      of added material.  If you use the latter option, you must take
    957      reasonably prudent steps, when you begin distribution of Opaque
    958      copies in quantity, to ensure that this Transparent copy will
    959      remain thus accessible at the stated location until at least one
    960      year after the last time you distribute an Opaque copy (directly or
    961      through your agents or retailers) of that edition to the public.
    962 
    963      It is requested, but not required, that you contact the authors of
    964      the Document well before redistributing any large number of copies,
    965      to give them a chance to provide you with an updated version of the
    966      Document.
    967 
    968   4. MODIFICATIONS
    969 
    970      You may copy and distribute a Modified Version of the Document
    971      under the conditions of sections 2 and 3 above, provided that you
    972      release the Modified Version under precisely this License, with the
    973      Modified Version filling the role of the Document, thus licensing
    974      distribution and modification of the Modified Version to whoever
    975      possesses a copy of it.  In addition, you must do these things in
    976      the Modified Version:
    977 
    978        A. Use in the Title Page (and on the covers, if any) a title
    979           distinct from that of the Document, and from those of previous
    980           versions (which should, if there were any, be listed in the
    981           History section of the Document).  You may use the same title
    982           as a previous version if the original publisher of that
    983           version gives permission.
    984 
    985        B. List on the Title Page, as authors, one or more persons or
    986           entities responsible for authorship of the modifications in
    987           the Modified Version, together with at least five of the
    988           principal authors of the Document (all of its principal
    989           authors, if it has fewer than five), unless they release you
    990           from this requirement.
    991 
    992        C. State on the Title page the name of the publisher of the
    993           Modified Version, as the publisher.
    994 
    995        D. Preserve all the copyright notices of the Document.
    996 
    997        E. Add an appropriate copyright notice for your modifications
    998           adjacent to the other copyright notices.
    999 
    1000        F. Include, immediately after the copyright notices, a license
    1001           notice giving the public permission to use the Modified
    1002           Version under the terms of this License, in the form shown in
    1003           the Addendum below.
    1004 
    1005        G. Preserve in that license notice the full lists of Invariant
    1006           Sections and required Cover Texts given in the Document's
    1007           license notice.
    1008 
    1009        H. Include an unaltered copy of this License.
    1010 
    1011        I. Preserve the section Entitled "History", Preserve its Title,
    1012           and add to it an item stating at least the title, year, new
    1013           authors, and publisher of the Modified Version as given on the
    1014           Title Page.  If there is no section Entitled "History" in the
    1015           Document, create one stating the title, year, authors, and
    1016           publisher of the Document as given on its Title Page, then add
    1017           an item describing the Modified Version as stated in the
    1018           previous sentence.
    1019 
    1020        J. Preserve the network location, if any, given in the Document
    1021           for public access to a Transparent copy of the Document, and
    1022           likewise the network locations given in the Document for
    1023           previous versions it was based on.  These may be placed in the
    1024           "History" section.  You may omit a network location for a work
    1025           that was published at least four years before the Document
    1026           itself, or if the original publisher of the version it refers
    1027           to gives permission.
    1028 
    1029        K. For any section Entitled "Acknowledgements" or "Dedications",
    1030           Preserve the Title of the section, and preserve in the section
    1031           all the substance and tone of each of the contributor
    1032           acknowledgements and/or dedications given therein.
    1033 
    1034        L. Preserve all the Invariant Sections of the Document, unaltered
    1035           in their text and in their titles.  Section numbers or the
    1036           equivalent are not considered part of the section titles.
    1037 
    1038        M. Delete any section Entitled "Endorsements".  Such a section
    1039           may not be included in the Modified Version.
    1040 
    1041        N. Do not retitle any existing section to be Entitled
    1042           "Endorsements" or to conflict in title with any Invariant
    1043           Section.
    1044 
    1045        O. Preserve any Warranty Disclaimers.
    1046 
    1047      If the Modified Version includes new front-matter sections or
    1048      appendices that qualify as Secondary Sections and contain no
    1049      material copied from the Document, you may at your option designate
    1050      some or all of these sections as invariant.  To do this, add their
    1051      titles to the list of Invariant Sections in the Modified Version's
    1052      license notice.  These titles must be distinct from any other
    1053      section titles.
    1054 
    1055      You may add a section Entitled "Endorsements", provided it contains
    1056      nothing but endorsements of your Modified Version by various
    1057      parties--for example, statements of peer review or that the text
    1058      has been approved by an organization as the authoritative
    1059      definition of a standard.
    1060 
    1061      You may add a passage of up to five words as a Front-Cover Text,
    1062      and a passage of up to 25 words as a Back-Cover Text, to the end of
    1063      the list of Cover Texts in the Modified Version.  Only one passage
    1064      of Front-Cover Text and one of Back-Cover Text may be added by (or
    1065      through arrangements made by) any one entity.  If the Document
    1066      already includes a cover text for the same cover, previously added
    1067      by you or by arrangement made by the same entity you are acting on
    1068      behalf of, you may not add another; but you may replace the old
    1069      one, on explicit permission from the previous publisher that added
    1070      the old one.
    1071 
    1072      The author(s) and publisher(s) of the Document do not by this
    1073      License give permission to use their names for publicity for or to
    1074      assert or imply endorsement of any Modified Version.
    1075 
    1076   5. COMBINING DOCUMENTS
    1077 
    1078      You may combine the Document with other documents released under
    1079      this License, under the terms defined in section 4 above for
    1080      modified versions, provided that you include in the combination all
    1081      of the Invariant Sections of all of the original documents,
    1082      unmodified, and list them all as Invariant Sections of your
    1083      combined work in its license notice, and that you preserve all
    1084      their Warranty Disclaimers.
    1085 
    1086      The combined work need only contain one copy of this License, and
    1087      multiple identical Invariant Sections may be replaced with a single
    1088      copy.  If there are multiple Invariant Sections with the same name
    1089      but different contents, make the title of each such section unique
    1090      by adding at the end of it, in parentheses, the name of the
    1091      original author or publisher of that section if known, or else a
    1092      unique number.  Make the same adjustment to the section titles in
    1093      the list of Invariant Sections in the license notice of the
    1094      combined work.
    1095 
    1096      In the combination, you must combine any sections Entitled
    1097      "History" in the various original documents, forming one section
    1098      Entitled "History"; likewise combine any sections Entitled
    1099      "Acknowledgements", and any sections Entitled "Dedications".  You
    1100      must delete all sections Entitled "Endorsements."
    1101 
    1102   6. COLLECTIONS OF DOCUMENTS
    1103 
    1104      You may make a collection consisting of the Document and other
    1105      documents released under this License, and replace the individual
    1106      copies of this License in the various documents with a single copy
    1107      that is included in the collection, provided that you follow the
    1108      rules of this License for verbatim copying of each of the documents
    1109      in all other respects.
    1110 
    1111      You may extract a single document from such a collection, and
    1112      distribute it individually under this License, provided you insert
    1113      a copy of this License into the extracted document, and follow this
    1114      License in all other respects regarding verbatim copying of that
    1115      document.
    1116 
    1117   7. AGGREGATION WITH INDEPENDENT WORKS
    1118 
    1119      A compilation of the Document or its derivatives with other
    1120      separate and independent documents or works, in or on a volume of a
    1121      storage or distribution medium, is called an "aggregate" if the
    1122      copyright resulting from the compilation is not used to limit the
    1123      legal rights of the compilation's users beyond what the individual
    1124      works permit.  When the Document is included in an aggregate, this
    1125      License does not apply to the other works in the aggregate which
    1126      are not themselves derivative works of the Document.
    1127 
    1128      If the Cover Text requirement of section 3 is applicable to these
    1129      copies of the Document, then if the Document is less than one half
    1130      of the entire aggregate, the Document's Cover Texts may be placed
    1131      on covers that bracket the Document within the aggregate, or the
    1132      electronic equivalent of covers if the Document is in electronic
    1133      form.  Otherwise they must appear on printed covers that bracket
    1134      the whole aggregate.
    1135 
    1136   8. TRANSLATION
    1137 
    1138      Translation is considered a kind of modification, so you may
    1139      distribute translations of the Document under the terms of section
    1140      4.  Replacing Invariant Sections with translations requires special
    1141      permission from their copyright holders, but you may include
    1142      translations of some or all Invariant Sections in addition to the
    1143      original versions of these Invariant Sections.  You may include a
    1144      translation of this License, and all the license notices in the
    1145      Document, and any Warranty Disclaimers, provided that you also
    1146      include the original English version of this License and the
    1147      original versions of those notices and disclaimers.  In case of a
    1148      disagreement between the translation and the original version of
    1149      this License or a notice or disclaimer, the original version will
    1150      prevail.
    1151 
    1152      If a section in the Document is Entitled "Acknowledgements",
    1153      "Dedications", or "History", the requirement (section 4) to
    1154      Preserve its Title (section 1) will typically require changing the
    1155      actual title.
    1156 
    1157   9. TERMINATION
    1158 
    1159      You may not copy, modify, sublicense, or distribute the Document
    1160      except as expressly provided under this License.  Any attempt
    1161      otherwise to copy, modify, sublicense, or distribute it is void,
    1162      and will automatically terminate your rights under this License.
    1163 
    1164      However, if you cease all violation of this License, then your
    1165      license from a particular copyright holder is reinstated (a)
    1166      provisionally, unless and until the copyright holder explicitly and
    1167      finally terminates your license, and (b) permanently, if the
    1168      copyright holder fails to notify you of the violation by some
    1169      reasonable means prior to 60 days after the cessation.
    1170 
    1171      Moreover, your license from a particular copyright holder is
    1172      reinstated permanently if the copyright holder notifies you of the
    1173      violation by some reasonable means, this is the first time you have
    1174      received notice of violation of this License (for any work) from
    1175      that copyright holder, and you cure the violation prior to 30 days
    1176      after your receipt of the notice.
    1177 
    1178      Termination of your rights under this section does not terminate
    1179      the licenses of parties who have received copies or rights from you
    1180      under this License.  If your rights have been terminated and not
    1181      permanently reinstated, receipt of a copy of some or all of the
    1182      same material does not give you any rights to use it.
    1183 
    1184   10. FUTURE REVISIONS OF THIS LICENSE
    1185 
    1186      The Free Software Foundation may publish new, revised versions of
    1187      the GNU Free Documentation License from time to time.  Such new
    1188      versions will be similar in spirit to the present version, but may
    1189      differ in detail to address new problems or concerns.  See
    1190      <http://www.gnu.org/copyleft/>.
    1191 
    1192      Each version of the License is given a distinguishing version
    1193      number.  If the Document specifies that a particular numbered
    1194      version of this License "or any later version" applies to it, you
    1195      have the option of following the terms and conditions either of
    1196      that specified version or of any later version that has been
    1197      published (not as a draft) by the Free Software Foundation.  If the
    1198      Document does not specify a version number of this License, you may
    1199      choose any version ever published (not as a draft) by the Free
    1200      Software Foundation.  If the Document specifies that a proxy can
    1201      decide which future versions of this License can be used, that
    1202      proxy's public statement of acceptance of a version permanently
    1203      authorizes you to choose that version for the Document.
    1204 
    1205   11. RELICENSING
    1206 
    1207      "Massive Multiauthor Collaboration Site" (or "MMC Site") means any
    1208      World Wide Web server that publishes copyrightable works and also
    1209      provides prominent facilities for anybody to edit those works.  A
    1210      public wiki that anybody can edit is an example of such a server.
    1211      A "Massive Multiauthor Collaboration" (or "MMC") contained in the
    1212      site means any set of copyrightable works thus published on the MMC
    1213      site.
    1214 
    1215      "CC-BY-SA" means the Creative Commons Attribution-Share Alike 3.0
    1216      license published by Creative Commons Corporation, a not-for-profit
    1217      corporation with a principal place of business in San Francisco,
    1218      California, as well as future copyleft versions of that license
    1219      published by that same organization.
    1220 
    1221      "Incorporate" means to publish or republish a Document, in whole or
    1222      in part, as part of another Document.
    1223 
    1224      An MMC is "eligible for relicensing" if it is licensed under this
    1225      License, and if all works that were first published under this
    1226      License somewhere other than this MMC, and subsequently
    1227      incorporated in whole or in part into the MMC, (1) had no cover
    1228      texts or invariant sections, and (2) were thus incorporated prior
    1229      to November 1, 2008.
    1230 
    1231      The operator of an MMC Site may republish an MMC contained in the
    1232      site under CC-BY-SA on the same site at any time before August 1,
    1233      2009, provided the MMC is eligible for relicensing.
    1234 
    1235 ADDENDUM: How to use this License for your documents
    1236 ====================================================
    1237 
    1238 To use this License in a document you have written, include a copy of
    1239 the License in the document and put the following copyright and license
    1240 notices just after the title page:
    1241 
    1242        Copyright (C)  YEAR  YOUR NAME.
    1243        Permission is granted to copy, distribute and/or modify this document
    1244        under the terms of the GNU Free Documentation License, Version 1.3
    1245        or any later version published by the Free Software Foundation;
    1246        with no Invariant Sections, no Front-Cover Texts, and no Back-Cover
    1247        Texts.  A copy of the license is included in the section entitled ``GNU
    1248        Free Documentation License''.
    1249 
    1250    If you have Invariant Sections, Front-Cover Texts and Back-Cover
    1251 Texts, replace the "with...Texts."  line with this:
    1252 
    1253          with the Invariant Sections being LIST THEIR TITLES, with
    1254          the Front-Cover Texts being LIST, and with the Back-Cover Texts
    1255          being LIST.
    1256 
    1257    If you have Invariant Sections without Cover Texts, or some other
    1258 combination of the three, merge those two alternatives to suit the
    1259 situation.
    1260 
    1261    If your document contains nontrivial examples of program code, we
    1262 recommend releasing these examples in parallel under your choice of free
    1263 software license, such as the GNU General Public License, to permit
    1264 their use in free software.
    1265 
    1266 
    1267 File: libitm.info,  Node: Index,  Prev: GNU Free Documentation License,  Up: Top
    1268 
    1269 Index
    1270 *****
    1271 
    1272 [index]
    1273 * Menu:
    1274 
    1275 * FDL, GNU Free Documentation License:   GNU Free Documentation License.
    1276                                                                 (line 6)
    1277 * Introduction:                          Top.                   (line 6)
    1278 
    1279 
    1280 
    1281 Tag Table:
    1282 Node: Top1141
    1283 Node: Enabling libitm2045
    1284 Node: C/C++ Language Constructs for TM2440
    1285 Node: The libitm ABI3923
    1286 Ref: txn-code-properties7721
    1287 Node: Internals18026
    1288 Ref: serial-lock-impl28064
    1289 Ref: progress-guarantees32825
    1290 Node: GNU Free Documentation License35103
    1291 Node: Index60224
    1292 
    1293 End Tag Table
  • libquadmath/libquadmath.info

    diff -Naur gcc-4.8.2.orig/libquadmath/libquadmath.info gcc-4.8.2/libquadmath/libquadmath.info
    old new  
    1 This is libquadmath.info, produced by makeinfo version 5.1 from
    2 libquadmath.texi.
    3 
    4 Copyright (C) 2010-2013 Free Software Foundation, Inc.
    5 
    6      Permission is granted to copy, distribute and/or modify this
    7      document under the terms of the GNU Free Documentation License,
    8      Version 1.2 or any later version published by the Free Software
    9      Foundation; with no Invariant Sections, with the Front-Cover Texts
    10      being "A GNU Manual," and with the Back-Cover Texts as in (a)
    11      below.  A copy of the license is included in the section entitled
    12      "GNU Free Documentation License."
    13 
    14      (a) The FSF's Back-Cover Text is: "You have the freedom to copy and
    15      modify this GNU manual.
    16 INFO-DIR-SECTION GNU Libraries
    17 START-INFO-DIR-ENTRY
    18 * libquadmath: (libquadmath).                  GCC Quad-Precision Math Library
    19 END-INFO-DIR-ENTRY
    20 
    21    This manual documents the GCC Quad-Precision Math Library API.
    22 
    23    Published by the Free Software Foundation 51 Franklin Street, Fifth
    24 Floor Boston, MA 02110-1301 USA
    25 
    26    Copyright (C) 2010-2013 Free Software Foundation, Inc.
    27 
    28      Permission is granted to copy, distribute and/or modify this
    29      document under the terms of the GNU Free Documentation License,
    30      Version 1.2 or any later version published by the Free Software
    31      Foundation; with no Invariant Sections, with the Front-Cover Texts
    32      being "A GNU Manual," and with the Back-Cover Texts as in (a)
    33      below.  A copy of the license is included in the section entitled
    34      "GNU Free Documentation License."
    35 
    36      (a) The FSF's Back-Cover Text is: "You have the freedom to copy and
    37      modify this GNU manual.
    38 
    39 
    40 File: libquadmath.info,  Node: Top,  Next: Typedef and constants,  Up: (dir)
    41 
    42 Introduction
    43 ************
    44 
    45 This manual documents the usage of libquadmath, the GCC Quad-Precision
    46 Math Library Application Programming Interface (API).
    47 
    48 * Menu:
    49 
    50 * Typedef and constants::      Defined data types and constants
    51 * Math Library Routines::      The Libquadmath math runtime application
    52                                programming interface.
    53 * I/O Library Routines::       The Libquadmath I/O runtime application
    54                                programming interface.
    55 * GNU Free Documentation License::
    56                                How you can copy and share this manual.
    57 * Reporting Bugs::             How to report bugs in GCC Libquadmath.
    58 
    59 
    60 File: libquadmath.info,  Node: Typedef and constants,  Next: Math Library Routines,  Prev: Top,  Up: Top
    61 
    62 1 Typedef and constants
    63 ***********************
    64 
    65 The following data type has been defined via 'typedef'.
    66 
    67 '__complex128': '__float128'-based complex number
    68 
    69    The following macros are defined, which give the numeric limits of
    70 the '__float128' data type.
    71 
    72 'FLT128_MAX': largest finite number
    73 'FLT128_MIN': smallest positive number with full precision
    74 'FLT128_EPSILON': difference between 1 and the next larger
    75      representable number
    76 'FLT128_DENORM_MIN': smallest positive denormalized number
    77 'FLT128_MANT_DIG': number of digits in the mantissa (bit precision)
    78 'FLT128_MIN_EXP': maximal negative exponent
    79 'FLT128_MAX_EXP': maximal positive exponent
    80 'FLT128_DIG': number of decimal digits in the mantissa
    81 'FLT128_MIN_10_EXP': maximal negative decimal exponent
    82 'FLT128_MAX_10_EXP': maximal positive decimal exponent
    83 
    84    The following mathematical constants of type '__float128' are
    85 defined.
    86 
    87 'M_Eq': the constant e (Euler's number)
    88 'M_LOG2Eq': binary logarithm of 2
    89 'M_LOG10Eq': common, decimal logarithm of 2
    90 'M_LN2q': natural logarithm of 2
    91 'M_LN10q': natural logarithm of 10
    92 'M_PIq': pi
    93 'M_PI_2q': pi divided by two
    94 'M_PI_4q': pi divided by four
    95 'M_1_PIq': one over pi
    96 'M_2_PIq': one over two pi
    97 'M_2_SQRTPIq': two over square root of pi
    98 'M_SQRT2q': square root of 2
    99 'M_SQRT1_2q': one over square root of 2
    100 
    101 
    102 File: libquadmath.info,  Node: Math Library Routines,  Next: I/O Library Routines,  Prev: Typedef and constants,  Up: Top
    103 
    104 2 Math Library Routines
    105 ***********************
    106 
    107 The following mathematical functions are available:
    108 
    109 'acosq': arc cosine function
    110 'acoshq': inverse hyperbolic cosine function
    111 'asinq': arc sine function
    112 'asinhq': inverse hyperbolic sine function
    113 'atanq': arc tangent function
    114 'atanhq': inverse hyperbolic tangent function
    115 'atan2q': arc tangent function
    116 'cbrtq': cube root function
    117 'ceilq': ceiling value function
    118 'copysignq': copy sign of a number
    119 'coshq': hyperbolic cosine function
    120 'cosq': cosine function
    121 'erfq': error function
    122 'erfcq': complementary error function
    123 'expq': exponential function
    124 'expm1q': exponential minus 1 function
    125 'fabsq': absolute value function
    126 'fdimq': positive difference function
    127 'finiteq': check finiteness of value
    128 'floorq': floor value function
    129 'fmaq': fused multiply and add
    130 'fmaxq': determine maximum of two values
    131 'fminq': determine minimum of two values
    132 'fmodq': remainder value function
    133 'frexpq': extract mantissa and exponent
    134 'hypotq': Eucledian distance function
    135 'ilogbq': get exponent of the value
    136 'isinfq': check for infinity
    137 'isnanq': check for not a number
    138 'j0q': Bessel function of the first kind, first order
    139 'j1q': Bessel function of the first kind, second order
    140 'jnq': Bessel function of the first kind, N-th order
    141 'ldexpq': load exponent of the value
    142 'lgammaq': logarithmic gamma function
    143 'llrintq': round to nearest integer value
    144 'llroundq': round to nearest integer value away from zero
    145 'logq': natural logarithm function
    146 'log10q': base 10 logarithm function
    147 'log1pq': compute natural logarithm of the value plus one
    148 'log2q': base 2 logarithm function
    149 'lrintq': round to nearest integer value
    150 'lroundq': round to nearest integer value away from zero
    151 'modfq': decompose the floating-point number
    152 'nanq': return quiet NaN
    153 'nearbyintq': round to nearest integer
    154 'nextafterq': next representable floating-point number
    155 'powq': power function
    156 'remainderq': remainder function
    157 'remquoq': remainder and part of quotient
    158 'rintq': round-to-nearest integral value
    159 'roundq': round-to-nearest integral value, return '__float128'
    160 'scalblnq': compute exponent using 'FLT_RADIX'
    161 'scalbnq': compute exponent using 'FLT_RADIX'
    162 'signbitq': return sign bit
    163 'sincosq': calculate sine and cosine simulataneously
    164 'sinhq': hyperbolic sine function
    165 'sinq': sine function
    166 'sqrtq': square root function
    167 'tanq': tangent function
    168 'tanhq': hyperbolic tangent function
    169 'tgammaq': true gamma function
    170 'truncq': round to integer, towards zero
    171 'y0q': Bessel function of the second kind, first order
    172 'y1q': Bessel function of the second kind, second order
    173 'ynq': Bessel function of the second kind, N-th order
    174 'cabsq' complex absolute value function
    175 'cargq': calculate the argument
    176 'cimagq' imaginary part of complex number
    177 'crealq': real part of complex number
    178 'cacoshq': complex arc hyperbolic cosine function
    179 'cacosq': complex arc cosine function
    180 'casinhq': complex arc hyperbolic sine function
    181 'casinq': complex arc sine function
    182 'catanhq': complex arc hyperbolic tangent function
    183 'catanq': complex arc tangent function
    184 'ccosq' complex cosine function:
    185 'ccoshq': complex hyperbolic cosine function
    186 'cexpq': complex exponential function
    187 'cexpiq': computes the exponential function of "i" times a
    188      real value
    189 'clogq': complex natural logarithm
    190 'clog10q': complex base 10 logarithm
    191 'conjq': complex conjugate function
    192 'cpowq': complex power function
    193 'cprojq': project into Riemann Sphere
    194 'csinq': complex sine function
    195 'csinhq': complex hyperbolic sine function
    196 'csqrtq': complex square root
    197 'ctanq': complex tangent function
    198 'ctanhq': complex hyperbolic tangent function
    199 
    200 
    201 File: libquadmath.info,  Node: I/O Library Routines,  Next: GNU Free Documentation License,  Prev: Math Library Routines,  Up: Top
    202 
    203 3 I/O Library Routines
    204 **********************
    205 
    206 * Menu:
    207 
    208 * 'strtoflt128':          strtoflt128,          Convert from string
    209 * 'quadmath_snprintf':    quadmath_snprintf,    Convert to string
    210 
    211 
    212 File: libquadmath.info,  Node: strtoflt128,  Next: quadmath_snprintf,  Up: I/O Library Routines
    213 
    214 3.1 'strtoflt128' -- Convert from string
    215 ========================================
    216 
    217 The function 'strtoflt128' converts a string into a '__float128' number.
    218 
    219 Syntax
    220      '__float128 strtoflt128 (const char *s, char **sp)'
    221 
    222 _Arguments_:
    223      S           input string
    224      SP          the address of the next character in the string
    225 
    226      The argument SP contains, if not 'NULL', the address of the next
    227      character following the parts of the string, which have been read.
    228 
    229 Example
    230           #include <quadmath.h>
    231 
    232           int main ()
    233           {
    234             __float128 r;
    235 
    236             r = strtoflt128 ("1.2345678", NULL);
    237 
    238             return 0;
    239           }
    240 
    241 
    242 File: libquadmath.info,  Node: quadmath_snprintf,  Prev: strtoflt128,  Up: I/O Library Routines
    243 
    244 3.2 'quadmath_snprintf' -- Convert to string
    245 ============================================
    246 
    247 The function 'quadmath_snprintf' converts a '__float128' floating-point
    248 number into a string.  It is a specialized alternative to 'snprintf',
    249 where the format string is restricted to a single conversion specifier
    250 with 'Q' modifier and conversion specifier 'e', 'E', 'f', 'F', 'g', 'G',
    251 'a' or 'A', with no extra characters before or after the conversion
    252 specifier.  The '%m$' or '*m$' style must not be used in the format.
    253 
    254 Syntax
    255      'int quadmath_snprintf (char *s, size_t size, const char *format,
    256      ...)'
    257 
    258 _Arguments_:
    259      S           output string
    260      SIZE        byte size of the string, including tailing NUL
    261      FORMAT      conversion specifier string
    262 
    263 Note
    264      On some targets when supported by the C library hooks are installed
    265      for 'printf' family of functions, so that 'printf ("%Qe", 1.2Q);'
    266      etc. works too.
    267 
    268 Example
    269           #include <quadmath.h>
    270           #include <stdlib.h>
    271           #include <stdio.h>
    272 
    273           int main ()
    274           {
    275             __float128 r;
    276             int prec = 20;
    277             int width = 46;
    278             char buf[128];
    279 
    280             r = 2.0q;
    281             r = sqrtq (r);
    282             int n = quadmath_snprintf (buf, sizeof buf, "%+-#*.20Qe", width, r);
    283             if ((size_t) n < sizeof buf)
    284               printf ("%s\n", buf);
    285               /* Prints: +1.41421356237309504880e+00 */
    286             quadmath_snprintf (buf, sizeof buf, "%Qa", r);
    287             if ((size_t) n < sizeof buf)
    288               printf ("%s\n", buf);
    289               /* Prints: 0x1.6a09e667f3bcc908b2fb1366ea96p+0 */
    290             n = quadmath_snprintf (NULL, 0, "%+-#46.*Qe", prec, r);
    291             if (n > -1)
    292               {
    293                 char *str = malloc (n + 1);
    294                 if (str)
    295                   {
    296                     quadmath_snprintf (str, n + 1, "%+-#46.*Qe", prec, r);
    297                     printf ("%s\n", str);
    298                     /* Prints: +1.41421356237309504880e+00 */
    299                   }
    300                 free (str);
    301               }
    302             return 0;
    303           }
    304 
    305 
    306 File: libquadmath.info,  Node: GNU Free Documentation License,  Next: Reporting Bugs,  Prev: I/O Library Routines,  Up: Top
    307 
    308 GNU Free Documentation License
    309 ******************************
    310 
    311                      Version 1.3, 3 November 2008
    312 
    313      Copyright (C) 2000, 2001, 2002, 2007, 2008 Free Software Foundation, Inc.
    314      <http://fsf.org/>
    315 
    316      Everyone is permitted to copy and distribute verbatim copies
    317      of this license document, but changing it is not allowed.
    318 
    319   0. PREAMBLE
    320 
    321      The purpose of this License is to make a manual, textbook, or other
    322      functional and useful document "free" in the sense of freedom: to
    323      assure everyone the effective freedom to copy and redistribute it,
    324      with or without modifying it, either commercially or
    325      noncommercially.  Secondarily, this License preserves for the
    326      author and publisher a way to get credit for their work, while not
    327      being considered responsible for modifications made by others.
    328 
    329      This License is a kind of "copyleft", which means that derivative
    330      works of the document must themselves be free in the same sense.
    331      It complements the GNU General Public License, which is a copyleft
    332      license designed for free software.
    333 
    334      We have designed this License in order to use it for manuals for
    335      free software, because free software needs free documentation: a
    336      free program should come with manuals providing the same freedoms
    337      that the software does.  But this License is not limited to
    338      software manuals; it can be used for any textual work, regardless
    339      of subject matter or whether it is published as a printed book.  We
    340      recommend this License principally for works whose purpose is
    341      instruction or reference.
    342 
    343   1. APPLICABILITY AND DEFINITIONS
    344 
    345      This License applies to any manual or other work, in any medium,
    346      that contains a notice placed by the copyright holder saying it can
    347      be distributed under the terms of this License.  Such a notice
    348      grants a world-wide, royalty-free license, unlimited in duration,
    349      to use that work under the conditions stated herein.  The
    350      "Document", below, refers to any such manual or work.  Any member
    351      of the public is a licensee, and is addressed as "you".  You accept
    352      the license if you copy, modify or distribute the work in a way
    353      requiring permission under copyright law.
    354 
    355      A "Modified Version" of the Document means any work containing the
    356      Document or a portion of it, either copied verbatim, or with
    357      modifications and/or translated into another language.
    358 
    359      A "Secondary Section" is a named appendix or a front-matter section
    360      of the Document that deals exclusively with the relationship of the
    361      publishers or authors of the Document to the Document's overall
    362      subject (or to related matters) and contains nothing that could
    363      fall directly within that overall subject.  (Thus, if the Document
    364      is in part a textbook of mathematics, a Secondary Section may not
    365      explain any mathematics.)  The relationship could be a matter of
    366      historical connection with the subject or with related matters, or
    367      of legal, commercial, philosophical, ethical or political position
    368      regarding them.
    369 
    370      The "Invariant Sections" are certain Secondary Sections whose
    371      titles are designated, as being those of Invariant Sections, in the
    372      notice that says that the Document is released under this License.
    373      If a section does not fit the above definition of Secondary then it
    374      is not allowed to be designated as Invariant.  The Document may
    375      contain zero Invariant Sections.  If the Document does not identify
    376      any Invariant Sections then there are none.
    377 
    378      The "Cover Texts" are certain short passages of text that are
    379      listed, as Front-Cover Texts or Back-Cover Texts, in the notice
    380      that says that the Document is released under this License.  A
    381      Front-Cover Text may be at most 5 words, and a Back-Cover Text may
    382      be at most 25 words.
    383 
    384      A "Transparent" copy of the Document means a machine-readable copy,
    385      represented in a format whose specification is available to the
    386      general public, that is suitable for revising the document
    387      straightforwardly with generic text editors or (for images composed
    388      of pixels) generic paint programs or (for drawings) some widely
    389      available drawing editor, and that is suitable for input to text
    390      formatters or for automatic translation to a variety of formats
    391      suitable for input to text formatters.  A copy made in an otherwise
    392      Transparent file format whose markup, or absence of markup, has
    393      been arranged to thwart or discourage subsequent modification by
    394      readers is not Transparent.  An image format is not Transparent if
    395      used for any substantial amount of text.  A copy that is not
    396      "Transparent" is called "Opaque".
    397 
    398      Examples of suitable formats for Transparent copies include plain
    399      ASCII without markup, Texinfo input format, LaTeX input format,
    400      SGML or XML using a publicly available DTD, and standard-conforming
    401      simple HTML, PostScript or PDF designed for human modification.
    402      Examples of transparent image formats include PNG, XCF and JPG.
    403      Opaque formats include proprietary formats that can be read and
    404      edited only by proprietary word processors, SGML or XML for which
    405      the DTD and/or processing tools are not generally available, and
    406      the machine-generated HTML, PostScript or PDF produced by some word
    407      processors for output purposes only.
    408 
    409      The "Title Page" means, for a printed book, the title page itself,
    410      plus such following pages as are needed to hold, legibly, the
    411      material this License requires to appear in the title page.  For
    412      works in formats which do not have any title page as such, "Title
    413      Page" means the text near the most prominent appearance of the
    414      work's title, preceding the beginning of the body of the text.
    415 
    416      The "publisher" means any person or entity that distributes copies
    417      of the Document to the public.
    418 
    419      A section "Entitled XYZ" means a named subunit of the Document
    420      whose title either is precisely XYZ or contains XYZ in parentheses
    421      following text that translates XYZ in another language.  (Here XYZ
    422      stands for a specific section name mentioned below, such as
    423      "Acknowledgements", "Dedications", "Endorsements", or "History".)
    424      To "Preserve the Title" of such a section when you modify the
    425      Document means that it remains a section "Entitled XYZ" according
    426      to this definition.
    427 
    428      The Document may include Warranty Disclaimers next to the notice
    429      which states that this License applies to the Document.  These
    430      Warranty Disclaimers are considered to be included by reference in
    431      this License, but only as regards disclaiming warranties: any other
    432      implication that these Warranty Disclaimers may have is void and
    433      has no effect on the meaning of this License.
    434 
    435   2. VERBATIM COPYING
    436 
    437      You may copy and distribute the Document in any medium, either
    438      commercially or noncommercially, provided that this License, the
    439      copyright notices, and the license notice saying this License
    440      applies to the Document are reproduced in all copies, and that you
    441      add no other conditions whatsoever to those of this License.  You
    442      may not use technical measures to obstruct or control the reading
    443      or further copying of the copies you make or distribute.  However,
    444      you may accept compensation in exchange for copies.  If you
    445      distribute a large enough number of copies you must also follow the
    446      conditions in section 3.
    447 
    448      You may also lend copies, under the same conditions stated above,
    449      and you may publicly display copies.
    450 
    451   3. COPYING IN QUANTITY
    452 
    453      If you publish printed copies (or copies in media that commonly
    454      have printed covers) of the Document, numbering more than 100, and
    455      the Document's license notice requires Cover Texts, you must
    456      enclose the copies in covers that carry, clearly and legibly, all
    457      these Cover Texts: Front-Cover Texts on the front cover, and
    458      Back-Cover Texts on the back cover.  Both covers must also clearly
    459      and legibly identify you as the publisher of these copies.  The
    460      front cover must present the full title with all words of the title
    461      equally prominent and visible.  You may add other material on the
    462      covers in addition.  Copying with changes limited to the covers, as
    463      long as they preserve the title of the Document and satisfy these
    464      conditions, can be treated as verbatim copying in other respects.
    465 
    466      If the required texts for either cover are too voluminous to fit
    467      legibly, you should put the first ones listed (as many as fit
    468      reasonably) on the actual cover, and continue the rest onto
    469      adjacent pages.
    470 
    471      If you publish or distribute Opaque copies of the Document
    472      numbering more than 100, you must either include a machine-readable
    473      Transparent copy along with each Opaque copy, or state in or with
    474      each Opaque copy a computer-network location from which the general
    475      network-using public has access to download using public-standard
    476      network protocols a complete Transparent copy of the Document, free
    477      of added material.  If you use the latter option, you must take
    478      reasonably prudent steps, when you begin distribution of Opaque
    479      copies in quantity, to ensure that this Transparent copy will
    480      remain thus accessible at the stated location until at least one
    481      year after the last time you distribute an Opaque copy (directly or
    482      through your agents or retailers) of that edition to the public.
    483 
    484      It is requested, but not required, that you contact the authors of
    485      the Document well before redistributing any large number of copies,
    486      to give them a chance to provide you with an updated version of the
    487      Document.
    488 
    489   4. MODIFICATIONS
    490 
    491      You may copy and distribute a Modified Version of the Document
    492      under the conditions of sections 2 and 3 above, provided that you
    493      release the Modified Version under precisely this License, with the
    494      Modified Version filling the role of the Document, thus licensing
    495      distribution and modification of the Modified Version to whoever
    496      possesses a copy of it.  In addition, you must do these things in
    497      the Modified Version:
    498 
    499        A. Use in the Title Page (and on the covers, if any) a title
    500           distinct from that of the Document, and from those of previous
    501           versions (which should, if there were any, be listed in the
    502           History section of the Document).  You may use the same title
    503           as a previous version if the original publisher of that
    504           version gives permission.
    505 
    506        B. List on the Title Page, as authors, one or more persons or
    507           entities responsible for authorship of the modifications in
    508           the Modified Version, together with at least five of the
    509           principal authors of the Document (all of its principal
    510           authors, if it has fewer than five), unless they release you
    511           from this requirement.
    512 
    513        C. State on the Title page the name of the publisher of the
    514           Modified Version, as the publisher.
    515 
    516        D. Preserve all the copyright notices of the Document.
    517 
    518        E. Add an appropriate copyright notice for your modifications
    519           adjacent to the other copyright notices.
    520 
    521        F. Include, immediately after the copyright notices, a license
    522           notice giving the public permission to use the Modified
    523           Version under the terms of this License, in the form shown in
    524           the Addendum below.
    525 
    526        G. Preserve in that license notice the full lists of Invariant
    527           Sections and required Cover Texts given in the Document's
    528           license notice.
    529 
    530        H. Include an unaltered copy of this License.
    531 
    532        I. Preserve the section Entitled "History", Preserve its Title,
    533           and add to it an item stating at least the title, year, new
    534           authors, and publisher of the Modified Version as given on the
    535           Title Page.  If there is no section Entitled "History" in the
    536           Document, create one stating the title, year, authors, and
    537           publisher of the Document as given on its Title Page, then add
    538           an item describing the Modified Version as stated in the
    539           previous sentence.
    540 
    541        J. Preserve the network location, if any, given in the Document
    542           for public access to a Transparent copy of the Document, and
    543           likewise the network locations given in the Document for
    544           previous versions it was based on.  These may be placed in the
    545           "History" section.  You may omit a network location for a work
    546           that was published at least four years before the Document
    547           itself, or if the original publisher of the version it refers
    548           to gives permission.
    549 
    550        K. For any section Entitled "Acknowledgements" or "Dedications",
    551           Preserve the Title of the section, and preserve in the section
    552           all the substance and tone of each of the contributor
    553           acknowledgements and/or dedications given therein.
    554 
    555        L. Preserve all the Invariant Sections of the Document, unaltered
    556           in their text and in their titles.  Section numbers or the
    557           equivalent are not considered part of the section titles.
    558 
    559        M. Delete any section Entitled "Endorsements".  Such a section
    560           may not be included in the Modified Version.
    561 
    562        N. Do not retitle any existing section to be Entitled
    563           "Endorsements" or to conflict in title with any Invariant
    564           Section.
    565 
    566        O. Preserve any Warranty Disclaimers.
    567 
    568      If the Modified Version includes new front-matter sections or
    569      appendices that qualify as Secondary Sections and contain no
    570      material copied from the Document, you may at your option designate
    571      some or all of these sections as invariant.  To do this, add their
    572      titles to the list of Invariant Sections in the Modified Version's
    573      license notice.  These titles must be distinct from any other
    574      section titles.
    575 
    576      You may add a section Entitled "Endorsements", provided it contains
    577      nothing but endorsements of your Modified Version by various
    578      parties--for example, statements of peer review or that the text
    579      has been approved by an organization as the authoritative
    580      definition of a standard.
    581 
    582      You may add a passage of up to five words as a Front-Cover Text,
    583      and a passage of up to 25 words as a Back-Cover Text, to the end of
    584      the list of Cover Texts in the Modified Version.  Only one passage
    585      of Front-Cover Text and one of Back-Cover Text may be added by (or
    586      through arrangements made by) any one entity.  If the Document
    587      already includes a cover text for the same cover, previously added
    588      by you or by arrangement made by the same entity you are acting on
    589      behalf of, you may not add another; but you may replace the old
    590      one, on explicit permission from the previous publisher that added
    591      the old one.
    592 
    593      The author(s) and publisher(s) of the Document do not by this
    594      License give permission to use their names for publicity for or to
    595      assert or imply endorsement of any Modified Version.
    596 
    597   5. COMBINING DOCUMENTS
    598 
    599      You may combine the Document with other documents released under
    600      this License, under the terms defined in section 4 above for
    601      modified versions, provided that you include in the combination all
    602      of the Invariant Sections of all of the original documents,
    603      unmodified, and list them all as Invariant Sections of your
    604      combined work in its license notice, and that you preserve all
    605      their Warranty Disclaimers.
    606 
    607      The combined work need only contain one copy of this License, and
    608      multiple identical Invariant Sections may be replaced with a single
    609      copy.  If there are multiple Invariant Sections with the same name
    610      but different contents, make the title of each such section unique
    611      by adding at the end of it, in parentheses, the name of the
    612      original author or publisher of that section if known, or else a
    613      unique number.  Make the same adjustment to the section titles in
    614      the list of Invariant Sections in the license notice of the
    615      combined work.
    616 
    617      In the combination, you must combine any sections Entitled
    618      "History" in the various original documents, forming one section
    619      Entitled "History"; likewise combine any sections Entitled
    620      "Acknowledgements", and any sections Entitled "Dedications".  You
    621      must delete all sections Entitled "Endorsements."
    622 
    623   6. COLLECTIONS OF DOCUMENTS
    624 
    625      You may make a collection consisting of the Document and other
    626      documents released under this License, and replace the individual
    627      copies of this License in the various documents with a single copy
    628      that is included in the collection, provided that you follow the
    629      rules of this License for verbatim copying of each of the documents
    630      in all other respects.
    631 
    632      You may extract a single document from such a collection, and
    633      distribute it individually under this License, provided you insert
    634      a copy of this License into the extracted document, and follow this
    635      License in all other respects regarding verbatim copying of that
    636      document.
    637 
    638   7. AGGREGATION WITH INDEPENDENT WORKS
    639 
    640      A compilation of the Document or its derivatives with other
    641      separate and independent documents or works, in or on a volume of a
    642      storage or distribution medium, is called an "aggregate" if the
    643      copyright resulting from the compilation is not used to limit the
    644      legal rights of the compilation's users beyond what the individual
    645      works permit.  When the Document is included in an aggregate, this
    646      License does not apply to the other works in the aggregate which
    647      are not themselves derivative works of the Document.
    648 
    649      If the Cover Text requirement of section 3 is applicable to these
    650      copies of the Document, then if the Document is less than one half
    651      of the entire aggregate, the Document's Cover Texts may be placed
    652      on covers that bracket the Document within the aggregate, or the
    653      electronic equivalent of covers if the Document is in electronic
    654      form.  Otherwise they must appear on printed covers that bracket
    655      the whole aggregate.
    656 
    657   8. TRANSLATION
    658 
    659      Translation is considered a kind of modification, so you may
    660      distribute translations of the Document under the terms of section
    661      4.  Replacing Invariant Sections with translations requires special
    662      permission from their copyright holders, but you may include
    663      translations of some or all Invariant Sections in addition to the
    664      original versions of these Invariant Sections.  You may include a
    665      translation of this License, and all the license notices in the
    666      Document, and any Warranty Disclaimers, provided that you also
    667      include the original English version of this License and the
    668      original versions of those notices and disclaimers.  In case of a
    669      disagreement between the translation and the original version of
    670      this License or a notice or disclaimer, the original version will
    671      prevail.
    672 
    673      If a section in the Document is Entitled "Acknowledgements",
    674      "Dedications", or "History", the requirement (section 4) to
    675      Preserve its Title (section 1) will typically require changing the
    676      actual title.
    677 
    678   9. TERMINATION
    679 
    680      You may not copy, modify, sublicense, or distribute the Document
    681      except as expressly provided under this License.  Any attempt
    682      otherwise to copy, modify, sublicense, or distribute it is void,
    683      and will automatically terminate your rights under this License.
    684 
    685      However, if you cease all violation of this License, then your
    686      license from a particular copyright holder is reinstated (a)
    687      provisionally, unless and until the copyright holder explicitly and
    688      finally terminates your license, and (b) permanently, if the
    689      copyright holder fails to notify you of the violation by some
    690      reasonable means prior to 60 days after the cessation.
    691 
    692      Moreover, your license from a particular copyright holder is
    693      reinstated permanently if the copyright holder notifies you of the
    694      violation by some reasonable means, this is the first time you have
    695      received notice of violation of this License (for any work) from
    696      that copyright holder, and you cure the violation prior to 30 days
    697      after your receipt of the notice.
    698 
    699      Termination of your rights under this section does not terminate
    700      the licenses of parties who have received copies or rights from you
    701      under this License.  If your rights have been terminated and not
    702      permanently reinstated, receipt of a copy of some or all of the
    703      same material does not give you any rights to use it.
    704 
    705   10. FUTURE REVISIONS OF THIS LICENSE
    706 
    707      The Free Software Foundation may publish new, revised versions of
    708      the GNU Free Documentation License from time to time.  Such new
    709      versions will be similar in spirit to the present version, but may
    710      differ in detail to address new problems or concerns.  See
    711      <http://www.gnu.org/copyleft/>.
    712 
    713      Each version of the License is given a distinguishing version
    714      number.  If the Document specifies that a particular numbered
    715      version of this License "or any later version" applies to it, you
    716      have the option of following the terms and conditions either of
    717      that specified version or of any later version that has been
    718      published (not as a draft) by the Free Software Foundation.  If the
    719      Document does not specify a version number of this License, you may
    720      choose any version ever published (not as a draft) by the Free
    721      Software Foundation.  If the Document specifies that a proxy can
    722      decide which future versions of this License can be used, that
    723      proxy's public statement of acceptance of a version permanently
    724      authorizes you to choose that version for the Document.
    725 
    726   11. RELICENSING
    727 
    728      "Massive Multiauthor Collaboration Site" (or "MMC Site") means any
    729      World Wide Web server that publishes copyrightable works and also
    730      provides prominent facilities for anybody to edit those works.  A
    731      public wiki that anybody can edit is an example of such a server.
    732      A "Massive Multiauthor Collaboration" (or "MMC") contained in the
    733      site means any set of copyrightable works thus published on the MMC
    734      site.
    735 
    736      "CC-BY-SA" means the Creative Commons Attribution-Share Alike 3.0
    737      license published by Creative Commons Corporation, a not-for-profit
    738      corporation with a principal place of business in San Francisco,
    739      California, as well as future copyleft versions of that license
    740      published by that same organization.
    741 
    742      "Incorporate" means to publish or republish a Document, in whole or
    743      in part, as part of another Document.
    744 
    745      An MMC is "eligible for relicensing" if it is licensed under this
    746      License, and if all works that were first published under this
    747      License somewhere other than this MMC, and subsequently
    748      incorporated in whole or in part into the MMC, (1) had no cover
    749      texts or invariant sections, and (2) were thus incorporated prior
    750      to November 1, 2008.
    751 
    752      The operator of an MMC Site may republish an MMC contained in the
    753      site under CC-BY-SA on the same site at any time before August 1,
    754      2009, provided the MMC is eligible for relicensing.
    755 
    756 ADDENDUM: How to use this License for your documents
    757 ====================================================
    758 
    759 To use this License in a document you have written, include a copy of
    760 the License in the document and put the following copyright and license
    761 notices just after the title page:
    762 
    763        Copyright (C)  YEAR  YOUR NAME.
    764        Permission is granted to copy, distribute and/or modify this document
    765        under the terms of the GNU Free Documentation License, Version 1.3
    766        or any later version published by the Free Software Foundation;
    767        with no Invariant Sections, no Front-Cover Texts, and no Back-Cover
    768        Texts.  A copy of the license is included in the section entitled ``GNU
    769        Free Documentation License''.
    770 
    771    If you have Invariant Sections, Front-Cover Texts and Back-Cover
    772 Texts, replace the "with...Texts."  line with this:
    773 
    774          with the Invariant Sections being LIST THEIR TITLES, with
    775          the Front-Cover Texts being LIST, and with the Back-Cover Texts
    776          being LIST.
    777 
    778    If you have Invariant Sections without Cover Texts, or some other
    779 combination of the three, merge those two alternatives to suit the
    780 situation.
    781 
    782    If your document contains nontrivial examples of program code, we
    783 recommend releasing these examples in parallel under your choice of free
    784 software license, such as the GNU General Public License, to permit
    785 their use in free software.
    786 
    787 
    788 File: libquadmath.info,  Node: Reporting Bugs,  Prev: GNU Free Documentation License,  Up: Top
    789 
    790 4 Reporting Bugs
    791 ****************
    792 
    793 Bugs in the GCC Quad-Precision Math Library implementation should be
    794 reported via <http://gcc.gnu.org/bugs.html>.
    795 
    796 
    797 
    798 Tag Table:
    799 Node: Top1633
    800 Node: Typedef and constants2367
    801 Node: Math Library Routines3786
    802 Node: I/O Library Routines7503
    803 Node: strtoflt1287828
    804 Node: quadmath_snprintf8588
    805 Node: GNU Free Documentation License10798
    806 Node: Reporting Bugs35944
    807 
    808 End Tag Table
  • libstdc++-v3/include/bits/shared_ptr_base.h

    diff -Naur gcc-4.8.2.orig/libstdc++-v3/include/bits/shared_ptr_base.h gcc-4.8.2/libstdc++-v3/include/bits/shared_ptr_base.h
    old new  
    391391    public:
    392392      template<typename... _Args>
    393393        _Sp_counted_ptr_inplace(_Alloc __a, _Args&&... __args)
    394         : _M_impl(__a), _M_storage()
     394        : _M_impl(__a)
    395395        {
    396396          _M_impl._M_ptr = static_cast<_Tp*>(static_cast<void*>(&_M_storage));
    397397          // _GLIBCXX_RESOLVE_LIB_DEFECTS
     
    819819        : _M_ptr(__r.get()), _M_refcount()
    820820        {
    821821          __glibcxx_function_requires(_ConvertibleConcept<_Tp1*, _Tp*>)
    822           auto __tmp = std::__addressof(*__r.get());
     822          auto __tmp = __r.get();
    823823          _M_refcount = __shared_count<_Lp>(std::move(__r));
    824824          __enable_shared_from_this_helper(_M_refcount, __tmp, __tmp);
    825825        }
  • libstdc++-v3/include/bits/stl_algo.h

    diff -Naur gcc-4.8.2.orig/libstdc++-v3/include/bits/stl_algo.h gcc-4.8.2/libstdc++-v3/include/bits/stl_algo.h
    old new  
    22792279                                _RandomAccessIterator __last)
    22802280    {
    22812281      _RandomAccessIterator __mid = __first + (__last - __first) / 2;
    2282       std::__move_median_to_first(__first, __first + 1, __mid, (__last - 2));
     2282      std::__move_median_to_first(__first, __first + 1, __mid, __last - 1);
    22832283      return std::__unguarded_partition(__first + 1, __last, *__first);
    22842284    }
    22852285
     
    22912291                                _RandomAccessIterator __last, _Compare __comp)
    22922292    {
    22932293      _RandomAccessIterator __mid = __first + (__last - __first) / 2;
    2294       std::__move_median_to_first(__first, __first + 1, __mid, (__last - 2),
     2294      std::__move_median_to_first(__first, __first + 1, __mid, __last - 1,
    22952295                                  __comp);
    22962296      return std::__unguarded_partition(__first + 1, __last, *__first, __comp);
    22972297    }
  • libstdc++-v3/include/c_global/cstdio

    diff -Naur gcc-4.8.2.orig/libstdc++-v3/include/c_global/cstdio gcc-4.8.2/libstdc++-v3/include/c_global/cstdio
    old new  
    6969#undef ftell
    7070#undef fwrite
    7171#undef getc
     72#undef getchar
    7273#undef gets
    7374#undef perror
    7475#undef printf
  • libstdc++-v3/include/debug/functions.h

    diff -Naur gcc-4.8.2.orig/libstdc++-v3/include/debug/functions.h gcc-4.8.2/libstdc++-v3/include/debug/functions.h
    old new  
    345345      return __check_sorted_set_aux(__first, __last, __pred, _SameType());
    346346   }
    347347
     348  // _GLIBCXX_RESOLVE_LIB_DEFECTS
     349  // 270. Binary search requirements overly strict
     350  // Determine if a sequence is partitioned w.r.t. this element.
    348351  template<typename _ForwardIterator, typename _Tp>
    349352    inline bool
    350   __check_partitioned_lower_aux(_ForwardIterator __first,
    351                                 _ForwardIterator __last, const _Tp& __value,
    352                                 std::forward_iterator_tag)
     353    __check_partitioned_lower(_ForwardIterator __first,
     354                              _ForwardIterator __last, const _Tp& __value)
    353355    {
    354356      while (__first != __last && *__first < __value)
    355357        ++__first;
     
    362364      return __first == __last;
    363365    }
    364366
    365   // For performance reason, as the iterator range has been validated, check on
    366   // random access safe iterators is done using the base iterator.
    367   template<typename _Iterator, typename _Sequence, typename _Tp>
    368     inline bool
    369     __check_partitioned_lower_aux(
    370                         const _Safe_iterator<_Iterator, _Sequence>& __first,
    371                         const _Safe_iterator<_Iterator, _Sequence>& __last,
    372                         const _Tp& __value,
    373                         std::random_access_iterator_tag __tag)
    374     {
    375       return __check_partitioned_lower_aux(__first.base(), __last.base(),
    376                                            __value, __tag);
    377     }
    378 
    379   // _GLIBCXX_RESOLVE_LIB_DEFECTS
    380   // 270. Binary search requirements overly strict
    381   // Determine if a sequence is partitioned w.r.t. this element.
    382367  template<typename _ForwardIterator, typename _Tp>
    383368    inline bool
    384     __check_partitioned_lower(_ForwardIterator __first,
     369    __check_partitioned_upper(_ForwardIterator __first,
    385370                              _ForwardIterator __last, const _Tp& __value)
    386371    {
    387       return __check_partitioned_lower_aux(__first, __last, __value,
    388                                            std::__iterator_category(__first));
    389     }
    390 
    391   template<typename _ForwardIterator, typename _Tp>
    392     inline bool
    393     __check_partitioned_upper_aux(_ForwardIterator __first,
    394                                   _ForwardIterator __last, const _Tp& __value,
    395                                   std::forward_iterator_tag)
    396     {
    397372      while (__first != __last && !(__value < *__first))
    398373        ++__first;
    399374      if (__first != __last)
     
    405380      return __first == __last;
    406381    }
    407382
    408   // For performance reason, as the iterator range has been validated, check on
    409   // random access safe iterators is done using the base iterator.
    410   template<typename _Iterator, typename _Sequence, typename _Tp>
    411     inline bool
    412     __check_partitioned_upper_aux(
    413                         const _Safe_iterator<_Iterator, _Sequence>& __first,
    414                         const _Safe_iterator<_Iterator, _Sequence>& __last,
    415                         const _Tp& __value,
    416                         std::random_access_iterator_tag __tag)
    417     {
    418       return __check_partitioned_upper_aux(__first.base(), __last.base(),
    419                                            __value, __tag);
    420     }
    421 
    422   template<typename _ForwardIterator, typename _Tp>
    423     inline bool
    424     __check_partitioned_upper(_ForwardIterator __first,
    425                               _ForwardIterator __last, const _Tp& __value)
    426     {
    427       return __check_partitioned_upper_aux(__first, __last, __value,
    428                                            std::__iterator_category(__first));
    429     }
    430 
     383  // Determine if a sequence is partitioned w.r.t. this element.
    431384  template<typename _ForwardIterator, typename _Tp, typename _Pred>
    432385    inline bool
    433     __check_partitioned_lower_aux(_ForwardIterator __first,
    434                                   _ForwardIterator __last, const _Tp& __value,
    435                                   _Pred __pred,
    436                                   std::forward_iterator_tag)
     386    __check_partitioned_lower(_ForwardIterator __first,
     387                              _ForwardIterator __last, const _Tp& __value,
     388                              _Pred __pred)
    437389    {
    438390      while (__first != __last && bool(__pred(*__first, __value)))
    439391        ++__first;
     
    446398      return __first == __last;
    447399    }
    448400
    449   // For performance reason, as the iterator range has been validated, check on
    450   // random access safe iterators is done using the base iterator.
    451   template<typename _Iterator, typename _Sequence,
    452            typename _Tp, typename _Pred>
    453     inline bool
    454     __check_partitioned_lower_aux(
    455                         const _Safe_iterator<_Iterator, _Sequence>& __first,
    456                         const _Safe_iterator<_Iterator, _Sequence>& __last,
    457                         const _Tp& __value, _Pred __pred,
    458                         std::random_access_iterator_tag __tag)
    459     {
    460       return __check_partitioned_lower_aux(__first.base(), __last.base(),
    461                                            __value, __pred, __tag);
    462     }
    463 
    464   // Determine if a sequence is partitioned w.r.t. this element.
    465401  template<typename _ForwardIterator, typename _Tp, typename _Pred>
    466402    inline bool
    467     __check_partitioned_lower(_ForwardIterator __first,
     403    __check_partitioned_upper(_ForwardIterator __first,
    468404                              _ForwardIterator __last, const _Tp& __value,
    469405                              _Pred __pred)
    470406    {
    471       return __check_partitioned_lower_aux(__first, __last, __value, __pred,
    472                                            std::__iterator_category(__first));
    473     }
    474 
    475   template<typename _ForwardIterator, typename _Tp, typename _Pred>
    476     inline bool
    477     __check_partitioned_upper_aux(_ForwardIterator __first,
    478                                   _ForwardIterator __last, const _Tp& __value,
    479                                   _Pred __pred,
    480                                   std::forward_iterator_tag)
    481     {
    482407      while (__first != __last && !bool(__pred(__value, *__first)))
    483408        ++__first;
    484409      if (__first != __last)
     
    490415      return __first == __last;
    491416    }
    492417
    493   // For performance reason, as the iterator range has been validated, check on
    494   // random access safe iterators is done using the base iterator.
    495   template<typename _Iterator, typename _Sequence,
    496            typename _Tp, typename _Pred>
    497     inline bool
    498     __check_partitioned_upper_aux(
    499                         const _Safe_iterator<_Iterator, _Sequence>& __first,
    500                         const _Safe_iterator<_Iterator, _Sequence>& __last,
    501                         const _Tp& __value, _Pred __pred,
    502                         std::random_access_iterator_tag __tag)
    503     {
    504       return __check_partitioned_upper_aux(__first.base(), __last.base(),
    505                                            __value, __pred, __tag);
    506     }
    507 
    508   template<typename _ForwardIterator, typename _Tp, typename _Pred>
    509     inline bool
    510     __check_partitioned_upper(_ForwardIterator __first,
    511                               _ForwardIterator __last, const _Tp& __value,
    512                               _Pred __pred)
    513     {
    514       return __check_partitioned_upper_aux(__first, __last, __value, __pred,
    515                                            std::__iterator_category(__first));
    516     }
    517 
    518418  // Helper struct to detect random access safe iterators.
    519419  template<typename _Iterator>
    520420    struct __is_safe_random_iterator
  • libstdc++-v3/include/debug/macros.h

    diff -Naur gcc-4.8.2.orig/libstdc++-v3/include/debug/macros.h gcc-4.8.2/libstdc++-v3/include/debug/macros.h
    old new  
    261261    w.r.t. the value _Value. */
    262262#define __glibcxx_check_partitioned_lower(_First,_Last,_Value)          \
    263263__glibcxx_check_valid_range(_First,_Last);                              \
    264 _GLIBCXX_DEBUG_VERIFY(__gnu_debug::__check_partitioned_lower(_First, _Last, \
    265                                                             _Value),    \
     264_GLIBCXX_DEBUG_VERIFY(__gnu_debug::__check_partitioned_lower(           \
     265                        __gnu_debug::__base(_First),                    \
     266                        __gnu_debug::__base(_Last), _Value),            \
    266267                      _M_message(__gnu_debug::__msg_unpartitioned)      \
    267268                      ._M_iterator(_First, #_First)                     \
    268269                      ._M_iterator(_Last, #_Last)                       \
     
    270271
    271272#define __glibcxx_check_partitioned_upper(_First,_Last,_Value)          \
    272273__glibcxx_check_valid_range(_First,_Last);                              \
    273 _GLIBCXX_DEBUG_VERIFY(__gnu_debug::__check_partitioned_upper(_First, _Last, \
    274                                                             _Value),    \
     274_GLIBCXX_DEBUG_VERIFY(__gnu_debug::__check_partitioned_upper(           \
     275                        __gnu_debug::__base(_First),                    \
     276                        __gnu_debug::__base(_Last), _Value),            \
    275277                      _M_message(__gnu_debug::__msg_unpartitioned)      \
    276278                      ._M_iterator(_First, #_First)                     \
    277279                      ._M_iterator(_Last, #_Last)                       \
     
    281283    w.r.t. the value _Value and predicate _Pred. */
    282284#define __glibcxx_check_partitioned_lower_pred(_First,_Last,_Value,_Pred) \
    283285__glibcxx_check_valid_range(_First,_Last);                              \
    284 _GLIBCXX_DEBUG_VERIFY(__gnu_debug::__check_partitioned_lower(_First, _Last, \
    285                                                          _Value, _Pred), \
     286_GLIBCXX_DEBUG_VERIFY(__gnu_debug::__check_partitioned_lower(           \
     287                        __gnu_debug::__base(_First),                    \
     288                        __gnu_debug::__base(_Last), _Value, _Pred),     \
    286289                      _M_message(__gnu_debug::__msg_unpartitioned_pred) \
    287290                      ._M_iterator(_First, #_First)                     \
    288291                      ._M_iterator(_Last, #_Last)                       \
     
    293296    w.r.t. the value _Value and predicate _Pred. */
    294297#define __glibcxx_check_partitioned_upper_pred(_First,_Last,_Value,_Pred) \
    295298__glibcxx_check_valid_range(_First,_Last);                              \
    296 _GLIBCXX_DEBUG_VERIFY(__gnu_debug::__check_partitioned_upper(_First, _Last, \
    297                                                          _Value, _Pred), \
     299_GLIBCXX_DEBUG_VERIFY(__gnu_debug::__check_partitioned_upper(           \
     300                        __gnu_debug::__base(_First),                    \
     301                        __gnu_debug::__base(_Last), _Value, _Pred),     \
    298302                      _M_message(__gnu_debug::__msg_unpartitioned_pred) \
    299303                      ._M_iterator(_First, #_First)                     \
    300304                      ._M_iterator(_Last, #_Last)                       \
  • libstdc++-v3/testsuite/20_util/shared_ptr/cons/58839.cc

    diff -Naur gcc-4.8.2.orig/libstdc++-v3/testsuite/20_util/shared_ptr/cons/58839.cc gcc-4.8.2/libstdc++-v3/testsuite/20_util/shared_ptr/cons/58839.cc
    old new  
     1// { dg-options "-std=gnu++11" }
     2// { dg-do compile }
     3
     4// Copyright (C) 2013 Free Software Foundation, Inc.
     5//
     6// This file is part of the GNU ISO C++ Library.  This library is free
     7// software; you can redistribute it and/or modify it under the
     8// terms of the GNU General Public License as published by the
     9// Free Software Foundation; either version 3, or (at your option)
     10// any later version.
     11
     12// This library is distributed in the hope that it will be useful,
     13// but WITHOUT ANY WARRANTY; without even the implied warranty of
     14// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
     15// GNU General Public License for more details.
     16
     17// You should have received a copy of the GNU General Public License along
     18// with this library; see the file COPYING3.  If not see
     19// <http://www.gnu.org/licenses/>.
     20
     21#include <memory>
     22
     23// libstdc++/58839
     24
     25struct D {
     26  void operator()(void*) const noexcept { }
     27};
     28
     29void test01()
     30{
     31  std::unique_ptr<void, D> y;
     32  std::shared_ptr<void> x = std::move(y);
     33}
  • libstdc++-v3/testsuite/25_algorithms/nth_element/58800.cc

    diff -Naur gcc-4.8.2.orig/libstdc++-v3/testsuite/25_algorithms/nth_element/58800.cc gcc-4.8.2/libstdc++-v3/testsuite/25_algorithms/nth_element/58800.cc
    old new  
     1// Copyright (C) 2013 Free Software Foundation, Inc.
     2//
     3// This file is part of the GNU ISO C++ Library.  This library is free
     4// software; you can redistribute it and/or modify it under the
     5// terms of the GNU General Public License as published by the
     6// Free Software Foundation; either version 3, or (at your option)
     7// any later version.
     8
     9// This library is distributed in the hope that it will be useful,
     10// but WITHOUT ANY WARRANTY; without even the implied warranty of
     11// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
     12// GNU General Public License for more details.
     13
     14// You should have received a copy of the GNU General Public License along
     15// with this library; see the file COPYING3.  If not see
     16// <http://www.gnu.org/licenses/>.
     17
     18// 25.3.2 [lib.alg.nth.element]
     19
     20// { dg-options "-std=gnu++11" }
     21
     22#include <algorithm>
     23#include <testsuite_hooks.h>
     24#include <testsuite_iterators.h>
     25
     26using __gnu_test::test_container;
     27using __gnu_test::random_access_iterator_wrapper;
     28
     29typedef test_container<int, random_access_iterator_wrapper> Container;
     30
     31void test01()
     32{
     33  std::vector<int> v = {
     34    207089,
     35    202585,
     36    180067,
     37    157549,
     38    211592,
     39    216096,
     40    207089
     41  };
     42
     43  Container con(v.data(), v.data() + 7);
     44
     45  std::nth_element(con.begin(), con.begin() + 3, con.end());
     46}
     47
     48int main()
     49{
     50  test01();
     51  return 0;
     52}
Note: See TracBrowser for help on using the repository browser.