[GHC] #9299: GHCi type inference error

#9299: GHCi type inference error ------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.8.2 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: Other Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- This code (required conduit-1.1.6): {{{ {- Bolled down from https://github.com/snoyberg/conduit/blob/process/conduit- extra/Data/Conduit/Process.hs -} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE RankNTypes #-} import System.Process import Control.Monad.IO.Class (MonadIO, liftIO) import System.IO (Handle, hClose) import Data.Conduit import Data.ByteString (ByteString) import Data.Maybe (fromMaybe) import Control.Applicative ((<$>), (<*>)) data UseProvidedHandle = UseProvidedHandle data Inherited = Inherited data ClosedStream = ClosedStream class InputSource a where isStdStream :: (Maybe Handle -> IO a, Maybe StdStream) instance InputSource Handle where isStdStream = (\(Just h) -> return h, Just CreatePipe) instance InputSource ClosedStream where isStdStream = (\(Just h) -> hClose h >> return ClosedStream, Just CreatePipe) instance (r ~ (), MonadIO m, i ~ ByteString) => InputSource (ConduitM i o m r) where isStdStream = (\(Just h) -> return $ sinkHandle h, Just CreatePipe) instance (r ~ (), r' ~ (), MonadIO m, MonadIO n, i ~ ByteString) => InputSource (ConduitM i o m r, n r') where isStdStream = (\(Just h) -> return (sinkHandle h, liftIO $ hClose h), Just CreatePipe) instance InputSource Inherited where isStdStream = (\Nothing -> return Inherited, Just Inherit) instance InputSource UseProvidedHandle where isStdStream = (\Nothing -> return UseProvidedHandle, Nothing) sinkHandle :: MonadIO m => Handle -> Consumer ByteString m () sinkHandle = error "sinkHandle" conduitProcess :: (MonadIO m, InputSource stdin) => CreateProcess -> m (stdin, ProcessHandle) conduitProcess cp = liftIO $ do let (getStdin, stdinStream) = isStdStream (stdinH, _, _, ph) <- createProcess cp { std_in = fromMaybe (std_in cp) stdinStream } (,) <$> getStdin stdinH <*> return ph main :: IO () main = putStrLn "Hello" }}} Compiles fine with ghc, and runs correctly with `runghc`, but fails to load into ghci with the following error: {{{ GHCi, version 7.8.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. [1 of 1] Compiling Main ( test.hs, interpreted ) test.hs:45:9: No instance for (InputSource a0) arising from the ambiguity check for ‘stdinStream’ The type variable ‘a0’ is ambiguous When checking that ‘stdinStream’ has the inferred type ‘Maybe StdStream’ Probable cause: the inferred type is ambiguous In the second argument of ‘($)’, namely ‘do { let (getStdin, stdinStream) = isStdStream; (stdinH, _, _, ph) <- createProcess (cp {std_in = fromMaybe (std_in cp) stdinStream}); (,) <$> getStdin stdinH <*> return ph }’ In the expression: liftIO $ do { let (getStdin, stdinStream) = isStdStream; (stdinH, _, _, ph) <- createProcess (cp {std_in = fromMaybe (std_in cp) stdinStream}); (,) <$> getStdin stdinH <*> return ph } Failed, modules loaded: none. }}} Same problem in 7.6.3, 7.8.2 and 7.8.3. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9299 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9299: GHCi type inference error -------------------------------------+------------------------------------ Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Other | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by erikd): From #ghc on Freenode: {{{ <dolio> Here's my theory. <dolio> The difference between GHC and GHCi is extended defaulting. <dolio> InputSource is only eligible for extended defaulting, not regular defaulting. <dolio> So, when loaded in ghci, it's getting defaulted, which is ambiguous. <dolio> Whereas in ghc, it doesn't get defaulted, and correctly gets tied to the stdin variable in the signature of conduitProcess. <dolio> None of the instances for InputSource are on the defaulting list, which is why it's ambiguous. <dolio> I don't understand why defaulting would kick in, though. <dolio> It's like it's overly aggressive. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9299#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9299: GHCi type inference error -------------------------------------+------------------------------------ Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Other | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by erikd): * version: 7.8.2 => 7.8.3 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9299#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9299: GHCi type inference error -------------------------------------+------------------------------------ Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Other | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by erikd): * version: 7.8.3 => 7.6.3 Comment: Setting version to earliest version I've tested. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9299#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9299: GHCi type inference error -------------------------------------+------------------------------------ Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Other | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by darchon): Do you have a `$HOME/.ghci` config file with `:set -XNoMonomorphismRestriction`? The reason I'm asking is because I'm only getting the reported error if run ghc/runghc/ghci with`-XNoMonomorphismRestriction`. Note that before 7.8.1, the monomorphism restriction was turned _on_ by default for all invocations of ghc. Starting from 7.8.1 however, the monomorphism restriction is turned _off_ by default in ghci, but left on in the other invocations. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9299#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9299: GHCi type inference error -------------------------------------+------------------------------------ Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Other | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by erikd): Yes, I had `-XNoMonomorphismRestriction` in my $HOME/.ghci file. If I remove it, the problem disappears. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9299#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9299: GHCi type inference error -------------------------------------+------------------------------------ Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Other | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by darchon): And the above is weird. The release notes for 7.8.1 state: {{{ The monomorphism restriction is now turned off by default in GHCi. }}} So I would expect that: {{{ ghci-7.8.3 test.hs }}} and {{{ ghci-7.8.3 -XNoMonomorphismRestriction test.hs }}} Would behave the same, that is, give an error. Otherwise I don't understand the release notes. What's the difference between having the monomorphism restriction turned off by default, and running with -XNoMonomorphismRestriction? If there is a difference, this should be documented more clearly in the release notes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9299#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9299: GHCi type inference error -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: Differential Revisions: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: Difficulty: Unknown | Blocking: Blocked By: | Related Tickets: | -------------------------------------+------------------------------------- Comment (by simonpj): It's fine actually. * GHCi maintains two sets of flags, one for the interactive REPL and one for loading module (see [http://www.haskell.org/ghc/docs/latest/html/users_guide/ghci-set.html #ghci-interactive-options the manual 2.8.3]). * The interactive flags has `-XNoMonomorphismRestriction` applied ''after'' initialising from the .ghci file. * The release notes mean that only the interactive flags have `-XNoMonomorphismRestriction`. The loading flages are unaffected. I'll clarify the documentation which isn't great I agree. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9299#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9299: GHCi type inference error
-------------------------------------+-------------------------------------
Reporter: erikd | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: GHCi | Version: 7.6.3
Resolution: | Keywords:
Differential Revisions: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Other
Unknown/Multiple | Test Case:
Difficulty: Unknown | Blocking:
Blocked By: |
Related Tickets: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#9299: GHCi type inference error -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 7.6.3 Resolution: fixed | Keywords: Differential Revisions: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: Difficulty: Unknown | Blocking: Blocked By: | Related Tickets: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9299#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC