[GHC] #14939: StaticPointers + -dcore-lint: cause Core Lint error??

GHC ghc-devs at haskell.org
Mon Mar 19 06:54:44 UTC 2018


#14939: StaticPointers + -dcore-lint: cause Core Lint error??
-------------------------------------+-------------------------------------
           Reporter:  Iceland_jack   |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.5
           Keywords:                 |  Operating System:  Unknown/Multiple
  StaticPointers                     |
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 This is an odd bug

 {{{#!hs
 {-# Language StaticPointers #-}

 import Data.Kind

 type Cat ob = ob -> ob -> Type

 type Alg cls ob = ob

 newtype Frí (cls::Type -> Constraint) :: (Type -> Alg cls Type) where
   Frí :: { with :: forall x. cls x => (a -> x) -> x }
       -> Frí cls a

 data AlgCat (cls::Type -> Constraint) :: Cat (Alg cls Type) where
   AlgCat :: (cls a, cls b) => (a -> b) -> AlgCat cls a b

 leftAdj :: AlgCat cls (Frí cls a) b -> (a -> b)
 leftAdj (AlgCat f) a = undefined
 }}}

 causes a

 {{{
 $ ./ghc-stage2 --interactive -ignore-dot-ghci -dcore-lint 222-bug.hs
 GHCi, version 8.5.20180128: http://www.haskell.org/ghc/  :? for help
 [1 of 1] Compiling Main             ( 222-bug.hs, interpreted )
 *** Core Lint errors : in result of Float out(FOS {Lam = Just 0,
                                                    Consts = True,
                                                    OverSatApps = False})
 ***
 <no location info>: warning:
     In the type ‘forall (cls :: * -> Constraint) (b :: Alg cls *). b’
     Variable escape in forall: forall (cls :: *
                                               -> Constraint) (b :: Alg cls
 *).
                                b
 *** Offending Program ***
 with
   :: forall (cls :: * -> Constraint) a.
      Frí cls a -> forall x. cls x => (a -> x) -> x
 [LclIdX[[RecSel]], Arity=2]
 with

  ..  . --->8------->8------->8--- ..
 }}}

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14939>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list