[GHC] #14327: Type error in program caused by unrelated definition
GHC
ghc-devs at haskell.org
Fri Oct 6 02:24:29 UTC 2017
#14327: Type error in program caused by unrelated definition
-------------------------------------+-------------------------------------
Reporter: lexi.lambda | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone: 8.4.1
Component: Compiler (Type | Version: 8.2.1
checker) |
Resolution: duplicate | Keywords: FunDeps
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect | Unknown/Multiple
error/warning at compile-time | Test Case:
Blocked By: | Blocking:
Related Tickets: #13506 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):
* keywords: => FunDeps
* status: new => closed
* resolution: => duplicate
* related: => #13506
Comment:
OK, it turns out this is actually a duplicate of #13506. First, here is
the program that I tested, for the sake of posterity:
{{{#!hs
{-# language DeriveFunctor, FunctionalDependencies
, MultiParamTypeClasses, FlexibleInstances #-}
module T14327 where
import Prelude hiding (readFile, writeFile)
import Data.Functor.Sum
data Free f a = Pure a | Free (f (Free f a)) deriving (Functor)
class Monad m => MonadFree f m | m -> f where
wrap :: f (m a) -> m a
instance Functor f => Applicative (Free f)
instance Functor f => Monad (Free f)
instance Functor f => MonadFree f (Free f) where
wrap = Free
liftF :: (Functor f, MonadFree f m) => f a -> m a
liftF fa = wrap (return <$> fa)
data FileSystemF a
= ReadFile FilePath (String -> a)
| WriteFile FilePath String a
deriving (Functor)
data ConsoleF a
= WriteLine String a
deriving (Functor)
data CloudF a
= GetStackInfo String (String -> a)
deriving (Functor)
type App = Free (Sum FileSystemF (Sum ConsoleF CloudF))
writeLine :: String -> App ()
writeLine line = liftF (InR (WriteLine line ()))
readFile :: FilePath -> App String
readFile path = liftF (InL (ReadFile path id))
writeFile :: FilePath -> String -> App ()
writeFile path contents = liftF (InL (WriteFile path contents ()))
}}}
On GHC 8.2.1 and earlier, this does indeed spuriously give more errors
than it should:
{{{
GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling T14327 (
/u/rgscott/Documents/Hacking/Haskell/Bug.hs, interpreted )
/u/rgscott/Documents/Hacking/Haskell/Bug.hs:37:18: error:
• Couldn't match type ‘Sum ConsoleF CloudF’ with ‘ConsoleF’
arising from a functional dependency between:
constraint ‘MonadFree
(Sum FileSystemF ConsoleF)
(Free (Sum FileSystemF (Sum ConsoleF CloudF)))’
arising from a use of ‘liftF’
instance ‘MonadFree f (Free f)’
at /u/rgscott/Documents/Hacking/Haskell/Bug.hs:15:10-42
• In the expression: liftF (InR (WriteLine line ()))
In an equation for ‘writeLine’:
writeLine line = liftF (InR (WriteLine line ()))
|
37 | writeLine line = liftF (InR (WriteLine line ()))
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
/u/rgscott/Documents/Hacking/Haskell/Bug.hs:40:17: error:
• Couldn't match type ‘ConsoleF’ with ‘Sum ConsoleF CloudF’
arising from a functional dependency between constraints:
‘MonadFree
(Sum FileSystemF (Sum ConsoleF CloudF))
(Free (Sum FileSystemF (Sum ConsoleF CloudF)))’
arising from a use of ‘liftF’
at /u/rgscott/Documents/Hacking/Haskell/Bug.hs:40:17-46
‘MonadFree
(Sum FileSystemF ConsoleF)
(Free (Sum FileSystemF (Sum ConsoleF CloudF)))’
arising from a use of ‘liftF’
at /u/rgscott/Documents/Hacking/Haskell/Bug.hs:37:18-48
• In the expression: liftF (InL (ReadFile path id))
In an equation for ‘readFile’:
readFile path = liftF (InL (ReadFile path id))
|
40 | readFile path = liftF (InL (ReadFile path id))
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
}}}
But on GHC HEAD, it doesn't!
{{{
GHCi, version 8.3.20171004: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling T14327 (
/u/rgscott/Documents/Hacking/Haskell/Bug.hs, interpreted )
/u/rgscott/Documents/Hacking/Haskell/Bug.hs:37:18: error:
• Couldn't match type ‘Sum ConsoleF CloudF’ with ‘ConsoleF’
arising from a functional dependency between:
constraint ‘MonadFree
(Sum FileSystemF ConsoleF)
(Free (Sum FileSystemF (Sum ConsoleF CloudF)))’
arising from a use of ‘liftF’
instance ‘MonadFree f (Free f)’
at /u/rgscott/Documents/Hacking/Haskell/Bug.hs:15:10-42
• In the expression: liftF (InR (WriteLine line ()))
In an equation for ‘writeLine’:
writeLine line = liftF (InR (WriteLine line ()))
|
37 | writeLine line = liftF (InR (WriteLine line ()))
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
}}}
It turns out that commit 48daaaf0bba279b6e362ee5c632de69ed31ab65d (`Don't
report fundep wanted/wanted errors`) fixed this problem. This led me to
realize that this entire ticket is simply a more involved version of the
program in #13506 (which concerns error cascades with functional
dependencies), the ticket that the aforementioned commit originally fixed.
So I'll close this as a duplicate.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14327#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list