[GHC] #9299: GHCi type inference error
GHC
ghc-devs at haskell.org
Sat Jul 12 03:25:56 UTC 2014
#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
More information about the ghc-tickets
mailing list