Skip to content

GitLab

  • Projects
  • Groups
  • Snippets
  • Help
    • Loading...
  • Help
    • Help
    • Support
    • Community forum
    • Submit feedback
  • Sign in / Register
GHC
GHC
  • Project overview
    • Project overview
    • Details
    • Activity
    • Releases
  • Repository
    • Repository
    • Files
    • Commits
    • Branches
    • Tags
    • Contributors
    • Graph
    • Compare
    • Locked Files
  • Issues 4,310
    • Issues 4,310
    • List
    • Boards
    • Labels
    • Service Desk
    • Milestones
    • Iterations
  • Merge Requests 382
    • Merge Requests 382
  • Requirements
    • Requirements
    • List
  • CI / CD
    • CI / CD
    • Pipelines
    • Jobs
    • Schedules
  • Security & Compliance
    • Security & Compliance
    • Dependency List
    • License Compliance
  • Operations
    • Operations
    • Incidents
    • Environments
  • Analytics
    • Analytics
    • CI / CD
    • Code Review
    • Insights
    • Issue
    • Repository
    • Value Stream
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Members
    • Members
  • Collapse sidebar
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
  • Glasgow Haskell Compiler
  • GHCGHC
  • Issues
  • #13025

Closed
Open
Opened Dec 21, 2016 by acowley@trac-acowley

Type family reduction irregularity (change from 7.10.3 to 8.0.1)

I was recently made aware that vinyl's performance dramatically deteriorated with GHC 8.0.1 when compared to GHC 7.x. Vinyl is an extensible records library that's been around for about four years; the aspect of its design relevant here is the basic HList-style indexed GADT. Care was taken in the past so that working with, say, a Storable Vector of records would suffer no overhead from vinyl when compared with standard records, and we have a benchmark suite to spot check this.

In the move to GHC-8.0.1, it turns out that we do introduce overhead. Inspecting the Core reveals that the benchmark inner loop includes a case match on an HEq_sc value whose presence I would not expect, and that is not present when compiling with GHC-7.10.3:

case HEq_sc
         @ Nat
         @ Nat
         @ ('S 'Z)
         @ (RIndex
              '("normal", V3 Float)
              '['("tex", V2 Float), '("normal", V3 Float)])
         ($s$fRElemar:S_$s$fRElemar:S_$cp1RElem
          `cast` (N:~[0] <Nat>_N <'S 'Z>_N <RIndex
                                              '("normal",
                                                V3 Float)
                                              '['("tex",
                                                  V2 Float),
                                                '("normal",
                                                  V3 Float)]>_N
                  :: (('S 'Z :: Nat)
                      ~
                      (RIndex
                         '("normal", V3 Float)
                         '['("tex", V2 Float),
                           '("normal",
                             V3 Float)] :: Nat) :: Constraint)
                     ~R#
                     (('S 'Z :: Nat)
                      ~~
                      (RIndex
                         '("normal", V3 Float)
                         '['("tex", V2 Float),
                           '("normal",
                             V3 Float)] :: Nat) :: Constraint)))
  of cobox0 { __DEFAULT ->

I have since made an effort to reproduce the issue, and discovered more fragility than I expected. I am attaching two modules: Rec.hs defines a kind of record type, Main.hs is a test program that I will reproduce here,

{-# LANGUAGE DataKinds #-}
module Main where
import Rec

type MyRec = Rec '[ '("A",Int), '("B",Int), '("C",Int) ]

getC :: MyRec -> Int
getC = getField (Proxy::Proxy '("C",Int))

doubleC :: MyRec -> MyRec
doubleC r = setC (2 * (getC r)) r
  where setC = set . (Field :: Int -> Field '("C",Int))

main :: IO ()
main = print (getC (Field 1 :& Field 2 :& Field 3 :& Nil :: MyRec))

If the doubleC definition is present, the Core emitted (with -O2) includes an HEq_sc case in the RHS of getC. If doubleC is commented out, that case HEq_sc ... is no longer present. In this example, the offending piece of Core is,

case HEq_sc
       @ Nat
       @ Nat
       @ (Index '("C", Int) '['("B", Int), '("C", Int)])
       @ ('S 'Z)
       ($s$fHasFieldkr:S_$s$fHasFieldkr:S_$cp1HasField
        `cast` (N:~[0] <Nat>_N <Index
                                  '("C", Int) '['("B", Int), '("C", Int)]>_N <'S 'Z>_N
                :: ((Index '("C", Int) '['("B", Int), '("C", Int)] :: Nat)
                    ~
                    ('S 'Z :: Nat) :: Constraint)
                   ~R#
                   ((Index '("C", Int) '['("B", Int), '("C", Int)] :: Nat)
                    ~~
                    ('S 'Z :: Nat) :: Constraint)))
of cobox1 { __DEFAULT ->

If the contents of Rec.hs are included in Main.hs, the case HEq_sc ... is not present in the resulting Core.

The result of what looks like a failure to normalize the Index type family (or RIndex in vinyl) manifests as a 2x slowdown in the benchmark available in the vinyl repository.

Trac metadata
Trac field Value
Version 8.0.1
Type Bug
TypeOfFailure OtherFailure
Priority normal
Resolution Unresolved
Component Compiler
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
Assignee
Assign to
8.2.1
Milestone
8.2.1 (Past due)
Assign milestone
Time tracking
None
Due date
None
Reference: ghc/ghc#13025