Request for feedback: deriving strategies syntax

Ryan Scott ryan.gl.scott at gmail.com
Thu Aug 4 13:08:29 UTC 2016


> I do not understand "not portable" here. Do you mean that some architectures don't support TH?

Template Haskell doesn't play nicely with cross compilation [1] or
stage-1 compilers, so Template Haskell is simply a non-starter for a
lot of uses. It's why the GHC codebase and boot libraries largely
don't use the -XTemplateHaskell extension (aside from the test suite,
of course).

> What staging issues?
>
> I'm imagining here having `deriving Blah` be surface syntax that desugars into some TH splice. You keep the nice user-facing syntax, but make the deriving mechanism itself specified in TH code.

That won't currently work with the way TH stages its splices. For
example, the following code:

    {-# LANGUAGE PackageImports, TemplateHaskell #-}

    import "deriving-compat" Data.Eq.Deriving

    bar :: Bar
    bar = Bar

    data Foo = Foo
    $(deriveEq ''Foo)

    data Bar = Bar
    $(deriveEq ''Bar)

will fail to compile because of the staging restrictions on Template
Haskell splices, whereas replacing the splices with `deriving Eq`
would make it compile.

> It's an interesting idea, but one probably best tackled after the current proposal.

Completely agreed. :)

Ryan S.
-----
[1] https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/CrossCompilation


More information about the ghc-devs mailing list