Browse Source

Merge pull request #244 from HurryStarfish/master

Function Ptr enhancements
Brucey 8 years ago
parent
commit
a3aa0dbb14
6 changed files with 224 additions and 278 deletions
  1. 21 3
      ctranslator.bmx
  2. 43 33
      decl.bmx
  3. 11 5
      expr.bmx
  4. 133 231
      parser.bmx
  5. 8 4
      translator.bmx
  6. 8 2
      type.bmx

+ 21 - 3
ctranslator.bmx

@@ -245,7 +245,6 @@ Type TCTranslator Extends TTranslator
 
 			TFunctionPtrType(ty).func.Semant
 
-			Local retType:String = TransType(TFunctionPtrType(ty).func.retType, "")
 			Local api:String
 			If TFunctionPtrType(ty).func.attrs & DECL_API_WIN32 Then
 				api = " __stdcall "
@@ -263,11 +262,24 @@ Type TCTranslator Extends TTranslator
 			If fpReturnTypeFunctionArgs Then
 				ret = Bra(fpReturnTypeFunctionArgs)
 			End If
+			
 			If fpReturnTypeClassFunc Then
 				' typedef for function pointer return type
 				Return ident + "x" + Bra(api + p +"* " + ident) + Bra(args)
 			Else
-				Return retType + Bra(api + p +"* " + ident + ret) + Bra(args)
+				' if a function F returns another function (let's call it G),
+				' then C syntax requires the declaration of F to be nested into that of the type of G
+				' e.g. "Function F:RetG(ArgG)(ArgF)" in BlitzMax becomes "RetG(* F(ArgF) )(ArgG)" in C
+				' solution: use "* F(ArgF)" as an ident to generate a declaration for G
+				'           the result will be the declaration for F
+				Local callable:String = Bra(api + p +"* " + ident + ret)
+				If TFunctionPtrType(TFunctionPtrType(ty).func.retType) Then
+					If Not args Then args = " " ' make sure the parentheses aren't ommited even if the parameter list is empty
+					Return TransType(TFunctionPtrType(ty).func.retType, callable, args)
+				Else
+					Local retTypeStr:String = TransType(TFunctionPtrType(ty).func.retType, "")
+					Return retTypeStr + callable + Bra(args)
+				End If
 			End If
 		End If
 
@@ -660,7 +672,11 @@ t:+"NULLNULLNULL"
 	Method TransLocalDecl$( decl:TLocalDecl,init:TExpr, declare:Int = False, outputInit:Int = True )
 		Local initTrans:String
 		If outputInit Then
-			initTrans = "=" + init.Trans()
+			If TInvokeExpr(init) And Not TInvokeExpr(init).invokedWithBraces Then
+				initTrans = "=" + TInvokeExpr(init).decl.munged
+			Else
+				initTrans = "=" + init.Trans()
+			End If
 		End If
 	
 		If Not declare And opt_debug Then
@@ -4200,6 +4216,8 @@ End Rem
 					Else
 						If TObjectType(decl.ty) And TObjectType(decl.ty).classdecl.IsStruct() And Not isPointerType(decl.ty) And (TConstExpr(decl.init) And Not TConstExpr(decl.init).value) Then
 							fld = "memset(&" + fld + ", 0, sizeof" + Bra(TransType(decl.ty, "")) + ");"
+						Else If TInvokeExpr(decl.init) And Not TInvokeExpr(decl.init).invokedWithBraces Then
+							fld :+ "= " + TInvokeExpr(decl.init).decl.munged + ";"
 						Else
 							fld :+ "= " + decl.init.Trans() + ";"
 						End If

+ 43 - 33
decl.bmx

@@ -378,41 +378,47 @@ Type TValDecl Extends TDecl
 			If declInit Then
 				If TFunctionPtrType(ty) Then
 					
-					' the default munged function value as defined in the interface
+					Local expr:TExpr
+					
 					If TInvokeExpr(declInit) Then
-						init = declInit.Copy()
+						expr = declInit.Copy()
 					Else If TConstExpr(declInit) Then
-						init = declInit.Copy().Semant()
+						expr = declInit.Copy().Semant()
+					Else If TFuncCallExpr(declInit) Then
+						expr=declInit.Copy().Semant()
+					Else If TNullExpr(declInit) Then
+						expr = declInit
 					Else
