ソースを参照

Added support for arrays of function pointers. Fixes #36.
Ensure super function has been semanted before use.
Fixed leaking stack from return inside Try block.

woollybah 11 年 前
コミット
0ec1bdadd7
6 ファイル変更134 行追加29 行削除
  1. 43 17
      ctranslator.bmx
  2. 4 1
      decl.bmx
  3. 55 7
      expr.bmx
  4. 8 4
      parser.bmx
  5. 23 0
      translator.bmx
  6. 1 0
      type.bmx

+ 43 - 17
ctranslator.bmx

@@ -74,6 +74,7 @@ Type TCTranslator Extends TTranslator
 		If TStringType( ty ) Return "~q$~q"
 		If TArrayType( ty ) Return "~q[~q"
 		If TObjectType( ty ) Return "~q:~q"
+		If TFunctionPtrType( ty ) Return "~q*b~q" ' TODO : use "(" instead? (it's mentioned in blitz array source somewhere)
 
 	End Method
 	
@@ -289,17 +290,17 @@ Type TCTranslator Extends TTranslator
 				
 									t:+ class + "->fn_" + fdecl.ident
 								Else
-									t:+ "&" + fdecl.munged
+									t:+ fdecl.munged
 								End If
 							Else
-								t:+ "&" + fdecl.munged
+								t:+ fdecl.munged
 							End If
 						End If
 						Continue
 					End If
 					' some cases where we are passing a function pointer via a void* parameter.
 					If TCastExpr(args[i]) And TInvokeExpr(TCastExpr(args[i]).expr) And Not TInvokeExpr(TCastExpr(args[i]).expr).invokedWithBraces Then
-						t:+ "&" + TInvokeExpr(TCastExpr(args[i]).expr).decl.munged
+						t:+ TInvokeExpr(TCastExpr(args[i]).expr).decl.munged
 						Continue
 					End If
 
@@ -342,6 +343,10 @@ t:+"NULLNULLNULL"
 						Else
 							t:+ decl.argDecls[i].init.Trans()
 						End If
+					Else If TFunctionPtrType(ty) Then
+						If TInvokeExpr(init) Then
+							t:+ TInvokeExpr(init).decl.munged
+						End If
 					Else
 						t:+ decl.argDecls[i].init.Trans()
 					End If
@@ -1321,6 +1326,16 @@ EndRem
 			'If TDoubleVarPtrType( src ) Return Bra("*" + t)
 			'If TPointerType( src ) Return Bra("(BBDOUBLE)"+t)
 		Else If TStringType( dst )
+
+			If src._flags & TType.T_VAR Then
+				If TByteType( src ) Return "bbStringFromInt"+Bra( "*" + t )
+				If TShortType( src ) Return "bbStringFromInt"+Bra( "*" + t )
+				If TIntType( src ) Return "bbStringFromInt"+Bra( "*" + t )
+				If TLongType( src ) Return "bbStringFromLong"+Bra( "*" + t )
+				If TFloatType( src ) Return "bbStringFromFloat"+Bra( "*" + t )
+				If TDoubleType( src ) Return "bbStringFromDouble"+Bra( "*" + t )
+			End If
+
 			If TBoolType( src ) Return "bbStringFromInt"+Bra( t )
 			If TByteType( src ) Return "bbStringFromInt"+Bra( t )
 			If TShortType( src ) Return "bbStringFromInt"+Bra( t )
@@ -1347,14 +1362,6 @@ EndRem
 			'	Return "*" + t
 			'End If
 			'If TStringCharPtrType( src ) Return "bbStringFromCString"+Bra( t )
-			If src._flags & TType.T_VAR Then
-				If TByteType( src ) Return "bbStringFromInt"+Bra( "*" + t )
-				If TShortType( src ) Return "bbStringFromInt"+Bra( "*" + t )
-				If TIntType( src ) Return "bbStringFromInt"+Bra( "*" + t )
-				If TLongType( src ) Return "bbStringFromLong"+Bra( "*" + t )
-				If TFloatType( src ) Return "bbStringFromFloat"+Bra( "*" + t )
-				If TDoubleType( src ) Return "bbStringFromDouble"+Bra( "*" + t )
-			End If
 		'Else If TStringVarPtrType( dst )
 'DebugStop
 		Else If TByteType( dst )
@@ -1530,7 +1537,11 @@ EndRem
 		End If
 
 		If TArrayType( expr.expr.exprType ) Then
-			Return Bra("(" + TransType(expr.exprType, "") + "*)BBARRAYDATA(" + t_expr + "," + t_expr + "->dims)") + "[" + t_index + "]"
+			If TFunctionPtrType(TArrayType( expr.expr.exprType ).elemType) Then
+				Return Bra(Bra(TransType(TArrayType( expr.expr.exprType).elemType, "")) + Bra(Bra("(void**)BBARRAYDATA(" + t_expr + "," + t_expr + "->dims)") + "[" + t_index + "]"))
+			Else
+				Return Bra("(" + TransType(expr.exprType, "") + "*)BBARRAYDATA(" + t_expr + "," + t_expr + "->dims)") + "[" + t_index + "]"
+			End If
 		End If
 
 		'Local swiz$
@@ -1592,7 +1603,12 @@ EndRem
 		Local tt$
 '		If Not _env tt="static "
 
-		Emit tt+TransType( elemType, tmpData.munged )+" "+tmpData.munged+"[]={"+t+"};"
+		If Not TFunctionPtrType(elemType) Then
+			tt :+ TransType( elemType, tmpData.munged ) + " "+tmpData.munged + "[]"
+		Else
+			tt :+ TransType( elemType, tmpData.munged + "[]" ) 
+		End If
+		Emit tt+"={"+t+"};"
 		Emit "BBARRAY " + tmpArray.munged + " = bbArrayFromData" + Bra(TransArrayType(elemType) + "," + count + "," + tmpData.munged ) + ";"
 
 		Return tmpArray.munged
@@ -1665,7 +1681,9 @@ EndRem
 		Emit "jmp_buf * buf = bbExEnter();"
 		Emit "switch(setjmp(*buf)) {"
 		Emit "case 0: {"
+		tryStack.Push("")
 		EmitBlock( stmt.block )
+		tryStack.Pop()
 		Emit "bbExLeave();"
 		Emit "}"
 		Emit "break;"
@@ -1707,6 +1725,12 @@ EndRem
 		Emit "}"
 		Emit "} while(0);"
 	End Method
+	
+	Method EmitTryStack()
+		For Local i:Int = 0 Until tryStack.Length()
+			Emit "bbExLeave();"
+		Next
+	End Method
 
 	Method TransAssignStmt$( stmt:TAssignStmt )
 		If Not stmt.rhs Return stmt.lhs.Trans()
@@ -2842,6 +2866,8 @@ End Rem
 					fld :+ "= 0;"
 				Else If TStringType(decl.ty) Then
 					fld :+ "= &bbEmptyString;"
+				Else If TArrayType(decl.ty) Then
+					fld :+ "= &bbEmptyArray;"
 				End If
 			End If
 
@@ -2926,10 +2952,10 @@ End Rem
 			End If
 		End If
 
-		If TObjectType(exprType) And (exprType._flags & TType.T_VAR) Then
-			' get the object from the pointer
-			variable = Bra("*" + variable)
-		End If
+		'If TObjectType(exprType) And (exprType._flags & TType.T_VAR) Then
+		'	' get the object from the pointer
+		'	variable = Bra("*" + variable)
+		'End If
 
 		If IsNumericType(decl.ty) Then
 			s = variable + "->" + decl.munged + " "

+ 4 - 1
decl.bmx

@@ -424,7 +424,10 @@ Type TArgDecl Extends TLocalDecl
 	End Method
 	
 	Method OnCopy:TDecl()
-		Return New TArgDecl.Create( ident,ty,CopyInit(),attrs )
+		Local d:TArgDecl = New TArgDecl.Create( ident,ty,CopyInit(),attrs )
+		d.ty = d.declTy
+		d.init = d.declInit
+		Return d
 	End Method
 	
 	Method ToString$()

+ 55 - 7
expr.bmx

@@ -723,12 +723,14 @@ Type TInvokeSuperExpr Extends TExpr
 
 		classScope=_env.ClassScope()
 		superClass=classScope.superClass
-
+		
 		If Not superClass Err "Type has no super class."
 
 		args=SemantArgs( args )
 		origFuncDecl=classScope.FindFuncDecl(ident,args)
 		funcDecl=superClass.FindFuncDecl( ident,args )
+		' ensure the super function has been semanted
+		funcDecl.Semant()
 		If Not funcDecl Err "Can't find superclass method '"+ident+"'."
 		args=CastArgs( args,funcDecl )
 		exprType=funcDecl.retType
