Re: [Haskell-cafe] needsaname :: ([a] - Maybe (b, [a])) - (b - [a]) - [a] - [a]

2007-07-06 Thread Donald Bruce Stewart
felipe.lessa:
 I've written it to run over lists, but it would not be difficult to
 make it run over ByteStrings instead, and exploit the 'no-copying'
 effect on the bits of the stream which were not modified, which would
 be very handy for programs processing large bytestrings.
 
 I wonder if there's a efficient way of writting generic code that runs
 over String or over ByteString? Or at least with Lazy and Strict
 ByteStrings?
 
 
 
 I mean, I can write something like
 
 double :: Num a = a - a
 double x = x * 2
 
 and, e.g. if I want speed on Doubles (and am using GHC)
 
 {-# SPECIALIZE double :: Double - Double #-}
 
 but AFAIK there isn't a way of doing so with all the string types?
 
 
 And, if we're really lacking these mechanisms, is it because of a lack
 of formulation or because it isn't possible to generalise String
 operations?
 
 
 Thanks! =)
 

The String API seems rather large, so finding a single type class to
encapsulate expected operations tends to produce big, unwieldly classes.

Smaller apis work though: Monoid, for example.

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


Re: [Haskell-cafe] A very edgy language (was: A very nontrivial parser)

2007-07-06 Thread Donald Bruce Stewart
trebla:
 Andrew Coppin wrote:
 Personally, I just try to avoid *all* language extensions - mainly 
 because most of them are utterly incomprehensible. (But then, perhaps 
 that's just because they all cover extremely rare edge cases?)
 
 Haskell is an extremely rare edge case to begin with.
 
 Non-strict (most implementations lazy): rarely useful if you ask the 
 mainstream.
 
 Static typing: extreme paranoia.
 
 Purely functional: vocal minority of edgy people.
 
 Haskell syntax: map f xs is utterly incomprehensible to both the 
 mainstream why not map(f,xs) and the Schemers why not (map f xs). 
 Great way to alienate everyone out there.

Give #haskell is a far larger community than:

#lisp
#erlang
#scheme
#ocaml

As well as

#java
#javascript
#ruby
#lua
#d
#perl6

Maybe we need to reconsider where the (FP) mainstream is now? :-)

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


Re: [Haskell-cafe] A very edgy language

2007-07-06 Thread Donald Bruce Stewart
trebla:
 Donald Bruce Stewart wrote:
 Give #haskell is a far larger community than:
 
 #lisp
 #erlang
 #scheme
 #ocaml
 
 As well as
 
 #java
 #javascript
 #ruby
 #lua
 #d
 #perl6
 
 Maybe we need to reconsider where the (FP) mainstream is now? :-)
 
 I don't know. #math is larger than #accounting. Is it because math is 
 more mainstream than accounting? I bet it is because math is more 

math is more *interesting* than accounting? :-)

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


[Haskell-cafe] Write a library today! Was: Binary serialization, was Re: Abstraction leakAKa

2007-07-05 Thread Donald Bruce Stewart
drtomc:
 I was explaining Haskell to a perl/python hacking friend recently and
 characterized things thus:
 
 Perl is a horrible language with fantastic libraries.
 Haskell is a fantastic language with horrible libraries.
 
 Actually, many of the libraries that exist for Haskell *are*
 fantastic, it's just that Haskell lacks the *coverage* that Perl or
 Python have.

Yes, and we know exactly what to do about this. hackage.haskell.org is
growing by a few packages a week -- and anyone who binds to any C lib
should just upload their stuff.

So ... if you're reading this message -- please upload a library today,
and more than just a few of us might have nice Haskell jobs tomorrow!

-- Don

P.S.  Maybe we should run 'bindathons' or have CPAN-style contests to
get new libraries written? If you're bored, write a binding to some C
lib, that python, ruby or perl have already got a binding to.  Do it!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Binary serialization, was Re: Abstraction leak

2007-07-05 Thread Donald Bruce Stewart
p.f.moore:
 On 05/07/07, Jonathan Cast [EMAIL PROTECTED] wrote:
 Can't say I agree.  I've been learning Python, and have been very 
 un-impressed
 so far with its library coverage, which I would rate no better than (in 
 terms
 of the POSIX bindings, worse than) Haskell.
 
 It probably depends on your perspective. I've found lots of tasks that
 would be a simple library call in Python, but which require me to
 write the code myself in Haskell. Examples:
 
 * Send an email

Sounds like a job for MissingH?

 * Parse an ini file

Probably have to write your own Parsec-based parser here.

 * Gzip compress a data stream

We have a wonderful library for this!

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/zlib-0.3

 * Calculate the MD5 checksum of a file

In the Crypto library, or use the openssl binding posted a couple of
days ago:

   http://thread.gmane.org/gmane.comp.lang.haskell.cafe/24165/focus=24170 

 
 (Of course, I may just not have found the relevant library - that says
 something about discoverability rather than coverage, I guess).


Find more libraries on hackage:

http://hackage.haskell.org/packages/archive/pkg-list.html

 For bindings, Python's Windows bindings (pywin32) are superb, where
 Haskell's are minimal and unmaintained. Of course, that won't matter
 to you if you use POSIX...
 
 The one thing off the top of my head that Python had was Base64, but 
 that's 20
 lines of Haskell tops.  Aside from that, nothing.
 
 But that's 20 lines of code I don't want to write, and more, I don't
 know how to write (without looking up the definition of Base64).
 Having lots of these seemingly trivial helpers available out of the
 box is what library coverage means to me. (And Python does have lots
 of these - I don't know how Haskell fares in practice).
 
 I'm not trying to start (or fan) a flamewar, but it's interesting how
 different people's perspectives on libraries can be...

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


Re: [Haskell-cafe] interrupting an accept()ing thread

2007-07-05 Thread Donald Bruce Stewart
drtomc:
 On 7/6/07, Lukas Mai [EMAIL PROTECTED] wrote:
 Hello, cafe!
 
 Have you been reading my mind? See the other recent Cafe thread (um,
 titled something about System.Exit).
 
 Here's my solution:

...

If you've got small examples illustrating how to use the various
concurrency abstractions, feel free to add them to:

http://haskell.org/haskellwiki/Concurrency_demos

So we can build up a large body of examples for all the libs and tricks
out there.

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


Re: [Haskell-cafe] A very nontrivial parser

2007-07-05 Thread Donald Bruce Stewart
andrewcoppin:
 Jonathan Cast wrote:
 On Thursday 05 July 2007, Andrew Coppin wrote:
   
 ...OK, anybody have a solution that works in Haskell 98?
 
 
 Rank-2 types are perhaps /the/ most common, widely accepted extension to 
 Haskell 98, after the approved addendum for FFI and the draft addendum for 
 hierarchical modules.  I would really be concerned about using them (it's 
 certainly not like they're going to just disappear on you one day, like 
 say functional dependencies almost certainly will).  But that's just me.
   
 
 Personally, I just try to avoid *all* language extensions - mainly 
 because most of them are utterly incomprehensible. (But then, perhaps 
 that's just because they all cover extremely rare edge cases?)

Some cover edge cases, some are just useful.  What about:

* the FFI
* bang patterns
* pattern guards
* newtype deriving

Surely, fairly simple, useful. Used a lot? :-)
 
-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Abstraction leak

2007-07-04 Thread Donald Bruce Stewart
phil:
 On Sun, Jul 01, 2007 at 06:07:13PM +0100, Andrew Coppin wrote:
 I haven't actually tried, but presumably a TCP connection is represented 
 in the same way as a file, and so has the same problems.
 
 Basically doing binary I/O seems to be one of those things that in Haskell 
 falls into the class of it's possibly but annoyingly messy...
 
 In an ideal world there would be a 'deriving Serializable[1]' you

derive Binary
(use an external tool for this)

 could do on datatypes which would get this right. In a really ideal
 world, you could specify the data layout somehow[2][2a], which would

Directly in Haskell data type decls -- see the ICFP 05 paper on the
House OS, which added packing annotations, and bit syntax. In current
Haskell, you specify the layout in instances Storable or Binary.

 make integrating Haskell code into a wider distributed network of
 processes exchanging binary data a cinch. In a super really ideal

Definitely. See things like the zlib or iconv
Data.Binary/Data.ByteString bindings, for prototypes. The 'tar'
reader/writer on hackage.haskell.org is also a good example.

 world, you could operate on the packets in place in Haskell where
 possible and save the deserialization overhead...

Data.ByteString.* for this.
  
 Anyone trying to do any of this?

Yeah, its a bit of a hot topic currently. :)
Gotta chase Erlang for hacking network data.

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


Re: [Haskell-cafe] Re: Abstraction leak

2007-07-04 Thread Donald Bruce Stewart
drtomc:
 Anyone trying to do any of this?
 
 I've done some work in this area. I'm particularly interested in
 manipulating ASN.1 in haskell. Actually, my first use of Parsec was an
 ASN.1 parser. I'd done one previously in Spirit (the Boost C++ rip-off
 of parsec), but semantic actions were horrible in the extreme. Mmmm
 Parsec.
 
 In the indexing system I'm currently building in Haskell for my day
 job, I'm serializing several data structures, and using Data.Bits and
 Data.ByteString heavily.
 
 I was using HaXml, but I found it was very slow. So instead, I'm using
 an internal (within the indexing system) representation that is more
 akin to WBXML:
 
 import Data.ByteString as ByteString
 import Data.List as List
 import Data.Sequence as Seq
 
 data DocTree
= DocElem ByteString [(ByteString,ByteString)] [DocTree]
| DocText ByteString
 
 serialize tree = ByteString.concat $ Seq.toList $ execState
 (serialize' tree) Seq.empty
 serialize' (DocText txt) = do
stuff - get
put (stuff | pack [0])
putStr txt
 serialize' (DocElem name attrs kids) = do
stuff - get
put (stuff | pack [1])
putStr name
putNum (List.length attrs)
mapM_ (putPair putStr putStr) attrs
putNum (List.length kids)
mapM_ serialize' kids
 
 putStr 
 
 You get the idea. Actually, the *real* code is trickier - it grovels
 first to find all the element names and numbers them. Likewise with
 attribute names (per element). The extra grovel is well worth it - it
 takes a little longer to serialize, but is more compact and
 deserializes quicker.
 
 Also worth noting - whether you compile a dictionary of element names
 or not, the result is much much much more space efficient than using
 HaXml, since it can all be decoded out of a single ByteString
 containing the document tree, with no actual string copying at all.
 That's the kind of [de]serialization I like. :-) Mind you, I still
 have to use HaXml when I first read documents into the system, and a
 very nice job it does too.

Can we do a cheap bytestring binding to libxml, to avoid any initial
String processing?

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


Re: [Haskell-cafe] Re: Abstraction leak

2007-07-04 Thread Donald Bruce Stewart
phil:
 On Wed, Jul 04, 2007 at 09:02:15PM +1000, Donald Bruce Stewart wrote:
 phil:
 On Sun, Jul 01, 2007 at 06:07:13PM +0100, Andrew Coppin wrote:
 I haven't actually tried, but presumably a TCP connection is represented 
 in the same way as a file, and so has the same problems.
 
 Basically doing binary I/O seems to be one of those things that in 
 Haskell falls into the class of it's possibly but annoyingly messy...
 
 In an ideal world there would be a 'deriving Serializable[1]' you
 
 derive Binary
(use an external tool for this)
 
 such as?

Binary instances are pretty easy to write. For a simple data type:

instance Binary Exp where
  put (IntE i)  = do put (0 :: Word8)
 put i
  put (OpE s e1 e2) = do put (1 :: Word8)
 put s
 put e1
 put e2

  get = do tag - getWord8
   case tag of
   0 - liftM  IntE get
   1 - liftM3 OpE  get get get

The Data.Binary comes with one tool to derive these. The DrIFT preprocessor
also can, as can Stefan O'Rear's SYB deriver.

I just write them by hand, or use the tool that comes with the lib.

More docs here,

http://hackage.haskell.org/packages/archive/binary/0.3/doc/html/Data-Binary.html

 
 could do on datatypes which would get this right. In a really ideal
 world, you could specify the data layout somehow[2][2a], which would
 
 Directly in Haskell data type decls -- see the ICFP 05 paper on the
 House OS, which added packing annotations, and bit syntax. In current
 Haskell, you specify the layout in instances Storable or Binary.
 
 I'll have a look.
 
 make integrating Haskell code into a wider distributed network of
 processes exchanging binary data a cinch. In a super really ideal
 
 Definitely. See things like the zlib or iconv
 Data.Binary/Data.ByteString bindings, for prototypes. The 'tar'
 reader/writer on hackage.haskell.org is also a good example.
 
 OK. Maybe this is the sort of stuff which ought to go into the new
 Haskell book? 'Integrating Haskell with external data sources' or
 something...

Indeed :-)
  
 world, you could operate on the packets in place in Haskell where
 possible and save the deserialization overhead...
 
 Data.ByteString.* for this.
 
 Anyone trying to do any of this?
 
 Yeah, its a bit of a hot topic currently. :)
 
 Gotta chase Erlang for hacking network data.
 
 Absolutely. Ta for the pointers anyway.

Yeah, so:

Data.ByteString
Data.Bits
Data.Binary

Hack those bytes! Quickly! :-)

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


Re: [Haskell-cafe] Binary serialization, was Re: Abstraction leak

2007-07-04 Thread Donald Bruce Stewart
phil:
 On Wed, Jul 04, 2007 at 09:44:13PM +1000, Donald Bruce Stewart wrote:
 Binary instances are pretty easy to write. For a simple data type:
 
instance Binary Exp where
  put (IntE i)  = do put (0 :: Word8)
 put i
  put (OpE s e1 e2) = do put (1 :: Word8)
 put s
 put e1
 put e2
 
  get = do tag - getWord8
   case tag of
   0 - liftM  IntE get
   1 - liftM3 OpE  get get get
 
 That's quite verbose! Plus I'm a bit concerned by the boxing implied
 by those IntE / OpE constructors in get. If you were using those
 values in a pattern match on the result of get, would the compiler be
 able to eliminate them and refer directly to the values in the source
 data?

Well, here's you're flattening a Haskell structure, so it has to get
reboxed. If it was bytestring chunks, or Ints, then you can avoid any
serious copying. The 'get' just tags a value.

 
 The Data.Binary comes with one tool to derive these. The DrIFT preprocessor
 also can, as can Stefan O'Rear's SYB deriver.
 
 I just write them by hand, or use the tool that comes with the lib.
 
 More docs here,

  http://hackage.haskell.org/packages/archive/binary/0.3/doc/html/Data-Binary.html
 
 This doesn't seem to deal with endianness. Am I missing something?

That's the Haskell serialisation layer. Look at Data.Binary.Get/Put for
endian-primitives, to be used instead of 'get'. i.e. getWord16be

 
 world, you could operate on the packets in place in Haskell where
 possible and save the deserialization overhead...
 
 Data.ByteString.* for this.
 
 Ah, does Data.Binary fuse with ByteString.* then?

They know about each other, and Binary avoids copying if you're reading
ByteStrings.

 
 Hack those bytes! Quickly! :-)
 
 :)
 
 It's a shame the layout definition is so verbose. Erlang's is quite
 compact. I wonder if something could be done with template haskell to
 translate an Erlang-style data layout definition to the Data.Binary
 form?

Right, simple but a bit verbose. The Erlang bit syntax is a nice pattern
matching/layout syntax for bit/byte data. There's a couple of ports of
this to Haskell -- one using pattern guards, another using Template
Haskell. Look on hackage.haskell.org for bitsyntax if you're interested.

 (Bonus points for being able to parse ASN.1 and generate appropriate
 Haskell datatypes  serialization primitives automatically :-) )

