On 2003-06-06 at 08:15BST "Simon Peyton-Jones" wrote:
>
> I forget whether I've aired this on the list, but I'm
> seriously thinking that we should change 'forall' to
> 'exists' in existential data constructors like this one.
You did mention it, and there were several replies. I'd
characterise th
I forget whether I've aired this on the list, but I'm seriously thinking
that we should change 'forall' to 'exists' in existential data constructors
like this one. One has to explain 'forall' every time. But we'd lose a
keyword.
"exists" (like "forall" in ghc only) could be used independently in a
Am Freitag, 6. Juni 2003 09:15 schrieb Simon Peyton-Jones:
> I forget whether I've aired this on the list, but I'm seriously thinking
> that we should change 'forall' to 'exists' in existential data constructors
> like this one. One has to explain 'forall' every time. But we'd lose a
> keyword.
O
| classify :: Eq b => [a->b] -> [a] -> [[[a]]]
| classify cs xs = ...
|
| where for each classifying function in cs, I would get the xs
| partitioned accordingly. E.g.
|
| classify [fst,snd] [(1,0), (1,2), (2,0)]
|
| would yield
|
| [ [(1,0), (1,2)], [(2,0)] -- classified by `fst`
|
On Wed, Jun 04, 2003 at 02:46:59PM +0200, [EMAIL PROTECTED] wrote:
> So what I actually do is
> > putStrLn $ concat [show a, show c, show d]
>
> Works, but a little bit clumsy, especially with long lists.
> Is there a nice solution?
One way is to define a special (polymorphic) combinator instead
Ketil Z. Malde writes:
:
| classify :: Eq b => [a->b] -> [a] -> [[[a]]]
| classify cs xs = ...
|
| where for each classifying function in cs, I would get the xs
| partitioned accordingly. E.g.
|
| classify [fst,snd] [(1,0), (1,2), (2,0)]
|
| would yield
|
| [ [(1,0), (1,2)
On Wed, Jun 04, 2003 at 04:43:10PM +0200, [EMAIL PROTECTED] wrote:
> Yes, this would work, thanks.
>
> But let me extent my question: what if all the types would be in a
> class FakeClass which has function specialID :: a -> ID and
> I would like to do
>
> > foo $ map specialID [a,b,c,d]
> ?
We
Yes, this would work, thanks.
But let me extent my question: what if all the types would be in a
class FakeClass which has function specialID :: a -> ID and
I would like to do
> foo $ map specialID [a,b,c,d]
?
___
Haskell mailing list
[EMAIL PROTECTED]
On Wed, Jun 04, 2003 at 02:46:59PM +0200, [EMAIL PROTECTED] wrote:
>
> Now I want to print part of the record. What I would like to do is the
> following
> > putStrLn $ concatMap show [a,c,d]
>
> !!! bang !!!
>
> So what I actually do is
> > putStrLn $ concat [show a, show c, show d]
>
> Works
I don't properly understand this either, but as it happens I was looking at
this in the GHC user guide only yesterday...
[[
:
MkFoo :: forall a. a -> (a -> Bool) -> Foo
Nil :: Foo
Notice that the type variable a in the type of MkFoo does not appear in the
data type itself, which is plain F
Ketil Z. Malde wrote:
I have a function declared as:
anova2 :: (Fractional c, Ord b)
=> [a->b] -> (a->c) -> [a] -> [Anova1 c]
where the first parameter is a list of classifiers. I could simplify
it, I guess, to something like
classify :: Eq b => [a->b] -> [a] -> [[[a]]]
> Now, obviously, the problem is that fst and snd, being passed in a
> list, needs to be of the same type; this complicates classifying a
> list of type [(Int,Bool)], for instance¹.
I have a similar problem.
Say I have a record:
> data Rec = Rec { a :: Int, b :: Type1, c :: Type2, d :: Type3, ...
Hi,
This is one of those topics everybody else seems to be familiar with,
but which I don't quite understand, and can't seem to find any good
information about.
I have a function declared as:
anova2 :: (Fractional c, Ord b)
=> [a->b] -> (a->c) -> [a] -> [Anova1 c]
where the first
13 matches
Mail list logo