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

« back to all changes in this revision

Viewing changes to erts/emulator/beam/ops.tab

  • 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:
23
23
# instruction transformations; thus, they never occur in BEAM files.
24
24
#
25
25
 
 
26
# Special instruction used to generate an error message when
 
27
# trying to load a module compiled by the V1 compiler (R5 & R6).
 
28
# (Specially treated in beam_load.c.)
 
29
 
 
30
too_old_compiler/0
 
31
too_old_compiler
 
32
 
 
33
#
 
34
# Obsolete instructions follow.
 
35
#
 
36
 
 
37
is_list p S => too_old_compiler
 
38
is_nonempty_list p R => too_old_compiler
 
39
is_nil p R => too_old_compiler
 
40
 
 
41
is_tuple p S => too_old_compiler
 
42
test_arity p S Arity => too_old_compiler
 
43
 
 
44
is_integer p R => too_old_compiler
 
45
is_float p R => too_old_compiler
 
46
is_atom p R => too_old_compiler
 
47
 
 
48
is_eq_exact p S1 S2 => too_old_compiler
 
49
 
 
50
#
 
51
# All the other instructions.
 
52
#
 
53
 
26
54
label L
27
55
i_func_info I a a I
28
56
int_code_end
35
63
i_count_breakpoint
36
64
i_return_to_trace
37
65
i_yield
 
66
i_global_cons
 
67
i_global_tuple
 
68
i_global_copy
38
69
 
39
70
return
40
71
 
234
265
 
235
266
# Receive operations.
236
267
 
237
 
wait_timeout Fail Src=iw => gen_literal_timeout(Fail, Src)
238
 
wait_timeout Fail Src=o => i_put_float Src x | wait_timeout Fail x
 
268
loop_rec Fail Src | smp_mark_target_label(Fail) => i_loop_rec Fail Src
 
269
 
 
270
label L | wait_timeout Fail Src | smp_already_locked(L) => label L | i_wait_timeout_locked Fail Src
 
271
wait_timeout Fail Src => i_wait_timeout Fail Src
 
272
i_wait_timeout Fail Src=aiow => gen_literal_timeout(Fail, Src)
 
273
i_wait_timeout_locked Fail Src=aiow => gen_literal_timeout_locked(Fail, Src)
 
274
 
 
275
label L | wait Fail | smp_already_locked(L) => label L | wait_locked Fail
 
276
wait Fail | smp() => wait_unlocked Fail
 
277
 
 
278
label L | timeout | smp_already_locked(L) => label L | timeout_locked
239
279
 
240
280
remove_message
241
281
timeout
242
 
loop_rec f r
243
 
loop_rec f x
 
282
timeout_locked
 
283
i_loop_rec f r
244
284
loop_rec_end f
245
285
wait f
246
 
wait_timeout f I
247
 
wait_timeout f s
 
286
wait_locked f
 
287
wait_unlocked f
 
288
i_wait_timeout f I
 
289
i_wait_timeout f s
 
290
i_wait_timeout_locked f I
 
291
i_wait_timeout_locked f s
248
292
i_wait_error
249
 
 
250
 
#
251
 
# Arithmethic operations.
252
 
#
253
 
m_times Lbl S1 S2=i==1 D => m_plus Lbl S1 i D
254
 
m_times Lbl S1 S2=i==2 D => m_plus Lbl S1 S1 D
255
 
 
256
 
m_plus   Lbl S1 S2 D => i_fetch S1 S2 | i_plus Lbl D
257
 
m_minus  Lbl S1 S2 D => i_fetch S1 S2 | i_minus Lbl D
258
 
m_times  Lbl S1 S2 D => i_fetch S1 S2 | i_times Lbl D
259
 
m_div    Lbl S1 S2 D => i_fetch S1 S2 | i_m_div Lbl D
260
 
int_div  Lbl S1 S2 D => i_fetch S1 S2 | i_int_div Lbl D
261
 
int_rem  Lbl S1 S2 D => i_fetch S1 S2 | i_rem Lbl D
262
 
int_band Lbl S1 S2 D => i_fetch S1 S2 | i_band Lbl D
263
 
int_bor  Lbl S1 S2 D => i_fetch S1 S2 | i_bor Lbl D
264
 
int_bxor Lbl S1 S2 D => i_fetch S1 S2 | i_bxor Lbl D
265
 
int_bsl  Lbl S1 S2 D => i_fetch S1 S2 | i_bsl Lbl D
266
 
int_bsr  Lbl S1 S2 D => i_fetch S1 S2 | i_bsr Lbl D
 
293
i_wait_error_locked
 
294
 
 
295
 
 
296
#
 
297
# Fetch operations (used for arithmetic instructions).
 
298
#
267
299
 
268
300
i_fetch S1=w S2=w => i_fetch r r  | i_fetch_big1 S1 | i_fetch_big2 S2
269
301
i_fetch S1=w S2   => i_fetch r S2 | i_fetch_big1 S1
273
305
i_fetch S1=o S2   => i_fetch r S2 | i_fetch_float1 S1
274
306
i_fetch S1 S2=o   => i_fetch S1 r | i_fetch_float2 S2
275
307
 
276
 
i_plus j d
277
 
i_minus j d
278
 
i_times j d
279
 
i_m_div j d
280
 
i_int_div j d
281
 
i_rem j d
282
 
i_band j d
283
 
i_bor j d
284
 
i_bxor j d
285
 
i_bsl j d
286
 
i_bsr j d
287
 
 
288
 
int_bnot j s d
289
 
 
290
308
send
291
309
 
292
310
#
303
321
is_ne Lbl S1 S2 => i_fetch S1 S2 | i_is_ne Lbl
304
322
 
305
323
is_eq_exact Lbl=f S1 S2 => i_fetch S1 S2 | i_is_eq_exact Lbl
306
 
is_eq_exact p S1 S2 => i_fetch S1 S2 | is_eq_exact_body
307
324
is_ne_exact Lbl S1 S2 => i_fetch S1 S2 | i_is_ne_exact Lbl
308
325
 
309
326
i_is_lt f
313
330
i_is_eq_exact f
314
331
i_is_ne_exact f
315
332
 
316
 
is_eq_exact_body
317
 
 
318
333
%macro: i_is_eq_const Equal -fail_action
319
334
i_is_eq_const f r c
320
335
i_is_eq_const f x c
477
492
is_tuple_of_arity f y A
478
493
is_tuple_of_arity f r A
479
494
 
480
 
is_tuple p S=rxy | test_arity p S=rxy Arity => is_tuple_of_arity_body S Arity
481
 
test_arity p S Arity => test_arity_body S Arity
482
 
 
483
 
%macro:is_tuple_of_arity_body IsTupleOfArity -fail_action
484
 
is_tuple_of_arity_body r A
485
 
is_tuple_of_arity_body x A
486
 
is_tuple_of_arity_body y A
487
 
 
488
495
%macro: is_tuple IsTuple -fail_action
489
496
is_tuple f x
490
497
is_tuple f y
491
498
is_tuple f r
492
499
 
493
 
is_tuple p R => is_tuple_body R
494
 
 
495
 
%macro: is_tuple_body IsTuple -fail_action
496
 
is_tuple_body r
497
 
is_tuple_body x
498
 
is_tuple_body y
499
 
 
500
500
test_arity Fail=f cwo Arity => jump Fail
501
501
 
502
502
%macro: test_arity IsArity -fail_action
504
504
test_arity f y A
505
505
test_arity f r A
506
506
 
507
 
%macro: test_arity_body IsArity -fail_action
508
 
%cold
509
 
test_arity_body x A
510
 
test_arity_body y A
511
 
test_arity_body r A
512
 
%hot
513
 
 
514
507
is_tuple_of_arity Fail=f Reg Arity | get_tuple_element Reg P=u==0 Dst=xy => \
515
508
  is_tuple_of_arity Fail Reg Arity | extract_next_element Dst | original_reg Reg P
516
509
 
570
563
is_integer f y
571
564
is_integer f r
572
565
 
573
 
is_integer p R => is_integer_body R
574
 
 
575
 
%macro: is_integer_body IsInteger -fail_action
576
 
%cold
577
 
is_integer_body r
578
 
is_integer_body x
579
 
is_integer_body y
580
 
%hot
581
 
 
582
566
is_list Fail=f n =>
583
567
is_list Fail=f cow => jump Fail
584
568
%macro: is_list IsList -fail_action
604
588
is_nonempty_list f y
605
589
is_nonempty_list f r
606
590
 
607
 
is_nonempty_list p R => is_nonempty_list_body R
608
 
 
609
 
%macro: is_nonempty_list_body IsNonemptyList -fail_action
610
 
is_nonempty_list_body x
611
 
is_nonempty_list_body y
612
 
is_nonempty_list_body r
613
 
 
614
 
is_nil p R => is_nil_body R
615
 
 
616
591
%macro: is_atom IsAtom -fail_action
617
592
is_atom f x
618
593
is_atom f r
631
606
is_float Fail=f nwai => jump Fail
632
607
is_float Fail=f o =>
633
608
 
634
 
is_float p R => is_float_body R
635
 
 
636
 
%macro: is_float_body IsFloat -fail_action
637
 
%cold
638
 
is_float_body r
639
 
is_float_body x
640
 
is_float_body y
641
 
