Re: [Haskell-cafe] Backpatching

2007-07-31 Thread Derek Elkins
On Tue, 2007-07-31 at 23:04 -0700, Stefan O'Rear wrote:
> On Wed, Aug 01, 2007 at 03:44:32PM +1000, Thomas Conway wrote:
> > This sounds like a common problem type. Is there a well known solution
> > to this sort of problem?
> 
> Mmm... logic programming?
> 
> http://citeseer.ist.psu.edu/claessen00typed.html
> 
> You'll only need the code for logic-variables, and even that can be
> simplified because your "terms" are non-recursive.  (Even in the
> recursive case, a logic program like a HM typechecker usually only needs
> ~50 lines of prelude).

If someone is interested, I did transcribe and mildly generalize the
code from that paper.

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


Re: [Haskell-cafe] Backpatching

2007-07-31 Thread Stefan O'Rear
On Wed, Aug 01, 2007 at 03:44:32PM +1000, Thomas Conway wrote:
> This sounds like a common problem type. Is there a well known solution
> to this sort of problem?

Mmm... logic programming?

http://citeseer.ist.psu.edu/claessen00typed.html

You'll only need the code for logic-variables, and even that can be
simplified because your "terms" are non-recursive.  (Even in the
recursive case, a logic program like a HM typechecker usually only needs
~50 lines of prelude).

(If you want an less enlightening answer, Map String (STRef s (Maybe 
Integer)))..

Stefan


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


Re: [Haskell-cafe] OS swapping and haskell data structures

2007-07-31 Thread Stefan O'Rear
On Tue, Jul 31, 2007 at 10:45:56PM -0700, Alex Jacobson wrote:
> If you create a Data.Map or Data.Set larger than fits in physical memory, 
> will OS level swapping enable your app to behave reasonably or will things 
> just die catastrophically as you hit a memory limit?

Data.{Set,Map} uses balanced binary trees.  So if you have a 1 billion
element data set which is so large that no significant fraction of it
fits into cache, you can expect to access a random element in ~9 seeks,
which is less than a second...  good enough?

This is a lot worse than it could be because memory access is too
transparent.  When GHC triggers a page fault, the Right Thing to do is
for Linux to somehow put *that haskell thread* to sleep; but instead it
will put the entire capability (or your whole program on the
non-threading rts) to sleep.

Linux's filesystems (which use various kinds of trees internally) avoid
this issue by using asynchronous IO requests, but that's not an option
for VM since there's only so much room for callbacks in a MOV
instruction!

There is much fertile territory for OS design space exploration here!

Stefan


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


Re[6]: [Haskell-cafe] i need wxHaskell compiled for ghc 6.6.1 on Windows

2007-07-31 Thread Bulat Ziganshin
Hello shelarcy,

Wednesday, August 1, 2007, 4:03:52 AM, you wrote:

>> problems. the only question that remains - does this version supports
>> unicode?

> Yes. Current darcs repository version support only unicode
> enabled version.

great, it's all what i need. but i'm still curious about other
features enabled when building this package. can i see
config.gcc or build.cfg or setup.h or any other file that shows
feature list? also it will be useful to include such file with the next
builds of wxHaskell

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] OS swapping and haskell data structures

2007-07-31 Thread Alex Jacobson
If you create a Data.Map or Data.Set larger than fits in physical 
memory, will OS level swapping enable your app to behave reasonably or 
will things just die catastrophically as you hit a memory limit?



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


[Haskell-cafe] Backpatching

2007-07-31 Thread Thomas Conway
Hi All,

One of the things I've been working on lately is some ASN.1 stuff.One
of the first things I wrote in Haskell was an ASN.1 parser. It only
worked for a subset, and I'm revisiting it to make it handle a
larger subset.

One of the things that gets messy is that in lots of places you can
put either a thing or a reference to a thing (i.e. the name of a thing
defined elsewhere). For example, consider the production:

NamedNumber ::= identifier "(" SignedNumber ")"
  | identifier "(" DefinedValue ")"

If we ignore the second alternative, the natural translation into a
Parsec parser would look like:

namedNumber = do
name <- identifier
val <- parens signedNumber
return (name, val)

Now to handle the second alternative is easy enough:

namedNumber = do
name <- identifier
val <- parens (fmap Left signedNumber <|> fmap Right definedValue)
return (name, val)

however because names can be used before they are defined the result
typegoes from being

type NamedNumber = (Name,Integer)

to

type NamedNumber = (Name,Either Integer Name)

Nothing too terrible so far. The messiness comes in when you
considerthe number of places that you have to replace a type 't' with
(Either t Name). I'd really like to avoid having to do this.

If I were using Prolog, I could finesse the problem by introducing
afree variable and filling it in when I come across the definition[*].
Logic variable backpatching. :-)

So one possibility would be to return a closure:

...
return $ \bindings -> (name,resolve val bindings)

resolve :: (Either t Name) -> Map Name t -> t

or something like that. Then when you get to the end, you apply the
bindings and voila, out pops the simple type. I'm not sure this will
work quite as well as it sounds.

This sounds like a common problem type. Is there a well known solution
to this sort of problem?

cheers,
Tom
[*] And then at the end use var/1 to look for undefined names. Urk.
Actually, if I were using Prolog in the way most Prolog programmers use
it, I wouldn't be thinking about the types.
-- 
Dr Thomas Conway
[EMAIL PROTECTED]

Silence is the perfectest herald of joy:
I were but little happy, if I could say how much.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: HDBC or HSQL

2007-07-31 Thread Alex Jacobson

Out of curiosity, can I ask what you are actually trying to do?

I am asking because I am trying to make HAppS a reasonable replacement 
for all contexts in which you would otherwise use an external relational 
database except those in which an external SQL database is a specific 
requirement.


-Alex-




Isto Aho wrote:

Hi,

I was also wandering between these different db-libs and thanks for your 
information.


I tried several (HDBC, HSQL, HaskellDB) and made only small trials.
HaskellDB has quite many examples on wiki that gave a quick start to 
further trials.
But, I wasn't able to tell that some of the fields have default values 
and then it

was already time to move on to the HSQL and HDBC trials.

Is it possible to use sql-array-types with HDBC with postgresql? I don't 
remember was this the
reason why I eventually tried HSQL - anyhow, it was rather difficult to 
get started with HDBC
but the src test cases helped here. One example in a wiki would do 
miracles :)


HSQL didn't have the array-types but it took only couple of hours to add 
"a sort of" support
for those. There are some problems though... (indexed table queries 
returning some nulls
is not yet working and ghci seems to be allergic to this)  I was even 
wondering, should I propose

a patch in some near future for this.

But if HDBC can handle those sql-arrays or if you can give a couple of 
hints, how to proceed
in order to add them there, given your view below, I'd be willing to try 
to help / to try to use HDBC.


br,
Isto

2007/7/30, John Goerzen <[EMAIL PROTECTED] 
>:


On 2007-07-25, George Moschovitis <[EMAIL PROTECTED]
> wrote:
 > I am a Haskell newbie and I would like to hear your suggestions
regarding a
 > Database conectivity library:
 >
 > HSQL or HDBC ?
 >
 > which one is better / more actively supported?

I am the author of HDBC, so take this for what you will.

There were several things that bugged me about HSQL, if memory serves:

1) It segfaulted periodically, at least with PostgreSQL

2) It had memory leaks

3) It couldn't read the result set incrementally.  That means that if
you have a 2GB result set, you better have 8GB of RAM to hold it.

4) It couldn't reference colums in the result set by position, only by
name

5) It didn't support pre-compiled queries (replacable parameters)

6) Its transaction handling didn't permit enough flexibility

I initially looked at fixing HSQL, but decided it would be easier to
actually write my own interface from scratch.

HDBC is patterned loosely after Perl's DBI, with a few thoughts from
Java's JDBC, Python's DB-API, and HSQL mixed in.

I believe it has fixed all of the above issues.  The HDBC backends that
I've written (Sqlite3, PostgreSQL, and ODBC) all use Haskell's C memory
management tools, which *should* ensure that there is no memory
leakage.

I use it for production purposes in various applications at work,
connecting to both Free and proprietary databases.  I also use it in my
personal projects.  hpodder, for instance, stores podcast
information in
a Sqlite3 database accessed via HDBC.  I have found HDBC+Sqlite3 to be a
particularly potent combination for a number of smaller projects.

http://software.complete.org/hdbc/wiki/HdbcUsers
 has a list of some
programs that are known to use HDBC.  Feel free to add yours to it.

-- John

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




--
br,
Isto




___
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] Newbie question about Haskell skills progress

2007-07-31 Thread Donald Bruce Stewart
bf3:
> 
>Having only a couple of days of practice programming Haskell
>(but having read lots of books and docs), I find myself
>writing very explicit low level code using inner "aux"
>functions (accumulators and loops). Then I force myself  to
>revise the code, replacing these aux functions with suitable
>higher-order functions from the library. However, I would
>like to use these higher order functions right away, without
>using low-level aux constructs, which is most likely caused
>by my very long history of imperative programming...
> 
> 
>Is this the "normal" way of progressing in Haskell, or
>should I consider a different approach?

I think this is normal: you start with manual loops, and you learn the
names for each loop form over time, using the combinator forms once
you're familiar with them.

Thanks for the insight!

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


Re: [Haskell-cafe] Knuth Morris Pratt for Lazy Bytestrings implementation

2007-07-31 Thread Donald Bruce Stewart
jgbailey:
> I've implemented KMP string searching for lazy bytestrings, and I'd
> like some help improving the performance of the code. I'd also like to
> know if it doesn't look correct - I've tested it pretty extensively
> but you never know ...
> 
> I've been testing on a 7 MB file, where the search sequence is not
> found. Using strict byestrings, lazy bytestrings, and regular strings,
> I've found my algorithm is about twice as slow as the strict version.
> Surprisingly, the strict version is a little bit *slower* than the
> regular strings version.
> 
> Thanks for any comments or help!
> 
> Justin

