Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-23 Thread Ryan Ingram
Haha, not exactly.

You can replace

sj - get
let (a, sk) = runState something sj
put sk

with

a - something

Also, you don't need do notation for single statements; do return x is
just return x


On Wed, Dec 22, 2010 at 7:21 PM, michael rice nowg...@yahoo.com wrote:

 Thanks for the tip, Ozgur. It worked for me. Is this what you had in mind,
 Ryan?

 Michael

 ==

 import Control.Monad.State.Lazy

 import Control.Monad
 import System.Random

 type GeneratorState = State StdGen
 data Craps a = Roll a | Win a | Lose a deriving (Show)

 genRandomR :: Random a = (a,a) - GeneratorState a
 genRandomR = state . randomR

 rollDie :: GeneratorState Int
 rollDie = genRandomR (1,6)

 roll2Dice :: GeneratorState Int
 roll2Dice = liftM2 (+) rollDie rollDie

 f :: Craps [Int] - GeneratorState (Craps [Int])
 f (Roll []) = do g0 - get
  let (throw1,g1) = runState roll2Dice g0
  put g1
  case throw1 of
 2 - return (Lose [throw1])
 3 - return (Lose [throw1])
 7 - return (Win [throw1])
 11 - return (Win [throw1])
 _ - do g1 - get
 let (throw2,g2) = runState roll2Dice g1
 put g2
 if throw2 == throw1
   then do return (Win [throw1,throw2])
   else
 if throw2 == 7
   then do return (Lose [throw1,throw2])
   else do f (Roll [throw1,throw2])
 f (Roll z@(throw1:throws)) = do g0 - get
 let (throw,g1) = runState roll2Dice g0
 put g1
 if throw == throw1
   then do return (Win (z ++ [throw]))
   else
 if throw == 7
   then do return (Lose (z ++ [throw]))
   else do f (Roll (z ++ [throw]))



 --- On *Wed, 12/22/10, Ozgur Akgun ozgurak...@gmail.com* wrote:


 From: Ozgur Akgun ozgurak...@gmail.com

 Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
 To: Ryan Ingram ryani.s...@gmail.com
 Cc: haskell-cafe@haskell.org, Daniel Fischer 
 daniel.is.fisc...@googlemail.com
 Date: Wednesday, December 22, 2010, 7:37 PM


 see also:
 http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-State-Lazy.html#v:state

 On 22 December 2010 20:02, Ryan Ingram 
 ryani.s...@gmail.comhttp://mc/compose?to=ryani.s...@gmail.com
  wrote:

 Interesting.  In that case,

 state f = StateT $ \s - Identity (f s)

 allows state to replace State in that code.


 Ozgur

 -Inline Attachment Follows-


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org http://mc/compose?to=haskell-c...@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] Why is Haskell flagging this?

2010-12-22 Thread Ryan Ingram
Huh, that's weird, I just copy and pasted this into a new file and it worked
for me.

I did prepend the line

module RandTest where

  -- ryan

On Tue, Dec 21, 2010 at 6:43 PM, michael rice nowg...@yahoo.com wrote:

 I changed your die function to rollDie in function roll2Dice (I assume
 that's what you meant) but get the errors listed below.

 Michael

 

 import Control.Monad.State
 import Control.Monad

 import System.Random

 type GeneratorState = State StdGen

 genRandom :: Random a = GeneratorState a
 genRandom = State random

 -- similar
 genRandomR :: Random a = (a,a) - GeneratorState a
 genRandomR = State . randomR

 rollDie :: GeneratorState Int
 rollDie = genRandomR (1,6)

 roll2Dice :: GeneratorState Int
 roll2Dice = liftM2 (+) rollDie rollDie

 ===

 Prelude :l craps7
 [1 of 1] Compiling Main ( craps7.hs, interpreted )

 craps7.hs:7:12: Not in scope: data constructor `State'

 craps7.hs:11:13: Not in scope: data constructor `State'

 Failed, modules loaded: none.
 Prelude


 --- On *Tue, 12/21/10, Ryan Ingram ryani.s...@gmail.com* wrote:


 From: Ryan Ingram ryani.s...@gmail.com

 Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
 To: michael rice nowg...@yahoo.com
 Cc: David Leimbach leim...@gmail.com, Daniel Fischer 
 daniel.is.fisc...@googlemail.com, haskell-cafe@haskell.org
 Date: Tuesday, December 21, 2010, 7:00 PM

 First, let's make some useful operations in your GeneratorState monad:

 -- State :: (s - (a,s)) - State s a
 -- random :: Random a = StdGen - (a, StdGen)
 genRandom :: Random a = GeneratorState a
 genRandom = State random

 -- similar
 genRandomR :: Random a = (a,a) - GeneratorState a
 genRandomR = State . randomR

 rollDie :: GeneratorState Int
 rollDie = genRandomR (1,6)

 roll2Dice :: GeneratorState Int
 roll2Dice = liftM2 (+) die die

 These can be used to simplify a lot of the code here.

   -- ryan


 On Fri, Dec 17, 2010 at 5:55 PM, michael rice 
 nowg...@yahoo.comhttp://mc/compose?to=nowg...@yahoo.com
  wrote:

 Paul Graham refers to all those features as orthogonality (On Lisp, pg.
 63) and you're right, Haskell has it in spades, but it takes time to
 understand all of it and even more time to use it effectively. One almost
 needs a checklist.

 But I think I'm catching on. I programmed this craps simulation last week.
 It's a problem from Problems For Computer Solution, Gruenberger  Jaffray,
 1965, The RAND Corp.

 import Control.Monad.State
 import System.Random

 type GeneratorState = State StdGen
 data Craps a = Roll a | Win a | Lose a deriving (Show)

 f :: Craps [Int] - GeneratorState (Craps [Int])
 f (Roll []) = do g0 - get
  let (d1,g1) = randomR (1,6) g0
  (d2,g2) = randomR (1,6) g1
  t1 = d1+d2
  put g2
  case t1 of
 2 - return (Lose [t1])
 3 - return (Lose [t1])
 7 - return (Win [t1])
 11 - return (Win [t1])
 _ - do g2 - get
 let (d3,g3) = randomR (1,6) g2
 (d4,g4) = randomR (1,6) g3
 t2 = d3+d4
 put g4
 if t2 == t1
   then do
 return (Win [t1,t2])
   else
 if t2 == 7
   then do
 return (Lose [t1,t2])
   else
 f (Roll [t2,t1])
 f (Roll l) = do g0 - get
 let (d1,g1) = randomR (1,6) g0
 (d2,g2) = randomR (1,6) g1
 t = d1+d2
 if t == (last l)
   then do
 put g2
 return (Win (reverse (t:l)))
   else
 if t == 7
   then do
 put g2
 return (Lose (reverse (t:l)))
   else do
 put g2
 f (Roll (t:l))

 progressive (z@(x:xs),n) (Win _) = let b = x + (last xs)
in (init xs,n+b)
 progressive (z@(x:xs),n) (Lose _) = let b = x + (last xs)
 in (z ++ [b],n-b)

 *Main let r = evalState (sequence $ replicate 6 (f (Roll []))) (mkStdGen
 987)
 *Main r
 [Win [8,12,10,3,8],Win [5,9,10,11,12,11,8,9,5],Win [7],Lose [9,7],Win
 [5,5],Win [5,2,6,4,6,8,5]]
 *Main foldl progressive ([1..10],0) r
 ([6],49)

 Function f generates the roll cycle outcomes which are then folded with the
 progressive betting system.

 In the final answer, the [6] is what's left of the original betting list
 [1..10]. The betting list is used to determine the bet: always bet the
 (first + last

Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-22 Thread Daniel Fischer
On Wednesday 22 December 2010 12:03:01, Ryan Ingram wrote:
 Huh, that's weird, I just copy and pasted this into a new file and it
 worked for me.

As a guess, you have mtl-1.*?
In mtl-2.*, State s is made a type synonym for StateT s Identity, so 
there's no longer a data constructor State.

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


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-22 Thread Ryan Ingram
Interesting.  In that case,

state f = StateT $ \s - Identity (f s)

allows state to replace State in that code.

On Wed, Dec 22, 2010 at 4:56 AM, Daniel Fischer
daniel.is.fisc...@googlemail.com wrote:
 On Wednesday 22 December 2010 12:03:01, Ryan Ingram wrote:
 Huh, that's weird, I just copy and pasted this into a new file and it
 worked for me.

 As a guess, you have mtl-1.*?
 In mtl-2.*, State s is made a type synonym for StateT s Identity, so
 there's no longer a data constructor State.


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


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-22 Thread Ozgur Akgun
see also:
http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-State-Lazy.html#v:state

On 22 December 2010 20:02, Ryan Ingram ryani.s...@gmail.com wrote:

 Interesting.  In that case,

 state f = StateT $ \s - Identity (f s)

 allows state to replace State in that code.


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


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-22 Thread michael rice
Thanks for the tip, Ozgur. It worked for me. Is this what you had in mind, Ryan?

Michael

==

import Control.Monad.State.Lazy
import Control.Monad
import System.Random

type GeneratorState = State StdGen
data Craps a = Roll a | Win a | Lose a deriving (Show)

genRandomR :: Random a = (a,a) - GeneratorState a
genRandomR = state . randomR

rollDie :: GeneratorState Int
rollDie = genRandomR (1,6)

roll2Dice :: GeneratorState Int
roll2Dice = liftM2 (+) rollDie rollDie

f :: Craps [Int] - GeneratorState (Craps [Int])
f (Roll []) = do g0 - get
 let (throw1,g1) = runState roll2Dice g0
 put g1
 case throw1 of
    2 - return (Lose [throw1])
    3 - return (Lose [throw1])
    7 - return (Win [throw1])
    11 - return (Win [throw1])
    _ - do g1 - get
    let (throw2,g2) = runState roll2Dice g1
    put g2
    if throw2 == throw1
  then do return (Win [throw1,throw2])
  else
    if throw2 == 7
  then do return (Lose [throw1,throw2])
  else do f (Roll [throw1,throw2])
f (Roll z@(throw1:throws)) = do g0 - get
    let (throw,g1) = runState roll2Dice g0
    put g1
    if throw == throw1
  then do return (Win (z ++ [throw]))
  else
    if throw == 7
  then do return (Lose (z ++ [throw]))
  else do f (Roll (z ++ [throw]))



--- On Wed, 12/22/10, Ozgur Akgun ozgurak...@gmail.com wrote:

From: Ozgur Akgun ozgurak...@gmail.com
Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
To: Ryan Ingram ryani.s...@gmail.com
Cc: haskell-cafe@haskell.org, Daniel Fischer 
daniel.is.fisc...@googlemail.com
Date: Wednesday, December 22, 2010, 7:37 PM

see 
also: http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-State-Lazy.html#v:state


On 22 December 2010 20:02, Ryan Ingram ryani.s...@gmail.com wrote:

Interesting.  In that case,



state f = StateT $ \s - Identity (f s)



allows state to replace State in that code.
Ozgur

-Inline Attachment Follows-

___
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] Why is Haskell flagging this?

2010-12-21 Thread Ryan Ingram
First, let's make some useful operations in your GeneratorState monad:

-- State :: (s - (a,s)) - State s a
-- random :: Random a = StdGen - (a, StdGen)
genRandom :: Random a = GeneratorState a
genRandom = State random

-- similar
genRandomR :: Random a = (a,a) - GeneratorState a
genRandomR = State . randomR

rollDie :: GeneratorState Int
rollDie = genRandomR (1,6)

roll2Dice :: GeneratorState Int
roll2Dice = liftM2 (+) die die

These can be used to simplify a lot of the code here.

  -- ryan


On Fri, Dec 17, 2010 at 5:55 PM, michael rice nowg...@yahoo.com wrote:

 Paul Graham refers to all those features as orthogonality (On Lisp, pg.
 63) and you're right, Haskell has it in spades, but it takes time to
 understand all of it and even more time to use it effectively. One almost
 needs a checklist.

 But I think I'm catching on. I programmed this craps simulation last week.
 It's a problem from Problems For Computer Solution, Gruenberger  Jaffray,
 1965, The RAND Corp.

 import Control.Monad.State
 import System.Random

 type GeneratorState = State StdGen
 data Craps a = Roll a | Win a | Lose a deriving (Show)

 f :: Craps [Int] - GeneratorState (Craps [Int])
 f (Roll []) = do g0 - get
  let (d1,g1) = randomR (1,6) g0
  (d2,g2) = randomR (1,6) g1
  t1 = d1+d2
  put g2
  case t1 of
 2 - return (Lose [t1])
 3 - return (Lose [t1])
 7 - return (Win [t1])
 11 - return (Win [t1])
 _ - do g2 - get
 let (d3,g3) = randomR (1,6) g2
 (d4,g4) = randomR (1,6) g3
 t2 = d3+d4
 put g4
 if t2 == t1
   then do
 return (Win [t1,t2])
   else
 if t2 == 7
   then do
 return (Lose [t1,t2])
   else
 f (Roll [t2,t1])
 f (Roll l) = do g0 - get
 let (d1,g1) = randomR (1,6) g0
 (d2,g2) = randomR (1,6) g1
 t = d1+d2
 if t == (last l)
   then do
 put g2
 return (Win (reverse (t:l)))
   else
 if t == 7
   then do
 put g2
 return (Lose (reverse (t:l)))
   else do
 put g2
 f (Roll (t:l))

 progressive (z@(x:xs),n) (Win _) = let b = x + (last xs)
in (init xs,n+b)
 progressive (z@(x:xs),n) (Lose _) = let b = x + (last xs)
 in (z ++ [b],n-b)

 *Main let r = evalState (sequence $ replicate 6 (f (Roll []))) (mkStdGen
 987)
 *Main r
 [Win [8,12,10,3,8],Win [5,9,10,11,12,11,8,9,5],Win [7],Lose [9,7],Win
 [5,5],Win [5,2,6,4,6,8,5]]
 *Main foldl progressive ([1..10],0) r
 ([6],49)

 Function f generates the roll cycle outcomes which are then folded with the
 progressive betting system.

 In the final answer, the [6] is what's left of the original betting list
 [1..10]. The betting list is used to determine the bet: always bet the
 (first + last) of betting list. If a win, delete the first and last. If a
 loss, add loss to end of betting list. The 49 is winnings, initially 0.

 There's no explanation in the book of what should happen if the betting
 list becomes empty, or a singleton, but that could be fixed by making it
 longer.

 Comments, criticism, and better ways of doing it are welcome.

 Michael


 --- On *Fri, 12/17/10, David Leimbach leim...@gmail.com* wrote:


 From: David Leimbach leim...@gmail.com

 Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
 To: michael rice nowg...@yahoo.com
 Cc: haskell-cafe@haskell.org, Daniel Fischer 
 daniel.is.fisc...@googlemail.com
 Date: Friday, December 17, 2010, 7:45 PM


 No problem.  Haskell is a different animal than even other functional
 languages in my experience, and it takes time to get used to the coolness in
 the type system, the lazy evaluation, the point free style, functional
 composition and all the other interesting techniques you now have at your
 fingertips for writing very expressive code :-).

 Do that for a while then go back to algol based languages, and wonder why
 the heck anyone uses those on purpose :-).  (yeah there's good reasons to
 use them, but it starts to feel confining)

 Dave

 On Fri, Dec 17, 2010 at 4:28 PM, michael rice 
 nowg...@yahoo.comhttp://mc/compose?to=nowg...@yahoo.com
  wrote:

 Hi, all.

 Plenty of answers. Thank you.

 Putting the list in the IO monad was deliberate. Another one I was looking

Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-21 Thread michael rice
Thanks, Ryan.

I rewrote it yesterday. Here's my updated version.

Better?

Michael

==

import Data.Functor (($))
import System.Random

data Craps a = Roll a | Win a | Lose a deriving (Show)

-- Returns an infinite list of die throws
rollDice :: IO [Int]
rollDice =  randomRs (1,6) $ newStdGen

-- fmap g rollDice - an infinite list of double dice throws.

g :: [Int] - [Int]
g (x:y:rest) = (x+y) : (g rest)

h :: Craps [Int] - [Int] - [Craps [Int]]
h (Roll []) (2:ys) = (Lose [2]) : (h (Roll []) ys)
h (Roll []) (3:ys) = (Lose [3]) : (h (Roll []) ys)
h (Roll []) (7:ys) = (Win [7]) : (h (Roll []) ys)
h (Roll []) (11:ys) = (Win [11]) : (h (Roll []) ys)
h (Roll []) (y:ys) = h (Roll [y]) ys 
h (Roll z@(x:xs)) (y:ys) = if y == 7
   then (Lose (z ++ [y])) : (h (Roll []) ys)
   else
 if x == y
   then (Win (z ++ [y])) : (h (Roll []) ys)
   else h (Roll (z ++ [y])) ys

progressive ((x:xs),won) (Win _) = let bet = x + (last xs)
   in (init xs,won+bet) 
progressive (z@(x:xs),won) (Lose _) = let bet = x + (last xs)
  in (z ++ [bet],won-bet) 
martingale (won,lost) (Win _) = let bet = max 1 (2*lost)
    in (won+bet,0)
martingale (won,lost) (Lose _) = let bet = max 1 (2*lost)
 in (won,lost+bet)

-- Play
 -- n : throw cycles
 -- f : betting system
 -- x : starting condition
playCraps n f x = let r = fmap ((take n) . (h (Roll [])) . g) rollDice
  in fmap (foldl f x) r

{-
*Main playCraps 5 progressive ([1..10],0)
([5,6,7],37)
*Main playCraps 5 martingale (0,0)
(7,1)
-}


--- On Tue, 12/21/10, Ryan Ingram ryani.s...@gmail.com wrote:

From: Ryan Ingram ryani.s...@gmail.com
Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
To: michael rice nowg...@yahoo.com
Cc: David Leimbach leim...@gmail.com, Daniel Fischer 
daniel.is.fisc...@googlemail.com, haskell-cafe@haskell.org
Date: Tuesday, December 21, 2010, 7:00 PM

First, let's make some useful operations in your GeneratorState monad:

-- State :: (s - (a,s)) - State s a
-- random :: Random a = StdGen - (a, StdGen)
genRandom :: Random a = GeneratorState a

genRandom = State random

-- similar
genRandomR :: Random a = (a,a) - GeneratorState a
genRandomR = State . randomR

rollDie :: GeneratorState Int
rollDie = genRandomR (1,6)

roll2Dice :: GeneratorState Int

roll2Dice = liftM2 (+) die die

These can be used to simplify a lot of the code here.

  -- ryan


On Fri, Dec 17, 2010 at 5:55 PM, michael rice nowg...@yahoo.com wrote:


Paul Graham refers to all those features as orthogonality (On Lisp, pg. 63) 
and you're right, Haskell has it in spades, but it takes time to understand all 
of it and even more time to use it effectively. One almost needs a checklist.


But I think I'm catching on. I programmed this craps simulation last week. It's 
a problem from Problems For Computer Solution, Gruenberger  Jaffray, 1965, 
The RAND Corp.

import Control.Monad.State

import System.Random

type
 GeneratorState = State StdGen
data Craps a = Roll a | Win a | Lose a deriving (Show)


f :: Craps [Int] - GeneratorState (Craps [Int])

f (Roll []) = do g0 - get
 let (d1,g1) = randomR (1,6) g0

 (d2,g2) = randomR (1,6) g1
 t1 = d1+d2

 put g2
 case t1 of

    2 - return (Lose [t1])
    3 - return (Lose [t1])

    7 - return (Win [t1])
    11 - return (Win [t1])

    _ - do g2 - get
    let (d3,g3) = randomR (1,6) g2

    (d4,g4) = randomR (1,6) g3
    t2 = d3+d4

    put g4
    if t2 == t1

  then do
    return (Win [t1,t2])

  else
    if t2 == 7

  then do
    return (Lose [t1,t2])

  else
    f (Roll [t2,t1])

f (Roll l) = do g0 - get
    let (d1,g1) = randomR (1,6) g0

    (d2,g2) = randomR (1,6) g1
    t = d1+d2

    if t == (last l)
  then do

    put g2
    return (Win (reverse (t:l)))

  else
    if t == 7

  then do
    put g2

    return (Lose (reverse (t:l)))
  else do

    put g2
    f (Roll (t:l)) 


progressive (z@(x:xs),n) (Win _) = let b = x + (last
 xs)
   in (init

Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-21 Thread michael rice
I changed your die function to rollDie in function roll2Dice (I assume that's 
what you meant) but get the errors listed below.

Michael



import Control.Monad.State
import Control.Monad
import System.Random

type GeneratorState = State StdGen

genRandom :: Random a = GeneratorState a
genRandom = State random

-- similar
genRandomR :: Random a = (a,a) - GeneratorState a
genRandomR = State . randomR

rollDie :: GeneratorState Int
rollDie = genRandomR (1,6)

roll2Dice :: GeneratorState Int
roll2Dice = liftM2 (+) rollDie rollDie

===

Prelude :l craps7
[1 of 1] Compiling Main ( craps7.hs, interpreted )

craps7.hs:7:12: Not in scope: data constructor `State'

craps7.hs:11:13: Not in scope: data constructor `State'
Failed, modules loaded: none.
Prelude


--- On Tue, 12/21/10, Ryan Ingram ryani.s...@gmail.com wrote:

From: Ryan Ingram ryani.s...@gmail.com
Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
To: michael rice nowg...@yahoo.com
Cc: David Leimbach leim...@gmail.com, Daniel Fischer 
daniel.is.fisc...@googlemail.com, haskell-cafe@haskell.org
Date: Tuesday, December 21, 2010, 7:00 PM

First, let's make some useful operations in your GeneratorState monad:

-- State :: (s - (a,s)) - State s a
-- random :: Random a = StdGen - (a, StdGen)
genRandom :: Random a = GeneratorState a

genRandom = State random

-- similar
genRandomR :: Random a = (a,a) - GeneratorState a
genRandomR = State . randomR

rollDie :: GeneratorState Int
rollDie = genRandomR (1,6)

roll2Dice :: GeneratorState Int

roll2Dice = liftM2 (+) die die

These can be used to simplify a lot of the code here.

  -- ryan


On Fri, Dec 17, 2010 at 5:55 PM, michael rice nowg...@yahoo.com wrote:


Paul Graham refers to all those features as orthogonality (On Lisp, pg. 63) 
and you're right, Haskell has it in spades, but it takes time to understand all 
of it and even more time to use it effectively. One almost needs a checklist.


But I think I'm catching on. I programmed this craps simulation last week. It's 
a problem from Problems For Computer Solution, Gruenberger  Jaffray, 1965, 
The RAND Corp.

import Control.Monad.State

import System.Random

type
 GeneratorState = State StdGen
data Craps a = Roll a | Win a | Lose a deriving (Show)


f :: Craps [Int] - GeneratorState (Craps [Int])

f (Roll []) = do g0 - get
 let (d1,g1) = randomR (1,6) g0

 (d2,g2) = randomR (1,6) g1
 t1 = d1+d2

 put g2
 case t1 of

    2 - return (Lose [t1])
    3 - return (Lose [t1])

    7 - return (Win [t1])
    11 - return (Win [t1])

    _ - do g2 - get
    let (d3,g3) = randomR (1,6) g2

    (d4,g4) = randomR (1,6) g3
    t2 = d3+d4

    put g4
    if t2 == t1

  then do
    return (Win [t1,t2])

  else
    if t2 == 7

  then do
    return (Lose [t1,t2])

  else
    f (Roll [t2,t1])

f (Roll l) = do g0 - get
    let (d1,g1) = randomR (1,6) g0

    (d2,g2) = randomR (1,6) g1
    t = d1+d2

    if t == (last l)
  then do

    put g2
    return (Win (reverse (t:l)))

  else
    if t == 7

  then do
    put g2

    return (Lose (reverse (t:l)))
  else do

    put g2
    f (Roll (t:l)) 


progressive (z@(x:xs),n) (Win _) = let b = x + (last
 xs)
   in (init xs,n+b) 
progressive (z@(x:xs),n) (Lose _) = let b = x + (last xs)
    in (z ++ [b],n-b)

*Main let r = evalState (sequence $ replicate 6 (f (Roll []))) (mkStdGen 987)

*Main r
[Win
 [8,12,10,3,8],Win [5,9,10,11,12,11,8,9,5],Win [7],Lose [9,7],Win [5,5],Win 
[5,2,6,4,6,8,5]]
*Main foldl progressive ([1..10],0) r

([6],49)

Function f generates the roll cycle outcomes which are then folded with the 
progressive betting system.

In the final answer, the [6] is what's left of the original betting list 
[1..10]. The betting list is used to determine the bet: always bet the (first + 
last) of betting list. If a win, delete the first and last. If a loss, add loss 
to end of betting list. The 49 is winnings, initially 0.


There's no explanation in the book of what should happen if the betting list 
becomes empty, or a singleton, but that could be fixed by
 making it longer.

Comments, criticism, and better ways of doing

Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-18 Thread Christopher Wilson
On Fri, Dec 17, 2010 at 11:04 AM, michael rice nowg...@yahoo.com wrote:

 I don't understand this error message. Haskell appears not to understand
 that 1 is a Num.

 Prelude :t 1
 1 :: (Num t) = t
 Prelude :t [1,2,3,4,5]
 [1,2,3,4,5] :: (Num t) = [t]
 Prelude

 Michael

 ===

 f :: [Int] - IO [Int]
 f lst = do return lst

 main = do let lst = f [1,2,3,4,5]
   fmap (+1) lst

 ===

 Prelude :l test
 [1 of 1] Compiling Main ( test.hs, interpreted )

 test.hs:5:17:
 No instance for (Num [Int])
   arising from the literal `1' at test.hs:5:17
 Possible fix: add an instance declaration for (Num [Int])
 In the second argument of `(+)', namely `1'
 In the first argument of `fmap', namely `(+ 1)'
 In the expression: fmap (+ 1) lst
 Failed, modules loaded: none.
 Prelude


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


Excuse any inaccuracies, I'm somewhat new at Haskell myself, but what it
looks like is happening is that at the point in main where you've bound
lst, it will have type of IO [Int].  The signature for fmap is:

fmap :: (Functor f) = (a - b) - f a - f b

if you call fmap (+1) the next argument that fmap expects is something
that is in just one functor, for example, this

fmap (+1) [1,2,3,4,5]

works fine, but, something that is IO [Int] won't.  You can compose two
'fmap's to solve this:

:t (fmap.fmap)
(fmap.fmap)
  :: (Functor f, Functor f1) = (a - b) - f (f1 a) - f (f1 b)

which means that 'main' looks like:


main = do let lst = f [1, 2, 3, 4, 5]
  (fmap.fmap) (+1) lst


-- 
Chris Wilson christopher.j.wil...@gmail.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-18 Thread aditya siram
I think it is giving you the error because you the fmap in your code is
operating on the IO monad and not the List monad. In order to get it to
work, you can remove the IO layer with = as below:

f :: [Int] - IO [Int]
f lst = do return lst

main = do let lst = f [1,2,3,4,5]
  lst = return . fmap (+1)

Or you can not wrap the list in IO to begin with, my guess is that you wrote
'f' to make the compiler happy at some point in development:
main = do let lst = [1,2,3,4,5]
  return $ fmap (+1) lst

-deech

On Fri, Dec 17, 2010 at 11:04 AM, michael rice nowg...@yahoo.com wrote:

 I don't understand this error message. Haskell appears not to understand
 that 1 is a Num.

 Prelude :t 1
 1 :: (Num t) = t
 Prelude :t [1,2,3,4,5]
 [1,2,3,4,5] :: (Num t) = [t]
 Prelude

 Michael

 ===

 f :: [Int] - IO [Int]
 f lst = do return lst

 main = do let lst = f [1,2,3,4,5]
   fmap (+1) lst

 ===

 Prelude :l test
 [1 of 1] Compiling Main ( test.hs, interpreted )

 test.hs:5:17:
 No instance for (Num [Int])
   arising from the literal `1' at test.hs:5:17
 Possible fix: add an instance declaration for (Num [Int])
 In the second argument of `(+)', namely `1'
 In the first argument of `fmap', namely `(+ 1)'
 In the expression: fmap (+ 1) lst
 Failed, modules loaded: none.
 Prelude


 ___
 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] Why is Haskell flagging this?

2010-12-18 Thread Antoine Latter
This is a bit tricky.

The type of 'f' is '[Int] - IO [Int]', which means that the type of 'lst'
is 'IO [Int]'.

So fmap (+1) tries to add one to the [Int] underneath the 'IO' type
constructor.

You can either use two 'fmap's, the first to lift up to IO and the second to
lift into the list, or you can use monad notation:

 do
   lst - f [1,2,3,4]
   return $ fmap (+1) lst

Does that make sense?

Take care,
Antoine

On Fri, Dec 17, 2010 at 11:04 AM, michael rice nowg...@yahoo.com wrote:

 I don't understand this error message. Haskell appears not to understand
 that 1 is a Num.

 Prelude :t 1
 1 :: (Num t) = t
 Prelude :t [1,2,3,4,5]
 [1,2,3,4,5] :: (Num t) = [t]
 Prelude

 Michael

 ===

 f :: [Int] - IO [Int]
 f lst = do return lst

 main = do let lst = f [1,2,3,4,5]
   fmap (+1) lst

 ===

 Prelude :l test
 [1 of 1] Compiling Main ( test.hs, interpreted )

 test.hs:5:17:
 No instance for (Num [Int])
   arising from the literal `1' at test.hs:5:17
 Possible fix: add an instance declaration for (Num [Int])
 In the second argument of `(+)', namely `1'
 In the first argument of `fmap', namely `(+ 1)'
 In the expression: fmap (+ 1) lst
 Failed, modules loaded: none.
 Prelude


 ___
 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] Why is Haskell flagging this?

2010-12-18 Thread Mads Lindstrøm
Hi Michael

The type of lst is IO [Int] and therefore fmap (+1) applies (+1) to
the hole lists of integers, and not to each member of the list. That is:

fmap (+1) lst   =
fmap (+1) (return [1,2,3,4,5])  =
return ([1,2,3,4,5] + 1)

and you cannot say [1,2,3,4,5] + 1.

Does that make sense?

Maybe you want to say:

main = do let lst = [1,2,3,4,5]
  print $ map (+1) lst

/Mads

On Fri, 2010-12-17 at 09:04 -0800, michael rice wrote:
 I don't understand this error message. Haskell appears not to
 understand that 1 is a Num.
 
 Prelude :t 1
 1 :: (Num t) = t
 Prelude :t [1,2,3,4,5]
 [1,2,3,4,5] :: (Num t) = [t]
 Prelude 
 
 Michael
 
 ===
 
 f :: [Int] - IO [Int]
 f lst = do return lst
 
 main = do let lst = f [1,2,3,4,5]
   fmap (+1) lst
 
 ===
 
 Prelude :l test
 [1 of 1] Compiling Main ( test.hs, interpreted )
 
 test.hs:5:17:
 No instance for (Num [Int])
   arising from the literal `1' at test.hs:5:17
 Possible fix: add an instance declaration for (Num [Int])
 In the second argument of `(+)', namely `1'
 In the first argument of `fmap', namely `(+ 1)'
 In the expression: fmap (+ 1) lst
 Failed, modules loaded: none.
 Prelude 
 
 
 ___
 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] Why is Haskell flagging this?

2010-12-18 Thread aditya siram
To make that a little clearer, here is code that uses two calls to fmap to
drill through two monadic layers:
f :: [Int] - IO [Int]
f lst = do return lst

main = do let lst = f [1,2,3,4,5]
  fmap (fmap (+1)) lst

So the order of operations is :
1. The first fmap converts an IO [Int] to [Int] and hands it off to the
second fmap
2. The second fmap applies the (+1) function to every element of the list.
3. The second fmap re-wraps the elements back into a [Int]
4. The first fmap re-wraps and returns the transformed [Int] into an IO
[Int].

-deech


On Fri, Dec 17, 2010 at 3:27 PM, aditya siram aditya.si...@gmail.comwrote:

 I think it is giving you the error because you the fmap in your code is
 operating on the IO monad and not the List monad. In order to get it to
 work, you can remove the IO layer with = as below:


 f :: [Int] - IO [Int]
 f lst = do return lst

 main = do let lst = f [1,2,3,4,5]
   lst = return . fmap (+1)

 Or you can not wrap the list in IO to begin with, my guess is that you
 wrote 'f' to make the compiler happy at some point in development:
 main = do let lst = [1,2,3,4,5]
   return $ fmap (+1) lst

 -deech

 On Fri, Dec 17, 2010 at 11:04 AM, michael rice nowg...@yahoo.com wrote:

 I don't understand this error message. Haskell appears not to understand
 that 1 is a Num.

 Prelude :t 1
 1 :: (Num t) = t
 Prelude :t [1,2,3,4,5]
 [1,2,3,4,5] :: (Num t) = [t]
 Prelude

 Michael

 ===

 f :: [Int] - IO [Int]
 f lst = do return lst

 main = do let lst = f [1,2,3,4,5]
   fmap (+1) lst

 ===

 Prelude :l test
 [1 of 1] Compiling Main ( test.hs, interpreted )

 test.hs:5:17:
 No instance for (Num [Int])
   arising from the literal `1' at test.hs:5:17
 Possible fix: add an instance declaration for (Num [Int])
 In the second argument of `(+)', namely `1'
 In the first argument of `fmap', namely `(+ 1)'
 In the expression: fmap (+ 1) lst
 Failed, modules loaded: none.
 Prelude


 ___
 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] Why is Haskell flagging this?

2010-12-18 Thread David Leimbach
On Fri, Dec 17, 2010 at 9:04 AM, michael rice nowg...@yahoo.com wrote:

 I don't understand this error message. Haskell appears not to understand
 that 1 is a Num.

 Prelude :t 1
 1 :: (Num t) = t
 Prelude :t [1,2,3,4,5]
 [1,2,3,4,5] :: (Num t) = [t]
 Prelude

 Michael

 ===

 f :: [Int] - IO [Int]
 f lst = do return lst

 main = do let lst = f [1,2,3,4,5]
   fmap (+1) lst


f takes [Int] and returns IO [Int]

fmap is

fmap :: (Functor f) = (a - b) - f a - f b

That is it takes a function of a's to b's, a functor of a, and returns you a
functor of b.

So when you fmap (+1) to an IO [Int], it's trying to add 1 to a [Int], and
[Int] is not an instance of Num, so the + does not work.

Luckily you can use function composition here

(fmap . fmap) (+1) $ f [1..10]
[2,3,4,5,6,7,8,9,10,11]

fmap . fmap is the type I think you wanted:

Prelude :t fmap . fmap
fmap . fmap
  :: (Functor f, Functor f1) = (a - b) - f (f1 a) - f (f1 b)


With IO as the f Functor, and [] as the f1 Functor.




 ===

 Prelude :l test
 [1 of 1] Compiling Main ( test.hs, interpreted )

 test.hs:5:17:
 No instance for (Num [Int])
   arising from the literal `1' at test.hs:5:17
 Possible fix: add an instance declaration for (Num [Int])
 In the second argument of `(+)', namely `1'
 In the first argument of `fmap', namely `(+ 1)'
 In the expression: fmap (+ 1) lst
 Failed, modules loaded: none.
 Prelude


 ___
 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] Why is Haskell flagging this?

2010-12-18 Thread Daniel Peebles
Write out more types and it'll get more clear.

f is [Int] - IO [Int]

lst is f applied to Num a = [a], so it is of type IO [Int]

fmap is applied to lst, which means it's stepping inside the IO. That
means it's applying +1 to [1,2,3,4,5], which doesn't make much sense unless
you have a Num instance for [Int]. That's what the error was saying.

What you probably want is fmap (fmap (+1)) lst.

Not sure why you're doing this stuff in the first place though, since the
return into IO is only restricting what you can do with it. Also, the do in
both cases is unnecessary (in the second case you can replace the let with a
let..in)

Hope this helps,
Dan

On Fri, Dec 17, 2010 at 12:04 PM, michael rice nowg...@yahoo.com wrote:

 I don't understand this error message. Haskell appears not to understand
 that 1 is a Num.

 Prelude :t 1
 1 :: (Num t) = t
 Prelude :t [1,2,3,4,5]
 [1,2,3,4,5] :: (Num t) = [t]
 Prelude

 Michael

 ===

 f :: [Int] - IO [Int]
 f lst = do return lst

 main = do let lst = f [1,2,3,4,5]
   fmap (+1) lst

 ===

 Prelude :l test
 [1 of 1] Compiling Main ( test.hs, interpreted )

 test.hs:5:17:
 No instance for (Num [Int])
   arising from the literal `1' at test.hs:5:17
 Possible fix: add an instance declaration for (Num [Int])
 In the second argument of `(+)', namely `1'
 In the first argument of `fmap', namely `(+ 1)'
 In the expression: fmap (+ 1) lst
 Failed, modules loaded: none.
 Prelude


 ___
 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] Why is Haskell flagging this?

2010-12-18 Thread Christopher Done
On 17 December 2010 18:04, michael rice nowg...@yahoo.com wrote:

 ===

 f :: [Int] - IO [Int]
 f lst = do return lst

 main = do let lst = f [1,2,3,4,5]
   fmap (+1) lst


The problem is that you are applying fmap to a type IO a.

fmap (+1) (return [1,2,3])

But to achieve the behaviour you expect, you need another fmap:

fmap (fmap (+1)) (return [1,2,3])
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-18 Thread Thomas Davie

On 17 Dec 2010, at 21:44, Christopher Done wrote:

 On 17 December 2010 18:04, michael rice nowg...@yahoo.com wrote:
 ===
 
 f :: [Int] - IO [Int]
 f lst = do return lst
 
 main = do let lst = f [1,2,3,4,5]
   fmap (+1) lst
  
 The problem is that you are applying fmap to a type IO a.
 
 fmap (+1) (return [1,2,3])
 
 But to achieve the behaviour you expect, you need another fmap:
 
 fmap (fmap (+1)) (return [1,2,3])

Which can be more neatly written with Conal's semantic editor cominators as

(fmap . fmap) (+1) (return [1,2,3])

Of course, I question why the list is put in the IO monad at all here... surely 
this would be much better

return $ fmap (+1) [1,2,3]

Finally, that has the wrong type for main... perhaps you meant to print it out?

main :: IO ()
main = print $ fmap (+1) [1,2,3]

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


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-18 Thread David Leimbach
No problem.  Haskell is a different animal than even other functional
languages in my experience, and it takes time to get used to the coolness in
the type system, the lazy evaluation, the point free style, functional
composition and all the other interesting techniques you now have at your
fingertips for writing very expressive code :-).

Do that for a while then go back to algol based languages, and wonder why
the heck anyone uses those on purpose :-).  (yeah there's good reasons to
use them, but it starts to feel confining)

Dave

On Fri, Dec 17, 2010 at 4:28 PM, michael rice nowg...@yahoo.com wrote:

 Hi, all.

 Plenty of answers. Thank you.

 Putting the list in the IO monad was deliberate. Another one I was looking
 at was

 f :: String - IO String
 f s = do return s

 main = do ios - f hello
   fmap tail ios

 which worked fine

 So, the big error was trying to add  1 + [1,2,3,4,5].

 I considered that I needed an additional fmap and thought I had tried

 fmap (fmap (1+)) iol

 but must have messed it up, because I got an error. I guess I was on the
 right track.

 I like to try various combinations to test my understanding. It's kind of
 embarrassing when I get stumped by something simple like this, but that's
 how one learns.

 Thanks again,

 Michael

 --- On Fri, 12/17/10, Daniel Fischer daniel.is.fisc...@googlemail.com
 wrote:


 From: Daniel Fischer daniel.is.fisc...@googlemail.com
 Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
 To: haskell-cafe@haskell.org
 Cc: michael rice nowg...@yahoo.com
 Date: Friday, December 17, 2010, 4:24 PM


 On Friday 17 December 2010 18:04:20, michael rice wrote:
  I don't understand this error message. Haskell appears not to
 understand
  that 1 is a Num.
 
  Prelude :t 1
  1 :: (Num t) = t
  Prelude :t [1,2,3,4,5]
  [1,2,3,4,5] :: (Num t) = [t]
  Prelude
 
  Michael
 
  ===
 
  f :: [Int] - IO [Int]
  f lst = do return lst
 
  main = do let lst = f [1,2,3,4,5]
fmap (+1) lst

 The fmap is relative to IO, your code is equivalent to

 do let lst = (return [1,2,3,4,5])
fmap (+1) lst

 ~

 fmap (+1) (return [1,2,3,4,5])

 ~

 do lst - return [1,2,3,4,5]
return $ (+1) lst

 but there's no instance Num [Int] in scope

 You probably meant


 do let lst = f [1,2,3,4,5]
fmap (map (+1)) lst


 
  ===
 
  Prelude :l test
  [1 of 1] Compiling Main ( test.hs, interpreted )
 
  test.hs:5:17:
  No instance for (Num [Int])
arising from the literal `1' at test.hs:5:17
  Possible fix: add an instance declaration for (Num [Int])
  In the second argument of `(+)', namely `1'
  In the first argument of `fmap', namely `(+ 1)'
  In the expression: fmap (+ 1) lst
  Failed, modules loaded: none.
  Prelude


 --- On *Fri, 12/17/10, Daniel Fischer 
 daniel.is.fisc...@googlemail.com*wrote:


 From: Daniel Fischer daniel.is.fisc...@googlemail.com
 Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
 To: haskell-cafe@haskell.org
 Cc: michael rice nowg...@yahoo.com
 Date: Friday, December 17, 2010, 4:24 PM

 On Friday 17 December 2010 18:04:20, michael rice wrote:
  I don't understand this error message. Haskell appears not to understand
  that 1 is a Num.
 
  Prelude :t 1
  1 :: (Num t) = t
  Prelude :t [1,2,3,4,5]
  [1,2,3,4,5] :: (Num t) = [t]
  Prelude
 
  Michael
 
  ===
 
  f :: [Int] - IO [Int]
  f lst = do return lst
 
  main = do let lst = f [1,2,3,4,5]
fmap (+1) lst

 The fmap is relative to IO, your code is equivalent to

 do let lst = (return [1,2,3,4,5])
fmap (+1) lst

 ~

 fmap (+1) (return [1,2,3,4,5])

 ~

 do lst - return [1,2,3,4,5]
return $ (+1) lst

 but there's no instance Num [Int] in scope

 You probably meant


 do let lst = f [1,2,3,4,5]
fmap (map (+1)) lst


 
  ===
 
  Prelude :l test
  [1 of 1] Compiling Main ( test.hs, interpreted )
 
  test.hs:5:17:
  No instance for (Num [Int])
arising from the literal `1' at test.hs:5:17
  Possible fix: add an instance declaration for (Num [Int])
  In the second argument of `(+)', namely `1'
  In the first argument of `fmap', namely `(+ 1)'
  In the expression: fmap (+ 1) lst
  Failed, modules loaded: none.
  Prelude



 ___
 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] Why is Haskell flagging this?

2010-12-17 Thread Darrin Chandler
On Fri, Dec 17, 2010 at 09:04:20AM -0800, michael rice wrote:
 I don't understand this error message. Haskell appears not to understand that 
 1 is a Num.
 
 Prelude :t 1
 1 :: (Num t) = t
 Prelude :t [1,2,3,4,5]
 [1,2,3,4,5] :: (Num t) = [t]
 Prelude 
 
 Michael
 
 ===
 
 f :: [Int] - IO [Int]
 f lst = do return lst
 
 main = do let lst = f [1,2,3,4,5]
   fmap (+1) lst

'f' operates on '[Int]', but '(+1)' operates on 'Int'... Does the
following do what you want?

main = do let lst = f [1,2,3,4,5] in
fmap (map (+1)) lst

 
 ===
 
 Prelude :l test
 [1 of 1] Compiling Main ( test.hs, interpreted )
 
 test.hs:5:17:
     No instance for (Num [Int])
   arising from the literal `1' at test.hs:5:17
     Possible fix: add an instance declaration for (Num [Int])
     In the second argument of `(+)', namely `1'
     In the first argument of `fmap', namely `(+ 1)'
     In the expression: fmap (+ 1) lst
 Failed, modules loaded: none.
 Prelude 
 
 
 
   

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


-- 
You've been warned.

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


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-17 Thread Miguel Mitrofanov

On 17 Dec 2010, at 20:04, michael rice wrote:

 I don't understand this error message. Haskell appears not to understand that 
 1 is a Num.

As it clearly states in the error message, it doesn't understand that [Int] is 
a Num - and it's not.

No instance for Num something usually indicates that you're trying to use an 
integer literal - in this case, 1 - as this something.

The problem is that your lst has the type IO [Int] (which is the same as 
IO ([] Int)). fmap has the type (a - b) - f a - f b, so, it tries to 
unify the type of (+1) with [Int] - something - which, probably, isn't 
what you've meant. In fact, I'm pretty sure you wanted lst to have the type 
[Int] (= [] Int), without IO. You can do that using - instead of let:

main =
   do lst - fst [1,2,3,4,5]
  return (fmap (+1) lst)

 
 Prelude :t 1
 1 :: (Num t) = t
 Prelude :t [1,2,3,4,5]
 [1,2,3,4,5] :: (Num t) = [t]
 Prelude 
 
 Michael
 
 ===
 
 f :: [Int] - IO [Int]
 f lst = do return lst
 
 main = do let lst = f [1,2,3,4,5]
   fmap (+1) lst
 
 ===
 
 Prelude :l test
 [1 of 1] Compiling Main ( test.hs, interpreted )
 
 test.hs:5:17:
 No instance for (Num [Int])
   arising from the literal `1' at test.hs:5:17
 Possible fix: add an instance declaration for (Num [Int])
 In the second argument of `(+)', namely `1'
 In the first argument of `fmap', namely `(+ 1)'
 In the expression: fmap (+ 1) lst
 Failed, modules loaded: none.
 Prelude 
 
 ___
 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] Why is Haskell flagging this?

2010-12-17 Thread michael rice
Hi, all.

Plenty of answers. Thank you.

Putting the list in the IO monad was deliberate. Another one I was looking at 
was

f :: String - IO String
f s = do return s

main = do ios - f hello
  fmap tail ios

which worked fine

So, the big error was trying to add  1 + [1,2,3,4,5].

I considered that I needed an additional fmap and thought I had tried

fmap (fmap (1+)) iol

but must have messed it up, because I got an error. I guess I was on the right 
track.

I like to try various combinations to test my understanding. It's kind of 
embarrassing when I get stumped by something simple like this, but that's how 
one learns.

Thanks again,

Michael

--- On Fri, 12/17/10, Daniel Fischer daniel.is.fisc...@googlemail.com wrote:


    From: Daniel Fischer daniel.is.fisc...@googlemail.com
    Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
    To: haskell-cafe@haskell.org
    Cc: michael rice nowg...@yahoo.com
    Date: Friday, December 17, 2010, 4:24 PM

    On Friday 17 December 2010 18:04:20, michael rice wrote:
     I don't understand this error message. Haskell appears not to understand
     that 1 is a Num.
    
     Prelude :t 1
     1 :: (Num t) = t
     Prelude :t [1,2,3,4,5]
     [1,2,3,4,5] :: (Num t) = [t]
     Prelude
    
     Michael
    
     ===
    
     f :: [Int] - IO [Int]
     f lst = do return lst
    
     main = do let lst = f [1,2,3,4,5]
       fmap (+1) lst

    The fmap is relative to IO, your code is equivalent to

    do let lst = (return [1,2,3,4,5])
   fmap (+1) lst

    ~

    fmap (+1) (return [1,2,3,4,5])

    ~

    do lst - return [1,2,3,4,5]
   return $ (+1) lst

    but there's no instance Num [Int] in scope

    You probably meant

    do let lst = f [1,2,3,4,5]
   fmap (map (+1)) lst

    
     ===
    
     Prelude :l test
     [1 of 1] Compiling Main ( test.hs, interpreted )
    
     test.hs:5:17:
     No instance for (Num [Int])
       arising from the literal `1' at test.hs:5:17
     Possible fix: add an instance declaration for (Num [Int])
     In the second argument of `(+)', namely `1'
     In the first argument of `fmap', namely `(+ 1)'
     In the expression: fmap (+ 1) lst
     Failed, modules loaded: none.
     Prelude


--- On Fri, 12/17/10, Daniel Fischer daniel.is.fisc...@googlemail.com wrote:

From: Daniel Fischer daniel.is.fisc...@googlemail.com
Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
To: haskell-cafe@haskell.org
Cc: michael rice nowg...@yahoo.com
Date: Friday, December 17, 2010, 4:24 PM

On Friday 17 December 2010 18:04:20, michael rice wrote:
 I don't understand this error message. Haskell appears not to understand
 that 1 is a Num.

 Prelude :t 1
 1 :: (Num t) = t
 Prelude :t [1,2,3,4,5]
 [1,2,3,4,5] :: (Num t) = [t]
 Prelude

 Michael

 ===

 f :: [Int] - IO [Int]
 f lst = do return lst

 main = do let lst = f [1,2,3,4,5]
   fmap (+1) lst

The fmap is relative to IO, your code is equivalent to

do let lst = (return [1,2,3,4,5])
   fmap (+1) lst

~

fmap (+1) (return [1,2,3,4,5])

~

do lst - return [1,2,3,4,5]
   return $ (+1) lst

but there's no instance Num [Int] in scope

You probably meant

do let lst = f [1,2,3,4,5]
   fmap (map (+1)) lst


 ===

 Prelude :l test
 [1 of 1] Compiling Main ( test.hs, interpreted )

 test.hs:5:17:
     No instance for (Num [Int])
   arising from the literal `1' at test.hs:5:17
     Possible fix: add an instance declaration for (Num [Int])
     In the second argument of `(+)', namely `1'
     In the first argument of `fmap', namely `(+ 1)'
     In the expression: fmap (+ 1) lst
 Failed, modules loaded: none.
 Prelude




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


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-17 Thread michael rice
Paul Graham refers to all those features as orthogonality (On Lisp, pg. 63) 
and you're right, Haskell has it in spades, but it takes time to understand all 
of it and even more time to use it effectively. One almost needs a checklist.

But I think I'm catching on. I programmed this craps simulation last week. It's 
a problem from Problems For Computer Solution, Gruenberger  Jaffray, 1965, 
The RAND Corp.

import Control.Monad.State
import System.Random

type GeneratorState = State StdGen
data Craps a = Roll a | Win a | Lose a deriving (Show)

f :: Craps [Int] - GeneratorState (Craps [Int])
f (Roll []) = do g0 - get
 let (d1,g1) = randomR (1,6) g0
 (d2,g2) = randomR (1,6) g1
 t1 = d1+d2
 put g2
 case t1 of
    2 - return (Lose [t1])
    3 - return (Lose [t1])
    7 - return (Win [t1])
    11 - return (Win [t1])
    _ - do g2 - get
    let (d3,g3) = randomR (1,6) g2
    (d4,g4) = randomR (1,6) g3
    t2 = d3+d4
    put g4
    if t2 == t1
  then do
    return (Win [t1,t2])
  else
    if t2 == 7
  then do
    return (Lose [t1,t2])
  else
    f (Roll [t2,t1])
f (Roll l) = do g0 - get
    let (d1,g1) = randomR (1,6) g0
    (d2,g2) = randomR (1,6) g1
    t = d1+d2
    if t == (last l)
  then do
    put g2
    return (Win (reverse (t:l)))
  else
    if t == 7
  then do
    put g2
    return (Lose (reverse (t:l)))
  else do
    put g2
    f (Roll (t:l)) 

progressive (z@(x:xs),n) (Win _) = let b = x + (last xs)
   in (init xs,n+b) 
progressive (z@(x:xs),n) (Lose _) = let b = x + (last xs)
    in (z ++ [b],n-b)

*Main let r = evalState (sequence $ replicate 6 (f (Roll []))) (mkStdGen 987)
*Main r
[Win [8,12,10,3,8],Win [5,9,10,11,12,11,8,9,5],Win [7],Lose [9,7],Win [5,5],Win 
[5,2,6,4,6,8,5]]
*Main foldl progressive ([1..10],0) r
([6],49)

Function f generates the roll cycle outcomes which are then folded with the 
progressive betting system.

In the final answer, the [6] is what's left of the original betting list 
[1..10]. The betting list is used to determine the bet: always bet the (first + 
last) of betting list. If a win, delete the first and last. If a loss, add loss 
to end of betting list. The 49 is winnings, initially 0.

There's no explanation in the book of what should happen if the betting list 
becomes empty, or a singleton, but that could be fixed by making it longer.

Comments, criticism, and better ways of doing it are welcome.

Michael


--- On Fri, 12/17/10, David Leimbach leim...@gmail.com wrote:

From: David Leimbach leim...@gmail.com
Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org, Daniel Fischer 
daniel.is.fisc...@googlemail.com
Date: Friday, December 17, 2010, 7:45 PM

No problem.  Haskell is a different animal than even other functional languages 
in my experience, and it takes time to get used to the coolness in the type 
system, the lazy evaluation, the point free style, functional composition and 
all the other interesting techniques you now have at your fingertips for 
writing very expressive code :-).

Do that for a while then go back to algol based languages, and wonder why the 
heck anyone uses those on purpose :-).  (yeah there's good reasons to use them, 
but it starts to feel confining)

Dave
On Fri, Dec 17, 2010 at 4:28 PM, michael rice nowg...@yahoo.com wrote:

Hi, all.

Plenty of answers. Thank you.

Putting the list in the IO monad was deliberate. Another one I was looking at 
was


f :: String - IO String
f s = do return s

main = do ios - f hello
  fmap tail ios

which worked fine

So, the big error was trying to add  1 + [1,2,3,4,5].

I considered that I needed an additional fmap and thought I had tried


fmap (fmap (1+)) iol

but must have messed it up, because I got an error. I guess I was on the right 
track.

I like to try various combinations to test my understanding. It's kind of 
embarrassing when I get stumped by something simple like this, but that's how 
one learns.


Thanks again,

Michael

--- On Fri, 12/17/10, Daniel Fischer
 daniel.is.fisc...@googlemail.com wrote:


    From: Daniel Fischer daniel.is.fisc...@googlemail.com

    Subject: Re

Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-17 Thread Daniel Fischer
On Friday 17 December 2010 18:04:20, michael rice wrote:
 I don't understand this error message. Haskell appears not to understand
 that 1 is a Num.

 Prelude :t 1
 1 :: (Num t) = t
 Prelude :t [1,2,3,4,5]
 [1,2,3,4,5] :: (Num t) = [t]
 Prelude

 Michael

 ===

 f :: [Int] - IO [Int]
 f lst = do return lst

 main = do let lst = f [1,2,3,4,5]
   fmap (+1) lst

The fmap is relative to IO, your code is equivalent to

do let lst = (return [1,2,3,4,5])
   fmap (+1) lst

~

fmap (+1) (return [1,2,3,4,5])

~

do lst - return [1,2,3,4,5]
   return $ (+1) lst

but there's no instance Num [Int] in scope

You probably meant

do let lst = f [1,2,3,4,5]
   fmap (map (+1)) lst


 ===

 Prelude :l test
 [1 of 1] Compiling Main ( test.hs, interpreted )

 test.hs:5:17:
     No instance for (Num [Int])
   arising from the literal `1' at test.hs:5:17
     Possible fix: add an instance declaration for (Num [Int])
     In the second argument of `(+)', namely `1'
     In the first argument of `fmap', namely `(+ 1)'
     In the expression: fmap (+ 1) lst
 Failed, modules loaded: none.
 Prelude


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


Re: [Haskell-cafe] Why does Haskell not infer most general type?

2010-04-06 Thread Brandon S. Allbery KF8NH

On Apr 6, 2010, at 15:56 , Job Vranish wrote:
Is haskell supposed to always infer the most general type (barring  
extensions)?



Look up the monomorphism restriction.

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does Haskell not infer most general type?

2010-04-06 Thread John Van Enk
I don't believe that the monomorphism restriction has anything to do with
this. Removing it does not generalize the type.

On Tue, Apr 6, 2010 at 4:46 PM, Brandon S. Allbery KF8NH 
allb...@ece.cmu.edu wrote:

 On Apr 6, 2010, at 15:56 , Job Vranish wrote:

 Is haskell supposed to always infer the most general type (barring
 extensions)?


 Look up the monomorphism restriction.

 --
 brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
 system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
 electrical and computer engineering, carnegie mellon universityKF8NH



 ___
 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] Why does Haskell not infer most general type?

2010-04-06 Thread Edward Z. Yang
Excerpts from Brandon S. Allbery KF8NH's message of Tue Apr 06 16:46:28 -0400 
2010:
 On Apr 6, 2010, at 15:56 , Job Vranish wrote:
  Is haskell supposed to always infer the most general type (barring  
  extensions)?
 Look up the monomorphism restriction.

Hey Brandon,

I tested the code with -XNoMonomorphismRestriction and it still inferred
the specific type, so perhaps this is either a GHC bug or something
different?  wnoise also points out that both functions take arguments,
so the monomorphism restriction doesn't apply.

See: 
http://www.reddit.com/r/haskell/comments/bn9to/type_checker_trivia_what_are_the_types_of_f_and_y/

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


Re: [Haskell-cafe] Why does Haskell not infer most general type?

2010-04-06 Thread Ross Paterson
On Tue, Apr 06, 2010 at 03:56:32PM -0400, Job Vranish wrote:
 f _ = undefined
   where
 _ = y :: Int - Int
 
 y x = undefined
   where
 _ = f x

Because f and y are mutually recursive, their types are inferred together,
so y gets the type Int - Int (as given), which forces f :: Int - a.

If you add the type signature f :: a - b, you break the cycle: that
type is used in inferring the type of y (namely a - b), which is then
used in checking the typeof f.  Ditto if you add y :: a - b instead.
(This is not Haskell 98, but the implementations have done this for
years, and it will be in Haskell 2010.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does Haskell not infer most general type?

2010-04-06 Thread Job Vranish
So in Haskell 98, would the added constraints result in a type error?

- Job

On Tue, Apr 6, 2010 at 5:12 PM, Ross Paterson r...@soi.city.ac.uk wrote:

 On Tue, Apr 06, 2010 at 03:56:32PM -0400, Job Vranish wrote:
  f _ = undefined
where
  _ = y :: Int - Int
 
  y x = undefined
where
  _ = f x

 Because f and y are mutually recursive, their types are inferred together,
 so y gets the type Int - Int (as given), which forces f :: Int - a.

 If you add the type signature f :: a - b, you break the cycle: that
 type is used in inferring the type of y (namely a - b), which is then
 used in checking the typeof f.  Ditto if you add y :: a - b instead.
 (This is not Haskell 98, but the implementations have done this for
 years, and it will be in Haskell 2010.)
 ___
 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] Why does Haskell not infer most general type?

2010-04-06 Thread Thomas Schilling
Yes, it has to do with mutually recursive bindings.  If you add a type
signature, you break the mutual recursion.  Mutually recursive
functions are type-checked together and then generalised.  Similarly,
polymorphic recursion cannot be inferred either, but is possible by
adding a type signature.

HTH

On 6 April 2010 20:56, Job Vranish job.vran...@gmail.com wrote:

 Is haskell supposed to always infer the most general type (barring
 extensions)?

 I found a simple case where this is not true:

 f _ = undefined
   where
     _ = y :: Int - Int

 y x = undefined
   where
     _ = f x

 Haskell infers the types of 'y' and 'f' as:
 f :: Int - a
 y :: Int - Int

 This confused me at first, but after thinking about it a while it seemed to
 make sense. But then my friend John pointed out that you can add type sigs
 for 'f' and 'y':
 f :: a - b
 y :: a - b
 and have it still typecheck!

 This thoroughly confused me.

 Why does haskell not infer the most general type for these functions? Is it
 a limitation of the algorithm? a limitation of the recursive let binding?

 Any insight would be appreciated :)

 - Job


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





-- 
Push the envelope.  Watch it bend.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does Haskell not infer most general type?

2010-04-06 Thread John Meacham
On Tue, Apr 06, 2010 at 03:56:32PM -0400, Job Vranish wrote:
 Why does haskell not infer the most general type for these functions? Is it
 a limitation of the algorithm? a limitation of the recursive let binding?
 
 Any insight would be appreciated :)

This is due to when Haskell does generalizing, first, the definitions
are broken up into strongly connected components based on their
dependencies. Then, in dependency order, the components are type checked
then generalized and the result is added to the environment and made
available to further typechecking. Notably the types are set in stone at
this point and should be the most general they can be.

So what is going on here is that your two function f and y depend on
each other so are part of the same binding group and hence typecheckd
together. this causes y's unknown type to be unified with its use in f,
giving it the more specific Int - Int type, even though it could be
assigned a more general one.

This is what should happen according to the haskell standard, however,
it was pointed out in the typing haskell in haskell paper that this is
more strict than neccessary, we can furuther split up the binding group
based on 'type dependency' as in, if g and h call each other and g has
an explicit signature, then h need not be considered to depend on it as
the explicit type for g can just be added to the envirornment. When
determining binding groups, we can ignore dependencies through explicit
types effecitively. This was proposed as an extension to haskell 98 in
the THIH paper, and is generally considederd a good idea.

What you have here is a more pathological variation on that, while y
doesn't have an explicit signature, it is used with an explicit one in
f, hence one could theoretically subdivide the binding group, typing f
alone, getting its most general type, then typing y, then going back and
verifying y's use in f is valid. It is ceratinly possible to come up
with a specification for an extended type inference algorithm such as
this, but whether it is worth it is another matter.

John


-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does Haskell not infer most general type?

2010-04-06 Thread Ross Paterson
On Tue, Apr 06, 2010 at 05:18:34PM -0400, Job Vranish wrote:
 So in Haskell 98, would the added constraints result in a type error?

Yes, because the types of the mutually recursive identifiers would be
inferred together without using the type signatures, and then would
fail to match the declared types.

But then there aren't any implementations of Haskell 98 to test this on.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does Haskell not infer most general type?

2010-04-06 Thread Job Vranish
Thank you all for your replies. This is all much more clear now :)

- Job

On Tue, Apr 6, 2010 at 7:00 PM, Ross Paterson r...@soi.city.ac.uk wrote:

 On Tue, Apr 06, 2010 at 05:18:34PM -0400, Job Vranish wrote:
  So in Haskell 98, would the added constraints result in a type error?

 Yes, because the types of the mutually recursive identifiers would be
 inferred together without using the type signatures, and then would
 fail to match the declared types.

 But then there aren't any implementations of Haskell 98 to test this on.
 ___
 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] Why can't Haskell be faster?

2007-11-01 Thread Hugh Perkins
On 10/31/07, Paulo J. Matos [EMAIL PROTECTED] wrote:
 Hello all,

 I, along with some friends, have been looking to Haskell lately. I'm
 very happy with Haskell as a language, however, a friend sent me the
 link:
 http://shootout.alioth.debian.org/gp4/


Careful: it's worse than you think.  Many of the solutions to the
shootout test are using imperative Haskell.  Real functional
Haskell performs significantly slower.  (Orders of magnitude)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why can't Haskell be faster?

2007-10-31 Thread manu

From what I've seen of Clean it seems almost like Haskell. It even


distributes a Haskell-Clean translator so the obvious question is,
why is Haskell slower?



It's also something I've wondered about, and I'm curious about the  
answer...


One of the differences between Haskell and Clean is how side-effects  
are allowed

(Uniqueness Types for Clean, and Monadic I/O for Haskell)

GHC also supports a lot of extensions beyong Haskell98.

Does it explain the difference in performances ? I don't know...

Experts please !


Manu


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


Re: [Haskell-cafe] Why can't Haskell be faster?

2007-10-31 Thread Adrian Hey

Paulo J. Matos wrote:

Hello all,

I, along with some friends, have been looking to Haskell lately. I'm
very happy with Haskell as a language, however, a friend sent me the
link:
http://shootout.alioth.debian.org/gp4/

which enables you compare several language implementations. Haskell
seems to lag behind of Clean.

From what I've seen of Clean it seems almost like Haskell. It even

distributes a Haskell-Clean translator so the obvious question is,
why is Haskell slower?
Being similar languages and being GHC a very good compiler, can't it
get at least as fast as Clean?

What am I missing here? (I wrote this mail assuming the results from
the URL are trustworthy).


I don't know for certain that this is still the case (and if so why).
But I do remember that when I was a Clean user a few years ago both
the Clean compiler and the resulting executables were amazingly fast
(certainly by FPL standards).

I've often thought it's a real shame that two different but very
similar languages exist. I think that the Clean compiler would
be one of the best if not *the* best Haskell implementations available,
apart from minor snag that it isn't Haskell at all :-)

As things are at the moment ghc has no serious competition so we don't
really know how fast it should be. Maybe this will change in future.

BTW, the reason I still jumped ship in the end and became a Haskell
user instead had nothing to do with performance. The reason was that if
I was going to invest a lot of time in progs/libs I wanted to have some
confidence I'd made the right choice long term and I had issues with the
Clean approach to concurrency (what the Clean folk call deterministic
concurrency). I didn't (and still don't) see this as viable, but during
a long and heated flame war on the Clean mailing list it became clear
that the Clean team did not agree with my point of view, so things
were not likely to change any time soon :-(

Regards
--
Adrian Hey
















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


Re: [Haskell-cafe] Why can't Haskell be faster?

2007-10-31 Thread Don Stewart
bf3:
 Are these benchmarks still up-to-date? When I started learning FP, I had 
 to choose between Haskell and Clean, so I made a couple of little 
 programs in both. GHC 6.6.1 with -O was faster in most cases, sometimes 
 a lot faster... I don't have the source code anymore, but it was based 
 on the book The Haskell road to math  logic.

Could be in the better Haskell libraries? We only really have the
shootout programs, which are very small.
  
 However, the Clean compiler itself is really fast, which is nice, it 
 reminds me to the feeling I had with Turbo Pascal under DOS :-) I find 
 GHC rather slow in compilation. But that is another topic of course.

I find it comforting that GHC thinks so hard about my code. :)

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


Re: [Haskell-cafe] Why can't Haskell be faster?

2007-10-31 Thread Peter Verswyvelen
Are these benchmarks still up-to-date? When I started learning FP, I had 
to choose between Haskell and Clean, so I made a couple of little 
programs in both. GHC 6.6.1 with -O was faster in most cases, sometimes 
a lot faster... I don't have the source code anymore, but it was based 
on the book The Haskell road to math  logic.


However, the Clean compiler itself is really fast, which is nice, it 
reminds me to the feeling I had with Turbo Pascal under DOS :-) I find 
GHC rather slow in compilation. But that is another topic of course.


Peter

Paulo J. Matos wrote:

Hello all,

I, along with some friends, have been looking to Haskell lately. I'm
very happy with Haskell as a language, however, a friend sent me the
link:
http://shootout.alioth.debian.org/gp4/

which enables you compare several language implementations. Haskell
seems to lag behind of Clean.
From what I've seen of Clean it seems almost like Haskell. It even
distributes a Haskell-Clean translator so the obvious question is,
why is Haskell slower?
Being similar languages and being GHC a very good compiler, can't it
get at least as fast as Clean?

What am I missing here? (I wrote this mail assuming the results from
the URL are trustworthy).

Cheers,

  


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


Re: [Haskell-cafe] Why is Haskell not homoiconic?

2006-10-31 Thread Jerzy Karczmarczuk

Henning Sato von Rosen wrote:


I am curious as to why Haskell not is homoiconic?
I am interested in the reasons behind that design descision.


I ask using this defintion og homiconicity:
Homiconic means that the primary representation of programs is also a
data structure in a primitive type of the language itself --
http://en.wikipedia.org/wiki/Homoiconic
Examples: LISP, Rebol, Natural Languages...


Could you say why do you think Haskell SHOULD belong to this class?

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


Re: [Haskell-cafe] Why Not Haskell?

2006-08-09 Thread Antti-Juhani Kaijanaho

Albert Lai wrote:

Let's have a fun quiz!  Guess the mainstream languages in question:


Spoilers for the quiz




































0. What language would allow

  4[hello world]

   when a normal person would just write

  hello world[4]


This is a classic C misfeature.


1. What language, supporting a kind of both parametric polymorphism
   and subclass polymorphism, allows and actually features such a class
   declaration as

 class EnumT extends EnumT { ... }


I have to guess here. Java.


2. What language allows you to test primality in constant runtime?
   That is, move all the work to compile time, using its polymorphism.


C++, also a classic feature. There are even books that discuss this 
technique, and I believe a SPJ paper referring to it.

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


Re: [Haskell-cafe] Why Not Haskell?

2006-08-09 Thread Robert Dockins

On Aug 8, 2006, at 5:36 PM, Albert Lai wrote:


Brian Hulley [EMAIL PROTECTED] writes:


Also, the bottom line imho is that Haskell is a difficult language to
understand, and this is compounded by the apparent cleverness of
unreadable code like:

 c = (.) . (.)

when a normal person would just write:

 c f g a b = f (g a b)


All mainstream languages are also difficult to understand, with
similarly clever, unreadable code.  Let's have a fun quiz!  Guess the
mainstream languages in question:


[snip]


2. What language allows you to test primality in constant runtime?
   That is, move all the work to compile time, using its polymorphism.


GHC-Haskell (with enough extensions enabled)?  We're most of the way  
there already with type arithmetic.  I bet putting together a nieve  
primality test would be pretty doable.  In fact, I suspect that GHC's  
type-checker is turing-complete with MPTCs, fundeps, and undecidable  
instances.  I've been contemplating the possibility of embedding the  
lambda calculus for some time (anybody done this already?)


Oops.  I see now the qualifier mainstream.  The point still stands,  
however.



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Why Not Haskell?

2006-08-09 Thread Donald Bruce Stewart
robdockins:
 On Aug 8, 2006, at 5:36 PM, Albert Lai wrote:
 
 Brian Hulley [EMAIL PROTECTED] writes:
 
 Also, the bottom line imho is that Haskell is a difficult language to
 understand, and this is compounded by the apparent cleverness of
 unreadable code like:
 
  c = (.) . (.)
 
 when a normal person would just write:
 
  c f g a b = f (g a b)
 
 All mainstream languages are also difficult to understand, with
 similarly clever, unreadable code.  Let's have a fun quiz!  Guess the
 mainstream languages in question:
 
 [snip]
 
 2. What language allows you to test primality in constant runtime?
That is, move all the work to compile time, using its polymorphism.
 
 GHC-Haskell (with enough extensions enabled)?  We're most of the way  
 there already with type arithmetic.  I bet putting together a nieve  
 primality test would be pretty doable.  In fact, I suspect that GHC's  
 type-checker is turing-complete with MPTCs, fundeps, and undecidable  
 instances.  I've been contemplating the possibility of embedding the  
 lambda calculus for some time (anybody done this already?)

http://haskell.org/haskellwiki/Type_arithmetic#A_Really_Advanced_Example_:_Type-Level_Lambda_Calculus

also

http://haskell.org/haskellwiki/Type_arithmetic#An_Advanced_Example_:_Type-Level_Quicksort

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


Re: [Haskell-cafe] Why Not Haskell?

2006-08-08 Thread Albert Lai
Brian Hulley [EMAIL PROTECTED] writes:

 Also, the bottom line imho is that Haskell is a difficult language to
 understand, and this is compounded by the apparent cleverness of
 unreadable code like:
 
  c = (.) . (.)
 
 when a normal person would just write:
 
  c f g a b = f (g a b)

All mainstream languages are also difficult to understand, with
similarly clever, unreadable code.  Let's have a fun quiz!  Guess the
mainstream languages in question:

0. What language would allow

  4[hello world]

   when a normal person would just write

  hello world[4]

   I first saw this in Dr. Dobb's Journal a decade ago; the author
   said that someone actually used it in interviews!

1. What language, supporting a kind of both parametric polymorphism
   and subclass polymorphism, allows and actually features such a class
   declaration as

 class EnumT extends EnumT { ... }

2. What language allows you to test primality in constant runtime?
   That is, move all the work to compile time, using its polymorphism.

*   *   *

I have programmed and watched programming for more than two decades.
I have observed that the rise and fall of popularity is, of course,
driven by many factors: cultural, social, economical, religious,
political, propagandic, ... but superiority is never one of them.
(Library abundance is, I say, less of a cause and more of an effect.
You have some popularity and then you have more contributors;
conversely you lose popularity and then you lose authors.  Yes there
is some feeding back, but the bootstrapping is more significant.  Perl
has a large library, but that's because it has got an impressive
following.  And where did that following come from?  Mostly economic
(there was a demand, a niche) and religious (it's like natural
languages).)

Recall that some decent technology that once attained as much as 49%
market share could still decline and vanish in less than a decade.  I
am referring to Betamax video tapes.  It lost to VHS video tapes, of
lesser picture quality and 51% market share.  What did Betamax miss?
Apparently, nothing.  It seems that the only difference you can put
your finger at - and even this is elusive - is price.  VHS was
slightly cheaper, and apparently that did it.

If you were born after Betamax had vanished, I congratulate you, on
two counts.  First, you skipped the dark age during which there was no
Haskell, no Gofer, not even Scheme; there was Lisp but even then not
all functions were first-class.  Second, don't feel bad about missing
the video war, as you will soon see an even better one, this time
between Blu-Ray and HD-DVD.  Any bet?

I am trying to say this, with much foregoing digression: we could
equip Haskell with the perfect library, the perfect IDEs and tools,
the perfect tutorials and examples, the license that pleases
everyone... every nice thing mentioned in this thread, and it may
still not become popular.  Betamax had everything and 49% market share
(if Haskell had 49% mind share, we would be really thrilled, right?),
and it could still vanish.

How to make Haskell more popular?  How to make anything at all more
popular?  I am inclined to think it's a purely social question.
Nothing short of a rigorous social science can answer it.  All the nice
things mentioned in this thread, we should strive to build for our own
sake of course, but they don't answer the question.

I have long stopped asking that question.  Once again, I say we should
strive to build all the missing things mentioned.  What impact will
they make to the grand scheme of things, we don't know.  If there will
be none, don't be surprised; it's life.  One day we may have a
rigorous social science that can explain it.  Until then, I share with
you a line a Greek friend puts in his .plan file:

  Man plans and God laughs.

*   *   *

Answers to quiz:
0. http://c-faq.com/aryptr/joke.html
1. http://weblogs.java.net/blog/arnold/archive/2005/06/generics_consid_1.html
2. http://homepage.mac.com/sigfpe/Computing/peano.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why Not Haskell?

2006-08-07 Thread Immanuel Litzroth
Brian Hulley [EMAIL PROTECTED] writes:



 I meant even a non-programmer in the sense of  even someone who is
 not a C hacker to show that the threat of people being able to steal
 code from a program is not the only source of problems that GPL could
 impose on a commercial application. No derogatory implication towards
 people who choose not to learn computer programming was intended.


 The GPL itself refers to a cost of distribution, since it recognizes
 such things are not free-in-price.  This is in reference to offering
 a copy of the source code.  The price of a binary copy can be as
 large as desired. Likewise for the cost of support.

 Well I understand the free as in free speech not free beer motto,
 but suppose person A is talented at writing software but prefers a
 peaceful existence and lacks the contacts/refs/desire/energy etc to be
 a consultant or contractor, and has had the bad experience of being
 forced to work extremely long hours with low pay while in an employed
 position, and person B is outgoing, ebullient, and talented at
 marketing and advertising. Now person A spends some years quietly
 writing some code, which uses a GPL library and is therefore GPL'd,
 and sells it, as is his/her right under the GPL to person B. Then
 person B is free, as in free speech to do whatever he/she likes with
 the software, and so in particular could use his/her marketing skills
 to completely undermine person A's one and only hope of earning a
 living, so from person A's point of view the *amortized* effect of the
 GPL is to make his/her software free as in free beer as well.

Then someone discovers a bug in the program of person A. Person B
is being so busy being outgoing, ebullient and effervescent that he
does not easily find the cause of the bug. Moreover the code needs to
be ported to a the new Warthog MacOSX release. Person A being not only
talented but also shrewd now uses the contractual obligations of
person B as leverage to screw him out of most of his previously made
profit for delivering said work. He lived peacefully ever after.

What is this, Economic Analysis by Parable?
Immanuel
-- 
***
I can, I can't.
Tubbs Tattsyrup

--
Immanuel Litzroth
Software Development Engineer
Enfocus Software
Antwerpsesteenweg 41-45
9000 Gent
Belgium
Voice: +32 9 269 23 90
Fax : +32 9 269 16 91
Email: [EMAIL PROTECTED]
web : www.enfocus.be
***
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why Not Haskell? (sidenote on licensing)

2006-08-07 Thread Matthias Fischmann

On Sun, Aug 06, 2006 at 10:46:16AM +0100, Chris Kuklewicz wrote:
 
 [...]
 
 The GPL only gets in the way if you put it there by choosing to derive work 
 from GPL code.  Note that most commercial programs do not allow you the 
 choice of deriving your work from theirs at all.  The GPL adds to your 
 free-as-in-freedom: you can derive work from others' GPL work and you can 

GPL also brings about restrictions to freedom-in-speech that are
rarely mentioned: Say you develop the code for a client to run her
production facilities.  This code contains sensitive information about
the way the facilities work and must not fall into the hands of the
client's competitors.  But if GPL is stuck to any part of the code and
manages to infect the rest, the client can make you sign as many NDAs
as there can be.  The GPL still entitles you to sell it.  I'm sure
there are other scenarios in which the restritions that GPL places on
the developer are equally prohibitive.

GPL/LGPL is interesting, LGPL v3 may turn into something cool or not.
(I heard they have problems sorting out the above scenario, too, or
something more tricky, I forgot.)  But placing restrictions on how the
code may be used has lead to surprising problems.  BSD on the other
hand is a safe bet.


cheers,
matthias


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


Re: [Haskell-cafe] Why Not Haskell? (sidenote on licensing)

2006-08-07 Thread Chris Kuklewicz

There is a false statement that must be corrected, about NDA's.

Matthias Fischmann wrote:

On Sun, Aug 06, 2006 at 10:46:16AM +0100, Chris Kuklewicz wrote:

[...]

The GPL only gets in the way if you put it there by choosing to derive work 
from GPL code.  Note that most commercial programs do not allow you the 
choice of deriving your work from theirs at all.  The GPL adds to your 
free-as-in-freedom: you can derive work from others' GPL work and you can 


GPL also brings about restrictions to freedom-in-speech that are
rarely mentioned: Say you develop the code for a client to run her
production facilities.  This code contains sensitive information about
the way the facilities work and must not fall into the hands of the
client's competitors.  But if GPL is stuck to any part of the code and
manages to infect the rest, the client can make you sign as many NDAs
as there can be. 


The GPL is not a disease that infects.  That is a metaphor made by people who 
hate such licenses.  The GPL does not blow in the window or from someone's 
sneeze and get stuck to code.  To introduce GPL derived code is a choice made 
be the programmer.  You can always choose not to derive from GPL code, and you 
can always change your mind later and rewrite the derived code so you can remove 
it.  Talking about biological metaphors is deliberately misleading.



 ...the client can make you sign as many NDAs
as there can be. 
The GPL still entitles you to sell it.  I'm sure

there are other scenarios in which the restritions that GPL places on
the developer are equally prohibitive.


No.  You are wrong. Google for GPL and NDA gives 
http://www.gnu.org/licenses/gpl-faq.html :



Does the GPL allow me to distribute a modified or beta version under a
nondisclosure agreement?

No. The GPL says that anyone who receives a copy of your version
from you has the right to redistribute copies (modified or not) of
that version. It does not give you permission to distribute the
work on any more restrictive basis.

Does the GPL allow me to develop a modified version under a
nondisclosure agreement?

Yes. For instance, you can accept a contract to develop changes
and agree not to release your changes until the client says
ok. This is permitted because in this case no GPL-covered code is
being distributed under an NDA.

You can also release your changes to the client under the GPL, but
agree not to release them to anyone else unless the client says
ok. In this case, too, no GPL-covered code is being distributed
under an NDA, or under any additional restrictions.

The GPL would give the client the right to redistribute your
version. In this scenario, the client will probably choose not to
exercise that right, but does have the right.


As the developer you can sign an NDA and it will bind you.  But it will not bind 
the client.



GPL/LGPL is interesting, LGPL v3 may turn into something cool or not.
(I heard they have problems sorting out the above scenario, too, or
something more tricky, I forgot.)  But placing restrictions on how the
code may be used has lead to surprising problems.  BSD on the other
hand is a safe bet.


Note that there are many people who will not do work on a BSD project since a 
company can just come along and take it.  People are free to choose GPL or BSD 
for their work and then other people are free to choose whether to derive work 
from them.  But if there was no GPL and the only choice was BSD then much of the 
current GPL'd work would not exist.


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


Re: [Haskell-cafe] Why Not Haskell? (sidenote on licensing)

2006-08-07 Thread Udo Stenzel
Matthias Fischmann wrote:
 But if GPL is stuck to any part of the code and
 manages to infect the rest, the client can make you sign as many NDAs
 as there can be.  The GPL still entitles you to sell it.

Nonsense.  The GPL says, *if* you distribute a binary, *then* you also
have to distribute the complete, machine readable source.  It also
specifically says that if that is impossible (because of an NDA or
whatever), you must not distribute the software at all.  Have you ever
read the damn thing?!


Udo.
-- 
Wo die Macht geistlos ist, ist der Geist machtlos.
-- aus einem Gipfelbuch


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


Re: [Haskell-cafe] Why Not Haskell? (sidenote on licensing)

2006-08-07 Thread Niklas Broberg

Note that there are many people who will not do work on a BSD project since a
company can just come along and take it.  People are free to choose GPL or BSD
for their work and then other people are free to choose whether to derive work
from them.


But this is just the thing, isn't it? The GPL has its purpose, and is
a great license for applications like Apache or RedHat, where you
don't want companies to just come along and take the code. But for
library code, which is what this discussion was all about from the
beginning, why ever would you *not* want anyone, anywhere, to take and
use your code? And in particular so for Haskell, where we are striving
hard to make industry catch on.

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


Re: [Haskell-cafe] Why Not Haskell? (sidenote on licensing)

2006-08-07 Thread Matthias Fischmann

On Mon, Aug 07, 2006 at 12:57:47PM +0100, Chris Kuklewicz wrote:
 To: Matthias Fischmann [EMAIL PROTECTED]
 CC: haskell-cafe@haskell.org
 From: Chris Kuklewicz [EMAIL PROTECTED]
 Date: Mon, 07 Aug 2006 12:57:47 +0100
 Subject: Re: [Haskell-cafe] Why Not Haskell?  (sidenote on licensing)
 
 There is a false statement that must be corrected, about NDA's.

Sorry.  Just learned something, thanks!

 Matthias Fischmann wrote:
 On Sun, Aug 06, 2006 at 10:46:16AM +0100, Chris Kuklewicz wrote:
 [...]
 
 The GPL only gets in the way if you put it there by choosing to derive 
 work from GPL code.  Note that most commercial programs do not allow you 
 the choice of deriving your work from theirs at all.  The GPL adds to 
 your free-as-in-freedom: you can derive work from others' GPL work and 
 you can 
 
 GPL also brings about restrictions to freedom-in-speech that are
 rarely mentioned: Say you develop the code for a client to run her
 production facilities.  This code contains sensitive information about
 the way the facilities work and must not fall into the hands of the
 client's competitors.  But if GPL is stuck to any part of the code and
 manages to infect the rest, the client can make you sign as many NDAs
 as there can be. 
 
 The GPL is not a disease that infects.  That is a metaphor made by people 
 who hate such licenses.  The GPL does not blow in the window or from 
 someone's sneeze and get stuck to code.  To introduce GPL derived code is 
 a choice made be the programmer.  You can always choose not to derive from 
 GPL code, and you can always change your mind later and rewrite the derived 
 code so you can remove it.  Talking about biological metaphors is 
 deliberately misleading.

Sorry, I didn't mean to offend anybody, or be misleading.  I like GPL,
but I also like the disease metaphor (although is not as much being
sneezed at as having sex with somebody :-).

And it's really not as easy to control as you suggest: If you ever
take in a single patch under the GPL, or even implement a new feature
in an obvious way that has been implemented by somebody else under the
GPL, you are in trouble.  AFAIR this happened to SSH.com with the
bigint code in ssh-v1.3, but if you contradict me now I have to take
your word for it.  (So please do! :)

 http://www.gnu.org/licenses/gpl-faq.html :
 
 Does the GPL allow me to distribute a modified or beta version under a
 nondisclosure agreement?
 
 No. The GPL says that anyone who receives a copy of your version
 from you has the right to redistribute copies (modified or not) of
 that version. It does not give you permission to distribute the
 work on any more restrictive basis.

(In my example I was worried about *less* restrictive, but the
subsequent points seem to cover that, too.)

 GPL/LGPL is interesting, LGPL v3 may turn into something cool or not.
 (I heard they have problems sorting out the above scenario, too, or
 something more tricky, I forgot.)  But placing restrictions on how the
 code may be used has lead to surprising problems.  BSD on the other
 hand is a safe bet.
 
 Note that there are many people who will not do work on a BSD project since 
 a company can just come along and take it.  People are free to choose GPL 
 or BSD for their work and then other people are free to choose whether to 
 derive work from them.  But if there was no GPL and the only choice was BSD 
 then much of the current GPL'd work would not exist.

I tend to agree.  Would be fun to have some empirical data to boost
the accuracy of the 'much' part of this.

cheers,
Matthias


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


Re: [Haskell-cafe] Why Not Haskell? (sidenote on licensing)

2006-08-07 Thread Udo Stenzel
Matthias Fischmann wrote:
 And it's really not as easy to control as you suggest: If you ever
 take in a single patch under the GPL,

This kind of thing doesn't happen by accident.  Patches don't magically
creep into your code, you have to apply them deliberately and you should
always know whether you are allowed to do so.  Applying a BSD-licensed
patch and neglecting to mention the author may get you into exactly as
much trouble.


 or even implement a new feature
 in an obvious way that has been implemented by somebody else under the
 GPL, you are in trouble.

Bullshit again, for the GPL applies to code, not to ideas.  Unless you
believe that copyright law does indeed apply to ideas, *and* that a
GPL-developer will come after you for reimplementing (not copying) his
work, you have nothing to fear unless you outright steal code.

May I humbly suggest some reading, like the text of the GPL itself and
then something basic about copyright law?  


 AFAIR this happened to SSH.com with the
 bigint code in ssh-v1.3

SSH included GMP, which was licensed under the GPL.  Nothing happened
there, only the OpenSSH folks disliked the license and reimplemented
GMP.


Udo.
-- 
The imagination of nature is far, far greater than the imagination of man.
-- Richard Feynman


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


Re: [Haskell-cafe] Why Not Haskell? (sidenote on licensing)

2006-08-07 Thread Matthias Fischmann

Udo,

us:
 mf:
  AFAIR this happened to SSH.com with the
  bigint code in ssh-v1.3
 
 SSH included GMP, which was licensed under the GPL.  Nothing happened
 there, only the OpenSSH folks disliked the license and reimplemented
 GMP.

... and had to fight an ugly battle over the question whether the
reimplementation was legitimate reuse of ideas or code theft.

I don't understand why you have to be so insulting.  I was making a
false claim because I didn't know better, but I don't consider that a
good reason to claim everything I am saying is bullshit and start a
bar fight.

Anyway this is not only getting ugly but also way off topic.  I'm out.


cheers,
Matthias


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


Re: [Haskell-cafe] Why Not Haskell?

2006-08-06 Thread Piotr Kalinowski

On 06/08/06, Brian Hulley [EMAIL PROTECTED] wrote:

Afaict a license such as GPL allows anyone, even a non-programmer, to just
re-distribute whatever application you created because one condition of it
is that anyone should be free to share software with anyone else without
having to pay anything extra to the people who wrote it, and I think this is
essentially based on the notion that software should not be regarded as an
ownable or sellable thing.


Actually, to the best of my knowledge, based on what Stallman said in
his life and reading the GPL license - it is not about software not
being sellable. The whole notion of open source is not in fact to
distribute it freely, because you can charge a fee for transfering
your work and the license does not impose any restrictions on that fee
(except the case of supplying the source code to someone who received
the work in binary form.)

Instead, the idea is that customers should be able to see the source
code and modify it according to their specific needs without paying
additional fees. And they should be able to distribute those changes.

Perhaps you encountered this: it's free as in freedom, not free as in free beer.

Regards,
Piotr Kalinowski

--
Intelligence is like a river: the deeper it is, the less noise it makes
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why Not Haskell?

2006-08-06 Thread Chris Kuklewicz

Brian Hulley wrote:

Henning Thielemann wrote:

On Fri, 4 Aug 2006, Brian Hulley wrote:


4) Haskell is open source and licensing restrictions forbid
commercial applications. I haven't seen any such restrictions, but
is this a problem for the standard modules?


The reason you have no seen any such restriction is because there are no such 
restrictions.  And no license on the compiler restricts what kind of application 
you can create with it, such as forbid commercial applications.


Haskell is a standard, not source code.  The Haskell 98 report ( 
http://www.haskell.org/onlinereport/ ) is



Copyright (c) Simon Peyton Jones.
The authors intend this Report to belong to the entire Haskell
community, and so we grant permission to copy and distribute it for
any purpose, provided that it is reproduced in its entirety, including
this Notice. Modified versions of this Report may also be copied and
distributed for any purpose, provided that the modified version is
clearly presented as such, and that it does not claim to be a
definition of the language Haskell 98.


Each third party library chooses its own license.



You can discover the licensing situation by downloading the GHC
source (or source for whatever distro you're using) and looking in
the directories for each package. For example the base package uses
a BSD-style licence and HaXml uses LGPL with the exception to allow
static linking.


The GHC compiler and its libraries are covered by the 3-clause BSD license:
http://haskell.org/ghc/license.html ( http://en.wikipedia.org/wiki/BSD_License 
).  Microsoft could copy the source of GHC into Office (Excel) to run Haskell 
code in spreadsheets and the only restriction is to append the GHC license (for 
its disclaimer) to the Office license.  It does not get more commercial than 
that, and it is permitted.


If you want to write a new spreadsheet in Haskell using GHC and sell it for 
$1000 a copy (without source code), then you can do that without looking at 
GHC's license.  If you want to take GHC and make a new version that supports 
your own improvements, then you can sell this myGHC (without source) for any 
price you chose.


The HaXml library is not part of GHC.  The authors of that particular library 
have given it a modified LGPL license: http://www.cs.york.ac.uk/fp/HaXml/COPYRIGHT
They have specifically made the LGPL less restrictive; since the LGPL is a bit 
hard to read quickly, http://en.wikipedia.org/wiki/LGPL may be easier.

The programs that come with the HaXml library are licensed under the GPL.


A license which requires programmers to disclose their sources
shouldn't be a problem for a commercial application. Which C hacker
would or could steal code from it? :-)


Since no compiler I know of does require disclosure, I recognize that the above 
is a purely sarcastic statement.  And the canonical use of the smiley gives it away.



Hi Henning -
Apologies for not replying sooner. I couldn't think what to say! ;-)

Disclaimer: the following essay only contains 2 Haskell functions and is 
not intended to cause offence to farmers...


Disclaimer: I like the GPL, I understand the LGPL, and I am releasing my work on 
Text.Regex.Lazy as BSD.


Afaict a license such as GPL allows anyone, even a non-programmer, to 
just re-distribute whatever application you created because one 
condition of it is that anyone should be free to share software with 
anyone else without having to pay anything extra to the people who wrote 
it, and I think this is essentially based on the notion that software 
should not be regarded as an ownable or sellable thing.


The GPL does indeed do that.  Your even a non-programmer aside is strange, as 
I cannot guess how to segregate people into such a category.


The GPL itself refers to a cost of distribution, since it recognizes such things 
are not free-in-price.  This is in reference to offering a copy of the source 
code.  The price of a binary copy can be as large as desired.  Likewise for the 
cost of support.


Nothing copyrighted is a ownable or sellable thing.  All copyrighted software 
is licensed.  You cannot make many useful analogies between things and licenses.


However a potato is sellable, even though farmers have such a great time 
out in the fields breathing in the fresh misty morning air and watching 
the beautiful colours of the sunrise, and basically just letting nature 
take its course with a bit of healthy exercise and free food thrown in 
for good measure (it might even be some of my personal sweat that 
evaporates and later falls as rain to nourish their crops). And what 
makes them think they have a right to own parts of the earth's surface 
anyway! ;-)


Farmers have great mystique and respect in modern society.  That was a good 
choice for emotion-based rhetoric.


While I'd personally like to live in a peaceful society where everything 
is freely available, the fact is that I have to deal with the situation 
I find myself in at the moment ie I 

Re: [Haskell-cafe] Why Not Haskell?

2006-08-06 Thread Piotr Kalinowski

On 06/08/06, Brian Hulley [EMAIL PROTECTED] wrote:

Therefore I think this distinction between concepts is just sophistry.


The distinction is there and relies on the community and people being
honest to avoid situations as you described. If you don't want it
however (well in this case relying on honesty seems ... naive, to say
the least), you may choose a different license. You're free after all
:)


The system of owners of software encourages
software owners to produce something---
but not what society really needs.
And it causes intangible ethical pollution
that affects us all.

Is this not designed to stir up feelings of guilt in proprietary software
developers? And is it desirable to limit the production of software to what
society really needs? Eg I'm glad the Coca-Cola company chooses to produce
Coke because I like drinking it but in no way could it be said that I
actually *need* it, and I wouldn't expect them to reveal their secret recipe
so endless other companies could instantly start competing with them.


The Coke is not the best example. First of all you don't expect that
Coca-Cole gives you right to modify the drink to suit your needs.
Nobody knows even what that would be supposed to mean :)

Secondly, even if Stallman's philosophy is quite idealistic, there is
number of practices in software industry that make ethical doubts
arise (at least when I'm concerned). Yet still it is customers' choice
that they allow to be fooled.


I can't entirely dismiss GNU/FSF/GPL but it poses a fundamental conflict
with the only way I can see of earning a living so it's like a continuous
background problem which drains some of my energy and enthusiasm hence the
length of my rambling post where I made another attempt to understand my
relation to it.


Well, setting aside usefulness of GPL in a commercial world, it did
serve a purpose not allowing anybody to buy out the opensource world
and kill it, didn't it?

Regards,
--
Intelligence is like a river: the deeper it is, the less noise it makes
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why Not Haskell?

2006-08-06 Thread Brian Hulley

Piotr Kalinowski wrote:

On 06/08/06, Brian Hulley [EMAIL PROTECTED] wrote:

Therefore I think this distinction between concepts is just
sophistry.


The distinction is there and relies on the community and people being
honest to avoid situations as you described. If you don't want it
however (well in this case relying on honesty seems ... naive, to say
the least), you may choose a different license. You're free after all
:)


True, but then I'm faced with the worry that someone at FSF may think I'm 
not ethical or that I don't care about human rights! :-)


Ok I can live with that, but to continue with an exploration of the ethical 
implications of GPL, consider this hypothetical situation between two 
law-abiding neighbours:


Ned : Howdy Homer! Come and see this new supperty-dupperty 
wimbly-wambly program I've just bought from Nick [who's now a software 
developer living in a tumble down shack on the edge of town]!


[Homer follows Ned inside and Ned types something into the program and 
a funny animation appears on the screen.]


   Ned : It can do lots of other stuff too!

   Homer: I want a copy

   Ned: It's really cheap. Only $20 from Nick.

   Homer: Come on Ned! We're neighbours! Just give me it!

   [Ned checks the license and finds it's GPL]

   Ned: Well I could give you it, but ...

   Homer: But what? [Jumping about trying to contain his excitement at 
being able to make funny animations at home]


   Ned: [Knowing that Nick is struggling to pay his bills] Well if I gave 
you it then that won't help Nick.


   Homer: I don't like him anyway! Come on Ned, we're friends...

   [Ned can see that if he refuses to give Homer a free copy, Homer is 
still so excited about the program that he'll go out and pay Nick the $20.]


So now Ned, who's a very conscientious person, is faced with an impossible 
moral dilemma, ie a choice between helping Nick establish his business or 
losing Homer (who's a bit slow when it comes to matters of conscience) as a 
friend.


If Ned is strong enough to just tell Homer that Nick needs the money and 
that Homer is being selfish and can easily afford it, then GPL would have 
played a positive role in forcing more honesty between neighbours so deeper 
friendship could develop in the community.


However if Ned is not that strong, and just agrees to give Homer a free 
copy, then he'll feel guilty about poor Nick, and he'd have GPL to blame for 
removing the only excuse that Homer would have understood.





The system of owners of software encourages
software owners to produce something---
but not what society really needs.
And it causes intangible ethical pollution
that affects us all.

Is this not designed to stir up feelings of guilt in proprietary
software developers? And is it desirable to limit the production of
software to what society really needs? Eg I'm glad the Coca-Cola
company chooses to produce Coke because I like drinking it but in no
way could it be said that I actually *need* it, and I wouldn't
expect them to reveal their secret recipe so endless other companies
could instantly start competing with them.


The Coke is not the best example. First of all you don't expect that
Coca-Cole gives you right to modify the drink to suit your needs.
Nobody knows even what that would be supposed to mean :)


Continuing the example, neither Ned nor Homer knows anything about computer 
programming so it never occurs to them to want to be able to alter the 
program. They just want to use it as it is.


Proprietary 3d art programs like 3ds Max and AliasWavefront's Maya allow 
users to write scripts or use third party plugins. This is not the same as 
the ability to completely re-write everything in the program or fix bugs 
etc, but perhaps it is enough for many people - after all, everyone only has 
so much time and it would be hard work trying to understand the code of such 
a large program anyway - why not just let the company that produced it do 
that work? If all else fails, people are always free to write their own code 
from scratch or pay someone else to do it.




Secondly, even if Stallman's philosophy is quite idealistic, there is
number of practices in software industry that make ethical doubts
arise (at least when I'm concerned). Yet still it is customers' choice
that they allow to be fooled.


I think the choice of whether or not to engage in unethical practices is 
orthogonal to the choice of whether or not to follow the course of action 
that Stallman wants to enforce using GPL.


However a positive aspect of his writings is that he draws attentions to 
issues that might otherwise go unnoticed, regardless of whether or not one 
agrees with his conclusions, and it certainly makes interesting reading 
(I've got RMS's book Free as in Freedom here in front of me as I type 
this).





I can't entirely dismiss GNU/FSF/GPL but it poses a fundamental
conflict with the only way I can see of earning a living so 

Re: [Haskell-cafe] Why Not Haskell?

2006-08-06 Thread Piotr Kalinowski
On 07/08/06, Brian Hulley [EMAIL PROTECTED] wrote:
So now Ned, who's a very conscientious person, is faced with an impossiblemoral dilemma, ie a choice between helping Nick establish his business orlosing Homer (who's a bit slow when it comes to matters of conscience) as a
friend.A good friend should not put him in such a position ;)Regards,-- Intelligence is like a river: the deeper it is, the less noise it makes
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why Not Haskell?

2006-08-05 Thread Bjorn Bringert

On Aug 4, 2006, at 11:10 PM, Bulat Ziganshin wrote:


Friday, August 4, 2006, 8:17:42 PM, you wrote:


1) Haskell is too slow for practical use, but the benchmarks I found
appear to contradict this.


it's an advertisement :D  just check yourself


2) Input and output are not good enough, in particular for graphical
user interfacing and/or data base interaction. But it seems there are
several user interfaces and SQL and other data base interfaces for
Haskell, even though the tutorials don't seem to cover this.


i've seen a paper which lists 7 (as i remember) causes of small
Haskell popularity, including teaching, libraries, IDEs and so on. may
be someone will give us the url


Is this the paper you are referring to?

Philip Wadler. Why no one uses functional languages. ACM SIGPLAN  
Notices, 33(8):23--27, 1998.

http://citeseer.ist.psu.edu/wadler98why.html

/Björn



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


Re: [Haskell-cafe] Why Not Haskell?

2006-08-05 Thread Brian Hulley

Henning Thielemann wrote:

On Fri, 4 Aug 2006, Brian Hulley wrote:


4) Haskell is open source and licensing restrictions forbid
commercial applications. I haven't seen any such restrictions, but
is this a problem for the standard modules?


You can discover the licensing situation by downloading the GHC
source (or source for whatever distro you're using) and looking in
the directories for each package. For example the base package uses
a BSD-style licence and HaXml uses LGPL with the exception to allow
static linking.


A license which requires programmers to disclose their sources
shouldn't be a problem for a commercial application. Which C hacker
would or could steal code from it? :-)


Hi Henning -
Apologies for not replying sooner. I couldn't think what to say! ;-)

Disclaimer: the following essay only contains 2 Haskell functions and is not 
intended to cause offence to farmers...


Afaict a license such as GPL allows anyone, even a non-programmer, to just 
re-distribute whatever application you created because one condition of it 
is that anyone should be free to share software with anyone else without 
having to pay anything extra to the people who wrote it, and I think this is 
essentially based on the notion that software should not be regarded as an 
ownable or sellable thing.


However a potato is sellable, even though farmers have such a great time out 
in the fields breathing in the fresh misty morning air and watching the 
beautiful colours of the sunrise, and basically just letting nature take its 
course with a bit of healthy exercise and free food thrown in for good 
measure (it might even be some of my personal sweat that evaporates and 
later falls as rain to nourish their crops). And what makes them think 
they have a right to own parts of the earth's surface anyway! ;-)


While I'd personally like to live in a peaceful society where everything is 
freely available, the fact is that I have to deal with the situation I find 
myself in at the moment ie I have to pay money whevener I need food, 
electricity, gas, internet, petrol, dvds, music, art etc and I absolutely 
don't agree that everyone else in the world except software developers has 
the right to earn a living, while we just give everything away because it's 
so much fun bringing it into existence, or that we should be chastised for 
trying to charge for our efforts!!! ;-)


Also, if we want a better world I can think of other professions to 
sacrifice (Hint: take 5 p = polit and last p = 'n').


Making complete end-user applications freely available is not always helpful 
to others, even to the end-users. Consider how a local corner-shop owner 
would feel if all the large supermarket chains stood outside his door giving 
away free food. The consumers are very happy! How selfless and beneficient 
those big supermarkets are! But how long would the corner-shop be able to 
stay open? And would the supermarkets continue to supply the free food after 
they'd finally wiped out his business? People no longer meet for a chat at 
the corner-shop. There is a void in the community. People start to feel 
alienated. Houses are vandalised. Crime is on the increase. The government 
claims it needs more powers to prevent it. Perhaps a few people see what's 
happening but really it's already too late...


Of course from a pragmatic point of view it is useful for developers to 
share parts of their source or coding ideas, since there is clearly too much 
work for any one person to do, thus BSD and LGPL make a lot of commercial 
sense, as well as being a nice gesture of fraternity between coders, and a 
blueprint for the future if we can only find the right strategies to achieve 
it given our own specific individual circumstances.


Therefore I think licenses which enforce a particular strategy or attempt to 
limit possible business models to further a specific agenda, however well 
meaning they may appear, are unattractive for commercial development in 
general, even though some specific niche companies can manage fine under 
those conditions (eg consultants/ trainers/ contracted developers etc).


Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Why Not Haskell?

2006-08-04 Thread Donn Cave
On Fri, 4 Aug 2006, Hans van Thiel wrote:
...
 Are there other reasons why there seem to be just a few thousand
 (hundred?) Haskell programmers in the world, compared to the 3 million
 Java programmers and x million C/C++ programmers?

I can think of several other possible reasons -
6.  Instability - available for 15 years, you say, but does the Haskell
of 15 years ago support today's programs?  Does standard Haskell
even support today's programs?
7.  Some difficult concepts, at a level that goes way beyond the commonly
used languages.
8.  Problems with evaluation model and space that other languages don't
have to deal with.
9.  Missing libraries

and more, I suppose.  I'm not saying any of these are necessarily compelling
reasons not to use Haskell, but altogether, maybe another way to look at it
is that it's really a strong statement when people decide to bet their
livelihood on Haskell software development - it isn't the safe choice, and
it means someone finds the reasons for it very compelling.

Donn Cave, [EMAIL PROTECTED]

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


Re: [Haskell-cafe] Why Not Haskell?

2006-08-04 Thread Brandon Moore

Hans van Thiel wrote:

Hello All,

I'm wondering why I can't find any commercial Haskell applications on
the Internet. Is there any reason for this?
I can think of the following possibilities only:
1) Haskell is too slow for practical use, but the benchmarks I found
appear to contradict this.
2) Input and output are not good enough, in particular for graphical
user interfacing and/or data base interaction. But it seems there are
several user interfaces and SQL and other data base interfaces for
Haskell, even though the tutorials don't seem to cover this.
3) Haskell is not scaleable for commercial use. This looks unlikely to
me, but could this be a factor?
4) Haskell is open source and licensing restrictions forbid commercial
applications. I haven't seen any such restrictions, but is this a
problem for the standard modules?


I wonder, how many languages have you seen commercial applications 
written in? I suppose you mean the sort of applications that might be 
sold in stores. I think a more interesting question around Haskell is 
what it takes to succeed in writing an application in a relatively 
uncommon language, what aspects of popularity are actually useful, and

how you can compensate.

What languages have gotten big without being the main language for a 
popular operating system, or pushed really hard by a big company?
Then there are moderately popular languages like perl and Python, but 
are there lots of commercial application even in those?


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


Re: [Haskell-cafe] Why Not Haskell?

2006-08-04 Thread Udo Stenzel
Hans van Thiel wrote:
 I'm wondering why I can't find any commercial Haskell applications on
 the Internet. Is there any reason for this?

Of course.  Corporations are conservative to the point of being
boneheaded.  So to avoid risk, they all went on the internet and said,
Gee, I can't find any commercial Haskell applications on the Internet.
There must be a reason for that, so I better use something else.


 Are there other reasons why there seem to be just a few thousand
 (hundred?) Haskell programmers in the world, compared to the 3 million
 Java programmers and x million C/C++ programmers?

Yah.  2.995 million programmer-wannabes were too lazy to think for
themselves and choose what everybody uses.

 
 Probably it doesn't make much sense to try and develop a
 tool in C++ or even Java, but if I have to go on my own on this, maybe
 Haskell could be feasible, both for fun and profit.

It never makes sense to limit yourself to only one programming language,
even if it happens to be Haskell.  There's always the FFI, should it
turn out that some part is better done in C or assembly or Fortran or
whatever comes to mind.


Udo.
-- 
The two most abundant things in the universe are hydrogen and
stupidity. -- Harlan Ellison 


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


Re: [Haskell-cafe] Why Not Haskell?

2006-08-04 Thread Brian Hulley

Hans van Thiel wrote:

Hello All,

I'm wondering why I can't find any commercial Haskell applications on
the Internet. Is there any reason for this?


I'm actually working on a Haskell program which I hope to release as a 
commercial application. The biggest problem I'm encountering is the lack of 
a really solid collections library that's as well thought out as C++ STL 
because although there are several competing collections libraries, each 
allowing fast development of powerful code, they all have various faults and 
limitations and I hate the idea of my code resting on half-baked 
foundations. I'm also a rabid perfectionist (and extremely fussy with regard 
to code aesthetics) when it comes to these kind of things so perhaps it's my 
fault.


Perhaps it's also because Haskell raises your expectations regarding what a 
good program should be like, so it's easy to get lost in abstraction. Eg 
last week all I needed was an equivalent of the C++ std::vector but I've 
wasted the whole of this week trying to create the perfect factoring of 
collection classes to try and avoid having concrete types everywhere and to 
be a foundation for all the uses of collection types in my program, and now 
I'm totally lost in a miasma of undecidable instances and difficult 
decisions.



I can think of the following possibilities only:
1) Haskell is too slow for practical use, but the benchmarks I found
appear to contradict this.


I think it's fast enough. There's also a very good foreign function 
interface if you need to get the full speed of C for some inner loop. And a 
bonus is that as more and more people use it, it's likely that more effort 
will be done to make it faster.



2) Input and output are not good enough, in particular for graphical
user interfacing and/or data base interaction. But it seems there are
several user interfaces and SQL and other data base interfaces for
Haskell, even though the tutorials don't seem to cover this.


You just need to check the licences for the various bindings and also the 
licences for the C libs they're bound to so you don't end up with a GPL 
infested program. WxWidgets uses LGPL with the linking exception so it 
should be 100% safe and easy to use 
(http://wxhaskell.sourceforge.net/license.html ). Gtk2Hs uses the LGPL 
according to http://haskell.org/gtk2hs/overview/ but it does not appear to 
admit the linking exception though this is not insurmountable - it just 
means you need to supply an object file of your code along with your exe 
(and if you use Unix there's no trouble at all because the lib is linked 
dynamically iirc)



3) Haskell is not scaleable for commercial use. This looks unlikely to
me, but could this be a factor?


It can be difficult to know how to organise a large program in Haskell if 
you're used to OOP but I don't think there are any limits on scalability per 
se - GHC is itself an example of a very large Haskell program that's widely 
used on many platforms.



4) Haskell is open source and licensing restrictions forbid commercial
applications. I haven't seen any such restrictions, but is this a
problem for the standard modules?


You can discover the licensing situation by downloading the GHC source (or 
source for whatever distro you're using) and looking in the directories for 
each package. For example the base package uses a BSD-style licence and 
HaXml uses LGPL with the exception to allow static linking.
It would be good if this info was also on the wiki somewhere but if it is I 
can't find it, or if there was a tool to identify or gather together the 
various licenses and create a composite license (eg including the list of 
the names of all contributors who want to be mentioned) to distribute with 
your app (a free lawyer implemented in Haskell together with its own 
self-generated license!!!).


If you're going to release your app on Windows using GHC you'll need to 
prepare an object file to distribute along with your exe to satisfy the 
annoying LGPL linking restriction imposed by the GMP library that's 
currently part of the statically linked runtime, but this shouldn't be an 
obstacle once you've written the appropriate batch file to generate it.


(There's a thread on the ghc users mailing list indicating that GMP might be 
removed from GHC at some point which would make life even easier - see 
http://www.haskell.org/pipermail/glasgow-haskell-users/2006-August/010665.html )


[snip]


Why hasn't Haskell made it into the business world (yet), after being
available for 15 years, or is this the wrong question?


This might just be because computers were too slow in the past to run 
programs written in such high level languages as Haskell, so everyone had to 
use low-level languages like C and C++ (people even now still spend 
sleepless nights debating whether or not to use a virtual function in a C++ 
class because of the extra indirection it requires).


Also, the bottom line imho is that Haskell is a difficult language to 

Re: [Haskell-cafe] Why Not Haskell?

2006-08-04 Thread Donn Cave
On Fri, 4 Aug 2006, Udo Stenzel wrote:
 Hans van Thiel wrote:
 I'm wondering why I can't find any commercial Haskell applications on
 the Internet. Is there any reason for this?
 
 Of course.  Corporations are conservative to the point of being
 boneheaded.  So to avoid risk, they all went on the internet and said,
 Gee, I can't find any commercial Haskell applications on the Internet.
 There must be a reason for that, so I better use something else.

Or maybe they're more clever than you imagine, and they all have rooms
full of Haskell programmers sworn to secrecy, trying to get a jump on
the competition.  Wouldn't it be funny if it turned out that the Python
stuff at Google was just a side-show, and Haskell was really the big
development language all along?  (Not true, I'm sure - you could sort
of stand a chance of starting a secret Python development project, but
Haskell I doubt.)

Donn

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


Re: [Haskell-cafe] Why Not Haskell?

2006-08-04 Thread Henning Thielemann

On Fri, 4 Aug 2006, Brian Hulley wrote:

  4) Haskell is open source and licensing restrictions forbid commercial
  applications. I haven't seen any such restrictions, but is this a
  problem for the standard modules?
 
 You can discover the licensing situation by downloading the GHC source (or
 source for whatever distro you're using) and looking in the directories for
 each package. For example the base package uses a BSD-style licence and HaXml
 uses LGPL with the exception to allow static linking.

A license which requires programmers to disclose their sources shouldn't
be a problem for a commercial application. Which C hacker would or could
steal code from it? :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why Not Haskell?

2006-08-04 Thread Bulat Ziganshin
Hello Hans,

Friday, August 4, 2006, 8:17:42 PM, you wrote:

 1) Haskell is too slow for practical use, but the benchmarks I found
 appear to contradict this.

it's an advertisement :D  just check yourself

 2) Input and output are not good enough, in particular for graphical
 user interfacing and/or data base interaction. But it seems there are
 several user interfaces and SQL and other data base interfaces for
 Haskell, even though the tutorials don't seem to cover this.

i've seen a paper which lists 7 (as i remember) causes of small
Haskell popularity, including teaching, libraries, IDEs and so on. may
be someone will give us the url

i personally think that Haskell in its current state is appropriate
for system programming

 Are there other reasons why there seem to be just a few thousand
 (hundred?) Haskell programmers in the world, compared to the 3 million
 Java programmers and x million C/C++ programmers?

i once analyzed why C++ and not Eiffel or Modula-2 becomes the
language of 90's. my conclusion was what C and C++ becomes a tandem at
the late 80's - C raised popularity because it had OOP successor while
C++ becomes popular because it had imperative predecessor. Pascal,
Modula-2 or Eiffel was great languages, but they don't form such
tandems. So, now we have 3 million of Java programmers just because C was
a great tool for writing DOS apps :)

 Now I'm trying to come up with a business model for my algorithm and to
 avoid the mistakes I made 10 years ago. There is a lot of difference
 between a prototype and a working tool, and then there is a lot of
 difference between a working tool and a successful commercial
 application. Probably it doesn't make much sense to try and develop a
 tool in C++ or even Java, but if I have to go on my own on this, maybe
 Haskell could be feasible, both for fun and profit.

if speed isn't critical, if you don't need to use many libs, don't
need help from RAD tools in developing UI of your program - you can
use Haskell, imho


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Why Not Haskell?

2006-08-04 Thread ajb
G'day all.

Quoting Udo Stenzel [EMAIL PROTECTED]:

 Uh, this one's wrong.  Does C++ of 15 years ago support today's programs?

C++ of _today_ doesn't support today's programs in some cases.  Just
ask the Boost developers about the various workarounds they still have
to deal with.

 No.  C++ of 10 years ago probably does, but the compiler will crash.

Even compiling a fully conforming ISO C++ standard library generally
requires a compiler from at most three years ago.

Generally speaking, any C++ application that was written 10 years ago
and hasn't been rewritten avoids large parts of the standard library
precisely because it was so poorly supported, and what was supported
was poorly implemented.  (That's why Qt looks like it does.)

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


Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread Fritz Ruehr

On Jul 26, 2006, at 6:44 PM, Sebastian Sylvan wrote:


For example ...

if :: Bool - a - a - a
if True t _ = t
if False _ e = e

-- example usage
myAbs x = if (x  0) (negate x) x


I suppose there might also be a case for flipping the arguments about 
like this:


if :: a - a - Bool - a
if t _ True = t
if _ e False = e

This way it would follow foldr more closely, in recognition that the 
conditional is essentially the fold/cata/eliminator/... for booleans.


But argument order is a pretty trivial thing, and I think the committee 
made the right choice with if-then-else as a language construct.


  --  Fritz

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


Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread Niklas Broberg

I often find myself at odds with this choice. The reason is that I use
Haskell as a host for embedded languages, and these often come with
their own control flows. So I find myself wanting to write my own
definition of the if-then-else construct that works on terms of some
other type, e.g. tests on values of type Exp Bool instead of Bool, and
at the same time make sure that the user doesn't use the built-in
if-then-else. Sure, I can (and do) call my own version if_, ifElse or
something else along those lines, but it's sure to be a constant
source of programmer errors, writing if-then-else instead of if_ by
habit.

A thought that has crossed my mind on several occasions is, why not
make the syntactic if-then-else construct rebindable, like the do
notation? I think I know the answer already -- the do notation is
syntactic sugar for = and company so it's easy to translate it into
non-prelude-qualified versions of functions with those names. This is
not the case for if-then-else. But it could be, the prelude could
define a function if_ (or whatever) that the if-then-else construct is
made to be sugar for, and thus also amenable to rebinding by not
prelude-qualifying.

/Niklas

On 7/27/06, Paul Hudak [EMAIL PROTECTED] wrote:

Mike Gunter wrote:

I had hoped the History of Haskell paper would answer a question
I've pondered for some time: why does Haskell have the if-then-else
syntax?  The paper doesn't address this.  What's the story?

thanks,
-m


Thanks for asking about this -- it probably should be in the paper.  Dan
Doel's answer is closest to the truth:

I imagine the answer is that having the syntax for it looks nicer/is
clearer. if a b c could be more cryptic than if a then b else c
for some values of a, b and c.

except that there was also the simple desire to conform to convention
here (I don't recall fewer parentheses being a reason for the choice).
In considering the alternative, I remember the function cond being
proposed instead of if, in deference to Scheme and to avoid confusion
with people's expectations regarding if.

A related issue is why Haskell does not have a single arm conditional
-- i.e. an if-then form, which would evaluate to bottom (i.e. error)
if the predicate were false.  This was actually discussed, but rejected
as a bad idea for a purely functional language.

  -Paul

___
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] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread Tom Schrijvers

I often find myself at odds with this choice. The reason is that I use
Haskell as a host for embedded languages, and these often come with
their own control flows. So I find myself wanting to write my own
definition of the if-then-else construct that works on terms of some
other type, e.g. tests on values of type Exp Bool instead of Bool, and
at the same time make sure that the user doesn't use the built-in
if-then-else. Sure, I can (and do) call my own version if_, ifElse or
something else along those lines, but it's sure to be a constant
source of programmer errors, writing if-then-else instead of if_ by
habit.

A thought that has crossed my mind on several occasions is, why not
make the syntactic if-then-else construct rebindable, like the do
notation? I think I know the answer already -- the do notation is
syntactic sugar for = and company so it's easy to translate it into
non-prelude-qualified versions of functions with those names. This is
not the case for if-then-else. But it could be, the prelude could
define a function if_ (or whatever) that the if-then-else construct is
made to be sugar for, and thus also amenable to rebinding by not
prelude-qualifying.


Wouldn't this cause a conflict with specialized knowledge the compiler has 
about if-then-else, e.g. for optimizations?


Tom

--
Tom Schrijvers

Department of Computer Science
K.U. Leuven
Celestijnenlaan 200A
B-3001 Heverlee
Belgium

tel: +32 16 327544
e-mail: [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread Chris Kuklewicz

Niklas Broberg wrote:

I often find myself at odds with this choice. The reason is that I use
Haskell as a host for embedded languages, and these often come with
their own control flows. So I find myself wanting to write my own
definition of the if-then-else construct that works on terms of some
other type, e.g. tests on values of type Exp Bool instead of Bool, and
at the same time make sure that the user doesn't use the built-in
if-then-else. Sure, I can (and do) call my own version if_, ifElse or
something else along those lines, but it's sure to be a constant
source of programmer errors, writing if-then-else instead of if_ by
habit.

A thought that has crossed my mind on several occasions is, why not
make the syntactic if-then-else construct rebindable, like the do
notation? I think I know the answer already -- the do notation is
syntactic sugar for = and company so it's easy to translate it into
non-prelude-qualified versions of functions with those names. This is
not the case for if-then-else. But it could be, the prelude could
define a function if_ (or whatever) that the if-then-else construct is
made to be sugar for, and thus also amenable to rebinding by not
prelude-qualifying.

/Niklas


You may not realize that if-then-else is just syntactic sugar like do.  Read 
the Haskell 98 Report


http://www.haskell.org/onlinereport/exps.html#conditionals


Translation:
The following identity holds:
if e1 then e2 else e3 = case e1 of { True - e2 ; False - e3 }
where True and False are the two nullary constructors from the type Bool,
as defined in the Prelude. The type of e1 must be Bool;
e2 and e3 must have the same type, which is also the type of the entire 
conditional expression.


So you could easily create a patched compiler that allows for rebindable syntax.

The fundamental syntax of do and if/then/else and patterns or guards in 
function definitions is always a case statement.


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


Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread Henning Thielemann

On Wed, 26 Jul 2006, Fritz Ruehr wrote:

 On Jul 26, 2006, at 6:44 PM, Sebastian Sylvan wrote:
 
  For example ...
  
  if :: Bool - a - a - a
  if True t _ = t
  if False _ e = e
  
  -- example usage
  myAbs x = if (x  0) (negate x) x
 
 I suppose there might also be a case for flipping the arguments about like
 this:
 
 if :: a - a - Bool - a
 if t _ True = t
 if _ e False = e
 
 This way it would follow foldr more closely, in recognition that the
 conditional is essentially the fold/cata/eliminator/... for booleans.

I found the argument order of the first if (Bool - a - a - a) already 
useful for a 'case' with computed conditions:
  select = foldr (uncurry if_)

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


Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread Jon Fairbairn
On 2006-07-27 at 01:33EDT Paul Hudak wrote:
 Thanks for asking about this -- it probably should be in the paper.  Dan 
 Doel's answer is closest to the truth:
 
 I imagine the answer is that having the syntax for it looks nicer/is
 clearer. if a b c could be more cryptic than if a then b else c
 for some values of a, b and c.
 
 except that there was also the simple desire to conform to convention 
 here (I don't recall fewer parentheses being a reason for the choice). 

In a sense, it explicitly wasn't: I suggested if _ then _
else _ fi -- something I was long used to from Algol68 --
but it was rejected on the ground that there wasn't a
dangling else problem in Haskell.  I probably muttered
something about wanting things to be self-bracketing (I've
certainly grumbled inwardly since about having to write (if
_ then _ else _)¹ in some Haskell contexts), but since I'm
quite slow witted, I expect that the discussion had moved on
by then.
 
 In considering the alternative, I remember the function cond being 
 proposed instead of if, in deference to Scheme and to avoid confusion 
 with people's expectations regarding if.

Did we talk about Dijkstra's fat bar, or was that a
discussion I had elsewhere?

  Jón

[1] which I find ugly, and besides, making all like
constructs self-bracketing would have allowed a saner (to my
mind) layout rule.


-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


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


RE: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread Simon Peyton-Jones
GHC does indeed include the notion of rebindable syntax.  It would be
straightforward to extend it to include if-then-else.  In effect, that
would mean that 
if e1 then e2 else e3
would behave exactly like
cond e1 e2 e3
including from the point of view of typing.  (You could choose a
different name than 'cond'.)  Then by importing a 'cond' with (say) type

cond :: MyBool - b - b
you could use a different kind of Boolean.  You could even overload the
bool:
cond :: Boolean a = a - b - b

This could be done with a few hours work.  But not a few minutes. Want
to put a feature request in Trac?

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Niklas
| Broberg
| Sent: 27 July 2006 09:01
| To: Haskell-cafe
| Subject: Re: [Haskell-cafe] Why does Haskell have the if-then-else
syntax?
| 
| I often find myself at odds with this choice. The reason is that I use
| Haskell as a host for embedded languages, and these often come with
| their own control flows. So I find myself wanting to write my own
| definition of the if-then-else construct that works on terms of some
| other type, e.g. tests on values of type Exp Bool instead of Bool, and
| at the same time make sure that the user doesn't use the built-in
| if-then-else. Sure, I can (and do) call my own version if_, ifElse or
| something else along those lines, but it's sure to be a constant
| source of programmer errors, writing if-then-else instead of if_ by
| habit.
| 
| A thought that has crossed my mind on several occasions is, why not
| make the syntactic if-then-else construct rebindable, like the do
| notation? I think I know the answer already -- the do notation is
| syntactic sugar for = and company so it's easy to translate it into
| non-prelude-qualified versions of functions with those names. This is
| not the case for if-then-else. But it could be, the prelude could
| define a function if_ (or whatever) that the if-then-else construct is
| made to be sugar for, and thus also amenable to rebinding by not
| prelude-qualifying.
| 
| /Niklas
| 
| On 7/27/06, Paul Hudak [EMAIL PROTECTED] wrote:
|  Mike Gunter wrote:
| 
|  I had hoped the History of Haskell paper would answer a question
|  I've pondered for some time: why does Haskell have the if-then-else
|  syntax?  The paper doesn't address this.  What's the story?
|  
|  thanks,
|  -m
|  
|  
|  Thanks for asking about this -- it probably should be in the paper.
Dan
|  Doel's answer is closest to the truth:
| 
|  I imagine the answer is that having the syntax for it looks
nicer/is
|  clearer. if a b c could be more cryptic than if a then b else
c
|  for some values of a, b and c.
| 
|  except that there was also the simple desire to conform to
convention
|  here (I don't recall fewer parentheses being a reason for the
choice).
|  In considering the alternative, I remember the function cond being
|  proposed instead of if, in deference to Scheme and to avoid
confusion
|  with people's expectations regarding if.
| 
|  A related issue is why Haskell does not have a single arm
conditional
|  -- i.e. an if-then form, which would evaluate to bottom (i.e.
error)
|  if the predicate were false.  This was actually discussed, but
rejected
|  as a bad idea for a purely functional language.
| 
|-Paul
| 
|  ___
|  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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread Tomasz Zielonka
On Thu, Jul 27, 2006 at 10:22:31AM +0100, Jon Fairbairn wrote:
 On 2006-07-27 at 01:33EDT Paul Hudak wrote:
  Thanks for asking about this -- it probably should be in the paper.  Dan 
  Doel's answer is closest to the truth:
  
  I imagine the answer is that having the syntax for it looks nicer/is
  clearer. if a b c could be more cryptic than if a then b else c
  for some values of a, b and c.
  
  except that there was also the simple desire to conform to convention 
  here (I don't recall fewer parentheses being a reason for the choice). 
 
 In a sense, it explicitly wasn't: I suggested if _ then _
 else _ fi -- something I was long used to from Algol68 --
 but it was rejected on the ground that there wasn't a
 dangling else problem in Haskell.

But because if-then-else is an expression, there is another
problem. Consider:

(if True then 0 else 1) + 2 -- 2
if True then 0 else 1 + 2   -- 0
let cond a b c = if a then b else c
cond True 0 1 + 2   -- 2   -- different from if-then-else 
withouth parentheses

It's quite easy to fall in this trap. I think it happened to me
at least twice. It goes like this: first I have an expression
that doesn't involve if-then-else, eg.

a + b

Then I realize that a has to be changed in some situations,
so I replace it with a conditional expression:

if c then a else a' + b

or

if c then f a else g a + b

But now  + b gets under the else branch.

If I used a cond function, or if if-then-else had a different
priority, it would be easier to avoid such a mistake. There is no
problem with the first version:

cond c a a' + b

For an experienced Haskell programmer it's obvious that function
application has a higher precendence than addition.

In the second version, it would be clear that parentheses have
to be added:

cond c (f a) (g a) + b

Could the cond function encourage other kinds of bugs? I think
it's less likely, because it's a normal function.

Also, after a few years of Haskell programming, I am still not
sure how to indent if-then-else.

Perhaps in Haskell' we could have some lightweight case-of version with
no pattern matching, guards only (cond could be a good name). I think
it was even discussed before. The usual case-of looks like this:

case x of
Left err | isEOFError e - ...
Left err - ...
Right result - ...

cond would involve no pattern matching, or only as pattern guards.

cond
x == 0 - ...
x == 1 - ...
otherwise - ...

currently it can be written as

case () of
_ | x == 0 - ...
_ | x == 1 - ...
_ | otherwise - ...

which is a bit ugly.

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


Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread Jon Fairbairn
On 2006-07-27 at 13:01+0200 Tomasz Zielonka wrote:
 But because if-then-else is an expression, there is another
 problem.

That was exactly my point when I made the muttering about
self-bracketing (if ... fi, like everything else, is an
expression in Algol68) all those years ago.  I really regret
not having been more forceful!

 Also, after a few years of Haskell programming, I am still not
 sure how to indent if-then-else.

what I was alluding to in my footnote...

 Jón
-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


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


Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread Brian Hulley

Jon Fairbairn wrote:

On 2006-07-27 at 13:01+0200 Tomasz Zielonka wrote:

Also, after a few years of Haskell programming, I am still not
sure how to indent if-then-else.


what I was alluding to in my footnote...


I think there's really only one way when it needs to occupy more than one 
line:


  if c
then t
else f

Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread David House

On 27/07/06, Brian Hulley [EMAIL PROTECTED] wrote:

I think there's really only one way when it needs to occupy more than one
line:

   if c
 then t
 else f


Confusingly,

if c
then t
else f

Also works, although no-one really knows why.

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread Brian Hulley

David House wrote:

On 27/07/06, Brian Hulley [EMAIL PROTECTED] wrote:

I think there's really only one way when it needs to occupy more
than one line:

   if c
 then t
 else f


Confusingly,

if c
then t
else f

Also works, although no-one really knows why.


Only if the if does not start a new layout line. Anyway, how about 
changing the syntax to:


   if exp { then exp ; else exp }

Then the layout rule + the offside rule would still allow (iiuc)

   if x  0 then 5 else 6

but would force the then to be further indented than the if (and the 
else to be indented at least as much as the then (indenting it more is 
where the offside rule is needed to make things work))


In addition, if we followed Jon's suggestion to make constructs 
self-bracketing, we could allow an optional keyword such as /if to 
terminate the construct early thus:


   a = if x  0 then 5 else 6 /if + 78

I'd also change the lambda syntax to:

   \{x 2 - x+5; x y - x*y}

which again would, by the layout rule, still allow current lambda syntax as 
a special case. The optional terminator could be /\ and if all constructs 
were now aexp's (as suggested by the desire to make them self-bracketing) 
instead of exp10's we could then write:


f \x y - y x /\ 6

instead of having to write

f (\x y - y x) 6

I'd be in favour of /if /case /let /\ etc instead of fi esac tel because it 
looks more systematic and follows the usual XML conventions for end tags. 
I'd suggest that floating point division should just be written `divide` - 
it's just a very specialised arithmetic op so why waste a nice symbol on it? 
(ditto ^ ^^ **) (I'd have thought integer division is used more often and 
no-one seems to mind writing `div`.)


Anyway having said all this, I can't help feeling that explicit brackets, as 
required at the moment, help to clarify the structure of the code, and that 
removing the need for them may negatively impact on readability.


Regards, Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread David House

On 27/07/06, Brian Hulley [EMAIL PROTECTED] wrote:

I'd be in favour of /if /case /let /\ etc instead of fi esac tel because it
looks more systematic and follows the usual XML conventions for end tags.
I'd suggest that floating point division should just be written `divide` -
it's just a very specialised arithmetic op so why waste a nice symbol on it?
(ditto ^ ^^ **) (I'd have thought integer division is used more often and
no-one seems to mind writing `div`.)


Why I'd oppose this:

1. Decreases readability/clarity (brackets group things so much clearer)
2. No obvious benefits over brackets (just as many keystrokes, if not more)
3. Not at all backwards-compatible.

I'd support your ideas to change the if syntax, if they weren't
backwards-incompatible. I think something as basic as if statements
can't really be changed now. It will always be a blot on the otherwise
lovely Haskell syntax.

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread Mike Gunter


Thanks for the answer.  (And doubly thanks for giving the answer I
hoped for!)

I propose that ifThenElse and thenElseIf be added to the Prelude for
Haskell'.  While these names are a bit long, I think we want both
functions and these names make the behaviors clear (to me, at least).

Comments?

-m


Paul Hudak [EMAIL PROTECTED] writes:

 Mike Gunter wrote:

I had hoped the History of Haskell paper would answer a question
I've pondered for some time: why does Haskell have the if-then-else
syntax?  The paper doesn't address this.  What's the story?

thanks,
-m


 Thanks for asking about this -- it probably should be in the paper.
 Dan Doel's answer is closest to the truth:

 I imagine the answer is that having the syntax for it looks nicer/is
 clearer. if a b c could be more cryptic than if a then b else c
 for some values of a, b and c.

 except that there was also the simple desire to conform to convention
 here (I don't recall fewer parentheses being a reason for the choice).
 In considering the alternative, I remember the function cond being
 proposed instead of if, in deference to Scheme and to avoid
 confusion with people's expectations regarding if.

 A related issue is why Haskell does not have a single arm
 conditional -- i.e. an if-then form, which would evaluate to bottom
 (i.e. error) if the predicate were false.  This was actually
 discussed, but rejected as a bad idea for a purely functional language.

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


Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-26 Thread mvanier

As opposed to what?

Mike

Mike Gunter wrote:

I had hoped the History of Haskell paper would answer a question
I've pondered for some time: why does Haskell have the if-then-else
syntax?  The paper doesn't address this.  What's the story?

thanks,
-m
___
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] Why does Haskell have the if-then-else syntax?

2006-07-26 Thread Sebastian Sylvan

On 7/27/06, mvanier [EMAIL PROTECTED] wrote:

As opposed to what?


For example case-of, guards (in combination with let or where), or
just a function:

if :: Bool - a - a - a
if True t _ = t
if False _ e = e

-- example usage
myAbs x = if (x  0) (negate x) x


/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-26 Thread Donn Cave
Quoth Sebastian Sylvan [EMAIL PROTECTED]:
| On 7/27/06, mvanier [EMAIL PROTECTED] wrote:
|  As opposed to what?
|
| For example case-of, guards (in combination with let or where), or
| just a function:
|
| if :: Bool - a - a - a
| if True t _ = t
| if False _ e = e
|
| -- example usage
| myAbs x = if (x  0) (negate x) x

That looks to me like a different way to spell if then else, but maybe
that's the answer to the question - conceptually, for every then there
really is an else, however you spell it, and only in a procedural language
does it make any sense to leave it implicit.  The exception that proves the
rule is else return () -, e.g.,

if_ :: Bool - IO () - IO ()
if_ True f = f
if_ False _ = return ()

main = do
args - getArgs
if_ (length args  0)
(print args)

Strictly speaking that generalizes to any functional context where a generic
value can be assigned to the else clause, but there don't tend to be that
many other such contexts.  Does that answer the question?

Donn Cave, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-26 Thread Paul Hudak

Mike Gunter wrote:


I had hoped the History of Haskell paper would answer a question
I've pondered for some time: why does Haskell have the if-then-else
syntax?  The paper doesn't address this.  What's the story?

thanks,
-m
 

Thanks for asking about this -- it probably should be in the paper.  Dan 
Doel's answer is closest to the truth:


   I imagine the answer is that having the syntax for it looks nicer/is
   clearer. if a b c could be more cryptic than if a then b else c
   for some values of a, b and c.

except that there was also the simple desire to conform to convention 
here (I don't recall fewer parentheses being a reason for the choice).  
In considering the alternative, I remember the function cond being 
proposed instead of if, in deference to Scheme and to avoid confusion 
with people's expectations regarding if.


A related issue is why Haskell does not have a single arm conditional 
-- i.e. an if-then form, which would evaluate to bottom (i.e. error) 
if the predicate were false.  This was actually discussed, but rejected 
as a bad idea for a purely functional language.


 -Paul

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