by-other-names-1.2.3.0: Give aliases to record fields.
Safe HaskellSafe-Inferred
LanguageHaskell2010

ByOtherNamesH

Description

This module provides the general mechanism for defining field and branch aliases for algebraic datatypes.

Aliases can be defined for multiple contexts (json serialization, orms...). Each of those contexts is termed a Rubric, basically a marker datakind used to namespace the aliases.

This module should only be imported if you want to define your own adapter package for some new Rubric. See ByOtherNamesH.Aeson for a concrete example.

This module provides a more versatile, but also more verbose, version of the functionality provided by ByOtherNames. If you plan to use both ByOtherNames and ByOtherNamesH, import this module qualified to avoid name collisions:

import qualified ByOthernamesH as H
Synopsis

Aliases

data Aliases rep a (h :: Type -> Type) Source #

This datatype carries the field/branch aliases, along with a value wrapped in h for each field in the original datatype.

It matches the shape of the generic Rep.

data AliasList (names_slots :: [(Symbol, [Type])]) a (h :: Type -> Type) Source #

An intermediate helper datatype for specifying the aliases.

Indexed by a list of names accompanied by field types.

See aliasListBegin, alias and aliasListEnd.

aliasListBegin Source #

Arguments

:: forall names_slots a h rep. ToAliases names_slots rep '[] 
=> AliasList names_slots a h

indexed by a list of alias names / slots types

-> Aliases rep a h

indexed by a generic Rep

alias Source #

Arguments

:: forall name slots a h names_slots. a

The alias value

-> SlotList slots h

"wrapped" values for each slot of the alias

-> AliasList names_slots a h 
-> AliasList ('(name, slots) ': names_slots) a h 

aliasListEnd :: AliasList '[] a h Source #

The empty AliasList.

data SlotList :: [Type] -> (Type -> Type) -> Type Source #

A list of slots associated an alias. Indexed by the types of each slot and a type constructor that wraps each slot value.

For records, each field alias will have one and only one slot: the corresponding record field. See singleSlot.

For sum types, each branch alias might have zero or more slots, depending on the structure of the datatype. See slot and slotListEnd.

singleSlot :: h v -> SlotList '[v] h Source #

slot :: h v -> SlotList rest h -> SlotList (v ': rest) h Source #

slotListEnd :: SlotList '[] h Source #

The empty SlotList.

Rubrics

class Rubric k Source #

Associated Types

type AliasType k :: Type Source #

type WrapperType k :: Type -> Type Source #

Instances

Instances details
Rubric 'JSON Source #

The aliases will be of type Data.Aeson.Key.

Instance details

Defined in ByOtherNamesH.Aeson

Associated Types

type AliasType 'JSON Source #

type WrapperType 'JSON :: Type -> Type Source #

class (Rubric k, Generic r) => Aliased k r where Source #

Generic helpers

class GRecord rep where Source #

Methods

gToRecord Source #

Arguments

:: Applicative g 
=> Aliases rep a h

Field aliases.

-> (forall v. a -> h v -> g v) 
-> g (rep z) 

Builds a parser for the entire generic Rep out of parsers for each field.

gFromRecord Source #

Arguments

:: rep z

Record representation.

-> Aliases rep String Identity 

gBiliftA2RecordAliases Source #

Arguments

:: (a1 -> a2 -> ar)

Combine aliases

-> (forall v. h1 v -> h2 v -> hr v)

Combine slots

-> Aliases rep a1 h1 
-> Aliases rep a2 h2 
-> Aliases rep ar hr 

Instances

Instances details
(GRecord left, GRecord right) => GRecord (left :*: right) Source # 
Instance details

Defined in ByOtherNamesH

Methods

gToRecord :: Applicative g => Aliases (left :*: right) a h -> (forall v. a -> h v -> g v) -> g ((left :*: right) z) Source #

gFromRecord :: (left :*: right) z -> Aliases (left :*: right) String Identity Source #

gBiliftA2RecordAliases :: (a1 -> a2 -> ar) -> (forall v. h1 v -> h2 v -> hr v) -> Aliases (left :*: right) a1 h1 -> Aliases (left :*: right) a2 h2 -> Aliases (left :*: right) ar hr Source #

GRecord prod => GRecord (D1 x (C1 y prod)) Source # 
Instance details

Defined in ByOtherNamesH

Methods

gToRecord :: Applicative g => Aliases (D1 x (C1 y prod)) a h -> (forall v. a -> h v -> g v) -> g (D1 x (C1 y prod) z) Source #

gFromRecord :: D1 x (C1 y prod) z -> Aliases (D1 x (C1 y prod)) String Identity Source #

gBiliftA2RecordAliases :: (a1 -> a2 -> ar) -> (forall v. h1 v -> h2 v -> hr v) -> Aliases (D1 x (C1 y prod)) a1 h1 -> Aliases (D1 x (C1 y prod)) a2 h2 -> Aliases (D1 x (C1 y prod)) ar hr Source #

KnownSymbol fieldName => GRecord (S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v)) Source # 
Instance details

Defined in ByOtherNamesH

Methods

gToRecord :: Applicative g => Aliases (S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v)) a h -> (forall v0. a -> h v0 -> g v0) -> g (S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v) z) Source #

gFromRecord :: S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v) z -> Aliases (S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v)) String Identity Source #

gBiliftA2RecordAliases :: (a1 -> a2 -> ar) -> (forall v0. h1 v0 -> h2 v0 -> hr v0) -> Aliases (S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v)) a1 h1 -> Aliases (S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v)) a2 h2 -> Aliases (S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v)) ar hr Source #

Re-exports

data Symbol #

(Kind) This is the kind of type-level symbols. Declared here because class IP needs it

Instances

Instances details
SingKind Symbol

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep Symbol

Methods

fromSing :: forall (a :: Symbol). Sing a -> DemoteRep Symbol

KnownSymbol a => SingI (a :: Symbol)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing a

KnownSymbol fieldName => GHasFieldNames (S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v)) Source # 
Instance details

Defined in ByOtherNames.Internal

Methods

gGetFieldNames :: Aliases (S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v)) String Source #

KnownSymbol fieldName => GRecord (S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v)) Source # 
Instance details

Defined in ByOtherNamesH

Methods

gToRecord :: Applicative g => Aliases (S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v)) a h -> (forall v0. a -> h v0 -> g v0) -> g (S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v) z) Source #

gFromRecord :: S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v) z -> Aliases (S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v)) String Identity Source #

gBiliftA2RecordAliases :: (a1 -> a2 -> ar) -> (forall v0. h1 v0 -> h2 v0 -> hr v0) -> Aliases (S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v)) a1 h1 -> Aliases (S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v)) a2 h2 -> Aliases (S1 ('MetaSel ('Just fieldName) unpackedness strictness laziness) (Rec0 v)) ar hr Source #

IsRecord (M1 S ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f) False 
Instance details

Defined in Data.Aeson.Types.Generic

type DemoteRep Symbol 
Instance details

Defined in GHC.Generics

type DemoteRep Symbol = String
data Sing (s :: Symbol) 
Instance details

Defined in GHC.Generics

data Sing (s :: Symbol) where
type Compare (a :: Symbol) (b :: Symbol) 
Instance details

Defined in Data.Type.Ord

type Compare (a :: Symbol) (b :: Symbol) = CmpSymbol a b