[GHC] #14231: Core lint error "in result of Static argument"
GHC
ghc-devs at haskell.org
Thu Sep 14 13:51:51 UTC 2017
#14231: Core lint error "in result of Static argument"
-------------------------------------+-------------------------------------
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:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Whilst investigating #14211 I encountered a core lint error.
{{{
{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
module Async where
data AsyncT m a =
AsyncT {
runAsyncT :: forall r.
Maybe Int -- state
-> m r -- stop
-> (a -> Maybe Int -> Maybe (AsyncT m a) -> m r) -- yield
-> m r
}
------------------------------------------------------------------------------
-- Monad
------------------------------------------------------------------------------
{-# INLINE bindWith #-}
bindWith
:: (forall c. AsyncT m c -> AsyncT m c -> AsyncT m c)
-> AsyncT m a
-> (a -> AsyncT m b)
-> AsyncT m b
bindWith k (AsyncT m) f = AsyncT $ \_ stp yld ->
m Nothing stp (\a _ m -> (\x -> (runAsyncT x) Nothing stp yld) $ maybe (f
a) (\r -> f a `k` (bindWith k r f)) m )
}}}
Compile with `ghc -O2 -fno-worker-wrapper -fstatic-argument-transformation
-dcore-lint`.
Error:
{{{
*** Core Lint errors : in result of Static argument ***
<no location info>: warning:
In the expression: bindWith @ m_aV5 @ a_aV6 @ b_aV7 k_aSU x_aX3 f_aSW
Mismatch in type between binder and occurrence
Var: bindWith_rpi
Binder type: forall (m1 :: * -> *) a1 b1 .
(forall c . AsyncT m_aV5 c -> AsyncT m_aV5 c -> AsyncT m_aV5 c)
-> AsyncT m_aV5 a_aV6 -> (a_aV6 -> AsyncT m_aV5 b_aV7) -> AsyncT m_aV5
b_aV7
Occurrence type: forall (m :: * -> *) a b .
(forall c . AsyncT m c -> AsyncT m c -> AsyncT m c)
-> AsyncT m a -> (a -> AsyncT m b) -> AsyncT m b
Before subst: forall (m :: * -> *) a b .
(forall c . AsyncT m c -> AsyncT m c -> AsyncT m c)
-> AsyncT m a -> (a -> AsyncT m b) -> AsyncT m b
*** Offending Program ***
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14231>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list