generic-labels-0.1.0.1: Generically extract and replace collections of record fields
Safe HaskellNone
LanguageHaskell2010

Data.Generic.Labels

Description

This module provides functionality for converting between different collections of fields.

Projections

To project out certain fields of a record, use project.

For instance:

data IBXD x = IBXD { i :: Int, b :: Bool, x :: x, d :: Double }
  deriving stock Generic
data XI x = XI { x :: c, i :: Int }
  deriving stock Generic

We can project out the two fields of interest from the first record type:

ibxd_to_xi :: IBXD x -> XI x
ibxd_to_xi = project

Injections

Going the other way, we can use inject to override fields of the larger record with those from the smaller record:

xi_into_ibxd :: XI x -> IBXD x -> IBXD x
xi_into_ibxd = inject

Adapters

project and inject are two instances of the more general adapt function, which allows us to only specify the missing arguments in the above example.

xi_plus_bd_makes_ibxd :: XI x -> ( "b" := Bool, "d" := Double ) -> IBXD x
xi_plus_bd_makes_ibxd = adapt

In this situation, we are building up a record of type IBXD x out of two parts.

More generally, adapt allows for fields in the first argument to override fields in the second argument, which provides a convenient mechanism for named optional arguments.

adapt :: _ => givenArgs -> optionalArgs -> allArgs

For instance, if we have a function f which takes in several named arguments

type AllArgsTuple = ( "arg1" := Ty1, "arg2" := Ty2, "arg3" := Ty3, "arg4" := Ty4 ) 

f :: AllArgsTuple -> r

and we have default values for some of those arguments, e.g.

type DefaultArgsTuple = ( "arg2" := Ty2, "arg3" := Ty3 )

f_defaults :: DefaultArgsTuple
f_defaults = ( arg3 := val3 )

then we can create a corresponding function f_defaulting, which allows user to only pass the remaining (required) arguments:

f_defaulting
  :: CheckedAdapt args DefaultArgsTuple AllArgsTuple => args -> r
f_defaulting args = adapt args f_defaults
Synopsis

Converting between collections of fields

class UncheckedAdapt args opt all => Adapt args opt all where Source #

Methods

adapt Source #

Arguments

:: args

Provided arguments

-> opt

Default values of optional arguments

-> all

Combination of provided arguments and non-overridden defaults

