Getting the inferred types of TH's UnboundVarEs

Sandy Maguire sandy at sandymaguire.me
Thu Mar 19 17:31:10 UTC 2020


I'm also generating code at the same time, and might have gotten confused
by that interaction :)

In the meantime I guess I'll implement HM. The world will be a much better
place when TTG is finished and we have ghc-as-an-easy-to-use-library :)

On Thu, Mar 19, 2020 at 2:51 AM Richard Eisenberg <rae at richarde.dev> wrote:

> Good to see you around, Sandy!
>
> On Mar 18, 2020, at 6:54 PM, Sandy Maguire <sandy at sandymaguire.me> wrote:
>
> I mean if `insert :: a -> Container a -> Container a`, and I call it with
> `[e| insert 5 True |]`, the quote will fail.
>
>
> I don't observe this. Specifically, when I compile
>
> {-# LANGUAGE TemplateHaskellQuotes #-}
>
> module Bug where
>
> import Prelude ( Bool(..), undefined )
>
> data Container a
>
> insert :: a -> Container a -> Container a
> insert = undefined
>
> quote = [e| insert 5 True |]
>
>
> GHC happily succeeds.
>
> I think what you want, though, is reasonable: you want the ability to send
> an expression through GHC's type-checker. I think we'd need to extend TH to
> be able to support this, and it will be hard to come up with a good design,
> I think. (Specifically, I'm worried about interactions with top-level
> defined entities, whose types might not really be known by the time of
> splice processing.) This might all be worthwhile -- singletons would be
> able to be improved with this, for example -- but it's not cheap, sadly.
>
> Richard
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20200319/450eded1/attachment.html>


More information about the ghc-devs mailing list