开发者

How do I accept parameters restricted only by type class

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)'


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))))


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.


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)

0

上一篇:

下一篇:

精彩评论

暂无评论...
验证码 换一张
取 消

最新问答

问答排行榜