#5380: Too general type with Arrows extension
-------------------------------+--------------------------------------------
    Reporter:  sebf            |       Owner:                             
        Type:  bug             |      Status:  new                        
    Priority:  normal          |   Component:  Compiler                   
     Version:  7.0.3           |    Keywords:                             
    Testcase:                  |   Blockedby:                             
          Os:  Linux           |    Blocking:                             
Architecture:  x86_64 (amd64)  |     Failure:  GHC accepts invalid program
-------------------------------+--------------------------------------------
 This is a reduced version of a function posted on
 [http://www.haskell.org/pipermail/haskell-cafe/2011-August/094434.html
 Haskell Cafe]:

 {{{
 {-# LANGUAGE Arrows #-}

 testB :: not_bool -> (() -> ()) -> () -> not_unit
 testB b f = proc () -> if b then f -< () else f -< ()
 }}}

 There are two problems with the type of this function

   * the first argument can be anything but should be {{{Bool}}} and
   * the result type can be anything but should be {{{()}}}.

 Yet the function is accepted by GHC.

 This function can be used to define a value of arbitrary type:

 {{{
 anythingYouWant :: anything
 anythingYouWant = testB () (const ()) ()
 }}}

 Here are some example calls from my machine:

 {{{
 ghci> anythingYouWant :: Int
 1098066529
 ghci> anythingYouWant :: String
 ""
 ghci> anythingYouWant :: Char
 '\1098066529'
 ghci> anythingYouWant () :: ()
 ()
 ghci> anythingYouWant () :: [()]
 [()Segmentation fault
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5380>
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