#3176: erroneous defaulting? behaviour for existentials
-----------------------------+----------------------------------------------
Reporter:  claus             |          Owner:                  
    Type:  bug               |         Status:  new             
Priority:  normal            |      Component:  Compiler        
 Version:  6.11              |       Severity:  normal          
Keywords:                    |       Testcase:                  
      Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
-----------------------------+----------------------------------------------
 consider
 {{{
 {-# LANGUAGE NoExtendedDefaultRules #-}
 {-# OPTIONS_GHC -fwarn-type-defaults #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE ExistentialQuantification #-}

 data EShow = forall a. Show a => EShow a

 smallPrint t = concatMap (\f-> case f t of EShow a -> show a) [EShow .
 foo, EShow . bar, EShow . baz]

 data ES = forall a. Show a => ES {unES:: a}

 smallPrintES t = concatMap (\f-> show $ unES $ f t) [ES . foo, ES . bar,
 ES . baz]

 data Test = Test { foo :: Int, bar :: Char, baz :: Bool }

 main = print $ smallPrintES $ Test 1 'x' False
 }}}
 for which
 {{{
 $ /cygdrive/c/ghc/ghc-6.11.20090320/bin/ghc -e "main" exists.hs
 "()()()"
 }}}
 while
 {{{
 $ /cygdrive/c/ghc/ghc-6.8.3/bin/ghc -e "main" exists.hs

 exists.hs:12:40:
     Cannot use record selector `unES' as a function due to escaped type
 variables
     Probably fix: use pattern-matching syntax instead
     In the first argument of `($)', namely `unES'
     In the second argument of `($)', namely `unES $ f t'
     In the expression: show $ unES $ f t
 }}}
 The expected results were error message or this
 {{{
 $ /cygdrive/c/ghc/ghc-6.11.20090320/bin/ghc -e "smallPrint $ Test 1 'x'
 False" exists.hs
 "1'x'False"
 }}}

 There seem to be two issues:

 - shouldn't ghc head report the use of `unES` as an error?

 - how does ghc head arrive at that result, with these flags, without any
 warnings?

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3176>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to