Re: [Haskell-cafe] [Off topic] Proving an impossibility

2007-09-05 Thread ok

On 4 Sep 2007, at 6:47 am, Vimal wrote:
In my Paradigms of Programming course, my professor presents this  
piece of code:


while E do
  S
  if F then
 break
  end
  T
end

He then asked us to *prove* that the above programming fragment cannot
be implemented just using if and while statement, even if S and T can
be duplicated a finite number of times


You might want to look up the Bohm-Jacopini theorem.
If you think about it, you'll realise that it's actually quite
straightforward to convert *any* flow-chart into a single while
loop containing a single case statement, with just one extra
integer variable.  (Hint: the integer variable plays to rôle of PC.)
But to keep it simple, all we really need is procedures and if;
no whiles and no extra variables.

proc Example
if E then
S
if not F then
T
Example
end if
end if
end proc

I remember my amusement, years ago, when I finally understood tail
recursion:  ANYTHING you can program using labels and gotos can be
programmed using procedure calls, provided your compiler supports
TRO (as both the C compilers I use do, in fact).

Now let's do the example without procedures:

Stopped: Boolean := False;
while not Stopped and (E) loop
S;
if F then
Stopped := True;
else
T;
end if;
end loop;

Off-hand, the only assumption I'm aware of making is that E, S, F, and
T do not themselves contain non-local control transfers.

Or let's do it in another language.

(do ()
((or (not E) (progn S F)))
  T)

That's Common Lisp.  To get the Scheme version, replace 'progn by  
'begin.


One can do very similar things in Algol 68, Pop-2, Pop-11, any member of
the Bliss family, BCPL, lots of languages.


1. There are boolean operations
2. Boolean expressions are evaluated from Left to Right
3. Boolean expressions can be short-circuited


You don't need 2 or 3.
Take the loop version and tweak it:

Stopped: Boolean := False;
while not Stopped loop
if E then
S;
if F then
Stopped := True;
else
T;
end if;
else
Stopped := True;
end if;
end loop;

In order to prove the transformation impossible, you now know that
you will need to assume that
A. You are not allowed to introduce any new variables.
B. You are not allowed to define any new procedures.
C. You are not allowed to use a programming language with a
   loop-and-a-half construct.

Ad C, consider Ada's

loop
exit when not E;
S;
exit when F;
T;
end loop;

It's a long time since I saw any reference to it, but there's
Zahn's situation-case, see http://en.wikipedia.org/wiki/ 
Zahn's_construct

This must also be ruled out under C.

In fact, you have to make so many apparently arbitary restrictions on
what you are allowed to do that the question becomes why?.  What *is*
the point of this exercise?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] About mplus

2007-09-05 Thread Henning Thielemann


On Tue, 4 Sep 2007, David Benbennick wrote:


On 9/4/07, ok [EMAIL PROTECTED] wrote:

I've been thinking about making a data type an instance of MonadPlus.
 From the Haddock documentation at haskell.org, I see that any such
instance should satisfy

mzero `mplus` x = x
x `mplus` mzero = x
mzero = f = mzero
v  mzero  = mzero

but is that all there is to it?  Are there no other requirements for
MonadPlus to make sense?


Also, mplus has to be associative.  I.e.
   (a `mplus` b) `mplus` c == a `mplus` (b `mplus` c)


I also wondered why, once MonadPlus was added to the language, the
definition of ++ wasn't changed to
(++) = MonadPlus
(with the MonadPlus instance for [] defined directly).


You mean (++) = mplus.  I've wondered that too.  Similarly, one should
define map = fmap.


I think it is very sensible to define the generalized function in terms of 
the specific one, not vice versa.



 And a lot of standard list functions can be
generalized to MonadPlus, for example you can define

filter :: (MonadPlus m) = (a - Bool) - m a - m a


Always using the most generalized form is not a good idea. If you know you 
are working on lists, 'map' and 'filter' tell the reader, that they are 
working on lists. The reader of a program doesn't need to start human type 
inference to deduce this. Also the type inference of the compiler will 
fail, if you write too general. Say, you are in GHCi, have your definition 
of 'filter' and you write


Prelude filter Char.isUpper (return 'a')

To what monad this shall be specialised? Rely on type defaulting? Ok, you 
can use type signatures.



See also:
 http://www.haskell.org/haskellwiki/Slim_instance_declaration
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] About mplus

2007-09-05 Thread ok

On 5 Sep 2007, at 6:16 pm, Henning Thielemann wrote:
I think it is very sensible to define the generalized function in  
terms of the specific one, not vice versa.


The specific point at issue is that I would rather use ++ than
`mplus`.  In every case where both are defined, they agree, so
it is rather frustrating to be blocked from using an operator
which would otherwise have been appropriate.

Of course it is not a show-stopper; I can simply make something
else up.

I am a little puzzled that there seems to be no connection between
MonadPlus and Monoid.  Monoid requires a unit and an associative
binary operator.  So does MonadPlus.  Unfortunately, they have different
names.  If only we'd had (Monoid m, Monad m) = MonadPlus m...


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-05 Thread Simon Peyton-Jones
| On that note, I've been finding GHC's type suggestions often worse
| than useless, and wish it wouldn't even bother to try -- even more
| confusing for new users to have the compiler suggest pointless things
| like declaring an instance of Num String or whatever. I'd prefer it
| if it could just tell me what *specific* part of an expression, which
| symbol even, the expected and inferred values differed. On the other
| hand, when trying to guess at operator precedence rules, the applied
| to too many and applied to too few errors are actually pretty handy.

It's difficult to make error messages helpful.  The best improvement mechanism 
I know is this:

when you come across a case where GHC produces an
unhelpful message, send it in, along with the program
that produced it,

AND

your suggestion for the error
message you'd like to have seen.

I don't promise instant action, but if you suffer in silence then nothing will 
improve.  Sending a message keeps it on our radar *and* provides an example to 
motivate improvements.  (Boiling the program down a bit is a help, so you don't 
have to send a massive tarball.)

Another thing that can be worth a try is to try your boiled-down program with 
Helium, whose error-message infrastructure has received much more conscious 
design attention than GHC's.

Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] About mplus

2007-09-05 Thread Henning Thielemann


On Wed, 5 Sep 2007, ok wrote:


On 5 Sep 2007, at 6:16 pm, Henning Thielemann wrote:

I think it is very sensible to define the generalized function in terms of 
the specific one, not vice versa.


The specific point at issue is that I would rather use ++ than
`mplus`.  In every case where both are defined, they agree, so
it is rather frustrating to be blocked from using an operator
which would otherwise have been appropriate.


What is your application, where you need (++) frequently? Today I like 
that (++) points me to the fact, that we are working on lists. Ok, I would 
be fine, if (++) would be a method for all sequence types. But for 
MonadPlus, this is too general for my taste.



I am a little puzzled that there seems to be no connection between
MonadPlus and Monoid.  Monoid requires a unit and an associative
binary operator.  So does MonadPlus.  Unfortunately, they have different
names.  If only we'd had (Monoid m, Monad m) = MonadPlus m...


Monoid is of kind *
MonadPlus is of kind * - *
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] About mplus

2007-09-05 Thread Jules Bean

David Benbennick wrote:

You mean (++) = mplus.  I've wondered that too.  Similarly, one should
define map = fmap.  And a lot of standard list functions can be
generalized to MonadPlus, for example you can define

filter :: (MonadPlus m) = (a - Bool) - m a - m a


Somehow this filter fails my intuition. Thanks to glguy on #haskell for 
showing me that you can define it as


filter p m = m = \x - if p x then return x else mzero

I want filter to commute with mplus:

(filter p m) `mplus` (filter p l) === filter p (m `plus` l)

This is true for lists, and seems to me a natural requirement for filter 
to be considered, well, a filter, along with the related filter p 
mzero == mzero. Unfortunately many of the MonadPlus instances we have 
don't satisfy that.


Jules

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] About mplus

2007-09-05 Thread Jules Bean

ok wrote:

On 5 Sep 2007, at 6:16 pm, Henning Thielemann wrote:
I think it is very sensible to define the generalized function in 
terms of the specific one, not vice versa.


The specific point at issue is that I would rather use ++ than
`mplus`.  In every case where both are defined, they agree, so
it is rather frustrating to be blocked from using an operator
which would otherwise have been appropriate.



You can. Just write:

(++) = mplus

in your programs (or in a module called OK.Utils or OK.Prelude!) and you 
can use ++. It's not (normally) a big problem to rename functions in 
haskell.



I am a little puzzled that there seems to be no connection between
MonadPlus and Monoid.  Monoid requires a unit and an associative
binary operator.  So does MonadPlus.  Unfortunately, they have different
names.  If only we'd had (Monoid m, Monad m) = MonadPlus m...


The correct connection is:

instance (Monoid (m a), Monad m) = MonadPlus m where
  mplus = mappend
  mzero = mempty


Except, of course, we can't reasonably require that. Because for any one 
Monad m, there will be many ways to make (m a) into a Monoid, and most 
of them will not form properly behaved MonadPlusses.


The converse notion is safer:

instance MonadPlus m = Monoid (m a) where
  mappend = mplus
  mempty = mzero

And I think the main reason we don't have this version, is that we can't 
cope well with multiple instances. Many data types admit more than one 
natural Monoid, and we don't have the language features to support that 
very cleanly.


For example, there is also the Monoid:

instance Monad m = Monoid (m ()) where
  mappend = ()
  mempty = return ()

and these two are not necessarily compatible. In fact, on [a] (or 
rather, [()]), the former gives us addition and the latter gives us 
multiplication, viewing [()] as isomorphic to Nat. These are two very 
well known monoids on Nat.



Jules
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-05 Thread Ketil Malde
On Wed, 2007-09-05 at 08:19 +0100, Simon Peyton-Jones wrote:

 | confusing for new users to have the compiler suggest pointless things
 | like declaring an instance of Num String or whatever. 

This also gets my vote for the
Error-message-most-likely-to-be-unhelpful-award.  IME, this often
arises from incorrect use of operators or wrong number of parameters,
not missing instances.

 It's difficult to make error messages helpful.  

Certainly. But better to err on the side of brevity.

 when you come across a case where GHC produces an
 unhelpful message, send it in, along with the program
 that produced it,

Contents of test/error.hs:
f x s = x + show s

Error message from GHCi:
test/error.hs:2:8:
No instance for (Num String)
  arising from use of `+' at test/error.hs:2:8-17
Possible fix: add an instance declaration for (Num String)
In the expression: x + (show s)
In the definition of `f': f x s = x + (show s)

 your suggestion for the error message you'd like to have seen.

Suggestion:
As is, with removal the Possible fix, as it is often misleading (i.e.
here, the programmer clearly meant to use '++' and not '+'.  Perhaps
rephrase to something like String is not an instance of Num?  For a
newbie, it may not be clear that Num is the class and String is the
type.

-k




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] ANNOUNCE: xmonad 0.3

2007-09-05 Thread Ketil Malde
On Wed, 2007-09-05 at 13:02 +1000, Donald Bruce Stewart wrote:

 The xmonad dev team is pleased to announce the 0.3 release of xmonad. 

I just wanted to congratulate the team, and say that xmonad is, along
with darcs, my favorite mainstream Haskell program.  I used to spend
days experimenting with different window managers and applets, docks and
whatnot; now I get so much more time to do more important stuff - like
spamming technical mailing lists with non-technical content.  But I
digress.  Nice work!

-k



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-05 Thread Simon Peyton-Jones
|  when you come across a case where GHC produces an
|  unhelpful message, send it in, along with the program
|  that produced it,
|
| Contents of test/error.hs:
| f x s = x + show s
|
| Error message from GHCi:
| test/error.hs:2:8:
| No instance for (Num String)
|   arising from use of `+' at test/error.hs:2:8-17
| Possible fix: add an instance declaration for (Num String)
| In the expression: x + (show s)
| In the definition of `f': f x s = x + (show s)
|
|  your suggestion for the error message you'd like to have seen.
|
| Suggestion:
| As is, with removal the Possible fix, as it is often misleading (i.e.
| here, the programmer clearly meant to use '++' and not '+'.

Is your suggestion specific to String?  E.g. if I wrote

data Complex = MkC Float Float

real :: Float - Complex
real f = MkC f 0

f x s = x + real 1

then I really might have intended to use Complex as a Num type, and the 
suggestion is precisely on target.  I'd be interested to know this particular 
helpful suggestion on GHC's part is more misleading than useful.  What do 
others think?

| rephrase to something like String is not an instance of Num?  For a
| newbie, it may not be clear that Num is the class and String is the
| type.

Good point.  Not so easy for multi-parameter type classes! E.g. No instance for 
(Bar String Int).  So we could have

String is not an instance of class Foo  -- single param
No instance for (Bar String Int)-- multi-param

Would that be better (single-param case is easier), or worse (inconsistent)?

Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-05 Thread Peter Verswyvelen
IMHO error reporting should be done in a hierarchical manner, so that 
you get a very brief description first, followed by many possible hints 
for fixing it, and each hint could have subhints etc... Now to make this 
easy to read, it should be integrated into some IDE of course, otherwise 
it would scare the hell out of newbies. When the system gets more clever 
(=AI stuff), it can hide much of the hierarchy, suggesting which hint is 
appropriate for the specific type of user. After all, depending on your 
skills, you will create different errors (although the stupid typo will 
be the most frequent?). Now I'm sure Simon can do the AI part much 
better than any computer ;-)


Cheers,
Peter Verswyvelen




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Off topic] Proving an impossibility

2007-09-05 Thread Jon Fairbairn
Sterling Clover [EMAIL PROTECTED] writes:


 of course you could rewrite this in a while loop too
 although you'd  have to use an assignment, but at least
 still not one with a silly  done variable.

People seem to have overlooked the bit of Algol68 I posted,
so I'll repeat it

While If E 
  Then S; F
  Else False
  Fi
Do T
Od

No break, no extra variables and natural to an A68
programmer, in fact much the same as a recursive function in
Haskell.

-- 
Jón Fairbairn [EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Elevator pitch for Haskell.

2007-09-05 Thread Ketil Malde

 WARNING: Learning Haskell is dangerous to your health!

:-)  I liked that so much I made a hazard image to go with it.

http://malde.org/~ketil/Hazard_lambda.svg

-k


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-05 Thread Ketil Malde
On Wed, 2007-09-05 at 09:56 +0100, Simon Peyton-Jones wrote:

 Is your suggestion specific to String? 

No.

 then I really might have intended to use Complex as a Num type

IME this is much rarer, and I think if a newbie is told that Complex is
not (but needs to be) and instance of Num, it is relatively easy to find
the relevant information (Looking up 'instance' and/or 'class' in the
index of any Haskell text book should do the trick)

 | rephrase to something like String is not an instance of Num?  For a
 | newbie, it may not be clear that Num is the class and String is the
 | type.
 
 Good point.  Not so easy for multi-parameter type classes! E.g. No instance 
 for (Bar String Int).  So we could have
 
 String is not an instance of class Foo  -- single param
 No instance for (Bar String Int)-- multi-param

If you quote things, you can also consider:

   'String Int' is not an instance of class 'Bar'.

Downside is that 'String Int' by itself may be confusingly unhaskellish.

-k


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Elevator pitch for Haskell.

2007-09-05 Thread Simon Marlow

Ketil Malde wrote:

WARNING: Learning Haskell is dangerous to your health!


:-)  I liked that so much I made a hazard image to go with it.

http://malde.org/~ketil/Hazard_lambda.svg


Cool! Can we have a license to reuse that image?  (I want it on a T-shirt)

Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-05 Thread Brandon S. Allbery KF8NH


On Sep 5, 2007, at 6:47 , Ketil Malde wrote:

On Wed, 2007-09-05 at 09:56 +0100, Simon Peyton-Jones wrote:
Good point.  Not so easy for multi-parameter type classes! E.g. No  
instance for (Bar String Int).  So we could have


String is not an instance of class Foo  -- single param
No instance for (Bar String Int)-- multi- 
param


If you quote things, you can also consider:

   'String Int' is not an instance of class 'Bar'.

Downside is that 'String Int' by itself may be confusingly  
unhaskellish.


I'd phrase it instead as:

  Class Num has no instance for String
  Class Num has no instance for Complex
  Class Bar has no instance for String and Int
(or maybe (String,Int) since it's conceptually similar to a  
tuple, and the formulation above could conceivably be misconstrued as  
looking for separate instances for String and Int?)


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Elevator pitch for Haskell.

2007-09-05 Thread Ketil Malde
On Wed, 2007-09-05 at 12:06 +0100, Simon Marlow wrote:
 Ketil Malde wrote:
  WARNING: Learning Haskell is dangerous to your health!
  
  :-)  I liked that so much I made a hazard image to go with it.
  
  http://malde.org/~ketil/Hazard_lambda.svg
 
 Cool! Can we have a license to reuse that image?  (I want it on a T-shirt)

Hereby licensed free for any imaginable use including creation of
derivative works. However, there is no warranty, neither express nor
implied of ever understanding category theory. :-)

-k

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-05 Thread Jules Bean

Ketil Malde wrote:


String is not an instance of class Foo  -- single param
No instance for (Bar String Int)-- multi-param


If you quote things, you can also consider:

   'String Int' is not an instance of class 'Bar'.

Downside is that 'String Int' by itself may be confusingly unhaskellish.


String is not an instance of class Foo
String and Int do not form an instance of multi-parameter class Bar


...alternatively, you can put the more mathsy form in brackets after the 
simple one, to make the generalisation from the single param to the 
multi-param more clear:


String is not an instance of class Foo (No instance for Foo String)
No instance for (Bar String Int)



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Elevator pitch for Haskell.

2007-09-05 Thread jerzy . karczmarczuk
Simon Marlow writes: 


Ketil Malde wrote:

WARNING: Learning Haskell is dangerous to your health!


:-)  I liked that so much I made a hazard image to go with it.
http://malde.org/~ketil/Hazard_lambda.svg


Cool! Can we have a license to reuse that image?  (I want it on a T-shirt)


People, are you crazy, with my deepest respect and friendliness...
You want to frighten newbies? it seems that they have already a good dose
of allergy... 


Some of them may *really* believe in that IRC citation, that Haskell is
bad since it makes people hate other languages. 


Actually, Haskell encouraged me to look more profoundly into other languages
such as Parsertongue,
and, well, you know better than myself that a good wizard is morally not
allowed to hate Muggles. Unless they become a nuisance. And a good wizard
is sweet as a lamb, and Unforgivable Spells like Monado! are to be used
only when unavoidable. 


Please be kind and cheerful. Don't attept to say to innocent that what
is on this picture
http://www.mansfield.ohio-state.edu/~sabedon/images/lambda_twins.jpg
are Dark Marks... 

