
#13547: ghc: panic! StgCmmEnv: variable not found -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: 10158 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Here is a much smaller test case. Still a big mess of applicative do and arrows, neither of which I am familiar with, alas. {{{ {-# LANGUAGE Arrows #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE UndecidableInstances #-} module Document.Phase.Proofs2 (step) where import Control.Applicative import Control.Arrow import Control.Category import Control.Monad import Data.Functor.Compose import Data.Maybe import Data.Proxy import Data.Typeable import GHC.Exts (Constraint) import Prelude hiding (id,(.)) data Inference rule data MachineP3 data RawProgressProp data Cell1 (f :: * -> *) (constr :: * -> Constraint) = forall a. (constr a, Typeable a) => Cell (f a) data Inst1 f constr a = (Typeable a,constr a) => Inst (f a) newtype RuleProxy = RuleProxy { _ruleProxyCell :: Cell1 Proxy RuleParser } type VoidInference = Cell1 (Compose Inference Proxy) RuleParser class Monad m => MonadReader r m | m -> r where instance MonadReader r ((->) r) where class RuleParser rule where type Lens' s a = Lens s s a a type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t type Getting r s a = (a -> Const r a) -> s -> Const r s class HasCell s a | s -> a where instance HasCell RuleProxy (Cell1 (Proxy :: * -> *) RuleParser) where data LatexParserA a g = LatexParserA instance Category LatexParserA where instance Arrow LatexParserA where ----------------------------- stepList :: MachineP3 -> LatexParserA (RawProgressProp,Inst1 Proxy RuleParser rule) VoidInference stepList m = error "urk" step :: MachineP3 -> LatexParserA (RawProgressProp,RuleProxy) VoidInference step m = insideOneEnvOf ["step","flatstep"] $ proc (goal,prxy) -> do Cell prxy' <- arr (view xcell) -< prxy stepList m -< (goal,Inst prxy') view :: MonadReader s m => Getting a s a -> m a view l = error "urk" insideOneEnvOf :: [String] -> LatexParserA a b -> LatexParserA a b insideOneEnvOf = error "urk" xcell :: HasCell s a => Lens' s a xcell = error "urk" }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13547#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler