Re[2]: [Haskell-cafe] C++ class = neutered (haskell class + haskell existential)

2006-08-17 Thread Bulat Ziganshin
Hello Thomas,

Friday, August 18, 2006, 7:57:13 AM, you wrote:

>> There is a major difference though, in C++ (or java, or sather, or c#,
>> etc..) the dictionary is always attached to the value, the actual class
>> data type you pass around. in haskell, the dictionary is passed
>> separately and the appropriae one is infered by the type system. C++
>> doesn't infer, it just assumes everything will be carying around its
>> dictionary with it.

> C++ programmers deal with this using a number of techniques, mostly
> involving templates.

Haskell type classes are closer to templates/generics than to classes
itself

> Actually, there is one technique using C++ templates that I really
> want to see going mainstream in the Haskell implementations.
> Existential types are already there, now I want to see associated
> types (trait types in C++). Maybe I've been doing too much C++
> programming in the last few years, but a lot of the times when I end
> up using multiparameter type classes, what I really want is an
> associated type.

i also wrote a lot of such code for Streams library and can say that
MPTC+FD are close enough to emulate AT, although need slightly more
verbose definitions. moreover, AT are already implemented in GHC 6.5,
afai seen in ghc-cvs reports

> For those who are interested, I'm sure the relevant papers are readily
> available on citeseer/Google. :-)

http://haskell.org/haskellwiki/Research_papers/Type_systems#Associated_types

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] HaXml question

2006-08-17 Thread Tim Newsham

I thought this one would be easy but I'm starting to think its not.
I am playing with HaXml and I want to transform an XML tree into
another tree.  The transforms are simple enough, but the kicker
is that I want them to be "stateful."  In this example, the state
is a random number generator.  So the transformation depends on
the current node and the random number generator state.  I want
to transform every node in the tree.

My feeble attempt at this is given in:
  http://www.thenewsh.com/~newsham/x/tweaker.hs

What I see when I run it is that the value of "p" in the "tweak"
function is identical each time.  Indeed, it seems "g" itself
is the same each time "tweak" is invoked (I wrote a variant of
the program that used sequential integers instead of generators
to verify this).

So here's what I think is going on.  You can probably skip this
section because I am probably off base anyway...  I guess "keep"
is being applied to one node, and returning a list of 1 node,
and this is zipped with my infinite list of generators and as
a result I get the same generator each time.  If this is the case
I guess foldXml is not the right tool for this job.  Perhaps I
want a newly-written foldXml that works with LabelFilters rather
than CFilters?

Ok.. so what's really going on here.  Can I do what I want to do?
Whats the right tool to transform every node in the tree?  Is there
a more general approach to doing stateful transformations?

Thanks in advance for letting me waste your time.

P.S. any stylistic advice, or alternate approaches also welcome.
The objective here is to learn...

Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] C++ class = neutered (haskell class + haskell existential)

2006-08-17 Thread Thomas Conway

On 8/18/06, John Meacham <[EMAIL PROTECTED]> wrote:
   [lots of good argument before and after deleted]


There is a major difference though, in C++ (or java, or sather, or c#,
etc..) the dictionary is always attached to the value, the actual class
data type you pass around. in haskell, the dictionary is passed
separately and the appropriae one is infered by the type system. C++
doesn't infer, it just assumes everything will be carying around its
dictionary with it.


C++ programmers deal with this using a number of techniques, mostly
involving templates.

Actually, there is one technique using C++ templates that I really
want to see going mainstream in the Haskell implementations.
Existential types are already there, now I want to see associated
types (trait types in C++). Maybe I've been doing too much C++
programming in the last few years, but a lot of the times when I end
up using multiparameter type classes, what I really want is an
associated type. For example

class Monad s => Store s where
   type Key
   insert :: Binary -> s Key
   retrStore :: Key -> s Binary
   ...

so that part of the instance is a choice of the key type.

For those who are interested, I'm sure the relevant papers are readily
available on citeseer/Google. :-)

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


Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Brian Hulley

Jared Updike wrote:

In other words, superscripts bind tighter than prefix ops but prefix
ops bind tighter than infix.


I see. My point is that there already exists a convention[1] that the
way to type in
   2
   -4
is -4^2 which means -(4^2) not (-4)^2 because - as a prefix op has the
same precedence as binary subtraction, not super tight like normal
prefix ops (i.e. normal function application) as you would like it to
be (if I understand correctly). You are welcome to break an existing
(unofficial) convention for the sake of lexical syntax[2].
[2] http://wadler.blogspot.com/2006/01/bikeshed-coloring.html


This choice of precedence for unary - conflicts with the normal usage in 
languages like C, where unary ops "obviously" bind tighter than infix.


The typesetting in maths conveys a lot of info eg to distinguish f -x from 
f - x or f-x, and so the relationship between the visual representation and 
the meaning depends on a knowledge of various conventions that have evolved 
over time, and the knowledge of when to apply them in a given context.


In contrast, a programming language should be based on general concepts 
uniformly applied. In Haskell we have operators, identifiers, prefix 
application using an identifier and infix application using a symbol, and a 
uniform way to convert a symbol to an identifier and vice versa, and a 
uniform way of forming sections.


All this machinery should be enough to be satisfied with. However, someone 
somewhere decided that one trivial arithmetic operation, namely unary minus, 
should be allowed to totally ruin everything, and not only that, but that 
half of any number line, the positives, should (literally!) have a special 
advantage over the other half, the negatives.


Thus while I can agree with Wadler that it's easy to have different opinions 
on "little" issues, I think that in this case the goal of uniformity leads 
to an objective answer.


Of course not all languages care about being uniform or neat ;-)

Best regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread John Meacham
On Fri, Aug 18, 2006 at 12:20:54AM +0100, Brian Hulley wrote:
>data Integer = ... | -1 | 0 | 1 | ...
> 
> tells me that the negative and positive integers are on an equal footing.
> 
> Ie the language is sending out a "mixed message" about the integers, which 
> is confusing.

Not only that but there is a run-time penalty for every polymorphic
negattive literal!

-3 desugars to negate (fromInteger 3)  rather than (fromInteger -3) so
you end up having to do 2 dictionary lookups (one for fromInteger, one
for negate) and indirect function calls rather than just the one.

John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] C++ class = neutered (haskell class + haskell existential)

2006-08-17 Thread John Meacham
On Tue, Aug 15, 2006 at 08:36:28PM +0200, Gabriel Dos Reis wrote:
> Roughly Haskell type classes correspond to parameterized abstract
> classes in C++ (i.e. class templates with virtual functions 
> representing the operations).  Instance declarations correspond to
> derivation and implementations of those parameterized classes.

There is a major difference though, in C++ (or java, or sather, or c#,
etc..) the dictionary is always attached to the value, the actual class
data type you pass around. in haskell, the dictionary is passed
separately and the appropriae one is infered by the type system. C++
doesn't infer, it just assumes everything will be carying around its
dictionary with it.

this makes haskell classes signifigantly more powerful in many ways.

class Num a where
   (+) :: a -> a -> a

is imposible to express in OO classes, since both arguments to +
necessarily carry their dictionaries with them, there is no way to
statically guarentee they have the same one. Haskell will pass a single
dictionary that is shared by both types so it can handle this just fine.

in haskell you can do

class Monoid a where
mempty :: a

