Re: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-02-01 Thread Tomasz Zielonka
On Wed, Jan 31, 2007 at 07:46:15PM +0300, Bulat Ziganshin wrote:
 Wednesday, January 31, 2007, 12:01:16 PM, you wrote:
 
  there are also many other similar issues, such as lack of good syntax
  for for, while, break and other well-known statements,
 
  On the other hand you have an ability to define your own control
  structures.
 
 i have a lot, but their features are limited, both in terms of
 automatic lifting and overall syntax. let's consider
 
 while (hGetBuf h buf bufsize == bufsize)
   crc := updateCrc crc buf bufsize
   break if crc==0
   print crc

A direct translation could look like this:

whileM c b = do { x - c; when x (b  whileM c b) }

f h buf =
flip runContT return $ do
callCC $ \break - do
flip execStateT 0 $ do
whileM (liftIO (liftM (== bufsize) (hGetBuf h buf 
bufsize))) $ do
do  crc - get
crc' - liftIO (updateCrc crc buf bufsize)
put crc'
crc - get
when (crc == 0) (lift (break crc))
liftIO (print crc)

Which, admittedly, is much more lengthy. If we assume that hGetBuf,
updateCrc and print can work in any MonadIO, and we define
inContT x = flip runContT return x
then it becomes slightly shorter:

inContT $ callCC $ \break - do
flip execStateT 0 $ do
whileM (liftM (== bufsize) (hGetBuf h buf bufsize)) $ do
do  crc - get
crc' - updateCrc crc buf bufsize
put crc'
crc - get
when (crc == 0) (lift (break crc))

Let's define:

modifyM f = do
x - get
x' - f x
put x'

and change the order of parametrs in updateCrc. We get:

inContT $ callCC $ \break - do
flip execStateT 0 $ do
whileM (liftM (== bufsize) (hGetBuf h buf bufsize)) $ do
modifyM (updateCrc buf bufsize)
crc - get
when (crc == 0) (lift (break crc))
print crc

 how this can be expressed in Haskell, without losing clarity?
 
I think it's quite clear what it does.

  inability is an exaggeration - you can use the ContT monad
  transformer, which even allows you to choose how high you
  want to jump. But you probably already know this and just want to point
  that it is cumbersome?
 
 don't know and don't want to use such a hard way.

I gave an example above. You can break with a return value, so it
seem it's what you want.

 there is a simpler solution, but it still requires to write more
 boilerplate code than C:
 
 res - doSomething
 if isLeft res  then return$ fromLeft res  else do
 let (Right x) = res
 ...

Not simpler, but easier... and uglier. Somehow I don't like to solve
problems on the level of programming language syntax.

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


Re[2]: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-02-01 Thread Bulat Ziganshin
Hello Tomasz,

Thursday, February 1, 2007, 1:15:39 PM, you wrote:

 while (hGetBuf h buf bufsize == bufsize)
   crc := updateCrc crc buf bufsize
   break if crc==0
   print crc

 inContT $ callCC $ \break - do
 flip execStateT 0 $ do
 whileM (liftM (== bufsize) (hGetBuf h buf bufsize)) $ do
 modifyM (updateCrc buf bufsize)
 crc - get
 when (crc == 0) (lift (break crc))
 print crc

 how this can be expressed in Haskell, without losing clarity?
  
 I think it's quite clear what it does.

first. it's longer than original. what we can learn here is that
imperative languages have built-in monadic features support,
including automatic lifting and continuations. OTOH, of course, they
don't support type inference. so in one environment we need to
explicitly declare types while in other environment we need to
explicitly specify lifting operations

second. unfortunately, current Haskell libs defined in terms of IO
monad, not MonadIO. while this issue, i hope, will be addressed in
future, i write programs right now :)

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-02-01 Thread Steve Downey

The 70's and early 80's were very different in terms of information
propagation. I really miss some the journals available back then,
because the editors really did their jobs, both in selecting and
helping to convey, information.
OO did get oversold. The same way that putting it on the internet did
at the beginning of this century (I love saying that, now, where's my
flying car)
but just like many of the good principles of structured programming
inform OO, it should be possible to take good OO and apply it
functionally.

On 1/30/07, Bulat Ziganshin [EMAIL PROTECTED] wrote:

Hello Steve,

Friday, January 26, 2007, 10:03:09 PM, you wrote:

 Haskell _is_ hard, although I don't think it's _too_ hard, or I wouldn't
...

 The audience for programming languages like Haskell is always going to
 be small, because it appeals to those who want to understand how the TV
 works,

i don't think so :)  imho, we just don't have good _teachers_. in
70's, OOP audience was also small, but it was popularized later and
now every student know about polymorphism via inheritance. but most of
OOP programmers don't reinvent the wheels, they just use patterns
described in OOP bestselling books

i have a positive experience of making complex concepts easy and
available for wide audience ([1]-[5]), [1] was even used to teach
students in some college. and i guess that good Haskell books, such as
yaht and printed ones, also make it easy to learn Haskell. but we need
to gather much more attention to Haskell to make it as patternized
as structured-programming and OOP. _nowadays_ there is no even one
advanced Haskell or Haskell in Real World book and this means that
anyone who want to learn Haskell in deep should study those terrible papers

(well, it's very like higher education in Russia - no one really
teaches you at our colleges so you should either learn yourself or die :)
but this means that at least whose who still alive, are Real Machos :)

the same apply to Haskell - now the only way to learn it is to learn
yourself, so we all definitely are cool mans. once i even got C# job
offer only because i know Haskell :)


[1] http://haskell.org/haskellwiki/IO_inside
http://haskell.org/haskellwiki/OOP_vs_type_classes
http://haskell.org/haskellwiki/Modern_array_libraries
http://haskell.org/bz/th3.htm
http://haskell.org/bz/thdoc.htm

--
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
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] Channel9 Interview: Software Composability and the Future of Languages

2007-01-31 Thread Neil Bartlett
 C# [..] has all the problems of language created by committee

Whereas Haskell has all the benefits of a language created by committee!
Actually, wasn't C# largely created by one man, Anders Hejlsberg?

- Neil

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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-01-31 Thread Tomasz Zielonka
On Wed, Jan 31, 2007 at 02:46:27AM +0300, Bulat Ziganshin wrote:
 2. it bites me too. it's why i say that C++ is better imperative
 language than Haskell.

 there are also many other similar issues, such as lack of good syntax
 for for, while, break and other well-known statements,

On the other hand you have an ability to define your own control
structures.

 inability to use return inside of block and so on

inability is an exaggeration - you can use the ContT monad
transformer, which even allows you to choose how high you
want to jump. But you probably already know this and just want to point
that it is cumbersome?

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


Re[2]: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-01-31 Thread Bulat Ziganshin
Hello Neil,

Wednesday, January 31, 2007, 11:09:06 AM, you wrote:

 C# [..] has all the problems of language created by committee

 Whereas Haskell has all the benefits of a language created by committee!
 Actually, wasn't C# largely created by one man, Anders Hejlsberg?

C# 1.0 may be nice language. but since then he has borrowed features
here and there. it's like Ocaml that tries to join FP and OOP together

Haskell suffers from committee problem in his extensions. for
example, declaration styles for regular data and GADTs are
different, because peoples creating first and second had different
stylistic preferences

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-01-31 Thread Bulat Ziganshin
Hello Tomasz,

Wednesday, January 31, 2007, 12:01:16 PM, you wrote:

 there are also many other similar issues, such as lack of good syntax
 for for, while, break and other well-known statements,

 On the other hand you have an ability to define your own control
 structures.

i have a lot, but their features are limited, both in terms of
automatic lifting and overall syntax. let's consider

while (hGetBuf h buf bufsize == bufsize)
  crc := updateCrc crc buf bufsize
  break if crc==0
  print crc

