Re: [Haskell-cafe] Refactoring status

2008-01-07 Thread Emil Axelsson
One approach to programming in Haskell, which I use all the time, is to write 
the type signature before the function body. This means that if I'm trying to do 
something strange, I will often be warned by the type checker even before I've 
written the strange code.


But I've also been bitten by the problem of having to change a lot of type 
signatures just because I want to e.g. show an overloaded variable.


/ Emil



On 2008-01-04 19:19, Peter Verswyvelen wrote:

Yes, sometimes it is neccerary to give an explicit type. But in so many
cases, type inference works fine no? What I usually do, is use the GHCi t:
command, copy/paste that in my code, and then make the type signature more
specific if it has to be. It's often funny to see how generic the code
really is :) 


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


RE: [Haskell-cafe] Refactoring status

2008-01-04 Thread Henning Thielemann

On Thu, 3 Jan 2008, Peter Verswyvelen wrote:

  I believe type signatures are the very essence of Haskell documentation!
  I'd much rather see a program with type signatures for functions and
  little (or no) comments over programs with no type signatures and
  ambigious comments (if any comments at all!).

 Okay, but when using a syntax directed editor, type signatures can be
 automatically provided because the types are known.

Types cannot always be derived automatically, especially when coming to
Haskell extensions. Sometimes you also want to restrict the type. E.g. for

  asTypeOf _ y = y

you explicitly want the type

  asTypeOf :: a - a - a

not the automatically derived one:

  asTypeOf :: b - a - a


 Furthermore, IMHO, type signatures alone are not enough, a good parameter
 name says at least as much as the type.

 E.g. what does a function Int - Int - Bool do? I have no idea. A good
 function name helps, e.g. isDivisible:: Int - Int - Bool. But then I still
 don't know which parameter is the numerator and denominator. So good names
 for the parameters are at least as important, e.g. isDivisible ::
 numerator:Int - denonimator:Int - Bool

It's a problem in Haskell that there are no unique parameter names, due to
pattern matching. E.g.

isDivisible _ 0 = error division by zero
isDivisible x y = ...


I'm tempted to write Haddock comments like

{- | check whether @x@ can be divided by @y@ -}
isDivisible :: Integral a = a - a - a

But this does not work, because unique parameter names cannot be extracted
from the code and are thus missing in Haddock documentation. If there
would not be pattern matching but only 'case' there wouldn't be a problem.

isDivisible x y =
   case (x,y) of
  (_,0) - error division by zero
  (x',y') - ...


Or even better, with a fictitious anonymous 'case' you could write:

isDivisible = curry $
   case
  (_,0) - error division by zero
  (x,y) - ...


  Type signatures really does make dealing with someone elses code that
  much easier.

 Yes, as is good documentation, which unfortunately is still limited to
 ASCII. I would prefer to have rich documentation right inside my source
 code, with math symbols, drawings, pictures, animations, whatever...

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


RE: [Haskell-cafe] Refactoring status

2008-01-04 Thread Peter Verswyvelen
 Types cannot always be derived automatically, especially when coming to
 Haskell extensions. Sometimes you also want to restrict the type. E.g. for
 asTypeOf _ y = y
 you explicitly want the type
 asTypeOf :: a - a - a
 not the automatically derived one:
 asTypeOf :: b - a - a

Yes, sometimes it is neccerary to give an explicit type. But in so many
cases, type inference works fine no? What I usually do, is use the GHCi t:
command, copy/paste that in my code, and then make the type signature more
specific if it has to be. It's often funny to see how generic the code
really is :) 

I wonder what a typical LISP/Scheme programmer thinks of type signatures...

 It's a problem in Haskell that there are no unique parameter names, due to
 pattern matching. 

Yes, but it would be nice to attach some parameter-comment to the types
no? Now a lot of documentation is written in the style the 7th parameter
is Not very user friendly :)

Cheers,
Peter


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


Re: [Haskell-cafe] Refactoring status

2008-01-04 Thread Felipe Lessa
On Jan 4, 2008 4:19 PM, Peter Verswyvelen [EMAIL PROTECTED] wrote:
 Yes, but it would be nice to attach some parameter-comment to the types
 no? Now a lot of documentation is written in the style the 7th parameter
 is Not very user friendly :)

Haddock allows you to put documentation inside the parameters. If you
function has that number of arguments, you can name them in the
parameter docs.

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


RE: [Haskell-cafe] Refactoring status

2008-01-04 Thread Henning Thielemann

On Fri, 4 Jan 2008, Peter Verswyvelen wrote:

 Yes, sometimes it is neccerary to give an explicit type. But in so many
 cases, type inference works fine no? What I usually do, is use the GHCi t:
 command, copy/paste that in my code, and then make the type signature more
 specific if it has to be. It's often funny to see how generic the code
 really is :)

Indeed.

  It's a problem in Haskell that there are no unique parameter names, due to
  pattern matching.

 Yes, but it would be nice to attach some parameter-comment to the types
 no? Now a lot of documentation is written in the style the 7th parameter
 is Not very user friendly :)

It's already possible to write

asTypeOf ::
 a   {- ^ the input value to be passed through -}
  - a   {- ^ the value is ignored, but the type is unified with the first 
parameter -}
  - a   {- ^ the value of the first parameter -}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Refactoring status

2008-01-04 Thread Peter Verswyvelen
 It's already possible to write
 asTypeOf ::
 a   {- ^ the input value to be passed through -}
  - a   {- ^ the value is ignored, but the type is unified with the first
parameter -}
  - a   {- ^ the value of the first parameter -}

Nice. Still using first parameter though ;-) 



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


Re: [Haskell-cafe] Refactoring status

2008-01-04 Thread Felipe Lessa
On Jan 4, 2008 5:52 PM, Peter Verswyvelen [EMAIL PROTECTED] wrote:
  It's already possible to write
  asTypeOf ::
  a   {- ^ the input value to be passed through -}
   - a   {- ^ the value is ignored, but the type is unified with the first
 parameter -}
   - a   {- ^ the value of the first parameter -}

 Nice. Still using first parameter though ;-)

-- | Pass through the input value but forces unification
--   of its type with the type of the other argument.
asTypeOf :: a -- ^ The input value to be passed through.
 - a -- ^ The other value whose type will be unified.
 - a -- ^ The input value.
asTypeOf = const

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


RE: [Haskell-cafe] Refactoring status

2008-01-04 Thread Henning Thielemann

On Fri, 4 Jan 2008, Peter Verswyvelen wrote:

  It's already possible to write
  asTypeOf ::
  a   {- ^ the input value to be passed through -}
   - a   {- ^ the value is ignored, but the type is unified with the first
 parameter -}
   - a   {- ^ the value of the first parameter -}

 Nice. Still using first parameter though ;-)

This was the problem I mentioned earlier.

I tend to write comments like

{- | @asTypeOf x y@  returns the value of @x@, while the types of @x@ and @y@ 
are unified   -}
asTypeOf :: a - a - a


This way I can introduce parameter names for the reader.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Refactoring status

2008-01-04 Thread Peter Verswyvelen
 Nice. Still using first parameter though ;-)

 This was the problem I mentioned earlier.
 I tend to write comments like
 {- | @asTypeOf x y@  returns the value of @x@, while the types of @x@ and
@y@ are unified   -}
 asTypeOf :: a - a - a
 This way I can introduce parameter names for the reader.

Ah, okay, I get it now. Sorry, I did not get much sleep yesterday ;-)


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


Re: [Haskell-cafe] Refactoring status

2008-01-03 Thread C.M.Brown
Hi Peter,

 Is any work being done on Haskell refactoring support, like HaRe or others?

HaRe is still very active and is due for a new release very soon.
There are probably in excess of 40 refactorings for HaRe in total now, and
I intend to add more! Sadly, I am currently the only maintainer left
on the project, so I am busy trying to implement new refactorings and
finish off my thesis.

 Is anyone actively using refactoring? When using C#, I used Resharper a lot,
 and ever since, I'm really hooked to refactoring, so I miss it a lot when
 doing Haskelling. (I never seem to get a function name or signature right
 the first time. is it just me? J)

The greatest problem that the HaRe group have experienced is that HaRe
supports Haskell 98. While this is the perfect model for academic
investigation and Haskell tool design, most of the real world use the de
facto standard of GHC haskell. We would really like HaRe to be ported over to 
GHC at some point
in the near future.

 I'm currently using Emacs with Haskell Mode (which does not offer
 refactoring support) but I think many of you use VIM (which does support
 it?)
 Can one use refactoring outside of an editor? This does not really sound
 practical,  but maybe it works?

HaRe works with both Emacs and VIM; you can also use it from a command
prompt meaning that it can be integrated into any tool that you require.
Indeed, there was even some investigation of porting it to Sub Etha Edit
with great success!

 PS: IMHO I don't think text should be the source format of our files. I
 think we should use a standarized decorated AST as the source, from which we
 can derive a textual (but also graphical) view and editor. Any comments on
 that? J

You mean a syntax-directed editor, right?

Kind regards,
Chris.

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


Re: [Haskell-cafe] Refactoring status

2008-01-03 Thread Neil Mitchell
Hi

 PS: IMHO I don't think text should be the source format of our files… I
 think we should use a standarized decorated AST as the source, from which we
 can derive a textual (but also graphical) view and editor… Any comments on
 that? J

Yes - I think you're wrong. I've seen non-textual editors for
programming languages, and they are severely unpleasant for all but
the most new beginners and restricted tasks.

There is a good chance that you can derive graphical views of source
code (call flow graphs, module dependencies etc) which perhaps could
be used to modify one particular sort of information in the code.
Other than that, I'd say text is going to remain the way forward.

Thanks

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


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread Peter Verswyvelen
 HaRe works with both Emacs and VIM; you can also use it from a command
 prompt meaning that it can be integrated into any tool that you require.
 Indeed, there was even some investigation of porting it to Sub Etha Edit
 with great success!

Cool! I'll check it out. However, I'm using some GHC extensions, so that is
indeed a show stopper :)

 You mean a syntax-directed editor, right?

Yes, but also that a compiler should directly read the syntax tree; the
frontend part of the compiler should really be the editor, providing
round-trip editing between text - AST. Nothing new really, I used to work
with a 6502 assembler on the Commodore 64 that did exactly that :)

Cheers,
Peter

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


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread C.M.Brown
 Cool! I'll check it out. However, I'm using some GHC extensions, so that
is
 indeed a show stopper :)

Which extensions are you using that are not Haskell 98? I would be very
interested to know what users would generally require from a refactorer.

  You mean a syntax-directed editor, right?

 Yes, but also that a compiler should directly read the syntax tree; the
 frontend part of the compiler should really be the editor, providing
 round-trip editing between text - AST. Nothing new really, I used to
work
 with a 6502 assembler on the Commodore 64 that did exactly that :)

I agree with Neil, AST editors are generally ugly and hard to use. There
is also the problem of laying out Haskell code. Everyone uses their own
layout style and pretty printing ASTs is generally a bad thing to do in
this context.

Cheers,
Chris.

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


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread Peter Verswyvelen
 Yes - I think you're wrong. I've seen non-textual editors for
 programming languages, and they are severely unpleasant for all but
 the most new beginners and restricted tasks.

For programmers and mathematicians, you are absolutely right. For beginners
and people who have highly developed visual skills (like computer graphic
artists), I'm afraid you are wrong. Most of the latter would never even try
to look at something like Haskell, while many of them are actually using a
(subset of) a dataflow or functional language (Apple's Shake, SideFX
Houdini, Digital Fusion, the Unreal 3 Game Engine, the Spirops AI system,
just to name a few). Most of these application also provide a textual
interface, but artists mostly prefer the graphical view.

 There is a good chance that you can derive graphical views of source
 code (call flow graphs, module dependencies etc) which perhaps could
 be used to modify one particular sort of information in the code.
 Other than that, I'd say text is going to remain the way forward.

But now everybody is developing their own parsers and structured data
representation for Haskell tools no, because text is the standard? 

Cheers,
Peter



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


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread Peter Verswyvelen
 I agree with Neil, AST editors are generally ugly and hard to use. There
 is also the problem of laying out Haskell code. Everyone uses their own
 layout style and pretty printing ASTs is generally a bad thing to do in
 this context.

I actually meant something more like
http://en.wikipedia.org/wiki/Intentional_programming

Cheers,
Peter


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


Re: [Haskell-cafe] Refactoring status

2008-01-03 Thread Bulat Ziganshin
Hello Peter,

Thursday, January 3, 2008, 9:13:27 PM, you wrote:

well, i use refactoring without help of any tool. according to my
own experience, it's much easier in Haskell than in other languages i
know - basically, you just cut-n-paste your code around. i don't use
type signatures at all - this creates some problems when i wrote large
portion of code and try to make it compile, but nothing more

 
   
   
 Hi all,
   
  
   
 Is any work being done on Haskell refactoring support, like HaRe or others?
   
  
   
 Is anyone actively using refactoring? When using C#, I used
 Resharper a lot, and ever since, I▓m really hooked to refactoring,
 so I miss it a lot when doing Haskelling. (I never seem to get a
 function name or signature right the first time┘ is it just me? J)
   
  
   
 I▓m currently using Emacs with Haskell Mode (which does not offer
 refactoring support) but I think many of you use VIM (which does support it?)
   
  
   
 Can one use refactoring outside of an editor? This does not really
 sound practical,  but maybe it works?
   
  
   
 Thank you,
   
 Peter
   
  
   
 PS: IMHO I don▓t think text should be the source format of our
 files┘ I think we should use a standarized decorated AST as the
 source, from which we can derive a textual (but also graphical) view
 and editor┘ Any comments on that? J
   
  
   
  
   
  
   
  
   

  
  
   
  
   
   
 


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Refactoring status

2008-01-03 Thread C.M.Brown
Hi Bulat,

 i don't use
 type signatures at all - this creates some problems when i wrote large
 portion of code and try to make it compile, but nothing more

I believe type signatures are the very essence of Haskell documentation!
I'd much rather see a program with type signatures for functions and
little (or no) comments over programs with no type signatures and
ambigious comments (if any comments at all!).

Type signatures really does make dealing with someone elses code that
much easier.

Regards,
Chris.


 
 
 
  Hi all,
 
   
 
  Is any work being done on Haskell refactoring support, like HaRe or others?
 
   
 
  Is anyone actively using refactoring? When using C#, I used
  Resharper a lot, and ever since, I▓m really hooked to refactoring,
  so I miss it a lot when doing Haskelling. (I never seem to get a
  function name or signature right the first time┘ is it just me? J)
 
   
 
  I▓m currently using Emacs with Haskell Mode (which does not offer
  refactoring support) but I think many of you use VIM (which does support 
  it?)
 
   
 
  Can one use refactoring outside of an editor? This does not really
  sound practical,  but maybe it works?
 
   
 
  Thank you,
 
  Peter
 
   
 
  PS: IMHO I don▓t think text should be the source format of our
  files┘ I think we should use a standarized decorated AST as the
  source, from which we can derive a textual (but also graphical) view
  and editor┘ Any comments on that? J
 
   
 
   
 
   
 
   
 

 
 
 
   
 
 
 



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


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread C.M.Brown
 Currently, I'm trying to learn arrows and Yampa (mainly to see how well it
 compares to my own dataflow/reactive stuff that was written in C#, C++ and
 assembler)

Arrows won't work with HaRe at the moment, therefore Yampa won't either;
which is a shame.

 First of all, let's see if I get the concept of a syntax directed editor
 right. The idea is, that I (or my company), has a specific indentation rule,
 naming convention rule, etc... When I get code from someone else (in a
 syntax tree form ala XML), it will immediately show the text using my
 conventions.

Yep, this was what I was thinking to some extent.

Furthermore, when I need to perform refactoring, a rename is
 just *one* change to the entire system, no matter how many other files use
 the name; no more merging for stupid renames.

I'm a little confused as to what you mean here. A renaming renames all
(and only those) uses of an identifier within a particular definition, and
not every use of a particular name. The binding structure of the program
must not be affected; and there must be no introduction of ambiguity in
the namespace. You can do this with HaRe, but HaRe currently refactors
Programatica data types. If you can
somehow convert your AST into what HaRe expects then the refactoring will
work, but you will need to tweak our pretty printer (and turn off layout
preservation).

When diffing, whitespace,
 indentation, etc does not matter; the structure of the files is compared
 instead.

There is also (preliminary at the moment) duplicate code detection built
into HaRe. This is based on the principle of looking at the shape of functions 
and
expressions, concentrating on where variables are bound and whether one
term is an intance of another. Duplicate expressions can be converted into
a more general abstraction, transforming the duplicate expressions into
function calls (parameterised by their differences).

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


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread C.M.Brown
 Furthermore, IMHO, type signatures alone are not enough, a good parameter
 name says at least as much as the type.

Yes! A very good point! :)


 E.g. what does a function Int - Int - Bool do? I have no idea. A good
 function name helps, e.g. isDivisible:: Int - Int - Bool. But then I still
 don't know which parameter is the numerator and denominator. So good names
 for the parameters are at least as important, e.g. isDivisible ::
 numerator:Int - denonimator:Int - Bool


I agree. But I was generally thinking of more complex functions than this,
especially if they use some kind of user-defined monad and have implicit
parameters, say.

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


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread Peter Verswyvelen
 I believe type signatures are the very essence of Haskell documentation!
 I'd much rather see a program with type signatures for functions and
 little (or no) comments over programs with no type signatures and
 ambigious comments (if any comments at all!).

Okay, but when using a syntax directed editor, type signatures can be
automatically provided because the types are known. 

Furthermore, IMHO, type signatures alone are not enough, a good parameter
name says at least as much as the type. 

E.g. what does a function Int - Int - Bool do? I have no idea. A good
function name helps, e.g. isDivisible:: Int - Int - Bool. But then I still
don't know which parameter is the numerator and denominator. So good names
for the parameters are at least as important, e.g. isDivisible ::
numerator:Int - denonimator:Int - Bool

 Type signatures really does make dealing with someone elses code that
 much easier.

Yes, as is good documentation, which unfortunately is still limited to
ASCII. I would prefer to have rich documentation right inside my source
code, with math symbols, drawings, pictures, animations, whatever... 

Cheers,
Peter


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


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread Peter Verswyvelen
 Furthermore, when I need to perform refactoring, a rename is
  just *one* change to the entire system, no matter how many other files
use
  the name; no more merging for stupid renames.
 I'm a little confused as to what you mean here. A renaming renames all
 (and only those) uses of an identifier within a particular definition, and
 not every use of a particular name. The binding structure of the program

Suppose we have a file Foo.hs, with the content:

foo ::Int
foo = 42

Translated into a syntax tree, this might look like (majorly simplified)

Definition id=68684 name=foo
Constant value=42 type=Int/
/Definition

and a file Bar.hs, with

bar :: Int
bar = foo + 27

or translated

Definition id=577647 name=bar
Add
 Reference id=68684/
   Constant value=27 type=Int/
/Add
/Definition

If you rename foo, using textual representation, both Foo.hs and Bar.hs will
be touched / checked-out.

However, if you work directly on the structure, then only the Foo XML file
is changed, Bar is not changed at all.

Of course this might only be the case with renames, more complex
refactorings usually require modifying other files :) 

Anyway, I hate merges caused by renames by others. And many developers tend
to leave names as they are, because you get used to strange names anyway...
A good example is Microsoft's Windows Presentation Foundation code: what do
you think the method FindName on an element tree does? It searches for an
element with a particular name, and returns that element ;)

 There is also (preliminary at the moment) duplicate code detection built
 into HaRe. This is based on the principle of looking at the shape of
functions and
 expressions, concentrating on where variables are bound and whether one
 term is an intance of another. Duplicate expressions can be converted into
 a more general abstraction, transforming the duplicate expressions into
 function calls (parameterised by their differences).

Impressive!

Cheers,
Peter


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


Re: [Haskell-cafe] Refactoring status

2008-01-03 Thread hjgtuyl

On Thu, 03 Jan 2008 19:48:05 +0100, C.M.Brown [EMAIL PROTECTED] wrote:

HaRe is still very active and is due for a new release very soon.
There are probably in excess of 40 refactorings for HaRe in total now,  
and

I intend to add more! Sadly, I am currently the only maintainer left
on the project, so I am busy trying to implement new refactorings and
finish off my thesis.



A possible first goal would be, to add extensions that are definitely in  
Haskell prime, see:

  
http://hackage.haskell.org/trac/haskell-prime/wiki/Status'#definitely-inProposalStatus



HaRe works with both Emacs and VIM; you can also use it from a command
prompt meaning that it can be integrated into any tool that you require.
Indeed, there was even some investigation of porting it to Sub Etha Edit
with great success!



It would be nice to have it built in to the functional programming  
extensions of Eclipse

( http://eclipsefp.sourceforge.net/ )

--
Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://functor.bamikanarie.com
http://Van.Tuyl.eu/
--

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


RE: [Haskell-cafe] Refactoring status

2008-01-03 Thread ajb

G'day all.

Quoting Peter Verswyvelen [EMAIL PROTECTED]:


I actually meant something more like
http://en.wikipedia.org/wiki/Intentional_programming


I'm pretty sure that Intentional programming is Hungarian for I want
to sell you another IDE.

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


Re: [Haskell-cafe] Refactoring status

2008-01-03 Thread C.M.Brown
Hi,

 A possible first goal would be, to add extensions that are definitely in
 Haskell prime, see:

 http://hackage.haskell.org/trac/haskell-prime/wiki/Status'#definitely-inProposalStatus

Oh great! Thanks for the link, I think the main issue is moving over to a
platform that is heavily maintained (such as GHC) and then working
towards, say, haskell prime coverage as a first goal.

 It would be nice to have it built in to the functional programming
 extensions of Eclipse
 ( http://eclipsefp.sourceforge.net/ )

Yes, I actually did some work on this but due to time restrictions it was
never finished. However, it wouldn't be difficult to add HaRe to any type
of interactive environment. HaRe is called from the command prompt and
requires positional and region information from the editor together with
the facility to display a prompt and read answers.

I would love to be able to work with people who may be interested in
porting HaRe to editors such as Eclipse... :)

Cheers,
Chris.

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