| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Diverse.Lens.Many
- _Many :: IsMany t xs a => Iso' (Many xs) (t xs a)
- _Many' :: IsMany Tagged xs a => Iso' (Many xs) a
- class HasItem a b s t | s a b -> t, t a b -> s where
- class HasItem' a s where
- class HasItemL (l :: k) a b s t | s l -> a, t l -> b, s l b -> t, t l a -> s where
- class HasItemL' (l :: k) a s | s l -> a where
- class HasItemTag (l :: k) a b s t | s l -> a, t l -> b, s l b -> t, t l a -> s where
- class HasItemTag' (l :: k) a s where
- class HasItemN (n :: Nat) a b s t | s n -> a, t n -> b, s n b -> t, t n a -> s where
- class HasItemN' (n :: Nat) a s | s n -> a where
- type Project (smaller :: [Type]) (smaller' :: [Type]) (larger :: [Type]) (larger' :: [Type]) = (Select smaller larger, Amend smaller smaller' larger, larger' ~ Replaces smaller smaller' larger)
- project :: forall smaller smaller' larger larger'. Project smaller smaller' larger larger' => Lens (Many larger) (Many larger') (Many smaller) (Many smaller')
- type Project' (smaller :: [Type]) (larger :: [Type]) = (Select smaller larger, Amend' smaller larger)
- project' :: forall smaller larger. Project' smaller larger => Lens' (Many larger) (Many smaller)
- type ProjectL (ls :: [k]) (smaller :: [Type]) (smaller' :: [Type]) (larger :: [Type]) (larger' :: [Type]) = (Select smaller larger, Amend smaller smaller' larger, smaller ~ KindsAtLabels ls larger, IsDistinct ls, UniqueLabels ls larger, larger' ~ Replaces smaller smaller' larger)
- projectL :: forall ls smaller smaller' larger larger'. ProjectL ls smaller smaller' larger larger' => Lens (Many larger) (Many larger') (Many smaller) (Many smaller')
- type ProjectL' (ls :: [k]) (smaller :: [Type]) (larger :: [Type]) = (Select smaller larger, Amend' smaller larger, smaller ~ KindsAtLabels ls larger, IsDistinct ls, UniqueLabels ls larger)
- projectL' :: forall ls smaller larger. ProjectL' ls smaller larger => Lens' (Many larger) (Many smaller)
- type ProjectN (ns :: [Nat]) (smaller :: [Type]) (smaller' :: [Type]) (larger :: [Type]) (larger' :: [Type]) = (SelectN ns smaller larger, AmendN ns smaller smaller' larger, larger' ~ ReplacesIndex ns smaller' larger)
- projectN :: forall ns smaller smaller' larger larger'. ProjectN ns smaller smaller' larger larger' => Lens (Many larger) (Many larger') (Many smaller) (Many smaller')
- type ProjectN' (ns :: [Nat]) (smaller :: [Type]) (larger :: [Type]) = (SelectN ns smaller larger, AmendN' ns smaller larger)
- projectN' :: forall ns smaller larger. ProjectN' ns smaller larger => Lens' (Many larger) (Many smaller)
Isomorphism
Single field
Lens for a single field
class HasItem a b s t | s a b -> t, t a b -> s where Source #
Polymorphic version of item'
Minimal complete definition
class HasItem' a s where Source #
fetch (view item) and replace' (set item') in Lens' form.
let x = (5 :: Int)./False./'X'./Just 'O'./nilx^.item'@Int `shouldBe` 5 (x&item'@Int .~ 6) `shouldBe` (6 :: Int)./False./'X'./Just 'O'./nil
Methods
class HasItemL (l :: k) a b s t | s l -> a, t l -> b, s l b -> t, t l a -> s where Source #
Polymorphic version of itemL'
let x = (5 :: Int)./Tagged @Foo False./Tagged @Bar 'X'./nil(x&itemL@Foo.~"foo") `shouldBe` (5 :: Int)./"foo"./Tagged @Bar 'X'./nil
Minimal complete definition
class HasItemL' (l :: k) a s | s l -> a where Source #
fetchL (view itemL) and replaceL (set itemL) in Lens' form.
let x = (5 :: Int)./Tagged @Foo False./Tagged @Bar 'X'./nilx^.itemL'@Foo `shouldBe` Tagged @Foo False (x&itemL'@Foo.~Tagged @Foo True) `shouldBe` (5 :: Int)./Tagged @Foo True./Tagged @Bar 'X'./nil
Minimal complete definition
Instances
| (UniqueLabelMember k * l xs, (~) * x (KindAtLabel k * l xs)) => HasItemL' k l x (Many xs) Source # | |
class HasItemTag (l :: k) a b s t | s l -> a, t l -> b, s l b -> t, t l a -> s where Source #
Variation of itemL that automatically tags and untags the field.
Minimal complete definition
class HasItemTag' (l :: k) a s where Source #
Variation of itemL' that automatically tags and untags the field.
A default implementation using generics is not provided as it make GHC think that l must be type Symbol
when l can actually be any kind.
Create instances of HasItemTag' using Data.Generics.Product.Fields as follows:
instance HasField' l Foo a => HasItemTag' l a Foo where
itemTag' = field l
@
Minimal complete definition
Instances
| (UniqueLabelMember k * l xs, (~) * (Tagged k l x) (KindAtLabel k * l xs)) => HasItemTag' k l x (Many xs) Source # | |
class HasItemN (n :: Nat) a b s t | s n -> a, t n -> b, s n b -> t, t n a -> s where Source #
Polymorphic version of itemN'
class HasItemN' (n :: Nat) a s | s n -> a where Source #
fetchN (view item) and replaceN' (set item') in Lens' form.
let x = (5 :: Int)./False./'X'./Just 'O'./(6 :: Int)./Just 'A' ./ nil x^.itemN'@0 `shouldBe` 5 (x&itemN'@0.~6) `shouldBe` (6 :: Int)./False./'X'./Just 'O'./(6 :: Int)./Just 'A'./nil
Minimal complete definition
Multiple fields
Lens for multiple fields
type Project (smaller :: [Type]) (smaller' :: [Type]) (larger :: [Type]) (larger' :: [Type]) = (Select smaller larger, Amend smaller smaller' larger, larger' ~ Replaces smaller smaller' larger) Source #
A friendlier constraint synonym for project.
project :: forall smaller smaller' larger larger'. Project smaller smaller' larger larger' => Lens (Many larger) (Many larger') (Many smaller) (Many smaller') Source #
Polymorphic version of project'
type Project' (smaller :: [Type]) (larger :: [Type]) = (Select smaller larger, Amend' smaller larger) Source #
A friendlier constraint synonym for project'.
project' :: forall smaller larger. Project' 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
type ProjectL (ls :: [k]) (smaller :: [Type]) (smaller' :: [Type]) (larger :: [Type]) (larger' :: [Type]) = (Select smaller larger, Amend smaller smaller' larger, smaller ~ KindsAtLabels ls larger, IsDistinct ls, UniqueLabels ls larger, larger' ~ Replaces smaller smaller' larger) Source #
A friendlier constraint synonym for projectL.
projectL :: forall ls smaller smaller' larger larger'. ProjectL ls smaller smaller' larger larger' => Lens (Many larger) (Many 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"].~(True./Tagged @"Changed" False./nil)) `shouldBe` False./True./Tagged @Foo False./Tagged @Bar 'X'./Tagged @"Changed" False./nil
type ProjectL' (ls :: [k]) (smaller :: [Type]) (larger :: [Type]) = (Select smaller larger, Amend' smaller larger, smaller ~ KindsAtLabels ls larger, IsDistinct ls, UniqueLabels ls larger) Source #
A friendlier constraint synonym for projectL'.
projectL' :: forall ls smaller larger. ProjectL' ls smaller larger => 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] `shouldBe` Tagged @Foo False./Tagged @Bar 'X'./nil (x&(projectL'@'["Hi", "Bye"].~(Tagged @"Hi" (6 :: Int)./Tagged @"Bye" 'P'./nil)) 'shouldBeFalse./Tagged @"Hi" (6 :: Int)./Tagged @Foo False./Tagged @Bar 'X'./Tagged @"Bye" 'P'./nil
type ProjectN (ns :: [Nat]) (smaller :: [Type]) (smaller' :: [Type]) (larger :: [Type]) (larger' :: [Type]) = (SelectN ns smaller larger, AmendN ns smaller smaller' larger, larger' ~ ReplacesIndex ns smaller' larger) Source #
A friendlier constraint synonym for projectN.
projectN :: forall ns smaller smaller' larger larger'. ProjectN ns smaller smaller' larger larger' => Lens (Many larger) (Many larger') (Many smaller) (Many smaller') Source #
Polymorphic version of projectN'
type ProjectN' (ns :: [Nat]) (smaller :: [Type]) (larger :: [Type]) = (SelectN ns smaller larger, AmendN' ns smaller larger) Source #
A friendlier constraint synonym for projectN'.
projectN' :: forall ns smaller larger. ProjectN' ns smaller larger => 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] `shouldBe` Just 'A'./(6 :: Int)./(5 ::Int)./nil(x&projectN@_ @'[5, 4, 0].~(Just 'B'./(8 :: Int)./(4 ::Int)./nil)) `shouldBe` (4 :: Int)./False./'X'./Just 'O'./(8 :: Int)./Just 'B'./nil