0

Code is below. I'd like to have parameters to my function that are only restricted by type class. I call a function of the type class on them and then I can use them. But I'm getting various errors as I'm trying to do this.

{-# LANGUAGE RankNTypes, TypeSynonymInstances, FlexibleInstances, UndecidableInstances #-}

class PlotValue a where
  value :: a -> Double
instance PlotValue Double where
  value = id
--instance PlotValue Int where
  --value x = fromIntegral x
instance (Integral a) => PlotValue a where
  value x = fromIntegral x
instance PlotValue String where
  value x = 5

type Input = (PlotValue a, PlotValue b) => (Maybe a, Maybe b)

test :: Input -> String
test (Just a, Just b) = (show $ value a) ++ (show $ value b)

main = do
  putStrLn (show ( test (Just "strl", Just 6.4)))

Current errors (though they change a little depending on what I try):

Test5.hs:17:5:
    Couldn't match expected type `Input' against inferred type `(a, b)'
    In the pattern: (Just a, Just b)
    In the definition of `test':
        test (Just a, Just b) = (show $ value a) ++ (show $ value b)

Test5.hs:20:30:
    Couldn't match expected type `a' against inferred type `[Char]'
      `a' is a rigid type variable bound by
          the polymorphic type
            `forall a b. (PlotValue a, PlotValue b) => (Maybe a, Maybe b)'
            at Test5.hs:20:19
    In the first argument of `Just', namely `"strl"'
    In the expression: Just "strl"
    In the first argument of `test', namely `(Just "strl", Just 6.4)'

Test5.hs:20:43:
    Could not deduce (Fractional b)
      from the context (PlotValue a, PlotValue b)
      arising from the literal `6.4' at Test5.hs:20:43-45
    Possible fix:
      add (Fractional b) to the context of
        the polymorphic type
          `forall a b. (PlotValue a, PlotValue b) => (Maybe a, Maybe b)'
    In the first argument of `Just', namely `6.4'
    In the expression: Just 6.4
    In the first argument of `test', namely `(Just "strl", Just 6.4)'
mentics
  • 6,852
  • 5
  • 39
  • 93
  • `{-# LANGUAGE OverlappingInstances #-}` can do the job, but I hate doing so without precise knowledge of what exactly am I doing – Boris Berkgaut Mar 24 '11 at 12:25
  • You're going to have problems inhabiting `Input` with values - I think the synonym definition is giving it an existential type that I doubt you will want in practice. – stephen tetley Mar 24 '11 at 12:45
  • To expand on Stephen's point, you could perhaps achieve what you want from the type synonym by writing `type Input a b = (PlotValue a, PlotValue b) => (Maybe a, Maybe b)`. But you'll need at least FlexibleContexts and possibly other extensions to do it, and I'd still think it's better form to write `type Input a b = (Maybe a, Maybe b)`, and then add the type class constraints to the function types. – Chris Smith Mar 24 '11 at 16:46

3 Answers3

2

Fixed a number of small things. Mainly, as stephen pointed out, hiding a free type variable under a type synonym is generally sort of silly and bad.

{-# LANGUAGE RankNTypes, TypeSynonymInstances, FlexibleInstances, OverlappingInstances, UndecidableInstances #-}

class PlotValue a where
  value :: a -> Double
instance PlotValue Double where
  value = id
instance (Integral a) => PlotValue a where
  value x = fromIntegral x
instance PlotValue String where
  value x = 5

test :: (PlotValue a, PlotValue b) => (Maybe a, Maybe b) -> String
test (Just a, Just b) = (show $ value a) ++ (show $ value b)

main = do
  putStrLn (show ( test (Just "strl", Just (6.4::Double))))
sclv
  • 38,665
  • 7
  • 99
  • 204
  • I am curious why it's silly and bad, but... It appears getting rid of the synonym and adding OverlappingInstances was what was needed. Is there some way to consolidate/alias the type class constraints? For example, if I had 10 functions test1 through test10 that all included that `(PlotValue a, PlotValue b) => (Maybe a, Maybe b)`, it would be nice to not have to put the class constraints in just one place (which is why I had it in the type synonym) instead of strewn about everywhere. Is there some other proper way to do that that works? Thanks! – mentics Mar 24 '11 at 14:51
  • How can you construct a value of type `Value`? It will be of the form `(Just x, Just y)` but the things you write in for `x` and `y` will have to occupy *all* `PlotValue` types, not *some* `PlotValue` type. This is what the second error is saying. – applicative Mar 24 '11 at 15:19
  • 1
    @taotree: you can define `type Input r = (PlotValue a, PlotValue b) => (Maybe a, Maybe b) -> r` then your `test` becomes `test :: Input String`. To add an extra argument: `test2 :: Input (Bool -> Double)`. – Ed'ka Mar 24 '11 at 21:53
2

Do you really need to be inventing new typeclasses here? The Prelude machinery is complicated enough, you'd think. It is only the inclusion of String that might be forcing this on you, but there are other ways. It seems you just want a general mapping from the standard numerical types (Int, Integer, Float, Double) to Double. There are a lot of ways of going about this, but what about d here, in place of your value?

d :: Real a => a -> Double
d  = fromRational . toRational 

test (Just a, Just b) = show (d a) ++ "  " ++ show (d b)
test (_, _)= "Something's missing"

-- Main> :t test
-- test :: (Real a, Real a1) => (Maybe a, Maybe a1) -> [Char]

double :: Double
double = 1.0
float :: Float
float = 1.0
int :: Int
int = 1
integer :: Integer
integer = 2

omnibus = d double * d float * d int / d integer

jdouble = Just double
jinteger = Just integer

goodtest = (jdouble,jinteger)
badtest =  (Nothing, jinteger)

main = print omnibus >> putStrLn (test goodtest) >> putStrLn (test badtest)

-- Main> main
-- 0.5
-- 1.0  2.0
-- Something's missing

If you want it to apply d to String, then you want to treat strings with numbers. Okay, one way to do that is to define a Num instance for String with a view to making a Real instance. Just google "instance Num String", or see e.g. this remark of dons for examples. Here's a frivolous example:

instance Num String where
  fromInteger  = show
  (+) =  (++)
  x * y = concatMap (const y) x
  abs = undefined
  signum = undefined

instance Real String where toRational = toRational . d . length
-- Main> fromInteger 500 * "moo "
-- "moo moo moo "
-- Main> d (fromInteger 500 * "moo")
-- 12.0

stringy = d "string"
jstringy = Just stringy 
stringytest = (jstringy, jinteger)

main' = print omnibus >> print stringy >>  
        putStrLn (test goodtest) >> putStrLn (test badtest) >> 
        putStrLn (test stringytest)
-- Main> main'
-- 0.5
-- 5.0
-- 1.0  2.0
-- Something's missing
-- 5.0  2.0

Or, if you want a PlotValue type class with value, why not instance it separately for the four leading numerical types and String? In fact, though, the Input type you seem to want is really something like (Maybe Double, Maybe Double).

Note that where you write

main = do
  putStrLn (show ( test (Just "strl", Just 6.4)))

you don't need do, since you just have one action in view; and you don't need 'show', since test yields a String already.

Community
  • 1
  • 1
applicative
  • 8,081
  • 35
  • 38
  • I apologize for the confusion. It is not about numeric types. That's just what I chose for a simple test trying to figure out how to do the general case. The general case is: take a set of types and be able to work with them as a single specific type. The type class providing the mechanism to convert them all to the specific type that the function can work with. – mentics Mar 24 '11 at 17:26
  • Various things might answer to that description, but I think it is plain you are trying to force a wrong model on the type class machinery. It is very rare that one has reason to introduce new type classes in Haskell, very common that one has reason to introduce new types, and thus new instances. You seem to be trying to outwit the type and type-class system before orienting yourself in it properly. – applicative Mar 24 '11 at 18:53
  • So, if I understand: let's say I have various types like: Height, Weight, Distance, Velocity, etc... All those things have a magnitude. You're suggesting that rather than creating a Magnitude type class and adding instances for those types for that, just add instances for them in an existing type class. That makes sense. Doesn't help me on this current problem (since it's related to the use of a type class, not the creation of one that I'm trying to work out), but it's a good thing for me to keep in mind. – mentics Mar 24 '11 at 19:53
1

For getting around the (to my eyes) 'strange' type synonym, I'd go with GADTs, like this:

{-# LANGUAGE GADTs #-} -- in addition to the rest
data Input where
    Input :: (PlotValue a, PlotValue b) => Maybe a -> Maybe b -> Input
test :: Input -> String
test (Input (Just a) (Just b)) = (show $ value a) ++ (show $ value b)

The only overhead is having to match on the Input constructor.

(The questions concerning class and instance design have already been answered, so I won't go into them)

yatima2975
  • 6,580
  • 21
  • 42
  • Interesting solution. Adding overhead and complexity just for syntactical sugar is probably not going to best serve what I need for this. – mentics Mar 24 '11 at 17:30
  • Well, it's just typing (in the keyboard sense) overhead! The `Input` datatype embodies the concept of two plottable values, which may or may not be present - you could just as well use `(Just Double, Just Double)` and store the result of `value`. If you later expand the `PlotValue` class then my solution is a bit more flexible, I guess. – yatima2975 Mar 24 '11 at 18:12
  • Oh, I thought you meant it would have runtime performance overhead. But maybe it wouldn't (and I'm working with performance critical code), in which case this looks interesting. Though I remember having issues with GADT's previously as I think you can't pattern match on them in certain places like where's and let's (get error that suggests using a case, I think, which wouldn't work for me in a certain case) – mentics Mar 24 '11 at 20:00
  • I'm no performance wizard, so I won't say anything about that. As far as I know, GADTs carry the dictionaries (in your case, for `PlotValue`s around) around so that would be a space overhead. For your other issue, I thought most bindings in `where` and `let` clauses were desugared to `case` anyway, so they should be equivalent. What are you having problems with? I guess there's an interesting question about performance aspects of GADTs; I'll ask it if you don't! – yatima2975 Mar 24 '11 at 22:01