Also, be sure to compare against a naive search, optimised for
strict and lazy bytestrings,

http://hpaste.org/1803

If its not faster than those 2, then you're doing something wrong :)

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


Re: [Haskell-cafe] infinite list of random elements

2007-07-31 Thread Matthew Brecknell
Chad Scherrer:
> Ok, that looks good, but what if I need some random values elsewhere
> in the program? This doesn't return a new generator (and it can't
> because you never get to the end of the list).

To fix that, just replace the call to getStdGen with a call to
newStdGen, as has already been suggested by Sebastian.

Internally, newStdGen uses "split" to produce an independent generator,
and also updates the global generator. Thus, repeated calls to newStdGen
all return independent generators.

So, bringing together the suggestions so far, we get this:

> import Random
> import Array
> 
> -- from Lauri Alanko
> randomElts rg xs = map (arr !) (randomRs bds rg)
>   where bds = (1, length xs)
> arr = listArray bds xs
> 
> -- see discussion below
> inspect_stream = foldr (\x -> (seq x).(x:)) []
> 
> main = do
>   let foo g = drop 1000 $ inspect_stream $ randomElts g [10,2,42::Int]
>   g1 <- newStdGen
>   g2 <- newStdGen
>   print $ take 10 $ foo g1
>   print $ take 10 $ foo g2

No space leaks, independent lazy infinite random sequences.

I was somewhat dismayed that I needed to write inspect_stream to make
the demonstration using drop work without a stack overflow. This is
because the current implementation of randomRs is quite lazy, making it
very easy to build up huge thunks which blow the stack if you don't
evaluate them from the inside out.

For most applications, where you inspect the random numbers in roughly
the same order as you extract them from the sequence, this wouldn't be a
problem. Are there real applications (as opposed to toy demonstrations)
where this wouldn't be the case? I don't know, but perhaps the question
of whether randomRs should be more strict warrants some discussion.

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


Re: [Haskell-cafe] Operational Semantics of Haskell

2007-07-31 Thread Thomas Conway
On 8/1/07, Lewis-Sandy, Darrell <[EMAIL PROTECTED]> wrote:
> Is there a good source for the operational semantics of Haskell?  I am
> trying to squeeze the most efficiency out of a bit of code and am looking to
> remove unnecessary reductions.

You're kind of asking two questions - the first you ask explicitly,
the second "how do I optimize my program" others have already
answered.

The first question is a very tricky one for haskell. For example, see
the following:

http://www.cs.chalmers.se/~rjmh/Haskell/Messages/Archived.cgi?id=102

-- 
Dr Thomas Conway
[EMAIL PROTECTED]

Silence is the perfectest herald of joy:
I were but little happy, if I could say how much.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Knuth Morris Pratt for Lazy Bytestrings implementation

2007-07-31 Thread Duncan Coutts
On Wed, 2007-08-01 at 02:30 +0100, Tim Docker wrote:
> > If anyone can come up with a fast search implementation for strict
> > and/or lazy ByteStrings I'll include it in the bytestring package.
> 
> Out of curiosity, is it intentional or an oversight that findSubstrings
> is only implemented on strict ByteStrings? (at least with the libs
> supplied with ghc-6.6.1).

We never got round to it, which is something I'd like to correct.

Duncan

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


Re: [Haskell-cafe] Operational Semantics of Haskell

2007-07-31 Thread Donald Bruce Stewart
darrelll:
> 
>Is there a good source for the operational semantics of
>Haskell?  I am trying to squeeze the most efficiency out of
>a bit of code and am looking to remove unnecessary
>reductions.

The best thing is to look at the tricks on the performance wiki,

http://haskell.org/haskellwiki/Performance

The most useful tools are profiling (ghc -O2 -prof -auto-all ; then run
./a.out with +RTS -p), and reading the intermediate Core GHC produces.

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


Re: [Haskell-cafe] Knuth Morris Pratt for Lazy Bytestrings implementation

2007-07-31 Thread Donald Bruce Stewart
twd_gg:
> > If anyone can come up with a fast search implementation for strict
> > and/or lazy ByteStrings I'll include it in the bytestring package.
> 
> Out of curiosity, is it intentional or an oversight that findSubstrings
> is only implemented on strict ByteStrings? (at least with the libs
> supplied with ghc-6.6.1).
> 

Lazy functional programmers.

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


[Haskell-cafe] Re: Newbie question about Haskell skills progress

2007-07-31 Thread Benjamin Franksen
peterv wrote:
> Having only a couple of days of practice programming Haskell (but having
> read lots of books and docs), I find myself writing very explicit low
level
> code using inner "aux" functions (accumulators and loops). Then I force
> myself  to revise the code, replacing these aux functions with suitable
> higher-order functions from the library. However, I would like to use
these
> higher order functions right away, without using low-level aux constructs,
> which is most likely caused by my very long history of imperative
> programming.
> 
> Is this the "normal" way of progressing in Haskell, or should I consider a
> different approach?

I can't really judge whether a different approch might be better, but I
learned, and still learn it, in a very similar same way. I think it just
takes a while until one can see an abstraction right away, that is, even
before one starts writing anything down. I am not nearly as far as I'd like
to be in this regard, but I can now 'see' folds and maps quite early in the
process (still having some difficulty to 'see' an unfold, though). More and
more often I watch myself immediately writing down pipelines of (often not
yet implemented) functions, combined with dots, maps, etc, something I
wouldn't have done a few months ago.

Still, most code I write goes through multiple refactorings, searching
through libary docs (for some function that might already implement the
pattern), re-thinking and then re-designing my data structures, and so on,
before I have the feeling that the solution is acceptable and I can move
forward. While this process can be frustrating in the beginning (when you
follow one or the other blind alley, for instance), in the end the result
is extremely rewarding: I regularly end up with code that is 5 times
smaller than what I started with, looks deceptively simple, almost trivial
(although that may be subjective, caused by the my advanced understanding
of the problem), and seeing how in the end everything nicely falls into
place gives me the sheer pleasure.

Cheers
Ben

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


Re: [Haskell-cafe] Knuth Morris Pratt for Lazy Bytestrings implementation

2007-07-31 Thread Tim Docker
> If anyone can come up with a fast search implementation for strict
> and/or lazy ByteStrings I'll include it in the bytestring package.

Out of curiosity, is it intentional or an oversight that findSubstrings
is only implemented on strict ByteStrings? (at least with the libs
supplied with ghc-6.6.1).

Tim

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


Re: [Haskell-cafe] Knuth Morris Pratt for Lazy Bytestrings implementation

2007-07-31 Thread Duncan Coutts
On Wed, 2007-08-01 at 01:51 +0100, Tim Docker wrote:
> Now I wonder what that 7MB file might be? :-)
> 
> We (team TNT) implemented KMP over lazy bytestrings as part of our icfp
> 2007 contest entry. As I remember, for the DNA evaluator it gave modest
> speed improvements over more naïve searching. Our implementation was based
> upon this blog post:
> 
> http://twan.home.fmf.nl/blog/

If anyone can come up with a fast search implementation for strict
and/or lazy ByteStrings I'll include it in the bytestring package. The
current Data.ByteString search uses a rather under-optimised KMP
implementation. I say under-optimised as I think it typically gets
beaten by a naive search.

Duncan

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


Re: [Haskell-cafe] Knuth Morris Pratt for Lazy Bytestrings implementation

2007-07-31 Thread Tim Docker
Now I wonder what that 7MB file might be? :-)

We (team TNT) implemented KMP over lazy bytestrings as part of our icfp
2007 contest entry. As I remember, for the DNA evaluator it gave modest
speed improvements over more naïve searching. Our implementation was based
upon this blog post:

http://twan.home.fmf.nl/blog/

Tim

> I've implemented KMP string searching for lazy bytestrings, and I'd
> like some help improving the performance of the code. I'd also like to
> know if it doesn't look correct - I've tested it pretty extensively
> but you never know ...
>
> I've been testing on a 7 MB file, where the search sequence is not
> found. Using strict byestrings, lazy bytestrings, and regular strings,
> I've found my algorithm is about twice as slow as the strict version.
> Surprisingly, the strict version is a little bit *slower* than the
> regular strings version.
>
> Thanks for any comments or help!
>
> Justin
> ___
> 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


Fwd: Re: Re[4]: [Haskell-cafe] i need wxHaskell compiled for ghc 6.6.1 on Windows

2007-07-31 Thread shelarcy
Oops, I made mistake to send this mail only for Bulat.

--- Forwarded message ---
From: shelarcy <[EMAIL PROTECTED]>
To: "Bulat Ziganshin" <[EMAIL PROTECTED]>
Subject: Re: Re[4]: [Haskell-cafe] i need wxHaskell compiled for ghc 6.6.1 on 
Windows
Date: Wed, 01 Aug 2007 09:03:52 +0900

Hello Bulat,

On Wed, 25 Jul 2007 22:18:58 +0900, Bulat Ziganshin <[EMAIL PROTECTED]> wrote:
> Tuesday, July 24, 2007, 2:32:01 AM, you wrote:
>
>> So I put newer Windows binary on my project's file space.
>
>> http://sourceforge.net/project/showfiles.php?group_id=168626
>
> thank you very much!!! now i'm really happy - it works without any
> problems. the only question that remains - does this version supports
> unicode?

Yes. Current darcs repository version support only unicode
enabled version.

http://article.gmane.org/gmane.comp.lang.haskell.wxhaskell.general/198

So you can use UTF-8 string in your program.


Best Regards,

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


Re: [Haskell-cafe] Re: [Haskell] View patterns in GHC: Request?for?feedback