I think there's at least an ASN.1 definition in the crypto library.
Dominic might be able to enlighten us on that.

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


Re: [Haskell-cafe] folds with escapes

2007-07-04 Thread Donald Bruce Stewart
dm.maillists:
 On Thursday 05 July 2007 11:20, Michael Vanier wrote:
  Again, I'm sure this has been done before (and no doubt better); I'd
  appreciate any pointers to previous work along these lines.
 
 Takusen is, if I recall correctly, based around a generalised fold supporting 
 accumulation and early termination.  Maybe have a look at that.
 

Streams are a similar idea, a generalised unfold supporting early
termination, skipping, and accumulation. Useful for coding up lots of
list functions with the same underlying type, so you can fuse them with
a single rule.

A data type to encode this unfold:

data Stream a = forall s.  Stream !(s - Step a s)  -- ^ a stepper function
  !s-- ^ an initial state

data Step a s = Yield a !s
  | Skip!s
  | Done

Give a way to introduce and remove these guys:

stream :: [a] - Stream a
stream xs0 = Stream next xs0
  where
next [] = Done
next (x:xs) = Yield x xs

unstream :: Stream a - [a]
unstream (Stream next s0) = unfold_unstream s0
  where
unfold_unstream !s = case next s of
  Done   - []
  Skips' - unfold_unstream s'
  Yield x s' - x : unfold_unstream s'

We can roll a fair few list functions:

-- folds
foldl :: (b - a - b) - b - Stream a - b
foldl f z0 (Stream next s0) = loop_foldl z0 s0
  where
loop_foldl z !s = case next s of
  Done   - z
  Skips' - loop_foldl z s'
  Yield x s' - loop_foldl (f z x) s'

foldr :: (a - b - b) - b - Stream a - b
foldr f z (Stream next s0) = loop_foldr s0
  where
loop_foldr !s = case next s of
  Done   - z
  Skips' - expose s' $ loop_foldr s'
  Yield x s' - expose s' $ f x (loop_foldr s')

-- short circuiting:
any :: (a - Bool) - Stream a - Bool
any p (Stream next s0) = loop_any s0
  where
loop_any !s = case next s of
  Done   - False
  Skips' - loop_any s'
  Yield x s' | p x   - True
 | otherwise - loop_any s'

-- maps
map :: (a - b) - Stream a - Stream b
map f (Stream next0 s0) = Stream next s0
  where
next !s = case next0 s of
Done   - Done
Skips' - Skips'
Yield x s' - Yield (f x) s'

-- filters
filter :: (a - Bool) - Stream a - Stream a
filter p (Stream next0 s0) = Stream next s0
  where
next !s = case next0 s of
  Done   - Done
  Skips' - Skips'
  Yield x s' | p x   - Yield x s'
 | otherwise - Skips'

-- taking
takeWhile :: (a - Bool) - Stream a - Stream a
takeWhile p (Stream next0 s0) = Stream next s0
  where
next !s = case next0 s of
  Done   - Done
  Skips' - Skip s'
  Yield x s' | p x   - Yield x s'
 | otherwise - Done

-- dropping
dropWhile :: (a - Bool) - Stream a - Stream a
dropWhile p (Stream next0 s0) = Stream next (S1 :!: s0)
  where
next (S1 :!: s)  = case next0 s of
  Done   - Done
  Skips' - Skip(S1 :!: s')
  Yield x s' | p x   - Skip(S1 :!: s')
 | otherwise - Yield x (S2 :!: s')

next (S2 :!: s) = case next0 s of
  Done   - Done
  Skips' - Skip(S2 :!: s')
  Yield x s' - Yield x (S2 :!: s')

-- zips
zipWith :: (a - b - c) - Stream a - Stream b - Stream c
zipWith f (Stream next0 sa0) (Stream next1 sb0) 
= Stream next (sa0 :!: sb0 :!: Nothing)
  where
next (sa :!: sb :!: Nothing) = case next0 sa of
Done- Done
Skipsa' - Skip (sa' :!: sb :!: Nothing)
Yield a sa' - Skip (sa' :!: sb :!: Just (L a))