@@ -1418,6 +1420,17 @@ Type TIndexExpr Extends TExpr
 		Return Semant()
 		'Return Self
 	End Method
+	
+	Method SemantFunc:TExpr( args:TExpr[] , throwError:Int = True, funcCall:Int = False )
+		Local ex:TExpr = Semant()
+		
+		If TArrayType( expr.exprType ) And TFunctionPtrType(exprType) Then
+			exprType = TFunctionPtrType(exprType).func.retType
+		End If
+		
+		Return ex
+	End Method
+
 
 	Method Trans$()
 		Return _trans.TransIndexExpr( Self )
@@ -1494,11 +1507,36 @@ Type TArrayExpr Extends TExpr
 
 		exprs[0]=exprs[0].Semant()
 		Local ty:TType=exprs[0].exprType
-
-		For Local i:Int=1 Until exprs.Length
-			exprs[i]=exprs[i].Semant()
-			ty=BalanceTypes( ty,exprs[i].exprType )
-		Next
+		
+		If TInvokeExpr(exprs[0]) And Not TInvokeExpr(exprs[0]).invokedWithBraces Then
+			ty = New TFunctionPtrType
+			Local cp:TDecl = TInvokeExpr(exprs[0]).decl
+			TInvokeExpr(exprs[0]).decl = TFuncDecl(TInvokeExpr(exprs[0]).decl.Copy())
+			TInvokeExpr(exprs[0]).decl.actual = cp
+			TInvokeExpr(exprs[0]).decl.attrs :| FUNC_PTR
+			TFunctionPtrType(ty).func = TInvokeExpr(exprs[0]).decl
+
+			For Local i:Int=1 Until exprs.Length
+				exprs[i]=exprs[i].Semant()
+				
+				If TInvokeExpr(exprs[i]) And Not TInvokeExpr(exprs[i]).invokedWithBraces
+					cp = TInvokeExpr(exprs[i]).decl
+					
+					TInvokeExpr(exprs[i]).decl = TFuncDecl(TInvokeExpr(exprs[i]).decl.Copy())
+					TInvokeExpr(exprs[i]).decl.actual = cp
+					TInvokeExpr(exprs[i]).decl.attrs :| FUNC_PTR
+					
+					ty=BalanceTypes( ty, New TFunctionPtrType )
+				Else
+					ty=BalanceTypes( ty,exprs[i].exprType )
+				End If
+			Next
+		Else
+			For Local i:Int=1 Until exprs.Length
+				exprs[i]=exprs[i].Semant()
+				ty=BalanceTypes( ty,exprs[i].exprType )
+			Next
+		End If
 
 		For Local i:Int=0 Until exprs.Length
 			exprs[i]=exprs[i].Cast( ty )
@@ -2077,7 +2115,17 @@ Type TFuncCallExpr Extends TExpr
 
 	Method Semant:TExpr()
 		args=SemantArgs( args )
-		Return expr.SemantFunc( args, True, True )
+		If TIndexExpr(expr) Then
+			expr = expr.SemantFunc( args, True, True )
+			exprType = expr.exprType
+			Return Self
+		Else
+			Return expr.SemantFunc( args, True, True )
+		End If
+	End Method
+
+	Method Trans$()
+		Return _trans.TransFuncCallExpr( Self )
 	End Method
 
 End Type

+ 8 - 4
parser.bmx

@@ -417,7 +417,7 @@ Type TParser
 		If CParse( "byte" ) Return New TByteType
 		If CParse( "int" ) Return New TIntType
 		If CParse( "float" ) Return New TFloatType
-		If CParse( "string" ) Return New TStringType
+		If CParse( "string" ) Return TType.stringType
 		If CParse( "object" ) Return New TIdentType.Create( "brl.classes.object" )
 		If CParse( "long" ) Return New TLongType
 		If CParse( "double" ) Return New TDoubleType
@@ -438,7 +438,7 @@ Type TParser
 		If CParse( "byte" ) Return New TByteType
 		If CParse( "int" ) Return New TIntType
 		If CParse( "float" ) Return New TFloatType
-		If CParse( "string" ) Return New TStringType
+		If CParse( "string" ) Return TType.stringType
 		If CParse( "object" ) Return New TIdentType.Create( "brl.classes.object" )
 		If CParse( "long" ) Return New TLongType
 		If CParse( "double" ) Return New TDoubleType
