How do you rewrite your code?

There are numerous threads on the Haskell Café involving rewriting, refactoring, refining, and in general improving code (for some definition of improve). I am interested in seeing examples of how Haskell code can be rewritten to make it better. Some general examples are: - Eta-reduce - Make more pointfree - Introduce monadic operators or do-notation - e.g. for Maybe, lists, State - Eliminate monadic operators or do-notation - Generalize types - e.g. change map to fmap, (++) to mappend - Use instances of Functor, Applicative, Alternative, Category, Arrow, Monoid, Traversable, etc. - Use library functions from Data.List, Data.Map, Data.Set, etc. - Use some form of generic programming (e.g. SYB, Uniplate, EMGM, Alloy) - Use other libraries not included in the Platform My question is simple: *How do you rewrite your code to improve it?* You can answer this in any way you like, but I think the most useful answer is to show a reasonably small, concrete example of what your code looked like before and after. Also, please describe how you think the rewrite improves such code. - Is it better style? More useful? More efficient? - Are the types (before and after) the same? - Are the semantics the same? - How did you prove or test equivalence? (e.g. Can you use equational reasoning to confirm the rewrite is valid? Did you use QuickCheck?) Here is an example that I find myself doing occasionally. For all x, f: x >>= return . f --> fmap f x or f <$> x -- requires importing Control.Applicative I think the right-hand side (RHS) is more concise and simpler. The types here do change: the type constructor has a Monad constraint in the left-hand side and a Functor constraint in the RHS. Types that are Monad instances are generally also Functor instances, so this is often possible. I'm convinced the semantics are preserved, though I haven't proven it. What's an example of a rewrite that you've encountered? Thanks, Sean

Not exactly answering your question, but here's the top refactorings that I'd like to see in a Haskell IDE: * rename identifier (aware of scopes, modules, qualified imports etc.) * move definition from one module to another (aware of ...) * change "type" to "newtype" or "data" * change positional to named record notation * introduce parameter (to function) (with a default value that is plugged in at each call site) * change order of parameters * introduce parameter object That's the kind of basic rewriting that is really really awkward to do with a plain text editor (because you really need the annotated AST, with names resolved, and types attached) - so it's usually avoided (well, by me) and the result is code that is a nightmare to maintain.

For the style part, I recommend hlint [1]. Regarding the testing, QuickCheck is excellent and I have been happy with it so far.
From a more general point of view, I agree with a point of view that many haskellers seem to share, but that Cale Gibbard put in words on #haskell regularly. It consists in looking at your code from a higher point of view and trying to express what you wrote in a "sublanguage" of primitives and combinators. He pointed to [2] for more details and examples.
Hope it helps.
[1] http://community.haskell.org/~ndm/hlint/
[2] http://contracts.scheming.org/
On Tue, Mar 2, 2010 at 8:20 PM, Sean Leather
There are numerous threads on the Haskell Café involving rewriting, refactoring, refining, and in general improving code (for some definition of improve). I am interested in seeing examples of how Haskell code can be rewritten to make it better. Some general examples are:
- Eta-reduce - Make more pointfree - Introduce monadic operators or do-notation - e.g. for Maybe, lists, State - Eliminate monadic operators or do-notation - Generalize types - e.g. change map to fmap, (++) to mappend - Use instances of Functor, Applicative, Alternative, Category, Arrow, Monoid, Traversable, etc. - Use library functions from Data.List, Data.Map, Data.Set, etc. - Use some form of generic programming (e.g. SYB, Uniplate, EMGM, Alloy) - Use other libraries not included in the Platform
My question is simple:
*How do you rewrite your code to improve it?*
You can answer this in any way you like, but I think the most useful answer is to show a reasonably small, concrete example of what your code looked like before and after. Also, please describe how you think the rewrite improves such code.
- Is it better style? More useful? More efficient? - Are the types (before and after) the same? - Are the semantics the same? - How did you prove or test equivalence? (e.g. Can you use equational reasoning to confirm the rewrite is valid? Did you use QuickCheck?)
Here is an example that I find myself doing occasionally.
For all x, f:
x >>= return . f --> fmap f x or f <$> x -- requires importing Control.Applicative
I think the right-hand side (RHS) is more concise and simpler. The types here do change: the type constructor has a Monad constraint in the left-hand side and a Functor constraint in the RHS. Types that are Monad instances are generally also Functor instances, so this is often possible. I'm convinced the semantics are preserved, though I haven't proven it.
What's an example of a rewrite that you've encountered?
Thanks, Sean
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alp Mestanogullari http://alpmestan.wordpress.com/ http://alp.developpez.com/

On Tue, Mar 02, 2010 at 08:20:30PM +0100, Sean Leather wrote:
There are numerous threads on the Haskell Café involving rewriting, refactoring, refining, and in general improving code (for some definition of improve). I am interested in seeing examples of how Haskell code can be rewritten to make it better. Some general examples are:
One handy manual transformation is trying to do more checks on the typechecker. GADT's + phantom types are very useful!
x >>= return . f --> fmap f x or f <$> x -- requires importing Control.Applicative
I think the right-hand side (RHS) is more concise and simpler. The types here do change: the type constructor has a Monad constraint in the left-hand side and a Functor constraint in the RHS. Types that are Monad instances are generally also Functor instances, so this is often possible. I'm convinced the semantics are preserved, though I haven't proven it.
Yes, they are the same, always. -- Felipe.

Am Dienstag 02 März 2010 21:00:56 schrieb Felipe Lessa:
I think the right-hand side (RHS) is more concise and simpler. The types here do change: the type constructor has a Monad constraint in the left-hand side and a Functor constraint in the RHS. Types that are Monad instances are generally also Functor instances, so this is often possible. I'm convinced the semantics are preserved, though I haven't proven it.
Yes, they are the same, always.
Provided the instances obey the monad/functor laws.
-- Felipe.

Speaking about macrorewriting, I do prefer to break big modules (prototypes) into smaller ones, then step by step separate them into a set of minimally dependent and highly general cabal packages. As for microrewriting I find it to be a good practice to explicate all possible (programmable or Real World) errors into dedicated ADT constructions. This draws enough attention to every error to guarantee that there is no missed risks and protection is good enough. Regards, Andrey -- View this message in context: http://old.nabble.com/How-do-you-rewrite-your-code--tp27760033p27760681.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Tue, Mar 2, 2010 at 11:20 AM, Sean Leather
For all x, f:
x >>= return . f --> fmap f x or f <$> x -- requires importing Control.Applicative
I think the right-hand side (RHS) is more concise and simpler. The types here do change: the type constructor has a Monad constraint in the left-hand side and a Functor constraint in the RHS. Types that are Monad instances are generally also Functor instances, so this is often possible. I'm convinced the semantics are preserved, though I haven't proven it.
(Hand-wavy part of proof) I believe that by parametricity, any two functions of the type: mapX :: forall a b. (a -> b) -> (X a -> X b) that satisfy the functor laws: mapX f . mapX g = mapX (f . g) mapX id = id must be equal to one another, and therefore equal to fmap. (formal part of proof): given any monad M, let mapM f m = m >>= return . f mapM id m -- apply mapM = m >>= return . id -- apply (.) = m >>= (\x -> return (id x)) -- apply id = m >>= (\x -> return x) -- eta reduce = m >>= return -- monad right identity = m -- un-apply id = id m (mapM f . mapM g) m -- apply (.) = mapM f (mapM g m) -- apply mapM twice = (m >>= return . g) >>= return . f -- apply (.) twice = (m >>= \x -> return (g x)) >>= \y -> return (f y) -- monad associativity = m >>= (\x -> return (g x) >>= \y -> return (f y)) -- monad left identity = m >>= (\x -> (\y -> return (f y)) (g x)) -- beta reduce = m >>= (\x -> return (f (g x))) -- unapply (.) = m >>= (\x -> return ((f . g) x)) -- unapply (.) = m >>= (\x -> (return . (f . g)) x) -- eta reduce = m >>= return (f . g) -- un-apply mapM = mapM (f . g) m So, we have mapM id m = id m (mapM f . mapM g) m = mapM (f . g) m and by extensionality mapM id = id mapM f . mapM g = mapM (f . g) So, if the handwavy part of the proof at the beginning holds, mapM = fmap, and your translation is sound. -- ryan

On 2 March 2010 19:20, Sean Leather
My question is simple:
How do you rewrite your code to improve it?
Hi Sean - excellent question! Some things I do... Quite often I do a 'worker-wrapper-lite' rewrite i.e. change a function to perform its recursive work in a step rather than calling the function again with all the arguments, e.g.
para :: (a -> ([a], b) -> b) -> b -> [a] -> b para phi b = step where step [] = b step (x:xs) = phi x (xs, step xs)
rather than...
para_ :: (a -> ([a], b) -> b) -> b -> [a] -> b para_ phi b [] = b para_ phi b (x:xs) = phi x (xs, para_ phi b xs)
I'm doing no type changing to improve efficiency so it isn't a real worker-wrapper, but I usually find the 'step' style more pleasing, especially when the code is somewhat more complicated than the paramorphism above. Another one is to eliminate do-notation, generally I do this by using the liftM2 family more appropriately, sometimes by using my own monadic combinators - for instance quite a few operators in Control.Exception are useful for other monads rather than IO so I've versions with more general types in the Utils module that add to my projects once they get above a certain size. Generally my types change only when I realize I hadn't got them right in the first instance. I can't think of instances where I've generalized types to make them functors and so could use Traversable, Foldable... But I have had a couple instances where I've needed to change the type of a 'leaf' in a structure so realized that the containing structure was obviously a functor. Best wishes Stephen

Stephen Tetley schrieb:
On 2 March 2010 19:20, Sean Leather
wrote: My question is simple:
How do you rewrite your code to improve it?
Hi Sean - excellent question!
Some things I do...
Quite often I do a 'worker-wrapper-lite' rewrite i.e. change a function to perform its recursive work in a step rather than calling the function again with all the arguments, e.g.
para :: (a -> ([a], b) -> b) -> b -> [a] -> b para phi b = step where step [] = b step (x:xs) = phi x (xs, step xs)
rather than...
para_ :: (a -> ([a], b) -> b) -> b -> [a] -> b para_ phi b [] = b para_ phi b (x:xs) = phi x (xs, para_ phi b xs)
I'm doing no type changing to improve efficiency so it isn't a real worker-wrapper, but I usually find the 'step' style more pleasing, especially when the code is somewhat more complicated than the paramorphism above.
Me too. http://haskell.org/haskellwiki/Top-level_vs._local_recursion I have written some articles in Category:Style on that topic.