Jerzy Karczmarczuk 



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-05 Thread Dan Piponi
On 9/5/07, Ketil Malde [EMAIL PROTECTED] wrote:
 On Wed, 2007-09-05 at 08:19 +0100, Simon Peyton-Jones wrote:
 Error message from GHCi:
 test/error.hs:2:8:
 No instance for (Num String)
   arising from use of `+' at test/error.hs:2:8-17
 Possible fix: add an instance declaration for (Num String)
 In the expression: x + (show s)
 In the definition of `f': f x s = x + (show s)

  your suggestion for the error message you'd like to have seen.

ghc --newbie-errors error.hs

. . .
. . .

Error message from GHCi:
test/error.hs:2:8:
You have tried to apply the operator '+' to 'x' and 'show s'
'show s' is a String.
I don't know how to apply '+' to a String.
May I suggest either:
(1) '+' is a method of type class Num. Tell me how to apply
'+' to a String by making String an instance of the class Num
(2) You didn't really mean '+'
In the expression: x + (show s)
In the definition of `f': f x s = x + (show s)
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-05 Thread Bulat Ziganshin
Hello Simon,

Wednesday, September 5, 2007, 11:19:28 AM, you wrote:

 when you come across a case where GHC produces an
 unhelpful message, send it in, along with the program
 that produced it,

i have put such tickets about year ago :)  basically, it was about
just changing wording: instead of inferred write:

Expected type: ...
Actual type: ...

http://hackage.haskell.org/trac/ghc/ticket/956

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-05 Thread Bulat Ziganshin
Hello Simon,

Wednesday, September 5, 2007, 12:56:18 PM, you wrote:

 String is not an instance of class Foo  -- single param
 No instance for (Bar String Int)-- multi-param

 Would that be better (single-param case is easier), or worse (inconsistent)?

easier - most classes are one-parameter



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Elevator pitch for Haskell.

2007-09-05 Thread Simon Michael
I agree actually. That picture, while very cool, won't help Haskell  
marketing one bit. :)


Lisp's made with alien technology is much more inviting:  
http://www.lisperati.com/logo.html .  I wish we could use it!


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-05 Thread Sterling Clover

I'd prefer something slightly more specific, such as instead of

No instance for (Num String)
  arising from use of `+' at test/error.hs:2:8-17
Possible fix: add an instance declaration for (Num String)
In the expression: x + (show s)
In the definition of `f': f x s = x + (show s)

Maybe
(+) is defined as Num a = a - a - a
The second argument of (+) is of type String at test/ 
error.hs:2:8-17

String is not an instance of Num
In the expression: x + (show s)
In the definition of `f': f x s = x + (show s)

It seems to me that anybody who gets declaring classes and instance  
declarations already will be able to figure out pretty quickly what  
to do if they wanted, e.g., Complex to be an instance of Real with a  
message like that. The problem is there's too much special-casing  
otherwise, since its not just Strings but other standard numeric  
types. For example, if I take mod $ sqrt n $ m then I probably  
don't want to declare an instance of Floating Int but just want to  
use a conversion operator like ceiling. Here's another related thing  
I ran into below (example simplified):


testErr :: Integral a = a - [a]
testErr n =
ceiling $ (exp $ sqrt $ log n) ** (1/2)

testMe.hs:8:14:
Could not deduce (Floating a) from the context (Integral a)
  arising from use of `**' at testMe.hs:8:14-42
Possible fix:
  add (Floating a) to the type signature(s) for `testErr'
In the second argument of `($)', namely
`(exp $ (sqrt $ (log n))) ** (1 / 2)'
In the expression: ceiling $ ((exp $ (sqrt $ (log n))) ** (1 / 2))
In the definition of `testErr':
testErr n = ceiling $ ((exp $ (sqrt $ (log n))) ** (1 / 2))

What I needed to do here was cast n using realToFrac (or at least I  
did that and it seemed to be the right decision). But, again, the  
compiler is suggesting that I declare something that's already an  
Integral as a Floating, which is conceptually similar to declaring an  
instance of Floating Integral (after all, it implies that such an  
instance can be/has been declared). Here the possible fix is a great  
deal more likely to be right, however, so I'm not sure it should be  
changed, except that a beginner might go and change Integral to  
Floating when they really *wanted* an Integral for other reasons. The  
real problem seems to be that the top level expression it returns is  
pretty huge.


If I remove the  ** (1/2) then I  get a message closer to the one  
I'd like:

Could not deduce (Floating a) from the context (Integral a)
  arising from use of `log' at testMe.hs:8:28-32
Possible fix:
  add (Floating a) to the type signature(s) for `testErr'
In the second argument of `($)', namely `log n'
In the second argument of `($)', namely `sqrt $ (log n)'
In the second argument of `($)', namely `(exp $ (sqrt $ (log n)))'

This seems like something more complicated with how the type- 
inference system works, and may not be as easily soluble, however.  
Alternately, it might lead to huge error-stack blowups in more  
complicated expressions?


Again, relatedly, and now I'm *really* digressing, if I don't fix a  
type signature for testErr but write it so that it needs conflicting  
types of n then I get (calling the function from main):


testErr n =
mod n $ ceiling $ (exp $ sqrt $ log n)

Ambiguous type variable `a' in the constraints:
  `Integral a' arising from use of `testErr' at testMe.hs:20:26-35
  `RealFrac a' arising from use of `testErr' at testMe.hs:20:26-35
  `Floating a' arising from use of `testErr' at testMe.hs:20:26-35
Probable fix: add a type signature that fixes these type variable 
(s)


Again, its probably too much to ask of the type-inference system that  
it catch this type error in parsing testErr itself. And the error  
message is pretty helpful because if I set a type signature, then it  
forces me to figure out the conflict. Still, if it could expand with  
which elements of testErr caused it to infer each type (if there is  
no explicit signature, there is), then maybe that could be useful?


--S

On Sep 5, 2007, at 4:56 AM, Simon Peyton-Jones wrote:


Is your suggestion specific to String?  E.g. if I wrote

data Complex = MkC Float Float

real :: Float - Complex
real f = MkC f 0

f x s = x + real 1

then I really might have intended to use Complex as a Num type, and  
the suggestion is precisely on target.  I'd be interested to know  
this particular helpful suggestion on GHC's part is more  
misleading than useful.  What do others think?


| rephrase to something like String is not an instance of Num?   
For a

| newbie, it may not be clear that Num is the class and String is the
| type.

Good point.  Not so easy for multi-parameter type classes! E.g. No  
instance for (Bar String Int).  So we could have


String is not an instance of class Foo  -- single param

Re: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-05 Thread Twan van Laarhoven

Bulat Ziganshin wrote:

Hello Simon,

Wednesday, September 5, 2007, 11:19:28 AM, you wrote:



   when you come across a case where GHC produces an
   unhelpful message, send it in, along with the program
   that produced it,



i have put such tickets about year ago :)  basically, it was about
just changing wording: instead of inferred write:

Expected type: ...
Actual type: ...


This doesn't help enough. What is an 'expected' type? How is it not 
'actual'? I want it to be immediatly clear which type is which.


Say I write
 x ++ 'y'
Right now the error is
Couldn't match expected type `[Char]' against inferred type `Char'
In the second argument of `(++)', namely 'y'

What always confuses me is which of these two types is the parameter I 
gave, and which is the one expected by the function? Changing 'infered' 
to 'actual' is an improvement, but it is not enough.


I would suggest:

(++) expects second argument to be of type '[Char]'
but was given 'y' of type 'Char'

Anothing thing that would be useful is *why* (++) expects a certian 
type, say I enter

 x ++ [1::Int]
Instead of the above, the following would be more useful:

the function (++) has type: [a] - [a] - [a]
the first argument suggests: a = Char
the second argument suggests: a = Int

Twan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Block-wise lazy sequences in Haskell

2007-09-05 Thread Henning Thielemann


 I want to have a data structure like Data.ByteString.Lazy, that is 
block-wise lazy, but polymorphic. I could use a lazy list of unboxed 
arrays (UArray) but the documentation says, that the element types are 
restricted. But I will need (strict) pairs of Double and the like as 
elements. It seems that I need generalized instances in order to use these 
arrays.
 I thought it must be possible to define an unboxed array type with 
Storable elements. I cannot find such a type in the standard libraries. 
Further on, I wonder why pairs are not instances of Storable.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-05 Thread Jonathan Cast
On Wed, 2007-09-05 at 19:50 +0200, Twan van Laarhoven wrote:
 Bulat Ziganshin wrote:
  Hello Simon,
  
  Wednesday, September 5, 2007, 11:19:28 AM, you wrote:
  
  
 when you come across a case where GHC produces an
 unhelpful message, send it in, along with the program
 that produced it,
  
  
  i have put such tickets about year ago :)  basically, it was about
  just changing wording: instead of inferred write:
  
  Expected type: ...
  Actual type: ...
 
 This doesn't help enough. What is an 'expected' type? How is it not 
 'actual'? I want it to be immediatly clear which type is which.
 
 Say I write
   x ++ 'y'
 Right now the error is
  Couldn't match expected type `[Char]' against inferred type `Char'
  In the second argument of `(++)', namely 'y'
 
 What always confuses me is which of these two types is the parameter I 
 gave, and which is the one expected by the function? Changing 'infered' 
 to 'actual' is an improvement, but it is not enough.
 
 I would suggest:
 
  (++) expects second argument to be of type '[Char]'
  but was given 'y' of type 'Char'
 
 Anothing thing that would be useful is *why* (++) expects a certian 
 type, say I enter
   x ++ [1::Int]
 Instead of the above, the following would be more useful:
 
  the function (++) has type: [a] - [a] - [a]
  the first argument suggests: a = Char
  the second argument suggests: a = Int

