Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- class RecMapMethod c (f :: u -> *) (ts :: [u]) where
- 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
- mapFields :: forall c ts. RecMapMethod c ElField ts => (forall a. c a => a -> a) -> FieldRec ts -> FieldRec ts
- class RecPointed c (f :: u -> *) (ts :: [u]) where
- data FieldTyper
- type family ApplyFieldTyper (f :: FieldTyper) (a :: k) :: * where ...
- type family PayloadType f (a :: u) :: * where ...
- recEq :: RecAll f rs Eq => Rec f rs -> Rec f rs -> Bool
- recCompare :: RecAll f rs Ord => Rec f rs -> Rec f rs -> Ordering
- recMempty :: RecAll f rs Monoid => Rec proxy rs -> Rec f rs
- recMappend :: RecAll f rs Monoid => Rec f rs -> Rec f rs -> Rec f rs
- recMconcat :: RecAll f rs Monoid => Rec proxy rs -> [Rec f rs] -> Rec f rs
- recAdd :: RecAll f rs Num => Rec f rs -> Rec f rs -> Rec f rs
- recSubtract :: RecAll f rs Num => Rec f rs -> Rec f rs -> Rec f rs
- recMultiply :: RecAll f rs Num => Rec f rs -> Rec f rs -> Rec f rs
- recAbs :: RecAll f rs Num => Rec f rs -> Rec f rs
- recSignum :: RecAll f rs Num => Rec f rs -> Rec f rs
- recNegate :: RecAll f rs Num => Rec f rs -> Rec f rs
- recMinBound :: RecAll f rs Bounded => Rec proxy rs -> Rec f rs
- recMaxBound :: RecAll f rs Bounded => Rec proxy rs -> Rec f rs
Mapping methods over records
class RecMapMethod c (f :: u -> *) (ts :: [u]) where Source #
Apply a typeclass method to each field of a Rec
.
rmapMethod :: (forall a. c (PayloadType f a) => f a -> g a) -> Rec f ts -> Rec g ts Source #
Instances
RecMapMethod c (f :: u -> *) ([] :: [u]) Source # | |
Defined in Data.Vinyl.Class.Method 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 -> *) (t ': ts :: [a]) Source # | |
Defined in Data.Vinyl.Class.Method 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 RecPointed c (f :: u -> *) (ts :: [u]) where Source #
Generate a record from fields derived from type class instances.
rpointMethod :: (forall (a :: u). c (f a) => f a) -> Rec f ts Source #
Instances
RecPointed c (f :: u -> *) ([] :: [u]) Source # | |
Defined in Data.Vinyl.Class.Method rpointMethod :: (forall (a :: u0). c (f a) => f a) -> Rec f [] Source # | |
(c (f t), RecPointed c f ts) => RecPointed c (f :: a -> *) (t ': ts :: [a]) Source # | |
Defined in Data.Vinyl.Class.Method rpointMethod :: (forall (a0 :: u). c (f a0) => f a0) -> Rec f (t ': ts) Source # |
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.
ApplyFieldTyper FieldId a = a | |
ApplyFieldTyper FieldSnd '(s, b) = b |
type family PayloadType f (a :: u) :: * where ... Source #
Shorthand for combining ApplyFieldTyper
and FieldPayload
.
PayloadType f a = ApplyFieldTyper (FieldPayload f) a |
Eq Functions
Ord Functions
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
.
Num Functions
Bounded Functions
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 Sublist
s
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.