Phillip Trelford's Array

POKE 36879,255

Small Basic Parser

Microsoft Small Basic is a minimal implementation of the BASIC programming language aimed at beginners. In my last article I described the implementation of an interpreter for Small Basic using an internal DSL to specify the abstract syntax tree (AST) for programs.

With the AST for the language well defined, a text parser for Small Basic programs is now relatively easy. There are quite a few options for writing parsers in F# from FsxLex and FSYyacc to hand rolled recursive descent parsers and parser combinator libraries.

For the expression parser in the open source spreadsheet Cellz, I initially used a simple parser combinator implementation based on an F# Journal article by Jon Harrop. Later I changed it to a hand rolled recursive descent parser using F# Active Patterns. Tomas Petricek has a chapter in F# Deep Dives which uses active patterns for parsing Markdown, the syntax used for Stack Overflow posts.

FParsec

To try something new, I decided to use the open source FParsec parser combinator library. FParsec, written by Stephan Tolksdorf, has great documentation including an in depth tutorial and user guide along with a convenient Nuget package. FogCreek use FParsec for parsing search queries.

With FParsec, parsers for code fragments can be written as simple functions and then composed into larger parsers for values, expressions, statements and programs. A parser can be written incrementally using the F# interactive environment giving quick feedback as you go. The library also gives really helpful error messages with line and column numbers when a parser fails.

I spent around an hour going through the tutorial which provided enough detail to get started on a parser for Small Basic. A Small Basic program is composed of statements, with one statement per line.

Parsing literals

Small Basic supports a small range of value types:

/// Small Basic value
type value =
    | Bool of bool
    | Int of int
    | Double of double
    | String of string

A parser for the boolean literal values “true” or “false” can be defined using stringReturn:

let ptrue = stringReturn "true" true
let pfalse = stringReturn "false" false

The parsers can then be combined to be either true or false using the <|> operator:

let pbool = ptrue <|> pfalse

To take the boolean parser to a value type we use the |>> pipeline combinator:

let pbool = (ptrue <|> pfalse) |>> fun x -> Bool(x)

FParsec contains parsers for many primitive types including integers:

let pint = pint32 |>> fun n -> Int(n)

These parsers can then be combined to create a parser for values:

let pvalue = pbool <|> pint // ...

Parsing expressions

Next up are Small Basic’s expressions:

/// Small Basic expression
type expr =
    | Literal of value
    | Var of identifier
    | GetAt of location
    | Func of invoke
    | Neg of expr
    | Arithmetic of expr * arithmetic * expr
    | Comparison of expr * comparison * expr
    | Logical of expr * logical * expr

A parser for literals can be created using the value parser:

let pliteral = pvalue |>> fun x -> Literal(x)

Identifiers are expected to start with a letter or underscore and may contain numerals. The FParsec tutorial contains a handy example:

let pidentifier =
    let isIdentifierFirstChar c = isLetter c || c = '_'
    let isIdentifierChar c = isLetter c || isDigit c || c = '_'
    many1Satisfy2L isIdentifierFirstChar isIdentifierChar "identifier"

This can be used to define a parser for variable names:

let pvar = pidentifier |>> fun name -> Var(name)

This can then be used to define a parser for simple expressions:

let pexpr = pliteral <|> pvar

Operators can be easily parsed using the built-in operator precedence parser described in the user guide.

Parsing statements

The longest of Small Basic’s statements is the for loop:

/// Small Basic assignment
type assign =
    | Set of identifier * expr
/// Small Basic instruction
type instruction =
    | Assign of assign
    | For of assign * expr * expr

A for statement is composed of an assignment and expressions for the end value and step:

For A=1 To 100 Step 1

To parse the assignment the pipe3 combinator can be used for the constituent parts:

let pset = pipe3 pidentifier (pstring "=") pexpr (fun id _ e -> Set(id, e))

The parser for the from, to and step components can be combined as:

let pfor =
    let pfrom = pstring "For" >>. spaces1 >>. pset
    let pto = pstring "To" >>. spaces1 >>. pexpr
    let pstep = pstring "Step" >>. spaces1 >>. pexpr
    let toStep = function None -> Literal(Int(1)) | Some s -> s
    pipe3 pfrom pto (opt pstep) (fun f t s -> For(f, t, toStep s))

It can be tested in F# interactive using the run function:

run pfor "For A=1 To 100"

Which produces a statement from the parser:

val it : ParserResult<instruction,unit> =
  Success: For (Set ("A",Literal (Int 1)),Literal (Int 100),Literal (Int 1))

Parsers for statements can be combined using the <|> operator or choice function:

let pstatement = 
    choice [
        attempt pfor
        // ... other statements
    ]

Parsing programs

Small Basic supports comments at the ends of the line:

let pcomment = 
    pchar '\'' >>. skipManySatisfy (fun c -> c <> '\n') >>. pchar '\n'

Thusly the end of a line is characterized either by a comment or a new line character:

let peol = pcomment <|> (pchar '\n')

The lines of the program can be parsed using the many function:

let plines = many (spaces >>. pstatement .>> peol) .>> eof

Finally the program can be parsed by applying the run function:

let parse (program:string) =    
    match run plines program with
    | Success(result, _, _)   -> result
    | Failure(errorMsg, e, s) -> failwith errorMsg

Running programs

The generated AST from the parser can be fed directly into the Small Basic interpreter built in the previous article.

The code from this example is available as a gist. The full parser and interpreter are available as an F# snippet.

Here’s FizzBuzz in Small Basic:

Sub Modulus
  Result = Dividend
  While Result >= Divisor
    Result = Result - Divisor
  EndWhile
EndSub

For A = 1 To 100    
  Dividend = A
  Divisor = 3
  Modulus()
  Mod3 = Result
  Divisor = 5
  Modulus()
  Mod5 = Result
  If Mod3 = 0 And Mod5 = 0 Then
    TextWindow.WriteLine("FizzBuzz")  
  ElseIf Mod3 = 0 Then
    TextWindow.WriteLine("Fizz")
  ElseIf Mod5 = 0 Then
    TextWindow.WriteLine("Buzz")
  Else
    TextWindow.WriteLine(A)        
  EndIf
EndFor

And the generated AST from the parser:

val program : instruction [] =
  [|
  Sub "Modulus"; Assign (Set ("Result",Var "Dividend"));
  While (Comparison (Var "Result",Ge,Var "Divisor"));
  Assign (Set ("Result",Arithmetic (Var "Result",Subtract,Var "Divisor")));
  EndWhile; 
  EndSub;
  For (Set ("A",Literal (Int 1)),Literal (Int 100),Literal (Int 1));
  Assign (Set ("Dividend",Var "A"));
  Assign (Set ("Divisor",Literal (Int 3))); GoSub "Modulus";
  Assign (Set ("Mod3",Var "Result"));
  Assign (Set ("Divisor",Literal (Int 5))); GoSub "Modulus";
  Assign (Set ("Mod5",Var "Result"));
  If
    (Logical
       (Comparison (Var "Mod3",Eq,Literal (Int 0)),And,
        Comparison (Var "Mod5",Eq,Literal (Int 0))));
  Action (Method ("TextWindow","WriteLine",[|Literal (String "FizzBuzz")|]));
  ElseIf (Comparison (Var "Mod3",Eq,Literal (Int 0)));
  Action (Method ("TextWindow","WriteLine",[|Literal (String "Fizz")|]));
  ElseIf (Comparison (Var "Mod5",Eq,Literal (Int 0)));
  Action (Method ("TextWindow","WriteLine",[|Literal (String "Buzz")|]));
  Else; 
  Action (Method ("TextWindow","WriteLine",[|Var "A"|])); 
  EndIf;
  EndFor|]

Conclusion

FParsec lets you declaratively build a parser for a programming language incrementally in F# interactive with minimal effort. If you need to write a parser for an external DSL or programming language then FParsec is well worth a look.

Small Basic Interpreter

Microsoft’s Small Basic is a minimal implementation of the BASIC programming language using only 14 keywords. It’s aimed at beginners with a very simple development environment and library. My kids have enjoyed playing with it particularly the Turtle API which are reminiscent of Logo. Small Basic programs can be run locally, online via Silverlight or migrated to full fat Visual Basic .Net.

I’m quite interested in building Domain Specific Languages (DSLs), including embedded DSLs, parsers and compilers. For a short exercise/experiment I wanted to recreate a simple imperative language and Small Basic looked like a fun option.

Abstract Syntax Tree

I started by sketching out an abstract syntax tree (AST) for the language which describes the values, expressions and instructions.

F# discriminated union’s make light work of this:

/// Small Basic instruction
type instruction =
    | Assign of assign
    | SetAt of location * expr
    | PropertySet of string * string * expr
    | Action of invoke
    | For of assign * expr * expr
    | EndFor
    | If of expr
    | ElseIf of expr
    | Else
    | EndIf
    | While of expr
    | EndWhile
    | Sub of identifier
    | EndSub
    | GoSub of identifier
    | Label of label
    | Goto of label

A parser or embedded DSL can be used to generate an AST for a program. The AST can then be evaluated by an interpreter, or transformed by a compiler to processor instructions, byte code or even another language.

Embedded DSL

To test the AST I built a small embedded DSL using custom operators and functions:

let I x = Literal(Int(x))
let (!) (name:string) = Var(name)
let FOR(var:identifier, from:expr, ``to``:expr) = 
    For(Set(var, from), ``to``, I(1))
let PRINT x = 
    let writeLine = typeof<Console>.GetMethod("WriteLine",[|typeof<obj>|])
    Action(Call(writeLine, [|x|]))

This can be used to specify a Small Basic program.

let program =
    [|
        FOR("A", I(1), I(100))
        PRINT(!"A")
        ENDFOR        
    |]

The program AST can then be evaluated in F# interactive:

val program : instruction [] =
  [|For (Set ("A",Literal (Int 1)),Literal (Int 100),Literal (Int 1));
    Action (Call (Void WriteLine(System.Object),[|Var "A"|])); 
    EndFor|]

Defining the embedded DSL in F# only took minutes using the interactive REPL environment and looks quite close to the target language.

