Absurd "Could not specialise imported function ‘$WSTKScalar’"
Summary
I will try to minimized if asked.
I'm getting
example/MnistFcnnRanked1.hs: warning: [-Wmissed-specialisations]
Could not specialise imported function ‘HordeAd.Core.TensorKind.$WSTKScalar’
when specialising ‘HordeAd.Core.OpsAst.$fBaseTensorAstNoSimplify_$s$csdot1’
Probable fix: add INLINABLE pragma on ‘HordeAd.Core.TensorKind.$WSTKScalar’
where STKScalar
is a constructor
data STensorKind y where
STKScalar :: GoodScalar r
=> STensorKind (TKScalar r)
...
and sdot0
is a method in a class (and has no definition in the AstNoSimplify
instance mentioned in the message)
sdot0 :: forall r sh. (GoodScalar r, KnownShS sh)
=> target (TKS sh r) -> target (TKS sh r) -> target (TKS '[] r)
{-# INLINE sdot0 #-} -- this doesn't want to specialize
sdot0 t u | SNat <- shsProduct (knownShS @sh) = ssum (sflatten (t * u))
My guesses what's wrong with the message (which comes from -Wmissed-specialisations
, which was very reliable to date):
-
sdot0
hasINLINE
, so should not be specialized, should it? - but if specialization is requested anyway, I don't see a reason it should fail
- I don't think one can add
INLINABLE
to a constructor - in any case,
-fexpose-all-unfoldings
is in effect, soINLINABLE
should never be needed
Steps to reproduce
git clone git@github.com:Mikolaj/horde-ad.git
cd horde-ad
git checkout repro-spec-scalar
curl https://ghc.gitlab.haskell.org/head.hackage/cabal.project > cabal.project.local
rm -rf ~/.cabal/packages/head.hackage.ghc.haskell.org
cabal update
cabal build exampleLibrary -w /home/mikolaj/r/ghc.HEAD/ghc/_build/stage1/bin/ghc --allow-newer --enable-optimization
Expected behavior
Emits a sensible warning message. Even better, inlines, as requested. Ideally, specializes without inlining (I have -fexpose-all-unfoldings
, -fspecialise-aggressively
and -fdicts-cheap
(and I add -fpolymorphic-specialisation
as often as I can) so it doesn't feel right I need to modify code and add dozens of pragmas to specialize things).
Environment
- GHC version used: ghc-9.13.20250212
Optional:
- Operating System: Ubuntu
- System Architecture: AMD64
Edited by Mikolaj Konarski