Maybe:

In the expression x ++ 'y':
(++) :: [a] - [a] - [a]
x :: String
'y' :: Char
(I expect the whole thing to have type String)

or

In the expression x ++ [1]:
(++) :: [a] - [a] - [a]
x :: String
[1] :: [Int]
(I expect the whole thing to have a type similar to [a])

jcc


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Block-wise lazy sequences in Haskell

2007-09-05 Thread Bryan O'Sullivan

Henning Thielemann wrote:

 I thought it must be possible to define an unboxed array type with 
Storable elements.


Yes, this just hasn't been done.  There would be a few potentially 
tricky corners, of course; Storable instances are not required to be 
fixed in size, though all the precanned instances are.  Using arbitrary 
Storable instances would make it necessary to scan an array linearly to 
get to a particular element, defeating one of the advantages of e.g. 
ByteStrings.



Further on, I wonder why pairs are not instances of Storable.


I think it hasn't been done simply because it hasn't been done.  The 
upcoming fusion-based list rewrite might hold some promise for relieving 
the pressure for this kind of work.


b
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Block-wise lazy sequences in Haskell

2007-09-05 Thread Henning Thielemann


On Wed, 5 Sep 2007, Bryan O'Sullivan wrote:


Henning Thielemann wrote:

 I thought it must be possible to define an unboxed array type with 
Storable elements.


Yes, this just hasn't been done.  There would be a few potentially tricky 
corners, of course; Storable instances are not required to be fixed in size, 
though all the precanned instances are.


I see. This could be solved with a StorableFixedSize class. But it hasn't 
been done, too, I assume.


 Using arbitrary Storable instances would make it necessary to scan an 
array linearly to get to a particular element, defeating one of the 
advantages of e.g. ByteStrings.


I doubt that someone is interested in such an array implementation.


Further on, I wonder why pairs are not instances of Storable.


I think it hasn't been done simply because it hasn't been done.


Maybe also because of the issue of varying sizes?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] (no subject)

2007-09-05 Thread Thomas Hartman
I think you want something like this

