{-# LANGUAGE CPP, TypeFamilies, MultiParamTypeClasses, UndecidableInstances, ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Data.Extensible.Label () where
import Data.Extensible.Class
import Data.Extensible.Field
import Data.Proxy
import GHC.OverloadedLabels
import Data.Extensible.Wrapper
instance (Extensible f p e
, Lookup xs k v
, Wrapper h
, ExtensibleConstr e xs (Field h) (k ':> v)
, rep ~ Repr h v
, s ~ e xs (Field h)
, s ~ t
, rep ~ rep'
)
=> IsLabel k (p rep (f rep') -> p s (f t)) where
fromLabel :: p rep (f rep') -> p s (f t)
fromLabel = Proxy k -> Optic' p f (e xs (Field h)) (Repr (Field h) (k ':> v))
forall {k1} {v1} (h :: Assoc k1 v1 -> Type) (f :: Type -> Type)
(p :: Type -> Type -> Type)
(t :: [Assoc k1 v1] -> (Assoc k1 v1 -> Type) -> Type)
(xs :: [Assoc k1 v1]) (k2 :: k1) (v2 :: v1) (proxy :: k1 -> Type).
(Wrapper h, Extensible f p t, Lookup xs k2 v2,
ExtensibleConstr t xs h (k2 ':> v2)) =>
proxy k2 -> Optic' p f (t xs h) (Repr h (k2 ':> v2))
itemAssoc (Proxy k
forall {k} (t :: k). Proxy t
Proxy :: Proxy k)