Some advice to F# beginners

This post is part of the F# Advent Calendar in English 2016 project. Check out all the other great posts there! And special thanks to Sergey Tihon for organizing this.

I’m very happy that F# is getting used more and more in my work place. It has even got to a point where some code has been written a while ago and maintenance is done by someone who hasn’t been involved in the project at all in the beginning. This has been an chance to work on a somewhat “legacy” F# code, which was the first time for me. The code on which we’ve worked had been written by someone who was a well-grounded C# dev, but not fluent in F#. Let’s say that the produced F# code is not very idiomatic. After going through this code, here is some advice I’d like to give to beginners.

Disclaimer: I’m talking about regular code here, there is no particular constraint on performance nor memory (this is not real-time nor high-frequency trading). We can afford to allocate memory and trigger GC collections. The advice given here may not be relevant to your specific use-case.

Type all the things

While gradually building something in F#, you’ll probably use tuples, because they’re so easy to use. And when writing a function, adding a new parameter is really easy, so of course you’ll do. However, if you keep doing that, you end up with code that’s difficult to maintain. The classical answer in a statically typed functional language for such a problem is “add more types”.

If you find yourself using:

  1. tuples with too many items in it: use a type to name your items (a record for instance)
  2. record types with too many properties: compose smaller types to group related properties
  3. higher-order functions: define a type for each non-trivial function signature you consume or return
  4. functions with too many arguments: group arguments with types (but still remember points 1 & 2)

Keep things simple

This applies to any language, and is not F# specific. However when some people start to “get” how F# works, they tend to over-complicate things, where they could have been kept simple. Don’t forget the common sense good practices that apply to other languages, just because you’re coding in F#. FSharpLint (available as part of F# Power Tools) is a tool that can help you with that. In particular, it enforces the use of:

  • small functions
  • even smaller lambdas
  • small tuples only (4 items max, and I’d say 4 is already too much)

Piping

Piping is super cool. I acknowledge that. In my opinion, it allows you to easily express the “flow” of data through steps, and is very expressive. However that doesn’t mean you should go crazy with pipes.

Piping into 10 steps of complicated filters, grouping, and folds, is not as readable after 6 months as you thought it was when you were writing it. Comments could help, but defining steps in named variables, and composing them in the end, is very easy to do and will allow you to express the intent directly in the code.

Curried functions

Curried functions only make sense if you can do partial applications that also make sense. If your arguments don’t make any sense if they’re not provided together, they compose a single unit of meaningful data, and you should:

  • either group those items in a tuple,
  • or (most probably) define a type.

Higher-order functions

“Higher-order” means that at least one parameter of the function is going to be a function itself. Why not? Functions are first-class citizens. However, don’t try to be too smart. Remember, “Keep things simple”. Taking functions as parameter is one thing, but taking higher-order functions as parameters starts to become complicated. There can probably be cases where it makes sense, but don’t overuse it. And if you need to take functions as parameters, consider defining meaningful types for theses function signatures.

Explicit side-effects

F# is not a pure functional language, as it doesn’t prevent you from mutating state or having side-effects in your code. However, when you write a function that has side effects, make it as explicit as you can. Don’t hide a function that has side effects in the middle of a call chain, unless it is obvious from the caller standpoint that the call is intended to have side effects. F# type system will not prevent you from such things, so you’ll need a bit of discipline there.

Tests

Writing tests in F# is supposed to be easy. When you write tests, you shouldn’t have to build a big context for each test. If you’ve kept your types and functions simple, your unit tests will not have many dependencies or boilerplate setup. Composition is what functional programming is really about. As soon as your tests feels like wiring things up instead of validating your code behaviour, stand back and try to see if concerns can be separated.

Conventions & whitespaces

I do get that it’s not easy to choose a convention and stay consistent when you’re new to a language, but having a consistent convention regarding spaces makes your code much more pleasant to read (or maybe it’s just me and my OCD). Please do.

Dependencies

Switching to a new language doesn’t mean you should forget everything you’ve learned so far. For instance, the Single responsibility principle is still a good practice! You can think of a function signature as an interface with a single method on it. When you provide a function as a parameter, it’s like injecting the implementation of an interface. Whenever you do it, you should ask yourself whether you really want to inject it. “Do you want to inject a database access function there, or do you want to perform the call somewhere else and just pass in the returned data to the function?”. Every function parameter can be considered a dependency.

Write (or don’t, actually) your own DSLs, Computation expressions, and Type providers

Don’t do that in the first week! I’m totally guilty of using fun and cool features just because I think they’re amazing (and sometimes I want to show off), but try to get the basics right first…

  • DSLs will only prove useful if they’re built on top of well-thought abstractions. Trying to build the DSL first, in order to have a user-friendly readable code, can also lead to overcomplicated implementation underneath.
  • Computation expressions are just syntactic sugar over abstractions. You can probably achieve the same result without them. Try to get your types and concepts right before you find yourself trying to use the “MaintainsVariableSpaceUsingBind” property on a CustomOperationAttribute.
  • Type providers (erased ones, at least) are usually also only syntactic sugar that helps ensure type-safety and convenience. Before writing your own, consider using a simpler approach (but it definitely can make sense to write your own, and if you ever need, you can ping me!)

The advice given here may seem too simplistic, but it can’t hurt, can it?

PS: Now I understand the imposter syndrome

Posted in F sharp love, Practices | Tagged , | 3 Comments

Making program behaviour explicit

When observing developers in their day-to-day work, it’s quite usual to see them swearing at their programs, because they don’t behave as they should. You often see them asking the program to obey, sometimes cursing, and even praying from time to time. If we take some time to think about it, the main reason why a programmer shouts at a running program is because it doesn’t quite behave as he/she wants it to do. Unfortunately, this is less common in the functional programming community. Having a language that promotes usage of immutability and option types (to name only a few), sometimes deprives you of cursing and praying.

Fortunately, F# has a feature called computation expressions, that can bring you back the joy of an unpredictable behaviour at runtime! I hope you’ll enjoy the ones I’m going to introduce today. For instance, they allow you to write the following code:

let theAnswer = usually { return 42 }
let basicArithmetic = mostProbably { return 6 * 7 }

As those samples clearly state, they usually and mostProbably behave as expected. However, they sometimes do slightly different things. Indeed, the computation expressions are sometimes mutated, and then evaluate to something else. Using this, you can cause subtle bugs, that only occur from time to time, deep inside more complex computations. And as you can expect, the debugging experience will be completely awful.

That’s a nice first step. But didn’t I mention cursing an praying? Stay tuned. Using a combination of custom operations and mutable state (ouch!), this is perfectly valid code:

pray God {
    // This begins a safe section
    ``The lord is my shepherd``
    let x = 6
    ``He led me in the paths of righteousness``
    // Here the safe section is over

    let y = 55

    // this is just another safe section
    ``Whoever walks in integrity walks securely``
    let z = 2
    ``But whoever takes crooked paths will be found out``
    // And here the safe section ends

    // This starts a perilous section
    ``I walk through the valley of the shadow of death``

    return (y * z + 1) * x
}

And it comes in different flavours, you can pray your own favourite god if you wish:

pray FlyingSpaghettiMonster {
    ``I believe Thou art the Creator of Goodness and Nourishment``
    let x = 1
    ``I believe that Thou are neither Male, nor Female``
    let y = 2
    ``I thank Thee for the giving of healthful Green Salad``
    let z = 3
    ``R'amen``
    return x + y - z
}

In the previous samples, you compose a prayer, that will change the mood of the god who listens to it:

  • in the default state, there is a small chance that mutation occur in the expressions,
  • when the god is pleased, the code is safe and no mutation occurs,
  • when the god is angry, expect numerous mutations.

Of course, using a sentence which is not intended for the right god will trigger mutations.

So how do we build this? Computation expressions are in most cases just used as syntactic sugar that allows you to bind continuation functions to a given state (as very well explained on fsharpforfunandprofit). But you can also use computation expressions to get a quotation of the expression. This is what’s behind the cloud expression offered by MBrace.

Once given an expression, you can manipulate it to build a new derived expression. In the end, in order to evaluate the expression, I’ve used the evaluator packaged in Unquote. In the end, the computation expression builder class is almost empty:

