
Am Montag, 8. März 2010 22:45:19 schrieb Wolfgang Jeltsch:
Hello,
some time ago, it was pointed out that generalized newtype deriving could be used to circumvent module borders. Now, I found out that generalized newtype deriving can even be used to define functions that would be impossible to define otherwise. To me, this is surprising since I thought that generalized newtype deriving was only intended to save the programmer from writing boilerplate code, not to extend expressiveness.
Have a look at the following code:
{-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses, FlexibleInstances #-}
class Iso a b where
conv :: item a -> item b
instance Iso a a where
conv = id
newtype Wrapped a = Wrap a deriving (Iso a, Show)
Now any value whose type contains some type t can be converted into a value of the type that you get if you replace t by Wrap t. Here is some code to demonstrate this for binary operations:
newtype BinOp a = BinOp (a -> a -> a)
convBinOp :: (a -> a -> a) -> (Wrapped a -> Wrapped a -> Wrapped a) convBinOp op = let BinOp op' = conv (BinOp op) in op'
Now, you can enter
convBinOp (*) (Wrap 5) (Wrap 3)
into GHCi, and you will get
Wrap 15
as the result.
The point is, of course, that such conversions are not only possible for binary operations but for arbitrary values and that these conversions are done by a single generic function conv. I don’t think it would be possible to implement conv without generalized newtype deriving.
Generalized newtype deriving doesn’t just allow otherwise undefinable functions to be defined. It probably also allows for faster function implementations. For example, with the above conv method, you could probably convert a list of some type [t] into a list of type [Wrapped t] in O(1) time. If you would code this conversion by hand, it would take O(n) time, of course. Best wishes, Wolfgang