Can I give unboxed tuple of ZeroBitType the kind ZeroBitType again?

My code:

{-# LANGUAGE UnboxedTuples, MagicHash, UnliftedNewtypes #-}

import GHC.Exts (ZeroBitType)

type Unit :: ZeroBitType
type Unit = (# #)

type TwoUnits :: ZeroBitType
newtype TwoUnits = TwoUnits (# Unit, Unit #)

The error:

File.hs:10:29: error: [GHC-83865]
    • Couldn't match kind: [GHC.Types.ZeroBitRep, GHC.Types.ZeroBitRep]
                     with: '[]
      Expected kind 'ZeroBitType',
        but '(# Unit, Unit #)' has kind 'TYPE
                                           (GHC.Types.TupleRep
                                              [GHC.Types.ZeroBitRep, GHC.Types.ZeroBitRep])'
    • In the type '(# Unit, Unit #)'
      In the definition of data constructor 'TwoUnits'
      In the newtype declaration for 'TwoUnits'
   |
10 | newtype TwoUnits = TwoUnits (# Unit, Unit #)
   |                             ^^^^^^^^^^^^^^^^
Failed, no modules loaded.

This makes a lot of sense, but also, it’s a bit annoying.
I have some code where I want to enforce that a type doesn’t exist at run-time, but it doesn’t cover cases like this where it’s a tuple of zero-sized types.

Is there any solution?

Write a type family UnariseRep that flattens tuples of tuples and test that the result has width 0.

1 Like

Right, something like:

{-# LANGUAGE TypeFamilies, DataKinds, UndecidableInstances #-}

import GHC.Exts (RuntimeRep(..), TYPE)

import Data.Kind (Constraint)
import Data.Type.Bool (type (&&))

type family IsZeroBitF (rr :: RuntimeRep) :: Bool where
  IsZeroBitF (TupleRep '[]   ) = 'True
  IsZeroBitF (TupleRep (x:xs)) = IsZeroBitF x && IsZeroBitF (TupleRep xs)
  IsZeroBitF _                 = 'False

type IsZeroBit (t :: TYPE rr) = IsZeroBitF rr ~ 'True :: Constraint
1 Like

Thanks! Not very clean but nonetheless a solution.