generic-data-surgery-0.3.0.0: Surgery for generic data types

Safe HaskellNone
LanguageHaskell2010

Generic.Data.Surgery.Internal

Contents

Description

Operate on data types: insert/modify/delete fields and constructors.

Synopsis

Documentation

newtype OR (l :: k -> Type) (x :: k) Source #

A sterile Operating Room, where generic data comes to be altered.

Generic representation in a simplified shape l at the type level (reusing the constructors from GHC.Generics for convenience). This representation makes it easy to modify fields and constructors.

We may also refer to the representation l as a "row" of constructors, if it represents a sum type, otherwise it is a "row" of unnamed fields or record fields for single-constructor types.

x corresponds to the last parameter of Rep, and is currently ignored by this module (no support for Generic1).

General sketch

               toOR                       surgeries                    fromOR'
data MyType  -------->  OR (Rep MyType)  ---------->  OR alteredRep  --------->  Data alteredRep
                                                                                       |
                                                                                       | myGenericFun :: Generic a => a -> a
               fromOR                     surgeries                    toOR'           v
data MyType  <--------  OR (Rep MyType)  <----------  OR alteredRep  <---------  Data alteredRep

If instead myGenericFun is only a consumer of a (resp. producer), then you only need the top half of the diagram (resp. bottom half). For example, in aeson: genericToJSON (consumer), genericParseJSON (producer).

Constructors

OR 

Fields

toOR :: forall a l x. (Generic a, ToORRep a l) => a -> OR l x Source #

Move fresh data to the Operating Room, where surgeries can be applied.

Convert a generic type to a generic representation.

When inserting or removing fields, there may be a mismatch with strict/unpacked fields. To work around this, you can switch to toORLazy, if your operations don't care about dealing with a normalized Rep (in which all the strictness annotations have been replaced with lazy defaults).

Details

Expand

Type parameters

a :: Type       -- Generic type
l :: k -> Type  -- Generic representation (simplified)
x :: k          -- Ignored

Functional dependencies

a -> l

toORLazy :: forall a l x. (Generic a, ToORRepLazy a l) => a -> OR l x Source #

Move normalized data to the Operating Room, where surgeries can be applied.

Convert a generic type to a generic representation, in which all the strictness annotations have been normalized to lazy defaults.

This variant is useful when one needs to operate on fields whose Rep has different strictness annotations than the ones used by DefaultMetaSel.

Details

Expand

Type parameters

a :: Type       -- Generic type
l :: k -> Type  -- Generic representation (simplified and normalized)
x :: k          -- Ignored

Functional dependencies

a -> l

fromOR' :: forall f l x. FromOR f l => OR l x -> Data f x Source #

Move altered data out of the Operating Room, to be consumed by some generic function.

Convert a generic representation to a "synthetic" type that behaves like a generic type.

Details

Expand

Type parameters

f :: k -> Type  -- Generic representation (proper)
l :: k -> Type  -- Generic representation (simplified)
x :: k          -- Ignored

Functional dependencies

f -> l
l -> f

Implementation details

The synthesized representation is made of balanced binary trees, corresponding closely to what GHC would generate for an actual data type.

That structure assumed by at least one piece of code out there (aeson).

toOR' :: forall f l x. ToOR f l => Data f x -> OR l x Source #

Move altered data, produced by some generic function, to the operating room.

The inverse of fromOR'.

Details

Expand

Type parameters

f :: k -> Type  -- Generic representation (proper)
l :: k -> Type  -- Generic representation (simplified)
x :: k          -- Ignored

Functional dependencies

f -> l
l -> f

fromOR :: forall a l x. (Generic a, FromORRep a l) => OR l x -> a Source #

Move restored data out of the Operating Room and back to the real world.

The inverse of toOR.

It may be useful to annotate the output type of fromOR, since the rest of the type depends on it and the only way to infer it otherwise is from the context. The following annotations are possible:

fromOR :: OROf a -> a
fromOR @a  -- with TypeApplications

When inserting or removing fields, there may be a mismatch with strict/unpacked fields. To work around this, you can switch to fromORLazy, if your operations don't care about dealing with a normalized Rep (in which all the strictness annotations have been replaced with lazy defaults).

Details

Expand

Type parameters

a :: Type       -- Generic type
l :: k -> Type  -- Generic representation (simplified)
x :: k          -- Ignored

Functional dependencies

a -> l

fromORLazy :: forall a l x. (Generic a, FromORRepLazy a l) => OR l x -> a Source #

Move normalized data out of the Operating Room and back to the real world.

The inverse of toORLazy.

It may be useful to annotate the output type of fromORLazy, since the rest of the type depends on it and the only way to infer it otherwise is from the context. The following annotations are possible:

fromORLazy :: OROfLazy a -> a
fromORLazy @a  -- with TypeApplications

Details

Expand

Type parameters

a :: Type       -- Generic type
l :: k -> Type  -- Generic representation (simplified and normalized)
x :: k          -- Ignored

Functional dependencies

a -> l

type OROf a = OR (Linearize (Rep a)) () Source #

The simplified generic representation type of type a, that toOR and fromOR convert to and from.

type OROfLazy a = OR (Linearize (Lazify (Rep a))) () Source #

The simplified and normalized generic representation type of type a, that toORLazy and fromORLazy convert to and from.

type ToORRep a l = ToOR (Rep a) l Source #

This constraint means that a is convertible to its simplified generic representation. Implies OROf a ~ OR l ().

type FromORRep a l = FromOR (Rep a) l Source #

This constraint means that a is convertible from its simplified generic representation. Implies OROf a ~ OR l ().

type ToOR f l = (GLinearize f, Linearize f ~ l, f ~ Arborify l) Source #

Similar to ToORRep, but as a constraint on the standard generic representation of a directly, f ~ Rep a.

type FromOR f l = (GArborify f, Linearize f ~ l, f ~ Arborify l) Source #

Similar to FromORRep, but as a constraint on the standard generic representation of a directly, f ~ Rep a.

type ToORRepLazy a l = ToORLazy (Rep a) l Source #

This constraint means that a is convertible to its simplified and normalized generic representation (i.e., with all its strictness annotations normalized to lazy defaults). Implies OROfLazy a ~ OR l ().

type FromORRepLazy a l = FromORLazy (Rep a) l Source #

This constraint means that a is convertible from its simplified and normalized generic representation (i.e., with all its strictness annotations normalized to lazy defaults). Implies OROfLazy a ~ OR l ().

type FromORLazy f l = (FromOR (Lazify f) l, Coercible (Arborify l) f) Source #

Similar to FromLazyORRep, but as a constraint on the standard generic representation of a directly, f ~ Rep a.

type ToORLazy f l = (ToOR (Lazify f) l, Coercible f (Arborify l)) Source #

Similar to ToORRepLazy, but as a constraint on the standard generic representation of a directly, f ~ Rep a.

removeCField :: forall n t lt l x. RmvCField n t lt l => OR lt x -> (t, OR l x) Source #

removeCField @n @t: remove the n-th field, of type t, in a non-record single-constructor type.

Inverse of insertCField.

Details

Expand

Type parameters

n  :: Nat        -- Field position
t  :: Type       -- Field type
lt :: k -> Type  -- Row with    field
l  :: k -> Type  -- Row without field
x  :: k          -- Ignored

Signature

OR lt x      -- Data with field
->
(t, OR l x)  -- Field value × Data without field

Functional dependencies

n lt  -> t l
n t l -> lt

removeRField :: forall fd n t lt l x. RmvRField fd n t lt l => OR lt x -> (t, OR l x) Source #

removeRField @"fdName" @n @t: remove the field fdName at position n of type t in a record type.

Inverse of insertRField.

Details

Expand

Type parameters

fd :: Symbol     -- Field name
n  :: Nat        -- Field position
t  :: Type       -- Field type
lt :: k -> Type  -- Row with    field
l  :: k -> Type  -- Row without field
x  :: k          -- Ignored

Signature

OR lt x      -- Data with field
->
(t, OR l x)  -- Field value × Data without field

Functional dependencies

fd lt    -> n  t l
n  lt    -> fd t l
fd n t l -> lt

insertCField :: forall n t lt l x. InsCField n t lt l => (t, OR l x) -> OR lt x Source #

insertCField @n @t: insert a field of type t at position n in a non-record single-constructor type.

Inverse of removeCField.

Details

Expand

Type parameters

n  :: Nat        -- Field position
t  :: Type       -- Field type
lt :: k -> Type  -- Row with    field
l  :: k -> Type  -- Row without field
x  :: k          -- Ignored

Signature

(t, OR l x)  -- Field value × Data without field
->
OR lt x      -- Data with field

Functional dependencies

n lt  -> t l
n t l -> lt

insertCField' :: forall n t lt l x. InsCField n t lt l => t -> OR l x -> OR lt x Source #

Curried insertCField.

insertRField :: forall fd n t lt l x. InsRField fd n t lt l => (t, OR l x) -> OR lt x Source #

insertRField @"fdName" @n @t: insert a field named fdName of type t at position n in a record type.

Inverse of removeRField.

Details

Expand

Type parameters

fd :: Symbol     -- Field name
n  :: Nat        -- Field position
t  :: Type       -- Field type
lt :: k -> Type  -- Row with    field
l  :: k -> Type  -- Row without field
x  :: k          -- Ignored

Signature

(t, OR l x)  -- Field value × Data without field
->
OR lt x      -- Data with field

Functional dependencies

fd lt    -> n  t l
n  lt    -> fd t l
fd n t l -> lt

insertRField' :: forall fd n t lt l x. InsRField fd n t lt l => t -> OR l x -> OR lt x Source #

Curried insertRField.

modifyCField :: forall n t t' lt lt' l x. ModCField n t t' lt lt' l => (t -> t') -> OR lt x -> OR lt' x Source #

modifyCField @n @t @t': modify the field at position n in a non-record via a function f :: t -> t' (changing the type of the field).

Details

Expand

Type parameters

n   :: Nat        -- Field position
t   :: Type       -- Initial field type
t'  :: Type       -- Final   field type
lt  :: k -> Type  -- Row with initial field
lt' :: k -> Type  -- Row with final   field
l   :: k -> Type  -- Row without field
x   :: k          -- Ignored

Signature

(t -> t')  -- Field modification
->
OR lt  x   -- Data with field t
->
OR lt' x   -- Data with field t'

Functional dependencies

n lt   -> t  l
n lt'  -> t' l
n t  l -> lt
n t' l -> lt'

modifyRField :: forall fd n t t' lt lt' l x. ModRField fd n t t' lt lt' l => (t -> t') -> OR lt x -> OR lt' x Source #

modifyRField @"fdName" @n @t @t': modify the field fdName at position n in a record via a function f :: t -> t' (changing the type of the field).

Details

Expand

Type parameters

fd  :: Symbol     -- Field name
n   :: Nat        -- Field position
t   :: Type       -- Initial field type
t'  :: Type       -- Final   field type
lt  :: k -> Type  -- Row with initial field
lt' :: k -> Type  -- Row with final   field
l   :: k -> Type  -- Row without field
x   :: k          -- Ignored

Signature

(t -> t')  -- Field modification
->
OR lt  x   -- Data with field t
->
OR lt' x   -- Data with field t'

Functional dependencies

fd lt     -> n  t  l
fd lt'    -> n  t' l
n  lt     -> fd t  l
n  lt'    -> fd t' l
fd n t  l -> lt
fd n t' l -> lt'

removeConstr :: forall c n t lc l x. RmvConstr c n t lc l => OR lc x -> Either t (OR l x) Source #

removeConstr @"C" @n @t: remove the n-th constructor, named C, with contents isomorphic to the tuple t.

Inverse of insertConstr.

Details

Expand

Type parameters

c   :: Symbol     -- Constructor name
t   :: Type       -- Tuple type to hold c's contents
n   :: Nat        -- Constructor position
lc  :: k -> Type  -- Row with    constructor
l   :: k -> Type  -- Row without constructor
l_t :: k -> Type  -- Field row of constructor c
x   :: k          -- Ignored

Signature

OR lc x            -- Data with constructor
->
Either t (OR l x)  -- Constructor (as a tuple) | Data without constructor

Functional dependencies

c lc      -> n l l_t
n lc      -> c l l_t
c n l l_t -> lc

Note that there is no dependency to determine t.

removeConstrT :: forall c n t lc l x. RmvConstrT c n t lc l => OR lc x -> Either t (OR l x) Source #

A variant of removeConstr that can infer the tuple type t to hold the contents of the removed constructor.

See removeConstr.

Details

Expand

Extra functional dependency

l_t -> t

insertConstr :: forall c n t lc l x. InsConstr c n t lc l => Either t (OR l x) -> OR lc x Source #

insertConstr @"C" @n @t: insert a constructor C at position n with contents isomorphic to the tuple t.

Inverse of removeConstr.

Details

Expand

Type parameters

c   :: Symbol     -- Constructor name
t   :: Type       -- Tuple type to hold c's contents
n   :: Nat        -- Constructor position
lc  :: k -> Type  -- Row with    constructor
l   :: k -> Type  -- Row without constructor
l_t :: k -> Type  -- Field row of constructor c
x   :: k          -- Ignored

Signature

Either t (OR l x)  -- Constructor (as a tuple) | Data without constructor
->
OR lc x            -- Data with constructor

Functional dependencies

c lc      -> n l l_t
n lc      -> c l l_t
c n l l_t -> lc

Note that there is no dependency to determine t.

insertConstrT :: forall c n t lc l x. InsConstrT c n t lc l => Either t (OR l x) -> OR lc x Source #

A variant of insertConstr that can infer the tuple type t to hold the contents of the inserted constructor.

See insertConstr.

Details

Expand

Extra functional dependency

l_t -> t

modifyConstr :: forall c n t t' lc lc' l x. ModConstr c n t t' lc lc' l => (t -> t') -> OR lc x -> OR lc' x Source #

modifyConstr @"C" @n @t @t': modify the n-th constructor, named C, with contents isomorphic to the tuple t, to another tuple t'.

Details

Expand

Type parameters

c    :: Symbol     -- Constructor name
t    :: Type       -- Tuple type to hold c's initial contents
t'   :: Type       -- Tuple type to hold c's final   contents
n    :: Nat        -- Constructor position
lc   :: k -> Type  -- Row with initial constructor
lc'  :: k -> Type  -- Row with final   constructor
l    :: k -> Type  -- Row without constructor
l_t  :: k -> Type  -- Initial field row of constructor c
l_t' :: k -> Type  -- Final   field row of constructor c
x    :: k          -- Ignored

Signature

(t -> t')  -- Constructor modification
->
OR lc  x   -- Data with initial constructor
->
OR lc' x   -- Data with final   constructor

Functional dependencies

c lc       -> n l l_t
c lc'      -> n l l_t'
n lc       -> c l l_t
n lc'      -> c l l_t'
c n l l_t  -> lc
c n l l_t' -> lc'

Note that there is no dependency to determine t and t'.

modifyConstrT :: forall c n t t' lc lc' l x. ModConstrT c n t t' lc lc' l => (t -> t') -> OR lc x -> OR lc' x Source #

A variant of modifyConstr that can infer the tuple types t and t' to hold the contents of the inserted constructor.

See modifyConstr.

Details

Expand

Extra functional dependencies

l_t  -> t
l_t' -> t'

type RmvCField n t lt l = (GRemoveField n t lt l, CFieldSurgery n t lt l) Source #

This constraint means that the (unnamed) field row lt contains a field of type t at position n, and removing it yields row l.

type RmvRField fd n t lt l = (GRemoveField n t lt l, RFieldSurgery fd n t lt l) Source #

This constraint means that the record field row lt contains a field of type t named fd at position n, and removing it yields row l.

type InsCField n t lt l = (GInsertField n t l lt, CFieldSurgery n t lt l) Source #

This constraint means that inserting a field t at position n in the (unnamed) field row l yields row lt.

type InsRField fd n t lt l = (GInsertField n t l lt, RFieldSurgery fd n t lt l) Source #

This constraint means that inserting a field t named fd at position n in the record field row l yields row lt.

type ModCField n t t' lt lt' l = (RmvCField n t lt l, InsCField n t' lt' l) Source #

This constraint means that modifying a field t to t' at position n in the (unnamed) field row lt yields row lt'. l is the row of fields common to lt and lt'.

type ModRField fd n t t' lt lt' l = (RmvRField fd n t lt l, InsRField fd n t' lt' l) Source #

This constraint means that modifying a field t named fd at position n to t' in the record field row lt yields row lt'. l is the row of fields common to lt and lt'.

type RmvConstr c n t lc l = (GRemoveConstr n t lc l, ConstrSurgery c n t lc l (Eval (ConstrAt n lc))) Source #

This constraint means that the constructor row lc contains a constructor named c at position n, and removing it from lc yields row l. Furthermore, constructor c contains a field row l_t compatible with the tuple type t.

type RmvConstrT c n t lc l = (RmvConstr c n t lc l, IsTuple (Arity (Eval (ConstrAt n lc))) t) Source #

A variant of RmvConstr allowing t to be inferred.

type InsConstr c n (t :: Type) lc l = (GInsertConstr n t l lc, ConstrSurgery c n t lc l (Eval (ConstrAt n lc))) Source #

This constraint means that inserting a constructor c at position n in the constructor row l yields row lc. Furthermore, constructor c contains a field row l_t compatible with the tuple type t.

type InsConstrT c n t lc l = (InsConstr c n t lc l, IsTuple (Arity (Eval (ConstrAt n lc))) t) Source #

A variant of InsConstr allowing t to be inferred.

type ModConstr c n t t' lc lc' l = (RmvConstr c n t lc l, InsConstr c n t' lc' l) Source #

This constraint means that the constructor row lc contains a constructor named c at position n of type isomorphic to t, and modifying it to t' yields row lc'.

type ModConstrT c n t t' lc lc' l = (ModConstr c n t t' lc lc' l, IsTuple (Arity (Eval (ConstrAt n lc))) t, IsTuple (Arity (Eval (ConstrAt n lc'))) t') Source #

A variant of ModConstr allowing t and t' to be inferred.

type FieldSurgery n t lt l = (t ~ Eval (FieldTypeAt n lt), l ~ Eval (RemoveField n t lt)) Source #

type CFieldSurgery n t lt l = (lt ~ Eval (InsertField n Nothing t l), FieldSurgery n t lt l) Source #

type RFieldSurgery fd n t lt l = (n ~ Eval (FieldIndex fd lt), lt ~ Eval (InsertField n (Just fd) t l), FieldSurgery n t lt l) Source #

type ConstrSurgery c n t lc l l_t = (Generic t, MatchFields (Linearize (UnM1 (Rep t))) l_t, n ~ Eval (ConstrIndex c lc), c ~ MetaConsName (MetaOf l_t), lc ~ Eval (InsertUConstrAtL n l_t l), l ~ Eval (RemoveUConstrAt_ n lc)) Source #

type family Linearize (f :: k -> Type) :: k -> Type Source #

Instances
type Linearize (M1 D m f :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Linearize (M1 D m f :: k -> Type) = M1 D m (LinearizeSum f (V1 :: k -> Type))
type Linearize (M1 C m f :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Linearize (M1 C m f :: k -> Type) = M1 C m (LinearizeProduct f (U1 :: k -> Type))

type family LinearizeSum (f :: k -> Type) (tl :: k -> Type) :: k -> Type Source #

Instances
type LinearizeSum (V1 :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type LinearizeSum (V1 :: k -> Type) (tl :: k -> Type) = tl
type LinearizeSum (f :+: g :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type LinearizeSum (f :+: g :: k -> Type) (tl :: k -> Type) = LinearizeSum f (LinearizeSum g tl)
type LinearizeSum (M1 c m f :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type LinearizeSum (M1 c m f :: k -> Type) (tl :: k -> Type) = M1 c m (LinearizeProduct f (U1 :: k -> Type)) :+: tl

type family LinearizeProduct (f :: k -> Type) (tl :: k -> Type) :: k -> Type Source #

Instances
type LinearizeProduct (U1 :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type LinearizeProduct (U1 :: k -> Type) (tl :: k -> Type) = tl
type LinearizeProduct (f :*: g :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type LinearizeProduct (f :*: g :: k -> Type) (tl :: k -> Type) = LinearizeProduct f (LinearizeProduct g tl)
type LinearizeProduct (M1 s m f :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type LinearizeProduct (M1 s m f :: k -> Type) (tl :: k -> Type) = M1 s m f :*: tl

class GLinearize f where Source #

Methods

gLinearize :: f x -> Linearize f x Source #

Instances
GLinearizeSum f (V1 :: k -> Type) => GLinearize (M1 D m f :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gLinearize :: M1 D m f x -> Linearize (M1 D m f) x Source #

GLinearizeProduct f (U1 :: k -> Type) => GLinearize (M1 C m f :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gLinearize :: M1 C m f x -> Linearize (M1 C m f) x Source #

class GLinearizeSum f tl where Source #

Methods

gLinearizeSum :: Either (f x) (tl x) -> LinearizeSum f tl x Source #

Instances
GLinearizeSum (V1 :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gLinearizeSum :: Either (V1 x) (tl x) -> LinearizeSum V1 tl x Source #

(GLinearizeSum g tl, GLinearizeSum f (LinearizeSum g tl)) => GLinearizeSum (f :+: g :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gLinearizeSum :: Either ((f :+: g) x) (tl x) -> LinearizeSum (f :+: g) tl x Source #

GLinearizeProduct f (U1 :: k -> Type) => GLinearizeSum (M1 c m f :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gLinearizeSum :: Either (M1 c m f x) (tl x) -> LinearizeSum (M1 c m f) tl x Source #

class GLinearizeProduct f tl where Source #

Methods

gLinearizeProduct :: f x -> tl x -> LinearizeProduct f tl x Source #

Instances
GLinearizeProduct (U1 :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gLinearizeProduct :: U1 x -> tl x -> LinearizeProduct U1 tl x Source #

(GLinearizeProduct g tl, GLinearizeProduct f (LinearizeProduct g tl)) => GLinearizeProduct (f :*: g :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gLinearizeProduct :: (f :*: g) x -> tl x -> LinearizeProduct (f :*: g) tl x Source #

GLinearizeProduct (M1 s m f :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gLinearizeProduct :: M1 s m f x -> tl x -> LinearizeProduct (M1 s m f) tl x Source #

class GArborify f where Source #

Methods

gArborify :: Linearize f x -> f x Source #

Instances
GArborifySum f (V1 :: k -> Type) => GArborify (M1 D m f :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gArborify :: Linearize (M1 D m f) x -> M1 D m f x Source #

GArborifyProduct f (U1 :: k -> Type) => GArborify (M1 C m f :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gArborify :: Linearize (M1 C m f) x -> M1 C m f x Source #

class GArborifySum f tl where Source #

Methods

gArborifySum :: LinearizeSum f tl x -> Either (f x) (tl x) Source #

Instances
GArborifySum (V1 :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gArborifySum :: LinearizeSum V1 tl x -> Either (V1 x) (tl x) Source #

(GArborifySum g tl, GArborifySum f (LinearizeSum g tl)) => GArborifySum (f :+: g :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gArborifySum :: LinearizeSum (f :+: g) tl x -> Either ((f :+: g) x) (tl x) Source #

GArborifyProduct f (U1 :: k -> Type) => GArborifySum (M1 c m f :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gArborifySum :: LinearizeSum (M1 c m f) tl x -> Either (M1 c m f x) (tl x) Source #

class GArborifyProduct f tl where Source #

Methods

gArborifyProduct :: LinearizeProduct f tl x -> (f x, tl x) Source #

Instances
GArborifyProduct (U1 :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gArborifyProduct :: LinearizeProduct U1 tl x -> (U1 x, tl x) Source #

(GArborifyProduct g tl, GArborifyProduct f (LinearizeProduct g tl)) => GArborifyProduct (f :*: g :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gArborifyProduct :: LinearizeProduct (f :*: g) tl x -> ((f :*: g) x, tl x) Source #

GArborifyProduct (M1 s m f :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gArborifyProduct :: LinearizeProduct (M1 s m f) tl x -> (M1 s m f x, tl x) Source #

type family Arborify (f :: k -> Type) :: k -> Type Source #

Instances
type Arborify (M1 C m f :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Arborify (M1 C m f :: k -> Type) = M1 C m (Eval (ArborifyProduct (Arity f) f))
type Arborify (M1 D m f :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Arborify (M1 D m f :: k -> Type) = M1 D m (Eval (ArborifySum (CoArity f) f))

data ArborifySum (n :: Nat) (f :: k -> Type) :: Exp (k -> Type) Source #

Instances
type Eval (ArborifySum n (V1 :: k -> Type) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (ArborifySum n (V1 :: k -> Type) :: (k -> Type) -> Type) = (V1 :: k -> Type)
type Eval (ArborifySum n (f :+: g) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (ArborifySum n (f :+: g) :: (k -> Type) -> Type) = Eval (If (n == 1) (ArborifyProduct (Arity f) f) (Arborify' (ArborifySum :: Nat -> (k -> Type) -> (k -> Type) -> Type) ((:+:) :: (k -> Type) -> (k -> Type) -> k -> Type) n (Div n 2) f g))

data ArborifyProduct (n :: Nat) (f :: k -> Type) :: Exp (k -> Type) Source #

Instances
type Eval (ArborifyProduct n (U1 :: k -> Type) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (ArborifyProduct n (U1 :: k -> Type) :: (k -> Type) -> Type) = (U1 :: k -> Type)
type Eval (ArborifyProduct n (M1 C s f) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (ArborifyProduct n (M1 C s f) :: (k -> Type) -> Type) = M1 C s (Eval (ArborifyProduct n f))
type Eval (ArborifyProduct n (f :*: g) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (ArborifyProduct n (f :*: g) :: (k -> Type) -> Type) = Eval (If (n == 1) (Pure f) (Arborify' (ArborifyProduct :: Nat -> (k -> Type) -> (k -> Type) -> Type) ((:*:) :: (k -> Type) -> (k -> Type) -> k -> Type) n (Div n 2) f g))

type Arborify' arb op n nDiv2 f g = (Uncurry (Pure2 op) <=< (Bimap (arb nDiv2) (arb (n - nDiv2)) <=< SplitAt nDiv2)) (op f g) Source #

type family Lazify (f :: k -> Type) :: k -> Type Source #

Instances
type Lazify (V1 :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Lazify (V1 :: k -> Type) = (V1 :: k -> Type)
type Lazify (U1 :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Lazify (U1 :: k -> Type) = (U1 :: k -> Type)
type Lazify (K1 i c :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Lazify (K1 i c :: k -> Type) = (K1 i c :: k -> Type)
type Lazify (f :+: g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Lazify (f :+: g :: k -> Type) = Lazify f :+: Lazify g
type Lazify (f :*: g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Lazify (f :*: g :: k -> Type) = Lazify f :*: Lazify g
type Lazify (M1 i m f :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Lazify (M1 i m f :: k -> Type) = M1 i (LazifyMeta m) (Lazify f)

type family LazifyMeta (m :: Meta) :: Meta Source #

Instances
type LazifyMeta (MetaCons n f s) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type LazifyMeta (MetaCons n f s) = MetaCons n f s
type LazifyMeta (MetaData n m p nt) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type LazifyMeta (MetaData n m p nt) = MetaData n m p nt
type LazifyMeta (MetaSel mn su ss ds) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

data SplitAt :: Nat -> (k -> Type) -> Exp (k -> Type, k -> Type) Source #

Instances
type Eval (SplitAt n (f :*: g) :: (k -> Type, k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (SplitAt n (f :*: g) :: (k -> Type, k -> Type) -> Type) = Eval (If (n == 0) (Pure ((,) (U1 :: k -> Type) (f :*: g))) ((Bimap (Pure2 ((:*:) :: (k -> Type) -> (k -> Type) -> k -> Type) f) (Pure :: (k -> Type) -> (k -> Type) -> Type) :: (k -> Type, k -> Type) -> (k -> Type, k -> Type) -> Type) =<< SplitAt (n - 1) g))
type Eval (SplitAt n (f :+: g) :: (k -> Type, k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (SplitAt n (f :+: g) :: (k -> Type, k -> Type) -> Type) = Eval (If (n == 0) (Pure ((,) (V1 :: k -> Type) (f :+: g))) ((Bimap (Pure2 ((:+:) :: (k -> Type) -> (k -> Type) -> k -> Type) f) (Pure :: (k -> Type) -> (k -> Type) -> Type) :: (k -> Type, k -> Type) -> (k -> Type, k -> Type) -> Type) =<< SplitAt (n - 1) g))

Surgeries

type MajorSurgery k = MajorSurgery_ k Source #

Kind of surgeries: operations on generic representations of types.

Treat this as an abstract kind (don't pay attention to its definition).

Implementation details

Expand

The name Surgery got taken first by generic-data.

k is the kind of the extra parameter reserved for Generic1, which we just don't use.

type Operate (f :: k -> Type) (s :: MajorSurgery k) = Operate_ f s Source #

Operate f s. Apply a surgery s to a generic representation f (e.g., f = Rep a for some Generic type a).

The first argument is the generic representation; the second argument is the surgery, which typically has the more complex syntax, which is why this reverse application order was chosen.

type MajorSurgery_ k = (k -> Type) -> Exp (k -> Type) Source #

Internal definition of MajorSurgery.

type Operate_ (f :: k -> Type) (s :: MajorSurgery k) = Arborify (OperateL (Linearize f) s) Source #

Internal definition of Operate.

type OperateL (l :: k -> Type) (s :: MajorSurgery k) = Eval (s l) Source #

Apply a surgery s to a linearized generic representation l.

data (:>>) :: MajorSurgery k -> MajorSurgery k -> MajorSurgery k infixl 1 Source #

Composition of surgeries (left-to-right).

Note

Surgeries work on normalized representations, so Operate, which applies a surgery to a generic representation, inserts normalization steps before and after the surgery. This means that Operate r (s1 :>> s2) is not quite the same as Operate (Operate r s1) s2. Instead, the latter is equivalent to Operate r (s1 :>> Suture :>> s2), where Suture inserts some intermediate normalization steps.

Instances
type PerformL (l :: k -> Type) (s :>> t :: (k -> Type) -> (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type PerformL (l :: k -> Type) (s :>> t :: (k -> Type) -> (k -> Type) -> Type) = (PerformL l s, PerformL (Eval (s l)) t)
type Eval ((s :>> t) l :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval ((s :>> t) l :: (k -> Type) -> Type) = Eval (t (Eval (s l)))

data IdSurgery :: MajorSurgery k Source #

The identity surgery: doesn't do anything.

Instances
type PerformL (l :: k -> Type) (IdSurgery :: (k -> Type) -> (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type PerformL (l :: k -> Type) (IdSurgery :: (k -> Type) -> (k -> Type) -> Type) = ()
type Eval (IdSurgery l :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (IdSurgery l :: (k -> Type) -> Type) = l

data Suture :: MajorSurgery k Source #

Use this if a patient ever needs to go out and back into the operating room, when it's not just to undo the surgery up to that point.

Instances
type Eval (Suture l :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (Suture l :: (k -> Type) -> Type) = Linearize (Arborify l)

type family PerformL (l :: k -> Type) (s :: MajorSurgery k) :: Constraint Source #

Instances
type PerformL (l :: k -> Type) (IdSurgery :: (k -> Type) -> (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type PerformL (l :: k -> Type) (IdSurgery :: (k -> Type) -> (k -> Type) -> Type) = ()
type PerformL (l :: k -> Type) (s :>> t :: (k -> Type) -> (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type PerformL (l :: k -> Type) (s :>> t :: (k -> Type) -> (k -> Type) -> Type) = (PerformL l s, PerformL (Eval (s l)) t)
type PerformL (lt :: k -> Type) (RemoveField n a :: (k -> Type) -> (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type PerformL (lt :: k -> Type) (RemoveField n a :: (k -> Type) -> (k -> Type) -> Type) = PerformL lt (RemoveFieldAt n ((FieldNameAt n :: (k -> Type) -> Maybe Symbol -> Type) @@ lt) a :: (k -> Type) -> (k -> Type) -> Type)
type PerformL (lt :: k -> Type) (RemoveRField fd a :: (k -> Type) -> (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type PerformL (lt :: k -> Type) (RemoveRField fd a :: (k -> Type) -> (k -> Type) -> Type) = PerformL lt (RemoveFieldAt ((FieldIndex fd :: (k -> Type) -> Nat -> Type) @@ lt) (Just fd) a :: (k -> Type) -> (k -> Type) -> Type)
type PerformL (lt :: k -> Type) (RemoveFieldAt n fd a :: (k -> Type) -> (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type PerformL (lt :: k -> Type) (RemoveFieldAt n fd a :: (k -> Type) -> (k -> Type) -> Type) = PerformLRemoveFieldAt n fd a lt (Eval (RemoveField_ n lt))
type PerformL (l :: k -> Type) (InsertField n fd t :: (k -> Type) -> (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type PerformL (l :: k -> Type) (InsertField n fd t :: (k -> Type) -> (k -> Type) -> Type) = PerformLInsert n fd t l (Eval (InsertField n fd t l))
type PerformL (lc :: Type -> Type) (RemoveConstr c t :: (Type -> Type) -> (Type -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type PerformL (lc :: Type -> Type) (RemoveConstr c t :: (Type -> Type) -> (Type -> Type) -> Type) = PerformLRemoveConstr lc c ((ConstrIndex c :: (Type -> Type) -> Nat -> Type) @@ lc) t
type PerformL (l :: Type -> Type) (InsertConstrAt c n t :: (Type -> Type) -> (Type -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type PerformL (l :: Type -> Type) (InsertConstrAt c n t :: (Type -> Type) -> (Type -> Type) -> Type) = PerformLInsertConstrAt0 l c n t

class Perform_ r s => Perform (r :: k -> Type) (s :: MajorSurgery k) Source #

A constraint Perform r s means that the surgery s can be applied to the generic representation r.

Instances
Perform_ r s => Perform (r :: k -> Type) (s :: MajorSurgery k) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Perform_ (r :: k -> Type) (s :: MajorSurgery k) = (PerformL (Linearize r) s, ToOR r (Linearize r), FromOR (Operate r s) (OperateL (Linearize r) s)) Source #

data FieldTypeAt (n :: Nat) (f :: k -> Type) :: Exp Type Source #

Instances
type Eval (FieldTypeAt n (f :+: (V1 :: k -> Type)) :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (FieldTypeAt n (f :+: (V1 :: k -> Type)) :: Type -> Type) = Eval (FieldTypeAt n f)
type Eval (FieldTypeAt n (M1 i c f) :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (FieldTypeAt n (M1 i c f) :: Type -> Type) = Eval (FieldTypeAt n f)
type Eval (FieldTypeAt n (f :*: g) :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (FieldTypeAt n (f :*: g) :: Type -> Type) = Eval (If (n == 0) (Pure (FieldTypeOf f)) (FieldTypeAt (n - 1) g))

type family FieldTypeOf (f :: k -> Type) :: Type Source #

Instances
type FieldTypeOf (M1 s m (K1 i a :: k -> Type) :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type FieldTypeOf (M1 s m (K1 i a :: k -> Type) :: k -> Type) = a

data FieldNameAt (n :: Nat) (f :: k -> Type) :: Exp (Maybe Symbol) Source #

Instances
type Eval (FieldNameAt n (f :+: (V1 :: k -> Type)) :: Maybe Symbol -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (FieldNameAt n (f :+: (V1 :: k -> Type)) :: Maybe Symbol -> Type) = Eval (FieldNameAt n f)
type Eval (FieldNameAt n (M1 i c f) :: Maybe Symbol -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (FieldNameAt n (M1 i c f) :: Maybe Symbol -> Type) = Eval (FieldNameAt n f)
type Eval (FieldNameAt n (f :*: g) :: Maybe Symbol -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (FieldNameAt n (f :*: g) :: Maybe Symbol -> Type) = Eval (If (n == 0) (FieldNameOf f) (FieldNameAt (n - 1) g))

data FieldNameOf (f :: k -> Type) :: Exp (Maybe Symbol) Source #

Instances
type Eval (FieldNameOf (M1 S (MetaSel mn _1 _2 _3) _4) :: Maybe Symbol -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (FieldNameOf (M1 S (MetaSel mn _1 _2 _3) _4) :: Maybe Symbol -> Type) = mn

data RemoveField (n :: Nat) (a :: Type) :: MajorSurgery k Source #

Instances
type PerformL (lt :: k -> Type) (RemoveField n a :: (k -> Type) -> (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type PerformL (lt :: k -> Type) (RemoveField n a :: (k -> Type) -> (k -> Type) -> Type) = PerformL lt (RemoveFieldAt n ((FieldNameAt n :: (k -> Type) -> Maybe Symbol -> Type) @@ lt) a :: (k -> Type) -> (k -> Type) -> Type)
type Eval (RemoveField n a f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (RemoveField n a f :: (k -> Type) -> Type) = Eval (RemoveField_ n f)

data RemoveField_ (n :: Nat) :: MajorSurgery k Source #

Like RemoveField but without the explicit field type.

Instances
type Eval (RemoveField_ n (f :*: g) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (RemoveField_ n (f :*: g) :: (k -> Type) -> Type) = Eval (If (n == 0) (Pure g) ((:*:) f <$> RemoveField_ (n - 1) g))
type Eval (RemoveField_ n (f :+: (V1 :: k -> Type)) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (RemoveField_ n (f :+: (V1 :: k -> Type)) :: (k -> Type) -> Type) = Eval (RemoveField_ n f) :+: (V1 :: k -> Type)
type Eval (RemoveField_ n (M1 i m f) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (RemoveField_ n (M1 i m f) :: (k -> Type) -> Type) = M1 i m (Eval (RemoveField_ n f))

data RemoveFieldAt (n :: Nat) (fd :: Maybe Symbol) (a :: Type) :: MajorSurgery k Source #

Instances
type PerformL (lt :: k -> Type) (RemoveFieldAt n fd a :: (k -> Type) -> (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type PerformL (lt :: k -> Type) (RemoveFieldAt n fd a :: (k -> Type) -> (k -> Type) -> Type) = PerformLRemoveFieldAt n fd a lt (Eval (RemoveField_ n lt))

type PerformLRemoveFieldAt_ n fd t lt l = (GRemoveField n t lt l, t ~ Eval (FieldTypeAt n lt), lt ~ Eval (InsertField n fd t l)) Source #

class PerformLRemoveFieldAt_ n fd t lt l => PerformLRemoveFieldAt n fd t lt l Source #

Instances
PerformLRemoveFieldAt_ n fd t lt l => PerformLRemoveFieldAt n fd t (lt :: k -> Type) (l :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

data RemoveRField (fd :: Symbol) (a :: Type) :: MajorSurgery k Source #

Instances
type PerformL (lt :: k -> Type) (RemoveRField fd a :: (k -> Type) -> (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type PerformL (lt :: k -> Type) (RemoveRField fd a :: (k -> Type) -> (k -> Type) -> Type) = PerformL lt (RemoveFieldAt ((FieldIndex fd :: (k -> Type) -> Nat -> Type) @@ lt) (Just fd) a :: (k -> Type) -> (k -> Type) -> Type)
type Eval (RemoveRField fd a f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (RemoveRField fd a f :: (k -> Type) -> Type) = Eval (RemoveField_ (Eval (FieldIndex fd f)) f)

data InsertField (n :: Nat) (fd :: Maybe Symbol) (t :: Type) :: MajorSurgery k Source #

Instances
type PerformL (l :: k -> Type) (InsertField n fd t :: (k -> Type) -> (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type PerformL (l :: k -> Type) (InsertField n fd t :: (k -> Type) -> (k -> Type) -> Type) = PerformLInsert n fd t l (Eval (InsertField n fd t l))
type Eval (InsertField 0 fd t (U1 :: k -> Type) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (InsertField 0 fd t (U1 :: k -> Type) :: (k -> Type) -> Type) = M1 S (DefaultMetaSel fd) (K1 R t :: k -> Type) :*: (U1 :: k -> Type)
type Eval (InsertField n fd t (f :*: g) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (InsertField n fd t (f :*: g) :: (k -> Type) -> Type) = Eval (If (n == 0) (Pure (M1 S (DefaultMetaSel fd) (K1 R t :: k -> Type) :*: (f :*: g))) ((:*:) f <$> InsertField (n - 1) fd t g))
type Eval (InsertField n fd t (f :+: (V1 :: k -> Type)) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (InsertField n fd t (f :+: (V1 :: k -> Type)) :: (k -> Type) -> Type) = Eval (InsertField n fd t f) :+: (V1 :: k -> Type)
type Eval (InsertField n fd t (M1 C m f) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (InsertField n fd t (M1 C m f) :: (k -> Type) -> Type) = M1 C m (Eval (InsertField n fd t f))
type Eval (InsertField n fd t (M1 D m f) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (InsertField n fd t (M1 D m f) :: (k -> Type) -> Type) = M1 D m (Eval (InsertField n fd t f))

type PerformLInsert_ n fd t l tl = (GInsertField n t l tl, l ~ Eval (RemoveField_ n tl), tl ~ Eval (InsertField n fd t l), CheckField n fd tl, t ~ Eval (FieldTypeAt n tl)) Source #

class PerformLInsert_ n fd t l tl => PerformLInsert n fd t l tl Source #

Instances
PerformLInsert_ n fd t l tl => PerformLInsert n fd t (l :: k -> Type) (tl :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type family CheckField (n :: Nat) (fd :: Maybe Symbol) (tl :: k -> Type) :: Constraint where ... Source #

Equations

CheckField n Nothing tl = () 
CheckField n (Just fd) tl = n ~ Eval (FieldIndex fd tl) 

data Succ :: Nat -> Exp Nat Source #

Instances
type Eval (Succ n :: Nat -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (Succ n :: Nat -> Type) = 1 + n

data FieldIndex (field :: Symbol) (f :: k -> Type) :: Exp Nat Source #

Position of a record field

Instances
type Eval (FieldIndex field (M1 S (MetaSel (Just field') su ss ds) f :*: g) :: Nat -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (FieldIndex field (M1 S (MetaSel (Just field') su ss ds) f :*: g) :: Nat -> Type) = Eval (If (field == field') (Pure 0) (Succ =<< FieldIndex field g))
type Eval (FieldIndex field (f :+: (V1 :: k -> Type)) :: Nat -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (FieldIndex field (f :+: (V1 :: k -> Type)) :: Nat -> Type) = Eval (FieldIndex field f)
type Eval (FieldIndex field (M1 C m f) :: Nat -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (FieldIndex field (M1 C m f) :: Nat -> Type) = Eval (FieldIndex field f)
type Eval (FieldIndex field (M1 D m f) :: Nat -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (FieldIndex field (M1 D m f) :: Nat -> Type) = Eval (FieldIndex field f)

type family Arity (f :: k -> Type) :: Nat Source #

Number of fields of a single constructor

Instances
type Arity (U1 :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Arity (U1 :: k -> Type) = 0
type Arity (K1 i c :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Arity (K1 i c :: k -> Type) = 1
type Arity (f :*: g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Arity (f :*: g :: k -> Type) = Arity f + Arity g
type Arity (f :+: (V1 :: k -> Type) :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Arity (f :+: (V1 :: k -> Type) :: k -> Type) = Arity f
type Arity (M1 d m f :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Arity (M1 d m f :: k -> Type) = Arity f

type family CoArity (f :: k -> Type) :: Nat Source #

Number of constructors of a data type

Instances
type CoArity (V1 :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type CoArity (V1 :: k -> Type) = 0
type CoArity (f :+: g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type CoArity (f :+: g :: k -> Type) = CoArity f + CoArity g
type CoArity (M1 C m f :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type CoArity (M1 C m f :: k -> Type) = 1
type CoArity (M1 D m f :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type CoArity (M1 D m f :: k -> Type) = CoArity f

class GRemoveField (n :: Nat) a f g where Source #

Methods

gRemoveField :: f x -> (a, g x) Source #

Instances
((n == 0) ~ False, f0g ~ (f0 :*: g), GRemoveField (n - 1) a f g) => GRemoveField n a (f0 :*: f :: k -> Type) (f0g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gRemoveField :: (f0 :*: f) x -> (a, f0g x) Source #

GRemoveField 0 a (M1 s m (K1 i a :: k -> Type) :*: f :: k -> Type) (f :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gRemoveField :: (M1 s m (K1 i a) :*: f) x -> (a, f x) Source #

GRemoveField n a f g => GRemoveField n a (f :+: (V1 :: k -> Type) :: k -> Type) (g :+: (V1 :: k -> Type) :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gRemoveField :: (f :+: V1) x -> (a, (g :+: V1) x) Source #

GRemoveField n a f g => GRemoveField n a (M1 i c f :: k -> Type) (M1 i c g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gRemoveField :: M1 i c f x -> (a, M1 i c g x) Source #

class GInsertField (n :: Nat) a f g where Source #

Methods

gInsertField :: a -> f x -> g x Source #

Instances
((n == 0) ~ False, f0f ~ (f0 :*: f), GInsertField (n - 1) a f g) => GInsertField n a (f0f :: k -> Type) (f0 :*: g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gInsertField :: a -> f0f x -> (f0 :*: g) x Source #

GInsertField 0 a (f :: k -> Type) (M1 s m (K1 i a :: k -> Type) :*: f :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gInsertField :: a -> f x -> (M1 s m (K1 i a) :*: f) x Source #

GInsertField n a f g => GInsertField n a (f :+: (V1 :: k -> Type) :: k -> Type) (g :+: (V1 :: k -> Type) :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gInsertField :: a -> (f :+: V1) x -> (g :+: V1) x Source #

GInsertField n a f g => GInsertField n a (M1 i c f :: k -> Type) (M1 i c g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gInsertField :: a -> M1 i c f x -> M1 i c g x Source #

data ConstrAt (n :: Nat) (f :: k -> Type) :: Exp (k -> Type) Source #

Instances
type Eval (ConstrAt n (f :+: g) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (ConstrAt n (f :+: g) :: (k -> Type) -> Type) = Eval (If (n == 0) (Pure f) (ConstrAt (n - 1) g))
type Eval (ConstrAt n (M1 i m f) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (ConstrAt n (M1 i m f) :: (k -> Type) -> Type) = Eval (ConstrAt n f)

data RemoveConstr (c :: Symbol) (t :: Type) :: MajorSurgery k Source #

Instances
type PerformL (lc :: Type -> Type) (RemoveConstr c t :: (Type -> Type) -> (Type -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type PerformL (lc :: Type -> Type) (RemoveConstr c t :: (Type -> Type) -> (Type -> Type) -> Type) = PerformLRemoveConstr lc c ((ConstrIndex c :: (Type -> Type) -> Nat -> Type) @@ lc) t
type Eval (RemoveConstr c t l :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (RemoveConstr c t l :: (k -> Type) -> Type) = Eval (RemoveConstrAt c ((ConstrIndex c :: (k -> Type) -> Nat -> Type) @@ l) t l)

type PerformLRemoveConstrAt_ c n t l_t lc l = (GRemoveConstr n t lc l, c ~ MetaConsName (MetaOf l_t), lc ~ Eval (InsertUConstrAtL n l_t l), MatchFields (Linearize (UnM1 (Rep t))) l_t, Arity l_t ~ Arity (Linearize (UnM1 (Rep t)))) Source #

class PerformLRemoveConstrAt_ c n t l_t lc l => PerformLRemoveConstrAt c n (t :: Type) l_t lc l Source #

Instances
PerformLRemoveConstrAt_ c n t l_t lc l => PerformLRemoveConstrAt c n t l_t lc l Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

data RemoveConstrAt (c :: Symbol) (n :: Nat) (t :: Type) :: MajorSurgery k Source #

Instances
type Eval (RemoveConstrAt _ n t l :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (RemoveConstrAt _ n t l :: (k -> Type) -> Type) = Eval (RemoveUConstrAt n t l)

data RemoveUConstrAt (n :: Nat) (t :: Type) :: MajorSurgery k Source #

Instances
type Eval (RemoveUConstrAt n _ l :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (RemoveUConstrAt n _ l :: (k -> Type) -> Type) = Eval (RemoveUConstrAt_ n l)

data RemoveUConstrAt_ (n :: Nat) :: MajorSurgery k Source #

Like RemoveConstr, but without the explicit constructor type.

Instances
type Eval (RemoveUConstrAt_ n (f :+: g) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (RemoveUConstrAt_ n (f :+: g) :: (k -> Type) -> Type) = Eval (If (n == 0) (Pure g) ((:+:) f <$> RemoveUConstrAt_ (n - 1) g))
type Eval (RemoveUConstrAt_ n (M1 i m f) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (RemoveUConstrAt_ n (M1 i m f) :: (k -> Type) -> Type) = M1 i m (Eval (RemoveUConstrAt_ n f))

data InsertConstrAt (c :: sym) (n :: Nat) (t :: ty) :: MajorSurgery k Source #

This is polymorphic to allow different ways of specifying the inserted constructor.

If sym (the kind of the constructor name c) is:

  • Symbol: treat it like a regular prefix constructor.
  • TODO Infix constructors and their fixities.

t must be a single-constructor type, then we reuse its generic representation for the new constructor, only replacing its constructor name with c.

Instances
type PerformL (l :: Type -> Type) (InsertConstrAt c n t :: (Type -> Type) -> (Type -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type PerformL (l :: Type -> Type) (InsertConstrAt c n t :: (Type -> Type) -> (Type -> Type) -> Type) = PerformLInsertConstrAt0 l c n t
type Eval (InsertConstrAt c n t l :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (InsertConstrAt c n t l :: (k -> Type) -> Type) = Eval (InsertUConstrAtL n (ConGraft c t :: k -> Type) l)

type family ConGraft (c :: sym) (t :: ty) :: k -> Type Source #

Instances
type ConGraft (c :: sym) (t :: Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type ConGraft (c :: sym) (t :: Type) = RenameCon c (Linearize (UnM1 (Rep t)))

type family RenameCon (c :: sym) (t :: k -> Type) :: k -> Type Source #

Instances
type RenameCon (c :: sym) (M1 C m f :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type RenameCon (c :: sym) (M1 C m f :: k -> Type) = M1 C (RenameMeta c m) f

type family RenameMeta (c :: sym) (m :: Meta) :: Meta Source #

Instances
type RenameMeta (s :: Symbol) (MetaCons _1 _2 r) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type RenameMeta (s :: Symbol) (MetaCons _1 _2 r) = MetaCons s PrefixI r

type PerformLInsertConstrAt_ c n t l_t l lc = (GInsertConstr n t l lc, c ~ MetaConsName (MetaOf l_t), n ~ (ConstrIndex c @@ lc), l_t ~ (ConstrAt n @@ lc), l ~ Eval (RemoveUConstrAt_ n lc), MatchFields (Linearize (UnM1 (Rep t))) l_t) Source #

class PerformLInsertConstrAt_ c n t l_t l lc => PerformLInsertConstrAt c n t l_t l lc Source #

Instances
PerformLInsertConstrAt_ c n t l_t l lc => PerformLInsertConstrAt c n t l_t l lc Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

data InsertUConstrAt (n :: Nat) (t :: Type) :: MajorSurgery k Source #

Instances
type Eval (InsertUConstrAt n t l :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (InsertUConstrAt n t l :: (Type -> Type) -> Type) = Eval (InsertUConstrAtL n (Linearize (UnM1 (Rep t))) l)

data InsertUConstrAtL (n :: Nat) (t :: k -> Type) :: MajorSurgery k Source #

Instances
type Eval (InsertUConstrAtL 0 t (V1 :: k -> Type) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (InsertUConstrAtL 0 t (V1 :: k -> Type) :: (k -> Type) -> Type) = t :+: (V1 :: k -> Type)
type Eval (InsertUConstrAtL n t (f :+: g) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (InsertUConstrAtL n t (f :+: g) :: (k -> Type) -> Type) = Eval (If (n == 0) (Pure (t :+: (f :+: g))) ((:+:) f <$> InsertUConstrAtL (n - 1) t g))
type Eval (InsertUConstrAtL n t (M1 i m f) :: (k -> Type) -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (InsertUConstrAtL n t (M1 i m f) :: (k -> Type) -> Type) = M1 i m (Eval (InsertUConstrAtL n t f))

data ConstrIndex (con :: Symbol) (f :: k -> Type) :: Exp Nat Source #

Instances
type Eval (ConstrIndex con (M1 C (MetaCons con' fx s) f :+: g) :: Nat -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (ConstrIndex con (M1 C (MetaCons con' fx s) f :+: g) :: Nat -> Type) = Eval (If (con == con') (Pure 0) (Succ =<< ConstrIndex con g))
type Eval (ConstrIndex con (M1 D m f) :: Nat -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

type Eval (ConstrIndex con (M1 D m f) :: Nat -> Type) = Eval (ConstrIndex con f)

class GRemoveConstr (n :: Nat) (t :: Type) f g where Source #

Methods

gRemoveConstr :: f x -> Either t (g x) Source #

Instances
ConstrArborify t l => GRemoveConstr 0 t (l :+: f :: Type -> Type) (f :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gRemoveConstr :: (l :+: f) x -> Either t (f x) Source #

(GRemoveConstr (n - 1) t f g, (n == 0) ~ False, f0g ~ (f0 :+: g)) => GRemoveConstr n t (f0 :+: f :: k -> Type) (f0g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gRemoveConstr :: (f0 :+: f) x -> Either t (f0g x) Source #

GRemoveConstr n t f g => GRemoveConstr n t (M1 i c f :: k -> Type) (M1 i c g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gRemoveConstr :: M1 i c f x -> Either t (M1 i c g x) Source #

constrArborify' :: forall t l x. ConstrArborify t l => l x -> t Source #

class GInsertConstr (n :: Nat) (t :: Type) f g where Source #

Methods

gInsertConstr :: Either t (f x) -> g x Source #

Instances
ConstrLinearize t l => GInsertConstr 0 t (f :: Type -> Type) (l :+: f :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gInsertConstr :: Either t (f x) -> (l :+: f) x Source #

(GInsertConstr (n - 1) t f g, (n == 0) ~ False, f0f ~ (f0 :+: f)) => GInsertConstr n t (f0f :: k -> Type) (f0 :+: g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gInsertConstr :: Either t (f0f x) -> (f0 :+: g) x Source #

GInsertConstr n t f g => GInsertConstr n t (M1 i c f :: k -> Type) (M1 i c g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

Methods

gInsertConstr :: Either t (M1 i c f x) -> M1 i c g x Source #

constrLinearize' :: forall t l x. ConstrLinearize t l => t -> l x Source #

class MatchFields (f :: k -> Type) (g :: k -> Type) Source #

Equate two generic representations, but ignoring constructor and field metadata.

Instances
g ~ (V1 :: k -> Type) => MatchFields (V1 :: k -> Type) (g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

g ~ (U1 :: k -> Type) => MatchFields (U1 :: k -> Type) (g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

g ~ (K1 i a :: k -> Type) => MatchFields (K1 i a :: k -> Type) (g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

(g ~ (g1 :*: g2), MatchFields f1 g1, MatchFields f2 g2) => MatchFields (f1 :*: f2 :: k -> Type) (g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

(g ~ (g1 :+: g2), MatchFields f1 g1, MatchFields f2 g2) => MatchFields (f1 :+: f2 :: k -> Type) (g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

(g ~ M1 S (MetaSel _w _x _y _z) g', MatchFields f' g') => MatchFields (M1 S c f' :: k -> Type) (g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

(g ~ M1 C (MetaCons _x _y _z) g', MatchFields f' g') => MatchFields (M1 C c f' :: k -> Type) (g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

(g ~ M1 D c g', MatchFields f' g') => MatchFields (M1 D c f' :: k -> Type) (g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

class IsTuple (n :: Nat) (t :: k) Source #

Instances
t ~ () => IsTuple 0 (t :: Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

t ~ Identity a => IsTuple 1 (t :: Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

t ~ (a, b) => IsTuple 2 (t :: Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

t ~ (a, b, c) => IsTuple 3 (t :: Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

t ~ (a, b, c, d) => IsTuple 4 (t :: Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

t ~ (a, b, c, d, e) => IsTuple 5 (t :: Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

t ~ (a, b, c, d, e, f) => IsTuple 6 (t :: Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal

t ~ (a, b, c, d, e, f, g) => IsTuple 7 (t :: Type) Source # 
Instance details

Defined in Generic.Data.Surgery.Internal