Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Luke Palmer
On Dec 18, 2007 7:31 AM, Cristian Baboi [EMAIL PROTECTED] wrote:
 Here is some strange example:

 module Hugs where

 aa::Int
 aa=7

 cc:: (Int-Int)-(Int-Int-Int)-Int-(Int-Int)
 cc a op b  =  \x- case x of  {   _ | x==aa - x+1 ;  _- a x `op` b }

 f::Int-Int
 f(1)=1
 f(2)=2
 f(_)=3

 g::Int-Int
 g(1)=13
 g(2)=23
 g(_)=33

 h::[Int-Int] - Int -Int
 h  []  x   = x
 h  [rr]  x=  let { u=Hugs.f ; v=Hugs.g } in  case rr of  {  u  -
 Hugs.g(x)+aa ; v - Hugs.f(x)+aa ; _ -rr (x) + aa }
 h  (rr:ll)  x =  h [rr] x + h (ll) x


 What I don't understand is why I'm forced to use guards like x==aa in cc,
 when aa is clearly bounded (is 7) and why in function h, the bounded u and
 v become free variables in the case expression.

It's a simple issue of scoping.   The left side of case expressions are
*patterns*, which bind new names, and don't look outside their scope for
names.  This is a good thing.  Say you have:

case Left 0 of
  Left  x - x
  Right y - show y

(The values are instances of the Either type, specifically Either Int)

This will match the value Left 0 against an expression which either looks
like Left x or Right y, for any x or y, and act accordingly.  If you decided
to add

x :: Int
x = 42

To the top level of your program, you wouldn't want the first case only to
match Left 42 when it previously matched any value starting with Left,
would you?

It is the same as scoping in C (or whatever language your background is, they
all support it); you don't want names in a larger scope to interfere with
names in a smaller scope.  Each case in a case expression introduces a scope,
and the left side of the arrow binds new names.

I hope this helps,

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


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Miguel Mitrofanov
 What I should have been told about upfront:
 - the syntax for an expression
 - the syntax for a block

Don't see your point.

 - the adhoc syntax rules (how to distinguish among a tuple and a  
 pharanthesized expression and how to find the start and end of a block for  
 example )

Oh, that's pretty easy, parenthesized expression is not divided by a comma.

 - what guarantees are made by the LANGUAGE that an IO action (such as  do  
 putStrLn Hello world ) is not performed twice

There are no such guarantees. If you write

a = putStrLn Hello world
main = do {a; a;}

then your putStrLn would be performed twice. IO actions are first-class values, 
that's a feature, not a bug.

 - the lambda expressions can be written (input) but cannot be printed  
 (output)

Yes, since two different lambda expressions can denote the same function.

 Here is some strange example:
 module Hugs where
 aa::Int
 aa=7
 cc:: (Int-Int)-(Int-Int-Int)-Int-(Int-Int)
 cc a op b  =  \x- case x of  {   _ | x==aa - x+1 ;  _- a x `op` b }
 f::Int-Int
 f(1)=1
 f(2)=2
 f(_)=3
 g::Int-Int
 g(1)=13
 g(2)=23
 g(_)=33
 h::[Int-Int] - Int -Int
 h  []  x   = x
 h  [rr]  x=  let { u=Hugs.f ; v=Hugs.g } in  case rr of  {  u  -  
 Hugs.g(x)+aa ; v - Hugs.f(x)+aa ; _ -rr (x) + aa }
 h  (rr:ll)  x =  h [rr] x + h (ll) x
 What I don't understand is why I'm forced to use guards like x==aa in cc,  
 when aa is clearly bounded (is 7) and why in function h, the bounded u and  
 v become free variables in the case expression.

No, pattern matching bounds variables; if you write case x of {aa - ...} then 
aa becomes a LOCAL variable for the case statement, and shadows the global 
definition. The same applies to u and v in h, except that in this case local 
variables shadow upper-level local variables.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Ketil Malde
Cristian Baboi [EMAIL PROTECTED] writes:

 Here is some strange example:

 module Hugs where

 aa::Int
 aa=7

Small note, it's common to use spaces around the :: and =   I've
never really noticed before.

 cc :: (Int-Int) - (Int-Int-Int) - Int - (Int-Int)
 cc a op b  = \x- case x of { _ | x==aa - x+1 ;  _- a x `op` b }

 What I don't understand is why I'm forced to use guards like x==aa in
 cc,  when aa is clearly bounded (is 7) 

I don't quite understand what you mean.  You don't have to use guards,
the function could equally well have been written using if-then-else.
Why not

  cc a op b x = if x==aa then (x+1) else a x `op` b

Oh, wait, you're asking why you can't write

case x of aa - x+1
  _  - a x `op` b

The answer is that case introduces a new binding for 'aa', so the
above is equivalent to 

  let aa = x in x+1

Case is really for deconstructing values with pattern matching, a
simple variable like aa (or _) will match any pattern.

 f::Int-Int
 f(1)=1
 f(2)=2
 f(_)=3

You can drop the parentheses here.

 g::Int-Int
 g(1)=13
 g(2)=23
 g(_)=33

 h :: [Int-Int] - Int - Int
 h []   x = x
 h [rr] x =  let { u=Hugs.f ; v=Hugs.g } in  case rr of  {  u  -
 Hugs.g(x)+aa ; v - Hugs.f(x)+aa ; _ -rr (x) + aa }
 h  (rr:ll)  x =  h [rr] x + h (ll) x

Same here, if I understand you correctly.  The case introduces new
bindings for u and v.  Note that you can't (directly) compare
functions for equality either, the only way to do that properly would
be to compare results over the entire domain.  (f == g iff f x == g x
forall x)

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Jules Bean

Miguel Mitrofanov wrote:

There's a third way, too, and I haven't seen anybody mention it yet


I've noticed it, but there are some problems with this representation, 
so I decided not to mention it. It's OK as far as we don't want 
functions working on two areas - I don't see, how we can implement, say, 
intersect :: Shape - Shape - Bool in this way. However, it's a useful 
pattern.


The problem is no better or worse for this third way than for type classes.

class Shape a where {
  intersect :: Shape b = a - b - Bool
}

data Shape a = { intersect :: Shape b = a - b - Bool }

in fact, the syntax is rather similar, too! :)

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


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Cristian Baboi
On Tue, 18 Dec 2007 10:29:43 +0200, Miguel Mitrofanov  
[EMAIL PROTECTED] wrote:



What I should have been told about upfront:
- the syntax for an expression
- the syntax for a block



Don't see your point.


The point is the syntax is introduced as transformation of layout form to  
non layout form.
As a user, I just want to be able to spot the basic components of a source  
file without thinking about transformation rules.



- the adhoc syntax rules (how to distinguish among a tuple and a
pharanthesized expression and how to find the start and end of a block  
for

example )


Oh, that's pretty easy, parenthesized expression is not divided by a  
comma.


Thanks! What is the end of a block ? What introduce new blocks ?
Is this legal (`plus`) x y ?
It's this a tuple ?  ([a,b,c,d ]) ?

etc.

- what guarantees are made by the LANGUAGE that an IO action (such as   
do

putStrLn Hello world ) is not performed twice


There are no such guarantees. If you write

a = putStrLn Hello world
main = do {a; a;}

then your putStrLn would be performed twice. IO actions are first-class  
values, that's a feature, not a bug.



What guarantees that by running the main, the string Hello world will be  
printed exactly twice ?



- the lambda expressions can be written (input) but cannot be printed
(output)



Yes, since two different lambda expressions can denote the same function.

I just want the sistem to be able to print one of these expressions !

Its this too much to ask ?
I find it very strange that I can write a lambda expresion, but the system  
cannot.



No, pattern matching bounds variables; if you write case x of {aa -  
...} then aa becomes a LOCAL variable for the case statement, and  
shadows the global definition. The same applies to u and v in h, except  
that in this case local variables shadow upper-level local variables.


Ok.


 Information from NOD32 
This message was checked by NOD32 Antivirus System for Linux Mail Servers.
 part000.txt - is OK
http://www.eset.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Miguel Mitrofanov
 class Shape a where {
intersect :: Shape b = a - b - Bool
 }
 data Shape a = { intersect :: Shape b = a - b - Bool }
 in fact, the syntax is rather similar, too! :)

Um, well, and how are you going to implement it?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] list utilities -- shouldn't these be in the hierarchical libs somewhere?

2007-12-18 Thread Jules Bean

Thomas Hartman wrote:


I found

  http://haskell.cs.yale.edu/haskell-report/List.html

  had many useful one off type list functions such as subsequences 
and permutations which are nowhere to be found in hoogle, Data.List, 
or the haskell hierarchical libs


Weird.

It's not very many. Other that those, I spotted: sums, products, 
elemIndexBy, elemBy.


I have no idea why they were removed between that version of the report 
and haskell98.


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


Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Jules Bean

Miguel Mitrofanov wrote:

class Shape a where {



   intersect :: Shape b = a - b - Bool



}



data Shape a = { intersect :: Shape b = a - b - Bool }



in fact, the syntax is rather similar, too! :)




Um, well, and how are you going to implement it?



Yes, exactly.

My only point is

There is no difference!

There is no difference between the manual dictionary approach and the 
typeclass approach, in terms of ease of implementing a binary function. 
Each one has the same fundamental problem: binary functions are much 
easier with the ADT approach.


Incidentally, my type sig was wrong, sorry:

data Shape a  = { intersect :: a - Shape b - Bool }

Jules

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


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Benja Fallenstein
Hi Cristian,

On Dec 18, 2007 10:53 AM, Cristian Baboi [EMAIL PROTECTED] wrote:
  - the lambda expressions can be written (input) but cannot be printed
  (output)

  Yes, since two different lambda expressions can denote the same function.
 I just want the sistem to be able to print one of these expressions !

 Its this too much to ask ?
 I find it very strange that I can write a lambda expresion, but the system
 cannot.

It's a trade-off. Haskell has as a design goal that you can use
equational reasoning everywhere -- that if you have two ways of
writing the same function, you can substitute one for the other in any
expression, without changing the result of that expression. For
example, since you can prove

sum = foldl (+) 0 = foldr (+) 0 = last . scanl (+) 0

you can, in any place you use 'sum,' substitute any of these
expressions without changing the result.

You couldn't do this if you could write (show sum) and (show $ foldl
(+) 0) and they would return different values.

You could design the language differently, of course, but the Haskell
designers want you -- and the compiler -- to be able to use equational
reasoning everywhere -- so they disallow printing functions.

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


[Haskell-cafe] Re: New to Haskell

2007-12-18 Thread Jon Fairbairn
Cristian Baboi [EMAIL PROTECTED] writes:

 What I should have been told about upfront:

 - the syntax for an expression

Since there are only declarations and expressions, the
syntax of an expression involves pretty much all of the
language, so it would be difficult to tell it upfront.

 - the syntax for a block

Not sure what you mean by block. 

do a - [1..10]
   b - [3,4]
   return (a,b)

is an expression... you can write that same expression as
do {a - [1..10]; b - [3,4]; return (a,b)} too.

 - the adhoc syntax rules (how to distinguish among a tuple
 and a  pharanthesized expression

a tuple has commas in it. I'll grant that (x) not being a
1-tuple is a little ad-hoc, but there really is very little
ad-hockery in Haskell (and a 1-tuple behaves very much like
a plain value after all).

 and how to find the start and end of a block for example )

again, I don't know what you mean by block, but if you write
the above expression with the braces ({}), it's obvious, I
think, and the layout rule just inserts braces as
necessary when the indentation changes.

do a
   b
  c  -- this is less indented, so will cause the end of the do.

 - the fact that lambda expressions are not the same thing
 as algebraic data values

It might help to know why you think they might be the same;
the syntax is different and the name is different...

 - what guarantees are made by the LANGUAGE that an IO action
 (such as  do  putStrLn Hello world ) is not performed
 twice

As has been pointed out, «do putStrLn Hello world» is an
expression that you can bind to a variable and use as many
times as you like. Incidentally, it means the same as
«putStrLn Hello World»; do connects a sequence of bindings
and expressions, so you don't need it if there's nothing to
be connected to.

 - the lambda expressions can be written (input) but cannot
 be printed  (output)

This is a fundamental property of the language.  A lambda
expression is programme and at runtime the system doesn't
know one lambda expression from another (all it can do with
one is apply it to something).

 The biggest problem for me, so far, is the last one.

I can't see how your example illustrates that, I'm afraid.

 Here is some strange example:

 What I don't understand is why I'm forced to use guards like
 x==aa in cc,  when aa is clearly bounded (is 7) and why in
 function h, the bounded u and  v become free variables in
 the case expression.

I would have liked the language design to have permitted
case to pattern match against variables too, but the
question is, what would the syntax be?  There was a fair bit
of discussion about this when the language was designed (and
since), but no-one could come up with a good way of doing
it. One aspect of it is this: we want

f 0 = 42
f x = 3*x

to work, and we want all function definitions to be
translated into the core language in the same way,
so you get
f = \a - case a of
0 - 42
x - 3*x

and given that, you can't have a variable on the LHS of -
do anything other than get bound to the value of the
expression in the case (a in the example). It's not just a
the top level, either:

f Nothing = 0
f (Just n) = n+1

just means
f = \v - case v of
Nothing - 0
Just n - n+1

so you can't have variables inside constructors do anything
but get bound at that point.


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

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


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Jules Bean

Cristian Baboi wrote:
On Tue, 18 Dec 2007 10:29:43 +0200, Miguel Mitrofanov 
[EMAIL PROTECTED] wrote:



What I should have been told about upfront:
- the syntax for an expression
- the syntax for a block



Don't see your point.


The point is the syntax is introduced as transformation of layout form 
to non layout form.
As a user, I just want to be able to spot the basic components of a 
source file without thinking about transformation rules.


Well, a block isn't really a unified syntactic unit. The layout rule 
is used for do {} expressions, which context they are expression syntax, 
but also in module, let, and where declarations in which context they 
are declaration syntax, and case expressions in which case they are, 
well, case alternatives; a little like declarations, I suppose.


Since layout is optional, it's often defined simply by the translation 
into explicit {} and ;. On the other hand, if there are specific areas 
of ambiguity which have confused you let us know, and we'll clarify.



- the adhoc syntax rules (how to distinguish among a tuple and a
pharanthesized expression and how to find the start and end of a 
block for

example )


Oh, that's pretty easy, parenthesized expression is not divided by a 
comma.


Thanks! What is the end of a block ? What introduce new blocks ?


I'm not sure what you mean by a block here, so I find it hard to answer 
that. The end of a layout block is when a line is indented less than the 
first line of the layout.



Is this legal (`plus`) x y ?


No.


It's this a tuple ?  ([a,b,c,d ]) ?


No, that's a list of four elements, in some parentheses which, in this 
context, make no semantic difference.


An expression in parentheses is one of two things:

(a) a tuple, if it is of the form (X,Y,Z,...) where the , are understood 
to be at the top level syntactically


(b) a simple expression which has been parenthesised just to aid clarity 
or achieve correct precedence.


- what guarantees are made by the LANGUAGE that an IO action (such 
as  do

putStrLn Hello world ) is not performed twice


There are no such guarantees. If you write

a = putStrLn Hello world
main = do {a; a;}

then your putStrLn would be performed twice. IO actions are 
first-class values, that's a feature, not a bug.



What guarantees that by running the main, the string Hello world will 
be printed exactly twice ?


The semantics of IO, and the guarantees of the runtime.

IO specifies that () means compose two actions to make a larger 
action which does the first actions, then the second action.


[do {a; a;} is notation for a  a]

The RTS specifies that the main action is performed exactly once.


- the lambda expressions can be written (input) but cannot be printed
(output)



Yes, since two different lambda expressions can denote the same function.

I just want the sistem to be able to print one of these expressions !

Its this too much to ask ?
I find it very strange that I can write a lambda expresion, but the 
system cannot.


Haskell doesn't contain a code representation natively. It is not a 
homoiconic language. Just like C, C++, Java, Python, Perl, and Ruby, 
the compiler/interpreter is free to transform code into some more 
efficient form for running (including transformation all the way to 
native code, which is what ghc does) and once it has done so, it retains 
no information about the shape of the source code which yielded the 
function.


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


[Haskell-cafe] Re: data vs newtype

2007-12-18 Thread ChrisK
Jonathan Cast wrote:
 So there is a program (or, rather, type) you can write with newtype that
 can't be written with data:
 
 newtype T = T T

That compiles, and anything of type T is ⊥.  But it breaks my mental model of
what the compiler does for newtypes.  I always think of them as differently
typed versions that share the same underlying data declaration and
representation; and then the compiler erases the type information.

So let me think about this one.  Looking at the Haskell 98 Report
http://www.haskell.org/onlinereport/decls.html#sect4.2.3

A declaration of the form
newtype cx = T u1 ... uk = N t
introduces a new type whose representation is the same as an existing type. The
type (T u1 ... uk) renames the datatype t. It differs from a type synonym in
that it creates a distinct type that must be explicitly coerced to or from the
original type

What I don't see is anything that discusses what newtype T = T T could mean.

Is there any difference in how GHC treats newtype T = T T versus data T?

-- 
Chris

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


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Miguel Mitrofanov
  - the syntax for an expression
  - the syntax for a block
  Don't see your point.
 The point is the syntax is introduced as transformation of layout form to  
 non layout form.
 As a user, I just want to be able to spot the basic components of a source  
 file without thinking about transformation rules.

Well, most users are.

  Oh, that's pretty easy, parenthesized expression is not divided by a  
  comma.
 Thanks! What is the end of a block ? What introduce new blocks ?

Not sure what you mean by block here.

 Is this legal (`plus`) x y ?

Never tried to write this myself, it looks stupid.

 It's this a tuple ?  ([a,b,c,d ]) ?

No, since all commas are in the subexpression.

  then your putStrLn would be performed twice. IO actions are first-class  
  values, that's a feature, not a bug.
 What guarantees that by running the main, the string Hello world will be  
 printed exactly twice ?

What kind of guarantees do you want?

 I just want the sistem to be able to print one of these expressions !
 Its this too much to ask ?

Yes, 'cause it means you want to embed almost all source code into the compiled 
program.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: New to Haskell

2007-12-18 Thread Cristian Baboi
On Tue, 18 Dec 2007 11:56:36 +0200, Jon Fairbairn  
[EMAIL PROTECTED] wrote:



Cristian Baboi [EMAIL PROTECTED] writes:




- the syntax for a block


Not sure what you mean by block.

do a - [1..10]
   b - [3,4]
   return (a,b)

is an expression... you can write that same expression as
do {a - [1..10]; b - [3,4]; return (a,b)} too.



I mean anything that you can put between { }, and between ;



- the adhoc syntax rules (how to distinguish among a tuple
and a  pharanthesized expression



a tuple has commas in it. I'll grant that (x) not being a
1-tuple is a little ad-hoc, but there really is very little
ad-hockery in Haskell (and a 1-tuple behaves very much like
a plain value after all).


Is this ([1 ,2 ,3 ,4]) a tuple or what ?
It has commas in it!


- the fact that lambda expressions are not the same thing
as algebraic data values



It might help to know why you think they might be the same;
the syntax is different and the name is different...


Ah, just a thought, nothing more.
Lambda expressions are values, which is just data, after all.
Even C can apply a function variable to an argument (function pointers).



- what guarantees are made by the LANGUAGE that an IO action
(such as  do  putStrLn Hello world ) is not performed
twice



As has been pointed out, «do putStrLn Hello world» is an
expression that you can bind to a variable and use as many
times as you like. Incidentally, it means the same as
«putStrLn Hello World»; do connects a sequence of bindings
and expressions, so you don't need it if there's nothing to
be connected to.


Yes, but that was not the question.
What make you so sure it will be printed the exact number of times you  
intended ?



- the lambda expressions can be written (input) but cannot
be printed  (output)



This is a fundamental property of the language.  A lambda
expression is programme and at runtime the system doesn't
know one lambda expression from another (all it can do with
one is apply it to something).


Even C can apply a function variable to an argument (function pointers).
What make Haskell different beside the lazy evaluation and mutable  
variables things ?



The biggest problem for me, so far, is the last one.


I can't see how your example illustrates that, I'm afraid.


In a very strange way. Nevermind.


Here is some strange example:



What I don't understand is why I'm forced to use guards like
x==aa in cc,  when aa is clearly bounded (is 7) and why in
function h, the bounded u and  v become free variables in
the case expression.



I would have liked the language design to have permitted
case to pattern match against variables too, but the
question is, what would the syntax be?  There was a fair bit
of discussion about this when the language was designed (and
since), but no-one could come up with a good way of doing
it. One aspect of it is this: we want



f 0 = 42
f x = 3*x

to work, and we want all function definitions to be
translated into the core language in the same way,
so you get
f = \a - case a of
0 - 42
x - 3*x

and given that, you can't have a variable on the LHS of -
do anything other than get bound to the value of the
expression in the case (a in the example). It's not just a
the top level, either:

f Nothing = 0
f (Just n) = n+1

just means
f = \v - case v of
Nothing - 0
Just n - n+1

so you can't have variables inside constructors do anything
but get bound at that point.





Thank you very much!


 Information from NOD32 
This message was checked by NOD32 Antivirus System for Linux Mail Servers.
 part000.txt - is OK
http://www.eset.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Cristian Baboi
On Tue, 18 Dec 2007 12:25:18 +0200, Miguel Mitrofanov  
[EMAIL PROTECTED] wrote:



 - the syntax for an expression
 - the syntax for a block
 Don't see your point.
The point is the syntax is introduced as transformation of layout form  
to

non layout form.
As a user, I just want to be able to spot the basic components of a  
source

file without thinking about transformation rules.



Well, most users are.

Are what ?

Able to spot or thinking about ...
Have you asked them all ?



Is this legal (`plus`) x y ?


Never tried to write this myself, it looks stupid.


What else haven't you tried to write by know ?

It's a kind of mirror, you know .



 then your putStrLn would be performed twice. IO actions are  
first-class

 values, that's a feature, not a bug.
What guarantees that by running the main, the string Hello world will  
be

printed exactly twice ?


What kind of guarantees do you want?


Written in blood.


I just want the sistem to be able to print one of these expressions !
Its this too much to ask ?


Yes, 'cause it means you want to embed almost all source code into the  
compiled program.


So ?


 Information from NOD32 
This message was checked by NOD32 Antivirus System for Linux Mail Servers.
 part000.txt - is OK
http://www.eset.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: New to Haskell

2007-12-18 Thread Miguel Mitrofanov
  - the lambda expressions can be written (input) but cannot
  be printed  (output)
  This is a fundamental property of the language.  A lambda
  expression is programme and at runtime the system doesn't
  know one lambda expression from another (all it can do with
  one is apply it to something).
 Even C can apply a function variable to an argument (function pointers).

Yes, and Haskell can do it also. But C, I guess, can't print out a source code 
for a function (well, there can be some weird dialects of C I'm not aware 
about). Haskell can't do it either.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: New to Haskell

2007-12-18 Thread Ketil Malde
Cristian Baboi [EMAIL PROTECTED] writes:

 I mean anything that you can put between { }, and between ;

Okay, there you have it then: the syntax for a block is a {, followed
by elements separated by ;s and terminated by a }.

Perhaps you are really asking about how the layout rule works?  (Which
has already been answered, btw.)

 Is this ([1 ,2 ,3 ,4]) a tuple or what ?
 It has commas in it!

Good observation.  Lists also have commas in them, and strings can,
too.  ,,, is not a tuple, either.  A tuple would have a (, and
subexpressions separated by commas, and terminated by ).  The
subexpressions would need to be maximal, and have no superexpression
except the tuple. 

I must admit I don't understand why you find this difficult, I've had
my share of problems grokking Haskell, but tuple syntax has always
seemed quite natural.

 - the fact that lambda expressions are not the same thing
 as algebraic data values

 It might help to know why you think they might be the same;
 the syntax is different and the name is different...

 Ah, just a thought, nothing more.
 Lambda expressions are values, which is just data, after all.

Yes.

 Even C can apply a function variable to an argument (function pointers).

Would you say that functions and structs in C are the same thing
because of this?

 This is a fundamental property of the language.  A lambda
 expression is programme and at runtime the system doesn't
 know one lambda expression from another (all it can do with
 one is apply it to something).

 Even C can apply a function variable to an argument (function pointers).
 What make Haskell different beside the lazy evaluation and mutable
 variables things ?

Referential transparency?  But if you are happy about how C can print
functions, perhaps you want to do:

  instance Show (a - b) where
 show x = A function

  Main show (+)
  A function

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Cristian Baboi

Thank you very much!

On Tue, 18 Dec 2007 12:17:54 +0200, Jules Bean [EMAIL PROTECTED]  
wrote:



Cristian Baboi wrote:
On Tue, 18 Dec 2007 10:29:43 +0200, Miguel Mitrofanov  
[EMAIL PROTECTED] wrote:




- what guarantees are made by the LANGUAGE that an IO action (such  
as  do

putStrLn Hello world ) is not performed twice


There are no such guarantees. If you write

a = putStrLn Hello world
main = do {a; a;}

then your putStrLn would be performed twice. IO actions are  
first-class values, that's a feature, not a bug.
  What guarantees that by running the main, the string Hello world  
will be printed exactly twice ?



The semantics of IO, and the guarantees of the runtime.

IO specifies that () means compose two actions to make a larger  
action which does the first actions, then the second action.


[do {a; a;} is notation for a  a]

The RTS specifies that the main action is performed exactly once.


Is this dependent on the implementation (if I use GHC or Hugs) or is  
something that the language say ?

Aside: I tried something like this in WinHugs:

do { xxx-getLine ; putStrLn xxx }

and pressed two keys at once for the getLine action.

The result I've got was an infinite loop !!!



- the lambda expressions can be written (input) but cannot be printed
(output)


Yes, since two different lambda expressions can denote the same  
function.

I just want the sistem to be able to print one of these expressions !
 Its this too much to ask ?
I find it very strange that I can write a lambda expresion, but the  
system cannot.


Haskell doesn't contain a code representation natively. It is not a  
homoiconic language. Just like C, C++, Java, Python, Perl, and Ruby,  
the compiler/interpreter is free to transform code into some more  
efficient form for running (including transformation all the way to  
native code, which is what ghc does) and once it has done so, it retains  
no information about the shape of the source code which yielded the  
function.


Thank you.


 Information from NOD32 
This message was checked by NOD32 Antivirus System for Linux Mail Servers.
 part000.txt - is OK
http://www.eset.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Miguel Mitrofanov
  As a user, I just want to be able to spot the basic components of a  
  source
  file without thinking about transformation rules.
  Well, most users are.
 Are what ?

Sorry if I've confused you. English isn't my native language. Are able, of 
course.

 Have you asked them all ?

If you're unsure, we can vote here or somewhere else.

  Is this legal (`plus`) x y ?
 
  Never tried to write this myself, it looks stupid.
 What else haven't you tried to write by know ?

Well, I hope, I haven't tried to write the most of stupid-looking things.

  What kind of guarantees do you want?
 Written in blood.

Write it yourself, I don't have too much blood.

  I just want the sistem to be able to print one of these expressions !
  Its this too much to ask ?
  Yes, 'cause it means you want to embed almost all source code into the  
  compiled program.
 So ?

So, I don't know any compiler of any language which does it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: New to Haskell

2007-12-18 Thread Cristian Baboi
On Tue, 18 Dec 2007 12:49:52 +0200, Miguel Mitrofanov  
[EMAIL PROTECTED] wrote:



 - the lambda expressions can be written (input) but cannot
 be printed  (output)
 This is a fundamental property of the language.  A lambda
 expression is programme and at runtime the system doesn't
 know one lambda expression from another (all it can do with
 one is apply it to something).
Even C can apply a function variable to an argument (function pointers).


Yes, and Haskell can do it also. But C, I guess, can't print out a  
source code for a function (well, there can be some weird dialects of C  
I'm not aware about). Haskell can't do it either.



Well, LISP can, if I remember it right.



 Information from NOD32 
This message was checked by NOD32 Antivirus System for Linux Mail Servers.
 part000.txt - is OK
http://www.eset.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Jules Bean

Cristian Baboi wrote:
   What guarantees that by running the main, the string Hello world

will be printed exactly twice ?



The semantics of IO, and the guarantees of the runtime.

IO specifies that () means compose two actions to make a larger 
action which does the first actions, then the second action.


[do {a; a;} is notation for a  a]

The RTS specifies that the main action is performed exactly once.


Is this dependent on the implementation (if I use GHC or Hugs) or is 
something that the language say ?


It's something the language says. IO is part of the runtime, its 
semantics are defined.



Aside: I tried something like this in WinHugs:

do { xxx-getLine ; putStrLn xxx }

and pressed two keys at once for the getLine action.

The result I've got was an infinite loop !!!


If that code loops you have a bug (in hugs?) it certainly shouldn't.

It will wait until you press return before it prints anything, though.

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


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Peter Lund
On Tue, 2007-12-18 at 12:53 +0200, Cristian Baboi wrote:

  The semantics of IO, and the guarantees of the runtime.
 
  IO specifies that () means compose two actions to make a larger  
  action which does the first actions, then the second action.
 
  [do {a; a;} is notation for a  a]
 
  The RTS specifies that the main action is performed exactly once.
 
 Is this dependent on the implementation (if I use GHC or Hugs) or is  
 something that the language say ?

Part of the language.  You do get your guarantee written in blood.

-Peter

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


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Spencer Janssen
On Tuesday 18 December 2007 01:31:59 Cristian Baboi wrote:
 A few days ago, for various reasons, I've started to look at Haskell.
 At first I was quite impressed, after reading some FAQ, and some tutorials.
 Evrything was nice and easy ... until I've started writing some code on my
 own.

 What I should have been told about upfront:

 - the syntax for an expression
 - the syntax for a block
 - the adhoc syntax rules (how to distinguish among a tuple and a
 pharanthesized expression and how to find the start and end of a block for
 example )

 - the fact that lambda expressions are not the same thing as algebraic
 data values
 - what guarantees are made by the LANGUAGE that an IO action (such as  do
 putStrLn Hello world ) is not performed twice
 - the lambda expressions can be written (input) but cannot be printed
 (output)

 The biggest problem for me, so far, is the last one.

 Here is some strange example:

 module Hugs where

 aa::Int
 aa=7

 cc:: (Int-Int)-(Int-Int-Int)-Int-(Int-Int)
 cc a op b  =  \x- case x of  {   _ | x==aa - x+1 ;  _- a x `op` b }

 f::Int-Int
 f(1)=1
 f(2)=2
 f(_)=3

 g::Int-Int
 g(1)=13
 g(2)=23
 g(_)=33

 h::[Int-Int] - Int -Int
 h  []  x   = x
 h  [rr]  x=  let { u=Hugs.f ; v=Hugs.g } in  case rr of  {  u  -
 Hugs.g(x)+aa ; v - Hugs.f(x)+aa ; _ -rr (x) + aa }
 h  (rr:ll)  x =  h [rr] x + h (ll) x


 What I don't understand is why I'm forced to use guards like x==aa in cc,
 when aa is clearly bounded (is 7) and why in function h, the bounded u and
 v become free variables in the case expression.

I don't think anyone has mentioned it yet, so I'll go ahead.  Many of the
questions you ask are well covered by the Haskell Report:

http://haskell.org/onlinereport/

The report is terse, but quite usable as a reference.  Moreover, it is The
Final Word on all these semantic and syntactic questions.


Cheers,
Spencer Janssen

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


Re: [Haskell-cafe] Re: New to Haskell

2007-12-18 Thread Miguel Mitrofanov
  Yes, and Haskell can do it also. But C, I guess, can't print out a  
  source code for a function (well, there can be some weird dialects of C  
  I'm not aware about). Haskell can't do it either.
 Well, LISP can, if I remember it right.

Only in an interpreter, if I remember it right.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: New to Haskell

2007-12-18 Thread Ketil Malde
Miguel Mitrofanov [EMAIL PROTECTED] writes:

 Well, LISP can [print functions], if I remember it right.

 Only in an interpreter, if I remember it right.

I think Emacs used to print #function or something for functions.
It seems to keep around the reresentation now.

Anyway, LISP has a bunch of different equalities (at least: =, eq, eql,
equal), so there are clearly different trade offs.

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


Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Jules Bean

Felipe Lessa wrote:

On Dec 18, 2007 7:51 AM, Jules Bean [EMAIL PROTECTED] wrote:

class Shape a where {
   intersect :: Shape b = a - b - Bool
}


Shouldn't this be

class Shape a where
  whatever

class (Shape a, Shape b) = Intersectable a b where
  intersect :: a - b - Bool

With your definition I don't see how you could make it work, as you
would have to write a function that takes care of this shape
intersecting with any other shape, but this is exactly the problem the
classes should solve!


Yes, that's a better solution, certainly. MPTCs are not haskell though 
:P I'm half joking, but there are solutions which don't involve 
non-standard extensions even ones as popular as MPTCs.


I didn't really think mine was particularly useful, just pointing out 
the design space, and in particular the precise parallel between the 
classes approach and the explicit dictionary approach.


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


Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Felipe Lessa
On Dec 18, 2007 7:51 AM, Jules Bean [EMAIL PROTECTED] wrote:
 class Shape a where {
intersect :: Shape b = a - b - Bool
 }

Shouldn't this be

class Shape a where
  whatever

class (Shape a, Shape b) = Intersectable a b where
  intersect :: a - b - Bool

With your definition I don't see how you could make it work, as you
would have to write a function that takes care of this shape
intersecting with any other shape, but this is exactly the problem the
classes should solve!

Cheers,

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


Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread C.M.Brown
 If however, you *really* want to keep your shapes as being seperate
 types, then you'll want to invoke the class system (note, not the same
 as OO classes).

 class Shape a where
area :: a - Int

 newtype Circle = C Int

 instance Shape Circle where
area (C r) = pi * r^2

 newtype Rectangle = R Int Int

 instance Shape Rectangle where
area (R h w) = h * w

 newtype Square = Sq Int

 instance Shape Square where
area (Sq l) = l * l

 -- Now we can do something with our shapes
 doubleArea :: Shape a = a - Int
 doubleArea s = (area s) * 2

Perhaps introduce an existensial quantification?

data Shape = forall a. Sh a = Shape a

class Sh a where
  area :: a - Float

data Circle = Circle Float

instance Sh Circle
  area (Circle r) = pi*r*2

data Rect = Rect Float Float

instance Sh Rect
  area (Rect h w) = h * w

doubleArea :: Shape - Float
doubleArea (Shape x) = (area x) * 2

I think this is more in the traditional OOP sense. But this way or Tom's:
one would have to convert functions like equality over Values of type
Shape into equality over different types (Circle and Rect). This can be
done using case analysis over the types with something like read.

Kind regards,
Chris.

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


Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Tillmann Rendel

Felipe Lessa wrote:

class Shape a where
  whatever

class (Shape a, Shape b) = Intersectable a b where
  intersect :: a - b - Bool


This looks nice at first sight, but is it usefull in practice? I can 
somehow express the type any shape wich is intersectable with a given 
other shape, but it is a pain:


  data Intersectable a = forall b . Intersectable a b = Intersectable b

  instance Intersectable a (Intersectable b) where
intersect a (Intersectable b) = intersect a b

Now consider I write another binary function as a type class:

  class (Shape a, Shape b) = Containment a b where
contains :: a - b - Bool

  data Containment a = forall b . Containment a b = Containment b

  instance Containment a (Containment b) where
contains a (Containment b) = contains a b

I cannot combine these types to express any shape wich is intersectable 
and can be united with a given other shape without writing another 
existiential wrapper.


I cannot express a list of pairwise intersectable shapes either.

Things get even worse if we consider a different definition of intersect:

  class (Shape a, Shape b, Shape c) = Intersect a b c | a b - c where
intersect :: a - b - c

My conclusion: To make Haskell a better OO language then current OO 
languages, we need either first-class typeclasses (to quantify over the 
classes an existential wrapped value supports) or inference of 
existential wrappers (to infer complicated wrappers automatically).


(Since it's not the goal of Haskell to be any OO language at all this 
may not be a problem)


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


[Haskell-cafe] New to Haskell: The End

2007-12-18 Thread Cristian Baboi

Haskell strengts as I see them:

- it is lazy with class
- it is strongly typed
- it has automatic memory management
- it has a standard library
- it has a compiler
- it is available on several platforms
- it has a community
- it is free

Is there anything you would like to add ?






 Information from NOD32 
This message was checked by NOD32 Antivirus System for Linux Mail Servers.
 part000.txt - is OK
http://www.eset.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Lutz Donnerhacke
* Tillmann Rendel wrote:
 My conclusion: To make Haskell a better OO language

Haskell is not an OO language and never should be.

 (Since it's not the goal of Haskell to be any OO language at all this
 may not be a problem)

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


Re: [Haskell-cafe] New to Haskell: The End

2007-12-18 Thread Reinier Lamers

Cristian Baboi wrote:

Haskell strengts as I see them:

- it is lazy with class
- it is strongly typed
- it has automatic memory management
- it has a standard library
- it has a compiler
- it is available on several platforms
- it has a community
- it is free

Is there anything you would like to add ? 
That list describes Java right on (apart from the lazy with class, 
which sounds Larry-Wall-ish though and might as well mean Perl :-)).


Higher-order functions, purity, pattern-matching, no-nonsense syntax, 
algebraic data types, ...


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


Re: [Haskell-cafe] New to Haskell: The End

2007-12-18 Thread Alex Sandro Queiroz e Silva

Hallo,

Cristian Baboi escreveu:
From your list, I agree to add some pattern matching abilities to 
mine, but that it all.



Keep using Haskell and resend your list in six months.

-alex

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


Re: [Haskell-cafe] New to Haskell: The End

2007-12-18 Thread Jules Bean

Cristian Baboi wrote:

Haskell strengts as I see them:

- it is lazy with class
- it is strongly typed
- it has automatic memory management
- it has a standard library
- it has a compiler
- it is available on several platforms
- it has a community
- it is free

Is there anything you would like to add ?


Purity/referential transparency is the most important point you're missing.

The other point is really an extension on the strong typing: other 
languages are strongly-typed too, but few of them have such an 
expressive type system as haskell, and the expressive type system helps 
with code design, helps code work right first time, and reduces bugs.


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


[Haskell-cafe] Multiple statements with Where

2007-12-18 Thread insertjokehere

Hi all, I am having problems adding multiple definitions with where for
example in my code

--A parser for recognising binary operations
parseBinaryOp :: String - String - [(Expr, Expr, String)]
parseBinaryOp op str
| (elem op binops)  (notElem '(' (snd bm))  (notElem ')' (snd bm)) 

(elem nstr!!1 binops) = [(EInt 1, EInt 1, HERE!)]
| otherwise = []
where bm = bracketMatch str
  nstr = words (snd (bracketMatch str))

I get the error message
parse error on input `='

Essentially this function is supposed to parse binary operations in a
string, nstr is just a [String], binops is a list of Strings. The types
appear to be fine, and GHCI dosnt say that this is the problem, the problem
seems to lie with that definition of nstr after the definition of bm. I
believe I have followed the definitions correctly, so I am at a loss for how
to solve this problem. The list that is given for the first case is only a
placeholder, once I get past this problem I should be able to make the
function operate properly

Any help would be much appreciated, please tell me if you need more info.

Thankyou :-)
-- 
View this message in context: 
http://www.nabble.com/Multiple-statements-with-Where-tp14397482p14397482.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] New to Haskell: The End

2007-12-18 Thread Cristian Baboi
On Tue, 18 Dec 2007 15:33:55 +0200, Reinier Lamers  
[EMAIL PROTECTED] wrote:



Cristian Baboi wrote:

Haskell strengts as I see them:

- it is lazy with class
- it is strongly typed
- it has automatic memory management
- it has a standard library
- it has a compiler
- it is available on several platforms
- it has a community
- it is free

Is there anything you would like to add ?
That list describes Java right on (apart from the lazy with class,  
which sounds Larry-Wall-ish though and might as well mean Perl :-)).


Higher-order functions, purity, pattern-matching, no-nonsense syntax,  
algebraic data types, ...


From your list, I agree to add some pattern matching abilities to mine,  
but that it all.



 Information from NOD32 
This message was checked by NOD32 Antivirus System for Linux Mail Servers.
 part000.txt - is OK
http://www.eset.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Multiple statements with Where

2007-12-18 Thread Jules Bean

insertjokehere wrote:

Hi all, I am having problems adding multiple definitions with where for
example in my code

--A parser for recognising binary operations
parseBinaryOp :: String - String - [(Expr, Expr, String)]
parseBinaryOp op str
| (elem op binops)  (notElem '(' (snd bm))  (notElem ')' (snd bm)) 

(elem nstr!!1 binops) = [(EInt 1, EInt 1, HERE!)]
| otherwise = []
where bm = bracketMatch str
  nstr = words (snd (bracketMatch str))


alignment. Where clauses are layout.

Here is how I suggest you layit out:

--A parser for recognising binary operations
parseBinaryOp :: String - String - [(Expr, Expr, String)]
parseBinaryOp op str
| (elem op binops) 
  (notElem '(' (snd bm)) 
  (notElem ')' (snd bm)) 
  (elem nstr!!1 binops) = [(EInt 1, EInt 1, HERE!)]
| otherwise = []
  where bm = bracketMatch str
nstr = words (snd (bracketMatch str))


Note that the where clause comes to the left of the |, because where 
clauses scope over all the guards


It may be a good idea not to use 'hard' tabs.

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


Re: [Haskell-cafe] Multiple statements with Where

2007-12-18 Thread Matthew Brecknell
insertjokehere wrote:
   where bm = bracketMatch str
 nstr = words (snd (bracketMatch str))

It looks like you have set your editor to make tabs look like four
spaces. Haskell compilers are required to interpret tabs as being
equivalent to eight spaces, so it sees bm = and nstr = at different
alignments.

Moral of the story: It's probably best to just not use tabs in Haskell
code.

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


Re: [Haskell-cafe] Multiple statements with Where

2007-12-18 Thread Tillmann Rendel

insertjokehere wrote:

--A parser for recognising binary operations
parseBinaryOp :: String - String - [(Expr, Expr, String)]
parseBinaryOp op str
| (elem op binops)  (notElem '(' (snd bm))  (notElem ')' (snd bm)) 

(elem nstr!!1 binops) = [(EInt 1, EInt 1, HERE!)]


You want (elem (nstr !! 1) binops) here because function application 
binds stronger then all operators. You can even write


  elem op binops  notElem '(' (snd bm)  ...

for that reason.


| otherwise = []
where bm = bracketMatch str
  nstr = words (snd (bracketMatch str))


You want

  where bm = ...
nstr = ...

here, because the first non-space characters of lines belonging to the 
same layout-block have to be at the same horizontal position. Your


  where bm = bracketMatch ...
nstr = ...

is parsed as

  where { bm = bracketMatch ... nstr = ... }

instead of

  where { bm = bracketMatch ...;
  nstr = ... }

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


[Haskell-cafe] Foldable Rose Trees

2007-12-18 Thread Dominic Steinitz
I've been trying to re-label nodes in a rose tree without re-inventing
wheels (although I'm beginning to wish I had). I've got as far as this
but haven't yet cracked the general case for Traversable.

Any help would be much appreciated.

Thanks, Dominic.

 *Main let (p,_) = runState (unwrapMonad (traverse (\x - WrapMonad update) 
 (Rose' 3 [Rose' 5 [Rose' 11 [Rose' 19 []], Rose' 13 [], Rose' 17[]], Rose' 7 
 []]))) 0 in p
 Rose' 0 [Rose' 1 [Rose' 2 [Rose' 3 []],Rose' 4 [],Rose' 5 []],Rose' 6 []]


 import Control.Applicative
 import Data.Foldable
 import Data.Traversable
 import Data.Monoid
 import Control.Monad.State
 
 update :: MonadState Int m = m Int
 update =
do x - get
   put (x + 1)
   return x
 
 data Rose' a = Rose' a [Rose' a]
deriving Show
 
 instance Functor Rose' where
   fmap f (Rose' x rs) = Rose' (f x) (map (fmap f) rs)
 
 instance Foldable Rose' where
foldMap f (Rose' x rs) =  f x `mappend` (mconcat (map (foldMap f) rs))
 
 instance Traversable Rose' where
traverse f (Rose' x []) = Rose' $ f x * pure []
traverse f (Rose' x [x0]) = Rose' $ f x * (pure (\x - [x]) * 
 traverse f x0)
traverse f (Rose' x [x0,x1]) = Rose' $ f x * (pure (\x y - x:y:[]) 
 * traverse f x0 * traverse f x1)
traverse f (Rose' x [x0,x1,x2]) = Rose' $ f x * (pure (\x y z - 
 x:y:z:[]) * traverse f x0 * traverse f x1 * traverse f x2)


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


Re: [Haskell-cafe] New to Haskell: The End

2007-12-18 Thread Henning Thielemann

On Tue, 18 Dec 2007, Cristian Baboi wrote:

 Haskell strengts as I see them:

 - it is lazy with class
 - it is strongly typed
 - it has automatic memory management
 - it has a standard library
 - it has a compiler
 - it is available on several platforms
 - it has a community
 - it is free

 Is there anything you would like to add ?

Haskell slogan discussion can start again. :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Henning Thielemann

On Tue, 18 Dec 2007, Benja Fallenstein wrote:

 Hi Cristian,

 On Dec 18, 2007 10:53 AM, Cristian Baboi [EMAIL PROTECTED] wrote:
   - the lambda expressions can be written (input) but cannot be printed
   (output)
 
   Yes, since two different lambda expressions can denote the same function.
  I just want the sistem to be able to print one of these expressions !
 
  Its this too much to ask ?
  I find it very strange that I can write a lambda expresion, but the system
  cannot.

 It's a trade-off. Haskell has as a design goal that you can use
 equational reasoning everywhere -- that if you have two ways of
 writing the same function, you can substitute one for the other in any
 expression, without changing the result of that expression. For
 example, since you can prove

 sum = foldl (+) 0 = foldr (+) 0 = last . scanl (+) 0

Since this was discussed already here, I summed it up in:
  http://www.haskell.org/haskellwiki/Show_instance_for_functions
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: New to Haskell

2007-12-18 Thread Jon Fairbairn
Cristian Baboi [EMAIL PROTECTED] writes:

 On Tue, 18 Dec 2007 11:56:36 +0200, Jon Fairbairn
 [EMAIL PROTECTED] wrote:

 Cristian Baboi [EMAIL PROTECTED] writes:


 - the syntax for a block

 Not sure what you mean by block.

 do a - [1..10]
b - [3,4]
return (a,b)

 is an expression... you can write that same expression as
 do {a - [1..10]; b - [3,4]; return (a,b)} too.


 I mean anything that you can put between { }, and between ;

That's a bit like asking for the syntax of anything you can
put between ( and ); The braces are used for grouping,
and can group different things:  

case 2 of {1 - 2 ; 2 - 2}
do {a - Just 1; return a}

 Is this ([1 ,2 ,3 ,4]) a tuple or what ?
 It has commas in it!

Not in any meaningful sense...

 - what guarantees are made by the LANGUAGE that an IO action
 (such as  do  putStrLn Hello world ) is not performed
 twice

 As has been pointed out, «do putStrLn Hello world» is an
 expression that you can bind to a variable and use as many
 times as you like.

 Yes, but that was not the question.
 What make you so sure it will be printed the exact number of
 times you  intended ?

I don't understand your question at all, then.  How many
times it gets printed depends on how many times the
programme is run, for one thing. Otherwise, it's a matter of
the definition of the semantics of the language.  Evaluation
of a Haskell programme proceeds from evaluation of «main»,
which returns an object of type IO -- a sequence of
Input/Output operatens -- that is run. IO doesn't happen
when you evaluate an IO action, it happens when the IO
action is run. For example, if you define

f x = seq (putStrLn foo!) (x+1)

and have 

main = print (f 2)

the «putStrLn foo!» is evaluated because seq forces its
first argument, but the only output you get is 3.


 This is a fundamental property of the language.  A lambda
 expression is programme and at runtime the system doesn't
 know one lambda expression from another (all it can do with
 one is apply it to something).

 Even C can apply a function variable to an argument (function pointers).

The secret of good language design is not what the language
allows, it's what the language forbids.

-- 
Jón Fairbairn [EMAIL PROTECTED]


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


Re: [Haskell-cafe] New to Haskell: The End

2007-12-18 Thread jerzy . karczmarczuk
Concerning the subject: The End of WHAT? 

Cristian Baboi writes: 

Reinier Lamers wrote: 

Cristian Baboi wrote:

Haskell strengts as I see them:

...

- it has a compiler

...

Is there anything you would like to add ?


Higher-order functions, purity, pattern-matching, no-nonsense syntax,  
algebraic data types, ...


From your list, I agree to add some pattern matching abilities to mine,  
but that it all.


Oh, it is anyway very generous of you. But tell me: do you *understand*
the remaining issues, notably the purity? 



Jerzy Karczmarczuk 



PS. For Henning T.: Don't worry, the slogan battle won't start again. The
discussion level is not appropriate. Although we can, of course, add to
this damned page the ad: people, use Haskell! It has a compiler! 



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


[Haskell-cafe] Re: Foldable Rose Trees

2007-12-18 Thread apfelmus

Dominic Steinitz wrote:

I've been trying to re-label nodes in a rose tree without re-inventing
wheels (although I'm beginning to wish I had). I've got as far as this
but haven't yet cracked the general case for Traversable.


Solution 1) Data.Tree is already an instance of Traversable. :)

Solution 2) The key observation is that you the instances for rose trees 
can/should be bootstrapped from corresponding instances for lists []. 
With this, we have



instance Functor Rose' where
  fmap f (Rose' x rs) = Rose' (f x) (map (fmap f) rs)


 fmap f (Rose' x rs) = Rose' (f x) (fmap (fmap f) rs)

(fmap instead of map to highlight the general structure)


instance Foldable Rose' where
   foldMap f (Rose' x rs) =  f x `mappend` (mconcat (map (foldMap f) rs))


  foldMap f (Rose' x rs) =  f x `mappend` (foldMap (foldMap f) rs)


instance Traversable Rose' where
   traverse f (Rose' x []) = Rose' $ f x * pure []
   traverse f (Rose' x [x0]) = Rose' $ f x * (pure (\x - [x]) * traverse 
f x0)
   traverse f (Rose' x [x0,x1]) = Rose' $ f x * (pure (\x y - x:y:[]) * 
traverse f x0 * traverse f x1)
   traverse f (Rose' x [x0,x1,x2]) = Rose' $ f x * (pure (\x y z - x:y:z:[]) * 
traverse f x0 * traverse f x1 * traverse f x2)


  traverse f (Rose' x xs) = Rose' $ f x * traverse (traverse f) xs




*Main let (p,_) = runState (unwrapMonad (traverse (\x - WrapMonad update) 
(Rose' 3 [Rose' 5 [Rose' 11 [Rose' 19 []], Rose' 13 [], Rose' 17[]], Rose' 7 []]))) 0 
in p
Rose' 0 [Rose' 1 [Rose' 2 [Rose' 3 []],Rose' 4 [],Rose' 5 []],Rose' 6 []]


This can be made shorter:

 Data.Traversable.mapM m = unwrapMonad . traverse . (\x - WrapMonad (m x))


Regards,
apfelmus

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


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Benja Fallenstein
Hi Henning,

On Dec 18, 2007 3:53 PM, Henning Thielemann
[EMAIL PROTECTED] wrote:
 Since this was discussed already here, I summed it up in:
   http://www.haskell.org/haskellwiki/Show_instance_for_functions

I find the discussion under theoretical answer unsatisfying. The
property that a Show instance for functions would break is
extensionality, and while extensionality is a desirable trait and
matches the common mathematical intuitions, a system with intensional
functions certainly isn't unmathematical or impure.

Further, even with extensionality, we can (with compiler support) in
principle have Show instances other than enumerating the graph. At
least for simple non-recursive functions, showing the Böhm tree of the
function could be useful (except that you loop forever if you
encounter bottom somewhere, of course, instead of printing bottom as
you would if you could print the actual Böhm tree). For example, id
would be shown as \a - a, maybe would be shown as \a b c - case c
of { Just d - b d; Nothing - a }, and all would be shown as \a -
case a of { (b:c) - case b of { False - False; True - case c of {
(d:e) - case d of { False - False et cetera ad infinitum.

Of course, for functions on ints this would indeed reduce to
enumerating the graph, printed as an infinite case expression.

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


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Benja Fallenstein
On Dec 18, 2007 4:50 PM, Benja Fallenstein [EMAIL PROTECTED] wrote:
 Further, even with extensionality, we can (with compiler support) in
 principle have Show instances other than enumerating the graph.

Now that I said it, I'm starting to doubt we even need compiler
support beyond what we have already. :-) I'm starting to think that a
smattering of unsafePerformIO might be able to do the trick.

I shall have to think on this :-)

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


Re: [Haskell-cafe] list utilities -- shouldn't these be in the hierarchical libs somewhere?

2007-12-18 Thread Twan van Laarhoven

Jules Bean wrote:


Thomas Hartman wrote:



I found

  http://haskell.cs.yale.edu/haskell-report/List.html

  had many useful one off type list functions such as subsequences 
and permutations which are nowhere to be found in hoogle, Data.List, 
or the haskell hierarchical libs



Weird.

It's not very many. Other that those, I spotted: sums, products, 
elemIndexBy, elemBy.


I have no idea why they were removed between that version of the report 
and haskell98.


For the ones you mention:

 - sums, products:

  The names don't make it clear what they do, I could for instance 
imagine sums being 'map sum'. And should it be a 'scanl' or 'scanr'?


 - elemIndexBy, elemBy:

  elemBy f x = any (f x)
  elemIndexBy f xs x = findIndex (f x) xs

On the other hand, I would love to see subsequences and permutations 
added to Data.List. In fact, I made a library proposal to make this 
happen, hopefully they will be added to the standard library soon.


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


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Henning Thielemann

On Tue, 18 Dec 2007, Benja Fallenstein wrote:

 Hi Henning,

 On Dec 18, 2007 3:53 PM, Henning Thielemann
 [EMAIL PROTECTED] wrote:
  Since this was discussed already here, I summed it up in:
http://www.haskell.org/haskellwiki/Show_instance_for_functions

 I find the discussion under theoretical answer unsatisfying. The
 property that a Show instance for functions would break is
 extensionality, and while extensionality is a desirable trait and
 matches the common mathematical intuitions, a system with intensional
 functions certainly isn't unmathematical or impure.

The mathematical definition of function I know of, says that functions
are special relations, and relations are sets of pairs. Their is nothing
about intension.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Paul Hudak




If the semantics of a language says that a function
f is equivalent to a function g, but there is a function h such that
h(f) is not equivalent to h(g), then h cannot be a function. Therefore
that language cannot be a (purely) functional language.

That is the pure and simple reason why functions are not Showable in
Haskell.

This doesn't mean that it isn't possible to show functions -- even
compiled code can usually be reverse-engineered to yield some printable
version of an equivalent function -- but if the language is to remain
pure, such facilities should be relegated to the development tools
(debugger, etc.).

 -Paul


Benja Fallenstein wrote:

  Hi Henning,

On Dec 18, 2007 3:53 PM, Henning Thielemann
[EMAIL PROTECTED] wrote:
  
  
Since this was discussed already here, I summed it up in:
  http://www.haskell.org/haskellwiki/Show_instance_for_functions

  
  
I find the discussion under "theoretical answer" unsatisfying. The
property that a Show instance for functions would break is
extensionality, and while extensionality is a desirable trait and
matches the common mathematical intuitions, a system with intensional
functions certainly isn't "unmathematical" or impure.

Further, even with extensionality, we can (with compiler support) in
principle have Show instances other than enumerating the graph. At
least for simple non-recursive functions, showing the Bhm tree of the
function could be useful (except that you loop forever if you
encounter bottom somewhere, of course, instead of printing "bottom" as
you would if you could print the actual Bhm tree). For example, id
would be shown as "\a - a," maybe would be shown as "\a b c - case c
of { Just d - b d; Nothing - a }," and all would be shown as "\a -
case a of { (b:c) - case b of { False - False; True - case c of {
(d:e) - case d of { False - False" et cetera ad infinitum.

Of course, for functions on ints this would indeed reduce to
enumerating the graph, printed as an infinite case _expression_.

- Benja
___
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] New to Haskell

2007-12-18 Thread Benja Fallenstein
Hi Henning,

On Dec 18, 2007 5:17 PM, Henning Thielemann
[EMAIL PROTECTED] wrote:
 The mathematical definition of function I know of, says that functions
 are special relations, and relations are sets of pairs. Their is nothing
 about intension.

That's the standard definition in set theory, but it's not the only
mathematical definition of function. It also doesn't suffice for
defining all Haskell functions-- consider

data T = T (T - Int)

fn :: T - Int
fn _ = 7

We have (fn (T fn) == 7), so in the graph of 'fn' we must have a pair
(T fn, 7). But if 'fn' is the same mathematical object as its graph,
that would mean that the graph of 'fn' would have to contain a pair
whose first element indirectly contains... the graph of fn!

This sort of circularity is not allowed in standard ZFC set theory, so
if we're going to be precise, we will have to choose a different
representation for functions than their graphs.

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


[Haskell-cafe] MonadFix

2007-12-18 Thread Joost Behrends
Hi,

since about three weeks i am learning Haskell now. One of my first excercises is
to decompose an Integer into its primefactors. I already posted discussion on
the solution to the problem 35 in 99 excercises.

My simple algorithm uses a datatype DivIter of 4 named fields together with the
core iteration 

divstep :: DivIter - DivIter
divstep x | divisor x  bound x = x
  | ximod  0= x { divisor = (divisor x) +2 }
  | otherwise=  x {dividend=xidiv, 
   bound=intsqrt(xidiv), 
   result = result x ++ [divisor x] } 
where
(xidiv, ximod) = divMod (dividend x) (divisor x)

(dividend x is already odd, when this is called).

The problem to solve for really large Integers is how to call divstep iterated
without not accumulating billions of stack frames. Here is one possibility:

divisions = do
y - get
if divisor y = bound y then do
put ( divstep y )
divisions
else 
return y

(this for a version of divstep without the first guard) called from

res = execState divisions (DivIter { dividend = o1, 
 divisor = 3, 
 bound = intsqrt(o1),
 result = o2 })

( where o1 the odd part of the number to decompose, o2 a list of its
contained twos). This computes the primefactors of 2^120+1 in 17 minutes after
all. But i cannot help feeling that this is an abuse of the State monad. The
MonadFix has a functionfix (a - a) - a   and i added the first guard in
divstep above for making this a fixpoint problem.

For me the signature looks, as if using fix doesn't afford to create explicitely
a variable of a MonadFix instance and a simple twoliner for divisions could do
the job. What i do not understand at all from the documentation of fix is:

   fix f is the least fixed point of the function f, i.e. the least defined x
such that f x = x.

What does least mean here ? There is nothing said about x being a variable of
an instance of Ord. And why fix has not the type a - (a - a) - a, means: How
can i provide a starting point of the iteration x == f x == f (f x) == ...?  



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


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Benja Fallenstein
Hi Paul,

On Dec 18, 2007 5:18 PM, Paul Hudak [EMAIL PROTECTED] wrote:
  If the semantics of a language says that a function f is equivalent to a
 function g, but there is a function h such that h(f) is not equivalent to
 h(g), then h cannot be a function.

Sure.

 Therefore that language cannot be a
 (purely) functional language.

  That is the pure and simple reason why functions are not Showable in
 Haskell.

Not so fast :-)

Caveat one, there may be useful ways to for functions to implement
Show that don't conflict with extensionality (i.e., the property that
two functions are equal if they yield the same results for all
inputs).

Caveat two, we generally assume extensionality when reasoning about
Haskell, but it's entirely possible to give a semantics for Haskell
that doesn't assume extensionality. IMHO, a good answer to the
question why functions aren't showable in Haskell needs to explain why
we prefer our semantics to be extensional, not say that by god-given
fiat, Haskell is extensional, so we can't show functions.

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


[Haskell-cafe] Re: New to Haskell: The End

2007-12-18 Thread Joost Behrends
Henning Thielemann lemming at henning-thielemann.de writes:

  - it is lazy with class
  - it is strongly typed
  - it has automatic memory management
  - it has a standard library
  - it has a compiler
  - it is available on several platforms
  - it has a community
  - it is free

There MUST be at least two adjectives added:

it has a FAST compiler (compare to MzScheme for example)
it is strongly and PARAMETRICALLY typed

And perhaps 

it has MONADS 

I am learning Haskell 3 weeks now and have the common difficulties to understand
them, but at the first sight this seems an extremely flexible and nevertheless
clean solution to the problem. And it doesn't stop at monads, there are comonads
and arrows too. And all this very actively and countiuously revised and
developed further.





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


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Paul Hudak



Benja Fallenstein wrote:

Not so fast :-)

Caveat one, there may be useful ways to for functions to implement
Show that don't conflict with extensionality (i.e., the property that
two functions are equal if they yield the same results for all
inputs).
  
Sure, and I suppose one way to do this is to put the show function for 
functions into the IO monad -- then you can't inspect the results.  But 
if you want to inspect the result, then I have no idea how to do this.



Caveat two, we generally assume extensionality when reasoning about
Haskell, but it's entirely possible to give a semantics for Haskell
that doesn't assume extensionality. IMHO, a good answer to the
question why functions aren't showable in Haskell needs to explain why
we prefer our semantics to be extensional, not say that by god-given
fiat, Haskell is extensional, so we can't show functions.
  
Well, my caveat was that the Haskell designers wanted it this way.  So 
you are essentially rejecting my caveat, rather than creating a new one. 
:-)


   -Paul


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


[Haskell-cafe] Re: New to Haskell: The End

2007-12-18 Thread apfelmus

Joost Behrends wrote:


it has MONADS 


Interestingly, this is not even a language feature, it just happens that 
the concept of monads can be expressed in Haskell. (Ok, ignoring 
syntactic sugar in form of do-notation for the moment. And ignoring that 
constructor classes have been introduced because monads were such a cool 
use case).



Regards,
apfelmus

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


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Benja Fallenstein
On Dec 18, 2007 6:01 PM, Paul Hudak [EMAIL PROTECTED] wrote:
 Well, my caveat was that the Haskell designers wanted it this way.  So
 you are essentially rejecting my caveat, rather than creating a new one.
 :-)

I mean, I reject the answer They wanted it this way because I think
the answer should be, They wanted it this way because They looked at
substituting equals under a lambda, and They saw it was good ;-)

  Caveat one, there may be useful ways to for functions to implement
  Show that don't conflict with extensionality (i.e., the property that
  two functions are equal if they yield the same results for all
  inputs).
 
 Sure, and I suppose one way to do this is to put the show function for
 functions into the IO monad -- then you can't inspect the results.  But
 if you want to inspect the result, then I have no idea how to do this.

If you can show and enumerate the argument type and show the result
type of a function, one way is to enumerate the graph of the function.
The wiki page gives the example,

Prelude \x - x+x
functionFromGraph [(0,0), (1,2), (2,4), (3,6),
Interrupted.

If you have special compiler support, and consider a fragment of
Haskell that contains only functions -- i.e., no algebraic data types,
no Ints etc. (it's kind of a boring fragment!, but you can have Church
numbers) --, you can reduce the function to head normal form. Head
normal form looks like this:

\VAR1 VAR2 ... VARm - VARi EXPR1 ... EXPRn

and there is a reduction strategy that finds the head normal form of
an arbitrary expression if there is one; a proof that if there isn't
one, the expression denotes bottom; and a proof that if you have two
HNFs, and they differ in the part before EXPR1 or differ in the number
of EXPRjs, these HNFs denote different values.

Therefore, when you have reduced the function to HNF, you can print

\VAR1 VAR2 ... VARm - VARi 

(or more precisely, you can write a lazy 'show' that yields the above
characters as soon as it has computed the HNF). Then, you go on to
recursively compute the HNF of EXPR1, and you show that inside
parantheses.

Some examples:

show (\x - x) == \a - a
show (.) == \a b c - a (b c)

(let fix f = f (fix f) in show fix)
== \a - a (a (a (a (a.

[Unless I'm making some stupid mistake] It's well-established that
this is computable and doesn't break extensionality (i.e., that
applying this show to two functions with the same extension will give
the same result -- or conversely, if show gives different results for
two functions, there are arguments for which these functions yield
different results).

By itself, this isn't very interesting, but I *think* you should be
able to add algebraic data types and case expressions to this fragment
of Haskell and still do essentially the same thing. Then, you could
show, for example,

show either == \a b c - case c of { Left d - a d; Right e - b e }

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


[Haskell-cafe] Re: Foldable Rose Trees

2007-12-18 Thread Dominic Steinitz
 Solution 1) Data.Tree is already an instance of Traversable. :)
 

Yes it's all there but I would have missed the fun of trying to do it
myself ;-) Plus the data structure I actually want to re-label isn't
quite a rose tree.

 Solution 2) The key observation is that you the instances for rose trees 
 can/should be bootstrapped from corresponding instances for lists []. 
 With this, we have
 
 instance Functor Rose' where
   fmap f (Rose' x rs) = Rose' (f x) (map (fmap f) rs)
 
   fmap f (Rose' x rs) = Rose' (f x) (fmap (fmap f) rs)
 
 (fmap instead of map to highlight the general structure)
 
 instance Foldable Rose' where
foldMap f (Rose' x rs) =  f x `mappend` (mconcat (map (foldMap f) rs))
 
foldMap f (Rose' x rs) =  f x `mappend` (foldMap (foldMap f) rs)

Interesting - I hadn't twigged that they were the same modulo
instantiation for [].

 ((.).(.)) mconcat map :: forall a b. (Monoid b) = (a - b) - [a] - b
 *Main :t foldMap
 foldMap :: forall a m (t :: * - *).
(Monoid m, Foldable t) =
(a - m) - t a - m


 
 instance Traversable Rose' where
traverse f (Rose' x []) = Rose' $ f x * pure []
traverse f (Rose' x [x0]) = Rose' $ f x * (pure (\x - [x]) * 
 traverse f x0)
traverse f (Rose' x [x0,x1]) = Rose' $ f x * (pure (\x y - x:y:[]) 
 * traverse f x0 * traverse f x1)
traverse f (Rose' x [x0,x1,x2]) = Rose' $ f x * (pure (\x y z - 
 x:y:z:[]) * traverse f x0 * traverse f x1 * traverse f x2)
 
traverse f (Rose' x xs) = Rose' $ f x * traverse (traverse f) xs
 

And then this becomes something you might guess.

 
 
 *Main let (p,_) = runState (unwrapMonad (traverse (\x - WrapMonad update) 
 (Rose' 3 [Rose' 5 [Rose' 11 [Rose' 19 []], Rose' 13 [], Rose' 17[]], Rose' 
 7 []]))) 0 in p
 Rose' 0 [Rose' 1 [Rose' 2 [Rose' 3 []],Rose' 4 [],Rose' 5 []],Rose' 6 []]
 
 This can be made shorter:
 
   Data.Traversable.mapM m = unwrapMonad . traverse . (\x - WrapMonad (m x))
 
 

Your help as ever is excellent.

Many thanks, Dominic.

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


Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Sterling Clover
Don't think the Haskell's Overlooked Object System paper has been posted
to this thread yet:

http://homepages.cwi.nl/~ralf/OOHaskell/paper.pdf

--s


On 12/18/07, Lutz Donnerhacke [EMAIL PROTECTED] wrote:

 * Tillmann Rendel wrote:
  My conclusion: To make Haskell a better OO language

 Haskell is not an OO language and never should be.

  (Since it's not the goal of Haskell to be any OO language at all this
  may not be a problem)

 Ack.
 ___
 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


[Haskell-cafe] A Show instance for simple functions

2007-12-18 Thread Benja Fallenstein
Hi all,

Below is a program that implements Show for functions whose type is
composed of only (-) and type variables (or, more precisely, of (-)
and (State Int Term), but any type composed of (-) and type variables
can obviously be specialized to that).

(-fglasgow-exts is needed only for the convenience of being able to
declare instance MkTerm (State Int Term) -- if we'd wrap the State
Int Term in a newtype, as far as I can see this would be H98.)

- Benja


{-# OPTIONS_GHC -fglasgow-exts #-}

import Control.Monad
import Control.Monad.State
import Data.Char

data Term = Var Int | App Term Term | Lam Int Term

showVar i = [chr (ord 'a' + i)]

showTerm :: Term - String
showTerm (Var i)   = showVar i
showTerm (Lam i x) = \\ ++ showVar i ++  -  ++ showTerm x
showTerm (App f x) = showTerm f ++   ++ showArg x where
showArg (Var i) = showVar i; showArg x = ( ++ showTerm x ++ )


class MkTerm a where
argument :: State Int Term - a
mkTerm :: a - State Int Term

instance MkTerm (State Int Term) where
argument = id
mkTerm = id

instance (MkTerm a, MkTerm b) = MkTerm (a - b) where
argument f x = argument $ liftM2 App f (mkTerm x)
mkTerm f = do i - get; modify (+1)
  body - mkTerm (f (argument (return (Var i
  return $ Lam i body

instance (MkTerm a, MkTerm b) = Show (a - b) where
show f = showTerm $ evalState (mkTerm f) 0


type X = State Int Term

main = do print (id :: X - X)
  print (id :: (X - X) - (X - X))
  print ((.) :: (X - X) - (X - X) - (X - X))
  print ((\x y - y x) :: X - (X - X) - X)
  print ((\f x - f x x) :: (X - X - X) - X - X)
  print ((\f - f id id) :: ((X - X) - (X - X) - X) - X)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is StateT what I need?

2007-12-18 Thread Andre Nathan
Hello

On Mon, 2007-12-17 at 21:22 -0200, Andre Nathan wrote:
 Thanks everyone for the great suggestions. The code is much cleaner now
 (not to mention it works :)

I'm trying to finish the process tree construction but I guess I'll need
some help again.

My idea is to have a function that would return a map representing the
process tree

 createTree :: IO PsTree
 createTree = do
   entries - getDirectoryContents /proc
   return $ foldr buildTree Map.empty entries

The return $ foldr ... part is missing something, because buildTree
would have be something like:

 buildTree :: String - PsTree - StateT PsMap IO PsTree
 buildTree entry tree = do
   case matchRegex (mkRegex ^[0-9]+$) entry of
 Nothing - return tree -- skip this entry
 Just _  - do
   psMap - get
   if Map.member dir psMap
 then return tree -- alread inserted
 else return $ insertInTree dir tree

so the types don't match. insertInTree would be something like (in
pseudo-code):

 insertInTree pid tree = do
   procInfo - insertProc pid -- this inserts pid in the state map
  -- and returns a PsInfo, so its type is
  -- Pid - StateT PsMap IO PsInfo.
  -- Can I use it here though?
   psMap - get
   if pid == 1 -- init is the root of the tree
 then do modify (Map.insert 1 procInfo psMap)
 return $ Map.insert 1 procInfo tree
 else do
   let pPid = parentPid procInfo
   if Map.member pPid psMap
 then do psMap' - new psMap with pid appended pPid's children
 return tree
 else do tree' - insert pPid in the process tree
 modify (new psMap with pid appended pPid's children)
 return tree'

insertProc was in my first message, and it's like this:

 insertProc :: Pid - StateT PsMap IO PsInfo
 insertProc pid = do
   process - lift $ procInfo pid
   psMap - get
   modify (Map.insert pid process)
   return (process)

At this point I'm not sure if this design is good or even correct. I'm
mixing (StateT PsMap IO PsInfo) with (StateT PsMap IO PsTree), which I'm
not sure I can do. There is probably a much cleaner way to do this but I
cannot see through the types right now :/

Anyone has any hints on how to make that scheme work?

Thanks,
Andre

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


[Haskell-cafe] [ANN] Wadler talk in San Francisco on Jan 9, 2008

2007-12-18 Thread Keith Fahlgren
Hi all,

Philip Wadler will be in San Francisco for POPL '08 so the Bay Area Functional
Programmers have asked him to reprise his ICFP '07 talk Well-typed programs
can’t be blamed. He's been good enough to set us up with a proper room in the
ACM conference hotel. The meeting will take place in the Stanford Room, The
Stanford Court Hotel, San Francisco at 7:30pm on Wednesday, January 9th, 2008.

Please watch http://groups.google.com/group/bayfp or http://www.bayfp.org/blog/
 for more details and pass this along to others in the area that might be
interested.


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


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Henning Thielemann

On Tue, 18 Dec 2007, Benja Fallenstein wrote:

 Hi Henning,

 On Dec 18, 2007 5:17 PM, Henning Thielemann
 [EMAIL PROTECTED] wrote:
  The mathematical definition of function I know of, says that functions
  are special relations, and relations are sets of pairs. Their is nothing
  about intension.

 That's the standard definition in set theory, but it's not the only
 mathematical definition of function. It also doesn't suffice for
 defining all Haskell functions-- consider

 data T = T (T - Int)

 fn :: T - Int
 fn _ = 7

 We have (fn (T fn) == 7), so in the graph of 'fn' we must have a pair
 (T fn, 7). But if 'fn' is the same mathematical object as its graph,
 that would mean that the graph of 'fn' would have to contain a pair
 whose first element indirectly contains... the graph of fn!

 This sort of circularity is not allowed in standard ZFC set theory, so
 if we're going to be precise, we will have to choose a different
 representation for functions than their graphs.

I see.

 I'm also wondering what 'total function' and 'partial function' might
mean in Haskell, since values can be partially defined. Is
   Just undefined
 defined or undefined and is
   const (Just undefined)
 a total or a partial function?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] MonadFix

2007-12-18 Thread Daniel Fischer
Am Dienstag, 18. Dezember 2007 17:26 schrieb Joost Behrends:
 Hi,

 since about three weeks i am learning Haskell now. One of my first
 excercises is to decompose an Integer into its primefactors. I already
 posted discussion on the solution to the problem 35 in 99 excercises.

 My simple algorithm uses a datatype DivIter of 4 named fields together with
 the core iteration

But a simple recursion that returns the list of primefactors lazily would also 
solve the stack frame problem, wouldn't it?
sort of
factor 0 = error 0 has no factorisation
factor 1 = []
factor n
| n  0 = (-1):factor (-n)
| even n= 2:factor (n `div` 2)
| otherwise = oddFactors 3 n

oddFactors k n
| k*k  n   = [n]
| r == 0= k:oddFactors k q
| otherwise = oddFactors (k+2) n
  where
(q,r) = n `divMod` k

you can then start consuming the prime factors as they come, before the 
factorisation is complete.

 divstep :: DivIter - DivIter
 divstep x | divisor x  bound x = x

   | ximod  0= x { divisor = (divisor x) +2 }
   | otherwise=  x {dividend=xidiv,

bound=intsqrt(xidiv),
result = result x ++ [divisor x] }
 where
 (xidiv, ximod) = divMod (dividend x) (divisor x)

 (dividend x is already odd, when this is called).

 The problem to solve for really large Integers is how to call divstep
 iterated without not accumulating billions of stack frames. Here is one
 possibility:

 divisions = do
 y - get
 if divisor y = bound y then do
 put ( divstep y )
 divisions
 else
 return y

 (this for a version of divstep without the first guard) called from

 res = execState divisions (DivIter { dividend = o1,
  divisor = 3,
  bound = intsqrt(o1),
  result = o2 })

 ( where o1 the odd part of the number to decompose, o2 a list of its
 contained twos). This computes the primefactors of 2^120+1 in 17 minutes
 after all. But i cannot help feeling that this is an abuse of the State
 monad. The MonadFix has a functionfix (a - a) - a   and i added the
 first guard in divstep above for making this a fixpoint problem.

 For me the signature looks, as if using fix doesn't afford to create
 explicitely a variable of a MonadFix instance and a simple twoliner for
 divisions could do the job. What i do not understand at all from the
 documentation of fix is:

fix f is the least fixed point of the function f, i.e. the least
 defined x such that f x = x.

 What does least mean here ? There is nothing said about x being a
 variable of an instance of Ord. And why fix has not the type a - (a - a)
 - a, means: How can i provide a starting point of the iteration x == f x
 == f (f x) == ...?


It's quite another thing,
fix is not a fixed point iteration as used in calculus, least here means 
'least defined'.
The least defined of all values is 'undefined' (aka bottom, often denoted by 
_|_).
For simple data types like Int or Bool, a value is either completely defined 
or undefined, and both True and False are more defined than bottom, but 
neither is more or less defined than the other.
For a recursive data type like lists, you have a more interesting hierarrchy 
of definedness:
_|_ is less defined than _|_:_|_ is less defined than _|_:_|_:_|_ is less 
defined than _|_:_|_:_|_:_|_ ...
And definedness of list elements is also interesting,
_|_:_|_:_|_ is less defined than 1:_|_:_|_ is less defined than 1:2:_|_ is 
less defined than 1:2:3:_|_ is less defined than ...

You cannot use fix on a strict function (a function is strict iff f _|_ = 
_|_), as by its implementation,
fix f = let x = fix f in f x
IIRC, it's calculated without knowing what x is when f is called.
fix f is basically
lim xn, when 
x0 = undefined, 
x(n+1) = f xn

And since f x is always at least as defined as x, xn is a monotonic sequence 
(monotonic with respect to definedness), so the limit exists - it's _|_ for 
strict functions, and if we follow a few steps of the easy example fix (1:), 
we see
x0 = _|_
x1 = 1:_|_
x2 = 1:1:_|_
x3 = 1:1:1:_|_,
hence fix (1:) == repeat 1.

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


Re: [Haskell-cafe] MonadFix

2007-12-18 Thread Marc A. Ziegert
Am Dienstag, 18. Dezember 2007 schrieb Joost Behrends:
snip
fix f is the least fixed point of the function f, i.e. the least defined x
 such that f x = x.
 
 What does least mean here ? There is nothing said about x being a variable 
 of
 an instance of Ord. And why fix has not the type a - (a - a) - a, means: 
 How
 can i provide a starting point of the iteration x == f x == f (f x) == 
 ...?  
 
snip

the starting point is undefined.
the ordering of functions is is_subset_of.


a more detailed explanation:

a function A - B is a subset of the cartesian product A x B, where for 
each element in A there is not more than one element in B.
subsets are partially ordered. the empty set (the function const undefined or 
simply undefined) is the lowest subset, and AxB is the largest (but in most 
cases not a function).
the function f0 (_::a) = (undefined::b) is the lowest subset.
the function f1 ('x'::a) = (5+fromEnum 'x'::b) is larger than f0.
the function f1' ('y'::a) = (7::b) is larger than f0, and not equal (neither 
equal, nor lower, nor larger) to f1.
the function f2 (c::a) | isUpper c = (5 + fromEnum c::b) is larger than f1, 
and not equal (neither equal, nor lower, nor larger) to f1'.
the function fn (c::a) | True = (5 + fromEnum c::b) is one maximal defined 
function: it is defined on every input parameter.

now, the fix function takes a function construct_f::(a-a)-(a-a) and 
calculates first (construct_f undefined) :: (a-a). undefined :: (a-a) 
equals f0, the lowest function/element, but it is not a fixpoint. construct_f 
undefined is a bit more defined
construct_f . construct_f . construct_f . construct_f . ... (oo times) $ 
undefined is the largest thing you can get this way, it does not need to be 
defined everywhere, but it is a fixpoint. there may be larger fixpoints, but no 
lower.

example:

fix construct_f
 where construct_f f = \x - (if x==0 then 42 else f (x-1))

look at construct_f undefined: it constructs a function which is defined on 
the input x==0; otherwise it tries to evaluate undefined (x-1), which is 
completely undefined.
look at construct_f $ construct_f undefined: it constructs a function which 
is defined on the input x==0 and x==1.

fix cf = cf (fix cf) is the fixpoint function, and with this...
fix construct_f constructs a function which is defined on all inputs x=0, 
but not on inputs x0. this function is one fixpoint (the least one) of 
construct_f.
another function is a fixpoint of construct_f: \x-42. but this is a larger 
function than the above fixpoint, so this is not the LEAST FIXPOINT; the above 
one is.
you can test, whether it is a fixpoint: construct_f (\x-42) == (\x-if x==0 
then 42 else (\x-42)(x-1)) == (\x-if x==0 then 42 else 42) == (\x-42)
exercise1: construct_f (\x-if x=0 then 42 else 23) == ...?
exercise2: construct_f (\x-if x=0 then 42 else undefined) == ...?

another example: lists.

fix (\fibs-1:1:zipWith (+) fibs (tail fibs))



i hope to have helped.
- marc





signature.asc
Description: This is a digitally signed message part.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell purity and printing

2007-12-18 Thread Cristian Baboi


This is what I understand so far ...

Suppose we have these two values:
a) \x-x + x
b) \x-2 * x
Because these to values are equal, all functions definable in Haskell must  
preserve this.

This is why I am not allowed to define a function like

h :: (a-b) - (a-b)
h x = x

The reasons are very complicated, but it goes something like this:

- when one put \x-x+x trough the function h, the compiler might change it  
to \x - 2*x
- when one put \x-2*x trough the function h, the compiler might change it  
to \x - x + x


And we all know that \x - 2*x is not the same as \x-x+x and this is the  
reason one cannot define h in Haskell

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


Re: [Haskell-cafe] Haskell purity and printing

2007-12-18 Thread Philip Weaver
On Dec 18, 2007 1:00 PM, Cristian Baboi [EMAIL PROTECTED] wrote:


 This is what I understand so far ...

 Suppose we have these two values:
 a) \x-x + x
 b) \x-2 * x
 Because these to values are equal, all functions definable in Haskell must
 preserve this.
 This is why I am not allowed to define a function like

 h :: (a-b) - (a-b)
 h x = x


Of course you can define h.  This is just a more specific (as far as types
go) version of 'id', as defined in the Prelude:

   id :: a - a
   id x = x

where 'a' can be any type, including a function such as (a - b).  You can
apply 'id' to either of your functions above, and get back an equivalent
function, so each of the following evaluates to 20:

let f = id (\x - x+x) in f 10
let f = id (\x - 2 * x) in f 10
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell purity and printing

2007-12-18 Thread Nicolas Frisby
Extensionality says that the only observable properties of functions
are the outputs they give for particular inputs. Accepting
extensionality as a Good Thing implies that enabling the user to
define a function that can differentiate between f x = x + x and g x =
2 * x is a Bad Thing.

Note that your h does not differentiate between f and g (in fact, it
does not investigate them at all), the only thing you can do with f,
g, (h f), and (g f) is apply them. Accordingly, it's a fine Haskell
definition.

Why is extensionality a good thing? might be a more enlightening
question. My answer would quickly be outshone by others', so I'll stop
here.

On Dec 18, 2007 3:00 PM, Cristian Baboi [EMAIL PROTECTED] wrote:

 This is what I understand so far ...

 Suppose we have these two values:
 a) \x-x + x
 b) \x-2 * x
 Because these to values are equal, all functions definable in Haskell must
 preserve this.
 This is why I am not allowed to define a function like

 h :: (a-b) - (a-b)
 h x = x

 The reasons are very complicated, but it goes something like this:

 - when one put \x-x+x trough the function h, the compiler might change it
 to \x - 2*x
 - when one put \x-2*x trough the function h, the compiler might change it
 to \x - x + x

 And we all know that \x - 2*x is not the same as \x-x+x and this is the
 reason one cannot define h in Haskell
 ___
 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] Haskell purity and printing

2007-12-18 Thread Nicolas Frisby
This is a fine warning you both point out, but I would suggest that it
distracts from the OP's question.

The previous, germane discussion holds if we assume that i) both f and
g have type Integer - Integer, ii) the compiler writer is not out to
get us, and iii) the GMP library, if used by that compiler, is
correct. Oh and also that the representations of the Integers involved
do not require more memory than the user's computer has to offer.
Anything else seem relevant?

I do apologize for my noise if the OP was indeed thinking of + and *
as unlawful methods of the Num typeclass. A nice property of Haskell
is to note that a little confusion of math and Haskell can be very
helpful to clear up some existing confusion about Haskell.

On Dec 18, 2007 3:31 PM, Bertram Felgenhauer
[EMAIL PROTECTED] wrote:
 Cristian Baboi wrote:
  This is what I understand so far ...
 
  Suppose we have these two values:
  a) \x-x + x
  b) \x-2 * x
  Because these to values are equal, all functions definable in Haskell must
  preserve this.

 Oh but you can distinguish these functions. Consider

  a x = x+x
  b x = 2*x
 
  data T = A | B deriving (Show, Eq)
 
  instance Num T where
  _ + _ = A
  _ * _ = B
 
  f :: (T - T) - T
  f y = y undefined
 
  main = print (f a)  print (f b)

 which prints A, then B.

 The key point here is that a and b have type (Num a = a - a) and
 while well behaved Num instances certainly can not distinguish a and b,
 artificial ones like above can.

 Enjoy,

 Bertram

 ___
 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


[Haskell-cafe] Re: MonadFix

2007-12-18 Thread Joost Behrends
Daniel Fischer daniel.is.fischer at web.de writes:

 
 Am Dienstag, 18. Dezember 2007 17:26 schrieb Joost Behrends:
  Hi,
 
  since about three weeks i am learning Haskell now. One of my first
  excercises is to decompose an Integer into its primefactors. I already
  posted discussion on the solution to the problem 35 in 99 excercises.
 
  My simple algorithm uses a datatype DivIter of 4 named fields together with
  the core iteration
 
 But a simple recursion that returns the list of primefactors lazily would 
 also 
 solve the stack frame problem, wouldn't it?
 sort of
 factor 0 = error 0 has no factorisation
 factor 1 = []
 factor n
   | n  0 = (-1):factor (-n)
   | even n= 2:factor (n `div` 2)
   | otherwise = oddFactors 3 n
 
 oddFactors k n
   | k*k  n   = [n]
   | r == 0= k:oddFactors k q
   | otherwise = oddFactors (k+2) n
 where
   (q,r) = n `divMod` k
 
 you can then start consuming the prime factors as they come, before the 
 factorisation is complete.
 
Hi and thanks for your answers,

@Daniel: no, this doesn't solve the stack problem. These are the primefactors of
2^120+1: [97,257,673,394783681,4278255361,46908728641]. 

oddFactors k n | otherwise = oddFactors (k+2) n

could eventually push 394783681-673 function calls onto the stack before finding
the factor 394783681. And indeed a recursive version of divisions trying to
compute this ran more than two hours on my machine, before i stopped it (this is
the time a python script needs for the computation). And there were peaks of
memory use  300 MB ! While the version with the State monad seems to 
work tail recursive - it has an absolutely constant memory use, slightly
different per run, i watched 2044k and 2056k. And it takes around 17 minutes on
my machine getting the result.

Thus it's vital here, how the recursion is done. Because of that i separated
divisions and divstep - for experimenting with divisions. If a factor is done,
it should leave as little traces as possible on the machine.

Both of your instructions for fix are well readable - thanks again. I'll spend
some time studying them, but it seems, fix doesn't fix the problem.


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


Re: [Haskell-cafe] Is StateT what I need?

2007-12-18 Thread Andre Nathan
On Tue, 2007-12-18 at 16:47 -0200, Andre Nathan wrote:
 I'm trying to finish the process tree construction but I guess I'll need
 some help again.

I guess I could do away with StateT and just pass the PsMap around as a
parameter, but I guess that wouldn't be the haskell way...

I think my code is a bit too long and that probably makes it hard for
someone to help... Does anyone know of good example code using StateT
for keeping a global state other than the one at the Simple StateT use
page on the wiki?

Best regards,
Andre

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


Re: [Haskell-cafe] Is StateT what I need?

2007-12-18 Thread Daniel Fischer
Am Dienstag, 18. Dezember 2007 19:47 schrieb Andre Nathan:
 Hello

 On Mon, 2007-12-17 at 21:22 -0200, Andre Nathan wrote:
  Thanks everyone for the great suggestions. The code is much cleaner now
  (not to mention it works :)

 I'm trying to finish the process tree construction but I guess I'll need
 some help again.

 My idea is to have a function that would return a map representing the
 process tree

  createTree :: IO PsTree
  createTree = do
entries - getDirectoryContents /proc
return $ foldr buildTree Map.empty entries

I believe instead of return $ foldr... you should use
evalStateT $ foldM (flip buildTree) Map.empty entries


 The return $ foldr ... part is missing something, because buildTree

 would have be something like:
  buildTree :: String - PsTree - StateT PsMap IO PsTree
  buildTree entry tree = do
case matchRegex (mkRegex ^[0-9]+$) entry of
  Nothing - return tree -- skip this entry
  Just _  - do

where does 'dir' below come from? should the pattern match not be
Just dir - do ?
psMap - get
if Map.member dir psMap
  then return tree -- alread inserted
  else return $ insertInTree dir tree

perhaps just
else insertInTree dir tree
if insertInTree :: dirtype - PsTree - StateT PsMap IO PsTree


 so the types don't match. insertInTree would be something like (in

 pseudo-code):
  insertInTree pid tree = do
procInfo - insertProc pid -- this inserts pid in the state map
   -- and returns a PsInfo, so its type is
   -- Pid - StateT PsMap IO PsInfo.
   -- Can I use it here though?

sure you can use it here, the monad is m = (StateT PsMap IO),
you can chain m a, m b, m Int, m PsTree, m PsInfo freely, as long as it's only 
the same m.

psMap - get
if pid == 1 -- init is the root of the tree
  then do modify (Map.insert 1 procInfo psMap)
  return $ Map.insert 1 procInfo tree
  else do
let pPid = parentPid procInfo
if Map.member pPid psMap
  then do psMap' - new psMap with pid appended pPid's children

rather: then do modify (insert pid in pPid's children)
return tree

you don't do anything with the new map here, so no need to bind the name 
psMap' to it.
I believe here you want something like
modify (Map.adjust (Map.insert pid procInfo) pPid)
but perhaps you also want to insert pid into the PsMap?

  return tree
  else do tree' - insert pPid in the process tree
  modify (new psMap with pid appended pPid's children)

Insert pPid in the PsMap before that?
I think, you can treat both cases at once using Map.insertWith.

  return tree'

 insertProc was in my first message, and it's like this:
  insertProc :: Pid - StateT PsMap IO PsInfo
  insertProc pid = do
process - lift $ procInfo pid
psMap - get

delete above line, it's dead code, originally you did
psMap - get
put (Map.insert pid process psMap)

modify does both.

modify (Map.insert pid process)
return (process)

 At this point I'm not sure if this design is good or even correct.

I'm not sure what the design is, what's the role of PsMap and the PsTree, 
respectively?

 I'm mixing (StateT PsMap IO PsInfo) with (StateT PsMap IO PsTree), which I'm
 not sure I can do.

No problem :)

 There is probably a much cleaner way to do this but I
 cannot see through the types right now :/

 Anyone has any hints on how to make that scheme work?


Take a piece of paper and write down your intended algorithm. In that process, 
think about how to represent your data.
From that, much of the code becomes automatic (well, if you know the libraries 
better than I do, otherwise it's still a lot of searching the docs and 
looking what functions/data types are on offer).
It looks like a promising start, though it definitely needs some polishing.

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


[Haskell-cafe] Creating a type for a subset of the integers

2007-12-18 Thread Brad Larsen

Hi there list,

How would one go about creating a new type for a subset of the integers,  
for (contrived) example just the even integers?  I was thinking of making  
a new type


newtype EvenInt = EvenInt Integer

but the problem with this is that it accepts any integer, even odd ones.   
So to prevent this, the module does not export the constructor for  
it---rather, the module exports a function `mkEvenInt' that creates an  
EvenInt if the given value is acceptable or raises an error otherwise.



What's the right way to do this?  Thanks!


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


Re: [Haskell-cafe] New to Haskell: The End

2007-12-18 Thread Jonathan Cast

On 18 Dec 2007, at 7:28 AM, [EMAIL PROTECTED] wrote:


Concerning the subject: The End of WHAT?
Cristian Baboi writes:

Reinier Lamers wrote:

Cristian Baboi wrote:

Haskell strengts as I see them:

...

- it has a compiler

...

Is there anything you would like to add ?


Higher-order functions, purity, pattern-matching, no-nonsense  
syntax,  algebraic data types, ...
From your list, I agree to add some pattern matching abilities  
to mine,  but that it all.


Oh, it is anyway very generous of you. But tell me: do you  
*understand*

the remaining issues, notably the purity?

Jerzy Karczmarczuk

PS. For Henning T.: Don't worry, the slogan battle won't start  
again. The
discussion level is not appropriate. Although we can, of course,  
add to

this damned page the ad: people, use Haskell! It has a compiler!


Not a bad advantage --- Haskell is much faster than any mainstream  
language with a tenth its feature set.


Of course, so is any other language with a tenth its feature set, but  
I don't see how anyone using Scheme or ML is anymore a bad thing for  
Haskell...


jcc

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


Re: [Haskell-cafe] Creating a type for a subset of the integers

2007-12-18 Thread gwern0
On 2007.12.18 21:07:25 -0500, Brad Larsen [EMAIL PROTECTED] scribbled 0.6K 
characters:
 Hi there list,

 How would one go about creating a new type for a subset of the integers,
 for (contrived) example just the even integers?  I was thinking of making a
 new type

 newtype EvenInt = EvenInt Integer

 but the problem with this is that it accepts any integer, even odd ones.
 So to prevent this, the module does not export the constructor for
 it---rather, the module exports a function `mkEvenInt' that creates an
 EvenInt if the given value is acceptable or raises an error otherwise.

 What's the right way to do this?  Thanks!

 Brad Larsen

Well, I've had cause to do this in the past.

Before I paste the following code, I'd like to emphasize that I wrote it a 
while when I was even more new to Haskell; that it compiles but hasn't been 
tested very much; and that I'm sure there are better ways to do it.

What I wanted to do was to define a type for a subset of 'reals' (floats) which 
are either 0, or positive. The code looks like this:

 {- For many equations and results, it is nonsensical to have negative 
 results,  but we don't want
 to use solely natural numbers because then we lose precision. So we define a
 PosReal type which tries
 to define the subset of real numbers which are 0 or positive; this way the 
 type
 system checks for negative
 results instead of every other function having conditionals checking for
 negative input or output. -}
 newtype PosReal = MakePosReal Float deriving (Show, Eq, Ord)

 -- Basic numerical operations on positive reals
 instance Num PosReal where
 fromInteger = toPosReal . fromInteger
 x + y = MakePosReal (fromPosReal x + fromPosReal y)
 x - y = toPosReal ((fromPosReal x) - (fromPosReal y))
 x * y = MakePosReal (fromPosReal x * fromPosReal y)
 abs x | x = 0 = x
   | otherwise = x * (-1)
 signum x | x = 0 = 1
  | otherwise = (-1)

 -- Define division on PosReals
 instance Fractional PosReal where
 x / y = toPosReal ((fromPosReal x) / (fromPosReal y))
 fromRational x = MakePosReal (fromRational x)

 -- Positive reals are truncated at 0
 toPosReal :: Float - PosReal
 toPosReal x
 | x  0 = MakePosReal 0
 | otherwise = MakePosReal x
 fromPosReal :: PosReal - Float
 fromPosReal (MakePosReal i) = i

 -- Define an instance to allow QuickCheck operations
 instance Arbitrary PosReal where
 arbitrary = liftM3 fraction arbitrary arbitrary arbitrary
 where fraction :: Integer - Integer - Integer - PosReal
   fraction a b c = fromInteger a + (fromInteger b / (abs 
 (fromInteger c) + 1))


--
gwern
RFI el Audiotel muezzin E911 B61-11 Revolution 5.0i N5P6 espionage


pgpL1SXFCbylD.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Paul Hudak




Benja Fallenstein wrote:

  I mean, I reject the answer "They wanted it this way" because I think
the answer should be, "They wanted it this way because They looked at
substituting equals under a lambda, and They saw it was good" ;-)
  

Your version of the answer is in fact correct, but is just an
elaboration of the original one.
So, I don't see what your point is...


  
Sure, and I suppose one way to do this is to put the show function for
functions into the IO monad -- then you can't inspect the results.  But
if you want to inspect the result, then I have no idea how to do this.

  
  
If you can show and enumerate the argument type and show the result
type of a function, one way is to enumerate the graph of the function.
  

Yes, but this requires a STANDARD way to do this -- meaning that the
underlying domains are enumerable in a standard way. I don't think
that is always possible. And of course you may have an infinite graph,
whereas the function itself is finite.

Regarding the rest of your message: I don't see how this helps, since
some terms do not have head-normal forms. Even in the pure lambda
calculus there are terms that denote the same value but that are not
convertible to one another. It seems that at best this approach would
yield only partial success.

 -Paul


  The wiki page gives the example,

Prelude \x - x+x
functionFromGraph [(0,0), (1,2), (2,4), (3,6),
Interrupted.

If you have special compiler support, and consider a fragment of
Haskell that contains only functions -- i.e., no algebraic data types,
no Ints etc. (it's kind of a boring fragment!, but you can have Church
numbers) --, you can reduce the function to head normal form. Head
normal form looks like this:

\VAR1 VAR2 ... VARm - VARi EXPR1 ... EXPRn

and there is a reduction strategy that finds the head normal form of
an arbitrary _expression_ if there is one; a proof that if there isn't
one, the _expression_ denotes bottom; and a proof that if you have two
HNFs, and they differ in the part before EXPR1 or differ in the number
of EXPRjs, these HNFs denote different values.

Therefore, when you have reduced the function to HNF, you can print

"\VAR1 VAR2 ... VARm - VARi "

(or more precisely, you can write a lazy 'show' that yields the above
characters as soon as it has computed the HNF). Then, you go on to
recursively compute the HNF of EXPR1, and you show that inside
parantheses.

Some examples:

show (\x - x) == "\a - a"
show (.) == "\a b c - a (b c)"

(let fix f = f (fix f) in show fix)
== "\a - a (a (a (a (a.

[Unless I'm making some stupid mistake] It's well-established that
this is computable and doesn't break extensionality (i.e., that
applying this show to two functions with the same extension will give
the same result -- or conversely, if show gives different results for
two functions, there are arguments for which these functions yield
different results).

By itself, this isn't very interesting, but I *think* you should be
able to add algebraic data types and case expressions to this fragment
of Haskell and still do "essentially" the same thing. Then, you could
show, for example,

show either == "\a b c - case c of { Left d - a d; Right e - b e }"

- Benja
  




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


Re: [Haskell-cafe] Creating a type for a subset of the integers

2007-12-18 Thread Jules Bean

Brad Larsen wrote:

Hi there list,

How would one go about creating a new type for a subset of the integers, 
for (contrived) example just the even integers?  I was thinking of 
making a new type


newtype EvenInt = EvenInt Integer

but the problem with this is that it accepts any integer, even odd 
ones.  So to prevent this, the module does not export the constructor 
for it---rather, the module exports a function `mkEvenInt' that creates 
an EvenInt if the given value is acceptable or raises an error otherwise.



What's the right way to do this?  Thanks!


There are two ways:

(1) Have a representation which admits invalid values, and provide 
combinators which only perfect validity, and prove that consumers using 
your combinators can't produce invalid values.


(2) Have a cleverly designed representation such that every 
representation is valid.


An example here, for (2) would be to store n/2; there is a bijection 
between 'Integer' and 'EvenInt' given by n/2.


In real, more complex problems, (2) often isn't possible and we resort 
to (1). E.g. the representation of balanced trees (AVL? RedBlack?) 
admits invalid values (both unbalanced trees and out-of-order trees) and 
 we rely on the reduced set of combinators never to generate one.


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


Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Benja Fallenstein
Hi Paul,

On Dec 19, 2007 6:54 AM, Paul Hudak [EMAIL PROTECTED] wrote:
  Your version of the answer is in fact correct, but is just an elaboration
 of the original one.
  So, I don't see what your point is...

Ok, sorry, I'll try again... I'm trying to say that in my opinion,
it's important to include the elaboration if you want to give a
*useful* answer to why can't I print functions. :)

  If you can show and enumerate the argument type and show the result
 type of a function, one way is to enumerate the graph of the function.

  Yes, but this requires a STANDARD way to do this -- meaning that the
 underlying domains are enumerable in a standard way.  I don't think that is
 always possible.

It isn't always, no; in Haskell, there's no way to enumerate the
instances of (IO Int), for example. But of course, you can't show (IO
Int) in the first place, so I guess there's no expectation that you
should be able to show functions with (IO Int) arguments, either.

Function domains also aren't enumerable in general, although you could
simply enumerate all functions writable in Haskell, and not care about
duplicates. But it seems very unlikely anyway that printing
higher-order functions in this way would be *practical*.

 And of course you may have an infinite graph, whereas the
 function itself is finite.

(you mean that the function term is finite, I suppose) Yes, but you
can show infinite lists, too -- resulting in an infinite String being
returned by 'show.'

  Regarding the rest of your message: I don't see how this helps, since some
 terms do not have head-normal forms.

But these terms denote bottom. Compare (show (1:2:_|_)); the behavior
would be similar.

 Even in the pure lambda calculus there
 are terms that denote the same value but that are not convertible to one
 another.

Such terms would return the same *infinite* String in this approach.
You couldn't write a program to test whether they're equal; but you
can't write a program that tests whether two arbitrary infinite lists
are equal, either.

 It seems that at best this approach would yield only partial
 success.

Oh, that's certainly true, in the sense that showing functions in this
way would often not be as practical as one might hope for -- the worst
problem being that recursive functions will often have infinite
representations.

Still, in my opinion, there is a difference between the theory says
you can't show functions and from the theoretical perspective, there
is an elegant way to show functions, but it would be a lot of work to
implement and the result wouldn't be as practical as you're hoping
for. Although I admit it's more of a theoretical difference than a
practical one. :-)

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