[GHC] #14858: Typed hole subtitution search fails in the REPL

GHC ghc-devs at haskell.org
Mon Feb 26 20:23:52 UTC 2018


#14858: Typed hole subtitution search fails in the REPL
-------------------------------------+-------------------------------------
           Reporter:  paf31          |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.4.1
          Component:  Compiler       |           Version:  8.4.1-alpha3
  (Type checker)                     |
           Keywords:  typed holes    |  Operating System:  Unknown/Multiple
  substitutions                      |
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 It seems as though type class defaulting might be happening before the
 search.

 This finds only undefined:

  {{{#!text
 > _traverse print "abc"

 <interactive>:20:1: error:
     • Found hole: _traverse :: (() -> IO ()) -> [Char] -> t
       Where: ‘t’ is a rigid type variable bound by
                the inferred type of it :: t
                at <interactive>:20:1-21
       Or perhaps ‘_traverse’ is mis-spelled, or not in scope
     • In the expression: _traverse
       In the expression: _traverse print "abc"
       In an equation for ‘it’: it = _traverse print "abc"
     • Relevant bindings include it :: t (bound at <interactive>:20:1)
       Valid substitutions include
         undefined :: forall (a :: TYPE r).
                      GHC.Stack.Types.HasCallStack =>
                      a
           (imported from ‘Prelude’ (and originally defined in ‘GHC.Err’))
  }}}

 Annotating the return type helps, but we still don't find traverse_:

  {{{#!text
 > _traverse print "abc" :: IO ()

 <interactive>:22:1: error:
     • Found hole: _traverse :: (() -> IO ()) -> [Char] -> IO ()
       Or perhaps ‘_traverse’ is mis-spelled, or not in scope
     • In the expression: _traverse
       In the expression: _traverse print "abc" :: IO ()
       In an equation for ‘it’: it = _traverse print "abc" :: IO ()
     • Relevant bindings include
         it :: IO () (bound at <interactive>:22:1)
       Valid substitutions include
         mempty :: forall a. Monoid a => a
           (imported from ‘Prelude’ (and originally defined in ‘GHC.Base’))
         undefined :: forall (a :: TYPE r).
                      GHC.Stack.Types.HasCallStack =>
                      a
           (imported from ‘Prelude’ (and originally defined in ‘GHC.Err’))
  }}}

 (note how print seems to have been defaulted to ())

 Annotating the type of print helps:

  {{{#!text
 > _traverse (print :: Char -> IO ()) "abc" :: IO ()

 <interactive>:23:1: error:
     • Found hole: _traverse :: (Char -> IO ()) -> [Char] -> IO ()
       Or perhaps ‘_traverse’ is mis-spelled, or not in scope
     • In the expression: _traverse
       In the expression:
           _traverse (print :: Char -> IO ()) "abc" :: IO ()
       In an equation for ‘it’:
           it = _traverse (print :: Char -> IO ()) "abc" :: IO ()
     • Relevant bindings include
         it :: IO () (bound at <interactive>:23:1)
       Valid substitutions include
         mempty :: forall a. Monoid a => a
           (imported from ‘Prelude’ (and originally defined in ‘GHC.Base’))
         undefined :: forall (a :: TYPE r).
                      GHC.Stack.Types.HasCallStack =>
                      a
           (imported from ‘Prelude’ (and originally defined in ‘GHC.Err’))
         foldMap :: forall (t :: * -> *).
                    Foldable t =>
                    forall m a. Monoid m => (a -> m) -> t a -> m
           (imported from ‘Prelude’
            (and originally defined in ‘Data.Foldable’))
         mapM_ :: forall (t :: * -> *) (m :: * -> *) a b.
                  (Foldable t, Monad m) =>
                  (a -> m b) -> t a -> m ()
           (imported from ‘Prelude’
            (and originally defined in ‘Data.Foldable’))
         traverse_ :: forall (t :: * -> *) (f :: * -> *) a b.
                      (Foldable t, Applicative f) =>
                      (a -> f b) -> t a -> f ()
           (imported from ‘Data.Foldable’)
  }}}

 This was found with 8.4.1-rc.1.

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


More information about the ghc-tickets mailing list