[Haskell-beginners] questionnaire data design patterns

Alia alia_khouri at yahoo.com
Mon Nov 21 10:02:54 CET 2011


Hi folks,
As a way to get my head wrapped around haskell data design idioms, I'm translating a questionnaire
data model (in python) to haskell, I would appreciate some advice and criticism on whether I'm 
going about this the right way.

Here's the initial translation:

<version1.hs>

module Main where

data QuestionType = Open | Test | Choice deriving (Show, Eq)

data Question = Question 
    { questionName  :: String 
    , questionText  :: String
    , questionType  :: QuestionType
    , answerType    :: String
    , correctAnswer :: Maybe String
    , options       :: Maybe [(String, String)]
    } deriving (Show, Eq)

data QuestionSet = QuestionSet
    { qsetTitle     :: String
    , qsetQuestions :: [Question]
    } deriving (Show, Eq)

data Questionnaire = Questionnaire
    { questionnaireTitle        :: String
    , questionnaireQuestionSets :: [QuestionSet]
    } deriving (Show, Eq)

q1 = Question 
    { questionName  = "q1"
    , questionText  = "What is our name?"
    , questionType  = Open
    , answerType    = "str"
    , correctAnswer = Nothing
    , options       = Nothing
    }

q2 = Question 
    { questionName  = "q2"
    , questionText  = "What is 1+1?"
    , questionType  = Test
    , answerType    = "int"
    , correctAnswer = Just "2"
    , options       = Nothing
    }

q3 = Question 
    { questionName  = "q2"
    , questionText  = "What is 2+1?"
    , questionType  = Choice
    , answerType    = "int"
    , correctAnswer = Just "3"
    , options       = Just [("1", "2"), ("2", "3"), ("3", "4")]
    }

qset = QuestionSet
    { qsetTitle     = "simple questions"
    , qsetQuestions = [q1, q2, q3]
    }

questionnaire = Questionnaire
    { questionnaireTitle        = "a questionnaire"
    , questionnaireQuestionSets = [qset]
    }

</version1.hs>

In this first version, the Question record basically holds all possible fields for any kind of question,
and fields which are not used are assigned Nothing thanks to the Maybe monad.

The final type of the answer is specified as a string in the record for later conversion.

Now I wanted to take into account a scenario where I don't need to specify the answerType by
creating a polymorphic Question type which is specialized to take different answertypes.
So I came up with this version:

<version2.hs>


module Main where

import Text.Show.Functions

-- type converters
str = id
int s = read s :: Int
float s = read s :: Double

data QuestionType = Open | Test | Choice deriving (Show, Eq)

data Question a = Question 
    { questionName    :: String 
    , questionText    :: String
    , questionType    :: QuestionType
    , answerFunc      :: (String -> a)
    , correctAnswer   :: Maybe a
    , options         :: Maybe [(String, a)]
    } deriving (Show)

data QuestionSet a = QuestionSet
    { qsetTitle     :: String
    , qsetQuestions :: [Question a]
    } deriving (Show)

data Questionnaire a = Questionnaire
    { questionnaireTitle        :: String
    , questionnaireQuestionSets :: [QuestionSet a]
    } deriving (Show)

q1 = Question 
    { questionName  = "q1"
    , questionText  = "What is our name?"
    , questionType  = Open
    , answerFunc    = id
    , correctAnswer = Nothing
    , options       = Nothing
    }

q2 = Question 
    { questionName  = "q2"
    , questionText  = "What is 1+1?"
    , questionType  = Test
    , answerFunc    = int
    , correctAnswer = Just 2
    , options       = Nothing
    }

q3 = Question 
    { questionName  = "q2"
    , questionText  = "What is 2+1?"
    , questionType  = Choice
    , answerFunc    = int
    , correctAnswer = Just 3
    , options       = Just [("a", 2), ("b", 3), ("c", 4)]
    }

qset = QuestionSet
    { qsetTitle     = "simple questions"
    , qsetQuestions = [q1, q2, q3]
    }

questionnaire = Questionnaire
    { questionnaireTitle        = "a questionnaire"
    , questionnaireQuestionSets = [qset]
    }

</version2.hs>

The problem is that now all the questionsets, and questionnaires expect the same
specialized type of question which is obviously not what I want and I get this error:

 Couldn't match expected type `[Char]' with actual type `Int'
    Expected type: Question String
      Actual type: Question Int
    In the expression: q2
    In the `qsetQuestions' field of a record

So what am I doing wrong here? Should I just revert back to version 1 which I sense is not
the haskell way.

Many thanks for any help or advice.

Alia



More information about the Beginners mailing list