%hot
642
 
 
643
609
is_nil Fail=f n =>
644
610
is_nil Fail=f owia => jump Fail
645
611
 
646
 
%macro: is_nil_body IsNil -fail_action
647
 
%cold
648
 
is_nil_body r
649
 
is_nil_body x
650
 
is_nil_body y
651
 
%hot
652
 
 
653
612
%macro: is_nil IsNil -fail_action
654
613
is_nil f x
655
614
is_nil f y
663
622
is_binary f y
664
623
%hot
665
624
 
666
 
is_ref Fail=f cwo => jump Fail
667
 
%macro: is_ref IsRef -fail_action
668
 
is_ref f r
669
 
is_ref f x
 
625
is_reference Fail=f cwo => jump Fail
 
626
%macro: is_reference IsRef -fail_action
 
627
is_reference f r
 
628
is_reference f x
670
629
%cold
671
 
is_ref f y
 
630
is_reference f y
672
631
%hot
673
632
 
674
633
is_pid Fail=f cwo => jump Fail
687
646
is_port f y
688
647
%hot
689
648
 
 
649
is_boolean Fail=f a==am_true =>
 
650
is_boolean Fail=f a==am_false =>
 
651
is_boolean Fail=f acwo => jump Fail
 
652
 
 
653
%cold
 
654
%macro: is_boolean IsBoolean -fail_action
 
655
is_boolean f r
 
656
is_boolean f x
 
657
is_boolean f y
 
658
%hot
 
659
 
 
660
is_function2 Fail=f acwo Arity => jump Fail
 
661
is_function2 Fail=f Fun awo => jump Fail
 
662
 
 
663
is_function2 f s s
 
664
%macro: is_function2 IsFunction2 -fail_action
 
665
 
690
666
# Allocating & initializing.
691
667
allocate Need Regs | init Y => allocate_init Need Regs Y
692
668
init Y1 | init Y2 => init2 Y1 Y2
694
670
%macro: allocate_init AllocateInit -pack
695
671
allocate_init t I y
696
672
 
697
 
%macro: init2 Init2 -pack
698
 
init2 y y
699
 
 
700
673
#################################################################
701
674
# External function and bif calls.
702
675
#################################################################
726
699
call_ext_only u==1 Bif=u$bif:erlang:garbage_collect/1 => i_call_ext_only Bif
727
700
 
728
701
#
729
 
# The BIF vector:set/3 must be called like a function,
730
 
# to allow it to invoke the garbage collector.
731
 
#
732
 
 
733
 
call_ext u==3 Bif=u$bif:vector:set/3 => i_call_ext Bif
734
 
call_ext_last u==3 Bif=u$bif:vector:set/3 D => i_call_ext_last Bif D
735
 
call_ext_only u==3 Bif=u$bif:vector:set/3 => i_call_ext_only Bif
736
 
 
737
 
#
738
702
# The process_info/1,2 BIF should be called like a function, to force
739
703
# the emulator to set c_p->current before calling it (a BIF call doesn't
740
704
# set it).
775
739
call_ext_only u==1 Bif=u$bif:erlang:throw/1 => call_bif1 Bif
776
740
 
777
741
#
778
 
# The fault/1 and fault/2 BIFs never execute the instruction following them;
 
742
# The error/1 and error/2 BIFs (and their old aliases fault/1 and
 
743
# fault/2) never execute the instruction following them;
779
744
# thus there is no need to generate any return instruction.
780
745
# However, they generate stack backtraces, so if the call instruction
781
746
# is call_ext_only/2 instruction, we explicitly do an allocate/2 to store
782
747
# the continuation pointer on the stack.
783
748
#
784
749
 
 
750
call_ext_last u==1 Bif=u$bif:erlang:error/1 D => call_bif1 Bif
785
751
call_ext_last u==1 Bif=u$bif:erlang:fault/1 D => call_bif1 Bif
 
752
call_ext_last u==2 Bif=u$bif:erlang:error/2 D => call_bif2 Bif
786
753
call_ext_last u==2 Bif=u$bif:erlang:fault/2 D => call_bif2 Bif
787
754
 
 
755
call_ext_only Ar=u==1 Bif=u$bif:erlang:error/1 => \
 
756
  allocate u Ar | call_bif1 Bif
788
757
call_ext_only Ar=u==1 Bif=u$bif:erlang:fault/1 => \
789
758
  allocate u Ar | call_bif1 Bif
 
759
call_ext_only Ar=u==2 Bif=u$bif:erlang:error/2 => \
 
760
  allocate u Ar | call_bif2 Bif
790
761
call_ext_only Ar=u==2 Bif=u$bif:erlang:fault/2 => \
791
762
  allocate u Ar | call_bif2 Bif
792
763
 