how this can be expressed in Haskell, without losing clarity?

 inability to use return inside of block and so on

 inability is an exaggeration - you can use the ContT monad
 transformer, which even allows you to choose how high you
 want to jump. But you probably already know this and just want to point
 that it is cumbersome?

don't know and don't want to use such a hard way. there is a simpler
solution, but it still requires to write more boilerplate code than C:

res - doSomething
if isLeft res  then return$ fromLeft res  else do
let (Right x) = res
...



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-01-30 Thread Bulat Ziganshin
Hello Neil,

Friday, January 26, 2007, 8:13:43 PM, you wrote:

 evolution of programming languages. In particular they identify
 composability, concurrency and FP as being important trends. However their
 focus is on borrowing features of FP and bringing them into mainstream
 imperative languages; principally C#.

afaik, C# borrows one feature after another from FP world - it has
limited type inference, anonymous functions, lazy evaluation (or not?)

it is why i prefer C# to Java (if i will ever use one of these) - Java
don't changed so radically. but really i don't tried C# yet and expect
that it has all the problems of language created by committee - it
combines features from many different worlds and should be hard to
master and it should be hard to use various-worlds features together

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-01-30 Thread Bulat Ziganshin
Hello Tim,

Saturday, January 27, 2007, 6:14:01 AM, you wrote:

 He brings up a very good point.  Using a monad lets you deal with
 side effects but also forces the programmer to specify an exact
 ordering.

1. it's just a *syntax* issue. at least, ML's solution can be applied:

x - .y + .z

where . is an explicit dereferencing operator (readIORef)

2. it bites me too. it's why i say that C++ is better imperative
language than Haskell. there are also many other similar issues, such
as lack of good syntax for for, while, break and other
well-known statements, inability to use return inside of block and
so on


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-01-30 Thread Bulat Ziganshin
Hello Tim,

Saturday, January 27, 2007, 10:23:31 PM, you wrote:

 Humm.  While I can accept that this is a valid criticism of Haskell's monadic
 structure for dealing with I/O, I fail to see how it could drive a decision
 to prefer an imperative language like C#, where every statement has this
 property (overspecification of evaluation order).

 True.. perhaps his objection was related to having a bulky syntax (one

on *practice*, C++ compilers can reorder statements. are this true for
Haskell compilers?


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-01-30 Thread Robert Dockins
On Tuesday 30 January 2007 19:02, Bulat Ziganshin wrote:
 Hello Tim,

 Saturday, January 27, 2007, 10:23:31 PM, you wrote:
  Humm.  While I can accept that this is a valid criticism of Haskell's
  monadic structure for dealing with I/O, I fail to see how it could drive
  a decision to prefer an imperative language like C#, where every
  statement has this property (overspecification of evaluation order).
 
  True.. perhaps his objection was related to having a bulky syntax (one

 on *practice*, C++ compilers can reorder statements. are this true for
 Haskell compilers?

Well... I think most reordering occurs very late in the process, during 
instruction selection.  These reorderings are very fine-grained, very local 
in scope and are really only (supposed to be!) done when the reordering can 
be shown to have no affect on the outcome of the computation.  I'd be very 
surprised to see a C or C++ compiler reordering something like function 
calls.  (Although, with gcc I believe there's a flag where you can explicitly 
mark a function as being side-effect free.  I can see a compiler perhaps 
moving calls to such functions around.  But really, how's that any better 
than what we've got in Haskell?).

Caveat: I have only a passing knowledge of the black art of C/C++ compiler 
construction, so I could be wrong.


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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-01-27 Thread Jacques Carette

Tim Newsham wrote:

 I have to write:

   do {
  x - getSomeNum
  y - anotherWayToGetANum
  return (x + y)
   }

even if the computation of x and y are completely independant of
each other.


I too have really missed a parallel composition operator to do 
something like the above.  Something like


do {
   { x - getSomeNum || y - anotherWayToGetANum}
   return (x+y)
}

Actually, that syntax is rather hideous.  What I would _really_ like to 
write is

do {
   (x,y) - getSomeNum || anotherWayToGetANum
   return (x+y)
}

I would be happy to tell Haskell explicitly that my computations are 
independent (like the above), to expose parallelization opportunities.  
Right now, not only can I NOT do that, I am forced to do the exact 
opposite, and FORCE sequentiality.


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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-01-27 Thread Chris Kuklewicz
Jacques Carette wrote:
 Tim Newsham wrote:
  I have to write:

do {
   x - getSomeNum
   y - anotherWayToGetANum
   return (x + y)
}

 even if the computation of x and y are completely independant of
 each other.
 
 I too have really missed a parallel composition operator to do
 something like the above.  Something like
 
 do {
{ x - getSomeNum || y - anotherWayToGetANum}
return (x+y)
 }
 
 Actually, that syntax is rather hideous.  What I would _really_ like to
 write is
 do {
(x,y) - getSomeNum || anotherWayToGetANum
return (x+y)
 }
 
 I would be happy to tell Haskell explicitly that my computations are
 independent (like the above), to expose parallelization opportunities. 
 Right now, not only can I NOT do that, I am forced to do the exact
 opposite, and FORCE sequentiality.
 
 Jacques

What is wanted is a specific relation of the ordering required by the Monad's
structure.  For pure computation Control.Parallel.Strategies may be helpful.  If
what was wanted was to keep sequencing but lose binding then the new
Control.Applicative would be useful.

It almost looks like we want your pair combinator:

do { (x,y) - parallelPair getSomeNum anotherWayToGetANum
 return (x+y)
   }

This is principled only in a Monad that can supply the same RealWorld to both
operations passed to parallelPair.  After they execute, this same RealWold is
the context for the return (x+y) statement.

This ability to run three computations from the same RealWorld seems (nearly)
identical to backtracking in a nondeterministic monad, which is usually exposed
by a MonadPlus instance.

The use of pairs looks alot like the arrow notation.  And
parallelPair a b = a  b
looks right for arrows.  And since monads are all arrows this works, but Kleisli
implies ordering like liftM2.

For a specific Monads you can write instances of a new class which approximate
the semantics you want.

 import Control.Arrow
 import Data.Char
 import Control.Monad
 import Control.Monad.State
 import System.IO.Unsafe
 
 type M = State Int
 
 main = print $ runState goPar 65 -- should be ((65,'A'),65)
 
 opA :: (MonadState Int m) = m Int
 opA = do i - get
  put (10+i)
  return i
 
 opB :: (MonadState Int m) = m Char
 opB = do i - get
  put (5+i)
  return (chr i)
 
 goPar :: State Int (Int,Char)
 goPar = opA `parallelPair` opB
 
 class (Monad m) = MonadPar m where
   parallelPair :: m a - m b - m (a,b)
 
 instance MonadPar (State s) where
   parallelPair a b = do s - get
 let a' = evalState a s
 b' = evalState b s
 return (a',b')
 
 -- No obvious way to run the inner monad (without more machinery),
 -- so we have to resort to ordering
 instance (Monad m) = MonadPar (StateT s m) where
   parallelPair a b = do s - get
 a' - lift $ evalStateT a s
 b' - lift $ evalStateT b s
 return (a',b')
 
 -- Reader and Writer work like State
 
 -- Use unsafeInterleaveIO to make a and b lazy and unordered...
 instance MonadPar IO where
   parallelPair a b = do a' - unsafeInterleaveIO a
 b' - unsafeInterleaveIO b
 return (a',b')

 k :: State Int b - Kleisli (State Int) a b
 k op = Kleisli (const op)

 runK :: Kleisli (State Int) a a1 - (a1, Int)
 runK kop = runState (runKleisli kop undefined) 65

 go :: State Int a - (a,Int)
 go op = runK (k op)

 kab :: Kleisli (State Int) a (Int, Char)
 --kab = k opA  k opB
 kab = proc x - do
 a - k opA - x
 b - k opB - x
 returnA - (a,b)


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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-01-27 Thread Robert Dockins
On Friday 26 January 2007 22:14, Tim Newsham wrote:
  impractical language, only useful for research. Erik Meijer at one point
  states that programming in Haskell is too hard and compares it to
  assembly programming!

 He brings up a very good point.  Using a monad lets you deal with
 side effects but also forces the programmer to specify an exact
 ordering.  This *is* a bit like making me write assembly language

 programming.  I have to write:
 do {
x - getSomeNum
y - anotherWayToGetANum
return (x + y)
 }

 even if the computation of x and y are completely independant of
 each other.  Yes, I can use liftM2 to hide the extra work (or
 fmap) but I had to artificially impose an order on the computation.
 I, the programmer, had to pick an order.

Humm.  While I can accept that this is a valid criticism of Haskell's monadic 
structure for dealing with I/O, I fail to see how it could drive a decision 
to prefer an imperative language like C#, where every statement has this 
property (overspecification of evaluation order).  The only mainstream-ish 
general-purpose language I know of that I know of that attempts to addresses 
this problem head-on is Fortress.  (Although, to be honest, I don't know 
enough about Fortress to know how it handles I/O to even know if it is an 
actual improvement over the situation in Haskell.)


 Ok, maybe assembly language is a bit extreme (I get naming, allocation
 and garbage collection!) but it is primitive and overspecifies the
 problem.

 Tim Newsham
 http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-01-27 Thread Tim Newsham

Humm.  While I can accept that this is a valid criticism of Haskell's monadic
structure for dealing with I/O, I fail to see how it could drive a decision
to prefer an imperative language like C#, where every statement has this
property (overspecification of evaluation order).


True.. perhaps his objection was related to having a bulky syntax (one 
line per action, if one is not using a higher order function to combine 
actions) rather than having an order of evaluation rule in the language

and letting the programmer (mostly) ignore it (sometime to is own
peril).

Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-01-26 Thread Neil Bartlett
No doubt many of you will have seen the interview[1] on Channel9 with
Anders Hejlsberg, Herb Sutter, Erik Meijer and Brian Beckman. These are
some of Microsoft's top language gurus, and they discuss the future
evolution of programming languages. In particular they identify
composability, concurrency and FP as being important trends. However their
focus is on borrowing features of FP and bringing them into mainstream
imperative languages; principally C#.

Naturally the subject of Haskell comes up repeatedly throughout the
interview. Disappointingly they characterize Haskell as being an
impractical language, only useful for research. Erik Meijer at one point
states that programming in Haskell is too hard and compares it to assembly
programming! Yet the interviewees continually opine on the difficulty of
creating higher level abstractions when you can never be sure that a
particular block of imperative code is free of side effects. If there were
ever a case of the answer staring somebody in the face...

I found this interview fascinating but also exasperating. It's a real
shame that no reference was made to STM in Haskell. I don't know why the
interviewer doesn't even refer to the earlier Channel9 interview with
Simon Peyton Jones and Tim Harris - it appears to be the same interviewer.
Still, it's nice to see that ideas from Haskell specifically and FP
generally are gaining more and more ground in the mainstream programming
world. It also highlights some of the misconceptions that still exist and
need to be challenged, e.g. the idea that Haskell is too hard or is
impractical for real work.

[1] http://channel9.msdn.com/Showpost.aspx?postid=273697


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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-01-26 Thread Tim Newsham

impractical language, only useful for research. Erik Meijer at one point
states that programming in Haskell is too hard and compares it to assembly
programming!


He brings up a very good point.  Using a monad lets you deal with
side effects but also forces the programmer to specify an exact
ordering.  This *is* a bit like making me write assembly language
programming.  I have to write:

   do {
  x - getSomeNum
  y - anotherWayToGetANum
  return (x + y)
   }

even if the computation of x and y are completely independant of
each other.  Yes, I can use liftM2 to hide the extra work (or
fmap) but I had to artificially impose an order on the computation.
I, the programmer, had to pick an order.

Ok, maybe assembly language is a bit extreme (I get naming, allocation
and garbage collection!) but it is primitive and overspecifies the
problem.

Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe