data-diverse-lens-0.5.2.0: Isos & Lens for Data.Diverse.Many and Prisms for Data.Diverse.Which

Safe HaskellNone
LanguageHaskell2010

Data.Diverse.Lens.Many

Contents

Synopsis

Isomorphism

_Many :: IsMany t xs a => Iso' (Many xs) (t xs a) Source #

_Many = iso fromMany toMany

_Many' :: IsMany Tagged xs a => Iso' (Many xs) a Source #

_Many' = iso fromMany' toMany'

Single field

Lens for a single field

item :: forall x xs. UniqueMember x xs => Lens' (Many xs) x Source #

fetch (view item) and replace (set item) in Lens' form.

let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil
x ^. item @Int `shouldBe` 5
(x & item @Int .~ 6) `shouldBe` (6 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil

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 proxy x. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => proxy l -> Lens' (Many xs) x Source #

fetchL (view itemL) and replaceL (set itemL) in Lens' form.

let x = (5 :: Int) ./ Tagged @Foo False ./ Tagged @Bar 'X' ./ nil
x ^. itemL @Foo Proxy `shouldBe` Tagged @Foo False
(x & itemL @Foo Proxy .~ Tagged @Foo True) `shouldBe` (5 :: Int) ./ Tagged @Foo True ./ Tagged @Bar 'X' ./ nil

itemL' :: forall l y xs proxy x. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => proxy l -> Lens (Many xs) (Many (Replace x y xs)) x y Source #

Polymorphic version of itemL

let x = (5 :: Int) ./ Tagged @Foo False ./ Tagged @Bar 'X' ./ nil
(x & itemL' @Foo Proxy .~ "foo") `shouldBe` (5 :: Int) ./ "foo" ./ Tagged @Bar 'X' ./ nil

itemTag :: forall l xs proxy x. (UniqueLabelMember l xs, Tagged l x ~ KindAtLabel l xs) => proxy l -> Lens' (Many xs) x Source #

Variation of itemL that automatically tags and untags the field.

itemTag' :: forall l y xs proxy x. (UniqueLabelMember l xs, Tagged l x ~ KindAtLabel l xs) => proxy l -> Lens (Many xs) (Many (Replace (Tagged l x) (Tagged l y) xs)) x y Source #

Variation of itemL' that automatically tags and untags the field.

itemN :: forall n xs proxy x. MemberAt n x xs => proxy n -> Lens' (Many xs) x 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 (Proxy @0) `shouldBe` 5
(x & itemN (Proxy @0) .~ 6) `shouldBe` (6 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil

itemN' :: forall n y xs proxy x. MemberAt n x xs => proxy n -> Lens (Many xs) (Many (ReplaceIndex n y xs)) x y Source #

Polymorphic version of itemN

Multiple fields

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 = lens select amend
let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ nil
x ^. (project @'[Int, Maybe Char]) `shouldBe` (5 :: Int) ./ Just 'O' ./ nil
(x & (project @'[Int, Maybe Char]) .~ ((6 :: Int) ./ Just P ./ nil)) `shouldBe`
    (6 :: Int) ./ False ./ 'X' ./ Just 'P' ./ nil

project' :: forall smaller smaller' larger. (Select smaller larger, Amend' smaller smaller' larger) => 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' ./ nil
x ^. (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)) 'shouldBe
    False ./ Tagged @"Hi" (6 :: Int) ./ Tagged @Foo False ./ Tagged @Bar 'X' ./ Tagged @"Bye" 'P' ./ nil

projectL' :: forall ls smaller smaller' larger proxy. (Select smaller larger, Amend' smaller smaller' larger, 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 = lens selectN amendN
let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil
x ^. (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. (SelectN ns smaller larger, AmendN' ns smaller smaller' larger) => proxy ns -> Lens (Many larger) (Many (ReplacesIndex ns smaller' larger)) (Many smaller) (Many smaller') Source #

Polymorphic version of projectN

Orphan instances

UniqueMember * x xs => HasType x (Many xs) Source #

I'm using Data.Generics as the canoical class for HasXXX. Overlap HasType typed with the more efficient item Undecidableinstances! Orphan instance!

Methods

typed :: Lens' (Many xs) x #

getTyped :: Many xs -> x #

setTyped :: x -> Many xs -> Many xs #

(MemberAt Type n x xs, (~) [Type] ys (ReplaceIndex Type n y xs)) => HasPosition n (Many xs) (Many ys) x y Source #

I'm using Data.Generics as the canoical class for HasXXX. Overlap HasPosition position with the more efficient itemN' Undecidableinstances! Orphan instance!

Methods

position :: Lens (Many xs) (Many ys) x y #

(UniqueLabelMember * Symbol l xs, (~) * (Tagged Symbol l x) (KindAtLabel * Symbol l xs), (~) [*] ys (Replace * (Tagged Symbol l x) (Tagged Symbol l y) xs)) => HasField l (Many xs) (Many ys) x y Source #

I'm using Data.Generics as the canoical class for HasXXX. Overlap HasField field with the more efficient itemN' Undecidableinstances! Orphan instance!

Methods

field :: Lens (Many xs) (Many ys) x y #

(Select smaller larger, Amend smaller larger) => Subtype (Many smaller) (Many larger) Source #

I'm using Data.Generics as the canoical class for HasXXX. Overlap Subtype super with the more efficient project Undecidableinstances! Orphan instance!

Methods

super :: Lens' (Many larger) (Many smaller) #

upcast :: Many larger -> Many smaller #

smash :: Many smaller -> Many larger -> Many larger #