2007-07-31 Thread David Roundy
On Tue, Jul 31, 2007 at 04:04:17PM -0700, Stefan O'Rear wrote:
> On Tue, Jul 31, 2007 at 03:31:54PM -0700, David Roundy wrote:
> > On Mon, Jul 30, 2007 at 11:47:46AM +0100, Jon Fairbairn wrote:
> > > ChrisK <[EMAIL PROTECTED]> writes:
> > > 
> > > > And the readability is destroyed because you cannot do any type 
> > > > inference in
> > > > your head.
> > > > 
> > > > If you see
> > > > 
> > > > {
> > > >  Matrix m = ;
> > > >  Matrix x = m * y;
> > > >  ...;
> > > > }
> > > > 
> > > > Then you know very little about the possible types of y
> > > > since can only conclude that:
> > > 
> > > [snippage] This is all very horrid, but as far as I can tell
> > > what I was proposing wouldn't lead to such a mess, except
> > > possibly via defaulting, which, as the least important
> > > aspect of the idea could easily be abandoned.
> > 
> > What your suggestion would do would be to make the type inferred for every
> > pattern-matched function polymorphic, which means that in order to
> > determine the correctness of a function you'd need to examine all other
> > modules.  Similarly, if you fail to include a type signature in some simple
> > pattern-matched function in a where clause, adding an import of another
> > module could make that function fail to compile (with an undeterminable
> > type error).
> 
> Excuse me?  One of the most critical properties of type classes is that
> adding new instances can never make old code that uses old instances
> stop compiling; the worst you could get is a definition conflict.

I see that I was wrong.  I was thinking of something like

foo :: C a => Int -> a
bar :: C a => a -> Int
baz :: Int -> Int

baz = bar . foo

and that this would compile if there was only one instance of class C.  But
I see that in fact it will fail to compile regardless, which makes sense.
-- 
David Roundy
Department of Physics
Oregon State University


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


Re: [Haskell-cafe] Re: HDBC or HSQL

2007-07-31 Thread david48
On 7/30/07, John Goerzen <[EMAIL PROTECTED]> wrote:
> On 2007-07-25, david48 <[EMAIL PROTECTED]> wrote:

> > HDBC Supports Mysql only through ODBC :(

> This is true, unless some MySQL hacker would like to contribute a native
> module.  I don't use MySQL myself and haven't had the time to write an
> interface to it.

I'd be glad to do it but I'm a newbie in haskell, so I don't know
where to get started.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] View patterns in GHC: Request?for?feedback

2007-07-31 Thread Stefan O'Rear
On Tue, Jul 31, 2007 at 03:31:54PM -0700, David Roundy wrote:
> On Mon, Jul 30, 2007 at 11:47:46AM +0100, Jon Fairbairn wrote:
> > ChrisK <[EMAIL PROTECTED]> writes:
> > 
> > > And the readability is destroyed because you cannot do any type inference 
> > > in
> > > your head.
> > > 
> > > If you see
> > > 
> > > {
> > >  Matrix m = ;
> > >  Matrix x = m * y;
> > >  ...;
> > > }
> > > 
> > > Then you know very little about the possible types of y
> > > since can only conclude that:
> > 
> > [snippage] This is all very horrid, but as far as I can tell
> > what I was proposing wouldn't lead to such a mess, except
> > possibly via defaulting, which, as the least important
> > aspect of the idea could easily be abandoned.
> 
> What your suggestion would do would be to make the type inferred for every
> pattern-matched function polymorphic, which means that in order to
> determine the correctness of a function you'd need to examine all other
> modules.  Similarly, if you fail to include a type signature in some simple
> pattern-matched function in a where clause, adding an import of another
> module could make that function fail to compile (with an undeterminable
> type error).

Excuse me?  One of the most critical properties of type classes is that
adding new instances can never make old code that uses old instances
stop compiling; the worst you could get is a definition conflict.

Stefan


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


Re: [Haskell-cafe] Exiting GLUT application

2007-07-31 Thread Dave Tapley
Excellent, thank you Marc your advice worked perfectly.

For reference the corrected code reads:

> import Graphics.UI.GLUT
> main = do
> getArgsAndInitialize
> createWindow ""
> actionOnWindowClose $= ContinueExectuion
> mainLoop

Dave,


On 31/07/07, Marc A. Ziegert <[EMAIL PROTECTED]> wrote:
> in old glut, the main loop was the core of the single threaded program. 
> exiting it did mean to exit the program completely.
> in freeglut, you have alternatives. but for compatibility, it defaults to the 
> old behaviour.
>
> 
>
> - marc
>
>
> Am Dienstag, 31. Juli 2007 19:16 schrieb Dave Tapley:
> > Hi everyone, I have the following skeleton GLUT code:
> >
> > > import Graphics.UI.GLUT
> > > main = do
> > > getArgsAndInitialize
> > > createWindow ""
> > > mainLoop
> >
> > It loads into both hugs and ghci fine and when 'main' is evaluated an
> > empty window opens as expected.
> > However when closing the window (clicking the window manager's x
> > button) both hugs and ghci exit with the window, as opposed to
> > returning to the the 'Main>' prompt.
> >
> > I suspect I need some callback to exit the GUI cleanly?
> >
> > Cheers,
> > Dave
> > ___
> > 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] Re: [Haskell] View patterns in GHC: Request?for?feedback

2007-07-31 Thread David Roundy
On Mon, Jul 30, 2007 at 11:47:46AM +0100, Jon Fairbairn wrote:
> ChrisK <[EMAIL PROTECTED]> writes:
> 
> > And the readability is destroyed because you cannot do any type inference in
> > your head.
> > 
> > If you see
> > 
> > {
> >  Matrix m = ;
> >  Matrix x = m * y;
> >  ...;
> > }
> > 
> > Then you know very little about the possible types of y
> > since can only conclude that:
> 
> [snippage] This is all very horrid, but as far as I can tell
> what I was proposing wouldn't lead to such a mess, except
> possibly via defaulting, which, as the least important
> aspect of the idea could easily be abandoned.

What your suggestion would do would be to make the type inferred for every
pattern-matched function polymorphic, which means that in order to
determine the correctness of a function you'd need to examine all other
modules.  Similarly, if you fail to include a type signature in some simple
pattern-matched function in a where clause, adding an import of another
module could make that function fail to compile (with an undeterminable
type error).

This isn't so horrid as C++, but also isn't nearly so beautiful as Haskell.
Admittedly, adding a type signature will make a function verifiably
correct, and avoid any of these ambiguities, but we really like type
inference, and it'd be a shame to introduce code that makes type inference
less powerful.

True, one could always forbid people to use the View class, but that sort
of defeats the purpose, and starts sounding once more like C++, where there
are language features that "shouldn't" be used... but just imagine what
would happen to your type checking, if someone decided that it'd be clever
to use [a] as a view for Integer using a Peano representation? Yikes! (Or
Integer as a view for [a] describing the length?)

Admittedly, havoc would also be wreaked if someone declared [a] to be an
instance of Num, and that's the risk one takes when using type
classes... but that's why it's nice that there is a convenient way to write
code that *doesn't* use type classes.
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Exiting GLUT application

2007-07-31 Thread Marc A. Ziegert
in old glut, the main loop was the core of the single threaded program. exiting 
it did mean to exit the program completely.
in freeglut, you have alternatives. but for compatibility, it defaults to the 
old behaviour.



- marc


Am Dienstag, 31. Juli 2007 19:16 schrieb Dave Tapley:
> Hi everyone, I have the following skeleton GLUT code:
> 
> > import Graphics.UI.GLUT
> > main = do
> > getArgsAndInitialize
> > createWindow ""
> > mainLoop
> 
> It loads into both hugs and ghci fine and when 'main' is evaluated an
> empty window opens as expected.
> However when closing the window (clicking the window manager's x
> button) both hugs and ghci exit with the window, as opposed to
> returning to the the 'Main>' prompt.
> 
> I suspect I need some callback to exit the GUI cleanly?
> 
> Cheers,
> Dave
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 


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


Re[2]: [Haskell-cafe] Newbie question about automatic memoization

2007-07-31 Thread Bulat Ziganshin
Hello peterv,

Tuesday, July 31, 2007, 11:06:23 PM, you wrote:

it is property of explicit *name* given to result of some expression.
for example, when you write

f x = g (x*x) (x*x)

result of x*x isn't stored because it may be very large and compiler
exactly follows your instruction - "calculate x*x two times" without
trying to do optimization that may turn out to pessimization (of
course, i mean that with *lazy* evaluation x*x is calculated only when
needed and it may become a pessimization to save value between its
usages as first and second argument)

when you write

f x = g t t where t=x*x

compiler gets an instruction to calculate x*x only once and share
calculated value between two parameters and it does just what you said

> Thanks! Is this is also the case when using let and where, or is this just
> syntactic sugar?

