[Haskell-cafe] 2D game graphics library for Haskell?

2007-08-24 Thread peterv
I’m currently playing around with SOE to make some simple interactive math
exercises for students. This worked fine, although I could have done this
much faster using C# (which I know very well), but since I’m addicted to
Haskell now, I used the latter language ;) Furthermore, I hope that one day,
I will know enough Haskell to learn it to the students, because I feel that
functional programming should not be given in the last bachelor or master
years, since most software engineering students then know OO programming
extremely well and have a horrible time with FP (I currently did not meet
anyone in my sector of game development that liked FP, and many of those
people had a masters degree and some were PhDs)

 

Anyway, SOE is great for learning Haskell, but it lacks a couple of
fundamental functions to make it really attractive, like:

 

-Support for images

-Support for rendering to an “offscreen graphics surface” and
reading the pixels from that surface (for pixel-wise collision detection)

-Support for detecting non-ASCII key presses (cursor keys, etc)

-Support for joysticks

 

Concurrent Clean seems to have a nice 2D game library and PLT/DrScheme also
has nice support for basic 2D graphics, but somehow I feel Haskell is more
mature and more elegant. 

 

So before digging into “advanced” APIs (like GTK itself, which I know
nothing about, I’m a Win32 GDI/XNA/WPF expert), I should ask the question if
something similar exists? It has to be as simple as SOE.

 

Would it be possible to extend the GTK SOE with support for the features
mentioned above? Is this insanely difficult for someone like me who knows a
lot about Win32 but little Haskell?

 

Thanks,

Peter Verswyvelen

 


No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.484 / Virus Database: 269.12.4/969 - Release Date: 23/08/2007
16:04
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Explaining monads

2007-08-13 Thread peterv
When I read side-effects, I understand it as unwanted effects, like
aliasing, and effects depending on the order of execution. I'm not sure
if my understanding here is correct. I hope Haskell does not allow
side-effects but only effects, meaning the monads do not allow you to
write the typical ill-behaving code you get when doing real imperative
programming, enforcing a single wiring of execution, not allowing the
capture of the RealWorld object. In Concurrent Clean special compiler
support is present to enforce uniqueness typing, and in Haskell special
compiler support is available to make the RealWorld object not available at
runtime (so e.g. you can't put the RealWorld object in a list). Is this
correct? 

BTW: What is the correct word in Haskell for object? I mean the (lazy)
value you get when evaluating a data constructor? 

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Kim-Ee Yeoh
Sent: Monday, August 13, 2007 15:30
To: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Explaining monads



Ronald Guida wrote:
 
 Given the question What is a Monad, I would have to say A Monad is
 a device for sequencing side-effects.
 

There are side-effects and there are side-effects. If the only
monad you use is Maybe, the only side-effect you get is a slight
warming of the CPU.

Dave Menendez pointed to that fine Wadler link earlier. Please read
it. To wit, in Section 2: Explaining Monads the essence of an
algorithm can become buried under the plumbing required to carry
data from its point of creation to its point of use. Monads can
help keep the clarity of your code untrammelled by providing
implicit plumbing, side-channels if you prefer, when data is
moved around.

In fact if you follow Wadler all the way to his monadic expression
evaluator, you see that you could modularize your code in awesomely
cool ways. You get to see how the kernel of the expression
evaluator could be written for a generic monad and compiled
once-and-for-all. Any additional feature (the variations) is
coded by enriching the monad.

Monads are powerful devices for modularizing code. Available for
free. Only in Haskell (thanks to type classes!). Get them today.

Side-effects is a piece of linguistic cruft played fast-and-loose
by too many people in this game. Sequencing suffers the same 
disease.

-- 
View this message in context:
http://www.nabble.com/Explaining-monads-tf4244948.html#a12126170
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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

No virus found in this incoming message.
Checked by AVG Free Edition. 
Version: 7.5.476 / Virus Database: 269.11.15/949 - Release Date: 12/08/2007
11:03
 

No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.476 / Virus Database: 269.11.15/949 - Release Date: 12/08/2007
11:03
 

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


[Haskell-cafe] Newbie question (again!) about phantom types

2007-08-08 Thread peterv
I’m having difficulty to understand what phantom types are good for. Is this
just for improving runtime performance? 

I read the wiki, and it says this is useful if you want to increase the
type-safety of your code, but the code below does not give a compiler error
for the function test1, I get a runtime error, just like test2.

Thanks,
Peter

-- CODE --
-- With phantom types
data T1 a = TI1 Int | TS1 String deriving Show

foo1 :: T1 String - T1 String - T1 String
foo1 (TS1 x) (TS1 y) = TS1 (x++y)

test1 = foo1 (TI1 1) (TI1 2) -- Shouldn't this give a compiler error instead
of a runtime error? 

-- Without phantom types
data T2 = TI2 Int | TS2 String deriving Show

foo2 :: T2 - T2 - T2
foo2 (TS2 x) (TS2 y) = TS2 (x++y)

test2 = foo2 (TI2 1) (TI2 2)



No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.476 / Virus Database: 269.11.8/941 - Release Date: 07/08/2007
16:06
 

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


RE: [Haskell-cafe] Newbie question (again!) about phantom types

2007-08-08 Thread peterv
Thanks, that is a much clearer explanation than
http://en.wikibooks.org/wiki/Haskell/Phantom_types

Peter

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Arie Peterson
Sent: Wednesday, August 08, 2007 5:59 PM
To: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Newbie question (again!) about phantom types


 I'm having difficulty to understand what phantom types are good for. Is
 this just for improving runtime performance?

No. As the wiki says, you can use them to add static guarantees.

 I read the wiki, and it says this is useful if you want to increase the
 type-safety of your code, but the code below does not give a compiler
 error
 for the function test1, I get a runtime error, just like test2.

It seems you're mixing up GADT's and phantom types.

 -- CODE --
 -- With phantom types
 data T1 a = TI1 Int | TS1 String deriving Show

Here, the 'a' is an extra type parameter, which has no manifestation on
the value level. Note the type of the constructors:

TI1 :: Int - T1 a
TS1 :: String - T1 a

In particular, the 'a' is not related to the 'Int' or 'String' arguments.

 foo1 :: T1 String - T1 String - T1 String
 foo1 (TS1 x) (TS1 y) = TS1 (x++y)

 test1 = foo1 (TI1 1) (TI1 2) -- Shouldn't this give a compiler error
 instead
 of a runtime error?

'TI1 1' has type 'T1 a', so this unifies with 'T1 String' (the type of the
argument of 'foo1'.


The type parameter 'a' can still be useful, but you have to use an
explicit type signature to constrain the type 'a':

ti1 :: Int - T1 Int
ti1 x = TI1 x

Now, 'ti1' will create values with the restricted type 'T1 Int', that you
can't use as arguments for your 'foo1'.


GADTs are perhaps more useful for what you seem to want. Try something
like this:

data T1 :: * - * where -- T1 has one type parameter
  TI1 :: Int - T1 Int
  TS1 :: String - T1 String

Now, the type systems guarantees that all values of the form 'TI1 x' have
type 'T1 Int'.


Greetings,

Arie


___
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] Newbie question: multi-methods in Haskell

2007-08-06 Thread peterv
In de book Modern C++ design, Andrei Alexandrescu writes that Haskell
supports “multi-methods”

http://books.google.com/books?id=aJ1av7UFBPwCpg=PA3ots=YPiJ_nWi6Ydq=moder
n+C%2B%2Bsig=FWO6SVfIrgtCWifj9yYHj3bnplQ#PPA263,M1

How is this actually done in Haskell? Maybe this is just a basic feature of
Haskell which I don't grasp yet because of my object-oriented background?

A good example is collision between pairs of objects of type (a,b). In
object oriented languages this cannot be handled in a nice way, because
neither a.Collide(b) or b.Collide(a) is the correct approach; one would like
to write (a,b).Collide()

A specific example might be better here. 

Assume the following class hierarchy:

Solid
|
+-- Asteroid
|
+-- Planet
|
+ -- Earth
|
+ -- Jupiter

Using multi-methods, I could write (in pseudo code)

collide (Asteroid, Planet) = an asteroid hit a planet
collide (Asteroid, Earth) = the end of the dinos
collide (Solid,Solid) =  solids collided
collide (Planet, Asteroid) = collide (Asteroid, Planet)
collide (Earth, Asteroid)  = collide (Earth, Asteroid)

So basically, the best collide function is picked, depending on the type
of the arguments.

How should I write Haskell code for something like this in general, in the
sense that this hierarchy is typically huge and the matrix (of collide
functions for each pair of types) is very sparse.

Thanks,
Peter




No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.476 / Virus Database: 269.11.6/938 - Release Date: 05/08/2007
16:16
 

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


RE: [Haskell-cafe] Newbie question: multi-methods in Haskell

2007-08-06 Thread peterv
This is very nice, but it does not really solve the original problem.

In your code, evaluating

collide (Jupiter, Asteroid)

will result in an endless loop. This is expected in your code, because no
inheritance relation is present between e.g Jupiter and Planet. With
multi-dispatch, it should pick the best matching collide function based on
inheritance, or raise an error when ambiguous types.

I could fix that be just keeping the leafs (Earth, Jupiter, Asteroid) as
datatypes, and adding type classes for the super classes (Planet, Solid),
like the code below, but I could not check Asteroid-Asteroid collision with
that, GHCi gives an error.

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

module Collide where

class Collide a where
collide :: a - String

data Asteroid = Asteroid
data Jupiter = Jupiter
data Earth = Earth

class IsSolid a
class IsSolid a = IsPlanet a

instance IsSolid Asteroid
instance IsSolid Jupiter
instance IsSolid Earth

instance IsPlanet Earth
instance IsPlanet Jupiter

instance (IsSolid a, IsSolid b) = Collide (a, b) where
collide (x,y) = generic collision

instance (IsPlanet a) = Collide (Asteroid, a) where
collide (x,y) = an asteroid hit a planet

instance (IsPlanet a) = Collide (a, Asteroid) where
collide (x, y) = an asteroid hit a planet

instance Collide (Asteroid, Earth) where
collide (_,_) = the end of the dinos

instance Collide (Earth, Asteroid) where
collide (_,_) = the end of the dinos

-- This is how you get dynamic dispatch in Haskell
data Collision = forall a. Collide a = Collision a

instance Collide Collision where
collide (Collision a) = collide a

ae = collide (Asteroid, Earth)
ea = collide (Earth, Asteroid)
ja = collide (Jupiter, Asteroid)
aj = collide (Asteroid, Jupiter)

-- However, this one gives an error?
--aa = collide (Asteroid, Asteroid)


-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Brian Hulley
Sent: Monday, August 06, 2007 9:15 PM
To: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Newbie question: multi-methods in Haskell

Dan Weston wrote:
 Remember that type classes do not provide object-oriented 
 functionality. The dispatch is static, not dynamic. Although OOP can 
 be simulated in Haskell, it is not a natural idiom. If you need 
 dynamic dispatch (including multiple dispatch), you may want to 
 reconsider your solution.
Dynamic dispatch is easily added to Haskell code by using an existential 
to represent any collision:

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

module Collide where

-- Changed to a single param to make life easier...
class Collide a where
collide :: a - String

data Solid = Solid
data Asteroid = Asteroid
data Planet = Planet
data Jupiter = Jupiter
data Earth = Earth

instance Collide (Asteroid, Planet) where
collide (Asteroid, Planet) = an asteroid hit a planet

instance Collide (Asteroid, Earth) where
collide (Asteroid, Earth) = the end of the dinos

-- Needs overlapping and undecidable instances
instance Collide (a, b) = Collide (b, a) where
collide (a,b) = collide (b, a)

-- This is how you get dynamic dispatch in Haskell
data Collision = forall a. Collide a = Collision a

instance Collide Collision where
collide (Collision a) = collide a

-- ghci output
*Collide let ae = Collision (Asteroid, Earth)
*Collide let pa = Collision (Planet, Asteroid)
*Collide collide ae
the end of the dinos
*Collide collide pa
an asteroid hit a planet
*Collide map collide [ae, pa]
[the end of the dinos,an asteroid hit a planet]


Best regards, Brian.
___
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


FW: RE [Haskell-cafe] Monad Description For Imperative Programmer

2007-08-01 Thread peterv
Kaveh A monad is like a loop that can run a new function against its variable 
in each iteration. 

I’m an imperative programmer learning Haskell, so I’m a newbie, but I’ll give 
it a try ☺ Making mistakes is the best way to learn it ;)

There are lots of different kinds of monads, but let’s stick to the IO monad 
first, which you seem to refer to.

No *an IO monad is not a loop at all*. Instead, from an imperative programmer’s 
point of view, the following might be better:

“an IO monad is a delayed action that will be executed as soon as that action 
is needed for further evaluation of the program.”

The simple program

main = getLine = putStrLn 

can be visually represented as (see attachment)

The “world” (=a representation of your computer’s hardware) is passed to the 
main function, which passes it to all actions that it encounters during its 
lazy evaluation, causing the executing of the actions as an effect. 

The red wire through which the “world flows” is a “single thread”, it cannot be 
split (because the physical world cannot be copied!!!), so no unwanted side 
effects can ever occur, making IO safe in Haskell. 

When you write your IO program, this world object is never available (the IO 
type is a special internal type), so the red wire is erased from the diagram, 
and the getLine and putStrLn boxes become “delayed actions”. 

Imperative programmers like myself might initially be confused when they see 
Haskell’s do notation, because it looks like the actions are strict statements 
as in C/C++/Pascal/Java/C#/etc, but they are not.

For example, try the following program:

main = do last [
   putStrLn NOT executed although it is first in the list, as it is 
not used by the main function!,
   putStrLn This action IS executed because it is evaluated by the 
main function. ]

This is of course all due to Haskell’s laziness which only evaluates just those 
expressions that it needs to evaluate the main function.

One thing to note in the diagram above is that the getLine box has TWO outputs, 
the String and the World. But functions can only have a single output, but this 
can be tuple. Hence the passing of the world from one box to the other is a bit 
more complicated. It is this pattern of extracting both values from the output 
and passing them to the next function and other related combinations that form 
the generic monad class, which can be used for many more things than IO.

See http://haskell.org/haskellwiki/IO_inside for a much deeper and more correct 
explanation ☺

And for the pros here, did this newbie make any sense? Probably not ;-) 

Oh no, yet another monad explanation!!! Now the universe will most certainly 
collapse… 


No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.476 / Virus Database: 269.11.0/929 - Release Date: 31/07/2007 17:26
 
  
attachment: IO monad.GIF___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Newbie question about Haskell skills progress

2007-07-31 Thread peterv
Having only a couple of days of practice programming Haskell (but having
read lots of books and docs), I find myself writing very explicit low level
code using inner aux functions (accumulators and loops). Then I force
myself  to revise the code, replacing these aux functions with suitable
higher-order functions from the library. However, I would like to use these
higher order functions right away, without using low-level aux constructs,
which is most likely caused by my very long history of imperative
programming.

 

Is this the normal way of progressing in Haskell, or should I consider a
different approach?

 

Thanks,

Peter

 

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


RE: [Haskell-cafe] Newbie question about automatic memoization

2007-07-31 Thread peterv
Thanks! Is this is also the case when using let and where, or is this just
syntactic sugar?

-Original Message-
From: Jules Bean [mailto:[EMAIL PROTECTED] 
Sent: Tuesday, July 31, 2007 5:09 PM
To: Bryan Burgers
Cc: peterv; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Newbie question about automatic memoization

Bryan Burgers wrote:
 On 7/30/07, peterv [EMAIL PROTECTED] wrote:
 Does Haskell support any form of automatic memorization?

 For example, does the function

 iterate f x

 which expands to

 [x, f(x), f(f(x)), f(f(f(x))), .

 gets slower and slower each iteration, or can it take advantage of the
fact
 that f is referentially transparent and hence can be memoized / cached?

 Thanks,
 Peter
 
 For 'iterate' the answer does not really need to be memoized.

Or, another way of phrasing that answer is 'yes'. The definition of 
iteration does memoize - although normally one would say 'share' - the 
intermediate results.

 
 I imagine the definition of 'iterate' looks something like this:
 
 iterate f x = x : iterate f (f x)
 

Haskell doesn't automatically memoize. But you are entitled to assume 
that named values are 'shared' rather than calculated twice. For 
example, in the above expression x, being a named value, is shared 
between (a) the head of the list and (b) the parameter of the function 
f inside the recursive call to iterate.

Of course sharing x may not seem very interesting, on the outermost 
call, but notice that on the next call the new x is the old f x, and 
on the call after that the new x is f (f x) w.r.t the original x.

Jules

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


RE: [Haskell-cafe] Newbie question about tuples

2007-07-13 Thread peterv
I'm beginning to see that my old implementation in C++ clutters my Haskell
design.

You see, in C++ I can write:

// A vector is an array of fixed-length N and elements of type T
templatetypename T, int N struct Vector 
{
  T Element[N];

  friend T dot(const Vector a, const Vector b)
  {
 T result = 0;
 for( int i=0; iN; ++i )
 {
result += a.Element[i] * b.Element[i];
 }
 return result;
  }
};

So basically a wrapper around a fixed-size array of any length.
Implementations of (+), (-), dot, length, normalize, etc... then work on
vectors of any size, without the overhead of storing the size, and with
compile-time checking that only vectors of the same size can be used, etc...
This also fits in nicely when creating a MatrixT,N,M class.

I don't think Haskell has something like a fixed-length array or constant
expressions that *must* be resolved at compile-time (like the N in the C++
template)? Or like Digital Mars D's static if statement (which is a
control-flow statement that *must* succeed at compile time)?

Tuples allow a different type for each element (they are more like
anonymous structs), so are not really suitable for what I want to do. 

Now in C++ when implementing this (together with fixed-size matrices), you
can get a lot of overhead because the code needs to compute many
intermediate results; it has a hard time to unroll all the loops (although I
think the latest compilers are much better). Now when implementing something
like this in Haskell, I would guess that its laziness would allow to
interleave many of the math operations, reordering them to be as optimal
as possible, removing many intermediate results (like processing streams).
So you would automatically get something like the C++ Expression Templates
http://ubiety.uwaterloo.ca/~tveldhui/papers/Expression-Templates/exprtmpl.ht
ml... Well at least I hope so :) 

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Lukas Mai
Sent: Friday, July 13, 2007 09:20
To: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Newbie question about tuples

Am Donnerstag, 12. Juli 2007 20:14 schrieb Andrew Coppin:

 The only thing the libraries provide, as far as I can tell, is the fact
 that tuples are all Functors. (In other words, you can apply some
 function to all the elements to get a new tuple.) I think that's about
 it. I doubt you can use that to define lifting functions...

Actually, they aren't (Functors). (,) takes two type arguments, (,,)
takes three, etc.  class Functor f requires f to take one type argument.
So something like

  instance Functor (,) where ...

won't compile. Besides, what should fmap (+1) (3, 4, foo) do?

(Somewhere in the libraries there is an
instance Functor (,) a where fmap f (x, y) = (x, f y)
but that's probably not what you expected.)

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

No virus found in this incoming message.
Checked by AVG Free Edition. 
Version: 7.5.476 / Virus Database: 269.10.4/898 - Release Date: 12/07/2007
16:08
 

No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.476 / Virus Database: 269.10.4/898 - Release Date: 12/07/2007
16:08
 

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


RE: [Haskell-cafe] Newbie question about tuples

2007-07-13 Thread peterv
 with guaranteed termination, of course

Just out of curiosity (not Haskell related): I always get confused when
people speak about guaranteed termination; what about the halting problem?
In which context can one check for guaranteed termination, as the halting
problem says it's not *generally* possible? 

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Jonathan Cast
Sent: Friday, July 13, 2007 16:21
To: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Newbie question about tuples

On Friday 13 July 2007, peterv wrote:
 I'm beginning to see that my old implementation in C++ clutters my Haskell
 design.

 You see, in C++ I can write:

 // A vector is an array of fixed-length N and elements of type T
 templatetypename T, int N struct Vector
 {
   T Element[N];

   friend T dot(const Vector a, const Vector b)
   {
  T result = 0;
  for( int i=0; iN; ++i )
  {
 result += a.Element[i] * b.Element[i];
  }
  return result;
   }
 };

 So basically a wrapper around a fixed-size array of any length.
 Implementations of (+), (-), dot, length, normalize, etc... then work on
 vectors of any size, without the overhead of storing the size, and with
 compile-time checking that only vectors of the same size can be used,
 etc... This also fits in nicely when creating a MatrixT,N,M class.

 I don't think Haskell has something like a fixed-length array or
constant
 expressions that *must* be resolved at compile-time (like the N in the C++
 template)?

I'm surprised no one has posted anything on type-level programming yet.  You

might google for that.  And GHC 6.8 will have true type-level functions
(with 
guaranteed termination, of course) which will help.  But I'm sure a good 
google will turn up a clearer explanation than I can provide; I've never 
needed or wanted to understand the type-level stuff.

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

No virus found in this incoming message.
Checked by AVG Free Edition. 
Version: 7.5.476 / Virus Database: 269.10.4/898 - Release Date: 12/07/2007
16:08
 

No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.476 / Virus Database: 269.10.4/898 - Release Date: 12/07/2007
16:08
 

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


RE: [Haskell-cafe] Re: Newbie question about tuples

2007-07-13 Thread peterv
Super. This is really a great mailing list :)

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Chung-chieh Shan
Sent: Friday, July 13, 2007 16:54
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Re: Newbie question about tuples

peterv [EMAIL PROTECTED] wrote in article
[EMAIL PROTECTED] in gmane.comp.lang.haskell.cafe:
 I don't think Haskell has something like a fixed-length array or
constant
 expressions that *must* be resolved at compile-time (like the N in the C++
 template)? Or like Digital Mars D's static if statement (which is a
 control-flow statement that *must* succeed at compile time)?

Actually, Haskell can do it one better: you can have fixed-length arrays
whose length is known only at run time.  That is, you can have the
compiler check that you will only be adding arrays with the same length,
but find out what that length is (and pass it around non-redundantly) at
run time.  (You can encode the same idea, more verbosely, using generics
in Java and C#.)

Please see (among other work):
http://ofb.net/~frederik/vectro/
http://www.cs.rutgers.edu/~ccshan/prepose/
http://www.eecs.usma.edu/webs/people/okasaki/icfp99.ps

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
http://www.unaids.org/en/HIV_data/epi2006/
UNAIDS/WHO AIDS Epidemic Update: December 2006

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

No virus found in this incoming message.
Checked by AVG Free Edition. 
Version: 7.5.476 / Virus Database: 269.10.4/898 - Release Date: 12/07/2007
16:08
 

No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.476 / Virus Database: 269.10.4/898 - Release Date: 12/07/2007
16:08
 

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


RE: Re[2]: [Haskell-cafe] Newbie question about tuples

2007-07-13 Thread peterv
Yes but doesn't GHC have a good strictness analyzer (or how is this
called?)? I haven't looked at the generated assembly code yet (if this is at
all readable; but good C/C++ compilers *do* generate reasonably readable
assembly code)

-Original Message-
From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
Sent: Friday, July 13, 2007 6:43 PM
To: peterv
Cc: 'Lukas Mai'; haskell-cafe@haskell.org
Subject: Re[2]: [Haskell-cafe] Newbie question about tuples

Hello peterv,

Friday, July 13, 2007, 5:03:00 PM, you wrote:

 think the latest compilers are much better). Now when implementing
something
 like this in Haskell, I would guess that its laziness would allow to
 interleave many of the math operations, reordering them to be as optimal
 as possible, removing many intermediate results (like processing streams).

don't forget that laziness by itself makes programs an orders of
magnitude slower :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]


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


RE: [Haskell-cafe] Looking for final year project - using Haskell, or another functional language

2007-07-13 Thread peterv
Yes, for a newbie like me it was actually the reason to abandon Haskell
initially; none of the examples at http://www.haskell.org/HOpenGL compiled!

Another very cool albeit difficult project would be automatic retargeting of
Haskell code to the graphics processor unit (GPU), or IBM Synergistic
Processor Unit  (SPU aka Cell processor, if you can get your hands on such a
board...). I think IBM has been working on something like that for
imperative languages, but it would be interesting to see how far you one can
go with Haskell. If this is not yet done of course...

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Stefan O'Rear
Sent: Friday, July 13, 2007 3:37 AM
To: wp
Cc: Haskell-Cafe@haskell.org
Subject: Re: [Haskell-cafe] Looking for final year project - using Haskell,
or another functional language

On Fri, Jul 13, 2007 at 02:31:58AM +0100, wp wrote:
 just be sure to ignore http://www.haskell.org/HOpenGL/ , which should 
 be moved to the wiki or to /dev/null.

 sorry for the basic question: why is hopengl so bad?

HOpenGL, the library, isn't bad at all.  It's the website that's absolutely
horrible.

Stefan

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


[Haskell-cafe] Newbie question about tuples

2007-07-12 Thread peterv
Hi,

I have a couple of questions about tuples.

Q1) Is it possible to treat a tuple of N elements in a generic way? So
instead of writing functions like lift1 e1, lift2 (e1,e2), lift3 (e1,e2,e3)
just one function liftN that works on tuples of any length? 

Q2) (Maybe related to Q1) Can I convert a tuple of length N to a
heterogeneous list (using forall aka existentially quantified types) and
vice versa? 

Q3) Suppose I want to declare an instance of Num on all tuple types having
(Num instances) as elements; is this possible? 

I tried

   instance Num a = Num (a,a) where .

but this fails

I also tried

   instance Num a = Num ((,) a a) where .

but that also fails.

I can of course create a new type like

   newtype Num a = Vector2 a = Vector2 (a,a) 

and then create an instance for Vector2, but I was wondering if it would be
possible without introducing a new type.

Thanks,
Peter










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


RE: [Haskell-cafe] Functional dependencies *not* part of the next Haskell standard?

2007-07-12 Thread peterv
 instance Vector Vector2 where
   dot (V2 x1 y1) (V2 x2 y2) = x1 * x2 + y1 * y2

Amazing, so simple it is, Yoda would say ;)

I did not realize one could perform partial application on types when
declaring instances (I mean not specifying the type of Vector2 in instance
Vector Vector2).

Now regarding these funcdeps, are they ill as the rumor goes?

Thanks,
Peter

-Original Message-
From: Henning Thielemann [mailto:[EMAIL PROTECTED] 
Sent: Thursday, July 12, 2007 11:44 AM
To: peterv
Cc: Haskell-Cafe@haskell.org
Subject: Re: [Haskell-cafe] Functional dependencies *not* part of the next
Haskell standard?


On Thu, 12 Jul 2007, peterv wrote:

 I tried to do something in CAL that I could not solve without functional
 dependencies. In their support forum, it got mentioned that func.deps
 propably won't make into the next Haskell standard... Any comments on
that?

 Now, the thing I tried to solve was:

data Vector2 a = Num a = V2 a a

class Vector a n | a - n where
  dot :: a - a - n

instance Num a = Vector (Vector2 a) a where
  dot (V2 x1 y1) (V2 x2 y2) = x1 * x2 + y1 * y2

test1 = dot (V2 1.0 2.0) (V2 3.0 4.0)


class Vector v where
   dot :: Num a = v a - v a - a

instance Vector Vector2 where
   dot (V2 x1 y1) (V2 x2 y2) = x1 * x2 + y1 * y2


This will work satisfyingly if you don't plan a larger type class
hierarchy.

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


RE: [Haskell-cafe] Haskell monads for newbies (was Functional dependencies *not* part of the next Haskell standard?)

2007-07-12 Thread peterv
Thanks for the advice. I did not really deeply investigate the monad type
classes yet...

It looks like its gonna take a long time for me to learn Haskell. I'm not
sure if my long history of imperative and object-oriented programming has
something to do with it. Reading Haskell books like SOE is one thing, but
writing software in Haskell is really difficult for me. Not only do I miss
the spoiled OO programmer IDEs with all their candy and code completion
and assistants, but I also get the feeling that although similar programs in
Haskell or typically N times shorter than their imp/OO counterparts, it
would take *me* at least N^2 longer to write them ;) (now I must admit I had
the same feeling when switching from 680x0 assembler to C++, but let's say
N*2 longer instread of N^2...) Is this true for Haskell in general? I mean
how long do experienced Haskell developers spent writing code to get it
right (excluding minor bugs and performance issues)? Or do they write down
Haskell fluently?

Regarding those monads, I read a lot of stuff about these beast, trying to
get a high-level understanding about them (and apparently I'm not the only
newby who struggled with that ;), but after having read You Could Have
Invented Monads! and then reading
http://research.microsoft.com/~simonpj/papers/marktoberdorf, it all became
much clearer. Those pictures really helped... 

Monads were very confusing because I first looked at Concurrent Clean (it
comes with an IDE and games! :), and that language uses a simple uniqueness
typing approach where the world or state is explicitly passed as an
object, and where the compiler garantees monadic usage of that object
(warning: that was a lot of fuzzy talk from a newbie trying to look
impressive ;) 

-Original Message-
From: Benja Fallenstein [mailto:[EMAIL PROTECTED] 
Sent: Thursday, July 12, 2007 3:11 PM
To: peterv
Cc: Henning Thielemann; Haskell-Cafe@haskell.org
Subject: Re: [Haskell-cafe] Functional dependencies *not* part of the next
Haskell standard?

2007/7/12, peterv [EMAIL PROTECTED]:
 Amazing, so simple it is, Yoda would say ;)

 I did not realize one could perform partial application on types when
 declaring instances (I mean not specifying the type of Vector2 in
instance
 Vector Vector2).

You ought to meditate on the type class 'Monad,' then, which was the
motivating example for allowing these kinds of classes in standard
Haskell ;-)

All the best,
- Benja

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


[Haskell-cafe] RE: Modern Haskell books (was Re: A very nontrivial parser)

2007-07-06 Thread peterv
 but afair you don't yet have too much experience even with H98
 language? from my POV, H98 as is useful for learning, but not for real 
 apps. there is wide common subset of GHC and Hugs language extensions
 and this set (with exception for FD) will probably become new Haskell'
 standard

The problem I face is that most (all?) Haskell books I could find deal with
Haskell 98... Are there any books out that cover the modern Haskell
extensions? 

Peter

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Bulat Ziganshin
Sent: Friday, July 06, 2007 10:33
To: Andrew Coppin
Cc: haskell-cafe@haskell.org
Subject: Re[2]: [Haskell-cafe] A very nontrivial parser

Hello Andrew,

Thursday, July 5, 2007, 11:45:14 PM, you wrote:

 Personally, I just try to avoid *all* language extensions - mainly
 because most of them are utterly incomprehensible. (But then, perhaps 
 that's just because they all cover extremely rare edge cases?)

 MPTCs and ATs look useful. The rest... hmm. If I ever figure out what 
 they do, maybe I can comment.

but afair you don't yet have too much experience even with H98
language? from my POV, H98 as is useful for learning, but not for real
apps. there is wide common subset of GHC and Hugs language extensions
and this set (with exception for FD) will probably become new Haskell'
standard

one problem of Haskell popularity is that language is rather complex
to learn. but one doesn't need to learn it all from the beginning. in
my *application* program i don't used even type classes but when i've
started to write general-purpose libs, aspiration to develop as general
solution as possible quickly leads to using all kinds of Haskell
type hackery

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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

No virus found in this incoming message.
Checked by AVG Free Edition. 
Version: 7.5.476 / Virus Database: 269.10.1/888 - Release Date: 06/07/2007
06:36
 

No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.476 / Virus Database: 269.10.1/888 - Release Date: 06/07/2007
06:36
 

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


[Haskell-cafe] Haskell's currying versus Business Objects Gem Cutter's burning

2007-07-03 Thread peterv
In Haskell, currying can only be done on the last (rightmost) function
arguments.

 

So 

 

foo x y

 

can be curried as 

 

foo x

 

but not as 

 

foo ? y

 

where ? would be a wilcard for the x parameter.

 

In Haskell, one must write a new function

 

foo2  y x = foo x y

 

and then one can curry the x parameter like

 

foo2 y

 

In Gem Cutter - which is a visual programming language - on can burn any
input argument (which is like putting the ? for any argument in the foo
function). See
http://resources.businessobjects.com/labs/cal/gemcutter-techpaper.pdf

 

This burning looks more general to me, but cannot be done using the textual
approach?

 

Does this reasoning make any sense? 

 

Thanks,

Peter

 

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


[Haskell-cafe] HGL on Windows

2007-06-29 Thread peterv
I vaguely  remember to have read that HGL is (currently) not supported on
Windows, but I can't find this information any more.

 

Is this correct? It seems not to be included in GHC 6.6

 

 

 

 

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


[Haskell-cafe] Newbie question: alternative for toInt/fromInt

2007-06-28 Thread peterv
I'm trying to get the SOE graphics library to compile for Win32 using the
latest libraries.

 

I fixed a couple of imports, but in the file GraphicsTypes.hs, the functions
toInt/fromInt are used, which are now obsolete:

 

type Dimension = Int

toDimension:: Win32.INT - Dimension

fromDimension  :: Dimension - Win32.INT

toDimension   = toInt

fromDimension = fromInt

 

I don't have a clue how to fix this, as I can't find alternatives for
toInt/fromInt (except toInteger/fromInteger, but that would convert to
heavyweight ints), but I guess it must be really easy? 

 

Thanks,

Peter

 

 

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


RE: [Haskell-cafe] New New newbie question/help

2007-06-27 Thread peterv
I'm also a haskell newbie, but I'll try to help; the experts here will
correct me if I'm wrong.

The compiler cannot in all cases infer the type of a number. pi can be a
Float, a Double, or even a complex number. 

Furthermore unlike in C/C++ you cannot just mix integer and floating
operations.

For example, the following works for me:

f :: Int - Int
f side = round ( (fromIntegral side) * sin ( (pi::Float) / 3 ) )

or easier

f side = round ( (fromIntegral side) * sin (pi / 3.0) )

I'm sure the experts here will have a better solution.

Peter
-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Balu Raman
Sent: Wednesday, June 27, 2007 1:25 PM
To: Haskell-Cafe@haskell.org
Subject: [Haskell-cafe] New New newbie question/help

Hi,
Hope someone can help me, just starting out with SOE.My code :
module Main where
import Graphics.SOE.Gtk

spaceClose :: WIndow - IO()
spaceClose w = do k - getKey w
   if k == ' ' then closeWindow w
   else spaceClose w

equilateralTri :: Window - Int - Int - Int - IO()
equilateralTri w x y side
   = drawInWindow w (withColor Red
   (polygon
[(x,y),(a,b),(x,y)]))
   where
b = y + side * sin(pi/3)
a = x + side * cos(pi/3)
main =
   runGraphics(
  do w - openWindow Equilateral
Triangle (400,400)
equilateralTri w 50 300 200
spaceClose w
)

all of the above in file triangle.hs
when I do a :l triangle.h in ghci,  I get the following error
triangle.hs:17:36:
No instance for (Floating Int)
 arising from use of 'pi' at triangle.hs:17:36-37
Probable fix: add an instance declaration for (Floating Int)
In the first argument of '(/)', namely 'pi'
In the first argument of 'cos', namely '(pi / 3)'
In the second argument of '(*)', namely 'cos (pi/3)'
Failed, modules loaded: none

Can someone help me what's going on to a brand new newbie. All I can
figure out is that some type mismatch between float and int . I tried
various
combinations of lets and wheres and I still get the same complaints.
I am just linearly studying SOE
Thanks,
- br
___
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] New New newbie question/help

2007-06-27 Thread peterv
Newbie helping newbie, cool J And indeed, this is an amazing mailing list!

 

Personally, I prefer to read fromIntegral :: (Num b, Integral a) = a - b
like

 

IF (b is a Num) AND (a is an Integral) THEN (fromIntegral is defined and is
a function from a to b)

 

This way it resembles the mathematical symbol for implication (=)

 

PS: Haskells generic number system can be very confusing for the beginner,
but it becomes very cool when you start working with type classes. You will
see that in the later chapters of  the great SOE book (animation and
reactive behaviors). The reactive behavior chapter is really hard, but don't
give up. In my case I got a real revelation, finally understanding the real
power of streams and lazy evaluation; it really changes the way you look at
the world. As a videogames developer, I still have a lot of unanswered
questions though (for example, how to efficiently handle events between
behaviors, like collision, but I hope to find that in Yampa or newer work)

 

From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Balu Raman
Sent: Wednesday, June 27, 2007 5:37 PM
To: Haskell-Cafe@haskell.org
Subject: Re: [Haskell-cafe] New New newbie question/help

 

I am for ever obliged to this haskell community. Who would have thought that
Prof.Hudak would reply instantly, from on-the-road. I am reading his SOE.
Thanks so much.

I went with peterv's response after trying so many things. 
I tried to change to : equilateralTri Window - Float - Float - Float -
IO()
which bombed because polygon wants list of integer-pairs.

I read the definitions of fromIntegral and round and they are defined as : 
fromIntegral :: (Num b, Integral a) = a - b
round :: (RealFrac a, Integral b) = a-b
Is it proper/ok to defines them as :
fromIntegral :: (a::Integral) - (b::Num)
and
round :: (a::RealFrac) - (b::Integral)  ? 
Is RealFrac is-a Num ?
Does the order matters in (Num b,Integral a) = a - b or
   (Integral a,Num b) = a - b

With your encouragements, I'll keep pluuging. Thanks. 
- br

On 6/27/07, peterv [EMAIL PROTECTED] wrote:

I'm also a haskell newbie, but I'll try to help; the experts here will
correct me if I'm wrong.

The compiler cannot in all cases infer the type of a number. pi can be a
Float, a Double, or even a complex number. 

Furthermore unlike in C/C++ you cannot just mix integer and floating
operations.

For example, the following works for me:

f :: Int - Int
f side = round ( (fromIntegral side) * sin ( (pi::Float) / 3 ) ) 

or easier

f side = round ( (fromIntegral side) * sin (pi / 3.0) )

I'm sure the experts here will have a better solution.

Peter
-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Balu Raman
Sent: Wednesday, June 27, 2007 1:25 PM
To: Haskell-Cafe@haskell.org
Subject: [Haskell-cafe] New New newbie question/help

Hi,
Hope someone can help me, just starting out with SOE.My code :
module Main where
import Graphics.SOE.Gtk

spaceClose :: WIndow - IO() 
spaceClose w = do k - getKey w
   if k == ' ' then closeWindow w
   else spaceClose w

equilateralTri :: Window - Int - Int - Int - IO() 
equilateralTri w x y side
   = drawInWindow w (withColor Red
   (polygon
[(x,y),(a,b),(x,y)]))
   where
b = y + side * sin(pi/3)
a = x + side * cos(pi/3)
main =
   runGraphics(
  do w - openWindow Equilateral
Triangle (400,400) 
equilateralTri w 50 300 200
spaceClose w
)

all of the above in file triangle.hs
when I do a :l triangle.h in ghci,  I get the following error
triangle.hs:17:36:
No instance for (Floating Int)
 arising from use of 'pi' at triangle.hs:17:36-37
Probable fix: add an instance declaration for (Floating Int) 
In the first argument of '(/)', namely 'pi'
In the first argument of 'cos', namely '(pi / 3)'
In the second argument of '(*)', namely 'cos (pi/3)' 
Failed, modules loaded: none

Can someone help me what's going on to a brand new newbie. All I can
figure out is that some type mismatch between float and int . I tried
various
combinations of lets and wheres and I still get the same complaints. 
I am just linearly studying SOE
Thanks,
- br
___
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] Practical Haskell question.

2007-06-25 Thread peterv
I'm baffled. So using the Arrow abstraction (which I don't know yet) would
solve this problem? How can (perfectActionB x) be checked with without ever
executing performActionA which evaluates to x? This can only be done when x
is a constant expression no?

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Tomasz Zielonka
Sent: Monday, June 25, 2007 10:43 AM
To: Henning Thielemann
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Practical Haskell question.

On Mon, Jun 25, 2007 at 10:29:14AM +0200, Henning Thielemann wrote:
 Imagine all performActions contain their checks somehow. Let
 performActionB take an argument.
 
   do
 x - performActionA
 y - performActionB x
 z - performActionC
 return $ calculateStuff x y z
 
 Now performActionB and its included check depend on x. That is, the check
 relies formally on the result of performActionA and thus check B must be
 performed after performActionA.

IIUC, this limitation of Monads was one of the reasons why John Hughes
introduced the new Arrow abstraction.

Best regards
Tomek
___
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] Graphical Haskell

2007-06-22 Thread peterv
Hi,

Since nobody gave an answer on this topic, I guess it is insane to do it in
Haskell (at least for a newbie)? :)

Thanks for any info,
Peter

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of peterv
Sent: Wednesday, June 20, 2007 21:48
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Graphical Haskell

In the book Haskell School of Expression, streams are nicely explained
using a graphical flow graph.

This is also done more or less in
http://research.microsoft.com/~simonpj/papers/marktoberdorf/Marktoberdorf.pp
t to explain monads and other concepts.

I would like to create a program that allows you to create such flow graphs,
and then let GHC generate the code and do type inference. 

I found a paper where Haskell is used to create a GUI application with
undo/redo etc for creating graphical Basian networks
(http://www.cs.uu.nl/dazzle/f08-schrage.pdf), so this gave me confidence
that I could it do all in Haskell.

Now, instead of generating Haskell code (which I could do first, would be
easier to debug), I would like to directly create an AST, and use an Haskell
API to communicate with GHC. 

I already found out that GHC indeed has such an API, but how possible is
this idea? Has this been done before? I only found a very old attempt at
this, confusingly also called Visual Haskell, see
http://ptolemy.eecs.berkeley.edu/%7Ejohnr/papers/visual.html, but I can't
find any source code for that project.

I did a similar project in C# that generated C++ code, so I've done it
before, just not in Haskell.

Thanks a lot,
Peter


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

No virus found in this incoming message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.1/857 - Release Date: 20/06/2007
14:18
 

No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.1/857 - Release Date: 20/06/2007
14:18
 

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


RE: [Haskell-cafe] Graphical Haskell

2007-06-22 Thread peterv
Wow thanks for all the info! This certainly can get me started.

And yet I have some more questions (sorry!):

- Unfortunately this project won't be open source; if my first tests are
successful, I will try to convince my employer (who wants to develop such a
graphical language) to use Haskell for building a prototype instead of
C#/F#/Java. Can Haskell be used for creating commercial projects? When the
product is released, it *will* be downloadable for free, but the source code
won't be (most likely). 

- If my employer agrees on Haskell, and when our first round of investment
is completed, we will be looking for a couple of good Haskell developers.
What would be the best place to look for good Haskell developers? This
mailing list? Ideally development will have to take place in
Antwerp/Belgium, although we might work with remotely located freelancers.
We prefer agile development (SCRUM, and maybe we will be doing extreme
programming, to be decided) with a small group of capable people. To get an
idea of what my employer is doing, visit http://www.nazooka.com. My
colleagues and I wrote most of the software for doing this back in the
1990s, and of course the real work is done by 3D graphics artists.

- Regarding GUIs, does a real FP-style GUI exist instead of those wrappers
around OO GUIs? I did some searches but besides some research papers about
FranTk and wxFruit I only found wrappers such as Gtk2Hs and wxHaskell that
use a lot of monadic IO. It's very hard for an old school OO style
programmer like myself to switch my mind into lazy functional programming
(although I think I've seen the light yesterday when digging deep into the
FRP of the SOE book, LOL ;-).
 
- Functional reactive programming like looks cool (I only looked at the SOE
book, must still look at Yampa), but somehow I feel this is still an active
area of research. What is the latest work on FRP (for GUIs / games /
animation / simulations...)? What are the major open issues? 

- Regarding performance (for real-time simulations, not GUIs), I think the
garbage collector will get really stressed using FRP because of all those
infinite lazy streams; my gut feeling says a generational garbage collector
like Microsoft's .NET could help here (but the gut is often wrong, see
http://www.youtube.com/watch?v=RF3m3f9iMRc for an laugh ;). Regarding the
GC, is http://hackage.haskell.org/trac/ghc/wiki/GarbageCollectorNotes still
up-to-date?  

Okay, that's enough for now. More is less...

- Peter

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Claus Reinke
Sent: Friday, June 22, 2007 14:02
To: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Graphical Haskell

 Since nobody gave an answer on this topic, I guess it is insane to do it
in
 Haskell (at least for a newbie)? :)

not necessarily; we're all waiting for your first release?-)

 I would like to create a program that allows you to create such flow
graphs,
 and then let GHC generate the code and do type inference. 

spun off from dazzle, which you've found, there's also blobs:

http://www.cs.york.ac.uk/fp/darcs/Blobs/
 
 Now, instead of generating Haskell code (which I could do first, would be
 easier to debug), I would like to directly create an AST, and use an
Haskell
 API to communicate with GHC. 

one thing to consider: things get a little more tricky when the generated
haskell and dynamically loaded code is meant to do graphics (such as 
updating the original diagram with the state of the simulation). in
particular, 
check that the gui framework actually works via that more circuituous route 
(similar problems to running in ghci instead of ghc).
 
 I already found out that GHC indeed has such an API, but how possible is
 this idea? Has this been done before? 

the ghc api is meant to support this kind of endeavours, and it isn't frozen
yet, either: the ghc team is happy to receive feedback about things that
work 
or things that could work better.

before the ghc api, before blobs (after dazzle, though;), i did an embedding
of haskell-coloured petri nets in haskell, with a very simplistic graphical
net editor on top of wxhaskell, which generated haskell code for the net,
then called ghci to type-check and run the resulting code with a copy of
the original net graphics to update during simulation (poor man's
reflection:):

http://www.cs.kent.ac.uk/people/staff/cr3/HCPN/

it worked, but some things were annoying: 

- no high-level support for writing graph editors in wxhaskell;
blobs aims to fix that

- awkward meta-programming and runtime reflection;
ghc api should help a lot (but i can't see anything wrong with
letting it work on generated source code first; optimization can
come latter)

- wxhaskell encourages low-level dependencies, at least when
you're writing your first wxhaskell programs, because it can
be rather difficult just to find the function you need, you're
tempted to use it right there, just to see if 

RE: [Haskell-cafe] Haskell version of ray tracer code is much slower than the original ML

2007-06-21 Thread peterv
So float math in *slower* than double math in Haskell? That is interesting.
Why is that?

BTW, does Haskell support 80-bit long doubles? The Intel CPU seems to use
that format internally.

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Philip Armstrong
Sent: Thursday, June 21, 2007 1:36 PM
To: Haskell-Cafe@haskell.org; Sebastian Sylvan
Subject: Re: [Haskell-cafe] Haskell version of ray tracer code is much
slower than the original ML

On Thu, Jun 21, 2007 at 12:25:44PM +0100, Sebastian Sylvan wrote:
Try using floats for the vector, and strict fields (add a ! to the
fields in the data declaration).

Because the optimisation page on the haskell wiki is very explicit
about never using Float when you can use Double, that's why. An older
revision used Float and it was slower than the current one. Making the
datatypes strict also makes no difference.

I have tried the obvious things :)

That's the simplest possible thing I can think of after about two
seconds of looking anyway. It appears that the ML version uses float
so I don't understand why you would use Double for the Haskell version
at all, and then think you could do any sort of valid comparisons
between them...

OCaML floats are Doubles, at least on x86.

cheers, Phil

-- 
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
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] Haskell mode for emacs - some questions

2007-06-20 Thread peterv
Yes, HopenGL works fine using GHCI, Gtk2HS/SOE doesn't (it already explained
in somewhere this mailing list)

For particle systems, the interpreted overhead will be large I guess. At
least for the L-System I tested, compiling with GHC resulted in much much
faster execution.

-Original Message-
From: Jules Bean [mailto:[EMAIL PROTECTED] 
Sent: Tuesday, June 19, 2007 09:58
To: peterv
Cc: 'David House'; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Haskell mode for emacs - some questions

peterv wrote:
 And when I will me using HopenGL, I will want performance, as I will be
 doing experiments with particle systems, 3D rendering, etc. Basically the
 stuff I did for many years but now using Haskell :)
 
 Having to do anything more than hitting a key to compile and run an
 application would simple be unacceptable from the point of view of an
imp/OO
 developer (all imp/OO IDEs have that). Furthermore, when programming
 videogames or special effects, you have to run and test a lot, because
what
 you see on screen usually 
 determines your next actions. 

I don't disagree that this should be possible. If you hit C-h f compile 
then you can read the documentation for the built-in compile command. By 
default this runs make, because many code projects especially in the 
unix world use make as their build system, but you can customise this.

On the other hand a simple haskell project doesn't have any way of 
indicating which is the 'main' file (indeed most of my haskell projects 
with more than one file have more than one 'main' file with different 
purposes) so it's not immediately obvious which arguments to give to ghc 
--make.  I suspect that this itch is just not sufficiently important to 
most haskell-mode users, since the alternatives (C-c C-l, C-x b M-p 
RET, or alt-tab up ret) [*] work so well.

Incidentally I've developed using HOpenGL in ghci with no problem. The 
performance is not really an issue: only the 'current file' is 
interpreted, all other files are used compiled, and in any case most of 
the CPU usage is in the (compiled) GL libraries of your system.

Jules

* C-x b M-p RET being 'switch to your shell buffer, select previous 
command and re-run it', since your previous command is obviously ghc 
--make foo.hs  ./foo.  Alt-tab up ret is the same thing except it 
switches to a non-emacs shell window using your window manager, if you 
don't like using emacs shells :)


No virus found in this incoming message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.1/854 - Release Date: 19/06/2007
13:12
 

No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.1/854 - Release Date: 19/06/2007
13:12
 

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


RE: [Haskell-cafe] Re: Haskell mode for emacs - some questions

2007-06-20 Thread peterv
 Sounds like it was difficult.  Could you describe what you tried

Actually, it was easy once I switched from xemacs to emacs... Of course, I 
missed the part in the wiki that xemacs does not work without some changes, mea 
culpa. The reason I used xemacs was because the previous version of emacs did 
not support good font smoothing (cleartype) on Windows, but that seems to be 
fixed now. Also, I just found out about the EmacsW32 package which is really 
easy to install on Windows. 

 currently Emacs doesn't know which file is the main one

So emacs has no concept of a startup project and a solution or workspace 
like Visual Studio and Eclipse? Well yes, that explains why this feature is 
missing. I guess I can just as will stick to typing run as the compile 
command and creating a run batch file...

 In VS or Eclipse, what do you have to do in order for F5 to work?

In VS you have a solution which is a set of projects. A project is 
basically a module, which can be an executable or library. The user marks one 
or more executable projects as startup projects. When hitting F5, all the 
dirty dependent projects are compiled and linked, and all the startup 
projects are run. Usually you just have a single startup project. 

 We could also add a binding which sends main to GHCi.

Would be nice. But I'll still have to use GHC a lot for performance.

 I use this hack all the time and haven't been bitten yet.  

Super! Then it's worth for me to figure out how that works. 

Thanks a lot,
Peter

-Original Message-
From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Stefan Monnier
Sent: Tuesday, June 19, 2007 20:52
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Re: Haskell mode for emacs - some questions

 I finally got emacs using Haskell-mode working. It seems that the latest

Sounds like it was difficult.  Could you describe what you tried, what
didn't work, and what did work in the end?  Hopefully I can then improve
the doc.

 - How can I just compile and run in one go without having to type ghc
 --make main.hs as arguments for the compile... command and then typing
 main.exe for shell command...? This is what you do all the time when
 using Visual Studio, Eclipse, etc: just hit the F5 key which builds all the
 dependencies and runs one or more generated executables. Easy. Visual
 Haskell does this (in the cases it does not hang for some unknown reason).
 Of course I could dig into ELISP, but somehow I feel this must be supported
 somehow.

I never use GHC in this way, I always use GHCi instead.  Furthermore, I tend
to work on only parts of a program, so there isn't necessarily
a main function.  I'd be happy to add support for your usage pattern, but
since I'm not familiar with it, I'm not sure what to add.
Another problem is that unless your project is tiny, it'll have several
files and currently Emacs doesn't know which file is the main one.  I added
very-preliminary support for Cabal in the CVS code of haskell-mode which
should allow haskell-mode (at some point in the future) to figure out what's
the main file an how to compile it.
Currently all it does (other than font-lock the cabal file itself) is look
for the Cabal file to figure out the root of the project, so that C-c C-l
first does a cd to the root, which should allow dependencies in other
directories to work more seemlessly.

Patches (or precise feature requests) are very welcome.  E.g. it should be
fairly easy to add an F5 binding like you describe.  The main issue is how
to inform Emacs of what should be done.  In VS or Eclipse, what do you have
to do in order for F5 to work?  Is opening some random source file enough,
or do you have to select a Cabal file or what?

 Use C-c C-l to load the file into GHCi. This is better than just compiling
 it: you get an interactive environment in which to play around with, test
 out functions, etc. You can still 'run' your program by typing 'main'
 in GHCi.

We could also add a binding which sends main to GHCi.

 - There seems to be support for Haskell Font Lock Symbols, which should
 convert \, - and maybe other symbols to good looking Unicode fonts.
 I can't get the correct fonts working on Windows.

I never use Windows so I can't really help you there.  Maybe ask on
gnu.emacs.help how to get those chars displayed.  I'm pretty sure Windows
has the needed fonts, so all that's missing is some way to help Emacs make
use of them.
If you figure it out, please send me a note about what you had to do, so
I can add it to the documentation.  

 Now as I understood this is not really supported because of indentation
 problems, as underneed the single Unicode arrow character is converted
 into -?

You slightly misunderstood: this hack is fully supported.  I just added some
warnings to the docstring to make sure the user doesn't blame me when he
gets bitten.

 This is unfortunate, because that's one of the things I really
 like about Sun's Fortress: the usage of Unicode symbols makes the text
 

RE: [Haskell-cafe] Avoiding Non-exhaustive patterns in function f

2007-06-20 Thread peterv
Super! Would be nice if this gets build into GHC/GHCI :)

-Original Message-
From: Neil Mitchell [mailto:[EMAIL PROTECTED] 
Sent: Wednesday, June 20, 2007 01:07
To: Felipe Almeida Lessa
Cc: peterv; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Avoiding Non-exhaustive patterns in function f

Hi

  I understand this has nothing to do with type checking, but why can't
the
  compiler give a warning about this? Or is this by design or because it
is
  impossible to check with more complex recursive data types?

 Take a look at Catch from Neil Mitchell:
 http://www-users.cs.york.ac.uk/~ndm/catch/ .

Using the released version of Catch on the example you gave:

Analysing
Checking [1/1]: Main: Pattern match failure in function at 5:1-5:10.
Partial: Main.f
Partial: Main.main
Partial: main
Answer: 0

This says: the error message you will get is about a pattern match on
line 5 (that's where 'f' is in the example program). The list of
partial functions, in some kind of call-stack order, is Main.f, then
Main.main - i.e. your main function calls f which is partial. Answer 0
means the necessary precondition for safety is false - or its not
safe at all.

If you turn on logging Catch will additionally tell you that the
precondition on 'f' is that the data structure must be a 'A'
constructed value.

Thanks

Neil

No virus found in this incoming message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.1/854 - Release Date: 19/06/2007
13:12
 

No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.1/854 - Release Date: 19/06/2007
13:12
 

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


RE: [Haskell-cafe] Useful IDE features -

2007-06-20 Thread peterv
 (which just states that record type and field label type together uniquely
determine the field value type)

That's nice. When will a new Haskell standard become official? It seems so
many new extensions exist, that one cannot judge the language by looking at
Haskell98 anymore.

 in practice, overloading introduces overhead that might hamper
performance.

You mean overloading in general, so using type classes? Is this comparable
to the Java/C#/C++ overhead with virtual methods, so one extra level of
indirection before the function gets called? Or is it much worse?

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Claus Reinke
Sent: Wednesday, June 20, 2007 01:28
To: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Useful IDE features - 

 That looks nice, just unfortunate you need to cast to ::Float in
homer2?Age::Float. I don't see 
 why this is needed, but I must say I don't understand your code completely
yet, working on that :)

that annotation is not needed if you keep the functional dependency
(which just states that record type and field label type together uniquely
 determine the field value type)

class Has field value record | field record - value where
(?)  :: record - field - value
(:) :: (field,value) - record - record

 Also, wouldn't this approach be less performant? Or is GHC that good that
ist compiles away all 
 the overhead?

in principle, there is no need for this to be less performant.
in practice, overloading introduces overhead that might hamper
performance.

claus

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

No virus found in this incoming message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.1/854 - Release Date: 19/06/2007
13:12
 

No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.1/854 - Release Date: 19/06/2007
13:12
 

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


RE: [Haskell-cafe] Haskell mode for emacs - some questions

2007-06-20 Thread peterv
Yes this was also very very confusing for me because I had the same idea
about that. I almost gave up on learning Haskell because of that (I wanted
to practice stuff from the SOE book using the latest versions), until I
suddenly found out that GHC *did* work.

Here's the explanation:

On Fri, 2007-06-15 at 23:15 +0200, [EMAIL PROTECTED] wrote:
 I'm learning Haskell using Paul Hudak's book SOE. 
 
 I'm using GHC 6.6 under Windows XP.
 
 GHC on Windows does not seem to come with HGL (is this correct?), so I 
 used Gtk2HS, which contains a SOE implementation.
 
 I noticed that most programs hang when using GHCI, but they work fine 
 with GHC.

It's not GHCi's fault as such. The reason it does not work well in GHCi at
the moment is a bit technical. The Gtk2Hs SOE implementation currently uses
Haskell threads. Like most GUI toolkits, Gtk+ is single threaded and
requires special attention to use it from multiple OS threads. Currently, by
default, GHC produces executables that use the single-threaded runtime
system, and this works fine with multiple Haskell threads because they get
multiplexed on the same OS thread. GHC can however produce executables that
use the multi-threaded runtime system and ghci.exe itself is such a program.
So when you use SOE with GHCi it's actually using multiple threads to access
Gtk+ an not in a safe way, so it goes wrong in a myriad of ways.

I'll take another look at trying to make the SOE stuff work with the
threaded runtime system by using the primitives Gtk2Hs provides to use
Gtk+ safely from multiple threads.

Duncan

-Original Message-
From: David House [mailto:[EMAIL PROTECTED] 
Sent: Wednesday, June 20, 2007 6:42 PM
To: peterv
Cc: 'David House'; haskell-cafe@haskell.org
Subject: RE: [Haskell-cafe] Haskell mode for emacs - some questions

peterv writes:
  Yes, but I can only use GHCI for error checking, because I'm using
  GTK2HS/SOE which does not work well with GHCI under Windows, it only runs
  when using GHC.

Why is this? I'm not that familiar with Gtk2Hs, but I don't understand why
it
wouldn't work with GHCi if it works with GHC. They use the same code to
compile
it.

On the other hand, you could always just set up a Makefile (which is pretty
trivial) and use M-x compile (which you should bind to a key if you use it a
lot).

-- 
-David House, [EMAIL PROTECTED]
---BeginMessage---
On Fri, 2007-06-15 at 23:15 +0200, [EMAIL PROTECTED] wrote:
 I'm learning Haskell using Paul Hudak's book SOE. 
 
 I'm using GHC 6.6 under Windows XP.
 
 GHC on Windows does not seem to come with HGL (is this correct?), so I
used
 Gtk2HS, which contains a SOE implementation.
 
 I noticed that most programs hang when using GHCI, but they work fine with
 GHC.

It's not GHCi's fault as such. The reason it does not work well in GHCi
at the moment is a bit technical. The Gtk2Hs SOE implementation
currently uses Haskell threads. Like most GUI toolkits, Gtk+ is single
threaded and requires special attention to use it from multiple OS
threads. Currently, by default, GHC produces executables that use the
single-threaded runtime system, and this works fine with multiple
Haskell threads because they get multiplexed on the same OS thread. GHC
can however produce executables that use the multi-threaded runtime
system and ghci.exe itself is such a program. So when you use SOE with
GHCi it's actually using multiple threads to access Gtk+ an not in a
safe way, so it goes wrong in a myriad of ways.

I'll take another look at trying to make the SOE stuff work with the
threaded runtime system by using the primitives Gtk2Hs provides to use
Gtk+ safely from multiple threads.

Duncan

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


[Haskell-cafe] Graphical Haskell

2007-06-20 Thread peterv
In the book Haskell School of Expression, streams are nicely explained
using a graphical flow graph.

This is also done more or less in
http://research.microsoft.com/~simonpj/papers/marktoberdorf/Marktoberdorf.pp
t to explain monads and other concepts.

I would like to create a program that allows you to create such flow graphs,
and then let GHC generate the code and do type inference. 

I found a paper where Haskell is used to create a GUI application with
undo/redo etc for creating graphical Basian networks
(http://www.cs.uu.nl/dazzle/f08-schrage.pdf), so this gave me confidence
that I could it do all in Haskell.

Now, instead of generating Haskell code (which I could do first, would be
easier to debug), I would like to directly create an AST, and use an Haskell
API to communicate with GHC. 

I already found out that GHC indeed has such an API, but how possible is
this idea? Has this been done before? I only found a very old attempt at
this, confusingly also called Visual Haskell, see
http://ptolemy.eecs.berkeley.edu/%7Ejohnr/papers/visual.html, but I can't
find any source code for that project.

I did a similar project in C# that generated C++ code, so I've done it
before, just not in Haskell.

Thanks a lot,
Peter


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


RE: Re[2]: [Haskell-cafe] Useful IDE features - implement instance

2007-06-19 Thread peterv
Hi Bulat,

Yes, that's what I had to do when using assembler in the 19080s, but it was
nice to get rid of that when using C/C++ or any other imperative/OO language
that I'm aware of. 

You see, for someone with an imperative/OO background, the Haskell record
restriction on field names looks incredibly dumb. 

But when using type classes to encapsulate the fields makes each function
polymorphic on any record that implements these field wrappers, thus
enhancing abstraction. Type inference helps a lot here, otherwise one would
have to type each constraint in the signature of the function, which is a
pain (forgive me if I'm using incorrect terms here, I come from the OO
world...) Personally I like that, but that's a question of taste I guess.

Peter

-Original Message-
From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] 
Sent: Tuesday, June 19, 2007 8:39 AM
To: peterv
Cc: 'Claus Reinke'; haskell-cafe@haskell.org
Subject: Re[2]: [Haskell-cafe] Useful IDE features - implement instance

Hello peterv,

Monday, June 18, 2007, 6:44:06 PM, you wrote:
 Just another wild idea which I might find useful, but is more like
 refactoring, is to convert the fields of a record to get/set type-classes,
 and refactor all usages of those fields.

i never done such refactoring. just use different names for fields. a
rule of thumb is including of record name in field names:

data PackedFilePath = PackedFilePath
  { fpPackedDirectory   :: !MyPackedString
  , fpPackedBasename:: !MyPackedString
  , fpLCExtension   :: !String
  , fpHash   :: {-# UNPACK #-} !Int32
  , fpParent:: !PackedFilePath
  } 
  | RootDir 

data FileInfo = FileInfo
  { fiFilteredName :: !PackedFilePath  
  , fiDiskName :: !PackedFilePath  
  , fiStoredName   :: !PackedFilePath  
  , fiSize  :: {-# UNPACK #-} !FileSize
  , fiTime  :: {-# UNPACK #-} !FileTime
  , fiIsDir :: {-# UNPACK #-} !Bool
  }

  


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]


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


RE: [Haskell-cafe] Haskell mode for emacs - some questions

2007-06-19 Thread peterv
Thanks for the info.

Yes, but I can only use GHCI for error checking, because I'm using
GTK2HS/SOE which does not work well with GHCI under Windows, it only runs
when using GHC.

And when I will me using HopenGL, I will want performance, as I will be
doing experiments with particle systems, 3D rendering, etc. Basically the
stuff I did for many years but now using Haskell :)

Having to do anything more than hitting a key to compile and run an
application would simple be unacceptable from the point of view of an imp/OO
developer (all imp/OO IDEs have that). Furthermore, when programming
videogames or special effects, you have to run and test a lot, because what
you see on screen usually 
determines your next actions. 


-Original Message-
From: David House [mailto:[EMAIL PROTECTED] 
Sent: Tuesday, June 19, 2007 12:34 AM
To: peterv
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Haskell mode for emacs - some questions

peterv writes:
  - How can I just compile and run in one go without having to type ghc
  --make main.hs as arguments for the compile... command and then typing
  main.exe for shell command...? This is what you do all the time when
  using Visual Studio, Eclipse, etc: just hit the F5 key which builds all
the
  dependencies and runs one or more generated executables. Easy. Visual
  Haskell does this (in the cases it does not hang for some unknown
reason).
  Of course I could dig into ELISP, but somehow I feel this must be
supported
  somehow. 

Use C-c C-l to load the file into GHCi. This is better than just compiling
it:
you get an interactive environment in which to play around with, test out
functions, etc. You can still 'run' your program by typing 'main' in GHCi.

  - There seems to be support for Haskell Font Lock Symbols, which should
  convert \, - and maybe other symbols to good looking Unicode fonts. I
can't
  get the correct fonts working on Windows. Now as I understood this is not
  really supported because of indentation problems, as underneed the single
  Unicode arrow character is converted into -? This is unfortunate,
because
  that's one of the things I really like about Sun's Fortress: the usage of
  Unicode symbols makes the text look much more mathematically, versus the
  half-century-old ASCII text. Furthermore in almost all Haskell books the
  richer font symbols are used for clarity. Any hints on this topic?

I wouldn't be surprised if this code had bit-rotted, or if there never has
been
Windows support. It's a corner function, used by few and therefore not that
polished. By all means, try it out, and if it doesn't work, feel free to
submit
patches, but I doubt it'll get changed any time soon by a haskell-mode
developer
:)

-- 
-David House, [EMAIL PROTECTED]

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


[Haskell-cafe] Avoiding Non-exhaustive patterns in function f

2007-06-19 Thread peterv
Haskell is known for its very strong static type checking, which eliminates
a lot of runtime errors.

 

But the following simple program crashes at runtime:

 

data D = A | B

f A = True

main = print (f B)

 

I understand this has nothing to do with type checking, but why can't the
compiler give a warning about this? Or is this by design or because it is
impossible to check with more complex recursive data types?

 

Thanks,

Peter

 

 

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


RE: [Haskell-cafe] IDE? (and WHY I'm looking at Haskell)

2007-06-18 Thread peterv
Thanks for the nice info. I'm going to give it another try then...

When I said I don't want to learn Emacs, I meant not learning its LISP
architecture with the goal of creating my own custom Emacs... 

OT: The reasons I'm looking at Haskell are:

- the object oriented approach failed for me when working on large projects
in medium to large teams. OO works reasonably if you have a good design and
follow some rules, but no language enforces those rules (yet), so aliasing
and unwanted side effects leak all over and you spend a lot of time
debugging.
 
- I noticed I was using the immutable pattern a lot for solving problems
lately... So I got steered automatically towards the FP world, which is
immutable by definition. That is, excluding the IO world I guess, but as
far as I understand, monadic IO is also pure, in the sense it has no
aliasing, unless using unsafePerformIO. But since I'm a Haskell newbie, I'm
not going to claim I understand monads! ;-)

- After 20 years of hitting keyboards like a madman to reach yet another
crazy deadline, I got myself RSI in both arms (Workrave helps, but it's too
late :\) So I want to spend more time thinking than typing, and I certainly
don't want to type boiler plate code. But most OO languages are FULL of
boiler plate code, and are much more verbose than Haskell. 

- A last but not least, if all goes well, I will be teaching an undergrad
applied mathematics for videogame development course. This will be very
basic and practical mathematics. These students love games, so I want to let
then *play* with the math using a mathematical programming language. If
the school approves it (which is unlikely because the students will also be
learning C++ = confusing), this will most likely be very basic Haskell.
Being an old school C/C++ developer, I would find it unfortunate that the
students don't get to see some FP, because I believe FP can play an
important part in the future of videogame and even business software
development (even the giants in my industry seem to believe that in some
degree: see e.g.
http://blogs.msdn.com/charlie/archive/2007/01/26/anders-hejlsberg-on-linq-an
d-functional-programming.aspx and
http://www.st.cs.uni-sb.de/edu/seminare/2005/advanced-fp/docs/sweeny.pdf)

So, if I decide to use Haskell, I want my students to get playing right away
using a nice IDE, because the young videogame generation is even more
spoiled and impatient than I am :) 

Peter V


No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.0/852 - Release Date: 17/06/2007
08:23
 

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


RE: Re[2]: [Haskell-cafe] IDE?

2007-06-18 Thread peterv
Well, if I was 15 again and had no RSI in both arms, I certainly would
create a basic IDE as my first Haskell project, it would be fun ;) I've
looked at the code of Visual Haskell, but I'm not (yet/ever?) capable of
enhancing it (the Haskell part, the COM/C++ part is a lot easier for me). So
it's a bit of a chicken and egg problem. To adapt existing code for getting
a better editor, I need to learn Haskell. To really learn Haskell, I need to
start typing and doing concrete projects, but I want to type as less as
possible, so I need a good IDE. Furthermore, because of my RSI, I see my
future in teaching and not coding. And it will remain a hobby project,
because I'm not able to convince my colleagues to switch to Haskell, mostly
because it has no production-stable .NET backend and Visual Studio
integration (yet, I know its work in progress)

Anyway, I'll start with emacs again, maybe I see the light this time ;)

Peter

-Original Message-
From: Simon Peyton-Jones [mailto:[EMAIL PROTECTED] 
Sent: Monday, June 18, 2007 11:46
To: Peter Verswyvelen; haskell-cafe@haskell.org
Subject: RE: Re[2]: [Haskell-cafe] IDE?


| L-System using HOpenGL), from what I've read Haskell is indeed much better
than typical OO
| languages... So it *deserves* an easy entry level IDE that will get many
many more people started with
| it.

I think you are right about that.  Still, I hope this problem may in time
fix itself: the Haskell community will grow to the point where there enough
people like you who *want* such an IDE, that among their ranks will be some
who feel able to *build* it.  (I quite understand that you do not.)  The
Haskell community has historically been somewhat oriented towards emacs and
Unix, but if Haskell is to succeed in becoming more of a mainstream
language, it need to jump the cultural gap over to the (much larger) IDE and
Windows community.

Presumably Visual Studio or Eclipse are the right places to start, and there
are prototype Haskell IDEs for both, even if they are not ready for
production use.

plenty of opportunities here!

Simon

No virus found in this incoming message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.0/852 - Release Date: 17/06/2007
08:23
 

No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.0/852 - Release Date: 17/06/2007
08:23
 

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


RE: [Haskell-cafe] Useful IDE features - Accessibility considerations

2007-06-18 Thread peterv
Well, yes and no. 

 

Such an IDE does not have to follow the guidelines, because as you said,
these are “flexible”. Take Microsoft Office 2007, completely new GUI,
shocked the world. 

 

But take Eclipse. This is a fairly standard GUI, mostly the same on unix,
mac, and Windows.  

 

IMHO, for a Windows user coming from Visual Basic, Visual Studio, Borland
Delphi, etc, switching to Eclipse is much easier than switching to emacs.

 

Or take the Concurrent Clean IDE. Totally not a windows GUI. But easy to get
started with. Just install, open an example, select run and off you go. 

 

From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of PR Stanley
Sent: Monday, June 18, 2007 15:06
To: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Useful IDE features - Accessibility
considerations

 

Hi
not sure if this is a real project to build a Haskell IDE ... adherence to
the MS accessibility guidelines.  Ironically the VS environement  seems to
deviate from the corporation's own advice to the rest of the world.
Paul

 

No virus found in this incoming message.
Checked by AVG Free Edition.
Version: 7.5.472 / Virus Database: 269.9.0/852 - Release Date: 17/06/2007
08:23


No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.0/852 - Release Date: 17/06/2007
08:23
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Useful IDE features - implement instance

2007-06-18 Thread peterv
That looks cool.

Just another wild idea which I might find useful, but is more like
refactoring, is to convert the fields of a record to get/set type-classes,
and refactor all usages of those fields.

So 

---
data Person = Person { name :: String, age :: Float }

main = print $ name p ++  is  ++ show (age p) ++  years old
where p = Person { name = Homer, age = 41 }
---

Would refactor into (just wild Haskell code from a newbie here)

---
data Person = Person String Float

class HasName a where
nameOf :: a - String
withName :: a - String - a

class HasAge a where
ageOf :: a - Float
withAge :: a - Float - a

instance HasName Person where
nameOf (Person name age) = name
withName (Person name age) newName = Person newName age

instance HasAge Person where
ageOf (Person name age) = age
withAge (Person name age) newAge = Person name newAge

defaultPerson = Person  0

---
main = print $ nameOf p ++  is  ++ show(ageOf p) ++  years old
where p = defaultPerson `withName` Homer `withAge` 41
-- or just where p = Person Homer 41

---

Visual Studio, Eclipse, IntelliJ etc already have these kind of wizards to
encapsulate fields with setters getters for C#/Java, and also introduce
boiler plate code, although less of it. However, Haskell turns each field
into a separate type class, so this is much more reusable code than their OO
counterparts.

Peter

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Claus Reinke
Sent: Monday, June 18, 2007 14:24
To: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Useful IDE features - implement instance

 Another feature which would be cool for an IDE is: implement instance.
So
 you automatically get to see all the functions of a type class you need to
 implement. Using C#/Java, this is used all over the place.

sounds potentially useful, but perhaps not quite as useful as one might
expect: if you only want to see all the class methods, hugs/ghci provide 
the ':info' command (and haskell modes tend to provide access to that). 

$ ghc -e ':i Monad'
class Monad m where
  (=) :: m a - (a - m b) - m b
  () :: m a - m b - m b
  return :: a - m a
  fail :: String - m a
-- Defined in GHC.Base
instance Monad Maybe -- Defined in Data.Maybe
instance Monad IO -- Defined in GHC.IOBase
instance Monad [] -- Defined in GHC.Base

with a little bit of filtering and replacing, we get

$ ghc -e ':i Monad' | sed -n '/^class/,/-- Defined
in/{s/class/instance/;p}'
instance Monad m where
  (=) :: m a - (a - m b) - m b
  () :: m a - m b - m b
  return :: a - m a
  fail :: String - m a
-- Defined in GHC.Base

i've used sed here, to keep it editor-independent, one can do the
equivalent within emacs/vim, without sed. now, if one wanted to
save typing, one might want to translate the type declarations into
definition templates, but the type has more information than such
template, and there are many forms of definition that fit a type, so
having to replace the type declarations with definitions is perhaps 
as good as it gets?

a similarly useful code template generation transformation would 
be to introduce complete case distinctions over sum types, so that

f x = undefined

would, if we knew (x::Maybe a), become

f (Just a) = undefined
f Nothing = undefined

or 'doSomething = \(x::Either l r)-body' would become

doSomething = \x-case x of {Left l-body; Right r-body}

which, of course, should rather be

doSomething = either (\l-body) (\r-body)

yes, there are many opportunities for making haskell editing
easier, and not all of them require detailed editor hacking or
haskell analysis and transformation skills (though some do).


keep the suggestions coming. perhaps summarize them on a
haskell.org wiki page, though, so they don't get lost. someone
might get round to implementing them, some of them might
already be available!-)

if someone were to put up a simple table/list of desired ide
features (with brief descriptions) on the wiki, everyone could
add links to each feature showing how their favourite ide 
handles said feature. 

then new users could go through that list and choose to learn
one of those ides that provides most of the features they need.
and fans of a particular ide could use the list to pick any 
missing feature that they feel able to implement..

claus

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

No virus found in this incoming message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.0/852 - Release Date: 17/06/2007
08:23
 

No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.0/852 - Release Date: 17/06/2007
08:23
 


[Haskell-cafe] Haskell mode for emacs - some questions

2007-06-18 Thread peterv
I finally got emacs using Haskell-mode working. It seems that the latest
version of emacs support nice font smoothing on Windows; the last time I
looked it didn't. Auto indent works, inf-haskell works, really great. So far
so good.

But I have some questions I did not find in the wiki:

- How can I just compile and run in one go without having to type ghc
--make main.hs as arguments for the compile... command and then typing
main.exe for shell command...? This is what you do all the time when
using Visual Studio, Eclipse, etc: just hit the F5 key which builds all the
dependencies and runs one or more generated executables. Easy. Visual
Haskell does this (in the cases it does not hang for some unknown reason).
Of course I could dig into ELISP, but somehow I feel this must be supported
somehow. 

- There seems to be support for Haskell Font Lock Symbols, which should
convert \, - and maybe other symbols to good looking Unicode fonts. I can't
get the correct fonts working on Windows. Now as I understood this is not
really supported because of indentation problems, as underneed the single
Unicode arrow character is converted into -? This is unfortunate, because
that's one of the things I really like about Sun's Fortress: the usage of
Unicode symbols makes the text look much more mathematically, versus the
half-century-old ASCII text. Furthermore in almost all Haskell books the
richer font symbols are used for clarity. Any hints on this topic?

Thanks again!
Peter

No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.0/852 - Release Date: 17/06/2007
08:23
 

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


RE: [Haskell-cafe] IDE?

2007-06-17 Thread peterv
I just tried the Haskell Mode using xemacs, adjust my init.el file, loaded
my haskell file, and got great syntax highlighting! So far so good.

But people, emacs is so weird for a Windows user... 

For example, ALL windows (and motif?) programs use CTRL-Z for undo. But not
emacs... So after some googling, I found and installed CUA, to get more
Windows compliant keys. CTRL-Z does undo, woohoo! But CTRL-Y doesn't do redo
yet, as in ALL windows programs. Select a block, press delete. ALL Windows
text editors will delete the block, but not emacs, it just deselects the
block and deletes the current character. I also couldn't get the auto
indentation working, not sure why, I thought that pressing ENTER would
automatically indent my code, especially when I end my line with $. Pressing
TAB will not insert a TAB, like in ALL Windows editors.

I guess I could spend time to configure all the keys and behavior. Heck with
LISP you can do anything! Even change the addition operator into whatever
other binary operator, at runtime, at any time, as a side-effect, horror! ;)
But I have no interest in learning emacs, I just want to learn Haskell
without having to perform too much manual text editing that one does not
expect to do in the 21st century :) 

So I could erase my brain and figure out all the emacs keys. But then I will
have a hard time using ANY other Windows program.

I'm sure if all you use is Emacs, this must really be great, but for the
average Windows coder that is used thay ANY other popular IDE, switching is
not obvious at all...

No pun intended; I know Emacs is an incredible system (I used to work with
it on OS/2, and if I recall correctly, I could even read my email right
inside of it, heck it could even make me lispy breakfast! ;), but it's just
so... alien, at least when looking at it from a Windows perspective. 

And that's why IMHO for Windows users, one needs a friendly IDE to get
started with Haskell in a modern way. And the Windows version should comply
to the Windows styleguides. Haskell is such a nice language, it should reach
a larger audience, and just like Concurrent Clean, that could be done by
providing a simple IDE.

Phew, my frustration leaked into this email, but at least now I got rid of
it, sorry guys ;)

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Peter Verswyvelen
Sent: Saturday, June 16, 2007 10:35 PM
To: haskell-cafe@haskell.org
Subject: Re: Re[2]: [Haskell-cafe] IDE?

That's just my point. Although I have no practical experience with Haskell
(besides writing a simple L-System using HOpenGL), from what I've read
Haskell is indeed much better than typical OO languages... So it *deserves*
an easy entry level IDE that will get many many more people started with it.
Like Concurrent Clean has, although their IDE is also far from perfect (e.g.
they don't have multi-level undo, sigh)

Anyway, it seems many people use Emacs for their Haskell edit/compile/run
cycle. I've used Emacs on IBM OS/2 a long time ago so I guess I can get back
into it. But man, was I happy back then when I could switch over to Visual
Studio... The productivity I nowadays have with Visual Studio 2005 and
Resharper for doing compilation, code-documentation-tips, code-completion,
refactoring, navigation, debugging, boiler plate code generation, is
amazing. Some of my colleagues still use Emacs, and maybe they are not using
it correctly, but at first sight their development is much much slower.

From this cafe talk I now know such an IDE for Haskell does not exist. So I
won't search any further for a great IDE before starting to do some real
Haskell programming, because my L-Systems experiment was a lot of fun! 

So I just installed XEmacs with the latest Haskell mode. I'll go from
here... If that doesn't work, Notepad++ and GHCI/GHC in a command prompt
also works, although it does make me feel I'm back in the eighties.

Thanks for all the help folks!

- Oorspronkelijk bericht -
Van: Bulat Ziganshin [mailto:[EMAIL PROTECTED]
Verzonden: zaterdag, juni 16, 2007 08:50 PM
Aan: [EMAIL PROTECTED]
CC: haskell-cafe@haskell.org
Onderwerp: Re[2]: [Haskell-cafe] IDE?

Hello bf3,

Saturday, June 16, 2007, 3:23:40 PM, you wrote:

 The point I wanted to make is, that I can't find an
 easy-to-install-ready-to-use-and-rock-n-roll IDE for Windows that comes
with
 all or most of those features. I mean something like Borland TurboPascal

it's well-known trap. haskell is an order of magnitude better than
widespread OOP languages. why it's not used by everyone? just due to
shortage on libs, training and - yes - IDEs. programming in Delphi
in many cases need just clicking here and there

so, you got something, you lost something

ps: i use editor which supports only syntax highlighting. it's very
like working in tp 3.0 or quickc 1.0 - are you had such experience? :)



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]






RE: [Haskell-cafe] IDE?

2007-06-16 Thread PeterV
Thank for the reply. 

I'll try the emacs approach (or better Xemacs because Emacs on Windows has
really ugly font smoothing), but I must say that - being an old school
object-oriented programmer who got spoiled by fully integrated IDEs like
Borland's TurboPascal, Microsoft Visual Studio, and Eclipse - switching to
emacs or VIM is not an easy task :) Even on the commodore 64 I used a mini
IDE for writing 6502 assembler ;)

About Apple's Shake: this is a flow-graph based image composition package.
It's like a tiny bit of functional programming (limited to images as
values), represented as a graphical acyclic graph of functional nodes. Each
of these nodes computes a result, and this result can be visualized by
clicking on a button on each node, so you can debug the output of any
node. An Haskell IDE could do the same for functions (it's like dynamically
adding an unsafePerformIO print to the selected function). And then like
Visual Studio one should be able to write debugger visualizers
http://msdn2.microsoft.com/en-us/library/zayyhzts(VS.80).aspx

Peter


-Original Message-
From: Thomas Schilling [mailto:[EMAIL PROTECTED] 
Sent: Saturday, June 16, 2007 12:47 AM
To: [EMAIL PROTECTED]
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] IDE?

Yes this is kind of sad.  FWIW, here's how I currently approximate  
these features using Emacs + Haskell mode:

On 15 jun 2007, at 23.38, [EMAIL PROTECTED] wrote:

 I've searched the internet for an Haskell IDE that supports the  
 following:

 - syntax highlighting

haskell mode

 - cross module refactoring

there is HaRe, haven't tried it.

changing a function's type and then recompiling gives you a pretty  
useful todo-list though.  :)

 - quick navigation (goto symbol,

if you run hasktags you can use M-.

 goto instance,

not sure, maybe one could cook something up using grep or even hasktags

 find usages, etc)

M-x grep RET downarrow RET


 - code completion

either you use shim or the built-in M-/, which completes everything  
(not semantically sensitive, though)

 - debugging (not imperative debugging, so no breakpoints, but just
 plugging in a visualizer/pretty printer for a function in a separate
 dedicated window, like what http://www.apple.com/shake does on each  
 node)

i don't know shake, can you explain a bit more?

ghc HEAD has the ghci debugger, haven't tried it


 So a bit what Jetbrains Resharper does for Visual Studio, but for  
 Haskell.
 IntelliJ and Eclipse also do this for Java.

 This does not seem to exist? If this is correct, this is a real shame,
 because although I read that the productivity increases a lot when  
 correctly
 using Haskell, it would increase even more when such an IDE is  
 available.

i agree

/ Thomas



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


RE: Re[2]: [Haskell-cafe] IDE?

2007-06-16 Thread PeterV
Indeed, that's what I forgot to mention, Resharper in Visual Studio 2005
does that for C#, IntelliJ  Eclipse for Java. You rarely need compilation,
its syntax checker runs inplace and incrementally and shows you the errors
and warning in the right margin. That saves you a lot of time. 

For Haskell, the Eclipse plugin should do something like that, at least
every time you save. http://eclipsefp.sourceforge.net But I never got it to
work with GHC (only GHCI/Hugs), I tried on 3 different machines (on
Windows). 

I also guess this should not be too difficult to implement in Emacs... for
someone how knows Emacs that is. 

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Christopher Lane
Hinson
Sent: Sunday, June 17, 2007 12:15 AM
To: haskell-cafe@haskell.org
Subject: Re: Re[2]: [Haskell-cafe] IDE?


While we're on the topic of IDE features.

I wish to have an editor that ran GHC[I] every few seconds or so, and 
underlined sites of syntax errors in red.  This would save me a lot of 
back-and-forth.  If an editor did this, I would switch (from kate) in a 
heartbeat.

This has been mentioned before in only one place that I can find:

http://compilers.iecc.com/comparch/article/99-09-067

Yeah, I could do it myself.

--Lane
___
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