RE: [Haskell-cafe] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread Simon Peyton-Jones
Congratulations, guys! Fast serialisation is one of the things that comes up 
over and over again, so an easy-to-use fast solution is a great step forward.

(Credit too to earlier pioneers, notably Bulat.)

Simon

| -Original Message-
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Donald
| Bruce Stewart
| Sent: 26 January 2007 02:51
| To: haskell@haskell.org
| Cc: haskell-cafe@haskell.org
| Subject: [Haskell-cafe] ANNOUNCE: binary: high performance, pure binary 
serialisation
|
|
| Binary: high performance, pure binary serialisation for Haskell
|  --
|
| The Binary Strike Team is pleased to announce the release of a new,
| pure, efficient binary serialisation library for Haskell, now available
| from Hackage:
|
|  tarball:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/binary/0.2
|  darcs:  darcs get http://darcs.haskell.org/binary
|  haddocks:   http://www.cse.unsw.edu.au/~dons/binary/Data-Binary.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble understanding records and existential typesy

2007-01-26 Thread Chris Kuklewicz
John Meacham wrote:
> On Wed, Jan 24, 2007 at 05:03:18PM -0800, Stefan O'Rear wrote:
>> Haskell-98 style records are widely acknowledged as sucking, and there are
>> something like half a dozen proposals all of which are widely acknowledged
>> as vastly superior.  Expect to be stuck with H98 records for the remainder
>> of time; see "bikeshed".
> 
> actually, the problem is that we keep calling them records. Haskell 98
> records are actually labeled fields, not records, and as labeled fields
> they perform just fine.
> 
> Not that records or named tuples or whatever you like to call them
> wouldn't be useful but they would likely be something in addition to labeled
> fields, not replacing it. (Not that the current labeled field mechanism
> couldn't be improved some.)
> 
> personally, something based on Daan's scoped labels proposal is the
> clear leader of the bunch.
> 
> 
> John

I also really liked Daan's "Extensible records with scoped labels", which is
available at http://www.cs.uu.nl/~daan/pubs.html#scopedlabels for those who
still have not read it.  The system seems very simple, but also seems to have
required moving beyond an imperative viewpoint to come up with.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: IO in lists

2007-01-26 Thread Magnus Therning
You are suggesting later in this thread that the old ListT could be used
to solve my initial problem.  I don't see how, so I'm wondering if you'd
mind sorting some things out for me?

On Tue, Jan 23, 2007 at 11:59:58 +0200, Yitzchak Gale wrote:
[..]
>test = do
> a <- liftIO getChar
> guard $ a /= 'q'
> return $ a `mplus` test

This piece has type problems.  I couldn't get ghci to accept it without
making some changes:

  test :: ListT IO Char
  test = do
  a <- liftIO getChar
  guard $ a /= 'q'
  (return a) `mplus` test

[..]
>test2 = runListT . mapM (liftIO print)

There are some type problems here too, and I don't really see how to fix
them.

  > :t liftIO
  liftIO :: (MonadIO m) => IO a -> m a
  > :t print
  print :: (Show a) => a -> IO ()
  > :t (liftIO print)
  Couldn't match expected type `IO a'
 against inferred type `a1 -> IO ()'
  In the first argument of `liftIO', namely `print'

I also don't quite see how 'mapM foo` can be applied to a ListT since
'mapM foo' would have the type [a] -> m [b] (a & b depending on foo).
Perhaps you didn't mean mapM but rather mapListT?
But using mapListT in a similar way:

  > runListT.mapListT (\ m -> m >>= mapM putChar) $ test

does not result in the desired interleaving.  Changing to using runListT
first also gives the wrong behaviour:

  > runListT test >>= mapM_ putChar

I am really confused about your statement that ListT as found in GHC 6.6
can be used to solve my problem.  I'd like to avoid using
unsafeInterleaveIO if there's a nice solution for it.  IMHO a solution
with ListT would be nice, so I'd really like to understand how to make
it work the way I want it.

/M

-- 
Magnus Therning (OpenPGP: 0xAB4DFBA4)
[EMAIL PROTECTED] Jabber: [EMAIL PROTECTED]
http://therning.org/magnus


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


Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-26 Thread Udo Stenzel
John Ky wrote:
> On 1/25/07, BBrraannddoonn SS.. AAllllbbeerryy 
> KKFF88NNHH <[EMAIL PROTECTED]> wrote:
>  I'm probably missing something, but:
> 
>  (a) Why not:
> 
>  data ANode = Branch { name :: String, description :: String,
>  children :: [AnyNode] }
>  | Leaf { name :: String, value :: String } -- this reuse
>  is legal
>  -- leaving Node available if you still need it
> 
> Would I be able to this?
> 
>getLeaves :: ANode -> [Leaf]


data Branch = Branch { name :: String, description :: String, children :: 
[AnyNode] }
data Leaf   = Leaf { name :: String, value :: String }

data AnyNode = Either Branch Leaf


Now if you absolutely insist on overloading the 'name' identifier, you
can do this:


data Branch = Branch { brName :: String, description :: String, children :: 
[AnyNode] }
data Leaf   = Leaf { lName :: String, value :: String }

data AnyNode = Either Branch Leaf

class HasName a where name :: a -> Name
instance HasName Branch where name = brName
instance HasName Leaf where name = lName
instance HasName AnyNode where name = either brName lName


Okay, you lose record update and construction syntax for AnyNode, but I
don't think that's so much of a loss.

On a side note, all this has nothing to do with OOP.  If you wanted to
simulate objects, you would "replace case by polymorphism", but I can't
demonstrate how to do that, since none of your "objects" has any
methods.


-Udo.
-- 
"Technology is a word that describes something that doesn't work yet."
-- Douglas Adams, JavaOne keynote, 1999


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


[Haskell-cafe] proposal: HaBench, a Haskell Benchmark Suite

2007-01-26 Thread Kenneth Hoste

Hello,

Following up and the threads on haskell and haskell-cafe, I'd like to  
gather ideas, comments and suggestions for a standarized Haskell  
Benchmark Suite.


The idea is to gather a bunch of programs written in Haskell, and  
which are representative for the Haskell community (i.e. apps,  
libraries, ...). Following the example of SPEC (besides the fact that  
the SPEC benchmarks aren't available for free), we would like to  
build a database containing performance measurements for the various  
benchmarks in the suite. Users should be able to submit their  
results. This will hopefully stimulate people to take performance  
into account when writing a Haskell program/library, and will also  
serve as a valuable tool for further optimizing both applications  
written in Haskell and the various Haskell compilers out there (GHC,  
jhc, nhc, ...).


This thread is meant to gather peoples thought on this subject.
Which programs should we consider for the first version of the  
Haskell benchmark suite?
How should we standarize them, and make them produce reliable  
performance measurement?
Should we only use hardware performance counters, or also do more  
thorough analysis such as data locality studies, ...
Are there any papers available on this subject (I know about the  
paper which is being written as we speak ICFP, which uses PAPI as a  
tool).


I have created a HaskellWiki page (http://www.haskell.org/haskellwiki/ 
HaBench) in order to centralize ideas and suggestions. Feel free to  
add anything, and if you're willing to contribute to this project (in  
any way), add your name to the wiki for future reference.


greetings,

Kenneth (a.k.a. boegel)

--

Statistics are like a bikini. What they reveal is suggestive, but  
what they conceal is vital (Aaron Levenstein)


Kenneth Hoste
ELIS - Ghent University
[EMAIL PROTECTED]
http://www.elis.ugent.be/~kehoste


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


RE: [Haskell-cafe] proposal: HaBench, a Haskell Benchmark Suite

2007-01-26 Thread Simon Peyton-Jones
| Following up and the threads on haskell and haskell-cafe, I'd like to
| gather ideas, comments and suggestions for a standarized Haskell
| Benchmark Suite.

Great idea.  Maybe this can subsume nofib.  I recommend reading the nofib paper 
though:
http://citeseer.ist.psu.edu/partain93nofib.html

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


RE: [Haskell-cafe] Type infer

2007-01-26 Thread Marco Túlio Gontijo e Silva
Em Qui, 2007-01-25 às 16:58 +, Simon Peyton-Jones escreveu:
> | -Original Message-
> | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Marco
> | Túlio Gontijo e Silva
> | Sent: 25 January 2007 12:57
> | To: haskell-cafe
> | Subject: Re: [Haskell-cafe] Type infer
> |
> | Em Qua, 2007-01-24 às 20:36 -0500, Bryan Donlan escreveu:
> | > Marco Túlio Gontijo e Silva wrote:
> | > > Hello,
> | > >
> | > > I'm trying to define a partition__ function that is like
> | > > Data.Set.partition, but use State Monad:
> | > >
> | > >> import Data.Set
> | > >> import Control.Monad.State
> | > >
> | > >> partition__ f =
> | > >> do
> | > >> snapshot <- get
> | > >> let
> | > >> (firsts, rest) = Set.partition f snapshot
> | > >> put rest
> | > >> return firsts
> | > >
> | > > When I try to infer it's type in ghci I got:
> | > >
> | > > $ ghci
> | > >___ ___ _
> | > >   / _ \ /\  /\/ __(_)
> | > >  / /_\// /_/ / /  | |  GHC Interactive, version 6.6, for Haskell 98.
> | > > / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
> | > > \/\/ /_/\/|_|  Type :? for help.
> | > >
> | > > Loading package base ... linking ... done.
> | > > Prelude> :load partition.hs
> | > > [1 of 1] Compiling Main ( partition.hs, interpreted )
> | > > Ok, modules loaded: Main.
> | > > *Main> :type partition__
> | > > partition__ :: (MonadState (Set a) t, Ord a) => (a -> Bool) -> t (Set a)
> | > >
> | > > Ok, then I add
> | > >
> | > >> partition__ :: (MonadState (Set a) t, Ord a) => (a -> Bool) -> t (Set
> | > > a)
> | > >
> | > > to the file and then:
> | > >
> | > > *Main> :reload
> | > > [1 of 1] Compiling Main ( partition.hs, interpreted )
> | > >
> | > > partition.hs:4:0:
> | > > Non type-variable argument in the constraint: MonadState (Set a) t
> | > > (Use -fglasgow-exts to permit this)
> | > > In the type signature for `partition__':
> | > >   partition__ :: (MonadState (Set a) t, Ord a) =>
> | > >  (a -> Bool) -> t (Set a)
> | > > Failed, modules loaded: none.
> | > >
> | > > Why do I need glasgow-exts to specify a type infered by GHCi without
> | > > -fglasgow-exts?
> | >
> | > I'd imagine the check that you're using -fglasgow-exts is performed when
> | > parsing type signatures from the parser. When you allow GHC to infer the
> | > type, it's pulling that from Control.Monad.State, which was compiled
> | > with -fglasgow-exts - it's simply not checking that all the types you
> | > might infer from there are legal without -fglasgow-exts.
> |
> | Makes sense, but isn't it a bug? It shouldn't be able infer types that
> | are not allowed without -fglasgow-exts, right?

> This isn't a type-soundness bug; but it could be considered a
> user-interface sort of bug.  After all, it's caused users to be
> puzzled.  It arises really because it was convenient for the
> implementation.

> Do go ahead and file it as a Trac bug if it tripped you up enough to be worth 
> fixing.  A fix should not take long, but might be a bit fiddly.

But if I can't write this type signature without -fglasgow-exts, I
thought that it couldn't infer this type. For me it's strange that it's
ok to have a very generic function if I don't have a type signature, but
if I write it the function will not be so generic. Shouldn't it infer
only types that could be written?

Thanks.

-- 
malebria
Marco Túlio Gontijo e Silva
Correio (MSN): [EMAIL PROTECTED]
Jabber (GTalk): [EMAIL PROTECTED]
Ekiga: [EMAIL PROTECTED]
IRC: [EMAIL PROTECTED]
 [EMAIL PROTECTED]
Skype: marcotmarcot
Telefone: 33346720
Celular: 98116720
Endereço:
Rua Paula Cândido, 257/201
Gutierrez 30430-260
Belo Horizonte/MG Brasil

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


[Haskell-cafe] Re: ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread Arie Peterson
Hello,


Donald Bruce Stewart wrote:

> Ok, I forgot one point. It is possible to automatically derive instances
> of Binary for your custom types, if they inhabit Data and Typeable,
> using an SYB trick. Load tools/derive/BinaryDerive.hs into ghci, and
> bring your type into scope, then run:
>
> *Main> mapM_ putStrLn . lines $ derive (undefined :: Drinks)

It would seem that one needs to rerun the script every time the type is
changed. That would be unfortunate. Perhaps I could have a go at writing a
template haskell function to derive those instances?

I also fear that the existing script does not handle types with more than
256 constructors correctly. While uncommon, those are not unrealistic.

Using DrIFT would probably automate the deriving just as well, but in my
particular situation TH support is easier to maintain than DrIFT support.


Greetings,

Arie

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


Re: [Haskell-cafe] Re: ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread Joel Reymont


On Jan 26, 2007, at 2:40 PM, Arie Peterson wrote:

Using DrIFT would probably automate the deriving just as well, but  
in my
particular situation TH support is easier to maintain than DrIFT  
support.


May I ask why TH is easier to maintain than DrIFT?

I'm not familiar with DrIFT.

Why would I prefer one over the other?

Thanks, Joel

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Re: ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread Dougal Stanton
Quoth Arie Peterson, nevermore,
> I also fear that the existing script does not handle types with more than
> 256 constructors correctly. While uncommon, those are not unrealistic.

"256 constructors ought to be enough for anybody"? ;-)

Seriously though, the thought of a type definition that heavyweight
quite terrifies me. I would be interested to see if such a thing could
be warranted and not more sensibly broken down into smaller (sets of)
units.

I like to think of types as being a bit like functions; and there is no
way I would ever think about a function with 256+ parameters. For a
start, my screen isn't wide enough for that kind of thing...

But, well done to the people responsible for the binary stuff. It looks
fab.

D.
-- 
Dougal Stanton <[EMAIL PROTECTED]>

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


[Haskell-cafe] Re: ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread Arie Peterson
Joel Reymont wrote:

> May I ask why TH is easier to maintain than DrIFT?
>
> I'm not familiar with DrIFT.

The reason is personal, and very silly. I only use ghc, so TH is available
automatically.

Like you, I have never used DrIFT, so I would have to get to know it, and
install it everywhere I want to compile my program. From a very quick look
at the DrIFT homepage, installation might be nontrivial on a windows
machine without some cygwin-like environment. At any rate, *for me* it's
more work than using TH, because I'm familiar with the latter and already
depend on its presence.

> Why would I prefer one over the other?

I wouldn't know. Please do not let my prejudice influence your preference
:-).


Greetings,

Arie

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


[Haskell-cafe] Re: proposal: HaBench, a Haskell Benchmark Suite

2007-01-26 Thread Al Falloon

Kenneth Hoste wrote:
The idea is to gather a bunch of programs written in Haskell, and which 
are representative for the Haskell community (i.e. apps, libraries, 
...).



A While ago I tried to write a Haskell version of John Harrops 
ray-tracer benchmark 
(http://www.ffconsultancy.com/free/ray_tracer/languages.html) but the 
performance was not very good (the OCaml version I based it on was at 
least 10x faster).


I would be happy to contribute my code to the benchmark suite if you are 
interested. Perhaps someone can point out obvious speed-ups that I 
missed while trying to improve the performance.


--
Alan Falloon

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


Re: [Haskell-cafe] Re: proposal: HaBench, a Haskell Benchmark Suite

2007-01-26 Thread David Roundy
On Fri, Jan 26, 2007 at 10:17:28AM -0500, Al Falloon wrote:
> Kenneth Hoste wrote:
> >The idea is to gather a bunch of programs written in Haskell, and which 
> >are representative for the Haskell community (i.e. apps, libraries, 
> >...).
> 
> A While ago I tried to write a Haskell version of John Harrops 
> ray-tracer benchmark 
> (http://www.ffconsultancy.com/free/ray_tracer/languages.html) but the 
> performance was not very good (the OCaml version I based it on was at 
> least 10x faster).
> 
> I would be happy to contribute my code to the benchmark suite if you are 
> interested. Perhaps someone can point out obvious speed-ups that I 
> missed while trying to improve the performance.

I would think that what we'd want to benchmark would be clean, optimized
actually-used code.  I.e. things like Data.Bytestring, so that we could see
how compilers differed on important code, or how the code generated on
different architectures differed.  e.g. if jhc beats ghc on amd64, the ghc
developers would probably be very curious as to why, and how to fix it.

Code that's not been properly optimized with respect to strictness, etc,
would fail to focus the tests on important optimizations of the compiler.
But of course, the benchmark code should also be clean, since we want to
ensure that our compilers are good enough that we can write useful
beautiful code that is also fast.

Just my $0.02.
-- 
David Roundy
http://www.darcs.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread Henning Thielemann

On Fri, 26 Jan 2007, Donald Bruce Stewart wrote:

> 
> Binary: high performance, pure binary serialisation for Haskell
>  -- 
> 
> The Binary Strike Team is pleased to announce the release of a new,
> pure, efficient binary serialisation library for Haskell, now available
> from Hackage:
> 
>  tarball:
> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/binary/0.2
>  darcs:  darcs get http://darcs.haskell.org/binary
>  haddocks:   http://www.cse.unsw.edu.au/~dons/binary/Data-Binary.html

I want to write out data in the machine's endianess, because that data 
will be post-processed by sox, which reads data in the machine's 
endianess. Is this also planned for the package?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread Tomasz Zielonka
On Fri, Jan 26, 2007 at 03:12:29PM +, Dougal Stanton wrote:
> Quoth Arie Peterson, nevermore,
> > I also fear that the existing script does not handle types with more than
> > 256 constructors correctly. While uncommon, those are not unrealistic.
> 
> "256 constructors ought to be enough for anybody"? ;-)
> 
> Seriously though, the thought of a type definition that heavyweight
> quite terrifies me.

Think about simple enumerations, eg. for keywords in a programming
language:

data Keyword = IF
 | THEN
 | ELSE
 | BEGIN
 | END
 ...

http://www.cs.vu.nl/grammars/cobol/:
Number of keywords: 420

Perhaps such examples could be treated differently, but I think it's
better to have a more general solution and not have to assume
unneccesary restrictions on user's datatypes.

> I would be interested to see if such a thing could be warranted and
> not more sensibly broken down into smaller (sets of) units.

I think in the above example the most sensible thing is to have all the
keywords in the same datatype.

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


[Haskell-cafe] Re: GHC concurrency runtime "breaks" every 497 (and a bit) days

2007-01-26 Thread Simon Marlow

Neil Davies wrote:

I've prototyped a fix for this issue which will now only wrap every
585,000 years or so. It also removes the 1/50th of a second timer
resolution for the runtime. This means that the additional 20ms (or
thereabouts) of delay in the wakeup has gone.

This means that GHC is now on a par with any other program, i.e. down
to the resolution of the  jiifies within the O/S.

I've done the non-Windows branch of the GHC.Conc - but I'll need some
help with the windows branch.

Anyone out there able to help with the intricacies of Windows?


Thanks Neil, just submit your patch and we'll look into making similar changes 
on Windows.


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


Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread Tomasz Zielonka
On Fri, Jan 26, 2007 at 02:16:22PM +1100, Donald Bruce Stewart wrote:
> We believe so, and its a bug if this is not the case.
> 
> The src documents the encoding format used for each type (we were unable
> to attach haddocks to instances.. grr.)
> 
> All data is encoded in Network order, and extended to 64 bits for word
> sized values (like Int). It should be possible to encode a structure
> with ghc on x86, and decode it on a sparc64 running hugs.

Did you consider using an encoding which uses variable number of bytes?
If yes, I would be interested to know your reason for not choosing such
an encoding. Efficiency?

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


Re: [Haskell-cafe] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread Tomasz Zielonka
On Fri, Jan 26, 2007 at 04:31:28PM +0100, Henning Thielemann wrote:
> On Fri, 26 Jan 2007, Donald Bruce Stewart wrote:
> 
> > 
> > Binary: high performance, pure binary serialisation for Haskell
> >  -- 
> > 
> > The Binary Strike Team is pleased to announce the release of a new,
> > pure, efficient binary serialisation library for Haskell, now available
> > from Hackage:
> > 
> >  tarball:
> > http://hackage.haskell.org/cgi-bin/hackage-scripts/package/binary/0.2
> >  darcs:  darcs get http://darcs.haskell.org/binary
> >  haddocks:   http://www.cse.unsw.edu.au/~dons/binary/Data-Binary.html
> 
> I want to write out data in the machine's endianess, because that data 
> will be post-processed by sox, which reads data in the machine's 
> endianess. Is this also planned for the package?

I also have to use a specific serialisation format. I guess we could
both simply use putWord8, but then we'll probably lose most of the
benefits of using the library.

Perhaps we could think about introducing some "encoding contexts", with
a default encoding that can be automatically derived, but also with the
ability to create one's own encodings?

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


[Haskell-cafe] Re: proposal: HaBench, a Haskell Benchmark Suite

2007-01-26 Thread Al Falloon

David Roundy wrote:

On Fri, Jan 26, 2007 at 10:17:28AM -0500, Al Falloon wrote:

Kenneth Hoste wrote:
The idea is to gather a bunch of programs written in Haskell, and which 
are representative for the Haskell community (i.e. apps, libraries, 
...).
A While ago I tried to write a Haskell version of John Harrops 
ray-tracer benchmark 
(http://www.ffconsultancy.com/free/ray_tracer/languages.html) but the 
performance was not very good (the OCaml version I based it on was at 
least 10x faster).


I would be happy to contribute my code to the benchmark suite if you are 
interested. Perhaps someone can point out obvious speed-ups that I 
missed while trying to improve the performance.


I would think that what we'd want to benchmark would be clean, optimized
actually-used code.  I.e. things like Data.Bytestring, so that we could see
how compilers differed on important code, or how the code generated on
different architectures differed.  e.g. if jhc beats ghc on amd64, the ghc
developers would probably be very curious as to why, and how to fix it.

Code that's not been properly optimized with respect to strictness, etc,
would fail to focus the tests on important optimizations of the compiler.
But of course, the benchmark code should also be clean, since we want to
ensure that our compilers are good enough that we can write useful
beautiful code that is also fast.


I tried to optimize it, but I couldn't approach the speed of the OCaml 
version. I followed the performance tuning advice from the Wiki, and had 
even resorted to writing the inner loop calculations using all unboxed 
doubles, but without significant improvements. This is exactly the kind 
of code that I write most often, and I would love to see improvements in 
the optimizations for this kind of numerically intensive code 
(especially without having to resort to compiler-specific unboxed 
representations).


I agree that common libraries like ByteString need to be well 
represented, but the original request additionally included programs 
that are representative of applications. A ray-tracer (even with a fixed 
scene and only one type of scene primitive) is a fairly nice 
approximation of a real numerical batch-oriented application while still 
being small enough to understand and modify. I expect thats why John 
chose it as his benchmark application in the first place.


I think it would also be a good idea to include SPJ's web server (I 
think its from an STM paper). A lot of the people outside the Haskell 
community will be able to relate better to metrics like pages/second.


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


Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread Malcolm Wallace
Tomasz Zielonka <[EMAIL PROTECTED]> wrote:

> Did you consider using an encoding which uses variable number of
> bytes? If yes, I would be interested to know your reason for not
> choosing such an encoding. Efficiency?

My Binary implementation (from 1998) used a type-specific number of bits
to encode the constructor - exactly as many as needed.  (If you were
writing custom instances, you could even use a variable number of bits
for the constructor, e.g. using Huffman encoding to make the more common
constructors have the shortest representation.)

The latter certainly imposes an extra time overhead on decoding, because
you cannot just take a fixed-size chunk of bits and have the value.  But
I would have thought that in the regular case, using a type-specific
(but not constructor-specific) size for representing the constructor
would be very easy and have no time overhead at all.

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


[Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-01-26 Thread Neil Bartlett
No doubt many of you will have seen the interview[1] on Channel9 with
Anders Hejlsberg, Herb Sutter, Erik Meijer and Brian Beckman. These are
some of Microsoft's top language gurus, and they discuss the future
evolution of programming languages. In particular they identify
composability, concurrency and FP as being important trends. However their
focus is on borrowing features of FP and bringing them into mainstream
imperative languages; principally C#.

Naturally the subject of Haskell comes up repeatedly throughout the
interview. Disappointingly they characterize Haskell as being an
impractical language, only useful for research. Erik Meijer at one point
states that programming in Haskell is too hard and compares it to assembly
programming! Yet the interviewees continually opine on the difficulty of
creating higher level abstractions when you can never be sure that a
particular block of imperative code is free of side effects. If there were
ever a case of the answer staring somebody in the face...

I found this interview fascinating but also exasperating. It's a real
shame that no reference was made to STM in Haskell. I don't know why the
interviewer doesn't even refer to the earlier Channel9 interview with
Simon Peyton Jones and Tim Harris - it appears to be the same interviewer.
Still, it's nice to see that ideas from Haskell specifically and FP
generally are gaining more and more ground in the mainstream programming
world. It also highlights some of the misconceptions that still exist and
need to be challenged, e.g. the idea that Haskell is too hard or is
impractical for real work.

[1] http://channel9.msdn.com/Showpost.aspx?postid=273697


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


Re: [Haskell-cafe] Re: proposal: HaBench, a Haskell Benchmark Suite

2007-01-26 Thread Chris Kuklewicz
Al Falloon wrote:
> David Roundy wrote:
>> On Fri, Jan 26, 2007 at 10:17:28AM -0500, Al Falloon wrote:
>>> Kenneth Hoste wrote:
 The idea is to gather a bunch of programs written in Haskell, and
 which are representative for the Haskell community (i.e. apps,
 libraries, ...).
>>> A While ago I tried to write a Haskell version of John Harrops
>>> ray-tracer benchmark
>>> (http://www.ffconsultancy.com/free/ray_tracer/languages.html) but the
>>> performance was not very good (the OCaml version I based it on was at
>>> least 10x faster).
>>>
>>> I would be happy to contribute my code to the benchmark suite if you
>>> are interested. Perhaps someone can point out obvious speed-ups that
>>> I missed while trying to improve the performance.
>>
>> I would think that what we'd want to benchmark would be clean, optimized
>> actually-used code.  I.e. things like Data.Bytestring, so that we
>> could see
>> how compilers differed on important code, or how the code generated on
>> different architectures differed.  e.g. if jhc beats ghc on amd64, the
>> ghc
>> developers would probably be very curious as to why, and how to fix itere 
>>
>> Code that's not been properly optimized with respect to strictness, etc,
>> would fail to focus the tests on important optimizations of the compiler.
>> But of course, the benchmark code should also be clean, since we want to
>> ensure that our compilers are good enough that we can write useful
>> beautiful code that is also fast.
> 
> I tried to optimize it, but I couldn't approach the speed of the OCaml
> version. I followed the performance tuning advice from the Wiki, and had
> even resorted to writing the inner loop calculations using all unboxed
> doubles, but without significant improvements. This is exactly the kind
> of code that I write most often, and I would love to see improvements in
> the optimizations for this kind of numerically intensive code
> (especially without having to resort to compiler-specific unboxed
> representations).
> 
> I agree that common libraries like ByteString need to be well
> represented, but the original request additionally included programs
> that are representative of applications. A ray-tracer (even with a fixed
> scene and only one type of scene primitive) is a fairly nice
> approximation of a real numerical batch-oriented application while still
> being small enough to understand and modify. I expect thats why Jo
> chose it as his benchmark application in the first place.

Writing numeric code that processes Doubles is hard to optimize.  See the
shootout example for the n-body problem:

http://haskell.org/haskellwiki/Shootout/Nbody
http://shootout.alioth.debian.org/debian/benchmark.php?test=nbody&lang=all

Some of the best work on making Haskell perform wonderfully at numerics is
summarized at http://haskell.org/haskellwiki/GHC/Data_Parallel_Haskell
and their status report http://www.cse.unsw.edu.au/~chak/papers/CLPKM06.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread Neil Davies

existing ecoding system - both the BER (Basic Encoding Rules) and the
PER (Packed Encoding Rules).

If you are looking to target a well supported standard - this would be the one.

Neil

On 26/01/07, Malcolm Wallace <[EMAIL PROTECTED]> wrote:

Tomasz Zielonka <[EMAIL PROTECTED]> wrote:

> Did you consider using an encoding which uses variable number of
> bytes? If yes, I would be interested to know your reason for not
> choosing such an encoding. Efficiency?

My Binary implementation (from 1998) used a type-specific number of bits
to encode the constructor - exactly as many as needed.  (If you were
writing custom instances, you could even use a variable number of bits
for the constructor, e.g. using Huffman encoding to make the more common
constructors have the shortest representation.)

The latter certainly imposes an extra time overhead on decoding, because
you cannot just take a fixed-size chunk of bits and have the value.  But
I would have thought that in the regular case, using a type-specific
(but not constructor-specific) size for representing the constructor
would be very easy and have no time overhead at all.

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


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


[Haskell-cafe] Re: [Haskell] FW: A history of Haskell

2007-01-26 Thread Justin Bailey

On 1/25/07, Simon Peyton-Jones <[EMAIL PROTECTED]> wrote:

Many of you will know that Paul Hudak, John Hughes, Phil Wadler and I have been 
working on a paper called

A History of Haskell: being lazy with class



Just wanted to say this paper is excellent, and actually a great tool
for learning Haskell. I read it about 2 months after I'd been
introduced to Haskell, and it made quite a few things about the
language clear to me. It's clearly not a tutorial, but somehow knowing
parts of the history made the language clearer.

Thanks for your (and all the other authors') effort!

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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and theFu ture of Languages

2007-01-26 Thread Steve Schafer
On Fri, 26 Jan 2007 17:13:43 - (GMT), you wrote:

>world. It also highlights some of the misconceptions that still exist and
>need to be challenged, e.g. the idea that Haskell is too hard or is
>impractical for real work.

Haskell _is_ hard, although I don't think it's _too_ hard, or I wouldn't
be here, obviously. Haskell is hard in the sense that in order to take
advantage of its ability to better solve your problems, you have to
THINK about your problems a lot more. Most people don't want to do that;
they want the quick fix served up on a platter. And even the
"intermediate" camp, the ones who are willing to invest some effort to
learn a better way, are only willing to go so far.

My analogy for this is the Sams PHOTOFACT series (If you're not old
enough to already know what these are, visit
http://www.samswebsite.com/photofacts.html). With an appropriate Sams
PHOTOFACT in hand, and some very basic skills with a voltmeter and maybe
an oscilloscope, you can diagnose and repair your TV with virtually no
understanding of electronics at all.

The audience for programming languages like Haskell is always going to
be small, because it appeals to those who want to understand how the TV
works, perhaps to the extent of being able to modify an existing TV or
even design one from scratch. And those kind of people are much fewer
and farther between than those who simply want to localize the problem
enough to be able to unplug the malfunctioning part and plug in a new
one.

It makes sense to publicize Haskell; you can't take advantage of
something you've never heard of. But I think evangelical effort is
largely wasted. The people who are going to gravitate towards Haskell
are the ones who are already searching for something better (they just
aren't sure what it is). The rest aren't really interested, and if at
some future point they become interested, they'll find the way on their
own.

Steve Schafer
Fenestra Technologies Corp.
http:/www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] newTArrayIO

2007-01-26 Thread Chad Scherrer

This seems like a natural thing to have around, but it's not in GHC 6.6...

newTArrayIO :: (Enum i, Ix i) => (i, i) -> a -> IO (TArray i a)
newTArrayIO (a,b) = liftM (TArray . listArray (a,b)) . sequence . zipWith
ignore [a..b] . repeat . newTVarIO
 where ignore = flip const

I haven't done any testing with this beyond type checking, but it seems like
it could be useful for similar cases to newTVarIO. Has anyone else played
with anything similar?

--

Chad Scherrer

"Time flies like an arrow; fruit flies like a banana" -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread John Meacham
On Fri, Jan 26, 2007 at 04:36:50PM +0100, Tomasz Zielonka wrote:
> Did you consider using an encoding which uses variable number of bytes?
> If yes, I would be interested to know your reason for not choosing such
> an encoding. Efficiency?

I am testing/benchmarking one right now I wrote for 'Integer', so far, I
think it may be better in time _and_ space! cache effects no doubt.

A nice thing about it is that for the common case, short ascii strings,
the serialized form takes up exactly as much as they would in C, very
nice. :)

John

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


Re: [Haskell-cafe] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread John Meacham
On Fri, Jan 26, 2007 at 04:42:48PM +0100, Tomasz Zielonka wrote:
> I also have to use a specific serialisation format. I guess we could
> both simply use putWord8, but then we'll probably lose most of the
> benefits of using the library.
> 
> Perhaps we could think about introducing some "encoding contexts", with
> a default encoding that can be automatically derived, but also with the
> ability to create one's own encodings?

one can use newtypes they would be faster in any case, I was thinking
something like:


> newtype XDRInt = XDRInt Int
> newtype XDRSTring sz = ...

and so forth, now if you build up a structure

> data NfsSattr = NfsSattr {
> mode :: XdrUnsigend,  -- protection mode bits
> uid :: XdrUnsigned,   -- owner user id 
> gid :: XdrUnsigned,   -- owner group id
> size :: XdrUnsigned,  -- file size in bytes
> atime :: XdrNfsTime,  -- time of last access
> mtime :: XdrNfsTime   -- time of last modification
> }

now you can speak nfs directly by serializing right from and to your
socket! :) a whole filesystem implemented in haskell in not so many
lines. very nice.

actually, I probably will write Data.Binary.Protocol.Xdr (better
location?). I actually do have a NFS server written in haskell in a much
more clunky way I could revive.

now, the only new primitives I would need are:

> alignTo :: Word8 -> Int -> Put
> alignTo _ _ = ...
>
> setAlignment :: Int -> Put
> setAlignment _ = ...

where alignTo would output some number of bytes in order to bring the
stream to the next alignment boundry specified, and setAlignment would
force the current alignment to be some value, without outputing any
bytes. Would these be doable? They would open up a lot of possibilities.

John


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


[Haskell-cafe] Re: Channel9 Interview: Software Composability and theFu ture of Languages

2007-01-26 Thread Benjamin Franksen
Steve Schafer wrote:
> Neil Bartlett wrote:
>>It also highlights some of the misconceptions that still exist and
>>need to be challenged, e.g. the idea that Haskell is too hard or is
>>impractical for real work.
> 
> Haskell _is_ hard, although I don't think it's _too_ hard, or I wouldn't
> be here, obviously. Haskell is hard in the sense that in order to take
> advantage of its ability to better solve your problems, you have to
> THINK about your problems a lot more. Most people don't want to do that;
> they want the quick fix served up on a platter. And even the
> "intermediate" camp, the ones who are willing to invest some effort to
> learn a better way, are only willing to go so far.

I agree, but I think it should be pointed out that primarily it is not
Haskell which is hard, it is Programming which is. Haskell only reflects
this better than the mainstream imperative languages. The latter encourage
and support operational reasoning, i.e. creating and understanding programs
by mentally modeling their execution on a machine. This form of reasoning
appeals to 'common sense', it is familiar to almost all (even completely
un-educated) people and is therefore easier acessible to them.

Haskell (more specifically: its purely functional core) makes such
operational reasoning comparatively hard(*). Instead it supports and
greatly simplifies denotional resp. equational reasoning(**), i.e. to
understand a program as an abstract formula with certain logical
properties; an abstract entity in its own right, independent of the
possibility of execution on a machine. This way of thinking is less
familiar to most people and thus appears 'difficult' and
even 'impractical' -- it requires a mental shift to a more abstract
understanding.(***)

What the hard-core 'common sense' type can't see and won't accept is that
denotational reasoning is strictly superior to operational reasoning (at
least with regard to correctness), if only because the latter invariably
fails to scale with the exploding number of possible system states and
execution paths that have to be taken into account for any non-trivial
program.

As Dijkstra once said, the main intellectual challenge for computer science
resp. programming is: how not to make a mess of it.

Those who don't want to think will invariably shoot themselves in the foot,
sooner or later. Their programs become a complex, unintelligible mess; the
prefered choice of apparently 'easier' or 'more practical' programming
languages often (but not always) reflects an inability or unwillingness to
appreciate the intellectual effort required to avoid building such a mess.

Cheers
Ben
(*) The downside of which is that it is also quite hard to reason about a
program's efficiency in terms of memory and CPU usage.
(**) At least the 'fast and loose' version of it, i.e. disregarding bottom
and seq.
(***) Many Haskell newcomers have described the feeling of being 'mentally
rewired' while learning programming in Haskell. IMO this is a very good
sign!

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


Re: [Haskell-cafe] Re: Channel9 Interview: Software Composability and theFu ture of Languages

2007-01-26 Thread Andrew Wagner

I thought it was very telling that, at the end of the interview, when
the interview asked, "In general, where is programming going?", the
responses were all things that haskell is good at. Shame it's such an
"impractical" language.

On 1/26/07, Benjamin Franksen <[EMAIL PROTECTED]> wrote:

Steve Schafer wrote:
> Neil Bartlett wrote:
>>It also highlights some of the misconceptions that still exist and
>>need to be challenged, e.g. the idea that Haskell is too hard or is
>>impractical for real work.
>
> Haskell _is_ hard, although I don't think it's _too_ hard, or I wouldn't
> be here, obviously. Haskell is hard in the sense that in order to take
> advantage of its ability to better solve your problems, you have to
> THINK about your problems a lot more. Most people don't want to do that;
> they want the quick fix served up on a platter. And even the
> "intermediate" camp, the ones who are willing to invest some effort to
> learn a better way, are only willing to go so far.

I agree, but I think it should be pointed out that primarily it is not
Haskell which is hard, it is Programming which is. Haskell only reflects
this better than the mainstream imperative languages. The latter encourage
and support operational reasoning, i.e. creating and understanding programs
by mentally modeling their execution on a machine. This form of reasoning
appeals to 'common sense', it is familiar to almost all (even completely
un-educated) people and is therefore easier acessible to them.

Haskell (more specifically: its purely functional core) makes such
operational reasoning comparatively hard(*). Instead it supports and
greatly simplifies denotional resp. equational reasoning(**), i.e. to
understand a program as an abstract formula with certain logical
properties; an abstract entity in its own right, independent of the
possibility of execution on a machine. This way of thinking is less
familiar to most people and thus appears 'difficult' and
even 'impractical' -- it requires a mental shift to a more abstract
understanding.(***)

What the hard-core 'common sense' type can't see and won't accept is that
denotational reasoning is strictly superior to operational reasoning (at
least with regard to correctness), if only because the latter invariably
fails to scale with the exploding number of possible system states and
execution paths that have to be taken into account for any non-trivial
program.

As Dijkstra once said, the main intellectual challenge for computer science
resp. programming is: how not to make a mess of it.

Those who don't want to think will invariably shoot themselves in the foot,
sooner or later. Their programs become a complex, unintelligible mess; the
prefered choice of apparently 'easier' or 'more practical' programming
languages often (but not always) reflects an inability or unwillingness to
appreciate the intellectual effort required to avoid building such a mess.

Cheers
Ben
(*) The downside of which is that it is also quite hard to reason about a
program's efficiency in terms of memory and CPU usage.
(**) At least the 'fast and loose' version of it, i.e. disregarding bottom
and seq.
(***) Many Haskell newcomers have described the feeling of being 'mentally
rewired' while learning programming in Haskell. IMO this is a very good
sign!

___
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: ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread John Meacham
On Fri, Jan 26, 2007 at 03:40:42PM +0100, Arie Peterson wrote:
> Using DrIFT would probably automate the deriving just as well, but in my
> particular situation TH support is easier to maintain than DrIFT support.

DrIFT as of 2.2.1 now supports binary for this package. using it is as
simple as this:

> import Data.Binary
> 
> data Foo = Foo Int Char | Bar Foo
> {-!derive: Binary -}

and then compiling with the following extra options to ghc

ghc -pgmF drift-ghc -F ...

now everything will be taken care of automatically.

John

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


Re: [Haskell-cafe] Re: proposal: HaBench, a Haskell Benchmark Suite

2007-01-26 Thread Jeremy Shaw
At Fri, 26 Jan 2007 07:23:26 -0800,
David Roundy wrote:

> I would think that what we'd want to benchmark would be clean, optimized
> actually-used code.  

Maybe there should be two versions of each benchmark:

 1) an clean, simple, idiomatic version, aka the code we would like to
write if performance was not an issue.

 2) a super-hand optimized version

This would hopefully show, which benchmarks have the biggest room for
improvement. And, it would provide information to the people working
on the compilers as to what optimizations are actually needed for that
test case.

j.

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


Re: [Haskell-cafe] newTArrayIO

2007-01-26 Thread Mattias Bengtsson
On Fri, 2007-01-26 at 11:34 -0800, Chad Scherrer wrote:
> This seems like a natural thing to have around, but it's not in GHC
> 6.6...
> 
> newTArrayIO :: (Enum i, Ix i) => (i, i) -> a -> IO (TArray i a)
> newTArrayIO (a,b) = liftM (TArray . listArray (a,b)) . sequence .
> zipWith ignore [a..b] . repeat . newTVarIO 
>   where ignore = flip const
> 
> I haven't done any testing with this beyond type checking, but it
> seems like it could be useful for similar cases to newTVarIO. Has
> anyone else played with anything similar?
> 

Agree. I learned lots regarding technologies that seemed like pure magic
before, like GADT's and fundeps etc.
Definately a good read.

Mattias


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


Re: [Haskell-cafe] newTArrayIO

2007-01-26 Thread Mattias Bengtsson
On Fri, 2007-01-26 at 23:26 +0100, Mattias Bengtsson wrote:
> On Fri, 2007-01-26 at 11:34 -0800, Chad Scherrer wrote:
> > This seems like a natural thing to have around, but it's not in GHC
> > 6.6...
> > 
> > newTArrayIO :: (Enum i, Ix i) => (i, i) -> a -> IO (TArray i a)
> > newTArrayIO (a,b) = liftM (TArray . listArray (a,b)) . sequence .
> > zipWith ignore [a..b] . repeat . newTVarIO 
> >   where ignore = flip const
> > 
> > I haven't done any testing with this beyond type checking, but it
> > seems like it could be useful for similar cases to newTVarIO. Has
> > anyone else played with anything similar?
> > 
> 
> Agree. I learned lots regarding technologies that seemed like pure magic
> before, like GADT's and fundeps etc.
> Definately a good read.


Hrrm. This was meant as a reply to Justin Bailey, sorry.


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


[Haskell-cafe] newbie timing question

2007-01-26 Thread Sean McLaughlin


Hello,

I'm trying to write a simple function to time an application.

-- this doesn't work

time f x =
  do n1 <- CPUTime.getCPUTime
 let res = f x in
   do n2 <- CPUTime.getCPUTime
  return (res,n2 - n1)

On a function that takes 8 seconds to complete, returns
(True,4600)

According to the documentation, this time is in picoseconds, making
this 46 microseconds.

I also tried

-- neither does this

time' f x =
  do n1 <- Time.getClockTime
 let res = f x in
   do n2 <- Time.getClockTime
  return (res,Time.diffClockTimes n2 n1)

It returns something on that scale for picoseconds.
How can I get a rough wall clock timing of functions?

Thanks!

Sean








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


Re: [Haskell-cafe] newbie timing question

2007-01-26 Thread Donald Bruce Stewart
seanmcl:
> 
> Hello,
> 
> I'm trying to write a simple function to time an application.
> 
> -- this doesn't work
> 
> time f x =
>   do n1 <- CPUTime.getCPUTime
>  let res = f x in
>do n2 <- CPUTime.getCPUTime
>   return (res,n2 - n1)
> 
> On a function that takes 8 seconds to complete, returns
> (True,4600)
> 
> According to the documentation, this time is in picoseconds, making
> this 46 microseconds.

That thunk you're allocating with 'let' isn't going to help much ;)

  http://haskell.org/haskellwiki/Timing_computations

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


