Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-30 Thread Ketil Malde
On Tue, 2007-05-29 at 21:28 +0100, Andrew Coppin wrote:

> > phantom types:
> >  the types of ghost values (in other words, we are only interested in
> >  the type, not in any value of that type).

> Mmm... Still not seeing a great amount of use for this one.

The point is to 'tag' something with a type (at compile time) without
actually having any value of that type around at run time.

For instance, you could use this to keep track of the encodings for
strings of 8-bit characters.

Say you have a data type for your strings, like so:

data FPS enc = FPS [Word8] deriving Show

'enc' is now a phantom type, it has no bearing on the actual value,
which is always a list of Word8s, right?

You can then define a set of encoding data types, and class for them:

data Latin1
data KOI8R

class Encoding e where
   w2c :: e -> Word8 -> Char
   c2w :: e -> Char  -> Word8

The Latin1 instance is easy:

instance Encoding Latin1 where
   w2c _ = chr . fromIntegral
   c2w _ = fromIntegral . ord

KOI8 is a bit more involved, so I omit that.  Now we can define
functions for converting to/from [Char]:

pack :: forall e . Encoding e => String -> FPS e
pack = FPS . map (c2w (undefined :: e))

unpack :: forall e . Encoding e => FPS e -> String 
unpack (FPS s) = map (w2c (undefined :: e)) s

Loading this in GHCi (requires -fglasgow-exts), you can do:

*Main> pack "foobar"  :: FPS Latin1
FPS [102,111,111,98,97,114]

i.e. ord 'f' to ord 'r'.

*Main> pack "foobar"  :: FPS KOI8R
FPS [202,211,211,198,197,214]

This is a fake KOI8R instance, but demonstrates the point: by requiring
a different type, a different result is achieved.  Note that the
resulting FPS retains the type, so that when I do:

*Main> unpack it
"foobar"

...I get back the original string.

Disclaimers: There are more elaborate and elegant examples of phantom
types out there, look for e.g. Oleg's posts on the subject.  The above
does not constitute legal advice.  Slippery when wet, do not cover,
batteries not included, and your mileage may vary.

-k




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


Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Ketil Malde
On Tue, 2007-05-29 at 21:39 +0100, Andrew Coppin wrote:

> My point is for most programs, trying to figure out exactly what you 
> want the program to do is going to be much harder than implementing a 
> program that does it.

And the solution is..to not say anything about what the program should
do? :-)

> Also, for most programs the spec is far more complicated (and hence 
> prone to error) than the actual program, so...

Since the program *is* a (complete) specification of itself, a
specification need not be any longer or more complicated than the
program.

Realistically, I think it is good practice to specify explicit type
signatures and quickcheck properties (or similar unit tests).  The
advantage over other documentation, is that they are verified or tested
(respectively) against the actual code.

The code itself explains "how", type signatures and unit tests explain
"what", which leaves only "why" to comments.

-k

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


Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Tomasz Zielonka
On Tue, May 29, 2007 at 09:43:03PM +0100, Andrew Coppin wrote:
> Henning Thielemann wrote:
> >On Sun, 27 May 2007, Andrew Coppin wrote:
> >>But every now and then I discover an expression which is apparently not
> >>expressible without them - which is odd, considering they're only
> >>"sugar"...
> >
> >Example?
> 
> Until I learned the trick of using lists as monads, I was utterly 
> perplexed as to how to get a Cartesian product

This is far from not expressible:
cart xs ys = concatMap (\x -> map ((,) x) ys) xs

> or why there's no library function to do this!

sequence?

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


Re: [Haskell-cafe] The C Equiv of != in Haskell miscommunication thread

2007-05-30 Thread Vincent Kraeutler
i would just like to say thank you for all the extensive replies. after
fiddling with them for an afternoon i'm positive i grokked the concept.

it's just too bad the nice wrapper concept from [1] does not seem to be
directly applicable to fix in haskell, since they require untyped
side-effects

anyhow, this has been very instructive.
thanks again!
v.

[1] http://citeseer.ist.psu.edu/mcadams01practical.html

Jason Dagit wrote:
> On 5/28/07, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote:
>> This thread should end, guys. It is inappropriate for the Haskell lists,
>> and appears to have been a simple misunderstanding anyway.
>>
>> Thanks everyone. Please stay friendly!
>>
>> -- Don
>>
>> P.S. Have some cute code:
>>
>> Control.Monad.Fix.fix ((1:) . scanl (+) 1)
>
> Speaking of cute code, I'm fond of this:
>
> map length . List.group . Control.Monad.Fix.fix $ show
>
> And other (longer) variations which generate only powers of two.  It's
> a great conversation starter for teaching about fix.
>
> Jason
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>




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


Re: [Haskell-cafe] The C Equiv of != in Haskell miscommunication thread

2007-05-30 Thread Tomasz Zielonka
On Tue, May 29, 2007 at 06:40:05PM -0700, Jason Dagit wrote:
> Speaking of cute code, I'm fond of this:
> 
> map length . List.group . Control.Monad.Fix.fix $ show

"fix show" is cool in itself! :-)

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


[Haskell-cafe] Is there a Template lib like Cheetah in python?

2007-05-30 Thread Albert Lee

I am writing some webpage using haskell, I know Xhtml, but I also need some
other persons to write simple htmls
so I need a template system like cheetah in python, but I didn't find
anything through google. any help?

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


[Haskell-cafe] Re: Language extensions

2007-05-30 Thread apfelmus
Ketil Malde wrote:
> On Tue, 2007-05-29 at 21:39 +0100, Andrew Coppin wrote:
>> Also, for most programs the spec is far more complicated (and hence 
>> prone to error) than the actual program, so...
> 
> Since the program *is* a (complete) specification of itself, a
> specification need not be any longer or more complicated than the
> program.

Almost. A program usually specifies too much, namely how a problem is
solved, not only that it's solved. But in 20-30 years when the
Curry-Howards isomorphism rules the world, the types *are* the
specification and the compiler won't accept anything that doesn't match
them. Dependent types for world-domination! :)

Regards,
apfelmus

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


Re: [Haskell-cafe] Is there a Template lib like Cheetah in python?

2007-05-30 Thread Johan Tibell

I've been planning to write a web templating system for a while now
but I haven't gotten around to it yet. I did write a small string
templating library that works like Python's string.Template but it's
probably not what you need. Here it is anyway:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/template-0.1

Cheers,

Johan

On 5/30/07, Albert Lee <[EMAIL PROTECTED]> wrote:

I am writing some webpage using haskell, I know Xhtml, but I also need some
other persons to write simple htmls
so I need a template system like cheetah in python, but I didn't find
anything through google. any help?

--
http://www.kamang.net
___
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] Language extensions

2007-05-30 Thread Dougal Stanton

On 28/05/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:

Then again, later on in the very same book there's a chapter entitled
"Fun with Phantom Types", which made precisely no sense at all...

(I find this a lot with Haskell. There is stuff that is clearly written,
fairly easily comprehensible, and extremely interesting. And then
there's stuff that no matter how many times you read it, it just makes
no sense at all. I'm not sure exactly why that is.)


Agreed, that does seem to happen a lot. I was utterly baffled by the
chapter on functors in HSE. It wasn't until I spent a rainy weekend on
my own in Aberdeen (harsh, I know) that I read the chapter enough
times to figure what it actually meant.

Of course at that point I thought it was fabulous and wanted to tell
someone. But I was still alone in the greyest city on Earth...

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


Re: [Haskell-cafe] More on the random idea

2007-05-30 Thread Duncan Coutts
On Mon, 2007-05-28 at 20:14 +0100, Andrew Coppin wrote:

> > You looked at the source to GHCi itself I presume? It uses the GHC API,
> > so it's a good place to start with building a variant of GHCi that uses
> > the GHC API :-)
> >   
> 
> No. Actually, as per the wiki, I was looking at the source code to the 
> GHC API. (Apparently there isn't even any Haddock docs, despite the 
> requisit comments existing in the source...)

Yes, it'd be nice to have haddock docs for it.

> I suppose I could have looked at the source for GHCi - but again I would 
> imagine it's littered with error checking and other user-friendliness, 
> rather than being written to be clearly readable by beginner hackers. ;-)

I suppose that's probably right. A minimal read-eval loop as a way of
seeing how to use the ghc api would be nice.

> (Also... presumably I'd have to download some giant tarball and work out 
> how to open it. And then find the source code for GHCi amoungst 
> everything else.)

It's not that scary :-)

http://darcs.haskell.org/ghc/compiler/ghci/


Duncan

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


Re: [Haskell-cafe] Distributing a program with support files

2007-05-30 Thread Duncan Coutts
On Mon, 2007-05-28 at 20:35 +0100, Neil Mitchell wrote:
> Hi Duncan,
> 
> > list the support files in the "data-files:" stanza in the .cabal file.
> > Then import the Paths_ module that Cabal generates for you. It
> > exports a few functions including:
> >
> >   getDataDir :: IO FilePath
> 
> A few questions:
> 
> 1) How do I test this? I'll need to develop in Hugs and GHC without
> going through Cabal building. Should I fake up a Paths_ module?

Or just use cabal and copy the .hs module it generates.

