Holes in GHC
Simon Peyton-Jones
simonpj at microsoft.com
Thu Jan 26 22:49:16 CET 2012
| The primary goal is to make this part of GHCi. Say, you're working on
| a file Foo.hs in your favorite editor, and you have: ....
Aha. That is helpful (below). Start a GHC wiki page to describe?
Now, if I compile
{-# LANGUAGE ImplicitParams #-}
module Foo where
foo = foldr ?x 'x' [True,False]
I get this:
Foo.hs:4:13:
Unbound implicit parameter (?x::Bool -> Char -> Char)
arising from a use of implicit parameter `?x'
That looks pretty close to what you want, no? You want the error
Foo.hs:4:13:
Found a hole of type: Bool -> Char -> Char
Same information, with different wording.
This reminds me of the recently implemented -fdefer-type-errors. You'd want to be able to *run* a program with hole in it, getting the "unfilled hole of type Bool -> Char -> Char" error if you ever need to evaluate the hole.
Anyway, now I understand more clearly what you are trying to do. Thanks.
Simon
| The primary goal is to make this part of GHCi. Say, you're working on
| a file Foo.hs in your favorite editor, and you have:
|
| ---
|
| foo = foldr __ 0 [1..5]
|
| ---
|
| And you have no idea what you should use at the location of the "__".
| You bring up GHCi, and load it as a module:
|
| $ ghci
| GHCi, version 7.5.20120126: http://www.haskell.org/ghc/ :? for help
| Loading package ghc-prim ... linking ... done.
| Loading package integer-gmp ... linking ... done.
| Loading package base ... linking ... done.
| Prelude> :load Foo.hs
| [1 of 1] Compiling Main ( Foo.hs, interpreted )
| Found a hole at Foo.hs:1:13-14: Integer -> Integer -> Integer
| ...
|
| You notice it needs a function, so you make some more changes and hit
| save, so Foo.hs now contains:
|
| ---
|
| foo = foldr (\x -> __) 0 [1..5]
|
| ---
|
| You reload GHCi, to see if you made progress:
|
| *Main> :r
| [1 of 1] Compiling Main ( Foo.hs, interpreted )
| Found a hole at Foo.hs:1:20-21: Integer -> Integer
| ...
|
| And that's it. It might help IDEs later on, but that is not our goal.
|
| Regards,
| Thijs Alkemade
More information about the Glasgow-haskell-users
mailing list