ten-0.1.0.2: Typeclasses like Functor, etc. over arity-1 type constructors.
Safe HaskellNone
LanguageHaskell2010

Data.Functor.Field

Description

Provides Generic1 derivation of Representable based on Field.

This relies on the observation that a parametric function forall a. f a -> a is isomorphic to the set of "indices" of f, i.e. Rep f. With the appropriate instances, we can do anything with it that we could with a hand-written ADT Rep type. So, this module provides a way to use exactly that type as Rep, and the needed instances to make it convenient to use.

Synopsis

Documentation

newtype Field f Source #

A Rep type in the form of a parametric accessor function.

Constructors

Field 

Fields

Instances

Instances details
(Traversable f, Applicative f) => Eq (Field f) Source # 
Instance details

Defined in Data.Functor.Field

Methods

(==) :: Field f -> Field f -> Bool #

(/=) :: Field f -> Field f -> Bool #

(Traversable f, Applicative f) => Ord (Field f) Source # 
Instance details

Defined in Data.Functor.Field

Methods

compare :: Field f -> Field f -> Ordering #

(<) :: Field f -> Field f -> Bool #

(<=) :: Field f -> Field f -> Bool #

(>) :: Field f -> Field f -> Bool #

(>=) :: Field f -> Field f -> Bool #

max :: Field f -> Field f -> Field f #

min :: Field f -> Field f -> Field f #

FieldPaths f => Show (Field f) Source # 
Instance details

Defined in Data.Functor.Field

Methods

showsPrec :: Int -> Field f -> ShowS #

show :: Field f -> String #

showList :: [Field f] -> ShowS #

(Traversable f, Applicative f) => Hashable (Field f) Source # 
Instance details

Defined in Data.Functor.Field

Methods

hashWithSalt :: Int -> Field f -> Int #

hash :: Field f -> Int #

FieldPaths f => Portray (Field f) Source # 
Instance details

Defined in Data.Functor.Field

(Traversable f, Applicative f, FieldPaths f) => Diff (Field f) Source # 
Instance details

Defined in Data.Functor.Field

Methods

diff :: Field f -> Field f -> Maybe Portrayal #

newtype FieldRep f a Source #

A newtype carrying instances for use with DerivingVia.

This provides Applicative, Monad, Representable, and Update.

Constructors

FieldRep (f a) 

Instances

Instances details
(Generic1 f, GTabulate (Rep1 f), Functor f) => Monad (FieldRep f) Source # 
Instance details

Defined in Data.Functor.Field

Methods

(>>=) :: FieldRep f a -> (a -> FieldRep f b) -> FieldRep f b #

(>>) :: FieldRep f a -> FieldRep f b -> FieldRep f b #

return :: a -> FieldRep f a #

Functor f => Functor (FieldRep f) Source # 
Instance details

Defined in Data.Functor.Field

Methods

fmap :: (a -> b) -> FieldRep f a -> FieldRep f b #

(<$) :: a -> FieldRep f b -> FieldRep f a #

(Generic1 f, GTabulate (Rep1 f), Functor f) => Applicative (FieldRep f) Source # 
Instance details

Defined in Data.Functor.Field

Methods

pure :: a -> FieldRep f a #

(<*>) :: FieldRep f (a -> b) -> FieldRep f a -> FieldRep f b #

liftA2 :: (a -> b -> c) -> FieldRep f a -> FieldRep f b -> FieldRep f c #

(*>) :: FieldRep f a -> FieldRep f b -> FieldRep f b #

(<*) :: FieldRep f a -> FieldRep f b -> FieldRep f a #

(Generic1 f, GTabulate (Rep1 f), Functor f) => Distributive (FieldRep f) Source # 
Instance details

Defined in Data.Functor.Field

Methods

distribute :: Functor f0 => f0 (FieldRep f a) -> FieldRep f (f0 a) #

collect :: Functor f0 => (a -> FieldRep f b) -> f0 a -> FieldRep f (f0 b) #

distributeM :: Monad m => m (FieldRep f a) -> FieldRep f (m a) #

collectM :: Monad m => (a -> FieldRep f b) -> m a -> FieldRep f (m b) #

(Generic1 f, GTabulate (Rep1 f), Functor f) => Representable (FieldRep f) Source # 
Instance details

Defined in Data.Functor.Field

Associated Types

type Rep (FieldRep f) #

Methods

tabulate :: (Rep (FieldRep f) -> a) -> FieldRep f a #

index :: FieldRep f a -> Rep (FieldRep f) -> a #

(Generic1 f, GTabulate (Rep1 f), GUpdate (Rep1 f), Functor f) => Update (FieldRep f) Source # 
Instance details

Defined in Data.Functor.Update

Methods

overRep :: Rep (FieldRep f) -> (a -> a) -> FieldRep f a -> FieldRep f a Source #

type Rep (FieldRep f) Source # 
Instance details

Defined in Data.Functor.Field

type Rep (FieldRep f) = Field f

class FieldPaths f where Source #

Build a record where each field has a description of the field's location.

This primarily powers the Show and Portray instances of Field.

Instances

Instances details
(Generic1 rec, GFieldPaths (Rep1 rec)) => FieldPaths (Wrapped1 (Generic1 :: (Type -> Type) -> Constraint) rec) Source # 
Instance details

Defined in Data.Functor.Field

class GFieldPaths rec where Source #

The Generic1 implementation of FieldPaths.

As with GTabulate, derive this only to enable using your type as a sub-record; otherwise just derive FieldPaths directly.

Methods

gfieldPaths :: ([PathComponent] -> r) -> rec r Source #

Instances

Instances details
GFieldPaths Par1 Source # 
Instance details

Defined in Data.Functor.Field

Methods

gfieldPaths :: ([PathComponent] -> r) -> Par1 r Source #

GFieldPaths (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Field

Methods

gfieldPaths :: ([PathComponent] -> r) -> U1 r Source #

GFieldPaths rec => GFieldPaths (Rec1 rec) Source # 
Instance details

Defined in Data.Functor.Field

Methods

gfieldPaths :: ([PathComponent] -> r) -> Rec1 rec r Source #

(GFieldPaths f, GFieldPaths g) => GFieldPaths (f :*: g) Source # 
Instance details

Defined in Data.Functor.Field

Methods

gfieldPaths :: ([PathComponent] -> r) -> (f :*: g) r Source #

GFieldPaths rec => GFieldPaths (M1 D ('MetaData n m p 'True) (M1 C i (M1 S j rec))) Source # 
Instance details

Defined in Data.Functor.Field

Methods

gfieldPaths :: ([PathComponent] -> r) -> M1 D ('MetaData n m p 'True) (M1 C i (M1 S j rec)) r Source #

GFieldPaths rec => GFieldPaths (M1 D ('MetaData n m p 'False) rec) Source # 
Instance details

Defined in Data.Functor.Field

Methods

gfieldPaths :: ([PathComponent] -> r) -> M1 D ('MetaData n m p 'False) rec r Source #

GFieldPaths rec => GFieldPaths (M1 C i rec) Source # 
Instance details

Defined in Data.Functor.Field

Methods

gfieldPaths :: ([PathComponent] -> r) -> M1 C i rec r Source #

(KnownSymbol sym, GFieldPaths rec) => GFieldPaths (M1 S ('MetaSel ('Just sym) b c d) rec) Source # 
Instance details

Defined in Data.Functor.Field

Methods

gfieldPaths :: ([PathComponent] -> r) -> M1 S ('MetaSel ('Just sym) b c d) rec r Source #

(GFieldPaths f, GFieldPaths g) => GFieldPaths (f :.: g) Source # 
Instance details

Defined in Data.Functor.Field

Methods

gfieldPaths :: ([PathComponent] -> r) -> (f :.: g) r Source #

class GTabulate rec where Source #

The Generic1 implementation of tabulate for Field.

Methods

gtabulate :: (Field rec -> r) -> rec r Source #

Instances

Instances details
GTabulate Par1 Source # 
Instance details

Defined in Data.Functor.Field

Methods

gtabulate :: (Field Par1 -> r) -> Par1 r Source #

GTabulate (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Field

Methods

gtabulate :: (Field U1 -> r) -> U1 r Source #

GTabulate rec => GTabulate (Rec1 rec) Source # 
Instance details

Defined in Data.Functor.Field

Methods

gtabulate :: (Field (Rec1 rec) -> r) -> Rec1 rec r Source #

(GTabulate f, GTabulate g) => GTabulate (f :*: g) Source # 
Instance details

Defined in Data.Functor.Field

Methods

gtabulate :: (Field (f :*: g) -> r) -> (f :*: g) r Source #

GTabulate rec => GTabulate (M1 k i rec) Source # 
Instance details

Defined in Data.Functor.Field

Methods

gtabulate :: (Field (M1 k i rec) -> r) -> M1 k i rec r Source #

(GTabulate f, GTabulate g) => GTabulate (f :.: g) Source # 
Instance details

Defined in Data.Functor.Field

Methods

gtabulate :: (Field (f :.: g) -> r) -> (f :.: g) r Source #