{-# LANGUAGE KindSignatures, TypeApplications #-} module Data.Ron.Class.Internal ( ProductSize (productSize) ) where import GHC.Generics ((:*:)(..), M1) import Data.Proxy (Proxy (Proxy)) import Data.Kind (Type) class ProductSize (f :: Type -> Type) where productSize :: Proxy f -> Int instance ProductSize (M1 c s f) where productSize :: Proxy (M1 c s f) -> Int productSize Proxy (M1 c s f) _ = Int 1 {-# INLINE productSize #-} instance (ProductSize fl, ProductSize fr) => ProductSize (fl :*: fr) where productSize :: Proxy (fl :*: fr) -> Int productSize Proxy (fl :*: fr) _ = Proxy fl -> Int forall (f :: * -> *). ProductSize f => Proxy f -> Int productSize (forall {k} (t :: k). Proxy t forall (t :: * -> *). Proxy t Proxy @fl) Int -> Int -> Int forall a. Num a => a -> a -> a + Proxy fr -> Int forall (f :: * -> *). ProductSize f => Proxy f -> Int productSize (forall {k} (t :: k). Proxy t forall (t :: * -> *). Proxy t Proxy @fr) {-# INLINE productSize #-}