[GHC] #8334: unexpected type inference failure in main

GHC ghc-devs at haskell.org
Fri Sep 20 09:53:09 CEST 2013


#8334: unexpected type inference failure in main
------------------------------------+-------------------------------------
       Reporter:  carter            |             Owner:
           Type:  bug               |            Status:  new
       Priority:  normal            |         Milestone:
      Component:  Compiler          |           Version:  7.7
       Keywords:                    |  Operating System:  Unknown/Multiple
   Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
     Difficulty:  Unknown           |         Test Case:
     Blocked By:                    |          Blocking:
Related Tickets:                    |
------------------------------------+-------------------------------------
 I'm not sure if this is a failure of me understanding the semantics of
 type families, or something where inference should work! Or maybe its just
 me failing to understand the rules / convention for main.


 {{{
 {-# LANGUAGE MagicHash, UnboxedTuples #-}

 module PrefetchTest where

 import GHC.Prim

 import Data.Vector.Storable.Mutable
 -- import Foreign.ForeignPtr -- (unsafeForeignPtrToPtr)
 import Foreign.Ptr
 import GHC.ST
 import Data.Primitive.ByteArray
 import Control.Monad.Primitive

 -- newByteArray :: PrimMonad m => Int -> m (MutableByteArray (PrimState
 m))
 -- sameMutableByteArray :: MutableByteArray s -> MutableByteArray s ->
 Bool
 --unsafeFreezeByteArray :: PrimMonad m => MutableByteArray (PrimState m)
 -> m ByteArray
 -- unsafeThawByteArray :: PrimMonad m => ByteArray -> m (MutableByteArray
 (PrimState m))



 --main :: IO ()
 main = do
     mv1 <- newByteArray 17
     v1 <- unsafeFreezeByteArray mv1
     return ()

 }}}


 i get

 {{{
 refetch.hs:42:5:
     No instance for (Monad m0) arising from a do statement
     The type variable ‛m0’ is ambiguous
     Relevant bindings include main :: m0 () (bound at prefetch.hs:41:1)
     Note: there are several potential instances:
       instance Monad (ST s) -- Defined in ‛GHC.ST’
       instance Monad ((->) r) -- Defined in ‛GHC.Base’
       instance Monad IO -- Defined in ‛GHC.Base’
       ...plus one other
     In a stmt of a 'do' block: mv1 <- newByteArray 17
     In the expression:
       do { mv1 <- newByteArray 17;
            v1 <- unsafeFreezeByteArray mv1;
            return () }
     In an equation for ‛main’:
         main
           = do { mv1 <- newByteArray 17;
                  v1 <- unsafeFreezeByteArray mv1;
                  return () }

 prefetch.hs:42:12:
     No instance for (PrimMonad m0) arising from a use of ‛newByteArray’
     The type variable ‛m0’ is ambiguous
     Relevant bindings include main :: m0 () (bound at prefetch.hs:41:1)
     Note: there are several potential instances:
       instance PrimMonad IO -- Defined in ‛Control.Monad.Primitive’
       instance PrimMonad (ST s) -- Defined in ‛Control.Monad.Primitive’
     In a stmt of a 'do' block: mv1 <- newByteArray 17
     In the expression:
       do { mv1 <- newByteArray 17;
            v1 <- unsafeFreezeByteArray mv1;
            return () }
     In an equation for ‛main’:
         main
           = do { mv1 <- newByteArray 17;
                  v1 <- unsafeFreezeByt

 }}}


 this is because main seems to not be assumed to have type IO ()

 If i add that type ascription to main, or I comment out the name, type
 inference succeeds.

 I understand and know we have special treatment for whats the main module,
 but this is an example of that special treatment changing the type
 inference! Is that a known issue? (its obvious to me now, but is it
 reasonable?)


 this is pretty much a nonissue, but i think its still worth noting.

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



More information about the ghc-tickets mailing list