Interpreter

Programs can now be run by evaluating the AST using an interpreter. The interpreter merely steps through each instruction using pattern matching:

let run (program:instruction[]) =
    /// ... 
    /// Instruction step
    let step () =
        let instruction = program.[!pi]
        match instruction with
        | Action(call) -> invoke state call |> ignore
        | For((Set(identifier,expr) as from), target, step) ->
            assign from
            let index = findIndex (!pi+1) (isFor,isEndFor) EndFor
            forLoops.[index] <- (!pi, identifier, target, step)
            if toInt(variables.[identifier]) > toInt(eval target) 
            then pi := index
        | EndFor ->
            let start, identifier, target, step = forLoops.[!pi]
            let x = variables.[identifier]
            variables.[identifier] <- arithmetic x Add (eval step)
            if toInt(variables.[identifier]) <= toInt(eval target) 
            then pi := start
    while !pi < program.Length do step (); incr pi

Scriptable Small Basic

The AST, embedded DSL and interpreter are available as an F# snippet that you can run in F# interactive or build as an executable. The script includes a Small Basic FizzBuzz sample.

FizzBuzz

Øredev 2013

Last week I travelled to Malmö in Sweden for Øredev, a large well established annual conference primarily covering enterprise development practices from programming to agile.

The first night at the event was probably the most surreal I’ve experienced at a developer conference. It began with a keynote from XKCD creator Randall Munroe covering their increasingly elaborate April fools’ day pranks and turning his lounge into a ball pit.

RandallMunroe

Then, along with Rachel Reese, Julie Lerman, Iris Classon and some enthusiastic locals, I found myself in a boxing ring at the hotel watching an impressive impromptu display of acroyoga and slacklining.

slack lining

The night continued on in to the early hours hacking F# with Iris, which attracted a small crowd of interested onlookers. Iris picked up F# really quickly and by the end of the night she had put together a great solution to a Kaggle machine learning competition task, while still finding time to squeeze in some tango dancing.

hacking 

In the morning I woke to the entire room shaking, to the point that I thought the TV was going to come off the wall, later I learnt I was sleeping below the running machines in the gym.

Just about everyone at the conference was staying in the same hotel, just around the corner from the venue, which made it a very fun social event. It was really nice to catch up with Ashic Mahtab, Torbjörn Gyllebring and Paul Stack, and finally meet in person Jessica Kerr, Bodil Stokke, Richard and Carl from .Net Rocks, Shay Friedman and Steve Klabnik, to name just a few.

It was Rikard Ottosson who kindly invited me to give two talks at the conference, first F# Eye for the C# Guy and then F# for Trading. All the sessions were recorded and most are already available online. For some more functional love I’d highly recommend watching Rachel Reese, Bodil Stokke and Jessica Kerr’s talks.

F# Eye for the C# Guy

I first presented this talk at DDD Belfast back in 2011, and somehow it got a mention on Microsoft’s Channel 9! Since then it’s taken me to Seattle, San Francisco, Cambridge (twice), London, Norwich, Sunderland and now Malmö. Each one is slightly different but the overall theme has remained constant.


The title was borrowed from a presentation by Leon Bambrick made in 2008, and the F# logo complete with unicorn is courtesy of Chris Smith who is also responsible for the faux art work on the Learning F# 1.0 book. The not entirely genuine F# 3.0 in Action cover is all my own doing.

In the live demos I take an immutable C# class and transform it into equivalent F#, to show some of the syntactic differences. Then the focus turns to unit testing with NUnit, FsUnit, Unquote and Foq, followed by automated acceptance testing with TickSpec.

From there the focus switched to Type Providers including FSharp.Data’s JSON provider. Then accessing data from the World Bank and presenting it in a web page with High Charts using Tomas Petricek’s FunScript sample.

It was great to get a lot of questions at the end:

questions 

and some really encouraging feedback on Twitter:

The F in F# stands for fun. It's actually a keyword." - @ptrelford :) #oredev

Best talk so far F# for C# developers! Thanks @ptrelford #oredev

F# for Trading

After seeing a video of Rich Hickey’s Simple made Easy talk at Stangeloop back in 2011, I really wanted to make it to the next event, and submitted F# for Trading. I was both hugely grateful and a little surprised that it was accepted and was able to attend what is a fantastic alternative conference. Since then I’ve presented variants in San Francisco, New York, London and Amsterdam.

 

Thanks again to Torbjörn for the nice quotes he put up on Twitter during the session:

When you look at a language you will also get a community, with a special feel and specialization. ~ @ptrelford #oredev

Non programmers learn F# easily. Those with OOP background need to spend time un-learning first. ~ @ptrelford #oredev

The real performance gains are found by having time finding better algorithms. F# frees time up for that. ~ @ptrelford #oredev

Immutability and strong typing let's me relax and be confident things will work ~ @ptrelford #oredev ergonomics matter.

Yes, @ptrelford did just intellisense his way through open World Bank data. That's what F# type providers enables. #oredev

And to Rikard for inviting me over and to the whole Øredev team for putting on a fantastic event.

The fun continues over the coming weeks, next up I’ll be at: