Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  data design for a questionnaire (retitled +  update) (Alia)
   2. Re:  data design for a questionnaire (retitled +  update) (Alia)
   3. Re:  Problems linking code from the book Haskell  School of
      Expression (Philippe Sismondi)


----------------------------------------------------------------------

Message: 1
Date: Sat, 26 Nov 2011 06:10:03 -0800 (PST)
From: Alia <alia_kho...@yahoo.com>
Subject: Re: [Haskell-beginners] data design for a questionnaire
        (retitled +     update)
To: "dmcbr...@neondsl.com" <dmcbr...@neondsl.com>
Cc: "beginners@haskell.org" <beginners@haskell.org>
Message-ID: <1322316603.2482.yahoomail...@web65711.mail.ac4.yahoo.com>
Content-Type: text/plain; charset="iso-8859-1"


?David McBride wrote:
> Why not have:


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

> data AnswerType = AnsD Double | AnsS String | AnsI Integer 
>?????????????????? deriving (Show, Read)

> Then, I'd personally make another change, why would you have a flat
> structure with a questionType and then optional correctAnswer and
> options fields?? There's no type safety in that.? I'd try:

> data Answer = StraightAnswer (String -> AnswerType) | MultipleChoice
> AnswerType [Option AnswerType]

> data Question = Question
>???? { questionName??? :: Name
>???? , questionText??? :: QuestionText
>???? , answerFunc????? :: (String -> AnswerType)
>???? , answer????????????? :: Answer
>???? } deriving (Show)

> If you are storing answers as string, just store them as "AnsD 5.589",
> "AnsS \"Constantiople\"".? Then with the read instance you can go:

> let answer = read x :: AnswerType