{-# OPTIONS -fglasgow-exts #-}

f :: (Integer, Float) - Integer
f (a,b) = a * floor (10/b) 

lst :: [(Integer, Integer)]
lst = [(a ^ 2 + b ^ 2, a) | a - [1..4], b - [1..4], a^2 + b^2  20, b = 
a]

lst3 = map (f) ( map ( intTupToFloatTup  ) lst )

intTupToFloatTup :: (Integer, Integer) - (Integer, Float)
intTupToFloatTup (int1, int2) = (int1, fromInteger int2)

load the whole thing into ghci with ghci proggie.hs

when I have this type of problem, my usual approach is to put the code 
into a text file, load that in ghci, derive type sigs on the functions 
that work, and then see if I can figure out
the mismatch.

you could probably get a fast answer to this kind of question on the 
#haskell irc channel as well.

hope this helps,

thomas.




Scott Williams [EMAIL PROTECTED] 
Sent by: [EMAIL PROTECTED]
09/05/2007 05:28 PM

To
Tomi Owens [EMAIL PROTECTED]
cc
haskell-cafe@haskell.org
Subject
[Haskell-cafe] Re: [Haskell] (no subject)






[bcc haskell, cc haskell-cafe]

On 9/5/07, Tomi Owens [EMAIL PROTECTED] wrote:
Hi there. I'm a teacher of Maths and am working my way through the Euler 
Project problems for fun. I have mostly been using Basic, but have read up 
about Haskell and think it looks like a sensible way to solve many of the 
problems. 

OK, so I've downloaded GHCi and am trying to teach myself. 

So far I have done this: 

  ___ ___ _ 
 / _ \ /\  /\/ __(_) 
/ /_\// /_/ / /  | |  GHC Interactive, version 6.6.1, for Haskell 98. 
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/ 
\/\/ /_/\/|_|  Type :? for help. 

Loading package base ... linking ... done. 
Prelude let f (a,b) = a * floor (10/b) 
Prelude f(2,5) 
4 

Here you can find out type ghci has inferred for this function.
 :t f
f :: (RealFrac b, Integral b1) = (b1, b) - b1

 

This function works just as I want it to. 

Now I try creating a list: 

Prelude [(a2+b2,a)| a - [1..4] , b- [1..4], a2+b220, b=a] 
[(2,1),(5,2),(8,2),(10,3),(13,3),(18,3),(17,4)] 

Let's assign this to an intermediate variable so we can query it's type:

Prelude let lst = [(a ^ 2 + b ^ 2, a) | a - [1..4], b - [1..4], a^2 + 
b^2  20, b = a]
Prelude lst 
[(2,1),(5,2),(8,2),(10,3),(13,3),(18,3),(17,4)]
Prelude :t lst
lst :: [(Integer, Integer)]

aha; here's the source of the type mismatch:
Prelude :t floor
floor :: (RealFrac a, Integral b) = a - b 

Floor has to take a RealFrac. According to hoogle[1], we can use various 
floating-point approximations (Float, Double, CFloat, etc) or we can use 
the exact Rational type.
[1] http://haskell.org/hoogle/?q=RealFrac

You can get your types to match by declaring your list to be of type 
[(Rational, Rational)] either by explicitly typing one of the untyped 
variables or the entire expression: 
Prelude let lst = [(a ^ 2 + b ^ 2, a) | (a::Rational) - [1..4], b - 
[1..4], a^2 + b^2  20, b = a]
Prelude :t lst
lst :: [(Rational, Rational)]
Prelude let lst :: [(Rational, Rational)] = [(a ^ 2 + b ^ 2, a) | a - 
[1..4], b - [1..4], a^2 + b^2  20, b = a] 
Prelude :t lst
lst :: [(Rational, Rational)]


and this works 
So now I try to apply the function to the list: 

Prelude map (f) [(a2+b2,a)| a - [1..4] , b- [1..4], a2+b220, b=a] 

and I get this result: 

interactive:1:5: 
   Ambiguous type variable `t' in the constraints: 
 `Integral t' arising from use of `f' at interactive:1:5 
 `RealFrac t' arising from use of `f' at interactive:1:5 
   Probable fix: add a type signature that fixes these type variable(s) 
I'm sorry, but I don't quite get how to set the type signature and how it 
will apply to my function... 

Thanks, 

Hope this helps
 

Tomi 

 

Department for Education, Sport and Culture E Mail
This message is for the named person's use only. It may contain
confidential, proprietary or legally privileged information. No
confidentiality or privilege is waived or lost by any mistransmission.
If you receive this message in error, please immediately delete it and all 
copies of it from your system, destroy any hard copies of it and notify 
the sender. You must not, directly or indirectly, use, disclose, 
distribute, print, or copy any part of this message if you are not the 
intended recipient. The Department for Education, Sport and Culture and 
any of its establishments each reserve the right to monitor all e-mail 
communications through its networks. 
Any views expressed in this message are those of the individual sender, 
except where the message states otherwise and the sender is authorised to 
state them to be the views of any such entity. 
The Department for Education, Sport and Culture shall not be liable to the 
recipient or any third party for any loss or damage, however it appears, 
from this e-mail or its content. This includes loss or damage caused by 
viruses. It is the responsibility of the recipient to ensure that the 
opening of this message and its 

Re: [Haskell-cafe] About mplus

2007-09-05 Thread ajb

G'day all.

Slight nit...

Quoting ok [EMAIL PROTECTED]:


I've been thinking about making a data type an instance of MonadPlus.
From the Haddock documentation at haskell.org, I see that any such
instance should satisfy

mzero `mplus` x = x
x `mplus` mzero = x
mzero = f = mzero
v  mzero  = mzero


As discussed previously, that last law is wrong.  In particular, it
can't be true of any monad transformer:

lift fireMissiles  mzero /= mzero


but is that all there is to it?  Are there no other requirements for
MonadPlus to make sense?


It's proposed to split nondeterminism-like monads and error catch-like
monads to allow for some other laws:

http://haskell.org/haskellwiki/MonadPlus_reform_proposal

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: xmonad 0.3

2007-09-05 Thread Max Vasin
2007/9/5, Peter Verswyvelen [EMAIL PROTECTED]:
 Looks really nice, but if I understand it correctly it is specific for
 X, so does not work on Windows?
This kind of programs is impossible in Windows. Of cause you can use X
server for Windows and xmonad as window manager with X server.

 If so, would it be possible to integrate this into GTK2HS so it works as
 a docking manager inside an application?
First of all, gtk is a cross platform toolkit and gtk2hs is just a
wrapper. It will be better to implement a docking manager in C to let
whole gtk community use it.

-- 
WBR,
Max Vasin

JID: [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-05 Thread Peter Verswyvelen
Instead of just adapting the compiler to give better errors, it would 
really help if a unique identifier was assigned to each error/warning, 
and if a WIKI and help file existed that describes the errors in detail. 
Maybe this is already the case, but after a quick search I failed to 
find such a list of errors.


Cheers,
Peter

Bulat Ziganshin wrote:

Hello Simon,

Wednesday, September 5, 2007, 12:56:18 PM, you wrote:

  

String is not an instance of class Foo  -- single param
No instance for (Bar String Int)-- multi-param



  

Would that be better (single-param case is easier), or worse (inconsistent)?



easier - most classes are one-parameter



  


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe