| CARVIEW |
Select Language
HTTP/2 301
server: nginx
date: Fri, 16 Jan 2026 14:59:24 GMT
content-type: text/html
content-length: 115
location: https://gitlab.haskell.org/ghc/ghc/-/issues/17810
cache-control: no-cache
nel: {"max_age": 0}
x-gitlab-meta: {"correlation_id":"01KF3N2YHGZ7B6P8YWZ1HMZYQY","version":"1"}
x-request-id: 01KF3N2YHGZ7B6P8YWZ1HMZYQY
x-runtime: 0.042010
HTTP/2 200
server: nginx
date: Fri, 16 Jan 2026 14:59:26 GMT
content-type: text/html; charset=utf-8
content-length: 86750
cache-control: max-age=0, private, must-revalidate
content-security-policy:
etag: W/"c58232975217e4acc048f4e446c7228d"
nel: {"max_age": 0}
permissions-policy: interest-cohort=()
referrer-policy: strict-origin-when-cross-origin
set-cookie: _gitlab_session=b4bf3e307b612a8d6d4543e03e259d8f; path=/; secure; HttpOnly; SameSite=None
vary: Accept
x-content-type-options: nosniff
x-download-options: noopen
x-frame-options: SAMEORIGIN
x-gitlab-meta: {"correlation_id":"01KF3N2ZV2Q1H646DXS6VR2BFD","version":"1"}
x-permitted-cross-domain-policies: none
x-request-id: 01KF3N2ZV2Q1H646DXS6VR2BFD
x-runtime: 0.415500
x-ua-compatible: IE=edge
x-xss-protection: 1; mode=block
Lint failure in Specialize (#17810) · Issues · Glasgow Haskell Compiler / GHC · GitLab
Skip to content
Lint failure in Specialize
Ticket extracted from #17801 (closed).
To reproduce, use two files:
-- Foo.hs
module Foo where
import Control.Monad.Except
class Monad m => ReadTCState m where
locallyTCState :: m ()
liftReduce :: m ()
instance ReadTCState m => ReadTCState (ExceptT err m) where
locallyTCState = undefined
liftReduce = lift liftReduce
instance MonadIO m => ReadTCState (TCMT m) where
locallyTCState = (undefined <$> liftReduce) <* TCM (\_ -> return ())
liftReduce = undefined
newtype TCMT m a = TCM { unTCM :: () -> m a }
instance MonadIO m => Functor (TCMT m) where
fmap f (TCM m) = TCM $ \r -> liftM f (m r )
instance MonadIO m => Applicative (TCMT m) where
pure x = TCM (\_ -> return x)
(<*>) (TCM mf) (TCM m) = TCM $ \r -> ap (mf r) (m r)
instance MonadIO m => Monad (TCMT m) where
(>>=) (TCM m) k = TCM $ \r -> m r >>= \x -> unTCM (k x) r
-- Bar.hs
module Bar where
import Control.Monad.Except
import Foo
f :: ExceptT e (TCMT IO) ()
f = liftReduce
and compile with
ghc -fforce-recomp Bar.hs -dcore-lint -O -fspecialise-aggressively
[1 of 2] Compiling Foo ( Foo.hs, Foo.o )
[2 of 2] Compiling Bar ( Bar.hs, Bar.o )
*** Core Lint errors : in result of Specialise ***
<no location info>: warning:
Recursive or top-level binder has strict demand info: $dMonad_s2iO
Binder's demand info: <S(LLC(C(S))L),U(1*U(1*U(1*C1(C1(U)),A),A,A,A,A,A),C(C1(U)),C(C1(U)),C(U))>
In the RHS of $dMonad_s2iO :: Monad IO
Substitution: [TCvSubst
In scope: InScope {f $trModule $dReadTCState_s2im $dMonad_s2in
f_s2ip $trModule_s2iq $trModule_s2ir $trModule_s2is
$trModule_s2it ww_s2iy ww1_s2iz ww3_s2iA ww4_s2iB ww8_s2iC
ww9_s2iD $dMonad_s2iO $s$fFunctorTCMT2_s2iQ
$s$fFunctorTCMT1_s2iR $s$fFunctorTCMT_s2iS
$s$fApplicativeTCMT_s2iT $s$fMonadTCMT_$c>>_s2iU
$s$fMonadTCMT_s2iV $s$w$cliftReduce_s2iW
$s$fReadTCStateExceptT1_s2iX $sap'_s2iZ
$s$fReadTCStateTCMT_$clocallyTCState_s2j0
$s$fReadTCStateTCMT_s2j1}
Type env: []
Co env: []]
@awson says that reverting b911c532 cures this issue. I could not confirm.
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information