[GHC] #16184: GHC said to report a bug

#16184: GHC said to report a bug -------------------------------------+------------------------------------- Reporter: TheKing01 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 (Type checker) | Keywords: panic, skolem | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I tried to run {{{#!hs {-# LANGUAGE Rank2Types, PartialTypeSignatures #-} import Control.Monad newtype Search b = Search {optimum :: forall a. Ord a => (b -> a) -> b} instance Monad Search where return a = Search $ const a Search ma >>= f = Search $ \p -> optimum (f (ma (\a -> p (optimum (f a) p)))) p instance Functor Search where fmap = liftM instance Applicative Search where pure = return (<*>) = ap pair a b = Search $ \p -> if p a >= p b then a else b toList s = igo [] where igo ls = let x = optimum s (\x' -> x' `notElem` ls) in if x `elem` ls then ls else igo (x:ls) cantor :: Search (Integer -> Bool) cantor = let igo :: _ igo p n = q n (optimum cantor $ q n) where q n a = p undefined in Search igo main = return () }}} When run, it said {{{ source_file.hs:24:5: No instance for (Ord a) When checking that ‘igo’ has the specified type igo :: forall t a t1. (t -> a) -> t1 -> a Probable cause: the inferred type is ambiguous In the expression: let igo :: _ igo p n = q n (optimum cantor $ q n) where q n a = ... in Search igo In an equation for ‘cantor’: cantor = let igo :: _ igo p n = q n (optimum cantor $ q n) where ... in Search igo source_file.hs:26:15: Couldn't match type ‘t’ with ‘Integer -> Bool’ ‘t’ is untouchable inside the constraints (Ord a1) bound by a type expected by the context: Ord a1 => ((Integer -> Bool) -> a1) -> Integer -> Bool at source_file.hs:26:8-17ghc: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-unknown-linux): No skolem info: t_aU3[sk] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} Since it said to report a bug, I am. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16184 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16184: GHC said to report a bug -------------------------------------+------------------------------------- Reporter: TheKing01 | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.3 checker) | Resolution: wontfix | Keywords: panic, skolem Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => wontfix Comment: Thanks. Seems OK with a more up to date GHC. E.g GHC 8.4 says {{{ T16184.hs:28:15: error: • Couldn't match type ‘a’ with ‘Bool’ ‘a’ is a rigid type variable bound by a type expected by the context: forall a. Ord a => ((Integer -> Bool) -> a) -> Integer -> Bool at T16184.hs:28:8-17 Expected type: ((Integer -> Bool) -> a) -> Integer -> Bool Actual type: ((Integer -> Bool) -> Bool) -> Integer -> Bool }}} I'm afraid we won't go back to fix 7.10. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16184#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC