Re: [Haskell-cafe] Trapped by the Monads

2005-09-21 Thread Ketil Malde
Bill Wood [EMAIL PROTECTED] writes:

 The variable mem is a so-called hybrid variable; it crunches
 together 2 different concepts: a boolean value (could I allocate
 memory?) and an address value (what is the address where I can find
 my allocated memory).

IMO, Maybe is exactly the oppsite, it extends a data type with a NULL
value (to use DB terminology), and leaves no opportunity for confusing
the extended type with the original.

 I mostly agree with the tightening-up, but there are times when I
 really miss the nil hacks :-)

In Haskell as well?  I alwasy felt the cost of inserting a null
predicate (when I want to test for an empty list) to be low.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] Trapped by the Monads

2005-09-20 Thread Neil Mitchell
Take a look at unsafePerformIO, it is of type IO a - a. Its not
particularly safe (the name gives a clue), but it does what you
want.

On 9/20/05, Mark Carter [EMAIL PROTECTED] wrote:
 I'm puzzling out how to get a Bool from am IO Bool. I know I'm not
 supposed to, but I don't see any way around my predicament.
 
 The basic setup is: I have an edit box, and a panel. If you click the
 LMB on the panel when the edit box is checked, this means you want to
 move a graphical object around the panel. If it is unchecked, then
 clicking the LMB means you want to add a graphical object.
 
 The relevant bits I've managed to put together so far are:
 
 mainFrame = do -- main application frame
 streams - varCreate []
...
 cbEdit - checkBox p1 [text := Edit Mode,  on command ::=
 onCbEdit textlog] -- p1 is the panel, ignore textlog
 let isEditing =  get cbEdit checked -- returns type IO Bool
 windowOnMouse p False {- no motion events -} (onMouse p streams
 isEditing)
...
   where
 onMouse w streams isEditChecked mouse
 = case mouse of
 MouseLeftDown pt mods  -
 if isEditChecked then
 findStream w streams pt
 else
 addStream w streams pt
 other  - skipCurrentEvent  --
 unprocessed event: send up the window chain
 
 where
  -- define findStream and addStream
 
 The problem is that isEditChecked is of type IO Bool, not Bool. I
 presume that I should actually be taking a different (non-imperative)
 approach, and I'm wondering if anyone could suggest what that approach
 should be? Many apologies for being a clueless n00b.
 
 
 
 
 ___
 Yahoo! Messenger - NEW crystal clear PC to PC calling worldwide with 
 voicemail http://uk.messenger.yahoo.com
 ___
 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] Trapped by the Monads

2005-09-20 Thread robert dockins


Mark Carter wrote:
I'm puzzling out how to get a Bool from am IO Bool. I know I'm not 
supposed to, but I don't see any way around my predicament.


The basic setup is: I have an edit box, and a panel. If you click the 
LMB on the panel when the edit box is checked, this means you want to 
move a graphical object around the panel. If it is unchecked, then 
clicking the LMB means you want to add a graphical object.


The relevant bits I've managed to put together so far are:

mainFrame = do -- main application frame
   streams - varCreate []
  ...
   cbEdit - checkBox p1 [text := Edit Mode,  on command ::=  onCbEdit 
textlog] -- p1 is the panel, ignore textlog

   let isEditing =  get cbEdit checked -- returns type IO Bool
   windowOnMouse p False {- no motion events -} (onMouse p streams  
isEditing)

  ...
 where
   onMouse w streams isEditChecked mouse  = case mouse of
   MouseLeftDown pt mods  -
   if isEditChecked then
   findStream w streams pt
   else
   addStream w streams pt
   other  - skipCurrentEvent  -- 
unprocessed event: send up the window chain


   where
-- define findStream and addStream

The problem is that isEditChecked is of type IO Bool, not Bool. I 
presume that I should actually be taking a different (non-imperative) 
approach, and I'm wondering if anyone could suggest what that approach 
should be? Many apologies for being a clueless n00b.


Well, your onMouse function is acutally in the IO monad, so you can just 
use the do notation.  You can also get rid of the case, like so:


 onMouse w streams isEditChecked (MouseLeftDown pt mods) =
  do ec - isEditChecked
 if ec then ... else ...

 onMouse _ _ _ _ = skipCurrentEvent

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


Re: [Haskell-cafe] Trapped by the Monads

2005-09-20 Thread Piyush P Kurur
On Tue, Sep 20, 2005 at 04:30:25PM +0100, Neil Mitchell wrote:
 Take a look at unsafePerformIO, it is of type IO a - a. Its not
 particularly safe (the name gives a clue), but it does what you
 want.
 
I dont think you would ever need to do unsafePerformIO unless
you are writing some lib calls or some such thing

  onMouse w streams isEditChecked mouse
  = case mouse of
  MouseLeftDown pt mods  -
  if isEditChecked then
  findStream w streams pt
  else
  addStream w streams pt
  other  - skipCurrentEvent  --

In your case the approach should be some thing along these lines


onMouse w streams isEditChecked mouse
= do
ischecked - isEditChecked
case mouse of
if ischecked then   
findStream w streams pt
...


I am assuming that findStream w streams pt is of type  IO a for
some a. otherwise you might have to use something like 

return $ findStream w streams pt

Also the function onMouse will return some IO something. Remember there is
no real reason to use unsafePerformIO unless you are writing  some new 
IO library call.


ppk

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


Re: [Haskell-cafe] Trapped by the Monads

2005-09-20 Thread Mark Carter

Greg Buchholz wrote:


   Have you read...
   
   http://haskell.org/hawiki/ThatAnnoyingIoType


 

Thanks. I'll take a look at it. I also need to take a look at the basic 
Haskell syntax. An interesting-looking web page which discusses monads is:

http://www.nomaware.com/monads/html/analogy.html

What struck me was this bit of code:

assemblyLine w = (return w) = makeChopsticks = polishChopsticks = 
wrapChopsticks


Interestingly, this looks like Forth (!), where you put a value on the 
stack, and successive operations fiddle with the stack as a series of 
transformations. Not that I know Forth, you understand. Hmm, so Haskell 
can be a concatenative language if you want it to be.







___ 
Yahoo! Messenger - NEW crystal clear PC to PC calling worldwide with voicemail http://uk.messenger.yahoo.com

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


Re: [Haskell-cafe] Trapped by the Monads

2005-09-20 Thread Mark Carter

Mark Carter wrote:


What struck me was this bit of code:

assemblyLine w = (return w) = makeChopsticks = polishChopsticks 
= wrapChopsticks



Interestingly, this looks like Forth (!), where you put a value on the 
stack, and successive operations fiddle with the stack as a series of 
transformations. Not that I know Forth, you understand. Hmm, so 
Haskell can be a concatenative language if you want it to be.


Another thing I noticed in my nano-experience of Haskell is the Maybe 
monad. This is interesting because it's a bit like a hybrid variables. 
If you look at a book like Writing Solid Code (or is it Code 
Complete, I can't remember now) which examine C style, they basically 
scorn the use of hybrid variables. However, I read in something like 
Thinking Forth (or maybe it was just a comment I saw atrributed to 
Charles Moore, the inventor of Forth), who actually advocated hybrid 
variables.


It would be interesting to see how far the notion of Haskell as Forth 
can go. Can Haskell make a better Forth than Forth can, or does it miss 
some things which are quite natural in Forth.




___ 
How much free photo storage do you get? Store your holiday 
snaps for FREE with Yahoo! Photos http://uk.photos.yahoo.com

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


Re: [Haskell-cafe] Trapped by the Monads

2005-09-20 Thread Bill Wood
   . . .
 What struck me was this bit of code:
 
 assemblyLine w = (return w) = makeChopsticks = polishChopsticks = 
 wrapChopsticks
 
 
 Interestingly, this looks like Forth (!), where you put a value on the 
 stack, and successive operations fiddle with the stack as a series of 
 transformations. Not that I know Forth, you understand. Hmm, so Haskell 
 can be a concatenative language if you want it to be.

Some time ago I had occasion to model a special-purpose machine in SML,
and the potential users wanted a programmatic interface that looked like
an assembly language for the machine.  I modeled the instructions as
curried functions with the machine state as the last parameter and
return value, and defined a reverse compose function -- (f  g) x ===
g (f x).  This allowed me to write programs with op codes and parameters
running down the page, just like real assembler (I tabbed over to place
the  so they kinda hung out in the comment area so as not to spoil
the illusion).  It was a quick 'n dirty hack that turned out to be
pretty slick.

 -- Bill Wood
[EMAIL PROTECTED]




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


Re: [Haskell-cafe] Trapped by the Monads

2005-09-20 Thread Bill Wood
   . . .
 Another thing I noticed in my nano-experience of Haskell is the Maybe 
 monad. This is interesting because it's a bit like a hybrid variables. 
 If you look at a book like Writing Solid Code (or is it Code 
 Complete, I can't remember now) which examine C style, they basically 
 scorn the use of hybrid variables. However, I read in something like 
 Thinking Forth (or maybe it was just a comment I saw atrributed to 
 Charles Moore, the inventor of Forth), who actually advocated hybrid 
 variables.

Could you briefly elaborate on what you mean by hybrid variables?

 It would be interesting to see how far the notion of Haskell as Forth 
 can go. Can Haskell make a better Forth than Forth can, or does it miss 
 some things which are quite natural in Forth.

I've always thought that there was a pretty natural correspondence
between Forth and FLs (functional languages); words that pop args from
the stack, compute, and push the results correspond to pure code, and
words that do IO, fetch and assign variables, etc. correspond to the
imperative code.

The facts that 1) the innards of the Forth machine are exposed to the
programmer and 2) that everything in Forth is a word make seamless
language extension easy; I don't think the same can be said for FLs.

On the other hand, recursion is difficult in Forth, and
interpretation-as-you-read make higher-order functions difficult (I
never saw any serious attempts at HOFs).

I suspect it's a levels-of-abstraction thing; after all, the Forth
environment could be viewed as the ideal stack machine upon which to
implement FLs and block-structured languages.

 -- Bill Wood
[EMAIL PROTECTED]


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


Re: [Haskell-cafe] Trapped by the Monads

2005-09-20 Thread Lennart Augustsson

Mark Carter wrote:

The typical example in C is:
mem = malloc(1024)
Malloc returns 0 to indicate that memory cannot be allocated, or a 
memory address if it can. The variable mem is a so-called hybrid 
variable; it crunches together 2 different concepts: a boolean value 
(could I allocate memory?) and an address value (what is the address 
where I can find my allocated memory).


It's considered a bad idea because it makes it easy for programmers to 
use the value inappropriately - witness the number of programmers who 
pass in 0 as a memory location. 


This is a bad idea in C, because you cannot force programmers to test
the return value properly.

The Maybe type in Haskell is a good idea, because you must test the
a Maybe value to extract the real value.  (Using the Maybe monad this
can be hidden.)

-- Lennart

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


Re: [Haskell-cafe] Trapped by the Monads

2005-09-20 Thread Bill Wood
   . . .
 The typical example in C is:
  mem = malloc(1024)
 Malloc returns 0 to indicate that memory cannot be allocated, or a 
 memory address if it can. The variable mem is a so-called hybrid 
 variable; it crunches together 2 different concepts: a boolean value 
 (could I allocate memory?) and an address value (what is the address 
 where I can find my allocated memory).

An infamous example would be the convention in Common Lisp that nil, the
empty list, is also false for conditionals while anything else is
true for conditionals.  So the member function ('a * ['a] - ['a]) can
be used either as a predicate or a function returning a useful value.

 It's considered a bad idea because it makes it easy for programmers to 
 use the value inappropriately - witness the number of programmers who 
 pass in 0 as a memory location. The suggested solution is to give each 

And the Scheme community chose #f and #t for boolean values so you
had to be a little more explicit about what you were doing.

I mostly agree with the tightening-up, but there are times when I
really miss the nil hacks :-)

 -- Bill Wood
[EMAIL PROTECTED]


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


Re: [Haskell-cafe] Trapped by the Monads

2005-09-20 Thread Mark Carter

Lennart Augustsson wrote:


Mark Carter wrote:


The typical example in C is:
mem = malloc(1024)
Malloc returns 0 to indicate that memory cannot be allocated, or a 
memory address if it can. The variable mem is a so-called hybrid 
variable; it crunches together 2 different concepts: a boolean value 
(could I allocate memory?) and an address value (what is the address 
where I can find my allocated memory).


It's considered a bad idea because it makes it easy for programmers 
to use the value inappropriately - witness the number of programmers 
who pass in 0 as a memory location. 



This is a bad idea in C, because you cannot force programmers to test
the return value properly.

The Maybe type in Haskell is a good idea, because you must test the
a Maybe value to extract the real value.  (Using the Maybe monad this
can be hidden.)


Yes, I didn't mean to imply that Haskell had got its ideas fundamentally 
wrong. I think that the main thrust of the argument is that in something 
like C, hybrid variables make it easy for a programmer to inadvertently 
use them wrongly, as opposed to just be lazy. I suppose there's some 
element of debate on the matter: for example, what C programmer doesn't 
honestly know that memory allocation can fail. And for an unfamiliar 
function, why doesn't the programmer read the documentation to find out 
what constitutes valid and invalid return values.


OTOH, I think Charles Moore is quoted as saying that if he want to add 1 
to the letter A, then he didn't want the programming language to stop 
him. Which is quite a contrast to Haskell and its notions on safety. I'm 
not flamebaiting, you understand, I'm just pointing out the various 
viewpoints to the argument.





___ 
How much free photo storage do you get? Store your holiday 
snaps for FREE with Yahoo! Photos http://uk.photos.yahoo.com

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


Re: [Haskell-cafe] Trapped by the Monads

2005-09-20 Thread Michael Walter
Compare:

  int *p=...;
  int x=*p;

and:

  let
p = ...
Just x = p

So actually, there is few difference between dereferencing a pointer
without checking for 0, and extracting the Maybe value without
handling Nothing, apart from that it leads to undefined behavior in C
which in fact isn't really a point against hybrid variables.

On 9/20/05, Lennart Augustsson [EMAIL PROTECTED] wrote:
 Mark Carter wrote:
  The typical example in C is:
  mem = malloc(1024)
  Malloc returns 0 to indicate that memory cannot be allocated, or a
  memory address if it can. The variable mem is a so-called hybrid
  variable; it crunches together 2 different concepts: a boolean value
  (could I allocate memory?) and an address value (what is the address
  where I can find my allocated memory).
 
  It's considered a bad idea because it makes it easy for programmers to
  use the value inappropriately - witness the number of programmers who
  pass in 0 as a memory location.
 
 This is a bad idea in C, because you cannot force programmers to test
 the return value properly.
 
 The Maybe type in Haskell is a good idea, because you must test the
 a Maybe value to extract the real value.  (Using the Maybe monad this
 can be hidden.)
 
 -- Lennart
 
 ___
 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] Trapped by the Monads

2005-09-20 Thread Greg Buchholz
Mark Carter wrote:
 What struck me was this bit of code:
 
 assemblyLine w = (return w) = makeChopsticks = polishChopsticks = 
 wrapChopsticks
 
 
 Interestingly, this looks like Forth (!), where you put a value on the 
 stack, and successive operations fiddle with the stack as a series of 
 transformations. Not that I know Forth, you understand. Hmm, so Haskell 
 can be a concatenative language if you want it to be.


  You might also like take a look the Joy language...

http://www.latrobe.edu.au/philosophy/phimvt/joy.html

...sort of a functional, higher level cousin of Forth.  In Joy, you
create programs by composing functions with other functions.  This is in
contrast to other languages where functions are mainly applied to other
functions (and data).  The composition operator Joy is denoted by white
space.  This is similar to the way juxtaposition is used to denote
function application in more conventional languages.  (i.e., in Joy f
g means g composed with f, while in other languages f(g) means
apply function f to argument g).  Now, what if we had a name for
this implicit composition operation?  We could then modify it to do a
whole host of other things with the functions f and g besides just
the boring old composition (like maybe skipping the execution of g if
f fails, or allowing backtracking, or something more bizarre and
clever).  And what should we name this new super composition operator?
= maybe?  Ah... 


Greg Buchholz

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


Re: [Haskell-cafe] Trapped by the Monads

2005-09-20 Thread Glynn Clements

Mark Carter wrote:

  Could you briefly elaborate on what you mean by hybrid variables?
 
 According to Google, hybrid in genetics means The offspring of 
 genetically dissimilar parents or stock, especially the offspring 
 produced by breeding plants or animals of different varieties, species, 
 or races. It's kind of like that - but for variables.
 
 The typical example in C is:
  mem = malloc(1024)
 Malloc returns 0 to indicate that memory cannot be allocated, or a 
 memory address if it can. The variable mem is a so-called hybrid 
 variable; it crunches together 2 different concepts: a boolean value 
 (could I allocate memory?) and an address value (what is the address 
 where I can find my allocated memory).

Well in that case, Maybe provides the perfect example of how to
implement hybrid variables correctly.

The types Ptr a and Maybe (Ptr a) are distinct. If you try to pass
the latter to a function which expects the former, you'll get a
compile-time error. You first have to extract the underlying value,
which means that you need to match against (Just x). If the wrapped
value is Nothing, you'll get an exception. Furthermore, if you forget
to handle the Nothing case, you'll get a compile-time warning.

In C, there's no way to distinguish (using the type system) between a
possibly-null pointer and a non-null pointer. Using a pair of a
boolean and a pointer is the wrong approach because the pointer is
meaningless if the boolean is false, but the type system won't prevent
you from using the value of the pointer in that case.

A more general example is structures where certain fields are only
valid in certain circumstances (e.g. depending upon the type field). 
Haskell-style sum types, (of which Maybe is an example) are a much
better solution, as the the fields only exist when they are
meaningful.

-- 
Glynn Clements [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trapped by the Monads

2005-09-20 Thread Lennart Augustsson

There's a big difference.
You can see you are doing something fishy, and the compiler
can too, and it can warn you.

-- Lennart

Michael Walter wrote:

Compare:

  int *p=...;
  int x=*p;

and:

  let
p = ...
Just x = p

So actually, there is few difference between dereferencing a pointer
without checking for 0, and extracting the Maybe value without
handling Nothing, apart from that it leads to undefined behavior in C
which in fact isn't really a point against hybrid variables.

On 9/20/05, Lennart Augustsson [EMAIL PROTECTED] wrote:


Mark Carter wrote:


The typical example in C is:
mem = malloc(1024)
Malloc returns 0 to indicate that memory cannot be allocated, or a
memory address if it can. The variable mem is a so-called hybrid
variable; it crunches together 2 different concepts: a boolean value
(could I allocate memory?) and an address value (what is the address
where I can find my allocated memory).

It's considered a bad idea because it makes it easy for programmers to
use the value inappropriately - witness the number of programmers who
pass in 0 as a memory location.


This is a bad idea in C, because you cannot force programmers to test
the return value properly.

The Maybe type in Haskell is a good idea, because you must test the
a Maybe value to extract the real value.  (Using the Maybe monad this
can be hidden.)

   -- Lennart

___
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