
#12734: Unexpected context reduction stack overflow -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by danilo2): Ok, @Simon: 1) There are some special cases using stack regarding how it outputs its dump files, the docs for stack have been updated: https://github.com/commercialhaskell/stack/issues/2720 2) I was cutting down the example this evening. It took some time, but I've got it. It could be probably much simpler, but I think it is small enough to put it here, so here goes the example file we can test to investigate the error! :) {{{ {-# LANGUAGE NoMonomorphismRestriction #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TypeApplications #-} module Main where import Prelude import Control.Applicative import Control.Monad.Fix import Control.Monad.Trans.Identity import Control.Monad.Trans data A data B data Net data Type data Layer4 t l data TermStore -- Helpers: Stack data Stack layers (t :: * -> *) where SLayer :: t l -> Stack ls t -> Stack (l ': ls) t SNull :: Stack '[] t instance ( Constructor m (t l) , Constructor m (Stack ls t)) => Constructor m (Stack (l ': ls) t) instance Monad m => Constructor m (Stack '[] t) -- Helpers: Expr newtype Expr t layers = Expr (TermStack t layers) type TermStack t layers = Stack layers (Layer4 (Expr t layers)) -- Helpers: Funny typeclass class Monad m => Constructor m t instance ( Monad m, expr ~ Expr t layers, Constructor m (TermStack t layers) ) => Constructor m (Layer4 expr Type) -- HERE IS A FUNNY BEHAVIOR: the commented line raises context reduction stack overflow test_gr :: ( Constructor m (TermStack t layers), Inferable A layers m, Inferable B t m , bind ~ Expr t layers -- ) => m (Expr t layers) ) => m bind test_gr = undefined -- Explicit information about a type which could be infered class Monad m => Inferable (cls :: *) (t :: k) m | cls m -> t newtype KnownTypex (cls :: *) (t :: k) (m :: * -> *) (a :: *) = KnownTypex (IdentityT m a) deriving (Show, Functor, Monad, MonadIO, MonadFix, MonadTrans, Applicative, Alternative) instance {-# OVERLAPPABLE #-} (t ~ t', Monad m) => Inferable cls t (KnownTypex cls t' m) instance {-# OVERLAPPABLE #-} (Inferable cls t n, MonadTrans m, Monad (m n)) => Inferable cls t (m n) runInferenceTx :: forall cls t m a. KnownTypex cls t m a -> m a runInferenceTx = undefined -- running it test_ghc_err :: (MonadIO m, MonadFix m) => m (Expr Net '[Type]) test_ghc_err = runInferenceTx @B @Net $ runInferenceTx @A @'[Type] $ (test_gr) main :: IO () main = return () }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12734#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler