[GHC] #14327: Type error in program caused by unrelated definition

GHC ghc-devs at haskell.org
Thu Oct 5 22:43:41 UTC 2017


#14327: Type error in program caused by unrelated definition
-------------------------------------+-------------------------------------
        Reporter:  lexi.lambda       |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler (Type    |              Version:  8.2.1
  checker)                           |
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Incorrect         |  Unknown/Multiple
  error/warning at compile-time      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by dfeuer):

 Even weirder: when I added the definitions of the relevant functions and
 classes from `Control.Monad.Free` to the test module (to remove the
 dependency on `free`), I found that the problem is now sensitive to the
 definition order in a ''different way''.

 {{{#!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 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))
 }}}

 The surprising error does not occur with the three functions defined in
 their original order, but it ''does'' occur if `writeLine` appears
 ''before'' at least one of the other definitions.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14327#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list