Create an adapter, to inject a smaller type into a larger one, providing defaults for optional values.

  myAdapt :: ( "i" := Int, "f" := Float ) -> ( "f" := Float, "b" := Bool, "i" := Int )
  myAdapt args = adapt args ( #b := False )
  > myAdapt ( f := 17.1 )
  > ( b = False, #i := 3 )

Here myAdapt re-arranges the arguments into the result, passing in additional (default) values that are overriden when they occur in the arguments.

Includes custom validation, e.g. to disallow duplicate arguments. Use uncheckedAdapt to disable this validation (you might get strange errors!).

Instances

Instances details
(UncheckedAdapt args opt all, CheckAdapt args opt all) => Adapt args opt all Source # 
Instance details

Defined in Data.Generic.Labels

Methods

adapt :: args -> opt -> all Source #

class UncheckedInject small big => Inject small big where Source #

Methods

inject :: small -> big -> big Source #

Inject a smaller type into a larger one, overriding the fields in the larger type with those from the smaller type.

  myInject
    :: ( "i" := Int, "f" := Float )
    -> ( "f" := Float, "b" := Bool, "i" := Int )
    -> ( "f" := Float, "b" := Bool, "i" := Int )
  myInject = inject

Here myInject overrides the fields of the second argument with those provided in the first argument.

  > myInject ( f := 17.1 ) ( b := False, #i := 22 )
  > ( b := False, #i := 3 )

Includes custom validation, e.g. to disallow duplicate arguments. Use uncheckedInject to disable this validation (you might get strange errors!).

Instances

Instances details
(UncheckedInject small big, CheckInject small big) => Inject small big Source # 
Instance details

Defined in Data.Generic.Labels

Methods

inject :: small -> big -> big Source #

class UncheckedProject big small => Project big small where Source #

Methods

project :: big -> small Source #

Project a smaller type out from a larger one, discarding the rest.

  myProject :: ( "f" := Float, "b" := Bool, "i" := Int ) -> ( "i" := Int, "f" := Float )
  myProject = project

Here myProject projects out a sub-component of the whole type, in this case discarding the boolean while re-arranging the other fields.

  > myProject ( b := False, #i := 3 )
  > ( f := 17.1 )

Includes custom validation, e.g. to disallow duplicate arguments. Use uncheckedProject to disable this validation (you might get strange errors!).

Instances

Instances details
(UncheckedProject big small, CheckProject big small) => Project big small Source # 
Instance details

Defined in Data.Generic.Labels

Methods

project :: big -> small Source #

Re-export of labelling functionality from Data.Label

newtype (lbl :: Symbol) := (a :: Type) infix 1 Source #

A type with a Label.

With OverloadedLabels:

 ( #bar := Just c ) :: ( "bar" := Maybe Char )

Constructors

Labelled 

Fields

Bundled Patterns

pattern (:=) :: Label lbl -> a -> lbl := a infix 1

Add a Label to a type.

With OverloadedLabels:

 ( #bar := Just c ) :: ( "bar" := Maybe Char )

Instances

Instances details
GLens' (HasTotalLabelPSym lbl) (args :*: opts) all => GAdapt args opts (M1 m meta (Rec0 (lbl := all))) Source #

This instance is INCOHERENT because we assume that no type variable (say all0) will later be instantiated to a labelled type lbl := all.

The end result is that, when we have both a built-in Haskell record field name as well as an explicit label, we prioritise the built-in record field name over the label.

Instance details

Defined in Data.Generic.Labels.Internal

Methods

gAdapt :: args p -> opts p -> M1 m meta (Rec0 (lbl := all)) p Source #

(Generic args, Generic all, optFld ~ S1 ('MetaSel ('Just lbl) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 o), GAdapt (Rep args) optFld (Rep all)) => UncheckedAdapt args (lbl := o) all Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: args -> (lbl := o) -> all Source #

(KnownSymbol lbl, Show a) => Show (lbl := a) Source # 
Instance details

Defined in Data.Label

Methods

showsPrec :: Int -> (lbl := a) -> ShowS #

show :: (lbl := a) -> String #

showList :: [lbl := a] -> ShowS #

(Generic opt, Generic all, argFld ~ S1 ('MetaSel ('Just lbl) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a), GAdapt argFld (Rep opt) (Rep all)) => UncheckedAdapt (lbl := a) opt all Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: (lbl := a) -> opt -> all Source #

a ~ b => UncheckedAdapt (lbl := a) opt (lbl := b) Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: (lbl := a) -> opt -> lbl := b Source #

(Generic all, argFld ~ S1 ('MetaSel ('Just lbl1) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a), optFld ~ S1 ('MetaSel ('Just lbl2) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 o), GAdapt argFld optFld (Rep all)) => UncheckedAdapt (lbl1 := a) (lbl2 := o) all Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: (lbl1 := a) -> (lbl2 := o) -> all Source #

(a ~ b, o ~ b) => UncheckedAdapt (lbl := a) (lbl := o) (lbl := b) Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: (lbl := a) -> (lbl := o) -> lbl := b Source #

Unchecked functions (can behave unpredictably).

class UncheckedAdapt args opt all where Source #

Methods

uncheckedAdapt :: args -> opt -> all Source #

Create an adapter, without extra type-level validation.

Unchecked uses (e.g. presence of duplicate fields) can throw abstruse compile-time error messages or produce unexpected results at runtime.

Prefer using adapt whenever possible.

Instances

Instances details
(Generic args, Generic opt, Generic all, GAdapt (Rep args) (Rep opt) (Rep all)) => UncheckedAdapt args opt all Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: args -> opt -> all Source #

UncheckedAdapt a opt a Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: a -> opt -> a Source #

UncheckedAdapt a a a Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: a -> a -> a Source #

(Generic args, Generic all, optFld ~ S1 ('MetaSel ('Just lbl) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 o), GAdapt (Rep args) optFld (Rep all)) => UncheckedAdapt args (lbl := o) all Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: args -> (lbl := o) -> all Source #

(Generic opt, Generic all, argFld ~ S1 ('MetaSel ('Just lbl) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a), GAdapt argFld (Rep opt) (Rep all)) => UncheckedAdapt (lbl := a) opt all Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: (lbl := a) -> opt -> all Source #

a ~ b => UncheckedAdapt (lbl := a) opt (lbl := b) Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: (lbl := a) -> opt -> lbl := b Source #

(Generic all, argFld ~ S1 ('MetaSel ('Just lbl1) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a), optFld ~ S1 ('MetaSel ('Just lbl2) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 o), GAdapt argFld optFld (Rep all)) => UncheckedAdapt (lbl1 := a) (lbl2 := o) all Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: (lbl1 := a) -> (lbl2 := o) -> all Source #

(a ~ b, o ~ b) => UncheckedAdapt (lbl := a) (lbl := o) (lbl := b) Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedAdapt :: (lbl := a) -> (lbl := o) -> lbl := b Source #

class UncheckedAdapt small big big => UncheckedInject small big where Source #

Methods

uncheckedInject :: small -> big -> big Source #

Inject a smaller type into a larger one, without extra type-level validation.

Unchecked uses (e.g. presence of duplicate fields) can throw abstruse compile-time error messages or produce unexpected results at runtime.

Prefer using inject whenever possible.

Instances

Instances details
UncheckedAdapt small big big => UncheckedInject small big Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedInject :: small -> big -> big Source #

class UncheckedAdapt big big small => UncheckedProject big small where Source #

Methods

uncheckedProject :: big -> small Source #

Project a smaller type out from a larger one, without extra type-level validation.

Unchecked uses (e.g. presence of duplicate fields) can throw abstruse compile-time error messages or produce unexpected results at runtime.

Prefer using project whenever possible.

Instances

Instances details
UncheckedAdapt big big small => UncheckedProject big small Source # 
Instance details

Defined in Data.Generic.Labels

Methods

uncheckedProject :: big -> small Source #