how do I avoid excessive constructor application?

For some reason, these two functions have different types. fun1 f (Left x)= Left (f x) fun1 _ r@(Right x) = Right x fun2 f (Left x) = Left (f x) fun2 _ r = r Is there a way to rewrite fun2 so that f has type (a->b)? In the general case, it seems wasteful to have to destruct and construct values just for type checking reasons, especially if your type has many more constructors than (Either a b). -Alex- ______________________________________________________________ S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com

S. Alexander Jacobson wrote:
For some reason, these two functions have different types.
fun1 f (Left x)= Left (f x) fun1 _ r@(Right x) = Right x
fun2 f (Left x) = Left (f x) fun2 _ r = r
fun1 :: forall a a1 b . (a -> a1) -> Either a b -> Either a1 b fun2 :: forall a b . (a -> a) -> Either a b -> Either a b fun1 is indeed more general than fun2 because there is no way for an x inside a (Left x) from the LHS of the function to be returned as part of the result. --- You can play games with the type checker to force them to have the same type without changing the "meaning" of your function. fun1' f (Left x) = if True then Left (f x) else Left x fun1' _ r@(Right x) = Right x
:type fun1' fun1' :: forall b a. (a -> a) -> Either a b -> Either a b
This assumes that the compiler doesn't perform an "optimisation" that throws away the second alternative of the if statement before it does type checking. --- A more sensible way is to add an explicit type signature to force it to have a less general type than what was inferred. fun1 :: forall a b . (a -> a) -> Either a b -> Either a b ----
Is there a way to rewrite fun2 so that f has type (a->b)? Delete the second line, but then you have a different function.
In the general case, it seems wasteful to have to destruct and construct values just for type checking reasons, especially if your type has many more constructors than (Either a b).
Standard type inference always returns the *most general* type, and it is never "wrong" (unless there's a bug in the compiler). If you actually want a less general type for one of your functions (maybe the more general one isn't useful in your particular program) then add a type signature to constrain it. Ben.

My point was that this code seems excessively complex: fun::(a->a1)->(Either a b)->Either a1 b fun f (Left x) = Left (f x) fun _ r@(Right x)= Right x I'd like to avoid the destruction and construction in the third line by replacing the right hand side with r. However, the typechecker then claims my type is wrong. How do I fix that? -Alex- ______________________________________________________________ S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com On Wed, 2 Mar 2005, Henning Thielemann wrote:
On Wed, 2 Mar 2005, Ben Lippmeier wrote:
You can play games with the type checker to force them to have the same type without changing the "meaning" of your function.
fun1' f (Left x) = if True then Left (f x) else Left x
Left (f x) `asTypeOf` Left x
?

Alex,
fun::(a->a1)->(Either a b)->Either a1 b fun f (Left x) = Left (f x) fun _ r@(Right x)= Right x
I'd like to avoid the destruction and construction in the third line by replacing the right hand side with r. However, the typechecker then claims my type is wrong. How do I fix that?
You can't. At the left-hand side r has type Either a b; at the right-hand side an expression of type Either a1 b is required, so you can't just supply b. You could do something like f :: (a -> c) -> Either a b -> Either c b f g (Left a) = Left (g a) f g x = coerceRight x coerceRight :: Either a b -> Either c b coerceRight (Right b) = Right b but I'm not too sure whether that's more elegant. HTH, Stefan

On Wed, 2 Mar 2005 09:20:15 -0500 (Eastern Standard Time), S.
Alexander Jacobson
My point was that this code seems excessively complex:
fun::(a->a1)->(Either a b)->Either a1 b fun f (Left x) = Left (f x) fun _ r@(Right x)= Right x
I'd like to avoid the destruction and construction in the third line by replacing the right hand side with r. However, the typechecker then claims my type is wrong. How do I fix that?
In your example, 'r' has type "Either a b" which doesn't match "Either a1 b". And you can "fix" it with some unsafeCoerce# magic. (: -- Friendly, Lemmih

I'd like to do this sort of thing with types other than Either. Is there a generic safe coerce function? -Alex- On Wed, 2 Mar 2005, Stefan Holdermans wrote:
Lemmih,
And you can "fix" it with some unsafeCoerce# magic. (:
Actually, as I pointed out, the required coercion in perfectly safe, though not implicit:
coerceRight :: Either a b -> Either c b coerceRight (Right b) = Right b
Regards,
Stefan
______________________________________________________________ S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com

Something like: class Coerce a b where coerce :: a -> b The class must be in a separate file from the instance so that the compiler does not determine that a == b for all instances. instance Coerce a a where coerce = id If it turns out the left and right types do not match, you get a "no instance of coerce for ..." error. Keean. S. Alexander Jacobson wrote:
I'd like to do this sort of thing with types other than Either. Is there a generic safe coerce function?
-Alex-
On Wed, 2 Mar 2005, Stefan Holdermans wrote:
Lemmih,
And you can "fix" it with some unsafeCoerce# magic. (:
Actually, as I pointed out, the required coercion in perfectly safe, though not implicit:
coerceRight :: Either a b -> Either c b coerceRight (Right b) = Right b
Regards,
Stefan
______________________________________________________________ S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wed, 2 Mar 2005 15:54:51 +0100, Stefan Holdermans
Lemmih,
And you can "fix" it with some unsafeCoerce# magic. (:
Actually, as I pointed out, the required coercion in perfectly safe, though not implicit:
coerceRight :: Either a b -> Either c b coerceRight (Right b) = Right b
I'm not disputing that. -- Friendly, Lemmih
participants (6)
-
Ben Lippmeier
-
Henning Thielemann
-
Keean Schupke
-
Lemmih
-
S. Alexander Jacobson
-
Stefan Holdermans