Re: [Haskell-cafe] newbie timing question

2007-01-26 Thread Spencer Janssen

On Jan 26, 2007, at 4:56 PM, Sean McLaughlin wrote:


Hello,

I'm trying to write a simple function to time an application.

-- this doesn't work

time f x =
  do n1 <- CPUTime.getCPUTime
 let res = f x in
   do n2 <- CPUTime.getCPUTime
  return (res,n2 - n1)

On a function that takes 8 seconds to complete, returns
(True,4600)


Remember that Haskell is lazy -- res won't be evaluated until it is  
forced.  See the evaluate function in Control.Exception to force a  
value in the IO monad.



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


Re: [Haskell-cafe] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread Donald Bruce Stewart
lemming:
> 
> On Fri, 26 Jan 2007, Donald Bruce Stewart wrote:
> 
> > 
> > Binary: high performance, pure binary serialisation for Haskell
> >  -- 
> > 
> > The Binary Strike Team is pleased to announce the release of a new,
> > pure, efficient binary serialisation library for Haskell, now available
> > from Hackage:
> > 
> >  tarball:
> > http://hackage.haskell.org/cgi-bin/hackage-scripts/package/binary/0.2
> >  darcs:  darcs get http://darcs.haskell.org/binary
> >  haddocks:   http://www.cse.unsw.edu.au/~dons/binary/Data-Binary.html
> 
> I want to write out data in the machine's endianess, because that data 
> will be post-processed by sox, which reads data in the machine's 
> endianess. Is this also planned for the package?

