[Haskell-cafe] RE: why isn't everything an instance of Data?

2006-06-16 Thread Ralf Lammel
Hi Frederik,
Cc Haskell-café as proposed by Frederik,

> Why isn't everything an instance of Data?
> 
> It seems natural to give every type which is defined via 'data' an
> automatic Data instance. This would make implementing many things much
> simpler. Certain types such as functions would only be able to have
> "stub" instances, for instance not allowing traversal of constructor
> arguments, but this would no more hurt the user than not having such
> instances defined in the first place. To clarify, what I am suggesting
> is that Data no longer be a class but an interface - one would be able
> to call 'toConstr' on any type.

[Ralf Lammel] 

I get your overall question but let me ask about one detail. When you say "an 
interface", what does this mean in the Haskell sense (where normally a 
type-class is like an OO interface *anyhow*)?

> Is there a fear that this would lead to "sloppy programming"?

[Ralf Lammel] 

I agree that it could be convenient to assume gfoldl and all that as true 
primitives. Personally, I wouldn't necessarily like that: Haskell's type system 
seems to be designed to (mostly) distinguish parametrically polymorphic 
functions from the rest; just as much as it (mostly) makes explicit any effects 
involved in a computation.

Also, how would these primitives need to be implemented? We would need a whole 
lot of type information in the sense of reflection to be around at run-time. 

> Also, it would be nice if it were possible to have the compiler infer,
> in a function such as
> 
> cast :: a -> Maybe b
> 
> that 'a' and 'b' are instances of the same classes. However, unless
> I'm mistaken this would require 'cast' to have special status with the
> compiler (or for there to be some new syntax allowing one to indicate
> that two type variables implement the same classes).

[Ralf Lammel] 

There are several problems here.

First, I doubt that we want to establish "that 'a' and 'b' are instances of the 
same classes". That sounds like a too special case. I guess we would want to 
establish that a given type instantiates a given type class.

Second, our new cast operation (which would indeed be very much like an OO 
down-cast) would need to be a special primitive indeed, including special 
syntax. If we had first-class type-classes, special syntax is not needed, but 
we would still need a primitive for the actual cast.

Third, we need to come up with some fairly tricky means of getting the 
dictionary for a type "out of the blue" at run-time. This would be sort of 
possible (certainly for monomorphic types) if we had the type of the 
value/expression around at run-time, so that we can use it to look up a 
dictionary from a global pool. However, that type is not available without 
extra effort.

To summarize, if this was the question, this expectation seems to lead pretty 
far away from what we have in Haskell and likely to get anywhere soon -- as far 
as I can tell.

> But without such
> inferences, the Generics stuff has limited usefulness - so much in
> Haskell is based on classes, but the only class one can use in the
> argument of say 'everywhere' is Data itself:
> 
> everywhere :: (forall a . Data a => a -> a) -> forall a . Data a => a -> a

[Ralf Lammel] 

There are two stories here:

a) Any type-specific case can make any amount of type-class assumptions even in 
the original SYB1 style. This gets you pretty far in practice.

b) If you want to write generic functions whose set of types is characterized 
by a designated type class, then you need to use SYB3 style.

HTH,
Ralf

PS: Some related stuff ...

- I uploaded a new SYB paper recently: http://www.cwi.nl/~ralf/syx/

- We also updated the SYB site to include other people's SYB papers: 
http://www.cs.vu.nl/boilerplate

- See Pablo Nogueira's paper "Context-Parametric Polykinded Types" for some 
interesting GH-related issues on type classes; 
http://www.cs.nott.ac.uk/~pni/Papers/ 

- Finally, I plan to use my new blog for Haskell-related stuff as well: 
http://blogs.msdn.com/ralflammel/ 

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


Re: [Haskell-cafe] Fibonacci numbers generator in Haskell

2006-06-16 Thread Doug Quale
Doug Quale <[EMAIL PROTECTED]> writes:

> Mathew Mills <[EMAIL PROTECTED]> writes:
> 
> > Is there anything that can be done (easily) to reduce the rounding errors?
> 
> The hint that I gave before is one easy way.
> 
> > fib :: Integer -> Integer
> > fib x = let phi = ( 1 + sqrt 5 ) / 2
> >  in truncate( ( 1 / sqrt 5 ) * ( phi ^ x + 0.5) )
> 
> You run out of precision eventually.  IEEE Double's give you about 15
> decimal digits, so the results become approximate for x > 75.

Sorry, I suffered brain lock.  The correct expression is parenthesized
differently:

> fib n = truncate(phi^n/sqrt 5 + 0.5)
>where phi = (1 + sqrt 5)/2
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] putStrLn

2006-06-16 Thread minh thu

you already know how to write "*" one ... so you just have to know how
to do it the neded amount :

two ways : 1/ you repeat the function
   2/ you reapet the data one which the function is applied.

this is like 2/

2006/6/16, J. Garrett Morris <[EMAIL PROTECTED]>:

main n = putStrLn (replicate n '*')

main n = putStrLn (take n (repeat '*'))


this is like 1/


main n = sequence (take n (repeat (putStr "*")))


in order to remove the interleaved '\n', just apply the trick (n-1)
times then one more for '\n'.


(but that doesn't have a final new line.  The more complicated:

main n = sequence (take (n - 1) (repeat (putStr "*"))) >> putStrLn "*"

should solve that problem.)


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


[Haskell-cafe] SMTP, HTTP, Telnet

2006-06-16 Thread Lyle Kopnicky




Hi all,

Anybody know of some good Haskell libraries providing:

  an SMTP client,
  an HTTP client,
  or a Telnet client?

There's a significant amount to these protocols, over and above the
socket layer.

Thanks,
Lyle Kopnicky



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


[Haskell-cafe] Inferring types from functional dependencies

2006-06-16 Thread Jeff . Harper

Thank you.  I followed your suggestion
and implemented my default Divide as you've shown below.

[EMAIL PROTECTED] wrote:
> If we assume that we need Reciprocate
only if we are going to use the 
> 'default' method, the solution becomes obvious. It does involve
> overlapping and undecidable instances, sorry. These extensions are
> really useful in practice. Here's the solution:
> 
> > class Divide a b c | a b -> c where
> >     (/) :: a -> b -> c
> 
> 
> Here's the most general instance. It applies when nothing more
> specific does.  It is in this case that we insist on being able
to
> take the reciprocal:
> 
> > instance (Reciprocate b recip, Multiply a recip c) =>
> >     Divide a b c where
> >     (/) x y = x * (recip y)

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


Re: [Haskell-cafe] putStrLn

2006-06-16 Thread J. Garrett Morris

main n = putStrLn (replicate n '*')

main n = putStrLn (take n (repeat '*'))

main n = sequence (take n (repeat (putStr "*")))

(but that doesn't have a final new line.  The more complicated:

main n = sequence (take (n - 1) (repeat (putStr "*"))) >> putStrLn "*"

should solve that problem.)

/g

On 6/16/06, Jenny678 <[EMAIL PROTECTED]> wrote:


Hello,

Can somebody help me

I want to work with putStrLn
main n = putStrLn "*"

for example
How must I define the code that:
>main 5
>*


Thanks for any help
--
View this message in context: 
http://www.nabble.com/putStrLn-t1799896.html#a4905456
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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




--
We have lingered in the chambers of the sea 
By sea-girls wreathed with seaweed red and brown
Till human voices wake us, and we drown.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] putStrLn

2006-06-16 Thread Jenny678

Hello,

Can somebody help me

I want to work with putStrLn
main n = putStrLn "*"

for example 
How must I define the code that:
>main 5
>*


Thanks for any help
--
View this message in context: 
http://www.nabble.com/putStrLn-t1799896.html#a4905456
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


Re: [Haskell-cafe] Fibonacci numbers generator in Haskell

2006-06-16 Thread Jon Fairbairn
On 2006-06-15 at 17:33BST "Vladimir Portnykh" wrote:
> Fibonacci numbers implementations in Haskell one of the classical examples. 
> An example I found is the following:
> 
> fibs :: [Int]
> fibs = 0 : 1 : [ a + b | (a, b) <- zip fibs (tail fibs)]
> 
> Can we do better?

Well, you've had various variously sensible responses, so
here's one with /worse/ space performance (but a degree of
cuteness):

   module Main where
  import InfiniteMap

  fib = memo fib'
  where fib' fib 0 = 0
fib' fib 1 = 1
fib' fib n = fib (n-1) + fib (n-2)

  memo f = f memf
   where memf n = locate n m
 m = build $ f memf
---
   module InfiniteMap where
  data IM t = Node {entry:: t, if_even::IM t, if_odd:: IM t}

  build f = Node (f 0)
 (build $ f . (*2))
 (build $ f . (+1) . (*2))

  locate 0 (Node e _ _) = e
  locate n (Node _ e o)
 | even n = locate (n`div`2) e
 | otherwise = locate ((n-1)`div`2) o


-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


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


Re: [Haskell-cafe] Fibonacci numbers generator in Haskell

2006-06-16 Thread Doug Quale
Mathew Mills <[EMAIL PROTECTED]> writes:

> Is there anything that can be done (easily) to reduce the rounding errors?

The hint that I gave before is one easy way.

> fib :: Integer -> Integer
> fib x = let phi = ( 1 + sqrt 5 ) / 2
>  in truncate( ( 1 / sqrt 5 ) * ( phi ^ x + 0.5) )

You run out of precision eventually.  IEEE Double's give you about 15
decimal digits, so the results become approximate for x > 75.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fibonacci numbers generator in Haskell

2006-06-16 Thread Chris Kuklewicz

Chris Kuklewicz wrote:

Mathew Mills wrote:

I guess I don't get any points for an approximate solution, ay?

Is there anything that can be done (easily) to reduce the rounding 
errors?




http://www.google.com/search?q=haskell+exact+real+arithmetic



Using Era.hs (with the patch at 
http://www.haskell.org/hawiki/ExactRealArithmetic) and add spaces around 1%n to 
1 % n (since I have -fglasgow-exts turned on and %n looks like a linear implicit 
thingie).



Now this works:


fib x = let phi,phi' :: CR
phi = (1 + sqrt 5) /2
phi' = (1 - sqrt 5)/2
in  truncate ( recip (sqrt 5) * (phi^x -phi'^x))


*Era> fib 100
354224848179261915075

which is the (allegedly) correct answer.


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


Re: [Haskell-cafe] Fibonacci numbers generator in Haskell

2006-06-16 Thread Chris Kuklewicz

Mathew Mills wrote:

I guess I don't get any points for an approximate solution, ay?

Is there anything that can be done (easily) to reduce the rounding errors?



http://www.google.com/search?q=haskell+exact+real+arithmetic

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


Re: [Haskell-cafe] Fibonacci numbers generator in Haskell

2006-06-16 Thread Mathew Mills
I guess I don't get any points for an approximate solution, ay?

Is there anything that can be done (easily) to reduce the rounding errors?


On 6/15/06 11:23 PM, "[EMAIL PROTECTED]" <[EMAIL PROTECTED]> wrote:

> G'day all.
> 
> Quoting Mathew Mills <[EMAIL PROTECTED]>:
> 
>> How about the closed form ;)
>> 
>>> -- fib x returns the x'th number in the fib sequence
>> 
>>> fib :: Integer -> Integer
>> 
>>> fib x = let phi = ( 1 + sqrt 5 ) / 2
>> 
>>> in truncate( ( 1 / sqrt 5 ) * ( phi ^ x - phi' ^ x ) )
>> 
>> 
>> Seems pretty quick to me, even with sqrt and arbitrarily large numbers.
> 
> I called my version "fib" and your version "fib2".  I get:
> 
> *Fib> [ i | i <- [30..100], fib i == fib2 i ]
> [32,35,43,46,51,71]
> 
> Yes, the closed form is faster.  But if, as part of the rules, one
> is allowed to give wrong answers, it's not difficult to write a
> function that's even faster than this.
> 
> Cheers,
> Andrew Bromage
> ___
> 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] Fibonacci numbers generator in Haskell

2006-06-16 Thread Ronny Wichers Schreur

Spencer Janssen writes (in the Haskell Cafe):


Here's some code I wrote a while back for computing the nth Fibonacci
number.  It has O(log n) time complexity [..]


The nth Fibonacci number has O(n) digits.


Cheers,

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


Re[4]: [Haskell-cafe] what do you think of haskell ? (yes, it's a bit general ...:)

2006-06-16 Thread Bulat Ziganshin
Hello minh,

Friday, June 16, 2006, 10:20:24 AM, you wrote:

> well, you're right, i've a bit to overemphased the learning difficulty..
> but, last time i tried to use your lib, i missed some other libraries
> (win32 for one ? .. i dont remember).

if it was with Streams 0.1e, just remove "win32" from cabal file

.. or better download www.haskell.org/library/Streams.tar.gz and try
it - i hope that i fixed this problem


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Rotating matrices

2006-06-16 Thread David House

On 15/06/06, Stefan Holdermans <[EMAIL PROTECTED]> wrote:

   transpose = foldr (zipWith (:)) (repeat [])


While one-liners like this are very pretty, it's worth thinking about
how they work:

1. (:) takes an element and a list and prepends that element to the list.
2. zipWith (:) takes a list of elements and a list of lists and
prepends each element to its corresponding list.
3. repeat [] is the infinite list [[], [], [], [], ... ], i.e. the
infinite list of empty lists.
4. transpose, therfore, takes the last list in your list-of-lists
input, then prepends each element of it to the empty list. That is, if
the last list in the input was [x1, x2, ..., xn] then it produces
[[x1], [x2], ..., [xn]].
5. Then this is repeated with the penultimate list in the input (say
its elements are y1..yn), giving [[y1, x1], [y2, x2], ..., [yn, xn]]
6. And so on down the input list.

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