-						Local expr:TExpr
-						
-						If TFuncCallExpr(declInit) Then
-							expr=declInit.Copy().Semant()
-						Else If TNullExpr(declInit) Then
-							expr = declInit
-						Else
-							Local argExpr:TExpr[] = New TExpr[0]
-
-							For Local arg:TArgDecl = EachIn TFunctionPtrType(ty).func.argDecls
-								Local ldecl:TLocalDecl = New TLocalDecl.Create(arg.ident, arg.declTy, Null, 0)
-								ldecl.Semant()
-								Local aexp:TVarExpr = New TVarExpr.Create(ldecl)
-								'Local aexp:TIdentTypeExpr = New TIdentTypeExpr.Create(arg.declTy)
-								aexp.Semant()
-								argExpr :+ [aexp]
-							Next
+						' declInit can only be an expression, never a statement
+						' this means that any function call in there is required to have parentheses, and will
+						' thus appear in the form of a TFuncCallExpr
+						' as such, trying SemantFunc in the Else branch seems pointless and will in fact wrongly
+						' interpret function pointers (as TIdentExpr, TIndexExpr, possibly others?) as calls
+						Rem
+						Local argExpr:TExpr[] = New TExpr[0]
+
+						For Local arg:TArgDecl = EachIn TFunctionPtrType(ty).func.argDecls
+							Local ldecl:TLocalDecl = New TLocalDecl.Create(arg.ident, arg.declTy, Null, 0)
+							ldecl.Semant()
+							Local aexp:TVarExpr = New TVarExpr.Create(ldecl)
+							'Local aexp:TIdentTypeExpr = New TIdentTypeExpr.Create(arg.declTy)
+							aexp.Semant()
+							argExpr :+ [aexp]
+						Next
 
-							expr=declInit.Copy().SemantFunc(argExpr, False, False)
-							If Not expr Then
-								expr = declInit.Copy().Semant()
-							End If
+						expr=declInit.Copy().SemantFunc(argExpr, False, False)
+						If Not expr Then
+							expr = declInit.Copy().Semant()
 						End If
+						End Rem
 						
-						If expr.exprType.EqualsType( ty ) Then
-							init = expr
-						Else
-							init = New TCastExpr.Create( ty,expr,CAST_EXPLICIT ).Semant()
-						End If
+						expr = declInit.Copy().Semant()
+					End If
+					
+					If expr.exprType.EqualsType( ty ) Then
+						init = expr
+					Else
+						init = New TCastExpr.Create( ty,expr,CAST_EXPLICIT ).Semant()
 					End If
 					
 					
@@ -1684,12 +1690,16 @@ Type TFuncDecl Extends TBlockDecl
 			End If
 		Else
 			' pass the scope into the function ptr
-			If TFunctionPtrType(retTypeExpr) Then
-				If Not TFunctionPtrType(retTypeExpr).func.scope Then
+			Local retTypeExpr_:TType = retTypeExpr
+			While TArrayType(retTypeExpr_) ' look into array types, since the element type might be function ptr
+				retTypeExpr_ = TArrayType(retTypeExpr_).elemType
+			Wend
+			If TFunctionPtrType(retTypeExpr_) Then
+				If Not TFunctionPtrType(retTypeExpr_).func.scope Then
 					If scope Then
-						TFunctionPtrType(retTypeExpr).func.scope = scope
+						TFunctionPtrType(retTypeExpr_).func.scope = scope
 					Else
-						TFunctionPtrType(retTypeExpr).func.scope = _env
+						TFunctionPtrType(retTypeExpr_).func.scope = _env
 					End If
 				End If
 			End If

+ 11 - 5
expr.bmx

@@ -691,8 +691,12 @@ Type TInvokeExpr Extends TExpr
 		'	exprType=decl.retType
 		'End If
 
-		If ((isArg Or isRhs) And Not invokedWithBraces) And (args = Null Or args.length = 0) Then
-			' nothing to do here, as we are probably a function pointer. i.e. no braces and no 
+		'If ((isArg Or isRhs) And Not invokedWithBraces) And (args = Null Or args.length = 0) Then
+
+		' if the call was a statement (even one written without parentheses), then invokedWithBraces is true
+		' so no complicated checks are needed here; if invokedWithBraces is false, this is definitely not a call
+		If Not invokedWithBraces Then
+			' nothing to do here, as we are a function pointer. i.e. no braces
 			' and our expression type is a function ptr...
 			exprType = New TFunctionPtrType.Create(decl)
 			
@@ -1323,9 +1327,11 @@ Type TCastExpr Extends TExpr
 				End If
 			Else
 				' return type should be function ptr?
