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. Trouble using MultiParamTypeClasses (Amy de Buitl?ir)
2. Re: Trouble using MultiParamTypeClasses (Daniel Fischer)
3. Re: Trouble using MultiParamTypeClasses (Amy de Buitl?ir)
4. Re: Exception Handling with Iteratees (Michael Craig)
5. Re: Trouble using MultiParamTypeClasses (Amy de Buitl?ir)
6. Re: questionnaire data design patterns (Amy de Buitl?ir)
7. Re: questionnaire data design patterns (Amy de Buitl?ir)
8. hlint and DoIfThenElse (Lee Short)
9. Re: hlint and DoIfThenElse (Mike Meyer)
----------------------------------------------------------------------
Message: 1
Date: Tue, 22 Nov 2011 12:41:11 +0000 (UTC)
From: Amy de Buitl?ir <[email protected]>
Subject: [Haskell-beginners] Trouble using MultiParamTypeClasses
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii
I would be very grateful if someone could tell me what I'm doing wrong. Here's
my
code:
-----
{-# LANGUAGE MultiParamTypeClasses #-}
class Eq a => Graph g a where
nodes :: g a -> [a]
neighbours :: g a -> a -> [a]
data WeightedGraph a w = WeightedGraph [(a, a, w)]
instance Eq a => Graph a (WeightedGraph w a) where
nodes = [] --stub
neighbours = [] --stub
-----
And here's the error message:
temp.hs:9:24:
Kind mis-match
The first argument of `Graph' should have kind `* -> *',
but `a' has kind `*'
In the instance declaration for `Graph a (WeightedGraph w a)'
------------------------------
Message: 2
Date: Tue, 22 Nov 2011 14:28:40 +0100
From: Daniel Fischer <[email protected]>
Subject: Re: [Haskell-beginners] Trouble using MultiParamTypeClasses
To: [email protected]
Cc: Amy de Buitl?ir <[email protected]>
Message-ID: <[email protected]>
Content-Type: Text/Plain; charset="iso-8859-1"
On Tuesday 22 November 2011, 13:41:11, Amy de Buitl?ir wrote:
> I would be very grateful if someone could tell me what I'm doing wrong.
> Here's my code:
>
> -----
> {-# LANGUAGE MultiParamTypeClasses #-}
>
> class Eq a => Graph g a where
> nodes :: g a -> [a]
> neighbours :: g a -> a -> [a]
You apply `g' to the type `a', so `g' must be a type constructor taking one
argument (because `g a' is a type).
That means `g' must have the kind `* -> *' (the kind of type constructors
taking one type as argument and producing a type).
>
> data WeightedGraph a w = WeightedGraph [(a, a, w)]
WeightedGraph takes two type arguments (`a' and `w' must be types, since
they're put in tuples) and constructs a type from them, so it has the kind
* -> * -> *
>
> instance Eq a => Graph a (WeightedGraph w a) where
> nodes = [] --stub
> neighbours = [] --stub
Since a is used as an argument to WeightedGraph, it must have kind *, but
it is also used as the first parameter to the Graph class, which demands it
has kind * -> *. Thus you have a kind mismatch.
You have probably confused the order of parameters, so the WeightedGraph
thing should be the first parameter and a the second. However, you mustn't
provide WeightedGraph with all type arguments it takes, since the type
expression you pass as first parameter to Graph must still take a type
argument to produce a type.
What you probably want is
instance Eq a => Graph (WeightedGraph w) a where
nodes _ = []
neighbours _ _ = []
------------------------------
Message: 3
Date: Tue, 22 Nov 2011 14:02:58 +0000 (UTC)
From: Amy de Buitl?ir <[email protected]>
Subject: Re: [Haskell-beginners] Trouble using MultiParamTypeClasses
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii
Thank you, Daniel. That did the trick, and thanks to your explanation, I have a
much better understanding of the syntax.
In case anyone else has a similar problem, I also had to add the
FlexibleInstances pragma.
------------------------------
Message: 4
Date: Tue, 22 Nov 2011 10:32:50 -0500
From: Michael Craig <[email protected]>
Subject: Re: [Haskell-beginners] Exception Handling with Iteratees
To: Felipe Almeida Lessa <[email protected]>
Cc: [email protected]
Message-ID:
<caha9zagepscy8ch26yn5sin1f53nruaspgsxfocbebaugrk...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"
That works well, but is there an extension free way of doing this cleanly?
I tried
handleErrors :: (Monad m, Exception e) => Maybe e -> Iteratee a m
Response
handleErrors (Just POSTOnlyException) = return "POSTs only!"
handleErrors (Just BadPathException) = return "Bad path!"
handleErrors _ = return "Unknown exception!"
app = catchError myApp (handleErrors . fromException)
But this won't compile because GHC "Couldn't match type `POSTOnlyException'
with `BadPathException'". I think I'm settling towards something like this:
data MyAppException = POSTOnlyException
| BadPathException
deriving ( Show, Typeable )
instance Exception MyAppException
handleErrors :: (Monad m) => SomeException -> Iteratee a m Response
handleErrors = hErr . fromException
where
hErr (Just POSTOnlyException) = return "POSTs only!"
hErr (Just BadPathException) = return "Bad path!"
hErr Nothing = return "Unknown exception!"
Mike S Craig
On Tue, Nov 22, 2011 at 1:42 AM, Felipe Almeida Lessa <
[email protected]> wrote:
> On Tue, Nov 22, 2011 at 4:35 AM, Michael Craig <[email protected]> wrote:
> > ... but of course this doesn't compile, because the types of the LHSs in
> the
> > case statement are different. I can get around it with some ugliness ...
> > handleErrors :: SomeException -> Iteratee a m String
> > handleErrors ex = case fromException ex of
> > Just POSTOnlyException -> return "POSTs only!"
> > _ -> case fromException ex of
> > Just BadPathException -> return "Bad path!"
> > _ -> return "Unknown exception!"
> > ... but there must be a better way. Enlighten me?
>
> If you enable the ViewPatterns extension
>
> {-# LANGUAGE ViewPatterns #-}
>
> then you can write handleErrors as
>
> handleErrors :: SomeException -> Iteratee a m String
> handleErrors (fromException -> Just POSTOnlyException) = return
> "POSTs only!"
> handleErrors (fromException -> Just BadPathException) = return "Bad
> path!"
> handleErrors _ = return "Unknown exception!"
>
> Cheers,
>
> --
> Felipe.
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL:
<http://www.haskell.org/pipermail/beginners/attachments/20111122/eb47765d/attachment-0001.htm>
------------------------------
Message: 5
Date: Tue, 22 Nov 2011 16:03:32 +0000 (UTC)
From: Amy de Buitl?ir <[email protected]>
Subject: Re: [Haskell-beginners] Trouble using MultiParamTypeClasses
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii
I tried to make my previous example a bit more flexible, but I guess I was
over-confident. Here's my code:
-----
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FunctionalDependencies,
UndecidableInstances #-}
class Eq a => Graph g a | g -> a where
nodes :: g a -> [a]
neighbours :: g a -> a -> [a]
class (Graph g a, Eq a, Ord w) => WeightedGraph g w a | g -> w, g -> a where
edges :: g w -> [(a, a, w)]
data MyGraph w a = MyGraph [(a, a, w)]
instance Eq a => Graph (MyGraph w) a where
nodes _ = [] --stub
neighbours _ _ = [] --stub
instance (Graph g a, Eq a, Ord w) => WeightedGraph (MyGraph w a) where
edges = [] -- stub
-----
The error message is
temp2.hs:16:53:
Kind mis-match
The first argument of `WeightedGraph' should have kind `* -> *',
but `MyGraph w a' has kind `*'
In the instance declaration for `WeightedGraph (MyGraph w a)'
Failed, modules loaded: none.
It seems to me that in the WeightedGraph class, g should have the kind * -> * ->
*, and MyGraph has the kind * -> * -> *, so I'm not sure why I have a kind
mismatch, but I suspect that I've written the instance declaration wrong. Any
ideas how to fix it?
------------------------------
Message: 6
Date: Tue, 22 Nov 2011 18:09:50 +0000 (UTC)
From: Amy de Buitl?ir <[email protected]>
Subject: Re: [Haskell-beginners] questionnaire data design patterns
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii
Hi Alia,
Here's my suggestion. It does compile.
Of course, there are lots of ways to approach this kind of thing. My choice was
to refactor it so that the Answer type contains the correct answer and the
possible answers, as appropriate. Then when you write the method that prompts
the user for an answer, and the method that checks the user's answer, you can
pattern match on the Answer type.
-----
module Main where
data Answer = Open
| Test { correctIntAnswer :: Int }
| Choice { correctStringAnswer :: Int, options :: [(String,
String)] }
deriving (Show, Eq)
data Question = Question
{ questionName :: String
, questionText :: String
, answer :: Answer
} 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?"
, answer = Open
}
q2 = Question
{ questionName = "q2"
, questionText = "What is 1+1?"
, answer = Test 2
}
q3 = Question
{ questionName = "q2"
, questionText = "What is 2+1?"
, answer = Choice 3 [("1", "2"), ("2", "3"), ("3", "4")]
}
qset = QuestionSet
{ qsetTitle = "simple questions"
, qsetQuestions = [q1, q2, q3]
}
questionnaire = Questionnaire
{ questionnaireTitle = "a questionnaire"
, questionnaireQuestionSets = [qset]
}
------------------------------
Message: 7
Date: Tue, 22 Nov 2011 18:23:58 +0000 (UTC)
From: Amy de Buitl?ir <[email protected]>
Subject: Re: [Haskell-beginners] questionnaire data design patterns
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii
Oops, I just realised that you have a couple of other threads with pretty much
the same question, and you have answers on them.
------------------------------
Message: 8
Date: Tue, 22 Nov 2011 14:46:37 -0800
From: Lee Short <[email protected]>
Subject: [Haskell-beginners] hlint and DoIfThenElse
To: <[email protected]>
Message-ID: <[email protected]>
Content-Type: text/plain; charset=UTF-8; format=flowed
hlint gives me a parse error on a clause using DoIfThenElse, even if I
have the language pragma. I don't see any hlint options to get around
that, are there any?
Is it considered good style to write code like this?
if "" == results
then return True
else return False
The obvious way rewrite below just seems clunky to me (though I can see
how others might prefer it to the code above).
return $ if "" == results
then True
else False
thanks
Lee
------------------------------
Message: 9
Date: Tue, 22 Nov 2011 14:58:58 -0800
From: Mike Meyer <[email protected]>
Subject: Re: [Haskell-beginners] hlint and DoIfThenElse
To: [email protected]
Message-ID: <20111122145858.72998fa8@mikmeyer-vm-fedora>
Content-Type: text/plain; charset=US-ASCII
On Tue, 22 Nov 2011 14:46:37 -0800
Lee Short <[email protected]> wrote:
> hlint gives me a parse error on a clause using DoIfThenElse, even if
> I have the language pragma. I don't see any hlint options to get
> around that, are there any?
>
> Is it considered good style to write code like this?
>
> if "" == results
> then return True
> else return False
>
> The obvious way rewrite below just seems clunky to me (though I can
> see how others might prefer it to the code above).
>
> return $ if "" == results
> then True
> else False
You've just pressed one of my language-independent style hot
buttons. Why on earth are you using an if/then/else here? What's wrong
with the straightforward:
return "" == results
The expression results in a boolean, and it's even the one you want to
return. So why not return it?
<mike
------------------------------
_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners
End of Beginners Digest, Vol 41, Issue 30
*****************************************