~rdoering/ubuntu/intrepid/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/parsetools/src/yecc.erl

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

Show diffs side-by-side

added added

removed removed

Lines of Context:
94
94
          rule_nmbr,
95
95
          head,
96
96
          nmbr_of_daughters,
97
 
          prec
 
97
          prec,
 
98
          unused % assure that #reduce{} comes before #shift{} when soring
98
99
         }).
99
100
 
100
101
-record(shift, {
101
102
          state,
102
 
          prec
 
103
          pos,
 
104
          prec,
 
105
          rule_nmbr
103
106
         }).
104
107
 
105
108
-record(user_code, {state, terminal, funname, action}).
1444
1447
                              prec = get_prec(Daughters ++ [Head], St)}}
1445
1448
                     | compute_parse_actions1(Items, N, St)]
1446
1449
            end;
1447
 
        [Symbol | _] ->
 
1450
        [Symbol | Daughters] ->
1448
1451
            case is_terminal(St#yecc.symbol_tab, Symbol) of
1449
1452
                true ->
1450
1453
                    DecSymbol = decode_symbol(Symbol, St#yecc.inv_symbol_tab),
1451
 
                    Prec1 = case rule(RulePointer, St) of
1452
 
                                {[Head, DecSymbol], _RuleLine, _} ->
1453
 
                                    get_prec([Head, DecSymbol], St);
1454
 
                                _ ->
1455
 
                                    get_prec([DecSymbol], St)
 
1454
                    {[Head | _], _RuleLine, _} = rule(RulePointer, St),
 
1455
                    %% A bogus shift-shift conflict can be introduced
 
1456
                    %% here if some terminal occurs in different rules
 
1457
                    %% which have been given precedence "one level up".
 
1458
                    Prec1 = case Daughters of
 
1459
                                [] -> get_prec([DecSymbol, Head], St);
 
1460
                                _ -> get_prec([DecSymbol], St)
1456
1461
                            end,
 
1462
                    Pos = case Daughters of
 
1463
                              [] -> z;
 
1464
                              _ -> a
 
1465
                          end,
1457
1466
                    [{[DecSymbol],
1458
 
                      #shift{state = goto(N, DecSymbol, St), prec = Prec1}}
 
1467
                      #shift{state = goto(N, DecSymbol, St), 
 
1468
                             pos = Pos,
 
1469
                             prec = Prec1,
 
1470
                             rule_nmbr = RulePointer}}
1459
1471
                     | compute_parse_actions1(Items, N, St)];
1460
1472
                false ->
1461
1473
                    compute_parse_actions1(Items, N, St)
1517
1529
 
1518
1530
find_action_conflicts2([Action], Cxt) ->
1519
1531
    {Action, Cxt};
 
1532
find_action_conflicts2([#shift{state = St, pos = Pos, prec = Prec},
 
1533
                        #shift{state = St}=S | As], 
 
1534
                       Cxt) when Pos =:= a; Prec =:= {0,none} ->
 
1535
    %% This is a kludge to remove the bogus shift-shift conflict
 
1536
    %% introduced in compute_parse_actions1().
 
1537
    find_action_conflicts2([S | As], Cxt);
 
1538
find_action_conflicts2([#shift{state = NewState, pos = z}=S1,
 
1539
                        #shift{state = NewState}=S2 | _], Cxt) ->
 
1540
    %% This is even worse than last clause. Give up.
 
1541
    Confl = conflict(S1, S2, Cxt),
 
1542
    #cxt{yecc = St0} = Cxt,
 
1543
    St = conflict_error(Confl, St0),
 
1544
    {S1, Cxt#cxt{yecc = St}}; % return any action
1520
1545
find_action_conflicts2([#shift{prec = {P1, Ass1}}=S | Rs], Cxt0) ->
1521
1546
    {R, Cxt1} = find_reduce_reduce(Rs, Cxt0),
1522
1547
    #cxt{res = Res0, yecc = St0} = Cxt1,
1547
1572
find_reduce_reduce([R], Cxt) ->
1548
1573
    {R, Cxt};
1549
1574
find_reduce_reduce([#reduce{head = Categ1, prec = {P1, _}}=R1, 
1550
 
         #reduce{head = Categ2, prec = {P2, _}}=R2 | Rs], Cxt0) ->
 
1575
                    #reduce{head = Categ2, prec = {P2, _}}=R2 | Rs], Cxt0) ->
1551
1576
    #cxt{res = Res0, yecc = St0} = Cxt0,
1552
1577
    Confl = conflict(R1, R2, Cxt0),
1553
1578
    {R, Res, St} = 
1604
1629
        {Symbol, StateN, _, {reduce, _, _, _}} ->
1605
1630
            St#yecc{reduce_reduce = [{StateN,Symbol} |St#yecc.reduce_reduce]};
1606
1631
        {Symbol, StateN, _, {shift, _, _}} ->
1607
 
            St#yecc{shift_reduce = [{StateN,Symbol} | St#yecc.shift_reduce]}
 
1632
            St#yecc{shift_reduce = [{StateN,Symbol} | St#yecc.shift_reduce]};
 
1633
        {_Symbol, _StateN, {one_level_up, _, _}, _Confl} ->
 
1634
            St
1608
1635
    end.
1609
1636
 
 
1637
conflict(#shift{prec = Prec1, rule_nmbr = RuleNmbr1}, 
 
1638
         #shift{prec = Prec2, rule_nmbr = RuleNmbr2}, Cxt) ->
 
1639
    %% Conflict due to precedences "one level up". Kludge.
 
1640
    #cxt{terminal = Symbol, state_n = N, yecc = St} = Cxt,    
 
1641
    {_, L1, RuleN1} = rule(RuleNmbr1, St),
 
1642
    {_, L2, RuleN2} = rule(RuleNmbr2, St),
 
1643
    Confl = {one_level_up, {L1, RuleN1, Prec1}, {L2, RuleN2, Prec2}},
 
1644
    {Symbol, N, Confl, Confl};
1610
1645
conflict(#reduce{rule_nmbr = RuleNmbr1}, NewAction, Cxt) ->
1611
1646
    #cxt{terminal = Symbol, state_n = N, yecc = St} = Cxt,
1612
1647
    {R1, RuleLine1, RuleN1} = rule(RuleNmbr1, St),
1619
1654
            end,
1620
1655
    {Symbol, N, {R1, RuleN1, RuleLine1}, Confl}.
1621
1656
 
 
1657
format_conflict({Symbol, N, _, {one_level_up, 
 
1658
                                {L1, RuleN1, {P1, Ass1}}, 
 
1659
                                {L2, RuleN2, {P2, Ass2}}}}) ->
 
1660
    S1 = io_lib:fwrite("Conflicting precedences of symbols when "
 
1661
                       "scanning ~s in state ~w:\n", 
 
1662
                       [format_symbol(Symbol), N]),
 
1663
    S2 = io_lib:fwrite("   ~s ~w (rule ~w at line ~w)\n"
 
1664
                        "      vs.\n",
 
1665
                       [format_assoc(Ass1), P1, RuleN1, L1]),
 
1666
    S3 = io_lib:fwrite("   ~s ~w (rule ~w at line ~w)\n", 
 
1667
                       [format_assoc(Ass2), P2, RuleN2, L2]),
 
1668
    [S1, S2, S3];
1622
1669
format_conflict({Symbol, N, Reduce, Confl}) ->
1623
1670
    S1 = io_lib:fwrite("Parse action conflict scanning symbol "
1624
1671
                       "~s in state ~w:\n", [format_symbol(Symbol), N]),
2094
2141
format_filename(Filename) ->
2095
2142
    io_lib:write_string(filename:flatten(Filename)).
2096
2143
 
 
2144
format_assoc(left) ->
 
2145
    "Left";
 
2146
format_assoc(right) ->
 
2147
    "Right";
 
2148
format_assoc(unary) ->
 
2149
    "Unary";
 
2150
format_assoc(nonassoc) ->
 
2151
    "Nonassoc".
 
2152
 
2097
2153
format_symbol(Symbol) ->
2098
2154
    String = concat([Symbol]),
2099
2155
    case erl_scan:string(String) of