in OOP, this cannot be done because where does the dicionary come from?
since dictionaries are always attached to a concrete class, every method
must take at least one argument of the class type (in fact, exactly one,
as I'll show below). In haskell again, this is not a problem since the
dictionary is passed in by the consumer of 'mempty', mempty need not
conjure one out of thin air.


In fact, OO classes can only express single parameter type classes where
the type argument appears exactly once in strictly covariant position.
in particular, it is pretty much always the first argument and often
(but not always) named 'self' or 'this'.


class HasSize a where
getSize :: a -> Int

can be expressed in OO, 'a' appears only once, as its first argument.


Now, another thing OO classes can do is they give you the ability to
create existential collections (?) of objects. as in, you can have a
list of things that have a size. In haskell, the ability to do this is
independent of the class (which is why haskell classes can be more
powerful) and is appropriately named existential types.

data Sized = exists a . HasSize a => Sized a 

what does this give you? you can now create a list of things that have a
size  [Sized] yay!

and you can declare an instance for sized, so you can use all your
methods on it.

instance HasSize Sized where
getSize (Sized a) = a


an exisential, like Sized, is a value that is passed around with its
dictionary in tow, as in, it is an OO class! I think this is where
people get confused when comparing OO classes to haskell classes. _there
is no way to do so without bringing existentials into play_. OO classes
are inherently existential in nature.

so, an OO abstract class declaration declares the equivalent of 3 things
in haskell: a class to establish the mehods, an existential type to
carry the values about, and an instance of the class for the exisential
type.

an OO concrete class declares all of the above plus a data declaration
for some concrete representation.


OO classes can be perfectly (even down to the runtime representation!)
emulated in Haskell, but not vice versa. since OO languages tie class
declarations to existentials, they are limited to only the intersection
of their capabilities, because haskell has separate concepts for them,
each is independently much much more powerful.

data CanApply = exists a b . CanApply (a -> b) a (b -> a)

is an example of something that cannot be expressed in OO, existentials
are limited to having exactly a single value since they are tied to a
single dictionary


class Num a where
   (+) :: a -> a -> a
   zero :: a
   negate :: a -> a

cannot be expressed in OO, because there is no way to pass in the same
dicionary for two elements, or for a returning value to conjure up a
dictionary out of thin air. (if you are not convinced, try writing a
'Number' existential and making it an instance of Num and it will be
clear why it is not possible)

negate is an interesting one, there is no technical reason it cannot be
implemented in OO languages, but none seem to actually support it.


so, when comparing, remember an OO class always cooresponds to a haskell
class + a related haskell existential.


incidentally, an extension I am working on is to allow

data Sized = exists a . HasSize a => Sized a 
deriving(HasSize)

which would have the obvious interpretation, obviously it would only work
under the same limitations as OO classes have, but it would be a simple
way for haskell programs to declare OO style classes if they so choose.

(actually, it is still signifigantly more powerful than OO classes since
you can derive many instances, and even declare your own for classes
that don't meet the OO consraints, also, your single class argument need
not appear as the first one. it can appear in any strictly co

Re: [Haskell-cafe] A restricted subset of CPP included in a revisionof Haskell 98

2006-08-17 Thread Lennart Augustsson


On Aug 17, 2006, at 17:11 , Brian Hulley wrote:


On Thursday, August 17, 2006 7:54 PM, Brian Smith  wrote:


I want to have conditionals limited in their placement
to make things easier for refactoring tools. But, I
don't have any ideas about how to deal with
conditional exports without allowing preprocessor
conditionals in the export list.


It seems to me that all uses of the preprocessor could be avoided  
except for cases like:


   #ifdef _SPARC
   -- sparc code
   #else
   #ifdef _INTEL86
   -- i86 code
   #else
   -- byte code
   #endif
   #endif


That's one of the worst ways to use CPP.  The code generator should  
have a parameter that determines what to generate code for.  That's  
much nicer in many ways.


-- Lennart

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


Re: [Haskell-cafe] A restricted subset of CPP included in a revision of Haskell 98

2006-08-17 Thread Lennart Augustsson
Even though I'm largely responsible for making CPP available in a  
Haskell compiler I think it's an abomination.  It should be avoided.
If we standardize it, people will use it even more.  I think we  
should discourage it instead, then looking at exactly what it's used  
for and supplying sane versions of it.


-- Lennart

On Aug 17, 2006, at 12:44 , Brian Smith wrote:


Hi,

I find it strange that right now almost every Haskell program  
directly or indirectly (through FPTOOLS) depends on CPP, yet there  
is no effort to replace CPP with something better or standardize  
its usage in Haskell. According to the following document, and my  
own limited experience in reading Haskell code, CPP is the most  
frequently used extension:
http://hackage.haskell.org/trac/haskell-prime/wiki/ 
HaskellExtensions
I think that if we accepted that CPP was part of the language, we  
could then place some restrictions on its use to facilitate easier  
parsing. Here are some suggestions, off the top of my head:


* #define can only be used for parameterless definitions
* #define'd symbols are only visible to the preprocessor
* #define can only give a symbol a value that is a valid  
preprocessor expression

* #define can only appear above the module declaration
* a preprocessor symbol, once defined, cannot be undefined or  
redefined

* #include and #undef are prohibited
* The preprocessor can only be used at the top level. In  
particular, a prepropcessor conditional, #error, #warn, #line would  
not be allowed within the export list or within a top-level binding.
* A Haskell program must assume that any top-level symbol  
definitions are constant over the entire program. For example, a  
program must not depend on having one module compiled with one set  
of command-line preprocessor symbol bindings and another module  
defined with a different set of bindings.
* preprocessor directives must obey Haskell's layout rules. For  
example, an #if cannot be indented more than the bindings it contains.


The result would be:
* Syntax can be fully checked without knowing the values of any  
preprocessor symbols.
* Preprocessor syntax can be added easily to a Haskell parser's BNF  
description of Haskell.
* No tool will need to support per-file/module preprocessor symbol  
bindings.


Again, all this is just off the top of my head. I am curious about  
what problems these restrictions might cause, especially for  
existing programs. I know that GHC itself uses some features that  
would be prohibited here. But, GHC is really difficult for tools to  
handle even with these restrictions on its source code. For now, I  
am more interested in the libraries in FPTOOLS and users' programs.  
What libraries/programs cannot easily be reorganizated to meet  
these restrictions? I suspect "#define'd symbols are only visible  
to the preprocessor" would be the most troublesome one.


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


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


Re: [Haskell-cafe] Description of Haskell extensions used by FPTOOLS

2006-08-17 Thread Donald Bruce Stewart
brianlsmith:
> 
>Is there any design document for the FPTOOLS libraries or
>some description of language features that are (allowed to
>be) used in them?

There's a list of extensions used at the bottom of this page:
http://hackage.haskell.org/trac/haskell-prime/wiki/HaskellExtensions

>I am going to be taking some significant time off from my
>normal jobs in the upcoming months. During part of that
>time, I would like to do some work to improve the Haskell
>toolchain. This involves creating or improving tools that
>parse and analyze Haskell code. My goal is to have these
>tools support enough of Haskell to be able to handle at
>least the most important libraries used by Haskell
>programmers. In particular, this includes all or most of the
>libraries in FPTOOLS. Plus, I want these tools to operate on
>Darcs as it is an obvious poster-child for Haskell. Thus, I
>need to support Haskell 98 plus all the extensions being
>used in Darcs and FPTOOLS as of approx. March, 2007 (as I
>intened to start working again at that time).

Cool!

>It would be very nice if there was some document that
>described "Haskell 98 plus all the extensions being used in
>Darcs and FPTOOLS as of March, 2007." Besides being useful
>to me, it would be a useful guide for potential contributors
>to FPTOOLS.

Darcs may also use GADTs then (not in the standard libs). Better check
with the darcs src.

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


Re: [Haskell-cafe] A restricted subset of CPP included in a revision of Haskell 98

2006-08-17 Thread Donald Bruce Stewart
brianlsmith:
> 
>Hi,
>I find it strange that right now almost every Haskell
>program directly or indirectly (through FPTOOLS) depends on
>CPP, yet there is no effort to replace CPP with something
>better or standardize its usage in Haskell. According to the

Note also cpphs,
http://www.cs.york.ac.uk/fp/cpphs/

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


Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Jared Updike

Yes but my point is that -4^2 is not the same as

2
-4

because the latter by convention means - (4^2).



In other words, superscripts bind tighter than prefix ops but prefix ops
bind tighter than infix.


I see. My point is that there already exists a convention[1] that the
way to type in
  2
-4
is -4^2 which means -(4^2) not (-4)^2 because - as a prefix op has the
same precedence as binary subtraction, not super tight like normal
prefix ops (i.e. normal function application) as you would like it to
be (if I understand correctly). You are welcome to break an existing
(unofficial) convention for the sake of lexical syntax[2].

Cheers,
 Jared.

[1] On my TI89 calculator (where there are even two - buttons: a
little "negative unary" button and a "binary subtract" button). It
pretty prints
  2
-4 =  -16
when I punch in -4^2  (where - is the "negative unary" button). The
answer is -16. Python (-4**2 = -4 ** 2 = - 4 ** 2 = -16) and Matlab
and Mathematica agree (-4^2 = -4 ^ 2 = - 4 ^ 2 = -16).

[2] http://wadler.blogspot.com/2006/01/bikeshed-coloring.html

--
http://www.updike.org/~jared/
reverse ")-:"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] More threading confusion

2006-08-17 Thread Chris Kuklewicz

Creighton Hogg wrote:

Good afternoon Haskellers,

So I'm trying to understand how STM works, and wrote a quick 'eating 
philosophers' example to see if I understood how it's supposed to work.

The problem is that while it executes, it doesn't appear to *do* anything.

Did I completely write things wrongheadedly or am I being bitten by 
something more subtle?




One of the things biting you is more subtle.  Since it is Aug 18th,2006, lets 
call that "snake #1".  Another is the single TVar, call that "snake #2":



Thanks.

import Control.Concurrent.STM
import Control.Concurrent
import Data.Array
import System.Random

think :: IO ()
think = do
  ms <- randomRIO (20,1000)
  threadDelay ms

data Philosopher = Philosopher {left::Bool,right::Bool,neighbors::(Int,Int)}
 deriving Show

makeInitPhilosopher a = Philosopher {left=False,right=False,neighbors=a}


Each philosopher starts with False False.

   


initPhilosophers = listArray (0,4)
   (map makeInitPhilosopher [(1,4),(2,0),(3,1),(4,2),(0,3)])


So philosopher 0 sits next to 1 and 4, and #1 sits next to 2 and 0.  Okay.



main = do
   z <- atomically $ newTVar initPhilosophers


There is a single TVar in the program with the global state.  By the way: This 
is not the best design, since it prevents concurrent updates.  Imagine 
philosopher #0 and #2 both taking left and right.  They will both contest the 
single TVar and one will have to retry even though this is unneeded.  This is 
snake #2.



   mapM_ (\x -> forkIO (loop x z 0 1)) [0,1,2,3,4]


This is good, but "main" finished immediately.  This may end your program...I 
forget the semantics of the extra threads.




loop n tps c l | c > l = (atomically (readTVar tps)) >>= (\x -> print x)
 | otherwise = do
   think 
   atomically $ eat n tps


So the atomic action of eat either will run to completion, or be retried.  The 
other philosophers only notice eat when it finishes.



   loop n tps (c+1) l

eat :: Int -> TVar (Array Int Philosopher) -> STM ()
eat n tps = do
  takeLeft n tps
  takeRight n tps
  releaseLeft n tps
  releaseRight n tps


Hmmm... if release undoes take then when eat completes there will be no visible 
change.  In that case "atomically $ eat n tps" will have had no affect on other 
parts of the program.  This could be snake #1




takeLeft :: Int -> TVar (Array Int Philosopher) -> STM ()
takeLeft n tps = do
  ps <- readTVar tps
  let p = ps ! n
  if right (ps ! (fst $ neighbors p)) == False
 then (writeTVar tps $ ps // [(n,p{left=True})])
 else retry


Okay.  I can see that if both #0's left and #1's right are both "True" then they 
are both holding the same piece of silverware, and this code is designed to 
avoid that. Skipping the *Right code:



releaseLeft n tps = do
  ps <- readTVar tps
  let p = ps ! n
  writeTVar tps $ ps // [(n,p{left=False})]
   


Okay, this reverses takeLeft.


So your "atomically $ eat", if it succeeds, changes the array in the TVar and 
then changes it back to what it was before.


If any other philosopher eats in the meantime, then you have to retry eating. 
So only one philosopher will get to eat at a time.  This is a poor solution to 
the problem.


Suggestion for killing snake #1: Give each piece of silverware a TVar.  Perhaps 
an (Array (TVar (Maybe Int))).  Philosopher #3 claims a piece by changing it 
from Nothing to (Just 3).  Now the silverware has a hope of being picked up in 
parallel.


Suggestion for killing snake #2:  Change atomically $ eat to

do atomically $ (takeRight ... >> takeLeft ...)
   -- print "Mmm... tasty snake" -- yield -- threadDelay
   atomically $ (releaseRight ... >> releaseLeft ...)


Now when a diner gets the silverware she can only get both or "retry".  Then 
other diners can see the first atomically block committed and they will block 
waiting for the silverware (only the TVars they need).

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


Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Brian Hulley

David House wrote:

On 17/08/06, Brian Hulley <[EMAIL PROTECTED]> wrote:

Literal highlighting in the editor would make it clear that x-2 ===
x (-2). I think a basic issue is that at the moment it is strange
that non-negative numbers can be specified as literals but negative
numbers can't - they can only get in through the "back door" of
evaluation - which just doesn't seem right.


You also can't specify string literals: they're sugar for
'a':'b':'c':[]. You seem to be arguing that syntactic sugar, and by
extension, a small core language, is bad.


All I'm saying is that given a type, either all the inhabitants should have 
a literal form or none of them should, because otherwise the availability of 
literals skews one's relationship to the inhabitants.


Ie the lack of negative literals tells me that I should think of negative 
integers as being "derived" from positive integers via negation, whereas the 
declaration


   data Integer = ... | -1 | 0 | 1 | ...

tells me that the negative and positive integers are on an equal footing.

Ie the language is sending out a "mixed message" about the integers, which 
is confusing.


Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Brian Hulley

Jared Updike wrote:

I'd also argue that in maths the necessary brackets are implied by
the superscripting syntax


ASCII text parsing issues aside, in math,

   2
-4   =?

(No you cannot ask if there is space between the 4 and the - symbol,
or if I "meant" (-4)^2   or -(4^2), or if I wrote a negative sign or a
subtract sign. I believe there is only one standard interpretation
here.)


Yes but my point is that -4^2 is not the same as

   2
   -4

because the latter by convention means - (4^2).

In other words, superscripts bind tighter than prefix ops but prefix ops 
bind tighter than infix.





they can only get in through the "back door" of evaluation
which just doesn't seem right.


Constant folding can eliminate any runtime cost, so effectively 0 - 2
==> negative 2 at compile time. No problem.


An Int8 has the range -128 to +127 inclusive, so I'd have expected a problem 
with the expression


   negate (128 :: Int8)

However I see from 
http://en.wikipedia.org/wiki/Two's_complement#The_weird_number that this 
works because -128 === +128 ie


  negate (128::Int8)
   ===negate (-128)-- literal to typed value
   ===(+128)  -- negation
   ===(-128)   -- overflow ignored

Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] A restricted subset of CPP included in a revisionof Haskell 98

2006-08-17 Thread Brian Hulley

On Thursday, August 17, 2006 7:54 PM, Brian Smith  wrote:


I want to have conditionals limited in their placement
to make things easier for refactoring tools. But, I
don't have any ideas about how to deal with
conditional exports without allowing preprocessor
conditionals in the export list.


It seems to me that all uses of the preprocessor could be avoided except for 
cases like:


   #ifdef _SPARC
   -- sparc code
   #else
   #ifdef _INTEL86
   -- i86 code
   #else
   -- byte code
   #endif
   #endif

and the above could afaics be dealt with by having a conditional import 
directive eg:


   module Platforms (Platform(..)) where
   data Platform = Sparc | Intel | ByteCode

   module Client where
   import Platform

   import qualified (

   case #Platform of
   Sparc -> Compiler.Sparc.CodeGen
   Intel -> Compiler.Intel.CodeGen
   _ -> Compiler.ByteCode.CodeGen

   ) as CodeGen

where a leading '#' denotes a preprocessor symbol (corresponding to the type 
of the same name) which can only be set outside the program ie on the 
command line, thus ensuring that the same module can't have multiple 
interpretations in the same program.


Conditions could be formed using case, if, and expressions which can be 
evaluated at compile time.


Of course this would require some effort to modify existing code, but it 
would have the great advantage that the conditional compilation would be 
well typed and be part of the normal grammar thus making it easier to write 
refactoring tools.


Regards, (another) Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

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


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


Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread John Meacham
On Thu, Aug 17, 2006 at 09:17:39PM +0100, David House wrote:
> On 17/08/06, Brian Hulley <[EMAIL PROTECTED]> wrote:
> >Literal highlighting in the editor would make it clear that x-2 === x (-2).
> >I think a basic issue is that at the moment it is strange that non-negative
> >numbers can be specified as literals but negative numbers can't - they can
> >only get in through the "back door" of evaluation - which just doesn't seem
> >right.
> 
> You also can't specify string literals: they're sugar for
> 'a':'b':'c':[]. You seem to be arguing that syntactic sugar, and by
> extension, a small core language, is bad.

No, I think he is saying this particular piece of syntactic sugar is more
like syntactic castor oil. Also, the main reason it needed to be
"special" was not for terms, but for n+k patterns, where you couldn't
use 'negate' and have it parse properly. but n+k patterns are likely to
be dropped anyway so we might as well do away with this subwart too.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Jared Updike

I'd also argue that in maths the necessary brackets are implied by the
superscripting syntax


ASCII text parsing issues aside, in math,

   2
-4   =?

(No you cannot ask if there is space between the 4 and the - symbol,
or if I "meant" (-4)^2   or -(4^2), or if I wrote a negative sign or a
subtract sign. I believe there is only one standard interpretation
here.)


they can only get in through the "back door" of evaluation
which just doesn't seem right.


Constant folding can eliminate any runtime cost, so effectively 0 - 2
==> negative 2 at compile time. No problem.

 Jared

--
http://www.updike.org/~jared/
reverse ")-:"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread David House

On 17/08/06, Brian Hulley <[EMAIL PROTECTED]> wrote:

Literal highlighting in the editor would make it clear that x-2 === x (-2).
I think a basic issue is that at the moment it is strange that non-negative
numbers can be specified as literals but negative numbers can't - they can
only get in through the "back door" of evaluation - which just doesn't seem
right.


You also can't specify string literals: they're sugar for
'a':'b':'c':[]. You seem to be arguing that syntactic sugar, and by
extension, a small core language, is bad.

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


Re: [Haskell-cafe] More threading confusion

2006-08-17 Thread Robert Dockins


On Aug 17, 2006, at 3:48 PM, Creighton Hogg wrote:


Good afternoon Haskellers,

So I'm trying to understand how STM works, and wrote a quick  
'eating philosophers' example to see if I understood how it's  
supposed to work.
The problem is that while it executes, it doesn't appear to *do*  
anything.


Did I completely write things wrongheadedly or am I being bitten by  
something more subtle?


From a quick read, it looks like your program doesn't produce any  
output until a philosopher finishes 1 think/eat iterations.   
Something tells me that could take awhile




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


[Haskell-cafe] More threading confusion

2006-08-17 Thread Creighton Hogg
Good afternoon Haskellers,So I'm trying to understand how STM works, and wrote a quick 'eating philosophers' example to see if I understood how it's supposed to work.The problem is that while it executes, it doesn't appear to *do* anything.
Did I completely write things wrongheadedly or am I being bitten by something more subtle?Thanks.import Control.Concurrent.STMimport Control.Concurrentimport Data.Arrayimport System.Random
think :: IO ()think = do  ms <- randomRIO (20,1000)  threadDelay msdata Philosopher = Philosopher {left::Bool,right::Bool,neighbors::(Int,Int)} deriving ShowmakeInitPhilosopher a = Philosopher {left=False,right=False,neighbors=a}
    initPhilosophers = listArray (0,4)    (map makeInitPhilosopher [(1,4),(2,0),(3,1),(4,2),(0,3)])main = do   z <- atomically $ newTVar initPhilosophers
   mapM_ (\x -> forkIO (loop x z 0 1)) [0,1,2,3,4]loop n tps c l | c > l = (atomically (readTVar tps)) >>= (\x -> print x) | otherwise = do                   think  
   atomically $ eat n tps   loop n tps (c+1) leat :: Int -> TVar (Array Int Philosopher) -> STM ()eat n tps = do
  takeLeft n tps  takeRight n tps  releaseLeft n tps  releaseRight n tpstakeLeft :: Int -> TVar (Array Int Philosopher) -> STM ()takeLeft n tps = do  ps <- readTVar tps  let p = ps ! n
  if right (ps ! (fst $ neighbors p)) == False then (writeTVar tps $ ps // [(n,p{left=True})]) else retrytakeRight :: Int -> TVar (Array Int Philosopher) -> STM ()takeRight n tps = do
  ps <- readTVar tps  let p = ps ! n  if left (ps ! (snd $ neighbors p)) == False then (writeTVar tps $ ps // [(n,p{right=True})]) else retryreleaseLeft n tps = do  ps <- readTVar tps
  let p = ps ! n  writeTVar tps $ ps // [(n,p{left=False})]    releaseRight n tps = do  ps <- readTVar tps  let p = ps ! n  writeTVar tps $ ps // [(n,p{right=False})]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Brian Hulley

Jared Updike wrote:

-4^2is not the same whether parsed as

(-4)^2  or  -(4^2)  (the correct version)

Basically, before someone argues this with me,

-4^2 should parse the same as

- 4^2 which should be the same thing as

0 - 4^2


I'd argue that -4^2 should parse as (-4)^2 in the same way that:

   f x `op` y===  (f x) `op` y

I'd also argue that in maths the necessary brackets are implied by the 
superscripting syntax, and for programming, as long as the editor does basic 
highlighting of literals it would be very clear that -4 is a single lexeme.


Stefan Monnier wrote:

I'd have thought it would have been simpler to just make the rule
that -2 (no spaces between '-' and '2') would be a single lexeme,


But then x-2 won't mean "subtract 2 from x" but "call x with arg -2".


Literal highlighting in the editor would make it clear that x-2 === x (-2).
I think a basic issue is that at the moment it is strange that non-negative 
numbers can be specified as literals but negative numbers can't - they can 
only get in through the "back door" of evaluation - which just doesn't seem 
right.


It's kind of like a Monty Python'esque sketch of a lecture theatre full of 
mathematicians where every attempt to mention a negative number is replaced 
by the word "apple"... ;-)


Regards, Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] A restricted subset of CPP included in a revision of Haskell 98

2006-08-17 Thread Brian Smith
On 8/17/06, John Meacham <[EMAIL PROTECTED]> wrote:
On Thu, Aug 17, 2006 at 11:44:17AM -0500, Brian Smith wrote:> Hi,>> I find it strange that right now almost every Haskell program directly or> indirectly (through FPTOOLS) depends on CPP, yet there is no effort to
> replace CPP with something better or standardize its usage in Haskell. 
see this paper for some interesting work on the subject.http://citeseer.ist.psu.edu/wansbrough99macros.htmlThanks for that. I should have not said "there is no effort to replace CPP" before. I hope I did not offend anybody that has worked on this problem previously.
I was also mistaken in saying that syntax could be fully checked without knowing any preprocessor symbol bindings. This is only true if one gets rid of the ability to choose between two syntaxes via the preprocessor.  But, if we allow syntax that we can't parse (but presumably another implementation can), then the preprocesor must remain a true preprocessor. Then there isn't much reason to place so many restrictions on where the various preprocessor directives may appear.
I proposed to limit where #define could appear mostly for asthetic reasons. If #define, #error, and #warn only appear at the beginning of a file, then the rest of the file would only contain Haskell syntax in between #if...#else...#endif. Also, a refactoring tool would not have these directives get in its way.
I want to have conditionals limited in their placement to make things easier for refactoring tools. But, I don't have any ideas about how to deal with conditional exports without allowing preprocessor conditionals in the export list.
* #define can only be used for parameterless definitions* #define'd symbols are only visible to the preprocessor
* #define can only give a symbol a value that is a valid preprocessor _expression_* #define, #error, and #warn can only appear above the module declaration* a preprocessor symbol, once defined, cannot be undefined or redefined with a different value

* #include and #undef are prohibited*
The preprocessor can only be used at the top level. In particular, a
prepropcessor conditional or #line would not be allowed
within the export list or within a top-level binding.
* A Haskell program must assume that any top-level symbol
definitions are constant over the entire program. For example, a
program must not depend on having one module compiled with one set of
command-line preprocessor symbol bindings and another module defined
with a different set of bindings.
* preprocessor directives must loosely obey * #define can only be used for parameterless definitions* #define'd symbols are only visible to the preprocessor
* #define can only give a symbol a value that is a valid preprocessor _expression_* #define can only appear above the module declaration* a preprocessor symbol, once defined, cannot be undefined or redefined

* #include and #undef are prohibited*
The preprocessor can only be used at the top level. In particular, a
prepropcessor conditional, #error, #warn, #line would not be allowed
within the export list or within a top-level binding.
* A Haskell program must assume that any top-level symbol
definitions are constant over the entire program. For example, a
program must not depend on having one module compiled with one set of
command-line preprocessor symbol bindings and another module defined
with a different set of bindings.
* preprocessor directives must obey a very simple layout rule: an #if, #else, or #endif cannot be indented more than the bindings it "contains."
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A restricted subset of CPP included in a revision of Haskell 98

2006-08-17 Thread John Meacham
On Thu, Aug 17, 2006 at 11:44:17AM -0500, Brian Smith wrote:
> Hi,
> 
> I find it strange that right now almost every Haskell program directly or
> indirectly (through FPTOOLS) depends on CPP, yet there is no effort to
> replace CPP with something better or standardize its usage in Haskell.
> According to the following document, and my own limited experience in
> reading Haskell code, CPP is the most frequently used extension:
>http://hackage.haskell.org/trac/haskell-prime/wiki/HaskellExtensions
> I think that if we accepted that CPP was part of the language, we could then
> place some restrictions on its use to facilitate easier parsing. Here are
> some suggestions, off the top of my head:

see this paper for some interesting work on the subject.
http://citeseer.ist.psu.edu/wansbrough99macros.html

there would be no need to integrate it with compilers, it could be a
stand-alone tool, like hsc2hs.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: map (-2) [1..5]

2006-08-17 Thread John Meacham
On Thu, Aug 17, 2006 at 11:18:59AM -0400, Stefan Monnier wrote:
> > I'd have thought it would have been simpler to just make the rule that -2 
> > (no spaces between '-' and '2') would be a single lexeme,
> 
> But then x-2 won't mean "subtract 2 from x" but "call x with arg -2".

but now at least a highlighting editor can tell the difference and
highlight '-2' as a number and x as a variable. I mean,

0x22 does not mean the same thing as 0 x 32 or 0.32 or 0 . 32.

we already have special lexical rules for numbers and no one has
complained about any of them. but issues with  the '-' handling come up
quite regularly.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread John Meacham
On Thu, Aug 17, 2006 at 11:14:32AM +0100, Brian Hulley wrote:
> I'd have thought it would have been simpler to just make the rule that -2 
> (no spaces between '-' and '2') would be a single lexeme, and then people 
> could just use (negate x) or (0 - x) instead of having a special rule and a 
> whole lot of confusion just for one arithmetic operator, which is never 
> actually needed in the first place (just as we don't need /x because it is 
> simple enough to write 1/x).

yes yes yes. the current handling of - is a huge wart that needs to be
excised. I run into issues with it still and grumble to myself, and have
been programming haskell for years. '-' should be part of the numerical
lexical syntax and not be special in any other way. we alreday have .
being treated as lexically part of a number, and 'e', and 'x' in certain
cases, so why the special anoying case for '-'?

> 
> I see with great disappointment that Haskell' Trac ticket#50 [1] looks as 
> if it will not be accepted [2] so we're likely to be stuck with this for 
> years to come...
> 
> [1] http://hackage.haskell.org/trac/haskell-prime/ticket/50
> [2] http://hackage.haskell.org/trac/haskell-prime/wiki/StrawPoll-2

I hope this changes.


John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] A restricted subset of CPP included in a revision of Haskell 98

2006-08-17 Thread Brian Smith
Hi,
I find it strange that right now almost every Haskell program
directly or indirectly (through FPTOOLS) depends on CPP, yet there is
no effort to replace CPP with something better or standardize its usage
in Haskell. According to the following document, and my own limited
experience in reading Haskell code, CPP is the most frequently used
extension:
    http://hackage.haskell.org/trac/haskell-prime/wiki/HaskellExtensions
I think that if we accepted that CPP was part of the language, we could
then place some restrictions on its use to facilitate easier parsing. Here are some suggestions, off the top of my head:* #define can only be used for parameterless definitions* #define'd symbols are only visible to the preprocessor
* #define can only give a symbol a value that is a valid preprocessor _expression_* #define can only appear above the module declaration* a preprocessor symbol, once defined, cannot be undefined or redefined
* #include and #undef are prohibited* The preprocessor can only be used at the top level. In particular, a prepropcessor conditional, #error, #warn, #line would not be allowed within the export list or within a top-level binding.
* A Haskell program must assume that any top-level symbol definitions are constant over the entire program. For example, a program must not depend on having one module compiled with one set of command-line preprocessor symbol bindings and another module defined with a different set of bindings.
* preprocessor directives must obey Haskell's layout rules. For example, an #if cannot be indented more than the bindings it contains.The result would be:* Syntax can be fully checked without knowing the values of any preprocessor symbols.
* Preprocessor syntax can be added easily to a Haskell parser's BNF description of Haskell.* No tool will need to support per-file/module preprocessor symbol bindings.Again, all this is just off the top of my head. I am curious about what problems these restrictions might cause, especially for existing programs. I know that GHC itself uses some features that would be prohibited here. But, GHC is really difficult for tools to handle even with these restrictions on its source code. For now, I am more interested in the libraries in FPTOOLS and users' programs. What libraries/programs cannot easily be reorganizated to meet these restrictions? I suspect "#define'd symbols are only visible to the preprocessor" would be the most troublesome one. 
Thanks,Brian
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Description of Haskell extensions used by FPTOOLS