The underlying Get and Put monads support explicit endian writes and
reads, which you can add to your instances explicitly:

http://www.cse.unsw.edu.au/~dons/binary/Data-Binary-Get.html#5
http://www.cse.unsw.edu.au/~dons/binary/Data-Binary-Put.html#5

So you can do that now. 

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


Re: [Haskell-cafe] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread Donald Bruce Stewart
tomasz.zielonka:
> On Fri, Jan 26, 2007 at 04:31:28PM +0100, Henning Thielemann wrote:
> > On Fri, 26 Jan 2007, Donald Bruce Stewart wrote:
> > 
> > > 
> > > Binary: high performance, pure binary serialisation for Haskell
> > >  
> > > -- 
> > > 
> > > The Binary Strike Team is pleased to announce the release of a new,
> > > pure, efficient binary serialisation library for Haskell, now available
> > > from Hackage:
> > > 
> > >  tarball:
> > > http://hackage.haskell.org/cgi-bin/hackage-scripts/package/binary/0.2
> > >  darcs:  darcs get http://darcs.haskell.org/binary
> > >  haddocks:   http://www.cse.unsw.edu.au/~dons/binary/Data-Binary.html
> > 
> > I want to write out data in the machine's endianess, because that data 
> > will be post-processed by sox, which reads data in the machine's 
> > endianess. Is this also planned for the package?
> 
> I also have to use a specific serialisation format. I guess we could
> both simply use putWord8, but then we'll probably lose most of the
> benefits of using the library.
> 
> Perhaps we could think about introducing some "encoding contexts", with
> a default encoding that can be automatically derived, but also with the
> ability to create one's own encodings?

