Copyright | (c) 2016, Peter Trško |
---|---|
License | BSD3 |
Maintainer | peter.trsko@gmail.com |
Stability | experimental |
Portability | DataKinds, FlexibleInstances, FunctionalDependencies, MagicHash, MultiParamTypeClasses, NoImplicitPrelude, TypeFamilies, UndecidableInstances |
Safe Haskell | None |
Language | Haskell2010 |
Magic classes for OverloadedRecordFields.
Implementation is based on: https://github.com/adamgundry/records-prototype/blob/master/CoherentPrototype.hs by Adam Gundry under MIT License.
- module Data.OverloadedLabels
- type family FieldType l s :: *
- class HasField l s a | l s -> a where
- type family UpdateType l s a :: *
- class (HasField l s b, FieldType l s ~ b) => SetField l s b where
- setField :: Proxy# l -> s -> b -> UpdateType l s b
- data Setter s t b
- set :: Setter s t b -> s -> b -> t
- type family FromArrow a :: Bool
- class (z ~ FromArrow x) => IsFieldAccessor l x y z | l y -> x where
- fieldAccessor :: Proxy# l -> x -> y
Oveloaded Labels
module Data.OverloadedLabels
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
type FieldType "fieldDerivation" DeriveOverloadedRecordsParams = FieldDerivation Source |
class HasField l s a | l s -> a where Source
Definition of this class is based on: https://phabricator.haskell.org/D1687
HasField "fieldDerivation" DeriveOverloadedRecordsParams FieldDerivation Source |
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
type UpdateType "fieldDerivation" DeriveOverloadedRecordsParams FieldDerivation = DeriveOverloadedRecordsParams Source |
class (HasField l s b, FieldType l s ~ b) => SetField l s b where Source
setField :: Proxy# l -> s -> b -> UpdateType l s b Source
Set value of a field.
SetField "fieldDerivation" DeriveOverloadedRecordsParams FieldDerivation 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.
(SetField l s b, (~) * (UpdateType l s b) t) => IsLabel l (Setter s t b) Source |
IsLabel For Getter and Lens
class (z ~ FromArrow x) => IsFieldAccessor l x y z | l y -> x where Source
Distinguish between getter and lens.
fieldAccessor :: Proxy# l -> x -> y Source
(HasField l s a, (~) * (FieldType l s) a, (~) Bool (FromArrow s) False) => IsFieldAccessor l s a False Source | Overloaded getter:
|
(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:
|