2006-08-17 Thread Brian Smith
Is there any design document for the FPTOOLS libraries or some description of language features that are (allowed to be) used in them?I am going to be taking some significant time off from my normal jobs in the upcoming months. During part of that time, I would like to do some work to improve the Haskell toolchain. This involves creating or improving tools that parse and analyze Haskell code. My goal is to have these tools support enough of Haskell to be able to handle at least the most important libraries used by Haskell programmers. In particular, this includes all or most of the libraries in FPTOOLS. Plus, I want these tools to operate on Darcs as it is an obvious poster-child for Haskell. Thus, I need to support Haskell 98 plus all the extensions being used in Darcs and FPTOOLS as of approx. March, 2007 (as I intened to start working again at that time). 
It would be very nice if there was some document that described "Haskell 98 plus all the extensions being used in Darcs and FPTOOLS as of March, 2007." Besides being useful to me, it would be a useful guide for potential contributors to FPTOOLS.
Regards,Brian
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: map (-2) [1..5]

2006-08-17 Thread Jón Fairbairn
Stefan Monnier <[EMAIL PROTECTED]> writes:

> > I'd have thought it would have been simpler to just make the rule that -2 
> > (no spaces between '-' and '2') would be a single lexeme,
> 
> But then x-2 won't mean "subtract 2 from x" but "call x with arg -2".

Well, since the normal typographical convention is that
"hyphenated-words" are read as closely connected, I've
always been in favour of including hyphen in variable names
and using spaces to separate them from tokens, so perhaps it
should just mean "the identifier 'x-2'".

Though in the days of Unicode we could get round the whole
thing by using code 0x002d for unary minus, 0x2010 in
identifiers and 0x2212 for infix minus... and spend many a
happy hour trying to tell which of the three was intended by
some short horizontal line.

-- 
Jón Fairbairn [EMAIL PROTECTED]
http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html  (updated 2006-07-14)

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


Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Jared Updike

I'd have thought it would have been simpler to just make the rule that -2
(no spaces between '-' and '2') would be a single lexeme


I'd have thought so too, until I implemented a parser with exponentiation.
It is easy to get confused and make a parser that is too eager to include
the minus sign as part of a numeric literal instead of as subtraction
or unary negation (all you parser-with-exponentiation-implementers out
there, pay attention!). And since many
programming languages (specifically C) don't have syntax for
exponentation as an infix operator (nothing authoritative to copy
precedence from), I had to implement this myself, get confused and see
that it was so---(I tried making the literal include the minus sign if
there was no space). I never noticed this before because in a C-like
language:

-4*2is the same whether parsed as

(-4)*2   or  -(4*2)

