Re: IO behaves oddly if used nested

2003-10-04 Thread Alastair Reid

 The odd is in the conceptual explanation. If I give a description of some f
 x = y function in Haskell I expect that some program f x is reduced to y
 and the result is given back (possibly printed). A good story to sell to
 students.

This is true of IO as well.

The bit that's tripping up your students is the question of what an object of 
type 'IO Int' is.  It sound like they think it is the same as Int.  But this 
isn't so - no more than an object of type [Int] or 'Maybe Int' is the same as 
an Int.

It sounds like you're trying to make that distinction when you talk about the 
'Nomad' datatype but you have to be careful to keep on making that 
distinction every time you talk about monads and be careful to distinguish 'a 
value of type t' from 'a computation which returns a value of type t' or, at 
least, keep making that distinction until after your audience fully 
appreciates the distinction and can handle more informal explanations.

Once they get round the idea that 'IO Int /= Int', surely it is reasonable to 
accept that '1' and 'return 1' might be printed in different ways?

And if you've previously shown them that 'show id' produces a fairly 
uninformative result, maybe they can accept that 'show (do{c - getChar; 
putChar c})' produces a similarly uninformative result?

You might also try to warm students up to the issues by having them think 
about what (incorrectly typed) expressions like:

  ord getChar + ord getChar

or

  (getChar, getChar)

or

  let f x = do{ print x; return (x+1) }
  in drop 3 [ f i | i - [1..10] ]

might do under different evaluation orders.  Understanding the problem makes 
it clearer why we want 'IO Int' /= 'Int'.


 * Why is an IO a evaluated if I am not interested in it's result? (opposite
 to the f x = y lazy behavior)

You are interested in its result though.

If you recall my example of mailing an order for socks to a clothing company, 
evaluating a value of type 'IO Int' corresponds to opening the envelope 
containing the order.

Opening the envelope does not, in itself, lead to socks being sent.  For  
example, they may decide to discard the first 3 valid orders they receive 
each day or they may reject orders from people with a 'b' in their name.  It 
is only when they decide to execute the order than the socks get sent.


 * Why is in the putStr hello world example Hello World not shown?
 (opposite to expected f x = y eval-first-then-show behavior)

For the same reason that my feet get cold and ink-stained if I wear orders for 
socks instead of wearing socks.

The value 'putStr hello world' is a computation which will print hello 
world when you execute it.  Evaluating the computation is not the same as 
executing it.

 * Why is in the IO (IO ()) example the inner IO () not evaluated? (somewhat
 opposite to expected f (f x) behavior - I personally wonder if it is even
 sound in a category theoretical setting)

It _is_ evaluated.

But evaluating a value is not the same as executing it just as opening an 
order is not the same as obeying instructions in the order.


 A nice (old) idea would be to represent
 IO as programs which are interpreted by some _outside_ RTS in a given
 manner, and leave the Haskell language clean.
 (It might even be a good idea with respect to the compiler implementation
 since it removes checking against unsafe IO behavior from the compiler --
 just a thought)

Haskell used to do this prior to Haskell 1.3.
We moved away from it for two reasons:


1) It was notoriously hard to write correct code using the old interface 
because you had to reason carefully about the order of evaluation of pure 
Haskell code.

2) As specified, it gave us a fixed language in which to express commands and 
responses.  For example, there was no command to open a network connection or 
to draw a circle on a window and no response to say 'the result is this COM 
object'.  IMHO, Haskell would be an interesting but useless academic toy 
without the ability to do things like that.

The first might have been fixable (e.g., Clean provides a non-monadic 
alternative).

The second might also be fixable but I doubt that any useful solution would 
avoid the cleanliness and safety issues you refer to.  The sad truth is that 
as soon as you connect to a world that is not strongly typed (and uses a 
different type system anyway) and doesn't perform any runtime checks to 
compensate, you get corrupted by the a bunch of safety issues.  

--
Alastair Reid www.haskell-consulting.com

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: ANNOUNCE: HaRe, the Haskell Refactorer, version 0.1

2003-10-04 Thread Jens Petersen
On Thu, Oct 02, 2003 at 11:19:47AM +0100, C.Reinke wrote:

 we are pleased to announce the availability of HaRe 0.1 (also 
 known as HaRe 01/10/2003 ;-), a snapshot of our Haskell Refactorer
 prototype.

Thank you - looks pretty nice!
Any chance of XEmacs support too? :-)

Jens
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Type tree traversals [Re: Modeling multiple inheritance]

2003-10-04 Thread oleg

This message illustrates how to get the typechecker to traverse
non-flat, non-linear trees of types in search of a specific type. We
have thus implemented a depth-first tree lookup at the typechecking
time, in the language of classes and instances.

The following test is the best illustration:

 instance HasBarMethod ClassA Bool Bool
 -- Specification of the derivation tree by adjacency lists
 instance SubClass (Object,()) ClassA
 instance SubClass (Object,()) ClassB
 instance SubClass (ClassA,(ClassB,())) ClassCAB
 instance SubClass (ClassB,(ClassA,())) ClassCBA
 instance SubClass (Object,(ClassCBA,(ClassCAB,(Object,() ClassD
 instance SubClass (Object,(ClassB,(ClassD,(Object,() ClassE

 test6::Bool = bar ClassE True

It typechecks. ClassE is not explicitly in the class HasBarMethod. But
the compiler has managed to infer that fact, because ClassE inherits
from ClassD, among other classes, ClassD inherits from ClassCBA, among
others, and ClassCBA has somewhere among its parents ClassA. The
typechecker had to traverse a notable chunk of the derivation tree to
find that ClassA.

Derivation failures are also clearly reported:

 test2::Bool = bar ClassB True
 No instance for (HasBarMethodS () ClassA)
 arising from use of `bar' at /tmp/m1.hs:46
 In the definition of `test2': bar ClassB True


Brandon Michael Moore wrote:
 Your code doesn't quite work. The instances you gave only allow you to
 inherit from the rightmost parent. GHC's inference algorithm seems to pick
 one rule for a goal and try just that. To find instances in the first
 parent and in other parents it needs to try both.

The code below fixes that problem. It does the full traversal. Sorry
for a delay in responding -- it picked a lot of fights with the
typechecker.

BTW, the GHC User Manual states:

However the rules are over-conservative. Two instance declarations can
 overlap, but it can still be clear in particular situations which to use.
 For example:
  
   instance C (Int,a) where ...  
   instance C (a,Bool) where ...
   
 These are rejected by GHC's rules, but it is clear what to do when trying
 to solve the constraint C (Int,Int) because the second instance cannot
 apply. Yell if this restriction bites you.

I would like to quietly mention that the restriction has bitten me
many times during the development of this code. I did survive though.


The code follows. Not surprisingly it looks like a logical program.
Actually it does look like a Prolog code -- modulo the case of the
variables and constants. Also
head :- ant, ant2, ant3
in Prolog is written
instance (ant1, ant2, ant3) = head
in Haskell.

{-# OPTIONS -fglasgow-exts -fallow-overlapping-instances -fallow-undecidable-instances 
#-}

data Object = Object
data ClassA = ClassA
data ClassB = ClassB
data ClassCAB = ClassCAB
data ClassCBA = ClassCBA
data ClassD = ClassD
data ClassE = ClassE

class SubClass super sub | sub - super where
  upCast:: sub - super
  
instance SubClass (Object,()) ClassA
instance SubClass (Object,()) ClassB
instance SubClass (ClassA,(ClassB,())) ClassCAB
instance SubClass (ClassB,(ClassA,())) ClassCBA
instance SubClass (Object,(ClassCBA,(ClassCAB,(Object,() ClassD
-- A quite bushy tree
instance SubClass (Object,(ClassB,(ClassD,(Object,() ClassE


class HasBarMethod cls args result where
  bar ::  cls - args - result
  
instance (SubClass supers sub, 
  HasBarMethodS supers ClassA)
 = HasBarMethod sub args result where
  bar obj args = undefined -- let the JVM bridge handle the upcast

class HasBarMethodS cls c

instance HasBarMethodS (t,x) t
instance (HasBarMethodS cls t) = HasBarMethodS (Object,cls) t
instance (HasBarMethodS cls t) = HasBarMethodS ((),cls) t

instance (SubClass supers c, HasBarMethodS (supers,cls) t) = 
HasBarMethodS (c,cls) t
instance (HasBarMethodS (a,(b,cls)) t) = HasBarMethodS ((a,b),cls) t

instance HasBarMethod ClassA Bool Bool where
  bar _ x = x


test1::Bool = bar ClassA True
--test2::Bool = bar ClassB True


test3::Bool = bar ClassCAB True
test4::Bool = bar ClassCBA True
test5::Bool = bar ClassD True
test6::Bool = bar ClassE True

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


Re: Haskellsupport in KDevelop

2003-10-04 Thread Wolfgang Jeltsch
Am Samstag, 4. Oktober 2003, 19:15 schrieb Peter Robinson:
 Hello,

 I've begun to write a plugin that provides basic support for Haskell in
 KDevelop 3.0 alpha. (http://www.kdevelop.org).

Great! I will probably use it since I like Haskell and KDE very much.

By the way, wasn't KDevelop only for developing in C and C++? Did they move to 
a plugin-based approach which allows support for other programming languages?

 [...]

 Regards,
 Peter

Wolfgang

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


Re: Haskellsupport in KDevelop

2003-10-04 Thread Peter Robinson
On Saturday 04 October 2003 20:20, Wolfgang Jeltsch wrote:
 Great! I will probably use it since I like Haskell and KDE very much.

 By the way, wasn't KDevelop only for developing in C and C++?

The current stable Release 2.1.* is a C/C++ only IDE but the upcoming 3.0 will 
probably support: Ada, Bash, C/C++, Fortran, Java, Pascal, Perl, PHP, Python, 
Ruby, Haskell, SQL

 Did they move
 to a plugin-based approach which allows support for other programming
 languages?

Yes, no other code has to be changed. Language support is plugin/kparts based. 
:-)

Peter


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

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


Re: Why does this work - haskell mysteries?

2003-10-04 Thread Petter Egesund
Thanks,

the Scheme-version made it even clearer!

Cheers,

Petter

On Saturday 04 October 2003 13:53, you wrote:
 On Sun, 5 Oct 2003 11:02:37 +

 Petter Egesund [EMAIL PROTECTED] wrote:
  Hi  thanks for answering.
 
  I think I got it - the chaning of the functions lies in the last part
  of
 
   (\w - if v==w then n else sto w)
 
  I am used to higher ordered functions from Scheme, but it was the
  delayed evaluation which played me the trick here. This function is
  built when updating, and not executed before asking value 'x'?!

 If by delayed evaluation you mean lazy evaluation then that has nothing
 to do with it.  Obviously the function isn't executed before asking the
 value of 'x' because no function can run without it's argument(s). The
 same representation will behave exactly the same in Scheme.

 (define init-store (lambda (key) 0))
 (define (lookup-store store key) (store key))
 (define (update-store store key value)
(lambda (lookup-key)
   (if (equal? key lookup-key)
   value
   (lookup-store store lookup-key

 Obviously, this will make the function taking lookup-key when
 update-store is called (just like Haskell) and (just like Haskell) it
 will only be executed when applied to a key to lookup.

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


Re: Haskellsupport in KDevelop

2003-10-04 Thread Ross Paterson
On Sat, Oct 04, 2003 at 07:15:32PM +0200, Peter Robinson wrote:
 What's really missing is a (primitive) background parser written that reports 
 syntax errors. It can be written in yacc, antlr, etc., anything that produces 
 C/C++ code. The only parsers for Haskell I could find are written themselves 
 in Haskell.
 Does anyone know about one or must I write it from scratch?

There's a yacc parser in Hugs.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Newbie qustion about monads

2003-10-04 Thread Juanma Barranquero
On Thu, 02 Oct 2003 14:57:22 +0200, Juanma Barranquero [EMAIL PROTECTED] wrote:

 data Accum s a = Ac [s] a
 
 instance Monad (Accum s) where
return x  = Ac [] x
Ac s1 x = f = let Ac s2 y = f x in Ac (s1++s2) y
 
 output :: a - Accum a ()
 output x = Ac [x] ()

After trying this one, and also

  output :: a - Accum a a
  output x = Ac [x] x

I though of doing:

  data Accum a = Ac [a] a

because I was going to accumulate a's into the list.

That didn't work; defining = gave an error about the inferred type
being less polymorphic than expected ('a' and 'b' unified, etc.).

After thinking a while, I sort of understood that = is really more
polymorphic, i.e., even if it is constraining [s] to be a list (because
it is using ++), it really is saying nothing about the contents of the
list. It is output who's doing the constraint, but, with the very same
monad, I could do:

  output :: [a] - Accum Int [a]
  output x = Ac [length x] x

or

  output :: a - Accum [a] a
  output x = Ac [[x]] x

or whatever.

But then I wondered, is there any way to really define

  data Accum a = Ac [a] a

i.e., constraining it to use a for both values, and make a monad from it?

Curious,

   Juanma

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