
Sorry, I forgot to reply-all earlier.
I hacked this up quickly just to show that it works in principle. In practice, I think it's good to not just represent Int# as Int, but as something like UInt where
data UInt = UInt Int#
i.e., is isomorphic to an Int, but distinguishable. Alternatively, have a generic "unboxed" flag that could be inserted as a tag into the surrounding K.
I suppose we'd have to decide which is easier for programmers to use.
Do we introduce UInt, UChar, et al. and require that users define
instances of the desired typeclass for them:
instance Lift UInt where
lift (UInt i) = litE (intPrimL (I# i))
or do we introduce an unboxed flag and require users to write generic
GLift instances using that flag:
instance GLift (K1 Unboxed Int) where
lift (K1 (Int i)) = litE (intPrimL (I# i))
The former has the advantage that you wouldn't need to change the
GLift code to distinguish between (K1 Unboxed Int) and (K1 R Int),
which might be a potential source of confusion for programmers. On the
other hand, having an Unboxed flag requires only introducing one new
data type, as opposed to a separate data type for each of the unlifted
types that we want to work over.
Ryan S.
On Tue, Sep 8, 2015 at 7:59 AM, Andres Loeh
I don't think there's any fundamental reason why unboxed fields prevent a Generic instance, as long as we're happy that unboxed values will be re-boxed in the generic representation. It simply seems as if nobody has thought of implementing this. As an example, consider the following hand-written example which works just fine:
{-# LANGUAGE MagicHash, KindSignatures, PolyKinds, TypeOperators, TypeFamilies #-} module GenUnboxed where
import GHC.Exts import GHC.Generics import Generics.Deriving.Eq
data UPair = UPair Int# Char#
instance Generic UPair where type Rep UPair = K1 R Int :*: K1 R Char from (UPair x y) = K1 (I# x) :*: K1 (C# y) to (K1 (I# x) :*: K1 (C# y)) = UPair x y
instance GEq UPair
test :: Bool test = let p = UPair 3# 'x'# in geq p p
Cheers, Andres
On Mon, Sep 7, 2015 at 10:02 PM, Ryan Scott
wrote: Unlifted types can't be used polymorphically or in instance declarations, so this makes it impossible to do something like
instance Generic Int#
or store an Int# in one branch of a (:*:), preventing generics from doing anything in #-land. (unless someone has found a way to hack around this).
I would be okay with implementing a generics-based approach, but we'd have to add a caveat that it will only work out-of-the-box on GHC 8.0 or later, due to TH's need to look up package information. (We could give users the ability to specify a package name manually as a workaround.)
If this were added, where would be the best place to put it? th-lift? generic-deriving? template-haskell? A new package (lift-generics)?
Ryan S.
On Mon, Sep 7, 2015 at 3:10 PM, Matthew Pickering
wrote: Continuing my support of the generics route. Is there a fundamental reason why it couldn't handle unlifted types? Given their relative paucity, it seems like a fair compromise to generically define lift instances for all normal data types but require TH for unlifted types. This approach seems much smoother from a maintenance perspective.
On Mon, Sep 7, 2015 at 5:26 PM, Ryan Scott
wrote: There is a Lift typeclass defined in template-haskell [1] which, when a data type is an instance, permits it to be directly used in a TH quotation, like so
data Example = Example
instance Lift Example where lift Example = conE (mkNameG_d "<package-name>" "<module-name>" "Example")
e :: Example e = [| Example |]
Making Lift instances for most data types is straightforward and mechanical, so the proposal is to allow automatic derivation of Lift via a -XDeriveLift extension:
data Example = Example deriving Lift
This is actually a pretty a pretty old proposal [2], dating back to 2007. I wanted to have this feature for my needs, so I submitted a proof-of-concept at the GHC Trac issue page [3].
The question now is: do we really want to bake this feature into GHC? Since not many people opined on the Trac page, I wanted to submit this here for wider visibility and to have a discussion.
Here are some arguments I have heard against this feature (please tell me if I am misrepresenting your opinion):
* We already have a th-lift package [4] on Hackage which allows derivation of Lift via Template Haskell functions. In addition, if you're using Lift, chances are you're also using the -XTemplateHaskell extension in the first place, so th-lift should be suitable. * The same functionality could be added via GHC generics (as of GHC 7.12/8.0, which adds the ability to reify a datatype's package name [5]), if -XTemplateHaskell can't be used. * Adding another -XDerive- extension places a burden on GHC devs to maintain it in the future in response to further Template Haskell changes.
Here are my (opinionated) responses to each of these:
* th-lift isn't as fully-featured as a -XDerive- extension at the moment, since it can't do sophisticated type inference [6] or derive for data families. This is something that could be addressed with a patch to th-lift, though. * GHC generics wouldn't be enough to handle unlifted types like Int#, Char#, or Double# (which other -XDerive- extensions do). * This is a subjective measurement, but in terms of the amount of code I had to add, -XDeriveLift was substantially simpler than other -XDerive extensions, because there are fewer weird corner cases. Plus, I'd volunteer to maintain it :)
Simon PJ wanted to know if other Template Haskell programmers would find -XDeriveLift useful. Would you be able to use it? Would you like to see a solution other than putting it into GHC? I'd love to hear feedback so we can bring some closure to this 8-year-old feature request.
Ryan S.
----- [1] http://hackage.haskell.org/package/template-haskell-2.10.0.0/docs/Language-H... [2] https://mail.haskell.org/pipermail/template-haskell/2007-October/000635.html [3] https://ghc.haskell.org/trac/ghc/ticket/1830 [4] http://hackage.haskell.org/package/th-lift [5] https://ghc.haskell.org/trac/ghc/ticket/10030 [6] https://ghc.haskell.org/trac/ghc/ticket/1830#comment:11 _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs