1

It's a followup question of Functions to Polymorphic data types

Data type Question models a question/answer with a Message (the text of the question) and a function (String -> a) that maps user's input to the result of the question:

data Question where
  Simple :: (Typeable a, Show a) => Message -> (String -> a) -> Question

This CLI program should first gets the name of the Question, find an instance using getQuestion function and then run the Question and print out the result.

{-# LANGUAGE GADTs #-}

import Data.Typeable

type Message = String

data Question where
  Simple :: (Typeable a, Show a) => Message -> (String -> a) -> Question
  -- more constructors

yourName :: Question
yourName = Simple "Your name?" id

yourWeight :: Question
yourWeight = Simple "What is your weight?" (read :: String -> Int)

getQuestion :: String -> Question
getQuestion "name" =  yourName
getQuestion "weight" =  yourWeight    

runQuestion :: (Typeable a, Show a) => Question -> IO a
runQuestion (Simple message parser) = do
  putStrLn message
  ans <- getLine
  return $ parser ans

main = getLine >>= (runQuestion . getQuestion) >>= print

Type checking fails at here: runQuestion :: (Typeable a, Show a) => Question -> IO a with No instance for (Typeable a0) arising from a use of ‘runQuestion’.

If I remove the class constraints (runQuestion :: Question -> IO a) then I get No instance for (Show a0) arising from a use of ‘print.

Community
  • 1
  • 1
homam
  • 1,945
  • 1
  • 19
  • 26

2 Answers2

5

This type

Question -> IO a

means "a function that accepts a Question and returns an IO a for whatever a the caller wants". This is obviously wrong; some questions have an Int answer and some have a String answer, but no question has an answer that can on demand be Int, String, or whatever else we may want.

If all you need from the answer is the ability to show itself, just return a shown answer as an IO String.

type Message = String

data Question = Simple Message (String -> String)
  -- more constructors

yourName :: Question
yourName = Simple "Your name?" show

yourWeight :: Question
yourWeight = Simple "What is your weight?" (show . (read :: String -> Int))

getQuestion :: String -> Question
getQuestion "name" =  yourName
getQuestion "weight" =  yourWeight

runQuestion :: Question -> IO String
runQuestion (Simple message parser) = do
  putStrLn message
  ans <- getLine
  return $ parser ans

main = getLine >>= (runQuestion . getQuestion) >>= putStrLn

Otherwise you can move existentiality to the answer, which you need to encapsulate in a new GADT:

type Message = String

data Question where
  Simple :: Message -> (String -> Answer) → Question
  -- more constructors

data Answer where
  Easy ::  (Typeable a, Show a) => a -> Answer

instance Show Answer where
  show (Easy a) = show a

yourName :: Question
yourName = Simple "Your name?" Easy

yourWeight :: Question
yourWeight = Simple "What is your weight?" (Easy . (read :: String -> Int))

getQuestion :: String -> Question
getQuestion "name" =  yourName
getQuestion "weight" =  yourWeight

runQuestion :: Question -> IO Answer
runQuestion (Simple message parser) = do
  putStrLn message
  ans <- getLine
  return $ parser ans

main = getLine >>= (runQuestion . getQuestion) >>= print

but this is IMHO overkill.

n. m. could be an AI
  • 112,515
  • 14
  • 128
  • 243
  • Can we make Question an instance of Monad or Category? I like it to be composable :: `Question o -> (o -> Question o') -> Question o'` This way at design time I can ensure that the questions are sequenced and will be asked in a "rational" order. – homam Aug 25 '16 at 14:48
  • While retaining the ability to `getQuestion :: String -> Question` as the first question perhaps. – homam Aug 25 '16 at 14:49
  • The original `Question` has kind `*` (no type parameters). If you want it to be parameterized by the type of its answer, it's a whole different kettle of fish. You can have `String->Question` but `String->Question a` has the same problem you are having with `Question -> IO a`. – n. m. could be an AI Aug 25 '16 at 14:59
  • I think I'll lose one important feature by avoiding type parameters, I described it here: http://stackoverflow.com/questions/39147517/functions-of-gadts/39148323?noredirect=1#comment65641921_39148529 – homam Aug 25 '16 at 15:31
4

The error you report is not the only error.

Let's put on the special spectacles which show the things usually kept invisible by "type inference".

Firstly, the data constructor:

Simple :: forall a. (Typeable a, Show a) =>
          Message -> (String -> a) -> Question

Effectively, a value of type Question looks like

Simple {a}{typeableDict4a}{showDict4a} message parser

where I've written the invisible things in braces. The constructor packs up a type and the two typeclass dictionaries that give the implementations for the members of Typeable and Show.

Now let's have the main program. I've renamed the type variable to make a point.

runQuestion :: forall b. (Typeable b, Show b) => Question -> IO b

The type to be given back is chosen by the caller of runQuestion, separately from whatever type is packed inside the argument of type Question. Now let's fill in the invisible components in the program itself.

runQuestion {b}{typeableDict4b}{showDict4b}
  (Simple {a}{typeableDict4a}{showDict4a} message parser) = do
                        -- so parser :: String -> a
      putStrLn message  -- ok, as message :: String
      ans <- getLine    -- ensures ans :: String
  return $ parser ans   -- has type IO a, not IO b

The parser computes a value of the type a packed up in the Question, which is totally separate from the type b passed directly to runQuestion. The program does not typecheck because there's a conflict between two types which can be made different by the program's caller.

Meanwhile, let's look at print

print :: forall c. Show c => c -> IO ()

When you write

main = getLine >>= (runQuestion . getQuestion) >>= print

you get

main = getLine >>=
  (runQuestion {b}{typeableDict4b}{showDict4b} . getQuestion) >>=
  print {b}{showDict4b}

and as the return type of runQuestion {b} is IO b, it must be the case that print's c type is the same as runQuestion's b type, but other than that, there is nothing to determine which type b is, or why it is an instance either of Typeable or Show. With the type annotation, the need for Typeable shows up first (in the runQuestion call); without, the need for Show in print causes the complaint.

The real problem, is that somehow, you seem to want runQuestion to deliver a thing in whatever type is hidden inside the question, as if you could somehow write a (dependently typed) program like

typeFrom :: Question -> *
typeFrom (Simple {a}{typeableDict4a}{showDict4a} message parser) = a

runQuestion :: (q :: Question) -> IO (typeFrom q)

That's a perfectly sensible thing to want, but it isn't Haskell: there's no way to name "the type packed up inside that argument". Everything which involves that type has to live in the scope of the case analysis or pattern match which exposes it. It's your attempt to do the print outside that scope that won't be allowed.

pigworker
  • 43,025
  • 18
  • 121
  • 214
  • I thought that I will run into dependent types. I want to create a rational question/answer; meaning that the sequence of Questions should be type checked at compile time like: `Question a b { run :: a -> Input -> Either (b, Question b)}`. The last question in any chain ends with `Left finalResult`. The top Questions in a chain take no input perhaps `a = ()`. Questions probably form a Category. `b` the result depends on the result of the previous Question `a`. `a` and `b` are Typeable, Show and Read because I want to continue a chain by getting and feeding it `a` from somewhere (eg. Redis). – homam Aug 25 '16 at 15:28
  • 1
    @homam can you show a specific example of a chain of questions? I'm having a hard time imagining how they might compose. To be specific, what question can you chain to either side of "What is your weight"? – n. m. could be an AI Aug 25 '16 at 15:35
  • @n.m. If `Simple :: lastResult -> Input -> Either result (result, Question result _)` then `yourName = Simple $ \ _ i -> Right (i, yourWeight)` `yourWieght = Simple $ \ name i -> let res = (name, read i :: Int) in Left res`. I can imagine that `yourName >>> yourWeight` is valid. – homam Aug 25 '16 at 15:50
  • @homam so does `yourName >>> yourWeight` result include both name and weight? I don't think Haskell tyoe system can handle that. You need dependent types, open rows, or probably just plain old magic. – n. m. could be an AI Aug 25 '16 at 16:00
  • @n.m. yes, I want the result `yourName >>> yourWeight` to contain the result of both Questions. This way I ensure that `yourWeight` can only be asked after `yourName`. The whole thing is probably similar to creating a type safe state machine where transitions are type checked. – homam Aug 25 '16 at 16:05