Chapter 9. Introducing Language-Oriented Programming

Chapters 3, 4, and 6 covered three well-known programming paradigms in F#: functional, imperative, and object-oriented programming. This chapter covers techniques and constructs related to what is essentially a fourth programming paradigm: language-oriented programming. The word language can have a number of meanings in this context. For example, take the simple language of arithmetic expressions and algebra that you learned in high-school mathematics, made up of named variables such as x and y and composite expressions such as x+y, xy, –x, and x2. For the purposes of this chapter, this language can have a number of manifestations:

  • One or more concrete representations: for example, using an ASCII text format or an XML representation of arithmetic expressions.

  • One or more abstract representations: for example, as F# values representing the normalized form of an arithmetic expression tree.

  • One or more computational representations, either by functions that compute the values of arithmetic expressions or via other engines that perform analysis, interpretation, compilation, execution, or transformation on language fragments. These can be implemented in F#, in another .NET language, or in external engines.

This and later chapters cover many of the tasks associated with language-oriented programming. The techniques covered in this book are as follows:

  • Manipulating formats such as XML, which are often used for concrete representations of languages (Chapters 9 and 11)

  • Writing parsers and lexers for other text formats, also often used as concrete representations of languages (Chapter 16)

  • Using F# types for abstract representations of languages (Chapters 9 and 11)

  • Using three techniques related to computational representations of languages: active patterns, quotations, and workflows (Chapters 9 and 13)

  • Interfacing with existing language execution components (SQL via LINQ in Chapter 15)

Language-oriented programming isn't a single technique; sometimes you work with fully concrete representations (for example, reading bits on a magnetic disk) and sometimes with fully computational representations (for example, defining and using functions that compute the value of arithmetic expressions). Most often, you work somewhere in between (for example, manipulating abstract syntax trees). These tasks require different techniques, and there are trade-offs between choosing to work with different kinds of representations. For example, if you're generating human-readable formulae, then you may need to store more concrete information; but if you're interested just in evaluating arithmetic expressions, then a purely computational encoding may be more effective. You see some of those trade-offs in this chapter.

Note

The term language-oriented programming was originally applied to F# by Robert Pickering in the Apress book Beginning F#, and it really captures a key facet of F# programming. Thanks, Robert!

Using XML as a Concrete Language Format

To get started with language-oriented programming, it's helpful to begin with the standard structured data format Extensible Markup Language (XML). .NET comes with well-engineered libraries for reading and generating XML, so you can initially skirt many of the issues associated with concrete language formats. Chapter 15 also covers XML as a data format, and Chapter 16 discusses techniques to tokenize and parse other textual formats. Chapter 16 also briefly covers binary formats.

Using the System.Xml Namespace

XML is a general-purpose markup language and is extensible because it allows its users to define their own tags. Its primary purpose is to facilitate the sharing of data across different information systems, particularly via the Internet. Here is a sample fragment of XML, defined as a string directly in F#:

let inp = "<?xml version="1.0" encoding="utf-8" ?>
           <Scene>
              <Composite>
                <Circle radius='2' x='1' y='0'/>
                <Composite>
                  <Circle radius='2' x='4' y='0'/>
                  <Square side='2' left='-3' top='0'/>
                </Composite>
                <Ellipse top='2' left='-2' width='3' height='4'/>
              </Composite>
           </Scene>"

The backbone of an XML document is a hierarchical structure, and each node is decorated with attributes keyed by name. You can parse XML using the types and methods in the System.Xml namespace provided by the .NET libraries and then examine the structure of the XML interactively:

> open System.Xml;;
> let doc = new XmlDocument();;
val doc : XmlDocument

> doc.LoadXml(inp);;
val it : unit = ()

> doc.ChildNodes;;
val it : XmlNodeList
    = seq [seq []; seq [seq [seq []; seq [seq []; seq []]; seq []]]]

The default F# Interactive display for the XmlNode type isn't particularly useful. Luckily, you can add an interactive printer to the fsi.exe session using the AddPrinter method on the fsi object:

> fsi.AddPrinter(fun (x:XmlNode) -> x.OuterXml);;

> doc.ChildNodes;;
val it : XmlNodeList
seq
    [<?xml version="1.0" encoding="utf-8"?>;
     <Scene><Composite><Circle radius="2" x="1" y="0" /><Composite>...</Scene>]

> doc.ChildNodes.Item(1);;
val it : XmlNode
  = <Scene><Composite><Circle radius="2" x="1" y="0" /><Composite>...</Scene>

> doc.ChildNodes.Item(1).ChildNodes.Item(0);;
val it : XmlNode
  = <Composite><Circle radius="2" x="1" y="0" /><Composite>...</Composite>

> doc.ChildNodes.Item(1).ChildNodes.Item(0).ChildNodes.Item(0);;
val it : XmlNode = <Circle radius="2" x="1" y="0" />

> doc.ChildNodes.Item(1).ChildNodes.Item(0).ChildNodes.Item(0).Attributes;;
val it : val it : XmlAttributeCollection = seq [radius="2"; x="1"; y="0"]

Table 9-1 shows the most commonly used types and members from the System.Xml namespace.

Table 9.1. Commonly Used Types and Members from the System.X Namespace

Type/Member

Description

type XmlNode

Represents a single node in an XML document

member ChildNodes

Gets all the child nodes of an XmlNode

member Attributes

Gets all the attributes of an XmlNode

member OuterXml

Gets the XML text representing the node and all its children

member InnerText

Gets the concatenated values of the node and all its children

member SelectNodes

Selects child nodes using an XPath query

type XmlAttribute

Represents one attribute for an XmlNode; also an XmlNode

member Value

Gets the string value for the attribute

type XmlDocument

Represents an entire XML document; also an XmlNode

member Load

Populates the document from the given XmlReader, stream, or file name

member LoadXml

Populates the document object from the given XML string

type XmlReader

Represents a reader for an XML document or source

type XmlWriter

Represents a writer for an XML document

Note

.NET provides tools to generate a typed .NET object model view of an XML schema, in particular xsd.exe from the .NET Framework SDK. This tool has some limitations, and sometimes it's worth exploring your own techniques for interoperating with external data schemas, whether they're in XML or otherwise, as discussed later in this chapter. Tools like xsd.exe can be configured to generate F# code through the use of the F# CodeDOM implementation that comes with the F# distribution. However, this chapter doesn't show how to use these tools. An alternative technique for querying XML is the XLinq API that is part of the LINQ framework, covered briefly in Chapter 15. You can also use F# active patterns to define decomposition and query techniques for XML (we cover F# active patterns later in this chapter).

From Concrete XML to Abstract Syntax

Often, your first task in processing a concrete language is to bring the language fragments under the type discipline of F#. This section shows how to transform the data contained in the XML from the previous section into an instance of the recursive type shown here. This kind of type is usually called an abstract syntax tree (AST):

open System.Drawing
type Scene =
    | Ellipse   of RectangleF
    | Rect      of RectangleF
    | Composite of Scene list

This example uses the types PointF and RectangleF from the System.Drawing namespace, although you can equally define your own types to capture the information carried by the leaves of the tree. Listing 9-1 shows a recursive transformation to convert XML documents like the one used in the previous section into the type Scene.

Example 9.1. Converting XML into a Typed Format Using the System.Xml Namespace

open System.Xml
open System.Drawing
type Scene =
    | Ellipse of RectangleF
    | Rect    of RectangleF
    | Composite   of Scene list

    /// A derived constructor
    static member Circle(center:PointF,radius) =
        Ellipse(RectangleF(center.X-radius,center.Y-radius,
                           radius*2.0f,radius*2.0f))

    /// A derived constructor
    static member Square(left,top,side) =
        Rect(RectangleF(left,top,side,side))

let extractFloat32 attrName (attribs: XmlAttributeCollection) =
    float32 (attribs.GetNamedItem(attrName).Value)

let extractPointF (attribs: XmlAttributeCollection) =
    PointF(extractFloat32 "x" attribs,extractFloat32 "y" attribs)

let extractRectangleF (attribs: XmlAttributeCollection) =
    RectangleF(extractFloat32 "left" attribs,extractFloat32 "top" attribs,
               extractFloat32 "width" attribs,extractFloat32 "height" attribs)

let rec extractScene (node: XmlNode) =
    let attribs = node.Attributes
    let childNodes = node.ChildNodes
    match node.Name with
    | "Circle"  ->
        Scene.Circle(extractPointF(attribs), extractFloat32 "radius" attribs)
    | "Ellipse"  ->
        Scene.Ellipse(extractRectangleF(attribs))
    | "Rectangle"  ->
        Scene.Rect(extractRectangleF(attribs))
    | "Square"  ->
        Scene.Square(extractFloat32 "left" attribs,extractFloat32 "top" attribs,
                     extractFloat32 "side" attribs)

    | "Composite"   ->
        Scene.Composite [ for child in childNodes -> extractScene(child) ]
    | _ -> failwithf "unable to convert XML '%s'" node.OuterXml

let extractScenes (doc: XmlDocument) =
   [ for node in doc.ChildNodes do
       if node.Name = "Scene" then
          yield (Composite
                     [ for child in node.ChildNodes -> extractScene(child) ]) ]

The inferred types of these functions are as follows:

type Scene =
    | Ellipse of RectangleF
    | Rect of RectangleF
    | Composite of Scene list
    static member Circle : PointF * float32 -> Scene
    static member Square : float32 * float32 * float32 -> Scene
val extractFloat32 : string -> XmlAttributeCollection -> float32
val extractPointF : XmlAttributeCollection -> PointF
val extractRectangleF :  XmlAttributeCollection -> RectangleF
val extractScene : XmlNode -> Scene
val extractScenes : XmlDocument -> Scene list

The definition of extractScenes in Listing 9-1 generates lists using sequence expressions, covered in Chapter 3. You can now apply the extractScenes function to the original XML. (You first add a pretty-printer to the F# Interactive session for the RectangleF type using the AddPrinter function on the fsi object, described in Chapter 10.)

> fsi.AddPrinter(fun (r:RectangleF) ->
      sprintf "[%A,%A,%A,%A]" r.Left r.Top r.Width r.Height);;
val it : unit = ()

> extractScenes doc;;
val it : Scene list
= [Composite
    [Composite
      [Ellipse [-1.0f,-2.0f,4.0f,4.0f];
       Composite [Ellipse [2.0f,-2.0f,4.0f,4.0f]; Rect [-3.0f,0.0f,2.0f,2.0f]];
       Ellipse [-2.0f,2.0f,3.0f,4.0f]]]]

The following sections more closely explain some of the choices we've made in the abstract syntax design for the type Scene.

Tip

Translating to a typed representation isn't always necessary: some manipulations and analyses are better performed directly on heterogeneous, general-purpose formats such as XML or even on strings. For example, XML libraries support XPath, accessed via the SelectNodes method on the XmlNode type. If you need to query a large semistructured document whose schema is frequently changing in minor ways, then XPath is the right way to do it. Likewise, if you need to write significant amounts of code that interprets or analyzes a tree structure, then converting to a typed abstract syntax tree is usually better.

Working with Abstract Syntax Representations

In the previous section, you saw how to move from one particular concrete language format to an abstract syntax format. You now learn about some important recurring techniques in designing and working with abstract syntax representations.

Abstract Syntax Representations: Less Is More

Let's look at the design of the abstract syntax type Scene from Listing 9-1. The type Scene uses fewer kinds of nodes than the concrete XML representation: the concrete XML has node kinds Circle, Square, Composite, and Ellipse, whereas Scene has just three (Rect, Ellipse, and Composite), with two derived constructors Circle and Square, defined as static members of the Scene:

static member Circle(center:PointF,radius) =
        Ellipse(RectangleF(center.X-radius,center.Y-radius,
                           radius*2.0f,radius*2.0f))

    /// A derived constructor
    static member Square(left,top,side) =
        Rect(RectangleF(left,top,side,side))

This is a common step when abstracting from a concrete syntax; details are dropped and unified to make the abstract representation simpler and more general. Extra functions are then added that compute specific instances of the abstract representation. This approach has pros and cons:

  • Transformational and analytical manipulations are almost always easier to program if you have fewer constructs in your abstract syntax representation.

  • You must be careful not to eliminate truly valuable information from an abstract representation. For some applications, it may really matter if the user specified a Square or a Rectangle in the original input; for example, an editor for this data may provide different options for editing these objects.

The AST uses the types PointF and RectangleF from the System.Drawing namespace. This simplification is also a design decision that should be assessed: PointF and RectangleF use 32-bit low-precision floating-point numbers, which may not be appropriate if you're eventually rendering on high-precision display devices. You should be wary of deciding on abstract representations on the basis of convenience alone, although of course this is useful during prototyping.

The lesson here is that you should look carefully at your abstract syntax representations, trimming out unnecessary nodes and unifying nodes where possible, but only as long as doing so helps you achieve your ultimate goals.

Processing Abstract Syntax Representations

Common operations on abstract syntax trees include traversals that collect information and transformations that generate new trees from old. For example, the abstract representation from Listing 9-1 has the property that for nearly all purposes, the Composite nodes are irrelevant (this wouldn't be the case if you added an extra construct such as an Intersect node). This means you can flatten to a sequence of Ellipse and Rectangle nodes as follows:

let rec flatten scene =
    seq { match scene with
          | Composite scenes -> for x in scenes do yield! flatten x
          | Ellipse _ | Rect _ -> yield scene }

Here, flatten is defined using sequence expressions, introduced in Chapter 3. Its type is as follows:

val flatten : Scene -> seq<Scene>

Let's look at this more closely. Recall from Chapter 3 that sequences are on-demand (lazy) computations. Using functions that recursively generate seq<'T> objects can lead to inefficiencies in your code if your abstract syntax trees are deep. It's often better to traverse the entire tree in an eager way (eager traversals run to completion immediately). For example, it's typically faster to use an accumulating parameter to collect a list of results. Here's an example:

let rec flattenAux scene acc =
    match scene with
    | Composite(scenes) -> List.foldBack flattenAux scenes acc
    | Ellipse _
    | Rect _ -> scene :: acc

let flatten2 scene = flattenAux scene [] |> Seq.ofList

The following does an eager traversal using a local mutable instance of a ResizeArray as the accumulator and then returns the result as a sequence. This example uses a local function and ensures that the mutable state is locally encapsulated:

let flatten3 scene =
    let acc = new ResizeArray<_>()
    let rec flattenAux s =
        match s with
        | Composite(scenes) -> scenes |> List.iter flattenAux
        | Ellipse _ | Rect _ -> acc.Add s
    flattenAux scene;
    Seq.readonly acc

The types of these are as follows:

val flatten2 : Scene -> seq<Scene>
val flatten3 : Scene -> seq<Scene>

There is no hard and fast rule about which of these is best. For prototyping, the second option—doing an efficient, eager traversal with an accumulating parameter—is often the most effective. However, even if you implement an accumulation using an eager traversal, returning the result as an on-demand sequence can still give you added flexibility later in the design process.

Transformational Traversals of Abstract Syntax Representations

In the previous section, you saw examples of accumulating traversals of a syntax representation. It's common to traverse abstract syntax in other ways:

Leaf rewriting (mapping):

Translating some leaf nodes of the representation but leaving the overall shape of the tree unchanged.

Bottom-up rewriting:

Traversing a tree but making local transformations on the way up.

Top-down rewriting:

Traversing a tree but before traversing each subtree, attempting to locally rewrite the tree according to some particular set of rules.

Accumulating and rewriting transformations:

For example, transforming the tree left to right but accumulating a parameter along the way.

For example, the following mapping transformation rewrites all leaf ellipses to rectangles:

let rec rectanglesOnly scene =
    match scene with
    | Composite scenes -> Composite (scenes |> List.map rectanglesOnly)
    | Ellipse rect | Rect rect -> Rect rect

Often, whole classes of transformations are abstracted into aggregate transformation operations, taking functions as parameters. For example, here is a function that applies one function to each leaf rectangle:

let rec mapRects f scene =
    match scene with
    | Composite scenes -> Composite (scenes |> List.map (mapRects f))
    | Ellipse rect -> Ellipse (f rect)
    | Rect rect -> Rect (f rect)

The types of these functions are as follows:

val rectanglesOnly : Scene -> Scene
val mapRects: (RectangleF -> RectangleF) -> Scene -> Scene

Here is a use of the mapRects function to adjust the aspect ratio of all the RectangleF values in the scene (RectangleF values support an Inflate method):

let adjustAspectRatio scene =
scene |> mapRects (fun r -> RectangleF.Inflate(r, 1.1f, 1.0f/1.1f))

Using On-Demand Computation with Abstract Syntax Trees

Sometimes it's feasible to delay the loading or processing of some portions of an abstract syntax tree. For example, imagine if the XML for the small geometric language from the previous section included a construct such as the following, where theFilenodes represent entire subtrees defined in external files:

<Composite>
     <File file='spots.xml'/>
     <File file='dots.xml'/>
</Composite>

It may be useful to delay the loading of these files. One general way to do this is to add a Delay node to the Scene type:

xstype Scene =
    | Ellipse   of RectangleF
    | Rect      of RectangleF
    | Composite of Scene list
    | Delay     of Lazy<Scene>

You can then extend the extractScene function of Listing 9-1 with the following case to handle this node:

let rec extractScene (node: XmlNode) =
    let attribs = node.Attributes
    let childNodes = node.ChildNodes
   match node.Name with
   | "Circle"  ->
       ...
   | "File"   ->
       let file = attribs.GetNamedItem("file").Value
       let scene = lazy (let d = XmlDocument()
                         d.Load(file)
                         extractScene(d :> XmlNode))
       Scene.Delay scene

Code that analyzes trees (for example, via pattern matching) must typically be adjusted to force the computation of delayed values. One way to handle this is to first call a function to eliminate immediately delayed values:

let rec getScene scene =
    match scene with
    | Delay d -> getScene (d.Force())
    | _ -> scene

Here is the function flatten2 from the "Processing Abstract Syntax Representations" section, but redefined to first eliminate delayed nodes:

let rec flattenAux scene acc =
    match getScene(scene) with
    | Composite   scenes -> List.foldBack flattenAux scenes acc
    | Ellipse _ | Rect _ -> scene :: acc
    | Delay _ -> failwith "this lazy value should have been eliminated by getScene"

let flatten2 scene = flattenAux scene []

It's generally advisable to have a single representation of laziness within a single syntax tree design. For example, the following abstract syntax design uses laziness in too many ways:

wtype SceneVeryLazy =
    | Ellipse   of Lazy<RectangleF>
    | Rect      of Lazy<RectangleF>
    | Composite of seq<SceneVeryLazy>
    | LoadFile  of string

The shapes of ellipses and rectangles are lazy computations; each Composite node carries a seq<SceneVeryLazy> value to compute subnodes on demand, and a LoadFile node is used for delayed file loading. This is a bit of a mess, because a single Delay node would in practice cover all these cases.

Note

The Lazy<'T> type is defined in System and represents delayed computations. You access a lazy value via the Value property. F# includes the special keyword lazy for constructing values of this type. Chapter 8 also covered lazy computations.

Caching Properties in Abstract Syntax Trees

For high-performance applications of abstract syntax trees, it can occasionally be useful to cache computations of some derived attributes within the syntax tree itself. For example, let's say you want to compute bounding boxes for the geometric language described in Listing 9-1. It's potentially valuable to cache this computation at Composite nodes. You can use a type such as the following to hold a cache:

type SceneWithCachedBoundingBox =
    | Ellipse of RectangleF
    | Rect    of RectangleF
    | CompositeRepr  of SceneWithCachedBoundingBox list * RectangleF option ref

This is useful for prototyping, although you should be careful to encapsulate the code that is responsible for maintaining this information. Listing 9-2 shows the full code for doing this.

Example 9.2. Adding the Cached Computation of a Local Attribute to an Abstract Syntax Tree

type SceneWithCachedBoundingBox =
    | Ellipse of RectangleF
    | Rect    of RectangleF
    | CompositeRepr   of SceneWithCachedBoundingBox list * RectangleF option ref

    member x.BoundingBox =
        match x with
        | Ellipse rect | Rect rect -> rect
        | CompositeRepr (scenes,cache) ->
            match !cache with
            | Some v -> v
            | None ->
                let bbox =
                    scenes
                    |> List.map (fun s -> s.BoundingBox)
                    |> List.reduce (fun r1 r2 -> RectangleF.Union(r1,r2))
cache := Some bbox
                bbox

   /// Create a Composite node with an initially empty cache
    static member Composite(scenes)  = CompositeRepr(scenes,ref None)

Other attributes that are sometimes cached include the hash values of tree-structured terms and the computation of all the identifiers in a subexpression. The use of caches makes it more awkward to pattern-match on terms. This issue can be largely solved by using active patterns, covered later inthis chapter.

Memoizing Construction of Syntax Tree Nodes

In some cases, abstract syntax tree nodes can end up consuming significant portions of the application's memory budget. In this situation, it can be worth memoizing some or all of the nodes constructed in the tree. You can even go as far as memoizing all equivalent nodes, ensuring that equivalence between nodes can be implemented by pointer equality, a technique often called hash-consing. Listing 9-3 shows an abstract representation of propositional logic terms that ensures that any two nodes that are syntactically identical are shared via a memoizing table. Propositional logic terms are terms constructed using P AND Q, P OR Q, NOT P, and variables a, b, and so on. A non-cached version of the expressions is as follows:

type Prop =
    | And of Prop * Prop
    | Or  of Prop * Prop
    | Not of Prop
    | Var of string
    | True

Example 9.3. Memoizing the Construction of Abstract Syntax Tree Nodes

type Prop =
    | Prop of int

and internal PropRepr =
    | AndRepr of Prop * Prop
    | OrRepr  of Prop * Prop
    | NotRepr of Prop
    | VarRepr of string
    | TrueRepr

open System.Collections.Generic

module PropOps =

    let internal uniqStamp = ref 0
    type internal PropTable() =
        let fwdTable = new Dictionary<PropRepr,Prop>(HashIdentity.Structural)
        let bwdTable = new Dictionary<int,PropRepr>(HashIdentity.Structural)
        member t.ToUnique repr =
            if fwdTable.ContainsKey repr then fwdTable.[repr]
            else let stamp = incr uniqStamp; !uniqStamp
                 let prop = Prop stamp
fwdTable.Add (repr, prop)
                 bwdTable.Add (stamp, repr)
                 prop
        member t.FromUnique (Prop stamp) =
            bwdTable.[stamp]

    let internal table = PropTable ()

  // Public construction functions
    let And (p1,p2) = table.ToUnique (AndRepr (p1, p2))
    let Not p       = table.ToUnique (NotRepr p)
    let Or (p1,p2)  = table.ToUnique (OrRepr (p1, p2))
    let Var p       = table.ToUnique (VarRepr p)
    let True        = table.ToUnique TrueRepr
    let False       = Not True

  // Deconstruction function
    let internal getRepr p = table.FromUnique p

You can construct terms using the operations in PropOps much as you would construct terms using the nonmemoized representation:

> open PropOps;;
> True;;
val it : Prop = Prop 1

> And (Var "x",Var "y");;
val it : Prop = Prop 5

> getRepr it;;
val it : PropRepr = AndRepr(Prop 3, Prop 4)

> And(Var "x",Var "y");;
val it : Prop = Prop 5

In this example, when you create two syntax trees using the same specification, And (Var "x",Var "y"), you get back the same Prop object with the same stamp 5. You can also use memoization techniques to implement interesting algorithms; in Chapter 12, you see an important representation of propositional logic called a binary decision diagram (BDD) based on a memoization table similar to the previous example.

The use of unique integer stamps and a lookaside table in the previous representation also has some drawbacks; it's harder to pattern-match on abstract syntax representations, and you may need to reclaim and recycle stamps and remove entries from the lookaside table if a large number of terms is created or if the overall set of stamps must remain compact. You can solve the first problem by using active patterns, covered next in this chapter. If necessary, you can solve the second problem by scoping stamps in an object that encloses the uniqStamp state, the lookaside table, and the construction functions. Alternatively, you can explicitly reclaim the stamps by using the IDisposable idiom described in Chapter 8, although this approach can be intrusive to your application.

Introducing Active Patterns

Pattern matching is one of the key techniques provided in F# for decomposing abstract syntax trees and other abstract representations of languages. So far in this book, all the examples of pattern matching have been directly over the core representations of data structures: for example, directly matching on the structure of lists, options, records, and discriminated unions. But pattern matching in F# is also extensible—that is, you can define new ways of matching over existing types. You do this through a mechanism called active patterns.

This book covers only the basics of active patterns. However, they can be indispensable, because they can let you continue to use pattern matching with your types even after you hide their representations. Active patterns also let you use pattern matching with .NET object types. The following section covers active patterns and how they work.

Converting the Same Data to Many Views

In high-school math courses, you were probably taught that you can view complex numbers in two ways: as rectangular coordinates x + yi or as polar coordinates of a phase r and magnitude φ. In most computer systems, complex numbers are stored in the first format, although often the second format is more useful.

Wouldn't it be nice if you could look at complex numbers through either lens? You could do this by explicitly converting from one form to another when needed, but it would be better to have your programming language look after the transformations needed to do this for you. Active patterns let you do exactly that. First, here is a standard definition of complex numbers:

[<Struct>]
type Complex(r: float, i: float) =
    static member Polar(mag,phase) = Complex(mag * cos phase, mag * sin phase)
    member x.Magnitude = sqrt(r*r + i*i)
    member x.Phase = atan2 i r
    member x.RealPart = r
    member x.ImaginaryPart = i

Here is a pattern that lets you view complex numbers as rectangular coordinates:

let (|Rect|) (x:Complex) = (x.RealPart, x.ImaginaryPart)

And here is an active pattern to help you view complex numbers in polar coordinates:

let (|Polar|) (x:Complex) = (x.Magnitude, x.Phase)

The key thing to note is that these definitions let you useRect Polar as tags in pattern matching. For example, you can now write the following to define addition and multiplication over complex numbers:

let addViaRect a b =
    match a, b with
    | Rect (ar, ai), Rect (br, bi) -> Complex (ar+br, ai+bi)

let mulViaRect a b =
    match a, b with
    | Rect (ar, ai), Rect (br, bi) -> Complex (ar*br - ai*bi, ai*br + bi*ar)

As it happens, multiplication on complex numbers is easier to express using polar coordinates, implemented as follows:

let mulViaPolar a b =
    match a, b with
    | Polar (m, p), Polar (n, q) -> Complex.Polar (m*n, p+q)

Here is an example of using the (|Rect|) and (|Polar|) active patterns directly on some complex numbers via the pattern tags Rect and Polar. You first make the complex number 3+4i:

> let c = Complex (3.0, 4.0);;
val c : complex

> c;;
val it : complex = 3.0r+4.0i

>  match c with
   | Rect (x, y) -> printfn "x = %g, y = %g" x y;;
x = 3, y = 4
val it : unit = ()

>  match c with
   | Polar (x, y) -> printfn "x = %g, y = %g" x y;;
x = 5.0, y = 0.927295
val it : unit = ()

> addViaRect c c;;
val it : complex = 6.0r+8.0i

> mulViaRect c c;;
val it : complex = −7.0r+24.0i

> mulViaPolar c c;;
val it : complex = −7.0r+24.0i

As you may expect, you get the same results if you multiply via rectangular or polar coordinates. However, the execution paths are quite different. Let's look closely at the definition of mulViaRect. The important lines are in bold here:

let mulViaRect a b =
    match a, b with
    | Rect (ar, ai), Rect (br, bi) ->
        Complex (ar*br - ai*bi, ai*br + bi*ar)

When F# needs to match the values a and b against the patterns Rect (ar, ai) and Rect (br, bi), it doesn't look at the contents of a and b directly. Instead, it runs a function as part of pattern matching (which is why they're called active patterns). In this case, the function executed is (|Rect|), which produces a pair as its result. The elements of the pair are then bound to the variables ar and ai. Likewise, in the definition of mulViaPolar, the matching is performed partly by running the function (|Polar|).

The functions (|Rect|) and (|Polar|) are allowed to do anything, as long as each ultimately produces a pair of results. Here are the types of (|Rect|) and (|Polar|):

val (|Rect|) : complex -> float * float
val (|Polar|) : complex -> float * float

These types are identical, but they implement completely different views of the same data.

The definitions of addViaRect and mulViaPolar can also be written using pattern matching in argument position:

let add2 (Rect (ar, ai)) (Rect (br, bi))   = Complex (ar+br, ai+bi)
let mul2 (Polar (r1, th1)) (Polar (r2, th2)) = Complex (r1*r2, th1+th2)

Matching on .NET Object Types

One of the useful things about active patterns is that they let you use pattern matching with existing.NET object types. For example, the .NET object type System.Type is a runtime representation of types in .NET and F#. Here are the members found on this type:

type System.Type with
    member IsGenericType : bool
    member GetGenericTypeDefinition : unit -> Type
    member GetGenericArguments : unit -> Type[]
    member HasElementType : bool
    member GetElementType : unit -> Type
    member IsByRef : bool
    member IsPointer : bool
    member IsGenericParameter : bool
    member GenericParameterPosition : int

This type looks very much like one you'd like to pattern-match against. There are clearly three or four distinct cases here, and pattern matching helps you isolate them. You can define an active pattern to achieve this, as shown in Listing 9-4.

Example 9.4. Defining an Active Pattern for Matching on System.Type Values

let (|Named|Array|Ptr|Param|) (typ : System.Type) =
    if typ.IsGenericType
    then Named(typ.GetGenericTypeDefinition(),typ.GetGenericArguments())
    elif typ.IsGenericParameter then Param(typ.GenericParameterPosition)
    elif not typ.HasElementType then Named(typ, [| |])
    elif typ.IsArray then Array(typ.GetElementType(),typ.GetArrayRank())
    elif typ.IsByRef then Ptr(true,typ.GetElementType())
    elif typ.IsPointer then Ptr(false,typ.GetElementType())
    else failwith "MSDN says this can't happen"

This then lets you use pattern matching against a value of this type:

open System
let rec formatType typ =
    match typ with
    | Named (con, [| |]) -> sprintf "%s" con.Name
    | Named (con, args) -> sprintf "%s<%s>" con.Name (formatTypes args)
    | Array (arg, rank) -> sprintf "Array(%d,%s)" rank (formatType arg)
    | Ptr(true,arg) -> sprintf "%s&" (formatType arg)
    | Ptr(false,arg) -> sprintf "%s*" (formatType arg)
    | Param(pos) -> sprintf "!%d" pos
and formatTypes typs =
    String.Join(",", Array.map formatType typs)
or collect the free generic type variables:
let rec freeVarsAcc typ acc =
    match typ with
    | Array (arg, rank) -> freeVarsAcc arg acc
    | Ptr (_,arg) -> freeVarsAcc arg acc
    | Param _ -> (typ :: acc)
    | Named (con, args) -> Array.foldBack freeVarsAcc args acc
let freeVars typ = freeVarsAcc typ []

Defining Partial and Parameterized Active Patterns

Active patterns can also be partial. You can recognize a partial pattern by a name such as (|MulThree|_|) and by the fact that it returns a value of type 'T option for some 'T. For example:

let (|MulThree|_|) inp = if inp % 3 = 0 then Some(inp/3) else None
let (|MulSeven|_|) inp = if inp % 7 = 0 then Some(inp/7) else None

Finally, active patterns can also be parameterized. You can recognize a parameterized active pattern by the fact that it takes several arguments. For example:

let (|MulN|_|) n inp = if inp % n = 0 then Some(inp/n) else None

The F# quotation API Microsoft.FSharp.Quotations uses both parameterized and partial patterns extensively.

Hiding Abstract Syntax Implementations with Active Patterns

Earlier in this chapter, you saw the following type that defines an optimized representation of propositional logic terms using a unique stamp for each syntactically unique term:

type Prop = Prop of int
and internal PropRepr =
    | AndRepr of Prop * Prop
    | OrRepr  of Prop * Prop
    | NotRepr of Prop
    | VarRepr of string
    | TrueRepr

However, what happens if you want to pattern-match against values of type Prop? Even if you exposed the representation, all you would get is an integer, which you would have to look up in an internal table. You can define an active pattern for restoring matching on that data structure, as shown in Listing 9-5.

Example 9.5. Extending Listing 9-3 with an Active Pattern for the Optimized Representation

module PropOps =
    ...
    let (|And|Or|Not|Var|True|) prop =
        match table.FromUnique prop with
        | AndRepr (x, y) -> And (x, y)
        | OrRepr (x, y) -> Or (x, y)
        | NotRepr x -> Not x
        | VarRepr v -> Var v
        | TrueRepr -> True

This code defines an active pattern in the auxiliary module PropOps that lets you pattern-match against Prop values, despite the fact that they're using optimized unique-integer references under the hood. For example, you can define a pretty-printer for Prop terms as follows, even though they're using optimized representations:

open PropOps
let rec showProp prec prop =
    let parenIfPrec lim s = if prec < lim then "(" + s + ")" else s
    match prop with
    | Or (p1, p2)  -> parenIfPrec 4 (showProp 4 p1 + " || " + showProp 4 p2)
    | And (p1, p2) -> parenIfPrec 3 (showProp 3 p1 + " && " + showProp 3 p2)
    | Not p        -> parenIfPrec 2 ("not " + showProp 1 p)
    | Var v        -> v
    | True         -> "T"

Likewise, you can define functions to place the representation in various normal forms. For example, the following function computes negation normal form (NNF), where all instances of NOT nodes have been pushed to the leaves of the representation:

let rec nnf sign prop =
    match prop with
    | And (p1, p2) -> if sign then And (nnf sign p1, nnf sign p2)
                      else Or (nnf sign p1, nnf sign p2)
    | Or (p1, p2)  -> if sign then Or (nnf sign p1, nnf sign p2)
                      else And (nnf sign p1, nnf sign p2)
    | Not p        -> nnf (not sign) p
    | Var _ | True -> if sign then prop else Not prop
let NNF prop = nnf true prop

The following demonstrates that two terms have equivalent NNF normal forms:

> let t1 = Not(And(Not(Var("x")),Not(Var("y"))));;
val t1 : Prop

> fsi.AddPrinter(showProp);;
> t1;;
val it : Prop = not (not x && not y)

> let t2 = Or(Not(Not(Var("x"))),Var("y"));;
val t2 : Prop

> t2;;
val it : Prop = not (not x) || y

> (t1 = t2);;
val it : bool = false

> NNF t1;;
val it : Prop = x || y

> NNF t2;;
val it : Prop = x || y

> NNF t1 = NNF t2;;
val it : bool = true

Embedded Computational Languages with Workflows

Chapter 3 introduced a useful notation for generating sequences of data, called sequence expressions. For example:

> seq { for i in 0 .. 3 -> (i,i*i) };;
val it : seq<int * int> = seq [ (0,0); (1,1); (2,4); (3,9) ]

Sequence expressions are used extensively throughout this book. For example, Chapter 15 uses sequence expressions for queries that are executed on a database. It turns out that sequence expressions are just one instance of a more general construct called computation expressions. These are also called workflows, although they bear only a passing similarity to the workflows used to model business processes. The general form of a computation expression is builder { comp-expr }. Table 9-2 shows the primary constructs that can be used within the braces of a computation expression and how these constructs are de-sugared by the F# compiler given a computation expression builder builder.

The three most important applications of computation expressions in F# programming are as follows:

  • General-purpose programming with sequences, lists, and arrays

  • Parallel, asynchronous, and concurrent programming using asynchronous workflows, discussed in detail in Chapter 13

  • Database queries, by quoting a workflow and translating it to SQL via the .NET LINQ libraries, a technique demonstrated in Chapter 15

This section covers briefly how computation expressions work through some simple examples.

Table 9.2. Main Constructs in Computation Expressions and Their De-sugaring

Construct

De-sugared Form

let! pat = expr in cexpr

b.Bind (expr, (fun pat -> «cexpr»))

let pat = expr in cexpr

b.Let (expr, (fun pat -> «cexpr»))

use pat = expr in cexpr

b.Using (expr, (fun pat -> «cexpr»))

use! pat = expr in cexpr

b.Bind (expr, (fun x -> b.Using (x, fun pat-> «cexpr»)))

do! expr in cexpr

b.Bind (expr, (fun () -> «cexpr»))

do expr in cexpr

b.Let (expr, (fun () -> «cexpr»))

for pat in expr do cexpr

b.For (expr, (fun pat -> «cexpr»))

while expr do cexpr

b.While ((fun () -> expr), b.Delay (fun () -> «cexpr»))

if expr then cexpr1 else cexpr2

if expr then «cexpr1» else «cexpr2»

if expr then cexpr

if expr then «cexpr» else b.Zero()

cexpr1cexpr2

v.Combine («cexpr1», b.Delay(fun () -> «cexpr2»))

yield expr

b.Yield expr

yield! expr

b.YieldFrom expr

return expr

b.Return expr

return! expr

b.ReturnFrom expr

Note

If you've never seen F# workflows or Haskell monads before, then you may find that workflows take a bit of getting used to. They give you a way to write computations that may behave and execute quite differently than normal programs.

An Example: Success/Failure Workflows

Perhaps the simplest kind of workflow is one where failure of a computation is made explicit: for example, where each step of the workflow may either succeed, by returning a result Some(v), or fail, by returning the value None. You can model such a workflow using functions of type unit -> 'T option—that is, functions that may compute a result or may not. In this section, you can assume that these functions are pure and terminating: they have no side effects, raise no exceptions, and always terminate.

Whenever you define a new kind of workflow, it's useful to give a name to the type of values/objects generated by the workflow. In this case, let's call them Attempt objects:

type Attempt<'T> = (unit -> 'T option)

Of course, you can use regular functional programming to start to build Attempt<'T> objects:

let succeed x = (fun () -> Some(x)) : Attempt<'T>
let fail      = (fun () -> None) : Attempt<'T>
let runAttempt (a:Attempt<'T>) = a()

These conform to the following types:

val succeed : 'T -> Attempt<'T>
val fail : Attempt<'T>
val runAttempt : Attempt<'T> -> 'T option

However, using only normal F# expressions to build Attempt values can be a little tedious and lead to a proliferation of many different functions that stitch together Attempt values in straightforward ways. Luckily, as you've seen with sequence expressions, F# comes with predefined syntax for building objects such as Attempt values. You can use this syntax with a new type by defining a builder object that helps stitch together the fragments that make up the computation expression. Here's an example of the signature of an object you have to define in order to use workflow syntax with a new type (note that this is a type signature for an object, not actual code—we show how to define the AttemptBuilder type and its members later in this section):

type AttemptBuilder =
    member Bind : Attempt<'T> * ('T -> Attempt<'U>) -> Attempt<'U>
    member Delay : (unit -> Attempt<'T>) -> Attempt<'T>
    member Let : 'T * ('T -> Attempt<'T>) -> Attempt<'T>
    member Return : 'T -> Attempt<'T>

Typically, there is one global instance of each such builder object. For example:

let attempt = new AttemptBuilder()
val attempt : AttemptBuilder

First, let's see how you can use the F# syntax for workflows to build Attempt objects. You can build Attempt values that always succeed:

> let alwaysOne = attempt { return 1 };;
val alwaysOne: Attempt<int>

> let alwaysPair = attempt { return (1,"two") };;
val alwaysPair: Attempt<int * string>

> runAttempt alwaysOne;;
val it : int option = Some 1

> runAttempt alwaysPair;;
val it : (int * string) option = Some(1,"two")

Note that Attempt values such as alwaysOne are just functions; to run an Attempt value, you just apply it. These correspond to uses of the succeed function, as you see shortly.

You can also build more interesting Attempt values that check a condition and return different Attempt values on each branch, as shown in the next example:

> let failIfBig n = attempt { if n > 1000 then return! fail else return n };;
val failIfBig: int -> Attempt<int>

> runAttempt (failIfBig 999);;
val it : int option = Some 999

> runAttempt (failIfBig 1001);;
val it : int option = None

Here, one branch uses return! to return the result of running another Attempt value, and the other uses return to give a single result. These correspond to yield! and yield in sequence expressions.

Next, you can build Attempt values that sequence together two Attempt values by running one, getting its result, binding it to a variable, and running the second. You do this by using the syntax form let! pat = expr, which is unique to computation expressions:

> let failIfEitherBig (inp1,inp2) =
        attempt { let! n1 = failIfBig inp1
                  let! n2 = failIfBig inp2
                  return (n1,n2) };;
val failIfEitherBig: int * int -> Attempt<int * int>

> runAttempt (failIfEitherBig (999,998));;
val it : (int * int) option = Some(999,998)

> runAttempt (failIfEitherBig (1003,998));;
val it : (int * int) option = None

> runAttempt (failIfEitherBig (999,1001));;
val it : (int * int) option = None

Let's look at this more closely. First, what does the first let! do? It runs the Attempt value failIfBig inp1; and if this returns None, the whole computation returns None. If the computation on the rightdelivers a value (that is, returns Some), then it binds the result to the variable n1 andcontinues. It's important to note the following for the expression let! n1 = failIfBig inp1:

  • The expression on the right (failIfBig inp1) has type Attempt<int>.

  • The variable on the left (n1) is of type int.

This is somewhat similar to a sequence of normal let binding. However, let! also controls whether the rest of the computation is executed; in the case of the Attempt type, it executes the rest of the computation only when it receives a Some value. Otherwise, it returns None, and the rest of the code is never executed.

You can use normal let bindings in computation expressions. For example:

let sumIfBothSmall (inp1,inp2) =
        attempt { let! n1 = failIfBig inp1
                  let! n2 = failIfBig inp2
                  let sum = n1 + n2
                  return sum }

In this case, the let binding executes exactly as you would expect; it takes the expression n1+n2 and binds its result to the value sum. To summarize, you've seen that computation expressions let you do the following:

  • Use an expression-like syntax to build Attempt computations

  • Sequence these computations together using the let! construct

  • Return results from these computations using return and return!

  • Compute intermediate results using let

Workflows let you do a good deal more than this, as you see in the sections that follow.

Defining a Workflow Builder

Listing 9-6 shows the implementation of the workflow builder for Attempt workflows; this is the simplest definition for AttemptBuilder.

Example 9.6. Defining a Workflow Builder

let succeed x = (fun () -> Some(x))
let fail      = (fun () -> None)
let runAttempt (a:Attempt<'T>) = a()
let bind p rest = match runAttempt p with None -> fail | Some r -> (rest r)
let delay f = (fun () -> runAttempt (f ()))

type AttemptBuilder() =
    /// Wraps an ordinary value into an Attempt value.
    /// Used to de-sugar uses of 'return' inside computation expressions.
member b.Return(x) = succeed x

    /// Composes two attempt values. If the first returns Some(x) then the result
    /// is the result of running rest(x).
    /// Used to de-sugar uses of 'let!' inside computation expressions.
member b.Bind(p,rest) = bind p rest


/// Delays the construction of an attempt until just before it is executed
    member b.Delay(f) = delay f

    /// Used to de-sugar uses of 'let' inside computation expressions.
    member b.Let(p,rest) : Attempt<'T> = rest p

let attempt = new AttemptBuilder()

The inferred types here are as follows:

type AttemptBuilder =
    new : unit -> AttemptBuilder
    member Bind   : Attempt<'T> * ('T -> Attempt<'U>) -> Attempt<'U>
    member Delay  : (unit -> Attempt<'T>) -> Attempt<'T>
    member Let    : 'T * ('T -> Attempt<'U>) -> Attempt<'U>
    member Return : 'T -> Attempt<'T>

val attempt : AttemptBuilder

F# implements workflows by de-sugaring computation expressions using a builder. For example, given the previous AttemptBuilder, the following workflow

attempt { let! n1 = failIfBig inp1
          let! n2 = failIfBig inp2
          let sum = n1 + n2
          return sum };;

de-sugars to this:

attempt.Bind( failIfBig inp1,(fun n1 ->
   attempt.Bind(failIfBig inp2,(fun n2 ->
      attempt.Return sum)))))

One purpose of the F# workflow syntax is to make sure you don't have to write this sort of thing by hand.

The de-sugaring of the workflow syntax is implemented by the F# compiler. Table 9-3 shows some of the typical signatures that a workflow builder needs to implement.

Table 9.3. Some Typical Workflow Builder Members as Required by the F# Compiler

Member

Description

member Bind : M<'T> * ('T -> M<'U>) -> M<'U>

Used to de-sugar let! and do! within computation expressions.

member Return : 'T -> M<'T>

Used to de-sugar return within computation expressions.

member ReturnFrom : M<'T> -> M<'T>

Used to de-sugar return! within computation expressions.

member Delay : (unit -> M<'T>) -> M<'T>

Used to ensure that side effects within a computation expression are performed when expected.

member For : seq<'T> * ('T -> M<'U>) -> M<'U>

Used to de-sugar for ... do ... within computation expressions. M<'U> can optionally be M<unit>.

Member

Description

member While : (unit -> bool) * M<'T> -> M<'T>

Used to de-sugar while ... do ... within computation expressions. M<'T> may optionally be M<unit>.

member Using : 'T * ('T -> M<'T>) -> M<'T> when 'T :> IDisposable

Used to de-sugar use bindings within computation expressions.

member Combine : M<'T> * M<'T> -> M<'T>

Used to de-sugar sequencing within computation expressions. The first M<'T> may optionally be M<unit>.

member Zero : unit -> M<'T>

Used to de-sugar empty else branches of if/then constructs within computation expressions.

Most of the elements of a workflow builder are usually implemented in terms of simpler primitives. For example, let's assume you're defining a workflow builder for some type M<'T> and you already have implementations of functions bindM and returnM with the following types:

val bindM : M<'T> -> ('T -> M<'U>) -> M<'U>
val returnM : 'T -> M<'T>

Then you can implement Delay using the following functions:

let delayM f = bindM (returnM ()) f

You can now define an overall builder in terms of all four functions:

type MBuilder() =
member b.Return(x)    = returnM x
member b.Bind(v,f)    = bindM v f
    member b.Delay(f)     = delayM f

However, Let and Delay may also have more efficient direct implementations, which is why F# doesn't insert the previous implementations automatically.

Workflows and Untamed Side Effects

It's possible, and in some cases even common, to define workflows that cause side effects. For example, you can use printfn in the middle of an Attempt workflow:

let sumIfBothSmall (inp1,inp2) =
    attempt { let! n1 = failIfBig inp1
              printfn "Hey, n1 was small!"
              let! n2 = failIfBig inp2
              printfn "n2 was also small!"
              let sum = n1 + n2
              return sum }

Here's what happens when you call this function:

> runAttempt(sumIfBothSmall (999,999));;
Hey, n1 was small!
n2 was also small!
val it : int option = Some 1998

> runAttempt(sumIfBothSmall (999,1003));;
Hey, n1 was small!
val it : int option = None

Side effects in workflows must be used with care, particularly because workflows are typically used to construct delayed or on-demand computations. In the previous example, printing is a fairly benign side effect. More significant side effects such as mutable state can also be sensibly combined with some kinds of workflows, but be sure you understand how the side effect will interact with the particular kind of workflow you're using. For example, this example allocates a piece of mutable state that is local to the Attempt workflow, and this is used to accumulate the sum:

let sumIfBothSmall (inp1,inp2) =
    attempt { let sum = ref 0
              let! n1 = failIfBig inp1
              sum := sum.Value + n1
              let! n2 = failIfBig inp2
              sum := sum.Value + n2
              return sum.Value }

We leave it as an exercise for you to examine the de-sugaring of this workflow to see that the mutable reference is indeed local, in the sense that it doesn't escape the overall computation, and that different executions of the same workflow use different reference cells.

As mentioned, workflows are nearly always delayed computations. As you saw in Chapter 4, delayed computations and side effects can interact. For this reason, the de-sugaring of workflow syntax inserts a Delay operation around the entire workflow. The following

let printThenSeven =
        attempt { printf "starting..."
                  return 3 + 4 }

de-sugars to

attempt.Delay(fun () ->
            printf "starting..."
            attempt.Return(3+4))

This means that "starting . . ." is printed each time the printThenSeven attempt object is executed.

Example: Probabilistic Workflows

Workflows provide a fascinating way to embed a range of nontrivial, nonstandard computations into F#. To give you a feel for this, this section defines a probabilistic workflow. That is, instead of writing expressions to compute, say, integers, you instead write expressions that compute distributions of integers. This case study is based on a paper by Ramsey and Pfeffer from 2002.

For the purposes of this section, you're interested in distributions over discrete domains characterized by three things:

  • You want to be able to sample from a distribution (for example, sample an integer or a coin flip).

  • You want to compute the support of a distribution: that is, a set of values where all elements outside the set have zero chance of being sampled.

  • You want to compute the expectation of a function over the distribution. For example, you can compute the probability of selecting element A by evaluating the expectation of the function (fun x -> if x = A then 1.0 else 0.0).

You can model this notion of a distribution with abstract objects. Listing 9-7 shows the definition of a type of distribution values and an implementation of the basic primitives always and coinFlip, which help build distributions.

Example 9.7. Implementing Probabilistic Modeling Using Computation Expressions

type Distribution<'T when 'T : comparison> =
    abstract Sample : 'T
    abstract Support : Set<'T>
    abstract Expectation: ('T -> float) -> float

let always x =
    { new Distribution<'T> with
         member d.Sample = x
         member d.Support = Set.singleton x
         member d.Expectation(H) = H(x) }

let rnd = System.Random()

let coinFlip (p:float) (d1:Distribution<'T>) (d2:Distribution<'T>) =
    if p < 0.0 || p > 1.0 then failwith "invalid probability in coinFlip"
    { new Distribution<'T> with
         member d.Sample =
             if rnd.NextDouble() < p then d1.Sample else d2.Sample
         member d.Support = Set.union d1.Support d2.Support
         member d.Expectation(H) =
             p * d1.Expectation(H) + (1.0-p) * d2.Expectation(H) }

The types of these primitives are as follows:

type Distribution<'T> =
    abstract Expectation: ('T -> float) -> float
    abstract Sample : 'T
    abstract Support : Set<'T>

val always: 'T -> Distribution<'T>
val coinFlip : float -> Distribution<'T> -> Distribution<'T> -> Distribution<'T>

The simplest distribution is always x; this is a distribution that always samples to the same value. Its expectation and support are easy to calculate. The expectation of a function H is just H applied to the value, and the support is a set containing the single value x. The next distribution defined is coinFlip, which is a distribution that models the ability to choose between two outcomes.

Listing 9-8 shows how you can define a workflow builder for distribution objects.

Example 9.8. Defining a Builder for Probabilistic Modeling Using Computation Expressions

let bind (dist:Distribution<'T>) (k: 'T -> Distribution<'U>) =
    { new Distribution<'U> with
         member d.Sample =
             (k dist.Sample).Sample
         member d.Support =
             Set.unionMany (dist.Support |> Set.map (fun d -> (k d).Support))
         member d.Expectation H =
             dist.Expectation(fun x -> (k x).Expectation H) }

type DistributionBuilder() =
    member x.Delay f = bind (always ()) f
    member x.Bind (d, f) = bind d f
    member x.Return v = always v
    member x.ReturnFrom vs = vs

let dist = new DistributionBuilder()

The types of these primitives are as follows:

val bind: Distribution<'T> -> ('T -> Distribution<'U>) -> Distribution<'U>
val dist: DistributionBuilder

Listing 9-8 shows the all-important bind primitive; it combines two distributions, using the sample from the first to guide the sample from the second. The support and expectation are calculated by taking the support from the first and splaying it over the support of the second. The expectation is computed by using the first distribution to compute the expectation of a function derived from the second. These are standard results in probability theory and are the basic machinery you need to get going with some interesting modeling.

Before you begin using workflow syntax, you define two derived functions to compute distributions. Listing 9-9 shows the additional derived operations for distribution objects that you use later in this example.

Example 9.9. Listing 9-9. Defining the Derived Operations for Probabilistic Modeling Using Computation Expressions

let weightedCases (inp: ('T * float) list) =
    let rec coinFlips w l =
        match l with
        | []          -> failwith "no coinFlips"
        | [(d,_)]     -> always d
        | (d,p)::rest -> coinFlip (p/(1.0-w)) (always d) (coinFlips (w+p) rest)
    coinFlips 0.0 inp

let countedCases inp =
    let total = Seq.sumBy (fun (_,v) -> v) inp
    weightedCases (inp |> List.map (fun (x,v) -> (x, float v / float total)))

The two functions weightedCases and countedCases build distributions from the weighted selection of a finite number of cases. The types are as follows:

val weightedCases : ('T * float) list -> Distribution<'T>
val countedCases : ('T * int) list -> Distribution<'T>

For example, here is the distribution of outcomes on a fair European roulette wheel:

type Outcome = Even | Odd | Zero
let roulette = countedCases [ Even,18; Odd,18; Zero,1]

You can now use sampling to draw from this distribution:

> roulette.Sample;;
val it:  Outcome = Even

> roulette.Sample;;
val it:  Outcome = Odd

And you can compute the expected payout of a $5 bet on Even, where you would get a $10 return:

> roulette.Expectation (function Even -> 10.0 | Odd -> 0.0 | Zero -> 0.0);;
val it:  float = 4.864864865

Now, let's model another scenario. Let's say you have a traffic light with the following probability distribution for showing red/yellow/green:

type Light =
    | Red
    | Green
    | Yellow

let trafficLightD = weightedCases [ Red,0.50; Yellow,0.10; Green, 0.40 ]

Drivers are defined by their behavior with respect to a traffic light. For example, a cautious driver is highly likely to brake on a yellow light and always stops on a red:

type Action = Stop | Drive

let cautiousDriver light =
    dist { match light with
           | Red -> return Stop
           | Yellow -> return! weightedCases [ Stop, 0.9; Drive, 0.1 ]
           | Green -> return Drive }

An aggressive driver is unlikely to brake on yellow and may even go through a red light:

let aggressiveDriver light =
    dist { match light with
           | Red    -> return! weightedCases [ Stop, 0.9; Drive, 0.1 ]
           | Yellow -> return! weightedCases [ Stop, 0.1; Drive, 0.9 ]
           | Green  -> return Drive }

The following gives the value of the light showing in the other direction:

let otherLight light =
    match light with
    | Red -> Green
    | Yellow -> Red
    | Green -> Red

You can now model the probability of a crash between two drivers given a traffic light. Assume there is a 10 percent chance that two drivers going through the intersection will avoid a crash:

type CrashResult = Crash | NoCrash

let crash (driverOneD, driverTwoD, lightD) =
    dist { // Sample from the traffic light
let! light = lightD

           // Sample the first driver's behavior given the traffic light
           let! driverOne = driverOneD light

           // Sample the second driver's behavior given the traffic light
           let! driverTwo = driverTwoD (otherLight light)

           // Work out the probability of a crash
           match driverOne, driverTwo with
             | Drive,Drive -> return! weightedCases [ Crash, 0.9; NoCrash, 0.1 ]
             | _ -> return NoCrash }

You can now instantiate the model to a cautious/aggressive driver pair, sample the overall model, and compute the overall expectation of a crash as approximately 3.7 percent:

> let model = crash (cautiousDriver, aggressiveDriver, trafficLightD);;
val model : Distribution<CrashResult>

> model.Sample;;
val it : CrashResult = NoCrash
...
> model.Sample;;
val it : CrashResult = Crash

> model.Expectation (function Crash -> 1.0 | NoCrash -> 0.0);;
val it : float = 0.0369

Note

This section showed how to define a simplistic embedded computational probabilistic modeling language. There are many more efficient and sophisticated techniques to apply to the description, evaluation, and analysis of probabilistic models than those shown here, and you can make the implementation of the primitives shown here more efficient by being more careful about the underlying computational representations.

Combining Workflows and Resources

In some situations, workflows can sensibly make use of transient resources such as files. The tricky thing is that you still want to be careful about closing and disposing of resources when the workflow is complete or when it's no longer being used. For this reason, the workflow type must be carefully designed to correctly dispose of resources halfway through a computation if necessary. Sequence expressions are a great example where this is useful. For example, the following sequence expression opens a file and reads lines on demand:

let linesOfFile(fileName) =
    seq { use textReader = System.IO.File.OpenText(fileName)
          while not textReader.EndOfStream do
              yield textReader.ReadLine() }

Chapter 8 discussed the construct use pat = expr. As shown in Table 9-2, you can also use this construct within workflows. In this case, the use pat = expr construct de-sugars into a call to seq.Using. In the case of sequence expressions, this function is carefully implemented to ensure that textReader is kept open for the duration of the process of reading from the file. Furthermore, the Dispose function on each generated IEnumerator object for a sequence calls the textReader.Dispose() method. This ensures that the file is closed even if you enumerate only half of the lines in the file. Workflows thus allow you to scope the lifetime of a resource over a delayed computation.

Recursive Workflow Expressions

Like functions, workflow expressions can be defined recursively. Many of the best examples are generative sequences. For example:

let rnd = System.Random()

let rec randomWalk k =
    seq { yield k
          yield! randomWalk (k + rnd.NextDouble() - 0.5) }
> randomWalk 10.0;;
val it: seq<float> = seq [10.0; 10.23817784; 9.956430122; 10.18110362; ...]

> randomWalk 10.0;;
val it : seq<float> = seq [10.0; 10.19761089; 10.26774703; 9.888072922; ...]

Using F# Reflection

The final topics in this chapter are F# quotations, which provide a way to get at a representation of F# expressions as abstract syntax trees, and reflection, which lets you get at representations of assemblies, type definitions, and member signatures. Let's look at reflection first.

Reflecting on Types

One of the simplest uses of reflection is to access the representation of types and generic type variables using the typeof operator. For example, typeof<int> and typeof<'T> are both expressions that generate values of type System.Type. Given a System.Type value, you can use the .NET APIs to access the System.Reflection.Assembly value that represents the .NET assembly that contains the definition of the type (.NET assemblies are described in Chapter 7). You can also access other types in the System.Reflection namespace, such as MethodInfo, PropertyInfo, MemberInfo, and ConstructorInfo. The following example examines the names associated with some common types:

> let intType = typeof<int>;;
val intType : System.Type

> intType.FullName;;
val it : string = "System.Int32"

> intType.AssemblyQualifiedName;;
val it : string = "System.Int32, mscorlib, Version=2.0.0.0, Culture=neutral,
PublicKeyToken=b77a5c561934e089"

> let intListType = typeof<int list>;;
val intListType : System.Type

> intListType.FullName;;
val it : string = "Microsoft.FSharp.Collections.List`1[[System.Int32, mscorlib,
Version=2.0.0.0, Culture=neutral, PublicKeyToken=b77a5c561934e089]]"

Schema Compilation by Reflecting on Types

The F# library includes the namespace Microsoft.FSharp.Reflection, which contains types and functions that extend the functionality of the System.Reflection namespace of .NET. Chapter 10 describes these types and functions.

You can use the combination of .NET and F# reflection to provide generic implementations of language-related transformations. This section gives one example of this powerful technique. Listing 9-10 shows the definition of a generic schema reader compiler, where a data schema is described using F# types and the schema compiler helps convert untyped data from text files into this data schema.

Example 9.10. Using Types and Attributes to Guide Dynamic Schema Compilation

open System
open System.IO
open System.Globalization
open Microsoft.FSharp.Reflection

/// An attribute to be added to fields of a schema record type to indicate the
/// column used in the data format for the schema.
type ColumnAttribute(col:int) =
    inherit Attribute()
    member x.Column = col

/// SchemaReader builds an object that automatically transforms lines of text
/// files in comma-separated form into instances of the given type 'Schema.
/// 'Schema must be an F# record type where each field is attributed with a
/// ColumnAttribute attribute, indicating which column of the data the record
/// field is drawn from. This simple version of the reader understands
/// integer, string and DateTime values in the CSV format.
type SchemaReader<'Schema>() =

    // Grab the object for the type that describes the schema
    let schemaType = typeof<'Schema>

    // Grab the fields from that type
    let fields = FSharpType.GetRecordFields(schemaType)

    // For each field find the ColumnAttribute and compute a function
    // to build a value for the field
    let schema =
        fields |> Array.mapi (fun fldIdx fld ->
            let fieldInfo = schemaType.GetProperty(fld.Name)
            let fieldConverter =
                match fld.PropertyType with
                |  ty when ty = typeof<string>   -> (fun (s:string) -> box s)
                |  ty when ty = typeof<int>      -> (System.Int32.Parse >> box)
                |  ty when ty = typeof<DateTime> ->
                     (fun s -> box (DateTime.Parse(s,CultureInfo.InvariantCulture)))
                |  ty -> failwithf "Unknown primitive type %A" ty

            let attrib =
                match fieldInfo.GetCustomAttributes(typeof<ColumnAttribute>,
                                                    false) with
                | [| (:? ColumnAttribute as attrib) |] ->   attrib
                | _ -> failwithf "No column attribute found on field %s" fld.Name
            (fldIdx, fld.Name, attrib.Column, fieldConverter))

    // Compute the permutation defined by the ColumnAttribute indexes
    let columnToFldIdxPermutation c =
      schema |> Array.pick (fun (fldIdx,_,colIdx,_) ->
          if colIdx = c then Some fldIdx else None)

    // Drop the parts of the schema we don't need
let schema =
      schema |> Array.map (fun (_,fldName,_,fldConv) -> (fldName,fldConv))

    // Compute a function to build instances of the schema type. This uses an
    // F# library function.
    let objectBuilder = FSharpValue.PreComputeRecordConstructor(schemaType)

    // OK, now we're ready to implement a line reader
    member reader.ReadLine(textReader: TextReader) =
        let line = textReader.ReadLine()
        let words = line.Split([|','|]) |> Array.map(fun s -> s.Trim())
        if words.Length <> schema.Length then
            failwith "unexpected number of columns in line %s" line
        let words = words |> Array.permute columnToFldIdxPermutation

        let convertColumn colText (fieldName, fieldConverter) =
           try fieldConverter colText
           with e ->
               failwithf "error converting '%s' to field '%s'" colText fieldName

        let obj = objectBuilder (Array.map2 convertColumn words schema)

        // OK, now we know we've dynamically built an object of the right type
        unbox<'Schema>(obj)

    /// This reads an entire file
    member reader.ReadFile(file) =
        seq { use textReader = File.OpenText(file)
              while not textReader.EndOfStream do
                  yield reader.ReadLine(textReader) }

The type of the SchemaReader is simple:

type SchemaReader<'Schema> =
    new : unit -> SchemaReader<'Schema>
    member ReadFile : string -> seq<'Schema>
    member ReadLine : System.IO.TextReader -> 'Schema

First you see how the SchemaReader is used in practice. Let's say you have a text file containing lines such as this:

Steve, 12 March 2010, Cheddar
Sally, 18 Feb 2010, Brie
...

It's reasonable to want to convert this data to a typed data representation. You can do this by defining an appropriate record type along with enough information to indicate how the data in the file maps into this type. This information is expressed using custom attributes, which are a way to add extra meta-information to assembly, type, member, property, and parameter definitions. Each custom attribute is specified as an instance of a typed object, here ColumnAttribute, defined in Listing 9-10. The suffix Attribute can be dropped when using the custom attribute:

type CheeseClub =
    { [<Column(0)>] Name            : string
      [<Column(2)>] FavouriteCheese : string
      [<Column(1)>] LastAttendance  : System.DateTime }

You can now instantiate the SchemaReader type and use it to read the data from the file into this typed format:

> let reader = new SchemaReader<CheeseClub>();;
val reader : SchemaReader<CheeseClub>

> fsi.AddPrinter(fun (c:System.DateTime) -> c.ToString());;
val it : unit = ()

> System.IO.File.WriteAllLines("data.txt", [| "Steve, 12 March 2010, Cheddar";
                                              "Sally, 18 Feb 2010, Brie"; |]);;
val it : unit = ()

> reader.ReadFile("data.txt");;
val it : seq<CheeseClub>
 = seq
    [{Name = "Steve";
      FavouriteCheese = "Cheddar";
      LastAttendance = 12/03/2010 00:00:00;};
     {Name = "Sally";
      FavouriteCheese = "Brie";
      LastAttendance = 18/02/2010 00:00:00;}]

There is something somewhat magical about this; you've built a layer that automatically does the impedance matching between the untyped world of a text-file format into the typed world of F# programming. Amazingly, the SchemaReader type itself is only about 50 lines of code. The comments in Listing 9-10 show the basic steps being performed. The essential features of this technique are as follows:

  1. The schema information is passed to the SchemaReader as a type variable. The SchemaReader then uses the typeof operator to extract a System.Type representation of the schema type.

  2. The information needed to drive the transformation process comes from custom attributes. Extra information can also be supplied to the constructor of the SchemaReader type if necessary.

  3. The let bindings of the SchemaReader type are effectively a form of precomputation (they can also be seen as a form of compilation). They precompute as much information as possible given the schema. For example, the section analyzes the fields of the schema type and computes functions for creating objects of the field types. It also computes the permutation from the text file columns to the record fields.

  4. The data objects are ultimately constructed using reflection functions, in this case a function computed by Microsoft.FSharp.Reflection.Value.GetRecordConstructor or primitive values parsed using System.Int32.Parse and similar functions. This and other functions for creating F# objects dynamically are in the Microsoft.FSharp.Reflection library. Other functions for creating other .NET objects dynamically are in the System.Reflection library.

  5. The member bindings of SchemaReader interpret the residue of the precomputation stage, in this case using the information and computed functions to process the results of splitting the text of a line.

This technique has many potential applications and has been used for CSV file reading, building F#-centric serializers/deserializers, and building generic strongly typed database schema access.

Using the F# Dynamic Reflection Operators

F# lets you define two special operators, (?) and (?<-), to perform dynamic lookups of objects. These are conceptually very simple operators, but they add interesting new opportunities for interoperability between dynamic data and static data in F# programming.

These operators implicitly translate their second argument to a string, if it's a simple identifier. That is, a use of these operators is translated as follows:

expr ? nm            à   (?) expr "nm"
   expr1 ? nm <- expr2  à   (?<-) expr1 "nm" expr2

This means the operators can be used to simulate a dynamic lookup of a property or a method on an object. This dynamic lookup can use any dynamic/reflective technique available to you. One such technique is to use .NET reflection to look up and/or set the properties of an object:

open System.Reflection

let (?) (obj:obj) (nm:string) : 'T =
    obj.GetType().InvokeMember(nm, BindingFlags.GetProperty, null, obj, [| |])
    |> unbox<'T>

let (?<-) (obj:obj) (nm:string) (v:obj) : unit =
    obj.GetType().InvokeMember(nm, BindingFlags.SetProperty, null, obj, [| v |])
    |> ignore

Now, you can use the operators to dynamically query data as follows:

type Record1 = { Length : int; mutable Values : int list }

let obj1 = box [1;2;3]
let obj2 = box { Length = 4; Values = [3;4;5;7] }

let n1 : int = obj1?Length
let n2 : int = obj2?Length
let valuesOld : int list = obj2?Values

Here, both obj1 and obj2 have type obj, but you can do dynamic lookups of the properties Length and Values using the ? operator. Of course, these uses aren't strongly statically typed—this is why you need the type annotations : int and : int list to indicate the return type of the operation. Given the earlier definition of the (?<-) operator, you can also set a property dynamically as follows:

obj2?Values <- [7;8;9]

let valuesNew : int list = obj2?Values

Using the (?) and (?<-) operators obviously comes with strong drawbacks: you lose considerable type safety, and performance may be affected by the use of dynamic techniques. Their use is recommended only when you're consistently interoperating with weakly typed objects, or when you continually find yourself doing string-based lookup of elements of an object.

Using F# Quotations

The other side to reflective meta-programming in F# is quotations. These allow you to reflect over expressions in much the same way you've reflected over types in the previous section. It's simple to get going with F# quotations; you open the appropriate modules and surround an expression with <@ . . . @> symbols:

> open Microsoft.FSharp.Quotations;;

> let oneExpr = <@ 1 @>;;
val oneExpr : Expr<int>

> oneExpr;;
val it : Expr<int> = <@ (Int32 1) @>

> let plusExpr = <@ 1 + 1 @>;;
val plusExpr : Expr<int>

> plusExpr;;
val it : Expr<int>
  = <@ Microsoft.FSharp.Core.Operators.op_Addition (Int32 1) (Int32 1) @>

You can see here that the act of quoting an expression gives you back the expression as data. Those familiar with Lisp or Scheme know a sophisticated version of this in the form of Lisp quotations; and those familiar with C# 3.0 will find it familiar because C# uses similar mechanisms for its lambda expressions. F# quotations are distinctive partly because they're typed (like C# lambda expressions) and because the functional, expression-based nature of F# means that so much of the language can be quoted and manipulated relatively easily.

This book uses quotations in only a few places. Chapter 15 uses an F# library that converts F# quotations to SQL via the .NET LINQ library. The essence of the way this converter works is summarized by the following type:

val SQL : Expr<'T> -> 'T

This function effectively acts as an evaluator for quotations. It successfully evaluates only a limited range of quotations (a runtime error may occur if the expression can't be converted to SQL).

Another application of quotations is to convert F# code to JavaScript to let you run it in web browsers. This technique is used by WebSharper, described in Chapter 14. This may be implemented by a function with a type such as the following:

val CompileToJavaScript : Expr<'T> -> string

Example: Using F# Quotations for Error Estimation

Listing 9-11 shows a prototypical use of quotations, in this case to perform error estimation on F# arithmetic expressions.

Example 9.11. Error Analysis on F# Expressions Implemented with F# Quotations

open Microsoft.FSharp.Quotations
open Microsoft.FSharp.Quotations.Patterns
open Microsoft.FSharp.Quotations.DerivedPatterns

type Error = Err of float

let rec errorEstimateAux (e:Expr) (env : Map<Var,_>) =
    match e with
    | SpecificCall <@@ (+) @@> (tyargs,_,[xt;yt]) ->
        let x,Err(xerr) = errorEstimateAux xt env
        let y,Err(yerr) = errorEstimateAux yt env
        (x+y,Err(xerr+yerr))

    | SpecificCall <@@ (-) @@> (tyargs,_,[xt;yt]) ->
        let x,Err(xerr) = errorEstimateAux xt env
        let y,Err(yerr) = errorEstimateAux yt env
        (x-y,Err(xerr+yerr))

    | SpecificCall <@@ ( * ) @@> (tyargs,_,[xt;yt]) ->
        let x,Err(xerr) = errorEstimateAux xt env
        let y,Err(yerr) = errorEstimateAux yt env
        (x*y,Err(xerr*abs(y)+yerr*abs(x)+xerr*yerr))
| SpecificCall <@@ abs @@> (tyargs,_,[xt]) ->
        let x,Err(xerr) = errorEstimateAux xt env
        (abs(x),Err(xerr))

    | Let(var,vet, bodyt) ->
        let varv,verr = errorEstimateAux vet env
        errorEstimateAux bodyt (env.Add(var,(varv,verr)))

    | Call(None,MethodWithReflectedDefinition(Lambda(v,body)),[arg]) ->
        errorEstimateAux  (Expr.Let(v,arg,body)) env

    | Var(x) -> env.[x]

    | Double(n) -> (n,Err(0.0))

    | _ -> failwithf "unrecognized term: %A" e

let rec errorEstimateRaw (t : Expr) =
    match t with
    | Lambda(x,t) ->
        (fun xv -> errorEstimateAux t (Map.ofSeq [(x,xv)]))
    | PropertyGet(None,PropertyGetterWithReflectedDefinition(body),[]) ->
        errorEstimateRaw body
    | _ -> failwithf "unrecognized term: %A - expected a lambda" t

let errorEstimate (t : Expr<float -> float>) = errorEstimateRaw t

The inferred types of the functions are as follows:

val errorEstimateAux : Expr -> Map<ExprVarName,(float * Error)> -> float * Error
val errorEstimateRaw : Expr -> (float * Error -> float * Error)
val errorEstimate : Expr<(float -> float)> -> (float * Error -> float * Error)

That is, errorEstimate is a function that takes an expression for a float -> float function and returns a function value of type float * Error -> float * Error.

Let's see it in action. First, you define the function err and a pretty-printer for float * Error pairs, here using the Unicode symbol for error bounds on a value:

> let err x = Err x;;
val err : float -> Error

> fsi.AddPrinter (fun (x:float,Err v) -> sprintf "%g±%g" x v);;
val it : unit = ()

> errorEstimate <@ fun x -> x+2.0*x+3.0*x*x @> (1.0,err 0.1);;
val it : float * Error = 6±0.61

> errorEstimate <@ fun x -> let y = x + x in y*y + 2.0 @> (1.0,err 0.1);;
val it : float * Error = 6±0.84

The key aspects of the implementation of errorEstimate are as follows:

  • The errorEstimate function converts the input expression to a raw expression, which is an untyped abstract syntax representation of the expression designed for further processing. It then calls errorEstimateRaw. Traversals are generally much easier to perform using raw terms.

  • The errorEstimateRaw function then checks that the expression given is a lambda expression, using the active pattern Lambda provided by the Microsoft.FSharp.Quotations.Patterns module.

  • The errorEstimateRaw function then calls the auxiliary function errorEstimateAux. This function keeps track of a mapping from variables to value/error estimate pairs. It recursively analyzes the expression looking for +, -, * and abs operations. These are all overloaded operators and hence are called generic functions in F# terminology, so the function uses the active pattern SpecificCall to detect applications of these operators. At each point, it performs the appropriate error estimation.

  • For variables, the environment map env is consulted. For constants, the error is zero.

  • Two additional cases are covered in errorEstimateAux and errorEstimateRaw. The Let pattern allows you to include expressions of the form let x = e1 in e2 in the subset accepted by the quotation analyzer. The MethodWithReflectedDefinition case allows you to perform analyses on some function calls, as you see next.

Resolving Top Definitions

One of the problems with meta-programming with explicit <@ ... @> quotation marks alone is that you can't analyze very large programs because the entire expression to be analyzed must be delimited by these markers. This is solved in F# by allowing you to tag top-level member and let bindings as reflected. This ensures that their definition is persisted to a table attached to their compiled DLL or EXE. These functions can also be executed as normal F# code. For example, here is a function whose definition is persisted:

[<ReflectedDefinition>]
let poly x = x+2.0*x+3.0/(x*x)

You can retrieve definitions like this using the MethodWithReflectedDefinition and PropertyGetterWithReflectedDefinition active patterns, as shown in Listing 9-11. You can now use this function in a regular <@ ... @> quotation and thus analyze it for errors:

> errorEstimate <@ poly @> (3.0, err 0.1);;
val it : float * Error = 9.33333±0.582149

> errorEstimate <@ poly @> (30271.3, err 0.0001);;
val it : float * Error = 90813.9±3.02723

Summary

This chapter covered key topics in a programming paradigm that is central to F#, called language-oriented programming. We covered one particular concrete language format, XML, and then looked at abstracted representations of languages using abstract syntax trees. You also saw some techniques to traverse abstract syntax trees. These language representation techniques give you powerful ways to manipulate concrete and abstract syntax fragments, which form a key part of modern programming.

You then saw two language representation techniques that are more tightly coupled to F#: the F# workflow syntax, which is useful for embedded computational languages involving sequencing, and quotations, which let you give an alternative meaning to existing F# program fragments. Along the way, the chapter touched on reflection and its use to mediate between typed and untyped representations.

That completes your look at F# as a language and the major programming paradigms it covers. The following chapters look at the libraries that come with F# and the .NET Framework and then move on to more applied topics, beginning with GUI programming using the .NET Windows Forms library.

..................Content has been hidden....................

You can't read the all page of ebook, please click here login for view all page.
Reset