 
            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
 
            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.
 
            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
 
            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.
 
            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
 
            G'day all.
Quoting Peter Verswyvelen 
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
 
            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.
I don't see myself as typical Haskell user yet, I'm way to new to the language to consider myself a real "user". 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) I also needed functional dependencies, and usually my code does not compile without -fglasgow-exts, and I really don't know why :)
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.
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. 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. When diffing, whitespace, indentation, etc does not matter; the structure of the files is compared instead. A lot of metadata (for different views) can be attached to the syntax tree without cluttering my text files (like e.g. most version control systems do). I could go on like that, but the intentional programming website explains most of it. Cheers, Peter
 
            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.
 
            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
 
            On Thu, 03 Jan 2008 19:48:05 +0100, C.M.Brown 
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/ --
 
            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.
 
            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
 
            Hello Neil, Thursday, January 3, 2008, 9:57:10 PM, you wrote:
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.
what sort of code you are tried to develop? visual designers are successfully used for GUI design (not surprising) and SQL pure parts of my haskell program is just functions which takes some input (as arguments) and produce some output (as result). these functions are built from other functions and i don't see why it should be bad to represent this graphically instead of textually. moreover, Haskell is known as hard-to-read language (at least for beginners) due to its great power of function composition, and graphical representation of complex expressions may make easier their understanding -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
 
            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
 
            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, Bulat mailto:Bulat.Ziganshin@gmail.com
 
            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
 
            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
 
            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.
 
            Hello Peter, Thursday, January 3, 2008, 11:03:58 PM, you wrote:
Okay, but when using a syntax directed editor, type signatures can be automatically provided because the types are known.
the same is possible for Haskell - it's possible to add to code type signatures deduced by the compiler -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
 
            On Fri, 4 Jan 2008, Bulat Ziganshin wrote:
Hello Peter,
Thursday, January 3, 2008, 11:03:58 PM, you wrote:
Okay, but when using a syntax directed editor, type signatures can be automatically provided because the types are known.
the same is possible for Haskell - it's possible to add to code type signatures deduced by the compiler
Ha! Yes, HaRe also has the facility to do this.... have I plugged it enough yet? :-) Cheers, Chris.
 
            the same is possible for Haskell - it's possible to add to code type signatures deduced by the compiler Ha! Yes, HaRe also has the facility to do this.... have I plugged it enough yet? :-)
Sounds great! But could you add support for arrows so I can use it for my Yampa experiments? Please? :) ;)
 
            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 ...
 
            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
 
            On Jan 4, 2008 4:19 PM, Peter Verswyvelen 
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.
 
            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 -}
 
            On Jan 4, 2008 5:52 PM, 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 ;-)
-- | 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.
 
            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.
 
            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 ;-)
 
            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 :)
 
            On Mon, 7 Jan 2008, Emil Axelsson wrote:
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.
... which is especially annoying if you need the Show instance for an 'error'. Since 'error' denotes a programming error it should never be evaluated and thus the Show instance is only for cases which must not happen. Paradoxical. It would be interesting if it is possible to tunnel Show class dictionaries through to an 'error' like IO is tunneled to 'trace'.
 
            * Henning Thielemann wrote:
happen. Paradoxical. It would be interesting if it is possible to tunnel Show class dictionaries through to an 'error' like IO is tunneled to 'trace'.
unsafeShow :: (forall a . Show a => a) -> String
 
            The only possible definition of such a function is something like unsafeShow :: (forall a . Show a => a) -> String unsafeShow a = show (a :: Bool) right? And you'd also need to coerce the argument type in order to use it: putStrLn $ unsafeShow $ unsafeCoerce True Right? Then a nicer definition might be unsafeShow :: Show a => a -> b -> String unsafeShow a b = show (unsafeCoerce b `asTypeOf` a) Here is an example of how to use it to show an overloaded variable without changing the type signature: test :: Eq a => a -> IO () test a = putStrLn $ unsafeShow (undefined :: Int) a Of course, this only works safely if a is an Int: *Main> test (5 :: Int) 5 *Main> test (5 :: Double) 0 / Emil On 2008-01-07 12:56, Lutz Donnerhacke wrote:
* Henning Thielemann wrote:
happen. Paradoxical. It would be interesting if it is possible to tunnel Show class dictionaries through to an 'error' like IO is tunneled to 'trace'.
unsafeShow :: (forall a . Show a => a) -> String _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
 
            I think partial type signatures http://hackage.haskell.org/trac/haskell-prime/wiki/PartialTypeAnnotations would allow that kind of "tunneling". Is there any ongoing work on that? / Emil Henning Thielemann skrev:
On Mon, 7 Jan 2008, Emil Axelsson wrote:
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.
... which is especially annoying if you need the Show instance for an 'error'. Since 'error' denotes a programming error it should never be evaluated and thus the Show instance is only for cases which must not happen. Paradoxical. It would be interesting if it is possible to tunnel Show class dictionaries through to an 'error' like IO is tunneled to 'trace'. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
 
            Hello C.M.Brown, Thursday, January 3, 2008, 10:46:54 PM, you wrote:
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.
well, i don't worry about types of things with which i work. i know that it is a file, for example. its actual type depends on the information i need inside this function. it may start as FileInfo type, then after refactoring it will become CompressedFile or (fileInfo,FileSize) type. while it's great to know types of every variable to better understand how program works, adding type signatures means more work when writing program and when changing it. i want to express only data processing algorithm leaving all the details to compiler. for me, ghc just "reads thoughts" types and type signatures was required in classic languages to fight with errors. but in haskell omitting type signatures doesn't make program less reliable, so i don't need to write this extra code in addition to the essential - algorithm itself. for the same reason, i like pointless notation -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
 
            On Fri, Jan 04, 2008 at 02:23:31AM +0300, Bulat Ziganshin wrote:
Thursday, January 3, 2008, 10:46:54 PM, you wrote:
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.
well, i don't worry about types of things with which i work. i know that it is a file, for example. its actual type depends on the information i need inside this function. it may start as FileInfo type, then after refactoring it will become CompressedFile or (fileInfo,FileSize) type. while it's great to know types of every variable to better understand how program works, adding type signatures means more work when writing program and when changing it. i want to express only data processing algorithm leaving all the details to compiler. for me, ghc just "reads thoughts"
types and type signatures was required in classic languages to fight with errors. but in haskell omitting type signatures doesn't make program less reliable, so i don't need to write this extra code in addition to the essential - algorithm itself. for the same reason, i like pointless notation
True, it's not necessary to *write* the type signatures, but it's often helpful for those who want to read your code. Of course, they could always fire up ghci (with the right incantations) to find out the types of your function, but that's not always convenient. Also, type signatures often make bugs much easier to pinpoint. -- David Roundy Department of Physics Oregon State University
 
            On 2008-01-04 0:23, Bulat Ziganshin wrote:
Hello C.M.Brown,
Thursday, January 3, 2008, 10:46:54 PM, you wrote:
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.
well, i don't worry about types of things with which i work. i know that it is a file, for example. its actual type depends on the information i need inside this function. it may start as FileInfo type, then after refactoring it will become CompressedFile or (fileInfo,FileSize) type. while it's great to know types of every variable to better understand how program works, adding type signatures means more work when writing program and when changing it. i want to express only data processing algorithm leaving all the details to compiler. for me, ghc just "reads thoughts"
types and type signatures was required in classic languages to fight with errors. but in haskell omitting type signatures doesn't make program less reliable, so i don't need to write this extra code in addition to the essential - algorithm itself. for the same reason, i like pointless notation
You are wrong. Without type signatures some type errors will not be caught by the compiler, resulting in erroneous program behaviour. An example: makeURI file index = "http://192.168.0.1/somescript.php?file=" ++ urlEncode file ++ "&index=" ++ show index the intended signature for the above function is: String -> Int -> String, but suppose I've used it that way: makeURI "somefile.txt" "1" this is a type error, String was used where Int was expected, but the program compiles just fine. So now the string: http://192.168.0.1/somescript.php?file=somefile.txt&index="1" will be sent to the server which is of course wrong because http://192.168.0.1/somescript.php?file=somefile.txt&index=1 is expected. Without type declarations You are not using the full power of static type checking.
 
            Hello Bob, Sunday, January 6, 2008, 3:45:42 AM, you wrote:
You are wrong. Without type signatures some type errors will not be caught by the compiler, resulting in erroneous program behaviour.
of course. moreover, the same applies to any type inference. are you give explicit type signature to every expression in the program? -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (12)
- 
                 ajb@spamcop.net ajb@spamcop.net
- 
                 Bob Bob
- 
                 Bulat Ziganshin Bulat Ziganshin
- 
                 C.M.Brown C.M.Brown
- 
                 David Roundy David Roundy
- 
                 Emil Axelsson Emil Axelsson
- 
                 Felipe Lessa Felipe Lessa
- 
                 Henning Thielemann Henning Thielemann
- 
                 hjgtuyl@chello.nl hjgtuyl@chello.nl
- 
                 Lutz Donnerhacke Lutz Donnerhacke
- 
                 Neil Mitchell Neil Mitchell
- 
                 Peter Verswyvelen Peter Verswyvelen