Re: [Haskell-cafe] How do you rewrite your code?

2010-03-03 Thread Henning Thielemann

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.

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


Re: [Haskell-cafe] How do you rewrite your code?

2010-03-03 Thread Max Bolingbroke
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  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:
>
> 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
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How do you rewrite your code?

2010-03-03 Thread Stephen Tetley
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.


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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How do you rewrite your code?

2010-03-02 Thread Ryan Ingram
On Tue, Mar 2, 2010 at 11:20 AM, Sean Leather  wrote:
> 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How do you rewrite your code?

2010-03-02 Thread Daniel Fischer
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.

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


Re: [Haskell-cafe] How do you rewrite your code?

2010-03-02 Thread Andrey Sisoyev

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.

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


Re: [Haskell-cafe] How do you rewrite your code?

2010-03-02 Thread Felipe Lessa
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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How do you rewrite your code?

2010-03-02 Thread Alp Mestanogullari
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  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:
>
>- 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/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] How do you rewrite your code?

2010-03-02 Thread 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