{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE MultiParamTypeClasses, UndecidableInstances, ScopedTypeVariables, TypeFamilies #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableSuperClasses #-}
module Data.Extensible.Class (
Extensible(..)
, piece
, pieceAssoc
, itemAt
, item
, itemAssoc
, itemKey
, Membership
, mkMembership
, getMemberId
, compareMembership
, leadership
, Member(..)
, type (∈)
, FindType
, Generate(..)
, Forall(..)
, ForallF
, Assoc(..)
, type (>:)
, Lookup(..)
, Associate
, Head
, Last
) where
import Data.Constraint
import Data.Extensible.Internal.Rig (Optic')
import Data.Extensible.Wrapper
import Data.Kind
import Data.Profunctor
import Type.Membership
import Type.Membership.Internal
class (Functor f, Profunctor p) => Extensible f p (t :: [k] -> (k -> Type) -> Type) where
type ExtensibleConstr t (xs :: [k]) (h :: k -> Type) (x :: k) :: Constraint
type ExtensibleConstr t xs h x = ()
pieceAt :: ExtensibleConstr t xs h x => Membership xs x -> Optic' p f (t xs h) (h x)
piece :: (x ∈ xs, Extensible f p t, ExtensibleConstr t xs h x) => Optic' p f (t xs h) (h x)
piece = pieceAt membership
{-# INLINE piece #-}
pieceAssoc :: (Lookup xs k v, Extensible f p t, ExtensibleConstr t xs h (k ':> v)) => Optic' p f (t xs h) (h (k ':> v))
pieceAssoc = pieceAt association
{-# INLINE pieceAssoc #-}
itemAt :: (Wrapper h, Extensible f p t, ExtensibleConstr t xs h x) => Membership xs x -> Optic' p f (t xs h) (Repr h x)
itemAt m = pieceAt m . _Wrapper
{-# INLINE itemAt #-}
item :: (Wrapper h, Extensible f p t, x ∈ xs, ExtensibleConstr t xs h x) => proxy x -> Optic' p f (t xs h) (Repr h x)
item p = piece . _WrapperAs p
{-# INLINE item #-}
itemAssoc :: (Wrapper h, Extensible f p t, Lookup xs k v, ExtensibleConstr t xs h (k ':> v))
=> proxy k -> Optic' p f (t xs h) (Repr h (k ':> v))
itemAssoc p = pieceAssoc . _WrapperAs (proxyKey p)
{-# INLINE itemAssoc #-}
itemKey :: forall k v xs h f p t. (Wrapper h, Extensible f p t, Lookup xs k v, ExtensibleConstr t xs h (k ':> v))
=> Optic' p f (t xs h) (Repr h (k ':> v))
itemKey = pieceAssoc . _WrapperAs (Proxy @ (k ':> v))
{-# INLINE itemKey #-}
proxyKey :: proxy k -> Proxy (k ':> v)
proxyKey _ = Proxy
{-# INLINE proxyKey #-}
type family Head (xs :: [k]) :: k where
Head (x ': xs) = x
type family Last (x :: [k]) :: k where
Last '[x] = x
Last (x ': xs) = Last xs
type Associate k v xs = Lookup xs k v
{-# DEPRECATED Associate "Use Lookup instead" #-}