nomeata / inspection-testing

Inspection Testing for Haskell
MIT License
172 stars 27 forks source link

how to permit this: "Found type classes: [(%,,,,,,,,%)]" #74

Open Mikolaj opened 1 year ago

Mikolaj commented 1 year ago

Hi! This is a great tool. I'm (ab)using it to find specializations that failed to fire. I have several problems (ab)using it in this way (with GHC 9.4.6):

  1. I don't know how recursive/transitive the check is. It probably depends on how much Core from other modules ends up being processed inside the module in question? I'm using -fexpose-all-unfoldings, so that's probably a lot of the core.

2, When it says "Found type classes: [(%,,,,,,,,%)]" I don't know how to add this name to the list of exceptions for hasNoTypeClassesExcept (see the snippet below for how that class arises). Could it perhaps be filtered out globally? That's a class that the user can add manually, is it?

  1. It complains also about type classes mentioned inside existential type values or functions creating or unpacking such values, where they don't indicate a failed specialization. E.g., here DynamicExists is an existential type getting unpacked and all the constraints are normally hidden inside it (and additionally hidden as superclasses of a GoodScalar class). but sameTypeRep decides to uncover them all, leading to many exceptions for hasNoTypeClassesExcept:
                                 { DynamicExists @r_ikSL $dGoodScalar [Dmd=1!P(A,A,A,A,A,A,1L,A,A)]
                                                 ds [Dmd=1!P(L,1!P(SL,L),1L)] ->
                                 case base:Data.Typeable.Internal.sameTypeRep
                                        @Type
                                        @Type
                                        @Double
                                        @r
                                        HordeAd.Core.TensorADVal.$fAdaptableDomainsFlipADVal50
                                        ((ghc-prim:GHC.Classes.$p6(%,,,,,,,,%)
                                            @(Show r)
                                            @(Ord r)
                                            @(Numeric r)
                                            @(Num r)
                                            @(Num (Data.Vector.Storable.Vector r))
                                            @(RowSum r)
                                            @(Typeable @Type r)
                                            @(IfDifferentiable r)
                                            @(NFData r)
                                            ($dGoodScalar
                                             `cast` (HordeAd.Core.Types.N:GoodScalar[0] <r>_N
                                                     :: Coercible
                                                          Constraint
                                                          (GoodScalar r)
                                                          (HordeAd.Core.Types.GoodScalarConstraint
                                                             r))))
                                         `cast` (base:Data.Typeable.Internal.N:Typeable[0] <Type>_N <r>_N
                                                 :: Coercible
                                                      Constraint
                                                      (Typeable @Type r)
                                                      (base:Data.Typeable.Internal.TypeRep
                                                         @Type r)))
  1. The Core the tools shows is similar but not quite the same as the one from -ddump-stranal (e.g., it lacks some of the made-up identifier suffixes, e.g,. above r and r_ikSL are both r_ikSL in -ddump-stranal output). An extra problem with -ddump-stranal is that the option dumps Core twice. What else should I be using?
nomeata commented 1 year ago

Glad you like it, I hope you’ll be able to use it.

  1. I don't know how recursive/transitive the check is.

This is the code:

https://github.com/nomeata/inspection-testing/blob/c2bfd2d99fef17431f772adb270a3c657733bbee/src/Test/Inspection/Core.hs#L84-L117

So the answer is: All local definitions involved in the definitions you ask for. So -fexpose-all-unfoldings on its own shouldn’t do much, but if GHC inlines some other modules’ definitions into this module, they may become relevant.

  1. When it says "Found type classes: [(%,,,,,,,,%)]"

That’s a constraint tuple, right? Yes, this could probably be filtered out in any case – if there are unwanted type classes, they will be inside.

  1. Existentials

I am not quite sure what’s best to do here. After all, the code does mention the type classes, doesn’t it?

  1. Output differences

Hmm, that's a bit odd. I wonder if it is due to

https://github.com/nomeata/inspection-testing/blob/c2bfd2d99fef17431f772adb270a3c657733bbee/src/Test/Inspection/Core.hs#L173-L179

Unfortunately, I don’t quite remember why I added that setting.

Mikolaj commented 1 year ago

So the answer is: All local definitions involved in the definitions you ask for. So -fexpose-all-unfoldings on its own shouldn’t do much, but if GHC inlines some other modules’ definitions into this module, they may become relevant.

"Local" meaning from the same module? So that's fully recursive, but only within the module (plus inlines). Thank you for the clarification. In that case I should start adding the inspect statements to the modules where my main functions are defined instead of to test or benchmark modules. A pity that I have many small modules.

  1. When it says "Found type classes: [(%,,,,,,,,%)]"

That’s a constraint tuple, right? Yes, this could probably be filtered out in any case – if there are unwanted type classes, they will be inside.

Yes, it's the constraint tuple. That would be very helpful.

  1. Existentials

I am not quite sure what’s best to do here. After all, the code does mention the type classes, doesn’t it?

Yes, it does. But the classes in the code snippet are all in type applications applied to a function from outside the module (from the base package, in fact). So that does not indicate that my code is too class-polymorphic. Perhaps some outside function is, but often there's nothing I can do to fix it (e.g., I may have no unfolding for them). My use case is to prevent polymorphic calls to my own functions and a better approximation for that seems to be detecting type classes inside type signatures of any of my own functions in the call chain.

  1. Output differences

This is not a big deal for me. I need the full Core anyway. A bigger problem is that I'm still unsure how to get the Core corresponding to the output of inspection-testing and, ideally, in just one copy. E.g., the very late Tidy Core dump already doesn't have the identifier names the tool warns about.

nomeata commented 1 year ago

My use case is to prevent polymorphic calls to my own functions

If you expect your function (say foo) to be replacted by their specialized version, then maybe one signal to look for is “is foo“ still mentioned? If it isn’t, then something has happend – hopefully specialization, but it could also just be a thin worker/wrapper inlining… hmm, yes, this isn’t great either.

A bigger problem is that I'm still unsure how to get the Core corresponding to the output of inspection-testing and, ideally, in just one copy

It should install itself at the very end of the core2core pipeline, according to https://hackage.haskell.org/package/inspection-testing-0.5.0.2/docs/src/Test.Inspection.Plugin.html#install. In the worst case, -dverbose-core2core should help…

nomeata commented 1 year ago

Yes, it's the constraint tuple. That would be very helpful.

Do you want to patch it yourself for now and see if it helps, and then maybe create a PR?

Mikolaj commented 1 year ago

It should install itself at the very end of the core2core pipeline, according to https://hackage.haskell.org/package/inspection-testing-0.5.0.2/docs/src/Test.Inspection.Plugin.html#install. In the worst case, -dverbose-core2core should help…

Yes, -dverbose-core2core is how I got the hypothesis it's -ddump-stranal. If there's no better hypothesis, then that's probably it and it's GHC's problem that it prints Core twice (because there are two "Demand analysis" passes). Oh well.

Do you want to patch it yourself for now and see if it helps, and then maybe create a PR?

Here you go.

https://github.com/nomeata/inspection-testing/pull/75

This made two of my tests pass, but the remaining two stumble, among other problems, over a type-level programming tilde operator (probably https://hackage.haskell.org/package/ghc-9.6.1/docs/GHC-Prelude-Basic.html#t:-126-?). No idea how it can be called. One of these: https://hackage.haskell.org/package/ghc-9.6.1/docs/GHC-Builtin-Types.html#g:20 perhaps?

bench/common/BenchProdTools.hs:156:1: revRankedListProdr does not contain dictionary values except of HordeAd.Core.Types.GoodScalar, GHC.TypeNats.KnownNat, Data.Array.Internal.Shape.Shape, HordeAd.Core.Ast.AstSpan, GHC.Show.Show, GHC.Clas
ses.Ord, Internal.Numeric.Numeric, GHC.Num.Num, HordeAd.Internal.TensorFFI.RowSum, Data.Typeable.Internal.Typeable, HordeAd.Core.Types.IfDifferentiable, Control.DeepSeq.NFData failed:
    Found type classes:  [~, Boolean, IfF, EqF, OrdF, RankedTensor,
                          ShapedTensor, ConvertTensor, CRanked, CShaped,
                          HordeAd.Core.TensorClass.YRanked, Integral,
                          HordeAd.Core.TensorClass.YShaped]
    lvl434 = HordeAd.Core.AstInterpret.$winterpretAst
               @(ADVal @GHC.TypeNats.Nat (AstRanked 'PrimalSpan))
               @(ADVal @[GHC.TypeNats.Nat] (AstShaped 'PrimalSpan))
               @1
               @'DualSpan
               @Double
               (HordeAd.Core.AstInterpret.$s$WAstReshape1
                `cast` (Sym (GHC.TypeNats.N:SNat[0] <1>_P)
                        ; Sym (GHC.TypeNats.N:KnownNat[0]) <1>_N
                        :: Coercible Type GHC.Num.Natural.Natural (KnownNat 1)))
               (HordeAd.Core.AstInterpret.interpretAst305
                `cast` (((%,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,%)
                           ((~)
                              <TensorKind [GHC.TypeNats.Nat]>_N
                              <ADVal @[GHC.TypeNats.Nat] (AstShaped 'PrimalSpan)>_N
                              ((ADVal
                                  <[GHC.Num.Natural.Natural]>_N
                                  (Sym (HordeAd.Core.Ast.D:R:ShapedOfNaturalAstRanked[0]
                                            <'PrimalSpan>_N)))_N
                               ; Sym (HordeAd.Core.TensorADVal.D:R:ShapedOfkADVal[0]
                                          <GHC.Num.Natural.Natural>_N <AstRanked 'PrimalSpan>_N)))_N
nomeata commented 1 year ago

See Note [The equality types story] in https://hackage.haskell.org/package/ghc-9.6.1/docs/src/GHC.Builtin.Types.Prim.html#heqTyCon

This is eqTyCon. Can’t you refer to it in the inspection predicate using (~)?

Mikolaj commented 1 year ago

See Note [The equality types story] in https://hackage.haskell.org/package/ghc-9.6.1/docs/src/GHC.Builtin.Types.Prim.html#heqTyCon

Thanks, that explains things.

This is eqTyCon. Can’t you refer to it in the inspection predicate using (~)?

When I add

|| (~) == tc ||

it says "Variable not in scope: (~) :: TyCon", so the laziest approach, at least, fails.

nomeata commented 1 year ago

Do you want to add it to the inspection testing code, or to the list of allowed typeclasses in your own assertion?

Mikolaj commented 1 year ago

Do you want to add it to the inspection testing code, or to the list of allowed typeclasses in your own assertion?

I did add it to the PR. I see I misunderstood your question about (~) and tried adding (~) to your tool internals. Let me try adding this to my own assertion...

My use case is to prevent polymorphic calls to my own functions and a better approximation for that seems to be detecting type classes inside type signatures of any of my own functions in the call chain.

Oh, but your hasNoTypeClassesExcept only checks Core code, not Core type signatures at all, does it? If so, that's a completely separate feature.

Mikolaj commented 1 year ago

I did add it to the PR. I see I misunderstood your question about (~) and tried adding (~) to your tool internals. Let me try adding this to my own assertion...

Hah, inspect $ hasNoTypeClassesExcept 'revRankedListProd [''GoodScalar, ''KnownNat, ''OS.Shape, ''AstSpan, ''Show, ''Ord, ''Numeric, ''Num, ''RowSum, ''Typeable, ''IfDifferentiable, ''NFData, ''RealFrac, ''Integral, ''(~)] works great. In that case, let me revert that from my PR --- it's better when the user can control that.

Mikolaj commented 1 year ago

My use case is to prevent polymorphic calls to my own functions and a better approximation for that seems to be detecting type classes inside type signatures of any of my own functions in the call chain.

Oh, but your hasNoTypeClassesExcept only checks Core code, not Core type signatures at all, does it? If so, that's a completely separate feature.

But looking at signatures is not enough, either. I've just, thanks to your tool, tracked down a failed specialization of my function that was inlined and the inlined code was polymorphic instead of specialized and it was applied to dictionaries (which is why it was flagged). There was no type signature to inspect in this case. A general solution is harder than I thought. But your tool gives a good overestimation, which I can then refine with the list of exceptions. And scanning also type signatures would probably not catch any new failed specialization cases.

Edit: actually the inlined code was not specialized, because the function calls it contained failed to specialize, so this would be visible in the signatures of the respective functions, but they are from another module and so not "local". So scanning beyond type signatures is at least a needed crutch for only having "local" visibility.

Mikolaj commented 1 year ago

I wonder, do constructors (in patterns or expressions) applied to dictionaries ever hint at a failed specialization? E.g., I'm yelled at for (note $dIntegral at the very bottom)

bench/common/BenchProdTools.hs:153:1: revRankedListProdr does not contain dictionary values except of HordeAd.Core.Types.GoodScalar, GHC.TypeNats.KnownNat, Data.Array.Internal.Shape.Shape, HordeAd.Core.Ast.AstSpan, GHC.Show.Show, GHC.Clas
ses.Ord, Internal.Numeric.Numeric, GHC.Num.Num, HordeAd.Internal.TensorFFI.RowSum, Data.Typeable.Internal.Typeable, HordeAd.Core.Types.IfDifferentiable, Control.DeepSeq.NFData, GHC.Real.RealFrac, GHC.Real.Fractional, GHC.Float.RealFloat, 
GHC.Float.Floating failed:
    Found type classes:  [Integral]
    $w$s$wshapeAst = \ (@(s :: AstSpanType))
                       (@r)
                       (ds [Dmd=1L] :: AstRanked s r (1 GHC.TypeNats.+ 0)) ->
                       case ds of {
                         AstVar sh [Dmd=1L] bx [Dmd=A] -> sh;
                         AstLet @n1_akGD @r1_akGE @s1_akGF $dKnownNat2 [Dmd=A]
                                $dKnownNat3 [Dmd=A] $dGoodScalar [Dmd=A] $dAstSpan [Dmd=A]
                                bx [Dmd=A] ds1 [Dmd=A] v [Dmd=1L] ->
                           $w$s$wshapeAst @s @r v;
                         AstLetADShare co [Dmd=A] ds1 [Dmd=A] v [Dmd=1L] ->
                           $w$s$wshapeAst @'PrimalSpan @r v;
                         AstCond _b [Dmd=A] v [Dmd=1L] _w [Dmd=A] -> $w$s$wshapeAst @s @r v;
                         AstMinIndex @r1_akGY co [Dmd=A] $dGoodScalar [Dmd=A] a ->
                           (HordeAd.Util.SizedList.$winitSized
                              @(1 GHC.TypeNats.+ 0)
                              @Int
                              ((lvl14 @r1 a)
                               `cast` (HordeAd.Util.SizedIndex.N:Shape[0] <1
                                                                           GHC.TypeNats.+ (1
                                                                                           GHC.TypeNats.+ 0)>_N <Int>_N
                                       :: Coercible
                                            Type
                                            (Shape (1 GHC.TypeNats.+ (1 GHC.TypeNats.+ 0)) Int)
                                            (SizedList
                                               (1 GHC.TypeNats.+ (1 GHC.TypeNats.+ 0)) Int))))
                           `cast` (Sym (HordeAd.Util.SizedIndex.N:Shape[0]) <1
                                                                             GHC.TypeNats.+ 0>_N <Int>_N
                                   :: Coercible
                                        Type
                                        (SizedList (1 GHC.TypeNats.+ 0) Int)
                                        (Shape (1 GHC.TypeNats.+ 0) Int));
                         AstMaxIndex @r1_akH3 co [Dmd=A] $dGoodScalar [Dmd=A] a ->
                           (HordeAd.Util.SizedList.$winitSized
                              @(1 GHC.TypeNats.+ 0)
                              @Int
                              ((lvl14 @r1 a)
                               `cast` (HordeAd.Util.SizedIndex.N:Shape[0] <1
                                                                           GHC.TypeNats.+ (1
                                                                                           GHC.TypeNats.+ 0)>_N <Int>_N
                                       :: Coercible
                                            Type
                                            (Shape (1 GHC.TypeNats.+ (1 GHC.TypeNats.+ 0)) Int)
                                            (SizedList
                                               (1 GHC.TypeNats.+ (1 GHC.TypeNats.+ 0)) Int))))
                           `cast` (Sym (HordeAd.Util.SizedIndex.N:Shape[0]) <1
                                                                             GHC.TypeNats.+ 0>_N <Int>_N
                                   :: Coercible
                                        Type
                                        (SizedList (1 GHC.TypeNats.+ 0) Int)
                                        (Shape (1 GHC.TypeNats.+ 0) Int));
                         AstFloor @r1_akH8 co [Dmd=A] $dGoodScalar [Dmd=A]
                                  $dRealFrac [Dmd=A] $dIntegral [Dmd=A] a [Dmd=1L] ->
                           $w$s$wshapeAst @'PrimalSpan @r1 a;

If that's never an indication of a failed specialization (perhaps on a function from another module we only see applied), it would be helpful to me to ignore such dictionary occurrences. Is it easily done? Or perhaps a general mechanism "ignore class C in context such and such" instead of the current "ignore class C".

Edit: and the constructor in this example has existentially quantified variables this dictionary relates to. But perhaps this can happen without existential quantification, though I'd hope, in any case, it's never the only hint for any specific specialization failure and so can be ignored.

nomeata commented 1 year ago

I don't know if ”specialization works” is such a clearly defined concept, and depends more what you want to do. But if it means “this typeclass isn't mentioned anymore”, shouldn't this also apply to constructors with existentials? But it may depend on the concrete optimizations you desire.

A richer API for specifying where in the AST what kind of things should or shouldn't be might be useful, but so far I didn't have a good inspiration for a good comprehensive designs.

Mikolaj commented 1 year ago

I don't know if ”specialization works” is such a clearly defined concept, and depends more what you want to do.

Yes, you are right this is ambiguous. I'm using the intuition that successful specialization of a set of functions monomorphises the types of all their calls in the whole program (this is a property only of the signatures of the specialized variants; the function bodies can have all kinds of spurious polymorphism in ignored or executed only for impure side-effects let expressions as long as the type variables don't escape to the signatures). This is extreme, but resolves a lot of the ambiguity. Existential types fit the monomorphisation intuition in that all their free type variables need to be monomorphised away, as with any other type. The bound existential variables are not free and so monomorphisation does not even see them.

But if it [specialization] means “this typeclass isn't mentioned anymore”

Not at all. This is why I "abuse" your tool for my purpose. :)

In fact, dictionaries and class overloading specialization (in the monomorphisation sense), are rather loosely related. E.g., one can add a constraint Num Int to a signature of a function, which can break performance (https://gitlab.haskell.org/ghc/ghc/-/issues/23798#note_520473), which suggests that GHC does apply dictionaries somewhere in there, So there is a dictionary, but no type variable and so specialization doesn't even make sense. This is spurious class occurrence without even spurious polymorphism.