806
777
call_ext_only u==3 u$func:erlang:hibernate/3 => i_hibernate
807
778
 
808
779
#
 
780
# Hybrid memory architecture need special cons and tuple instructions
 
781
# that allocate on the message area. These looks like BIFs in the BEAM code.
 
782
#
 
783
 
 
784
call_ext u==2 u$func:hybrid:cons/2 => i_global_cons
 
785
call_ext_last u==2 u$func:hybrid:cons/2 D => i_global_cons | deallocate_return D
 
786
call_ext_only Ar=u==2 u$func:hybrid:cons/2 => i_global_cons | return
 
787
 
 
788
call_ext u==1 u$func:hybrid:tuple/1 => i_global_tuple
 
789
call_ext_last u==1 u$func:hybrid:tuple/1 D => i_global_tuple | deallocate_return D
 
790
call_ext_only Ar=u==1 u$func:hybrid:tuple/1 => i_global_tuple | return
 
791
 
 
792
call_ext u==1 u$func:hybrid:copy/1 => i_global_copy
 
793
call_ext_last u==1 u$func:hybrid:copy/1 D => i_global_copy | deallocate_return D
 
794
call_ext_only u==1 Ar=u$func:hybrid:copy/1 => i_global_copy | return
 
795
 
 
796
#
809
797
# The general case for BIFs that have no special instructions.
810
798
# A BIF used in the tail must be followed by a return instruction.
811
799
#
831
819
  allocate u Ar | call_bif3 Bif | deallocate_return u
832
820
 
833
821
#
834
 
# Any remaining calls are called to Erlang functions, not BIFs.
835
 
# We change to instructions to internal names.  This is necessary,
 
822
# Any remaining calls are calls to Erlang functions, not BIFs.
 
823
# We rename the instructions to internal names.  This is necessary,
836
824
# to avoid an end-less loop, because we want to call a few BIFs
837
825
# with call instructions.
838
826
#
839
827
 
 
828
move S=c r | call_ext Ar=u Func=u$is_not_bif => i_move_call_ext S r Func
 
829
move S=c r | call_ext_last Ar=u Func=u$is_not_bif D => i_move_call_ext_last Func D S r
 
830
move S=c r | call_ext_only Ar=u Func=u$is_not_bif => i_move_call_ext_only Func S r 
 
831
 
840
832
call_ext Ar=u Func        => i_call_ext Func
841
833
call_ext_last Ar=u Func D => i_call_ext_last Func D
842
834
call_ext_only Ar=u Func   => i_call_ext_only Func
860
852
# Calls to non-building and guard BIFs.
861
853
#
862
854
 
863
 
bif0 Bif=u$bif:erlang:self/0 Dst=d => self Dst
864
 
bif0 Bif=u$bif:erlang:node/0 Dst=d => node Dst
 
855
bif0 u$bif:erlang:self/0 Dst=d => self Dst
 
856
bif0 u$bif:erlang:node/0 Dst=d => node Dst
 
857
 
 
858
bif1 Fail Bif=u$bif:erlang:get/1 Src=s Dst=d => i_get Src Dst
865
859
 
866
860
bif2 Jump=j u$bif:erlang:element/2 S1=ow S2=ow Dst=d => badarg Jump
867
861
bif2 Jump=j u$bif:erlang:element/2 S1=ow S2=s Dst=d => badarg Jump
875
869
bif2 p Bif S1 S2 Dst => i_fetch S1 S2 | i_bif2_body Bif Dst
876
870
bif2 Fail=f Bif S1 S2 Dst => i_fetch S1 S2 | i_bif2 Fail Bif Dst
877
871
 
 
872
i_get s d
 
873
 
878
874
%macro: self Self
879
875
self r
880
876
self x
899
895
# Internal calls.
900
896
#
901
897
 
 
898
move S=c r | call Ar P=f => i_move_call S r P
902
899
move S=s r | call Ar P=f => move_call S r P
903
900
 
 
901
i_move_call c r f
 
902
 
904
903
%macro:move_call MoveCall -arg_f -size -nonext
905
 
 
906
904
move_call/3
 
905
 
907
906
move_call x r f
908
907
move_call y r f
909
 
move_call n r f
910
 
move_call c r f
911
908
 
 
909
move S=c r | call_last Ar P=f D => i_move_call_last P D S r
912
910
move S r | call_last Ar P=f D => move_call_last S r P D
913
911
 
 
912
i_move_call_last f P c r
 
913
 
914
914
%macro:move_call_last MoveCallLast -arg_f -nonext
915
915
 
916
916
move_call_last/4
917
917
move_call_last x r f P
918
918
move_call_last y r f P
919
 
move_call_last c r f P
920
 
move_call_last n r f P
 
919
 
 
920
move S=c r | call_only Ar P=f => i_move_call_only P S r
 