@@ -923,7 +923,7 @@ Type TParser
 					TConstExpr(expr).ty = ty
 				End If
 			Case TOKE_STRINGLIT
-				expr=New TConstExpr.Create( New TStringType,BmxUnquote( _toke ) )
+				expr=New TConstExpr.Create( TType.stringType,BmxUnquote( _toke ) )
 				_app.mapStringConsts(BmxUnquote( _toke ))
 				NextToke
 			Default
@@ -1400,7 +1400,7 @@ Type TParser
 				Local ty:TType
 				If Not CParse(":") Then
 					Parse "$"
-					ty=New TStringType
+					ty= TType.stringType
 				Else
 					ty=ParseType()
 				End If
@@ -1780,6 +1780,10 @@ Type TParser
 
 				TFunctionPtrType(ty).func.ident = ""
 
+				While CParse( "[]" )
+					ty=New TArrayType.Create(ty)
+				Wend
+
 				' check for function pointer init
 				If CParse("=") Then
 					init=ParseExpr()

+ 23 - 0
translator.bmx

@@ -40,6 +40,8 @@ Type TTranslator
 	Field customVarStack:TStack = New TStack
 	Field varStack:TStack = New TStack
 
+	Field tryStack:TStack = New TStack
+
 	Field mungedScopes:TMap=New TMap'<StringSet>
 '	Field funcMungs:=New StringMap<FuncDeclList>
 '	Field mungedFuncs:=New StringMap<FuncDecl>
@@ -416,6 +418,8 @@ End Rem
 	Method TransArraySizeExpr$ ( expr:TArraySizeExpr ) Abstract
 	
 	Method TransIntrinsicExpr$( decl:TDecl,expr:TExpr,args:TExpr[]=Null ) Abstract
+	
+	Method TransArgs$( args:TExpr[],decl:TFuncDecl, objParam:String = Null ) Abstract
 
 	Method BeginLocalScope()
 		mungStack.Push mungScope
@@ -512,6 +516,8 @@ End Rem
 
 		If (decl.attrs & FUNC_PTR) And (decl.attrs & FUNC_INIT) And Not expr.InvokedWithBraces Return decl.munged
 		
+		If ((decl.attrs & FUNC_PTR) Or (expr.decl.attrs & FUNC_PTR)) And Not expr.InvokedWithBraces Return decl.munged
+		
 		If decl.munged.StartsWith( "$" ) Return TransIntrinsicExpr( decl,Null,expr.args )
 		
 		If decl Return TransFunc( TFuncDecl(decl),expr.args,Null )
@@ -539,6 +545,18 @@ End Rem
 		InternalErr
 	End Method
 	
+	Method TransFuncCallExpr:String( expr:TFuncCallExpr )
+
+		If TIndexExpr(expr.expr) And TArrayType(TIndexExpr(expr.expr).expr.exprType) And TFunctionPtrType(TArrayType(TIndexExpr(expr.expr).expr.exprType).elemType) Then
+			Local decl:TDecl = TFunctionPtrType(TArrayType(TIndexExpr(expr.expr).expr.exprType).elemType).func.actual
+			decl.Semant()
+			expr.args=expr.CastArgs( expr.args,TFuncDecl(decl) )
+			Return expr.expr.Trans() + TransArgs(expr.args, TFuncDecl(decl))
+		End If
+		
+		InternalErr
+	End Method
+	
 	Method TransExprStmt$( stmt:TExprStmt )
 		Return stmt.expr.TransStmt()
 	End Method
@@ -567,6 +585,9 @@ End Rem
 			End If
 			t:+" "+stmt.expr.Trans()
 		End If
+		
+		EmitTryStack()
+
 		Return t
 	End Method
 	
@@ -583,6 +604,8 @@ End Rem
 	
 	Method TransTryStmt$( stmt:TTryStmt )
 	End Method
+	
+	Method EmitTryStack() Abstract
 
 	Method TransThrowStmt$( stmt:TThrowStmt )
 	End Method

+ 1 - 0
type.bmx

@@ -73,6 +73,7 @@ Type TType
 	Global emptyArrayType:TArrayType=New TArrayType.Create( voidType )
 	Global objectType:TIdentType=New TIdentType.Create( "brl.classes.object" )
 	Global nullObjectType:TNullType=New TNullType
+	Global stringType:TStringType=New TStringType
 
 	Rem
 	bbdoc: map to a pointer type