type check optimization is here

cvs
Slava Pestov 2004-12-31 07:17:45 +00:00
parent 80b4d13a54
commit 6159c82407
20 changed files with 145 additions and 95 deletions

View File

@ -5,13 +5,8 @@
[error] AWT-EventQueue-0: at factor.jedit.WordPreview.actionPerformed(WordPreview.java:79) [error] AWT-EventQueue-0: at factor.jedit.WordPreview.actionPerformed(WordPreview.java:79)
[error] AWT-EventQueue-0: at javax.swing.Timer.fireActionPerformed(Timer.java:271) [error] AWT-EventQueue-0: at javax.swing.Timer.fireActionPerformed(Timer.java:271)
+ inference/dataflow:
- type inference
+ compiler: + compiler:
- slot compilation
- optimize away dispatch - optimize away dispatch
- getenv/setenv: if literal arg, compile as a load/store - getenv/setenv: if literal arg, compile as a load/store
- assembler opcodes dispatch on operand types - assembler opcodes dispatch on operand types

View File

@ -117,6 +117,7 @@ USE: namespaces
"/library/inference/branches.factor" "/library/inference/branches.factor"
"/library/inference/words.factor" "/library/inference/words.factor"
"/library/inference/stack.factor" "/library/inference/stack.factor"
"/library/inference/types.factor"
"/library/compiler/assembler.factor" "/library/compiler/assembler.factor"
"/library/compiler/xt.factor" "/library/compiler/xt.factor"

View File

@ -54,7 +54,7 @@ BUILTIN: dll 15
BUILTIN: alien 16 BUILTIN: alien 16
M: alien hashcode ( obj -- n ) M: alien hashcode ( obj -- n )
alien-address ; alien-address >fixnum ;
M: alien = ( obj obj -- ? ) M: alien = ( obj obj -- ? )
over alien? [ over alien? [

View File

@ -121,6 +121,10 @@ USE: math
#! MOV INDIRECT <reg> TO <reg>. #! MOV INDIRECT <reg> TO <reg>.
HEX: 8b compile-byte 0 MOD-R/M ; HEX: 8b compile-byte 0 MOD-R/M ;
: D[R]>R ( disp reg reg -- )
#! MOV INDIRECT DISPLACED <reg> TO <reg>.
HEX: 8b compile-byte 1 MOD-R/M compile-byte ;
: R>[R] ( reg reg -- ) : R>[R] ( reg reg -- )
#! MOV <reg> TO INDIRECT <reg>. #! MOV <reg> TO INDIRECT <reg>.
HEX: 89 compile-byte swap 0 MOD-R/M ; HEX: 89 compile-byte swap 0 MOD-R/M ;

View File

@ -82,7 +82,9 @@ USE: math
#slot [ #slot [
PEEK-DS PEEK-DS
2unlist type-tag >r cell * r> - EAX EAX D[R]>R
DS ECX [I]>R absolute-ds
EAX ECX R>[R]
] "generator" set-word-property ] "generator" set-word-property
#call [ #call [

View File

@ -105,3 +105,7 @@ SYMBOL: previous-offset
] catch ; ] catch ;
#label [ save-xt ] "generator" set-word-property #label [ save-xt ] "generator" set-word-property
: type-tag ( type -- tag )
#! Given a type number, return the tag number.
dup 6 > [ drop 3 ] when ;

View File

@ -168,13 +168,10 @@ SYMBOL: classes
SYMBOL: object SYMBOL: object
: type-union ( list list -- list ) : type-union ( list list -- list )
append prune [ > ] sort ; append prune ;
: type-intersection ( list list -- list )
intersection [ > ] sort ;
: lookup-union ( typelist -- class ) : lookup-union ( typelist -- class )
classes get hash [ object ] unless* ; [ > ] sort classes get hash [ object ] unless* ;
: class-or ( class class -- class ) : class-or ( class class -- class )
#! Return a class that both classes are subclasses of. #! Return a class that both classes are subclasses of.
@ -182,12 +179,19 @@ SYMBOL: object
swap builtin-supertypes swap builtin-supertypes
type-union lookup-union ; type-union lookup-union ;
: class-or-list ( list -- class )
#! Return a class that every class in the list is a
#! subclass of.
[
[ builtin-supertypes [ unique, ] each ] each
] make-list lookup-union ;
: class-and ( class class -- class ) : class-and ( class class -- class )
#! Return a class that is a subclass of both, or raise an #! Return a class that is a subclass of both, or raise an
#! error if this is impossible. #! error if this is impossible.
over builtin-supertypes over builtin-supertypes
over builtin-supertypes over builtin-supertypes
type-intersection dup [ intersection dup [
nip nip lookup-union nip nip lookup-union
] [ ] [
drop [ drop [
@ -196,8 +200,18 @@ SYMBOL: object
] make-string throw ] make-string throw
] ifte ; ] ifte ;
: define-promise ( class -- )
#! A promise is a word that has no effect during
#! interpretation, but instructs the compiler that the value
#! at the top of the stack is statically-known to be of the
#! given type. Promises should only be used by kernel code.
dup word-name "%" swap cat2 "in" get create
dup [ ] define-compound
swap "promise" set-word-property ;
: define-class ( class metaclass -- ) : define-class ( class metaclass -- )
dupd "metaclass" set-word-property dupd "metaclass" set-word-property
dup define-promise
dup builtin-supertypes [ > ] sort dup builtin-supertypes [ > ] sort
classes get set-hash ; classes get set-hash ;

View File