921
move S=x r | call_only Ar P=f => move_call_only S r P
 
922
 
 
923
i_move_call_only f c r
 
924
 
 
925
%macro:move_call_only MoveCallOnly -arg_f -nonext
 
926
move_call_only/3
 
927
 
 
928
move_call_only x r f
921
929
 
922
930
call Ar Func        => i_call Func
923
931
call_last Ar Func D => i_call_last Func D
931
939
i_call_ext_last e P
932
940
i_call_ext_only e
933
941
 
 
942
i_move_call_ext c r e
 
943
i_move_call_ext_last e P c r
 
944
i_move_call_ext_only e c r
 
945
 
934
946
# Fun calls.
935
947
 
936
948
call_fun Arity=u | deallocate D | return => i_call_fun_last Arity D
939
951
i_call_fun I
940
952
i_call_fun_last I P
941
953
 
942
 
make_fun Lbl=f Uniq=u NumFree=u => gen_make_fun(Lbl, Uniq, NumFree)
943
954
make_fun2 OldIndex=u => gen_make_fun2(OldIndex)
944
955
 
945
956
%macro: i_make_fun MakeFun -pack
953
964
is_function f r
954
965
is_function Fail=f cwo => jump Fail
955
966
 
 
967
func_info M=a a==am_module_info A=u==0 | label L | move n r => gen_func_info_mi(M, A, L)
 
968
func_info M=a a==am_module_info A=u==1 | label L | move n r => gen_func_info_mi(M, A, L)
956
969
func_info M=a F=a A=u | label L => gen_func_info(M, F, A, L)
957
970
 
958
 
#
959
 
# Matching binaries: Getting started.
960
 
#
 
971
# ================================================================
 
972
# New bit syntax matching (R11B).
 
973
# ================================================================
 
974
 
961
975
%cold
962
 
%macro: bs_start_match BsStartMatch -fail_action
963
 
bs_start_match f x
964
 
bs_start_match f y
965
 
bs_start_match f r
966
 
bs_start_match Fail=f icwoa => jump Fail
967
 
 
968
 
bs_save I
969
 
bs_restore I
970
 
 
971
 
#
972
 
# Fetching integers from binaries.
973
 
#
974
 
bs_get_integer Fail=f Sz=s Unit=u Flags=u Dst=d => \
975
 
                        gen_get_integer(Fail, Sz, Unit, Flags, Dst)
976
 
%macro: i_bs_get_integer_imm BsGetIntegerImm -fail_action -gen_dest
977
 
%macro: i_bs_get_integer BsGetInteger -fail_action -gen_dest
978
 
%macro: i_bs_get_integer8 BsGetInteger8 -fail_action -gen_dest
979
 
%macro: i_bs_get_integer16 BsGetInteger16 -fail_action -gen_dest
980
 
%macro: i_bs_get_integer32 BsGetInteger32 -fail_action -gen_dest
981
 
i_bs_get_integer_imm f I I d
982
 
i_bs_get_integer f s I d
983
 
i_bs_get_integer8 f d
984
 
i_bs_get_integer16 f d
985
 
i_bs_get_integer32 f d
986
 
 
987
 
#
988
 
# Fetching integers from binaries.
989
 
#
990
 
bs_get_binary Fail=f Sz=s Unit=u Flags=u Dst=d => \
991
 
                        gen_get_binary(Fail, Sz, Unit, Flags, Dst)
992
 
%macro: i_bs_get_binary_imm BsGetBinaryImm -fail_action -gen_dest
993
 
%macro: i_bs_get_binary BsGetBinary -fail_action -gen_dest
994
 
%macro: i_bs_get_binary_all BsGetBinaryAll -fail_action -gen_dest
995
 
i_bs_get_binary_imm f I I d
996
 
i_bs_get_binary f s I d
997
 
i_bs_get_binary_all f d
998
 
 
999
 
#
1000
 
# Fetching floats from binaries.
1001
 
#
1002
 
bs_get_float Fail=f Sz=s Unit=u Flags=u Dst=d => \
1003
 
                        gen_get_float(Fail, Sz, Unit, Flags, Dst)
1004
 
 
1005
 
%macro: i_bs_get_float BsGetFloat -fail_action -gen_dest
1006
 
i_bs_get_float f s I d
1007
 
 
1008
 
#
1009
 
# Skipping uninteresting bits.
1010
 
#
1011
 
bs_skip_bits Fail=f Sz=s Unit=u Flags=u => gen_skip_bits(Fail, Sz, Unit, Flags)
1012
 
 
1013
 
%macro: i_bs_skip_bits_imm BsSkipBitsImm -fail_action
1014
 
i_bs_skip_bits_imm f I
1015
 
 
1016
 