> -Original Message-
> From: Jules Bean [mailto:[EMAIL PROTECTED] 
> Sent: Tuesday, July 31, 2007 5:09 PM
> To: Bryan Burgers
> Cc: peterv; haskell-cafe@haskell.org
> Subject: Re: [Haskell-cafe] Newbie question about automatic memoization

> Bryan Burgers wrote:
>> On 7/30/07, peterv <[EMAIL PROTECTED]> wrote:
>>> Does Haskell support any form of automatic memorization?
>>>
>>> For example, does the function
>>>
>>> iterate f x
>>>
>>> which expands to
>>>
>>> [x, f(x), f(f(x)), f(f(f(x))), .
>>>
>>> gets slower and slower each iteration, or can it take advantage of the
> fact
>>> that f is referentially transparent and hence can be "memoized / cached"?
>>>
>>> Thanks,
>>> Peter
>> 
>> For 'iterate' the answer does not really need to be memoized.

> Or, another way of phrasing that answer is 'yes'. The definition of 
> iteration does memoize - although normally one would say 'share' - the
> intermediate results.

>> 
>> I imagine the definition of 'iterate' looks something like this:
>> 
>> iterate f x = x : iterate f (f x)
>> 

> Haskell doesn't automatically memoize. But you are entitled to assume 
> that named values are 'shared' rather than calculated twice. For 
> example, in the above expression "x", being a named value, is shared 
> between (a) the head of the list and (b) the parameter of the function
> "f" inside the recursive call to iterate.

> Of course sharing "x" may not seem very interesting, on the outermost 
> call, but notice that on the next call the new "x" is the old "f x", and
> on the call after that the new "x" is "f (f x)" w.r.t the original "x".

> Jules

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


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] problem building lambdabot

2007-07-31 Thread Stefan O'Rear
On Tue, Jul 31, 2007 at 04:46:30PM -0400, Thomas Hartman wrote:
> Can anybody shout out about the latest version of ghc compatible with 
> building lambdabot?
> 
> http://www.cse.unsw.edu.au/~dons/lambdabot.html
> 
> shows it working on 6.4.1. 
> 
> can it build under anything more recent?

It works under GHC 6.6.1, if you pull the patch that I sent yesterday.

Stefan


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


Re: [Haskell-cafe] problem building lambdabot

2007-07-31 Thread Michael Vanier
Stefan just got it working yesterday with ghc 6.6.1 and sent me the patch.  I imagine it'll be in 
the darcs repo soon if it isn't already.


Mike

Thomas Hartman wrote:


Can anybody shout out about the latest version of ghc compatible with 
building lambdabot?


http://www.cse.unsw.edu.au/~dons/lambdabot.html

shows it working on 6.4.1.

can it build under anything more recent?

t.



*"Stefan O'Rear" <[EMAIL PROTECTED]>*
Sent by: [EMAIL PROTECTED]

07/30/2007 11:59 PM


To
Michael Vanier <[EMAIL PROTECTED]>
cc
"haskell-cafe@haskell.org" 
Subject
Re: [Haskell-cafe] problem building lambdabot








On Mon, Jul 30, 2007 at 08:54:12PM -0700, Michael Vanier wrote:
 > So, now that I've got all the libraries installed, the compile fails 
like

 > this:
 >
 > Building lambdabot-4.0...
 > [13 of 91] Compiling Lib.Parser   ( Lib/Parser.hs,
 > dist/build/lambdabot/lambdabot-tmp/Lib/Parser.o )
 >
 > Lib/Parser.hs:19:39:
 > Module `Language.Haskell.Syntax' does not export `as_name'
 >
 > Lib/Parser.hs:19:48:
 > Module `Language.Haskell.Syntax' does not export `qualified_name'
 >
 > Lib/Parser.hs:19:64:
 > Module `Language.Haskell.Syntax' does not export `hiding_name'
 >
 > Lib/Parser.hs:19:77:
 > Module `Language.Haskell.Syntax' does not export `minus_name'
 >
 > Lib/Parser.hs:19:89:
 > Module `Language.Haskell.Syntax' does not export `pling_name'
 >
 > I'm using the latest darcs pull of lambdabot along with ghc 6.6.1. 
 Anyone

 > have any ideas?
 >
 > Thanks in advance for all the help,
 >
 > Mike

Lambdabot is incompatible with GHC 6.6.1, because of changes in
undocumented internal modules that lambdabot really shouldn't be
importing in the first place.  I had an idea for how to avoid the nasty
dependency a few days ago, *tries to implement it*.

Stefan
[attachment "signature.asc" deleted by Thomas Hartman/ext/dbcom] 
___

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


---

This e-mail may contain confidential and/or privileged information. If you
are not the intended recipient (or have received this e-mail in error)
please notify the sender immediately and destroy this e-mail. Any
unauthorized copying, disclosure or distribution of the material in this
e-mail is strictly forbidden.

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


Re: [Haskell-cafe] problem building lambdabot

2007-07-31 Thread Thomas Hartman
Can anybody shout out about the latest version of ghc compatible with 
building lambdabot?

http://www.cse.unsw.edu.au/~dons/lambdabot.html

shows it working on 6.4.1. 

can it build under anything more recent?

t.




"Stefan O'Rear" <[EMAIL PROTECTED]> 
Sent by: [EMAIL PROTECTED]
07/30/2007 11:59 PM

To
Michael Vanier <[EMAIL PROTECTED]>
cc
"haskell-cafe@haskell.org" 
Subject
Re: [Haskell-cafe] problem building lambdabot






On Mon, Jul 30, 2007 at 08:54:12PM -0700, Michael Vanier wrote:
> So, now that I've got all the libraries installed, the compile fails 
like 
> this:
>
> Building lambdabot-4.0...
> [13 of 91] Compiling Lib.Parser   ( Lib/Parser.hs, 
> dist/build/lambdabot/lambdabot-tmp/Lib/Parser.o )
>
> Lib/Parser.hs:19:39:
> Module `Language.Haskell.Syntax' does not export `as_name'
>
> Lib/Parser.hs:19:48:
> Module `Language.Haskell.Syntax' does not export `qualified_name'
>
> Lib/Parser.hs:19:64:
> Module `Language.Haskell.Syntax' does not export `hiding_name'
>
> Lib/Parser.hs:19:77:
> Module `Language.Haskell.Syntax' does not export `minus_name'
>
> Lib/Parser.hs:19:89:
> Module `Language.Haskell.Syntax' does not export `pling_name'
>
> I'm using the latest darcs pull of lambdabot along with ghc 6.6.1. 
Anyone 
> have any ideas?
>
> Thanks in advance for all the help,
>
> Mike

Lambdabot is incompatible with GHC 6.6.1, because of changes in
undocumented internal modules that lambdabot really shouldn't be
importing in the first place.  I had an idea for how to avoid the nasty
dependency a few days ago, *tries to implement it*.

Stefan
[attachment "signature.asc" deleted by Thomas Hartman/ext/dbcom] 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] infinite list of random elements

2007-07-31 Thread Lennart Augustsson
Well, I don't know how many generators you need.  But I'm sure you can pass
them around in a way that doesn't leak.

On 7/31/07, Chad Scherrer <[EMAIL PROTECTED]> wrote:
>
> Ok, that looks good, but what if I need some random values elsewhere
> in the program? This doesn't return a new generator (and it can't
> because you never get to the end of the list). Without using IO or ST,
> you'd have to thread the parameter by hand or use the State monad,
> right? This is where I was leaking space before.
>
> Actually, this makes me wonder... I think what killed it before was
> that the state was threaded lazily through the various (= very many)
> calls. I suppose a State' monad, strict in the state, could help here.
> I wonder how performance for this would compare with IO or ST. Might
> have to try that sometime...
>
> Chad
>
> On 7/31/07, Lennart Augustsson <[EMAIL PROTECTED]> wrote:
> > No leak in sight.
> >
> >   -- Lennart
> >
> > import Random
> > import Array
> >
> > randomElts :: RandomGen g => g -> [a] -> [a]
> > randomElts _ [] = []
> > randomElts g xs = map (a!) rs
> >where a = listArray (1, n) xs
> > rs = randomRs (1, n) g
> >  n = length xs
> >
> > main = do
> > g <- getStdGen
> > let xs = randomElts g [10,2,42::Int]
> > print $ sum $ take 100 xs
> ___
> 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] infinite list of random elements

2007-07-31 Thread Chad Scherrer
On 7/31/07, Brandon S. Allbery KF8NH <[EMAIL PROTECTED]> wrote:
>
> On Jul 31, 2007, at 16:20 , Chad Scherrer wrote:
>
> > calls. I suppose a State' monad, strict in the state, could help here.
>
> You mean Control.Monad.State.Strict ?

Umm, yeah, I guess I do. Glad I hadn't started recoding it!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] infinite list of random elements

2007-07-31 Thread Brandon S. Allbery KF8NH


On Jul 31, 2007, at 16:20 , Chad Scherrer wrote:


calls. I suppose a State' monad, strict in the state, could help here.


You mean Control.Monad.State.Strict ?

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


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


Re: [Haskell-cafe] infinite list of random elements

2007-07-31 Thread Chad Scherrer
Ok, that looks good, but what if I need some random values elsewhere
in the program? This doesn't return a new generator (and it can't
because you never get to the end of the list). Without using IO or ST,
you'd have to thread the parameter by hand or use the State monad,
right? This is where I was leaking space before.

Actually, this makes me wonder... I think what killed it before was
that the state was threaded lazily through the various (= very many)
calls. I suppose a State' monad, strict in the state, could help here.
I wonder how performance for this would compare with IO or ST. Might
have to try that sometime...

Chad

On 7/31/07, Lennart Augustsson <[EMAIL PROTECTED]> wrote:
> No leak in sight.
>
>   -- Lennart
>
> import Random
> import Array
>
> randomElts :: RandomGen g => g -> [a] -> [a]
> randomElts _ [] = []
> randomElts g xs = map (a!) rs
>where a = listArray (1, n) xs
> rs = randomRs (1, n) g
>  n = length xs
>
> main = do
> g <- getStdGen
> let xs = randomElts g [10,2,42::Int]
> print $ sum $ take 100 xs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] infinite list of random elements

2007-07-31 Thread Lennart Augustsson
No leak in sight.

  -- Lennart

import Random
import Array

randomElts :: RandomGen g => g -> [a] -> [a]
randomElts _ [] = []
randomElts g xs = map (a!) rs
   where a = listArray (1, n) xs
rs = randomRs (1, n) g
 n = length xs

main = do
g <- getStdGen
let xs = randomElts g [10,2,42::Int]
print $ sum $ take 100 xs



On 7/31/07, Chad Scherrer <[EMAIL PROTECTED]> wrote:
>
> Thanks for your responses.
>
> Stefan, I appreciate your taking a step back for me (hard to judge
> what level of understanding someone is coming from), but the example
> you gave doesn't contradict my intuition either. I don't consider the
> output [IO a] a "list of tainted a's", but, as you suggest, a "list of
> IO actions, each returning an a". I couldn't return an IO [a], since
> that would force evaluation of an infinite list of random values, so I
> was using [IO a] as an intermediary, assuming I'd be putting it
> through something like (sequence . take n) rather than sequence alone.
> Unfortunately, I can't use your idea of just selecting one, because I
> don't have any way of knowing in advance how many values I'll need (in
> my case, that depends on the results of several layers of Map.lookup).
> Also, I'm using GHC 6.6, so maybe there have been recent fixes that
> would now allow my idea to work.
>
> Cale, that's interesting. I wouldn't have thought this kind of
> laziness would work in this context.
>
> Lennart, I prefer the purely functional approach as well, but I've
> been bitten several times by laziness causing space leaks in this
> context. I'm on a bit of a time crunch for this, so I avoided the
> risk.
>
> Sebastian, this seems like a nice abstraction to me, but I don't think
> it's the same thing statistically. If I'm reading it right, this gives
> a concatenation of an infinite number of random shuffles of a
> sequence, rather than sampling with replacement for each value. So
> shuffles [1,2] g
> would never return [1,1,...], right?
>
> Chad
>
> > I was thinking the best way to do this might be to first write this
> function:
> >
> > randomElts :: [a] -> [IO a]
> > randomElts [] = []
> > randomElts [x] = repeat (return x)
> > randomElts xs = repeat r
> >   where
> >   bds = (1, length xs)
> >   xArr = listArray bds xs
> >   r = do
> > i <- randomRIO bds
> > return (xArr ! i)
> >
> > Then I should be able to do this in ghci:
> >
> > > sequence . take 5 $ randomElts [1,2,3]
> > [*** Exception: stack overflow
> ___
> 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] curious hxt error

2007-07-31 Thread Albert Y. C. Lai

brad clawsie wrote:

i am having a problem with hxt, i was wondering if anyone here has
experience with it. in particular, i find that the xread function
chokes on xml files with xml declarations, and i am not sure why.

[...]

This is intended. Generally, wherever the HXT manual says "content" 
(e.g., the description of xread says "with the XML content parser"), it 
means the (one and only) top level element, i.e., the 


To parse a complete XML file, look for a parser that says "document", 
which means the whole thing, e.g., parseXmlDocument.


main = do
  xml <- getContents
  print $ head $ parseXmlDocument "test.xml" xml
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Knuth Morris Pratt for Lazy Bytestrings implementation

2007-07-31 Thread Justin Bailey
I've implemented KMP string searching for lazy bytestrings, and I'd
like some help improving the performance of the code. I'd also like to
know if it doesn't look correct - I've tested it pretty extensively
but you never know ...

I've been testing on a 7 MB file, where the search sequence is not
found. Using strict byestrings, lazy bytestrings, and regular strings,
I've found my algorithm is about twice as slow as the strict version.
Surprisingly, the strict version is a little bit *slower* than the
regular strings version.

Thanks for any comments or help!

Justin


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


Re: [Haskell-cafe] Newbie question about Haskell skills progress

2007-07-31 Thread Dougal Stanton
On 31/07/07, peterv <[EMAIL PROTECTED]> wrote:
>
>
>
>
> Having only a couple of days of practice programming Haskell (but having
> read lots of books and docs), I find myself writing very explicit low level
> code using inner "aux" functions (accumulators and loops). Then I force
> myself  to revise the code, replacing these aux functions with suitable
> higher-order functions from the library. However, I would like to use these
> higher order functions right away, without using low-level aux constructs,
> which is most likely caused by my very long history of imperative
> programming…

Seems sensible to me! It'll come with time, I'm sure.

I often find it useful to think about general abstractions and then
choose an approach from there:

- many-to-one -> fold
- many-to-many -> map
- one-to-many -> unfold

And so on in a similar fashion. This might mean you do something
stupid (as witnessed by my most recent visit to Haskell Cafe, where I
said some very silly things [1] but also got some enormously
clever/silly pointers [2]). But it's all part of life's rich pattern,
and I can't think of a nicer place to make a fool of one's self than
in this community.

[1]: 
[2]: 

> Is this the "normal" way of progressing in Haskell, or should I consider a
> different approach?

There are probably some people here who were imbibing type theory and
lambda calculus with their mammy's milk... but for the rest of us,
it's just one small step at a time.

Cheers

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


RE: [Haskell-cafe] Newbie question about automatic memoization

2007-07-31 Thread peterv
Thanks! Is this is also the case when using let and where, or is this just
syntactic sugar?

-Original Message-
From: Jules Bean [mailto:[EMAIL PROTECTED] 
Sent: Tuesday, July 31, 2007 5:09 PM
To: Bryan Burgers
Cc: peterv; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Newbie question about automatic memoization

Bryan Burgers wrote:
> On 7/30/07, peterv <[EMAIL PROTECTED]> wrote:
>> Does Haskell support any form of automatic memorization?
>>
>> For example, does the function
>>
>> iterate f x
>>
>> which expands to
>>
>> [x, f(x), f(f(x)), f(f(f(x))), .
>>
>> gets slower and slower each iteration, or can it take advantage of the
fact
>> that f is referentially transparent and hence can be "memoized / cached"?
>>
>> Thanks,
>> Peter
> 
> For 'iterate' the answer does not really need to be memoized.

Or, another way of phrasing that answer is 'yes'. The definition of 
iteration does memoize - although normally one would say 'share' - the 
intermediate results.

> 
> I imagine the definition of 'iterate' looks something like this:
> 
> iterate f x = x : iterate f (f x)
> 

Haskell doesn't automatically memoize. But you are entitled to assume 
that named values are 'shared' rather than calculated twice. For 
example, in the above expression "x", being a named value, is shared 
between (a) the head of the list and (b) the parameter of the function 
"f" inside the recursive call to iterate.

Of course sharing "x" may not seem very interesting, on the outermost 
call, but notice that on the next call the new "x" is the old "f x", and 
on the call after that the new "x" is "f (f x)" w.r.t the original "x".

Jules

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


[Haskell-cafe] Newbie question about Haskell skills progress

2007-07-31 Thread peterv
Having only a couple of days of practice programming Haskell (but having
read lots of books and docs), I find myself writing very explicit low level
code using inner "aux" functions (accumulators and loops). Then I force
myself  to revise the code, replacing these aux functions with suitable
higher-order functions from the library. However, I would like to use these
higher order functions right away, without using low-level aux constructs,
which is most likely caused by my very long history of imperative
programming.

 

Is this the "normal" way of progressing in Haskell, or should I consider a
different approach?

 

Thanks,

Peter

 

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


Re: [Haskell-cafe] problem implementing an EDSL in Haskell

2007-07-31 Thread Conal Elliott
Hi Daniil,

oops -- i just noticed this response from you from weeks ago.  i'm guessing
your question is all resolved for you by now.  if not, please say so.

cheers,  - Conal

On 6/25/07, Daniil Elovkov <[EMAIL PROTECTED]> wrote:
>
> Hi Conal
>
> 2007/6/24, Conal Elliott <[EMAIL PROTECTED]>:
> > By "embedded" DSL, we usually mean identifying meta-language (Haskell)
> > expressions with object language (DSL) expressions, rather than having
> an
> > "Exp" data type.  Then you just use meta-language variables as
> > object-language variables.  The new data types you introduce are then
> > domain-oriented rather than language-oriented.  Is there a reason that
> this
> > kind of "embedded" approach doesn't work for you?
>
> Hmm, sorry, I must admit I didn't quite get it.
>
> However, in the situation I described, I don't just have an "Exp" data
> type, rather have it (and probably some other data types) typeful.
> Which lets me leverage the meta-language's (Haskell's) typing rules to
> enforce correctness of my DS language's expression correctness.
>
> I absolutely didn't want to make an accent on "embedded". Sorry, if
> that introduced some confusion. And that's not important or principal
> to me, it's just how I called it.
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] RE: Definition of the Haskell standard library

2007-07-31 Thread brad clawsie
> The problem with generating one of those is what manages it? What
> package would it belong to etc.

the same package that provides us with our interactive hackage prompt

rebuilding a central index will be a logical post-process for the
installation function
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] RE: Definition of the Haskell standard library

2007-07-31 Thread Chris Smith
Duncan Coutts <[EMAIL PROTECTED]> wrote:
> What is missing from the local docs is a single integrated index page
> that lists all the modules and then links off to the various packages's
> docs like we have on the ghc website.
> 
> The problem with generating one of those is what manages it? What
> package would it belong to etc.

