Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- data Label (label :: Symbol) value
- label :: forall label value. value -> Label label value
- label' :: forall label value. Proxy label -> value -> Label label value
- getLabel :: forall label record a. HasField label record a => record -> Label label a
- mapLabel :: forall label a b. (a -> b) -> Label label a -> Label label b
- traverseLabel :: forall label f a b. Functor f => (a -> f b) -> Label label a -> f (Label label b)
- data T2 (l1 :: Symbol) t1 (l2 :: Symbol) t2 = T2 (Label l1 t1) (Label l2 t2)
- focusOnField :: forall field rec subrec t. HasField field subrec t => (rec -> subrec) -> rec -> T2 field t "dat" rec
- monoMapT2 :: (t -> t') -> T2 l1 t l2 t -> T2 l1 t' l2 t'
- tupleToT2 :: forall l1 l2 t1 t2. (t1, t2) -> T2 l1 t1 l2 t2
- data T3 (l1 :: Symbol) t1 (l2 :: Symbol) t2 (l3 :: Symbol) t3 = T3 (Label l1 t1) (Label l2 t2) (Label l3 t3)
- monoMapT3 :: (t -> t') -> T3 l1 t l2 t l3 t -> T3 l1 t' l2 t' l3 t'
- tupleToT3 :: forall l1 l2 l3 t1 t2 t3. (t1, t2, t3) -> T3 l1 t1 l2 t2 l3 t3
- data E2 (l1 :: Symbol) t1 (l2 :: Symbol) t2
- mapE2 :: forall l1 t1 t1' l2 t2 t2'. (Label l1 t1 -> t1') -> (Label l2 t2 -> t2') -> E2 l1 t1 l2 t2 -> E2 l1 t1' l2 t2'
- monoMapE2 :: (t -> t') -> E2 l1 t l2 t -> E2 l1 t' l2 t'
- monoFoldE2 :: E2 l1 t l2 t -> t
- monoTraverseE2 :: Functor f => (t -> f t') -> E2 l1 t l2 t -> f (E2 l1 t' l2 t')
- partitionE2 :: forall l1 t1 l2 t2. [E2 l1 t1 l2 t2] -> T2 l1 [t1] l2 [t2]
- isE21 :: forall l1 t1 l2 t2. E2 l1 t1 l2 t2 -> Bool
- isE22 :: forall l2 t2 l1 t1. E2 l1 t1 l2 t2 -> Bool
- getE21 :: forall l1 t1 l2 t2. E2 l1 t1 l2 t2 -> Maybe t1
- getE22 :: forall l2 t2 l1 t1. E2 l1 t1 l2 t2 -> Maybe t2
- data E3 (l1 :: Symbol) t1 (l2 :: Symbol) t2 (l3 :: Symbol) t3
- mapE3 :: forall l1 t1 t1' l2 t2 t2' l3 t3 t3'. (Label l1 t1 -> t1') -> (Label l2 t2 -> t2') -> (Label l3 t3 -> t3') -> E3 l1 t1 l2 t2 l3 t3 -> E3 l1 t1' l2 t2' l3 t3'
Labels
data Label (label :: Symbol) value Source #
Instances
HasField (label :: Symbol) (Label label value) value Source # | Fetches the labelled value. |
Monoid value => Monoid (Label label value) Source # | |
Semigroup value => Semigroup (Label label value) Source # | |
(KnownSymbol label, Show value) => Show (Label label value) Source # | |
Eq value => Eq (Label label value) Source # | |
Ord value => Ord (Label label value) Source # | |
Defined in Label compare :: Label label value -> Label label value -> Ordering # (<) :: Label label value -> Label label value -> Bool # (<=) :: Label label value -> Label label value -> Bool # (>) :: Label label value -> Label label value -> Bool # (>=) :: Label label value -> Label label value -> Bool # max :: Label label value -> Label label value -> Label label value # min :: Label label value -> Label label value -> Label label value # |
label :: forall label value. value -> Label label value Source #
Attach a label to a value; should be used with a type application to name the label.
let f = label @"foo" f
:: Label "foo" Char
in f.foo :: Char
Use dot-syntax to get the labelled value.
label' :: forall label value. Proxy label -> value -> Label label value Source #
Attach a label to a value; Pass it a proxy with the label name in the argument type.
This is intended for passing through the label value;
you can also use label
.
let f = label' (Proxy @"foo") f
:: Label "foo" Char
in f.foo :: Char
Use dot-syntax to get the labelled value.
getLabel :: forall label record a. HasField label record a => record -> Label label a Source #
Fetch a value from a record, like getField
, but also keep it wrapped by its label.
mapLabel :: forall label a b. (a -> b) -> Label label a -> Label label b Source #
fmap
over the contents of the labbelled value. Helper.
traverseLabel :: forall label f a b. Functor f => (a -> f b) -> Label label a -> f (Label label b) Source #
traverse
over the contents of the labbelled value. Helper.
Named Tuples
data T2 (l1 :: Symbol) t1 (l2 :: Symbol) t2 Source #
A named 2-element tuple. Since the elements are named, you can access them with .
.
let t2 = T2 (label "myfield" c
) (label
"otherfield" True) :: T2 "myfield" Char "otherfield" Bool
in (
t2.myfield :: Char,
t2.otherfield :: Bool
)
Instances
HasField (l1 :: Symbol) (T2 l1 t1 l2 t2) t1 Source # | Access the first field by label |
HasField (l2 :: Symbol) (T2 l1 t1 l2 t2) t2 Source # | Access the second field by label |
(Monoid t1, Monoid t2) => Monoid (T2 l1 t1 l2 t2) Source # | |
(Semigroup t1, Semigroup t2) => Semigroup (T2 l1 t1 l2 t2) Source # | |
(KnownSymbol l1, KnownSymbol l2, Show t1, Show t2) => Show (T2 l1 t1 l2 t2) Source # | |
(Eq t1, Eq t2) => Eq (T2 l1 t1 l2 t2) Source # | |
(Ord t1, Ord t2) => Ord (T2 l1 t1 l2 t2) Source # | |
Defined in Label compare :: T2 l1 t1 l2 t2 -> T2 l1 t1 l2 t2 -> Ordering # (<) :: T2 l1 t1 l2 t2 -> T2 l1 t1 l2 t2 -> Bool # (<=) :: T2 l1 t1 l2 t2 -> T2 l1 t1 l2 t2 -> Bool # (>) :: T2 l1 t1 l2 t2 -> T2 l1 t1 l2 t2 -> Bool # (>=) :: T2 l1 t1 l2 t2 -> T2 l1 t1 l2 t2 -> Bool # |
focusOnField :: forall field rec subrec t. HasField field subrec t => (rec -> subrec) -> rec -> T2 field t "dat" rec Source #
Given a record with some field, “focus” on that field by pulling it into the first part of the T2, and put the original record into the second part of the T2.
This can be useful when you have a function that requires something with a field, but the field itself is nested somewhere in the record.
Example:
data Foo = Foo { nested :: Label "myId" Text } foo = Foo {nested = "hi"} fn :: HasField "myId" rec Text => rec -> Text fn rec = rec.myId <> "!" x = fn (focusOnField @"myId" (.nested) foo) == "hi!"
Note that you will have to give focusOnField
a type annotation of which label to use,
otherwise it cannot infer it.
monoMapT2 :: (t -> t') -> T2 l1 t l2 t -> T2 l1 t' l2 t' Source #
Map a function over all fields in the tuple. All fields have to have the same type.
tupleToT2 :: forall l1 l2 t1 t2. (t1, t2) -> T2 l1 t1 l2 t2 Source #
Convert a tuple to a T2 by giving its elements names.
tupleToT2
"left" "right" (
c
, True) :: T2 "left" Char "right" Bool
data T3 (l1 :: Symbol) t1 (l2 :: Symbol) t2 (l3 :: Symbol) t3 Source #
A named 3-element tuple. Since the elements are named, you can access them with .
. See T2
for an example.
Instances
HasField (l1 :: Symbol) (T3 l1 t1 l2 t2 l3 t3) t1 Source # | Access the first field by label |
HasField (l2 :: Symbol) (T3 l1 t1 l2 t2 l3 t3) t2 Source # | Access the second field by label |
HasField (l3 :: Symbol) (T3 l1 t1 l2 t2 l3 t3) t3 Source # | Access the third field by label |
(Monoid t1, Monoid t2, Monoid t3) => Monoid (T3 l1 t1 l2 t2 l3 t3) Source # | |
(Semigroup t1, Semigroup t2, Semigroup t3) => Semigroup (T3 l1 t1 l2 t2 l3 t3) Source # | |
(KnownSymbol l1, KnownSymbol l2, KnownSymbol l3, Show t1, Show t2, Show t3) => Show (T3 l1 t1 l2 t2 l3 t3) Source # | |
(Eq t1, Eq t2, Eq t3) => Eq (T3 l1 t1 l2 t2 l3 t3) Source # | |
(Ord t1, Ord t2, Ord t3) => Ord (T3 l1 t1 l2 t2 l3 t3) Source # | |
Defined in Label compare :: T3 l1 t1 l2 t2 l3 t3 -> T3 l1 t1 l2 t2 l3 t3 -> Ordering # (<) :: T3 l1 t1 l2 t2 l3 t3 -> T3 l1 t1 l2 t2 l3 t3 -> Bool # (<=) :: T3 l1 t1 l2 t2 l3 t3 -> T3 l1 t1 l2 t2 l3 t3 -> Bool # (>) :: T3 l1 t1 l2 t2 l3 t3 -> T3 l1 t1 l2 t2 l3 t3 -> Bool # (>=) :: T3 l1 t1 l2 t2 l3 t3 -> T3 l1 t1 l2 t2 l3 t3 -> Bool # max :: T3 l1 t1 l2 t2 l3 t3 -> T3 l1 t1 l2 t2 l3 t3 -> T3 l1 t1 l2 t2 l3 t3 # min :: T3 l1 t1 l2 t2 l3 t3 -> T3 l1 t1 l2 t2 l3 t3 -> T3 l1 t1 l2 t2 l3 t3 # |
monoMapT3 :: (t -> t') -> T3 l1 t l2 t l3 t -> T3 l1 t' l2 t' l3 t' Source #
Map a function over all fields in the tuple. All fields have to have the same type.
tupleToT3 :: forall l1 l2 l3 t1 t2 t3. (t1, t2, t3) -> T3 l1 t1 l2 t2 l3 t3 Source #
Convert a tuple to a T3 by giving its elements names.
tupleToT3
"left" "right"
"grip" (c
, True, Maybe x
) :: T3 "left" Char "right" Bool "grip" (Maybe Char)@
Named Sums/Enums
data E2 (l1 :: Symbol) t1 (l2 :: Symbol) t2 Source #
A named 2-alternative sum (“Either
with labels”).
Instances
(Bounded t1, Bounded t2) => Bounded (E2 l1 t1 l2 t2) Source # | |
Enum (E2 l1 () l2 ()) Source # | |
Defined in Label succ :: E2 l1 () l2 () -> E2 l1 () l2 () # pred :: E2 l1 () l2 () -> E2 l1 () l2 () # toEnum :: Int -> E2 l1 () l2 () # fromEnum :: E2 l1 () l2 () -> Int # enumFrom :: E2 l1 () l2 () -> [E2 l1 () l2 ()] # enumFromThen :: E2 l1 () l2 () -> E2 l1 () l2 () -> [E2 l1 () l2 ()] # enumFromTo :: E2 l1 () l2 () -> E2 l1 () l2 () -> [E2 l1 () l2 ()] # enumFromThenTo :: E2 l1 () l2 () -> E2 l1 () l2 () -> E2 l1 () l2 () -> [E2 l1 () l2 ()] # | |
(KnownSymbol l1, KnownSymbol l2, Show t1, Show t2) => Show (E2 l1 t1 l2 t2) Source # | |
(Eq t1, Eq t2) => Eq (E2 l1 t1 l2 t2) Source # | |
mapE2 :: forall l1 t1 t1' l2 t2 t2'. (Label l1 t1 -> t1') -> (Label l2 t2 -> t2') -> E2 l1 t1 l2 t2 -> E2 l1 t1' l2 t2' Source #
Map a separate function over every possibility in this enum. The label names stay the same.
Each function has access to its label, this is intentional so that you have to mention the label once (e.g. by using dot-notation), to prevent confusing the cases.
monoMapE2 :: (t -> t') -> E2 l1 t l2 t -> E2 l1 t' l2 t' Source #
Map a single function over every possiblity in this enum. All fields have to have the same type.
monoFoldE2 :: E2 l1 t l2 t -> t Source #
If ever branch of this enum has the same type, fold the enum into its contents. This loses the distinction between cases.
monoTraverseE2 :: Functor f => (t -> f t') -> E2 l1 t l2 t -> f (E2 l1 t' l2 t') Source #
Map a monadic (actually just a functor-ic) function over each possibility in this enum. All fields have to have the same type.
partitionE2 :: forall l1 t1 l2 t2. [E2 l1 t1 l2 t2] -> T2 l1 [t1] l2 [t2] Source #
Partition a list of E2 into two lists that each keep their respective label.
Like partitionEithers
, but with labels.
isE21 :: forall l1 t1 l2 t2. E2 l1 t1 l2 t2 -> Bool Source #
Check the E21 case. Use TypeApplications to make sure you are checking the right case.
>>>
isE21 @"foo" (E21 (label @"foo" 'c') :: E2 "foo" Char "bar" Int)
True
isE22 :: forall l2 t2 l1 t1. E2 l1 t1 l2 t2 -> Bool Source #
Check the E22 case. Use TypeApplications to make sure you are checking the right case.
>>>
isE22 @"bar" (E21 (label @"foo" 'c') :: E2 "foo" Char "bar" Int)
False
data E3 (l1 :: Symbol) t1 (l2 :: Symbol) t2 (l3 :: Symbol) t3 Source #
A named 3-alternative sum (“Either
with labels”).
Instances
(Bounded t1, Bounded t3) => Bounded (E3 l1 t1 l2 t2 l3 t3) Source # | |
Enum (E3 l1 () l2 () l3 ()) Source # | |
Defined in Label succ :: E3 l1 () l2 () l3 () -> E3 l1 () l2 () l3 () # pred :: E3 l1 () l2 () l3 () -> E3 l1 () l2 () l3 () # toEnum :: Int -> E3 l1 () l2 () l3 () # fromEnum :: E3 l1 () l2 () l3 () -> Int # enumFrom :: E3 l1 () l2 () l3 () -> [E3 l1 () l2 () l3 ()] # enumFromThen :: E3 l1 () l2 () l3 () -> E3 l1 () l2 () l3 () -> [E3 l1 () l2 () l3 ()] # enumFromTo :: E3 l1 () l2 () l3 () -> E3 l1 () l2 () l3 () -> [E3 l1 () l2 () l3 ()] # enumFromThenTo :: E3 l1 () l2 () l3 () -> E3 l1 () l2 () l3 () -> E3 l1 () l2 () l3 () -> [E3 l1 () l2 () l3 ()] # | |
(KnownSymbol l1, KnownSymbol l2, KnownSymbol l3, Show t1, Show t2, Show t3) => Show (E3 l1 t1 l2 t2 l3 t3) Source # | |
(Eq t1, Eq t2, Eq t3) => Eq (E3 l1 t1 l2 t2 l3 t3) Source # | |