@ -90,3 +90,6 @@ predicate [
PREDICATE: compound generic ( word -- ? ) PREDICATE: compound generic ( word -- ? )
"combination" word-property ; "combination" word-property ;
PREDICATE: compound promise ( obj -- ? )
"promise" word-property ;

View File

@ -39,42 +39,41 @@ USE: words
USE: hashtables USE: hashtables
USE: prettyprint USE: prettyprint
: vector-length< ( vec1 vec2 -- ? ) : longest-vector ( list -- length )
swap vector-length swap vector-length < ; [ vector-length ] map [ > ] top ;
: unify-length ( vec1 vec2 -- vec1 ) : computed-value-vector ( n -- vector )
2dup vector-length< [ swap ] unless [ [ drop object <computed> ] vector-project ;
vector-length over vector-length -
empty-vector [ swap vector-append ] keep
] keep ;
: unify-classes ( value value -- class ) : add-inputs ( count stack -- count stack )
#! If one of the values is f, it was added as a result of #! Add this many inputs to the given stack.
#! length unification so we just replace it with a computed [ vector-length - dup ] keep
#! object value. >r computed-value-vector dup r> vector-append ;
2dup and [
value-class swap value-class class-or : unify-lengths ( list -- list )
#! Pad all vectors to the same length. If one vector is
#! shorter, pad it with unknown results at the bottom.
dup longest-vector swap [ dupd add-inputs nip ] map nip ;
: unify-results ( list -- value )
#! If all values in list are equal, return the value.
#! Otherwise, unify types.
dup all=? [
car
] [ ] [
2drop object [ value-class ] map class-or-list <computed>
] ifte ; ] ifte ;
: unify-results ( value value -- value ) : vector-transpose ( list -- vector )
#! Replace values with unknown result if they differ, #! Turn a list of same-length vectors into a vector of lists.
#! otherwise retain them. dup car vector-length [
2dup = [ over [ dupd vector-nth ] map nip
drop ] vector-project nip ;
] [
unify-classes <computed>
] ifte ;
: unify-stacks ( list -- stack ) : unify-stacks ( list -- stack )
#! Replace differing literals in stacks with unknown #! Replace differing literals in stacks with unknown
#! results. #! results.
uncons [ unify-lengths vector-transpose [ unify-results ] vector-map ;
unify-length vector-zip [
uncons unify-results
] vector-map
] each ;
: balanced? ( list -- ? ) : balanced? ( list -- ? )
#! Check if a list of [ instack | outstack ] pairs is #! Check if a list of [ instack | outstack ] pairs is
@ -139,9 +138,16 @@ SYMBOL: cloned
meta-d off meta-r off d-in off meta-d off meta-r off d-in off
] when ; ] when ;
: propagate-type ( [ value | class ] -- )
#! Type propagation is chained.
[
unswons 2dup set-value-class
[ type-propagations get ] bind assoc propagate-type
] when* ;
: infer-branch ( value -- namespace ) : infer-branch ( value -- namespace )
<namespace> [ <namespace> [
uncons [ unswons set-value-class ] when* uncons propagate-type
dup value-recursion recursive-state set dup value-recursion recursive-state set
copy-inference copy-inference
literal-value dup infer-quot literal-value dup infer-quot
@ -234,9 +240,8 @@ SYMBOL: cloned
#! Infer effects for all branches, unify. #! Infer effects for all branches, unify.
[ object vector ] ensure-d [ object vector ] ensure-d
dataflow-drop, pop-d vtable>list dataflow-drop, pop-d vtable>list
[ f cons ] map
>r 1 meta-d get vector-tail* #dispatch r> >r 1 meta-d get vector-tail* #dispatch r>
pop-d drop ( n ) pop-d ( n ) num-types [ dupd cons ] project nip zip
infer-branches ; infer-branches ;
USE: kernel-internals USE: kernel-internals

View File

@ -56,18 +56,24 @@ SYMBOL: d-in
! Recursive state. An alist, mapping words to labels. ! Recursive state. An alist, mapping words to labels.
SYMBOL: recursive-state SYMBOL: recursive-state
! A value has the following slots:
GENERIC: literal-value ( value -- obj ) GENERIC: literal-value ( value -- obj )
GENERIC: value= ( literal value -- ? ) GENERIC: value= ( literal value -- ? )
GENERIC: value-class ( value -- class ) GENERIC: value-class ( value -- class )
GENERIC: value-class-and ( class value -- ) GENERIC: value-class-and ( class value -- )
GENERIC: set-value-class ( class value -- ) GENERIC: set-value-class ( class value -- )
! A value has the following slots in addition to those relating
! to generics above:
! An association list mapping values to [ value | class ] pairs
SYMBOL: type-propagations
TRAITS: computed TRAITS: computed
C: computed ( class -- value ) C: computed ( class -- value )
[ [
\ value-class set \ value-class set
gensym \ literal-value set gensym \ literal-value set
type-propagations off
] extend ; ] extend ;
M: computed literal-value ( value -- obj ) M: computed literal-value ( value -- obj )
"Cannot use a computed value literally." throw ; "Cannot use a computed value literally." throw ;
@ -82,7 +88,11 @@ M: computed set-value-class ( class value -- )
TRAITS: literal TRAITS: literal
C: literal ( obj rstate -- value ) C: literal ( obj rstate -- value )
[ recursive-state set \ literal-value set ] extend ; [
recursive-state set
\ literal-value set
type-propagations off
] extend ;
M: literal literal-value ( value -- obj ) M: literal literal-value ( value -- obj )
[ \ literal-value get ] bind ; [ \ literal-value get ] bind ;
M: literal value= ( literal value -- ? ) M: literal value= ( literal value -- ? )

View File

@ -38,15 +38,14 @@ USE: strings
USE: vectors USE: vectors
USE: words USE: words
USE: stdio USE: stdio
USE: prettyprint
! Enhanced inference of primitives relating to data types. ! Enhanced inference of primitives relating to data types.
! Optimizes type checks and slot access. ! Optimizes type checks and slot access.
: infer-check ( assert class -- ) : infer-check ( assert class -- )
peek-d dup value-class pick = [ peek-d dup value-class pick = [
[ 3drop
"Optimized out " , rot word-name , " check." ,
] make-string print 2drop
] [ ] [
value-class-and value-class-and
dup "infer-effect" word-property consume/produce dup "infer-effect" word-property consume/produce
@ -65,6 +64,7 @@ USE: stdio
] "infer" set-word-property ] "infer" set-word-property
\ slot [ \ slot [
[ object fixnum ] ensure-d
dataflow-drop, pop-d literal-value dataflow-drop, pop-d literal-value
peek-d value-class builtin-supertypes dup length 1 = [ peek-d value-class builtin-supertypes dup length 1 = [
cons #slot dataflow, [ cons #slot dataflow, [
@ -77,3 +77,26 @@ USE: stdio
"slot called without static type knowledge" throw "slot called without static type knowledge" throw
] ifte ] ifte
] "infer" set-word-property ] "infer" set-word-property
: type-value-map ( value -- )
[
num-types [
dup builtin-type dup [
pick swons cons ,
] [
2drop
] ifte
] times*
] make-list nip ;
\ type [
[ object ] ensure-d
\ type #call dataflow, [
peek-d type-value-map >r
1 0 node-inputs
[ object ] consume-d
[ fixnum ] produce-d
r> peek-d [ type-propagations set ] bind
1 0 node-outputs
] bind
] "infer" set-word-property

View File

@ -112,6 +112,9 @@ M: compound (apply-word) ( word -- )
infer-compound infer-compound
] ifte ; ] ifte ;
M: promise (apply-word) ( word -- )
"promise" word-property unit ensure-d ;
M: symbol (apply-word) ( word -- ) M: symbol (apply-word) ( word -- )
apply-literal ; apply-literal ;
@ -125,7 +128,7 @@ M: symbol (apply-word) ( word -- )
#! diverging recursion. Note that this check is not done for #! diverging recursion. Note that this check is not done for
#! mutually-recursive words. Generally they should be #! mutually-recursive words. Generally they should be
#! avoided. #! avoided.
recursive-state get car = [ current-word = [
d-in get vector-length d-in get vector-length
meta-d get vector-length > [ meta-d get vector-length > [
current-word word-name " diverges." cat2 throw current-word word-name " diverges." cat2 throw
@ -183,6 +186,8 @@ M: symbol (apply-word) ( word -- )
\ call [ infer-call ] "infer" set-word-property \ call [ infer-call ] "infer" set-word-property
\ * [ [ number number ] [ number ] ] "infer-effect" set-word-property
\ undefined-method t "terminator" set-word-property \ undefined-method t "terminator" set-word-property
\ not-a-number t "terminator" set-word-property \ not-a-number t "terminator" set-word-property
\ throw t "terminator" set-word-property \ throw t "terminator" set-word-property

View File

@ -31,6 +31,8 @@ USE: kernel
USE: vectors USE: vectors
: dispatch ( n vtable -- ) : dispatch ( n vtable -- )
#! This word is unsafe in compiled code since n is not
#! bounds-checked. Do not call it directly.
vector-nth call ; vector-nth call ;
IN: kernel IN: kernel

View File

@ -37,11 +37,11 @@ USE: math-internals
GENERIC: real ( #{ re im } -- re ) GENERIC: real ( #{ re im } -- re )
M: real real ; M: real real ;
M: complex real 0 slot ; M: complex real 0 slot %real ;
GENERIC: imaginary ( #{ re im } -- im ) GENERIC: imaginary ( #{ re im } -- im )
M: real imaginary drop 0 ; M: real imaginary drop 0 ;
M: complex imaginary 1 slot ; M: complex imaginary 1 slot %real ;
: rect> ( xr xi -- x ) : rect> ( xr xi -- x )
over real? over real? and [ over real? over real? and [

View File

@ -34,11 +34,11 @@ USE: math-internals
GENERIC: numerator ( a/b -- a ) GENERIC: numerator ( a/b -- a )
M: integer numerator ; M: integer numerator ;
M: ratio numerator 0 slot ; M: ratio numerator 0 slot %integer ;
GENERIC: denominator ( a/b -- b ) GENERIC: denominator ( a/b -- b )
M: integer denominator drop 1 ; M: integer denominator drop 1 ;
M: ratio denominator 1 slot ; M: ratio denominator 1 slot %integer ;
IN: math-internals IN: math-internals

View File

@ -72,7 +72,7 @@ USE: words
[ sbuf-reverse " sbuf -- " [ [ sbuf ] [ ] ] ] [ sbuf-reverse " sbuf -- " [ [ sbuf ] [ ] ] ]
[ sbuf-clone " sbuf -- sbuf " [ [ sbuf ] [ sbuf ] ] ] [ sbuf-clone " sbuf -- sbuf " [ [ sbuf ] [ sbuf ] ] ]
[ sbuf= " sbuf sbuf -- ? " [ [ sbuf sbuf ] [ boolean ] ] ] [ sbuf= " sbuf sbuf -- ? " [ [ sbuf sbuf ] [ boolean ] ] ]
[ sbuf-hashcode " sbuf -- n " [ [ sbuf ] [ integer ] ] ] [ sbuf-hashcode " sbuf -- n " [ [ sbuf ] [ fixnum ] ] ]
[ arithmetic-type " n n -- type " [ [ number number ] [ number number fixnum ] ] ] [ arithmetic-type " n n -- type " [ [ number number ] [ number number fixnum ] ] ]
[ >fixnum " n -- fixnum " [ [ number ] [ fixnum ] ] ] [ >fixnum " n -- fixnum " [ [ number ] [ fixnum ] ] ]
[ >bignum " n -- bignum " [ [ number ] [ bignum ] ] ] [ >bignum " n -- bignum " [ [ number ] [ bignum ] ] ]

View File

@ -34,7 +34,7 @@ USE: math
! Define methods bound to primitives ! Define methods bound to primitives
BUILTIN: string 12 BUILTIN: string 12
M: string hashcode 2 slot ; M: string hashcode 2 slot %fixnum ;
M: string = str= ; M: string = str= ;
: str-length ( str -- len ) >string 1 integer-slot ; inline : str-length ( str -- len ) >string 1 integer-slot ; inline

View File

@ -36,9 +36,9 @@ USE: generic
: inline-test : inline-test
car car ; inline car car ; inline
[ t ] [ ! [ t ] [
\ slot [ inline-test ] dataflow dataflow-contains-param? >boolean ! \ slot [ inline-test ] dataflow dataflow-contains-param? >boolean
] unit-test ! ] unit-test
[ t ] [ [ t ] [
#ifte [ [ drop ] [ + ] ifte ] dataflow dataflow-contains-op? >boolean #ifte [ [ drop ] [ + ] ifte ] dataflow dataflow-contains-op? >boolean

View File

@ -20,41 +20,18 @@ unit-test
[ [ vector ] [ cons vector cons integer object cons ] ] [ [ vector ] [ cons vector cons integer object cons ] ]
[ [ vector ] [ cons vector cons ] ] [ [ vector ] [ cons vector cons ] ]
decompose decompose
] ] unit-test
[ [ [ object ] [ object ] ] ] [ [ [ object ] [ object ] ] ]
[ [
[ [ object number ] [ object ] ] [ [ object number ] [ object ] ]
[ [ object number ] [ object ] ] [ [ object number ] [ object ] ]
decompose decompose
] ] unit-test
: old-effect ( [ in-types out-types ] -- [ in | out ] ) : old-effect ( [ in-types out-types ] -- [ in | out ] )
uncons car length >r length r> cons ; uncons car length >r length r> cons ;
[
[ 1 | 2 ]
[ 2 | 1 ]
[ 0 | 3 ]
[ 4 | 2 ]
[ 3 | 3 ]
[ 0 | 0 ]
[ 1 | 5 ]
[ 3 | 4 ]
] "effects" set
[ { f 1 2 } { 1 2 3 } ] [
{ 1 2 } { 1 2 3 } unify-length
] unit-test
[ [ sq ] ] [
[ sq ] f <literal> [ sq ] f <literal> unify-results literal-value
] unit-test
[ fixnum ] [
5 f <literal> 6 f <literal> unify-results value-class
] unit-test
[ [ 0 | 2 ] ] [ [ 2 "Hello" ] infer old-effect ] unit-test [ [ 0 | 2 ] ] [ [ 2 "Hello" ] infer old-effect ] unit-test
[ [ 1 | 2 ] ] [ [ dup ] infer old-effect ] unit-test [ [ 1 | 2 ] ] [ [ dup ] infer old-effect ] unit-test
@ -109,10 +86,10 @@ unit-test
[ [ 1 | 1 ] ] [ [ simple-recursion-2 ] infer old-effect ] unit-test [ [ 1 | 1 ] ] [ [ simple-recursion-2 ] infer old-effect ] unit-test
: bad-recursion-1 ! : bad-recursion-1
dup [ drop bad-recursion-1 5 ] [ ] ifte ; ! dup [ drop bad-recursion-1 5 ] [ ] ifte ;
!
[ [ bad-recursion-1 ] infer old-effect ] unit-test-fails ! [ [ bad-recursion-1 ] infer old-effect ] unit-test-fails
: bad-recursion-2 : bad-recursion-2
dup [ uncons bad-recursion-2 ] [ ] ifte ; dup [ uncons bad-recursion-2 ] [ ] ifte ;
@ -236,11 +213,12 @@ SYMBOL: sym-test
! Type inference ! Type inference
! [ [ [ object ] [ ] ] ] [ [ drop ] infer ] unit-test [ [ [ object ] [ ] ] ] [ [ drop ] infer ] unit-test
! [ [ [ object ] [ object object ] ] ] [ [ dup ] infer ] unit-test [ [ [ object ] [ object object ] ] ] [ [ dup ] infer ] unit-test
! [ [ [ object object ] [ cons ] ] ] [ [ cons ] infer ] unit-test [ [ [ object object ] [ cons ] ] ] [ [ cons ] infer ] unit-test
! [ [ [ cons ] [ cons ] ] ] [ [ uncons cons ] infer ] unit-test [ [ [ cons ] [ cons ] ] ] [ [ uncons cons ] infer ] unit-test
! [ [ [ object ] [ object ] ] ] [ [ dup [ car ] when ] infer ] unit-test [ [ [ general-list ] [ object ] ] ] [ [ dup [ car ] when ] infer ] unit-test
! [ [ [ vector ] [ vector ] ] ] [ [ vector-clone ] infer ] unit-test [ [ [ vector ] [ vector ] ] ] [ [ vector-clone ] infer ] unit-test
! [ [ [ number ] [ number ] ] ] [ [ dup + ] infer ] unit-test ! [ [ [ number ] [ number ] ] ] [ [ dup + ] infer ] unit-test
! [ [ [ number number number ] [ number ] ] ] [ [ digit+ ] infer ] unit-test ! [ [ [ number number number ] [ number ] ] ] [ [ digit+ ] infer ] unit-test
[ [ [ number ] [ real real ] ] ] [ [ >rect ] infer ] unit-test

View File

@ -37,7 +37,7 @@ USE: strings
BUILTIN: word 1 BUILTIN: word 1
M: word hashcode 1 slot ; M: word hashcode 1 slot %fixnum ;
: word-xt ( w -- xt ) >word 2 integer-slot ; inline : word-xt ( w -- xt ) >word 2 integer-slot ; inline
: set-word-xt ( xt w -- ) >word 2 set-integer-slot ; inline : set-word-xt ( xt w -- ) >word 2 set-integer-slot ; inline
@ -84,7 +84,11 @@ PREDICATE: word undefined ( obj -- ? ) word-primitive 0 = ;
: intern-symbol ( word -- ) : intern-symbol ( word -- )
dup undefined? [ define-symbol ] [ drop ] ifte ; dup undefined? [ define-symbol ] [ drop ] ifte ;
: word-name ( word -- str ) "name" word-property ; #! The type declaration is for the benefit of stack effect
#! inference.
: word-name ( word -- str )
"name" word-property >string ;
: word-vocabulary ( word -- str ) "vocabulary" word-property ; : word-vocabulary ( word -- str ) "vocabulary" word-property ;
: stack-effect ( word -- str ) "stack-effect" word-property ; : stack-effect ( word -- str ) "stack-effect" word-property ;
: documentation ( word -- str ) "documentation" word-property ; : documentation ( word -- str ) "documentation" word-property ;