Locally, I've kludged things together to add to the documentation 
package that GHC builds.  That may be the wrong place, but it kinda 
works anyway.  This script gets you much of the way there (with some 
unfortunate line wrapping at the end that you'd have to fix).  Of 
course, the script does more than just build haddock; and there are 
several other quirks here to that were needed to get random stuff to 
work for some packages, and unfortunately there are a number of packages 
for which it seems that 'runhaskell Setup haddock' just doesn't work at 
all due to use of features in the source that haddock can't parse.

What it doesn't do is fix up the links to contents and index from the 
other packages so that they point back to the right place.

-- begin attached script --

#!/bin/sh

ghcver=`ls -d /usr/local/lib/ghc-* | sort`
ghcver=`expr match "$ghcver" '.*\(ghc-6.7.[0-9]*\)'`

sudo rm /usr/local/lib/${ghcver}/share
sudo ln -s /usr/local/share /usr/local/lib/${ghcver}/share
sudo cp ../ghc/libraries/libraries-*.txt /usr/local/share/ghc/doc/html

for ln in `cat packages.list`
do
d=${ln:0:1}
p=${ln:1}

echo ===
echo == BUILDING: $p
echo ===

echo $d $p

cd $p   || exit 1

if [ -d _darcs ]
then
   darcs pull   || exit 1
fi

if [ -f configure.in -o -f configure.ac ]
then
   autoreconf   || exit 1
fi

if [ -f Setup.hs -o -f Setup.lhs ]
then
   runhaskell Setup clean   || exit 1
   runhaskell Setup configure   || exit 1
   runhaskell Setup build   || exit 1

   if [ $d = "+" ]
   then
 runhaskell Setup haddock --html-location=/usr/local/share/ghc \
|| exit 1
   fi

   sudo runhaskell Setup install|| exit 1
elif [ -f Makefile -o -f Makefile.in -o -f Makefile.am ]
then

   if [ $d = "+" ]
   then
   echo "Don't know how to run haddock"
   exit 1
   fi

   make distclean   || true
   ./configure  || exit 1
   make || exit 1
   sudo make install|| exit 1
else
   echo "Don't know how to make $p"
   exit 1
fi

cd ..
done

ls /usr/local/share/*/doc/html/*/haddock.css   \
| grep -v '/usr/local/share/ghc'   \
| sed 's/\(\/usr\/local\/share\/.*\/doc\/html\/\([^/]*\)\)
\/haddock.css/cp -r \1 \/usr\/local\/share\/ghc\/doc\/html\/\2 ; echo \2 
> \/usr\/local\/share\/ghc\/doc\/html\/\2\/prologue.txt/' \
| sudo /bin/sh
ls ../ghc/libraries/*/prologue.txt \
| sed 's/\(\.\.\/ghc\/libraries\/\([^\/]*\)\/prologue.txt\)/cp \1 
\/usr\/local\/share\/ghc\/doc\/html\/\2/' \
| sudo /bin/sh
cd /usr/local/share/ghc/doc/html
sudo ./gen_contents_index

-- 
Chris Smith

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


[Haskell-cafe] Re: Haskell-Cafe Digest, Vol 47, Issue 237

2007-07-31 Thread Chad Scherrer
Maybe I'm going about this the wrong way, but using the State monad
for random numbers was always leaky for me. Any time I use it, I have
to go through and strategically place "seq"s to counter the excessive
laziness. IO and ST have worked well, and seem to be faster as well
(though that's purely self-anecdotal evidence). I'm stuck in IO anyway
for a lot of this (reading data from files to build my lookup tables),
so ST didn't seem worth the extra trouble either. Admittedly it would
have been good practice, though.

What monad do most people use for random numbers? If performance is an
issue, do you still use State? Generating an infinite list of randoms
seems like a good approach if you just use them in one place, but
beyond that you end up passing around the tail of the list at each
step, so then you may as well wrap the generator in State, I think.

Thanks,
Chad

> Chad Scherrer wrote:
> > I prefer the purely functional approach as well, but I've
> > been bitten several times by laziness causing space leaks in this
> > context. I'm on a bit of a time crunch for this, so I avoided the
> > risk.
>
> Well, space leaks won't magically disappear if you use  IO a .
>
> Regards,
> apfelmus
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Exiting GLUT application

2007-07-31 Thread Dave Tapley
Hi everyone, I have the following skeleton GLUT code:

> import Graphics.UI.GLUT
> main = do
> getArgsAndInitialize
> createWindow ""
> mainLoop

It loads into both hugs and ghci fine and when 'main' is evaluated an
empty window opens as expected.
However when closing the window (clicking the window manager's x
button) both hugs and ghci exit with the window, as opposed to
returning to the the 'Main>' prompt.

I suspect I need some callback to exit the GUI cleanly?

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


RE: [Haskell-cafe] RE: Definition of the Haskell standard library

2007-07-31 Thread Duncan Coutts
On Tue, 2007-07-31 at 17:26 +0100, Simon Peyton-Jones wrote:
> | I see it as a really big deal that documentation becomes fragmented when
> | one is using many packages, so that it's harder to find what you want.
> | In fact, I'd classify that as the single biggest reason that I don't use
> | many packages now
> 
> When you install packages A,B,C, the documentation for A,B,C (and
> nothing else) ought to be locally available as an integrated whole,
> much as at the GHC web site.  I don't know whether Cabal does, or
> could do, that, but it's surely what one would expect.

The docs for those packages would be available for packages installed
via cabal (assuming the user did the optional haddock step) and would
link to each other.

What is missing from the local docs is a single integrated index page
that lists all the modules and then links off to the various packages's
docs like we have on the ghc website.

The problem with generating one of those is what manages it? What
package would it belong to etc.

On some systems (windows, gnome) there are dedicated help viewers that
can help with this contents/index issue. haddock supports both (mshelp,
devhelp). I'm not sure everyone would find that a sufficient solution
however.

Duncan

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


Re: [Haskell-cafe] RE: Definition of the Haskell standard library

2007-07-31 Thread Stefan O'Rear
On Tue, Jul 31, 2007 at 05:26:31PM +0100, Simon Peyton-Jones wrote:
> | I see it as a really big deal that documentation becomes fragmented when
> | one is using many packages, so that it's harder to find what you want.
> | In fact, I'd classify that as the single biggest reason that I don't use
> | many packages now
> 
> When you install packages A,B,C, the documentation for A,B,C (and
> nothing else) ought to be locally available as an integrated whole,
> much as at the GHC web site.  I don't know whether Cabal does, or
> could do, that, but it's surely what one would expect.

I don't think that would be terribly hard.  We would need to modify
Haddock with the ability to generate links following a schema like
/usr/share/doc/libghc6-$lowercasepackagename/html/$modulepath.html; this
would be fairly easy with Haddock-GHC's ability to access package names
and ghc-pkg haddock data, assuming Cabal and Haddock-GHC are fixed to
work on the same system...

Stefan


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


RE: [Haskell-cafe] RE: Definition of the Haskell standard library

2007-07-31 Thread Simon Peyton-Jones
| I see it as a really big deal that documentation becomes fragmented when
| one is using many packages, so that it's harder to find what you want.
| In fact, I'd classify that as the single biggest reason that I don't use
| many packages now

When you install packages A,B,C, the documentation for A,B,C (and nothing else) 
ought to be locally available as an integrated whole, much as at the GHC web 
site.  I don't know whether Cabal does, or could do, that, but it's surely what 
one would expect.

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


Re: [Haskell-cafe] RE: Definition of the Haskell standard library

2007-07-31 Thread brad clawsie
On Tue, Jul 31, 2007 at 09:16:33AM -0600, Chris Smith wrote:
> If there could be built-in quality control in promoting certain 
> packages, that would be great. 

it needs to be more fine grained. a new version of a package may
indeed rollback some positive attributes (stability for example) that
a previous version demonstrated...perhaps intentionally (when an
author is choosing to break an api, etc), perhaps not (plain old bugs)

we already have "quality claims" of two kinds for hackage packages:
implicit (version number, 0.* indicating lack of maturity) and
explicit (stability: experimental, stable, etc). allowing two scores
to be maintained for "stability" - author score AND audience score,
seems like a good way of moderating claims. simply allow people with
haskell.org accounts to select a pulldown in the package listing with
options for the stability score, with obvious safety features (one
vote per account per package version, etc)






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


Re: [Haskell-cafe] Operational Semantics of Haskell

2007-07-31 Thread Neil Mitchell
Hi

> Is there a good source for the operational semantics of Haskell?  I am
> trying to squeeze the most efficiency out of a bit of code and am looking to
> remove unnecessary reductions.

You probably aren't after operational semantics - the compiler takes
your code and optimises it to something bearing little relation to the
original. Are you passing -O2? Have you read the performance wiki
page? http://haskell.org/haskellwiki/Performance

Thanks

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


[Haskell-cafe] RE: Definition of the Haskell standard library

2007-07-31 Thread Chris Smith
> On Tue, 2007-07-31 at 10:15 +0100, Simon Peyton-Jones wrote:
> > - Package X is "blessed"; lots of people have argued over its design,
> > it's stable, widely used, and actively maintained.  Changes to this
> > package goes through a quality-control process.

> > Then, in effect, the "standard library" is all the X packages.

Duncan Coutts <[EMAIL PROTECTED]> wrote:
> I'm not sure that belongs in the cabal file, afterall, being "blessed"
> is a central community consensus thing, not a distributed decision taken
> by each person writing the cabal file for their package. I can't make a
> blessed package by just saying that it is so.

Yes, pretty much.  The ideas mentioned in this thread for Hackage sound 
great.  I definitely was missing a lot there, as I thought of Hackage as 
just somewhere people could upload their libraries.  If there could be 
built-in quality control in promoting certain packages, that would be 
great.  Even greater would be if:

1. Hackage tracked which packages had this "blessed" status.

2. There were a simple automated way, as part of the GHC install or 
otherwise immediately visible without knowing about it ahead of time, to 
download the whole set and install them.

3. There were either (a) a single URL that can be used to see 
documentation for all of them without worrying about which package 
something is in first; or (b) something like Cabal's haddock and install 
steps would combine documentation for all installed packages into a 
single URL; or even better, (c) both.

I see it as a really big deal that documentation becomes fragmented when 
one is using many packages, so that it's harder to find what you want.  
In fact, I'd classify that as the single biggest reason that I don't use 
many packages now; they aren't documented at 
http://haskell.org/ghc/docs/latest/html/libraries/, and it's a pain to 
keep open several windows with documentation for different libraries.  
(I already have done it a lot for gtk2hs and happs, but at least it's a 
Big Deal to be using those, so one can justify the extra window!)

> So it's clear at the moment that the base package is blessed, changes to
> it go through the library submissions process. It's not so clear for the
> other packages that ghc has distributed and have often been taken to be
> the standard library. Many of them look more like Y's above (like
> parsec, regex-*).

I've always thought of at least these packages in the existing 
"standard" library as being pretty stable: base, arrows, stm, mtl, 
Cabal, haskell-src, template-haskell, network, process, directory, 
filepath, unix, random, parsec, and pretty.  Perhaps my perception has 
been skewed... but given how often these things are recommended, I'd 
hope they are stable.

> Even then though, I think Chris was looking for something slightly
> wider.

I'm not entirely sure I can articulate precisely what I'm looking for.  
It sounds like things are going in a reasonable direction.  I'll try to 
get my head around it, and see if I can pitch in somehow.

I was simply worried that from an outsider's perspective, several recent 
comments in various mailing list threads, IRC dicussions, etc. seemed to 
predict the demise of any standard library except for base -- which 
would be quite disturbing given that base is becoming smaller, not 
larger, over time.

> What is not clear
> to me yet is if we should just rely on mechanisms in hackage to
> distinguish the gems from the failed experiments or something more
> centralised.

Good question.  I would guess the best way to answer it is to 
simultaneously establish something centralized in the short term, and 
then try to develop the technological structures to make it obsolete.

-- 
Chris Smith

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


Re: [Haskell-cafe] Newbie question about automatic memoization

2007-07-31 Thread Jules Bean

Bryan Burgers wrote:

On 7/30/07, peterv <[EMAIL PROTECTED]> wrote:

Does Haskell support any form of automatic memorization?

For example, does the function

iterate f x

which expands to

[x, f(x), f(f(x)), f(f(f(x))), …

gets slower and slower each iteration, or can it take advantage of the fact
that f is referentially transparent and hence can be "memoized / cached"?

Thanks,
Peter


For 'iterate' the answer does not really need to be memoized.


Or, another way of phrasing that answer is 'yes'. The definition of 
iteration does memoize - although normally one would say 'share' - the 
intermediate results.




I imagine the definition of 'iterate' looks something like this:

iterate f x = x : iterate f (f x)



Haskell doesn't automatically memoize. But you are entitled to assume 
that named values are 'shared' rather than calculated twice. For 
example, in the above expression "x", being a named value, is shared 
between (a) the head of the list and (b) the parameter of the function 
"f" inside the recursive call to iterate.


Of course sharing "x" may not seem very interesting, on the outermost 
call, but notice that on the next call the new "x" is the old "f x", and 
on the call after that the new "x" is "f (f x)" w.r.t the original "x".


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


[Haskell-cafe] Operational Semantics of Haskell

2007-07-31 Thread Lewis-Sandy, Darrell
Is there a good source for the operational semantics of Haskell?  I am
trying to squeeze the most efficiency out of a bit of code and am looking to
remove unnecessary reductions.  

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


Re: [Haskell-cafe] RLE in Haskell: why does the type variable get instantiated?

2007-07-31 Thread Pekka Karjalainen
On 7/31/07, Chris Eidhof <[EMAIL PROTECTED]> wrote:
> Hey Haskell-Cafe,
>
> I was trying out the code in Dons's article [1], and I noticed a
> weird thing when doing it in GHCi. When binding the function
> composition to a variable, the type suddenly changes. I'm not
> completely sure why this happens. Is this because GHCi is in a monad
> and wants to find an instance for the type variable? Here's my GHCi
> session: [ ... ]

Apfelmus already explained why it happens. I'd like to add one thing.
If you are experimenting with GHCi, you can turn the restriction off
with the option -fno-monomorphism-restriction. In GHCi itself this is
given as follows:

Prelude> :set -fno-monomorphism-restriction

After giving this and entering the same things as in your original
message, the type of encode came out to be as follows:

Prelude Control.Arrow Data.List> let encode = map (length &&& head) . group
Prelude Control.Arrow Data.List> :t encode
encode :: (Eq a) => [a] -> [(Int, a)]

This option also saves some typing (of the variety you do on the
keyboard!) when you just want to use GHCi as a calculator:

Prelude Control.Arrow Data.List> let x = 5
Prelude Control.Arrow Data.List> let y = 6.3
Prelude Control.Arrow Data.List> x*y
31.5

Instead of Integer, the type of x is now x :: (Num t) => t without the
restriction, and I don't need to add fromInteger to the
multiplication.

I don't recommend you to use this option all the time, of course. It's
just a convenience.

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


Re: [Haskell-cafe] Re: Conditional compilation of Setup.hs

2007-07-31 Thread Duncan Coutts
On Tue, 2007-07-31 at 17:20 +0400, Bulat Ziganshin wrote:
> Hello Duncan,
> 
> Tuesday, July 31, 2007, 5:06:35 PM, you wrote:
> 
> >> #ifdef __CABAL_VERSION__ > 117
> >>
> >> Is something like this possible with Cabal?
> 
> > No, Cabal does not define any cpp defines like that.
> 
> фафшкб one of this year GSOC projects is "Cabal sections"
> impelementation which should allow to make parts of cabal files
> specific, for example, for windows and unix. may be this new feature
> will allow to check library version too?

This allows conditional compilation in the library/program code but not
in Setup.hs itself.

Duncan

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


[Haskell-cafe] Re: Definition of the Haskell standard library

2007-07-31 Thread Simon Marlow

Chris Smith wrote:
Can someone clarify what's going on with the standard library in 
Haskell?


As of right now, I can download, say, GHC from haskell.org/ghc and get a 
set of libraries with it.  I can visit 
http://haskell.org/ghc/docs/latest/html/libraries/, linked from the 
haskell.org home page, and see descriptions of all of those libraries.  
I can build with --make (or if I'm feeling masochistic, add several 
lines of -package options) and it works.  That's all great.


I've seen some stuff lately on -libraries and this list indicating that 
there's an effort to change this.  People asking whether something 
should be included in the standard library are being told that there is 
no standard library really.  I'm hearing that the only distinction that 
matters is "used by GHC" or "not used by GHC", and that being on hackage 
is as official as it gets.


Am I misunderstanding?
Is there something awesome about Hackage that I'm not seeing?


My take on it is this: Hackage is a pre-requisite for a comprehensive 
well-maintained standard library.  We don't have a comprehensive standard 
library yet, but from Hackage will emerge a large number of components that 
will someday be reviewed and filtered by a group of people who define the 
standard library.  This might be part of the Haskell prime effort, or a 
subsequent library standardisation process.


I agree that a standard library is important, I also believe it's vital 
that we have an effective distributed collaborative mechanism by which good 
libraries can emerge.  In the early days of the hierarchical libraries I 
think we tried to define a defacto standard set of libraries which we 
shipped with the various compilers; I now believe the distributed model 
will achieve better results in the long run, and the rate at which Hackage 
is growing seems to back this up.  This is why we developed the package 
system and Cabal, and why we no longer have a single global module 
namespace - every package author has the right to independently choose what 
their modules are called.


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


Re: [Haskell-cafe] Re: Conditional compilation of Setup.hs

2007-07-31 Thread Bulat Ziganshin
Hello Duncan,

Tuesday, July 31, 2007, 5:06:35 PM, you wrote:

>> #ifdef __CABAL_VERSION__ > 117
>>
>> Is something like this possible with Cabal?

> No, Cabal does not define any cpp defines like that.

фафшкб one of this year GSOC projects is "Cabal sections"
impelementation which should allow to make parts of cabal files
specific, for example, for windows and unix. may be this new feature
will allow to check library version too?


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


RE: [Haskell-cafe] Definition of the Haskell standard library

2007-07-31 Thread Duncan Coutts
On Tue, 2007-07-31 at 10:15 +0100, Simon Peyton-Jones wrote:

> All true, but not so helpful for Joe User.  For Joe, I think it might
> be helpful to have some easily-discoverable notion of which package
> quality and stability.
> 
> - Package X is "blessed"; lots of people have argued over its design,
> it's stable, widely used, and actively maintained.  Changes to this
> package goes through a quality-control process.
> 
> - Package Y is a bit specialised, but it's the result of work by a
> small group, and it's actively maintained.
> 
> - Package Z is designed, written, and maintained by one person.  That
> person has kindly put it on Hackage so that others may share it, but
> you probably don't want to rely on it unless you are happy to help
> maintain it.
> 
> 
> Then, in effect, the "standard library" is all the X packages.

Yes.

> I wonder if it'd help to have some  descriptions such as those above
> (better worded), and use them?  Cabal already has a "stability"
> indication, and that might serve, but we'd want to articulate much
> more clearly what it meant.

I'm not sure that belongs in the cabal file, afterall, being "blessed"
is a central community consensus thing, not a distributed decision taken
by each person writing the cabal file for their package. I can't make a
blessed package by just saying that it is so.

So it's clear at the moment that the base package is blessed, changes to
it go through the library submissions process. It's not so clear for the
other packages that ghc has distributed and have often been taken to be
the standard library. Many of them look more like Y's above (like
parsec, regex-*).

So yes, I think we should make this clear, and that blessed packages
that are covered by the library submission process should be clearly
recorded and publicised centrally.

Even then though, I think Chris was looking for something slightly
wider. For example ghc has distributed quite a range of packages that
would probably not be classified as X above, eg OpenGL, GLUT, OpenAL,
FGL, HGL, etc. These are not necessarily blessed packages but are known
to be of a high quality (ok, except HGL). Chris wanted to know this to
distinguish from the many other packages on hackage. What is not clear
to me yet is if we should just rely on mechanisms in hackage to
distinguish the gems from the failed experiments or something more
centralised.

Duncan

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


[Haskell-cafe] Re: Conditional compilation of Setup.hs

2007-07-31 Thread Duncan Coutts
On Tue, 2007-07-31 at 13:46 +0100, Bayley, Alistair wrote:
> I'd like to add a #ifdef to Takusen's Setup.hs, so that we can have a
> single source file that will compile with ghc-6.6 and ghc-6.6.1. With
> ghc-6.6 and Cabal-1.1.6.1 we use splitFileName and joinPaths from
> Distribution.Compat.FilePath. With ghc-6.6.1 (which includes
> Cabal-1.1.6.2) these have been moved to System.FilePath. I'd like to do
> something like the following:
> 
> #ifdef __CABAL_VERSION__ > 117
> import System.FilePath (splitFileName, combine)
> joinPaths = combine
> #else
> import Distribution.Compat.FilePath (splitFileName, joinPaths)
> #endif
> 
> Is something like this possible with Cabal?

No, Cabal does not define any cpp defines like that.

> It's either that, or make Takusen's install depend on filepath. I'm
> not sure which is the least desirable, but I'm open to suggestions.
> 
> To be fair, we already require our ghc-6.6 users to upgrade Cabal from
> 1.1.6 to 1.1.6.1, so making them install filepath instead perhaps
> isn't so bad, and is no more effort.

I'd got with filepath in that case.

Duncan

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


[Haskell-cafe] Conditional compilation of Setup.hs

2007-07-31 Thread Bayley, Alistair
I'd like to add a #ifdef to Takusen's Setup.hs, so that we can have a
single source file that will compile with ghc-6.6 and ghc-6.6.1. With
ghc-6.6 and Cabal-1.1.6.1 we use splitFileName and joinPaths from
Distribution.Compat.FilePath. With ghc-6.6.1 (which includes
Cabal-1.1.6.2) these have been moved to System.FilePath. I'd like to do
something like the following:

#ifdef __CABAL_VERSION__ > 117
import System.FilePath (splitFileName, combine)
joinPaths = combine
#else
import Distribution.Compat.FilePath (splitFileName, joinPaths)
#endif

Is something like this possible with Cabal?

It's either that, or make Takusen's install depend on filepath. I'm not
sure which is the least desirable, but I'm open to suggestions.

To be fair, we already require our ghc-6.6 users to upgrade Cabal from
1.1.6 to 1.1.6.1, so making them install filepath instead perhaps isn't
so bad, and is no more effort.

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] RLE in Haskell: why does the type variable get instantiated?

2007-07-31 Thread Arthur van Leeuwen


On 31-jul-2007, at 11:38, Chris Eidhof wrote:


Hey Haskell-Cafe,

I was trying out the code in Dons's article [1], and I noticed a  
weird thing when doing it in GHCi. When binding the function  
composition to a variable, the type suddenly changes. I'm not  
completely sure why this happens. Is this because GHCi is in a  
monad and wants to find an instance for the type variable?


Yes, that is mostly correct. GHCi does defaulting of types, and in  
this case

the type variable defaults to Integer.

With regards, Arthur.

--

  /\/ |   [EMAIL PROTECTED]   | Work like you don't need  
the money
/__\  /  | A friend is someone with whom | Love like you have never  
been hurt
/\/__ | you can dare to be yourself   | Dance like there's nobody  
watching




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


Re: [Haskell-cafe] Re: RLE in Haskell: why does the type variable get instantiated?

2007-07-31 Thread Brandon S. Allbery KF8NH


On Jul 31, 2007, at 6:00 , apfelmus wrote:


Chris Eidhof wrote:

When binding the function composition to a variable, the type
suddenly changes.

Prelude Control.Arrow List> :t map (length &&& head) . group
map (length &&& head) . group :: (Eq a) => [a] -> [(Int, a)]
Prelude Control.Arrow List> let encode = map (length &&& head) .  
group

Prelude Control.Arrow List> :t encode
encode :: [Integer] -> [(Int, Integer)]


In short, you have to supply a type signature

  encode :: (Eq a) => [a] -> [(Int, a)]
  encode = map (length &&& head) . group


Note that you can do this at the GHCi prompt like this:

> let encode :: (Eq a) => [a] -> [(Int,a)]; encode = map (length &&&  
head) . group


since you can't use multi-line declarations from the prompt.

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


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


Re: [Haskell-cafe] HDBC Laziness (was Re: HDBC or HSQL)

2007-07-31 Thread Henk-Jan van Tuyl
On Mon, 30 Jul 2007 00:56:30 +0200, John Goerzen <[EMAIL PROTECTED]>  
wrote:



I have heard from a number of people that this behavior is not very
newbie-friendly.  I can see how that is true.  I have an API revision
coming anyway, so perhaps this is the time to referse the default
laziness of HDBC calls (there would be a '-version of everything with
laziness enabled, still).

Thoughts?



I would like the libraries as stable as possible; it seems to me that, if  
you make the functions strict, there should be a new set of functions for  
this. This prevents a lot of work on existing applications. I get the  
impression that the bit rot rate is very high for Haskell applications.



--
Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://functor.bamikanarie.com
http://Van.Tuyl.eu/
--

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


Re: [Haskell-cafe] Definition of the Haskell standard library

2007-07-31 Thread Lutz Donnerhacke
* Simon Peyton-Jones wrote:
> Then, in effect, the "standard library" is all the X packages.  I wonder
> if it'd help to have some descriptions such as those above (better
> worded), and use them?  Cabal already has a "stability" indication, and
> that might serve, but we'd want to articulate much more clearly what it
> meant.

You need an external indicator, not an indicator from the package author.
It might be interesting to transform the dependency graph of cabalized
packaged at hackage into a ranking indicator.
It's like the Google Pagerank: Same benefit, same illness.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: RLE in Haskell: why does the type variable get instantiated?

2007-07-31 Thread apfelmus
Chris Eidhof wrote:
> When binding the function composition to a variable, the type
> suddenly changes.
> 
> Prelude Control.Arrow List> :t map (length &&& head) . group
> map (length &&& head) . group :: (Eq a) => [a] -> [(Int, a)]
> Prelude Control.Arrow List> let encode = map (length &&& head) . group
> Prelude Control.Arrow List> :t encode
> encode :: [Integer] -> [(Int, Integer)]

You've tripped over the Monomorphism Restriction.

  http://haskell.org/haskellwiki/Monomorphism_restriction
  http://haskell.org/onlinereport/decls.html#sect4.5.5

In short, you have to supply a type signature

  encode :: (Eq a) => [a] -> [(Int, a)]
  encode = map (length &&& head) . group

to get the polymorphic function type when type-classes like  Eq  or
especially  Num  are involved. Without signature, the compiler will
_default_ some the type variables mentioned in the class context to
Integer  or similar.

Note that definitions on the GHCi prompt will receive more defaulting
than those in Haskell source files. This is to make things like

  show []
  1+5

work at the prompt.

Also note that the monomorphism restriction only applies to constant
applicative forms, i.e. point-free definitions of values. In other words,

  encode x = map (length &&& head) . group $ x

will result in the proper polymorphic type.

Regards,
apfelmus

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


[Haskell-cafe] RLE in Haskell: why does the type variable get instantiated?

2007-07-31 Thread Chris Eidhof

Hey Haskell-Cafe,

I was trying out the code in Dons's article [1], and I noticed a  
weird thing when doing it in GHCi. When binding the function  
composition to a variable, the type suddenly changes. I'm not  
completely sure why this happens. Is this because GHCi is in a monad  
and wants to find an instance for the type variable? Here's my GHCi  
session:


Prelude> :m +Control.Arrow
Prelude Control.Arrow> :m + List
Prelude Control.Arrow List> :t map (length &&& head) . group
map (length &&& head) . group :: (Eq a) => [a] -> [(Int, a)]
Prelude Control.Arrow List> let encode = map (length &&& head) . group
Prelude Control.Arrow List> :t encode
encode :: [Integer] -> [(Int, Integer)]

Thanks,
-chris

[1]: http://cgi.cse.unsw.edu.au/~dons/blog/2007/07/31
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Definition of the Haskell standard library

2007-07-31 Thread Simon Peyton-Jones
| On the other hand, it's not entirely true that there's no standard
| library, it's just that it's borders are slightly fuzzy. For example, we
| do have the library change submission process for modifying the standard
| libraries. Up until now that has been taken to mean changes to the base
| package. That package is now being split up, so we'll have to think
| about what it'll apply to in the future.
|
| My opinion is that in the past it has been too difficult to get changes
| into the base library, that there's been too much stability at the
| expense of improving scope and quality. Making it easy to install new
| packages and upgrade existing standard libraries should make it easier
| to trial more major changes outside of the standard libs before
| proposing getting those changes integrated.

All true, but not so helpful for Joe User.  For Joe, I think it might be 
helpful to have some easily-discoverable notion of which package quality and 
stability.

- Package X is "blessed"; lots of people have argued over its design, it's 
stable, widely used, and actively maintained.  Changes to this package goes 
through a quality-control process.

- Package Y is a bit specialised, but it's the result of work by a small group, 
and it's actively maintained.

- Package Z is designed, written, and maintained by one person.  That person 
has kindly put it on Hackage so that others may share it, but you probably 
don't want to rely on it unless you are happy to help maintain it.


Then, in effect, the "standard library" is all the X packages.  I wonder if 
it'd help to have some  descriptions such as those above (better worded), and 
use them?  Cabal already has a "stability" indication, and that might serve, 
but we'd want to articulate much more clearly what it meant.

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


[Haskell-cafe] Re: infinite list of random elements

2007-07-31 Thread apfelmus
Chad Scherrer wrote:
> I prefer the purely functional approach as well, but I've
> been bitten several times by laziness causing space leaks in this
> context. I'm on a bit of a time crunch for this, so I avoided the
> risk.

Well, space leaks won't magically disappear if you use  IO a .

Regards,
apfelmus

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