Is there a way to define "pairmap
" like the following:
pairmap f (x,y) = (f x, f y)
So that the following works:
pairmap (+2) (1::Int, 2::Float)
pairmap succ (1::Int, 'a')
pairmap Just ('a', True)
etc.
Naturally, in the first case, both the elements must be of class Num
, and in the second case, both of class Enum
. In the third case however, there's no restriction required.
Answer (but could be improved)
The following code (ideone) solves the problem, but note that my functions have to be wrapped in a datatype that encapsulates both the relation between the input and output types and also any constraints on the input type. This works but there's a bit of boilerplate. It would be nice if I could use a bit less boilerplate to achieve this, so any answer would be appreciated (although this solution is reasonably fine for my purposes).
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE RankNTypes #-}
import GHC.Exts (Constraint)
class Function f where
type Constraints f a :: Constraint
type instance Constraints f a = ()
type Result f a
type instance Result f a = a
applyFunc :: (Constraints f a) => f -> a -> Result f a
pairmap ::
(Function f, Constraints f a, Constraints f b) =>
f -> (a, b) -> (Result f a, Result f b)
pairmap f (x,y) = (applyFunc f x, applyFunc f y)
data NumFunc where
NumFunc :: (forall a. Num a => a -> a) -> NumFunc
instance Function NumFunc where
type Constraints NumFunc a = (Num a)
applyFunc (NumFunc f) = f
data EnumFunc where
EnumFunc :: (forall a. Enum a => a -> a) -> EnumFunc
instance Function EnumFunc where
type Constraints EnumFunc a = (Enum a)
applyFunc (EnumFunc f) = f
data MaybeFunc where
MaybeFunc :: (forall a. a -> Maybe a) -> MaybeFunc
instance Function MaybeFunc where
type Result MaybeFunc a = Maybe a
applyFunc (MaybeFunc f) = f
y1 = pairmap (NumFunc (+2)) (1::Int, 2::Float)
y2 = pairmap (EnumFunc succ) (1::Int, 'a')
y3 = pairmap (MaybeFunc Just) ('a', True)
main = do
print y1
print y2
print y3
Answer 2
I think this is better and more flexible (ideone), but again, any improvements to reduce the boilerplate welcome:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeApplications #-}
import GHC.Exts (Constraint)
data Func (c :: (* -> * -> Constraint)) where
Func :: (forall a b. c a b => a -> b) -> Func c
class (c a, a ~ b) => BasicConstraint c a b
instance (c a, a ~ b) => BasicConstraint c a b
numFunc = Func @(BasicConstraint Num)
enumFunc = Func @(BasicConstraint Enum)
class (c a, t a ~ b) => NewtypeConstraint c t a b
instance (c a, t a ~ b) => NewtypeConstraint c t a b
class EmptyConstraint a
instance EmptyConstraint a
maybeFunc = Func @(NewtypeConstraint EmptyConstraint Maybe)
applyFunc :: Func c -> (forall a b. c a b => a -> b)
applyFunc (Func f) = f
pairmap :: (c a a', c b b') => Func c -> (a, b) -> (a', b')
pairmap f (x,y) = (applyFunc f x, applyFunc f y)
main = do
print $ pairmap (numFunc (+2)) (1::Int, 2::Float)
print $ pairmap (enumFunc succ) (1::Int, 'a')
print $ pairmap (maybeFunc Just) ('a', True)
The first two of your examples are somewhat simpler to generalize than the third.
{-# LANGUAGE RankNTypes, ConstraintKinds, KindSignatures, AllowAmbiguousTypes, TypeApplications #-}
import GHC.Exts (Constraint)
pairmap :: forall (c :: * -> Constraint) d e. (c d, c e) =>
(forall a. (c a) => a -> a) -> (d,e) -> (d,e)
pairmap f (x,y) = (f x, f y)
The caveat with this solution is that you need to explicitly instantiate the constraint you are using:
ghci> pairmap @Num (+1) (1 :: Int, 1.0 :: Float)
(2,2.0)
As for the third, here is a half solutions. If the second type is always a type parametrized over the first (like f a
), then you can do the same thing as above (albeit your first examples cease to work - you could make them work by wrapping them in Identity
).
pairmap' :: forall (c :: * -> Constraint) f d e. (c d, c e) =>
(forall a. (c a) => a -> f a) -> (d,e) -> (f d,f e)
pairmap' f (x,y) = (f x, f y)
And again, at GHCi
ghci> pairmap' @Num (Just . (+1)) (1 :: Int , 1.0 :: Float)
(Just 2,Just 2.0)
If you love us? You can donate to us via Paypal or buy me a coffee so we can maintain and grow! Thank you!
Donate Us With