3

I'm playing around with specialization of singletons:

{-# LANGUAGE DataKinds      #-}
{-# LANGUAGE GADTs          #-}
{-# LANGUAGE KindSignatures #-}

module Data.Test where

data SingBool (b :: Bool) where
  STrue :: SingBool 'True
  SFalse :: SingBool 'False

sing :: SingBool b -> Bool
sing SFalse = False
sing STrue  = True
{-# SPECIALIZE sing :: SingBool 'False -> Bool #-}

This specializes to something like the following:

singSFalse :: SingBool 'False -> Bool
singSFalse SFalse = False

I'd expect it to generate an RHS of singSFalse _ = False instead.

Is that coercion unpacked only to satisfy the type-checker or is there actual runtime overhead involved in that pattern match? I imagine that GHC does not discard the pattern match on the argument to account for bottom, in order not to increase laziness. But I want to be sure before I begin to model this through Proxy + a SingI-style type class.

Sebastian Graf
  • 3,602
  • 3
  • 27
  • 38
  • 1
    I think your diagnosis is correct, but I should mention that last I heard the GHC documentation was kind of lying about `SPECIALIZE` and GADTs. That pragma (probably) has no effect, and if specialization happens its through constructor specialization. – dfeuer Aug 17 '17 at 16:24
  • Ah, that explains the warnings (something along the lines of 'SPECIALIZE has no effect here'). But even in my bigger use case, GHC specializes correctly beyond module boundaries without warnings, probably because there are also some type class dictionaries involved which I don't really specialize. Edit: That might have to do with INLINABLE... – Sebastian Graf Aug 17 '17 at 17:15
  • Anyway, I'm going with the type class solution https://github.com/sgraf812/pomaps/blob/ebfad35ca1864c6cb8f5921fb804cac26ca944f7/library/Data/POMap/Internal.hs#L207-L211 – Sebastian Graf Aug 17 '17 at 17:16

1 Answers1

2

OK, to mostly answer my own question: Knowing that SingBool 'False only has one inhabitant is not enough for GHC to get rid of the pattern match, because we could call the function like singSFalse (error "matched"), e.g. bottom is always another inhabitant.

So, specialization (e.g. inlining based on concrete TypeApplications) does not really work well with singletons (turning those type applications into presumably constant value applications) in Haskell (lazy, non-total) w.r.t. zero cost abstractions.

However, by using a SingI-style type class with a proxy (e.g. singByProxy), we don't have the same problems:

{-# LANGUAGE DataKinds      #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MagicHash      #-}

module Data.Test where

import           GHC.Exts (Proxy#)

class SingIBool (b :: Bool) where
  sing :: Proxy# b -> Bool

instance SingIBool 'False where
  sing _ = False

instance SingIBool 'True where
  sing _ = True

refurbulate :: SingIBool b => Proxy# b -> Int
refurbulate p
  | sing p = 0
  | otherwise = 1

The specialization refurbulate @(Proxy# 'False) will not only be implemented as const False, also there will not be passed any Proxy# argument at the value level, so it's rather coerce False :: Proxy# -> Bool. Neat! However, I don't get to use singletons in the real world :(


To recap why singletons fail (to get optimized) and type classes work:

By specializing the type class instance, we get to know the RHS of sing, from which we can deduce totality.

By specializing the singleton, we get to know what value the parameter evaluates to, if evaluation terminates.

Knowing the canonical RHS of a type class method x :: () is more informative than just knowing that a parameter x :: () can only evaluate to one value in a non-total, lazy (e.g. Haskell's) setting.

Sebastian Graf
  • 3,602
  • 3
  • 27
  • 38
  • The pattern match shouldn't be terribly expensive. It's really just `seq`; once the value is in WHNF, there's nothing else to do. And if you use a `SingI` class method that produces a `SingBool`, the application of `sing` to the result should be optimized properly, I believe. The problem with an overly class-based approach is that it gets messy when the type isn't statically known. – dfeuer Aug 17 '17 at 17:53
  • I'll probably benchmark this when the rest of the code is stable. – Sebastian Graf Aug 17 '17 at 18:28