Reputation: 5554
This is a personal exercise to understand the limits of Haskell's type system a little better. I want to create the most generic function I can that applies some function to each entry in a 2 entry tuple eg:
applyToTuple fn (a,b) = (fn a, fn b)
I am trying to make this function work in each of the following cases:
(1) applyToTuple length ([1,2,3] "hello")
(2) applyToTuple show ((2 :: Double), 'c')
(3) applyToTuple (+5) (10 :: Int, 2.3 :: Float)
So for length
the items in the pair must be Foldable
, for show they must be instances of Show
etc.
Using RankNTypes
I can go some of the way, for example:
{-# LANGUAGE RankNTypes #-}
applyToTupleFixed :: (forall t1. f t1 -> c) -> (f a, f b) -> (c, c)
applyToTupleFixed fn (a,b) = (fn a, fn b)
This allows a function that can work on a general context f
to be applied to items in that context. (1)
works with this, but the tuple items in (2)
and (3)
have no context and so they don't work (and anyway, 3 would return different types). I could of course define a context to place items in eg:
data Sh a = Show a => Sh a
instance Show (Sh a) where show (Sh a) = show a
applyToTuple show (Sh (2 :: Double), Sh 'c')
to get other examples working. I am just wondering whether it is possible to define such a generic function in Haskell without having to wrap the items in the tuples or give applyToTuple a more specific type signature.
Upvotes: 17
Views: 920
Reputation: 10793
You were pretty close with the last one, but you need to add constraints:
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ConstraintKinds #-}
import Data.Proxy
both :: (c a, c b)
=> Proxy c
-> (forall x. c x => x -> r)
-> (a, b)
-> (r, r)
both Proxy f (x, y) = (f x, f y)
demo :: (String, String)
demo = both (Proxy :: Proxy Show) show ('a', True)
The Proxy
is necessary to pass the ambiguity check. I think this is because it wouldn't otherwise know which part of the constraint to use from the function.
In order to unify this with other cases, you need to allow empty constraints. It might be possible, but I'm not sure. You can't partially apply type families, which might make it a bit trickier.
This is a bit more flexible than I thought it would be though:
demo2 :: (Char, Char)
demo2 = both (Proxy :: Proxy ((~) Char)) id ('a', 'b')
I had no idea you could partially apply type equality until this moment, haha.
Unfortunately, this doesn't work:
demo3 :: (Int, Int)
demo3 = both (Proxy :: Proxy ((~) [a])) length ([1,2,3::Int], "hello")
For the particular case of lists though, we can use IsList
from GHC.Exts
to get this to work (IsList
is usually used with the OverloadedLists
extension, but we don't need that here):
demo3 :: (Int, Int)
demo3 = both (Proxy :: Proxy IsList) (length . toList) ([1,2,3], "hello")
Of course, the simplest (and even more general) solution is to use a function of type (a -> a') -> (b -> b') -> (a, b) -> (a', b')
(like bimap
from Data.Bifunctor
or (***)
from Control.Arrow
) and just give it the same function twice:
λ> bimap length length ([1,2,3], "hello")
(3,5)
Okay, after some more thought and coding, I figured out how to at least unify the three examples you gave into a single function. It's not the most intuitive thing maybe, but it seems to work. The trick is that, in addition to what we have above, we allow the function to give back two different result types (the elements of the resulting pair can be of different types) if we give the type system the following restriction:
Both result types must have a relation to the corresponding input type given by a two-parameter type class (we can look at a one parameter type class as a logical predicate on a type and we can look at a two parameter type class as capturing a binary relation between two types).
This is necessary for something like applyToTuple (+5) (10 :: Int, 2.3 :: Float)
, since it gives you back (Int, Float)
.
With this, we get:
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
import Data.Proxy
import GHC.Exts
both :: (c a, c b
,p a r1 -- p relates a and r1
,p b r2 -- and also relates b and r2
)
=> Proxy c
-> Proxy p
-> (forall r x. (c x, p x r) => x -> r) -- An input type x and a corresponding
-- result type r are valid if the p from
-- before relates x and r,
-- where x is an instance of c
-> (a, b)
-> (r1, r2)
both Proxy Proxy f (x, y) = (f x, f y)
Proxy p
represents our relation between the input and output types. Next, we define a convenience class (which, as far as I know, doesn't exist anywhere already):
class r ~ a => Constant a b r
instance Constant a b a -- We restrict the first and the third type argument to
-- be the same
This lets us use both
when the result type stays the same by partially applying Constant
to the type we know it will be (I also didn't know you could partially apply type classes until now. I'm learning a lot for this answer, haha). For example, if we know that it will be Int
in both results:
example1 :: (Int, Int)
example1 =
both (Proxy :: Proxy IsList) -- The argument must be an IsList instance
(Proxy :: Proxy (Constant Int)) -- The result type must be Int
(length . toList)
([1,2,3], "hello")
Likewise for your second test case:
example2 :: (String, String)
example2 =
both (Proxy :: Proxy Show) -- The argument must be a Show instance
(Proxy :: Proxy (Constant String)) -- The result type must be String
show
('a', True)
The third one is where it gets a bit more interesting:
example3 :: (Int, Float)
example3 =
both (Proxy :: Proxy Num) -- Constrain the the argument to be a Num instance
(Proxy :: Proxy (~)) -- <- Tell the type system that the result type of
-- (+5) is the same as the argument type.
(+5)
(10 :: Int, 2.3 :: Float)
Our relation between input and output type here is actually only slightly more complex than the other two examples: instead of ignoring the first type in the relation, we say that the input and output types must be the same (which works since (+5) :: Num a => a -> a
). In other words, in this particular case, our relation is the equality relation.
Upvotes: 15
Reputation: 584
What you want is a function with a type
applyToTuple :: (a -> b) -> (c, d) -> (b, b)
where the compiler would check if a
, c
, and d
are in the same typeclass. This is unfortunately not possible as far as I know (though there may be an extension for that somewhere). When you pass a function of a certain typeclass to another function, it's type becomes that of the first thing it is applied to (observation from GHC):
applyToTuple f (x, y) = (f x, f y)
has a derived type of applyToTuple :: (t -> t1) -> (t, t) -> (t1, t1)
.
Testing it with show
shows these results:
λ> applyToTuple show (8, 9)
("8","9")
λ> applyToTuple show (8, [8,9])
<interactive>:5:14:
No instance for (Show t0) arising from a use of `show'
The type variable `t0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Note: there are several potential instances:
instance Show Double -- Defined in `GHC.Float'
instance Show Float -- Defined in `GHC.Float'
instance (Integral a, Show a) => Show (GHC.Real.Ratio a)
-- Defined in `GHC.Real'
...plus 28 others
In the first argument of `applyToTuple', namely `show'
In the expression: applyToTuple show (8, [8, 9])
In an equation for `it': it = applyToTuple show (8, [8, 9])
<interactive>:5:20:
No instance for (Num [t0]) arising from the literal `8'
Possible fix: add an instance declaration for (Num [t0])
In the expression: 8
In the second argument of `applyToTuple', namely `(8, [8, 9])'
In the expression: applyToTuple show (8, [8, 9])
<interactive>:5:24:
No instance for (Num t0) arising from the literal `8'
The type variable `t0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Note: there are several potential instances:
instance Num Double -- Defined in `GHC.Float'
instance Num Float -- Defined in `GHC.Float'
instance Integral a => Num (GHC.Real.Ratio a)
-- Defined in `GHC.Real'
...plus three others
In the expression: 8
In the expression: [8, 9]
In the second argument of `applyToTuple', namely `(8, [8, 9])'
You can, however do something like applyToTuple' f1 f2 (x, y) = (f1 x, f2 y)
. I think you may be able to use Template Haskell to transform that into what you want.
Upvotes: 0