Re: [Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

2010-03-12 Thread Wolfgang Jeltsch
Am Donnerstag, 11. März 2010 00:37:18 schrieb wren ng thornton:
 Wolfgang Jeltsch wrote:
  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.
 
 Let's dig down and figure out the problem. When you annotate the type
 Wrapped a with deriving (Iso a) what are you saying? You're saying
 that the compiler should derive an instance (Iso a (Wrapped a)). Well,
 that instance gives you the method instance conv :: forall f. f a - f
 (Wrapped a). The funny thing is that the only implementation for
 ---something like--- that type would be fmap Wrap.

If the parameter of f is contravariant then we would need a “contraMap”, not 
an fmap. Example:

 newtype CoFun a b = CoFun (b - a)

 class ContraFunctor f where

 contraMap :: (a - b) - f b - f a

 instance ContraFunctor (CoFun a) where

 contraMap f (CoFun g) = CoFun (g . f)

 coFun :: CoFun Int Char
 coFun = CoFun ord

 directlyConverted :: CoFun Int (Wrapped Char)
 directlyConverted = conv coFun

 manuallyConverted :: CoFun Int (Wrapped Char)
 manuallyConverted = contraMap unwrap coFun

Here, unwrap is the inverse of Wrap.

Let us look at the Set example from John Meacham. Set is a (covariant) 
functor, not a contravariant functor. However, it isn’t a functor from and to 
the category of Haskell types and functions but the category of types of class 
Ord and Ord homomorphisms (functions that respect ordering). The problem in 
John Meacham’s Set example is that Down doesn’t preserve ordering. If conv is 
used with a newtype wrapper constructor that does preserve ordering, this is 
the same as applying Set.map or Set.mapMonotonic.

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


Re: [Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

2010-03-12 Thread wren ng thornton

Wolfgang Jeltsch wrote:

Am Donnerstag, 11. März 2010 00:37:18 schrieb wren ng thornton:

Wolfgang Jeltsch wrote:

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.

Let's dig down and figure out the problem. When you annotate the type
Wrapped a with deriving (Iso a) what are you saying? You're saying
that the compiler should derive an instance (Iso a (Wrapped a)). Well,
that instance gives you the method instance conv :: forall f. f a - f
(Wrapped a). The funny thing is that the only implementation for
---something like--- that type would be fmap Wrap.


If the parameter of f is contravariant then we would need a “contraMap”, not 
an fmap. Example:


Right, but it's the same basic idea, just violating the (nonexistent?) 
ContraFunctor class instead of the Functor class. The underlying problem 
---which is what I was trying to identify--- is that generalized newtype 
deriving is assuming that every tycon of kind *-* is a functor (i.e., 
co-/contravariant endofunctor on all of Hask), and it's that assumption 
which causes breakage.


My conservative solution to disallow deriving methods where the newtype 
occurs beneath an unknown tycon would, I think, still work. The only 
difference is that in addition to considering all instances of 
Functor[1] as well known (as well as a few special cases: e.g., the 
first argument to (-) or (,)) we could consider all instances of 
ContraFunctor to be well known as well. That is, if there's an 
official version of that class.


My solution is conservative in that it doesn't offer any support for 
GADTs or type families, which are the particular concern in the bug 
tracker ticket. The problem for them is the same one, only it's even 
more pertinent since some things given the kind *-* should really have 
a different kind like |*|-* since their argument is an index instead of 
a type--- which means they're _really_ not functors on Hask.



Let us look at the Set example from John Meacham. Set is a (covariant) 
functor, not a contravariant functor. However, it isn’t a functor from and to 
the category of Haskell types and functions


Right, which is why the assumption that kind *-* implies functorality 
is broken. Again, in some sense even the kind is wrong; it's something 
more like Ord-*, but that only underscores the point.



[1] And Monad since Monad doesn't state the Functor requirement.

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

2010-03-10 Thread wren ng thornton

Wolfgang Jeltsch wrote:

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.


Let's dig down and figure out the problem. When you annotate the type 
Wrapped a with deriving (Iso a) what are you saying? You're saying 
that the compiler should derive an instance (Iso a (Wrapped a)). Well, 
that instance gives you the method instance conv :: forall f. f a - f 
(Wrapped a). The funny thing is that the only implementation for 
---something like--- that type would be fmap Wrap. But that 
implementation would introduce the requirement (Functor f), which is 
missing in the conv type. This is possible because of the representation 
model where a and (N a) have the same runtime representation, but it 
violates the intensional distinction between those types, by way of 
presuming functorality of any type of kind (k - *). Yeah, we can't do 
that legally in the language, so the GeneralizedNewtypeDeriving 
implementation is buggy.


Regarding the use of GeneralizedNewtypeDeriving for implementing 
functions that are faster than otherwise possible, these particular 
derivations should not be done without the (Functor f) restriction in 
the type of the derived function. It doesn't matter that the 
implementation does not use the fmap implementation (assuming that 
implementation is lawful), it matters that the derived function cannot 
be written at all ---efficiently or otherwise--- without assuming such 
an fmap exists.


Special casing things like this so they require the (Functor f) 
restriction won't solve everything. I'm sure we could create a different 
example that violates a different class. The general solution would seem 
to be making sure that the newtype only occurs in top-level positions 
within the type of the derived functions. Where top-level means  that 
it is not embedded within an unknown type constructor, though we can 
legitimately bake in support for well-known type constructors like (-), 
(,), Either, Maybe, [],...


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

2010-03-09 Thread Wolfgang Jeltsch
Am Dienstag, 9. März 2010 07:24:35 schrieb Steffen Schuldenzucker:
 On 03/08/2010 10:45 PM, Wolfgang Jeltsch wrote:
  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.
 
  Any thoughts?
 
 Hi Wolfgang,
 
 it's not exactly the same, but...
 
  import Control.Applicative
 
  newtype Wrapped a = Wrap a deriving Show
 
  instance Functor Wrapped where
  fmap f (Wrap x) = Wrap $ f x
 
  instance Applicative Wrapped where
  pure = Wrap
  (Wrap f) * (Wrap x) = Wrap $ f x
 
  convBinOp :: (a - a - a) - (Wrapped a - Wrapped a - Wrapped a)
  convBinOp op x y = pure op * x * y

I think this is fundamentally different. As I said above:

 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.

Your applicative functor Wrapped allows conversions only for n-ary functions, 
so, for example, John Meachem’s trick to break the invariant of Set doesn’t 
work. On the other hand, you need a separate conversion function for each 
arity (pure, fmap, liftA2, liftA3, …) whereas generalized newtype deriving 
allows you to use the same conversion function for all arities.

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


RE: [Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

2010-03-09 Thread Simon Peyton-Jones
| 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.

Yes indeed.  See http://hackage.haskell.org/trac/ghc/ticket/1496 for why this 
is really a bug in general. 

The trouble described there really happens when 'item' (in your iso class) in 
instantiated to a data type with a constructor whose fields use type functions.

Stephanie Weirich, Steve Zdancewic, Dimitrios Vytiniotis and I have been 
working hard on a development of the FC intermediate language, and hence of the 
source language, that will close this (embarrassing) loophole, and allow some 
new expressiveness.  Nothing written down in a form that someone other than us 
can make sense of, but there will be!  In brief, though, we're going to end up 
with kinds looking like
* = *
as well as the existing
* - *
The new form means a type-indexed function whereas the latter means a 
type-parametric function. 

John Meacham's example is also very interesting. Even if the data type doesn't 
use type functions, it might have invariants concerning type classes (his 
example is Set), and converting all the elements might destroy the invariants.  
Excellent point!  There's no type-soundness issue (no run-time seg fault) but 
something nearly as bad.  Will have to think about that.  Probably declaring 
Set to have kind (* = *) will do the job.

Thanks for the thread.

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


Re: [Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

2010-03-09 Thread Wolfgang Jeltsch
Am Dienstag, 9. März 2010 11:53:14 schrieben Sie:
 Isn't this just an extension of the notion that multi-parameter typeclasses
 without functional dependencies or type families are dangerous and allow
 for type-naughtiness?

Multi-parameter typeclasses are dangerous? It’s the first time I hear that. 
Could you elaborate, please?

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


Re: [Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

2010-03-09 Thread Jan-Willem Maessen

On Mar 9, 2010, at 5:26 AM, Simon Peyton-Jones wrote:
 ...
 Stephanie Weirich, Steve Zdancewic, Dimitrios Vytiniotis and I have been 
 working hard on a development of the FC intermediate language, and hence of 
 the source language, that will close this (embarrassing) loophole, and allow 
 some new expressiveness.  Nothing written down in a form that someone other 
 than us can make sense of, but there will be!  In brief, though, we're going 
 to end up with kinds looking like
   * = *
 as well as the existing
   * - *
 The new form means a type-indexed function whereas the latter means a 
 type-parametric function. 
 
 John Meacham's example is also very interesting. Even if the data type 
 doesn't use type functions, it might have invariants concerning type classes 
 (his example is Set), and converting all the elements might destroy the 
 invariants.  Excellent point!  There's no type-soundness issue (no run-time 
 seg fault) but something nearly as bad.  Will have to think about that.  
 Probably declaring Set to have kind (* = *) will do the job.

It occurs to me to observe: if we give class constraints in data types some 
force, and write:

data Ord a = Set a = ...[internals go here]...

Would this be enough to cue us that Set has a more interesting kind than just * 
- * ?

-Jan-Willem Maessen

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


Re: [Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

2010-03-09 Thread Jan-Willem Maessen

On Mar 9, 2010, at 5:53 AM, Max Cantor wrote:

 Isn't this just an extension of the notion that multi-parameter typeclasses 
 without functional dependencies or type families are dangerous and allow for 
 type-naughtiness?  

I wondered the same thing, but came up with an analogous problematic case that 
*only* uses generalized newtype deriving:

 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 module Main(main) where
 import Data.Set

 class IsoInt a where
 stripToInt :: item a - item Int
 convFromInt :: item Int - item a

 instance IsoInt Int where
 stripToInt = id
 convFromInt = id

 newtype Down a = Down a deriving (Eq, Show, IsoInt)

 instance Ord a = Ord (Down a) where
 compare (Down a) (Down b) = compare b a

 asSetDown :: Set (Down Int) - Set (Down Int)
 asSetDown = id

 a1 = toAscList . asSetDown . convFromInt . fromAscList $  [0..10]
 a2 = toAscList . asSetDown . fromAscList . reverse . convFromInt $ [0..10]

 main = do
 print a1
 print a2

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


Re: [Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

2010-03-09 Thread Max Cantor
Isn't this just an extension of the notion that multi-parameter typeclasses 
without functional dependencies or type families are dangerous and allow for 
type-naughtiness?  


On Mar 9, 2010, at 5:45 AM, Wolfgang Jeltsch wrote:

 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.
 
 Any thoughts?
 
 Best wishes,
 Wolfgang
 ___
 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] generalized newtype deriving allows the definition of otherwise undefinable functions

2010-03-09 Thread Wolfgang Jeltsch
Am Dienstag, 9. März 2010 15:54:16 schrieb Jan-Willem Maessen:
 On Mar 9, 2010, at 5:53 AM, Max Cantor wrote:
  Isn't this just an extension of the notion that multi-parameter
  typeclasses without functional dependencies or type families are
  dangerous and allow for type-naughtiness?
 
 I wondered the same thing, but came up with an analogous problematic case
 that *only* uses generalized newtype deriving:

 […]

Originally, I had a more restricted example in mind which is similar to yours. 
However, I wanted to generalize the problem and therefore introduced the 
general Iso class which made MultiParamTypeClasses and FlexibleInstances 
necessary. The actual problem is related neither to MultiParamTypeClasses nor 
to FlexibleInstances.

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


Re: [Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

2010-03-09 Thread John Meacham
On Tue, Mar 09, 2010 at 09:56:45AM -0500, Jan-Willem Maessen wrote:
 It occurs to me to observe: if we give class constraints in data types some 
 force, and write:
 
 data Ord a = Set a = ...[internals go here]...
 
 Would this be enough to cue us that Set has a more interesting kind than just 
 * - * ?

Yes. I was thinking something along the same lines. Could this just be
another example of contravariance flipping the meaning of
quantification? If we take the simpler example given:

 class Iso a where
conv :: item a - item Int

let's give the whole type

 class Iso a where
conv :: forall (item :: * - *) . item a - item Int

It seems to me the issue may not be with newtype deriving, but with that
universal quantification over a type constructor. If we were to declare
'Set' like so

 data Ord a = Set a = ...

like Jan-Willem suggests, then it seems that 'Set' should not be able to
unify with 'item' since it has the extra 'Ord' consraint on the
contravariant argument to item and item is universally quantified. Item
would need a psuedo-type like (Ord a = item :: a - *) to match.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

2010-03-09 Thread Ryan Ingram
I am pretty sure this problem is known, but you should add this code
to the bug report:

http://hackage.haskell.org/trac/ghc/ticket/1496

  -- ryan

On Tue, Mar 9, 2010 at 6:54 AM, Jan-Willem Maessen
jmaes...@alum.mit.edu wrote:

 On Mar 9, 2010, at 5:53 AM, Max Cantor wrote:

 Isn't this just an extension of the notion that multi-parameter typeclasses 
 without functional dependencies or type families are dangerous and allow for 
 type-naughtiness?

 I wondered the same thing, but came up with an analogous problematic case 
 that *only* uses generalized newtype deriving:

 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 module Main(main) where
 import Data.Set

 class IsoInt a where
     stripToInt :: item a - item Int
     convFromInt :: item Int - item a

 instance IsoInt Int where
     stripToInt = id
     convFromInt = id

 newtype Down a = Down a deriving (Eq, Show, IsoInt)

 instance Ord a = Ord (Down a) where
     compare (Down a) (Down b) = compare b a

 asSetDown :: Set (Down Int) - Set (Down Int)
 asSetDown = id

 a1 = toAscList . asSetDown . convFromInt . fromAscList $  [0..10]
 a2 = toAscList . asSetDown . fromAscList . reverse . convFromInt $ [0..10]

 main = do
     print a1
     print a2

 -Jan-Willem Maessen___
 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


[Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

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

Any thoughts?

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


Re: [Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

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


Re: [Haskell-cafe] generalized newtype deriving allows the definition of otherwise undefinable functions

2010-03-08 Thread Steffen Schuldenzucker
On 03/08/2010 10:45 PM, Wolfgang Jeltsch wrote:
 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.
 
 Any thoughts?
 

Hi Wolfgang,

it's not exactly the same, but...

 import Control.Applicative

 newtype Wrapped a = Wrap a deriving Show

 instance Functor Wrapped where
 fmap f (Wrap x) = Wrap $ f x

 instance Applicative Wrapped where
 pure = Wrap
 (Wrap f) * (Wrap x) = Wrap $ f x

 convBinOp :: (a - a - a) - (Wrapped a - Wrapped a - Wrapped a)
 convBinOp op x y = pure op * x * y

Best regards,

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