next (sa' :!: sb :!: Just (L a)) = case next1 sb of
Done- Done
Skipsb' - Skip  (sa' :!: sb' :!: Just (L a))
Yield b sb' - Yield (f a b) (sa' :!: sb' :!: Nothing)

-- concat
concat :: Stream [a] - [a]
concat (Stream next s0) = loop_concat_to s0
  where
loop_concat_go [] !s = loop_concat_tos
loop_concat_go (x:xs) !s = x : loop_concat_go xs s

loop_concat_to !s = case next s of
  Done- []
  Skip s' - loop_concat_tos'
  Yield xs s' - loop_concat_go xs s'

The nice thing is that once all your functions are in terms of these, usually
non-recursive guys, and you have a rewrite rule:

{-# RULES

STREAM stream/unstream fusion forall s.
stream (unstream s) = s

  #-}

GHC will do all the loop fusion for you. Particularly nice with strict arrays,

Re: [Haskell-cafe] Re: Abstraction leak

2007-07-04 Thread Donald Bruce Stewart
drtomc:
 On 7/4/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote:
 Can we do a cheap bytestring binding to libxml, to avoid any initial
 String processing?
 
 For my part, it's not too big an issue. A version of HaXml or at least
 Parsec built on top of ByteString would be a good start. I know there
 was a SoC for the latter, though I have not looked to see where it
 ended up.
 
 Actually, if you were looking for a good bit of abstraction to build
 how's this? It would be *really* nice to do all my IO with mmap so my
 program isn't hit by the buffer duplication problem[*].  The kind of
 API I have in mind is something like:
 
 data Mapping -- abstract
 
 mmap :: Handle {- or Fd, perhaps -} - Offset - Length - IO Mapping
 
 read :: Mapping - Offset - Length - IO ByteString
 
 write :: Mapping - Offset - ByteString - IO ()
 
 munmap :: Mapping - IO () -- maybe just use a finalizer

Oh, we should really restore the mmapFile interface in Data.ByteString.
Currently its commented out to help out windows people.

And the current implementation does indeed use finalisers to handle the
unmapping.

 This API has the problem that read in particular still has to do
 copying. If you think about the binary XML stuff I mentioned before,
 you'll see that it would be really nice if I could mmap in a record
 and parse it without having to do any copying, or at least to defer
 any copying with a copy-on-write scheme. Doing a simple implementation
 of read that just put a ByteString wrapper around the mmapped memory
 would be nice and efficient, but would suffer from the problem that if
 something changed that bit of the underlying file, things would break.
 Maybe it's just not possible to finesse this one.

Yep. The current impl is:

mmapFile :: FilePath - IO ByteString
mmapFile f = mmap f = \(fp,l) - return $! PS fp 0 l

mmap :: FilePath - IO (ForeignPtr Word8, Int)
mmap = do
 ...
 p  - mmap l fd
 fp - newForeignPtr p unmap -- attach unmap finaliser
 return fp

Maybe I should just stick this in the unix package.

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


Re: [Haskell-cafe] sha1 implementation thats only 12 times slower then C

2007-07-03 Thread Donald Bruce Stewart
aeyakovenko:
 inlining some of the functions definitely gave me a boost, so i am
 about 8.5 times slower then openssl sha1sum.  I dont really understand
 the core output, but after inlining i got a completely different
 profile output, i am guessing its because the cost of the inlined
 functions is spread to the callers.
 
 COST CENTREMODULE   %time %alloc
 
 updateElem SHA1  13.40.0
 sRotateL   SHA1  13.40.0
 hashElem   SHA1  12.50.0
 sXor   SHA1  10.90.0
 unboxW SHA1  10.00.0

So I'd now dive in and seriously look at the Core for these guys.
Work out what they're doing, and how they differ from the C version.

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


[Haskell-cafe] Organising teams for ICFP 2007

2007-06-30 Thread Donald Bruce Stewart
Interested in competing in the ICFP 2007 programming contest -- the
hackers contest of choice! 

http://www.icfpcontest.org

There's 2000 people on this mailing list, and 350 people in #haskell, we
must be able to put together a few decent teams out of that talent
pool

To help people get organised, I've created a page on the haskell.org
wiki to help Haskell (and FP) people find teams:

http://haskell.org/haskellwiki/ICFP_Programming_Contest/Teams_2007

If you've got a team, but need more people, or need a team, add your
details, and hopefully people will be able to find you. The more teams
the better.

Also, drop by the #haskell-icfp07 IRC channel to talk to people and
organise.

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


Re: [Haskell-cafe] sha1 implementation thats only 12 times slower then C

2007-06-30 Thread Donald Bruce Stewart
aeyakovenko:
 So I tried implementing a more efficient sha1 in haskell, and i got to
 about 12 times slower as C.  The darcs implementation is also around
 10 to 12 times slower, and the crypto one is about 450 times slower.
 I haven't yet unrolled the loop like the darcs implementation does, so
 I can still get some improvement from that, but I want that to be the
 last thing i do.
 
 I think I've been getting speed improvements when minimizing
 unnecessary allocations.  I went from 40 times slower to 12 times
 slower by converting a foldM to a mapM that modifies a mutable array.
 
 Anyone have any pointers on how to get hashElem and updateElem to run
 faster, or any insight on what exactly they are allocating.  To me it
 seems that those functions should be able to do everything they need
 to without a malloc.

Try inlining key small functions, and check the core.

-O2 -ddump-simpl | less

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


Re: [Haskell-cafe] ANN: newports.hs utility for freebsd

2007-06-29 Thread Donald Bruce Stewart
clawsie:
 i have written a small haskell program to solve a problem many users
 of freebsd may have - knowing what ports have been updated after a
 daily/weekly etc cvsup. this is a trivial bit of coding hardly worth
 attention, but if it might be of use to you, you can find it here:
 
 http://www.b7j0c.org/content/haskell-newports.html
 
 standard disclaimers - coded  tested mildly by me, a hobbyist
 haskeller

nice brad, always good to see `scripting' work in Haskell. 
would you like to wrap it in a .cabal file and upload it to hackage, so
people can find it in the future?

details on that process here:

http://www.haskell.org/haskellwiki/How_to_write_a_Haskell_program
and
http://cgi.cse.unsw.edu.au/~dons/blog/2006/12/11

Free the source!

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


Re: [Haskell-cafe] ANNOUNCE: hiccup, a toy tcl impersonator in haskell

2007-06-29 Thread Donald Bruce Stewart
consalus:
 A while back I saw a toy tcl interpreter in 550 lines of C called
 'picol'. I was looking for a simple language to implement in haskell,
 so I made my own toy tcl interpreter. It was surprisingly easy to
 make, thanks to the magic of Haskell and Bytestrings. :)  It handles a
 few things incorrectly, and it is not feature complete, but I thought
 maybe somebody else might find it interesting.
 
 For the record (though it means nothing), my interpreter is about half
 the size of picol and runs  about 30% faster in the few tests I've
 run, despite having a few more features. (it was certainly less than
 half the size of picol, but I keep tacking on functions when I get
 bored).
 
 Anyway, you can check it out at:
 http://code.google.com/p/hiccup/
 
 I plan on making it more complete and faithful to tcl, but I'm
 branching into a different project for this one. However, any
 suggestions to make hiccup more efficient, elegant, or correct are
 certainly appreciated.
 
 Cheers,

Great work! Would you like to upload it to hackage.haskell.org, so it
can be found more easily?

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


Re: [Haskell-cafe] Preferred way to get data from a socket

2007-06-27 Thread Donald Bruce Stewart
bulat.ziganshin:
 Hello Donald,
 
 Wednesday, June 27, 2007, 6:37:07 AM, you wrote:
 
  I also know Bulat Ziganshin had put together a nice-looking Streams
  library (http://unix.freshmeat.net/projects/streams/) based on John
  Goerzen's previous HVIO work, but I wasn't sure if the ByteString
  stuff matches the speed and encapsulates all of the functionality of
  that anyway. Or can/should they be used together somehow?
 
  Should be similar in speed, and most high-perf stuff seems to use
  ByteStrings now. ByteStrings also have some nice high level
  optimisations not available to lower level libraries.
 
 i recommend you to try ByteString own i/o capabilities at first. if it
 will not satisfy you, you can try Streams 0.2 which supports
 ByteString i/o:
 
 http://www.haskell.org/library/StreamsBeta.tar.gz
 
 using my library should allow 30-50 mb/s i/o speed but its
 installation may be tricky since it was not updated over a year

That's interesting, Bulat. Two points I'd like to ask about the streams library:

What machine did you do the IO benchmarks on? Since we get well over 10x
that speed word writing in Data.Binary now, for example, on a fast
machine. (Duncan, what's the max throughput we've seen?)

And secondly, will the streams stuff be updated? I had trouble
benchmarking against it back in January, and am wondering if it will be
maintained?

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


Re: [Haskell-cafe] ANN: Scripting.Lua 0.1

2007-06-26 Thread Donald Bruce Stewart
gracjanpolak:
 
 Hi all,
 
 I'm pleased to announce the first public release of Scripting.Lua.
 
 The package hslua-0.1 contains Haskell FFI bindings for a Lua interpreter
 along with some Haskell utility functions simplifying Haskell to Lua and
 Lua to Haskell calls. Full Lua interpreter is included in the package.
 
 Example
 
  import qualified Scripting.Lua as Lua
 
  main = do
  l - Lua.newstate
  Lua.openlibs l
  Lua.callproc l print Hello from Lua
  Lua.close l
 
 More information
 
  http://home.agh.edu.pl/~gpolak/hslua
 
 The Lua language

  http://www.lua.org
 
 --
 Gracjan

Great work! would you like to upload it to hackage.haskell.org too, so
it will be archived for the ages?

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


Re: [Haskell-cafe] Preferred way to get data from a socket

2007-06-26 Thread Donald Bruce Stewart
chad.scherrer:
 I've never used sockets before, but I need to now, and I need to be
 able to get a lot of data quickly. I was thinking about doing
 something like this (below), but I'm wondering if there's a way that
 would be faster. Is the obvious way of doing this the right way? I'm
 happy to install outside libraries if that would help, as long as they
 work on Linux and MS. Thanks!
 
 -Chad
 
 --8---
 
 import Network
 import qualified Data.ByteString.Lazy as B
 
 hostName = myComputer
 portID = PortNumber 54321
 
 theData :: IO B.ByteString
 theData = connectTo hostName portID = B.hGetContents
 ___

Looks like the obvious, right way to me.

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


Re: [Haskell-cafe] loading an Haskell symbol at run-time

2007-06-26 Thread Donald Bruce Stewart
tittoassini:
 Hi,
 
 to load an Haskell symbol at run-time is still necessary to use the load 
 functions from the hs-plugins library (System.Plugins.Load) or is there some 
 function in the GHC API that does the same job?
 

yes, definitely possible. i think Lemmih put an example on the wiki a
while ago. basically, ghc-api exposes the lower level api also used by
hs-plugins -- a nice project would be to provide the hs-plugins api
directly in ghc-api - avoiding the need for an external hs-plugins package.

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


Re: [Haskell-cafe] Preferred way to get data from a socket

2007-06-26 Thread Donald Bruce Stewart
chad.scherrer:
 Ok, cool. FWIW, the current documentation for Network says:
 
 For really fast I/O, it might be worth looking at the hGetBuf and
 hPutBuf family of functions in System.IO.
 
 But this looked pretty low-level to me, and I figured it might be outdated.
 
 I also know Bulat Ziganshin had put together a nice-looking Streams
 library (http://unix.freshmeat.net/projects/streams/) based on John
 Goerzen's previous HVIO work, but I wasn't sure if the ByteString
 stuff matches the speed and encapsulates all of the functionality of
 that anyway. Or can/should they be used together somehow?

Should be similar in speed, and most high-perf stuff seems to use
ByteStrings now. ByteStrings also have some nice high level
optimisations not available to lower level libraries.

 
 Chad
 
 
  --8---
 
  import Network
  import qualified Data.ByteString.Lazy as B
 
  hostName = myComputer
  portID = PortNumber 54321
 
  theData :: IO B.ByteString
  theData = connectTo hostName portID = B.hGetContents
  ___
 
 Looks like the obvious, right way to me.
 
 -- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wikipedia archiving bot - code review

2007-06-25 Thread Donald Bruce Stewart
gwern0:
 Hey everyone. So I've been learning Haskell for a while now, and I've
 found the best way to move from theory to practice is to just write
 something useful for yourself. Now, I'm keen on editing Wikipedia and
 I've long wanted some way to stop links to external websites from
 breaking on me. So I wrote this little program using the TagSoup
 library which will download Wikipedia articles, parse out external
 links, and then ask WebCite to archive them.
 
 But there's a problem: no matter how I look at it, it's just way too
 slow. Running on a measly 100 articles at a time, it'll eat up to half
 my processor time and RAM (according to top). I converted it over to
 ByteStrings since that's supposed to be a lot better than regular
 Strings, but that didn't seem to help much.  So I'm curious: in what
 way could this code be better? How could it be more idiomatic or
 shorter? Particularly, how could it be more efficient either in space
 or time? Any comments are appreciate.
 
 {- Module  :  Main.hs
License :  public domain
Maintainer  :  Gwern Branwen [EMAIL PROTECTED]
Stability   :  unstable
Portability :  portable
Functionality: retrieve specified articles from Wikipedia and request 
 WebCite to archive all URLs found.
TODO: send an equivalent request to the Internet Archive.
  Not in any way rate-limited.
BUGS: Issues redundant archive requests.
  Currently uses Data.ByteString.Lazy.Char8. If I'm understanding the 
 documentation right, this barfs
  on the full UTF-8 character set, but Wikipedia definitely exercises 
 the full UTF-8 set.
USE: Print to stdin a succession of Wikipedia article names (whitespace in 
 names should be escaped as '_').
 A valid invocation might be, say: '$echo Fujiwara_no_Teika 
 Fujiwara_no_Shunzei | archive-bot'
 All URLs in [[Fujiwara no Teika]] and [[Fujiwara no Shunzei]] would 
 then be backed up.
 If you wanted to run this on all of Wikipedia, you could take the 
 current 'all-titles-in-ns0'
 gzipped file from [[WP:DUMP]], gunzip it, and then pipe it into 
 archive-bot. -}
 
 module Main where
 import Text.HTML.TagSoup (parseTags, Tag(TagOpen))
 import Text.HTML.Download (openURL)
 import Data.List (isPrefixOf)
 import Monad (liftM)
 import Data.Set (toList, fromList)
 import qualified Data.ByteString.Lazy.Char8 as B (ByteString(), getContents, 
 lines, unlines, pack, unpack, words)
 
 main :: IO ()
 main = do mapM_ archiveURL = (liftM sortNub $ mapM fetchArticleText = 
 (liftM B.words $ B.getContents))
   where sortNub :: [[B.ByteString]] - [B.ByteString]
 sortNub = toList . fromList . concat
 
 fetchArticleText :: B.ByteString - IO [B.ByteString]
 fetchArticleText article = liftM (B.lines . extractURLs) (openURL(wikipedia 
 ++ B.unpack article))
where wikipedia = http://en.wikipedia.org/wiki/;
 
 extractURLs :: String - B.ByteString
 extractURLs arg = B.unlines $ map B.pack ([x | TagOpen a atts - (parseTags 
 arg), (_,x) - atts, http://; `isPrefixOf` x])
 
 archiveURL :: B.ByteString - IO String
 archiveURL url = openURL(www.webcitation.org/archive?url= ++ (B.unpack url) 
 ++ emailAddress)
  where emailAddress = [EMAIL PROTECTED]
 

you don't seem to be using bytestrings for anything important here --
you just pass them in, and immediately unpack them back to String anyway
-- since tagsoup only downloads String, and parses String. 

Probably, as neil says, TagSoup just isn't optimised much yet. Perhaps
try the bytestring-based urlcheck?

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

Neil, perhaps tagsoup should provide at the bottom a bytestring layer --
so there's some hope of efficient downloading, with a String layer on
top -- not the other way around?

-- Don

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


Re: [Haskell-cafe] Parallel + exceptions

2007-06-24 Thread Donald Bruce Stewart
andrewcoppin:
 Bulat Ziganshin wrote:
 Hello Andrew,
 
   
 definitive reading: Tackling the awkward squad: monadic input/output,
 concurrency, exceptions, and foreign-language calls in Haskell
 http://research.microsoft.com/Users/simonpj/papers/marktoberdorf/marktoberdorf.ps.gz
   
 
 I've read it.
 
 Is everything described in that paper actually implemented now? (And 
 implemented in exactly the same way as the paper says?)
 
 in my experience, exceptions are rarely required in Haskell program -
 i use them only to roll out when IO problems occur.
 
 Indeed. Somebody else mentioned Maybe; much cleaner, more intuitive 
 solution.
 
 OTOH, concurrency
 is very handy in Haskell/GHC - it's easy to create threads and
 communicate in reliable way, so it's a great tool to split algorithm
 into subtasks. and GHC lightweight threads make it very cheap - you
 may run thousands of threads. example program that uses one thread to
 produce numbers and another to print them is less than 10 lines long
   
 
 It's nice that you can have millions of threads if you want to do 
 something very concurrent. What I tend to want is parallel - doing 
 stuff that *could* be done in a single thread, but I want it to go 
 faster using my big mighty multicore box. As I understand it, you have 
 to do something special to make that happen...?
 
 While we're on the subject... has anybody ever looked at using muptiple 
 processors on *networked* machines? Haskell's very pure semantics would 
 seem quite well-suited to this...
 

MPI/cluster stuff has also been done a fair bit, but in these days SMP
multicore machines are a hot topic. Start here:


http://haskell.org/haskellwiki/Applications_and_libraries/Concurrency_and_parallelism

P.S. An awful lot of your questions are previously answered on the wiki :-)
It's a good resource!

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


Re: [Haskell-cafe] Need for speed: the Burrows-Wheeler Transform

2007-06-23 Thread Donald Bruce Stewart
 ...OK...so how do I make Haskell go faster still?
 
 Presumably by transforming the code into an ugly mess that nobody can 
 read any more...?
 

http://haskell.org/haskellwiki/Performance

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


Re: [Haskell-cafe] Compile-time here document facility

2007-06-22 Thread Donald Bruce Stewart
bayer:
 I couldn't find a compile-time here document facility, so I wrote one  
 using Template Haskell:

Very nice! You should wrap it in a little .cabal file, and upload it to
hackage.haskell.org, so we don't forget about it.

Details on cabalising and uploading here:

http://haskell.org/haskellwiki/How_to_write_a_Haskell_program
http://cgi.cse.unsw.edu.au/~dons/blog/2006/12/11

-- Don

 
 module HereDocs(hereDocs) where
 
 import Control.Exception
 import Language.Haskell.TH.Syntax
 
 getDoc :: String - [String] - (String,[String])
 getDoc eof txt =
 let (doc,rest) = break (== eof) txt
 in  (unlines doc, drop 1 rest)
 
 makeVal :: String - String - [Dec]
 makeVal var doc = let name = mkName var in
 [SigD name (ConT (mkName String)),
 ValD (VarP name) (NormalB (LitE (StringL doc))) []]
 
 scanSrc :: [Dec] - [String] - Q [Dec]
 scanSrc vals [] = return vals
 scanSrc vals (x:xs) = case words x of
 [var, =, ('':'':eof)] -
 let (doc,rest) = getDoc eof xs
 val = makeVal var doc
 in  scanSrc (vals ++ val) rest
 _ - scanSrc vals xs
 
 hereDocs :: FilePath - Q [Dec]
 hereDocs src =
 let fin = catchJust assertions (evaluate src) (return.takeWhile  
 (/= ':'))
 in  runIO (fin = readFile = return . lines) = scanSrc []
 
 One binds here documents embedded in comments by writing
 
 import HereDocs
 $(hereDocs Main.hs)
 
 As an idiom, one can refer to the current file as follows; the first  
 thing hereDocs does is catch assert errors in order to learn the file  
 name:
 
 import HereDocs
 $(hereDocs $ assert False )
 
 Here is an example use:
 
 {-# OPTIONS_GHC -fth -Wall -Werror #-}
 
 module Main where
 
 import System
 import Control.Exception
 
 import HereDocs
 $(hereDocs $ assert False )
 
 {-
 ruby = RUBY
 #!/usr/bin/env ruby
 hello = EOF
 Ruby is not
an acceptable Lisp
 EOF
 puts hello
 RUBY
 
 lisp = LISP
 #!/usr/bin/env mzscheme -qr
 (display #EOF
 Lisp is not
an acceptable Haskell
 EOF
 )
 (newline)
 LISP
 -}
 
 exec :: FilePath - String - IO ExitCode
 exec fout str = do
writeFile fout str
system (chmod +x  ++ fout ++ ; ./ ++ fout)
 
 main :: IO ExitCode
 main = do
exec hello.rb ruby
exec hello.scm lisp
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell version of ray tracer code is much slower than the original ML

2007-06-22 Thread Donald Bruce Stewart
jon:
 On Friday 22 June 2007 19:54:16 Philip Armstrong wrote:
  On Fri, Jun 22, 2007 at 10:11:27PM +0400, Bulat Ziganshin wrote:
  btw, *their* measurement said that ocaml is 7% faster :)
 
  Indeed. The gcc-4.0 compilied binary runs at about 15s IIRC, but it's
  still much better than 7% faster than the ocaml binary.
 
 What architecture, platform, compiler versions and compile lines are you 
 using?
 
 On my 2x 2.2GHz Athlon64 running x64 Debian I now get:
 
 GHC 6.6.1:26.5sghc -funbox-strict-fields -O3 ray.hs -o ray

Don't use -O3 , its *worse* than -O2, and somewhere between -Onot and -O iirc,

ghc -O2 -funbox-strict-fields -fvia-C -optc-O2 -optc-ffast-math 
-fexcess-precision

Are usually fairly good.



 OCaml 3.10.0: 14.158s  ocamlopt -inline 1000 ray.ml -o ray
 g++ 4.1.3: 8.056s  g++ -O3 -ffast-math ray.cpp -o ray
 
 Also, the benchmarks and results that I cited before are more up to date than 
 the ones you're using. In particular, you might be interested in these faster 
 versions:
 
   http://www.ffconsultancy.com/languages/ray_tracer/code/5/ray.ml
   http://www.ffconsultancy.com/languages/ray_tracer/code/5/ray.cpp
 
 For ./ray 6 512, I get:
 
 OCaml: 3.140s  ocamlopt -inline 1000 ray.ml -o ray
 C++:   2.970s  g++ -O3 -ffast-math ray.cpp -o ray
 
 -- 
 Dr Jon D Harrop, Flying Frog Consultancy Ltd.
 The OCaml Journal
 http://www.ffconsultancy.com/products/ocaml_journal/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Graphical Haskell

2007-06-22 Thread Donald Bruce Stewart
bf3:
 Wow thanks for all the info! This certainly can get me started.
 
 And yet I have some more questions (sorry!):
 
 - Unfortunately this project won't be open source; if my first tests are
 successful, I will try to convince my employer (who wants to develop such a
 graphical language) to use Haskell for building a prototype instead of
 C#/F#/Java. Can Haskell be used for creating commercial projects? When the
 product is released, it *will* be downloadable for free, but the source code
 won't be (most likely). 

It can, and is used. See the industry page, 

   http://haskell.org/haskellwiki/Haskell_in_industry 

they're the big players, there's numerous small groups that have maybe a
few in house Haskell tools.

 
 - If my employer agrees on Haskell, and when our first round of investment
 is completed, we will be looking for a couple of good Haskell developers.

Wonderful.

 What would be the best place to look for good Haskell developers? This
 mailing list? Ideally development will have to take place in
 Antwerp/Belgium, although we might work with remotely located freelancers.
 We prefer agile development (SCRUM, and maybe we will be doing extreme
 programming, to be decided) with a small group of capable people. To get an
 idea of what my employer is doing, visit http://www.nazooka.com. My
 colleagues and I wrote most of the software for doing this back in the
 1990s, and of course the real work is done by 3D graphics artists.

I suspect the best place to advertise is still [EMAIL PROTECTED]
Most jobs seems to be sent here, and its also cheap :-) You have access
to a few thousand competent Haskell people directly.

 - Regarding GUIs, does a real FP-style GUI exist instead of those wrappers
 around OO GUIs? I did some searches but besides some research papers about
 FranTk and wxFruit I only found wrappers such as Gtk2Hs and wxHaskell that
 use a lot of monadic IO. It's very hard for an old school OO style
 programmer like myself to switch my mind into lazy functional programming
 (although I think I've seen the light yesterday when digging deep into the
 FRP of the SOE book, LOL ;-).

gtk2hs is probably the most 'industrial' UI lib.

  
 - Functional reactive programming like looks cool (I only looked at the SOE
 book, must still look at Yampa), but somehow I feel this is still an active
 area of research. What is the latest work on FRP (for GUIs / games /
 animation / simulations...)? What are the major open issues? 
 
 - Regarding performance (for real-time simulations, not GUIs), I think the
 garbage collector will get really stressed using FRP because of all those
 infinite lazy streams; my gut feeling says a generational garbage collector
 like Microsoft's .NET could help here (but the gut is often wrong, see
 http://www.youtube.com/watch?v=RF3m3f9iMRc for an laugh ;). Regarding the
 GC, is http://hackage.haskell.org/trac/ghc/wiki/GarbageCollectorNotes still
 up-to-date?  

Well, best to find out. In practice i've not found GC to be an issue.
Premature optimisation and all that.

 
 Okay, that's enough for now. More is less...
 

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


Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread Donald Bruce Stewart
ttmrichter:
 
On Wed, 2007-20-06 at 15:21 +1000, Donald Bruce Stewart
wrote:
 
 -- unsigned char *MD5(const unsigned char *d, unsigned long n, un
 signed char *md);
 foreign import ccall openssl/md5.h MD5 c_md5
 :: Ptr CChar - CULong - Ptr CChar - IO (Ptr Word8)
 
 ByteStrings were designed for this zero-copy passing of big data to C
 ,
 by the way, so its a perfect fit.
 
I'm not so sure I like the idea of having to do this by

You don't *have* to do it via C, but you *can* do it, if you want.

passing it over to C.  Crypto sounds like exactly the kind
of application that would require the certainty of FP
reasoning.  Is there no way to make it work reasonably
efficiently in Haskell proper?

Sure, why not? We've a good native code compiler, after all. Write an
md5 over ByteString -- it should be pretty competitive. Here's a
reference C implementation to start from:

http://www.cse.unsw.edu.au/~dons/tmp/md5.c

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


Re: [Haskell-cafe] hSetBuffering woes

2007-06-19 Thread Donald Bruce Stewart
eeoam:
 Bryan O'Sullivan wrote:
 Eric wrote:
 
 I'm writing  a simple HTTP server and am trying to implement the POST 
 method.
 
 That's a rather general problem statement, indeed :-)  For an 
 application like this, I'd suggest that explicit resource management 
 is the way to go, and that you should not be using hGetContents at 
 all, under any guise.  For example, any scheme involving reading an 
 entire stream is going to do completely the wrong thing in the face of 
 HTTP keepalive.  Also, code that leaves open sockets piling up in 
 drifts, to eventually be shoveled up by the RTS, is going to be 
 trivially easy to DoS.
 Are there any good resources/tutorials on Haskell network programming?
 
 E.

Some articles have been written here,

http://haskell.org/haskellwiki/Blog_articles#Network

Intro stuff mostly.

See also HAppS, and Simon Marlow's concurrent webserver paper.

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


Re: [Haskell-cafe] Reading/writing packed bytes from file

2007-06-19 Thread Donald Bruce Stewart
jeff:
 I've read the documentation for some of the marshalling packages out
 there for Haskell, and I'm left confused as to which one I should be
 using and how to actually do what I want to do.   I have a file, a
 little over 2gb, of packed data in the format
 
 (recordcount) records of:
 
 4-byte int (count),
 (count) 2-byte unsigned shorts,
 (count) 4-byte floats
 
 all in little-endian order.  What I want to do is read each record
 (lazily), and unpack it into Data.IntMap.IntMap Float where the unsigned
 shorts become the keys and the 4-byte floats become the values.
 
 Then I want to do a lot of interesting processing which we'll skip here,
 and write back out packed data to a file in the format of
 
 4-byte float,
 4-byte float,
 4-byte float
 
 for each record. I need these output records to be four-byte C floats.
 I've gotten as far as datatypes and a couple of signatures, but I can't
 figure out the functions themselves that go with the signatures, and
 then again, maybe I have the signatures wrong.  
 
 -- 
 import qualified Data.IntMap as M
 import qualified Data.ByteString.Lazy.Char8 as B
 
 data InputRecord = M.IntMap Float
 data OutputRecord = (Float, Float, Float)
 
 -- open a file as a lazy ByteString and break up the individual records
 -- by reading the count variable, reading that many bytes times 
 -- sizeof short + sizeof float into a lazy ByteString.
 readRawRecordsFromFile :: String - IO [B.ByteString] 
 
 
 -- take a bytestring as returned by readRawRecordsFromFile and turn it
 -- into a map.
 decodeRawRecord :: B.ByteString - M.IntMap Float
 --
 
 Can anyone help with how to construct these functions?  I'm going to
 have to make a few passes over this file, so I'd like the IO to be as
 fast as Haskelly possible.
 
 -- Jeff

Data.ByteString.Lazy.Char8.readFile should suffice for the IO.
then use drop/take to split up the file in pieces if you know the length
of each field.

For converting ByteString chunks to Floats, I'd probably call C for that.

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


Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-19 Thread Donald Bruce Stewart
aeyakovenko:
 $ time ./md5sum ./md5sum
 [105,252,52,138,187,192,216,17,225,123,185,3,124,101,86,132]
 
 real0m4.790s
 user0m3.688s
 sys 0m0.492s
 
 $ time md5sum ./md5sum
 69fc348abbc0d811e17bb9037c655684  ./md5sum
 
 real0m0.023s
 user0m0.000s
 sys 0m0.008s
 
 this is my implementation using crypto
 (http://www.haskell.org/crypto/).  Am I doing something wrong?
 
 module Main where
 
 import System
 import qualified Data.Digest.MD5 as MD5
 import qualified Data.ByteString as BS
 
 main = do
   args - getArgs
   dt - BS.readFile $ head args
   putStrLn $ show $ MD5.hash . BS.unpack $ dt
     ^

 not a good idea.

You need an MD5 over bytestrings, not [Word8].

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


Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-19 Thread Donald Bruce Stewart
dons:
 aeyakovenko:
  $ time ./md5sum ./md5sum
  [105,252,52,138,187,192,216,17,225,123,185,3,124,101,86,132]
  
  real0m4.790s
  user0m3.688s
  sys 0m0.492s
  
  $ time md5sum ./md5sum
  69fc348abbc0d811e17bb9037c655684  ./md5sum
  
  real0m0.023s
  user0m0.000s
  sys 0m0.008s
  
  this is my implementation using crypto
  (http://www.haskell.org/crypto/).  Am I doing something wrong?
  
  module Main where
  
  import System
  import qualified Data.Digest.MD5 as MD5
  import qualified Data.ByteString as BS
  
  main = do
args - getArgs
dt - BS.readFile $ head args
putStrLn $ show $ MD5.hash . BS.unpack $ dt
  ^
 
  not a good idea.
 
 You need an MD5 over bytestrings, not [Word8].
 
 -- Don

I note a couple of other issues:

crypto is compiled with:

Ghc-options: -fglasgow-exts

that is, no optimisations, although it would certainly benefit from

Ghc-options: -O2 -fexcess-precision -funbox-strict-fields

So I'd recompile the crypto package with that first.
Then be sure to compile your code with ghc -O2  -- bytestrings love -O2.

Finally, to actually get C speed, use a C md5. Here's an example Haskell
binding to the OpenSSL libraries 'md5' function, which you can compile
and run like so:

$ ghc MD5.hs -lcrypto -o hsmd5 

$ time ./hsmd5 /usr/share/dict/words
MD5 (/usr/share/dict/words) = e5c152147e93b81424c13772330e74b3 

./hsmd5 /usr/share/dict/words  0.01s user 0.02s system 80% cpu 0.029 total

versus my system's 'md5' program:

$ time md5 /usr/share/dict/words 
MD5 (/usr/share/dict/words) = e5c152147e93b81424c13772330e74b3
md5 /usr/share/dict/words  0.02s user 0.00s system 29% cpu 0.052 total

Oh huh, that's interesting...

And the code:

{-# OPTIONS -O2 -fffi -#include openssl/md5.h #-}

--
-- A few imports, should tidy these up one day.
--
import System.Environment
import qualified Data.ByteString.Base as B (unsafeUseAsCStringLen)
import qualified Data.ByteString  as B
import Foreign
import Foreign.C.Types
import Numeric
import Text.Printf


main = do
(f:_)  - getArgs
src- B.readFile f
printf MD5 (%s) = %s \n f (md5sum src)


-- -
--
-- Fast md5 using OpenSSL and zero-copying bytestrings
--

--
-- The md5 hash should be referentially transparent..
--
md5sum :: B.ByteString - String
md5sum p = unsafePerformIO $ B.unsafeUseAsCStringLen p $ \(ptr,n) - do
digest  - c_md5 ptr (fromIntegral n) nullPtr
go digest 0 []
  where

-- print it in 0-padded hex format
go :: Ptr Word8 - Int - [String] - IO String
go p n acc
| n = 16   = return $ concat (reverse acc)
| otherwise = do w - peekElemOff p n
 go p (n+1) (draw w : acc)

draw w = case showHex w [] of
[x] - ['0', x]
x   - x

-- unsigned char *MD5(const unsigned char *d, unsigned long n, unsigned 
char *md);
--
foreign import ccall openssl/md5.h MD5 c_md5
:: Ptr CChar - CULong - Ptr CChar - IO (Ptr Word8)


Happy hacking.

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


Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-19 Thread Donald Bruce Stewart
stefanor:
 On Wed, Jun 20, 2007 at 01:24:00PM +1000, Donald Bruce Stewart wrote:
  aeyakovenko:
   $ time ./md5sum ./md5sum
   [105,252,52,138,187,192,216,17,225,123,185,3,124,101,86,132]
   
   real0m4.790s
   user0m3.688s
   sys 0m0.492s
   
   $ time md5sum ./md5sum
   69fc348abbc0d811e17bb9037c655684  ./md5sum
   
   real0m0.023s
   user0m0.000s
   sys 0m0.008s
   
   this is my implementation using crypto
   (http://www.haskell.org/crypto/).  Am I doing something wrong?
   
   module Main where
   
   import System
   import qualified Data.Digest.MD5 as MD5
   import qualified Data.ByteString as BS
   
   main = do
 args - getArgs
 dt - BS.readFile $ head args
 putStrLn $ show $ MD5.hash . BS.unpack $ dt
   ^
  
   not a good idea.
  
  You need an MD5 over bytestrings, not [Word8].
 
 Wouldn't deforestation have produced something within a factor of 4-ish
 of optimal?

There's no deforestation between ByteString.unpack and MD5.hash.

So all the time here is spent taking some big bytestring, and unpacking
it into n list cons cells. md5ing the bytestring directly should knock
95% off that.

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


Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-19 Thread Donald Bruce Stewart
  aeyakovenko:
   $ time ./md5sum ./md5sum
   [105,252,52,138,187,192,216,17,225,123,185,3,124,101,86,132]
   
   real0m4.790s
   user0m3.688s
   sys 0m0.492s
   
   $ time md5sum ./md5sum
   69fc348abbc0d811e17bb9037c655684  ./md5sum
   
   real0m0.023s
   user0m0.000s
   sys 0m0.008s
   

I wasn't happy with the hex printing loop. Here's a shorter version.


{-# OPTIONS -O2 -fffi #-}
--
-- ghc MD5.hs -o hsmd5 -lcrypto
--

import System.Environment
import qualified Data.ByteString.Base as B (unsafeUseAsCStringLen)
import qualified Data.ByteString  as B
import Foreign
import Foreign.C.Types
import Numeric
import Text.Printf
import Control.Monad

main = do
(f:_)  - getArgs
src- B.readFile f
printf MD5 (%s) = %s \n f (md5sum src)

-- Fast md5 using OpenSSL and non-copying bytestrings
md5sum :: B.ByteString - String
md5sum p = unsafePerformIO $ B.unsafeUseAsCStringLen p $ \(ptr,n) - do
digest  - c_md5 ptr (fromIntegral n) nullPtr
liftM concat $ forM [0..15] $ \n - do
w - peekElemOff digest n
return $ case showHex w [] of [x] - ['0', x]; x - 
x

-- unsigned char *MD5(const unsigned char *d, unsigned long n, unsigned 
char *md);
foreign import ccall openssl/md5.h MD5 c_md5
:: Ptr CChar - CULong - Ptr CChar - IO (Ptr Word8)


ByteStrings were designed for this zero-copy passing of big data to C,
by the way, so its a perfect fit.

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


Re: [Haskell-cafe] Haskell, crypto and OpenSSL

2007-06-19 Thread Donald Bruce Stewart
dons:
 -- Fast md5 using OpenSSL and non-copying bytestrings
 md5sum :: B.ByteString - String
 md5sum p = unsafePerformIO $ B.unsafeUseAsCStringLen p $ \(ptr,n) - do
 digest  - c_md5 ptr (fromIntegral n) nullPtr
 liftM concat $ forM [0..15] $ \n - do
 w - peekElemOff digest n
 return $ case showHex w [] of [x] - ['0', x]; x 
 - x
 
 -- unsigned char *MD5(const unsigned char *d, unsigned long n, unsigned 
 char *md);
 foreign import ccall openssl/md5.h MD5 c_md5
 :: Ptr CChar - CULong - Ptr CChar - IO (Ptr Word8)
 
 ByteStrings were designed for this zero-copy passing of big data to C,
 by the way, so its a perfect fit.

by the way, I note we do have a binding to OpenSSL, of sorts:

http://cryp.to/hopenssl/

But it needs updating to use ByteStrings. Would make a good project for
someone into crypto.

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


Re: [Haskell-cafe] Re: Efficient signal processing

2007-06-18 Thread Donald Bruce Stewart
lemming:
 
 On Sun, 17 Jun 2007, Donald Bruce Stewart wrote:
 
  simonmarhaskell:
   Henning Thielemann wrote:
  
   The program is compiled with GHC-6.4 and option -O2, CPU clock 1.7 GHz.
  
   ByteString is much faster with GHC 6.6, IIRC.  We optimised the
   representation of ForeignPtr, and ByteString takes advantage of that.  I
   recommend upgrading.
 
  Yes, a 2x speedup isn't uncommon.
 
 Indeed, in my simple example the speedup factor was 2. However this is
 still far from being enough for real-time signal processing. I found
 another problem: The rounding functions from RealFrac are much slower than
 GHC.Float.double2Int. I've set up a bug ticket in GHC trac.

if there's floating point math involved, carefully check the Core
output. -ddump-simpl -O2

 
  ByteString is even faster with the GHC head, branch, given the cranked
  up rules and constructor specialisation.
 
 Can I test them without compiling GHC myself? I.e. can I still install the
 FPS package separately?

oh, i was just suggesting trying the GHC HEAD branch for its improved
optimisations, not the `unstable' branch of fps.

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


Re: [Haskell-cafe] Re: Efficient signal processing

2007-06-16 Thread Donald Bruce Stewart
simonmarhaskell:
 Henning Thielemann wrote:
 
 The program is compiled with GHC-6.4 and option -O2, CPU clock 1.7 GHz.
 
 ByteString is much faster with GHC 6.6, IIRC.  We optimised the 
 representation of ForeignPtr, and ByteString takes advantage of that.  I 
 recommend upgrading.

Yes, a 2x speedup isn't uncommon. ByteString is even faster with the GHC
head, branch, given the cranked up rules and constructor specialisation.

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


Re: [Haskell-cafe] TorDNSEL

2007-06-13 Thread Donald Bruce Stewart
newsham:
 I wanted to point out:
http://exitlist.torproject.org/
 
 written in Haskell.  I haven't seen any announcements or info on this list 
 (apologies if someone else mentioned it already).  For the record, I'm not 
 affiliated with the project in any way.
 

Is the source available?

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


Re: [Haskell-cafe] haskell version of fractal benchmark

2007-06-09 Thread Donald Bruce Stewart
dons:
 sic:
  * Andrew Coppin [EMAIL PROTECTED] [070608 02:45]:
  Bayley, Alistair wrote:
   
   [[1]mailto:[EMAIL PROTECTED] On Behalf Of Andrew Coppin
   
   Donald Bruce Stewart wrote:
   
   Some things to remember using Doubles:
   
   * {-# OPTIONS -fexcess-precision #-}
   * -fvia-C
   * -fbang-patterns
   * -optc-O2 -optc-mfpmath=sse -optc-msse2
   * -optc-march=pentium4
   
   1. What do all those things do?
   2. Is the effect actually that large?
   
   Large? Depends what you mean by large, but adding a few flags to get
   just a 10-20% speedup isn't to be ignored:
   
  Sure - if it really is 10-20%. (And not, say, 0.001 - 0.002%.)
  
  A single data point for all of this, I have a program that calculates:
  
  P^1_i = S_i/sum_k S_k
  P^m_i = sum_{k!=i} P^1_k*P^m-1_i(S_~k)
  
  Here's timings for the different options:
  
  options  run timecompile time
  none  46.401   3.136
  -O 5.033   4.906
  -O24.967   6.755
  -O2 -fexcess-precision 3.710   6.396
  all listed options 3.602   6.344

My apologies. Misread that last line. 

/me drinks more tea.

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


Re: [Haskell-cafe] haskell version of fractal benchmark

2007-06-08 Thread Donald Bruce Stewart
andrewcoppin:
 Donald Bruce Stewart wrote:
 Some things to remember using Doubles:
 
 * {-# OPTIONS -fexcess-precision #-} 
 * -fvia-C
 * -fbang-patterns
 * -optc-O2 -optc-mfpmath=sse -optc-msse2
 * -optc-march=pentium4
   
 
 1. What do all those things do?

Check the GHC user's guide.

 2. Is the effect actually that large?

1) {-# OPTIONS -fexcess-precision #-

I've had this halved runtimes for runtimes for numeric-intensive programs.

2) -fvia-C

Probably still worth 10% for Double-based stuff (maybe more).

3) -fbang-patterns

Better than `seq`

4) -optc-O2 -optc-mfpmath=sse -optc-msse2 -optc-march=pentium4

Can be worth 0 to hmm, quite a few, percent, depending on the code.
This is all assuming you've written low level code anyway, so that the 
effects of, say, using SSE instructions are actually apparent.

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


Re: [Haskell-cafe] haskell version of fractal benchmark

2007-06-08 Thread Donald Bruce Stewart
Alistair_Bayley:
  [mailto:[EMAIL PROTECTED] On Behalf Of Donald 
  Bruce Stewart
  
  3) -fbang-patterns
  
  Better than `seq`
 
 Better in the more convenient to write sense, right? AFAIUI, seq and
 bang patterns should be equivalent.
 

Yes, in the 'more convenient' sense. Adding strictness speculatively,
while trying to debug a leak, is easier when inserting !, than to insert
`seq`'s. It also doesn't obfuscate the code as much as the seq tricks
do.

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


[Haskell-cafe] Fast number parsing with strict bytestrings [Was: Re: Seemingly subtle change causes large performance variation]

2007-06-07 Thread Donald Bruce Stewart
mdanish:
 Hello,
 
 I've been playing with the INTEST problem on SPOJ which demonstrates
 the ability to write a program which processes large quantities of
 input data.  http://www.spoj.pl/problems/INTEST/
  
 But when I make a slight modification, the program chews up a ton more memory
 and takes more time:
 
 import Control.Monad
 import Data.Maybe
 import qualified Data.ByteString.Char8 as B
 
 divisibleBy :: Int - Int - Bool
 a `divisibleBy` n = a `rem` n == 0
 
 main :: IO ()
 main = do
 [n,k] - (map int . B.split ' ') `fmap` B.getLine :: IO [Int]
 
 let
 doLine :: Int - Int - IO Int
 doLine r _ = B.getLine = return . testDiv r
 -- 'return' moved here  ^^


What follows is a solution to the original question, and then a dramatic
rewrite, showing the fastest way (that I know of) to parse \n separated
lists of numbers in Haskell.  The results should outperform C fairly
well.


*** Solution 1: don't be so lazy in the fold.

First, look at that lazy fold. A simple fix, try being explict about forcing
your accumulator:

doLine :: Int - Int - IO Int
doLine r _ = B.getLine = \s - return $! testDiv r s


And some timing data:

Original:
$ time ./A  in
29359
./A  in  1.52s user 0.06s system 93% cpu 1.679 total

Too lazy:
$ time ./B  in
29359
./B  in  3.84s user 0.26s system 82% cpu 4.957 total

Hand back some strictness hints:
$ time ./D  in
29359
./D  in  1.52s user 0.03s system 94% cpu 1.637 total


*** Solution 2: use lazy bytestrings to avoid gunky IO


Now, however, I'd give up on that explict getLine stuff, and use a lazy
bytestring. Something like this:

import Data.Maybe
import Data.List
import qualified Data.ByteString.Lazy.Char8 as L

main :: IO ()
main = do
(l:ls) - L.lines `fmap` L.getContents -- done with IO now.
let [n,k] = map int (L.split ' ' l)
print . foldl' (test k) 0 . map int . take n $ ls

test :: Int - Int - Int - Int
test k acc n | n `divisibleBy` k = acc+1
 | otherwise = acc

int :: L.ByteString - Int
int = fst . fromJust . L.readInt

divisibleBy :: Int - Int - Bool
a `divisibleBy` n = a `rem` n == 0


The general rule for bytestring loops is to avoid IO, and to use lazy
bytestrings if you need 'lines'. Also, program in a high level, using
combinators, rather than your own loops, so that fusion will kick in (we
get some list fusion here).

And running it:

$ time ./C  in
29359
./C  in  1.22s user 0.04s system 94% cpu 1.335 total

Ok, faster, and cleaner. Avoid mixing IO into your code!


*** Solution 3: 4x faster by processing strict cache chunks


Now the fun part.

The following code is the fastest way I know to process lists of numbers
(in any language). Its' based on similar code I wrote for the language
shootout.  The key trick is to use lazy bytestrings *only* as a method
for filling the cache with newline-aligned chunks of numbers. Once
you've got that perfectly-sized chunk, walk its lines, and process them.
This is all done in Haskell, and relies on an understanding of the low
level details of bytestring optimisations.

The general framework could be reused for any code that needs to process
a list of numbers in a file, where you care about speed.

It performs as follows:

$ time ./F  in
29359
./F  in  0.24s user 0.01s system 76% cpu 0.327 total

Pretty fast..

Previous experience[1] indicates it is pretty hard to write a C line
parsing program[2] that that run this fast.  And the code, with comments:

1. http://shootout.alioth.debian.org/gp4/benchmark.php?test=sumcollang=ghcid=0
2. http://shootout.alioth.debian.org/gp4/benchmark.php?test=sumcollang=gccid=2


{-# OPTIONS -fbang-patterns #-}

import Data.Char
import Data.Maybe
import Data.ByteString.Base
import qualified Data.ByteString.Char8  as S
import qualified Data.ByteString.Lazy.Char8 as L

main = do
ss - L.getContents -- done with IO now.

let (l,ls) = L.break (=='\n') ss

-- don't need count, we're allocating lazily
k  = fst . fromJust . L.readInt . last . L.split ' ' $ l

file   = L.toChunks (L.tail ls) -- a lazy list of strict cache 
chunks

print $ process k 0 file

divisibleBy :: Int - Int - Bool
a `divisibleBy` n = a `rem` n == 0

-- -
--
-- Optimised parsing of strict bytestrings representing \n separated numbers
--

--
-- we have the file as a list of cache chunks
-- align them on \n boundaries, and process each chunk separately
-- when the next chunk is demanded, it will be read in.
--
process :: Int - Int - [S.ByteString] - Int
process k i []  = i
process k !i (s:t:ts) | S.last s /= '\n' = process k (add k i s') ts'
  where
(s',r) = S.breakEnd (=='\n') s
ts'= 

Re: [Haskell-cafe] Fast number parsing with strict bytestrings [Was: Re: Seemingly subtle change causes large performance variation]

2007-06-07 Thread Donald Bruce Stewart
dons:
 mdanish:
  Hello,
  
  I've been playing with the INTEST problem on SPOJ which demonstrates
  the ability to write a program which processes large quantities of
  input data.  http://www.spoj.pl/problems/INTEST/
   
  But when I make a slight modification, the program chews up a ton more 
  memory
  and takes more time:
  
  import Control.Monad
  import Data.Maybe
  import qualified Data.ByteString.Char8 as B
  
  divisibleBy :: Int - Int - Bool
  a `divisibleBy` n = a `rem` n == 0
  
  main :: IO ()
  main = do
  [n,k] - (map int . B.split ' ') `fmap` B.getLine :: IO [Int]
  
  let
  doLine :: Int - Int - IO Int
  doLine r _ = B.getLine = return . testDiv r
  -- 'return' moved here  ^^
 


And just following up with some GC statistics:

Original,

95% cpu 1.668 total

ghc: 258766440 bytes,
   452 GCs,
   3036/3036 avg/max bytes residency (1 samples), 
   3M in use, 0.00 INIT (0.00 elapsed), 
   1.51 MUT (1.63 elapsed), 
   0.01 GC (0.03 elapsed) :ghc

Too lazy:

96% cpu 4.219 total

ghc: 278683532 bytes,
   495 GCs,
   -- 14729345/52642396 avg/max bytes residency (7 samples),
   -- 85M in use,
   0.00 INIT (0.00 elapsed),
   1.68 MUT (1.81 elapsed),
   -- 2.07 GC (2.36 elapsed) :ghc

(clear space leak)

Fixing above program with $!:

94% cpu 1.656 total
ghc: 257394052 bytes
   451 GCs,
--2288/2288 avg/max bytes residency (1 samples),
--1M in use,
   0.00 INIT (0.00 elapsed),
   1.49 MUT (1.64 elapsed),
   0.01 GC (0.01 elapsed) :ghc

Using lazy bytestrings for pure processing:

90% cpu 1.424 total
ghc: 219403252 bytes,
   410 GCs,
   70527/74236 avg/max bytes residency (10 samples),
   2M in use,
   0.00 INIT (0.00 elapsed), 
   1.25 MUT (1.40 elapsed),
   0.01 GC (0.01 elapsed) :ghc

And the killer strict chunk parser:

78% cpu 0.327 total
ghc: 20685092 bytes,
--38 GCs,
--81348/81348 avg/max bytes residency (1 samples),
   2M in use,
   0.00 INIT (0.00 elapsed),
--0.21 MUT (0.32 elapsed),
   0.00 GC (0.00 elapsed) :ghc

Very little data shuffled around in the last one.

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


Re: [Haskell-cafe] haskell version of fractal benchmark

2007-06-07 Thread Donald Bruce Stewart
clawsie:
 i recently saw a (yet-another) benchark comparing various languages:
 
 http://www.timestretch.com/FractalBenchmark.html
 
 while no haskell example was listed, i thought i would try a naive
 implementation myself for comparison. it is available here:
 
 http://www.b7j0c.org/dev/haskell/misc/time.hs
 
 my timing of the compiled code was slightly under three seconds over a
 few tests, landing sort of where i would expect a naive haskell
 implementation to place. i am sure people here could greatly improve
 my attempt. it may be that my solution is not even correct.

There's also a mandelbrot generator on the shootout,


http://shootout.alioth.debian.org/gp4/benchmark.php?test=mandelbrotlang=ghcid=4

Some things to remember using Doubles:

* {-# OPTIONS -fexcess-precision #-} 
* -fvia-C
* -fbang-patterns
* -optc-O2 -optc-mfpmath=sse -optc-msse2
* -optc-march=pentium4

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


Re: [Haskell-cafe] Fast number parsing with strict bytestrings [Was: Re: Seemingly subtle change causes large performance variation]

2007-06-07 Thread Donald Bruce Stewart
dons:
 dons:
  mdanish:
   Hello,
   
   I've been playing with the INTEST problem on SPOJ which demonstrates
   the ability to write a program which processes large quantities of
   input data.  http://www.spoj.pl/problems/INTEST/

   But when I make a slight modification, the program chews up a ton more 
   memory
   and takes more time:
   
   import Control.Monad
   import Data.Maybe
   import qualified Data.ByteString.Char8 as B
   
   divisibleBy :: Int - Int - Bool
   a `divisibleBy` n = a `rem` n == 0
   
   main :: IO ()
   main = do
   [n,k] - (map int . B.split ' ') `fmap` B.getLine :: IO [Int]
   
   let
   doLine :: Int - Int - IO Int
   doLine r _ = B.getLine = return . testDiv r
   -- 'return' moved here  ^^
  
 
 
 Original,
 
 95% cpu 1.668 total
 
 ghc: 258766440 bytes,
452 GCs,
3036/3036 avg/max bytes residency (1 samples), 
3M in use, 0.00 INIT (0.00 elapsed), 
1.51 MUT (1.63 elapsed), 
0.01 GC (0.03 elapsed) :ghc
  
 And the killer strict chunk parser:
 
 78% cpu 0.327 total
 ghc: 20685092 bytes,
 --38 GCs,
 --81348/81348 avg/max bytes residency (1 samples),
2M in use,
0.00 INIT (0.00 elapsed),
 --0.21 MUT (0.32 elapsed),
0.00 GC (0.00 elapsed) :ghc
 

I note there was a missing constructor specialisation happening in the
calls to 'add', in the good program. We can fix that with some well
place inline pragma:

add :: Int - Int - S.ByteString - Int
add k i s = if S.null s then i else test k i (parse x) xs
  where (x,xs) = uncons s
{-# INLINE add #-}

Before, GHC -ddump-simpl-stats reported:

22 RuleFired
2 SC:$wprocess1
4 SC:$wprocess2
2 SC:comb1

After:
24 RuleFired
4 SC:$wprocess1
4 SC:$wprocess2
2 SC:comb1

And timing stats:

$ time ./F  in
29359
./F  in  0.20s user 0.04s system 81% cpu 0.288 total

So some 10% better.  It's often a good idea to inline non-recursive wrapper
functions like this, in bytestring code.

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


Re: [Haskell-cafe] (pre)compiled Haskell compiler for True64/Alpha

2007-06-06 Thread Donald Bruce Stewart
lutz:
 Does anyone have a haskell compiler for True64 (formerly known as OSF/1) on
 Alpha hardware?
 
 I'm currently unable to compile the first bootstrap compiler.
 Any hint which compiler should I start with?
 
 I'll send detailed error reports only if I do not succeed in the next hours.

I think the last ghc I ran on OSF/1 alpha was hmm, 5.04.2?

You might be able to get a newer one working though. The 6.x series is
fairly easy to bootstrap (there's alpha/debian for example), so if you
run into problems, let glasgow-haskell-users@ know.

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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Donald Bruce Stewart
Phlex:
 Hello all,
 
 I'm coming from the OO world, and there's something i don't quite 
 understand in the way haskellers manipulate data (as all functional 
 programmers i guess).
 
 Let's say i have a deep nested data structure.
 Universe containing galaxies, containing solar systems, containing 
 planets, containing countries, containing inhabitants, containing 
 ...whatever.
 
 Using the OO paradigm, once i get a reference to an inhabitant, i can 
 update it quite easily (say by changing it's age), and that's the end of it.
 
 On the other side, using the functional paradigm, it seems to me that 
 the function i use in order to create a _new_ inhabitant with a 
 different age will need to have knowledge of the country over it, the 
 planet ..and so on up to the universe...as i need to update all these 
 structures to reflect the change. This is pretty bad and most probably 
 doesn't need to be like this.
 
 So here I am hoping for you all to give me some pointers on how this is 
 done the functional way.
 

Nope, its not done like that. You share as much of the original
structure as you can, as a general principle.

Imagine updating a node in a tree by just detaching and reattaching a
pointer.

[1] [1]
/ \ / \
  [2] [3] update node 5   [2] [3] 
   / \ with value 7   / \
 [4] [5] [4] *

and share the rest of the structure. Since the rest isn't mutable
anyway, you can share all over.

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


Re: [Haskell-cafe] Re: I just don't get it (data structures and OO)

2007-06-03 Thread Donald Bruce Stewart
apfelmus:
 Phlex wrote:
  Donald Bruce Stewart wrote:
 
  Imagine updating a node in a tree by just detaching and reattaching a
  pointer.
 
  [1] [1]
  / \ / \
[2] [3] update node 5   [2] [3]
/ \ with value  7   / \
  [4] [5] [4]  *
 
  and share the rest of the structure. Since the rest isn't mutable
  anyway, you can share all over.
  
  That's precisely the thing i don't understand.
  In order to update node 3 with a new pointer, i need to mutate it, so i
  need to recreate it, and so on up to node 1.
 
 Yes, that's correct, I think Dons shared a bit too much here :)

Spent too much time with zippers lately ;)

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


Re: [Haskell-cafe] Re: Just for a laugh...

2007-06-03 Thread Donald Bruce Stewart
almeidaraf:
 On 6/3/07, Rafael Almeida [EMAIL PROTECTED] wrote:
 The site seems to be asking for the internal floating point
 representation.  So it doesn't matter if it's IEEE 754, if the ints are
 2-complements, or whatever. I used this code as a quick hack for one of
 my programs, but I think it would work in this case. It should work for
 any Storable type.
 
 import qualified Data.ByteString as BS
 import Data.ByteString.Base
 import Foreign.ForeignPtr
 import Foreign.Storable
 binPut num =
 do
 fptr - mallocForeignPtrBytes (sizeOf num)
 withForeignPtr (castForeignPtr fptr) (\x - poke x num)
 BS.writeFile /tmp/foo (BS.reverse $ fromForeignPtr fptr (sizeOf 
 num))
 
 Ops, that reverse was needed for what I was doing, but not needed for
 this particular problem, so the code should actually be:
 
 import qualified Data.ByteString as BS
 import Data.ByteString.Base
 import Foreign.ForeignPtr
 import Foreign.Storable
 binPut num =
do
fptr - mallocForeignPtrBytes (sizeOf num)
withForeignPtr (castForeignPtr fptr) (\x - poke x num)
BS.writeFile /tmp/foo (fromForeignPtr fptr (sizeOf num))
 ^^^
Interesting use of ByteStrings to print foreigin ptr arrays there. 

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


Re: [Haskell-cafe] Just for a laugh...

2007-06-01 Thread Donald Bruce Stewart
bulat.ziganshin:
 Hello Andrew,
 
 Thursday, May 31, 2007, 11:47:28 PM, you wrote:
  (Otherwise... wasn't there some library somewhere for serialising values
  in binary?)
 
 Binary, AltBinary (see latest HCAR), just an example using AltBinary:
 
 main = do
   let s = encode (1.1::Float)  -- s has type String
   print (decode s::Float, s)
 

Data.Binary is on hackage, 

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/binary-0.3

encode :: (Binary a) = a - ByteString
decode :: (Binary a) = ByteString - a

 let s = encode (1.1 :: Float)
 :t s
s :: Data.ByteString.Lazy.ByteString
 s
LPS [\NUL\NUL\140\204\205\255\255\255\255\255\255\255\233]

 decode s :: Float
1.1

See also the older NewBinary, 
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/NewBinary-0.1

-- Don

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


Re: [Haskell-cafe] Just for a laugh...

2007-06-01 Thread Donald Bruce Stewart
jules:
 Donald Bruce Stewart wrote:
  let s = encode (1.1 :: Float)
  :t s
 s :: Data.ByteString.Lazy.ByteString
  s
 LPS [\NUL\NUL\140\204\205\255\255\255\255\255\255\255\233]
 
  decode s :: Float
 1.1
 
 But doesn't Data.Binary serialise to a guaranteed representation, i.e. 
 machine-independent? Whereas this (stupid) question explicitly asked for 
 *your particular hardware's* floating point rep.
 

Ah right. Missed that. There was a long thread on the libraries@ mailing
list on doing this (David Roundy suggested it, initially, iirc) a couple
of months ago. Might be useful to read.

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


Re: [Haskell-cafe] Just for a laugh...

2007-06-01 Thread Donald Bruce Stewart
andrewcoppin:
 Donald Bruce Stewart wrote:
 See also the older NewBinary, 
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/NewBinary-0.1
   
 
 Now that's just ironic...
 
 
 Incidentally, I've been thinking. You *might* want the binary 
 representation of things if you were going to, say, compress or encrypt 
 data before putting it into a file or whatever. Actually in Java 
 (bleeeh) you can wrap things around a stream so that data gets 
 compressed and transformed between where the program writes it, and 
 where it hits the endpoint. Haskell doesn't have a library for this, and 
 I don't immediately see how to implement one. It would be darn useful to 
 have a standard setup for this though. That way, when somebody wants to 
 implement a new way to do zlib compression or a SHA-256 implementation 
 or... there will already be a standardised way to access the binary 
 representation of data without having to write it to a file.
 
 (If any of that made sense...)?)

Our zlib and bzlib2 bindings operate on in-memory lazy bytestrings. 
They thus provide:

compress :: ByteString - ByteString

and its inverse. So you can chain them with decoding:


writeFile foo.gz . compress . encode $ myvalue

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


Re: [Haskell-cafe] Has anyone looked into adding subtyping to Haskell?

2007-05-31 Thread Donald Bruce Stewart
stefan:
 Al,
 
 Has there been any work on extending Haskell's type system with  
 structural subtyping?
 
   Koji Kagawaga. Polymorphic variants in Haskell. In Andres Loeh,  
 editor, Proceedings of the 2006 ACM SIGPLAN Workshop on Haskell,  
 Portland, Oregon, USA, September 17, 2006, pages 37--47. ACM Press,  
 2006. [1]
 
 What is the canonical solution to the expression problem in Haskell?
 
 Not canonical but Loeh and Hinze have proposed open data types:
 

For a short term solution, we used Typeable + type classes to provide a
open Message data type. Similar techniques are used in Simon Marlow's
extensible exceptions paper.

-- An open Message type
class Typeable a = Message a

--
-- A wrapped value of some type in the Message class.
--
data SomeMessage = forall a. Message a = SomeMessage a

--
-- And now, unwrap a given, unknown Message type, performing a (dynamic)
-- type check on the result.
--
fromMessage :: Message m = SomeMessage - Maybe m
fromMessage (SomeMessage m) = cast m

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


Re: [Haskell-cafe] Efficiency question

2007-05-30 Thread Donald Bruce Stewart
rwiggerink:
 
 I'm pretty new to Haskell, so forgive me if my question is due to my
 non-functional way of thinking...
 
 I have the following code:
 
 module Main where
 
 main = print solution
 
 solution = solve 100
 
 solve d = countUniqueFractions d 2 1 0
 
 canBeSimplified (a,b) = gcd a b  1
 
 countUniqueFractions stopD currentD currentN count | currentD  stopD =
 count
| currentN == currentD =
 countUniqueFractions stopD (currentD + 1) 1 count
| canBeSimplified
 (currentN, currentD) = countUniqueFractions stopD currentD (currentN+1)
 count
| otherwise =
 countUniqueFractions stopD currentD (currentN+1) (count + 1)
 
 When I run this code, I get a stack overflow. I don't understand why. Could
 anyone explain please?

Lazy accumulators. Did you try compiling with ghc -O2 ?

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


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

2007-05-30 Thread Donald Bruce Stewart
jon:
 On Wednesday 30 May 2007 06:58:36 Ketil Malde wrote:
  On Tue, 2007-05-29 at 14:05 -0500, Doug Kirk wrote:
   I *want* people (and companies) to move to Haskell
 
 As a complete noob considering making a commercial venture into Haskell, may 
 I 
 ask what people's opinions are on this? Are there many Haskell products?

Have a look at the industry page for the larger businesses using Haskell,

http://haskell.org/haskellwiki/Haskell_in_industry

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


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

2007-05-29 Thread Donald Bruce Stewart
kahl:
   
   P.S. Have some cute code:
   
   Control.Monad.Fix.fix ((1:) . scanl (+) 1)
 
 
 Cute!
 
 But what an un-cute qualified name:
 
 :t Control.Monad.Fix.fix
 Control.Monad.Fix.fix :: (a - a) - a
 
 
 Has nothing to do with monads,
 and would perhaps be considered as ``out of Control'' in any case...
 

I see it has moved into Data.Function,

module Data.Function
( -- * Prelude re-exports
id, const, (.), flip, ($)
-- * Other combinators
, fix
, on
  ) where

A much better place.

-- Don

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


[Haskell-cafe] data PLZ a

2007-05-29 Thread Donald Bruce Stewart
We got the names wrong!

data PLZ a = AWSUM_THX a | O_NOES String

instance Monad PLZ where
return= AWSUM_THX
fail  = O_NOES
O_NOES s= _ = O_NOES s
AWSUM_THX x = f = f x

Thanks to mauke on #haskell.

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


Re: [Haskell-cafe] data PLZ a

2007-05-29 Thread Donald Bruce Stewart
d.w.mead:
 
is that your implementation of LOLCODE?
:P
 
On 5/29/07, Donald Bruce Stewart [EMAIL PROTECTED]
wrote:
 
  We got the names wrong!

  data PLZ a = AWSUM_THX a | O_NOES String

  instance Monad PLZ where
  return= AWSUM_THX
  fail  = O_NOES
  O_NOES s= _ = O_NOES s
  AWSUM_THX x = f = f x

  Thanks to mauke on #haskell.
  -- Don

Yeah. Someone want to finish off LOLCODE as a EDSL? :-)

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


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

2007-05-29 Thread Donald Bruce Stewart
vincent:
 i see that the definition of fix (from Control.Monad.Fix) could not be
 any simpler:
 
  fix f = let x = f x in x
 
 same goes for the type:
 
 Prelude :t Control.Monad.Fix.fix
 Control.Monad.Fix.fix :: (a - a) - a
 
 it's just that i find it difficult to get concrete intellectual mileage
 out of it.
 i can reproduce results for specific examples (and even manipulate them
 a bit), but feel like i'm missing something deep yet simple. say, i
 would not know where and how to apply it. so obviously true
 understanding is still missing. reminds me of my first encounters with
 $H \psi = E \psi$. ;-)
 
 most likely, i should just more carefully read the references i cited
 myself ;-)
 
 anyhow. if someone has a pedestrian's guide to the fixed point
 operator lying around, a link would be much appreciated.

I use it when I need a local loop expression, maybe once every couple of
months. A real world example from xmonad,

 f = fix $ \again - do
more - checkMaskEvent d enterWindowMask ev
when more again 

That is, keep sucking up X events till there's no 'more'.
Of course, you can always just name your loop with 'where' and use that.

 f = go
   where
 go = do
more - checkMaskEvent d enterWindowMask ev
when more go

TMTOWTDI with recursion :-)

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


Re: [Haskell-cafe] Coding Standards (Coding Conventions)

2007-05-28 Thread Donald Bruce Stewart
pvolgger:
 I wonder if there are any Coding Standards or Coding Conventions for 
 Haskell. Does anybody know something about it?

We've collected some style guides on the wiki. You could also look at
projects whose code you think is in good style.

http://haskell.org/haskellwiki/Category:Style

GHC has a style guide. Our small little window manager, xmonad, also has
a pretty strict style guide.

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


Re: [Haskell-cafe] Coding Standards (Coding Conventions)

2007-05-28 Thread Donald Bruce Stewart
conrad:
 On 28/05/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote:
 Our small little window manager, xmonad, also has a pretty strict style 
 guide.
 
 where? Perhaps I need coffee, but I couldn't find this in the source
 (xmonad, x11-extras, XMonadContrib) or documentation links from
 xmonad.org :-/

Oh, sorry, it doesn't have a written style guide, just some conventions
we should write down. I was unclear.

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


Re: [Haskell-cafe] Slower with ByteStrings?

2007-05-28 Thread Donald Bruce Stewart
bulat.ziganshin:
 Hello Bryan,
 
 Sunday, May 27, 2007, 3:30:50 AM, you wrote:
  I think, given my simple algorithm that means that (==) for
  ByteStrings is slower than (==) for String.  Is this possible?
 
  Yes indeed.  Over ByteStrings, (==) is implemented as a call to memcmp.
For small strings, this loses by a large margin because it has to go
  through the FFI.
 
 how about using *unsafe* memcmp import and more complex code for the
 case of large BS length?
 
 a==b | min (length a) (length b)  20   = memcmp a b
  
 

Good idea. I'll try to do this before the next bytestring comes out .

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


Re: [Haskell-cafe] Newbie list question

2007-05-27 Thread Donald Bruce Stewart
junkywunky:
 
 type Person = (NI, Age, Balance)
 type Bank = [Person]
 
 credit :: Bank - [Person]
 credit [(a,b,c)] = [(a,b,c)]
 
 This code works when I type in:
 
 credit [(1,2,3)]
 
 but doesn't work when I type in:
 
 credit [(1,2,3),(4,5,6)]

You're pattern matching in 'credit' on a list of a single element.
Perhaps you mean to write:

credit :: Bank - [Person]
credit x = x

or perhaps return just the first element of the list:

credit [] = []
credit (x:xs) = x

You might want to start with one of the tutorials on Haskell programming
listed on haskell.org. The wikibook is quite a good start.

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


Re: [Haskell-cafe] Newbie list question

2007-05-27 Thread Donald Bruce Stewart
junkywunky:
 
 That's the thing. I want to return a list of people who are not overdrawn.
 Something like:
 
 type NI = Int
 type Age = Int
 type Balance = Int
 type Person = (NI, Age, Balance)
 type Bank = [Person]
 
 credit :: Bank - [Person]
 credit [(a,b,c)] = [(a,b,c)] if c = 0 
   then [(a,b,c)] 
   else error overdrawn customer
 
 except this doesn't work with things like:
 

Right, you mean to write a list filter. List comprehensions are useful
for this:


credit xs = [ p | p@(a,b,c) - xs, c = 0 ] 

or maybe:

credit xs = filter ok xs
where
ok (a,b,c) = c = 0

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


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

2007-05-27 Thread Donald Bruce Stewart
isaacdupree:
 -BEGIN PGP SIGNED MESSAGE-
 Hash: SHA1
 
 Isaac Dupree wrote:
  The expression is bound to a random top level identifier (harmless to
  guess)
  
  What about the non-recursive
  
  case ...expr... of x - take 2048 (show x)
  
  this way expr can't refer to x (it doesn't at all need to be randomly
  generated this way) and definitely can't bind other things like take and
  show (they probably should be qualified anyway)
 
 er, wait, I'm confused. Is it top-level? If not, it could just be
 
 take 2048 (show ( ...expr... ))
 
 and it doesn't look top-level to me from the lambdabot code in
 scripts/RunPlugs.hs

Ah right. No, it is bound to a top level value, but is itself not -- its
a local binding so we can use {-# #-} pragmas to get more precise error
messages (if I recall correctly).

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


Re: [Haskell-cafe] Cannot compile Network.CGI programs

2007-05-26 Thread Donald Bruce Stewart
aneumann:
 -BEGIN PGP SIGNED MESSAGE-
 Hash: RIPEMD160
 
 Hi,
 
 I installed the Network.CGI package and tried to compile the Hello World
 example on my Ubuntu machine.
 
 ghc cgi.hs -o cgi

Missing --make to link against the cgi and network and mtl packages.

Also, -O or -O2, you may as well optimise your code :-)

I'd use:

ghc --make -O cgi.hs -o cgi

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


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

2007-05-26 Thread Donald Bruce Stewart
andrewcoppin:
 Since the online lambdabot still doesn't seem to want to talk to me, 
 I've been thinking about how I might rectify the situation...
 
 Apparently GHC has a flag that makes it execute a Haskell expression 
 directly. For example,
 
 C:\ ghc -e map (2*) [1,2,3]
 [2,4,6]
 
 Now, if I could just figure out how to make a web server call GHC... I'm 
 laughing!
 
 Oh, but there is the *minor* detail that I am literally allowing 
 unauthenticated users to perform arbitrary code execution. For example,
 
 C:\ ghc -e writeFile \Test.txt\ \Hi mum!\
 
 (Generates a file on my harddrive Test.txt containing the text Hi mum!.)
 
 AFAIK, Lambdabot dissalows any expression that performs IO. In Haskell, 
 this is beautifully easy: reject any expression having an IO type. And 
 it seems that GHC accepts not just an *expression*, but a *command*. In 
 particular, this works:
 
 C:\ ghc -e :t writeFile \Test.txt\ \Hi mum!\
 writeFile Test.txt Hi mum! :: IO ()
 
 However, when you consider that the result type could be IO () or IO 
 String or IO [Either (Maybe Int, (String, Bool)) [Either (Int - 
 String) (Complex Integer)]], and the expression itself may well contain 
 the :: sequence... you see we have a nontrivial parsing task here! 
 (Get the parsing wrong and somebody might be able to do Evil Things to 
 the box.)

Don't use parsing for security, use the type checker. By using 'show',
you can write an instance for IO a that renders all IO harmless. Then
just wrap your user's arbitrary expression in 'show. 

This is what lambdabot does. So we have:

Safe, pure expressions, just shown:

20:04  dons  map (^2) [1..]
20:04  lambdabot 
[1,4,9,16,25,36,49,64,81,100,121,144,169,196,225,256,289,324,361,400,441,484...

IO, shown, by a Show instance that renders it harmless:

20:04  dons  readFile /etc/passwd
20:04  lambdabot  IO [Char]

And we can then play some clever tricks for functions:

20:04  dons  ord
20:04  lambdabot  Char - Int

 The other possibility is to somehow run GHC under a user context that 
 doesn't *have* write access to anything on the filesystem. That way 
 there is no margin for error.

Well, that's overkill, when you have a pure language, with a strong type
system that tags IO. :-)

 This leaves only the problem of how to make a web server call GHC. I can 
 think of a number of possibilities.
 - Write my own HTTP server from scratch. (Not keen...)
 - Configure Apache to do it. (Is that physically possible?)
 - Use Apache and some bizzare Perl scripting to do the actual call. 
 (Assuming *that* is possible.)
 - Use Apache and some Perl scripts to write the data to a text file, and 
 write a small Haskell program to poll the filesystem waiting for request 
 files to appear, run then though GHC, and put the result back into a 
 file. Write another Perl script to slurp up the result and send it back 
 to the caller.
 - Doesn't Java have a free HTTP server implementation? Maybe I could use 
 that...
 - ...others?

You could also just use 'runplugs' from lambdabot, which also handles
non-terminating programs :-)

 (I'm not sure why this should be, but it seems that Don has made several 
 replies to my emails that didn't show up in my inbox, and only show up 
 on the list archives. Oh well, anyway...)
 
 I lurk on the POV-Ray NNTP server, and we recently had quite a 
 discussion about Haskell. I'd *love* to be able to say to people hey, 
 you don't even need to bother working out how to install GHC, just CLICK 
 THIS LINK and you can play with Haskell instantly! But at the moment 
 I'm not entirely sure how to set this up. Ideas?

Yeah, an online solution to this would be good. lambdabot gives us a
start, lambdaweb goes further. But the last 5% need more work.

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


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

2007-05-26 Thread Donald Bruce Stewart
On 26/05/07, Matthew Sackman [EMAIL PROTECTED] wrote:
(On the other hand, I don't know of anyone outside immediate
haskellers using Darcs.)
  
Good idea to get some data on this, instead of speculating. Let's do that.
A quick google reveals the Haskell crew is far from alone as users. 

http://www.google.com.au/search?hl=enq=_darcs

Here's the first 20 hits google finds:

repo.nitroproject.org/_darcs/ 
darcs.pugscode.org/_darcs/
common-lisp.net/project/cffi/darcs/cffi/_darcs/
www.cymraeg.ru/repos/geiriadur/_darcs/current/
www.cse.unsw.edu.au/~dons/code/polymer/_darcs/  -- Haskell
www.cse.unsw.edu.au/~dons/code/goa/_darcs/  -- Haskell
zargon.hobbesnet.org/~squires/repos/torbutton/_darcs/
facets.rubyforge.org/src/_darcs/
www.n-heptane.com/nhlab/repos/cabalDebianTemplate/_darcs/
www.khjk.org/~sm/code/advopost/_darcs/
repetae.net/john/repos/GetOptions/_darcs/  -- Haskell
james.tooraweenah.com/darcs/netrek-server/_darcs/ 
users.tkk.fi/~ptotterm/darcs/macports/_darcs/ 
mumble.net/~campbell/darcs/slime48/_darcs/ 
galinha.ucpel.tche.br/chicken/_darcs/
mp3fs.sourceforge.net/mp3fs/_darcs/ 
www.scannedinavian.com/~eric/hpaste/_darcs/-- Haskell
www.lshift.net/~tonyg/json-scheme/_darcs/ 
darcs.fh-wedel.de/hxt/_darcs/  -- Haskell

Of which only 5/20 are Haskell repos.

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


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

2007-05-26 Thread Donald Bruce Stewart
claus.reinke:
 Oh, but there is the *minor* detail that I am literally allowing
 unauthenticated users to perform arbitrary code execution. For example,
 ..
 AFAIK, Lambdabot dissalows any expression that performs IO. In Haskell,
 this is beautifully easy: reject any expression having an IO type.
 ..
 Don't use parsing for security, use the type checker. By using 'show',
 you can write an instance for IO a that renders all IO harmless. Then
 just wrap your user's arbitrary expression in 'show.
 
 careful please!-) we've had enough of that kind of issues in scripts, CGI, 
 ..
 sandboxes, etc. to have learned the lesson that *this is not a minor 
 detail*,
 and requires full attention to details, especially, but not only if, meta-
 programming is involved (interpreting input strings as programs, or using
 hs-plugins, template haskell).
 
 two obvious exceptions: 'unsafePerformIO' and FFI. even expressions
 not involving IO might use it internally (also, you want to disallow both
 write and read access). less obvious: DOS-style issues, eg, filling the
 process table or claiming all memory. least obvious: things we've missed.
 
 it would really be nice if someone would sit down and sort this all out
 in detail. there'd still be no guarantee that such a Haskell sandbox was
 totally safe, but at least all issues and solutions could be shared, making
 it as safe as the community  knows how.

Claus is right. You need type guarantees, and more!

Lambdabot uses 1) type guarantee of no-IO at the top level, along with
2) a trusted module base (pure module only, that are trusted to not
export evil things), as well as 3) restricting only to H98-language only
(things like TH can, and have been, exploited, for example).

So, no-IO type, trusted base of no FFI, no unsafe*, resource limits, and
no extensions beyond H98, then , hopefully, we're ok.

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


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

2007-05-26 Thread Donald Bruce Stewart
 it would really be nice if someone would sit down and sort this all out
 in detail. there'd still be no guarantee that such a Haskell sandbox was
 totally safe, but at least all issues and solutions could be shared, making
 it as safe as the community  knows how.

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

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

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

The security mechanisms were briefly described in the 2004 hs-plugins
paper, if I recall, but otherwise, I don't think we've documented the 
techniques. Maybe we should, as many issues have been encountered over
the years, further and further constraining the kinds of things that are
allowed.

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


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

2007-05-26 Thread Donald Bruce Stewart
isaacdupree:
 -BEGIN PGP SIGNED MESSAGE-
 Hash: SHA1
 
 Donald Bruce Stewart wrote:
  Lambdabot uses 1) type guarantee of no-IO at the top level, along with
  2) a trusted module base (pure module only, that are trusted to not
  export evil things), as well as 3) restricting only to H98-language only
  (things like TH can, and have been, exploited, for example).
 
 And lambdabot's only allowing _expressions_, so GHC's (former?)
 vulnerability to instances of Ix that return out-of-bounds indexes did
 not affect it.

Oh yes, it only allows expressions (how could I forget that?), meaning
also that, for example, crafty newtype recursion is disallowed. And of
course, no evil Ix instances.

Oh, also, there's another exploit using a variety crafty expressions
that trigger pathological type inference behaviour, causing the type
checker to effectively lock up the system. (One is particularly easy to
come up with...). There's really a lot of things to watch out for,
actually.

We should document all the interesting exploits that have been found
over the years!

 There are some extensions that are safe... explicit forall, rank-N
 types, etc... which can be enabled on an opt-in basis so that only
 safe ones are chosen?

We could do that (explicit forall is probably the most requested).
Currently we only allow -fextended-defaulting, (giving ghci like
defaulting).

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


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

2007-05-26 Thread Donald Bruce Stewart
overdrigzed:
 
  As far as I know, hs-plugins works by taking an
  expression, writing it
  to a file, calling GHC to parse it, transform it to Core,
  optimise it,
  transform it to STG, optimise it, transform it to C--,
  optimise it,
  transform it to ANSI C, optimise it, pass it to GCC,
  compile it, link
  it, and *then* using the GHC runtime linker to load the
  generated object
  code into memory, type-check it, and, finally, execute
  it.
 
Don't forget the Evil Mangler, which optimises the compiled
assembly!
[1]http://www.cse.unsw.edu.au/~chak/haskell/ghc/comm/the-bea
st/mangler.html
 

Close, but hs-plugins uses -fasm, so its:

File - Core - STG - C-- - ASM - ld - link - typecheck - run.

Avoiding mangler and gcc.

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


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

2007-05-26 Thread Donald Bruce Stewart
claus.reinke:
 The #haskell people have been working on this for about 3 years now.
 The result is the 'runplugs' program, which I've talked about in
 previous mails.
 
http://www.cse.unsw.edu.au/~dons/code/lambdabot/scripts/RunPlugs.hs
 
 It uses hs-plugins for the evaluation, along with the points about IO
 prevention via type checking, resource limits controlled by the OS,
 language extension preventions, and a trusted (audited) module base.
 
 great! and since it is presumably in daily use, there is both pressure to
 fix holes as soon as they are discovered, and ongoing discovery in a
 safe (or at least friendly) environment.

I've listed the mechanisms we use, and exploits that have been thought
of, or discovered, over the years, on the page:

http://haskell.org/haskellwiki/Safely_running_untrusted_Haskell_code

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


Re: [Haskell-cafe] Slower with ByteStrings?

2007-05-26 Thread Donald Bruce Stewart
bos:
 Jason Dagit wrote:
 
 I think, given my simple algorithm that means that (==) for
 ByteStrings is slower than (==) for String.  Is this possible?
 
 Yes indeed.  Over ByteStrings, (==) is implemented as a call to memcmp. 
  For small strings, this loses by a large margin because it has to go 
 through the FFI.
 