> 2) Is there any reasonable limit on the number of data files? Is 1000 too 
> many?

They have to be listed in the .cabal file, so you might get bored adding
them all and decide to send in a patch to support glob/wildcards :-)

> 3) Can I create files in this DataDir directory?

Probably not necessarily. For example if under unix you install the
package globally then the data dir will probably be in some read-only
directory under /usr/share. If it's a per-user install it might be
writable. For per-user writable stuff you probably want
getAppUserDataDirectory from System.Directory.

> It does seem that creating a new Paths_ module and include it is
> not very pleasant. It requires everyone to compile from source to get
> the paths working, which doesn't make much sense.

As Isaac mentioned, on windows it is relocatable I think. You can see
the code than Cabal generates. If you want patches so it'll work with
yhc without using #ifdefs and using dynamic tests instead then I'm happy
to look at patches that do that. This isn't set in stone and if you have
better general workable solutions then do suggest them.

Duncan

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


Re: [Haskell-cafe] The C Equiv of != in Haskell miscommunication thread

2007-05-30 Thread Roberto Zunino

Jason Dagit wrote:

On 5/28/07, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote:

P.S. Have some cute code:

Control.Monad.Fix.fix ((1:) . scanl (+) 1)


Speaking of cute code, I'm fond of this:

map length . List.group . Control.Monad.Fix.fix $ show


Indeed, very nice examples!

I actually misread the first one as

Control.Monad.Fix.fix ((1:) . tail . scanl (+) 1)

which is quite nice too, although

map (2^) [0..]

would be much simpler! ;-)

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


[Haskell-cafe] Re: Shared libraries in GHC

2007-05-30 Thread Simon Marlow

Georg Sauthoff wrote:


while searching, if ghc can create packages as shared libraries I found
a ticket with a kind of non-accepted status:
http://hackage.haskell.org/trac/summer-of-code/ticket/46

But at the google SoC page it looks like an accepted project:
http://code.google.com/soc/haskell/appinfo.html?csaid=D0137F8B637176F1

Well what is the status of the project? Does the student have a
blog/webpage where one can track the progress of the project?

Btw, the problem I want to solve with shared libraries is the case,
where I want to program 2 frontends (==2 executables), which share a lot
of Haskell-Code. I am afraid, if both frontends are linked statically,
the result will look a bit 'bloated' ...


Yes, Clemens Fruhwirth is working on shared libraries for GHC in the summer of 
code.  Some of the work has already been done, he'll be fixing up the bits that 
don't work and polishing it all for inclusion in a future release (probably not 
6.8, but we'll see).


There should be a wiki page with progress and work plan up soon, we'll post 
details when that's ready.


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


Resolved: [Haskell-cafe] ffi linking problem

2007-05-30 Thread jeff p

Hello,

 In case anyone else finds this useful...

 My linking problem was finally resolved by using the -fvia-C flag
when compiling with ghc.

Thanks to Stefan O'Rear who pointed out the possibility and wrote:


Does using -fvia-C help at all?  The C compiler understands header
files and is sometimes better equipped to resolve things.



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


Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Jules Bean

Andrew Coppin wrote:
My point is for most programs, trying to figure out exactly what you 
want the program to do is going to be much harder than implementing a 
program that does it.


Also, for most programs the spec is far more complicated (and hence 
prone to error) than the actual program, so...


If you can't figure out exactly what the program is supposed to do, then 
your program clearly can't do it. So your program is buggy. Or, you got 
it precisely right, by chance, despite your ignorance. That's unlikely.


Most existing programs are in this category: unspecified, and hence buggy.

It *is* hard to work out *exactly* what a program should do. It's 
important though. If you don't do it, then no one knows what your 
program does...


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


Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Henning Thielemann

On Tue, 29 May 2007, Andrew Coppin wrote:

> OTOH, how many function can you write with :: [Int] -> Int? I can think
> of a few...

You will probably more like to implement functions like
  Ord a => [a] -> a
  Num a => [a] -> a
 and those generalized signatures tell you more. :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: More on the random idea

2007-05-30 Thread Simon Marlow

Duncan Coutts wrote:

On Mon, 2007-05-28 at 20:14 +0100, Andrew Coppin wrote:


You looked at the source to GHCi itself I presume? It uses the GHC API,
so it's a good place to start with building a variant of GHCi that uses
the GHC API :-)
  
No. Actually, as per the wiki, I was looking at the source code to the 
GHC API. (Apparently there isn't even any Haddock docs, despite the 
requisit comments existing in the source...)


Yes, it'd be nice to have haddock docs for it.

I suppose I could have looked at the source for GHCi - but again I would 
imagine it's littered with error checking and other user-friendliness, 
rather than being written to be clearly readable by beginner hackers. ;-)


I suppose that's probably right. A minimal read-eval loop as a way of
seeing how to use the ghc api would be nice.

(Also... presumably I'd have to download some giant tarball and work out 
how to open it. And then find the source code for GHCi amoungst 
everything else.)


It's not that scary :-)

http://darcs.haskell.org/ghc/compiler/ghci/


BTW, you want to look at InteractiveUI.hs and GhciMonad.hs.  The rest of the 
files in that directory belong to the implementation of the bytecode compiler, 
and hence are *below* the GHC API.  One day we'll reorganise the sources to make 
this clearer.


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


Re: [Haskell-cafe] Efficiency question

2007-05-30 Thread Henning Thielemann

On Sun, 27 May 2007, Evil Bro wrote:

> I'm pretty new to Haskell, so forgive me if my question is due to my
> non-functional way of thinking...
>
> I have the following code:

Counting can be done elegantly by 'filter' and 'length':

length $ filter (>1) $ Monad.liftM2 gcd [2..1000] [2..1000]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: More on the random idea

2007-05-30 Thread Simon Marlow

Stefan O'Rear wrote:

On Sat, May 26, 2007 at 07:41:19PM +0100, Andrew Coppin wrote:

Donald Bruce Stewart wrote:

The #haskell people have been working on this for about 3 years now.
The result is the 'runplugs' program, which I've talked about in
previous mails.

   http://www.cse.unsw.edu.au/~dons/code/lambdabot/scripts/RunPlugs.hs

It uses hs-plugins for the evaluation, along with the points about IO
prevention via type checking, resource limits controlled by the OS, 
language extension preventions, and a trusted (audited) module base.


The security mechanisms were briefly described in the 2004 hs-plugins
paper, if I recall, but otherwise, I don't think we've documented the 
techniques. Maybe we should, as many issues have been encountered over

the years, further and further constraining the kinds of things that are
allowed.
 
For me, the unfortunate thing is that there seems to be no interpreter 
for Haskell written in Haskell. (Except for GHC, which is *huge*.) We


Actually, there exists no interpreter for Haskell.  Period.


Historical note: the first implementation of GHCi (by Alastair Reid) was a pure 
interpreter, IIRC.  The second implementation, which was the predecessor to the 
current implementation, was also a pure interpreter, but we rewrote it to use a 
bytecode compiler/interpreter before it was ever released.  The development 
history is all in darcs, if you care to take a look..


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


Re: [Haskell-cafe] Efficiency question

2007-05-30 Thread Evil Bro

> Counting can be done elegantly by 'filter' and 'length':
I figured out the following code after posting:

solve d = length [(y,x) | x <- [2..d], y <- [1..(x-1)], gcd x y == 1]
main = print (solve 100)

However when running it, it gave an answer of -1255316543. How on earth can
a length be negative?

> length $ filter (>1) $ Monad.liftM2 gcd [2..1000] [2..1000]
Thanks... now I'll just have to figure out what it does and why it does what
it does.


-- 
View this message in context: 
http://www.nabble.com/Efficiency-question-tf3823154.html#a10873232
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


[Haskell-cafe] Re: System.Timeout problems

2007-05-30 Thread Simon Marlow

Neil Mitchell wrote:

Hi

I'm using the System.Timeout module from base, copied into my local
repo, so that I can work with GHC 6.6.1. My copy is at:
http://www.cs.york.ac.uk/fp/darcs/catch/catch_1/System/TimeoutGHC.hs
(but it is identical to the one in base)

Sadly, it doesn't seem to work for me. Here are the tests I've been
using, the results I get, and what I would have liked. All are GHC 6.6
on Windows.

-- TEST 1
import System.TimeoutGHC

main :: IO ()
main = do
   r <- timeout (5 * 10^6) (putStrLn "here")
   print r

Without -threaded:
here >> Just () >> wait 5 seconds

Without -threaded:
here >> wait 5 seconds >> Just ()

So, either way, I get a 5 second delay - not something I want.


I think you're using GHC 6.6, right?  6.6.1 with -threaded has a new 
implementation of threadDelay on Windows that eliminates the final 5 second 
wait.  The problem was that threadDelay used to spawn a new OS thread to do the 
sleep, and the RTS would refuse to shut down until all the threads had finished 
(the latter requirement was introduced to fix bug with DLL shutdown, grrr).  We 
still have a similar bug that affects I/O: 
http://hackage.haskell.org/trac/ghc/ticket/1177


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


[Haskell-cafe] Re: Memoization

2007-05-30 Thread Simon Marlow

Rodrigo Queiro wrote:
sorear pointed me to this paper a while ago: 
http://citeseer.ist.psu.edu/peytonjones99stretching.html


I never tried any of the code in the end, but it will probably be useful?


An implementation of that memo table scheme can be found here:

http://darcs.haskell.org/testsuite/tests/ghc-regress/lib/should_run/Memo.lhs

It's probably too slow for general use, though.  You might find it useful if 
your keys are huge (or infinite) and comparing them directly is impractical.


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


Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Tomasz Zielonka
On Wed, May 30, 2007 at 02:35:38PM +0200, Henning Thielemann wrote:
> 
> On Tue, 29 May 2007, Andrew Coppin wrote:
> 
> > OTOH, how many function can you write with :: [Int] -> Int? I can think
> > of a few...
> 
> You will probably more like to implement functions like
>   Ord a => [a] -> a
>   Num a => [a] -> a
>  and those generalized signatures tell you more. :-)

Nice observation! Let's see what these types guarantee...

In the Ord variant, the result value pretty much has to come from the
input list or be bottom. It has to be bottom for the empty list. If
f :: Ord a => [a] -> a and g preserves order (is monotonic) then
f (map g l) == g (f l)
This could be nice for testing Ord instances. Unfortunately, for bounded
types the only order preserving function is id.

In Num variant, the result for the empty list with be an integer (or
bottom), no matter what type is 'a'.

All this assuming 'a' has sane Num and Ord instances.

More ideas?

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


Re: [Haskell-cafe] Re: Frisby grammars that have context

2007-05-30 Thread Jan-Willem Maessen


On May 29, 2007, at 10:44 AM, apfelmus wrote:


Mark T.B. Carroll wrote:
I've been playing with Text.Parsers.Frisby to see how it stacks  
against

other options and, while it's been great so far, I am finding that I
can't encode a grammar where what's acceptable depends on what's  
already

been parsed in some nontrivial way.
[...]
Is this supposed to not be possible in Frisby, or (quite likely) am I
missing something that allows me to?


It's intentionally impossible. Frisby uses a dynamic programming
approach that crucially depends on the fact that the grammar in  
question

is context-free (actually something related, but the effect is the
same). You're trying to parse a context-sensitive language.


Interestingly, Rats (a packrat-based parser generator for Java)  
permits you to insert arbitrary boolean conditions into the grammar;  
if the test fails, we simply record this as "parsing this nonterminal  
failed" in the memo table, I believe.  So I believe it'd actually  
feasible to incorporate some of the checking you're looking for into  
Frisby.  Of course, as others point out, you can always generate  
grammar fragments up front if you have a fixed set of things you're  
looking for in any given program run (something a parser tool like  
Rats isn't capable of---though with its parametric module system Rats  
can come *very* close, doing multiple compile-time instantiations of  
grammar fragments).


Packrat parsing, by the way, has made it vastly easier to structure  
and maintain a grammar for a highly ambiguous, hard-to-parse language  
(Fortress).  I recommend it.



Sometimes, you can avoid context-sensitivity if there's a way to parse
the token in question regardless of whether it's valid. For example,
Pascal is a context-sensitive language because you may not use a
variable before it has been declared:

  procedure Foo(x:Integer)
  begin
y := 1;
  end;

This not a correct Pascal program, nevertheless the parse succeeds  
just

fine. ...


I'm pretty sure predicates in the grammar would let you catch this  
error at parse time (if you maintained a symbol table and looked up  
expression occurrences in it as you parsed).  That said, I wouldn't  
necessarily try to structure my parser that way.


-Jan-Willem Maessen


smime.p7s
Description: S/MIME cryptographic signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Darcs users [was: New book: Real-World Haskell!]

2007-05-30 Thread Laurent Deniau

Jon Harrop wrote:

On Wednesday 30 May 2007 06:58:36 Ketil Malde wrote:

On Tue, 2007-05-29 at 14:05 -0500, Doug Kirk wrote:

I *want* people (and companies) to move to Haskell


As a complete noob considering making a commercial venture into
Haskell, may I ask what people's opinions are on this? Are there many
Haskell products?

Our expertise is in scientific, numerical and graphical computing.
Our product catalog should elucidate this:

http://www.ffconsultancy.com/products/

I'd like to know how feasible it would be to rewrite some of these
products in Haskell. For example, our time-frequency add-on for
Mathematica might sell a lot better if it were a standalone
cross-platform GUI application or even a web application. Is it
feasible to write such a thing in Haskell? Are any core Haskell
libraries non-free for commercial use?

Also, would anyone be interested in a Haskell for Scientists book,
following our OCaml for Scientists and forthcoming F# for Scientists
books?


I didn't read these books but I would if one exists on Haskell. But
I expect that you will first have to convince scientists that Haskell 
can be efficient in numerical analysis (both memory and speed). My guess 
is that it can be efficient if missing efficient data structures are 
provided. This has been solved for strings so I guess it can be done for 
other data structures as well but it seems to be a huge work. If the 
target is only to wrap the GSL or equivalent, then I expect that it will 
only be considered as a curiosity.


a+, ld.

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


Re: [Haskell-cafe] Re: Frisby grammars that have context

2007-05-30 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Robin Green wrote:
> On Tue, 29 May 2007 19:28:02 -0400
> Isaac Dupree <[EMAIL PROTECTED]> wrote:
>> Luckily, Haskell's laziness means that doing an extra "postprocessing
>> pass" doesn't necessarily yield two traversals requiring the whole
>> file to be stored in memory, nor worse hacks.  (For grammars that
>> aren't too wild / sequential)
> 
> But the suggested code fragment on the frisby homepage:
> 
>   -- parse complete file, returning 'Nothing' if parse fails
>   fmap Just (myParser <<- eof) // unit Nothing
> 
> does require one traversal of the file all by itself. Obviously, in
> order to know whether the file was fully parsed without error, you need
> to read in the whole file, before you can write out anything. Hence
> you end up with *some* representation of the whole file in memory. So,
> yes, it doesn't necessarily yield two traversals, but you need to be
> careful if you want to avoid two traversals.

Yes, then the choices are being failable (using something like "error",
or whatever happens if you don't wrap your parser as suggested)
or better yet, a careful lazy datatype like
data ListOutput a = Nil | Cons a (ListOutput a) | Error (ErrorInfo)

Isaac
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGXXryHgcxvIWYTTURAnEeAJ9PrQUQLxeoTuIhaG8GcHW5mN6T4QCeL6FT
KCQeF43ye/GzLka4zFUK66s=
=y7MZ
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficiency question

2007-05-30 Thread Bertram Felgenhauer
Evil Bro wrote:
> 
> > Counting can be done elegantly by 'filter' and 'length':
> I figured out the following code after posting:
> 
> solve d = length [(y,x) | x <- [2..d], y <- [1..(x-1)], gcd x y == 1]
> main = print (solve 100)
> 
> However when running it, it gave an answer of -1255316543. How on earth can
> a length be negative?

Yu got an integer overflow - length returns an Int. You can use
Data.List.genericLength  instead, however, which can return its
result in any Num instance. (In particular, Integer works)

> import Data.List
> 
> solve :: Integer -> Integer
> solve d = genericLength [(y,x) | x <- [2..d], y <- [1..(x-1)], gcd x y == 1]
> 
> main = print (solve 100)

(Note: untested.)

HTH,

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


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-30 Thread Claus Reinke



quantified types (forall/exist):
 an easy way to memorize this is to think of 'forall' as a big 'and'
 and of 'exists' as a big 'or'.
   e :: forall a. a  -- e has type 'Int' and type 'Bool' and type ..
   e :: exists a. a  -- e has type 'Int' or  type 'Bool' or  type ..


That doesn't entirely make sense. (What am I on about? That doesn't 
make *any* sense...)


indeed?-) then you've probably already figured out what those types
mean! there aren't many variations of an expression that has *all* types
("you can't please everyone"), and if an expression has a type but we
have no way of knowing what that type is, there isn't much we can do
with it (like advice from the Oracle of Delphi).  but both of these
kinds of quantified types make a lot more sense in larger contexts. 


lets take 'forall'/'big and' first: the problem with 'forall a. a' is to
produce something that is everything to everyone, which is rather hard;
but what about 'forall a. a -> a'? that is like a general shipping
agency - they don't care what you give them, they just put it in a box
and move it from one place to another (if it doesn't like to be shipped
in such an indifferent way, it'll break, but that's not their problem);
such general shipping is both 'Integer' shipping *and* 'String' shipping
*and* ..; other examples are 'forall a. a -> a -> a', which is a general
selector (given two 'a's, it returns one of them), or 
'forall a,b. a -> b -> a' (given an 'a' and a 'b', it returns the 'a').


'id :: forall a. a -> a' can be instantiated to 'id :: Bool -> Bool'
*and* to 'id :: Char -> Char' *and* to all other identities on rank-1
types besides, so one could say that it really has *all* of those types.

what about 'exists'/'big or' then? the problem with 'exists a. a' is
that while we know there exists a type, we have no way of knowing 
what that type is, so we can't really do anything with an expression 
of such a type. 


that is very much like an abstract data type, implemented on top
of a hidden representation type. what we need are some operations 
on that abstract type, so how about 


   'exists r.(r a, r a -> a -> r a, r a -> a)'

we still don't know what 'r' is, but we have some 'r a', we have a way
to combine 'r a' and 'a' into a new 'r a', and a way to extract an 'a'
from an 'r a', so we're no longer entirely helpless. in fact, that looks
a lot like an abstract container type, perhaps a stack with push and
top, or a queue with add and front, or a cell with put and get. 
whatever it may be, the 'r' is hidden, so it could be 

   '([a], [a]->a->[a], [a]->a)' 

*or* it could be 

   '(Set a, Set a -> a -> Set a, Set a -> a)' 


*or* it could be based on *any* other rank-1 type constructor.

hth,
claus

oracle advice: 'invade :: exists great_empire. great_empire -> ()'



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


Re: [Haskell-cafe] Memoization

2007-05-30 Thread Creighton Hogg

On 5/26/07, Mark Engelberg <[EMAIL PROTECTED]> wrote:


I'd like to write a memoization utility.  Ideally, it would look
something like this:

memoize :: (a->b) -> (a->b)

memoize f gives you back a function that maintains a cache of
previously computed values, so that subsequent calls with the same
input will be faster.

I've searched the web for memoization examples in Haskell, and all the
examples use the trick of storing cached values in a lazy list.  This
only works for certain types of functions, and I'm looking for a more
general solution.

In other languages, one would maintain the cache in some sort of
mutable map.  Even better, in many languages you can "rebind" the name
of the function to the memoized version, so recursive functions can be
memoized without altering the body of the function.

I don't see any elegant way to do this in Haskell, and I'm doubting
its possible.  Can someone prove me wrong?



Now maybe I'm being dense here, but would you really *want* a way in Haskell
to do something like
memo :: (a->b) -> a->b
since it changes the semantics of the function?
It seems like a better abstraction would be to have
memo :: (a->b)-> M a b
where M is an instance of Arrow so that you can keep a proper notion of
composition between memoized functions.
Is there something wrong with my thinking?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-30 Thread Creighton Hogg

On 5/29/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:


Claus Reinke wrote:



<>



> phantom types:
>  the types of ghost values (in other words, we are only interested in
>  the type, not in any value of that type).

Mmm... Still not seeing a great amount of use for this one.



Okay, well phantom types are something I like because they allow some notion
of static capabilities, a la
http://okmij.org/ftp/papers/lightweight-static-capabilities.pdf
One of my big interests is how much of a true capability based security
system can be pushed up into the type level.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2007-05-30 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Creighton Hogg wrote:
> Now maybe I'm being dense here, but would you really *want* a way in
> Haskell
> to do something like
> memo :: (a->b) -> a->b
> since it changes the semantics of the function?
> It seems like a better abstraction would be to have
> memo :: (a->b)-> M a b
> where M is an instance of Arrow so that you can keep a proper notion of
> composition between memoized functions.
> Is there something wrong with my thinking?

"memoize f gives you back a function that maintains a cache of
previously computed values, so that subsequent calls with the same
input will be faster."

Speed isn't part of Haskell function semantics (luckily, or we wouldn't
be able to have an optimizer in the first place).

memoize does not change the semantics of the function (I think)

Your "better abstraction" is, anyway, better in terms of being
implementable in existing Haskell - you might need an (Eq a) context or
something. However it interferes with code structure for a
non-semantical change (strong effects on memory use and speed which you
might _want_ to manage more explicitly, but that's not theoretically
affecting purity)


Isaac
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGXZPDHgcxvIWYTTURAi9fAJ44oIE85tZd+OtUOKswZnleBdt7eACeJuET
65AkQ2zI15CH6pnMHFmQddE=
=n5OS
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Henk-Jan van Tuyl
On Wed, 30 May 2007 09:38:10 +0200, Tomasz Zielonka  
<[EMAIL PROTECTED]> wrote:



On Tue, May 29, 2007 at 09:43:03PM +0100, Andrew Coppin wrote:

Henning Thielemann wrote:
>On Sun, 27 May 2007, Andrew Coppin wrote:
>>But every now and then I discover an expression which is apparently  
not

>>expressible without them - which is odd, considering they're only
>>"sugar"...
>
>Example?

Until I learned the trick of using lists as monads, I was utterly
perplexed as to how to get a Cartesian product


This is far from not expressible:
cart xs ys = concatMap (\x -> map ((,) x) ys) xs



A bit simpler is:
  cart xs ys = [(x, y) | x <- xs, y <- ys]

or:
  cart xs ys =
do
  x <- xs
  y <- ys
  return (x, y)

--
Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
--

Using Opera's revolutionary e-mail client:
https://secure.bmtmicro.com/opera/buy-opera.html?AID=789433

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


[Haskell-cafe] Data.Generics

2007-05-30 Thread Mark T.B. Carroll
Do we have a simple example somewhere of how to use gzipWithQ ? I can
get things like everything and everywhere working with mkQ and mkT,
but I can't work out how to make a curried query thing for gzipWithQ -
I'm sure I'm missing the obvious.

-- Mark

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


Re: [Haskell-cafe] Memoization

2007-05-30 Thread Creighton Hogg

On 5/30/07, Isaac Dupree <[EMAIL PROTECTED]> wrote:


-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Creighton Hogg wrote:
> Now maybe I'm being dense here, but would you really *want* a way in
> Haskell
> to do something like
> memo :: (a->b) -> a->b
> since it changes the semantics of the function?
> It seems like a better abstraction would be to have
> memo :: (a->b)-> M a b
> where M is an instance of Arrow so that you can keep a proper notion of
> composition between memoized functions.
> Is there something wrong with my thinking?

"memoize f gives you back a function that maintains a cache of
previously computed values, so that subsequent calls with the same
input will be faster."

Speed isn't part of Haskell function semantics (luckily, or we wouldn't
be able to have an optimizer in the first place).

memoize does not change the semantics of the function (I think)

Your "better abstraction" is, anyway, better in terms of being
implementable in existing Haskell - you might need an (Eq a) context or
something. However it interferes with code structure for a
non-semantical change (strong effects on memory use and speed which you
might _want_ to manage more explicitly, but that's not theoretically
affecting purity)



Eh, I guess I was just being fascist.  I suppose that even if there are side
effects involved in the memoization, it doesn't break referential
transparency which is the real measure of purity.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The C Equiv of != in Haskell miscommunication thread

2007-05-30 Thread Albert Y. C. Lai

Roberto Zunino wrote:

I actually misread the first one as

Control.Monad.Fix.fix ((1:) . tail . scanl (+) 1)

which is quite nice too, although

map (2^) [0..]

would be much simpler! ;-)


We apply a lesson learned from my last derivation. The lesson was to 
look at s!!(n+1).


s = 1 : tail (scanl (+) 1 s)

s!!(n+1) = (1 : tail (scanl (+) 1 s))!!(n+1)
 = tail (scanl (+) 1 s) !! n
 = scanl (+) 1 s !! (n+1)
 = 1 + s!!0 + s!!1 + s!!2 + ... + s!!n

It turns out that we can generalize it a bit to

s!!n = 1 + s!!0 + ... + s!!(n-1)

since, in case n=0, it gives s!!0 = 1 + empty sum, which is still right.

But now plugging the equation of s!!n into that of s!!(n+1) gives

s!!(n+1) = 1 + s!!0 + s!!1 + s!!2 + ... s!!(n-1) + s!!n
 = s!!n + s!!n
 = 2 * s!!n

Together with s!!0 = 1, this explains why s!!n = 2^n.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] ST vs State

2007-05-30 Thread Bulat Ziganshin
Hello Federico,

Wednesday, May 30, 2007, 12:54:35 PM, you wrote:

> Control.Monad.ST
> And
> Control.Monad.State

ST monad is just reduced IO monad which like IO organizes sequential
(imperative) ordr of execution but unlike IO supports only a small
closed set of operations - those working with STRef and STArray

State monad provides just two operations - get and put, which provides
access to some "monad state". unlike ST/IO monads operations in State
monad (and all other monads) can be performed in any order as typical
for lazy computations. of course, there are guarantees that put
operation will be performed before get that reads appropriate state

you may be interested looking at http://haskell.org/haskellwiki/IO_inside
although it doesn't say about ST/State monads directly

(btw, there is also Lazy.ST monad but it is not used too much :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: Distributing a program with support files

2007-05-30 Thread Simon Marlow

Neil Mitchell wrote:

Hi Duncan,


list the support files in the "data-files:" stanza in the .cabal file.
Then import the Paths_ module that Cabal generates for you. It
exports a few functions including:

  getDataDir :: IO FilePath


A few questions:

1) How do I test this? I'll need to develop in Hugs and GHC without
going through Cabal building. Should I fake up a Paths_ module?

2) Is there any reasonable limit on the number of data files? Is 1000 
too many?


3) Can I create files in this DataDir directory?

It does seem that creating a new Paths_ module and include it is
not very pleasant. It requires everyone to compile from source to get
the paths working, which doesn't make much sense.


The idea is that you get to refer to your data files without any explicit paths, 
Cabal chooses where to install them, and it works on any OS.  Furthermore, on 
Windows you can generate a relocatable binary distribution, because Windows lets 
you put the files in a path relative to the binary.


The Cabal docs describe how to do it.  Also check out Happy, Alex and Haddock - 
they all have data files that come with the package.  Personally, I think it 
works nicely!


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


Re: [Haskell-cafe] Building error Gtk2Hs under GHC 6.6.1 on Solaris 10 x86

2007-05-30 Thread Duncan Coutts
On Wed, 2007-05-23 at 21:42 -0700, lebed wrote: 
> Hi, haskell-caffe!
> 
> I'm trying to build Gtk2Hs 0.9.11 under GHC 6.6.1 on Solaris 10 x86:

> ./mk/chsDepend -iglib:gtk:sourceview
> sourceview/Graphics/UI/Gtk/SourceView/Types.chs
> could not find {#import.chs on search path glib gtk sourceview
> gmake[1]: *** [sourceview/Graphics/UI/Gtk/SourceView/Types.dep] Error 1
> gmake[1]: Leaving directory `/usr/export/home/lebed/tmp/gtk2hs-0.9.11'
> 
> : can't find file: glib/System/Glib/FFI.hs
> gmake: *** [glib/libHSglib_a.deps] Error 1
> gmake: *** Deleting file `glib/libHSglib_a.deps'
> 
> Where is my mistake?

This is a bug in mk/chsDepend(.in) probably due to some difference in
how sed works in Solaris compared to Linux.

the mk/chsDepend shell script looks at a .chs file and tries to find all
the lines that look like:

{#import Some.Module.Name#}

and then find the .chi files corresponding to those import lines. It
looks from the error message that it's picking up "{#import" as if it
were a module.

The shell/sed code that is probably going wrong is:

  DEPS=`$GREP "{#import" $FULLNAME 2> /dev/null \
   | $SED 'y/./\//;s/^{#import \(qualified \)*\([a-zA-Z1-9/]*\)#}.*/\2/'`;

testing this with standard solaris sed (on Solaris 9) reveals the
problem, standard Solaris sed is terrible! :-)

The problem is that standard Solaris /usr/bin/sed does not allow * on
sub-expressions, for example this sed regexp "\(bar\)*" does not match
the string "bar bar". The other Solaris sed that is not on the path by
default works fine (/usr/xpg4/bin/sed). Well actually it needs a minor
patch too, it doesn't like the escape in "y/./\//", but if we change it
to "y|.|/|" then it's happy.

So the solution I think is for me to change the configure script to look
for /usr/xpg4/bin/sed in preference to /usr/bin/sed on Solaris and also
to make that other minor syntax fix.

The workaround you can try is to edit mk/chsDepend and set SED to either
gnu sed or to /usr/xpg4/bin/sed though in the latter case you'll also
need to fix the "y|.|/|" bit. Then you'll need to make clean and make
again.

Duncan

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


Re: [Haskell-cafe] Implementing Mathematica

2007-05-30 Thread Andrew Coppin

Jon Harrop wrote:
I noticed a recent thread about writing a Mathematica implementation in 
Haskell.


Yeah, that was me.

I think this is an excellent idea and would be a great project for a 
Haskell newbie.


Uh... I think it's actually a tad harder than it looks. [Understatement!]

I wrote a toy Mathematica implementation in OCaml while I 
waited to be viva'd for my PhD. It garnered so much interest that Wolfram 
Research bought it from me for £4,500 and gave me several free copies of 
Mathematica.
  


Are you serious?! o_O


Regarding the specific points made:

1. Numerical libraries: you should be able to reuse existing libraries like 
GMP, BLAS, LAPACK, FFTW and so on. These are often much faster than 
Mathematica's. For example, FFTW was about 4x faster than Mathematica's FFT 
the last time I benchmarked it. However, they do not support interval 
arithmetic.
  


Now this is interesting. The claim is that Mathematica is the fastest, 
most powerful software on planet earth, second to none. Actually it 
turns out that at least for factoring moderately big integers, pari/gp 
seems to be a fair bit faster (50% or so). I have no idea about the rest.


Note that (as I understand it) GHC implements Haskell's Integer type 
using the GMP. And for some reason or other, they want to remove this 
feature...



2. GUI: I would take our existing vector graphics software:

  http://www.ffconsultancy.com/products/smoke_vector_graphics/
  http://www.ffconsultancy.com/products/fsharp_for_visualization/

and rewrite it in Haskell as the foundation. This would far exceed anything 
that Mathematica has to offer, in part because Mathematica's graphics are 
still evaluated via the completely generic rewrite engine which is extremely 
slow. Our code already implements high-performance hardware-accelerated 
vector graphics and it is probably one of the first things I would consider 
porting to Haskell (if there is any commercial interest in such a library).
  


Erm... have you seen Mathematica 6? That's OpenGL accelerated too. I've 
just been playing with it in fact - it's pretty fast as far as I can tell.


3. The language: the hardest part of reimplementing Mathematica is inferring 
what it means (there are no formal evaluation semantics). Once you've done 
that it is just a case of implementing an extensible term rewriter and 
putting in about 20 core rules. The pattern matcher is well under 100 LOC and 
you can do various things to make it more efficient. There are two tricks 
that vastly improve performance of the rewriter: return physically identical 
results whenever possible, and perform substitution and evaluation at the 
same time rather than as two separate passes.
  


Haskell has pattern matching, but what Mathematica does is much more 
sophisticated. I have tried to implement it several times, and failed. 
(But that was Pascal, this is Haskell...)


4. Libraries: You should have no trouble exceeding the capabilities of 
Mathematica by pulling in existing libraries. For example, Mathematica 
provides no wavelet transforms, no time-frequency transforms, no function 
minimization over an arbitrary number of variables etc.
  


What...the...hell...?

Mathematica contains the largest, most comprehensive set of 
implementations of special functions anywhere in the world. It has a 
*vast* collection of identities and transformation rules constituting 
man-centuries of R&D work. It has cutting edge symbolic integration 
capabilities. It has multiple numerical solver algorithms. It has...


Yeah, should only take 5 minutes or so to exceed those capabilities. 
Easy really...


You should easily be able to implement a rewriter for the language that is ten 
times faster and doesn't leak.


Incidentally, my implementation of Mathematica in OCaml took four days, and it 
was one of my first OCaml programs.
  


OK, so you're saying that in 4 days you wrote something that 
out-performs Mathematica, a program that has existed for decades and has 
a vast, highly-funded R&D effort behind it featuring some of the 
brightest minds in the field?


I'm in a state of disbelief here.

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


Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Roberto Zunino
Tomasz Zielonka wrote:
> In the Ord variant, the result value pretty much has to come from the
> input list or be bottom. It has to be bottom for the empty list. If
> f :: Ord a => [a] -> a and g preserves order (is monotonic) then
> f (map g l) == g (f l)
> This could be nice for testing Ord instances. Unfortunately, for bounded
> types the only order preserving function is id.

Interesting... are the following g allowed? (I am relatively new to
parametericity results.)

(\!x -> (x,4))-- bounded types (?)
($!) Data.List.repeat -- ;-) unbounded types

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


Re: [Haskell-cafe] Implementing Mathematica

2007-05-30 Thread Alex Queiroz

Hallo,

On 5/30/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:


OK, so you're saying that in 4 days you wrote something that
out-performs Mathematica, a program that has existed for decades and has
a vast, highly-funded R&D effort behind it featuring some of the
brightest minds in the field?

I'm in a state of disbelief here.



If you want some amusement, just search for "Jon Harrop" in comp.lang.lisp.

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


Re: [Haskell-cafe] Implementing Mathematica

2007-05-30 Thread Lennart Augustsson
Why do you seem so in awe of Mathematica?  It's just another language with 
a good set of libraries.  Claims that it is the best, fastest, etc comes 
from Wolfram advertising, no doubt. :)


-- Lennart

On Wed, 30 May 2007, Andrew Coppin wrote:


Date: Wed, 30 May 2007 22:15:55 +0100
From: Andrew Coppin <[EMAIL PROTECTED]>
To: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Implementing Mathematica

Jon Harrop wrote:
I noticed a recent thread about writing a Mathematica implementation in 
Haskell.


Yeah, that was me.

I think this is an excellent idea and would be a great project for a 
Haskell newbie.


Uh... I think it's actually a tad harder than it looks. [Understatement!]

I wrote a toy Mathematica implementation in OCaml while I waited to be 
viva'd for my PhD. It garnered so much interest that Wolfram Research 
bought it from me for £4,500 and gave me several free copies of 
Mathematica.




Are you serious?! o_O


Regarding the specific points made:

1. Numerical libraries: you should be able to reuse existing libraries like 
GMP, BLAS, LAPACK, FFTW and so on. These are often much faster than 
Mathematica's. For example, FFTW was about 4x faster than Mathematica's FFT 
the last time I benchmarked it. However, they do not support interval 
arithmetic.




Now this is interesting. The claim is that Mathematica is the fastest, most 
powerful software on planet earth, second to none. Actually it turns out that 
at least for factoring moderately big integers, pari/gp seems to be a fair 
bit faster (50% or so). I have no idea about the rest.


Note that (as I understand it) GHC implements Haskell's Integer type using 
the GMP. And for some reason or other, they want to remove this feature...



