On Mon, Apr 6, 2009 at 7:39 PM, Manuel M T Chakravarty <chak@cse.unsw.edu.au> wrote:
The thing that confuses me about this case is how, if the type sig on memo_fmap is omitted, ghci has no problem with it, and even gives it the type that it rejected:
------------------------------------------------
{-# LANGUAGE TypeFamilies #-}
class Fun d where
type Memo d :: * -> *
abst :: (d -> a) -> Memo d a
appl :: Memo d a -> (d -> a)
memo_fmap f x = abst (f . appl x)
-- [m@monire a]$ ghci -ignore-dot-ghci
-- GHCi, version 6.10.1: http://www.haskell.org/ghc/ :? for help
--
-- Prelude> :l ./Memo.hs
-- [1 of 1] Compiling Main ( Memo.hs, interpreted )
-- Ok, modules loaded: Main.
--
-- *Main> :t memo_fmap
-- memo_fmap :: (Fun d) => (a -> c) -> Memo d a -> Memo d c
-- copy/paste the :t sig
memo_fmap_sig :: (Fun d) => (a -> c) -> Memo d a -> Memo d c
memo_fmap_sig f x = abst (f . appl x)
-- and,
-- *Main> :r
-- [1 of 1] Compiling Main ( Memo.hs, interpreted )
--
-- Memo.hs:26:35:
-- Couldn't match expected type `Memo d'
-- against inferred type `Memo d1'
-- In the first argument of `appl', namely `x'
-- In the second argument of `(.)', namely `appl x'
-- In the first argument of `abst', namely `(f . appl x)'
-- Failed, modules loaded: none.
------------------------------------------------
Matt