fsharp icon indicating copy to clipboard operation
fsharp copied to clipboard

Improve diagnostics for inlining in class methods - FS1114, FS1113, FS1116, FS1118

Open abelbraaksma opened this issue 7 years ago • 28 comments

The general rule in F# let-bindings is that they must appear in order if they are dependent on one another, but inside classes, and among classes chained with and , the order is irrelevant.

Most of the time this is true, but if you use inlined members and these are forward-declared in your class or class hierarchy, they may lead to spurious compile-time errors. These errors (see below) are generally only raised when using inlining on recursive functions, leading to very hard-to-diagnose uncompilable code. Besides, these errors are not only misplaced, they seem to be plain wrong, there should probably not be an error at all.

Repro steps

Over the cause of a few weeks analyzing this, leading to a first and a second yet to be answered StackOverflow question, it suddenly dawned to me that rearranging the members solved the problem. But first things first, here's how to repro.

First example (copy/paste and compile to see the error)

/// Does a bounds check and raises an error if bounds check is not met
let inline checkBounds f (g: 'b -> ^c) (tp: ^a) = 
    let convertFrom = (^a: (static member name: string) ())
    let convertTo = (^c: (static member name : string) ())
    let value =  (^a: (member Value: 'b) tp)
    if f value then
        g value
    else 
        failwithf "Cannot convert from %s to %s." convertFrom convertTo


type ConverterA =
    struct 
        val Value: sbyte
        new v = { Value = v }
    end

    static member inline name with get() = "converter-a"
    static member inline convert (x: ConverterA) : ConverterB = 
        checkBounds ((>=) 0y) (byte >> ConverterB) x

and ConverterB =
    struct 
        val Value: byte
        new v = { Value = v }
    end
    static member inline name with get() = "converter-b"

Second example:

[<Flags>]
type MyType =
    | Integer = 0b0001
    | Float   = 0b0010

module Test =
    [<CustomEquality;NoComparison>]
    type SomeType =
        | Int of int64
        | Float of float

        override x.Equals other =
            match other with
            | :? SomeType as y -> 
                // following line throws on compiling this
                match SomeType.getType x &&& SomeType.getType y with
                | MyType.Integer -> int64 x = int64 y       // highest type is integer (both are int)
                | MyType.Float -> float x = float y         // highest type is float (either is or both are float)
                | _ -> false // impossible
            | _ -> false

        override x.GetHashCode() =
            match x with Int i -> hash i | Float f -> hash f

        static member inline op_Explicit(n: SomeType): float =
            match n with
            | Int i -> float i
            | Float f -> f

        static member inline op_Explicit(n: SomeType): int64 =
            match n with
            | Int i ->  i
            | Float f -> int64 f

        static member inline getType x =
            match x with
            | Int _ -> MyType.Integer
            | Float _ -> MyType.Float

Third (simplest I could muster) example:

module Test =
    type SomeType =
        | Int of int64
        | Float of float

        static member MyEquals (x, other: SomeType) =
            // following line throws on compiling this
            float x = float other 

        static member inline op_Explicit(n: SomeType): float =
            match n with
            | Int i -> float i
            | Float f -> f

        static member inline op_Explicit(n: SomeType): int64 =
            match n with
            | Int i ->  i
            | Float f -> int64 f

(these examples are also used in the SO questions)

Expected behavior

While typing these examples, the syntax checker and inference algorithms won't show any errors. When you compile them, the expected behavior is that they compile just fine (apart from perhaps debatable practices of the code examples, but I had to simplify, they originate from a large codebase).

Actual behavior

Instead of compiling just fine, the following errors and warnings are raised by the compiler (and the variants thereof for each example above, but the error numbers and order wherein they appear are the same).

error FS1114: The value 'Foo.Bar.name' was marked inline but was not bound in the optimization environment

error FS1113:The value 'name' was marked inline but its implementation makes use of an internal or private function which is not sufficiently accessible

warning FS1116: A value marked as 'inline' has an unexpected value

error FS1118: Failed to inline the value 'name' marked 'inline', perhaps because a recursive value was marked 'inline'

Note that the errors seem to point out that it fails to inline the following method, which itself has no dependencies and seems trivial to inline:

static member inline name with get() = "converter-b"

Note also that FS1113 is not applicable at all, there are no private or internal members or functions.

Note that FS1116 is incomprehensible (how can an inline function have an unexpected value? What is it? And what is the value?)

Note that FS1118 suggests it is a recursive function marked inline. This is the only error that hints that the compiler has not enough knowledge to inline the method, but hints in the wrong direction (there is nothing recursive).

This gets worse when you have a compilable codebase and you decide, for instance, to implement override x.Equals(), or IComparable. It is common practice to place these on top. But if they call into inline functions you suddenly get those errors. And I've found that they can appear in related classes, not even in the just-added methods, which furthers the troubles of diagnosing this.

Known workarounds

Changing the order in which the class members, or classes themselves appear solves the problem. Though this is, I believe, against the policy that inside a class the order ought to be insignificant. An example of a compilable version of repro 2 above:

/// Does a bounds check and raises an error if bounds check is not met
let inline checkBounds f (g: 'b -> ^c) (tp: ^a) = 
    let convertFrom = (^a: (static member name: string) ())
    let convertTo = (^c: (static member name : string) ())
    let value =  (^a: (member Value: 'b) tp)
    if f value then
        g value
    else 
        failwithf "Cannot convert from %s to %s." convertFrom convertTo

// place ConverterB before ConverterA solves the error
type ConverterB =
    struct 
        val Value: byte
        new v = { Value = v }
    end
    static member inline name with get() = "converter-b"

and ConverterA =
    struct 
        val Value: sbyte
        new v = { Value = v }
    end

    static member inline name with get() = "converter-a"
    static member inline convert (x: ConverterA) : ConverterB = 
        checkBounds ((>=) 0y) (byte >> ConverterB) x

Related information

The examples above fail to compile with VS2015, Update 1, 2 and 3, using F# 4.0 (FSharp.Core 4.4.0.0).

I consider this issue relatively severe because the errors raised have so little to do with the actual situation and can appear "out of nowhere" after you add a simple new method. Even if an error is legit in this case, something like "Method X is unknown, but exists in your declarations, consider changing the order in which they appear in the source so that the optimization environment can bind to them."

BTW, there are many situations where the order of inlined functions does not matter, leading to situations where you have compilable code that just, after adding an otherwise independent method, stops being compilable.

abelbraaksma avatar Sep 27 '16 01:09 abelbraaksma

@abelbraaksma Thanks for the analysis and detailed repros.

Though this is, I believe, against the policy that inside a class the order ought to be insignificant.

Just to note that the order is definitely significant for inlining between members, as your examples show. But the error messages definitely are sub-par in this case.

dsyme avatar Sep 27 '16 20:09 dsyme

Thanks for your quick response.

I've been trying on MSDN and the F# 4.0 language spec to find out where it states that the order inside a class (between members) is important w.r.t. inline members.

Experimenting myself shows that sometimes it is and sometimes it isn't. Or put in another way, I can't deduct the apparent rules from just experimenting alone.

For instance, in the following example, A() and B() are normal members and they don't seem to care about order. But test() does matter, if I place it one or more lines up, it gives the earlier mentioned errors. Then again, add a b does not have any problem here, even though its dependent on definitions of op_Explicit that are defined below it.

type SomeType =
    | Foo
    | Bar
    static member inline add a b = int a + int b
    static member inline op_Explicit(n: SomeType): float = 2.
    static member inline op_Explicit(n: SomeType): int = 2
    static member test() = SomeType.add SomeType.Foo SomeType.Bar

    static member B() = SomeType.A()
    static member A() = 3

In several online sources it is explained that the order of members inside classes, and between classes when chained with and, doesn't matter. But none of them are specific about inline or mention it as a special case that must be ordered. Well, I mean to say, I couldn't find it, that doesn't mean it isn't out there, specified somewhere.

abelbraaksma avatar Sep 28 '16 01:09 abelbraaksma

Mmm, letting this sink in a bit more, it seems to me that the general rule is that any inline member of a class must be declared prior to its usage, that is, the moment the inlining materializes.

// successful compilation
static member B() = OtherType.A()
static member A() = 3
static member inline C() = OtherType.B()

Then, order between inline members is important when they are "normal" (i.e., have no member constraints):

// fails to compile with FS1113, FS1114 etc
static member inline B() = OtherType.A()
static member inline A() = 3

With member constraints (here (+)), order seems less important, but I think that is simply because the type, until the method is actually used, is not known, so nothing gets compiled (except for the stubs):

// no error, even though `add` is dependent on `(+)`
static member inline add a b = a + b
static member inline (+) (a, b) = 3 + 4

All in all, there seems to be some logic, esp. if you try to think as a compiler. And if that's the status-quo and intent of how it is supposed to work I have no problem with that (apart from the already mentioned clarity of the errors, of course ;).

abelbraaksma avatar Sep 28 '16 02:09 abelbraaksma

@abelbraaksma Yes, good summary. Certainly neither the language spec nor MSDN is clear about this. Could you submit a clarification to the MSDN docs please? (which are open source now).

dsyme avatar Sep 28 '16 10:09 dsyme

@dsyme: it appears I never acted on your request for updating the docs, but I think we can close this issue, with VS2017 I cannot repro this anymore given the examples in the original post (I tried all four of them), hurray!!! This moots the requirement for updating the docs.

And much to my surprise, apparently the fix applies to both F# 4.0 as well as F# 4.1. Not sure what actual PR solved this one, but this could be placed on the list of achievements: order of declarations in classes does not lead to compile errors anymore!

abelbraaksma avatar Aug 25 '17 09:08 abelbraaksma

@abelbraaksma Thanks for checking all these old issues so thoroughly

I don't recall a specific change that would have fixed this - but I will close it since you have validated that it is fixed

dsyme avatar Aug 25 '17 10:08 dsyme

@dsyme, I think we should reopen this. I must have incorrectly tested it. Try the first example in VS2017:

  • no error when loaded
  • errors when compiled as described

This report by @vasily-kirichenko reminded me that this old bug isn't fixed yet. #3634.

abelbraaksma avatar Sep 23 '17 23:09 abelbraaksma

just to keep you posted, I am running into this FS1114 due to let rec inline ... on an SRTP'd function. ;-(

christianparpart avatar Jan 29 '19 00:01 christianparpart

type Test<'F> (value: 'F) =
    member val Value : 'F = value

module Test =
    let rec inline foo (value: Test<'F>) : 'F =
        let v = value.Value 
        if v <= v/v then
            v/v
        else
            foo (Test<'F>(v - (v/v)))

[<EntryPoint>]
let main argv =
    let f = Test<float>(3.14)
    let g = Test.foo f
    printfn "g: %s" (g.ToString())

This really very trivial example shows how to reproduce the errors minimally:

  • error FS1114: The value 'Program.Test.foo' was marked inline but was not bound in the optimization environment
  • error FS1113: The value 'foo' was marked inline but its implementation makes use of an internal or private function which is not sufficiently accessible
  • warning FS1116: A value marked as 'inline' has an unexpected value
  • error FS1118: Failed to inline the value 'foo' marked 'inline', perhaps because a recursive value was marked.

The above code is an attempt to create a minimal example. In my own code I am having my own Matrix class and module and a (rec [inline]) determinant function inside whose compiler errors cause me night mares.

I first wanted to have everything SRTP (^F) but then I realized I just can't get my recursive determinant() function to compile due to compile errors (like above), so I regex't all to 'F and now I am stuck again. As soon as I make use of recursion my whole world is imploding. OTOH, I moved from ^F to 'F in order to not be forced to flag all inline, but it turns out, in my case, as soon as I remove the inline on my determinant function, it even gives me different errors (all as spooky and non-telling at the above!).

christianparpart avatar Feb 04 '19 06:02 christianparpart

@christianparpart, iirc, in most cases you cannot use inline rec, even if tail call optimization is possible, as your example shows. Though maybe you can put the recursive function inside an inner closure.

I agree that the errors tell little to nothing here and only confuse programmes that hit this.

Note that my original issue deals with these errors without even using rec inline.

abelbraaksma avatar Feb 04 '19 16:02 abelbraaksma

@christianparpart, I took your code and had a look. The problem is indeed that rec inline cannot itself be use here (not sure when it can, if it never can, @dsyme, is that true? Then we should issue a warning or error early on whenever the compiler sees rec inline).

The reason that you don't see errors until you compile is because the compiler does a lot more in the optimization phase than the language services do that run continuously to show you the squigglies (but the errors are still notoriously hard to understand).

If I update your code as follows (I made use of a DU for ease of programming, generally I try to stay away from those OO peculiarities with val and member val, they also screw up type inference).

type Test<'F> = Value of 'F

module Test =
    let inline foo value =
        let rec innerFoo value =
            let (Value v) = value
            if v <= v/v then
                v/v
            else
                innerFoo (Test<_>.Value(v - (v/v)))

        innerFoo value

Now you have both the inline auto-SRTP benefits (you can use it with different concrete types as long as they support the minus and division operators) and you have the recursion, the latter itself being non-inlined.

The reason this works is that the compiler creates a separate version of your inline function for each type you use it with (and inlines it at the call-site, which is my guess why rec inline is so problematic). Since the inner function is part of the closure of the inlined function, each time this gets included in the call site, all the declarations are also copied.

Surprisingly, though, the inner function is now automatically inlined (you can see it when you hover over it). But when you put back the inline modifier, it will still blow up with the aforementioned errors.

Calling it as follows works as expected:

    let f = Test<float>.Value(3.14)
    let g = Test.foo f
    printfn "g: %f" g   // better not to use ToString() in F# if you can avoid it

    let f = Test<int>.Value(16)
    let h = Test.foo f
    printfn "h: %i" h

Running it doesn't cause errors and outputs:

g: 1.000000 h: 1

You're not the first that hit this issue, and you won't be the last. Here is an incomplete snippet of some user (without any comments), but you see that let rec inline before works, because it never recursively calls itself, and that for the let rec inline after he changed it to let inline after and a let rec inner (btw, his code won't compile, but for other reasons). http://www.fssnip.net/qe/title/inline-rec-functions

Also, this is a very old issue, the ominous factorial was attempted with rec inline and SRTP back in 2009, and it gave the same problem: http://fpish.net/topic/None/58328

abelbraaksma avatar Feb 04 '19 16:02 abelbraaksma

So I'm trying a trivial generic vector implementation in F#6.0 and hitting this error instantaneously.

type Vector<'t 
    when ^t:(static member (+): 't*'t->'t)>
    ([<System.ParamArray>] v: 't array) =

    member inline _.components = v

error FS1113: The value 'components' was marked inline but its implementation makes use of an internal or private function which is not sufficiently accessible. Which use of function? Does inlining members with generics is ever supposed to work at all?

konst-sh avatar Jun 18 '22 09:06 konst-sh

@konst-sh, according to the docs, you cannot use SRTP on types. I know there are cases that do work, but certainly not all. The private function in this case is probably the hidden, private get function, which the member (which is a property) automatically generates. Oh, and there’s the hidden set function as well.

The main issue raised in this thread is the unclarity of these errors. It’s rather hard to find out what’s the illegal stuff that you’re doing…

abelbraaksma avatar Jun 21 '22 16:06 abelbraaksma

type Vector<'t when ^t:(static member (+): 't*'t->'t)> =
    { components: 't array }
let inline Vector v = { components = v }

Happypig375 avatar Jun 21 '22 16:06 Happypig375

@abelbraaksma In the SRTP chapter I see the examples of class declarations with inline static members, while in usage comparison table above it is said that SRTP cannot be used on types (which is again pretty confusing - how can be that the type parameters cannot be used on types)

@Happypig375 yes, I was able to find examples of Vector implementation based on DU, at that moment I was wondering what was the reason, but now I see the answer - this is just how its working.

konst-sh avatar Jun 22 '22 04:06 konst-sh

how can be that the type parameters cannot be used on types

@konst-sh Because these are not your everyday type params, but are statically resolved type params. They need to be inlined. You are right that in some cases "it just works". The reason it is mentioned in the docs is that it is (currently, at least) not supported and just a side-effect of how it is implemented. After all, you cannot create a type that is 100% inline, hence it is not possible to support SRTP 100% on types.

The problem with "it accidentally just works" is, of course, that you can get pretty weird late-binding compiler errors (errors that are not covered by the lang service but only by the compiler in a later stage). The editor thinks "types are ok, so I'm not showing errors". Then the compiler tries to put everything together and hits a snag (in this case: inlining of a private member that is then externally exposed). You hit similar weird errors if you try to use string inside a constructor, IIRC.

These are my interpretations of the feature and how it is implemented/supported. Whether this is totally correct I do not know.

abelbraaksma avatar Jun 22 '22 12:06 abelbraaksma

@konst-sh Btw, side note, but your code contains mixed SRTP types (with ^t) and normal generic types (with 't). They cannot be mixed as being the same types (though sometimes you'll find that the compiler is lenient). For any single type, choose either static, or dynamic generic syntax.

Fixing it that way, your code compiles just fine:

type Vector<'t when ^t: (static member (+): ^t * ^t -> ^t)>([<System.ParamArray>] v: ^t array) =

    member inline _.components = v

Which also basically means that my original analysis of your code (sorry for not trying it first) was incorrect. You're still in unsupported territory, but you're fairly safe inside the "it just works" area.

abelbraaksma avatar Jun 22 '22 12:06 abelbraaksma

@abelbraaksma the snippet with your corrections still reports the same error for me in FSI, what F# version are you trying?

konst-sh avatar Jun 22 '22 12:06 konst-sh

@konst-sh, most recent version, from within VS 2022. These are my settings:

image

This is what I see when I copy/paste the code above, which I just also tried with dotnet fsi in case it made a difference:

> type Vector<'t when ^t: (static member (+): ^t * ^t -> ^t)>([<System.ParamArray>] v: ^t array) =

    member inline _.components = v;;
type Vector< ^t when  ^t: (static member (+) :  ^t *  ^t ->  ^t)> =
  new: [<ParamArray>] v:  ^t array -> Vector< ^t>
  member components:  ^t array

Using the type isn't a problem either, here I use it with an integer array:

image

abelbraaksma avatar Jun 27 '22 21:06 abelbraaksma

@abelbraaksma for some reason it doesn’t work for me, the F# Interactive settings are the same, lang version is 6.0 — should be the latest 

konst-sh avatar Jun 28 '22 04:06 konst-sh

@konst-sh, can you try it in a project or *.fs file and compile, see if there's a difference?

abelbraaksma avatar Jun 28 '22 14:06 abelbraaksma

@abelbraaksma I’m getting the same error if trying to compile it from .fs file

konst-sh avatar Jun 28 '22 17:06 konst-sh

@konst-sh that's really weird. Can you create a minimal fsproj + fs file and share that (using my fixed version of the code above, with ^t syntax). Are you sure you’re using latest F# and not some beta version or feature flags on? What’s your OS and .NET version?

abelbraaksma avatar Jun 29 '22 10:06 abelbraaksma

@abelbraaksma Hope I’ve made it correctly, here is the link to the project zip: https://drive.google.com/file/d/1zBMsKxzMlTL9lKbHkvz50zziKXEEEpbA/view?usp=sharing I’ve installed all the recommended packages and updates and NET SDK that VS installer offers, and as far as I remember no any beta language features should be enabled. Thanks for you time.  

konst-sh avatar Jun 30 '22 05:06 konst-sh

@konst-sh, fyi your comments show parts of your private mail thread, which clutters your message... Maybe because you comment from mail and Github is messing it up (you can edit your prev. comments if you wish to clean it up).

Any way, I noticed that your code works fine in FSI, but you would get the error when you compile it, because Vector is a public type and the constructor contains the constraint. Apparently that's not allowed (the error hints at this).

One way to fix it is to use a private type, which compiles fine, and use functions. FWIW, generally SRTP works better with functions than with types. You may also check @gusty code, like F#+ or https://gist.github.com/gusty/cc7bcb3803930f8a1181098c064c626b, which uses types, but forces the SRTP stuff inside private functions.

You may also want to report this issue separately, as there shouldn't be a difference between FSI and the compiler, afaik.

This compiles:

module X =
    type private Vector< ^t when ^t: (static member (+): ^t * ^t -> ^t)>(v: ^t array) =

        member inline _.components = v

    let foo () = Vector<_>([| 1; 2; 3 |]).components

abelbraaksma avatar Jul 05 '22 10:07 abelbraaksma

@abelbraaksma Thanks, making it private seem to solve it, though without private it doesn't commits in interactive still for me.

konst-sh avatar Jul 05 '22 11:07 konst-sh

@KevinRansom, you closed this (old) issue, and I see a mention to this issue in a commit above.

What was fixed here and in what PR? Then I can test it. The comment in the commits isn't really conclusive.

abelbraaksma avatar Jan 04 '24 20:01 abelbraaksma

I closed a bunch of bugs created prior to 2018 --- because they are unlikely to get worked on.

KevinRansom avatar Jan 04 '24 21:01 KevinRansom