| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Diverse.Many
Contents
Description
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
- nil :: 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
- fetchL :: forall l xs x proxy. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => proxy l -> Many xs -> 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
- replace' :: forall x y xs proxy. UniqueMember x xs => proxy x -> Many xs -> y -> Many (Replace x y xs)
- replaceL :: forall l xs x proxy. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => proxy l -> Many xs -> x -> Many xs
- replaceL' :: forall l y xs x proxy. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => proxy l -> Many xs -> y -> Many (Replace x y xs)
- replaceN :: forall n x y xs proxy. MemberAt n x xs => proxy n -> Many xs -> y -> Many xs
- replaceN' :: forall n x y xs proxy. MemberAt n x xs => proxy n -> Many xs -> y -> Many (ReplaceIndex n y xs)
- item :: forall x xs. UniqueMember x xs => Lens' (Many xs) x
- item' :: forall x y xs. UniqueMember x xs => Lens (Many xs) (Many (Replace x y xs)) x y
- itemL :: forall l xs x proxy. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => proxy l -> Lens' (Many xs) x
- itemL' :: forall l y xs x proxy. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => proxy l -> Lens (Many xs) (Many (Replace x y xs)) x y
- itemN :: forall n x xs proxy. MemberAt n x xs => proxy n -> Lens' (Many xs) x
- itemN' :: forall n x y xs proxy. MemberAt n x xs => proxy n -> Lens (Many xs) (Many (ReplaceIndex n y xs)) x y
- type Select smaller larger = AFoldable (CollectorAny (CaseSelect smaller larger) larger) (Maybe (Int, WrappedAny))
- select :: forall smaller larger. Select smaller larger => Many larger -> Many smaller
- selectL :: forall ls smaller larger proxy. (Select smaller larger, smaller ~ KindsAtLabels ls larger, IsDistinct ls, UniqueLabels ls larger) => proxy ls -> Many larger -> Many smaller
- type SelectN ns smaller larger = (AFoldable (CollectorAnyN (CaseSelectN ns smaller) 0 larger) (Maybe (Int, WrappedAny)), smaller ~ KindsAtIndices ns larger, IsDistinct ns)
- selectN :: forall ns smaller larger proxy. SelectN ns smaller larger => proxy ns -> Many larger -> Many smaller
- type Amend smaller larger = (AFoldable (CollectorAny (CaseAmend larger) smaller) (Int, WrappedAny), IsDistinct smaller)
- amend :: forall smaller larger. Amend smaller larger => Many larger -> Many smaller -> Many larger
- type Amend' smaller smaller' larger zipped = (AFoldable (CollectorAny (CaseAmend' larger) zipped) (Int, WrappedAny), IsDistinct smaller, zipped ~ Zip smaller smaller')
- amend' :: forall smaller smaller' larger proxy zipped. Amend' smaller smaller' larger zipped => proxy smaller -> Many larger -> Many smaller' -> Many (Replaces smaller smaller' larger)
- amendL :: forall ls smaller larger proxy. (Amend smaller larger, smaller ~ KindsAtLabels ls larger, IsDistinct ls, UniqueLabels ls larger) => proxy ls -> Many larger -> Many smaller -> Many larger
- amendL' :: forall ls smaller smaller' larger proxy zipped. (Amend' smaller smaller' larger zipped, smaller ~ KindsAtLabels ls larger, IsDistinct ls, UniqueLabels ls larger) => proxy ls -> Many larger -> Many smaller' -> Many (Replaces smaller smaller' larger)
- type AmendN ns smaller larger = (AFoldable (CollectorAnyN (CaseAmendN ns larger) 0 smaller) (Int, 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
- type AmendN' ns smaller smaller' larger zipped = (AFoldable (CollectorAnyN (CaseAmendN' ns larger) 0 zipped) (Int, WrappedAny), smaller ~ KindsAtIndices ns larger, IsDistinct ns, zipped ~ Zip smaller smaller')
- amendN' :: forall ns smaller smaller' larger proxy zipped. AmendN' ns smaller smaller' larger zipped => proxy ns -> Many larger -> Many smaller' -> Many (ReplacesIndex ns smaller' larger)
- project :: forall smaller larger. (Select smaller larger, Amend smaller larger) => Lens' (Many larger) (Many smaller)
- project' :: forall smaller smaller' larger zipped. (Select smaller larger, Amend' smaller smaller' larger zipped) => Lens (Many larger) (Many (Replaces smaller smaller' larger)) (Many smaller) (Many smaller')
- projectL :: forall ls smaller larger proxy. (Select smaller larger, Amend smaller larger, smaller ~ KindsAtLabels ls larger, IsDistinct ls, UniqueLabels ls larger) => proxy ls -> Lens' (Many larger) (Many smaller)
- projectL' :: forall ls smaller smaller' larger proxy zipped. (Select smaller larger, Amend' smaller smaller' larger zipped, smaller ~ KindsAtLabels ls larger, IsDistinct ls, UniqueLabels ls larger) => proxy ls -> Lens (Many larger) (Many (Replaces smaller smaller' larger)) (Many smaller) (Many smaller')
- projectN :: forall ns smaller larger proxy. (SelectN ns smaller larger, AmendN ns smaller larger) => proxy ns -> Lens' (Many larger) (Many smaller)
- projectN' :: forall ns smaller smaller' larger proxy zipped. (SelectN ns smaller larger, AmendN' ns smaller smaller' larger zipped) => proxy ns -> Lens (Many larger) (Many (ReplacesIndex ns smaller' larger)) (Many smaller) (Many smaller')
- forMany :: c xs r -> Many xs -> Collector c xs r
- collect :: Many xs -> c xs r -> Collector c xs r
- forManyN :: c n xs r -> Many xs -> CollectorN c n xs r
- collectN :: Many xs -> c n xs r -> CollectorN 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:
fetchandreplace - getter/setter for multiple fields:
selectandamend - folds:
forManyorcollect
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:
fetchNandreplaceN - getter/setter for multiple fields:
selectNandamendN - folds:
forManyNorcollectN
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
Instances
| Eq (Many_ xs) => Eq (Many xs) Source # | Two |
| Ord (Many_ xs) => Ord (Many xs) Source # | Two |
| Read (Many_ xs) => Read (Many xs) Source # | read "5 . False . |
| Show (Many_ xs) => Show (Many xs) Source # | Two |
| Generic (Many ((:) Type x xs)) Source # | A |
| Generic (Many ([] Type)) Source # | |
| 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.
Instances
| 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 #
fetchL :: forall l xs x proxy. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => proxy l -> Many xs -> x Source #
Setter for single field
replace' :: forall x y xs proxy. UniqueMember x xs => proxy x -> Many xs -> y -> Many (Replace x y xs) Source #
replaceL :: forall l xs x proxy. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => proxy l -> Many xs -> x -> Many xs Source #
Setter by unique label. Set the field with label l.
let y = (5 :: Int)./False./Tagged @Foo 'X'./Tagged @"Hello" (6 :: Int)./nilreplaceL@Foo Proxy y (Tagged @Foo 'Y') `shouldBe` (5 :: Int)./False./Tagged @Foo 'Y'./Tagged @"Hello" (6 :: Int)./nilreplaceL@"Hello" Proxy y (Tagged @"Hello" 7) `shouldBe` (5 :: Int)./False./Tagged @Foo 'X'./Tagged @"Hello" (7 :: Int)./nil
replaceL' :: forall l y xs x proxy. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => proxy l -> Many xs -> y -> Many (Replace x y xs) Source #
Polymorphic setter by unique type. Set the field with type x, and replace with type y
let y = (5 :: Int)./False./Tagged @Foo 'X'./Tagged @"Hello" (6 :: Int)./nilreplaceL' @Foo Proxy y (Tagged @Bar 'Y')shouldBe(5 :: Int)./False./TaggedBarHello (6 :: Int)Y./Tagged./nilreplaceL' @"Hello" Proxy y (Tagged @"Hello" False) `shouldBe` (5 :: Int)./False./Tagged @Foo 'X'./Tagged @"Hello" False./nil
replaceN' :: forall n x y xs proxy. MemberAt n x xs => proxy n -> Many xs -> y -> Many (ReplaceIndex n y xs) Source #
Polymorphic version of replaceN
Lens for a single field
item' :: forall x y xs. UniqueMember x xs => Lens (Many xs) (Many (Replace x y xs)) x y Source #
Polymorphic version of item
itemL :: forall l xs x proxy. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => proxy l -> Lens' (Many xs) x Source #
itemL' :: forall l y xs x proxy. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => proxy l -> Lens (Many xs) (Many (Replace x y xs)) x y Source #
itemN' :: forall n x y xs proxy. MemberAt n x xs => proxy n -> Lens (Many xs) (Many (ReplaceIndex n y xs)) x y Source #
Polymorphic version of itemN
Multiple fields
Getter for multiple fields
type Select smaller larger = AFoldable (CollectorAny (CaseSelect smaller larger) larger) (Maybe (Int, WrappedAny)) Source #
A friendlier type constraint synomyn for select
select :: forall smaller larger. Select 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'./nilselect@'[Bool, Char] x `shouldBe` False./'X'./nil
selectL :: forall ls smaller larger proxy. (Select smaller larger, smaller ~ KindsAtLabels ls larger, IsDistinct ls, UniqueLabels ls larger) => proxy ls -> Many larger -> Many smaller Source #
A variation of select which selects by labels
let x = False./Tagged @"Hi" (5 :: Int)./Tagged @Foo False./Tagged @Bar 'X'./Tagged @"Bye"O./nilselectL@'[Foo, Bar] Proxy x `shouldBe` Tagged @Foo False./Tagged @Bar 'X'./nilselectL@'["Hi", "Bye"] Proxy x `shouldBe` Tagged @"Hi" (5 :: Int)./Tagged @"Bye" 'O'./nil
type SelectN ns smaller larger = (AFoldable (CollectorAnyN (CaseSelectN ns smaller) 0 larger) (Maybe (Int, WrappedAny)), smaller ~ KindsAtIndices ns larger, IsDistinct ns) Source #
A friendlier type constraint synomyn for selectN
selectN :: forall ns smaller larger proxy. SelectN ns smaller larger => proxy ns -> Many larger -> Many smaller Source #
A variation of select 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'./nilselectN(Proxy @'[5, 4, 0]) x `shouldBe` Just 'A'./(6 :: Int)./(5 ::Int)./nil
Setter for multiple fields
type Amend smaller larger = (AFoldable (CollectorAny (CaseAmend larger) smaller) (Int, 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 #
type Amend' smaller smaller' larger zipped = (AFoldable (CollectorAny (CaseAmend' larger) zipped) (Int, WrappedAny), IsDistinct smaller, zipped ~ Zip smaller smaller') Source #
A friendlier type constraint synomyn for amend'
amend' :: forall smaller smaller' larger proxy zipped. Amend' smaller smaller' larger zipped => proxy smaller -> Many larger -> Many smaller' -> Many (Replaces smaller smaller' larger) Source #
amendL :: forall ls smaller larger proxy. (Amend smaller larger, smaller ~ KindsAtLabels ls larger, IsDistinct ls, UniqueLabels ls larger) => proxy ls -> Many larger -> Many smaller -> Many larger Source #
A variation of amend which amends via labels.
let x = False . Tagged @"Hi" (5 :: Int) . Tagged @Foo False . Tagged @Bar 'X' . Tagged @"Bye" 'O' ./nilamendL@'[Foo, Bar] Proxy x (Tagged @Foo True . Tagged @Bar 'Y' . nil)shouldBeFalse . Tagged @"Hi" (5 :: Int) . Tagged @Foo True . Tagged @Bar 'Y' . Tagged @"Bye" 'O' ./nilamendL@'["Hi", "Bye"] Proxy x (Tagged @"Hi" (6 :: Int) . Tagged @"Bye" 'P' . nil)shouldBeFalse . Tagged @"Hi" (6 :: Int) . Tagged @Foo False . Tagged @Bar 'X' . Tagged @"Bye" 'P' ./nil
amendL' :: forall ls smaller smaller' larger proxy zipped. (Amend' smaller smaller' larger zipped, smaller ~ KindsAtLabels ls larger, IsDistinct ls, UniqueLabels ls larger) => proxy ls -> Many larger -> Many smaller' -> Many (Replaces smaller smaller' larger) Source #
A variation of amend which amends via labels.
let x = False./Tagged @"Hi" (5 :: Int)./Tagged @Foo False./Tagged @BarX./Tagged @"Bye" 'O'./nilamendL'@'[Foo, Bar] Proxy x ('Y'./True./nil) `shouldBe` False./Tagged @"Hi" (5 :: Int)./'Y'./True./Tagged @"Bye" 'O'./nilamendL'@'["Hi", "Bye"] Proxy x (True./Tagged @"Changed" True./nil) `shouldBe` False./True./Tagged @Foo False./Tagged @Bar 'X'./Tagged @"Changed" True./nil
type AmendN ns smaller larger = (AFoldable (CollectorAnyN (CaseAmendN ns larger) 0 smaller) (Int, 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'./nilamendN(Proxy @'[5, 4, 0]) x (Just 'B'./(8 :: Int)./(4 ::Int)./nil) `shouldBe` (4 :: Int)./False./'X'./Just 'O'./(8 :: Int)./Just 'B'./nil
type AmendN' ns smaller smaller' larger zipped = (AFoldable (CollectorAnyN (CaseAmendN' ns larger) 0 zipped) (Int, WrappedAny), smaller ~ KindsAtIndices ns larger, IsDistinct ns, zipped ~ Zip smaller smaller') Source #
A friendlier type constraint synomyn for amendN
amendN' :: forall ns smaller smaller' larger proxy zipped. AmendN' ns smaller smaller' larger zipped => proxy ns -> Many larger -> Many smaller' -> Many (ReplacesIndex ns smaller' larger) Source #
A polymorphic variation of amendN
Lens for multiple fields
project :: forall smaller larger. (Select smaller larger, Amend smaller larger) => Lens' (Many larger) (Many smaller) Source #
select (view project) and amend (set project) in Lens' form.
project=lensselectamend
let x = (5 :: Int)./False./'X'./Just 'O'./nilx^.(project@'[Int, Maybe Char]) `shouldBe` (5 :: Int)./Just 'O'./nil(x&(project@'[Int, Maybe Char]).~((6 :: Int)./JustP./nil)) `shouldBe` (6 :: Int)./False./'X'./Just 'P'./nil
project' :: forall smaller smaller' larger zipped. (Select smaller larger, Amend' smaller smaller' larger zipped) => Lens (Many larger) (Many (Replaces smaller smaller' larger)) (Many smaller) (Many smaller') Source #
Polymorphic version of project'
projectL :: forall ls smaller larger proxy. (Select smaller larger, Amend smaller larger, smaller ~ KindsAtLabels ls larger, IsDistinct ls, UniqueLabels ls larger) => proxy ls -> Lens' (Many larger) (Many smaller) Source #
selectL (view projectL) and amendL (set projectL) in Lens' form.
let x = False./Tagged @"Hi" (5 :: Int)./Tagged @Foo False./Tagged @Bar 'X'./Tagged @"Bye" 'O'./nilx^.(projectL@'[Foo, Bar] Proxy) `shouldBe` Tagged @Foo False./Tagged @Bar 'X'./nil (x&(projectL@'["Hi", "Bye"] Proxy).~(Tagged @"Hi" (6 :: Int)./Tagged @"Bye" 'P'./nil)) 'shouldBeFalse./Tagged @"Hi" (6 :: Int)./Tagged @Foo False./Tagged @Bar 'X'./Tagged @"Bye" 'P'./nil
projectL' :: forall ls smaller smaller' larger proxy zipped. (Select smaller larger, Amend' smaller smaller' larger zipped, smaller ~ KindsAtLabels ls larger, IsDistinct ls, UniqueLabels ls larger) => proxy ls -> Lens (Many larger) (Many (Replaces smaller smaller' larger)) (Many smaller) (Many smaller') Source #
Polymorphic version of projectL'
let x = False./Tagged @"Hi" (5 :: Int)./Tagged @Foo False./Tagged @Bar 'X'./Tagged @"Bye" 'O'./nil(x&(projectL'@'["Hi", "Bye"] Proxy).~(True./Tagged @"Changed" False./nil)) `shouldBe` False./True./Tagged @Foo False./Tagged @Bar 'X'./Tagged @"Changed" False./nil
projectN :: forall ns smaller larger proxy. (SelectN ns smaller larger, AmendN ns smaller larger) => proxy ns -> Lens' (Many larger) (Many smaller) Source #
selectN (view projectN) and amendN (set projectN) in Lens' form.
projectN=lensselectNamendN
let x = (5 :: Int)./False./'X'./Just 'O'./(6 :: Int)./Just 'A'./nilx^.(projectN@'[5, 4, 0] Proxy) `shouldBe` Just 'A'./(6 :: Int)./(5 ::Int)./nil(x&(projectN@'[5, 4, 0] Proxy).~(Just 'B'./(8 :: Int)./(4 ::Int)./nil)) `shouldBe` (4 :: Int)./False./'X'./Just 'O'./(8 :: Int)./Just 'B'./nil
projectN' :: forall ns smaller smaller' larger proxy zipped. (SelectN ns smaller larger, AmendN' ns smaller smaller' larger zipped) => proxy ns -> Lens (Many larger) (Many (ReplacesIndex ns smaller' larger)) (Many smaller) (Many smaller') Source #
Polymorphic version of projectN
Destruction
By type
forMany :: c xs r -> Many xs -> Collector 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'./nily = show @Int./show @Char./show @(Maybe Char)./show @Bool./nilafoldr(:) [] (forMany(casesy) x) `shouldBe` ["5", "False", "'X'", "Just 'O'", "6", "Just 'A'"]
By Nat index offset
forManyN :: c n xs r -> Many xs -> CollectorN 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'./nily = show @Int./show @Bool./show @Char./show @(Maybe Char)./show @Int./show @(Maybe Char)./nilafoldr(:) [] (forManyN(casesNy) x) `shouldBe` ["5", "False", "'X'", "Just 'O'", "6", "Just 'A'"]
collectN :: Many xs -> c n xs r -> CollectorN c n xs r Source #
This is flip forManyN
let x = (5 :: Int)./False./'X'./Just 'O'./(6 :: Int)./Just 'A'./nily = show @Int./show @Bool./show @Char./show @(Maybe Char)./show @Int./show @(Maybe Char)./nilafoldr(:) [] (collectNx (casesNy)) `shouldBe` ["5", "False", "'X'", "Just 'O'", "6", "Just 'A'"]