Skip to content

GitLab

  • Menu
Projects Groups Snippets
  • Help
    • Help
    • Support
    • Community forum
    • Submit feedback
  • Sign in / Register
  • GHC GHC
  • Project information
    • Project information
    • Activity
    • Labels
    • Members
  • Repository
    • Repository
    • Files
    • Commits
    • Branches
    • Tags
    • Contributors
    • Graph
    • Compare
    • Locked Files
  • Issues 4,864
    • Issues 4,864
    • List
    • Boards
    • Service Desk
    • Milestones
    • Iterations
  • Merge requests 457
    • Merge requests 457
  • CI/CD
    • CI/CD
    • Pipelines
    • Jobs
    • Schedules
    • Test Cases
  • Deployments
    • Deployments
    • Releases
  • Analytics
    • Analytics
    • Value stream
    • CI/CD
    • Code review
    • Insights
    • Issue
    • Repository
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
Collapse sidebar
  • Glasgow Haskell Compiler
  • GHCGHC
  • Issues
  • #9688
Closed
Open
Created Oct 13, 2014 by David Feuer@treeowlReporter

Improve the interaction between CSE and the join point transformation

It appears that the join point transformation sometimes interferes with CSE when CSE would be much better. Two examples:

digitToIntMaybe

Suppose we define

isHexDigit              :: Char -> Bool
isHexDigit c            =  (fromIntegral (ord c - ord '0')::Word) <= 9 ||
                           (fromIntegral (ord c - ord 'a')::Word) <= 5 ||
                           (fromIntegral (ord c - ord 'A')::Word) <= 5

digitToInt c
  | (fromIntegral dec::Word) <= 9 = dec
  | (fromIntegral hexl::Word) <= 5 = hexl + 10
  | (fromIntegral hexu::Word) <= 5 = hexu + 10
  | otherwise = error ("Char.digitToInt: not a digit " ++ show c) -- sigh
  where
    dec = ord c - ord '0'
    hexl = ord c - ord 'a'
    hexu = ord c - ord 'A'
-- We could also expand this out in cases manually, but it makes no
-- difference as far as I can tell.

Suppose we then write a naive digitToIntMaybe function:

digitToIntMaybe c
  | isHexDigit c = Just (digitToInt c)
  | otherwise    = Nothing

What I would want this to do is "zip" the nested cases and give Core like this:

$wdigitToIntMaybe
$wdigitToIntMaybe =
  \ ww_s2Ag ->
    let {
      x#_a2yy
      x#_a2yy = -# (ord# ww_s2Ag) 48 } in
    case tagToEnum# (leWord# (int2Word# x#_a2yy) (__word 9)) of _ {
      False ->
        let {
          x#1_X2z7
          x#1_X2z7 = -# (ord# ww_s2Ag) 97 } in
        case tagToEnum# (leWord# (int2Word# x#1_X2z7) (__word 5)) of _ {
          False ->
            let {
              x#2_X2zh
              x#2_X2zh = -# (ord# ww_s2Ag) 65 } in
            case tagToEnum# (leWord# (int2Word# x#2_X2zh) (__word 5)) of _ {
              False -> Nothing;
              True -> Just (I# (+# x#2_X2zh 10))
            };
          True -> Just (I# (+# x#1_X2z7 10))
        };
      True -> Just (I# x#_a2yy)
    }

digitToIntMaybe
digitToIntMaybe =
  \ w_s2Ad ->
    case w_s2Ad of _ { C# ww1_s2Ag -> $wdigitToIntMaybe ww1_s2Ag }

But instead, the join point transformation triggers, and we get this:

digitToIntMaybe1
digitToIntMaybe1 =
  \ ww_s2Cp ->
    error
      (unpackAppendCString#
         "Char.digitToInt: not a digit "# ($w$cshowsPrec15 ww_s2Cp ([])))

$wdigitToIntMaybe
$wdigitToIntMaybe =
  \ ww_s2Cp ->
    let {
      $j_s2Bc
      $j_s2Bc =
        \ _ ->
          Just
            (let {
               a_s2B5
               a_s2B5 = int2Word# (-# (ord# ww_s2Cp) 48) } in
             case tagToEnum# (leWord# a_s2B5 (__word 9)) of _ {
               False ->
                 let {
                   a1_s2B7
                   a1_s2B7 = int2Word# (-# (ord# ww_s2Cp) 97) } in
                 case tagToEnum# (leWord# a1_s2B7 (__word 5)) of _ {
                   False ->
                     let {
                       a2_s2B9
                       a2_s2B9 = int2Word# (-# (ord# ww_s2Cp) 65) } in
                     case tagToEnum# (leWord# a2_s2B9 (__word 5)) of _ {
                       False -> digitToIntMaybe1 ww_s2Cp;
                       True -> I# (+# (word2Int# a2_s2B9) 10)
                     };
                   True -> I# (+# (word2Int# a1_s2B7) 10)
                 };
               True -> I# (word2Int# a_s2B5)
             }) } in
    case tagToEnum#
           (leWord# (int2Word# (-# (ord# ww_s2Cp) 48)) (__word 9))
    of _ {
      False ->
        case tagToEnum#
               (leWord# (int2Word# (-# (ord# ww_s2Cp) 97)) (__word 5))
        of _ {
          False ->
            case tagToEnum#
                   (leWord# (int2Word# (-# (ord# ww_s2Cp) 65)) (__word 5))
            of _ {
              False -> Nothing;
              True -> $j_s2Bc void#
            };
          True -> $j_s2Bc void#
        };
      True -> $j_s2Bc void#
    }

digitToIntMaybe
digitToIntMaybe =
  \ w_s2Cm ->
    case w_s2Cm of _ { C# ww1_s2Cp -> $wdigitToIntMaybe ww1_s2Cp }

We perform the same three tests twice each, and test for an error condition that obviously can't happen.

quotRem and divMod

If we define

x `quot` y = fst (x `quotRem` y)
x `rem` y = snd (x `quotRem` y)

and then write something like

f x y | x `rem` y == 0 = x `quot` y
      | otherwise = 17

then CSE works some magic and we only calculate quotRem x y once.

Unfortunately, if we do this:

whatever x y = if x `myRem` y == 0 then (x `myQuot` y) + 14 else x `myQuot` y

then the join point transformation fires, collecting the myQuot x y expressions in the case branches and preventing CSE from recognizing the much better opportunity to eliminate those calculations altogether.

The situation with divMod is much worse. The join point transformation applied to the cases defining divMod prevents CSE from working magic on it in even simple situations, unless one of the arguments is known, making this definition unusable (the resulting Core is too horrifyingly long to paste here). It would probably be possible to improve the divMod situation to something close to the quotRem one by making divMod NOINLINE and adding special divModLit rules, but I'd much rather see a general solution.

Trac metadata
Trac field Value
Version 7.9
Type FeatureRequest
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
Assignee
Assign to
Time tracking