Thank you very much for the reply which is eye-opening. But I do have to spend 
time 
implementing your revised schema in the prior question handling functions to 
get my head around it? (-:

Best,

Alia
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111126/9bd9e377/attachment-0001.htm>

------------------------------

Message: 2
Date: Sat, 26 Nov 2011 09:20:55 -0800 (PST)
From: Alia <alia_kho...@yahoo.com>
Subject: Re: [Haskell-beginners] data design for a questionnaire
        (retitled +     update)
To: "beginners@haskell.org" <beginners@haskell.org>
Cc: "dmcbr...@neondsl.com" <dmcbr...@neondsl.com>
Message-ID:
        <1322328055.62922.yahoomail...@web65712.mail.ac4.yahoo.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi folks,

Just to wrap things up: I think I'm satisfied with the design below, mostly due 
to David McBride's advice.
My final code is a slight variation on his suggested course, but not by much. 
Many thanks to all those
who replied and helped with this problem.

<survey.final.hs>

module Main where

import Text.Show.Functions

type Name??????????? = String
type QuestionText??? = String
type Score?????????? = Double
type Option a??????? = (String, a)

-- type converters
convert x = read x :: AnswerType
str s = convert ("AnsS \""++ s ++"\"")
int s = convert ("AnsI "++s)
double s = convert ("AnsD "++s)


data AnswerType = AnsD Double
??????????????? | AnsS String
??????????????? | AnsI Integer
????????????????? deriving (Show, Read, Eq)

data Answer = AnyAnswer
??????????? | TestAnswer AnswerType
??????????? | MultipleChoice AnswerType [Option AnswerType]
????????????? deriving (Show)

data Question = Question
??? { questionName??? :: Name
??? , questionText??? :: QuestionText
??? , answerFunc????? :: String -> AnswerType
??? , answer????????? :: Answer
??? } deriving (Show)


data QuestionSet = QuestionSet
??? { qsetTitle???? :: Name
??? , qsetQuestions :: [Question]
??? , qsetPoints??? :: Score
??? } deriving (Show)

data Survey = Survey
??? { surveyTitle??????? :: Name
??? , surveyQuestionSets :: [QuestionSet]
??? } deriving (Show)


askQuestion?? :: Question -> IO String
askQuestion q = do
??? putStrLn $ questionText q
??? getLine

askQuestionSet :: QuestionSet -> IO [String]
askQuestionSet qs = mapM askQuestion (qsetQuestions qs)

takeQuestionSet :: QuestionSet -> IO [Bool]
takeQuestionSet qs = do
??? answers <- askQuestionSet qs
??? return (testQuestionSet qs answers)

testQuestion :: Question -> String -> Bool
testQuestion q ans = case answer q of
??? AnyAnswer?????????? -> not (null ans)
??? TestAnswer c??????? -> c == answerFunc q ans
??? MultipleChoice c os -> c == answerFunc q ans

testQuestionSet :: QuestionSet -> [String] -> [Bool]
testQuestionSet qs = zipWith testQuestion (qsetQuestions qs)

evalQuestionSet :: QuestionSet -> [String] -> Score
evalQuestionSet qs as = (total_correct / total_questions) * score
??? where
??????? total_questions = fromIntegral (length $ qsetQuestions qset)
??????? total_correct = fromIntegral (length $ filter (== True) 
(testQuestionSet qset as))
??????? score = qsetPoints qset


-- TESTING


q1 = Question
??? { questionName? = "q1"
??? , questionText? = "What is our name?"
??? , answerFunc??? = str
??? , answer??????? = AnyAnswer
??? }

q2 = Question
??? { questionName? = "q2"
??? , questionText? = "What is 1+1?"
??? , answerFunc??? = int
??? , answer??????? = TestAnswer (AnsI 2)
??? }

q3 = Question
??? { questionName? = "q3"
??? , questionText? = "What is 2+1?"
??? , answerFunc??? = int
??? , answer??????? = MultipleChoice (AnsI 3) [ ("a", AnsI 2)
????????????????????????????????????????????? , ("b", AnsI 3)
????????????????????????????????????????????? , ("c", AnsI 4)
????????????????????????????????????????????? ]
??? }

q4 = Question
??? { questionName? = "q4"
??? , questionText? = "What is 2.0 + 1.5 ?"
??? , answerFunc??? = double
??? , answer??????? = MultipleChoice (AnsD 3.5) [ ("a", AnsD 2.1)
??????????????????????????????????????????????? , ("b", AnsD 3.5)
??????????????????????????????????????????????? , ("c", AnsD 4.4)
??????????????????????????????????????????????? ]
??? }


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

survey = Survey
??? { surveyTitle??????? = "a survey"
??? , surveyQuestionSets = [qset]
??? }


t1 = evalQuestionSet qset ["1", "2", "3", "4"]


</survey.final.hs>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111126/905f71f7/attachment-0001.htm>

------------------------------

Message: 3
Date: Sat, 26 Nov 2011 16:11:02 -0500
From: Philippe Sismondi <psismo...@arqux.com>
Subject: Re: [Haskell-beginners] Problems linking code from the book
        Haskell School of Expression
To: Beginners Haskell <Beginners@haskell.org>
Message-ID: <f4a77057-ae16-4344-82a7-4e6d2d73e...@arqux.com>
Content-Type: text/plain; charset="us-ascii"


On 2011-11-25, at 10:53 PM, Brandon Allbery wrote:

> On Fri, Nov 25, 2011 at 22:30, Philippe Sismondi <psismo...@arqux.com> wrote:
> Well, I just realized that since I only need this for learning purposes (not 
> production code) I may as well do it under linux. I have my linux box on a 
> kvm with the mac. (That's my current form of "virtualization" ;-) I'll do 
> this if ubuntu and HP work well together. Thoughts?
> 
> That's where I've ended up for my xmonad development (well, still setting it 
> up), since xmonad is crashing when I use a ghc that is built against MacPorts 
> (both MP's own GHC and a locally built up to date haskell-platform) which I 
> need for X11-xft :/
>  

I am now set up on ubuntu 11.04. Code using Graphics.SOE.Gtk is running without 
a hitch.

Thanks again. 

> -- 
> brandon s allbery                                      allber...@gmail.com
> wandering unix systems administrator (available)     (412) 475-9364 vm/sms
> 

-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111126/55531b61/attachment.htm>

------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 41, Issue 39
*****************************************

Reply via email to