%macro: i_bs_skip_bits BsSkipBits -fail_action
1017
 
i_bs_skip_bits f x I
1018
 
i_bs_skip_bits f r I
1019
 
i_bs_skip_bits f y I
1020
 
 
1021
 
%macro: i_bs_skip_bits_all BsSkipBitsAll -fail_action
1022
 
i_bs_skip_bits_all f
1023
 
 
1024
 
%macro: i_bs_skip_bits_all_aligned BsSkipBitsAllAligned -fail_action
1025
 
i_bs_skip_bits_all_aligned
1026
 
 
1027
 
#
1028
 
# Testing the tail.
1029
 
#
1030
 
bs_test_tail Fail=f Bits=u==0 => bs_test_zero_tail Fail
1031
 
bs_test_tail Fail=f Bits=u => bs_test_tail_imm Fail Bits
1032
 
bs_test_zero_tail f
1033
 
bs_test_tail_imm f I
1034
 
 
1035
 
#
1036
 
# Some optimisations.
1037
 
#
1038
 
i_bs_get_binary_all Fail Dst | bs_test_tail f u==0 => i_bs_get_binary_all Fail Dst
1039
 
i_bs_skip_bits_all_aligned | bs_test_tail f u==0 =>
1040
 
i_bs_skip_bits_all Fail | bs_test_tail f u==0 => i_bs_skip_bits_all Fail
 
976
%macro: bs_start_match2 BsStartMatch2 -fail_action -gen_dest
 
977
bs_start_match2 f r I I d
 
978
bs_start_match2 f x I I d
 
979
bs_start_match2 f y I I d
 
980
bs_start_match2 Fail=f icwoa X Y D => jump Fail
 
981
 
 
982
bs_save2 r I
 
983
bs_save2 x I
 
984
bs_restore2 r I
 
985
bs_restore2 x I
 
986
 
 
987
# Fetching integers from binaries.
 
988
bs_get_integer2 Fail=f Ms=rx Live=u Sz=s Unit=u Flags=u Dst=d => \
 
989
                        gen_get_integer2(Fail, Ms, Live, Sz, Unit, Flags, Dst)
 
990
%macro: i_bs_get_integer_imm2 BsGetIntegerImm2 -fail_action -gen_dest
 
991
%macro: i_bs_get_integer2 BsGetInteger2 -fail_action -gen_dest
 
992
%macro: i_bs_get_integer2_8 BsGetInteger2_8 -fail_action -gen_dest
 
993
%macro: i_bs_get_integer2_16 BsGetInteger2_16 -fail_action -gen_dest
 
994
%macro: i_bs_get_integer2_32 BsGetInteger2_32 -fail_action -gen_dest
 
995
i_bs_get_integer_imm2 f r I I I d
 
996
i_bs_get_integer_imm2 f x I I I d
 
997
i_bs_get_integer2 f r I s I d
 
998
i_bs_get_integer2 f x I s I d
 
999
i_bs_get_integer2_8 f r d
 
1000
i_bs_get_integer2_8 f x d
 
1001
i_bs_get_integer2_16 f r d
 
1002
i_bs_get_integer2_16 f x d
 
1003
i_bs_get_integer2_32 f r I d
 
1004
i_bs_get_integer2_32 f x I d
 
1005
 
 
1006
# Fetching binaries from binaries.
 
1007
bs_get_binary2 Fail=f Ms=rx Live=u Sz=s Unit=u Flags=u Dst=d => \
 
1008
                        gen_get_binary2(Fail, Ms, Live, Sz, Unit, Flags, Dst)
 
1009
%macro: i_bs_get_binary_imm2 BsGetBinaryImm_2 -fail_action -gen_dest
 
1010
%macro: i_bs_get_binary2 BsGetBinary_2 -fail_action -gen_dest
 
1011
%macro: i_bs_get_binary_all2 BsGetBinaryAll_2 -fail_action -gen_dest
 
1012
i_bs_get_binary_imm2 f r I I I d
 
1013
i_bs_get_binary_imm2 f x I I I d
 
1014
i_bs_get_binary2 f r I s I d
 
1015
i_bs_get_binary2 f x I s I d
 
1016
i_bs_get_binary_all2 f r I I d
 
1017
i_bs_get_binary_all2 f x I I d
 
1018
 
 
1019
# Fetching float from binaries.
 
1020
bs_get_float2 Fail=f Ms=rx Live=u Sz=s Unit=u Flags=u Dst=d => \
 
1021
                gen_get_float2(Fail, Ms, Live, Sz, Unit, Flags, Dst)
 
1022
 
 
1023
%macro: i_bs_get_float2 BsGetFloat2 -fail_action -gen_dest
 
1024
i_bs_get_float2 f r I s I d
 