-				' TODO
-				exprType = ty
-				Return expr
+				Local retType:TType = expr.exprType
+				If TFunctionPtrType(retType) And TFunctionPtrType(ty).func.EqualsFunc(TFunctionPtrType(retType).func) Then
+					exprType = retType
+					Return expr
+				End If
 			End If
 		End If
 

+ 133 - 231
parser.bmx

@@ -829,10 +829,16 @@ Type TParser
 			Wend
 		End Select
 		
-		' array ?
-		While IsArrayDef()
-			ty = ParseArrayType(ty)
-		Wend
+		' array or function pointer?
+		Repeat
+			If (_toke = "[" Or _toke = "[]") And IsArrayDef()
+				ty = ParseArrayType(ty)
+			Else If _toke = "(" Then
+				ty = New TFunctionPtrType.Create(New TFuncDecl.CreateF("", ty, ParseFuncParamDecl(), FUNC_PTR))
+			Else
+				Exit
+			End If
+		Forever
 		
 		Return ty
 	End Method
@@ -1816,27 +1822,6 @@ End Rem
 				If varty._flags & (TType.T_CHAR_PTR | TType.T_SHORT_PTR) Then
 					DoErr "Illegal variable type"
 				End If
-
-				If _toke = "(" Then
-
-					Local fdecl:TFuncDecl = ParseFuncDecl("", FUNC_PTR | DECL_ARG)
-
-					If Not varty Then
-						varty = New TFunctionPtrType
-						TFunctionPtrType(varty).func = fdecl
-					Else
-						fdecl.retType = varty
-						varty = New TFunctionPtrType
-						TFunctionPtrType(varty).func = fdecl
-					End If
-
-					TFunctionPtrType(varty).func.ident = varid
-
-					' function pointer array ?
-					While IsArrayDef()
-						varty = ParseArrayType(varty)
-					Wend
-				End If
 				
 				Parse( "=" )
 			'EndIf
@@ -2374,40 +2359,25 @@ End Rem
 		Local id$=ParseIdent()
 		Local ty:TType
 		Local init:TExpr
-
+		
+		
 		If attrs & DECL_EXTERN
 			ty=ParseDeclType()
-
-'			If CParse("(") Then
-			If _toke = "(" Then
-
-				' function pointer?
-				Local decl:TFuncDecl = ParseFuncDecl("", attrs | FUNC_PTR)
-
-				If Not ty Then
-					ty = New TFunctionPtrType
-					TFunctionPtrType(ty).func = decl
-				Else
-					decl.retType = ty
-					ty = New TFunctionPtrType
-					TFunctionPtrType(ty).func = decl
-				End If
-
-				TFunctionPtrType(ty).func.ident = id
-
-			Else If toke = "const" Then
+			
+			If toke = "const" Then
 				If CParse("=") Then
 					init=ParseExpr()
 				End If
 			End If
 		Else If CParse( ":=" )
 			init=ParseExpr()
+			ty = init.exprType
 		Else
 			ty=ParseDeclType()
 
 			If CParse( "=" )
 				init=ParseExpr()
-			Else If CParse( "[" )
+			Else If CParse( "[" ) ' an initialised array?
 				Local ln:TExpr[]
 				Repeat
 					If CParse(",") Then
@@ -2426,63 +2396,13 @@ End Rem
 				'Wend
 				init=New TNewArrayExpr.Create( ty,ln)
 				ty=New TArrayType.Create( ty, ln.length )
-			Else If _toke = "(" Then
-	 			' function pointer?
-				Local fdecl:TFuncDecl = ParseFuncDecl("", FUNC_PTR)
-				If toke = "field" Then
-					fdecl.attrs :| FUNC_METHOD
-				End If
-
-				If Not ty Then
-					ty = New TFunctionPtrType
-					TFunctionPtrType(ty).func = fdecl
-				Else
-					fdecl.retType = ty
-					ty = New TFunctionPtrType
-					TFunctionPtrType(ty).func = fdecl
-				End If
-
-				TFunctionPtrType(ty).func.ident = ""
-
-				' an initialised array of function pointers?
-				If Not IsArrayDef() And CParse( "[" )
-					Local ln:TExpr[]
-					Repeat
-						If CParse(",") Then
-							ln = ln + [New TNullExpr]
-							Continue
-						End If
-						If CParse("]") Exit
-						ln = ln + [ParseExpr()]
-						If CParse("]") Exit
-						Parse(",")
-					Forever
-					'Parse "]"
-					ty = ParseArrayType(ty)
-					'While CParse( "[]" )
-					'	ty=New TArrayType.Create(ty)
-					'Wend
-					init=New TNewArrayExpr.Create( ty,ln)
-					ty=New TArrayType.Create( ty, ln.length )
-				Else
-					While IsArrayDef()
-						ty = ParseArrayType(ty)
-					Wend
-
-					' check for function pointer init
-					If CParse("=") Then
-						init=ParseExpr()
-					Else
-						init=New TConstExpr.Create( ty,"" )
-					End If
-				End If
-
 			Else If toke<>"const"
 				init=New TConstExpr.Create( ty,"" )
 			Else
 				Err "Constants must be initialized."
 			EndIf
 		EndIf
+		
 
 		Local decl:TValDecl
 
@@ -2686,9 +2606,9 @@ End Rem
 		'parse this into something
 		Return meta
 	End Method
-
-
-	Method ParseFuncDecl:TFuncDecl( toke$,attrs:Int, returnType:TType = Null, parent:TScopeDecl = Null )
+	
+	
+	Method ParseFuncDecl:TFuncDecl( toke$, attrs:Int, parent:TScopeDecl = Null )
 		SetErr
 
 		If toke Parse toke
@@ -2701,140 +2621,85 @@ End Rem
 
 		Local classDecl:TClassDecl = TClassDecl(parent)
 
-		If Not returnType Then
-			If attrs & FUNC_METHOD
-				If _toke="new"
-					If attrs & DECL_EXTERN
-						Err "Extern classes cannot have constructors"
-					EndIf
-					id="New"
-					NextToke
-					attrs:|FUNC_CTOR
-					attrs:&~FUNC_METHOD
-				Else If _toke="operator" Then
-					attrs:|FUNC_OPERATOR
-					NextToke
-					
-					Local t:String = _toke.ToLower()
-					NextToke
-					
-					Select t
-						Case "*","/","+","-","&","|","~~"
-							id = t
-						Case ":*",":/",":+",":-",":&",":|",":~~"
-							id = t
-						Case "<",">"',"="',"<=",">=","=","<>"
-							If CParse("=") Then
-								t :+ "="
-							Else If t = "<" And CParse(">") Then
-								t :+ ">"
-							End If
-							id = t
-						Case "="
-							id = t
-						Case "mod", "shl", "shr"
-							id = t
-						Case ":mod", ":shl", ":shr"
-							id = t
-						Default
-							DoErr "Operator must be one of: * / + - & | ~~ :* :/ :+ :- :& :| :~~ < > <= >= = <> mod shl shr :mod :shl :shr"
-					End Select
-					ty=ParseDeclType()
-				Else
-					id=ParseIdent()
-					ty=ParseDeclType()
-					If ty._flags & (TType.T_CHAR_PTR | TType.T_SHORT_PTR) Then
-						DoErr "Illegal function return type"
-					End If
-	
-					' Delete() return type should always be Void
-					If id.ToLower() = "delete" Then
-						attrs:|FUNC_DTOR
-						If TIntType(ty) Then
-							ty = New TVoidType
-						End If
-					End If
+		If attrs & FUNC_METHOD
+			If _toke="new"
+				If attrs & DECL_EXTERN
+					Err "Extern classes cannot have constructors"
 				EndIf
+				id="New"
+				NextToke
+				attrs:|FUNC_CTOR
+				attrs:&~FUNC_METHOD
+				ty=ParseDeclType()
+			Else If _toke="operator" Then
+				attrs:|FUNC_OPERATOR
+				NextToke
+				
+				Local t:String = _toke.ToLower()
+				NextToke
+				
+				Select t
+					Case "*","/","+","-","&","|","~~"
+						id = t
+					Case ":*",":/",":+",":-",":&",":|",":~~"
+						id = t
+					Case "<",">"',"="',"<=",">=","=","<>"
+						If CParse("=") Then
+							t :+ "="
+						Else If t = "<" And CParse(">") Then
+							t :+ ">"
+						End If
+						id = t
+					Case "="
+						id = t
+					Case "mod", "shl", "shr"
+						id = t
+					Case ":mod", ":shl", ":shr"
+						id = t
+					Default
+						DoErr "Operator must be one of: * / + - & | ~~ :* :/ :+ :- :& :| :~~ < > <= >= = <> mod shl shr :mod :shl :shr"
+				End Select
+				ty=ParseDeclType()
 			Else
-				If Not (attrs & FUNC_PTR) Then
-					id=ParseIdent()
-					ty=ParseDeclType()
-					' can only return "$z" and "$w" from an extern function.
-					If ty._flags & (TType.T_CHAR_PTR | TType.T_SHORT_PTR) And Not (attrs & DECL_EXTERN) Then
-						DoErr "Illegal function return type"
-					End If
+				id=ParseIdent()
+				ty=ParseDeclType()
+				If ty._flags & (TType.T_CHAR_PTR | TType.T_SHORT_PTR) Then
+					DoErr "Illegal function return type"
 				End If
-			EndIf
-		End If
-		
-		Local args:TArgDecl[]
-
-		Parse "("
-		SkipEols
-		If _toke<>")"
-			Local nargs:Int
-			Repeat
-
-				Local argId$=ParseIdent()
 
-				Local ty:TType=ParseDeclType()
-
-				Local init:TExpr
-				' function pointer ?
-				If _toke = "(" Then
-
-					Local fdecl:TFuncDecl = ParseFuncDecl("", FUNC_PTR | DECL_ARG)
-
-					If Not ty Then
-						ty = New TFunctionPtrType
-						TFunctionPtrType(ty).func = fdecl
-					Else
-						fdecl.retType = ty
-						ty = New TFunctionPtrType
-						TFunctionPtrType(ty).func = fdecl
+				' Delete() return type should always be Void
+				If id.ToLower() = "delete" Then
+					attrs:|FUNC_DTOR
+					If TIntType(ty) Then
+						ty = New TVoidType
 					End If
-
-					TFunctionPtrType(ty).func.ident = argId
-
-					' function pointer array ?
-					While IsArrayDef()
-						ty = ParseArrayType(ty)
-					Wend
 				End If
-				
-				' var argument?
-				If CParse("var") Then
-					ty = TType.MapToVarType(ty)
-				Else If CParse( "=" )
-					init=ParseExpr()
+				' TODO: make sure Delete cannot be declared with parameters?
+			EndIf
+		Else
+			'If Not (attrs & FUNC_PTR) Then
+				id=ParseIdent()
+				ty=ParseDeclType()
+				' can only return "$z" and "$w" from an extern function.
+				If ty._flags & (TType.T_CHAR_PTR | TType.T_SHORT_PTR) And Not (attrs & DECL_EXTERN) Then
+					DoErr "Illegal function return type"
 				End If
-				
-				Local arg:TArgDecl=New TArgDecl.Create( argId,ty,init )
-				If args.Length=nargs args=args + New TArgDecl[10]
-				args[nargs]=arg
-				nargs:+1
-				If _toke=")" Exit
-
-				Parse ","
-			Forever
-			args=args[..nargs]
+			'End If
 		EndIf
-		Parse ")"
 		
-		If returnType Then
-			Return New TFuncDecl.CreateF(Null,returnType,args,attrs)
+		' every branch in that nested If block up there contains the line "ty=ParseDeclType()";
+		' this already consumed all sets of parentheses and brackets belonging to this function declaration
+		' so we will now extract our actual return type and args from the result
+		Local args:TArgDecl[]
+		If Not TFunctionPtrType(ty) Then
+			DoErr "Expecting function type"
+		Else
+			Local fdecl:TFuncDecl = TFunctionPtrType(ty).func
+			ty = fdecl.retTypeExpr
+			args = fdecl.argDecls
 		End If
 		
-		Local fdecl:TFuncDecl
-		' wait.. so everything until now was a function pointer return type, and we still have to process the function declaration...
-		If _toke = "(" Then
-			Local retTy:TType = New TFunctionPtrType
-			TFunctionPtrType(retTy).func = New TFuncDecl.CreateF("",ty,args,attrs )
-			TFunctionPtrType(retTy).func.attrs :| FUNC_PTR
-			fdecl = ParseFuncDecl("", attrs, retTy)
-			ty = retTy
-		End If
-
+		
 		If CParse( "nodebug" ) Then
 			attrs :| DECL_NODEBUG
 		End If
@@ -2889,12 +2754,12 @@ End Rem
 		If attrs & FUNC_CTOR Then
 			funcDecl=New TNewDecl.CreateF( id,ty,args,attrs )
 		Else
-			If fdecl Then
-				funcDecl = fdecl
-				funcDecl.ident = id
-			Else
+			'If fdecl Then
+			'	funcDecl = fdecl
+			'	funcDecl.ident = id
+			'Else
 				funcDecl=New TFuncDecl.CreateF( id,ty,args,attrs )
-			End If
+			'End If
 			funcDecl.noMangle = noMangle
 		End If
 		If meta Then
@@ -2995,6 +2860,43 @@ End Rem
 
 		Return funcDecl
 	End Method
+	
+	
+	Method ParseFuncParamDecl:TArgDecl[]()
+		Local args:TArgDecl[]
+		Parse "("
+		SkipEols
+		If _toke<>")"
+			Local nargs:Int
+			Repeat
+				
+				Local argId$=ParseIdent()
+
+				Local ty:TType=ParseDeclType()
+
+				Local init:TExpr
+				
+				' var argument?
+				If CParse("var") Then
+					ty = TType.MapToVarType(ty)
+				Else If CParse( "=" )
+					init=ParseExpr()
+				End If
+				
+				Local arg:TArgDecl=New TArgDecl.Create( argId,ty,init )
+				If args.Length=nargs args=args + New TArgDecl[10]
+				args[nargs]=arg
+				nargs:+1
+				If _toke=")" Exit
+
+				Parse ","
+			Forever
+			args=args[..nargs]
+		EndIf
+		Parse ")"
+		Return args
+	End Method
+	
 
 	Method ParseClassDecl:TClassDecl( toke$,attrs:Int )
 		SetErr
@@ -3246,7 +3148,7 @@ End Rem
 				If (attrs & CLASS_STRUCT) And (attrs & DECL_EXTERN) Then
 					Err "Structs can only contain fields."
 				EndIf
-				Local decl:TFuncDecl=ParseFuncDecl( _toke,method_attrs,,classDecl )
+				Local decl:TFuncDecl=ParseFuncDecl( _toke,method_attrs,classDecl )
 				If decl.IsCtor() decl.retTypeExpr=New TObjectType.Create( classDecl )
 				classDecl.InsertDecl decl
 			Case "function"
@@ -3263,7 +3165,7 @@ End Rem
 				If attrs & DECL_EXTERN Then
 					Err "Extern Types can only contain methods."
 				End If
-				Local decl:TFuncDecl=ParseFuncDecl( _toke,decl_attrs,,classDecl )
+				Local decl:TFuncDecl=ParseFuncDecl( _toke,decl_attrs,classDecl )
 				classDecl.InsertDecl decl
 			Default
 				Err "Syntax error - expecting class member declaration, not '" + _toke + "'"
@@ -3277,7 +3179,7 @@ End Rem
 	
 	Method ParseNativeStmt()
 		If Not _toke.StartsWith("'!") Then
-			Err "Syntax error - expecting !'"
+			Err "Syntax error - expecting '!"
 		End If
 		Local raw:String = _toke[2..]
 		_block.AddStmt New TNativeStmt.Create( raw )

+ 8 - 4
translator.bmx

@@ -886,12 +886,16 @@ End Rem
 		If Not decl.munged Then
 			MungDecl decl
 		End If
-
-		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.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 Not expr.InvokedWithBraces And expr.IsRhs Return decl.munged
 		
-		If Not expr.InvokedWithBraces And expr.IsRhs Return decl.munged
+		' if the call was a statement (even one written without parentheses), then invokedWithBraces is true
+		' so no complicated checks are needed here; if invokedWithBraces is false, this is definitely not a call
+		If Not expr.InvokedWithBraces Then Return decl.munged
 		
 		If decl.munged.StartsWith( "$" ) Return TransIntrinsicExpr( decl,Null,expr.args )
 		

+ 8 - 2
type.bmx

@@ -1740,8 +1740,14 @@ Type TFunctionPtrType Extends TType
 	End Method
 
 	Method EqualsType:Int( ty:TType )
-' TODO : compare function decl
-		Return TFunctionPtrType( ty )<>Null
+		If Not TFunctionPtrType(ty) Then Return False
+		Local tyfunc:TFuncDecl = TFunctionPtrType(ty).func
+		If Not tyfunc.retType.EqualsType(func.retType) Then Return False
+		If Not (tyfunc.argDecls.Length = func.argDecls.Length) Then Return False
+		For Local a:Int = 0 Until func.argDecls.Length
+			If Not tyfunc.argDecls[a].ty.EqualsType(func.argDecls[a].ty) Then Return False
+		Next
+		Return True
 	End Method
 	
 	Method ExtendsType:Int( ty:TType, noExtendString:Int = False, widensTest:Int = False )