Safe Haskell | None |
---|---|
Language | Haskell2010 |
Re-export Many without the constructor
- data Many xs
- class IsMany t xs a where
- fromMany' :: IsMany Tagged xs a => Many xs -> a
- toMany' :: IsMany Tagged xs a => a -> Many xs
- _Many :: IsMany t xs a => Iso' (Many xs) (t xs a)
- _Many' :: IsMany Tagged xs a => Iso' (Many xs) a
- nul :: Many '[]
- single :: x -> Many '[x]
- prefix :: x -> Many xs -> Many (x ': xs)
- (./) :: x -> Many xs -> Many (x ': xs)
- postfix :: Many xs -> y -> Many (Append xs '[y])
- (\.) :: Many xs -> y -> Many (Append xs '[y])
- append :: Many xs -> Many ys -> Many (Append xs ys)
- (/./) :: Many xs -> Many ys -> Many (Append xs ys)
- front :: Many (x ': xs) -> x
- back :: Many (x ': xs) -> Last (x ': xs)
- aft :: Many (x ': xs) -> Many xs
- fore :: Many (x ': xs) -> Many (Init (x ': xs))
- fetch :: forall x xs. UniqueMember x xs => Many xs -> x
- (.^.) :: forall x xs proxy. UniqueMember x xs => Many xs -> proxy x -> x
- fetchN :: forall n x xs proxy. MemberAt n x xs => proxy n -> Many xs -> x
- replace :: forall x xs. UniqueMember x xs => Many xs -> x -> Many xs
- (.~.) :: forall x xs. UniqueMember x xs => Many xs -> x -> Many xs
- replaceN :: forall n x xs proxy. MemberAt n x xs => proxy n -> Many xs -> x -> Many xs
- item :: forall x xs. UniqueMember x xs => Lens' (Many xs) x
- itemN :: forall n x xs proxy. MemberAt n x xs => proxy n -> Lens' (Many xs) x
- type Narrow smaller larger = AFoldable (Collector (Via (CaseNarrow smaller larger)) larger) [(Key, WrappedAny)]
- narrow :: forall smaller larger. Narrow smaller larger => Many larger -> Many smaller
- (\^.) :: forall smaller larger proxy. Narrow smaller larger => Many larger -> proxy smaller -> Many smaller
- type NarrowN ns smaller larger = (AFoldable (CollectorN (ViaN (CaseNarrowN ns smaller)) 0 larger) [(Key, WrappedAny)], smaller ~ KindsAtIndices ns larger, IsDistinct ns)
- narrowN :: forall ns smaller larger proxy. NarrowN ns smaller larger => proxy ns -> Many larger -> Many smaller
- type Amend smaller larger = (AFoldable (Collector (Via (CaseAmend larger)) smaller) (Key, WrappedAny), IsDistinct smaller)
- amend :: forall smaller larger. Amend smaller larger => Many larger -> Many smaller -> Many larger
- (\~.) :: forall smaller larger. Amend smaller larger => Many larger -> Many smaller -> Many larger
- type AmendN ns smaller larger = (AFoldable (CollectorN (ViaN (CaseAmendN ns larger)) 0 smaller) (Key, WrappedAny), smaller ~ KindsAtIndices ns larger, IsDistinct ns)
- amendN :: forall ns smaller larger proxy. AmendN ns smaller larger => proxy ns -> Many larger -> Many smaller -> Many larger
- project :: forall smaller larger. (Narrow smaller larger, Amend smaller larger) => Lens' (Many larger) (Many smaller)
- projectN :: forall ns smaller larger proxy. (NarrowN ns smaller larger, AmendN ns smaller larger) => proxy ns -> Lens' (Many larger) (Many smaller)
- data Via c xs r
- via :: c xs r -> Many xs -> Via c xs r
- forMany :: c xs r -> Many xs -> Collector (Via c) xs r
- collect :: Many xs -> c xs r -> Collector (Via c) xs r
- data ViaN c n xs r
- viaN :: c n xs r -> Many xs -> ViaN c n xs r
- forManyN :: c n xs r -> Many xs -> CollectorN (ViaN c) n xs r
- collectN :: Many xs -> c n xs r -> CollectorN (ViaN c) n xs r
Many
type
A Many is an anonymous product type (also know as polymorphic record), with no limit on the number of fields.
The following functions are available can be used to manipulate unique fields
- getter/setter for single field:
fetch
andreplace
- getter/setter for multiple fields:
narrow
andamend
- folds:
forMany
orcollect
These functions are type specified. This means labels are not required because the types themselves can be used to access the 'Many. It is a compile error to use those functions for duplicate fields.
For duplicate fields, Nat-indexed versions of the functions are available:
- getter/setter for single field:
fetchN
andreplaceN
- getter/setter for multiple fields:
narrowN
andamendN
- folds:
forManyN
orcollectN
Encoding: The record is encoded as (Offset, Map Int Any). This encoding should reasonabily efficient for any number of fields.
The map Key is index + offset of the type in the typelist.
The Offset is used to allow efficient cons prefix
.
Key = Index of type in typelist + Offset
The constructor will guarantee the correct number and types of the elements. The constructor is only exported in the Data.Diverse.Many.Internal module
AFoldable (Collector * (EmitEqMany *) xs) Bool => Eq (Many xs) Source # | Two |
(Eq (Many xs), AFoldable (Collector * (EmitOrdMany *) xs) Ordering) => Ord (Many xs) Source # | Two |
AFoldable (Collector0 * (EmitReadMany *) xs) (ReadPrec [(Key, WrappedAny)]) => Read (Many xs) Source # | read "5 . False . |
AFoldable (Collector0 * (EmitShowMany *) xs) ShowS => Show (Many xs) Source # | read "5 . False . |
Generic (Many ((:) Type x xs)) Source # | A |
Generic (Many ([] Type)) Source # | Inferred role is phantom which is incorrect |
type Rep (Many ((:) Type x xs)) Source # | |
type Rep (Many ([] Type)) Source # | |
Isomorphism
class IsMany t xs a where Source #
This instance allows converting to and from Many There are instances for converting tuples of up to size 15.
IsMany * (Tagged [Type]) ([] Type) () Source # | These instances add about 7 seconds to the compile time! |
IsMany * (Tagged [Type]) ((:) Type a ([] Type)) a Source # | This single field instance is the reason for |
IsMany * (Tagged [Type]) ((:) Type a ((:) Type b ([] Type))) (a, b) Source # | |
IsMany * (Tagged [Type]) ((:) Type a ((:) Type b ((:) Type c ([] Type)))) (a, b, c) Source # | |
IsMany * (Tagged [Type]) ((:) Type a ((:) Type b ((:) Type c ((:) Type d ([] Type))))) (a, b, c, d) Source # | |
IsMany * (Tagged [Type]) ((:) Type a ((:) Type b ((:) Type c ((:) Type d ((:) Type e ([] Type)))))) (a, b, c, d, e) Source # | |
IsMany * (Tagged [Type]) ((:) Type a ((:) Type b ((:) Type c ((:) Type d ((:) Type e ((:) Type f ([] Type))))))) (a, b, c, d, e, f) Source # | |
IsMany * (Tagged [Type]) ((:) Type a ((:) Type b ((:) Type c ((:) Type d ((:) Type e ((:) Type f ((:) Type g ([] Type)))))))) (a, b, c, d, e, f, g) Source # | |
IsMany * (Tagged [Type]) ((:) Type a ((:) Type b ((:) Type c ((:) Type d ((:) Type e ((:) Type f ((:) Type g ((:) Type h ([] Type))))))))) (a, b, c, d, e, f, g, h) Source # | |
IsMany * (Tagged [Type]) ((:) Type a ((:) Type b ((:) Type c ((:) Type d ((:) Type e ((:) Type f ((:) Type g ((:) Type h ((:) Type i ([] Type)))))))))) (a, b, c, d, e, f, g, h, i) Source # | |
IsMany * (Tagged [Type]) ((:) Type a ((:) Type b ((:) Type c ((:) Type d ((:) Type e ((:) Type f ((:) Type g ((:) Type h ((:) Type i ((:) Type j ([] Type))))))))))) (a, b, c, d, e, f, g, h, i, j) Source # | |
IsMany * (Tagged [Type]) ((:) Type a ((:) Type b ((:) Type c ((:) Type d ((:) Type e ((:) Type f ((:) Type g ((:) Type h ((:) Type i ((:) Type j ((:) Type k ([] Type)))))))))))) (a, b, c, d, e, f, g, h, i, j, k) Source # | |
IsMany * (Tagged [Type]) ((:) Type a ((:) Type b ((:) Type c ((:) Type d ((:) Type e ((:) Type f ((:) Type g ((:) Type h ((:) Type i ((:) Type j ((:) Type k ((:) Type l ([] Type))))))))))))) (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
IsMany * (Tagged [Type]) ((:) Type a ((:) Type b ((:) Type c ((:) Type d ((:) Type e ((:) Type f ((:) Type g ((:) Type h ((:) Type i ((:) Type j ((:) Type k ((:) Type l ((:) Type m ([] Type)))))))))))))) (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
IsMany * (Tagged [Type]) ((:) Type a ((:) Type b ((:) Type c ((:) Type d ((:) Type e ((:) Type f ((:) Type g ((:) Type h ((:) Type i ((:) Type j ((:) Type k ((:) Type l ((:) Type m ((:) Type n ([] Type))))))))))))))) (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
IsMany * (Tagged [Type]) ((:) Type a ((:) Type b ((:) Type c ((:) Type d ((:) Type e ((:) Type f ((:) Type g ((:) Type h ((:) Type i ((:) Type j ((:) Type k ((:) Type l ((:) Type m ((:) Type n ((:) Type o ([] Type)))))))))))))))) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
fromMany' :: IsMany Tagged xs a => Many xs -> a Source #
Converts from a Many to a value (eg a tuple), via a Tagged wrapper
Construction
prefix :: x -> Many xs -> Many (x ': xs) infixr 5 Source #
Add an element to the left of a Many.
Not named cons
to avoid conflict with cons
Simple queries
front :: Many (x ': xs) -> x Source #
Extract the first element of a Many, which guaranteed to be non-empty.
Analogous to head
aft :: Many (x ': xs) -> Many xs Source #
Extract the elements after the front of a Many, which guaranteed to be non-empty.
Analogous to tail
Single field
Getter for single field
fetch :: forall x xs. UniqueMember x xs => Many xs -> x Source #
(.^.) :: forall x xs proxy. UniqueMember x xs => Many xs -> proxy x -> x infixl 8 Source #
fetchN :: forall n x xs proxy. MemberAt n x xs => proxy n -> Many xs -> x Source #
Getter by index. Get the value of the field at index type-level Nat n
getchN (Proxy @2) t
Setter for single field
Lens for a single field
Multiple fields
Getter for multiple fields
type Narrow smaller larger = AFoldable (Collector (Via (CaseNarrow smaller larger)) larger) [(Key, WrappedAny)] Source #
A friendlier type constraint synomyn for narrow
narrow :: forall smaller larger. Narrow smaller larger => Many larger -> Many smaller Source #
Construct a Many
with a smaller number of fields than the original.
Analogous to fetch
getter but for multiple fields.
This can also be used to reorder fields in the original Many
.
let x = (5 :: Int)./
False./
'X'./
Just 'O'./
(6 :: Int)./
Just 'A'./
nul
narrow
@'[Bool, Char] x `shouldBe` False./
'X'./
nul
(\^.) :: forall smaller larger proxy. Narrow smaller larger => Many larger -> proxy smaller -> Many smaller infixl 8 Source #
type NarrowN ns smaller larger = (AFoldable (CollectorN (ViaN (CaseNarrowN ns smaller)) 0 larger) [(Key, WrappedAny)], smaller ~ KindsAtIndices ns larger, IsDistinct ns) Source #
A friendlier type constraint synomyn for narrowN
narrowN :: forall ns smaller larger proxy. NarrowN ns smaller larger => proxy ns -> Many larger -> Many smaller Source #
A variation of narrow
which uses a Nat list n
to specify how to reorder the fields, where
indices[branch_idx] = tree_idx@
This variation allows smaller
or larger
to contain indistinct since
the mapping is specified by indicies
.
let x = (5 :: Int)./
False./
'X'./
Just 'O'./
(6 :: Int)./
Just 'A'./
nul
narrowN
(Proxy @'[5, 4, 0]) x `shouldBe` Just 'A'./
(6 :: Int)./
(5 ::Int)./
nul
Setter for multiple fields
type Amend smaller larger = (AFoldable (Collector (Via (CaseAmend larger)) smaller) (Key, WrappedAny), IsDistinct smaller) Source #
A friendlier type constraint synomyn for amend
amend :: forall smaller larger. Amend smaller larger => Many larger -> Many smaller -> Many larger Source #
(\~.) :: forall smaller larger. Amend smaller larger => Many larger -> Many smaller -> Many larger infixl 1 Source #
infix version of amend
. Mnemonic: Like 'Control.Lens.(.~)' but with an extra '\' (narrow to the right) in front.
Mnemonic: Like backwards 'Control.Lens.(^.)' but with an extra '\' (narrow to the right) in front.
let x = (5 :: Int)./
False./
'X'./
Just 'O'./
nul
(x\~.
(6 :: Int)./
Just 'P'./
nul
) `shouldBe` (6 :: Int)./
False./
'X'./
Just 'P'./
nul
type AmendN ns smaller larger = (AFoldable (CollectorN (ViaN (CaseAmendN ns larger)) 0 smaller) (Key, WrappedAny), smaller ~ KindsAtIndices ns larger, IsDistinct ns) Source #
A friendlier type constraint synomyn for amendN
amendN :: forall ns smaller larger proxy. AmendN ns smaller larger => proxy ns -> Many larger -> Many smaller -> Many larger Source #
A variation of amend
which uses a Nat list n
to specify how to reorder the fields, where
indices[branch_idx] = tree_idx@
This variation allows smaller
or larger
to contain indistinct since
the mapping is specified by indicies
.
let x = (5 :: Int)./
False./
'X'./
Just 'O'./
(6 :: Int)./
Just 'A'./
nul
amendN
(Proxy @'[5, 4, 0]) x (Just 'B'./
(8 :: Int)./
(4 ::Int)./
nul
) `shouldBe` (4 :: Int)./
False./
'X'./
Just 'O'./
(8 :: Int)./
Just 'B'./
nul
Lens for multiple fields
project :: forall smaller larger. (Narrow smaller larger, Amend smaller larger) => Lens' (Many larger) (Many smaller) Source #
narrow
(view
project
) and amend
(set
project
) in Lens'
form.
project
=lens
narrow
amend
let x = (5 :: Int)./
False./
'X'./
Just 'O'./
nul
x^.
(project
@'[Int, Maybe Char]) `shouldBe` (5 :: Int)./
Just 'O'./
nul
(x&
(project
@'[Int, Maybe Char]).~
((6 :: Int)./
JustP
./
nul
)) `shouldBe` (6 :: Int)./
False./
'X'./
Just 'P'./
nul
projectN :: forall ns smaller larger proxy. (NarrowN ns smaller larger, AmendN ns smaller larger) => proxy ns -> Lens' (Many larger) (Many smaller) Source #
narrowN
(view
projectN
) and amendN
(set
projectN
) in Lens'
form.
projectN
=lens
narrowN
amendN
let x = (5 :: Int)./
False./
'X'./
Just 'O'./
(6 :: Int)./
Just 'A'./
nul
x^.
(projectN
@'[5, 4, 0] Proxy) `shouldBe` Just 'A'./
(6 :: Int)./
(5 ::Int)./
nul
(x&
(projectN
@'[5, 4, 0] Proxy).~
(Just 'B'./
(8 :: Int)./
(4 ::Int)./
nul)) `shouldBe` (4 :: Int)./
False./
'X'./
Just 'O'./
(8 :: Int)./
Just 'B'./
nul
Destruction
By type
Wraps a Case
into an instance of Emit
, reiterate
ing and feeding Case
with the value from the Many
and emit
ting the results.
Internally, this holds the left-over [(k, v)] from the original Many
for the remaining typelist xs
.
That is the first v in the (k, v) is of type x
, and the length of the list is equal to the length of xs
.
via :: c xs r -> Many xs -> Via c xs r Source #
Creates an Via
safely, so that the invariant of "typelist to the value list type and size" holds.
forMany :: c xs r -> Many xs -> Collector (Via c) xs r Source #
Folds any Many
, even with indistinct types.
Given distinct handlers for the fields in Many
, create a Collector
of the results of running the handlers over the fields in Many
.
The Collector
is AFoldable
to combine the results.
let x = (5 :: Int)./
False./
'X'./
Just 'O'./
(6 :: Int)./
Just 'A'./
nul
y = show @Int./
show @Char./
show @(Maybe Char)./
show @Bool./
nul
afoldr
(:) [] (forMany
(cases
y) x) `shouldBe` ["5", "False", "'X'", "Just 'O'", "6", "Just 'A'"]
By Nat index offset
A variation of Via
which reiterateN
instead.
viaN :: c n xs r -> Many xs -> ViaN c n xs r Source #
Creates an ViaN
safely, so that the invariant of "typelist to the value list type and size" holds.
forManyN :: c n xs r -> Many xs -> CollectorN (ViaN c) n xs r Source #
Folds any Many
, even with indistinct types.
Given index handlers for the fields in Many
, create a CollectorN
of the results of running the handlers over the fields in Many
.
The CollectorN
is AFoldable
to combine the results.
let x = (5 :: Int)./
False./
'X'./
Just 'O'./
(6 :: Int)./
Just 'A'./
nul
y = show @Int./
show @Bool./
show @Char./
show @(Maybe Char)./
show @Int./
show @(Maybe Char)./
nul
afoldr
(:) [] (forManyN
(casesN
y) x) `shouldBe` ["5", "False", "'X'", "Just 'O'", "6", "Just 'A'"]
collectN :: Many xs -> c n xs r -> CollectorN (ViaN c) n xs r Source #
This is flip
forManyN
let x = (5 :: Int)./
False./
'X'./
Just 'O'./
(6 :: Int)./
Just 'A'./
nul
y = show @Int./
show @Bool./
show @Char./
show @(Maybe Char)./
show @Int./
show @(Maybe Char)./
nul
afoldr
(:) [] (collectN
x (casesN
y)) `shouldBe` ["5", "False", "'X'", "Just 'O'", "6", "Just 'A'"]