| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Diverse.Lens.Which
- class AsFacet a s where
- class AsFacet a s => MatchingFacet a s t | s a -> t where
- class AsFacetL (l :: k) a s | s l -> a where
- class AsFacetL l a s => MatchingFacetL l a s t | s a -> t where
- class AsFacetTag (l :: k) a s | s l -> a where
- class AsFacetTag l a s => MatchingFacetTag l a s t | l s a -> t where
- class AsFacetN (n :: Nat) a s | s n -> a where
- class AsFacetN n a s => MatchingFacetN n a s t | s a -> t where
- type Inject (branch :: [Type]) (tree :: [Type]) = (Diversify branch tree, Reinterpret' branch tree)
- inject :: forall branch tree. Inject branch tree => Prism' (Which tree) (Which branch)
- type InjectL (ls :: [k]) (branch :: [Type]) (tree :: [Type]) = (Diversify branch tree, Reinterpret' branch tree, branch ~ KindsAtLabels ls tree, UniqueLabels ls tree, IsDistinct ls)
- injectL :: forall ls branch tree. InjectL ls branch tree => Prism' (Which tree) (Which branch)
- type InjectN (ns :: [Nat]) (branch :: [Type]) (tree :: [Type]) = (DiversifyN ns branch tree, ReinterpretN' ns branch tree)
- injectN :: forall ns branch tree. InjectN ns branch tree => Prism' (Which tree) (Which branch)
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] --pickx =preview(facet@Int) y --trialx `shouldBe` (Just 5)
Methods
class AsFacet a s => MatchingFacet a s t | s a -> t where Source #
Minimal complete definition
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 desirec is: (UniqueMember x xs, ys ~ Remove x xs) => prism_ (pick :: x -> Which xs) (trial :: Which xs -> Either (Which ys) x)
So we expose the polymorhpic matching explicitly.
Instances
| (UniqueMember * x xs, (~) [*] ys (Remove * x xs)) => MatchingFacet x (Which xs) (Which ys) Source # | |
class AsFacetL (l :: k) a s | s l -> a where Source #
pickL (review facetL) and trialL' (preview facetL') in Prism' form.
let y =reviewfacetL@Bar (Tagged (5 :: Int)) :: Which '[Tagged Foo Bool, Tagged Bar Int, Char, Bool, Char] x =previewfacetL@Bar y x `shouldBe` (Just (Tagged 5))
Minimal complete definition
Instances
| (UniqueLabelMember k * l xs, (~) * x (KindAtLabel k * l xs)) => AsFacetL k l x (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
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 # | |
class AsFacetTag (l :: k) a s | s l -> a where Source #
Variation of fetchL 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.
Create instances of AsFacetTag' using Data.Generics.Sum.Constructors as follows:
instance AsConstructor' l Foo Foo a a => AsFacetTag l a Foo where
facetTag = _Ctor l
@
Minimal complete definition
Instances
| (UniqueLabelMember k * l xs, (~) * (Tagged k l x) (KindAtLabel k * l xs)) => AsFacetTag k l x (Which xs) Source # | |
class AsFacetTag l a s => MatchingFacetTag l a s t | l s a -> t where Source #
Untagged version of MatchingFacet
Minimal complete definition
Methods
matchingFacetTag :: s -> Either t a Source #
Instances
| (UniqueLabelMember k * l xs, (~) * (Tagged k l x) (KindAtLabel k * l xs), (~) [*] ys (Remove * (Tagged k l x) xs)) => MatchingFacetTag k l x (Which xs) (Which ys) Source # | |
class AsFacetN (n :: Nat) a s | s n -> a where Source #
pickN (review facetN) and trialN (preview facetN) in Prism' form.
facetNp =prism'(pickNp) (trialN'p)
let y =review(facetN@4) (5 :: Int) ::Which'[Bool, Int, Char, Bool, Int, Char] --pickNx =preview(facetN@4) y --trialNx `shouldBe` (Just 5)
Minimal complete definition
class AsFacetN n a s => MatchingFacetN n a s t | s a -> t where Source #
Nat indexed version of MatchingFacet
Minimal complete definition
Methods
matchingFacetN :: s -> Either t a Source #
Instances
| (MemberAt * n x xs, (~) [*] ys (RemoveIndex * n xs)) => MatchingFacetN n x (Which xs) (Which ys) 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 --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])
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 --diversifyNy `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])