Note that using Binary directly for non-Haskell structures is a bit like
using Read/Show instances for parsing non-Haskell structures: possible,
but not optimal. 

It would be better to use the underlying Get/Put monads available in
binary, with the low level support for explicit endian and word sized
writes/reads, to build a combinator library on top for these more
flexible parsing/binary requirements (like layering Parsec over ReadP or
HughesPJ).

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


Re: [Haskell-cafe] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread Donald Bruce Stewart
john:
> On Fri, Jan 26, 2007 at 04:42:48PM +0100, Tomasz Zielonka wrote:
> > I also have to use a specific serialisation format. I guess we could
> > both simply use putWord8, but then we'll probably lose most of the
> > benefits of using the library.
> > 
> > Perhaps we could think about introducing some "encoding contexts", with
> > a default encoding that can be automatically derived, but also with the
> > ability to create one's own encodings?
> 
> one can use newtypes they would be faster in any case, I was thinking
> something like:
> 
> 
> > newtype XDRInt = XDRInt Int
> > newtype XDRSTring sz = ...
> 
> and so forth, now if you build up a structure
> 
> > data NfsSattr = NfsSattr {
> > mode :: XdrUnsigend,  -- protection mode bits
> > uid :: XdrUnsigned,   -- owner user id 
> > gid :: XdrUnsigned,   -- owner group id
> > size :: XdrUnsigned,  -- file size in bytes
> > atime :: XdrNfsTime,  -- time of last access
> > mtime :: XdrNfsTime   -- time of last modification
> > }
> 
> now you can speak nfs directly by serializing right from and to your
> socket! :) a whole filesystem implemented in haskell in not so many
> lines. very nice.
> 
> actually, I probably will write Data.Binary.Protocol.Xdr (better
> location?). I actually do have a NFS server written in haskell in a much
> more clunky way I could revive.
> 
> now, the only new primitives I would need are:
> 
> > alignTo :: Word8 -> Int -> Put
> > alignTo _ _ = ...
> >
> > setAlignment :: Int -> Put
> > setAlignment _ = ...
> 
> where alignTo would output some number of bytes in order to bring the
> stream to the next alignment boundry specified, and setAlignment would
> force the current alignment to be some value, without outputing any
> bytes. Would these be doable? They would open up a lot of possibilities.

