Hi,

I am experimenting with rewrite rules, but found that they do not fire
as often as I wanted them. Here is a small example:

        module MapId where
        
        myMap f [] = []
        myMap f (x:xs) = f x : myMap f xs
        
        {-# RULES "map id" myMap id = id #-}
        {-# RULES "map id2" myMap (\x -> x) = id #-}
        
        mapId = myMap id
        mapIdApp x = myMap id x
        
        mapLamId = myMap (\x -> x)
        mapLamIdApp x = myMap (\x -> x) x

This works as expected, i.e. the latter four functions become some kind
of identity. But I am a bit surprised that I do need two rules to catch
all cases, as I thought that the simplifier „looks through“ definitions
like "id". But when I remove the "map id" rule, the functions "mapId"
and "mapIdApp" are not optimized. 

So I wonder: Why is rule "map id2" not enough here?

Thanks,
Joachim


-- 
Joachim "nomeata" Breitner
  m...@joachim-breitner.de  |  nome...@debian.org  |  GPG: 0x4743206C
  xmpp: nome...@joachim-breitner.de | http://www.joachim-breitner.de/

Attachment: signature.asc
Description: This is a digitally signed message part

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to