Send Beginners mailing list submissions to
        [email protected]

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
        [email protected]

You can reach the person managing the list at
        [email protected]

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


Today's Topics:

   1. Re:  Typing/N00b question/My first haskell (Bryan Hunt)
   2.  data design for a questionnaire (retitled +      update) (Alia)
   3. Re:  data design for a questionnaire (retitled +  update) (Alia)
   4.  User defined operators : setting precedence (Hugo Ferreira)
   5. Re:  User defined operators : setting precedence (Antoine Latter)
   6. Re:  Need advice on R vs Haskell (Allen S. Rout)
   7. Re:  User defined operators : setting precedence (Hugo Ferreira)


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

Message: 1
Date: Mon, 21 Nov 2011 12:04:04 +0000
From: Bryan Hunt <[email protected]>
Subject: Re: [Haskell-beginners] Typing/N00b question/My first haskell
To: Haskell Beginners List <[email protected]>
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii


Thank you for your helpful replies, program works correctly now:

module Main where

ageJudge age
   | age >= 40 = "You're too old!"
   | age <= 30 = "You're too young"
   | otherwise   = "Not in the programming age range.."

main = do
   putStrLn "What is your name?"
   name <- getLine
   putStrLn ("Nice to meet you, " ++ name ++ "!")
   putStrLn "What is your age?"
   age <- getLine
   let inpIntegral = (read age)::Int
   putStrLn ( "We decided:\n" ++ ageJudge inpIntegral )







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

Message: 2
Date: Mon, 21 Nov 2011 05:46:28 -0800 (PST)
From: Alia <[email protected]>
Subject: [Haskell-beginners] data design for a questionnaire (retitled
        +       update)
To: "[email protected]" <[email protected]>
Message-ID:
        <[email protected]>
Content-Type: text/plain; charset=iso-8859-1

I've retitled this post just in case (-:

Having spent some more time on the prior post (questionnaire data design 
patterns), I've managed
to produce a version that allows for heterogeneous lists but that seems to 
necessarily involve existential
quantification.

