FreeBASIC Grammar Part I

Forum for discussion about the documentation project.
AGS
Posts: 1284
Joined: Sep 25, 2007 0:26
Location: the Netherlands

FreeBASIC Grammar Part I

Post by AGS »

The FreeBASIC grammar is spread out across many pages of the manual.

So I thought it would be nice to get the grammar on one page.
And to get the grammar I took the FreeBASIC sources and extracted the lines containing FreeBASIC grammar rules.

This grammer has been written in a format somewhat similar to ebnf.

Keywords have been written in UPPERCASE.

Non - terminals have been written using CamelCase.

This grammar is very much a work in progress (not finished yet/contains errors).

FreeBASIC grammar (non-preprocessor)

This grammer has been written in a format somewhat similar to ebnf.

Keywords have been written "UPPERCASE".

Non - terminals have been written using CamelCase.

This grammar is very much a work in progress (not finished yet/contains errors).


Free"BASIC" grammer (non-preprocessor)

Alpha = "A" - "Z"
Digit = "0" - "9"
Eol = '\n' | '\l\f'
Hexdig = "A" - "F" | Digit
Octdig = "0" - "7"
Bindig = "0" | "1"
AlphaDigit = Alpha | Digit
Isuffix = "%" | "&"
Fsuffix = "!" | "#"
Suffix = Isuffix | Fsuffix | "$"

Expchar = "D" | "E"

AssignmentOperator = "=" | "*=" | "/=" | "\=" | "MOD=" | "^=" | "SHL=" | "SHR="
Operator = "=" | "<" | ">" | "+" | "-" | "*" | "/" | "\" | "^" | "SHL" | "SHR"

SttSeparator = (Separator | Eol)+ .

Separator = ":"

