[GHC] #10651: Type checking issue with existential quantification, rank-n types and constraint kinds

GHC ghc-devs at haskell.org
Fri Sep 15 13:25:13 UTC 2017


#10651: Type checking issue with existential quantification, rank-n types and
constraint kinds
-------------------------------------+-------------------------------------
        Reporter:  Roboguy           |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler (Type    |              Version:  7.10.1
  checker)                           |
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  GHC rejects       |  Unknown/Multiple
  valid program                      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by RyanGlScott):

 Indeed, that seems to the fix. Note that you can get rid of the explicit
 `Proxy b` argument if you turn on `AllowAmbiguousTypes`:

 {{{#!hs
 {-# LANGUAGE AllowAmbiguousTypes #-}
 {-# LANGUAGE ConstraintKinds #-}
 {-# LANGUAGE ExistentialQuantification #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE ScopedTypeVariables #-}

 data ConstrList c = forall a. c a => a :> ConstrList c
                   | CNil
 infixr :>

 constrMap :: (forall a. c a => a -> b) -> ConstrList c -> [b]
 constrMap f (x :> xs) = f x : constrMap f xs
 constrMap f CNil      = []

 constrMapM :: Monad m => (forall a. c a => a -> m b) -> ConstrList c -> m
 [b]
 constrMapM f = sequence . constrMap f

 constrMapM_ :: forall m c b. Monad m =>
     (forall a. (c a) => a -> m b) -> ConstrList c -> m ()
 constrMapM_ f x =
   constrMapM f x >>= (\(_ :: [b]) -> return ())
 }}}

 This has the potential downside that you might need to explicitly provide
 some extra type information to `constrMapM_` in places that you invoke it,
 perhaps in the form of `TypeApplications`:

 {{{#!hs
 constrMapM_ @IO @Show @() print
 }}}

 But that's the price you pay for dancing with ambiguity.

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


More information about the ghc-tickets mailing list