Three question remain:
(1) figure out how to show 'questions' in version3.hs (I'm stumped so far)
(2) figure out how to make Question and its subtypes polymorphic in the context 
of existential quantification:
??? such that you can have a Choice a where a is an Int and another Choice 
Double, etc... yet still allow for
??? heterogeneous lists so that questions = [open ...., test ...., choice ...] 
would still be possible.
(3) translate version3.hs to use records (if possible)

<version3.hs>

{-# LANGUAGE ExistentialQuantification #-} 
{-# LANGUAGE TypeSynonymInstances #-}

module Main where

import Text.Show.Functions

-- dummy funcs for now
class Question_ a where
??? ask??????? :: a -> String
??? view?????? :: a -> String
??? parse????? :: a -> String
??? 

data Question = forall a. Question_ a => Question a

type Name????????? = String
type QString?????? = String
type AnswerType??? = String
type CorrectAnswer = String
type Option??????? = (String, String)
type Options?????? = [Option]

-- question types
data Open????? = Open?? Name QString AnswerType
data Test????? = Test?? Name QString AnswerType CorrectAnswer
data Choice??? = Choice Name QString AnswerType CorrectAnswer Options

instance Question_ Open where
??? ask?? (Open n q a) = n
??? view? (Open n q a) = q
??? parse (Open n q a) = a

instance Question_ Test where
??? ask?? (Test n q a c) = n ++ c
??? view? (Test n q a c) = q ++ c
??? parse (Test n q a c) = a ++ c

instance Question_ Choice where
??? ask?? (Choice n q a c os) = n ++ c 
??? view? (Choice n q a c os) = q ++ c
??? parse (Choice n q a c os) = a ++ c

instance Question_ Question where
??? ask?? (Question q) = ask?? q
??? view? (Question q) = view? q
??? parse (Question q) = parse q

--
-- Smart constructor
--

open :: Name -> QString -> AnswerType -> Question
open n q a = Question (Open n q a)

test :: Name -> QString -> AnswerType -> CorrectAnswer -> Question
test n q a c = Question (Test n q a c)

choice :: Name -> QString -> AnswerType -> CorrectAnswer -> Options -> Question
choice n q a c os = Question (Choice n q a c os)

questions :: [Question]
questions = [ open?? "q1" "what is your name" "str"
??????????? , test?? "q2" "what is 1+1?"????? "int" "2"
??????????? , choice "q3" "what is 2+2?"????? "int" "4" [("a", "4")]
??????????? ]
</version.hs>

Alia



??????????? ]




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

Message: 3
Date: Mon, 21 Nov 2011 06:04:36 -0800 (PST)
From: Alia <[email protected]>
Subject: Re: [Haskell-beginners] data design for a questionnaire
        (retitled +     update)
To: "[email protected]" <[email protected]>
Message-ID:
        <[email protected]>
Content-Type: text/plain; charset="iso-8859-1"

As a followup, I just received a simpler and more elegant solution due to 
Lorenzo Bolla which involves wrapping
the question type in another type and achieves the objective nicely. I think 
this is much cleaner than
using existential types as per my prior posting.

<version4.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 Question' = QuestionS (Question String) | QuestionI (Question Int) 
deriving (Show)

data QuestionSet a = QuestionSet
??? { qsetTitle???? :: String
??? , qsetQuestions :: [Question']
??? } 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 = [QuestionS q1, QuestionI q2, QuestionI q3]
??? }

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


</version4.hs>


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

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

Message: 4
Date: Mon, 21 Nov 2011 15:34:23 +0000
From: Hugo Ferreira <[email protected]>
Subject: [Haskell-beginners] User defined operators : setting
        precedence
To: "[email protected]" <[email protected]>
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-15; format=flowed

Hello,

Can anyone point me to some documentation that describes
how one may set precedence in a user defined operators?
I have composition operators so that I can write:

   let ruleSuffixCapsFreq = ruleT |> suffixT .> capitalizeT .> freqT

but I seem to be forced to write:

   let ruleSuffixCapsFreq = ruleT |> (suffixT .> capitalizeT .> freqT)

and I would like to avoid this.

TIA,
Hugo F.




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

Message: 5
Date: Mon, 21 Nov 2011 09:47:45 -0600
From: Antoine Latter <[email protected]>
Subject: Re: [Haskell-beginners] User defined operators : setting
        precedence
To: Hugo Ferreira <[email protected]>
Cc: "[email protected]" <[email protected]>
Message-ID:
        <CAKjSnQFRM7j_iy7=wwpc1bwtfyxfrcbue7ro59wyqrzp-xt...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Mon, Nov 21, 2011 at 9:34 AM, Hugo Ferreira <[email protected]> wrote:
> Hello,
>
> Can anyone point me to some documentation that describes
> how one may set precedence in a user defined operators?
> I have composition operators so that I can write:
>
> ?let ruleSuffixCapsFreq = ruleT |> suffixT .> capitalizeT .> freqT
>
> but I seem to be forced to write:
>
> ?let ruleSuffixCapsFreq = ruleT |> (suffixT .> capitalizeT .> freqT)
>
> and I would like to avoid this.
>

Hello,

Here's a brief introduction to Haskell fixity declarations:

http://www.haskell.org/tutorial/functions.html#sect3.2.2

Here's the relevant part of the language definition, which includes a
precedence table for  the operators that ship with the language:

http://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-820004.4.2

Antoine

> TIA,
> Hugo F.
>
>
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
>



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

Message: 6
Date: Mon, 21 Nov 2011 11:15:01 -0500
From: "Allen S. Rout" <[email protected]>
Subject: Re: [Haskell-beginners] Need advice on R vs Haskell
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

On 11/20/2011 12:57 AM, haskell heath wrote:
> [ I've dabbled in lots of stuff, which language should I use for what?]

and

>     I'm new to Haskell and I can't really call myself a decent
>     programmer in any other language. Do you think it's wrong to think
>     that I can contribute to the statistics library?


I'm a journeyman R coder and a bare novice at Haskell.  What springs to 
my mind here is, what's your primary goal:  to enhance the statistical 
toolset available in Haskell, or to accomplish a task?

If the former, then I think the critical question isn't your language 
competence but your statistical props;  if you watch the R devel list 
for any duration, you'll see how deeply the real stats folks treat these 
problems;  to have a broken tool (and not know it) is often worse than 
to have no tool.  If you've got the stats clue, then by all means 
soldier on. Subject Matter Experts rock. :)

If your goal is to accomplish your task, then I suggest that R is 
absolutely the superior environment for statistical thinking these days. 
  Cobble together whatever data-collection bits you need in whatever 
toolset is convenient, and if you're scraping web, then node.js is as 
good a place to start as any.   Drop CSV files from your scraping, and 
go to town in R.

- Allen S. Rout




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

Message: 7
Date: Mon, 21 Nov 2011 16:21:53 +0000
From: Hugo Ferreira <[email protected]>
Subject: Re: [Haskell-beginners] User defined operators : setting
        precedence
To: Antoine Latter <[email protected]>
Cc: "[email protected]" <[email protected]>
Message-ID: <[email protected]>
Content-Type: text/plain; charset=UTF-8; format=flowed

Antoine,

On 11/21/2011 03:47 PM, Antoine Latter wrote:
> On Mon, Nov 21, 2011 at 9:34 AM, Hugo Ferreira<[email protected]>  wrote:
>> Hello,
>>
>> Can anyone point me to some documentation that describes
>> how one may set precedence in a user defined operators?
>> I have composition operators so that I can write:
>>
>>   let ruleSuffixCapsFreq = ruleT |>  suffixT .>  capitalizeT .>  freqT
>>
>> but I seem to be forced to write:
>>
>>   let ruleSuffixCapsFreq = ruleT |>  (suffixT .>  capitalizeT .>  freqT)
>>
>> and I would like to avoid this.
>>
>
> Hello,
>
> Here's a brief introduction to Haskell fixity declarations:
>
> http://www.haskell.org/tutorial/functions.html#sect3.2.2
>
> Here's the relevant part of the language definition, which includes a
> precedence table for  the operators that ship with the language:
>
> http://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-820004.4.2
>

Exactly what I was looking for.

Thank you,
Hugo F.


> Antoine
>
>> TIA,
>> Hugo F.
>>
>>
>> _______________________________________________
>> Beginners mailing list
>> [email protected]
>> http://www.haskell.org/mailman/listinfo/beginners
>>
>




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

_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners


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

Reply via email to