[GHC] #10767: SPECIALIZE generates warning but works fine

GHC ghc-devs at haskell.org
Tue Aug 11 19:05:25 UTC 2015


#10767: SPECIALIZE generates warning but works fine
-------------------------------------+-------------------------------------
              Reporter:  osa1        |             Owner:
                  Type:  bug         |            Status:  new
              Priority:  normal      |         Milestone:
             Component:  Compiler    |           Version:  7.10.2
              Keywords:              |  Operating System:  Unknown/Multiple
          Architecture:              |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
             Test Case:              |        Blocked By:
              Blocking:              |   Related Tickets:
Differential Revisions:              |
-------------------------------------+-------------------------------------
 I have this code:

 {{{#!hs
 {-# LANGUAGE ScopedTypeVariables, TypeFamilies #-}

 module Main where

 import Data.Proxy

 class SpecList a where
     type List a :: *

     slCase      :: List a -> b -> (a -> List a -> b) -> b

 data IntList
   = ILNil
   | ILCons {-# UNPACK #-} !Int IntList
   deriving (Show)

 instance SpecList Int where
   type List Int = IntList

   slCase ILNil        n _  = n
   slCase (ILCons i t) _ c  = c i t

 fromList :: [Int] -> IntList
 fromList []      = ILNil
 fromList (h : t) = ILCons h (fromList t)

 lst1 :: IntList
 lst1 = fromList [1..10]

 {-# SPECIALIZE genLength :: Proxy Int -> List Int -> Int #-}
 genLength :: forall a . SpecList a => Proxy a -> List a -> Int
 genLength p lst = slCase lst 0 (\(_ :: a) tail -> 1 + genLength p tail)

 main :: IO ()
 main = print (genLength (Proxy :: Proxy Int) lst1)
 }}}

 When I compile it(no matter which optimization level is used), it prints
 this warning:

 {{{
 Main.hs:30:1: Warning:
     RULE left-hand side too complicated to desugar
       Optimised lhs: case cobox_a17r
                      of _ [Occ=Dead] { GHC.Types.Eq# cobox ->
                      genLength @ Int $dSpecList_a17q
                      }
       Orig lhs: case cobox_a17r of cobox_a17r { GHC.Types.Eq# cobox ->
                 genLength @ Int $dSpecList_a17q
                 }
 }}}

 (I presume this is related with the rewrite rule generated to be able to
 replace calls to generic version to calls to specialized versions when
 possible.)

 But this program compiles fine with -O2, i.e. `genLength lst1` is replaced
 with specialized definition of `genLength`, without any dictionary
 passing.

 So the warning is confusing for two reasons:

 - It's not related with the code, it seems like it's a problem with GHC-
 generated rewrite rule.
 - It still works fine.

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


More information about the ghc-tickets mailing list