generalized newtype deriving allows the definition of otherwise undefinable functions

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

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

On Mon, Mar 08, 2010 at 11:32:16PM +0100, Wolfgang Jeltsch wrote:
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.
So you can! wrapList :: [a] -> [Wrapped a] wrapList xs = conv xs
wrapList "Hello" [Wrap 'H',Wrap 'e',Wrap 'l',Wrap 'l',Wrap 'o']
This is quite interesting. And perhaps very, very bad. Take this example:
newtype Down a = Down a deriving (Iso a, Show, Eq)
instance Ord a => Ord (Down a) where compare (Down x) (Down y) = compare y x
downSet :: Set.Set a -> Set.Set (Down a) downSet ss = conv ss
xs = "abcdef"
sxs1 = downSet (Set.fromList xs) sxs2 = Set.fromList (map Down xs)
Set.toAscList sxs1 [Down 'a',Down 'b',Down 'c',Down 'd',Down 'e',Down 'f'] Set.toAscList sxs2 [Down 'f',Down 'e',Down 'd',Down 'c',Down 'b',Down 'a'] We have been able to break the invarients of 'Set' using newtype deriving of a completely unrelated class 'Iso'. It seems that generalized newtype deriving may break type classes in a big way. John -- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/

On Mon, 2010-03-08 at 23:32 +0100, Wolfgang Jeltsch wrote:
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.
Wouldn't timing be exactly the same? I mean: (map Wrapped xs) !! k and (conv xs :: [Wrapped t]) !! k They have exactly the same 'complexity' - O(k) (if k is constant we have constant time access - even if list is infinite). The 'problem' is that if you combine O(f) algorithm and O(g) algorithm resulting complexity is somewhere in between. For example head (O(1)) combined with sort (O(n log n)) gives us O(n) complexity. Map have nice property that combined it 'borrows' complexity from another algorithm. So g . map f have complexity of g (if f have O(1) of course). I don't see any benefits of conv as: - If the conversion is valid it is usually provided (see for example mapMonotonic). Unfortunately Set is strict but I guess it belongs to compiler optimization then conv function[1] - If conversion is not valid it should not be performed in the first place. Regards [1] I don't know maybe something like: {-# RULES mapMonotonic/iso mapMonotonic <ISO> = unsafeCoerce #-} When <ISO> is special value which indicate newtype constructor (example keyword). It is up to programmer (library or user - here user as it is in preconditions) to assure that conversion is safe. As in example given in other post Wrapped is not monotonic it cannot be used argument as mapMonotonic (ok. due to precondition but still).

On Tuesday 09 March 2010 9:36:51 am Maciej Piechotka wrote:
On Mon, 2010-03-08 at 23:32 +0100, Wolfgang Jeltsch wrote:
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.
Wouldn't timing be exactly the same?
I mean: (map Wrapped xs) !! k and (conv xs :: [Wrapped t]) !! k
They have exactly the same 'complexity' - O(k) (if k is constant we have constant time access - even if list is infinite).
Comparing the complexity isn't really going to tell you which of these does more work. If n is O(m), then an algorithm that takes 'm + n' steps has the same overall complexity as one that simply takes 'm' steps, but obviously the first does more work. The difference (in work) between map Wrapped and conv is the difference between map id and id :: [a] -> [a]. In the absence of any fusion/rewrite rules, the former breaks down a list, and builds up a new one with exactly the same elements (or, every element x becomes an id x thunk, perhaps). So, in a lazy language, inspecting each cons cell carries an additional O(1) overhead over inspecting the corresponding cons cell in the original list (because inspecting the former implicitly inspects the latter, and then yields a new cons cell with the same values for inspection). So, if 'id xs !! k' takes costs f(k), then 'map id xs !! k' costs f(k) + C*k. Both are O(k), but the latter is more expensive. -- Dan

On Tue, Mar 09, 2010 at 02:16:11PM -0500, Dan Doel wrote:
The difference (in work) between map Wrapped and conv is the difference between map id and id :: [a] -> [a]. In the absence of any fusion/rewrite rules, the former breaks down a list, and builds up a new one with exactly the same elements (or, every element x becomes an id x thunk, perhaps). So, in a lazy language, inspecting each cons cell carries an additional O(1) overhead over inspecting the corresponding cons cell in the original list (because inspecting the former implicitly inspects the latter, and then yields a new cons cell with the same values for inspection).
So, if 'id xs !! k' takes costs f(k), then 'map id xs !! k' costs f(k) + C*k. Both are O(k), but the latter is more expensive.
Not to mention they can have radically different space usages. xs = 'x':xs id xs => constant space map id xs => potentially infinite space John -- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/

The difference (in work) between map Wrapped and conv is the difference between map id and id :: [a] -> [a]. In the absence of any fusion/rewrite rules, the former breaks down a list, and builds up a new one with exactly the same elements (or, every element x becomes an id x thunk, perhaps). So, in a lazy language, inspecting each cons cell carries an additional O(1) overhead over inspecting the corresponding cons cell in the original list (because inspecting the former implicitly inspects the latter, and then yields a new cons cell with the same values for inspection).
On a related note, I've been occasionally worried about conversions like 'map convert huge' where 'convert' is from one newtype to another with the same underlying type. I tried some simple examples and looking at core it seems like the 'map id huge' is optimized away. However, I'm guessing that's only because of a 'map id xs -> id xs' rewrite rule involved, and it won't work for all data structures. It seems like a better solution than relying on rewrite rules would be to lift the newtype up one level, e.g. convert 'M (Newtype x)' to 'Newtype (M x)'. Actually what I really want is to replace every function that goes M x -> x with M x -> Newtype x, but we don't have parameterized modules and doing this for something like Data.Map means a lot of boilerplate. Surely there is some more general approach?

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

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

| 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

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

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/

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

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

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

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
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

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

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

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

Wolfgang Jeltsch wrote:
Am Donnerstag, 11. März 2010 00:37:18 schrieb wren ng thornton:
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
Wolfgang Jeltsch wrote: 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
participants (11)
-
Dan Doel
-
Evan Laforge
-
Jan-Willem Maessen
-
John Meacham
-
Maciej Piechotka
-
Max Cantor
-
Ryan Ingram
-
Simon Peyton-Jones
-
Steffen Schuldenzucker
-
Wolfgang Jeltsch
-
wren ng thornton