1025
i_bs_get_float2 f x I s I d
 
1026
 
 
1027
# Miscellanous
 
1028
 
 
1029
bs_skip_bits2 Fail=f Ms=rx Sz=s Unit=u Flags=u => \
 
1030
                        gen_skip_bits2(Fail, Ms, Sz, Unit, Flags)
 
1031
 
 
1032
%macro: i_bs_skip_bits_imm2 BsSkipBitsImm2 -fail_action
 
1033
i_bs_skip_bits_imm2 f r I
 
1034
i_bs_skip_bits_imm2 f x I
 
1035
 
 
1036
%macro: i_bs_skip_bits2 BsSkipBits2 -fail_action
 
1037
i_bs_skip_bits2 f r x I
 
1038
i_bs_skip_bits2 f r r I
 
1039
i_bs_skip_bits2 f r y I
 
1040
i_bs_skip_bits2 f x x I
 
1041
i_bs_skip_bits2 f x r I
 
1042
i_bs_skip_bits2 f x y I
 
1043
 
 
1044
%macro: i_bs_skip_bits_all2 BsSkipBitsAll2 -fail_action
 
1045
i_bs_skip_bits_all2 f r I
 
1046
i_bs_skip_bits_all2 f x I 
 
1047
 
 
1048
bs_test_tail2 Fail=f Ms=rx Bits=u==0 => bs_test_zero_tail2 Fail Ms
 
1049
bs_test_tail2 Fail=f Ms=rx Bits=u => bs_test_tail_imm2 Fail Ms Bits
 
1050
bs_test_zero_tail2 f r
 
1051
bs_test_zero_tail2 f x
 
1052
bs_test_tail_imm2 f r I
 
1053
bs_test_tail_imm2 f x I
 
1054
 
 
1055
 
 
1056
%hot
1041
1057
 
1042
1058
#
1043
1059
# Constructing binaries
1044
1060
#
1045
1061
%cold
1046
1062
 
1047
 
bs_init Size Flags=u | bs_need_buf Bits=u | assign_heap_bin_flag(Flags, Bits) => \
1048
 
        i_bs_init
1049
 
bs_init Size Flags | reset_heap_bin_flag() => i_bs_init
1050
 
bs_need_buf Bits =>
1051
 
 
1052
 
bs_final Fail Dst | generate_heap_bin() => i_bs_final_heap Dst
1053
 
bs_final Fail Dst => i_bs_final Fail Dst
1054
 
 
1055
 
i_bs_init
1056
 
i_bs_final_heap d
1057
 
i_bs_final j d
 
1063
bs_init2 Fail Sz=u Words=u==0 Regs Flags Dst | should_gen_heap_bin(Sz) | new_bs_instructions() => i_bs_init_heap_bin Sz Regs Dst
 
1064
bs_init2 Fail Sz=u Words=u==0 Regs Flags Dst | new_bs_instructions() => i_bs_init Sz Regs Dst
 
1065
 
 
1066
bs_init2 Fail Sz=u Words Regs Flags Dst | should_gen_heap_bin(Sz) | new_bs_instructions() => i_bs_init_heap_bin_heap Sz Words Regs Dst
 
1067
bs_init2 Fail Sz=u Words Regs Flags Dst | new_bs_instructions() => \
 
1068
   i_bs_init_heap Sz Words Regs Dst
 
1069
 
 
1070
bs_init2 Fail Sz Words=u==0 Regs Flags Dst | new_bs_instructions() => \
 
1071
  i_bs_init_fail Sz Fail Regs Dst
 
1072
bs_init2 Fail Sz Words Regs Flags Dst | new_bs_instructions() => \
 
1073
  i_fetch Sz r | i_bs_init_fail_heap Words Fail Regs Dst
 
1074
 
 
1075
i_bs_init_fail r j I d
 
1076
i_bs_init_fail x j I d
 
1077
i_bs_init_fail y j I d
 
1078
 
 
1079
i_bs_init_fail_heap I j I d
 
1080
 
 
1081
i_bs_init I I d
 
1082
i_bs_init_heap_bin I I d
 
1083
 
 
1084
i_bs_init_heap I I I d
 
1085
i_bs_init_heap_bin_heap I I I d
 
1086
 
 
1087
bs_bits_to_bytes Fail Src Dst => i_bs_bits_to_bytes Src Fail Dst
 
1088
 
 
1089
i_bs_bits_to_bytes r j d
 
1090
i_bs_bits_to_bytes x j d
 
1091
i_bs_bits_to_bytes y j d
 
1092
 
 
1093
bs_bits_to_bytes2 Src Dst => i_bs_bits_to_bytes2 Src Dst
 
1094
 
 
1095
i_bs_bits_to_bytes2 r d
 
1096
i_bs_bits_to_bytes2 x d
 
1097
i_bs_bits_to_bytes2 y d
 
1098
 
 
1099
bs_final2 Src Dst => i_bs_final2 Src Dst
 
1100
 
 
1101
i_bs_final2 r d
 
1102
i_bs_final2 x d
 
1103
i_bs_final2 y d
 
1104
 
 
1105
bs_add Fail S1 S2 Unit D => i_fetch S1 S2 | i_bs_add Fail Unit D
 
1106
 
 
1107
i_bs_add j I d
1058
1108
 
1059
1109
#
1060
1110
# Storing integers into binaries.
1066
1116
bs_put_integer Fail=j Sz=s Unit=u Flags=u Src=s => \
1067
1117
                        gen_put_integer(Fail, Sz, Unit, Flags, Src)
1068
1118
 
1069
 
%macro: i_bs_put_integer BsPutInteger
1070
 
%macro: i_bs_put_integer_imm BsPutIntegerImm
 
1119
%macro: i_new_bs_put_integer NewBsPutInteger
 
1120
%macro: i_new_bs_put_integer_imm NewBsPutIntegerImm
1071
1121
 
1072
 
i_bs_put_integer j s I s
1073
 
i_bs_put_integer_imm j I I s
 
1122
i_new_bs_put_integer j s I s
 
1123
i_new_bs_put_integer_imm j I I s
1074
1124
 
1075
1125
#
1076
1126
# Storing floats into binaries.
1084
1134
 
1085
1135
bs_put_float Fail=j Sz=s Unit=u Flags=u Src=s => \
1086
1136
                        gen_put_float(Fail, Sz, Unit, Flags, Src)
1087
 
i_bs_put_float j s I s
1088
 
i_bs_put_float_imm j I I s
1089
 
 
1090
 
%macro: i_bs_put_float BsPutFloat
1091
 
%macro: i_bs_put_float_imm BsPutFloatImm
 
1137
 
 
1138
%macro: i_new_bs_put_float NewBsPutFloat
 
1139
%macro: i_new_bs_put_float_imm NewBsPutFloatImm
 
1140
 
 
1141
i_new_bs_put_float j s I s
 
1142
i_new_bs_put_float_imm j I I s
1092
1143
 
1093
1144
#
1094
1145
# Storing binaries into binaries.
1098
1149
bs_put_binary Fail=j Sz=s Unit=u Flags=u Src=s => \
1099
1150
                        gen_put_binary(Fail, Sz, Unit, Flags, Src)
1100
1151
 
1101
 
%macro: i_bs_put_binary BsPutBinary
1102
 
i_bs_put_binary j s I s
1103
 
 
1104
 
%macro: i_bs_put_binary_imm BsPutBinaryImm
1105
 
i_bs_put_binary_imm j I s
1106
 
 
1107
 
%macro: i_bs_put_binary_all BsPutBinaryAll
1108
 
i_bs_put_binary_all j s
 
1152
%macro: i_new_bs_put_binary NewBsPutBinary
 
1153
i_new_bs_put_binary j s I s
 
1154
 
 
1155
%macro: i_new_bs_put_binary_imm NewBsPutBinaryImm
 
1156
i_new_bs_put_binary_imm j I s
 
1157
 
 
1158
%macro: i_new_bs_put_binary_all NewBsPutBinaryAll
 
1159
i_new_bs_put_binary_all j s
1109
1160
 
1110
1161
#
1111
 
# Warning: The bs_put_string instruction is specially treated in the loader.
 
1162
# Warning: The i_bs_put_string and i_new_bs_put_string instructions
 
1163
# are specially treated in the loader.
1112
1164
# Don't change the instruction format unless you change the loader too.
1113
1165
#
1114
 
bs_put_string I I
 
1166
 
 
1167
bs_put_string Len String | query_new_instructions() => i_new_bs_put_string Len String
 
1168
 
 
1169
i_new_bs_put_string I I
1115
1170
 
1116
1171
%hot
1117
1172
 
1131
1186
 
1132
1187
fmove o l
1133
1188
fmove d l
1134
 
fmove l d
1135
1189
fconv d l
1136
1190
 
1137
1191
i_fadd l l l
1146
1200
 
1147
1201
i_fcheckerror
1148
1202
fclearerror
 
1203
 
 
1204
fmove FR=l Dst=d | new_float_allocation() => fmove_new FR Dst
 
1205
 
 
1206
# The new instruction for moving a float out of a floating point register.
 
1207
# (No allocation.)
 
1208
fmove_new l d
 
1209
 
 
1210
#
 
1211
# New apply instructions in R10B.
 
1212
#
 
1213
 
 
1214
apply I
 
1215
apply_last I P