data-diverse-lens-1.0.0.1: 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

class HasItem a b s t | s a b -> t, t a b -> s where Source #

Polymorphic version of item'

Minimal complete definition

item

Methods

item :: Lens s t a b Source #

Instances

(UniqueMember * x xs, (~) [*] ys (Replace * x y xs)) => HasItem x y (Many xs) (Many ys) Source # 

Methods

item :: Lens (Many xs) (Many ys) x y Source #

class HasItem' a s where 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

Methods

item' :: Lens' s a Source #

Make it easy to create an instance of item using Typed

item' :: HasType a s => Lens' s a Source #

Make it easy to create an instance of item using Typed

Instances

UniqueMember * x xs => HasItem' x (Many xs) Source # 

Methods

item' :: Lens' (Many xs) x Source #

class HasItemL l 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 Proxy .~ "foo") `shouldBe` (5 :: Int) ./ "foo" ./ Tagged @Bar 'X' ./ nil

Minimal complete definition

itemL

Methods

itemL :: Lens s t a b Source #

Instances

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

Methods

itemL :: Lens (Many ys) t y (Many xs) Source #

class HasItemL' l 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' ./ 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

Minimal complete definition

itemL'

Methods

itemL' :: Lens' s a Source #

Instances

(UniqueLabelMember * k l xs, (~) * x (KindAtLabel * k l xs)) => HasItemL' k l x (Many xs) Source # 

Methods

itemL' :: Lens' s (Many xs) Source #

class HasItemTag l 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

itemTag

Methods

itemTag :: Lens s t a b Source #

Instances

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

Methods

itemTag :: Lens (Many ys) t y (Many xs) Source #

class HasItemTag' l 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

itemTag'

Methods

itemTag' :: Lens' s a Source #

Instances

(UniqueLabelMember * k l xs, (~) * (Tagged k l x) (KindAtLabel * k l xs)) => HasItemTag' k l x (Many xs) Source # 

Methods

itemTag' :: Lens' s (Many xs) Source #

class HasItemN n a b s t | s n -> a, t n -> b, s n b -> t, t n a -> s where Source #

Polymorphic version of itemN'

Methods

itemN :: Lens s t a b Source #

Make it easy to create an instance of itemN using Positions

itemN :: HasPosition n s t a b => Lens s t a b Source #

Make it easy to create an instance of itemN using Positions

Instances

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

Methods

itemN :: Lens (Many xs) (Many ys) x y Source #

class HasItemN' n 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' (Proxy @0) `shouldBe` 5
(x & itemN' (Proxy @0) .~ 6) `shouldBe` (6 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil

Minimal complete definition

itemN'

Methods

itemN' :: Lens' s a Source #

Instances

MemberAt * n x xs => HasItemN' n x (Many xs) Source # 

Methods

itemN' :: Lens' (Many xs) x Source #

Multiple fields

Lens for multiple fields

class HasProject as bs ss ts a b s t | a -> as, b -> bs, s -> ss, t -> ts, b as -> a, s as -> a, t as -> a, a bs -> b, s bs -> b, t bs -> b, a ss -> s, b ss -> s, t ss -> s, a ts -> t, b ts -> t, s ts -> t, s a b -> t, t a b -> s where Source #

Polymorphic version of project'

Minimal complete definition

project

Methods

project :: Lens s t a b Source #

Instances

(Select smaller larger, Amend smaller smaller' larger, (~) [Type] larger' (Replaces Type smaller smaller' larger)) => HasProject [Type] smaller smaller' larger larger' (Many smaller) (Many smaller') (Many larger) (Many larger') Source # 

Methods

project :: Lens (Many larger') t (Many smaller') (Many larger) Source #

class HasProject' as ss a s | a -> as, s -> ss, s as -> a, a ss -> s where 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

Methods

project' :: Lens' s a Source #

Make it easy to create an instance of project using Subtype

project' :: Subtype a s => Lens' s a Source #

Make it easy to create an instance of project using Subtype

Instances

(Select smaller larger, Amend' smaller larger) => HasProject' [Type] smaller larger (Many smaller) (Many larger) Source # 

Methods

project' :: Lens' s (Many larger) Source #

class HasProjectL ls as bs ss ts a b s t | a -> as, b -> bs, s -> ss, t -> ts, b as -> a, s as -> a, t as -> a, a bs -> b, s bs -> b, t bs -> b, a ss -> s, b ss -> s, t ss -> s, a ts -> t, b ts -> t, s ts -> t, s ls -> as, t ls -> bs, s ls b -> t, t ls a -> s where 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

Minimal complete definition

projectL

Methods

projectL :: Lens s t a b Source #

Instances

(Select smaller larger, Amend smaller smaller' larger, (~) [Type] smaller (KindsAtLabels Type k1 ls larger), IsDistinct k1 ls, UniqueLabels Type k1 ls larger, (~) [Type] larger' (Replaces Type smaller smaller' larger)) => HasProjectL [Type] [k1] ls smaller smaller' larger larger' (Many smaller) (Many smaller') (Many larger) (Many larger') Source # 

Methods

projectL :: Lens s t (Many larger) (Many larger') Source #

class HasProjectL' ls as ss a s | a -> as, s -> ss, s as -> a, a ss -> s, s ls -> as where 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

Minimal complete definition

projectL'

Methods

projectL' :: Lens' s a Source #

Instances

(Select smaller larger, Amend' smaller larger, (~) [Type] smaller (KindsAtLabels Type k1 ls larger), IsDistinct k1 ls, UniqueLabels Type k1 ls larger) => HasProjectL' [Type] [k1] ls smaller larger (Many smaller) (Many larger) Source # 

Methods

projectL' :: Lens' s a Source #

class HasProjectN ns as bs ss ts a b s t | a -> as, b -> bs, s -> ss, t -> ts, b as -> a, s as -> a, t as -> a, a bs -> b, s bs -> b, t bs -> b, a ss -> s, b ss -> s, t ss -> s, a ts -> t, b ts -> t, s ts -> t, s ns -> as, t ns -> bs, s ns b -> t, t ns a -> s where Source #

Polymorphic version of projectN'

Minimal complete definition

projectN

Methods

projectN :: Lens s t a b Source #

Instances

(SelectN ns smaller larger, AmendN ns smaller smaller' larger, (~) [Type] larger' (ReplacesIndex Type ns smaller' larger)) => HasProjectN [Type] ns smaller smaller' larger larger' (Many smaller) (Many smaller') (Many larger) (Many larger') Source # 

Methods

projectN :: Lens (Many larger') t (Many smaller') (Many larger) Source #

class HasProjectN' ns as ss a s | a -> as, s -> ss, s as -> a, a ss -> s, s ns -> as where 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

Minimal complete definition

projectN'

Methods

projectN' :: Lens' s a Source #

Instances

(SelectN ns smaller larger, AmendN' ns smaller larger) => HasProjectN' [Type] ns smaller larger (Many smaller) (Many larger) Source # 

Methods

projectN' :: Lens' s (Many larger) Source #