[GHC] #14321: -fsolve-constant-dicts is not very robust when dealing with GADTs

#14321: -fsolve-constant-dicts is not very robust when dealing with GADTs -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #9701 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I expected `-fsolve-constant-dicts` to nail #9701, it didn't fire at all but a slightly modified version does. {{{ {-# LANGUAGE GADTs #-} {-# LANGUAGE TypeApplications #-} module Foo where data Silly a where Silly :: Ord a => a -> Silly a isItSilly :: a -> Silly a -> Bool isItSilly a (Silly x) = a < x isItSillyIntTA :: Int -> Silly Int -> Bool isItSillyIntTA = isItSilly @Int isItSillyInt :: Int -> Silly Int -> Bool isItSillyInt a x = isItSilly a x isItSillyInt2 :: Int -> Silly Int -> Bool isItSillyInt2 a (Silly x) = a < x isItSillyInt3 :: Int -> Silly Int -> Bool isItSillyInt3 a (Silly x) = isItSilly a (Silly x) }}} Both versions 2 and 3 specialise nicely using the `Int` `Ord` dictionary. The first two versions don't. I'm unsure whether it *should* fire or not but I am making this ticket to record this fact. Clonable code and core dump - https://gist.github.com/mpickering/f84a5f842861211e8e731c63e82d5c01 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14321 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14321: -fsolve-constant-dicts is not very robust when dealing with GADTs -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9701 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm not sure what you are expecting here. `isItSilly` tyepchecks and elaborates thus: {{{ isItSilly (v::a) (Silly (d:: Ord a) (x::a)) = (<) d v x }}} It can't do anyting else. `isItSillyIntTA` is simply a call to `isItSilly`. No dictionaries at all; solving constant dictionries doesn't arise. Ditto `isItSillyInt`. Look as if it's all behaving precisely as advertised. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14321#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14321: -fsolve-constant-dicts is not very robust when dealing with GADTs -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9701 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): In `isItSillyIntTA`, if `isItSilly` was inlined.. {{{ isItSillyIntTA = (\@a1 -> \(a :: a1) -> \(s :: Silly1 a1) -> case s of (Silly1 ($dOrd :: Ord a1) (x :: a1)) -> (< $dOrd) a x) @Int }}} Then beta reduction on the type argument leaves you with {{{ isItSillyIntTA = (\(a : Int) -> \(s :: Silly1 Int) -> case s of (Silly1 ($dOrd :: Ord Int) (x :: Int) -> (< $dOrd) a x)) }}} So is the dictionary not statically known here in the same sense that -fsolve-constant-dicts is meant to solve? I think I am subtly misunderstanding the scope of the flag. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14321#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14321: -fsolve-constant-dicts is not very robust when dealing with GADTs -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9701 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): ALl constraint solving is done on the original source programming. No inlining, nothing. When simplification/inlining starts, constraint solving is over. Nothign more than that. The flag controls only what happens at constraint-solving time. Maybe it should be better documented -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14321#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC