[Haskell-cafe] Weird behavior with arrow commands
Ronald Guida
oddron at gmail.com
Fri Jul 23 23:27:00 EDT 2010
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
More information about the Haskell-Cafe
mailing list