I think a StateT over Put/Get that carries around a count of the bytes
written, and the alignment, could be used. In general we envisage monad
transformers over Get/Put for adding things like bitwise writes, aligned
writes and so on.

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


Re: [Haskell-cafe] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread Chris Kuklewicz
Donald Bruce Stewart wrote:
> lemming:
>> On Fri, 26 Jan 2007, Donald Bruce Stewart wrote:
>>
>>> Binary: high performance, pure binary serialisation for Haskell
>>>  -- 
>>>
>>> The Binary Strike Team is pleased to announce the release of a new,
>>> pure, efficient binary serialisation library for Haskell, now available
>>> from Hackage:
>>> 
>>>  tarball:
>>> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/binary/0.2
>>>  darcs:  darcs get http://darcs.haskell.org/binary
>>>  haddocks:   http://www.cse.unsw.edu.au/~dons/binary/Data-Binary.html
>> I want to write out data in the machine's endianess, because that data 
>> will be post-processed by sox, which reads data in the machine's 
>> endianess. Is this also planned for the package?
> 
> The underlying Get and Put monads support explicit endian writes and
> reads, which you can add to your instances explicitly:
> 
> http://www.cse.unsw.edu.au/~dons/binary/Data-Binary-Get.html#5
> http://www.cse.unsw.edu.au/~dons/binary/Data-Binary-Put.html#5
> 
> So you can do that now. 
> 
> -- Don

The documentation has a small organization bug:

http://www.cse.unsw.edu.au/~dons/binary/Data-Binary-Get.html#5

The "Big-endian reads" section has both big endian and little endian functions.
Same for the "Little-endian reads" section. The page for Put is okay.

-- 
Chris

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


Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: binary: high performance, pure binary serialisation

2007-01-26 Thread Donald Bruce Stewart
tomasz.zielonka:
> On Fri, Jan 26, 2007 at 02:16:22PM +1100, Donald Bruce Stewart wrote:
> > We believe so, and its a bug if this is not the case.
> > 
> > The src documents the encoding format used for each type (we were unable
> > to attach haddocks to instances.. grr.)
> > 
> > All data is encoded in Network order, and extended to 64 bits for word
> > sized values (like Int). It should be possible to encode a structure
> > with ghc on x86, and decode it on a sparc64 running hugs.
> 
> Did you consider using an encoding which uses variable number of bytes?
> If yes, I would be interested to know your reason for not choosing such
> an encoding. Efficiency?

Yes, efficiency. If you look in tests/ there's a pretty heavy duty
benchmark we use to compare against C. Sticking to word sized writes
where possible is a big one (up to 10 fold).

Interestingly, I did write an aligned-only, host-endian layer, and it
was only some 10% faster on x86 over network order code.

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


Re: [Haskell-cafe] newbie timing question

2007-01-26 Thread Cale Gibbard

On 26/01/07, Sean McLaughlin <[EMAIL PROTECTED]> wrote:


Hello,

I'm trying to write a simple function to time an application.

-- this doesn't work

time f x =
   do n1 <- CPUTime.getCPUTime
  let res = f x in
do n2 <- CPUTime.getCPUTime
   return (res,n2 - n1)

On a function that takes 8 seconds to complete, returns
(True,4600)

According to the documentation, this time is in picoseconds, making
this 46 microseconds.



The statement "let res = f x" on its own causes essentially no
computation to occur. In your program, res is only getting computed
when the result of that do-block is finally *printed*. Before that,
it's just a pointer to some code which has yet to run. There's no
reason to compute res there, and so it isn't computed.

Note that the amount of time spent computing res might depend on just
how much of it is ever used by the program. Consider the case where
res is an infinite list, for example.

One easy solution would be to print the value of res between the
timers, though that will include the time for show and IO of course.

Another is to use Control.Exception.evaluate to force the evaluation
of res to occur in sequence with the other IO actions. Be aware that
if res is compound data, you may need to sequence the computation of
each of the components of res as well, as Control.Exception.evaluate
will only cause evaluation to occur to the point of determining the
top-level constructor (Weak Head Normal Form).

In order to control evaluation, there is a primitive in Haskell called
seq with the behaviour that evaluating seq x y will cause x to become
evaluated to WHNF before resulting in y. Note that this only occurs
when the seq itself is evaluated. Writing seq x x instead of x is
redundant, as evaluation is being forced anyway, by the time the seq
is seen. Using this, one can write functions which traverse
datastructures and cause them to be fully evaluated as soon as any
part of them is needed.

strictPair (x,y) = x `seq` y `seq` (x,y)
strictList xs = foldr seq xs xs

As a generalisation of this idea, in the module
Control.Parallel.Strategies, there is a class called NFData, with the
function rnf :: (NFData a) => a -> () (note that the type doesn't
really capture the evaluation side-effect -- when the empty tuple
returned is evaluated, the whole structure passed to rnf will be
forced.). Using this, we could write:
strictList xs = rnf xs `seq` xs

Anyway, that's the quick intro to subverting Haskell's lazy evaluation.

Before I go, there's another rather more honest way to do this sort of
thing, provided that you're more interested in the timing for your own
sake rather than having it be a value that your program is interested
in. GHC has a fairly extensive profiler which will produce beautifully
detailed reports on just how much time and memory were spent on each
part of your program, and it will even let you tag subexpressions to
watch and so on. For that, read
http://www.haskell.org/ghc/docs/latest/html/users_guide/profiling.html
Or if you're impatient, just build your program with the compiler
options -prof -auto-all, and then run the resulting executable with
+RTS -p -RTS on the commandline. It'll produce a profiling report
which will show the relative amount of time spent in each part of the
program, or +RTS -P -RTS, which will report the number of ticks and
actual memory used in addition to the percentages.

Hope this helps,

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


Re: [Haskell-cafe] Concurrency in Haskell

2007-01-26 Thread Alexy Khrabrov

