Detailed Release notes for 1.9.1.8

Detailed Release Notes for release 1.9.18 of the F# Compiler and Tools.  

research.microsoft.com/research/downloads/details/b46c7032-149c-4da3-a027-7768210a158d/details.aspx

[ Note: we've had one report of an installation issue on Windows XP, and one on Windows Vista. If you have a problem try installing the VC runtime libraries www.microsoft.com/downloads/details.aspx?FamilyID=32BC1BEE-A3F9-4C13-9C99-220B62A191EE&displaylang=en
Please let us know if you have problems, by emailing us at "fsbugs at microsoft dot com". ]

Language Enhancement: Implicit Class Construction

This release includes a preview version of ``implicit class construction'' or the ``compact class syntax''. An class has an implicit constructor if arguments are present following its type declaration. The arguments to the implicit constructor follow the type name, then a sequence of let-bindings (prior to the members) define the object initialisation. Note, the let bindings are in scope over the members, but they are private to this class. For example:

     type File1(path) = class
        let innerFile = new FileInfo(path)
        member x.InnerFile = innerFile
    end
    let myFile1 = new File1("file.txt")

Classes with an implicit constructor have zero, one or more arguments such as path after the name of the type constructor. Furthermore the body of the class may contain let bindings, which are always private to the class, indeed private to the object (you can't access the let bindings even for other values of the same type). Above we have also added the a property member InnerFile to reveal the value of the value of the innerFile. Here is a second example:

     type Counter(start, increment, length) = class 
        let finish = start + length
        let mutable current = start
        member obj.Current = current
        member obj.Increment() = 
            if current > finish then failwith "finished!";
            current <- current + increment
    end

Logically speaking, this class is equivalent to:

     // The above code is equivalent to the following:
    type Counter = class 
        val start: int
        val increment: int
        val length : int
        val finish : int
        val mutable current : int
        new(start, increment, length) = 
            { start=start;
              increment=increment;
              length=length;
              finish = start + length; 
              current = start; }
        member obj.Current = current
        member obj.Increment() = 
            if obj.current > obj.finish then failwith "finished!";
              obj.current <- obj.current + obj.increme
    end

The first definition of Counter is one third the size of the second, so obviously the syntax has some advantages. Indeed we believe this feature is part of the key to enabling mixed OO/functional programming in practice.

Note this feature is in many ways similar to those found in OCaml and other langauges.

Classes can include both implicit and explicit constructors

When using implicit class construction the call to the base class constructor is specified as part of the inherits declaration itself.

     type Base1(state:int) = class
        member x.State = state
    end
                   
    type Sub1(state:int) = class
        inherit Base1(state)
        member x.OtherState = state
    end
    
    let myOtherObject = new Sub1(1)

The types may be generic. Type annotations are generally required:

     type Base1<'a>(state:'a) = class
        member x.State = state
    end
                   
    let myObject1 = new Base1<int>(1)
    let myObject2 = new Base1<string>("1")

Known Limitation: The F# compiler is free to optimize and represent the let-bindings in anyway it deems fit. However, in this release each ``let'' binding gives rise to a field in the class. This is the main reason why we say this feature is only a ``tech-preview'' - while it is extremely useful even as it stands you have to be a little careful not to put thousands of helper (e.g. closed-form) ``let'' bindings in a critical class. In the above example, the start value is only required during initialization of the object and thus should in principle not be included as a field of the object.

Known Limitation: In this release classes with implicit constructors may not be mutually recursive.

Known Limitation: Patterns may not be used in the arguments to the constructor.

Known Limitation: The bindings are established in order. However base class constructors written in other .NET languages can in principal call virtual members prior to the complete initialization of the object. This means you should be careful about using your ``let'' bindings from override members that may be activated by base classes during base initialization. In this case the behaviour is unspecified and the 'default' or 'zero' values of some of the let bound variables may be observed.

Language Enhancement: Active Patterns

Active patterns give a form of extensible pattern matching on abstract values. F# active patterns allow you to pattern match against .NET object values such as XML, System.Type values and LINQ Expression trees. They allow a function to give a complete decomposition of an abstract type by projecting it into a union type.

Active Decomposition. An active pattern discrimination function declares a ``view'' on a type. It is a function whose name includes surrounding (| ... |) marks. It gives a technique for automatically decomposing the values of a type when the enclosed label(s) are used as pattern discriminator(s). For example:

    open Microsoft.FSharp.Math
   let (|Rect|) (x:complex) = Rect(x.RealPart, x.ImaginaryPart)
   let (|Polar|) (x:complex) = Polar(x.Magnitude , x.Phase)

These functions declare two unrelated discriminators for viewing the (abstract) type of complex numbers as tuples in rectangular and polar coordinates. Multiplication can now be expressed using either coordinate system:

    let mulViaRect c1 c2 = 
       match c1,c2 with 
       | Rect(ar,ai), Rect(br,bi) -> Complex.mkRect(ar*br - ai*bi, ai*br + bi*ar)
  
   let mulViaPolar c1 c2 = 
       match c1,c2 with 
       | Polar(r1,th1),Polar(r2,th2) -> Complex.mkPolar(r1*r2, th1+th2)

In the first case, the decomposition function (|Rect|) is run when the inputs c1 and c2 are matched.

Because Rect and Polar are simply pattern discriminators they can be used in any position where an existing pattern discriminator can be used:

       let mul2 (Polar(r1,th1)) (Polar(r2,th2)) = Complex.mkPolar(r1*r2, th1+th2)
  
      for (Polar(r,th)) in myComplexNumberList do 
          printf "r = %O, th = %O" r th

Active Discrimination. Active pattern discrimination functions may include multiple active pattern labels. For example, the following defines a function (|Named|Array|ByRef|Ptr|Param|) that discriminates and decomposes System.Type values into one of the five indicated cases:

       open System
      
      let (|Named|Array|ByRef|Ptr|Param|) (typ : System.Type) =
          if typ.IsGenericType        then Named(typ.GetGenericTypeDefinition(), typ.GetGenericArguments())
          elif not typ.HasElementType then Named(typ, [| |])
          elif typ.IsArray            then Array(typ.GetElementType(), typ.GetArrayRank())
          elif typ.IsByRef            then ByRef(typ.GetElementType())
          elif typ.IsPointer          then Ptr(typ.GetElementType())
          elif typ.IsGenericParameter then Param(typ.GenericParameterPosition, typ.GetGenericParameterConstraints())
          else failwith "unexpected System.Type"

You can now use these discrimination labels in pattern matching:

       let rec toString typ =
          match typ with
          | Named (con, args) -> "(" + con.Name + " " + String.Join(";",Array.map toString args) + ")"
          | Array (arg, rank) -> "(Array"  + rank.ToString() + " " + toString arg + ")"
          | ByRef arg         -> "(ByRef " + toString arg + ")"
          | Ptr arg           -> "(Ptr "   + toString arg + ")"
          | Param(pos,cxs)    -> "(Param " + any_to_string (pos,cxs) + ")"

This is by no means the only view that could be applied to this type, but it is a useful one when performing operations that are sensitive to the presence of type variables (Param) and generic type constructors (Named).

Active Patterns in the F# Library The F# library currently only includes active patterns for a few constructs. One is the LazyList type, a cached, lazily-computed list. This allows you to pattern match on LazyList values, including nested patterns, e.g. the following code performs pairwise summation on a lazy list:

     open LazyList
    
    let rec pairReduce xs =
      match xs with
        | Cons (x, Cons (y,ys)) -> LazyList.consf (x+y) (fun () -> pairReduce ys)
        | Cons (x, Nil ())      -> LazyList.cons x (LazyList.empty ())
        | Nil ()                -> LazyList.empty ()

Partial Active Patterns. Partial patterns are signified by adding a |_| to the name of the discrimination function. The body of the discrimination function must return a value of type 'option'. They are most useful when dealing with repeatedly recurring queries on very "heterogeneous" data sets, i.e. data sets able to represent a large range of possible entities, but where you're often interested in focusing on a subset of the entities involved. Strings, term structures and XML are common examples. Here is an example when matching on integers:

      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
  
     let example1 inp = 
         match 21 with 
         | MulThree(residue) -> printf "residue = %d!\n" residue
         | MulSeven(residue) -> printf "residue = %d!\n" residue
         | _ -> printf "no match!\n"
  
     example1 777
     example1 9
     example1 10
     example1 21

Partial patterns are by their nature incomplete and thus the benefits of completeness checking in pattern matching are almost completely lost when using these patterns.

Parameterized Active Patterns. So far all the pattern discrimination functions have taken one argument, i.e. the input being discriminated. Pattern discrimination functions may also take additional arguments that represent parameters to the pattern:

      let (|Equal|_|) x y = 
        printf "x = %d!\n" x
        if x = y then Some() else None

When used in a pattern a parameterized pattern tag may be followed by simple expressions that represent arguments, and then finally followed by the pattern being matched against, e.g.:

         
     let example1 = 
         match 3 with 
         | Equal 4 () -> printf "3 = 4!\n"
         | Equal 3 () -> printf "3 = 3!\n"
         | _ -> printf "3 = ?!\n"

Note: not all expressions can be used in this position. Only identifiers, tuples, applications, lists and array expressions may be written in this position. Here is a second example. Extra parentheses can be useful to distinguish pattern parameters from the variables being bound by the pattern:

      let (|Lookup|_|) x map = Map.tryfind x map
        
     let example2 = 
         match Map.of_list [ "2", "Two" ; "3", "Three" ] with 
         | Lookup("4")(v) -> printf "4 should not be present!\n"
         | Lookup("3")(v) -> printf "map(3) = %s\n" v
         | Lookup("2")(v) -> printf "this should not be reached\n"
         | _ -> printf "3 = ?!\n"

Values with the names of the form (| ... |) can in theory all be used as parameters, e.g.

     let mapQ1 f (|P|_|) = function (P x) -> Some (f x) | _ -> None

