~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to erts/emulator/utils/beam_makeops

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
29
29
my $num_file_opcodes = 0;
30
30
 
31
31
# This is shift counts and mask for the packer.
32
 
my $WHOLE_WORD = 0xFFFFFFFF;
 
32
my $WHOLE_WORD = '';
33
33
my @pack_instr;
34
34
my @pack_shift;
35
35
my @pack_mask;
37
37
$pack_instr[2] = ['6', 'i'];
38
38
$pack_instr[3] = ['0', '0', 'i'];
39
39
 
40
 
$pack_shift[2] = [0, 16];
41
 
$pack_shift[3] = [0, 10, 20];
42
 
 
43
 
$pack_mask[2]  = [0xFFF, $WHOLE_WORD];
44
 
$pack_mask[3]  = [0xFFC, 0xFFC, 0xFFC];
45
 
 
46
 
my $max_args = 4;
 
40
$pack_shift[2] = ['0', 'BEAM_LOOSE_SHIFT'];
 
41
$pack_shift[3] = ['0', 'BEAM_TIGHT_SHIFT', '(2*BEAM_TIGHT_SHIFT)'];
 
42
 
 
43
$pack_mask[2]  = ['BEAM_LOOSE_MASK', $WHOLE_WORD];
 
44
$pack_mask[3]  = ['BEAM_TIGHT_MASK', 'BEAM_TIGHT_MASK', 'BEAM_TIGHT_MASK'];
 
45
 
 
46
# Maximum number of operands for a specific instruction.
 
47
# Must be even. The beam_load.c file must be updated, too.
 
48
my $max_operands = 6;
 
49
 
47
50
my %gen_opnum;
48
51
my %num_specific;
49
52
my %gen_to_spec;
203
206
        foreach (@flags) {
204
207
            /^-/ or &error("Flags for macros should start with a hyphen");
205
208
        }
 
209
        error("Macro for '$op' is already defined")
 
210
            if defined $macro{$op};
206
211
        $macro{$op} = $macro;
207
212
        $macro_flags{$op} = join('', @flags);
208
213
        next;
259
264
    #    Name Arg1 Arg2...
260
265
    #
261
266
    my($name, @args) = split;
262
 
    &error("too many arguments")
263
 
        if @args > $max_args;
 
267
    &error("too many operands")
 
268
        if @args > $max_operands;
264
269
    &syntax_check($name, @args);
265
270
    my $arity = @args;
266
271
    push(@{$specific_op{"$name/$arity"}}, [$name, $hot, @args]);
399
404
            # instruction.
400
405
            #
401
406
 
402
 
            my(@bits) = (0, 0);
 
407
            my(@bits) = (0) x ($max_operands/2);
403
408
            my($shift) = 16;
404
409
            my($i);