Yes, a non-memcmp version can sometimes be profitably used here.

Something like this Core:

eq !n (Ptr p) (Ptr q) = inlinePerformIO $ IO $ go n p q
  where 
go !n p q s
| n == 0= (# s , True #)
| otherwise = case readInt8OffAddr# p 0# s of
(# s, a #) - case readInt8OffAddr# q 0# s of
(# s, b #) | a /=# b   - (# s, False #)
   | otherwise - go (n-1) (plusAddr# p 1#) 
(plusAddr# q 1#) s

Ok, so that's not Core, but it could be ;)

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


Re: [Haskell-cafe] Why this exception occurs ?

2007-05-25 Thread Donald Bruce Stewart
leaveye.guo:
 Hi.
 
 In GHCi ver 6.6, why this happens ?
 
 Prelude Data.ByteString Data.ByteString.pack $! Prelude.map (`rem` 256) $ 
 [0..511]
 *** Exception: divide by zero

Interesting...

Is that just,
Data.ByteString.pack $ [0..255] ++ [0..255]
?

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


Re: [Haskell-cafe] Why this exception occurs ?

2007-05-25 Thread Donald Bruce Stewart
leaveye.guo:
 Hi.
 
 In GHCi ver 6.6, why this happens ?
 
 Prelude Data.ByteString Data.ByteString.pack $! Prelude.map (`rem` 256) $ 
 [0..511]
 *** Exception: divide by zero

It's the use of `rem` on Word8, by the way:

Prelude (0 `rem` 256) :: Data.Word.Word8 
*** Exception: divide by zero

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


Re: [Haskell-cafe] Why this exception occurs ?

2007-05-25 Thread Donald Bruce Stewart
dons:
 leaveye.guo:
  Hi.
  
  In GHCi ver 6.6, why this happens ?
  
  Prelude Data.ByteString Data.ByteString.pack $! Prelude.map (`rem` 256) $ 
  [0..511]
  *** Exception: divide by zero
 
 It's the use of `rem` on Word8, by the way:
 
 Prelude (0 `rem` 256) :: Data.Word.Word8 
 *** Exception: divide by zero
 

Sorry, I should clarify, think about how to represent:

256 :: Word8

;-)

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


Re: [Haskell-cafe] Why this exception occurs ?

2007-05-25 Thread Donald Bruce Stewart
ketil:
 On Fri, 2007-05-25 at 17:33 +1000, Donald Bruce Stewart wrote:
 
  Sorry, I should clarify, think about how to represent:
  
  256 :: Word8
 
 So the error isn't really divide by zero, but overflow.  I've been
 bitten by this, too, and L.Guo should count him/herself lucky to get an
 error, and not just incorrect results.

I've always thought that the obfuscation opportunities for Num
literal overloading, combined with Num *overflowing* were
underappreciated.

instance Num String anyone? Mwhaha


-- Don

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


Re: [Haskell-cafe] instance Monad AppF - Faster than the list monad?

2007-05-25 Thread Donald Bruce Stewart
greenrd:
 The following Haskell 98 module implements a generalisation of
 Prelude.ShowS for any type. Should be pretty easy to incorporate this
 into code which currently uses the list monad non-trivially, and get
 better performance - but can this be right? Surely someone would have
 published this before if that was true? I haven't actually done any
 performance tests. Anyway, with this module you end up using function
 composition instead of list concatenation - except when converting from
 a list.
 
 module Data.List.AppF where
 
 import Control.Monad (MonadPlus (mplus, mzero), msum)
 
 -- Generalisation of ShowS
 newtype AppF a = AppF { unAppF :: [a] - [a] }
 
 instance Monad AppF where
 (=) = (msum .) . flip map . appFToList
 return = AppF . (:)
 
 instance MonadPlus AppF where
 mzero = AppF id
 mplus x y = AppF $ unAppF x . unAppF y
 
 -- Use this to convert Maybe a into AppF a, or indeed any other
 -- MonadPlus instance.
 maybeToMonadPlus :: MonadPlus m = Maybe a - m a
 maybeToMonadPlus = maybe mzero return
 
 listToAppF :: [a] - AppF a
 listToAppF = AppF . (++)
 
 appFToList :: AppF a - [a]
 appFToList = ($ []) . unAppF

Very nice!  Perhaps stick it on the wiki, or send it as a patch to the
dlist library?

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/dlist-0.2

I'd be happy to package it in that.

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


Re: [Haskell-cafe] (no subject)

2007-05-24 Thread Donald Bruce Stewart
leaveye.guo:
 Hi MailList Haskell-Cafe:
 
 Till now, which module / package / lib can i use to access binary
 file ? And is this easy to use in GHC ?

Data.Binary? Or perhaps just Data.ByteString, available on hackage,

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/binary-0.3

or in base.

-- Don


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


Re: [Haskell-cafe] (no subject)

2007-05-24 Thread Donald Bruce Stewart
leaveye.guo:
 Thanks for your suggestion, and sorry for the subject.
 
 I have read the introduction of Data.ByteString, it is helpful.
 
 And also, there is one problem left. When i read a binary file, data
 is truncated at the charactor EOF.
 
 Which function could do this work correctly ?

Hmm. Do you have an example?

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


Re: [Haskell-cafe] (no subject)

2007-05-24 Thread Donald Bruce Stewart
marco-oweber:
 On Thu, May 24, 2007 at 02:38:05PM +0800, L.Guo wrote:
  Thanks for your suggestion, and sorry for the subject.
  
  I have read the introduction of Data.ByteString, it is helpful.
  
  And also, there is one problem left. When i read a binary file, data is 
  truncated at the charactor EOF.
 
 You have to use readBinaryFile instead of readFile.
 I had the same trouble as well.
 
 I finally implemented accessing single characters in C and did use ffi
 because I didn't know haw to do this i haskell properly. ( using
 peek/poke functions 4 bytes got written (wihch is annotateted somewhere
 ) If you are interested I can sent you the modified ByteString package.
 
 If someone can tell me which haskell function to use to set a random
 char in a memory buffer I would be pleased ..

'poke'

or else use unboxed Word8 arrays

Check the src for Data.ByteString for examples.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re: [Haskell-cafe] (no subject)

2007-05-24 Thread Donald Bruce Stewart
leaveye.guo:
 to Ketil :
 
 Tring openBinaryFile, I notice that I cannot make one usable buffer,
 just because I can not find one function to malloc a memory or just
 get one change-able buffer.
 
 :-$

No 'malloc' here in Haskell land: that's done automatically.  Recall
that 'getContents' will read your opened file into a [Char]. (or use
Data.ByteString to get a stream of Word8).

What are you trying to do?

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


Re: Re: [Haskell-cafe] (no subject)

2007-05-24 Thread Donald Bruce Stewart
leaveye.guo:
 To read the handle openBinaryFile returns, both the hGetBuf and
 hGetBufNonBlocking needs one parameter _buf_ of type Ptr a.
 I can not get one data of that type.
 
 In the doc, there is only nullPtr, and also some type cast functions.
 I failed to find some other buffer-maker function.
 
 What should I do ?

I mean, what problem are you trying to solve? Ptrs aren't the usual way
to manipulate files in Haskell.

Here, for example, is a small program to print the first byte of a
binary file:

import System.IO
import qualified Data.ByteString as B

main = do
h - openBinaryFile a.out ReadMode
s - B.hGetContents h
print (B.head s)

When run:

$ ./a.out 
127

Note there's no mallocs or pointers involved.

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


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

2007-05-24 Thread Donald Bruce Stewart
bos:
 I'll condense my remaining replies to this thread into a single message, 
 to save people a little noise.

I'd just add that the response is literally overwhelming! Some 100-odd
volunteers to review, and a lot of mail besides.

Please bear with us as we try to surface under this mountain of
correspondance -- I'll try to summarise some answers tomorrow.

Yay, Haskell community!

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


Re: [Haskell-cafe] Re: Editor

2007-05-22 Thread Donald Bruce Stewart
Alistair_Bayley:
   I'm sure that I can quite reliably hit the command editor 
  keybindings I
   use many, many times faster than if I had to select them 
  from a menu.
  
  Note that the claimed time-consuming part is not to actually press the
  keybinding, but to chose and remember which one to press.
 
 Yes... except that for a lot of people, programmers especially, a lot of
 key bindings have become part of your motor memory, and so you can
 probably hit the common ones quite quickly without having to stop to
 think about which combination of keys to press. Cut/copy/paste are good
 examples of this, I think.

Exactly, this is why my shell, window manager, mp3 player, web browser,
and editor all use hjkl to navigate :-)

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


Re: [Haskell-cafe] Currying: The Rationale

2007-05-22 Thread Donald Bruce Stewart
prstanley:
 
  Hi
  What is the rationale behind currying? is it for breaking subroutines 
 into
  pure one-to-one mappings?
 
 We don't have 'subroutines' as such, but otherwise yes. Also, it gives us
 partial application - we don't have to apply all the parameters at once,
 and we can do interesting and useful things by applying only some to get a
 new function.
 
  If f x y = f x - a function which takes y for
  argument then does that mean that the second function already has 
 value x, as
  it were, built into it?
 
 Yep, though I can't make sense of what your syntax is supposed to mean.
 I shouldn't take it too literally. It's just to illustrate the point 
 that f x returns another function with x already in it and y passed 
 as argument.
 Could you perhaps demonstrate how you can apply parts of curried 
 functions in other functions in Haskell?

(^) applied to 2, produces a new function, we can map over a list:

Prelude let sq = (^2)
Prelude map sq [1..10]
[1,4,9,16,25,36,49,64,81,100]

or more explicitly:

Prelude let x `to` y = x ^ y
Prelude let sq x = x `to` 2
Prelude map sq [1..10]
[1,4,9,16,25,36,49,64,81,100]

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


[Haskell-cafe] Wanted: extended static checking for xmonad

2007-05-21 Thread Donald Bruce Stewart

When working on xmonad, we're trying to produce very clean, correct
code -- a window manager that just works. To do this, we're looking to
employ more static checking tools to the code base. Currently we use:

* QuickCheck (checks high level window manager behaviour)
* Catch (Neil's pattern match verifier, caught a couple of bugs)
* ghc -Wall

One other tool we're considering:

* HPC. check program coverage of the test suite.

But I suspect that there's an awful lot of other small checkers of
various kinds out there. 

So: 
* Do you know of some other cool code checking tool for Haskell?
* That could be used on xmonad (xmonad.org) to reduce code smell? 

If so, let us know! :-)

-- Don

P.S. Perhaps it is time for a wiki page documenting the available
extended static checking tools for Haskell.

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


Re: [Haskell-cafe] Random idea

2007-05-20 Thread Donald Bruce Stewart
andrewcoppin:
 Greetings.
 
 I was thinking... we already have Lambdabot sitting in an IRC channel. 
 How hard would it be to mangle Lambdabot to the point where it works 
 over HTTP? You know - so you could type some Haskell into a form on a 

Lambdabot web server is here:

http://lambdabot.codersbase.com/

Thought we never announced it off channel, and it hasn't been updated in
a while.

 web page, hit [submit], and get the result sent back to you? (Again, 
 assuming it can be computed in a sane amount of time/space, and 
 truncated to some reasonable textual length.)
 
 I think it might be kinda neat to have such a thing linked from the 
 Haskell.org homepage. You know, sort of hey, wanna try Haskell without 
 installing any stuff? Click here!

yeah, we've had this in mind as a base for an online haskell
quiz/tutorial series. Perhaps someone would like to make this happen :-)

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


Re: [Haskell-cafe] What really happens

2007-05-19 Thread Donald Bruce Stewart
andrewcoppin:
 Hi everybody.
 
 Is there any circumstances under which an expression like map (2*) would 
 perform an in-place update rather than generating a new list? (Obviously 

Yes, should be fine, if the result is consumed. We have fusion
frameworks that do this.

 this depends on which compiler we're talking about. I'm implicitly 
 assuming GHC.) Assuming the old list isn't needed again, an in-place 
 update is obviously significantly cheaper. (Less RAM used, less time 
 allocating RAM, less GC time, etc.) For something like an integer which 
 can be unboxed, you could write a very tight loop of machine code to 
 perform a multiplication by 2 over a single-linked list.
 
 
 Similarly, according to the rules, something like length . filter odd 

length . filter won't fuse in ghc's current list fusion system, as
length is a left fold. However, we do know how to fuse it, and a couple
of libraries do provide a fusible length . filter api (bytestring, using
functional array fusion, and stream fusion, and the Data.List.Streams
library). They use library specified rewrite rules to augment ghc's
optimiser with domain specific strategies for optimising their api.

 I spend lots of time telling people that Haskell compilers can actually 
 make big optimizations like this, and coding my own stuff as if this 
 will happen, but is it actually so? Am I assuming the optimizer is 
 all-powerful when in fact it's not?

It does do some pretty clever optimisations, because purity helps
compilers out a lot. So yes, I think its safe to say that the various
optimising Haskell compilers are pretty smart, and do many things not
feasible in an impure setting.

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


Re: [Haskell-cafe] Pesky monads...

2007-05-19 Thread Donald Bruce Stewart
matt:
 It occurred to me that the predicate will generally be a monadic function 
 itself, so here's a
 refined version:
 
  :: Monad m = (a - m Bool) - (a - m a) - a - m a
 untilM pred f x = do c - pred x
  if c then return x
   else f x = untilM pred f

Here's a cute example of a loop from xmonad:

fix $ \again - do
more - checkMaskEvent d enterWindowMask p
when more again 

But maybe Spencer was just being funny when he wrote that.

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


Re: [Haskell-cafe] idlelog

2007-05-19 Thread Donald Bruce Stewart
lpenz:
 
 Hi
 
 I made a program that detects user presence in a linux box by checking 
 for keyboard interruptions in /proc/interrupts.
 
 Problem is, it is supposed to run for a long time, and it keeps about 
 40MB for itself.
 
 Yeah, this is one more help me with this memory problem mails...
 
 The code can be found in http://hpaste.org/1907, and in darcs get 
 http://lpenz.50webs.com/idlelog
 
 I guess I'm having some conceptual problem.

I'd seriously consider using Data.ByteString instead of [Char] string 
for your IO.

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


Re: [Haskell-cafe] global variables

2007-05-17 Thread Donald Bruce Stewart
eeoam:
 H|i,
 
 Does anyone know of a simple and straightforward way to use global 
 variables in Haskell?
 
 E.

The usual way is to run the code that needs a global variable in a State monad.

The next answer is: you don't really need global variables, since you
don't have mutable variables anyway :-)

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


Re: [Haskell-cafe] CUFP website

2007-05-16 Thread Donald Bruce Stewart
cyril.schmidt:
 I noticed recently that the website of CUFP conference (Commercial Uses of
 Function Programming), which used to be at http://www.galois.com/cufp,
 is not accessible anymore.
 
 Does anybody know where it moved?

Try http://cufp.galois.com/

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


Re: [Haskell-cafe] Co-arbitrary

2007-05-08 Thread Donald Bruce Stewart
joelr1:
 Would someone kindly explain why we need co-arbitrary in QuickCheck  
 and how to define it?

Generating random function generators.

A nice explanation was given recently on the programming subreddit:

The CoArbitrary class continues to confuse me
http://programming.reddit.com/info/1mcu8/comments/c1md04

 Detailed examples would be awesome!
 
 I would be willing to paste an in-depth explanation on my wall and  
 keep it forever.

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


Re: [Haskell-cafe] Intermediate Haskell Books?

2007-05-06 Thread Donald Bruce Stewart
aneumann:
 -BEGIN PGP SIGNED MESSAGE-
 Hash: RIPEMD160
 
 Are there any good books about intermediate to advanced Haskell? The
 descriptions here http://haskell.org/haskellwiki/Books_and_tutorials
 aren't very helpful.

Not in real-world paper form, yet.

Mostly advanced techniques and tools are documented in research papers
(see the wiki), wiki articles and blog articles.

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


[Haskell-cafe] Mounting haskell.org wiki under WikipediaFS?

2007-05-06 Thread Donald Bruce Stewart
Anyone tried editing haskell.org's wiki as text, using:

http://wikipediafs.sourceforge.net/

WikipediaFS is a mountable Linux virtual file system that enables you
to deal with Wikipedia (or any Mediawiki-based site) articles as if they
were real files. It is thus possible to use a real text editor to view
and edit articles.

Seems like this might make some of the larger edit passes a lot easier.

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


[Haskell-cafe] Haskell Weekly News: May 07, 2007

2007-05-06 Thread Donald Bruce Stewart
---
Haskell Weekly News
http://sequence.complete.org/hwn/20070507
Issue 62 - May 07, 2007
---

   Welcome to issue 62 of HWN, a weekly newsletter covering developments
   in the [1]Haskell community.

   This week sees the release of Atom, a hardware description language
   embedded in Haskell, along with the usual suite of new libraries and
   tools. In addition, The Monad.Reader Issue 7 was released, and the
   hackage upload festival continues unabated.

   1. http://haskell.org/

Announcements

   Atom: Hardware Description in Haskell. Tom Hawkins [2]announced the
   release of [3]Atom, a high-level hardware description language
   embedded in Haskell, compiles conditional term rewriting systems into
   conventional HDL.

   2. http://article.gmane.org/gmane.comp.lang.haskell.general/15209
   3. http://www.funhdl.org/

   The Monad.Reader: Issue 7. Wouter Swierstra [4]announced the latest
   issue of [5]The Monad.Reader. The Monad.Reader is a quarterly magazine
   about functional programming. It is less-formal than journal, but
   somehow more enduring than a wiki page or blog post.

   4. http://article.gmane.org/gmane.comp.lang.haskell.cafe/22038
   5. http://www.haskell.org/haskellwiki/The_Monad.Reader

   HDBC: Haskell Database Connectivity. John Goerzon [6]announced that
   [7]HDBC 1.1.2 is now released. HDBC provides an abstraction layer
   between Haskell programs and SQL relational databases. This lets you
   write database code once, in Haskell, and have it work with any number
   of backend SQL databases.

   6. http://article.gmane.org/gmane.comp.lang.haskell.general/15227
   7. http://software.complete.org/hdbc

   FileManip: Expressive Filesystem Manipulation. Bryan O'Sullivan
   [8]announced the [9]FileManip package provides expressive functions
   and combinators for searching, matching, and manipulating files.

   8. http://article.gmane.org/gmane.comp.lang.haskell.cafe/22090
   9. http://hackage.haskell.org/cgi-bin/hackage-scripts/package/FileManip-0.1

   photoname: manipulate photos using EXIF data. Dino Morelli
   [10]announced the release of [11]photoname, a command-line utility for
   renaming and moving photo image files. The new folder location and
   naming are determined by two things: the photo shoot date information
   contained within the file's EXIF tags and the usually-camera-assigned
   serial number, often appearing in the filename.

  10. http://article.gmane.org/gmane.comp.lang.haskell.general/15187
  11. http://ui3.info/d/proj/photoname.html

   RSA-Haskell: Command-line Cryptography. David Sankel [12]announced the
   release of [13]RSA-Haskell, a collection of command-line cryptography
   tools and a cryptography library written in Haskell. It is intended to
   be useful to anyone who wants to secure files or communications or who
   wants to incorporate cryptography in their Haskell application.

  12. http://article.gmane.org/gmane.comp.lang.haskell.general/15207
  13. http://www.netsuperbrain.com/rsa-haskell.html

   Haskell modes for Vim. Claus Reinke [14]summarised the various
   Haskell/Vim support currently available

  14. http://article.gmane.org/gmane.comp.lang.haskell.general/15180

   French Translation of Gentle Introduction to H98. The haskell-fr team
   [15]announced a completed a [16]translation into French of the 'Gentle
   Introduction to Haskell'.

  15. http://article.gmane.org/gmane.comp.lang.haskell.general/15193
  16. http://gorgonite.developpez.com/livres/traductions/haskell/gentle-haskell/

Haskell'

   This section covers the [17]Haskell' standardisation process.

 * [18]Polymorphic strict fields

  17. http://hackage.haskell.org/trac/haskell-prime
  18. http://thread.gmane.org/gmane.comp.lang.haskell.prime/2192

Hackage

   This week's new libraries in [19]the Hackage library database.

  19. http://hackage.haskell.org/

 * BitSyntax-0.2. Adam Langley. [20]A simple function for the
   construction of binary data.

  20. http://hackage.haskell.org/cgi-bin/hackage-scripts/package/BitSyntax-0.2

 * filepath-1.0. Neil Mitchell. [21]Library for manipulating
   FilePath's in a cross platform way.

  21. http://hackage.haskell.org/cgi-bin/hackage-scripts/package/filepath-1.0

 * Chart-2007.3.5. Tim Docker [22]A library for generating 2D Charts
   and Plots.

  22. http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Chart-2007.3.5

 * FileManip-0.1. Bryan O'Sullivan [23]A Haskell library for working
   with files and directories.

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

 * hsns-0.5.2. Austin Seipp [24]A network sniffer written in a purely
   fun language.

  24. http://hackage.haskell.org/cgi-bin/hackage-scripts/package/hsns-0.5.2

 * template-0.1. Johan Tibell [25]Simple string substitution library
   that 

<    1   2   3   4   5   6   >