| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Diverse.Lens.Which
- facet :: forall x xs. UniqueMember x xs => Prism' (Which xs) x
- facetL :: forall l xs proxy x. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => proxy l -> Prism' (Which xs) x
- facetN :: forall n xs proxy x. MemberAt n x xs => proxy n -> Prism' (Which xs) x
- inject :: forall branch tree. (Diversify branch tree, Reinterpret' branch tree) => Prism' (Which tree) (Which branch)
- 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)
- injectN :: forall indices branch tree proxy. (DiversifyN indices branch tree, ReinterpretN' indices branch tree) => proxy indices -> Prism' (Which tree) (Which branch)
Single type
Prism
facetL :: forall l xs proxy x. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => proxy l -> Prism' (Which xs) x Source #
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 --diversifyy `shouldBe` pick (5 :: Int) ::Which'[Bool, Int, Char, String] let y' =preview(inject@[String, Int]) y --reinterprety' `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 --diversifyNy `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])