#4444: SPECIALISE pragma rejected; regression
---------------------------------+------------------------------------------
    Reporter:  igloo             |        Owner:              
        Type:  bug               |       Status:  new         
    Priority:  highest           |    Milestone:  7.0.1       
   Component:  Compiler          |      Version:  7.0.1 RC1   
    Keywords:                    |     Testcase:              
   Blockedby:                    |   Difficulty:              
          Os:  Unknown/Multiple  |     Blocking:              
Architecture:  Unknown/Multiple  |      Failure:  None/Unknown
---------------------------------+------------------------------------------

Comment(by igloo):

 Hmm, is this example (from `docs/users_guide/glasgow_exts.xml`) wrong
 then?:
 {{{
 {-# LANGUAGE GADTs, MagicHash #-}
 module Q where

 import GHC.Exts

 data Arr e where
   ArrInt :: !Int -> ByteArray# -> Arr Int
   ArrPair :: !Int -> Arr e1 -> Arr e2 -> Arr (e1, e2)

 (!:) :: Arr e -> Int -> e
 {-# SPECIALISE INLINE (!:) :: Arr Int -> Int -> Int #-}
 {-# SPECIALISE INLINE (!:) :: Arr (a, b) -> Int -> (a, b) #-}
 (ArrInt _ ba)     !: (I# i) = I# (indexIntArray# ba i)
 (ArrPair _ a1 a2) !: i      = (a1 !: i, a2 !: i)
 }}}
 {{{
 Q.hs:11:1:
     Discarding pragma for non-overloaded function `!:'
     In the SPECIALISE pragma
       {-# SPECIALIZE INLINE (sat-args=2) !: :: Arr Int -> Int -> Int #-}

 Q.hs:12:1:
     Discarding pragma for non-overloaded function `!:'
     In the SPECIALISE pragma
       {-# SPECIALIZE INLINE (sat-args=2) !: ::
                                            Arr (a, b) -> Int -> (a, b) #-}
 }}}

 If it doesn't make sense, then personally I'm happy for it to be an error.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4444#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to