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

class AsFacet a s where 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)

Minimal complete definition

facet

Methods

facet :: Prism' s a Source #

Instances

AsFacet x x Source # 

Methods

facet :: Prism' x x Source #

UniqueMember * x xs => AsFacet x (Which xs) Source # 

Methods

facet :: Prism' (Which xs) x Source #

AsFacet Void (Which ([] Type)) Source # 
AsFacet (Which ([] Type)) Void Source # 

class AsFacet a s => MatchingFacet a s t | s a -> t where Source #

Minimal complete definition

matchingFacet

Methods

matchingFacet :: s -> Either t a Source #

Unfortunately, polymorphic Prism s t a b cannot be used as it can only be created with: (UniqueMember x xs, UniqueMember y ys, ys ~ Remove x xs) => prism (pick :: y -> Which ys) (trial :: Which xs -> Either (Which ys) x) This above causes problems when used monomorphically with s ~ t and x ~ y since xs cannot equal ys ~ Remove x x.

What is desired is: (UniqueMember x xs, ys ~ Remove x xs) => prism_ (pick :: x -> Which xs) (trial :: Which xs -> Either (Which ys) x)

So we expose the polymorphic matching explicitly.

Instances

(UniqueMember * x xs, (~) [*] ys (Remove * x xs)) => MatchingFacet x (Which xs) (Which ys) Source # 

Methods

matchingFacet :: Which xs -> Either (Which ys) x Source #

facetTag :: forall l a s. AsFacet (Tagged l a) s => Prism' s a Source #

Variation of facet specialized to Tagged which 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.

matchingFacetTag :: forall l a s t. MatchingFacet (Tagged l a) s t => s -> Either t a Source #

Untagged version of MatchingFacet

class AsFacetL (l :: k) a s | s l -> a where Source #

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

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

Minimal complete definition

facetL

Methods

facetL :: Prism' s a Source #

Instances

(UniqueLabelMember k * l xs, (~) * x (KindAtLabel k * l xs)) => AsFacetL k l x (Which xs) Source # 

Methods

facetL :: Prism' s (Which xs) Source #

class AsFacetL l a s => MatchingFacetL l a s t | s a -> t where Source #

Labelled version of MatchingFacet

Minimal complete definition

matchingFacetL

Methods

matchingFacetL :: s -> Either t a Source #

Instances

(UniqueLabelMember k * l xs, (~) * x (KindAtLabel k * l xs), (~) [*] ys (Remove * x xs)) => MatchingFacetL k l x (Which xs) (Which ys) Source # 

Methods

matchingFacetL :: Which ys -> Either t (Which xs) Source #

class AsFacetN (n :: Nat) a s | s n -> a where Source #

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

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

Minimal complete definition

facetN

Methods

facetN :: Prism' s a Source #

Instances

MemberAt * n x xs => AsFacetN n x (Which xs) Source # 

Methods

facetN :: Prism' (Which xs) x Source #

class AsFacetN n a s => MatchingFacetN n a s t | s a -> t where Source #

Nat indexed version of MatchingFacet

Minimal complete definition

matchingFacetN

Methods

matchingFacetN :: s -> Either t a Source #

Instances

(MemberAt * n x xs, (~) [*] ys (RemoveIndex * n xs)) => MatchingFacetN n x (Which xs) (Which ys) Source # 

Methods

matchingFacetN :: Which xs -> Either (Which ys) x Source #

Multiple types

Prism

type Inject (branch :: [Type]) (tree :: [Type]) = (Diversify branch tree, Reinterpret' branch tree) Source #

A friendlier constraint synonym for inject

inject :: forall branch tree. Inject 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])

type InjectL (ls :: [k]) (branch :: [Type]) (tree :: [Type]) = (Diversify branch tree, Reinterpret' branch tree, branch ~ KindsAtLabels ls tree, UniqueLabels ls tree, IsDistinct ls) Source #

A friendlier constraint synonym for injectL

injectL :: forall ls branch tree. InjectL ls branch tree => 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]) b
    b' = preview (injectL @_ @[Foo, Bar]) t'
t `shouldBe` t'
b' `shouldBe` Just b

type InjectN (ns :: [Nat]) (branch :: [Type]) (tree :: [Type]) = (DiversifyN ns branch tree, ReinterpretN' ns branch tree) Source #

A friendlier constraint synonym for injectN

injectN :: forall ns branch tree. InjectN ns branch tree => 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]) x -- diversifyN
y `shouldBe` pick (5 :: Int) :: Which '[Bool, Int, Char, String]
let y' = preview (injectN @_ @[3, 1] @[String, Int]) y -- reinterpertN'
y' `shouldBe` Just (pick (5 :: Int)) :: Maybe (Which '[String, Int])