[GHC] #8537: confusing error message for specialize pragma
GHC
ghc-devs at haskell.org
Sun Nov 17 22:53:19 UTC 2013
#8537: confusing error message for specialize pragma
------------------------------------+-------------------------------------
Reporter: carter | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.6.3
Keywords: | Operating System: Unknown/Multiple
Architecture: Unknown/Multiple | Type of failure: None/Unknown
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: |
------------------------------------+-------------------------------------
I get the following confusing error/warning about SPECIALIZE
{{{
SPECIALISE pragma for non-overloaded function `$cfmap'
}}}
with the following example module
{{{
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Numerical.Types.Shape where
import Control.Applicative
import Data.Foldable
import Data.Monoid
import Data.Functor
import Prelude (seq, ($!),($),Show(..),Eq(),Int)
data Nat = S !Nat | Z
--deriving (Eq,Show,Read)
{-
not doing the HLIST style shape because I don't want to have
any pattern matchings going on.
Also would play hell with locality quality in the address translation
hackery,
because there'd be an extra load to get those ints!
-}
infixr 3 :*
{-
the concern basically boils down to "will it specialize / inline well"
-}
data Shape (rank :: Nat) a where
Nil :: Shape Z a
(:*) :: !(a) -> !(Shape r a ) -> Shape (S r) a
--deriving instance (Show (Shape rank a))
-- deriving instance Eq (Shape rank a)
-- #if defined( __GLASGOW_HASKELL__ ) && ( __GLASGOW_HASKELL__ >=
707)
--deriving instance Typeable (Shape rank a)
-- #endif
instance Functor (Shape Z) where
fmap = \ f Nil -> Nil
{-# INLINABLE fmap #-}
{-# SPECIALIZE fmap :: (Int ->Int )-> (Shape Z Int)-> (Shape Z Int)
#-}
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8537>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list