views:

114

answers:

1

I'd like to see if it is feasible to have a type class for converting one thing into another and back again from a mapping of [(a,b)].

This example should illustrate what I'd like to do:

data XX = One | Two | Three deriving (Show, Eq)
data YY = Eno | Owt | Eerht deriving (Show, Eq)

instance Convert XX YY where
   mapping = [(One, Eno), (Two, Owt), (Three, Eerht)]

-- // How can I make this work?:
main = do print $ (convert One :: YY) -- Want to output: Eno
          print $ (convert Owt :: XX) -- Want to output: Two

Here's my stab at making this work:

{-# LANGUAGE MultiParamTypeClasses #-}    
import Data.Maybe(fromJust)

lk = flip lookup
flipPair = uncurry $ flip (,)

class (Eq a, Eq b) => Convert a b where

   mapping :: [(a, b)]
   mapping = error "No mapping defined"

   convert :: a -> b
   convert = fromJust . lk mapping

-- // This won't work:
instance (Convert a b) => Convert b a where
   convert = fromJust . lk (map flipPair mapping)

It is easy to do this with defining two instances for the conversion going either way but I'd like to only have to declare one as in the first example. Any idea how I might do this?


Edit: By feasible I mean, can this be done without overlapping instances any other nasty extensions?

+3  A: 

I, er... I almost hate to suggest this, because doing this is kinda horrible, but... doesn't your code work as is?

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE OverlappingInstances #-}
import Data.Maybe(fromJust)

lk x = flip lookup x
flipPair = uncurry $ flip (,)

class (Eq a, Eq b) => Convert a b where
   mapping :: [(a, b)]
   mapping = error "No mapping defined"
   convert :: a -> b
   convert = fromJust . lk mapping

instance (Convert a b) => Convert b a where
   convert = fromJust . lk (map flipPair mapping)

data XX = One | Two | Three deriving (Show, Eq)
data YY = Eno | Owt | Eerht deriving (Show, Eq)

instance Convert XX YY where
   mapping = [(One, Eno), (Two, Owt), (Three, Eerht)]

main = do print $ (convert One :: YY)
          print $ (convert Owt :: XX)

And:

[1 of 1] Compiling Main             ( GeneralConversion.hs, interpreted )
Ok, modules loaded: Main.
*Main> main
Eno
Two
*Main> 

I'm not sure how useful such a type class is, and all the standard disclaimers about dubious extensions apply, but that much seems to work. Now, if you want to do anything fancier... like Convert a a or (Convert a b, Convert b c) => Convert a c... things might get awkward.


I suppose I might as well leave a few thoughts about why I doubt the utility of this:

  • In order to use the conversion, both types must be unambiguously known; likewise, the existence of a conversion depends on both types. This limits how useful the class can be for writing very generic code, compared to things such as fromIntegral.

  • The use of error to handle missing conversions, combined with the above, means that any allegedly generic function using convert will be a seething pit of runtime errors just waiting to happen.

  • To top it all off, the generic instance being used for the reversed mapping is in fact a universal instance, only being hidden by overlapped, more specific instances. That (Convert a b) in the context? That lets the reversed mapping work, but doesn't restrict it to only reversing instances that are specifically defined.

camccann
For simplicity's sake, you could fold all the `LANGUAGE` pragmas into a comma-separated list: `{-# LANGUAGE MultiParamTypeClasses, … #-}`.
Antal S-Z
@Antal S-Z: Yeah, the separate lines thing is just a habit of mine. I use a fairly simpleminded editor for Haskell and adding/removing pragmas while refactoring code is easier if they're self-contained.
camccann
That's fair; I've never really had more than one or two in a project, so refactoring them hasn't been a major issue. I can see the advantage, though, now that I think about it.
Antal S-Z
@Antal S-Z: It's easy to get more than a half dozen when doing stupid type-level metaprogramming crap. Those are also the ones I'm most finicky about not leaving lying around unnecessarily, so... yeah.
camccann
@camccann: I was sort of aware that this might work with enough extensions enabled. But, can this be done without overlapping instances any other nasty extensions? Of the three criticisms you mentioned only the last really bothers me.
Ollie Saunders
@Ollie Saunders: I don't think so. A "reversed mapping" sort of instance will always be universal and maximally-overlapping, because instance selection is done looking only at the head (i.e., `Convert a b`), ignoring the context. This sort of thing doesn't really work well using just instance declarations--have you considered using Template Haskell to generate instances, instead?
camccann