405
 
            for ($i = 0; $i < 4 && defined $args[$i]; $i++) {
 
410
            for ($i = 0; $i < $max_operands && defined $args[$i]; $i++) {
406
411
                my $t = $args[$i];
407
412
                if (defined $type_bit{$t}) {
408
413
                    $bits[int($i/2)] |= $type_bit{$t} << (16*($i%2));
411
416
 
412
417
            printf "/* %3d */  ", $spec_opnum;
413
418
            my $print_name = $sign ne '' ? "${name}_$sign" : $name;
414
 
            &init_item($print_name, sprintf("{0x%X, 0x%X}", @bits),
415
 
                       $size, $pack, $sign, 0);
 
419
            my $init = "{";
 
420
            my $sep = "";
 
421
            foreach (@bits) {
 
422
                $init .= sprintf("%s0x%X", $sep, $_);
 
423
                $sep = ",";
 
424
            }
 
425
            $init .= "}";
 
426
            &init_item($print_name, $init, $size, $pack, $sign, 0);
416
427
            $op_to_name[$spec_opnum] = $instr;
417
428
            $spec_opnum++;
418
429
        }
468
479
    print "#define NUM_GENERIC_OPS ", scalar(@gen_opname), "\n";
469
480
    print "#define NUM_SPECIFIC_OPS ", scalar(@op_to_name), "\n";
470
481
    print "\n";
 
482
    print "#ifdef ARCH_64\n";
 
483
    print "#  define BEAM_LOOSE_MASK 0x1FFFUL\n";
 
484
    print "#  define BEAM_TIGHT_MASK 0x1FF8UL\n";
 
485
    print "#  define BEAM_LOOSE_SHIFT 16\n";
 
486
    print "#  define BEAM_TIGHT_SHIFT 16\n";
 
487
    print "#else\n";
 
488
    print "#  define BEAM_LOOSE_MASK 0xFFF\n";
 
489
    print "#  define BEAM_TIGHT_MASK 0xFFC\n";
 
490
    print "#  define BEAM_LOOSE_SHIFT 16\n";
 
491
    print "#  define BEAM_TIGHT_SHIFT 10\n";
 
492
    print "#endif\n";
 
493
    print "\n";
471
494
 
472
495
    #
473
496
    # Definitions of tags.
570
593
    open(STDOUT, ">$name") || die "Failed to open $name for writing: $!\n";
571
594
    &comment('C');
572
595
    &print_code(\%cold_code);
 
596
 
573
597
}
574
598
 
575
599
sub init_item {
861
885
    my($code);
862
886
    if (defined $macro{$name}) {
863
887
        my($macro_code) = "$prefix$macro(" . join(', ', @f) . ");";
864
 
        $var_decls .= "unsigned tmp_packed1;"
 
888
        $var_decls .= "Uint tmp_packed1;"
865
889
            if $macro_code =~ /tmp_packed1/;
866
 
        $var_decls .= "unsigned tmp_packed2;"
 
890
        $var_decls .= "Uint tmp_packed2;"
867
891
            if $macro_code =~ /tmp_packed2/;
868
892
        if ($flags =~ /-nonext/) {
869
893
            $code = "$macro_code\n";
978
1002
 
979
1003
    my($e) = "tmp_packed$tmpnum";
980
1004
    $e = "($e>>$shift)" if $shift;
981
 
    $e = sprintf("%s&0x%X", $e, $mask) unless $mask == $WHOLE_WORD;
 
1005
    $e .= "&$mask" unless $mask eq $WHOLE_WORD;
982
1006
    $e;
983
1007
}
984
1008
 
1093
1117
        $cond = 'is_bif';
1094
1118
        $cond_val = -1;
1095
1119
        $_ = $1;
 
1120
    } elsif (/^\$is_not_bif(.*)/) {
 
1121
        $cond = 'is_not_bif';
 
1122
        $cond_val = -1;
 
1123
        $_ = $1;
1096
1124
    } elsif (m@^\$bif:(\w+):(\w+)/(\d)(.*)@) {
1097
1125
        $cond = 'is_bif';
1098
1126
        if ($1 eq 'erlang') {
1167
1195
        }
1168
1196
        print "\n";
1169
1197
    }
 
1198
    print "/*\n";
 
1199
    print " * Total number of words: $offset\n";
 
1200
    print " */\n";
1170
1201
    print "};\n\n";
1171
1202
}
1172
1203
 
1250
1281
                    push(@code, &make_op($var, 'set_var', $var{$var}));
1251
1282
                }
1252
1283
            }
1253
 
            push(@code, &make_op('', 'next_arg'));
 
1284
            if (is_set_var_instr($code[$#code])) {
 
1285
                my $ref = pop @code;
 
1286
                my $comment = $ref->[2];
 
1287
                my $var = $ref->[1][1];
 
1288
                push(@code, make_op($comment, 'set_var_next_arg', $var));
 
1289
            } else {
 
1290
                push(@code, &make_op('', 'next_arg'));
 
1291
            }
1254
1292
        }
1255
1293
        push(@code, &make_op('', 'next_instr'));
1256
1294
        pop(@code) if $code[$#code]->[1][0] eq 'next_arg';
1400
1438
    [scalar(@op), [@op], $comment];
1401
1439
}
1402
1440
 
 
1441
sub is_set_var_instr {
 
1442
    my($ref) = @_;
 
1443
    return 0 unless ref($ref) eq 'ARRAY';
 
1444
    $ref->[1][0] eq 'set_var';
 
1445
}
 
1446
 
1403
1447
sub tr_gen_call {
1404
1448
    my(@call_table) = @_;
1405
1449
    my($i);