type ChaosBuilder (mutationSitePicker:IMutationSitePicker,
                   expressionReplacer:IExpressionReplacer) =
    member this.Return(x) = x
    member this.Quote (expr) = expr
    member this.Run (expr:Expr<'T>) =
        let choaticExpr =
            mutate mutationSitePicker expressionReplacer expr
        choaticExpr.Eval<'T>()

The IMutationSitePicker is responsible for choosing a site, ant the IExpressionReplacer actually performs the expression maniputation. Here is a sample implementation that give every eligible expression a random chance to be replaced:

type MutateWithProbability(proportion) =
    let r = new System.Random()
    let mutable lastRandom = r.NextDouble()
    interface IMutationSitePicker with
       member this.PickNextSite = lastRandom < proportion
       member this.NotifyIgnoredSite() = lastRandom <- r.NextDouble()
       member this.NotifyMutation() = lastRandom <- r.NextDouble()

I’m not going to include the actual expression manipulation code here, but my current work on this very valuable feature is available as a Gist. Implementing computation expressions which allow (and encourage) cursing is left as an exercise to the reader.

Some of the code used here could actually be used to perform mutation testing. the only replacement implemented so far is numeric constants mutation, but there are many other kinds of fun mutations to add (see Mutation Testing of Functional Programming Languages for instance) such as “replacing an arithmetic, relational, logical, bitwise logical […] operator by another of the same class”, “Reordering Pattern Matching”, and even “Type-aware Function Replacement”.

As a conclusion, I want to say that even if I often abuse computation expressions to do stupid things, they’re a really powerful feature of the F# language and really allow to write cool DSLs.

EDIT: I’ve implemented the arithmetic operator replacement in the train this morning, the gist has been updated.

Posted in F sharp love, Syntax Puzzles | Tagged , | 1 Comment

Visualizing F# Advent Calendar contributors

This post is part of the F# Advent Calendar in English 2015 project. Check out all the other great posts there! And special thanks to Sergey Tihon for organizing this.

A few weeks ago, while at BuildStuff, I walked next to an image built with words, like a tag cloud picturing some company’s logo. My first reaction was: “That looks nice, but has someone been paid to manually placed all these words? I bet it can be automated…”

I started putting together a script, in order to fill an image with words. My first attempt had disastrous performance and memory characteristics. Several hours of work later (quite a few, actually), and with contributions from my co-workers, we ended-up with a much better algorithm.

F# is a wonderful language to experiment with ideas. The convenience of quickly defining types with almost no ceremony lets you focus on what you’re really trying to build. The power of the .NET ecosystem lets you use all the standard APIs that you expect to find on a serious platform. This is really enjoyable and helps you to build simple things first, and evolve to more complicated ones while staying focused.

In the end we’re able to produce images such as:

In order to produce such an image, we need an image to use as the model, and a list of words to fill the shape with. We had much fun doing it, both trying to identify strategies to make the images look good and get the generation time down. You can find the full source code on Github: https://github.com/pirrmann/Wordz

The goal: build a nice picture

Another area where F# shines is related to getting data from various sources and manipulate it. This enables so many scenarios. What if we could get pictures, and related text, from some place such as https://sergeytihon.wordpress.com/2015/10/25/f-advent-calendar-in-english-2015/ for instance, and generate all sorts of images?

Step 1: parse the the posts list

I’m happy @TeaDrivenDev hasn’t published his first post idea about generating the RSS feed from the FsAdvent page, because I also have to parse the page in order to get my data… so first thing, we need to get the posts URLs from the page. It gives me a chance to mention the HTML Type Provider, which is part of the FSharp.Data library. Accessing the list of posts and downloading all the posts is as easy as:

type adventCalendarPage =
    HtmlProvider<"https://sergeytihon.wordpress.com/[...]/">
type PageRow =
    adventCalendarPage.FAdventCalendarInEnglish2015.Row

let postsTable =
    adventCalendarPage
        .GetSample()
        .Tables
        .``F# Advent Calendar in English 2015``

let extractPostsLinks (tr:HtmlNode) =
    let lastTd = tr.Elements("td") |> Seq.last

    lastTd.Elements("a")
    |> List.map (fun a -> a.AttributeValue("href"))

let postLinks =
    postsTable.Html.Descendants("tr")
    |> Seq.tail
    |> Seq.map extractPostLinks

let downloadPostsAsync links = 
    links
    |> Seq.map HtmlDocument.AsyncLoad
    |> Async.Parallel

let postsDownloads =
    postLinks
    |> Seq.map downloadPostsAsync
    |> Async.Parallel
    |> Async.RunSynchronously

let allPosts = Array.zip postsTable.Rows postsDownloads

From the previous sample, you may notice how the HTML type provider also allows you to access the elements of the page through the DOM. This is quite representative of how a good library design gracefully lets you use the underlying technology when the high-level API doesn’t suit your needs.

Step 2: extract words

We have now obtained all published FsAdvent posts in the form of HtmlDocument objects, but we don’t have their content yet… No magic type provider here, all posts are hosted on different blogging platforms, I had to use several strategies and fallbacks to identify the HTML element containing the post in each case. Semantic web is really not there yet! The search function finally looks like this:

let search =
    findDivWithEntryClassUnderDivWithPostClass
    |> fallback findWintellectContent
    |> fallback findDivWithClassStoryContent
    |> fallback findArticle
    |> fallback findElementWithClassOrIdPost
    |> fallback findH1TitleParentWithEnoughContent
    |> fallback findScottwContent
    |> fallback findMediumContent
    |> fallback wholePageContent

The next step of interest is how to extract the most important words from each post. Another handy feature of F# are computation expressions, and in particular the built-in ones such as async an seq. Returning a sequence while recursively traversing a tree is as easy as:

let getMultiplier (node:HtmlNode) =
    match node.Name() with
    | "h1" -> 16 | "h2" -> 12 | "h3" -> 8
    | "h4" -> 4  | "h5" -> 3  | "h6" -> 2
    | _ -> 1

let rec collectAllWords multiplier (node:HtmlNode) = seq {
    match node.Elements() with
    | [] ->
        let text = node.InnerText()
        let words =
            text.Split(delimiters)
            |> Seq.filter (not << String.IsNullOrWhiteSpace)
            |> Seq.filter (fun s -> s.Length > 1)
            |> Seq.map (fun s -> s.ToLowerInvariant())
        for word in words do
            if not(filteredWords.Contains word) then
                yield word, multiplier

    | children ->
        let multiplier' = getMultiplier node
        yield! children
               |> Seq.collect (collectAllWords multiplier')
}

The last step once we’ve obtained all the words from each post with is to group them and sum their weight in order to get an indicator of their importance in the post. We define a function for that:

let sumWeights words =
    words
    |> Seq.groupBy fst
    |> Seq.map (fun (word, weights) -> word,
                                       weights |> Seq.sumBy snd)
    |> Seq.sortByDescending snd
    |> Seq.take 100
    |> Seq.toList

Step 3: get Twitter profile pictures

So we have all words from the FsAdvent posts published so far, and their relative importance in each post. But in order to create a visualization, we need model images, right? Let’s download the Twitter profile pictures of the authors! The profile urls can be extracted from the FsAdvent page (actually some of them are not links to twitter, so I had to cheat a bit, and this is why the function extractCleanLink is omitted…)

let extractProfileLink (tr:HtmlNode) =
    let lastTd = tr.Elements("td") |> Seq.item 1
    let a = lastTd.Elements("a") |> Seq.head
    a.InnerText(), a.AttributeValue("href")

let profilesLinks =
    postsTable.Html.Descendants("tr")
    |> Seq.tail
    |> Seq.map extractProfileLink

let downloadAndSavePictureAsync (name:string, twitterProfileUrl:string) = async {
    let fileName = getFileName "profiles" name

    let cookieContainer = new Net.CookieContainer()

    let! twitterProfileString = Http.AsyncRequestString(twitterProfileUrl,
                                                        cookieContainer = cookieContainer)
    let twitterProfile = HtmlDocument.Parse(twitterProfileString)

    let profileImageLink =
        twitterProfile.Descendants("a")
        |> Seq.find(fun a -> a.HasClass("ProfileAvatar-container"))
            
    let profilePictureUrl = profileImageLink.AttributeValue("href")

    let! imageStream = Http.AsyncRequestStream profilePictureUrl

    use image = Image.FromStream(imageStream.ResponseStream)
    image.Save(fileName, Imaging.ImageFormat.Png)

    return () }

profilesLinks
|> Seq.map (extractCleanLink >> downloadAndSavePictureAsync)
|> Async.Parallel
|> Async.RunSynchronously
|> ignore

Step 4: cut the profile pictures into layers

My early experiments with this did not have any feature to cut pictures into layers, but I didn’t want to manually edit each picture profile! So what I’ve done to build “layers” is just to cluster pixels by color similarity (actually I’ve tried to really cluster them with a K-means cluster but I ended up using my custom clustering with magic numbers, as it performs better on that specific set of pictures).

This topic could be a blog post of its own so I’ll just sum up the steps I’ve performed:

  • In order to get rid of outliers, first blur the image
  • then generate color clusters using the following algorithm:
    • considering each pixel, if it’s close enough (below a given threshold) to an existing cluster, put it in the cluster. If too far from any existing cluster, create a new cluster with the single pixel in it.
    • after having seen each pixel, merge clusters that are close enough
    • finally, merge clusters that are too small with their nearest neighbour, regardless of the distance

This way, we can go from one image to several ones with the grouped pixels:

Step 5: fill images with words

As some authors have decided to blog more that once, I’ve decided to merge their posts and generate a single image per author.

let mergePosts posts =
    let allImportantWords =
        posts
        |> Seq.collect (fun post -> post.Words)
        |> Seq.toList
    { Seq.head posts with Words = sumWeights allImportantWords }

let mergedPosts =
    parsePosts allPosts
    |> Seq.groupBy (fun post -> post.Author)
    |> Seq.map(fun (_, posts) -> mergePosts posts)
    |> Seq.toArray

Using sumWeights to merge posts is like considering that each post is a paragraph containing only its 100 most important words.

I then consider each layer generated previously from the Twitter profile picture of an author, and fill it with the most important words from his/her posts. This generates one file per layer on the disk.

Step 6: generate the calendar!

So… 62 posts (before the last one) – 2 which were not published – 1 because I decided to group Steffen’s posts (even if scheduled on 2 different dates) + 1 because Steffen’s post have been unmerged (as I neeeded 60 posts in the end) = 60 posts (yeah!). This gives me a nice 8 * 8 square, with a 2 * 2 tile in the middle for the F# foundation! All is needed is to iterate on the generates layers filled with words, and place them on the calendar. I’ve randomly shuffled the posts list, can you identify everybody? Here is the result, enjoy!

(click on the calendar to view the full size image)

I’ve just updated this post with all posts written so far…

Posted in F sharp love | Tagged , , | 6 Comments

Fun with turtles

F# is a great language to build internal DSLs, but I had no idea that you could go as far as what I’m going to present here…

Let’s start from the start: my goal was to design some way for me to explain my daughter what programming is about and how it works. There are some nice graphical tools for that, like Scratch or more recently Hour of code, however I wanted to show something which is closer to what I actually do on a daily basis: write (and read) code. There are some nice educational programming languages, some of them are even usable in a localized way (French, in my case). LOGO is a good example of this, and I could have used an existing tool, but where is the fun if you don’t build your own?

It appears that building an internal LOGO-like DSL is surprisingly easy, and requires almost no code! What you need is just to define the basic types to describe your actions:

type Distance_Unit = STEPS
type Rotation_Unit = GRADATIONS
type Rotation_Direction = | LEFT | RIGHT
let STEP = STEPS
let GRADATION = GRADATIONS

type Color = | RED | GREEN | BLUE

type Action =
    | Walk of int * Distance_Unit
    | Turn of int * Rotation_Unit * Rotation_Direction
    | LiftPenUp
    | PutPenDown
    | PickColor of Color

type Turtle = Action seq

And then a computation expression to do the trick of transforming sentences to sequences of actions:

type AS_word = AS
type TO_word = TO
type THE_word = THE
type PEN_word = PEN
type UP_word = UP
type DOWN_word = DOWN
type TIMES_word = TIMES
type WHAT_word = WHAT
type DOES_word = DOES

type TurtleBuilder() =
    member x.Yield(()) = Seq.empty
    [<CustomOperation("WALK", MaintainsVariableSpace = true)>]
    member x.Walk(source:Turtle, nb, unit:Distance_Unit) =
        Seq.append source [Walk(nb, unit)]
    [<CustomOperation("TURN", MaintainsVariableSpace = true)>]
    member x.Turn(source:Turtle, nb, unit:Rotation_Unit, to_word:TO_word,
                  the_word:THE_word, direction:Rotation_Direction) =
        Seq.append source [Turn(nb, unit, direction)]
    [<CustomOperation("LIFT", MaintainsVariableSpace = true)>]
    member x.LiftPenUp(source:Turtle, the_word:THE_word, pen_word:PEN_word,
                       up_word:UP_word) =
        Seq.append source [LiftPenUp]
    [<CustomOperation("PUT", MaintainsVariableSpace = true)>]
    member x.PutPenDown(source:Turtle, the_word:THE_word, pen_word:PEN_word,
                        down_word:DOWN_word) =
        Seq.append source [PutPenDown]
    [<CustomOperation("PICK", MaintainsVariableSpace = true)>]
    member x.PickColor(source:Turtle, the_word:THE_word, color:Color, pen_word:PEN_word) =
        Seq.append source [PickColor color]
    [<CustomOperation("DO", MaintainsVariableSpace = true)>]
    member x.Do(source:Turtle, as_word:AS_word, turtle:Turtle) =
        Seq.append source turtle
    [<CustomOperation("REPEAT", MaintainsVariableSpace = true)>]
    member x.Repeat(source:Turtle, nb:int, times_word:TIMES_word, what_word:WHAT_word,
                    turtle:Turtle, does_word:DOES_word) =
        Seq.append source (List.replicate nb turtle |> Seq.collect id)

let turtle = new TurtleBuilder()

And with nothing more, you can now write this kind of plain English instructions:

turtle {
    LIFT THE PEN UP
    WALK 4 STEPS
    TURN 3 GRADATIONS TO THE RIGHT
    PICK THE GREEN PEN
    PUT THE PEN DOWN
    WALK 4 STEPS }

Now, this doesn’t solve my initial problem, I want a French DSL. But I just need to define another builder, and a few translation functions:

type Tortue = Turtle

type Unite_De_Distance = PAS with
    member x.enAnglais = match x with | PAS -> STEP

type Unite_De_Rotation = | CRANS with
    member x.enAnglais = match x with | CRANS -> GRADATION
let CRAN = CRANS

type Sens_De_Rotation = | GAUCHE | DROITE with
    member x.enAnglais = match x with
                         | GAUCHE -> LEFT
                         | DROITE -> RIGHT

type Couleur = | ROUGE | VERT | BLEU with
    member x.enAnglais = match x with
                         | ROUGE -> RED
                         | VERT -> GREEN
                         | BLEU -> BLUE

type Mot_A = A
type Mot_DE = DE
type Mot_LE = LE
type Mot_STYLO = STYLO
type Mot_COMME = COMME
type Mot_FOIS = FOIS
type Mot_CE = CE
type Mot_QUE = QUE
type Mot_FAIT = FAIT

type TortueBuilder() =
    member x.Yield(()) = Seq.empty
    member x.For(_) = Seq.empty
    [<CustomOperation("AVANCE", MaintainsVariableSpace = true)>]
    member x.Avance(source:Tortue, de:Mot_DE, nb, unite:Unite_De_Distance) =
        Seq.append source [Walk(nb, unite.enAnglais)]
    [<CustomOperation("TOURNE", MaintainsVariableSpace = true)>]
    member x.Tourne(source:Tortue, de:Mot_DE, nb, unite:Unite_De_Rotation,
                    a:Mot_A, sens:Sens_De_Rotation) =
        Seq.append source [Turn(nb, unite.enAnglais, sens.enAnglais)]
    [<CustomOperation("LEVE", MaintainsVariableSpace = true)>]
    member x.Leve(source:Tortue, le:Mot_LE, stylo:Mot_STYLO) =
        Seq.append source [LiftPenUp]
    [<CustomOperation("POSE", MaintainsVariableSpace = true)>]
    member x.Pose(source:Tortue, le:Mot_LE, stylo:Mot_STYLO) =
        Seq.append source [PutPenDown]
    [<CustomOperation("PRENDS", MaintainsVariableSpace = true)>]
    member x.Prends(source:Tortue, le:Mot_LE, stylo:Mot_STYLO, couleur:Couleur) =
        Seq.append source [PickColor couleur.enAnglais]
    [<CustomOperation("FAIS", MaintainsVariableSpace = true)>]
    member x.Fais(source:Tortue, comme:Mot_COMME, tortue:Tortue) =
        Seq.append source tortue
    [<CustomOperation("REPETE", MaintainsVariableSpace = true)>]
    member x.Repete(source:Tortue, nb:int, fois:Mot_FOIS, ce:Mot_CE, que:Mot_QUE,
                    tortue:Tortue, fait:Mot_FAIT) =
        Seq.append source (List.replicate nb tortue |> Seq.collect id)

let tortue = new TortueBuilder()

And I can write my instructions in French!

tortue {
    AVANCE DE 5 PAS
    TOURNE DE 6 CRANS A DROITE
    AVANCE DE 5 PAS
    TOURNE DE 6 CRANS A DROITE
    AVANCE DE 5 PAS
    TOURNE DE 6 CRANS A DROITE
    AVANCE DE 10 PAS }

The next steps involved:

  • Writing a Windows Forms client to actually see the turtle draw things
  • Making it possible to send actions to the turtle using FSI
  • Hand-coding every letter of the alphabet
  • Adding a new keyword to my turtle builders

And please welcome my “Hello world” sample:

turtle {
    WRITE "MR T. SAYS:\nHELLO WORLD!\n\n"
}

As usual, all the code is available on my github.

Posted in F sharp love, Syntax Puzzles | Tagged , , , | Comments Off

F# |> I <3

I’ve been writing about F# for a little while now, and how it has influenced the way I code in C# on an everyday basis for 3 years. During the last couple weeks, I’ve finally had the chance to use F# at work for a real project (I’ll probably talk about that later). Yesterday evening (Europe time) at Build, Roslyn was open-sourced. That’s nice and people are probably going to talk about it for a while. But for me there was another very nice announcement : Visual F# is now taking contributions! F# is already an exciting language, full of clever features. With this new step, I’m convinced that it will go even further and I’m already looking forward to F# 4.0!

So don’t expect to see many more posts about C# on this blog, I’ve totally gone F#.

And now, the latest sample from Arolla’s Code Jam. The aim was to write code to express values with a range of uncertainty, and operations which manipulate those numbers. For instance, a value 3.5 +/- 0.5, multiplied by 1.0 +/- 0.1. The goal of the kata was to write code that expresses intent (the why), and not implementation details (the how).

In F#, I’ve just defined a type to wrap both the value and its precision, and an operator to conveniently build those values :

type Number = | Number of float * float

let (+-) n a = Number (n, a)

This code alone already allows me to build values just by writing expressions such as “4.0 +- 1.0”. The next step for me was to write some expressive tests, using FsUnit.

let [<test>] ``A number with accuracy is equal to itself`` () =
    (1.0 +- 0.5) |> should equal (1.0 +- 0.5)

let [<test>] ``Sum of two numbers sums the numbers and accuracies`` () =
    ((5.0 +- 0.5) + (3.0 +- 0.5)) |> should equal (8.0 +- 1.0)

Although we could handle distinctly every operator with specific logic, the goal of this kata is to express the intent in a generic fashion, so here is a combine method that has no specific meaning of what an operator does:

let combine op (Number(n1, a1), Number(n2, a2)) =
   let all =
      seq {
         for x in [n1-a1; n1+a1] do
         for y in [n2-a2; n2+a2] do
         yield op x y
      }
   let minimum = all |> Seq.min
   let maximum = all |> Seq.max
   Number((minimum + maximum) / 2.0, (maximum - minimum) / 2.0)

Finally, we just have to add operator overloading to the type, the full code becomes:

type Number = | Number of float * float
    with override x.ToString() = match x with | Number(a, b) -> sprintf "%f +- %f" a b
         static member private combine op (Number(n1, a1), Number(n2, a2)) =
            let all =
                seq {
                    for x in [n1-a1; n1+a1] do
                    for y in [n2-a2; n2+a2] do
                    yield op x y
                }
            let minimum = all |> Seq.min
            let maximum = all |> Seq.max
            Number((minimum + maximum) / 2.0, (maximum - minimum) / 2.0)
         static member (+) (x, y) = (x, y) |> Number.combine (+)
         static member (-) (x, y) = (x, y) |> Number.combine (-)
         static member (*) (x, y) = (x, y) |> Number.combine (*)
         static member (/) (x, y) = (x, y) |> Number.combine (/)
         static member Pow (x, y) = (x, y) |> Number.combine ( ** )

Thanks to @luketopia for the interactions on Twitter, and the trick which allows to pass the operator ** as an argument: use spaces between the parenthesis and the operator!

Posted in F sharp love | Tagged , | Comments Off