{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-deprecations #-}
module Data.Barbie.Internal.ProductC
( ProductBC(..)
, buniqC
, CanDeriveProductBC
, GAll
, GProductBC(..)
, gbdictsDefault
)
where
import Barbies.Generics.Constraints(GAll, Self, Other, X)
import Barbies.Internal.ConstraintsB(ConstraintsB(..), GAllRepB)
import Barbies.Internal.Dicts(Dict (..), requiringDict)
import Barbies.Internal.FunctorB(FunctorB(bmap))
import Barbies.Internal.Trivial(Unit(..))
import Barbies.Internal.Wrappers(Barbie(..))
import Data.Barbie.Internal.Product(ProductB(..))
import Data.Generics.GenericN
import Data.Functor.Product (Product (..))
import Data.Kind(Type)
import Data.Proxy(Proxy (..))
class (ConstraintsB b, ProductB b) => ProductBC (b :: (k -> Type) -> Type) where
bdicts :: AllB c b => b (Dict c)
default bdicts :: (CanDeriveProductBC c b, AllB c b) => b (Dict c)
bdicts = forall {k} (b :: (k -> *) -> *) (c :: k -> Constraint).
(CanDeriveProductBC c b, AllB c b) =>
b (Dict c)
gbdictsDefault
type CanDeriveProductBC c b
= ( GenericN (b (Dict c))
, AllB c b ~ GAll 0 c (GAllRepB b)
, GProductBC c (GAllRepB b) (RepN (b (Dict c)))
)
{-# DEPRECATED buniqC "Use bpureC instead" #-}
buniqC :: forall c f b . (AllB c b, ProductBC b) => (forall a . c a => f a) -> b f
buniqC :: forall {k} (c :: k -> Constraint) (f :: k -> *)
(b :: (k -> *) -> *).
(AllB c b, ProductBC b) =>
(forall (a :: k). c a => f a) -> b f
buniqC forall (a :: k). c a => f a
x
= forall k (b :: (k -> *) -> *) (f :: k -> *) (g :: k -> *).
FunctorB b =>
(forall (a :: k). f a -> g a) -> b f -> b g
bmap (forall {k} (c :: k -> Constraint) (a :: k) r.
(c a => r) -> Dict c a -> r
requiringDict @c forall (a :: k). c a => f a
x) forall k (b :: (k -> *) -> *) (c :: k -> Constraint).
(ProductBC b, AllB c b) =>
b (Dict c)
bdicts
instance ProductBC b => ProductBC (Barbie b) where
bdicts :: forall (c :: k -> Constraint).
AllB c (Barbie b) =>
Barbie b (Dict c)
bdicts = forall k (b :: (k -> *) -> *) (f :: k -> *). b f -> Barbie b f
Barbie forall k (b :: (k -> *) -> *) (c :: k -> Constraint).
(ProductBC b, AllB c b) =>
b (Dict c)
bdicts
instance ProductBC Unit where
bdicts :: forall (c :: k -> Constraint). AllB c Unit => Unit (Dict c)
bdicts = forall k (f :: k -> *). Unit f
Unit
gbdictsDefault
:: forall b c
. ( CanDeriveProductBC c b
, AllB c b
)
=> b (Dict c)
gbdictsDefault :: forall {k} (b :: (k -> *) -> *) (c :: k -> Constraint).
(CanDeriveProductBC c b, AllB c b) =>
b (Dict c)
gbdictsDefault
= forall a x. GenericN a => RepN a x -> a
toN forall a b. (a -> b) -> a -> b
$ forall {k} {k} (c :: k -> Constraint) (repbx :: * -> *)
(repbd :: k -> *) (x :: k).
(GProductBC c repbx repbd, GAll 0 c repbx) =>
repbd x
gbdicts @c @(GAllRepB b)
{-# INLINE gbdictsDefault #-}
class GProductBC c repbx repbd where
gbdicts :: GAll 0 c repbx => repbd x
instance GProductBC c repbx repbd => GProductBC c (M1 i k repbx) (M1 i k repbd) where
gbdicts :: forall (x :: k). GAll 0 c (M1 i k repbx) => M1 i k repbd x
gbdicts = forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (forall {k} {k} (c :: k -> Constraint) (repbx :: * -> *)
(repbd :: k -> *) (x :: k).
(GProductBC c repbx repbd, GAll 0 c repbx) =>
repbd x
gbdicts @c @repbx)
{-# INLINE gbdicts #-}
instance GProductBC c U1 U1 where
gbdicts :: forall (x :: k). GAll 0 c U1 => U1 x
gbdicts = forall k (p :: k). U1 p
U1
{-# INLINE gbdicts #-}
instance
( GProductBC c lx ld
, GProductBC c rx rd
) => GProductBC c (lx :*: rx)
(ld :*: rd) where
gbdicts :: forall (x :: k). GAll 0 c (lx :*: rx) => (:*:) ld rd x
gbdicts = forall {k} {k} (c :: k -> Constraint) (repbx :: * -> *)
(repbd :: k -> *) (x :: k).
(GProductBC c repbx repbd, GAll 0 c repbx) =>
repbd x
gbdicts @c @lx @ld forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: forall {k} {k} (c :: k -> Constraint) (repbx :: * -> *)
(repbd :: k -> *) (x :: k).
(GProductBC c repbx repbd, GAll 0 c repbx) =>
repbd x
gbdicts @c @rx @rd
{-# INLINE gbdicts #-}
type P0 = Param 0
instance c a => GProductBC c (Rec (P0 X a_or_pma) (X a))
(Rec (P0 (Dict c) a_or_pma) (Dict c a)) where
gbdicts :: forall (x :: k).
GAll 0 c (Rec (P0 X a_or_pma) (X a)) =>
Rec (P0 (Dict c) a_or_pma) (Dict c a) x
gbdicts = forall {k} p a (x :: k). K1 R a x -> Rec p a x
Rec (forall k i c (p :: k). c -> K1 i c p
K1 forall {k} (c :: k -> Constraint) (a :: k). c a => Dict c a
Dict)
{-# INLINE gbdicts #-}
instance
( ProductBC b
, AllB c b
) => GProductBC c (Self (b' (P0 X)) (b X))
(Rec (b' (P0 (Dict c))) (b (Dict c))) where
gbdicts :: forall (x :: k).
GAll 0 c (Self (b' (P0 X)) (b X)) =>
Rec (b' (P0 (Dict c))) (b (Dict c)) x
gbdicts = forall {k} p a (x :: k). K1 R a x -> Rec p a x
Rec forall a b. (a -> b) -> a -> b
$ forall k i c (p :: k). c -> K1 i c p
K1 forall a b. (a -> b) -> a -> b
$ forall k (b :: (k -> *) -> *) (c :: k -> Constraint).
(ProductBC b, AllB c b) =>
b (Dict c)
bdicts @_ @b
instance
( ProductBC b
, AllB c b
) => GProductBC c (Other (b' (P0 X)) (b X))
(Rec (b' (P0 (Dict c))) (b (Dict c))) where
gbdicts :: forall (x :: k).
GAll 0 c (Other (b' (P0 X)) (b X)) =>
Rec (b' (P0 (Dict c))) (b (Dict c)) x
gbdicts = forall {k} p a (x :: k). K1 R a x -> Rec p a x
Rec forall a b. (a -> b) -> a -> b
$ forall k i c (p :: k). c -> K1 i c p
K1 forall a b. (a -> b) -> a -> b
$ forall k (b :: (k -> *) -> *) (c :: k -> Constraint).
(ProductBC b, AllB c b) =>
b (Dict c)
bdicts @_ @b
instance ProductBC Proxy where
bdicts :: forall (c :: k -> Constraint). AllB c Proxy => Proxy (Dict c)
bdicts = forall {k} (t :: k). Proxy t
Proxy
{-# INLINE bdicts #-}
instance (ProductBC a, ProductBC b) => ProductBC (Product a b) where
bdicts :: forall (c :: k -> Constraint).
AllB c (Product a b) =>
Product a b (Dict c)
bdicts = forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
Pair forall k (b :: (k -> *) -> *) (c :: k -> Constraint).
(ProductBC b, AllB c b) =>
b (Dict c)
bdicts forall k (b :: (k -> *) -> *) (c :: k -> Constraint).
(ProductBC b, AllB c b) =>
b (Dict c)
bdicts
{-# INLINE bdicts #-}