vinyl-0.14.3: Extensible Records
Safe HaskellNone
LanguageHaskell2010

Data.Vinyl.Class.Method

Description

This module uses RecAll to extend common typeclass methods to records. Generally, it is preferable to use the original typeclass methods to these variants. For example, in most places where recCompare could be used, you could use compare instead. They are useful in scenarios that involve working on unknown subsets of a record's fields because RecAll constraints can easily be weakened. An example of this is given at the bottom of this page.

Synopsis

Mapping methods over records

class RecMapMethod c f ts where Source #

Apply a typeclass method to each field of a Rec where the class constrains the index of the field, but not its interpretation functor.

Methods

rmapMethod :: (forall a. c (PayloadType f a) => f a -> g a) -> Rec f ts -> Rec g ts Source #

Instances

Instances details
RecMapMethod c (f :: u -> Type) ('[] :: [u]) Source # 
Instance details

Defined in Data.Vinyl.Class.Method

Methods

rmapMethod :: (forall (a :: u0). c (PayloadType f a) => f a -> g a) -> Rec f '[] -> Rec g '[] Source #

(c (PayloadType f t), RecMapMethod c f ts) => RecMapMethod c (f :: a -> Type) (t ': ts :: [a]) Source # 
Instance details

Defined in Data.Vinyl.Class.Method

Methods

rmapMethod :: (forall (a0 :: u). c (PayloadType f a0) => f a0 -> g a0) -> Rec f (t ': ts) -> Rec g (t ': ts) Source #

rmapMethodF :: forall c f ts. (Functor f, FieldPayload f ~ 'FieldId, RecMapMethod c f ts) => (forall a. c a => a -> a) -> Rec f ts -> Rec f ts Source #

Apply a typeclass method to each field of a Rec f ts using the Functor instance for f to lift the function into the functor. This is a commonly-used specialization of rmapMethod composed with fmap.

mapFields :: forall c ts. RecMapMethod c ElField ts => (forall a. c a => a -> a) -> FieldRec ts -> FieldRec ts Source #

Apply a typeclass method to each field of a FieldRec. This is a specialization of rmapMethod.

class RecMapMethod1 c f ts where Source #

Apply a typeclass method to each field of a Rec where the class constrains the field when considered as a value interpreted by the record's interpretation functor.

Methods

rmapMethod1 :: (forall a. c (f a) => f a -> g a) -> Rec f ts -> Rec g ts Source #

Instances

Instances details
RecMapMethod1 c (f :: u -> Type) ('[] :: [u]) Source # 
Instance details

Defined in Data.Vinyl.Class.Method

Methods

rmapMethod1 :: (forall (a :: u0). c (f a) => f a -> g a) -> Rec f '[] -> Rec g '[] Source #

(c (f t), RecMapMethod1 c f ts) => RecMapMethod1 c (f :: a -> Type) (t ': ts :: [a]) Source # 
Instance details

Defined in Data.Vinyl.Class.Method

Methods

rmapMethod1 :: (forall (a0 :: u). c (f a0) => f a0 -> g a0) -> Rec f (t ': ts) -> Rec g (t ': ts) Source #

class RecPointed c f ts where Source #

Generate a record from fields derived from type class instances.

Methods

rpointMethod :: (forall a. c (f a) => f a) -> Rec f ts Source #

Instances

Instances details
RecPointed c (f :: u -> Type) ('[] :: [u]) Source # 
Instance details

Defined in Data.Vinyl.Class.Method

Methods

rpointMethod :: (forall (a :: u0). c (f a) => f a) -> Rec f '[] Source #

(c (f t), RecPointed c f ts) => RecPointed c (f :: a -> Type) (t ': ts :: [a]) Source # 
Instance details

Defined in Data.Vinyl.Class.Method

Methods

rpointMethod :: (forall (a0 :: u). c (f a0) => f a0) -> Rec f (t ': ts) Source #

rtraverseInMethod :: forall c h f g rs. (RMap rs, RPureConstrained c rs, RApply rs) => (forall a. c a => f a -> g (ApplyToField h a)) -> Rec f rs -> Rec g (MapTyCon h rs) Source #

Like rtraverseIn, but the function between functors may be constrained.

rsequenceInFields :: forall f rs. (Functor f, AllFields rs, RMap rs) => Rec (f :. ElField) rs -> Rec ElField (MapTyCon f rs) Source #

Push an outer layer of interpretation functor into each named field.

Support for RecMapMethod

data FieldTyper Source #

When we wish to apply a typeclass method to each field of a Rec, we typically care about typeclass instances of the record field types irrespective of the record's functor context. To expose the field types themselves, we utilize a constraint built from a defunctionalized type family in the rmapMethod method. The symbols of the function space are defined by this data type.

type family ApplyFieldTyper (f :: FieldTyper) (a :: k) :: * where ... Source #

The interpretation function of the FieldTyper symbols.

Equations

ApplyFieldTyper 'FieldId a = a 
ApplyFieldTyper 'FieldSnd a = Snd a 

type family PayloadType f (a :: u) :: * where ... Source #

Shorthand for combining ApplyFieldTyper and FieldPayload.

Equations

PayloadType f a = ApplyFieldTyper (FieldPayload f) a 

Eq Functions

recEq :: RecAll f rs Eq => Rec f rs -> Rec f rs -> Bool Source #

Ord Functions

recCompare :: RecAll f rs Ord => Rec f rs -> Rec f rs -> Ordering Source #

Monoid Functions

recMempty :: RecAll f rs Monoid => Rec proxy rs -> Rec f rs Source #

This function differs from the original mempty in that it takes an argument. In some cases, you will already have a record of the type you are interested in, and that can be passed an the argument. In other situations where this is not the case, you may need the interpretation function of the argument record to be Const () or Proxy so the you can generate the argument with rpure.

recMappend :: RecAll f rs Monoid => Rec f rs -> Rec f rs -> Rec f rs Source #

recMconcat :: RecAll f rs Monoid => Rec proxy rs -> [Rec f rs] -> Rec f rs Source #

This function differs from the original mconcat. See recMempty.

Num Functions

recAdd :: RecAll f rs Num => Rec f rs -> Rec f rs -> Rec f rs Source #

recSubtract :: RecAll f rs Num => Rec f rs -> Rec f rs -> Rec f rs Source #

recMultiply :: RecAll f rs Num => Rec f rs -> Rec f rs -> Rec f rs Source #

recAbs :: RecAll f rs Num => Rec f rs -> Rec f rs Source #

recSignum :: RecAll f rs Num => Rec f rs -> Rec f rs Source #

recNegate :: RecAll f rs Num => Rec f rs -> Rec f rs Source #

Bounded Functions

recMinBound :: RecAll f rs Bounded => Rec proxy rs -> Rec f rs Source #

This function differs from the original minBound. See recMempty.

recMaxBound :: RecAll f rs Bounded => Rec proxy rs -> Rec f rs Source #

This function differs from the original maxBound. See recMempty.

Example

This module provides variants of typeclass methods that have a RecAll constraint instead of the normal typeclass constraint. For example, a type-specialized compare would look like this:

compare :: Ord (Rec f rs) => Rec f rs -> Rec f rs -> Ordering

The recCompare function looks like this:

recCompare :: RecAll f rs Ord => Rec f rs -> Rec f rs -> Ordering

The only difference is the constraint. Let's look at a potential use case for these functions.

Let's write a function that projects out a subrecord from two records and then compares those for equality. We can write this with the <: operator from Data.Vinyl.Lens and the normal compare function. We don't need recCompare:

-- This needs ScopedTypeVariables
projectAndCompare :: forall super sub f. (super <: sub, Ord (Rec f sub))
                  => Proxy sub -> Rec f super -> Rec f super -> Ordering
projectAndCompare _ a b = compare (rcast a :: Rec f sub) (rcast b :: Rec f sub)

That works fine for the majority of use cases, and it is probably how you should write the function if it does everything you need. However, let's consider a somewhat more complicated case.

What if the exact subrecord we were projecting couldn't be known at compile time? Assume that the end user was allowd to choose the fields on which he or she wanted to compare records. The projectAndCompare function cannot handle this because of the Ord (Rec f sub) constraint. Even if we amend the constraint to read Ord (Rec f super) instead, we cannot use this information to recover the Ord (Rec f sub) constraint that we need. Let's try another approach.

We can use the following GADT to prove subsethood:

data Sublist (super :: [k]) (sub :: [k]) where
  SublistNil   :: Sublist '[]
  SublistSuper :: Proxy r -> Sublist super sub -> Sublist (r ': super) sub
  SublistBoth  :: Proxy r -> Sublist super sub -> Sublist (r ': super) (r ': sub)

projectRec :: Sublist super sub -> Rec f super -> Rec f sub
projectRec s r = case s of
  SublistNil -> RNil
  SublistBoth n snext -> case r of
    rhead :& rtail -> rhead :& projectRec snext rtail
  SublistSuper n snext -> case r of
    rhead :& rtail -> projectRec snext rtail

It is also possible to write a typeclass to generate Sublists implicitly, but that is beyond the scope of this example. Let's now write a function to use Sublist to weaken a RecAll constraint:

import Data.Vinyl.Core hiding (Dict)
import Data.Constraint

weakenRecAll :: Proxy f -> Proxy c -> Sublist super sub -> RecAll f super c :- RecAll f sub c
weakenRecAll f c s = case s of
  SublistNil -> Sub Dict
  SublistSuper _ snext -> Sub $ case weakenRecAll f c snext of
    Sub Dict -> Dict
  SublistBoth _ snext -> Sub $ case weakenRecAll f c snext of
    Sub Dict -> Dict

Now we can write a different version of our original function:

-- This needs ScopedTypeVariables
projectAndCompare2 :: forall super sub f. (RecAll f super Ord)
                   => Sublist super sub -> Rec f super -> Rec f super -> Ordering
projectAndCompare2 s a b = case weakenRecAll (Proxy :: Proxy f) (Proxy :: Proxy Ord) s of
  Sub Dict -> recCompare (projectRec s a) (projectRec s b)

Notice that in this case, the Ord constraint applies to the full set of fields and is then weakened to target a subset of them instead.