but

-4^2is not the same whether parsed as

(-4)^2  or  -(4^2)  (the correct version)

Basically, before someone argues this with me,

-4^2 should parse the same as

- 4^2 which should be the same thing as

0 - 4^2

(you don't want -4^2  and 0-4^2 giving different results, no matter
how much you think whitespace belongs around operators)

Math follows these same rules but it's slightly harder to get confused
because of the way exponentiation is written by superscripting. See
http://mathforum.org/library/drmath/view/55709.html and
http://mathforum.org/library/drmath/view/53240.html.

I thought this was surprising, that parsing the minus sign into
lexemes would cause such confusion, but it is born out in many places
(Python, Frink (http://futureboy.homeip.net/frinkdocs/FrinkApplet.html),
etc.)

(Note: this email isn't about Haskell specifically and I'm sure issues
with the minus sign in Haskell are more confusing than this; this is
purely about parsing a C-like langauge extended with exponentionation
and how including the minus sign in the literal is dangerous in
conjuntion with exponentiation.)

 Jared.
--
http://www.updike.org/~jared/
reverse ")-:"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: map (-2) [1..5]

2006-08-17 Thread Stefan Monnier
> I'd have thought it would have been simpler to just make the rule that -2 
> (no spaces between '-' and '2') would be a single lexeme,

But then x-2 won't mean "subtract 2 from x" but "call x with arg -2".


Stefan

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


Re[2]: [Haskell-cafe] Haskell wiki: most popular pages

2006-08-17 Thread Bulat Ziganshin
Hello Tamas,

Thursday, August 17, 2006, 2:29:26 PM, you wrote:

> The link from http://haskell.org/haskellwiki/Learning (to
> http://www.cs.uu.nl/~afie/haskell/tourofprelude.html) is dead, so is
> the one from Books_and_Tutorials.

thank you. i have fixed both. btw, you can register himself on the
wiki at http://haskell.org/haskellwiki/?title=Special:Userlogin and
get rights to edit it yourself 

> 1. I would move it from the Reference to the Introduction section.  A
>reference is something you look at when you know what you are
>looking for.  Also, it is at the bottom of the page, few would
>scroll that far.

> 2. How would newbies know what the Prelude is?  Some tutorials mention
>it, but it is not emphasized that most functions they use come from
>the Prelude.  Since they do not know that they need the Prelude,
>they are not interested in a tour of it.

i agree with both points. it's a really helpful thing, with all its
coloring, examples and even definitions. and it's of interest for very
beginning Haskellers, may be even those who don't know anything about
Haskell. it's just a pleasure to see all those one-line definitions
and feel how power the language should be to allow such cool things.
The only problem that makes it harder to learn is what functions are
sorted in alphabetic order instead of be grouped by theme (math, lists,
chars and strings, ordering, i/o, higher-order funcs and their applications)

so we can move this to the Tutorials column, make better description
(how about "Tour of Haskell Prelude (basic functions)"?) and i will
try to reorganize it by splitting into the thematic sections



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: Samba/FTP bindings

2006-08-17 Thread John Goerzen
On 2006-08-16, Ivan Tarasov <[EMAIL PROTECTED]> wrote:
> Is there some Haskell library which provides Samba bindings and some FTP
> client library bindings (e.g. ftplib3)?

MissingH provides a pure-Haskell FTP client (and server!)
implementation.

-- John

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


Re: [Haskell-cafe] Last statement in 'do' must be an expression error.

2006-08-17 Thread Udo Stenzel
Szymon Z??bkiewicz wrote:
> The compiler tells me thats there's an error on line 10:
> "The last statement in a 'do' construct must be an expression"

I think, you have reached the point where treating do-notation as magic
won't help you.  Remember, 

> do
> nr1 <- read (prompt "enter 1. number: ")
> nr2 <- read (prompt "enter 2. number: ")

is syntactic sugar for

> read (prompt "enter 1. number: ") >>= \nr1 ->
> read (prompt "enter 2. number: ") >>= \nr2 ->

and it obvious that something is missing after the last arrow.  That's
the expression the compiler is complaining about.  After the
translation, it is also completely clear, that there is no "variable"
which is ever "declared" and could be "assigned".

On a side note, using "trap values" like the special 0 is an ugly style
inherited from C.  You might want to get used to explicit
representations for missing values.  Compare this:

> read_new :: Maybe (Int, Int) -> IO (Int, Int)
> read_new (Just ab) = return ab
> read_new Nothing   = do
>   n1 <- read_prompt "enter 1. number: "
>   n2 <- read_prompt "enter 2. number: "
>   return (n1, n2)
>   where
> read_prompt p = prompt p >>= readIO

Also note the 'read_prompt' function; I'm pretty sure you got the types
of 'prompt' and 'read' messed up, too.  So in anticipation of your next
question: 'read'ing the 'prompt' action is not the same as 'read'ing the
result of the 'prompt' action.  Only the latter makes sense.


Udo.
-- 
"Enthusiasm is contagious, and so is boredom." -- Paul Graham


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


Re: [Haskell-cafe] Haskell wiki: most popular pages

2006-08-17 Thread Tamas K Papp
Hi Bulat,

The link from http://haskell.org/haskellwiki/Learning (to
http://www.cs.uu.nl/~afie/haskell/tourofprelude.html) is dead, so is
the one from Books_and_Tutorials.

Furthermore, 

1. I would move it from the Reference to the Introduction section.  A
   reference is something you look at when you know what you are
   looking for.  Also, it is at the bottom of the page, few would
   scroll that far.

2. How would newbies know what the Prelude is?  Some tutorials mention
   it, but it is not emphasized that most functions they use come from
   the Prelude.  Since they do not know that they need the Prelude,
   they are not interested in a tour of it.

Best,

Tamas


On Thu, Aug 17, 2006 at 01:01:43PM +0400, Bulat Ziganshin wrote:

> Hello Tamas,
> 
> Thursday, August 17, 2006, 11:14:22 AM, you wrote:
> 
> >> Haskell (252,505 views)
> >> Introduction (50,091 views) 
> >> Libraries and tools (41,864 views) 
> >> Books and tutorials (40,040 views) 
> >> Language and library specification (32,773 views) 
> >> Haskell in practice (31,698 views) 
> >> Implementations (24,141 views) 
> >> GHC (20,634 views) 
> >> Haskell in 5 steps (16,707 views) 
> >> Learning (14,088 views) 
> >> Hitchhikers guide to Haskell (13,191 views) 
> >> Future (12,754 views)
> 
> > A link to "A tour of the Haskell Prelude" might be very useful for
> > newbies (like me ;-)
> 
> btw, it's listed on Learning page but it seems that newbies don't very
> much like it, preferring to go to Language Specification or at least
> Books page. what you think - why it is so unpopular?
> 
> (i think that language specification is the last thing Haskeller
> should read, just when he goes to implementing his own private Haskell
> compiler :D )
> 
> 
> -- 
> Best regards,
>  Bulatmailto:[EMAIL PROTECTED]
> 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Brian Hulley

Tamas K Papp wrote:

The code in the subject generates an error.  I understand why this is
(- is treated as part of the number), but I don't know how to solve
it, ie how to tell Haskell that - is a function/binary operator?


Actually looking at the Haskell98 report, -2 seems to be treated as (negate 
(2)), which I find really strange because there does not appear to be any 
way of specifying negative literals, and the range of negative values is 
always 1 more than the range of positive values (when you use a fixed 
bit-length representation eg Int instead of Integer)


I'd have thought it would have been simpler to just make the rule that -2 
(no spaces between '-' and '2') would be a single lexeme, and then people 
could just use (negate x) or (0 - x) instead of having a special rule and a 
whole lot of confusion just for one arithmetic operator, which is never 
actually needed in the first place (just as we don't need /x because it is 
simple enough to write 1/x).


I see with great disappointment that Haskell' Trac ticket#50 [1] looks as if 
it will not be accepted [2] so we're likely to be stuck with this for years 
to come...


[1] http://hackage.haskell.org/trac/haskell-prime/ticket/50
[2] http://hackage.haskell.org/trac/haskell-prime/wiki/StrawPoll-2

So in answer to your question, you can't (except for workarounds already 
posted).


Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


[Haskell-cafe] wxFruit with OpenGL and IO action

2006-08-17 Thread shelarcy

Hello.

Sometimes, a few people are interested in wxFruit.

http://zoo.cs.yale.edu/classes/cs490/03-04b/bartholomew.robinson/

But nobady knows current status of wxFruit. Over one
and half year ago, I heard that students working on
that ... .

http://www.haskell.org/pipermail/haskell-cafe/2005-January/008765.html
http://www.haskell.org/pipermail/haskell-cafe/2006-March/014998.html

So, I'm working on that for subproject of Kamiariduki
... but progress is very slowly.

I uploaded current (initial) version on Kamiariduki's
file space. File name is "YaPan-initial.tgz".

Because this file includes YaPan - Yet another
implementation, and reimplementation of Panic
(http://www.cse.unsw.edu.au/~sseefried/pan/index.html)
using Yampa (and wxFruit).

http://sourceforge.net/project/showfiles.php?group_id=168626

I didn't think current verion is good enough to
announse [Haskell] list, so I didn't announce that and
repraced "YaPan.tgz" file sometimes ... but I know that
a few people downloaded my file already. So, I decide
to upload initial file on that space.

Of cource, "YaPan-initial.tgz" has other wxFuit example.
paddle.hs is almost same as original example, except
that use menu istead of button. And CFK_GL* is a OpenGL
sample code.

But current version has some faults. Cabal file support
to build and install only YaPan, doesn't support wxFruit.
Code is very messy, and YaPan doesn't support all of
Panic's features.

And I should notice additonal things for older version's
user. Now YaPan depends on AutoForms (not for wxFruit
now).

http://autoforms.sourceforge.net/

And YaPan can't save static one picture, YaPan can save
animation by consecutive number files only.

Current version, I tested on only Windows with my build
of wxWidgets 2.4.2's wxHaskell (I uplaoded Kamiariduki's
file space) and afrp-0.4 environment. So I don't know
wxFruit and YaPan can works well other environments.


Finally, I show current problem of wxFruit with IO
action.

I extend that button menu allow to regist extra IO
action like this.

pan pixels = hBox $ proc _ -> do
  let start = False
  rec v <- boxSF $ iPre 0 -< 1 + v
  ev <- getEvent -< ()
  vTrans <- boxSF $ iPre (0,0,1) -< (keyboardEvent 0.1 vTrans) ev
  panedPixels <- boxSF $ pictureEvent -< (pixels, vTrans, (circle v),  
v, gameBox)
  _ <- glpicture (glpsizeWithAttributes gameBox [WXCore.GL_RGBA,  
WXCore.GL_DOUBLEBUFFER]) -< glppic $ paintGL gameBox panedPixels

  _ <- menu (mtextWithDialog "&SaveImage")
   -< mcommandWithDialog $
(\v f -> saveImageHandler (animToDisplayFun (circle))  
circle (WX.sizeW gameBox, WX.sizeH gameBox) vTrans 1 v f) v

  returnA -< ()

This design is suitable for button and menu's command.
But if I want to use IO action out of these control
event, modualiry is broken. Because I want to do that
action out of control's event, but I have to change
control's action. And I must choose using what kind of
event handler. (Is interval the best?)

So I tried to implement command function that intend to
use IO action on reative loop wihtout control  in
wxFruit.hs ... but action doesn't do registered action
or program is not work on my apporoach. (I commented out
current command function that occur action.)

If anyone have good idea how to use IO action on wxFuit,
please tell me that idea.


Thanks.

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


Re: [Haskell-cafe] Last statement in 'do' must be an expression error.

2006-08-17 Thread Bulat Ziganshin
Hello Szymon,

Thursday, August 17, 2006, 12:18:25 PM, you wrote:

>  8.if (a == 0) && (b == 0)
>  9.   then do
> 10. nr1 <- read (prompt "enter 1. number: ")
> 11. nr2 <- read (prompt "enter 2. number: ")
> 12.   else do
> 13.let nr1 = a
> 14.nr2 = b
> {...}

1. as already said, your nr vars is local to the do blocks. you can't
_assign_ to variables in Haskell, instead you should return
_values_ that will become result of whole "if" expression:

(nr1,nr2) <- if ...
   then do x <- ..
   y <- ..
   return (x,y)
   else
do return (a,b)

2. as Chris said, "read" is a function (at least 'read' predefined in
std Haskell library), while your 'prompt' should be I/O procedure. you
can't call I/O procedures inside of functions, i.e. that is possible:

function calls function
I/O procedure calls function
I/O procedure calls I/O procedure

and that's impossible:
function calls I/O procedure

So you should assign result of procedure call to "variable" and then call
function on this value:

(nr1,nr2) <- if a==0 && b==0
   then do x <- prompt "enter 1. number: "
   y <- prompt "enter 2. number: "
   return (read x, read y)
   
   else return (a,b)

to be exact, x and y are not variables, but just bound identifiers
like a and b. '<-' is special construct inside of 'do' block that
binds to identifier value returned by I/O procedure call


i've written tutorial on Haskell IO monad. you can try to read it, but
it's more appropriate for intermediate Haskellers who has a good
understanding of pure facilities of the language. but nevertheless try
it - http://haskell.org/haskellwiki/IO_inside . i will be interesting
to hear your opinion and depending on it will become more or less
skeptical about suggesting it to Haskell newcomers fighting with
mysterious IO monad :D

in general, i suggest to learn pure foundations of Haskell such as
lazy evaluation and higher-order functions. after that, learning IO
monad using my tutorial will be as easy as saying "cheese" :)


-- 
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] Haskell wiki: most popular pages

2006-08-17 Thread Bulat Ziganshin
Hello Tamas,

Thursday, August 17, 2006, 11:14:22 AM, you wrote:

>> Haskell (252,505 views)
>> Introduction (50,091 views) 
>> Libraries and tools (41,864 views) 
>> Books and tutorials (40,040 views) 
>> Language and library specification (32,773 views) 
>> Haskell in practice (31,698 views) 
>> Implementations (24,141 views) 
>> GHC (20,634 views) 
>> Haskell in 5 steps (16,707 views) 
>> Learning (14,088 views) 
>> Hitchhikers guide to Haskell (13,191 views) 
>> Future (12,754 views)

> A link to "A tour of the Haskell Prelude" might be very useful for
> newbies (like me ;-)

btw, it's listed on Learning page but it seems that newbies don't very
much like it, preferring to go to Language Specification or at least
Books page. what you think - why it is so unpopular?

(i think that language specification is the last thing Haskeller
should read, just when he goes to implementing his own private Haskell
compiler :D )


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread David House

On 17/08/06, Tamas K Papp <[EMAIL PROTECTED]> wrote:

The code in the subject generates an error.  I understand why this is
(- is treated as part of the number), but I don't know how to solve
it, ie how to tell Haskell that - is a function/binary operator?


There's a Prelude function for exactly this purpose, which leads your
code still quite readable:

Prelude> map (subtract 2) [1..5]
[-1,0,1,2,3]

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


Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Stefan Holdermans

Tamas,


The code in the subject generates an error.  I understand why this is
(- is treated as part of the number), but I don't know how to solve
it, ie how to tell Haskell that - is a function/binary operator?


What about

  map (flip (-) 2) [1 .. 5]

or

  map (+ (- 2)) [1 .. 5]

?

HTH,

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


[Haskell-cafe] Re: map (-2) [1..5]

2006-08-17 Thread Christian Maeder
 map (\x -> x - 2) [1..5]
or
 map (flip (-) 2) [1..5]

HTH Christian

Tamas K Papp schrieb:
> The code in the subject generates an error.  I understand why this is
> (- is treated as part of the number), but I don't know how to solve
> it, ie how to tell Haskell that - is a function/binary operator?
> 
> Thanks,
> 
> Tamas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Tamas K Papp
The code in the subject generates an error.  I understand why this is
(- is treated as part of the number), but I don't know how to solve
it, ie how to tell Haskell that - is a function/binary operator?

Thanks,

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


Re: [Haskell-cafe] Last statement in 'do' must be an expression error.

2006-08-17 Thread Chris Kuklewicz

Szymon Ząbkiewicz wrote:

Hi.

When trying to compilke this code:

{...}
8.if (a == 0) && (b == 0)
9.   then do
10. nr1 <- read (prompt "enter 1. number: ")
11. nr2 <- read (prompt "enter 2. number: ")


The nr2 here is not passed to the rest of the do block started on line 9


12.   else do
13.let nr1 = a
14.nr2 = b


The nr1 and nr2 in the else block have absolutely nothing to do with the nr1 and 
nr2 from the then block.  The names are the same, but that does not make them 
the same as they could be totally different types.



{...}

The compiler tells me thats there's an error on line 10:
"The last statement in a 'do' construct mesy be an expression"

Could you tell me how to change it so that the "declaration" of the
first nr1 and nr2 is still in the "then" block.


The "x <- foo" syntax is not a declaration.

Also, the type of "read" is String->a which is NOT a monad type, so I will fix 
that as well:


One could do this:

(nr1,nr2) <- if (a==0) && (b==0)
   then do a' <- liftM read (prompt "...")
   b' <- liftM read (prompt "...")
   return (a',b')
   else return (a,b)

The ghc compiler is usually smart enough to remove the tuple (,) construction 
from the code.

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


Re: [Haskell-cafe] Last statement in 'do' must be an expression error.

2006-08-17 Thread Matthias Fischmann
On Thu, Aug 17, 2006 at 10:18:25AM +0200, Szymon Z??bkiewicz wrote:
> To: haskell-cafe@haskell.org
> From: Szymon Z??bkiewicz <[EMAIL PROTECTED]>
> Date: Thu, 17 Aug 2006 10:18:25 +0200
> Subject: [Haskell-cafe] Last statement in 'do' must be an expression error.
> 
> Hi.
> 
> When trying to compilke this code:
> 
> {...}
> 8.if (a == 0) && (b == 0)
> 9.   then do
> 10. nr1 <- read (prompt "enter 1. number: ")
> 11. nr2 <- read (prompt "enter 2. number: ")

each do block needs to evaluate to some value when performed.  if you
have nothing to return, do something like "return ()".  (note this
only works if the type checker is happy with it.  possibly you need to
restructure parts of the code you didn't post, too.)

> 12.   else do
> 13.let nr1 = a
> 14.nr2 = b
> {...}
> 
> The compiler tells me thats there's an error on line 10:
> "The last statement in a 'do' construct mesy be an expression"
> 
> Could you tell me how to change it so that the "declaration" of the
> first nr1 and nr2 is still in the "then" block.

what about this code (untested)?

do
  nr1 <- if a == 0 then read (prompt ":") else return a
  nr2 <- if b == 0 then read (prompt ":") else return b
  ...



hth,
m.


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


Re: [Haskell-cafe] Last statement in 'do' must be an expression error.

2006-08-17 Thread Ulf Norell


On Aug 17, 2006, at 10:18 AM, Szymon Ząbkiewicz wrote:


Hi.

When trying to compilke this code:

{...}
8.if (a == 0) && (b == 0)
9.   then do
10. nr1 <- read (prompt "enter 1. number: ")
11. nr2 <- read (prompt "enter 2. number: ")
12.   else do
13.let nr1 = a
14.nr2 = b
{...}

The compiler tells me thats there's an error on line 10:
"The last statement in a 'do' construct mesy be an expression"

Could you tell me how to change it so that the "declaration" of the
first nr1 and nr2 is still in the "then" block.


The problem is that variables defined in the branch of an if are  
local to the branch. If you want to use them outside you have to  
return them from the branch:


do
  (nr1, nr2) <-
if (a == 0) && (b == 0)
then do
   nr1 <- read (prompt "enter 1. number: ")
   nr2 <- read (prompt "enter 2. number: ")
   return (nr1, nr2)
else do
   let nr1 = a
   nr2 = b
   return (nr1, nr2)

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


[Haskell-cafe] Last statement in 'do' must be an expression error.

2006-08-17 Thread Szymon Ząbkiewicz

Hi.

When trying to compilke this code:

{...}
8.if (a == 0) && (b == 0)
9.   then do
10. nr1 <- read (prompt "enter 1. number: ")
11. nr2 <- read (prompt "enter 2. number: ")
12.   else do
13.let nr1 = a
14.nr2 = b
{...}

The compiler tells me thats there's an error on line 10:
"The last statement in a 'do' construct mesy be an expression"

Could you tell me how to change it so that the "declaration" of the
first nr1 and nr2 is still in the "then" block.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell wiki: most popular pages

2006-08-17 Thread Tamas K Papp
On Thu, Aug 17, 2006 at 01:55:47AM +0400, Bulat Ziganshin wrote:
> Hello haskell-cafe,
> 
> The http://haskell.org/haskellwiki/Special:Popularpages page lists
> most popular pages on haskell wiki. I think this list is very
> useful because it shows us what are the questions about Haskell
> people most interested and gives us hints what should be improved in
> first place. The only catch is that most of popular pages are just
> ones listed on the title page. But nevertheless... On the other side,
> we can simplify title page by omitting links to page that are of
> little interest for casual readers (such as History). We can also add
> here links to most popular pages, such as GHC and "Hitchhikers guide".
> Below is beginning of this list:
> 
> Haskell (252,505 views)
> Introduction (50,091 views) 
> Libraries and tools (41,864 views) 
> Books and tutorials (40,040 views) 
> Language and library specification (32,773 views) 
> Haskell in practice (31,698 views) 
> Implementations (24,141 views) 
> GHC (20,634 views) 
> Haskell in 5 steps (16,707 views) 
> Learning (14,088 views) 
> Hitchhikers guide to Haskell (13,191 views) 
> Future (12,754 views)

A link to "A tour of the Haskell Prelude" might be very useful for
newbies (like me ;-)

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


Re: [Haskell-cafe] iterative algorithms: how to do it in Haskell?

2006-08-17 Thread Tamas K Papp
On Thu, Aug 17, 2006 at 01:23:19AM -0400, [EMAIL PROTECTED] wrote:
> G'day all.
> 
> Quoting Chris Kuklewicz <[EMAIL PROTECTED]>:
> 
> > The compiler may not deforest that list, so creating the list may be a small
> > overhead of this method.
> 
> And in return, you get:
> 
> - Code that is smaller than the imperative version, AND
> - a reusable function, making the next incarnation of
>   an algorithm like this even shorter.
> 
> For most interesting cases, the cost of f and goOn will surely dominate
> anyway.
> 
> > Note that "f x" should be "f a" above.
> 
> Yes, you're right.  I abstracted out "f" after testing and before
> posting.

Chris, Christian, Andrew, Antti-Juhani and Ivan,

Thanks for your answers, they were very enlightening (though it will
take some time to understand everything).  Haskell looks even more
elegant than Scheme...

Best,

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