{-# LANGUAGE UndecidableInstances #-}
module Z.Data.Generics.Utils
( ProductSize(..)
, productSize
, SumSize(..)
, sumSize
) where
import GHC.Generics
import GHC.TypeNats
import GHC.Exts (Proxy#, proxy#)
class KnownNat (PSize f) => ProductSize (f :: * -> *) where
type PSize f :: Nat
instance ProductSize (S1 s a) where
type PSize (S1 s a) = 1
instance (KnownNat (PSize a + PSize b), ProductSize a, ProductSize b) => ProductSize (a :*: b) where
type PSize (a :*: b) = PSize a + PSize b
productSize :: forall f. KnownNat (PSize f) => Proxy# f -> Int
{-# INLINE productSize #-}
productSize :: Proxy# f -> Int
productSize Proxy# f
_ = Natural -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy# (PSize f) -> Natural
forall (n :: Nat). KnownNat n => Proxy# n -> Natural
natVal' (Proxy# (PSize f)
forall k (a :: k). Proxy# a
proxy# :: Proxy# (PSize f)))
class KnownNat (SSize f) => SumSize (f :: * -> *) where
type SSize f :: Nat
instance SumSize (C1 c a) where
type SSize (C1 c a) = 1
instance (KnownNat (SSize a + SSize b), SumSize a, SumSize b) => SumSize (a :+: b) where
type SSize (a :+: b) = SSize a + SSize b
sumSize :: forall f. KnownNat (SSize f) => Proxy# f -> Int
{-# INLINE sumSize #-}
sumSize :: Proxy# f -> Int
sumSize Proxy# f
_ = Natural -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy# (SSize f) -> Natural
forall (n :: Nat). KnownNat n => Proxy# n -> Natural
natVal' (Proxy# (SSize f)
forall k (a :: k). Proxy# a
proxy# :: Proxy# (SSize f)))