overloaded-records-0.3.0.0: Overloaded Records based on current GHC proposal.

Copyright(c) 2016, Peter Trško
LicenseBSD3
Maintainerpeter.trsko@gmail.com
Stabilityexperimental
PortabilityDataKinds, FlexibleInstances, FunctionalDependencies, MagicHash, MultiParamTypeClasses, NoImplicitPrelude, TypeFamilies, UndecidableInstances
Safe HaskellNone
LanguageHaskell2010

Data.OverloadedRecords

Contents

Description

Magic classes for OverloadedRecordFields.

Implementation is based on: https://github.com/adamgundry/records-prototype/blob/master/CoherentPrototype.hs by Adam Gundry under MIT License.

Synopsis

Oveloaded Labels

Overloaded Record Fields

Getter

type family FieldType l s :: * Source

When accessing field named l :: Symbol of a record s :: *, then the type of the value in that field is FieldType l s.

class HasField l s a | l s -> a where Source

Definition of this class is based on: https://phabricator.haskell.org/D1687

Methods

getField :: Proxy# l -> s -> a Source

Get value of a field.

Setter

type family UpdateType l s a :: * Source

If field l :: Symbol of a record s :: * is set to new value which has type a :: *, then the modified record will have type UpdateType l s a.

class (HasField l s b, FieldType l s ~ b) => SetField l s b where Source

Methods

setField :: Proxy# l -> s -> b -> UpdateType l s b Source

Set value of a field.

data Setter s t b Source

Wrapper for a set function, lens naming convention is used for type variables. Its instance for IsLabel forces overloaded label to behave as a setter.

Instances

(SetField l s b, (~) * (UpdateType l s b) t) => IsLabel l (Setter s t b) Source 

set :: Setter s t b -> s -> b -> t Source

Extract set function from Setter. Using Setter instance for IsLabel forces overloaded label to behave as a setter.

Usage example:

newtype Bar a = Bar {_bar :: a}
  deriving Show

overloadedRecord ''Bar
>>> set bar (Bar (Just False)) Nothing
Bar {_bar = Nothing}

IsLabel For Getter and Lens

type family FromArrow a :: Bool Source

Returns True if type a is a function.

Equations

FromArrow (x -> y) = True 
FromArrow t = False 

class (z ~ FromArrow x) => IsFieldAccessor l x y z | l y -> x where Source

Distinguish between getter and lens.

Methods

fieldAccessor :: Proxy# l -> x -> y Source

Instances

(HasField l s a, (~) * (FieldType l s) a, (~) Bool (FromArrow s) False) => IsFieldAccessor l s a False Source

Overloaded getter:

Proxy# l -> r -> a
(Functor f, HasField l s a, SetField l s b, (~) * (FieldType l s) a, (~) * (UpdateType l s b) t) => IsFieldAccessor l (a -> f b) (s -> f t) True Source

Overloaded lens:

Functor f => Proxy# l -> (a -> f b) -> s -> f t