[GHC] #14715: GHC 8.4.1-alpha regression with PartialTypeSignatures

GHC ghc-devs at haskell.org
Wed Jan 24 20:31:53 UTC 2018


#14715: GHC 8.4.1-alpha regression with PartialTypeSignatures
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  highest        |         Milestone:  8.4.1
          Component:  Compiler       |           Version:  8.4.1-alpha1
  (Type checker)                     |
           Keywords:                 |  Operating System:  Unknown/Multiple
  PartialTypeSignatures              |
       Architecture:                 |   Type of failure:  GHC rejects
  Unknown/Multiple                   |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 This bug prevents `lol-apps`' tests and benchmarks from building with GHC
 8.4.1-alpha2. This is as much as I'm able to minimize the issue:

 {{{#!hs
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE PartialTypeSignatures #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# OPTIONS_GHC -Wno-partial-type-signatures #-}
 module Bug (bench_mulPublic) where

 data Cyc r
 data CT zp r'q
 class Reduce a b
 type family LiftOf b

 bench_mulPublic :: forall z zp zq . (z ~ LiftOf zq, _) => Cyc zp -> Cyc z
 -> IO (zp,zq)
 bench_mulPublic pt sk = do
   ct :: CT zp (Cyc zq) <- encrypt sk pt
   undefined ct

 encrypt :: forall z zp zq. Reduce z zq => Cyc z -> Cyc zp -> IO (CT zp
 (Cyc zq))
 encrypt = undefined
 }}}

 On GHC 8.2.2, this compiles without issue. But on GHC 8.4.1-alpha2, this
 errors with:

 {{{
 $ /opt/ghc/8.4.1/bin/ghc Bug.hs
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )

 Bug.hs:15:1: error:
     • Could not deduce (Reduce fsk0 zq)
       from the context: (z ~ LiftOf zq, Reduce fsk zq)
         bound by the inferred type for ‘bench_mulPublic’:
                    forall z zp zq fsk.
                    (z ~ LiftOf zq, Reduce fsk zq) =>
                    Cyc zp -> Cyc z -> IO (zp, zq)
         at Bug.hs:(15,1)-(17,14)
       The type variable ‘fsk0’ is ambiguous
     • In the ambiguity check for the inferred type for ‘bench_mulPublic’
       To defer the ambiguity check to use sites, enable
 AllowAmbiguousTypes
       When checking the inferred type
         bench_mulPublic :: forall z zp zq fsk.
                            (z ~ LiftOf zq, Reduce fsk zq) =>
                            Cyc zp -> Cyc z -> IO (zp, zq)
    |
 15 | bench_mulPublic pt sk = do
    | ^^^^^^^^^^^^^^^^^^^^^^^^^^...
 }}}

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


More information about the ghc-tickets mailing list