{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Comp.Projection (pr, (:<)) where
import Data.Comp.SubsumeCommon
import Data.Kind
type family Elem (f :: Type)
(g :: Type) :: Emb where
Elem f f = Found Here
Elem (f1, f2) g = Sum' (Elem f1 g) (Elem f2 g)
Elem f (g1, g2) = Choose (Elem f g1) (Elem f g2)
Elem f g = NotFound
class Proj (e :: Emb) (p :: Type)
(q :: Type) where
pr' :: Proxy e -> q -> p
instance Proj (Found Here) f f where
pr' :: Proxy ('Found 'Here) -> f -> f
pr' Proxy ('Found 'Here)
_ = forall a. a -> a
id
instance Proj (Found p) f g => Proj (Found (Le p)) f (g, g') where
pr' :: Proxy ('Found ('Le p)) -> (g, g') -> f
pr' Proxy ('Found ('Le p))
_ = forall (e :: Emb) p q. Proj e p q => Proxy e -> q -> p
pr' (forall {k} (a :: k). Proxy a
P :: Proxy (Found p)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst
instance Proj (Found p) f g => Proj (Found (Ri p)) f (g', g) where
pr' :: Proxy ('Found ('Ri p)) -> (g', g) -> f
pr' Proxy ('Found ('Ri p))
_ = forall (e :: Emb) p q. Proj e p q => Proxy e -> q -> p
pr' (forall {k} (a :: k). Proxy a
P :: Proxy (Found p)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd
instance (Proj (Found p1) f1 g, Proj (Found p2) f2 g)
=> Proj (Found (Sum p1 p2)) (f1, f2) g where
pr' :: Proxy ('Found ('Sum p1 p2)) -> g -> (f1, f2)
pr' Proxy ('Found ('Sum p1 p2))
_ g
x = (forall (e :: Emb) p q. Proj e p q => Proxy e -> q -> p
pr' (forall {k} (a :: k). Proxy a
P :: Proxy (Found p1)) g
x, forall (e :: Emb) p q. Proj e p q => Proxy e -> q -> p
pr' (forall {k} (a :: k). Proxy a
P :: Proxy (Found p2)) g
x)
infixl 5 :<
type f :< g = (Proj (ComprEmb (Elem f g)) f g)
pr :: forall p q . (p :< q) => q -> p
pr :: forall p q. (p :< q) => q -> p
pr = forall (e :: Emb) p q. Proj e p q => Proxy e -> q -> p
pr' (forall {k} (a :: k). Proxy a
P :: Proxy (ComprEmb (Elem p q)))