
#12466: Typechecker regression: Inaccessible code in a type expected by the context -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): mpickering, I'm a bit confused too why `foo 5 'a'` itself doesn't typecheck, but that's not how `lens` is using this style of code. The way `lens` is using it, it's closer in style to something like this: {{{#!hs bar :: Foo a => a -> a bar = foo 5 }}} Now `bar 'a'` will typecheck. Similarly, if you want a more complete `lens`-based piece of code to test against, you can use the following: {{{#!hs {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} module Lens where indexing :: Indexable Int p => ((a -> Indexing f b) -> s -> Indexing f t) -> p a (f b) -> s -> f t indexing l iafb s = snd $ runIndexing (l (\a -> Indexing (\i -> i `seq` (i + 1, indexed ia fb i a))) s) 0 newtype Indexing f a = Indexing { runIndexing :: Int -> (Int, f a) } instance Functor f => Functor (Indexing f) where fmap f (Indexing m) = Indexing $ \i -> case m i of (j, x) -> (j, fmap f x) instance Applicative f => Applicative (Indexing f) where pure x = Indexing $ \i -> (i, pure x) Indexing mf <*> Indexing ma = Indexing $ \i -> case mf i of (j, ff) -> case ma j of ~(k, fa) -> (k, ff <*> fa) type IndexedTraversal i s t a b = forall p f. (Indexable i p, Applicative f) => p a (f b) -> s -> f t class Conjoined p where conjoined :: ((p ~ (->)) => q (a -> b) r) -> q (p a b) r -> q (p a b) r conjoined _ r = r class Conjoined p => Indexable i p where indexed :: p a b -> i -> a -> b --------------------------------------------------------------------- newtype Indexed i a b = Indexed { runIndexed :: i -> a -> b } -- You'll need to comment out the instance below to typecheck on HEAD instance Conjoined (Indexed i) --------------------------------------------------------------------- -- This now typechecks: traversed :: Traversable f => IndexedTraversal Int (f a) (f b) a b traversed = conjoined traverse (indexing traverse) }}} ----- The fact that `foo 5 'a'` doesn't typecheck might be part of the bug. As Edward mentioned above, I suspect that we are too eagerly discharging an obligation somewhere, and that explains: 1. Why `foo 5 'a'` doesn't typecheck but `bar 'a'` does 2. Why a manually implemented `instance Foo Char where foo _ a = a` typechecks but a default `instance Foo Char` doesn't But these are just my suspicions. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12466#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler