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

Safe HaskellNone
LanguageHaskell2010

Data.Diverse.Lens.Which

Contents

Synopsis

Single type

Prism

facet :: forall x xs. UniqueMember x xs => Prism' (Which xs) x Source #

pick (review facet) and trial (preview facet) in Prism' form.

facet = prism' pick (trial')
let y = review (facet @Int) (5 :: Int) :: Which '[Bool, Int, Char, Bool, Char] -- pick
    x = preview (facet @Int) y -- trial
x `shouldBe` (Just 5)

facetL :: forall l xs proxy x. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => proxy l -> Prism' (Which xs) x Source #

pickL (review facetL) and trialL' (preview facetL') in Prism' form.

let y = review (facetL @Bar Proxy) (Tagged (5 :: Int)) :: Which '[Tagged Foo Bool, Tagged Bar Int, Char, Bool, Char]
    x = preview (facetL @Bar Proxy) y
x `shouldBe` (Just (Tagged 5))

facetN :: forall n xs proxy x. MemberAt n x xs => proxy n -> Prism' (Which xs) x Source #

pickN (review facetN) and trialN (preview facetN) in Prism' form.

facetN p = prism' (pickN p) (trialN' p)
let y = review (facetN (Proxy @4)) (5 :: Int) :: Which '[Bool, Int, Char, Bool, Int, Char] -- pickN
    x = preview (facetN (Proxy @4)) y -- trialN
x `shouldBe` (Just 5)

Multiple types

Prism

inject :: forall branch tree. (Diversify branch tree, Reinterpret' branch tree) => Prism' (Which tree) (Which branch) Source #

diversify (review inject) and reinterpret' (preview inject) in Prism' form.

let x = pick (5 :: Int) :: Which '[String, Int]
    y = review (inject @_ @[Bool, Int, Char, String]) x -- diversify
y `shouldBe` pick (5 :: Int) :: Which '[Bool, Int, Char, String]
let y' = preview (inject @[String, Int]) y -- reinterpret
y' `shouldBe` Just (pick (5 :: Int)) :: Maybe (Which '[String, Int])

injectL :: forall ls branch tree proxy. (Diversify branch tree, Reinterpret' branch tree, branch ~ KindsAtLabels ls tree, UniqueLabels ls tree, IsDistinct ls) => proxy ls -> Prism' (Which tree) (Which branch) Source #

diversifyL (review injectL) and reinterpretL' (preview injectL) in Prism' form.

let t = pick @[Tagged Bar Int, Tagged Foo Bool, Tagged Hi Char, Tagged Bye Bool] (5 :: Tagged Bar Int)
    b = pick @'[Tagged Foo Bool, Tagged Bar Int] (5 :: Tagged Bar Int)
    t' = review (injectL @[Foo, Bar] @_ @[Tagged Bar Int, Tagged Foo Bool, Tagged Hi Char, Tagged Bye Bool] Proxy) b
    b' = preview (injectL @[Foo, Bar] Proxy) t'
t `shouldBe` t'
b' `shouldBe` Just b

injectN :: forall indices branch tree proxy. (DiversifyN indices branch tree, ReinterpretN' indices branch tree) => proxy indices -> Prism' (Which tree) (Which branch) Source #

diversifyN (review injectN) and reinterpretN' (preview injectN) in Prism' form.

let x = pick (5 :: Int) :: Which '[String, Int]
    y = review (injectN @[3, 1] @_ @[Bool, Int, Char, String] Proxy) x -- diversifyN
y `shouldBe` pick (5 :: Int) :: Which '[Bool, Int, Char, String]
let y' = preview (injectN @[3, 1] @[String, Int] Proxy) y -- reinterpertN'
y' `shouldBe` Just (pick (5 :: Int)) :: Maybe (Which '[String, Int])