One for mark..
BlitzMax Forums/BlitzMax Programming/One for mark..
| ||
| Or anyone else who knows how to parse expressions, basically I'm writing a script language in bmax, Basic# if you like, like C# with the syntax of basic. It's going fine, it's all done parsed and converted into opcodes, but when it comes to running the code, I can't do an expression parser with oepration precendence. The current one posted below processes expressions but it does so in order. Here's the whole code. Here's the expression part it's self, Method ExecExpression( ep:expression.ep,index Var) nnum = ep.op[index].van Select ep.op[index].toke Case t_add,t_minus lop=ep.op[index].toke Case t_times lop=t_Times Case t_devide lop=t_devide Case T_numeric Select lop Case t_add lnum:+nnum Case t_minus lnum:-nnum Case t_times lnum:*nnum Case t_devide lnum:/nnum Default lnum = ep.op[index].van End Select End Select index+1 execexpression( ep,index ) End Method It simply fills a double variable or operates on it based on the last active opeator. Each expression contained within paranatheses(spellcheck, stat) are already grouped off by the parser(for no real reason other than to make it easier to process fast at run time) so (2+2*(4+4)) will be grouped off into two seperate expressions. The idea being I can process each individual expression, then create a simplified dynamic expression consisting of their whole values and then run that through the expression processor. Here's a test prog. Class Main int i function void program() i = 2*2 end function End Class
Strict
'DaVinchi2D
'
Import "tokens.bmx"
Global toke_id=0
Type deli
Field id
Global cur:TList
Field tag
Function deliTag( deli$,ntag )
Local del = deli[0]
For Local d:deli = EachIn cur
If d.id = del
d.tag=ntag
End If
Next
End Function
Function setcurrent( d:TList )
cur = d
End Function
Function isDel( in )
For Local de:Deli = EachIn cur
If de.id = in Return True
Next
Return False
End Function
Function hastag( in )
For Local de:Deli = EachIn cur
If de.id = in
If de.tag<>0 Return True
End If
Next
Return False
End Function
Function Create:Deli( word )
Local out:deli = New deli
out.id = word
Return out
End Function
Method debug()
Print "Delimiter Debug spool:"
Print "Actual id:"+id
Print "Textural referece "+Chr(id)
End Method
Function CreateDelis:TList( words$ )
Local dli:TList = CreateList()
Local wl = Len(words)
For Local j=1 To wl
Local d:Deli = deli.create( words[j] )
dli.addlast( d )
Next
cur = dli
Return dli
End Function
Function debugList( in:TList )
For Local v:Object = EachIn in
Local d:Deli = Deli(v)
d.debug()
Next
End Function
End Type
Type tokens
Field tokes:TList
Field toke:Object[]
Method set( tok:TList )
tokes = tok
toke = tok.toarray()
End Method
Function create:Tokens()
Return New tokens
End Function
Method New()
tokes = CreateList()
End Method
Method add( itoke:Token )
tokes.addlast( itoke )
toke = tokes.toarray()
End Method
Method debug()
For Local t:Token = EachIn tokes
Print t.id
Next
End Method
End Type
Type token
Field id$
Function Create:Token( toke$ )
Local out:token = New token
out.id = toke
Return out
End Function
Function CreateTokens:TList( tokes$ )
Local out:TList = CreateList()
Local tc = Len(tokes)
For Local j=1 To tc
Local nt:token = token.create( tokes[j] )
out.addlast( nt )
nt.debug()
Next
'Print "Approx " + CountList(out)+"Tokens were defined'
Return out
End Function
Method debug()
Print "Token symbolic info"
Print id
End Method
End Type
Type tokenizer
Function create:tokenizer()
Return New tokenizer
End Function
Method Tokenize:Tokens( text:String )
text = " "+text+" "
Local tk:Tokens = tokens.create()
Local lvc,fvc
lvc=-1
fvc=-1
Local tl= Len(text)
Local snc=0,igdot=0
For Local j=0 To tl-1
Local li = text[j]
If li = 39
If snc=0
fvc=j+1
snc=1
Else
lvc=j-1
snc=0
EndIf
EndIf
If li>47 And li<58
igdot = True
End If
Local skpdel=0
If snc=0
If deli.isdel( li )
If igdot = True
If li = 46
skpdel=True
End If
EndIf
If Not skpdel
If lvc<>fvc And fvc<>-1
If lvc<fvc lvc=fvc
Local tst$ = text[fvc..lvc+1]
' Print "Token:"+tst
tk.add( token.create( tst ) )
fvc=-1
lvc=-1
EndIf
If deli.hastag( li )
tk.add( token.create( Chr(li) ) )
Print "deli "+li+" Had a tag"
EndIf
igdot=False
End If
Else
If fvc=-1
fvc=j
Else
lvc=j
EndIf
EndIf
EndIf
Next
Return tk
End Method
End Type
Type scope
Method New()
vpool = CreateList()
scope.scopes.addlast( Self )
tokes = CreateList()
funcs = CreateList()
code = CreateList()
classes = CreateList()
End Method
Function debug()
For Local sc:scope = EachIn scope.scopes
Print "Scope Variables:"
For Local va:Varn = EachIn sc.vpool
Print "Variable :"+va.name+" Value:"+varValue( va )
Next
Print "Scope has "+sc.code.count()+" Lines of code"
Next
End Function
Method clone:Scope()
Local out:scope = New scope
For Local vn:Varn = EachIn vpool
out.vpool.addlast( vn )
Next
Return out
End Method
Method copyvars( in:scope )
For Local va:Varn = EachIn in.vpool
vpool.addlast( va )
Next
End Method
Method findvar:varn( nam:String )
For Local vn:varn = EachIn vpool
If vn.name = nam
Return vn
End If
Next
End Method
Method addvar( Va:Varn )
If va = Null
Print "Cannot add null variable."
Return
End If
For Local vn:varn = EachIn vpool
If vn.name.tolower() = va.name.tolower()
Throw "Variable |"+va.name+"| already exists within current scope"
End If
Next
vpool.addlast( va )
End Method
Field tokes:TList
Field vpool:TList
Field own:scope
Global scopes:TList
Field funcs:TList
Method addfunc( fun:func )
funcs.addlast( fun:Func )
End Method
Field classes:TList
Method addclass( clas:Class )
classes.addlast( clas )
End Method
Field code:TList
End Type
scope.scopes=CreateList()
Type varn Abstract
Field name$
Field val
End Type
Type vari Extends varn
Field val%
End Type
Type varf Extends varn
Field val#
End Type
Type vard Extends varn
Field Val!
End Type
Type vars Extends varn
Field val$
End Type
Type varia Extends varn
Field val%[]
End Type
Type varfa Extends varn
Field val#[]
End Type
Function varValue:String( va:Varn )
If vari(va)<>Null
Local vai:Vari = vari(va)
Return vai.val
End If
If varf(va)<>Null
Local vaf:varf = varf(va)
Return vaf.val
End If
If vard(va)<>Null
Local vad:vard = vard(va)
Return vad.val
End If
If vars(va)<>Null
Local vas:vars = vars(va)
Return vas.val
End If
End Function
Type class Extends varn
Method New()
code = CreateList()
funcs= CreateList()
class.classes.addlast( Self )
End Method
Method findfunc:Func( nam:String )
For Local fun:func = EachIn funcs
If fun.name = nam Return fun
Next
Return Null
End Method
Function find:Class( nam:String )
For Local cla:class = EachIn class.classes
If cla.name = nam
Return cla
End If
Next
Return Null
End Function
Field classto$
Field scop:Scope
Field code:TList
Field funcs:TList
Field be,fi
Global classes:TList
Field real:Class
End Type
class.classes = CreateList()
Type func
Method New()
in = CreateList()
End Method
Field name:String
Field scop:Scope
Field in:TList
Field be,fi
Field ops:opline[5000],opl
Method addOp( op:Opline )
ops[opl] = op
opl:+1
End Method
Field toke:Tokens[5000],toc
Method AddTokeLine( ntoke:tokens )
toke[ toc ] = ntoke
toc:+1
End Method
End Type
Type Cpu
Field mem:Byte Ptr 'global memory heap
Field stack:Byte Ptr 'local dynamic stack
Field msize,ssize
Function Create:Cpu( memsize = 32,stacksize =1 )
Local out:Cpu = New cpu
out.mem = MemAlloc( memsize*1024 )
out.stack = MemAlloc( memsize*1024 )
out.msize = memsize
out.ssize =stacksize
Return out
End Function
Method Delete()
MemFree mem,msize*1024
MemFree stack,ssize*1024
End Method
Method run:varn( main:Class )
Local pf:Func = main.findFunc("program")
If pf = Null
Print "Program function not defined or illegally defined."
End
End If
Print "Found main func."
ato=Null
runFunc( pf )
End Method
Method runfunc( in:func )
For Local j=0 Until in.opl
Local op:opline = in.ops[j]
Local index=0
ExecOp( op,index )
Next
End Method
Method ExecOp( op:Opline,index Var )
If index=>op.opl Return
If op.op[index].ep<>Null
Local eindex=0
ExecExpression( op.op[index].ep,eindex )
Print "Expression result:"+lnum
End If
Select op.op[index].toke
Case t_var
If index+1<op.opl
Select op.op[index+1].toke
Case t_assign
index:+2
ExecOp(op,index)
Return
End Select
End If
Case t_class
Select op.op[index+1].toke
Case t_entry
index:+2
ExecOp(op,index)
Return
End Select
Case t_funccall
index:+1
ExecOp(op,index)
Return
End Select
End Method
Local ostack[255],oc
Local val![255],vc
Local cnum!,lnum!,lop
Method ExecExpression( ep:expression.ep,index Var)
nnum = ep.op[index].van
Select ep.op[index].toke
Case t_add,t_minus
lop=ep.op[index].toke
Case t_times
lop=t_Times
Case t_devide
lop=t_devide
Case T_numeric
Select lop
Case t_add
lnum:+nnum
Case t_minus
lnum:-nnum
Case t_times
lnum:*nnum
Case t_devide
lnum:/nnum
Default
lnum = ep.op[index].van
End Select
End Select
index+1
execexpression( ep,index )
End Method
Field num![255],nv
Field opv[255],ov
Field anum!,eop
Method procExp( op:opline,ind Var )
End Method
Field expnum!
Field ato:varn
Method procSeq( ops:opline,ind Var )
Local op:Opcode = ops.op[ind]
Select op.toke
Case t_var
End Select
End Method
End Type
Type expression
Field op:opcode[255],opl
Method addToke( opc:opcode)
op[opl]=opc
opl:+1
End Method
Field lval!,lvas$
End Type
Type opline
Field op:opcode[255],opl
Field ep:expression[255],ec,ce
Method newexp:expression()
ep[ec] = New expression
ec:+1
Return ep[ec-1]
End Method
Method addExp(opc:opcode)
ep[ce].addtoke( opc )
End Method
Method backExp()
ce=ce-1
If ce<-1
Print "Attempt to write to expression that does not exist."
End
End If
End Method
End Type
Type opcode
Field toke
Field ep:expression
Field Vo:varn
Field vas:String
Field van:Double
Method debug()
Print "Toke Debug:"+toke
Print "VAS:"+vas+" VAN:"+String(van)
End Method
End Type
Type Parser
Field toker:Tokenizer
Field prog:TList
Method New()
toker = New tokenizer
prog = CreateList()
End Method
Method Debug()
For Local tk:tokens =EachIn prog
For Local toke:Token = EachIn tk.tokes
Print "Token |"+toke.id+"|"
Next
Next
End Method
Method LoadApp( file:String )
Local fi = ReadFile(File)
If fi =0
Print file+" not found."
End If
While Not Eof(fi)
prog.addlast( toker.tokenize( ReadLine(fi) ) )
Wend
CloseFile fi
Print "App has "+CountList( prog)+" lines of code"
End Method
Method parse:class()
Local gMode=0
Local mainscope:Scope = New scope
Local cscope:Scope = mainscope
Local cclass:Class
Local lscope:Scope
Local cfunc:func
Local l_gmode
Local fs = WriteFile( "test.cpp" )
Local tokel=0
For Local tk:Tokens = EachIn prog
Local toka:Object[] = tk.tokes.toarray()
If toka.length=0 Continue
Local toke:token[ toka.length ]
For Local j=0 To toka.length-1
toke[j] = token( toka[j] )
toke[j].id = toke[j].id.tolower()
Next
Local isCode=True
Select toke[0].id
Case "class"
Local className:String = toke[1].id
Print "New class "+Classname
l_gmode = gmode
gmode = g_inclass
cclass = New class
cclass.scop = New scope
cscope = cclass.scop
cscope.own = mainscope
cclass.name = classname
iscode=False
cclass.be = tokel
Case "function"
Print "New Function"
Local retType:String = toke[1].id
Local funcname:String = toke[2].id
Print "Function name:"+funcname+" Return type:"+rettype
lscope = cscope
Local fun:func = New func
cscope.addfunc( fun )
If gmode=g_inclass
fun.scop = cscope.clone()
Else
fun.scop = mainscope.clone()
EndIf
If cclass<>Null
cclass.funcs.addlast( fun )
End If
fun.name = funcname
fun.scop.own = lscope
cscope = fun.scop
l_gmode = gmode
gmode = g_infunc
'GenVars( toke,4,fun.scop,fun.in )
iscode=False
fun.be=tokel
cfunc=fun
Case "end"
If toke.length>1
Select toke[1].id
Case "class"
If gmode<>g_inclass
Throw "End class without class definition"
End If
gmode = l_gmode
cclass.fi=tokel
cclass = Null
cscope = mainscope
Print "End of class definition"
iscode=False
Case "function"
If gmode<>g_infunc
Print "End function without function definition"
End If
cfunc.fi = tokel
cfunc=Null
gmode = l_gmode
cscope = lscope
iscode=False
End Select
End If
'Case "int","float","double","string"
' Print "variable type:"+toke[0].id
' For Local j=1 Until toke.length
' Local va:Varn = genvar( toke[0].id,toke[j].id )
' cscope.addvar(va)
' Next
' iscode=False
End Select
' If iscode
' cscope.code.addlast( tk )
'EndIf
If cfunc<>Null
cfunc.addtokeline( tk )
End If
tokel:+1
Next
Local pcode:Object[] = prog.toarray()
For Local Cla:Class = EachIn class.classes
cscope = cla.scop
For Local j=cla.be To cla.fi
Local tk:Tokens = tokens( pcode[j] )
Local toka:Object[] = tk.tokes.toarray()
If toka.length=0 Continue
Local toke:token[ toka.length ]
For Local j=0 To toka.length-1
toke[j] = token( toka[j] )
toke[j].id = toke[j].id.tolower()
Next
Select toke[0].id
Case "int","float","double","string"
Print "variable type:"+toke[0].id
For Local j=1 Until toke.length
Print "Var Name:"+toke[j].id
Local va:Varn = genvar( toke[0].id,toke[j].id )
cscope.addvar(va)
Next
Case "function"
Local fun:func = cla.findfunc( toke[2].id )
If fun = Null
Print "Syntax error. Function "+toke[2].id+" illegally defined."
End
End If
cfunc = fun
cscope = fun.scop
GenVars( toke,4,fun.scop,fun.in )
' fun.be = j
Case "end"
If toke.length>1
If toke[1].id="function"
cscope = cla.scop
' cfunc.fi = j
End If
End If
Default
If toke.length>1
Local vcl:Class = class.find( toke[0].id )
If vcl<>Null
Local vn:Varn= genvar( toke[0].id,toke[1].id )
cscope.addvar( vn )
End If
End If
End Select
Next
Next
For Local cla:Class = EachIn class.classes
For Local fun:func = EachIn cla.funcs
fun.scop.copyvars( cla.scop )
Print "Func name:"+fun.name
Print "Start line:"+fun.be
Print "Fin line:"+fun.fi
For Local j=1 To fun.toc-1
Local tk:Tokens = fun.toke[j] 'tokens( pcode[j] )
Local toka:Object[] = tk.tokes.toarray()
If toka.length=0 Continue
Local toke:token[ toka.length ]
For Local k=0 To toka.length-1
toke[k] = token( toka[k] )
toke[k].id = toke[k].id.tolower()
Next
Local ol:opline = New opline
Local ade=0
For Local k=0 Until toke.length
Local tokeid= tokeType( toke,k,cla,fun)
Print "Token:"+tokeid
Local oc:opcode = New opcode
oc.toke = tokeid
ol.op[ol.opl]=oc
ol.opl:+1
Select tokeid
Case t_var,t_class
Local vn:varn = fun.scop.findvar( toke[k].id )
oc.vo = vn
Case t_numeric
oc.van = Double(toke[k].id)
Print "Added Numeric :"+toke[k].id
If Mid(toke[k].id,toke[k].id.length,1)="f"
Print "Was a floating point numeric"
Else
If Instr(toke[k].id,".")>0
Print "Was a double"
Else
Print "Was a int."
End If
End If
Case t_string
oc.vas = toke[k].id
End Select
Next
Local index=0
processExpression( ol,index)
fun.addop( ol )
Next
Next
Next
Local cla:class = class.find( "main" )
If cla = Null
Print "Main class not defined or illegally defined."
End
End If
Return cla
End Method
Method ProcessExpression( op:opline,index Var )
If index=>op.opl Return
Select op.op[index].toke
Case t_var
If index+1<op.opl
Select op.op[index+1].toke
Case t_assign
index:+2
processExpression(op,index)
Return
End Select
End If
Case t_class
Select op.op[index+1].toke
Case t_entry
index:+2
processExpression(op,index)
Return
End Select
Case t_funccall
index:+1
processExpression(op,index)
Return
End Select
Print "Expressin toke id:"+op.op[index].toke
Select op.op[index].toke
Case t_scopein
Local ep:Expression = op.newexp()
op.op[index].ep = ep
Case t_scopeout
op.backexp()
Default
op.addExp( op.op[index] )
op.op[index].debug()
End Select
index:+1
processExpression(op,index)
End Method
Method procop( op:opline )
Select op.op[0].toke
Case t_var
End Select
End Method
Method tokeType( toke:token[],ind Var,inclass:class,infunc:func)
Print "Token for:"+toke[ind].id
Select toke[ind].id
Case "if"
Return t_if
Case "("
Return t_scopeIn
Case ")"
Return t_scopeout
Case "else"
Return t_else
Case "."
Return t_entry
Case "new"
Return t_new
Case "end"
Select toke[ind+1].id
Case "if"
ind:+1
Return t_endif
Case "select"
ind:+1
Return t_endselect
End Select
Case "case"
Return t_case
Case "select"
Return t_select
Case "for"
Return t_for
Case "next"
Return t_next
Case "step"
Return t_step
Case "+"
Return t_add
Case "-"
Return t_sub
Case "/"
Return t_devide
Case "*"
Return t_times
Case "="
Return t_assign
End Select
Local cla:class = class.find( toke[ind].id )
If cla<>Null
Return t_class
End If
Local fun:func = inclass.findfunc( toke[ind].id )
If fun<>Null
Return t_funccall
End If
If infunc.scop = Null
Else
Local va:Varn = infunc.scop.findvar( toke[ind].id )
If va<>Null
Return t_var
End If
End If
If toke[ind].id[0]>47 And toke[ind].id[0]<58
Return t_numeric
End If
Return t_funccall
End Method
Method genVars( toke:Token[],from,scop:scope,tl:TList )
For Local j=from Until toke.length Step 2
Select toke[j].id
Case "("
Case ")"
Return
Default
Print "Toke ID:"+toke[j].id
Local vn:Varn = genvar( toke[j].id,toke[j+1].id )
If vn <>Null
tl.addlast( vn )
scop.addvar( vn )
End If
End Select
Next
End Method
End Type
Function genVar:Varn( typ:String,name:String)
Select typ
Case "int"
Local out:vari = New vari
out.name=name
Return out
Case "float"
Local out:varf = New varf
out.name=name
Return out
Case "double"
Local out:vard = New vard
out.name=name
Return out
Case "string"
Local out:vars = New vars
out.name=name
Return out
Default
Local cla:class = class.find(typ)
If cla<>Null
Local out:class = New class
out.name = name
out.real = cla
Return out
Else
Print "Unknown variable type:"+typ
End
End If
End Select
End Function
Function err(cond,error$,resp=1)
If cond=True Return
Print error
Select resp
Case 1
End
End Select
End Function
Const g_main=1,g_inclass=2,g_infunc=3,g_intemplate=5
Const Scope_Entry=1,Scope_Exit=2
Const Assign = 3,Minus=4,Plus=5,Times=7,Devide=8
Const classentry=9
Const delimiters:String = "{}[]';;!@#$%^&*()_+=-/.,?{><\|<> ` "
Global maindel:TList = deli.createdelis( delimiters )
deli.delitag( "(",Scope_Entry )
deli.delitag( ")",Scope_Exit )
deli.delitag( "=",Assign )
deli.delitag( "-",Minus)
deli.delitag( "+",Plus)
deli.delitag( "*",Times)
deli.delitag( "/",Devide)
deli.delitag( ".",ClassEntry)
Local tp:Parser = New parser
tp.loadapp("test.txt")
Local prog:Class
Print "Debug ------"
Try
prog = tp.parse()
Catch s$
Print s
End
End Try
Local cp:Cpu = cpu.create()
cp.run( prog )
End
|
| ||
| Some example code would be great. Something that works on the assumption each element in the expression is a unique object, like in my code. I.e fill out this template [code] type obj field val,typ end type local o1,o2,o3 o1:obj = createValue("1") o2:obj = CreateOperator("+") o3:obj = createValue("5") I.e i'm not looking for something that parses or tokenizes the expression, that's already done. |
| ||
'tokes Const t_if=1,t_else=2,t_endif=3 Const t_select=4,t_case=5,t_endselect=6 Const t_funccall=7,t_assign=8,t_var=9,t_class=10 Const t_constant=11,t_string=12,t_numeric=13 Const t_add=14,t_sub=15,t_times=16,t_devide=17 Const t_is=18,t_for=19,t_next=20,t_step=21,t_entry=22,t_new=23 Const t_scopein=24,t_scopeout=25 forgot the tokens import. |
| ||
'tokes Const t_if=1,t_else=2,t_endif=3 Const t_select=4,t_case=5,t_endselect=6 Const t_funccall=7,t_assign=8,t_var=9,t_class=10 Const t_constant=11,t_string=12,t_numeric=13 Const t_add=14,t_sub=15,t_times=16,t_devide=17 Const t_is=18,t_for=19,t_next=20,t_step=21,t_entry=22,t_new=23 Const t_scopein=24,t_scopeout=25 forgot the tokens import. |
| ||
| Try Googling "Operator Precedence Parsing". It is good just for parsing expressions, but not very good for parsing entire languages, although it is possible. |
| ||
| A great way to go about it is writing a Post Fix to Reverse Polish Notation convertor, from there you can simply write a 'stack machine' based operation. Infact I wrote one for blitz3d a while ago, should be in the code archives. Click on my name. :) (btw, hey antony, long time no talk XD) http://www.blitzbasic.com/codearcs/codearcs.php?code=926 (Pardon the old ugly code!) Oh, and also my math evaluator - http://www.blitzbasic.com/codearcs/codearcs.php?code=931 Can't remember how good it is, I'm not sure if it can do negative numbers, haha.. |
| ||
| you might find some help in (the old) Crenshaws "Let's build a compiler" series.. here; http://compilers.iecc.com/crenshaw/ |
| ||
| Zenith, your the second person I've seen suggest that. Could you elabrotate a bit more on what doing that would actually entail? I'm useless at understanding other people's code unless it's laden with comments and pointed out to me as if I was an idiot. Because in all probabilities, I am. Largs, thanks, already found that one and found it to be as much help as a umbrella in space. |
| ||
| Yeah, I'm teh same way with code -- sorry. Basically, I dont' even know what I did, I havn't touched the code in about 2 years. :) But here's the article I looked at (other than the red dragon compiler book!) http://www.qiksearch.com/articles/cs/infix-postfix/ |
| ||
| So you had no prior knowledge once you looked at that article? Cos I'm basically in the same boat, despite all the above(All coded based on Antony-Techniques (c)2005 rather than any pre-existing methods.) I found all the tutorials to be...like the jungle. Big and scary. |
| ||
| If you want to learn how to write compilers use the book that Zenith mentioned, its real title is something like Compilers: Principles, Tools, and something like that by Aho Sethi and Ullman, but it is better know as "The Dragon Book" because of the dragon on its cover. Talks about everything used in compiler design from Lexical Analysis to Parsing to Bootstraping a compiler. I would like to know, did you write a specific grammar for your compiler and then work from there and translate that into BMX code, or did you just work from your head into BMX? |
| ||
| I invented the grammar as it were on the fly. It's an almagmation(spell check, that.) of C# and basic though in reality so it's not like I re-invented the wheel. |
| ||
| http://en.wikipedia.org/wiki/Postfix_notation#Converting_from_infix_notation When I made some scripting languages in b3d I wrote this section of a wikipedia article as no other website seemed to have a complete outline of how to parse math. |
| ||
| Thanks bot. Any interest in co-writing the script engine bot or anyone with the knowledge, for a share of the profits when it goes commercial? Even if it's just working on the maths parsing problem bit. I could do with some help as tutorials just don't seem to stick. |
| ||
| Been reading your site Bot, seems like the way to go but any chance you could knock up a simple conversation function example that takes tokens and converts them into rpn notion? Here's the template code so all you have to do is fill in the blanks, and i'll use this as a basis for conversation. I'll throw in a free license to this once done, it'll be a script language for bmax + a virtual machine for non blitz maxers like net framework is.
type token
field toke,number#
end type
const toke_add=1,toke_plus=2,toke_function=3,toke_sub=4,toke_devide=5
function NewToken:Token(typ,num=0)
local t:token = new token
t.toke = typ
t.number = num
return t
end function
'example
local tokes:Token[10]
tokes[0] = new Token(toke_number,4); number token
toke
tokes[1] = new Token(toke_add)
tokes[2] = new token(toke_number,5)
tokes[3] = new token(toke_times)
tokes[4] = new token(toke_number,2)
function convert:token[](tokes:token[])
for local j=0 until tokes.length
next
end function
|
| ||
| I've coded a simple converter that works for very simple expressions like 4+4-2 but I still don't get it. Say you have an expression 4-2+4+4? it'll be converted to, 4244-++ How does that help me? There's no way of knowing the order of the operations. Or do I keep the value and operator stacks seperate when actually evaluating? Local op:opline = New opline op.op[0] = New opcode op.op[1] = New opcode op.op[2] = New opcode op.opl=3 op.op[0].toke=t_numeric op.op[0].van = 4 op.op[1].toke=t_add op.op[2].toke=t_numeric op.op[2].van = 8 op.debugenglish() op = conviff( op ) op.debugenglish() Function conviff:opline( op:opline ) Local opstack:opcode[255],oc Local out:opline = New opline For Local j=0 Until op.opl Select op.op[j].toke Case t_add,t_sub,t_devide,t_times opstack[oc]=op.op[j] oc:+1 Case t_numeric out.op[out.opl]=op.op[j] out.opl:+1 End Select Next For Local j=0 Until oc out.op[out.opl] = opstack[j] out.opl:+1 Next Return out End Function |
| ||
| For the operation order (*/ before +-) you could handle the +- expressions as encapsulated part. So a+b*c-d would become (a+b)*(c-d) -> ab+cd-* or similar Beside that your conversion seems to be wrong, it should be: 42-4+4+ if it is meant to work as single stack (With that information you can create a parsing tree with operators in tree nodes and values in leaves, which is what you wanted to know) |
| ||
Yeah I think you can create a tree like:
4-2+4+4:
+
/ \
+ 4
/ \
- 4
/ \
4 2
That would be the parse tree for the infix notation 4-2+4+4. Then you just go from bottom to top to convert to RPN: Push '4' onto the stack, then '2' cause that is the bottom most leaf. Then you push '-' onto the stack cause that is the next level up. At that same level is another '4' which you push onto the stack. Then up a level is '+' and '4' and then the final level of '4'. So then your stack contains '42-4+4+' which is the RPN version of your equation. Basically you just push them onto the stack in the order you find them going from left to right and bottom to top in the parse tree. |
| ||
| Bah it's still all double dutch to me. Anyone who helps me code this gets a free copy of vivid.2d.net and any other project I make in the future. I just can't do it. It's like there's some sort of dampening field obscuring the knowledge in my brain. |
| ||
| Antony, Contact me via email (spammehere@...). I have code that parses math. I wrote it in Delphi, but you should be able to follow the logic of it. I can also try to explain how it works. It's easier then it looks :-) |
| ||
| will do, thanks. you'll have to explain really, 'cos i've seen code examples, even simple ones wrote in blitz, but it just doesn't compute. I'm an idiot. |
| ||
| You're not a complete idiot, I struggled with the same problem for almost a year or two(on and off). When you figure it out, you won't be able to express it in words; Maybe syllables, but that's about it. :) |
| ||
| Thanks, although there is still the possibility that we're both complete idiots, explaining the snergy :) |