2. GUI: I would take our existing vector graphics software:

  http://www.ffconsultancy.com/products/smoke_vector_graphics/
  http://www.ffconsultancy.com/products/fsharp_for_visualization/

and rewrite it in Haskell as the foundation. This would far exceed anything 
that Mathematica has to offer, in part because Mathematica's graphics are 
still evaluated via the completely generic rewrite engine which is 
extremely slow. Our code already implements high-performance 
hardware-accelerated vector graphics and it is probably one of the first 
things I would consider porting to Haskell (if there is any commercial 
interest in such a library).




Erm... have you seen Mathematica 6? That's OpenGL accelerated too. I've just 
been playing with it in fact - it's pretty fast as far as I can tell.


3. The language: the hardest part of reimplementing Mathematica is 
inferring what it means (there are no formal evaluation semantics). Once 
you've done that it is just a case of implementing an extensible term 
rewriter and putting in about 20 core rules. The pattern matcher is well 
under 100 LOC and you can do various things to make it more efficient. 
There are two tricks that vastly improve performance of the rewriter: 
return physically identical results whenever possible, and perform 
substitution and evaluation at the same time rather than as two separate 
passes.




Haskell has pattern matching, but what Mathematica does is much more 
sophisticated. I have tried to implement it several times, and failed. (But 
that was Pascal, this is Haskell...)


4. Libraries: You should have no trouble exceeding the capabilities of 
Mathematica by pulling in existing libraries. For example, Mathematica 
provides no wavelet transforms, no time-frequency transforms, no function 
minimization over an arbitrary number of variables etc.




What...the...hell...?

Mathematica contains the largest, most comprehensive set of implementations 
of special functions anywhere in the world. It has a *vast* collection of 
identities and transformation rules constituting man-centuries of R&D work. 
It has cutting edge symbolic integration capabilities. It has multiple 
numerical solver algorithms. It has...


Yeah, should only take 5 minutes or so to exceed those capabilities. Easy 
really...


You should easily be able to implement a rewriter for the language that is 
ten times faster and doesn't leak.


Incidentally, my implementation of Mathematica in OCaml took four days, and 
it was one of my first OCaml programs.




OK, so you're saying that in 4 days you wrote something that out-performs 
Mathematica, a program that has existed for decades and has a vast, 
highly-funded R&D effort behind it featuring some of the brightest minds in 
the field?


I'm in a state of disbelief here.

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




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


Re: [Haskell-cafe] Implementing Mathematica

2007-05-30 Thread Jon Harrop
On Wednesday 30 May 2007 22:15:55 Andrew Coppin wrote:
> Jon Harrop wrote:
> > I wrote a toy Mathematica implementation in OCaml while I
> > waited to be viva'd for my PhD. It garnered so much interest that Wolfram
> > Research bought it from me for £4,500 and gave me several free copies of
> > Mathematica.
>
> Are you serious?! o_O

Yes.

> > 1. Numerical libraries: you should be able to reuse existing libraries
> > like GMP, BLAS, LAPACK, FFTW and so on. These are often much faster than
> > Mathematica's. For example, FFTW was about 4x faster than Mathematica's
> > FFT the last time I benchmarked it. However, they do not support interval
> > arithmetic.
>
> Now this is interesting. The claim is that Mathematica is the fastest,
> most powerful software on planet earth, second to none.

If you write a simple, numerically-intensive program that runs in the 
Mathematica rewriter then its performance is about 100-1,000x slower than 
that of a native-code compiled language like Haskell. Mathematica is often 
30x slower than interpreted OCaml bytecode.

Take this ray tracer, for example:

scene = {Sphere[{0., 0., 4.}, 1.], Sphere[{-1., 1., 4.}, 1.], 
 Sphere[{-1., -1., 4.}, 1.], Sphere[{1., 1., 4.}, 1.], 
 Sphere[{1., -1., 4.}, 1.]};

\[Delta] = Sqrt[$MachineEpsilon];

Unitise[p_] := p/Sqrt[p.p]

RaySphere[o_, d_, c_, r_] :=
  Block[{v = c - o, b = v.d, disc = b^2 - v.v + r^2},
If[disc <= 0., \[Infinity],
  disc = Sqrt[disc];
  Block[{t2 = b + disc},
If[t2 <= 0., \[Infinity],
  Block[{t1 = b - disc},
If[t1 > 0., t1, t2]]

Intersect[o_, d_][{lambda_, n_}, Sphere[c_, r_]] :=
  Block[{lambda2 = RaySphere[o, d, c, r]},
If[lambda2 >= lambda, {lambda, n}, {lambda2, Unitise[o + lambda2 d - c]}]
]
Intersect[o_, d_][hit_, list_List] := Fold[Intersect[o, d], hit, list]

nohit = {\[Infinity], {0., 0., 0.}};

RayTrace[o_, d_, scene_] :=
  Block[{lambda, n, g, p},
{lambda, n} = Intersect[o, d][nohit, scene];
If[lambda === \[Infinity], 0.,
  g = n.neglight;
  If[g <= 0., 0.,
p = o + lambda d + \[Delta] n;
{lambda, n} = Intersect[p, neglight][nohit, scene];
If[lambda < \[Infinity], 0., g

Timing[image = 
  Table[Table[
  RayTrace[{0., 0., -2.5}, Unitise[{x, y, 128.}], scene], {y, -64, 
64}], {x, -64, 64}];]

This program takes 4.8s to run here. I bet if we translate it into Haskell it 
will run much faster than that.

As a guide, this Haskell ray tracer is much more advanced and it can render a 
bigger (100x100) image in only 0.2s:

  http://www.nobugs.org/developer/htrace/

Incidentally, when I try to recompile with optimizations turned on, GHC 
refuses to work:

$ ghc htrace.hs -o htrace
$ ghc -O2 htrace.hs -o htrace
compilation IS NOT required

I must delete the target or edit the source to get it to recompile. I assume 
this is a known bug?

> Actually it 
> turns out that at least for factoring moderately big integers, pari/gp
> seems to be a fair bit faster (50% or so). I have no idea about the rest.

Right, but that is just calling an internal function that is written in C. 
Provided you only ever call a few library functions, performance will be 
excellent in Mathematica. But when you cannot phrase your program in terms of 
the built-in library functions, performance is terrible and this is when 
everyone reaches for a more efficient tool.

To me, performance is way down on the list of things that make Mathematica 
great. Integrated graphics is probably the main benefit. I mostly use MMA as 
a glorified graph plotter.

> Note that (as I understand it) GHC implements Haskell's Integer type
> using the GMP. And for some reason or other, they want to remove this
> feature...

Arbitrary precision integers are quite a performance burden and they are 
rarely used. I would not expect a language that is trying to be efficient to 
impose arbitrary precision integers (or floats).

> Erm... have you seen Mathematica 6?

Yes.

> That's OpenGL accelerated too.

Yes. Similarly, making graphics fast takes a lot more than just "using 
OpenGL".

> I've just been playing with it in fact - it's pretty fast as far as I can
> tell= 

It still invokes a completely generic term rewriter for everything it 
evaluates. You can really feel this when you play with some of their 
interactive demos. Even the simple ones are notably sluggish. Try translating 
the Tiger demo from our site into Mathematica, for example.

Many of their demos will be trivial to write in Haskell but performance would 
be a lot better. I'd like to write some graphics demos in Haskell using 
OpenGL...

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
OCaml for Scientists
http://www.ffconsultancy.com/products/ocaml_for_scientists/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] OpenGL

2007-05-30 Thread Jon Harrop

I've found HOpenGL and the Debian package libghc6-opengl-dev. The former seems 
to be very out of date (last release 2003) but I can't find any demos for the 
latter.

Where should I go to get started with OpenGL and Haskell?

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
OCaml for Scientists
http://www.ffconsultancy.com/products/ocaml_for_scientists/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] OpenGL

2007-05-30 Thread Creighton Hogg

On 5/30/07, Jon Harrop <[EMAIL PROTECTED]> wrote:



I've found HOpenGL and the Debian package libghc6-opengl-dev. The former
seems
to be very out of date (last release 2003) but I can't find any demos for
the
latter.

Where should I go to get started with OpenGL and Haskell?



For at least GHC you can use the libraries that come with.
Check out this blog entry as a nice starting place
http://blog.mikael.johanssons.org/archive/2006/09/opengl-programming-in-haskell-a-tutorial-part-1/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] OpenGL

2007-05-30 Thread Bryan O'Sullivan

Jon Harrop wrote:


Where should I go to get started with OpenGL and Haskell?


Take a look at Gtk2Hs, which has OpenGL bindings.

For example, see http://darcs.haskell.org/gtk2hs/demo/opengl/

http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing Mathematica

2007-05-30 Thread Stefan O'Rear
On Wed, May 30, 2007 at 11:56:30PM +0100, Jon Harrop wrote:
> On Wednesday 30 May 2007 22:15:55 Andrew Coppin wrote:
> > Jon Harrop wrote:
> > > I wrote a toy Mathematica implementation in OCaml while I
> > > waited to be viva'd for my PhD. It garnered so much interest that Wolfram
> > > Research bought it from me for £4,500 and gave me several free copies of
> > > Mathematica.
> >
> > Are you serious?! o_O
> 
> Yes.

You said that constructing a specification is the hardest part of
implementing Mathematica, and you also say you managed to clone it.
Can you reveal your specification, or did WR give you a NDA? 

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


Re: [Haskell-cafe] OpenGL

2007-05-30 Thread Duncan Coutts
On Wed, 2007-05-30 at 16:09 -0700, Bryan O'Sullivan wrote:
> Jon Harrop wrote:
> 
> > Where should I go to get started with OpenGL and Haskell?
> 
> Take a look at Gtk2Hs, which has OpenGL bindings.
> 
> For example, see http://darcs.haskell.org/gtk2hs/demo/opengl/

The Gtk2Hs OpenGL stuff is only a replacement for the GLUT windowing
tookkit. The Gtk2Hs OpenGL stuff still has to be used in combination
with the standard Graphics.Rendering.OpenGL modules.

The Gtk2Hs OpenGL stuff basically consists of a GL widget that you can
embed into other Gtk+ windows and then use the standard OpenGL calls to
render into the GL widget.

Duncan

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


Re: [Haskell-cafe] Implementing Mathematica

2007-05-30 Thread Tim Chevalier

On 5/30/07, Jon Harrop <[EMAIL PROTECTED]> wrote:


Incidentally, when I try to recompile with optimizations turned on, GHC
refuses to work:

$ ghc htrace.hs -o htrace
$ ghc -O2 htrace.hs -o htrace
compilation IS NOT required

I must delete the target or edit the source to get it to recompile. I assume
this is a known bug?



If the sources haven't changed and you're only using a different combination
of command-line options, GHC's recompilation checker will determine that no
recompilation is necessary. You can turn off the recompilation checker and
force recompilation unconditionally by adding the -no-recomp flag. (There's
already a feature request to make the recompilation checker consider changes
to command-line options as well as code, it just haven't been implemented.)

Cheers,
Tim

--
Tim Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] OpenGL

2007-05-30 Thread Thomas Schilling

See the examples/RedBook directory in the source code.  It gives you a
good idea how the C-idioms are translated.

For an actual documentation on OpenGL you'll better take a look at
general OpenGL literature and translate them into Haskell.  Note that
it's quite complex, though.

On 5/31/07, Jon Harrop <[EMAIL PROTECTED]> wrote:


I've found HOpenGL and the Debian package libghc6-opengl-dev. The former seems
to be very out of date (last release 2003) but I can't find any demos for the
latter.

Where should I go to get started with OpenGL and Haskell?

--
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
OCaml for Scientists
http://www.ffconsultancy.com/products/ocaml_for_scientists/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




--
"Remember! Everytime you say 'Web 2.0' God kills a startup!" -
userfriendly.org, Jul 31, 2006
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] OpenGL

2007-05-30 Thread Jason Dagit

On 5/30/07, Jon Harrop <[EMAIL PROTECTED]> wrote:


I've found HOpenGL and the Debian package libghc6-opengl-dev. The former seems
to be very out of date (last release 2003) but I can't find any demos for the
latter.

Where should I go to get started with OpenGL and Haskell?


I started converting the (famous?) NeHe tutorials to Haskell.  I made
it through the 12th tutorial before I moved on to other things.  You
can find my darcs repository here:
http://www.codersbase.com/index.php/Nehe-tuts

If you convert any more of the NeHe lessions to haskell, I accept darcs patches.

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


[Haskell-cafe] ANNOUNCE: xmonad 0.2

2007-05-30 Thread Spencer Janssen
The xmonad dev team is pleased to announce the 0.2 release of:

xmonad: a tiling window manager
   http://xmonad.org

About:

Xmonad is a tiling window manager for X. Windows are arranged
automatically to tile the screen without gaps or overlap, maximising
screen use. All features of the window manager are accessible from the
keyboard: a mouse is strictly optional, greatly increasing productivity
in X. 

Xmonad is written and extensible in Haskell, and custom layout
algorithms, and other extesions, may be implemented by the user in
config files. Layouts may be applied dynamically, and separate layouts
can be used on each workspace. A guiding principle of the user interface
is predictability: users should know in advance precisely the window
arrangement that will result from any action, leading to an intuitive
user interface.  

Features:

* Automatic window tiling and management
* First class keyboard support: a mouse is unnecessary
* Full multihead/Xinerama support
* XRandR support to rotate, add or remove monitors
* Per-workspace layout algorithms
* Per-screen non-built in status bars, with arbitrary geometry
* Dynamic restart/reconfigure preserving workspace state
* Tiny code base (~500 lines of Haskell)
* Fast, small and simple. No interpreters, no heavy extension
languages 

Since 0.1, the following notable features and bug fixes have appeared:

 New features:

  * XRandR support, for dynamically adding, removing or rotating
monitors
  * State-preserving dynamic restart
  * Popup, customisable status bar support
  * Multiple clients may appear in the master pane
  * mod-shift-j/k, to swap windows with their neighbours
  * mod-n, to resize windows
  * User-specified layout algorithms may be written in config files
  * All layouts may be 'mirrored' (rotated)
  * configurable window border size and colour

 Design changes:

  * Reimplemented core of xmonad with a 'zipper' data type to track
focus by construction. We believe this is a first.
  * Use of Neil Mitchell's 'catch' program to verify pattern match
safety
  * Use of ReaderT and StateT to partition read-only and modifiable
values
  * Custom layout messages handled with open data type simulation
  * More QuickCheck properties

Bug fixes:

  * numlock handling is fixed

More information, screenshots, documentation and community resources are
available from:

http://xmonad.org

Xmonad is available from hackage, and via darcs. Happy hacking!

The Xmonad Team:

Spencer Janssen
Don Stewart
Jason Creighton

Xmonad has also received patches from:

Alec Berryman
Chris Mears
Daniel Wagner
David Glasser
David Lazar
David Roundy
Joe Thornber
Miikka Koskinen
Neil Mitchell
Nick Burlett
Robert Marlow
Sam Hughes
Shae Erisson
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing Mathematica

2007-05-30 Thread Jon Harrop
On Wednesday 30 May 2007 07:04:31 Jon Harrop wrote:
> 3. The language: the hardest part of reimplementing Mathematica is
> inferring what it means (there are no formal evaluation semantics). Once
> you've done that it is just a case of implementing an extensible term
> rewriter and putting in about 20 core rules. The pattern matcher is well
> under 100 LOC and you can do various things to make it more efficient.
> There are two tricks that vastly improve performance of the rewriter:
> return physically identical results whenever possible, and perform
> substitution and evaluation at the same time rather than as two separate
> passes.

Sorry for replying to myself. :-)

It occurs to me that laziness will eliminate the intermediate data structure 
between substitution and evaluation anyway, so that isn't such a concern in 
Haskell.

However, I can't think how you might return physically identical results when 
possible in Haskell. Essentially, you need a higher-order map function:

  val id_map : ('a -> 'a) -> 'a t -> 'a t

that returns its input when "f x = x" for every x. How might this be done?

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
OCaml for Scientists
http://www.ffconsultancy.com/products/ocaml_for_scientists/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Crazy idea: overloading function application notation

2007-05-30 Thread Jon Harrop

This is a crazy idea I've been working on: overload the syntax "x y" so it can 
mean function application "f x = f(x)" or multiplication "x y = x*y". The 
reason is simply that I appreciate the brevity of MLs function application 
but I also appreciate the brevity of Mathematica's multiplication.

Is it possible to implement this in Haskell using type classes? Is there any 
way this could actually be practicable?

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
OCaml for Scientists
http://www.ffconsultancy.com/products/ocaml_for_scientists/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] enumFrom* strangeness on GHC?

2007-05-30 Thread Felipe Almeida Lessa

Hello =),

I'm puzzled, and maybe someone can help me out. Why does this happens?

$ time ghci -e "last $ take 100 $ [1..100]"
100

real0m0.673s
user0m0.554s
sys 0m0.024s

$ time ghci -e "last $ take 100 $ [1..]"
*** Exception: stack overflow

real0m1.305s
user0m1.057s
sys 0m0.062s

$ ghci -V
The Glorious Glasgow Haskell Compilation System, version 6.6


Looking at http://darcs.haskell.org/ghc-6.6/packages/base/GHC/Enum.lhs
, I still have no clue of what may be happening. Any ideas? Should I
file a bug on GHC?

Thanks,

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


Re: [Haskell-cafe] enumFrom* strangeness on GHC?

2007-05-30 Thread Stefan O'Rear
On Wed, May 30, 2007 at 11:41:55PM -0300, Felipe Almeida Lessa wrote:
> Hello =),
> 
> I'm puzzled, and maybe someone can help me out. Why does this happens?
> 
> $ time ghci -e "last $ take 100 $ [1..100]"
> 100
> 
> real0m0.673s
> user0m0.554s
> sys 0m0.024s
> 
> $ time ghci -e "last $ take 100 $ [1..]"
> *** Exception: stack overflow
> 
> real0m1.305s
> user0m1.057s
> sys 0m0.062s
> 
> $ ghci -V
> The Glorious Glasgow Haskell Compilation System, version 6.6
> 
> 
> Looking at http://darcs.haskell.org/ghc-6.6/packages/base/GHC/Enum.lhs
> , I still have no clue of what may be happening. Any ideas? Should I
> file a bug on GHC?

No, because anything you file will be closed immediately as "duplicate
of http://hackage.haskell.org/trac/ghc/ticket/1097";

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


Re: [Haskell-cafe] enumFrom* strangeness on GHC?

2007-05-30 Thread Felipe Almeida Lessa

On 5/30/07, Stefan O'Rear <[EMAIL PROTECTED]> wrote:

No, because anything you file will be closed immediately as "duplicate
of http://hackage.haskell.org/trac/ghc/ticket/1097";


Oh, sorry for not having searched better for this problem on the net.
I spend a lot of time finding out where the stack was blowing and
forgot to google about it.

Thanks,

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


Re: [Haskell-cafe] enumFrom* strangeness on GHC?

2007-05-30 Thread Stefan O'Rear
On Thu, May 31, 2007 at 12:15:01AM -0300, Felipe Almeida Lessa wrote:
> On 5/30/07, Stefan O'Rear <[EMAIL PROTECTED]> wrote:
> >No, because anything you file will be closed immediately as "duplicate
> >of http://hackage.haskell.org/trac/ghc/ticket/1097";
> 
> Oh, sorry for not having searched better for this problem on the net.
> I spend a lot of time finding out where the stack was blowing and
> forgot to google about it.

You don't need to feel too bad about this:

19:52 < dons> sorear: be nice to people reporting bugs please.
19:53  * sorear grumbles
19:53  * sorear wishes he had more luck with this "politeness" thing
19:54 < dons> try the same text, but hadd 'thanks for the report! looks like a 
duplicate of ... . cheers, .."
19:54 < dons> makes a huge different to the scared guy at the other end just 
hoping to help
19:55 < SamB_XP> please don't eat me!

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


Re: [Haskell-cafe] enumFrom* strangeness on GHC?

2007-05-30 Thread Felipe Almeida Lessa

On 5/31/07, Stefan O'Rear <[EMAIL PROTECTED]> wrote:

You don't need to feel too bad about this:

[snip]

Don't worry, I should have googled anyway =).

BTW, how do you usually proceed when finding out why your code said
"Segmentation fault."?  (should this question move to a new thread?)

Thanks,

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


Re: [Haskell-cafe] enumFrom* strangeness on GHC?

2007-05-30 Thread Stefan O'Rear
On Thu, May 31, 2007 at 12:34:36AM -0300, Felipe Almeida Lessa wrote:
> On 5/31/07, Stefan O'Rear <[EMAIL PROTECTED]> wrote:
> >You don't need to feel too bad about this:
> [snip]
> 
> Don't worry, I should have googled anyway =).
> 
> BTW, how do you usually proceed when finding out why your code said
> "Segmentation fault."?  (should this question move to a new thread?)

I skim the GHC bugs listing, then file one.  The nice thing about
segmentation faults is that (assuming you aren't using stuff like
unsafeCoerce#) they are never your fault, and always GHC bugs.

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


[Haskell-cafe] updating packages

2007-05-30 Thread jeff p

Hello,

 I just moved to ghc-6.6.1and was wondering if there is an automatic
way to update the various packages I had installed previously.

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


[Haskell-cafe] What puts False before True?

2007-05-30 Thread PR Stanley

Hi
What is the basic philosophy for Bool being a member of Ord?
What justifies False < True?
many Thanks in advance,
Paul

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


Re: [Haskell-cafe] What puts False before True?

2007-05-30 Thread kahl
 > 
 > What is the basic philosophy for Bool being a member of Ord?
 > What justifies False < True?

The implication ordering,
which on this smallest non-trivial Boolean algebra
happens to be a linear order,
is therefore the natural candidate for Ord,
the type class of ``default linear orders''.


False ==> True


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


Re: [Haskell-cafe] What puts False before True?

2007-05-30 Thread Marc A. Ziegert
Am Donnerstag, 31. Mai 2007 05:52 schrieb PR Stanley:
> What is the basic philosophy for Bool being a member of Ord?
you can do sth like

Data.Set.fromList [minBound .. maxBound] :: Data.Set.Set Bool

> What justifies False < True?
in most interpretations this equals:

False == 0
True == 1
and == (*)
or == max
not == (1 -)
a `xor` b == (a + b) `mod` 2

and not this:

False == 1
True == 0
and == max
or == (*)
not == (1 -)
a `xor` b == (a + b) `mod` 2


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


[Haskell-cafe] equations and patterns

2007-05-30 Thread mingli yuan

Hi, buddies. I am a newbie on Haskell. Recently I want to implement a simple
Lattice in Haskell, but I met some difficulties.
Scrap of the code is as below, but I met syntax error:


 class Lattice e where
 join :: e -> e -> e
 meet :: e -> e -> e

 -- associative law
 join x (join y z) = join (join x y) z
 join (join x y) z = join x (join y z)


The main problem is that mathematic equations is bi-directed, but in Haskell
the pattern matching is only in one direction -
from left to right. And only variables and constructors could be occur in
the right side of the pattern matching.

Seems mathematic axioms and pattern matching are different things.

So how could I rewrite the equations to pattern matching? Which technique
should I learn?

Thanks for your help.

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


Re: [Haskell-cafe] Implementing Mathematica

2007-05-30 Thread Stefan Holdermans

Jon,

However, I can't think how you might return physically identical  
results when
possible in Haskell. Essentially, you need a higher-order map  
function:


  val id_map : ('a -> 'a) -> 'a t -> 'a t

that returns its input when "f x = x" for every x. How might this  
be done?


fmap :: (Functor f) => (a -> b) -> f a -> f b

Cheers,

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


Re: [Haskell-cafe] Crazy idea: overloading function application notation

2007-05-30 Thread Stefan Holdermans

Jon,

This is a crazy idea I've been working on: overload the syntax "x  
y" so it can
mean function application "f x = f(x)" or multiplication "x y =  
x*y". The
reason is simply that I appreciate the brevity of MLs function  
application

but I also appreciate the brevity of Mathematica's multiplication.

Is it possible to implement this in Haskell using type classes? Is  
there any

way this could actually be practicable?


Well, of course, it is certainly not possible to implement it  
directly. Juxtaposition denotes by no means an ordinary binary  
operator. If you do pick an ordinary binary operator for application,  
say (#), then you can get quite far with some language extensions,  
although I think it'll render your code less readable. Anyway, I  
remember doing this dark deed once when working with finite maps.


I use associated type synonyms here, because we should get used to  
them anyway ;-). However, I'll attach a snippet employing functional  
dependencies, so you can actually play with it:


  infixl 9 #

  class Fun a where
type Dom a :: *
type Cod a :: *
(#):: a -> Dom a -> Cod a

Now, let's have some fun ;-).

  instance Fun (a -> b) where
type Arg (a -> b) = a
type Res (a -> b) = b
(#)   = ($)

  instance Fun Int where
type Arg Int = Int
type Res Int = Int
(#)  = (*)

  instance Fun Bool where
type Arg Bool = Bool
type Res Bool = Bool
(#)   = (&&)

  instance (Eq a) => Fun [(a, b)] where
type Arg [(a, b)] = a
type Res [(a, b)] = Maybe b
(#)   = flip lookup

And here we go:

  head   # [2, 3, 5]==>2
  2  # 3==>6
  False  # True ==>False
  [('E', 2), ('H', 3), ('C', 5)] # 'E'  ==>Just 2

Now, how practicable is it? As said, I think constructions like this  
have a negative impact on the readability of your programs. Moreover,  
overloading function applications is bound to introduce a lot of  
ambiguities in your programs and, hence, the need for type annotations.


Cheers,

  Stefan




Fun.hs
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Crazy idea: overloading function application notation

2007-05-30 Thread Stefan Holdermans

Jon,

This is a crazy idea I've been working on: overload the syntax "x  
y" so it can

mean function application "f x = f(x)" or multiplication "x y = x*y".


On a related (?) note, but definitely not what you're after: there  
are constructor classes that allow you to lift function application  
into a functor and equip it with specific semantics:


  fmap  :: (Functor f) => (a -> b)   -> f a -> f b
  (<*>) :: (Applicative f) => f (a -> b) -> f a -> f b
  (=<<) :: (Monad m)   => (a -> m b) -> m a -> m b

Cheers,

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


Re: [Haskell-cafe] equations and patterns

2007-05-30 Thread Stefan Holdermans

Mingli,


>  class Lattice e where
>  join :: e -> e -> e
>  meet :: e -> e -> e
>
>  -- associative law
>  join x (join y z) = join (join x y) z
>  join (join x y) z = join x (join y z)


If you are not to sell your soul to advanced and perhaps obscure type  
hacking, you cannot express laws like this *in* Haskell.


More concretely, one usually does not provide such laws as default  
implementations of a class' methods. Instead, they are stated in, for  
instance, comments and the documentation that goes with your library.  
These then form an informal obligation for programmers that provide  
instances of your class to let these instances obey the laws.


If you provide an instance of the class you could use testing  
framework, e.g., QuickCheck [1], to assert that the required  
properties hold.


Cheers,

  Stefan


[1] www.cs.chalmers.se/~rjmh/QuickCheck/



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