Well, I'm a bit suspicious if the top references on Haskell
concurrency are either research papers or compiler manual sections.
How about some good ol' bundles of them codes to peruse and take
example from?  E.g., dining philosophers?

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


Re: [Haskell-cafe] Concurrency in Haskell

2007-01-26 Thread Donald Bruce Stewart
deliverable:
> Well, I'm a bit suspicious if the top references on Haskell
> concurrency are either research papers or compiler manual sections.
> How about some good ol' bundles of them codes to peruse and take
> example from?  E.g., dining philosophers?

The point was that there are *lots* of examples out there :)

Typing 'concurrency' into the http://haskell.org wiki search box gives
me:

http://www.haskell.org/haskellwiki/Concurrency_demos
http://www.haskell.org/haskellwiki/Concurrency_demos/Zeta
http://www.haskell.org/haskellwiki/Shootout/Cheap_concurrency
http://www.haskell.org/haskellwiki/Concurrency_demos/Two_reader_threads

http://www.haskell.org/haskellwiki/Libraries_and_tools/Concurrency_and_parallelism
...

A book chapter on concurrency in Haskell with software transactional
memory appeared just a few weeks ago:

http://research.microsoft.com/~simonpj/tmp/beautiful.ps

And of course the very fast examples on the shootout:


http://shootout.alioth.debian.org/gp4/benchmark.php?test=chameneos&lang=ghc&id=0
http://shootout.alioth.debian.org/gp4/benchmark.php?test=message&lang=all

Another good resource for simple concurrency tutorials is the 'Awkward
Squad':
http://research.microsoft.com/%7Esimonpj/Papers/marktoberdorf

Enjoy! Concurrency in Haskell is both fun and rich, since we have:

explicit lightweight threads:

http://haskell.org/ghc/docs/latest/html/libraries/base/Control-Concurrent.html

symmetric multiprocessor support:

http://www.haskell.org/ghc/dist/current/docs/users_guide/sec-using-smp.html

implicit parallelism:

http://haskell.org/ghc/docs/latest/html/libraries/base/Control-Parallel-Strategies.html

software transactional memory:
http://www.haskell.org/haskellwiki/Software_transactional_memory

locks:

http://haskell.org/ghc/docs/latest/html/libraries/base/Control-Concurrent-MVar.html

concurrent channels:

http://haskell.org/ghc/docs/latest/html/libraries/base/Control-Concurrent-Chan.html
   
transparently parallel arrays:
http://haskell.org/haskellwiki/GHC/Data_Parallel_Haskell
 
user level threads and scheduling:
http://www.seas.upenn.edu/~lipeng/homepage/unify.html

And more! As usual, http://haskell.org is the place to start.

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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-01-26 Thread Tim Newsham

impractical language, only useful for research. Erik Meijer at one point
states that programming in Haskell is too hard and compares it to assembly
programming!


He brings up a very good point.  Using a monad lets you deal with
side effects but also forces the programmer to specify an exact
ordering.  This *is* a bit like making me write assembly language
programming.  I have to write:

  > do {
  >x <- getSomeNum
  >y <- anotherWayToGetANum
  >return (x + y)
  > }

even if the computation of x and y are completely independant of
each other.  Yes, I can use liftM2 to hide the extra work (or
fmap) but I had to artificially impose an order on the computation.
I, the programmer, had to pick an order.

Ok, maybe "assembly language" is a bit extreme (I get naming, allocation
and garbage collection!) but it is primitive and overspecifies the
problem.

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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and theFu ture of Languages

2007-01-26 Thread Collin Winter

On 1/26/07, Steve Schafer <[EMAIL PROTECTED]> wrote:

On Fri, 26 Jan 2007 17:13:43 - (GMT), you wrote:
>world. It also highlights some of the misconceptions that still exist and
>need to be challenged, e.g. the idea that Haskell is too hard or is
>impractical for real work.

Haskell _is_ hard, although I don't think it's _too_ hard, or I wouldn't
be here, obviously. Haskell is hard in the sense that in order to take
advantage of its ability to better solve your problems, you have to
THINK about your problems a lot more. Most people don't want to do that;
they want the quick fix served up on a platter. And even the
"intermediate" camp, the ones who are willing to invest some effort to
learn a better way, are only willing to go so far.

My analogy for this is the Sams PHOTOFACT series (If you're not old
enough to already know what these are, visit
http://www.samswebsite.com/photofacts.html). With an appropriate Sams
PHOTOFACT in hand, and some very basic skills with a voltmeter and maybe
an oscilloscope, you can diagnose and repair your TV with virtually no
understanding of electronics at all.

The audience for programming languages like Haskell is always going to
be small, because it appeals to those who want to understand how the TV
works, perhaps to the extent of being able to modify an existing TV or
even design one from scratch. And those kind of people are much fewer
and farther between than those who simply want to localize the problem
enough to be able to unplug the malfunctioning part and plug in a new
one.

It makes sense to publicize Haskell; you can't take advantage of
something you've never heard of. But I think evangelical effort is
largely wasted. The people who are going to gravitate towards Haskell
are the ones who are already searching for something better (they just
aren't sure what it is). The rest aren't really interested, and if at
some future point they become interested, they'll find the way on their
own.


You have a PhD in computer science from Princeton, so your measure of
what's "hard" and what isn't in this regard is nearly worthless.

I find it incredibly insulting for you to assert that people who
complain about Haskell's difficulty are too lazy and aren't really
interested in a better solution. Maybe they just don't want to have to
take graduate-level classes in category theory to get their job done.
Maybe they want a solution that meets them half-way, one that doesn't
require that they understand how to build their own resistors and
capacitors in order to make their TV work again (to use your analogy).
That's what Meijer means when he says that Haskell is too hard.

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


Re: [Haskell-cafe] Channel9 Interview: Software Composability and theFu ture of Languages

2007-01-26 Thread Kirsten Chevalier

On 1/26/07, Collin Winter <[EMAIL PROTECTED]> wrote:

You have a PhD in computer science from Princeton, so your measure of
what's "hard" and what isn't in this regard is nearly worthless.

I find it incredibly insulting for you to assert that people who
complain about Haskell's difficulty are too lazy and aren't really
interested in a better solution. Maybe they just don't want to have to
take graduate-level classes in category theory to get their job done.


I've never taken a graduate-level class in category theory, or any
course on category theory, and I'm a Haskell implementor. So perhaps
the people who think they need to taken graduate-level classes in
category theory in order to use Haskell are barking up the wrong tree
(or perhaps I'm not a very good Haskell implementor, which is always
possible.)


Maybe they want a solution that meets them half-way, one that doesn't
require that they understand how to build their own resistors and
capacitors in order to make their TV work again (to use your analogy).
That's what Meijer means when he says that Haskell is too hard.



On the other hand, Meijer also has a PhD in computer science... is his
judgment on Haskell's difficulty or lack thereof worthless, too? If
not, then surely, judgments about whether Haskell is too hard can't
have much to do with who has a PhD and who doesn't.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"Would you be my clock if I promise not to hang you / Too close to the window
or the picture of the pope? / I won't set you back and I won't push you
forward / I just want to look in your face and see hope" -- Dom Leone
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Channel9 Interview: Software Composability and theFu ture of Languages

2007-01-26 Thread Donald Bruce Stewart
catamorphism:
> On 1/26/07, Collin Winter <[EMAIL PROTECTED]> wrote:
> >You have a PhD in computer science from Princeton, so your measure of
> >what's "hard" and what isn't in this regard is nearly worthless.
> >
> >I find it incredibly insulting for you to assert that people who
> >complain about Haskell's difficulty are too lazy and aren't really
> >interested in a better solution. Maybe they just don't want to have to
> >take graduate-level classes in category theory to get their job done.
> 
> I've never taken a graduate-level class in category theory, or any
> course on category theory, and I'm a Haskell implementor. So perhaps
> the people who think they need to taken graduate-level classes in
> category theory in order to use Haskell are barking up the wrong tree
> (or perhaps I'm not a very good Haskell implementor, which is always
> possible.)

I haven't done any graduate level category theory either, and I hack
Haskell 24/7! Let's form a union!!

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