[GHC] #15388: GHC reports missing INLINABLE pragmas in vector and ghc-prim

GHC ghc-devs at haskell.org
Sun Jul 15 19:27:08 UTC 2018


#15388: GHC reports missing INLINABLE pragmas in vector and ghc-prim
-------------------------------------+-------------------------------------
        Reporter:  ChaiTRex          |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:  8.6.1
       Component:  Compiler          |              Version:  8.4.3
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Description changed by ChaiTRex:

Old description:

> When compiling a program with GHC 8.4.3, vector 0.12.0.1 (with a
> dependency on primitive 0.6.4.0) and `-Weverything`, I get several
> warnings that `INLINABLE` pragmas should be added to the vector and ghc-
> prim packages.
>
> It would be nicer if these warnings didn't happen, even with
> `-Weverything`. Also, perhaps there are optimization opportunities that
> are lost.
>
> A somewhat reduced example (can be reduced further by removing the
> function definitions and unused imports that creates):
>
> {{{#!hs lineno=1
> {-# OPTIONS_GHC -Wall-missed-specialisations #-}
> {-# LANGUAGE MultiParamTypeClasses, TypeFamilies #-}
>
> module Warnings2 where
>
> import GHC.Base (liftM)
> import qualified Data.Vector.Generic.Base as G (Vector,
> basicUnsafeFreeze,
>   basicUnsafeThaw, basicLength, basicUnsafeSlice, basicUnsafeIndexM,
>   basicUnsafeCopy, elemseq)
> import qualified Data.Vector.Generic.Mutable.Base as GM (MVector,
> basicLength,
>   basicUnsafeSlice, basicOverlaps, basicUnsafeNew, basicInitialize,
>   basicUnsafeReplicate, basicUnsafeRead, basicUnsafeWrite, basicClear,
> basicSet,
>   basicUnsafeCopy, basicUnsafeMove, basicUnsafeGrow)
> import qualified Data.Vector.Unboxed as U (Unbox, Vector)
> import qualified Data.Vector.Unboxed.Mutable as U (MVector)
>
> newtype T = T () deriving (Show, Eq, Ord)
> newtype C = C (T, U.Vector T) deriving (Show, Eq, Ord)
>
> instance U.Unbox T
>
> newtype instance U.MVector s T = MV_T (U.MVector s ())
> instance GM.MVector U.MVector T where
>   basicLength (MV_T mv) = GM.basicLength mv
>   basicUnsafeSlice i l (MV_T mv) = MV_T (GM.basicUnsafeSlice i l mv)
>   basicOverlaps (MV_T mv1) (MV_T mv2) = GM.basicOverlaps mv1 mv2
>   basicUnsafeNew l = MV_T `liftM` GM.basicUnsafeNew l
>   basicInitialize (MV_T mv) = GM.basicInitialize mv
>   basicUnsafeReplicate l _ = MV_T `liftM` GM.basicUnsafeReplicate l ()
>   basicUnsafeRead (MV_T mv) i = const (T ()) `liftM` GM.basicUnsafeRead
> mv i
>   basicUnsafeWrite (MV_T mv) i _ = GM.basicUnsafeWrite mv i ()
>   basicClear (MV_T mv) = GM.basicClear mv
>   basicSet (MV_T mv) x = GM.basicSet mv ()
>   basicUnsafeCopy (MV_T mv1) (MV_T mv2) = GM.basicUnsafeCopy mv1 mv2
>   basicUnsafeMove (MV_T mv1) (MV_T mv2) = GM.basicUnsafeMove mv1 mv2
>   basicUnsafeGrow (MV_T mv) l = MV_T `liftM` GM.basicUnsafeGrow mv l
>
> newtype instance U.Vector T = V_T (U.Vector ())
> instance G.Vector U.Vector T where
>   basicUnsafeFreeze (MV_T mv) = V_T `liftM` G.basicUnsafeFreeze mv
>   basicUnsafeThaw (V_T v) = MV_T `liftM` G.basicUnsafeThaw v
>   basicLength (V_T v) = G.basicLength v
>   basicUnsafeSlice i l (V_T v) = V_T (G.basicUnsafeSlice i l v)
>   basicUnsafeIndexM (V_T v) i = const (T ()) `liftM` G.basicUnsafeIndexM
> v i
>   basicUnsafeCopy (MV_T mv) (V_T v) = G.basicUnsafeCopy mv v
>   elemseq (V_T v) _ = G.elemseq v ()
> }}}
>
> The warnings:
>
> {{{#!default lineno=1 marks=16,31,46
> src/Warnings2.hs: warning:
>     Could not specialise imported function
> ‘Data.Vector.Unboxed.$w$cshowsPrec’
>       when specialising ‘Data.Vector.Unboxed.$fShowVector_$cshowsPrec’
>       when specialising ‘Data.Vector.Unboxed.$fShowVector’
>     Probable fix: add INLINABLE pragma on
> ‘Data.Vector.Unboxed.$w$cshowsPrec’
>
> src/Warnings2.hs: warning:
>     Could not specialise imported function
> ‘Data.Vector.Unboxed.$fShowVector_$cshow’
>       when specialising ‘Data.Vector.Unboxed.$fShowVector’
>     Probable fix: add INLINABLE pragma on
> ‘Data.Vector.Unboxed.$fShowVector_$cshow’
>
> src/Warnings2.hs: warning:
>     Could not specialise imported function
> ‘Data.Vector.Unboxed.$fShowVector_$cshowList’
>       when specialising ‘Data.Vector.Unboxed.$fShowVector’
>     Probable fix: add INLINABLE pragma on
> ‘Data.Vector.Unboxed.$fShowVector_$cshowList’
>
> src/Warnings2.hs: warning:
>     Could not specialise imported function ‘ghc-
> prim-0.5.2.0:GHC.Classes.$w$c==’
>       when specialising ‘ghc-prim-0.5.2.0:GHC.Classes.$fEq(,)_$c==’
>     Probable fix: add INLINABLE pragma on ‘ghc-
> prim-0.5.2.0:GHC.Classes.$w$c==’
>
> src/Warnings2.hs: warning:
>     Could not specialise imported function
> ‘Data.Vector.Unboxed.$fOrdVector_$cmax’
>       when specialising ‘Data.Vector.Unboxed.$fOrdVector’
>     Probable fix: add INLINABLE pragma on
> ‘Data.Vector.Unboxed.$fOrdVector_$cmax’
>
> src/Warnings2.hs: warning:
>     Could not specialise imported function
> ‘Data.Vector.Unboxed.$fOrdVector_$cmin’
>       when specialising ‘Data.Vector.Unboxed.$fOrdVector’
>     Probable fix: add INLINABLE pragma on
> ‘Data.Vector.Unboxed.$fOrdVector_$cmin’
>
> src/Warnings2.hs: warning:
>     Could not specialise imported function ‘ghc-
> prim-0.5.2.0:GHC.Classes.$w$c>=’
>       when specialising ‘ghc-prim-0.5.2.0:GHC.Classes.$fOrd(,)_$c>=’
>     Probable fix: add INLINABLE pragma on ‘ghc-
> prim-0.5.2.0:GHC.Classes.$w$c>=’
>
> src/Warnings2.hs: warning:
>     Could not specialise imported function ‘ghc-
> prim-0.5.2.0:GHC.Classes.$w$c<’
>       when specialising ‘ghc-prim-0.5.2.0:GHC.Classes.$fOrd(,)_$c<’
>     Probable fix: add INLINABLE pragma on ‘ghc-
> prim-0.5.2.0:GHC.Classes.$w$c<’
>
> src/Warnings2.hs: warning:
>     Could not specialise imported function ‘ghc-
> prim-0.5.2.0:GHC.Classes.$w$c<=’
>       when specialising ‘ghc-prim-0.5.2.0:GHC.Classes.$fOrd(,)_$c<=’
>     Probable fix: add INLINABLE pragma on ‘ghc-
> prim-0.5.2.0:GHC.Classes.$w$c<=’
>
> src/Warnings2.hs: warning:
>     Could not specialise imported function ‘ghc-
> prim-0.5.2.0:GHC.Classes.$w$ccompare’
>       when specialising ‘ghc-prim-0.5.2.0:GHC.Classes.$fOrd(,)_$ccompare’
>     Probable fix: add INLINABLE pragma on ‘ghc-
> prim-0.5.2.0:GHC.Classes.$w$ccompare’
> }}}

New description:

 When compiling a program with GHC 8.4.3, vector 0.12.0.1 (with a
 dependency on primitive 0.6.4.0) and `-Weverything`, I get several
 warnings that `INLINABLE` pragmas should be added to the vector and ghc-
 prim packages.

 It would be nicer if these warnings didn't happen, even with
 `-Weverything`. Also, perhaps there are optimization opportunities that
 are lost.

 A somewhat reduced example (can be reduced further by removing the
 function definitions and unused imports that creates):

 {{{#!hs
 {-# OPTIONS_GHC -Wall-missed-specialisations #-}
 {-# LANGUAGE MultiParamTypeClasses, TypeFamilies #-}

 module Warnings2 where

 import GHC.Base (liftM)
 import qualified Data.Vector.Generic.Base as G (Vector, basicUnsafeFreeze,
   basicUnsafeThaw, basicLength, basicUnsafeSlice, basicUnsafeIndexM,
   basicUnsafeCopy, elemseq)
 import qualified Data.Vector.Generic.Mutable.Base as GM (MVector,
 basicLength,
   basicUnsafeSlice, basicOverlaps, basicUnsafeNew, basicInitialize,
   basicUnsafeReplicate, basicUnsafeRead, basicUnsafeWrite, basicClear,
 basicSet,
   basicUnsafeCopy, basicUnsafeMove, basicUnsafeGrow)
 import qualified Data.Vector.Unboxed as U (Unbox, Vector)
 import qualified Data.Vector.Unboxed.Mutable as U (MVector)

 newtype T = T () deriving (Show, Eq, Ord)
 newtype C = C (T, U.Vector T) deriving (Show, Eq, Ord)

 instance U.Unbox T

 newtype instance U.MVector s T = MV_T (U.MVector s ())
 instance GM.MVector U.MVector T where
   basicLength (MV_T mv) = GM.basicLength mv
   basicUnsafeSlice i l (MV_T mv) = MV_T (GM.basicUnsafeSlice i l mv)
   basicOverlaps (MV_T mv1) (MV_T mv2) = GM.basicOverlaps mv1 mv2
   basicUnsafeNew l = MV_T `liftM` GM.basicUnsafeNew l
   basicInitialize (MV_T mv) = GM.basicInitialize mv
   basicUnsafeReplicate l _ = MV_T `liftM` GM.basicUnsafeReplicate l ()
   basicUnsafeRead (MV_T mv) i = const (T ()) `liftM` GM.basicUnsafeRead mv
 i
   basicUnsafeWrite (MV_T mv) i _ = GM.basicUnsafeWrite mv i ()
   basicClear (MV_T mv) = GM.basicClear mv
   basicSet (MV_T mv) x = GM.basicSet mv ()
   basicUnsafeCopy (MV_T mv1) (MV_T mv2) = GM.basicUnsafeCopy mv1 mv2
   basicUnsafeMove (MV_T mv1) (MV_T mv2) = GM.basicUnsafeMove mv1 mv2
   basicUnsafeGrow (MV_T mv) l = MV_T `liftM` GM.basicUnsafeGrow mv l

 newtype instance U.Vector T = V_T (U.Vector ())
 instance G.Vector U.Vector T where
   basicUnsafeFreeze (MV_T mv) = V_T `liftM` G.basicUnsafeFreeze mv
   basicUnsafeThaw (V_T v) = MV_T `liftM` G.basicUnsafeThaw v
   basicLength (V_T v) = G.basicLength v
   basicUnsafeSlice i l (V_T v) = V_T (G.basicUnsafeSlice i l v)
   basicUnsafeIndexM (V_T v) i = const (T ()) `liftM` G.basicUnsafeIndexM v
 i
   basicUnsafeCopy (MV_T mv) (V_T v) = G.basicUnsafeCopy mv v
   elemseq (V_T v) _ = G.elemseq v ()
 }}}

 The warnings:

 {{{#!default lineno=1 marks=16,31,46
 src/Warnings2.hs: warning:
     Could not specialise imported function
 ‘Data.Vector.Unboxed.$w$cshowsPrec’
       when specialising ‘Data.Vector.Unboxed.$fShowVector_$cshowsPrec’
       when specialising ‘Data.Vector.Unboxed.$fShowVector’
     Probable fix: add INLINABLE pragma on
 ‘Data.Vector.Unboxed.$w$cshowsPrec’

 src/Warnings2.hs: warning:
     Could not specialise imported function
 ‘Data.Vector.Unboxed.$fShowVector_$cshow’
       when specialising ‘Data.Vector.Unboxed.$fShowVector’
     Probable fix: add INLINABLE pragma on
 ‘Data.Vector.Unboxed.$fShowVector_$cshow’

 src/Warnings2.hs: warning:
     Could not specialise imported function
 ‘Data.Vector.Unboxed.$fShowVector_$cshowList’
       when specialising ‘Data.Vector.Unboxed.$fShowVector’
     Probable fix: add INLINABLE pragma on
 ‘Data.Vector.Unboxed.$fShowVector_$cshowList’

 src/Warnings2.hs: warning:
     Could not specialise imported function ‘ghc-
 prim-0.5.2.0:GHC.Classes.$w$c==’
       when specialising ‘ghc-prim-0.5.2.0:GHC.Classes.$fEq(,)_$c==’
     Probable fix: add INLINABLE pragma on ‘ghc-
 prim-0.5.2.0:GHC.Classes.$w$c==’

 src/Warnings2.hs: warning:
     Could not specialise imported function
 ‘Data.Vector.Unboxed.$fOrdVector_$cmax’
       when specialising ‘Data.Vector.Unboxed.$fOrdVector’
     Probable fix: add INLINABLE pragma on
 ‘Data.Vector.Unboxed.$fOrdVector_$cmax’

 src/Warnings2.hs: warning:
     Could not specialise imported function
 ‘Data.Vector.Unboxed.$fOrdVector_$cmin’
       when specialising ‘Data.Vector.Unboxed.$fOrdVector’
     Probable fix: add INLINABLE pragma on
 ‘Data.Vector.Unboxed.$fOrdVector_$cmin’

 src/Warnings2.hs: warning:
     Could not specialise imported function ‘ghc-
 prim-0.5.2.0:GHC.Classes.$w$c>=’
       when specialising ‘ghc-prim-0.5.2.0:GHC.Classes.$fOrd(,)_$c>=’
     Probable fix: add INLINABLE pragma on ‘ghc-
 prim-0.5.2.0:GHC.Classes.$w$c>=’

 src/Warnings2.hs: warning:
     Could not specialise imported function ‘ghc-
 prim-0.5.2.0:GHC.Classes.$w$c<’
       when specialising ‘ghc-prim-0.5.2.0:GHC.Classes.$fOrd(,)_$c<’
     Probable fix: add INLINABLE pragma on ‘ghc-
 prim-0.5.2.0:GHC.Classes.$w$c<’

 src/Warnings2.hs: warning:
     Could not specialise imported function ‘ghc-
 prim-0.5.2.0:GHC.Classes.$w$c<=’
       when specialising ‘ghc-prim-0.5.2.0:GHC.Classes.$fOrd(,)_$c<=’
     Probable fix: add INLINABLE pragma on ‘ghc-
 prim-0.5.2.0:GHC.Classes.$w$c<=’

 src/Warnings2.hs: warning:
     Could not specialise imported function ‘ghc-
 prim-0.5.2.0:GHC.Classes.$w$ccompare’
       when specialising ‘ghc-prim-0.5.2.0:GHC.Classes.$fOrd(,)_$ccompare’
     Probable fix: add INLINABLE pragma on ‘ghc-
 prim-0.5.2.0:GHC.Classes.$w$ccompare’
 }}}

--

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15388#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list