[GHC] #10769: Yet another crash from typed holes
GHC
ghc-devs at haskell.org
Wed Aug 12 18:24:37 UTC 2015
#10769: Yet another crash from typed holes
-------------------------------+-----------------------------------------
Reporter: rpglover64 | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 7.10.3
Component: Compiler | Version: 7.10.2
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64 (amd64)
Type of failure: GHCi crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------+-----------------------------------------
Comment (by bgamari):
I would probably say that the bug was that GHC 7.10.2 didn't realize it
needed a `Functor` instance (hence crashing at runtime as it had no
dictionary to provide). This appears to be fixed in `master`.
The problem here is that you program is ambiguous; GHC has no way of
knowing which functor you mean here. GHC will gladly help you fill in the
holes of an unambiguous program, but it won't make decisions on your
behalf.
This can be resolved by telling GHC which functor `a'` is supposed to be.
For instance, perhaps you want `a` and `a'` to be values of the same
functor,
{{{#!hs
{-# OPTIONS_GHC -fdefer-typed-holes #-}
{-# LANGUAGE ScopedTypeVariables #-}
hylo :: Functor f => (a -> f a) -> (f b -> b) -> a -> b
hylo a b = h where h = b . fmap h . a
foo :: forall f a b. Functor f => (a -> f a) -> (f b -> b) -> a -> b
foo a b = hylo a' b'
where a' x = _
b' :: f b -> b
b' = _
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10769#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list