Skip to content

Derived Enum for small number of constructors seems suboptimal

{-# LANGUAGE MagicHash #-}
module En (toEnum', toEnum'', toEnum''', toEnum'''') where

import GHC.Int
import GHC.Prim
import GHC.Word

data Q' = Foo' | Bar'
    deriving Enum

toEnum' :: Int -> Q'
toEnum' 0 = Foo'
toEnum' 1 = Bar'
toEnum' x = error $ "out of range " <> show x

toEnum'' :: Int -> Q'
toEnum'' x@(I# n) | x >= 0 && x <= 1 = tagToEnum# n
toEnum'' x = error $ "out of range " <> show x

toEnum''' :: Int -> Q'
toEnum''' x@(I# n) | x == 0 || x == 1 = tagToEnum# n
toEnum''' x = error $ "out of range " <> show x

toEnum'''' :: Int -> Q'
toEnum'''' x@(I# n) = case int2Word# n `leWord#` 1## of
    0# -> error $ "out of range " <> show x
    _ -> tagToEnum# n

For the derived toEnum, we get something as

-- RHS size: {terms: 19, types: 4, coercions: 0, joins: 0/0}
En.$w$ctoEnum [InlPrag=NOUSERINLINE[2]] :: Int# -> Q'
[GblId,
 Arity=1,
 Str=<S,U>,
 Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
         WorkFree=True, Expandable=True, Guidance=IF_ARGS [0] 83 0}]
En.$w$ctoEnum
  = \ (ww_s3Kl :: Int#) ->
      case >=# ww_s3Kl 0# of {
        __DEFAULT -> En.$wlvl ww_s3Kl;
        1# ->
          case <=# ww_s3Kl 1# of {
            __DEFAULT -> En.$wlvl ww_s3Kl;
            1# -> tagToEnum# @ Q' ww_s3Kl
          }
      }

-- RHS size: {terms: 6, types: 3, coercions: 0, joins: 0/0}
En.$fEnumQ'_$ctoEnum [InlPrag=NOUSERINLINE[2]] :: Int -> Q'
[GblId,
 Arity=1,
 Str=<S(S),1*U(U)>,
 Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
         WorkFree=True, Expandable=True,
         Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False)
         Tmpl= \ (w_s3Ki [Occ=Once!] :: Int) ->
                 case w_s3Ki of { I# ww1_s3Kl [Occ=Once] ->
                 En.$w$ctoEnum ww1_s3Kl
                 }}]
En.$fEnumQ'_$ctoEnum
  = \ (w_s3Ki :: Int) ->
      case w_s3Ki of { I# ww1_s3Kl -> En.$w$ctoEnum ww1_s3Kl }

Two comparisons to find out one thing! Contrast this with something like toEnum':

toEnum'
  = \ (ds_d3dp :: Int) ->
      case ds_d3dp of { I# ds1_d3dr ->
      case ds1_d3dr of ds2_X3dR {
        __DEFAULT -> En.$wlvl1 ds2_X3dR;
        0# -> En.Foo';
        1# -> En.Bar'
      }
      }

Surely this seems better? But we don't even have to write out the constructors by hand in this case. toEnum''' actually produces the same code as toEnum'.

I also wrote toEnum'''' which I had some hopes for but actually runs the slowest. I'm unsure why. Seems simple enough:

toEnum''''
  = \ (x_a2Sd :: Int) ->
      case x_a2Sd of { I# n_a2Se ->
      case leWord# (int2Word# n_a2Se) 1## of {
        __DEFAULT -> tagToEnum# @ Q' n_a2Se;
        0# -> En.$wlvl4 n_a2Se
      }
      }

The point of this ticket is to consider whether it's not better to simply expand small number of constructors in a derived enumeration into a pattern match. In microbenchmark, toEnum' seems faster.

Trac metadata
Trac field Value
Version 8.6.3
Type Bug
TypeOfFailure OtherFailure
Priority normal
Resolution Unresolved
Component Compiler
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information