Delimiter = Separator | "." | "," | ";" | """ | "'"

Literal = Num_Literal
| Str_Literal Str_Literal* .

Id = (Alpha | "_") (AlphaDigit | "_")* [Suffix].

Hex_Oct_Bin = "H" Hexdig+
| "O" Octdig+
| "B" Bindig+

Float = "." Digit ( Digit )* (Fsuffix | ( Expchar [OpAdd] Digit Digit )* )* | ).

Num_Literal = Digit Dig_Dot_Nil I_Fsufx_Nil
| "." Float
| "&" Hex_Oct_Bin

Dig_Dot_Nil = Digit Dig_Dot_Nil
| ("."|Expchar) Float
| .

I_Fsufx_Nil = Isuffix # Is Integer
| Fsuffix # Is float
| "." # Is def### !!! context sensitive !!!

Str_Literal = "( ANY_CHAR_BUT_QUOTE )*". # less quotes

Comment = ' Any_Char Eol
MultiLineComment = "/'" (CommentSymbol)* "'/"
CommentSymbol = MultiLineComment | (Any_Char)*


Program = Line* [EOF] .

Line = [Label] [Statement] [Comment] Eol .

Label = Num_Lit
| Id ":" .

Statement = [Separator] [Declaration | ProcCallOrAssign | CompoundStatement | QuirkStatement | AsmBlock | Assignment]
(SttSeparator Statement)* .

Declaration = ConstDecl | TypeDecl | VariableDecl | ProcDecl | DefDecl | EnumDecl | OptDecl.

ConstDecl = "CONST" ["AS" SymbolType] ConstAssign ("," ConstAssign)*
ConstAssign = Id ["AS" SymbolType] "=" ConstExpression

TypeDecl = ("TYPE"|"UNION") Id [Alias Lit_str] [Field "=" Expression] [Comment] SttSeparator TypeBody "END" ("TYPE"|"UNION") .


TypeBody = ( (("UNION"|"TYPE") [Comment] SttSeparator
ElementDecl
"END" ("UNION"|"TYPE"))
| ElementDecl
| "AS" AsElementDecl )+ .

TypeBody = (TypeElementDecl | TypeMultElelementDecl | TypeProtoDecl)+ .

TypeElementDecl = Id [ArrayDecl| ":" Num_Lit] "AS" SymbolType ["=" Expression]

TypeMultElelementDecl = "AS" SymbolType Id [ArrayDecl | ":" Num_Lit] ["=" Expression]

TypeProtoDecl = "DECLARE" ( "CONSTRUCTOR" Params
| "DESTRUCTOR"
| "OPERATOR" Op Params
| "PROPERTY" Params
| ["STATIC"|"CONST"] ("SUB"|"FUNCTION") Params ) .


VariableDecl = ("REDIM" "PRESERVE"?|"DIM"|"COMMON") "SHARED"? SymbolDef
| "EXTERN" "IMPORT"? SymbolDef "ALIAS"u Str_Lit
| "STATIC" SymbolDef .


ProcDecl = "DECLARE" (("SUB"|"FUNCTION") ProcHeader | Operator OperatorHeader ) .

ProcHeader = Id [CallConvention] ["OVERLOAD"] ["ALIAS" Lit_String]
[Parameters] [["AS" SymbolType] | "CONSTRUCTOR"|"DESTRUCTOR"]
Priority? "STATIC"? "EXPORT"?

Parameters = "(" ParamDecl ("," ParamDecl)* ")" .

ParamDecl = ["BYVAL"|"BYREF"] Id [["(" ")"] ["AS" SymbolType]] ["=" (Num_Lit|Str_Lit)] .

SymbolType = ["CONST"] ["UNSIGNED"] (
"ANY"
| ("CHAR"|"BYTE")
| ("SHORT"|"WORD")
| ("INTEGER"|"LONG"|"DWORD")
| "SINGLE"
| "DOUBLE"
| ["W"]"STRING" ["*" Num_Lit]
| UserDefType
| ("FUNCTION"|"SUB") ("(" Parameters ")") ["AS" SymbolType] (["CONST"] ("PTR"|"POINTER"))* .

UserDefType = Id

OperatorHeader = Operator [CallConvention] ["OVERLOAD"] ["ALIAS" Lit_String] [Parameters] ["AS" SymbolType] ["STATIC"] ["EXPORT"]

DefDecl = ("DEFINT"|"DEFLNG"|"DEFSNG"|"DEFDBL"|"DEFSTR") (CHAR ("-" CHAR ","?)* .

OptDecl = "OPTION" ("EXPLICIT"|"BASE" Num_Lit|"BYVAL"|"PRIVATE"|"ESCAPE"|"DYNAMIC"|"STATIC")

ProcCallOrAssign= "CALL" Id ["(" ProcParamList ")"]
| Id ProcParamList?
| (Id | "FUNCTION" | "OPERATOR" | "PROPERTY") "=" Expression .

ProcParamList = ProcArg ("," ProcArg)* .
ProcArg = ["BYVAL"|"BYREF"] Id[("(" ")"] | Expression) .

EnumDecl = "ENUM" [Id] ["ALIAS" Lit_str] ["EXPLICIT"] [Comment] SttSeparator
EnumBody
"END" "ENUM" .

EnumBody = (EnumDecl ["," EnumDecl] [Comment] SttSeparator)+ .

EnumDecl = Id ["=" ConstExpression]

CompoundStatement = IfStatement
| ForStatement
| DoStatement
| WhileStatement
| SelectStatement
| ExitStatement
| ContinueStatement
| WithStatement
| ScopeStatement
| ExternStatament
| NameSpaceStatement

IfStatement = IfStatementBegin IfStatementBody IfStatementEnd

IfStamentBegin = "IF" Expression "THEN" IfStatementBody

IfStatementBody = (Statement)* ("ELSEIF" Expression "THEN" (Statement)*)* "ELSE" (Statement)*

IfStatementEnd = "END" "IF" | "ENDIF" |.

ForStatementBegin = "FOR" Id ["AS" DataType] "=" Expression "TO" Expression ["STEP" Expression] ForStatementBody ForStatementEnd.

ForStatementBody = (Statement)*

ForStatementEnd = "NEXT" [Id ("," [Id])]

DoStatement = DoStatementBegin DoStatementBody DoStatementEnd
DoStatementBegin = "DO" [("WHILE" | "UNTIL") Expression] .
DoStatementBody = (Statement)*
DoStatementEnd = "LOOP" [("WHILE" | "UNTIL") Expression] .

WhileStatement = WhileStatementBegin WhileStatementBody WhileStatementEnd
WhileStatementBegin = "WHILE" Expression .
WhileStatementBody = (Statement)*
WhileStatementEnd = "WEND"

SelectStatement = SelectStatementBegin SelectStatementBody SelectStatementEnd
SelectStatementBegin = "SELECT" "CASE" ["AS" "CONST"] Expression .
SelectStatementBody = (Case_Alternative)* [Final_Case_Alternative]
SelectStatementEnd = "End" "Select"

Case_Alternative = "CASE" (Case_ExpressionList) (Statement)*
Case_ExpressionList = (Expression [TO Expression])|"IS" (">"|"<"|"<="|">="|"<>"|"=")

Final_Case_Alternative = "CASE" "ELSE" (Statement)*

ExitStatement = "EXIT" ("FOR" | "DO" | "WHILE" | "SELECT" | "SUB" | "FUNCTION")

ContinueStatement = "CONTINUE" ("FOR" | "DO" | "WHILE")

WithStatement = WithStatementBegin WithStatementtBody WithStatementEnd
WithStatementBegin = "WITH" Id
WithStatementBody = (Statement)*
WithStatementEnd = "END" "WITH"

ScopteStatement = ScopeStatementBegin ScopeStatementBody ScopeStatementEnd
ScopeStatementBegin = "SCOPE"
ScopeStatementBody = (Statement)*
ScopeStatementEnd = "END" "SCOPE" .

ExternStatement = ExternstatementBegin ExternStatementBody ExternStatementEnd
ExternStatetemenBegin = "EXTERN" ManglingSpec ["LIB" Lit_Str] .
ManglingSpec = "C" | "C++" | "WINDOWS" | "WINDOWS"-"MS"
ExsternStatementBody = (Declaration)*
ExternStatementEnd = "END" "EXTERN"

NamespaceStatement = NameSpaceStatementBegin NameSpaceStatementBody NameSpaceStatementEnd
NameSpaceStatementBegin = "NAMESPACE" [Id [("ALIAS" Lit_String]] .
NameSpaceStatementBody = (Statement)*
NamespaceStatementEnd = "END" "NAMESPACE" .

QuirkStatement = PrintStatement
| GotoStatement
| DataStatement
| ArrayStatement
| LineInputStatement
| InputStatement
| PokeStatement
| FileStatement
| OnStatement
| WriteStatement
| ErrorStatement
| ViewStatement
| MidStatement
| "LS"etStatement
| WidthStatement
| GfxStatement

PrintStatement = ("PRINT"|"?") ["#" Expression ","] ["USING" Expression ";"] ([Expression] ";"|"," )*

GotoStatement = "GOTO" Label
| "GOSUB" Label
| "RETURN" [Label]
| "RESUME" ["NEXT"] .

DataStatement = "RESTORE" [Label]
| "READ" Variable ("," Variable)*
| "DATA" (Literal|Constant) ("," Literal|Constant)*

ArrayStatement = "ERASE" Id ("," Id)*
| "SWAP" Variable, Variable .

LineInputStatement = "LINE" "INPUT" [";"]? ("#" Expression| Expression) [","|";"] [Variable] .

InputStatement = "INPUT" [";"] (("#" Expression| String_Lit) [","|";"] Variable ("," Variable)*

PokeStatement = "POKE" Expression, Expression .

FileStatement = FileStatementOpen
| FileStatementClose
| FileStatementSeek
| FileStatementPut
| FileStatementGet
| FileStatementLock
| FileStatementName

FileStatementOpen = "OPEN" Expression
"FOR" FileStatementType

FileStatementType = (FileStatementText | FileStatementBinary)

FileStatementText = ("INPUT"|"OUTPUT"|"APPEND") [Encoding_Type] [Lock_Type] "AS" ["#"] FileNumber
Encoding_Type = ("ASCII"|"UTF8"|"UTF16"|"UTF32")
Lock_Type = ("SHARED"|"LOCK"[("READ"|"WRITE")])
FileNumber = Num_Literal

FileStatementBinary = ("BINARY"|"RANDOM") [Access_Type] [Lock_Type] "AS" ["#"] FileNumber ["LEN" "=" Expression]
Access_Type = "READ"
| "WRITE"


FileStatementClose = "CLOSE" (["#"] Expression)*
FileStatementSeek = "SEEK" ["#"] Expression "," Expression
FileStatementPut = "PUT" "#" Expression "," [Expression] "," Expression
FileStatementGet = "GET" "#" Expression "," [Expression] "," Variable
FileStatementLock = ("LOCK"|"UNLOCK") ["#"] Expression, Expression ["TO" Expression]
FileStatementName = "NAME" oldfilespec "AS" newfilespec

OnStatement = "ON" ["LOCAL"] (Keyword | Expression) ("GOTO"|"GOSUB") Label .

WriteStatement = "WRITE" ["#" Expression] ([Expression] "," )*

ErrorStatement = "ERROR" Expression
| "ERR" "=" Expression .

ViewStatement = "VIEW" ("PRINT" [Expression "TO" Expression]) .

MidStatement = "MID" "(" Expression{str}, Expression ("," Expression) ")" "=" Expression .

LsetStatement = "LSET" (String_Lit|UserDefinedType) (","|"=") Expression|"UDT"

WidthStatement = "WIDTH" [Expression] [,Expression]
| "WIDTH" "LPRINT" Expression
| "WIDTH" "#"(Expression | Expression), Expression


GfxStatement = GfxPset
| GfxCircle
| GfxPaint
| GfxDrawString
| GfxDraw
| GfxView
| GfxPalette
| GfxPut
| GfxGet
| GfxScreen
| GfxScreenRes
| GfxPoint
| GfxImageCreate

GfxPset = "PSET" [ Expr "," ] ["STEP"] "(" Expr "," Expr ")" ["," Expr]
GfxCircle = "CIRCLE" [ Expr "," ] ["STEP"] "(" Expr "," Expr ")" "," Expr (("," [Expr] ("," [Expr] ("," [Expr] ("," Expr ("," Expr)? )? )?)?)?)?
GfxPaint = "PAINT" [ Expr "," ] ["STEP"] "(" expr "," expr ")" ("," [expr] ("," [expr] ) )
GfxDrawString = "DRAW" "STRING" [ Expr "," ] ["STEP"] "(" Expr "," Expr ")" "," Expr ( "," Expr ( "," Expr ( "," Expr ( "," Expr )? )? )? )?
GfxDraw = "DRAW" [ Expr "," ] Expr
GfxView = "VIEW" [["SCREEN"] "(" Expr "," Expr ")" "-" "(" Expr "," Expr ")" ["," [Expr] ["," Expr]] ]
GfxPalette = "PALETTE" ["GET"] ((Using Variable) | [Expr "," Expr ["," Expr "," Expr]])
GfxPut = "PUT" [ Expr "," ] ["STEP"] "(" Expr "," Expr ")" "," ("(" Expr "," Expr ")" "-" "(" Expr "," Expr ")" ",")? Variable ["," Mode ["," Alpha]]
GfxGet = "GET" [ Expr "," ] ["STEP"] "(" Expr "," Expr ")" "-" ["STEP"] "(" Expr "," Expr ")" "," Variable
GfxScreen = "SCREEN" (num | ((expr [[["," expr] "," expr] expr] "," expr))
GfxScreenRes = "SCREENRES" expr "," expr [[["," expr] "," expr] "," expr]
GfxPoint = "POINT" "(" Expr [ "," [ Expr ] [ "," Expr ] ] ")"
GfxImageCreate = "IMAGECREATE" "(" Expr "," Expr [ "," [ Expr ] [ "," Expr ] ] ")"

AsmBlock = "ASM" [Comment] ":" (AsmCode [Comment] NewLine)+ "END" "ASM" .

AsmCode = (Text !("END"|Comment|Newline))*

Comment = (Comment_Char | "REM") ((Directive_Char Directive)
| (Any_Char_But_"EOL"*)) .

Directive = "INCLUDE" ["ONCE"] ":" "\"' Str_Lit "\"'
| "DYNAMIC"
| "STATIC" .

Assignment = ["LET"] Variable AssignmentOperator Expression
| Variable{Function Ptr} "(" ProcParamList ")" .

Expression = LogExpression .
LogExpression = LogOrExpression ( ("XOR" | "EQV" | "IMP") LogOrExpression )* .
LogOrExpression = LogAndExpression ( "OR" LogAndExpression )* .
LogAndExpression = RelExpression ( "AND" RelExpression )* .
RelExpression = CatExpression ( ("=" | ">" | "<" | '<>' | '<=' | '>=') CatExpression )* .
CatExpression = AddExpression ( "AND" AddExpression )* .
AddExpression = ShiftExpression ( ("+" | "-") ShiftExpression )* .
ShiftExpression = ModExpression ( ("SHL" | "SHR") ModExpression )* .
ModExpression = IntDivExpression ( "MOD" IntDivExpression )* .
MultExpression = ExpExpression ( ("*" | "/") ExpExpression )* .
ExpExpression = NegNotExpression ( "^" NegNotExpression )* .
NegNotExpression= ("-"|"+"|) ExpExpression
| Not RelExpression
| HighestPrecExpression .

HighestPrecExpression= AddrOfExpression
|( DerefExpression | CastingExpression | PtrTypeCastingExpression | ParentExpression ) [FuncPtrOrMemberDeref]
|AnonUDT
|Atom .

AddrOfExpression = "VARPTR" "(" HighestPrecExpression ")"
| "PROCPTR" "(" Proc ("(")")? ")"
| "@" (Proc ("(")")? | HighestPrecExpression)
| ("SADD"|"STRPTR") "(" (Variable|Const|Literal) ")" .


Variable = Id [ArrayIdx] [UdtMember] [FuncPtrOrMemberDeref]
|

ArrayIdx = "(" Expression ("," Expression)* ")" .

DerefExpression = ("*")+ HighestPrecExpression .

CastingExpr = "CAST" "(" DataType "," Expression ")"

PtrTypeCastingExpression = "CPTR" "(" DataType "," Expression ")"

ParentExpression = "(" Expression ")"
| "DEFINED"(" Id ")"
| Literal
| Not RelExpression .

FuncPtrOrDeref = FuncPtr "(" [Args] ")"
| MemberDeref .

MemberDeref = (('->' "DREF"* | "[" Expression "]" "."?) UdtMember)* .

UdtMember = MemberId ("." MemberId)*

MemberId = Id ArrayIdx?

AnonUDT = "TYPE" ["<" SymbolType ">"] "(" "..." ")"

Atom = Constant | Function | QuirkFunction | Variable | Literal .

Constant = Id .

Function = Id ["(" ProcParamList ")"] [FuncPtrOrMemberDeref] .
| Not RelExpression
| HighestPrecExpression .
| ( DerefExpression
| CastingExpression
| PtrTypeCastingExpression
| ParentExpression
| AnonUDT
| Atom .

QuirkFunction = MKXFunction
| CVXFunction
| StringFunction
| MathFunction
| ScreenFunction
| PeekFunction
| OpenFunction
| WidthFunction

MKXFunction = "MKD" "(" Expression ")"
| "MKS" "(" Expression")"
| "MKI" "(" Expression")"
| "MKL" "(" Expression")"
| "MKSHORT" "(" Expression")"
| "MKLONGINT" "(" Expression")"

CVXFunction = "CVD" "(" Expression ")"
| "CVS" "(" Expression")"
| "CVI" "(" Expression")"
| "CVL" "(" Expression ")"
| "CVSHORT" "(" Expression ")"
| "CVLONGINT" "(" Expression ")"

StringFunction = ["W"]"STR" "(" Expression ")"
| "LEFT" "(" Expression ")"
| "RIGHT" "(" Expression ")"
| "MID" "(" Expression "," Expression ["," Expression] ")"
| ["W"]"STRING" "(" Expression "," Expression ")" .
| "INSTR" "(" [Expression","] Expression, ["ANY"] Expression ")"
| "INSTRREV" "(" Expression, ["ANY"] Expression ["," Expression] ")"
| "RTRIM" "(" Expression[, "ANY" Expression ] ")"
| "LTRIM" "(" Expression [, "ANY" Expression ] ")"
| "TRIM" "(" Expression [, "ANY" Expression ] ")"

MathFunction = "ABS"( Expression )
| "ABS"(Expression)
| "SGN"( Expression )
| "FIX"( Expression )
| "FRAC"(Expression)
| "LEN"( DataType | Expression ) .
| "SIZEOF"(Expression)
| "SIN"( Expression )
| "ASIN"( Expression )
| "COS"( Expression )
| "ACOS"(Expression)
| "TAN"(Expression)
| "ATN"(Expression)
| "SQR"(Expression)
| "LOG"(Expression)
| "EXP"(Expression)
| "ATAN"(Expression)
| "INT"( Expression )


ScreenFunction = "SCREEN" "(" expr "," expr [ "," expr ] ")"
| "SCREEN" [ "(" ")" ]?

PeekFunction = "PEEK" "(" [SymbolType ","] Expression ")" .


Free"BASIC" preprocessor grammer


PreProcess = PpDefine
| PpMacro
| PpUndef
| PpIfDef
| PpIfnDef
| PpIfExpression
| PpElse
| PpPrint
| PpInclude
| PpIncludeLibrary
| PpLibraryPath
| PpError
| PpLine
| PpPragma

PpDefine = Id [!"WHITESPC" "(" Id ("," Id)* ")"] "LITERAL"*
PpMacro = "MACRO" Id "(" Id ("," Id)* ")" [Comment] Eol Literal* "ENDMACRO"
PpUndef = "#" "UNDEF" Id
PpIfDef = "#" "IFNDEF" Id
PpIfExpression = "#"IF" PpExpression
PpElse = "#" "ELSE"
PpPrint = "#" "PRINT" Literal*
PpInclude = "#" "INCLUDE" ["ONCE"] Lit_Str
PpIncludeLibrary = "#" "INCLIB" Lit_Str
PpLibraryPath = "#" "LIBPATH" Lit_Str
PpError = "#" "ERROR" Lit_Str
PpLine = "#" "LINE" Lit_Num [Lit_Str]
PpPragma = "#" "PRAGMA" Symbol ["=" Expression]
| "#" "PRAGMA" "PUSH" "(" Symbol ["," Expression] ")"
| "#" "PRAGMA" "POP" "(" symbol ")"

PpExpression = PpLogExpression
PpLogExpression = PpRelExpression ( ("AND" | "OR") PpRelExpression )* .
PpRelExpression = PpAddExpression ( ("=" | ">" | "<" | "<>" | "<=" | ">=") PpAddExpression )* .
PpAddExpression = PpMultExpression ( ("+" | "-") PpMultExpression )* .
PpMultExpression = PpParentExpr ( ("*" | "/" | "\") PpParentExpr )* .
PpParentExpr = "(" Expression ")"
| "DEFINED" "(" Id ")"
| Literal
| "NOT" PpRelExpression
Last edited by AGS on Feb 26, 2009 23:14, edited 10 times in total.
Conexion
Posts: 236
Joined: Feb 23, 2006 6:04

Post by Conexion »

Oooo, Purdy! It is looking nice so far! It does need some cleaning up, but that's awesome so far :)
AGS
Posts: 1284
Joined: Sep 25, 2007 0:26
Location: the Netherlands

Post by AGS »

Cleaned up the grammar some more today and added declaration rules. Next up will be the expressions.

And I'm glad at least someone appreciates the fruits of my labor ;)
AGS
Posts: 1284
Joined: Sep 25, 2007 0:26
Location: the Netherlands

Post by AGS »

Added big part of expression grammar today. FreeBASIC Grammar Part I could and should be ready by the end of this week.
VonGodric
Posts: 997
Joined: May 27, 2005 9:06
Location: London
Contact:

Post by VonGodric »

could you perhaps put it into code block ?
AGS
Posts: 1284
Joined: Sep 25, 2007 0:26
Location: the Netherlands

Post by AGS »

VonGodric wrote:could you perhaps put it into code block ?
I've put the 'finished' part of the grammar into codeblock.
AGS
Posts: 1284
Joined: Sep 25, 2007 0:26
Location: the Netherlands

Post by AGS »

Added many statements (mostly so called QuirckStatements) to the grammer. Did a small rewrite of the definition of the CompoundStatement.
The definition of the CompoundStatement isn't right yet.
aleofjax
Posts: 117
Joined: Oct 18, 2007 8:10

Post by aleofjax »

I don't understand this at all, but I'm fascinated with the concept. What other subjects could you break down this way. Math, perhaps? Biology? Chemistry? History? Art? Well, yeah. maybe not art.
rolliebollocks
Posts: 2655
Joined: Aug 28, 2008 10:54
Location: new york

Post by rolliebollocks »

aleofjax wrote:I don't understand this at all, but I'm fascinated with the concept. What other subjects could you break down this way. Math, perhaps? Biology? Chemistry? History? Art? Well, yeah. maybe not art.
Believe me when I tell you that people try to break down art in this exact same way generating sterile and dehumanized results simultaneously. Careers have been made out of missing the point.

rb
AGS
Posts: 1284
Joined: Sep 25, 2007 0:26
Location: the Netherlands

Post by AGS »

aleofjax wrote:I don't understand this at all, but I'm fascinated with the concept. What other subjects could you break down this way. Math, perhaps? Biology? Chemistry? History? Art? Well, yeah. maybe not art.
There is a nice article on wikipedia about what I'm trying to achieve http://en.wikipedia.org/wiki/Formal_grammar

The main advantage of writing down a formal syntax/grammar of a programming language is the possibility to feed the grammar to a compiler compiler and get the compiler compiler to build a parser for the language specified.

Whether I will get to that point (= to the point where I can feed the FreeBASIC grammar to a compiler compiler and get it to produce a working parser for the FreeBASIC language) remains to be seen but I'm hopeful.
marcov
Posts: 3454
Joined: Jun 16, 2005 9:45
Location: Netherlands
Contact:

Post by marcov »

aleofjax wrote:I don't understand this at all, but I'm fascinated with the concept. What other subjects could you break down this way. Math, perhaps? Biology? Chemistry? History? Art? Well, yeah. maybe not art.
Language predominately. Though natural language is considerably harder than artificial.

The foundations of grammars were done by Chomsky who targeted natural languages, not artificial ones.

I think not even something as simple DNA is really generally parsable using such constructs. (the lexer is, more or less, synthesizing proteins, but the parser (e.g. compare two parts of DNA not)) It relies too much on moving markers and pattern matching, and less on the interpretation of a linear stream of tokens
AGS
Posts: 1284
Joined: Sep 25, 2007 0:26
Location: the Netherlands

Post by AGS »

Added preprocessor rules, changed some things in the notation (UPPERCASE = keyword), added lots of other lines of grammer and removed the lines starting with ''.

Removed code tags around grammer because it changes the keywords in the grammer to lowercase.
TheMG
Posts: 376
Joined: Feb 08, 2006 16:58

Post by TheMG »

I would advise you change it to the format of [X] instead of X?, and "string literal".
AGS
Posts: 1284
Joined: Sep 25, 2007 0:26
Location: the Netherlands

Post by AGS »

TheMG wrote:I would advise you change it to the format of [X] instead of X?, and "string literal".
Thanks for the advice and I will change the grammar. So it's going to be [X] instead of X? and "keyword" instead of KEYWORD.
Last edited by AGS on Jan 18, 2009 17:29, edited 1 time in total.
TheMG
Posts: 376
Joined: Feb 08, 2006 16:58

Post by TheMG »

Yeah, thats just some of the more modern syntax rules. Also, theres {X} instead of X*. I noticed that there was a bit of confusion inside the syntax as to operator precedence. Remember that:

X | Y Z means X or Y, and, irrespective of which one was chosen, followed by Z. Furthermore, A | B C | D means A or B, followed by C or D. If you need it, use A | (B C) | D, which refers to A or B and C or D.
Post Reply