Re: [Haskell-cafe] Weird behavior with arrow commands

2010-07-24 Thread Jürgen Doser
El vie, 23-07-2010 a las 23:27 -0400, Ronald Guida escribió:
 I am trying to figure out how to use GHC's arrow commands, and I found
 some extremely weird behavior.

CC'ed to ghc-users, because this may be a ghc bug.

 In GHC's manual, there is a description of arrow commands, which I
 don't really understand.
 http://www.haskell.org/ghc/docs/latest/html/users_guide/arrow-notation.html#id667303
 (Primitive Constructs)
 
 I have two questions:
 1. What are arrow commands supposed to do?
 2. What is this code supposed to do?
 
 -- start of code --
 
 {-# LANGUAGE Arrows #-}
 module Main where
 
 import Control.Arrow
 
 foo :: (b - String) - b, Int), Float), Double) - String) - (b - 
 String)
 foo f g b = f b ++   ++ g (((b, 8), 1.0), 6.0)
 
 bar :: (t - String) - ((Double, Int) - String) - t - String
 bar f g  = proc x - do
   (f - x) `foo` \n m - g - (n)
 
 main = do
   putStrLn $ foo show show 17
   putStrLn $ bar show show 17
   putStrLn $ foo show show 42
   putStrLn $ bar show show 42
 
 -- end of code --
 
 Output from GHCi:
 
 17 (((17,8),1.0),6.0)
 17 (6.730326920298707e-306,0)
 42 (((42,8),1.0),6.0)
 42 (6.730326920298707e-306,0)
 
 Output after compiling with GHC:
 
 17 (((17,8),1.0),6.0)
 17 (5.858736684536801e-270,0)
 42 (((42,8),1.0),6.0)
 42 (5.858736684536801e-270,0)
 
 GHC Version:
 The Glorious Glasgow Haskell Compilation System, version 6.12.3


This seems to be a bug in ghc. First, let's fix bar to give the full
three arguments (Int, Float, Double)  to g:

bar f g  = proc x - do
  (f - x) `foo` (\n m k - g - (n,m,k))

ghc infers the type:

bar :: (t - String) - ((Double, Float, Int) - String) - t - String

and we see that the argument order in the second argument to bar is
reversed. But the arguments are still given to bar in the order (Int,
Float, Double). For example, the 6.0 in foo is interpreted as an Int and
outputs a 0 (the first 32 bits in such a small double are zeros).
When one varies the numbers in foo, one can see the effects in bar. Can
someone from GHC HQ confirm my understanding, or is this just not
supposed to work with multiple arguments?

Jürgen


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Weird behavior with arrow commands

2010-07-24 Thread Ross Paterson
On Sat, Jul 24, 2010 at 01:10:56PM +0200, Jürgen Doser wrote:
 This seems to be a bug in ghc. First, let's fix bar to give the full
 three arguments (Int, Float, Double)  to g:
 
 bar f g  = proc x - do
   (f - x) `foo` (\n m k - g - (n,m,k))
 
 ghc infers the type:
 
 bar :: (t - String) - ((Double, Float, Int) - String) - t - String
 
 and we see that the argument order in the second argument to bar is
 reversed. But the arguments are still given to bar in the order (Int,
 Float, Double). For example, the 6.0 in foo is interpreted as an Int and
 outputs a 0 (the first 32 bits in such a small double are zeros).
 When one varies the numbers in foo, one can see the effects in bar. Can
 someone from GHC HQ confirm my understanding, or is this just not
 supposed to work with multiple arguments?

You're right: it's getting the argument order wrong, so -dcore-lint
fails on this example and all bets are off.  Definitely a bug.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Weird behavior with arrow commands

2010-07-23 Thread Ronald Guida
I am trying to figure out how to use GHC's arrow commands, and I found
some extremely weird behavior.

In GHC's manual, there is a description of arrow commands, which I
don't really understand.
http://www.haskell.org/ghc/docs/latest/html/users_guide/arrow-notation.html#id667303
(Primitive Constructs)

I have two questions:
1. What are arrow commands supposed to do?
2. What is this code supposed to do?

-- start of code --

{-# LANGUAGE Arrows #-}
module Main where

import Control.Arrow

foo :: (b - String) - b, Int), Float), Double) - String) - (b - String)
foo f g b = f b ++   ++ g (((b, 8), 1.0), 6.0)

bar :: (t - String) - ((Double, Int) - String) - t - String
bar f g  = proc x - do
  (f - x) `foo` \n m - g - (n)

main = do
  putStrLn $ foo show show 17
  putStrLn $ bar show show 17
  putStrLn $ foo show show 42
  putStrLn $ bar show show 42

-- end of code --

Output from GHCi:

17 (((17,8),1.0),6.0)
17 (6.730326920298707e-306,0)
42 (((42,8),1.0),6.0)
42 (6.730326920298707e-306,0)

Output after compiling with GHC:

17 (((17,8),1.0),6.0)
17 (5.858736684536801e-270,0)
42 (((42,8),1.0),6.0)
42 (5.858736684536801e-270,0)

GHC Version:
The Glorious Glasgow Haskell Compilation System, version 6.12.3

Thank you
-- Ron
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe