
Using Brandon's code as a starting point (as it's far neater than mine), let's try asking some questions about fractions (I've included the whole program at the end). questions = [ addition 1 2, addition (1%2) (1%3) ] This works, but the the fractions are shown as "1 % 2" and to make it presentable to non-Haskellers, we have to change that to "1/2". In order to do this, I tried to replace show with my own version which I call view (in type class View). At this point I get ../arithmetic/hackBrandon.hs:63:23: Ambiguous type variable `t' in the constraints: `Num t' arising from the literal `1' at ../arithmetic/hackBrandon.hs:63:23 `View t' arising from a use of `addition' at ../arithmetic/hackBrandon.hs:63:14-25 `Read t' arising from a use of `addition' at ../arithmetic/hackBrandon.hs:63:14-25 Probable fix: add a type signature that fixes these type variable(s) My problem is that I don't see where I could add a type signature, but still keep addition :: a -> a -> Question polymorphic. ======= Here's the code demonstrating the problem ===== {-# LANGUAGE NoMonomorphismRestriction #-} import System.IO (hFlush, stdout) import Data.Ratio data Result = Correct | Improve String | Huh String | Incorrect String deriving Show data Question = Question { ask :: String , answer :: String , check :: String -> Result } bool2result True = Correct bool2result False = Incorrect "" readCheckBy :: (Read a) => (a -> Bool) -> String -> Result readCheckBy pred str = case reads str of [(val,"")] -> bool2result (pred val) _ -> Huh "" readCheck :: (Read a, Eq a) => a -> String -> Result readCheck v s = readCheckBy (==v) s -- customized show class View a where view :: a -> String instance View Int where view = show instance (Integral n) => View (Ratio n) where view = show -- helpers value val prompt = Question prompt (view val) (readCheck val) infix2 op symbol a b = value (op a b) (unwords [view a, symbol, view b]) addParam :: (View a) => (funTy -> String -> qty) -> (a -> funTy) -> String -> (a -> qty) addParam qmakr fun string v = qmakr (fun v) (string++" "++view v) prefix1 = addParam value prefix2 = addParam prefix1 prefix3 = addParam prefix2 -- question 'types' addition = infix2 (+) "+" questions = [ addition 1 2 , addition (1%2) (1%3) ] test :: Question -> IO () test q = do putStr $ ask q ++ " = " hFlush stdout reply <- getLine putStrLn $ show $ check q reply main = mapM_ test questions