[GHC] #11766: Lazy application gives "No instance" error while strict application works

#11766: Lazy application gives "No instance" error while strict application works -------------------------------------+------------------------------------- Reporter: MichaelK | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This might make sense if there were any IO. Here's the code: {{{#!hs {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverlappingInstances #-} {-# LANGUAGE UndecidableInstances #-} import Data.Maybe (isJust) data Wrapper a = Wrapper a deriving (Show) class Resolution a instance Resolution (Wrapper a) class (Resolution b, Resolution d) => C a b c d | a -> b, c -> d, a d -> c, b c -> a where cfun :: (b -> d) -> a -> c instance (Resolution b, Resolution d, a ~ b, c ~ d) => C a b c d where cfun = ($) instance (Eq a, C b c d e) => C (Maybe a -> b) c (Maybe a -> d) e where cfun f b = \x -> cfun f (b x) foo :: Maybe a -> Wrapper Bool foo = Wrapper . isJust }}} Applying `Nothing` strictly or in a `let` clause gives the expected answer (I expect that `cfun id foo` would be equivalent to `foo`): {{{#!hs *Main> cfun id foo $! Nothing Wrapper False *Main> let f = cfun id foo in f Nothing Wrapper False }}} But regular application (or just `(cfun id foo) Nothing`) returns the following error: {{{#!hs *Main> cfun id foo $ Nothing <interactive>:6:1: No instance for (Resolution (Maybe a0 -> Wrapper Bool)) (maybe you haven't applied enough arguments to a function?) arising from a use of ‘cfun’ In the expression: cfun id foo In the expression: cfun id foo $ Nothing In an equation for ‘it’: it = cfun id foo $ Nothing }}} In case it helps, the purpose of this code is for `cfun` to have the effective type of {{{#!hs cfun :: (Eq a0, Eq a1, .., Eq an) => (Wrapped b -> Wrapped c) -> (Maybe a0 -> Maybe a1 -> .. -> Maybe an -> Wrapped b) -> (Maybe a0 -> Maybe a1 -> .. -> Maybe an -> Wrapped c) }}} i.e. apply a function to the "wrapped" return value of another function of the above form. Tested on GHC 8.0.1-rc2 (most recent OSX binary as of now) and 7.10.3. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11766 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11766: Lazy application gives "No instance" error while strict application works -------------------------------------+------------------------------------- Reporter: MichaelK | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Happily this works in HEAD. Can someone check on the 8.0 branch? It'd might be easier for the regression test to use these defns {{{ t1 = cfun id foo $! Nothing t2 = let f = cfun id foo in f Nothing t3 = cfun id foo Nothing t4 = cfun id foo $ Nothing }}} But then remove the `Eq a` constraint from the `C` instance, which is ambiguous and only resolved by GHCi's generous defaulting. Check that `t4` does not work with RC2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11766#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11766: Lazy application gives "No instance" error while strict application works -------------------------------------+------------------------------------- Reporter: MichaelK | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Happily, this does work with HEAD. I'll commit a regression test. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11766#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11766: Lazy application gives "No instance" error while strict application works
-------------------------------------+-------------------------------------
Reporter: MichaelK | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1-rc2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#11766: Lazy application gives "No instance" error while strict application works -------------------------------------+------------------------------------- Reporter: MichaelK | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T11766 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * testcase: => typecheck/should_compile/T11766 * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11766#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC