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,334
    • Issues 4,334
    • List
    • Boards
    • Labels
    • Service Desk
    • Milestones
    • Iterations
  • Merge Requests 368
    • Merge Requests 368
  • 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
  • #15135

Closed
Open
Opened May 09, 2018 by Antoine Leblanc@trac-nicuveo

Overlapping typeclass instance selection depends on the optimisation level

A file A defines a typeclass, and gives an instance for all types a, and exports a function relying on said typeclass. A file B defines a data type, makes it a specific OVERLAPPING instance of that class, and uses the function defined in A. Which instance ends up being picked for B depends on the optimisation level those files are compiled with.

  • *Minimal test case**

//A.hs//

{-# LANGUAGE FlexibleInstances #-}
{-# OPTIONS_GHC -fno-warn-simplifiable-class-constraints #-}

module A where

import           Data.Maybe

class A a where
  someValue :: a -> Maybe Int

instance A a where
  someValue = const Nothing

getInt :: A a => a -> Int
getInt x = fromMaybe 0 $ someValue x

//B.hs//

module B where

import           A

data B = B Int

instance {-# OVERLAPPING #-} A B where
  someValue (B x) = Just x

getBInt :: Int
getBInt = getInt $ B 42

//Main.hs//

import           B

main :: IO ()
main = putStrLn $ "B: " ++ show getBInt

To reproduce:

$ ghc -O0 -fforce-recomp Main.hs && ./Main 
[1 of 3] Compiling A                ( A.hs, A.o )
[2 of 3] Compiling B                ( B.hs, B.o )
[3 of 3] Compiling Main             ( Main.hs, Main.o )
Linking Main ...
B: 42

$ ghc -O2 -fforce-recomp Main.hs && ./Main 
[1 of 3] Compiling A                ( A.hs, A.o )
[2 of 3] Compiling B                ( B.hs, B.o )
[3 of 3] Compiling Main             ( Main.hs, Main.o )
Linking Main ...
B: 0

The fix introduced to fix #14434 (closed) instructs the "short-cut solver" to not automatically choose a matching instance if it marked as INCOHERENT or OVERLAPPABLE, but in this case the instance is not marked in any way. This might be the source of the bug?

Additionally, whatever the optimisation level, ghc emits a warning about the A a => class constraint being simplifiable; but if it is removed, then the program prints "0" in both cases.

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