Safe Haskell | None |
---|---|
Language | Haskell2010 |
Interop with standard GHC generics
Synopsis
- newtype ThroughLRGenerics a p = WrapThroughLRGenerics {}
- data GhcMetadata a = GhcMetadata {}
- data GhcFieldMetadata :: Type -> Type where
- GhcFieldMetadata :: forall (f :: Meta) (a :: Type). Selector f => Proxy f -> GhcFieldMetadata a
- ghcMetadata :: Generic a => proxy a -> GhcMetadata a
From GHC to LR generics
newtype ThroughLRGenerics a p Source #
Route from GHC generics to LR generics
Suppose a function such as
allEqualTo :: Eq a => a -> [a] -> Bool allEqualTo x = all (== x)
is instead written as
allEqualTo :: (GHC.Generic a, GHC.GEq' (GHC.Rep a)) => a -> [a] -> Bool allEqualTo x = all (GHC.geqdefault x)
where instead of using an indirection through an auxiliary type class Eq
,
it directly assumes GHC.Generics
and uses a concrete generic
implementation. Such design is arguably questionable, but for example
beam-core
contains many such deeply ingrained assumptions of the
availability of GHC.Generics
.
In order to be able to call such a function on a large record Foo
,
largeRecord
will generate an instance
instance GHC.Generic Foo where type Rep Foo = ThroughLRGenerics Foo from = WrapThroughLRGenerics to = unwrapThroughLRGenerics
For our running example, this instance makes it possible to call allEqualTo
provided we then provide an instance
instance ( LR.Generic a , LR.Constraints a Eq ) => GHC.GEq' (ThroughLRGenerics a) where geq' = LR.geq `on` unwrapThroughLRGenerics
Effectively, ThroughLRGenerics
can be used to redirect a function that uses
GHC generics to a function that uses LR generics.
GHC generics metadata
data GhcMetadata a Source #
GHC generics metadata
TODO: Currently we provide metadata only for the record fields, not the constructor or type name
data GhcFieldMetadata :: Type -> Type where Source #
GhcFieldMetadata :: forall (f :: Meta) (a :: Type). Selector f => Proxy f -> GhcFieldMetadata a |
ghcMetadata :: Generic a => proxy a -> GhcMetadata a Source #