Type class for converting unlifted types

TL;DR: Should I add support for unlifted types to Witch?


I maintain Witch, a library for converting values between types. At its core, Witch provides this type class:

class From source target where
  from :: source -> target

This lets you handle conversions that cannot fail, like going from a Word8 to a Word:

instance From Word8 Word where
  from = fromIntegral
>>> from (15 :: Word8) :: Word
15

I don’t normally work with unlifted types. As a result, Witch doesn’t support them. If you try to define a From instance between, say, Word8# and Word#, you’ll get an error:

instance From Word8# Word# where
  from = word8ToWord#
Example.hs:1:15: error:
    • Expecting a lifted type, but ‘Word8#’ is unlifted
    • In the first argument of ‘From’, namely ‘Word8#’
      In the instance declaration for ‘From Word8# Word#’
  |
1 | instance From Word8# Word# where
  |               ^^^^^^

This isn’t a fundamental limitation though. Haskell supports levity polymorphism, so it should be possible to define a type class that would support these conversions. For example:

class FromP (source :: TYPE rep1) (target :: TYPE rep2) where
  from :: s -> t

All the old instances would be supported, since rep1 and rep2 would both be 'LiftedRep.

instance FromP Word8 Word where
  from = fromIntegral

This would also support converting between Word8# and Word#, since the two runtime representations don’t need to be the same.

instance FromP Word8# Word# where
  from = word8ToWord#

And this new type class could even support converting between runtime representations, like from an unlifted Word# to a lifted Word.

instance FromP Word8# Word where
  from = W#

This seems like a good change to make to the Witch library. It allows more instances to be provided at the cost of a slightly more complicated implementation. But since I only ever use lifted types, I haven’t actually run into this limitation. So I’m wondering: Would this be useful?

7 Likes

I’m also curious about the question: why not? Does inference get worse with this extra polymorphism?

1 Like

It sounds like this would add many new instances. What would be the cost, in term of compilation time, code size, …? This makes me wonder, what is the highest number of instances introduced by a typeclass on hackage?

1 Like

Great questions!

While Witch isn’t necessarily targeting beginners, I do think there’s value in presenting something that is understandable to beginners. It would be slightly unfortunate to have source :: TYPE a in the documentation, only to essentially tell people to ignore it unless they already know what it means.

Another potential problem is maintaining the same interface with type applications. The from method is designed to be usable with type applications, so you can say from @Word8 @Word to convert from a Word8 into a Word. With the new kind variables, the type signature is more complicated and requires you to say from @_ @_ @Word8 @Word, which isn’t ideal.

I know how to solve that problem with a function, but not with a type class method. I could say from :: forall {a} {b} s t . From (s :: TYPE a) (t :: TYPE b) => s -> t to make those kind variables implicit. Is that possible to do with methods?

Another problem introduced by the kind variables is the default implementation. Witch provides default from :: Coercible s t => s -> t; from = coerce so you can get newtype instances “for free”. With the kind variables, that default implementation doesn’t work, and I’m not sure if it’s an actual limitation or just something I don’t understand.

Adding more instances would certainly take longer to compile, but I don’t know how much longer. Currently Witch provides 321 instances. Compiling it on my machine takes about 7 seconds. If I remove all the instances, it takes about 4 seconds. So very roughly that’s about 3 milliseconds per instance.

3 Likes

Couldn’t you move from outside the class, perhaps making its definition from = realFrom, where realFrom is in the class? Or alternatively, keep from in the class and define nicerFrom = from outside the class.

3 Likes

Another problem introduced by the kind variables is the default implementation. Witch provides default from :: Coercible s t => s -> t; from = coerce so you can get newtype instances “for free”. With the kind variables, that default implementation doesn’t work

Made it work by introducing an auxiliary typeclass:

class FromP (s :: TYPE rep1) (t :: TYPE rep2) where
  from :: s -> t
  default from :: Aux s t => s -> t
  from = from'

class Aux (s :: TYPE rep1) (t :: TYPE rep2) where
    from' :: s -> t

instance Coercible s t => Aux s t where
    from' = coerce

instance FromP Int (Sum Int)

Not sure why this way works.

4 Likes

Thanks for the feedback!

@tomjaguarpaw: I can of course define realFrom as a method and make from a regular function. That would be a breaking change to Witch’s API, but perhaps it would be worth it.

@danidiaz: That’s a neat trick! I also found that it’s possible to remove the default instance and using standalone deriving with via to achieve more or less the same thing.

I’ve been playing around with this in a smaller example to try to come to grips with it. Like I said, I don’t often work with unlifted or unboxed types, so this is all a bit unusual for me. In particular I am frequently running into variations of the following two errors:

  • Expected a type, but 'x' has kind 'TYPE y': For example when trying to define something like tryFrom :: (source :: TYPE s) -> Maybe (target :: TYPE t).
  • [Something] does not have a fixed runtime representation: For example when trying to define a levity polymorphic version of via :: forall u s t . (Cast s u, Cast u t) => s -> t; via x = cast (cast x :: u).

It’s very possible that I’m trying to do things that don’t make any sense. I’m out of my depth here.

3 Likes

For what it’s worth, I have decided not to continue working on this. I couldn’t figure out how to get everything working with the API that Witch currently exposes. (Or something similar to it.) If someone more familiar with unboxed/unlifted types wants to give it a shot, please do!

5 Likes

That’s a reasonable decision, I can get behind that :relieved:
I feared that adding support for Unlifted Types may lead to the combinatorial explosion of instances in the witch library.


On this note, does anyone have examples of successful Haskell libraries that provided levity polymorphic abstractions? It’s great that you can abstract over the representation in Haskell but I wonder if it’s actually too cumbersome and awkward to the point that nobody bothered to do so :disappointed:

1 Like