However this is not a common technique. Our final example shows the use of a simple set of active patterns to match on the concrete structure of an XML document and extract a recursive algebra from the document:

     open System.Xml
    open System.Collections
    open System.Collections.Generic
  
    let Select (|P|_|) (x: #XmlNode) = [ for P y as n in x.ChildNodes -> y ]
  
    let Select2 (|A|B|) (x: #XmlNode) = [ for (A y | B y) as n in x.ChildNodes -> y ]
  
    let (|Elem|_|) name (inp: #XmlNode) = 
        if inp.Name = name then Some(inp) 
        else None
  
    let (|Attr|_|) attr (inp: #XmlNode) = 
        match inp.Attributes.GetNamedItem(attr) with
        | null -> None
        | node -> Some(node.Value)
  
    let (|Num|_|) attr inp = 
        match inp with 
        | Attr attr v -> Some (Float.of_string v) 
        | _           -> None
  
    type scene = 
        | Sphere of float * float * float * float
        | Intersect of scene list 
    
    let (|Vector|_|) = function (Num "x" x & Num "y" y & Num "z" z) -> Some(x,y,z) | _ -> None
    
    let rec (|ShapeElem|_|) inp = 
        match inp with 
        | Elem "Sphere" (Num "r" r  & Num "x" x & Num "y" y & Num "z" z) -> Some (Sphere (r,x,y,z)) 
        | Elem "Intersect" (ShapeElems(objs)) -> Some (Intersect objs) 
        | _ -> None
  
    and (|ShapeElems|) inp = Select (|ShapeElem|_|) inp 
  
    let parse inp = 
        match (inp :> XmlNode) with 
        | Elem "Scene" (ShapeElems elems) -> elems
        | _                               -> failwith "not a scene graph"
  
    let inp = "<Scene>
                  <Intersect>
                    <Sphere r='2' x='1' y='0' z='0'/>
                    <Intersect>
                      <Sphere r='2' x='4' y='0' z='0'/>
                      <Sphere r='2' x='-3' y='0' z='0'/>
                    </Intersect>
                    <Sphere r='2' x='-2' y='1' z='0'/>
                  </Intersect>
               </Scene>"
    let doc = new XmlDocument()
    doc.LoadXml(inp)
    //print_endline doc.DocumentElement.Name
    printf "results = %A\n" (parse doc.DocumentElement)

Signatures for Active Patterns The signature for an active discrimination function is given in terms of a function returning a Choice type:

     val (|Cons|Nil|) : 'a llist -> Choice<('a * 'a llist),unit>

Notes: Some obvious issues with using active patterns in languages with side effects - how many times are discrimination functions executed? The specification used for F# is that "if pattern matching requires that an active discrimination function be run on a given input, then the pattern matching apparatus is free to run that function on the same input as many times as it wishes". In the presence of active patterns, rules of patterns are searched exhaustively on a left-to-right, top-to-bottom basis. We have chosen this semantics partly because we want to strongly discourage discriminator functions with side effects, in much the same way that side effects are strongly discouraged in code that implements the C# and F# property notations.

Known Limitation: Individual active pattern discrimination functions may decompose using at most 7 labels. Multiple partial active patterns can be used instead. It is planned that this limitation will be lifted in the next release.

Known Limitation: Choice types of size greater than 7 are not implemented in this release.

Much of this work was done by Gregory Neverov in the summer of 2006.

Language Enhancement: Methods as first-class values

Methods can now be used as first class values without eta-expansion. Context-sensitive type information is used to resolve overloading. For example:

     open System.IO
    let data1 = List.map File.ReadAllLines ["a.txt"; "b.txt"]

If applied to arguments methods must still be applied to a syntactic tuple of arguments where the number of elements in the tuple is the same as the numebr of arguments expected by the method.

Language Enhancement: Nested types may now be written C<D<int>>

This long-standing problem has now been fixed. This only applies if the type arguments follow immediately after a leading constructor without spaces, e.g. C<D<int>> not C <D <int>> .

Language Enhancement: Precedence of type annotations in pattern tuples

Until now, F# followed OCaml and give "comma" in parenthesized tupled patterns higher precedence than type constraints. This has changed. Thus we would previously disallow

      let f (samplefreq:int64, s:int64) 

and previously parse

      let f (samplefreq, s : int64) 

as

      let f ((samplefreq, s) : int64) 

(leading to a type error). We are changing this behaviour for parenthesized patterns, and now

      let f (samplefreq:int64, s:int64) 

will be accepted and parsed in the same way as

      let f ((samplefreq:int64), (s:int64)) 

and the following current code will almost certainly give an error

      let f (samplefreq, s:int64*int64) 

since it is now parsed as

      let f (samplefreq, (s:int64*int64)) 

Technically speaking this is a breaking change, though we have encountered only one example of user code affected by this. The readability of the user code was massively improved after taking the above change into account, hence in the balance we have decided the improvement to the language is more important in the long term. In all cases there are still reasonable and simple ways to ensure your code cross compiles with OCaml if necessary.

Other Language Enhancements

StructLayout, FieldOffset etc. attributes now supported for C interoperability.

F# Lists support IEnumerable/seq. In previous versions the F# list type was not compatible with the .NET IEnumerable<'a> type, which is called seq<'a> in F#. This was because null was used as a representation for lists. This has now been changed. See further discussion below.

Normalization of class and interface constraints. When constraints are used extensively situations can arise where a single type parameter can be constrained by multiple related constraints. For example,

    let f1 (x : #seq<('a * 'b)>) = ()
   let f2 (x : #seq<('a * 'b * 'c)>) = ()
   let g x = f1 x; f2 x

Here g is constrained to operate over both sequences of pairs and sequences of triples. While it is in principle possible for a .NET type to implement both of these interfaces, in practice this is never used. In prior versions F# was not normalizing such constraints to ensure that any particular nominal type occurred at only one instantiation for a given collection of constraints. This has now been added to the language specification and has been implemented. This gives earlier detection of errors involving incompatible constraints and ensures that multiple related constraints never need to be listed in signatures should one constraint subsume another.

Lexer literals 32u and 32uL now accepted. These are unsigned 32-bit and 64-bit integers.

new now optional. The construct new Type(args) can now optionally be replaced by simply Type(args) . This applies when no ambiguity exists as to which type is being constructed and where no type instantiation is given. However, a warning is given if the type supports the IDisposable interface. For these constructs it is felt that the potential use of resources by the construct means that new Type(args) is much clearer

More F# keywords accepted as identifiers in --ml-compatibility-mode.

Enum values now support the ||| and &&& operators. This applies when the Enum type is marked with the FlagsAttribute attribute.

Extend overload inference for (+), (*) etc. to allow return types to propagate to the overload resolution. This reduces the need for type annotations in many circumstances.

Explicit type applications at member calls and path lookups. You can now explicitly apply type arguments in lookups, e.g.

     let x = Map.empty<string,int>
    // The next is from the Microsoft Research 'Joins' library
    let subscribe = Asynchronous.CreateChannel<EventSink<'b>>(client.Join)

Flexible printf integer and floating point format enhancements. %d, %u, %i, %x and %o formats can now be used with any integer types. Many of the other format specifiers have now been deprecated or marked 'for OCaml compatibility'. %f and %g and other floating point specifiers can now be used with both Single and Double precision numbers. The use of the format specifiers is still checked at compile time to ensure static type correctness.

Printf format enhancements. * can now be used as a width and/or precision specifier. This corresponds to a 'computed' specifier and an extra integer argument giving the width is required in the argument list for the specifier. For example:

      sprintf "|%*s|%*s|" 10 "hello" 8 "world" ;;
     sprintf "|%*s|%*s|" 12 "hello" 6 "world" ;;
  

Give:

     val it : string = "|     hello|   world|"
    val it : string = "|       hello| world|"

OCaml Compatibility Warnings. Several constructs in the F# libraries are only present for OCaml compatibility. While OCaml compatibility is a key goal of the language, we have also become aware that users coming to F# from a non-OCaml background get very confused by the presence of 'multiple ways of doing things' and are bemused when the explanation is that 'we need that for OCaml compatibility, but we don't really recommend using it'. As such, we've begun marking some constructs as 'not recommended for use unless you need it for OCaml compativility.' In this relesae this applies to &

Null no longer used as a representation for F# list values. We made this change to allow the F# "List" type to implement the IEnumerable/seq interface. This means we are dropping null as a representation for F# list values (null values cannot implement interfaces), and are indeed abandoning the use of "null" for option values and where an attribute is explicitly attached to a discriminated union with a nullary discriminator, e.g.

     [<CompilationRepresentation(CompilationRepresentationFlags.PermitNull)>]
    type HashChain<'a,'b> = 
      | EmptyChain // note: representation is "null"
      | Chain of { Key: 'a; 
                   Value: 'b; 
                   mutable Rest: ('a,'b) HashChain }

This is thus a breaking change to the language spec, which previously specified different conditions where "null" is used. Using non-null values for the empty list comes with a small performance penalty for list-intensive code (around 10%), but little overall space penalty. Array, loop, matrix, vector, hashtable, set, sequence and map-dominated code is not affected, and since these are the primary high-performance data structures in F# we have decided that the language clarity of having "list" implement "IEnumerable" is more important than the performance considerations for this case.

This change does mean that C# samples that search for "null" as the empty list will no longer function correctly. They should instead use the IsNil property (now a true instance property) or switch on tags, e.g. as follows:

        List<int> x = List>int>.Cons(3, (List<int>.Nil));

       switch (x.Tag)
       {
           case List<int>.tag_Cons:
               Console.WriteLine("Cons({0},{1})", x.Head, x.Tail);
               break;
           case List<int>.tag_Nil:
               Console.WriteLine("[]");
               break;
       }

Library Enhancements

Representation of the LazyList type is now private. Active patterns can now be used to match on values of type LazyList.

Sparse matrix implementation. See Math.Matrix.init_sparse. You can now create and multiply matrices up to size ~10M x 10M, as long as most elements are zero.

Updated quotations API. The quotations API has been substantially simplified through the use of active patterns. Code using the old quotations API directly will no longer compile but is easy to update. Contact the F# team if you need help you with this.

The F# map type now supports equality and comparison over entire map values. In particular Map<k,v> implements IDictionary<'k,'v> , IEnumerable<KeyValuePair<k,v>> and IComparable. Note: this is a breaking change. In 1.1.13.8 Map supported IEnumerable<'k,'v> . However, this meant that the type could never also support IDictionary. We have decided to make this breeaking change immediately since it is obviously correct for Map values to support IDictionary.

Interactive pretty-printer for IDictionary values.

Pervasive values cleaned up. Many values that are now "officially" part of Microsoft.FSharp.Core.Operators were still being redefined in Microsoft.FSharp.Compatibility.OCaml.Pervasives. These have now been removed from that module. The path Microsoft.FSharp.Compatibility.OCaml.Pervasives is still opened be default but contains very few values.

Overloading of math operations like sin, cos, abs etc. These are now overloaded over basic types, e.g. abs on all floating point and signed types, and sin on the floating point types. They also work with any type supporting corresponding static members, e.g. types supporting the static member Sin or Abs.

Choice types.

Choice types up to size 7 are defined in the F# library and can be used for general purpose programming.

     type Choice<'a,'b> = 
      | Choice2_1 of 'a 
      | Choice2_2 of 'b
    
    type Choice<'a,'b,'c> = 
      | Choice3_1 of 'a 
      | Choice3_2 of 'b
      | Choice3_3 of 'c

etc.

F# Reflection library additions to pre-compute faster accessors. The following functions have been added to thee reflection library:

     /// Precompute a function for reading a particular field from a record.
    val GetRecordFieldReader     : Type * field:string -> (obj -> obj)

    /// Precompute a function for reading all the fields from a record.
    val GetRecordReader          : Type -> (obj -> obj array)
    
    /// Precompute a function for reading an integer representing the discriminant tag of a sum type.
    val GetSumTagReader          : Type -> (obj -> int)

    /// Precompute a function for reading all the fields for a particular discriminant tag of a sum type
    val GetSumRecordReader       : Type * int -> (obj -> obj array)
    
    /// Precompute a function for reading the values of a particular tuple type
    val GetTupleReader           : Type -> (obj -> obj array)

    /// Precompute a function for constructing a record value. 
    val GetRecordConstructor     : Type -> (obj array -> obj)
    
    /// Precompute a function for constructing a discriminated union value for a particular tag. 
    val GetSumConstructor        : Type * tag:int -> (obj array -> obj)
    
    /// Precompute a function for reading the values of a particular tuple type
    val GetTupleConstructor      : Type -> (obj array -> obj)

    /// Precompute a pair of functions for converting between integer discriminant tags
    /// the names of the discriminants for the given sum type. The number of tags is also
    /// returned.
    val GetSumTagConverters      : Type -> int * (int -> string) *  (string -> int)

F# Reflection library no longer reports F# class types as records. This was a mistake from the early implementation of the reflection library.

Deprecated llist functions. Deprecated some LazyList functions.

LexBuffer.AsNewLinePos() renamed to LexBuffer.NextLine. The old name has been deprecated.

List.concat now accepts a sequence. This brings it into line with Seq.concat.

Notation for complex/matrix/vector/set/dict notation at the top level The following functions are now defined in Microsoft.FSharp.Core.Pervasives and are available for use in the top level:

     val complex : float -> float -> complex
    val matrix : #seq< #seq<float> > -> matrix
    val vector : #seq<float> -> vector
    val rowvec : #seq<float> -> rowvec
    val set : #seq<'a> -> Set<'a>
    val dict : #seq<'a * 'b> -> System.Collections.Generic.IDictionary <'a,'b>

Visual Studio Enhancements

Intelisense on more expressions, including method calls.

Visual Studio ToolsOptionsPage for FSI startup arguments

Visual Studio fixes to allow "ReadLine" calls when using VFSI

Minor bug fixes.

    Bug fixes to permit printf on binary channels (Reported by Richard Mortier - thanks Mort!)

   Fixed mod_float to be ocaml compatible (reported by Andrew Phillips - thanks Andrew!)

   Bug 858: Function types not erased from type constraints on typars of methods or types.
   
   Bug 856: no more inlining of protected calls, e.g. out of class defn.
   
   Bug 851. Removed ``0 from non-generic member names in xmldoc.

   Fix base calls to F# abstract members (reported by Ralf Herbrich and Phil Trelford - thanks guys!)
   
   XMLDOC changes (suggested by Andyman - thanks Andy)
 
   Permit access to nested generic classes (reported by Claudio Russo - thanks Claudio!)
 
   Fixed generation of unverifiable code when using the "property bag" syntax with properties 
   of type 'object' and values that are value types, a bug reported by Julien Ortin 
 
   Bug 880: Type definition bug (reported by Laurent on hubfs - thanks Laurent!)

   Bug 881: fsi needs a way to specify command line arguments (reported by Dmitry - thanks Dmitry!)

   Bug 882: StartupCode and PrivateImplemntationDetails types should be private (reported by Robert Pickering - thanks Robert!)

   Bug 883: Add check for phantom and permuting type abbreviations causing potential problems in type inference

   Bug 884: Instrumented profiling doesn't work on XP or Vista
   
   Bug 889: Excessive 'base' variable usage checks (reported by Tomas Petricek - thanks Tomas!)