data-diverse-lens-2.1.0.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

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 :: 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

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 :: 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' ./ nil
x ^. 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

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 :: 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

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 :: 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

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 :: 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'

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 :: 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

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

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 = 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

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' ./ nil
x ^. (projectL' @'[Foo, Bar] `shouldBe` Tagged @Foo False ./ Tagged @Bar 'X' ./ nil
(x & (projectL' @'["Hi", "Bye"] .~ (Tagged @"Hi" (6 :: Int) ./ Tagged @"Bye" 'P' ./ nil)) 'shouldBe
    False ./ 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 = lens selectN amendN
let x = (5 :: Int) ./ False ./ 'X' ./ Just 'O' ./ (6 :: Int) ./ Just 'A' ./ nil
x ^. 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