Inferred type is less polymorphic than expected?

Benjamin Franksen benjamin.franksen at bessy.de
Tue Aug 9 05:55:41 EDT 2005


On Monday 08 August 2005 09:43, Simon Peyton-Jones wrote:
| | > Are you saying, that the second error causes the first one? Thus,
| | > everything is caused by 'printer' being recursively defined?
| |
| | Yes, that's what I believe. I'm not sure why it shows the first
| | error message at all; in my experience, strange things happen when
| | ghc continues after an error message that you shouldn't pay too
| | much attention to. Perhaps ghc-6.4 just assumes identical contexts
| | in recursive groups without checking the type signatures.
|
| After an error in a function definition for f, GHC carries on
| assuming the function has type
|
| 	f :: forall a. a
|
| That very seldom leads to subsequent errors, but maybe it did this
| time.  The way to find out is to show the program that elicits this
| message but not the other.

As Thomas correctly guessed, this happens if the type signatures of both 
'printer' and 'printCatalog':

\begin{code}
class Catalog c where
  traverse :: c -> Viewer -> IO ()

instance Catalog Int where
  traverse i v = viewShowable v i

type View a = a -> IO ()

data Viewer = Viewer {
    viewShowable :: forall s. Show s => View s,
    viewCatalog :: forall c. Catalog c => View c
  }

--printer :: Viewer
--printer = Viewer {
--  viewCatalog = \x -> traverse x printer,
--  viewShowable = putStrLn . show }
printer = Viewer {
  viewCatalog = printCatalog,
  viewShowable = putStrLn . show }

--printCatalog :: forall c. Catalog c => View c
printCatalog x = traverse x printer

data X = X {
    cat :: Int
  }

instance Catalog X where
  traverse x v = do
    viewCatalog v (cat x)

main = do
  let x = X { cat = 20 }
  traverse x printer
\end{code}

Ben


More information about the Glasgow-haskell-users mailing list