[GHC] #14607: Core Lint error

GHC ghc-devs at haskell.org
Sat Dec 23 04:44:14 UTC 2017


#14607: Core Lint error
-------------------------------------+-------------------------------------
        Reporter:  Iceland_jack      |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.2.2
      Resolution:                    |             Keywords:  TypeInType,
                                     |  DeferredTypeErrors
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:  #14605 #14584     |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Description changed by Iceland_jack:

Old description:

> This produces long {{{#!hs
> {-# Language DerivingStrategies #-}
> {-# Language GADTs #-}
> {-# Language GeneralizedNewtypeDeriving #-}
> {-# Language InstanceSigs #-}
> {-# Language KindSignatures #-}
> {-# Language TypeFamilies #-}
> {-# Language TypeInType #-}
> {-# Language TypeOperators #-}
>
> import Data.Kind
>
> data DEFUNC :: Type -> Type -> Type where
>   (:~>) :: a -> b -> DEFUNC a b
>
> type a ~> b = DEFUNC a b -> Type
>
> data LamCons a :: Type ~> Type where
>   LamCons :: a -> LamCons a ([a] :~> [a])
>
> class Mk (app :: Type ~> Type) where
>   type Arg app :: Type
>
>   mk :: Arg app -> app (a :~> b)
>
> instance Mk (LamCons a :: Type ~> Type) where
>   type Arg (LamCons a) = a
>
>   mk :: a -> LamCons (a :~> b)
>   mk = LamCons
> }}}
>
> erros with `ghci -ignore-dot-ghci -fdefer-type-errors -dcore-lint bug.hs`
> on GHC 8.2.1 and 8.3.20171208.

New description:

 This produces a long Core lint error:

 {{{#!hs
 {-# Language DerivingStrategies #-}
 {-# Language GADTs #-}
 {-# Language GeneralizedNewtypeDeriving #-}
 {-# Language InstanceSigs #-}
 {-# Language KindSignatures #-}
 {-# Language TypeFamilies #-}
 {-# Language TypeInType #-}
 {-# Language TypeOperators #-}

 import Data.Kind

 data DEFUNC :: Type -> Type -> Type where
   (:~>) :: a -> b -> DEFUNC a b

 type a ~> b = DEFUNC a b -> Type

 data LamCons a :: Type ~> Type where
   LamCons :: a -> LamCons a ([a] :~> [a])

 class Mk (app :: Type ~> Type) where
   type Arg app :: Type

   mk :: Arg app -> app (a :~> b)

 instance Mk (LamCons a :: Type ~> Type) where
   type Arg (LamCons a) = a

   mk :: a -> LamCons (a :~> b)
   mk = LamCons
 }}}

 with `ghci -ignore-dot-ghci -fdefer-type-errors -dcore-lint bug.hs` on GHC
 8.2.1 and 8.3.20171208.

--

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


More information about the ghc-tickets mailing list