Reputation: 337
Is it possible to code in either Haskell98 or with extensions the following function f
?
f :: (a -> b) -> (b -> a) -> c -> d
where (c,d) :: (a,b) || (c,d) :: (b,a)
I am attempting to create some generic function to convert between any two types a
and b
but am having difficulty with both being somewhat arbitrary. They are immediately set however by the first argument a ->b
, so I'm hoping this is possible. Any guidance is appreciated...
Thanks!
[EDIT]
The way I see it, my question question boils down to whether haskell's type system supports the or
keyword... as the intuitive signature of my function is: f :: (a->b) -> (b->a) -> a -> b or (a->b) -> (b->a) -> b -> a
...
Upvotes: 2
Views: 229
Reputation: 127711
I doubt that it is possible to do what you want directly, but you can use some workarounds:
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
class Converter a b c where
($$) :: a -> b -> c
data Conv a b = Conv a b
instance Converter (Conv (a -> b) (b -> a)) a b where
($$) (Conv f _) = f
instance Converter (Conv (a -> b) (b -> a)) b a where
($$) (Conv _ g) = g
intToString :: Int -> String
intToString = show
stringToInt :: String -> Int
stringToInt = read
printString :: String -> IO ()
printString = print
printInt :: Int -> IO ()
printInt = print
main = do
let convert = Conv intToString stringToInt
printString $ convert $$ (12345 :: Int)
printInt $ convert $$ "12345"
I believe this is sufficiently close to what you want. The only difference is a mandatory $$
operator, but it is inevitable.
Update: you can even drop special Conv
structure and use plain tuples:
instance Converter (a -> b, b -> a) a b where
($$) (f, _) = f
instance Converter (a -> b, b -> a) b a where
($$) (_, g) = g
-- ...
printString $ (intToString, stringToInt) $$ (12345 :: Int)
printInt $ (intToString, stringToInt) $$ "12345"
I think this is even closer to your requirement.
Upvotes: 6
Reputation: 34378
As alecb explains, it can't be done in the way your signature suggests, at least through ordinary means (it would require checking the types at runtime). An alternative you might like are Iso and Prism from lens
. Iso
fits the bill if your conversion functions are total and bijective; if one of the functions is partial you can use a Prism
instead. Here is a throwaway example:
import Control.Lens
import Text.ReadMaybe
stringInt :: Prism' String Int
stringInt = prism' show readMaybe
GHCi> "3" ^? stringInt
Just 3
it :: Maybe Int
GHCi> 3 ^. re stringInt
"3"
it :: String
Upvotes: 8
Reputation: 3428
Let's say we've got these two conversion functions:
i2s :: Int -> String
s2i :: String -> Int
What would be the type of g = f i2s s2i
? We'd like g 1
to be a legal expression, and also g "one"
. So g
accepts Int
and String
. That leaves us with three options:
g
is a fully polymorphic function - that is, it's first argument is of type a
. So g True
and g [1,2,3]
are also legal. A function so generic has nothing to do with conversion, and you can prove that this sort of functions can't do anything interesting (for example, a function of type a -> Int
must be constant)
g
expects an argument of a certain typeclass - for example, show
is a function that accepts only a restricted groups of types (including Int
and String
). But now your function is not fully polymorphic - it'll work only for this restricted type group.
We can define a new data type for this task:
data IntOrString = I Int | S String
-- the type signature is slightly different
f :: (Int -> String) -> (String -> Int) -> IntOrString -> IntOrString
f i2s s2i (I n) = S $ i2s n
f i2s s2i (S s) = I $ s2i S
While this function may be useful in some cases, it's not generic anymore (the only pair it supports is Int
and String
).
So the answer is - you can define a function with this type signature, but it will work only for a specific type or typeclass.
EDIT: No, there's no support for a function of type a -> b where a is Int or String
. This requires either a dynamic language or a static language that supports subtyping.
Upvotes: 6
Reputation: 6488
I'm not totally sure how you'd expect to use such a function, but my intuition is no. Suppose we had:
intToString :: Int -> String
intToString = show
stringToInt :: String -> Int
stringToInt = read
foo = f intToString stringToInt
What is foo
's type? You'd have to be able to apply foo
to both an Int
and a String
, and this is generally not possible in haskell: you could apply foo
to one or the other but not both.
edit: This doesn't feel like the whole story -- foo
could certainly be of type foo :: c -> d
, but this would allow it to be applied to any type, not just Int
or String
. Perhaps it would be possible to throw an error when applied to the wrong type. Even if something like that is possible though, it doesn't sound like a good idea.
Upvotes: 3