linear-generics-0.2: Generic programming library for generalised deriving.
Safe HaskellUnsafe
LanguageHaskell2010

Generics.Linear.Unsafe.ViaGHCGenerics

Description

DerivingVia targets to instantiate Generic and Generic1, both using GHC.Generics.Generic.

Caution

Synopsis

Documentation

newtype GHCGenerically a Source #

When a is an instance of GHC.Generics.Generic, GHCGenerically a is an instance of Generic.

Warnings

GHCGenerically is intended for use as a DerivingVia target. Most other uses of its Generic instance will be quite wrong.

GHCGenerically must not be used with datatypes that have nonlinear or linearity-polymorphic fields. Doing so will produce completely bogus results, breaking the linearity rules.

GHCGenerically is otherwise safe to use with derived GHC.Generics.Generic instances, which are linear. If you choose to use it with a hand-written instance, you should check that the underlying instance is linear.

Example

data Foo a = Bar a (Either Int a) | Baz (Maybe a) Int
  deriving stock (Show, GHC.Generics.Generic)
  deriving Generic via GHCGenerically (Foo a)

Constructors

GHCGenerically 

Fields

Instances

Instances details
Generic a => Generic (GHCGenerically a) Source # 
Instance details

Defined in Generics.Linear.Unsafe.ViaGHCGenerics

Associated Types

type Rep (GHCGenerically a) :: Type -> Type Source #

Methods

to :: forall p (m :: Multiplicity). Rep (GHCGenerically a) p %m -> GHCGenerically a Source #

from :: forall p (m :: Multiplicity). GHCGenerically a %m -> Rep (GHCGenerically a) p Source #

type Rep (GHCGenerically a) Source # 
Instance details

Defined in Generics.Linear.Unsafe.ViaGHCGenerics

type Rep (GHCGenerically a) = Rep a

newtype GHCGenerically1 f a Source #

When f a is an instance of GHC.Generics.Generic for all a, GHCGenerically1 f is an instance of Generic1.

Warning

GHCGenerically1 is intended for use as a DerivingVia target. Most other uses of its Generic1 instance will be quite wrong.

GHCGenerically1 must not be used with datatypes that have nonlinear or linearity-polymorphic fields. Doing so will produce completely bogus results, breaking the linearity rules.

GHCGenerically1 is otherwise safe to use with derived GHC.Generics.Generic instances, which are linear. If you choose to use it with a hand-written instance, you should check that the underlying instance is linear.

Example

data Foo a = Bar a (Either Int a) | Baz (Maybe a) Int
  deriving stock (Show, GHC.Generics.Generic)
  deriving Generic1 via GHCGenerically1 Foo

Constructors

GHCGenerically1 

Fields

Instances

Instances details
(forall (a :: k). Generic (f a)) => Generic1 (GHCGenerically1 f :: k -> Type) Source # 
Instance details

Defined in Generics.Linear.Unsafe.ViaGHCGenerics

Associated Types

type Rep1 (GHCGenerically1 f) :: k -> Type Source #

Methods

to1 :: forall (p :: k0) (m :: Multiplicity). Rep1 (GHCGenerically1 f) p %m -> GHCGenerically1 f p Source #

from1 :: forall (p :: k0) (m :: Multiplicity). GHCGenerically1 f p %m -> Rep1 (GHCGenerically1 f) p Source #

type Rep1 (GHCGenerically1 f :: k -> Type) Source # 
Instance details

Defined in Generics.Linear.Unsafe.ViaGHCGenerics

type Rep1 (GHCGenerically1 f :: k -> Type)