Something I've been doing a lot lately is selective
defunctionalisation, transformation into continuation passing style,
and the combination of both things (CPS followed by defunctionalising
the continuations). This is probably because I'm playing around with
lambda calculus evaluators a lot though :-) (see Olivier Danvy's
homepage for more: http://www.cs.au.dk/~danvy/)
Cheers,
Max
On 2 March 2010 19:20, Sean Leather
There are numerous threads on the Haskell Café involving rewriting, refactoring, refining, and in general improving code (for some definition of improve). I am interested in seeing examples of how Haskell code can be rewritten to make it better. Some general examples are:
Eta-reduce Make more pointfree Introduce monadic operators or do-notation
e.g. for Maybe, lists, State
Eliminate monadic operators or do-notation Generalize types
e.g. change map to fmap, (++) to mappend
Use instances of Functor, Applicative, Alternative, Category, Arrow, Monoid, Traversable, etc. Use library functions from Data.List, Data.Map, Data.Set, etc. Use some form of generic programming (e.g. SYB, Uniplate, EMGM, Alloy) Use other libraries not included in the Platform
My question is simple:
How do you rewrite your code to improve it?
You can answer this in any way you like, but I think the most useful answer is to show a reasonably small, concrete example of what your code looked like before and after. Also, please describe how you think the rewrite improves such code.
Is it better style? More useful? More efficient? Are the types (before and after) the same? Are the semantics the same? How did you prove or test equivalence? (e.g. Can you use equational reasoning to confirm the rewrite is valid? Did you use QuickCheck?)
Here is an example that I find myself doing occasionally.
For all x, f:
x >>= return . f --> fmap f x or f <$> x -- requires importing Control.Applicative
I think the right-hand side (RHS) is more concise and simpler. The types here do change: the type constructor has a Monad constraint in the left-hand side and a Functor constraint in the RHS. Types that are Monad instances are generally also Functor instances, so this is often possible. I'm convinced the semantics are preserved, though I haven't proven it.
What's an example of a rewrite that you've encountered?
Thanks, Sean
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

*How do you rewrite your code to improve it?*
Edward Kmett just introduced one in another thread. Simplifying, it would be this: For all x, y, f: do { x' <- x ; y' <- y ; return (f x' y') } --> f <$> x <*> y This is a great example, because (1) it reduces clutter and "temporary" names and (2) requires significant background knowledge on monads and idioms. We can also generalize this to functions f with increasing arity (f <$> x <*> y <*> z, etc.). Beginners would not get this, but once you know this rule, it can greatly improve your coding style. Similarly with liftM2, liftM3, etc. as mentioned by Stephen. Any other useful tidbits to share? Sean

Hi Sean, that's certainly *the* question I try to solve too. My thoughts on this are a bit different from the answers I've seen here so far, apart maybe from the "Contracts" response. All my code, whether neat or not so neat is still way too concrete, too direct. I think the correct answer is one should try to find abstractions and not code straight down to the point. Which to me is still a really tough one, I have to admit. Günther

All my code, whether neat or not so neat is still way too concrete, too direct. I think the correct answer is one should try to find abstractions and not code straight down to the point. Which to me is still a really tough one, I have to admit.
Taking this cue, since you've raised it before, and because the current thread holds my favourite answer to your problem: "Small moves, Ellie, small moves.." :-) Don't think of "finding abstractions" as an all-or-nothing problem. One good way of finding good abstractions is to start with straight code, to get the functionality out of the way, then try to abstract over repetitive details, improving the code structure without ruining the functionality. The abstractions you're trying to find evolved this way, and can be understood this way, as can new abstractions that have not been found yet. There are, of course, problems one cannot even tackle (in any practical sense) unless one knows some suitable abstractions, and design pattern dictionaries can help to get up to speed there. But unless one has learned to transform straight code into nicer/more concise/more maintainable code in many small steps, using other people's nice abstractions wholesale will remain a "Chinese room" style black art. For instance, the whole point of "refactoring" is to separate general code rewriting into rewrites that change observable behaviour (API or semantics), such as bug fixes, new features, and those that don't change observable behaviour, such as cleaning up, restructuring below the externally visible API, and introducing internal abstractions. Only the latter group fall under refactoring, and turn out to be a nice match to the equational reasoning that pure-functional programmers value so highly. What that means is simply that many small code transformations are thinkable without test coverage (larger code bases should still have tests, as not every typo/thinko is caught by the type system). Even better, complex code transformations, such as large-scale refactorings, can be composed from those small equational-reasoning-based transformations, and these small steps can be applied *without having to understand what the code does* (so they are helpful even for exploratory code reviews: transform/simplify the code until we understand it - if it was wrong before, it will still be wrong the same way, but the issues should be easier to see or fix).
From a glance at this thread, it seems mostly about refactorings/ meaning-preserving program transformations, so it might be helpful to keep the customary distinction between rewriting and refactoring in mind. A couple of lessons we learned in the old "refactoring functional programs" project:
1 refactoring is always with respect to a boundary: things within that boundary can change freely, things beyond need to stay fixed to avoid observable changes. It is important to make the boundary, and the definition of "observable change" explicit for every refactoring session (it might simply mean denotational equivalence, or operational equivalence, or API equivalence, or performance equivalence, or..) 2. refactoring is always with respect to a goal: adding structure, removing structure, changing structure, making code more readable, more maintainable, more concise, .. These goals often conflict, and sometimes even lie in opposite directions (eg.,removing clever abstractions to understand what is going on, or adding clever abstractions to remove boilerplate), so it is important to be clear about the current goal when refactoring. Hth, Claus PS. Obligatory nostalgia: - a long time ago, HaRe did implement some of the refactorings raised in this thread (more were catalogued than implemented, and not all suggestions in this thread were even catalogued, but the project site should still be a useful resource) http://www.cs.kent.ac.uk/projects/refactor-fp/ A mini demo that shows a few of the implemented refactorings in action can be found here: http://www.youtube.com/watch?v=4I7VZV7elnY - once upon a time, a page was started on the haskell wiki, to collect experiences of Haskell code rewriting in practice (the question of how to find/understand advanced design patterns governs both of the examples listed there so far, it would be nice if any new examples raised in this thread would be added to the wiki page) http://www.haskell.org/haskellwiki/Equational_reasoning_examples

Sean Leather
My question is simple:
*How do you rewrite your code to improve it?*
The short answer is: I don't. Long answer: In the Haskell community there is a strong bias towards making your code as generic and abstract as possible. That's not because it is the recommended coding style (there is no official recommendation here), but simply because you can do it in Haskell and more importantly you can do it _easily_ compared to other languages, without (necessarily) making your code obscure. Genericity and abstraction are supposed to make coding more efficient, and if you understand them well, they do just that. However, there is a catch. If you do _not_ understand them well in your language, they will make you less efficient at first. As a hobby Haskell programmer of course you're happy with that, but you will get your code done slower than people, who 'just do it'. I'm someone, who likes to get things done, so I found it's best for me not to improve the style/genericity of existing code, unless there is a reason to do it. But I do improve my understanding of the language and the abstractions it provides, so in general I can say that my code is written in the best style and the highest genericity I understand.
What's an example of a rewrite that you've encountered?
For example as a beginner, when I didn't understand the list monad or how folds work, my implementation of the 'subsequences' function looked like this: subsets :: [a] -> [[a]] subsets [] = [[]] subsets (x:xs) = ys ++ map (x:) ys where ys = subsets xs When I started to comprehend folds, the function started to look more like this: subsets :: [a] -> [[a]] subsets = foldr (\x xs -> xs ++ map (x:) xs) [[]] Finally now that I understand the list monad very well, my implementation looks like this: subsets :: [a] -> [[a]] subsets = filterM (const [True, False]) Or even like this: subsets :: MonadPlus m => [a] -> m [a] subsets = filterM (const . msum . map return $ [True, False]) Note that I have never rewritten an existing 'subsets' function and today I would just use Data.List.subsequences, which was added recently. So my conclusion is: In production code don't worry too much about it, just write your code and don't stop learning. If your code works and is readable, there is no need to make it look nicer or more abstract. If you have to rewrite or change the function, you can still make it better. The exception is: If you code for fun or exercise, there is nothing wrong with playing with abstractions and enhance your skills in a funny way. As a side note: I have found that many people don't understand the filterM-based solution. That's because many people don't understand the list monad and the power of the monadic interface. So if you work in a group, either don't write code like this or preferably explain monads to your groupmates. Greets Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/

Ertugrul Soeylemez schrieb:
As a side note: I have found that many people don't understand the filterM-based solution. That's because many people don't understand the list monad and the power of the monadic interface. So if you work in a group, either don't write code like this or preferably explain monads to your groupmates.
Alternatively, keep all versions and compare them in a QuickCheck test-suite.
participants (13)
-
Alp Mestanogullari
-
Andrey Sisoyev
-
Claus Reinke
-
Daniel Fischer
-
Ertugrul Soeylemez
-
Felipe Lessa
-
Günther Schmidt
-
Henning Thielemann
-
Johannes Waldmann
-
Max Bolingbroke
-
Ryan Ingram
-
Sean Leather
-
Stephen Tetley