{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE LambdaCase #-}
module Data.Extensible.Plain (
AllOf
, OneOf
, (<%)
, pluck
, bury
, (<%|)
, accessing
) where
import Data.Extensible.Internal.Rig
import Data.Extensible.Class
import Data.Extensible.Product
import Data.Extensible.Sum
import Data.Functor.Identity
import Data.Extensible.Wrapper
import Data.Coerce
import Data.Profunctor.Unsafe
type AllOf xs = xs :& Identity
type OneOf xs = xs :/ Identity
(<%) :: x -> AllOf xs -> AllOf (x ': xs)
(<%) = (<:) .# Identity
{-# INLINE (<%) #-}
infixr 5 <%
pluck :: (x ∈ xs) => AllOf xs -> x
pluck = views piece runIdentity
{-# INLINE pluck #-}
bury :: (x ∈ xs) => x -> OneOf xs
bury = embed .# Identity
{-# INLINE bury #-}
(<%|) :: (x -> r) -> (OneOf xs -> r) -> OneOf (x ': xs) -> r
(<%|) = (<:|) . (.# runIdentity)
infixr 1 <%|
accessing :: (Coercible x a, x ∈ xs, Extensible f p t, ExtensibleConstr t xs Identity x) => (a -> x) -> Optic' p f (t xs Identity) a
accessing c = piece . _Wrapper . dimap coerce (fmap c)
{-# INLINE accessing #-}