[Haskell-cafe] flipped IO sequence

2008-10-01 Thread Cetin Sert
warn :: String → IO Int
warn = return 1  putStrLn-- causes an error
  -- = \msg → return 1  putStrLn msg -- works just fine
  -- = \msg → putStrLn msg  return 1 -- works just fine

() :: Monad m ⇒ m b → m a → m b
b  a = a = \_ → b

Why do I get this compile-time error?? How can one define  ?

[EMAIL PROTECTED]:~/lab/test/qths/p ghc -fglasgow-exts -O2 -o d64x --make
demo2.hs system.hs
[1 of 2] Compiling Netman.System( system.hs, system.o )

system.hs:23:14:
No instance for (Num (IO Int))
  arising from the literal `1' at system.hs:23:14
Possible fix: add an instance declaration for (Num (IO Int))
In the first argument of `return', namely `1'
In the first argument of `()', namely `return 1'
In the expression: return 1  putStrLn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] flipped IO sequence

2008-10-01 Thread Dougal Stanton
2008/10/1 Cetin Sert [EMAIL PROTECTED]:
 warn :: String → IO Int
 warn = return 1  putStrLn-- causes an error
   -- = \msg → return 1  putStrLn msg -- works just fine
   -- = \msg → putStrLn msg  return 1 -- works just fine

 () :: Monad m ⇒ m b → m a → m b
 b  a = a = \_ → b

 Why do I get this compile-time error?? How can one define  ?

 [EMAIL PROTECTED]:~/lab/test/qths/p ghc -fglasgow-exts -O2 -o d64x --make
 demo2.hs system.hs
 [1 of 2] Compiling Netman.System( system.hs, system.o )

 system.hs:23:14:
 No instance for (Num (IO Int))
   arising from the literal `1' at system.hs:23:14
 Possible fix: add an instance declaration for (Num (IO Int))
 In the first argument of `return', namely `1'
 In the first argument of `()', namely `return 1'
 In the expression: return 1  putStrLn


This works for me (type signature added so GHCi doesn't choke)

Prelude let () = flip () :: IO b - IO a - IO b

And thus:

Prelude return 1  putStrLn yo
yo
1
Prelude

You might be having problems with the point-free code:

Prelude let warn' = return 1  putStrLn

interactive:1:24:
Couldn't match expected type `IO a'
   against inferred type `String - IO ()'
In the second argument of `()', namely `putStrLn'
In the expression: return 1  putStrLn
In the definition of `warn'': warn' = return 1  putStrLn

Adding in variable names straightens that out for me:

Prelude let warn s = return 1  putStrLn s
Prelude warn help
help
1
Prelude


Cheers,


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


Re: [Haskell-cafe] flipped IO sequence

2008-10-01 Thread Martin Huschenbett
Hi Cetin,

what you seem to want is

 warn :: String - IO Int
 warn = (return 1 ) . putStrLn

Cetin Sert schrieb:
 warn :: String → IO Int
 warn = return 1  putStrLn-- causes an error
   -- = \msg → return 1  putStrLn msg -- works just fine
   -- = \msg → putStrLn msg  return 1 -- works just fine
 
 () :: Monad m ⇒ m b → m a → m b
 b  a = a = \_ → b
 
 Why do I get this compile-time error?? How can one define  ?
 
 [EMAIL PROTECTED]:~/lab/test/qths/p ghc -fglasgow-exts -O2 -o d64x 
 --make demo2.hs system.hs
 [1 of 2] Compiling Netman.System( system.hs, system.o )
 
 system.hs:23:14:
 No instance for (Num (IO Int))
   arising from the literal `1' at system.hs:23:14
 Possible fix: add an instance declaration for (Num (IO Int))
 In the first argument of `return', namely `1'
 In the first argument of `()', namely `return 1'
 In the expression: return 1  putStrLn
 
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] flipped IO sequence

2008-10-01 Thread Daniel Fischer
Am Mittwoch, 1. Oktober 2008 12:18 schrieb Cetin Sert:
 warn :: String → IO Int
 warn = return 1  putStrLn-- causes an error

try
warn = (return 1 ) . putStrLn


   -- = \msg → return 1  putStrLn msg -- works just fine
   -- = \msg → putStrLn msg  return 1 -- works just fine

 () :: Monad m ⇒ m b → m a → m b
 b  a = a = \_ → b

() = flip ()

 Why do I get this compile-time error?? How can one define  ?

 [EMAIL PROTECTED]:~/lab/test/qths/p ghc -fglasgow-exts -O2 -o d64x --make
 demo2.hs system.hs
 [1 of 2] Compiling Netman.System( system.hs, system.o )

 system.hs:23:14:
 No instance for (Num (IO Int))
   arising from the literal `1' at system.hs:23:14
 Possible fix: add an instance declaration for (Num (IO Int))
 In the first argument of `return', namely `1'
 In the first argument of `()', namely `return 1'
 In the expression: return 1  putStrLn

Okay
warn = (return 1)  putStrLn

putStrLn :: String - IO ()
return 1 :: m b
() :: m b - m a - m b
warn :: String - IO Int

so we must have
(String - IO ()) === m a
(String - IO Int) === m b

So the monad is ((-) String),
a === IO ()
b === IO Int,
hence in
return 1 :: String - IO Int
the 1 must have type IO Int. Now 1 is actually 
fromInteger 1, 
fromInteger :: (Num a) = Integer - a,
so the compiler looks for the
instance Num (IO Int) where ...
which it doesn't find.

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


Re: [Haskell-cafe] flipped IO sequence

2008-10-01 Thread Luke Palmer
2008/10/1 Cetin Sert [EMAIL PROTECTED]:
 warn :: String → IO Int
 warn = return 1  putStrLn-- causes an error
   -- = \msg → return 1  putStrLn msg -- works just fine
   -- = \msg → putStrLn msg  return 1 -- works just fine

 () :: Monad m ⇒ m b → m a → m b
 b  a = a = \_ → b

 Why do I get this compile-time error?? How can one define  ?

While this isn't directly what you're doing, you might be interested
in the Kleisli composition operators in Control.Monad:

  (=) :: (Monad m) = (a - m b) - (b - m c) - (a - m c)
  (=) :: (Mnoad m) = (b - m c) - (a - m b) - (a - m c)

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