1

For a library I'm writing, I would like to be able to retrieve the size of any type with Bounded and Enum constraints, as a type-level Nat. The purpose is to define typeclass instances such as:

instance ( Enum a, Bounded a, n ~ BoundedEnumSize a ) => Action ( CyclicGroup n ) ( CyclicEnum a ) where
  ...

Is there perhaps a way to achieve this using Template Haskell, e.g.

class    ( Enum a, Bounded a ) => BoundedEnum a where
  type FiniteEnumSize a :: Nat
instance ( Enum a, Bounded a ) => BoundedEnum a where
  type BoundedEnumSize a = ... Template Haskell ... 1 + fromEnum maxBound - fromEnum minBound

The only other "solution" I can think of would be to manually define BoundedEnum instances for all types that have both Enum and Bounded instances, but this would lead to many orphan instances for users of the library (as I wouldn't be able to define all the necessary instances without importing the entire universe).

Sam Derbyshire
  • 719
  • 1
  • 4
  • 12

2 Answers2

1

Here's a solution with Generics:

{-# LANGUAGE DeriveGeneric,UndecidableInstances,TypeFamilies,FlexibleInstances #-}
{-# LANGUAGE DataKinds,ConstraintKinds,TypeOperators,TypeApplications          #-}

import GHC.Generics
import GHC.TypeLits
import Data.Proxy

class (KnownNat (FiniteEnumSize a)) => BoundedEnum' a where
  type FiniteEnumSize a :: Nat

type BoundedEnum a = (Bounded a, Enum a, BoundedEnum' a)

instance BoundedEnum' (V1 a) where
  type FiniteEnumSize (V1 a) = 0

instance BoundedEnum' (U1 a) where
  type FiniteEnumSize (U1 a) = 1

instance BoundedEnum' c => BoundedEnum' (K1 i c a) where
  type FiniteEnumSize (K1 i c a) = FiniteEnumSize c

instance BoundedEnum' (f a) => BoundedEnum' (M1 i t f a) where
  type FiniteEnumSize (M1 i t f a) = FiniteEnumSize (f a)

instance ( BoundedEnum' (f a), BoundedEnum' (g a)
         , KnownNat (FiniteEnumSize (f a) * FiniteEnumSize (g a)) )
   => BoundedEnum' ((f:*:g) a) where
 type FiniteEnumSize ((f:*:g) a) = FiniteEnumSize (f a)
                                    * FiniteEnumSize (g a)

instance ( BoundedEnum' (f a), BoundedEnum' (g a)
         , KnownNat (FiniteEnumSize (f a) + FiniteEnumSize (g a)) )
   => BoundedEnum' ((f:+:g) a) where
 type FiniteEnumSize ((f:+:g) a) = FiniteEnumSize (f a)
                                    + FiniteEnumSize (g a)

Then you can do e.g.

data Foo = Foo0 | Foo1 | Foo2
  deriving (Eq, Enum, Bounded, Show, Generic)

instance BoundedEnum' Foo where
  type FiniteEnumSize Foo = FiniteEnumSize (Rep Foo ())

main = print (natVal (Proxy :: Proxy (FiniteEnumSize Foo)))

Result: 3.

This also works for more complex ADTs – but note that Enum and Bounded can not be simply derived for such types, so maybe better just do away entirely with those classes and simply put a universe method in your own class.

leftaroundabout
  • 117,950
  • 5
  • 174
  • 319
  • Thanks for the answer. You bypass the problem entirely by (in effect) defining custom instances for generic types. This approach will work with any algebraic datatype, but (unless I'm mistaken) it unfortunately can't tackle types like `Word8` where you need to call out to the `Enum` and `Bounded` methods (where you end up hitting the original problem). – Sam Derbyshire Feb 11 '20 at 14:35
0

The finitary library is exactly what I was looking for, as it gives access at the type-level to the cardinality of any finite type, which works for types which contain fields.

Sam Derbyshire
  • 719
  • 1
  • 4
  • 12