Re: [Haskell-cafe] The Garbage Collector Ate My Homework

2007-07-04 Thread Stefan O'Rear
On Wed, Jul 04, 2007 at 03:56:20PM +1000, Thomas Conway wrote:
 Well, not quite, but look at the following:
 
 118,342,689,824 bytes allocated in the heap
 144,831,738,780 bytes copied during GC (scavenged)
 335,086,064 bytes copied during GC (not scavenged)
 255,257,516 bytes maximum residency (42 sample(s))
 
 222884 collections in generation 0 (3891.90s)
 42 collections in generation 1 (153.99s)
 
536 Mb total memory in use
 
  INIT  time0.00s  (  0.00s elapsed)
  MUT   time  233.66s  (776.99s elapsed)
  GCtime  4045.89s  (4251.52s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time  4279.55s  (5028.52s elapsed)
 
  %GC time  94.5%  (84.5% elapsed)
 
  Alloc rate506,470,897 bytes per MUT second
 
  Productivity   5.5% of total user, 4.6% of total elapsed
 
 Can anyone offer general suggestions for how to fix this!

The fact that so many collections occured in the nursery suggests that
you are creating a huge amount of temporary objects and immediately
throwing them away.  This is expected if the strictness analyser is
disabled by not enabling optimizations.  Passing -funbox-strict-fields
may help.  Otherwise, as Tim says, your best bet is to post a profile.

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


Re: [Haskell-cafe] The Garbage Collector Ate My Homework

2007-07-04 Thread Tim Chevalier

[I assume this was meant to go to the list as well, so I'm adding it
back to the CCs]

On 7/3/07, Thomas Conway [EMAIL PROTECTED] wrote:

It occurs to me that tweaking the GC parameters can probably make a
big difference: is starting with a bigger heap likely to help, or more
generations? My generation hypothesis is that more generations will
encourage the cached data to drop down out of generation 0, reducing
the GC load.



Starting with a bigger heap is likely to help, since it means that GCs
will be needed less often. I'm not sure I buy your generation
hypothesis, because even with two generations, you would expect to see
some of the cached data move to generation 1. Lots of data in
generation 0 implies your code continues to allocate many objects as
it goes on running. On the other hand, you could still try and see if
it helps.

Cheers,
Tim

--
Tim Chevalier* catamorphism.org *Often in error, never in doubt
The illegal we do immediately. The unconstitutional takes a little
longer.  -- Henry Kissinger
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Sparse documentation

2007-07-04 Thread Simon Peyton-Jones
| Fortunately, some kind soul has gone through and converted the
| documentation to haddock format:
| http://hackage.haskell.org/trac/ghc/ticket/1410
|
| So it'll all appear in the html docs in the next version. In the mean
| time one can look at the haddock comments in the source:
| http://darcs.haskell.org/packages/mtl/Control/Monad/

Furthermore, you can always get the GHC HEAD documentation here
http://www.haskell.org/ghc/dist/current/docs
From there you can get to Control.Monad, which indeed shows at least some 
documentation.

Simon

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


RE: [Haskell-cafe] Sparse documentation

2007-07-04 Thread Simon Peyton-Jones
Writing documentation for libraries is one way in which ordinary Haskell users 
can really contribute to the Haskell community.  It's not hard to do (grab the 
Darcs repo, type away), and it's widely appreciated.

People often don't feel qualified do to this, but documentation written by an 
intelligent but unqualified person (perhaps including not sure what happens 
here) is a lot more useful than no documentation at all.  Yes I know that 
misleading documentation can be a Bad Thing but I think lack of documentation 
is a much bigger problem than misleading documentation, as of today.

Simon

From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Brent Yorgey
Sent: 03 July 2007 22:09
To: Andrew Coppin
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Sparse documentation


It's also nice to have some brief comments in the API docs to say what
the heck a particular module is even *for*, and provide enough info on
the stuff in that module that you can quickly dip into it when you can't
remember the name of something...

I certainly don't disagree with you!  I was just commenting on the tendency of 
the community to document things in academic papers.  But I'm glad to hear from 
Duncan that better Haddock documentation will be in the next version of the 
libraries.

After many hours tying my brain in knots, I *think* I need to use a
monad transformer... but I've never ever done that before. So I'd like
to learn how it works.

Try http://uebb.cs.tu-berlin.de/~magr/pub/Transformers.en.html.  I found that 
paper very clear and helpful in learning to use monad transformers.  Then you 
will probably also want to read 
http://cale.yi.org/index.php/How_To_Use_Monad_Transformers.

-Brent

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


RE: [Haskell-cafe] Sparse documentation

2007-07-04 Thread Michael T. Richter
On Wed, 2007-04-07 at 08:03 +0100, Simon Peyton-Jones wrote:

 | Fortunately, some kind soul has gone through and converted the
 | documentation to haddock format:
 | http://hackage.haskell.org/trac/ghc/ticket/1410
 |
 | So it'll all appear in the html docs in the next version. In the mean
 | time one can look at the haddock comments in the source:
 | http://darcs.haskell.org/packages/mtl/Control/Monad/
 
 Furthermore, you can always get the GHC HEAD documentation here
 http://www.haskell.org/ghc/dist/current/docs
 From there you can get to Control.Monad, which indeed shows at least some 
 documentation.


Simon, if the less-talented among us (like me) want to contribute to
GHC's docs -- and especially documenting the libraries -- what's the
best way to go about this?  I'm not too comfortable with the notion of
just going into GHC's guts and Haddocking the comments, contributing
patches willy-nilly because I'd not be certain I did the job right, that
I explained things correctly where I had to amplify, etc.  Is there some
kind of documentation team we poor souls could interact with to assist?

-- 
Michael T. Richter [EMAIL PROTECTED] (GoogleTalk:
[EMAIL PROTECTED])
When debugging, novices insert corrective code; experts remove defective
code. (Richard Pattis)


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


Re: [Haskell-cafe] Sparse documentation

2007-07-04 Thread Jules Bean

Andrew Coppin wrote:
Essentially I want to run a parser on top of a parser, and I think maybe 
this is the way to do it.


I doubt monad transformers are the answer.

I imagine you just want to one run parser over the result of the 
previous, which is just function composition, modulo a sensible way of 
handling errors.


If you give more details on what you're trying, people may have helpful 
insights. Or not :)


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


[Haskell-cafe] Playing with delimited continuations

2007-07-04 Thread Dan Doel
Hello,

My interest was recently caught reading some of Oleg Kiselyov's material on 
delimited continuations, and so I decided to look into them a little closer. 
Don Stewart also mentioned in passing on #haskell that'd it'd be nice to have 
support for delimited continuations either in the standard library, or in 
some other easily installable package. So, I thought I'd see what such a 
beast might look like, and dug up the Dybvig, Petyon-Jones, Sabry paper[1] on 
the subject that I'd read long ago, but probably not understood much. :)

After a day or so of hacking, I have (what I think is) a proper implementation 
of the monad and transformer, along with a suitable typeclass, and instances 
for the various transformers in the MTL. However, I have by no means tested 
it extensively (as I don't have a lot of ideas off hand for monad stacks 
involving delimited continuations), and I'm not totally thrilled with the 
results I have, so I thought I'd ask for advice/commentary here. Code is 
attached.

First, I guess, should come an example of code using the delimited 
continuations:

 pop = do (h:t) - get
  put t
  return h

 abortP p e = withSubCont p (\_ - e)

 loop 0 _ = return 1
 loop n p = do i - pop
   if i == 0
 then abortP p (return 0)
 else do r - loop (n-1) p
 return (i*r)

 test1 n l = runDelCont
   (runStateT (newPrompt = \p - 
  pushPrompt p (loop n p)) l)  

 test2 n l = runState 
   (runDelContT (newPrompt = \p -
  pushPrompt p (loop n p))) l  

So, loop finds the product of the first n numbers stored in a list in the 
state, but aborts immediately if it sees a 0. test1 and test2 stack the 
monads in the opposite order, but the results are the same in this case (it 
isn't a very sophisticated example).

Another example, from the paper, is that you can think of normal continuations 
as delimited continuations with a global prompt p0 that denotes the end of 
the computation. You can emulate this using the reader monad to store the 
prompt:

 type Continue r b a = ReaderT (Prompt.Prompt r b) (DelCont r) a

 runContinue :: (forall r. Continue r b b) - b
 runContinue ct = runDelCont (newPrompt = \p - 
  pushPrompt p (runReaderT ct p)) 

 callCC' f = withCont (\k - pushSubCont k (f (reify k)))
  where
  reify k v = abort (pushSubCont k (return v))
  abort e = withCont (\_ - e)
  withCont e = ask = \p - withSubCont p (\k - pushPrompt p (e k))

 loop2 l = callCC' (\k - loop' k l 1)
  where
  loop' _ [] n = return (show n)
  loop' k (0:_) _ = k The answer must be 0.
  loop' k (i:t) n = loop' k t (i*n)

So, the loop computes the product of a list of numbers, returning a string 
representation thereof, but aborts with a different message if it sees 0. 
Again, nothing special, but it seems to work.

However, this is where I started to run into some uglines that followed from 
my design choices. Most flows from the typeclass:

  class (Monad m) = MonadDelCont p s m | m - p s where
  newPrompt   :: m (p a)
  pushPrompt  :: p a - m a - m a
  withSubCont :: p b - (s a b - m b) - m a
  pushSubCont :: s a b - m a - m b

So, 'm' is the delimited control monad in question, 'p' is the type of prompts 
associated with said monad, and 's' is the associated type of 
subcontinuations that take an 'a', and produce a 'b'. Those four functions 
are the generalizations of the four control operators from the paper. The 
crux of the matter is the way the prompts and subcontinuations are typed. A 
prompt 'p a' can have values of type 'a' returned through it, which is fine 
in the vanilla DelCont monad. However, in a monad transformed by a StateT, a 
computation 'm a' isn't returning an 'a' through the prompt. It's actually 
returning an '(a,s)', due to the state threading. And the same is an issue 
with the subcontinuation. So, I came up with a couple wrappers:

  newtype PairedPrompt s p a = PP { unPP :: p (a, s) }
  newtype PairedSubCont s k a b = PSC { unPSC :: k (a, s) (b, s) }

And then you can declare instances like so:

  instance (MonadDelCont p s m) =
MonadDelCont (PairedPrompt t p) (PairedSubCont t s) (StateT t m) where ...

Where the declarations not only lift the delimited control actions, but wrap 
and unwrap the prompts and subcontinuations appropriately. However, this has 
two issues:

1) It seems kind of kludgy at first glance, although maybe that's just me.

2) It doesn't always work correctly. Consider the following code:

 loop3 l = callCC' (\k - loop' k l 1)
  where
  loop' _ []n = return n
  loop' k (0:_) _ = k 0
  loop' k (i:t) n = tell [n]  loop' k t (i*n)

It does almost the same thing as loop2, only it has some writer output, too. 
And we'd like to write:

 test3 l = runContinue (runWriterT (loop3 l))

but we can't, because that's a type error, because the prompt is created 
outside of runWriterT, where it will have type 

Re: [Haskell-cafe] Re: Abstraction leak

2007-07-04 Thread Philip Armstrong

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
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
make integrating Haskell code into a wider distributed network of
processes exchanging binary data a cinch. In a super really ideal
world, you could operate on the packets in place in Haskell where
possible and save the deserialization overhead...

Anyone trying to do any of this?

Phil

[1] deriving picklable?
[2] DFDL does this for XML / binary data translation.
[2a] Or even dump to arbitrary formats: XML, JSON for concrete
 datatypes[3], mabe use the approach from
 http://www.ps.uni-sb.de/Papers/abstracts/hotPickles2007.html
 (link stolen shamelessly from Lambda the Ultimate) for higher
 order data?
[3] Maybe UBL from http://www.erlang.se/workshop/2002/Armstrong.pdf ?

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Sparse documentation

2007-07-04 Thread Claus Reinke

Simon, if the less-talented among us (like me) want to contribute to
GHC's docs -- and especially documenting the libraries -- what's the
best way to go about this?  I'm not too comfortable with the notion of
just going into GHC's guts and Haddocking the comments, contributing
patches willy-nilly because I'd not be certain I did the job right, that
I explained things correctly where I had to amplify, etc.  Is there some
kind of documentation team we poor souls could interact with to assist?


there was the idea of using the wiki for developing documentation
improvements, prior to actually submitting the improved texts. the
only hint of that scheme i can find right now is:

http://www.haskell.org/haskellwiki/Improving_library_documentation

but establishing a documentation team to help organise the process
and to define a realistic workflow (how and where to edit, how and
who submits when its ready, how to avoid extra work due to 
working in different formats, ..) seems like a good idea. go for it!-)


claus

___
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 Thomas Conway

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.

T.
--
Dr Thomas Conway
[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: 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 Philip Armstrong

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?


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...


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.

Phil

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
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] Haskell's partial application (not currying!) versus Business Objects Gem Cutter's burning

2007-07-04 Thread Conor McBride

Hi Jules

Your explanation of lambda-abstraction, dealing in full generality  
with both scope and
multiplicity, is a good one. But it's still interesting to  
investigate the possibility
of a privileged notation for linear abstraction, based on leaving  
holes in things, by
way of illustrating the design space. I seem to remember this topic  
coming up before

(on Haskell Prime?), but I can't find the archival references just now.

On 3 Jul 2007, at 11:19, Jules Bean wrote:


peterv wrote:
In Haskell, currying can only be done on the last (rightmost)  
function arguments.


[..]




This burning looks more general to me, but cannot be done using  
the textual approach?


Well, it can be done, but basically there are two issues:


Dead right.

1. You need to demarquate the 'scope' of the ?. What 'lump' of  
expression is the partially evaluated part. An obvious way to do  
this is with parentheses, but you have to be careful.


Let me borrow braces {..} for purposes of discussion. One might  
imagine a form of
abstraction where one simply writes an expression in braces,  
replacing some

subexpressions with ?, like Haskell Emmental

  {? * 10 + ?}

Of course...

2. If you have more than one ?, you need to remember which is  
which. Think of nested expressions, nested ?s. What if you want to  
use the 'same' ? more than once?


...we need a convention to handle this. The obvious convention is  
that each ? is
distinct and that they (and only they!) are abstracted from a brace  
in left-to-right

order. That's to say, the above means

  \x y - x * 10 + y

hence

  {? * 10 + ?} 4 2 = 42

It can make sense to allow nested applications inside braces, using  
parentheses.


  {f ? (g ? x)}

It can even make sense to allow nested braces, provided we adopt the  
convention that

a ? is bound by its most local brace.

  {foldr {? : ?} ? ?} = flip (++)

For expressions with no ?s, {..} and (..) coincide. {f ? ... ?} means  
f. All sorts
of compositions, not just {f (g ?)}, are readily expressed, without  
resorting either

to naming or to lurid ascii-art.

[Local notational speculation: use (..) for {..}

  One might well wonder: if ?-less {..} are like (..) and ?-ful (..)  
are currently
  meaningless, why not overload (..) ? This can be done, but it  
gives a rather
  peculiar semantics to previously innocent syntax---you lose the  
ability to add

  extra parentheses to clarify grouping, so

(f a) b   is not necessarily the same as   f a b

  and you also lose the ability to nest expressions, except via  
precedence


(f (g ?))  means  f g  and not  f . g
(? * 10 + ?)  may work, but  ((? * 10) + ?)  causes trouble.

End local speculation]

Oddly, to my mind, this is exactly the approach that the Gem Cutter  
crew take, but
pictorially. On the one hand, they use tree diagrams for expressions,  
so they
don't need parentheses for grouping. On the other hand, they  
explicitly choose
only to allow the abstraction of burnt arguments from the very  
application in

which they occur. Correspondingly

  {foo ? y}  is expressible, but
  {? * 10 + ?}   has to be expanded.

This seems like a missed opportunity to me.

What should Haskell take away from this?

(1) You know where you are with lambda-abstraction. You can even do  
some sorts
of fast and loose reasoning under binders, with some hope of  
preserving the
meaning of your expressions. By comparison, computing inside {..} is  
very

dangerous:

  {0 * ?} is not {0}
  {const ? ?} is not {?}
  {flip f ? ?} is not {f ? ?}
  {(\x - (x, x)) ?} is not {(?, ?)}

(2) Even so, it might be a useful feature. Something of the sort  
*has* been

proposed before. I just found it

  http://hackage.haskell.org/trac/haskell-prime/wiki/ 
FlexiblePartialApplication


but without the special {..} bracket, it's a nightmare. Brackets are  
always at

a premium in syntax design. What would we do?

(3) Exercise for readers:

  implement constructors
P v  for embedding pure values v
Ofor holes
f :$ a   for application, left-associative
  and an interpreting function
emmental
  such that
emmental (P (+) :$ (P (*) :$ O :$ P 10) :$ O) 4 2 = 42

I think the question of whether to support linear abstractions other  
than of
an argument suffix is an interesting one. The flip answer is a bad  
answer;
lambda abstraction is a good answer, but sometimes feels too heavy  
for this
job. I really don't have a strong opinion about whether it's worth  
supporting
a lighter notation for the linear case, but I thought I'd at least  
try to

inform the debate.

All the best

Conor


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


[Haskell-cafe] Re: Sparse documentation

2007-07-04 Thread apfelmus
Claus Reinke wrote:
 Simon, if the less-talented among us (like me) want to contribute to
 GHC's docs -- and especially documenting the libraries -- what's the
 best way to go about this?  I'm not too comfortable with the notion of
 just going into GHC's guts and Haddocking the comments, contributing
 patches willy-nilly because I'd not be certain I did the job right, that
 I explained things correctly where I had to amplify, etc.  Is there some
 kind of documentation team we poor souls could interact with to assist?
 
 there was the idea of using the wiki for developing documentation
 improvements, prior to actually submitting the improved texts. the
 only hint of that scheme i can find right now is:
 
 http://www.haskell.org/haskellwiki/Improving_library_documentation
 
 but establishing a documentation team to help organise the process
 and to define a realistic workflow (how and where to edit, how and
 who submits when its ready, how to avoid extra work due to working in
 different formats, ..) seems like a good idea. go for it!-)

Of course, the visionary solution would be to wikify the haddocks
themselves: imagine to simply point a browser to the documentation and
edit it in-place.

I think that web-browsers are not ready for that, though: editing things
in an extra input box after being redirected to a edit this page
version just sucks for me, especially for the intended haddock editing.
The dream is to have WYSIWYG editing in-place (modulo keyboard/mouse
control. Mathematica's front-end comes close to what I have in mind.).
Why to learn and adjust wiki markup on a separate page? It's not
difficult but it's unnecessary and thus wasted time.

Regards,
apfelmus

___
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 Philip Armstrong

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?


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?


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?


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?

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

Phil

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Where's the problem ?

2007-07-04 Thread Rome

Hi everyone,

I write a program for fast online multiplication, this means, leading digits
are computed first, so this program is able to handle real numbers. 

My program and Source-Code is available under
http://www.romeinf04.de http://www.romeinf04.de 

but only with german comments, because this is my master thesis.

Now the problem:
My program computes using the schoenhage-strassen multiply-subroutine the
output everytime only until the 32777th Digit, but then it holds without an
error message. Windows Task manager tells me CPU Usage 100% and Memory
Allocation is increasing.
Profiling told me, the function Algorithm.resultOfMult is using this memory.
To compute the 32777th digit, my program needs several digits of the
input-numbers including the 32800th.
I'm using GHC 6.6.1 with option -O2 to compile.

Output is row-wise by an IO-function, calling itself recursively with
updated parameters, hte output looks like:

dig11 dig21 -- res1
dig12 dig22 -- res2
dig12 dig23 -- res3
.
.
. and so on

If I use the Naive-Multiply-Subroutine, the problem occurs at the 16392th
digit.

A friend of mine compiled it under Linux and got:
.
.
.
32779 :  1   1 ---32776--  0
32780 :  1   0 ---32777-- -1
Main: Ix{Integer}.index: Index (32766) out of range ((0,32765))

If I convert every Integer into Int and use instead of the generic list
functions the prelude-list functions, it works.
I don't have any idea, where the problem might be...

Greetings

Roman

Please excuse my english writing, I'm from Germany.
-- 
View this message in context: 
http://www.nabble.com/Where%27s-the-problem---tf4022913.html#a11426358
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


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

2007-07-04 Thread Bulat Ziganshin
Hello Philip,

Wednesday, July 4, 2007, 5:50:42 PM, you wrote:
 This doesn't seem to deal with endianness. Am I missing something?

alternative:
http://haskell.org/haskellwiki/Library/AltBinary
http://haskell.org/haskellwiki/Library/Streams

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Very simple parser

2007-07-04 Thread Alexis Hazell
On Tuesday 03 July 2007 09:51, Arie Peterson wrote:

 No, there is a 'State s' monad provided (for arbitrary state type 's'),
 which implements the 'get' and 'put' methods. In other words, 'State s' is
 an instance of the 'MonadState s' class. This terminology can be really
 confusing at first.

 For now, you may forget about the MonadState class. Simply use 'get' 
 friends and everything will work fine.

This may be a stupid question, but i don't understand how (indeed, if) one can 
maintain multiple states using the State monad, since 'get' etc. don't seem 
to require that one specify which particular copy of a State monad one wishes 
to 'get' from, 'put' to etc.? Does one have to use (say) a tuple or a list to 
contain all the states, and when one wishes to change only one of those 
states, pass that entire tuple or list to 'put' with one element changed and 
the rest unchanged?


Alexis.
___
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 Philip Armstrong

On Wed, Jul 04, 2007 at 06:52:08PM +0400, Bulat Ziganshin wrote:

Hello Philip,

Wednesday, July 4, 2007, 5:50:42 PM, you wrote:

This doesn't seem to deal with endianness. Am I missing something?


alternative:
http://haskell.org/haskellwiki/Library/AltBinary
http://haskell.org/haskellwiki/Library/Streams


Nice: bit aligning if you want it, little or big endian IO. Intermixed
endianness in the same datastream even[1]. However:

  3.2.10 Defining Binary instances for custom serialization formats (unwritten)

Does that mean that the code is unwritten or that the documentation is
unwritten. IAMFI :)

There seems to be some overlap between Streams and ByteStrings: Could
a Stream built on a ByteString backend benefit from all the fusion
work that's been put into ByteStrings recently? Oh wait, I see you
list that as 'future work' on the wiki page...

Phil

[1] Which sick application *needs* intermixed endianness?

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Abstraction leak

2007-07-04 Thread Malcolm Wallace
Andrew Coppin [EMAIL PROTECTED] wrote:

 While we're on the subject... am I the first person to notice that 
 Haskell doesn't appear to have much support for fiddling with streams
 of  bits?

See
  The Bits Between The Lambdas: Binary Data in a Lazy Functional Language
  Malcolm Wallace and Colin Runciman,
  International Symposium on Memory Management, Vancouver, Canada, Oct 1998
  ftp://ftp.cs.york.ac.uk/pub/malcolm/ismm98.html

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


Re: [Haskell-cafe] Parsers are monadic?

2007-07-04 Thread Malcolm Wallace
Claus Reinke [EMAIL PROTECTED] wrote:

 (b) i like my combinator grammars to be reversible, so that a single
 grammar specification can be used for both parsing and
 unparsing/pretty-printing.  that means i have to define the
 details myself anyway.

Oh cool - this is something I have wanted for a long time.  Anything
released or otherwise available?

 about the only thing that spoils this nice setup is error handling.
...  so it is easier to  see where it is headed: a
 three-valued logic. 

I wrote a set of monadic combinators (the polyparse library) for exactly
this reason - improving error messages (in HaXml originally).  As
indeed, the basic error structure is a three-valued logic, with success
and two separate kinds of error:
   type EitherE a b = Either (Bool,a) b

The error categories I used were recoverable failure, to enable
backtracking, and hard failure to disallow backtracking when no
alternative good parses were possible.  The combinator 'commit' changes
recoverable failures into hard failures.

I guess you could easily model this setup with three continuations
instead of a monad.

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


Re: [Haskell-cafe] Haskell's partial application (not currying!) versus Business Objects Gem Cutter's burning

2007-07-04 Thread Marc A. Ziegert
exercise done. :D
there is still a problem with the functional dependencies. see last line of 
code.
- marc

Am Mittwoch, 4. Juli 2007 14:22 schrieb Conor McBride:
{? * 10 + ?} 4 2 = 42
   
 http://hackage.haskell.org/trac/haskell-prime/wiki/FlexiblePartialApplication

 
 (3) Exercise for readers:
 
implement constructors
  P v  for embedding pure values v
  Ofor holes
  f :$ a   for application, left-associative
and an interpreting function
  emmental
such that
  emmental (P (+) :$ (P (*) :$ O :$ P 10) :$ O) 4 2 = 42
 
 I think the question of whether to support linear abstractions other  
 than of
 an argument suffix is an interesting one. The flip answer is a bad  
 answer;
 lambda abstraction is a good answer, but sometimes feels too heavy  
 for this
 job. I really don't have a strong opinion about whether it's worth  
 supporting
 a lighter notation for the linear case, but I thought I'd at least  
 try to
 inform the debate.
 
 All the best
 
 Conor
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
{-# OPTIONS  -fglasgow-exts -farrows -fbang-patterns -fno-full-laziness -funbox-strict-fields  -fallow-undecidable-instances #-}
{-# PACKAGE ghc-6.6 #-}
{-# LANGUAGE ExistentialQuantification #-}

module Main where

--import Control.Arrow
--import Data.Array as Array
--import Data.Array.ST as STArray
--import Data.Array.Unboxed as UArray
--import Data.Map as Map
--import Data.Set as Set
--import Data.List as List
--import Data.Queue
--import Data.Sequence as Seq
--import Data.IntSet as IntSet
--import Data.IntMap as IntMap
--import Data.Maybe
--import Data.Bits (xor)
--import Data.Word
--import Data.Int
--import Control.Monad
--import Control.Arrow
--import Control.Monad.State
--import Control.Monad.Writer
--import Data.Foldable (foldrM)
--import Control.Applicative
--import Data.Traversable
--import System.Posix
--import System.IO.Unsafe
--import Data.Graph.Inductive as Gr hiding (())
--import qualified Data.Graph.Inductive.Example as Example
--import Data.Graph.Inductive.Query.BFS
--import Control.Monad.ST.Strict
--import Data.STRef
--import System.Random
--import Data.Ratio
--import System.Exit
--import MonadLib



{-

   implement constructors
 P v  for embedding pure values v
 Ofor holes
 f :$ a   for application, left-associative
   and an interpreting function
 emmental
   such that
 emmental (P (+) :$ (P (*) :$ O :$ P 10) :$ O) 4 2 = 42

-}
type ONE = SUCC ZERO
type TWO = SUCC ONE

data ZERO
data NAT n = SUCC n

class NAT n where
  nat :: n - Int
instance NAT ZERO where
  nat _ = 0
instance NAT n = NAT (SUCC n)  where
  nat _ = succ $ nat (undefined::n)


newtype HOLE a = HOLE a

class NAT n = UNHOLE n h f | n h - f where
  unhole :: n - h - f
instance UNHOLE ZERO (P v) v where
  unhole _ (P v) = v
instance (NAT n , UNHOLE n f g) = UNHOLE (SUCC n) ((HOLE a)-f) (a-g) where
  unhole _ f = unhole (undefined::n) . f . HOLE

data P v = P v
data O = O
data (:$) f a = f :$ a

infixl 8 :$

{-
class PLUS a b c | a b - c where
instance PLUS ZERO b b where
instance (PLUS a b c) = PLUS (SUCC a) b (SUCC c) where

class COUNT a n | a - n where
  countH :: a - n
  countH _ = undefined
instance COUNT (P v) ZERO where
instance COUNT O ONE where
instance (COUNT f nf,COUNT a na,PLUS nf na nfa) = COUNT (f :$ a) (nfa) where
-}

class EmToH e n h | e - n h where
  emToH :: e - h
instance EmToH (P v) ZERO v where
  emToH (P v) = v
instance EmToH O ONE (HOLE h-h) where
  emToH O (HOLE h) = h
instance (EmToH f nf f',EmToH a na a',ApplyH nf f' na a' nfa fa) = EmToH (f :$ a) nfa fa where
  emToH (f :$ a) = applyH (undefined::(nf,na)) (emToH f) (emToH a)

class ApplyH nf f na a nfa fa | nf f na a - nfa fa where
  applyH :: (nf,na) - f - a - fa
instance ApplyH ZERO (a-fa) ZERO a ZERO fa where
  applyH _ f a = f a
instance (ApplyH ZERO f na a na fa) = ApplyH ZERO f (SUCC na) (HOLE h-a) (SUCC na) (HOLE h-fa) where
  applyH _ f a h@(HOLE _) = applyH (undefined::(ZERO,na))f (a h)
instance (ApplyH nf f na a nfa fa) = ApplyH (SUCC nf) (HOLE h-f) na a (SUCC nfa) (HOLE h-fa) where
  applyH _ f a h@(HOLE _) = applyH (undefined::(nf,na)) (f h) a

class UnH n f r | n f - r where
  unH :: n - f - r
instance UnH ZERO f f where
  unH _ = id
instance (UnH n f r) = UnH (SUCC n) (HOLE h-f) (h-r) where
  unH _ f h = unH (undefined::n) $ f (HOLE h)


class Emmental e f | e - f where
  emmental :: e - f

instance (EmToH e n h, UnH n h r) = Emmental e r where
  emmental = unH (undefined::n) . emToH








main :: IO ()
--main = print $ emmental (P (+) :$ (P (*) :$ O :$ P 10) :$ O) 4 2
main = print $ emmental (P ((+)::Int-Int-Int) :$ (P ((*)::Int-Int-Int) :$ O :$ P (10::Int)) :$ O) (4::Int) (2::Int)





pgpCnHKLE0z6g.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org

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

2007-07-04 Thread Stefan O'Rear
On Wed, Jul 04, 2007 at 02:50:42PM +0100, Philip Armstrong wrote:
 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?

The Data.Binary high level interface standardizes on 64-bit big endian.
The low level interface allows you to choose it yourself.

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


Re: [Haskell-cafe] Where's the problem ?

2007-07-04 Thread Stefan O'Rear
On Wed, Jul 04, 2007 at 07:30:55AM -0700, Rome wrote:
 I write a program for fast online multiplication, this means, leading digits
 are computed first, so this program is able to handle real numbers. 
 
 My program and Source-Code is available under
 http://www.romeinf04.de http://www.romeinf04.de 
 
 but only with german comments, because this is my master thesis.
 
 Now the problem:
 My program computes using the schoenhage-strassen multiply-subroutine the
 output everytime only until the 32777th Digit, but then it holds without an
 error message. Windows Task manager tells me CPU Usage 100% and Memory
 Allocation is increasing.
 Profiling told me, the function Algorithm.resultOfMult is using this memory.
 To compute the 32777th digit, my program needs several digits of the
 input-numbers including the 32800th.
 I'm using GHC 6.6.1 with option -O2 to compile.
 
 Output is row-wise by an IO-function, calling itself recursively with
 updated parameters, hte output looks like:
 
 dig11 dig21 -- res1
 dig12 dig22 -- res2
 dig12 dig23 -- res3
 .
 .
 . and so on
 
 If I use the Naive-Multiply-Subroutine, the problem occurs at the 16392th
 digit.
 
 A friend of mine compiled it under Linux and got:
 .
 .
 .
 32779 :  1   1 ---32776--  0
 32780 :  1   0 ---32777-- -1
 Main: Ix{Integer}.index: Index (32766) out of range ((0,32765))
 
 If I convert every Integer into Int and use instead of the generic list
 functions the prelude-list functions, it works.
 I don't have any idea, where the problem might be...

If you're using the standard Schoenhage-Strassen algorithm, you might
try using (*) on Integer - it uses Schoenhage-Strassen internally and is
already debugged.

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


Re: [Haskell-cafe] Very simple parser

2007-07-04 Thread Arie Peterson
Alexis Hazell wrote:

| This may be a stupid question, but i don't understand how (indeed, if) one
| can
| maintain multiple states using the State monad, since 'get' etc. don't
| seem
| to require that one specify which particular copy of a State monad one
| wishes
| to 'get' from, 'put' to etc.? Does one have to use (say) a tuple or a list
| to
| contain all the states, and when one wishes to change only one of those
| states, pass that entire tuple or list to 'put' with one element changed
| and
| the rest unchanged?

There are (at least) two ways to do this:

1.

If the pieces of state are in any way related, I would try to put them
together in some data structure. Ideally, this structure is useful beyond
the state monad alone.

The 'gets' and 'modify' functions from Control.Monad.State can help to
keep low overhead.


If you use something like functional references (see
http://www.mail-archive.com/haskell-cafe@haskell.org/msg24704.html), and
define helper functions

 getR = gets . Data.Ref.select
 modifyR = modify . Data.Ref.update

, you may deal with state like this:

 data S = S
  {
foo :: Foo
bar :: Int
  }

 $(deriveRecordRefs ''S)

 do
   foo - getR fooRef
   modifyR barRef succ
   return foo

The syntax can be improved, but it works OK.

2.

If the pieces of state are unrelated, and especially if the different
states are not always present at the same time, I would stack multiple
StateT monad transformers. There was a question about this recently, see
http://www.nabble.com/advice:-instantiating-duplicating-modules-t4000935.html.


Greetings,

Arie

-- 

Rules to a drinking game concerning this badge will be forthcoming.


___
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 Philip Armstrong

On Wed, Jul 04, 2007 at 09:15:59PM +0400, Bulat Ziganshin wrote:

Does that mean that the code is unwritten or that the documentation is
unwritten. IAMFI :)


of course all unwritten notes means unfinished docs. library
contains more than 100 functions so it was not easy to document them
all. you can browse sources, although probably it will not help too
much


OK.


There seems to be some overlap between Streams and ByteStrings: Could
a Stream built on a ByteString backend benefit from all the fusion
work that's been put into ByteStrings recently? Oh wait, I see you
list that as 'future work' on the wiki page...


if you will write all popular words together, this probably will be
just a set of popular words, not something working :)  how fusion
should work together with serialization?


I'm thinking of the elimination of the boxing of values drawn out of
the input stream where possible, eg if I was writing a stream
processor that folded across the values in the input stream, it would
(presumably) be more efficient if the compiler noticed that the
function in question was (say) just reading Int values at offsets
within the stream, and could pass those as unboxed references in the
compiled code rather than freshly constructed values.

Fusion might be the wrong term: I was thinking by analogy with loop
fusion, with one of the loops was the 'data reading' loop. Does that
make sense?


[1] Which sick application *needs* intermixed endianness?


i just tried to implement everything possible :)


Completeness is always good!

Thanks for the pointers,

Phil

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Deadlock in real number multiplication (Was: Where's the problem ?)

2007-07-04 Thread Henning Thielemann

On Wed, 4 Jul 2007, Rome wrote:

 I write a program for fast online multiplication, this means, leading digits
 are computed first, so this program is able to handle real numbers.

 My program and Source-Code is available under
 http://www.romeinf04.de http://www.romeinf04.de

 but only with german comments, because this is my master thesis.

 Now the problem:
 My program computes using the schoenhage-strassen multiply-subroutine the
 output everytime only until the 32777th Digit, but then it holds without an
 error message. Windows Task manager tells me CPU Usage 100% and Memory
 Allocation is increasing.

This sounds like an unresolvable data dependency. E.g. a digit depends via
some other variables on its own value or it depends on an infinite number
of other digits.

 Profiling told me, the function Algorithm.resultOfMult is using this memory.
 To compute the 32777th digit, my program needs several digits of the
 input-numbers including the 32800th.
 I'm using GHC 6.6.1 with option -O2 to compile.

 Output is row-wise by an IO-function, calling itself recursively with
 updated parameters, hte output looks like:

 dig11 dig21 -- res1
 dig12 dig22 -- res2
 dig12 dig23 -- res3
 .
 .
 . and so on

 If I use the Naive-Multiply-Subroutine, the problem occurs at the 16392th
 digit.

 A friend of mine compiled it under Linux and got:
 .
 .
 .
 32779 :  1   1 ---32776--  0
 32780 :  1   0 ---32777-- -1
 Main: Ix{Integer}.index: Index (32766) out of range ((0,32765))

 If I convert every Integer into Int and use instead of the generic list
 functions the prelude-list functions, it works.

... and the result is right?

 I don't have any idea, where the problem might be...

Stupid question: Did you pay enough attentation to carries? There might be
an unresolvable dependency if you request a digit which depends on
infinitely many carries from following digits.


If you like to compare with other implementations of real numbers, see:
 
http://www.haskell.org/haskellwiki/Applications_and_libraries/Mathematics#Real_and_rational_numbers
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Sparse documentation

2007-07-04 Thread Andrew Coppin

Simon Peyton-Jones wrote:


Writing documentation for libraries is one way in which ordinary 
Haskell users can really contribute to the Haskell community. It’s not 
hard to do (grab the Darcs repo, type away), and it’s widely appreciated.


People often don’t feel “qualified” do to this, but documentation 
written by an intelligent but “unqualified” person (perhaps including 
“not sure what happens here”) is a lot more useful than no 
documentation at all. Yes I know that misleading documentation can be 
a Bad Thing but I think lack of documentation is a much bigger problem 
than misleading documentation, as of today.


Simon



How exactly do I get started?

(Obviously I can't write the documentation for the monad transformers - 
I don't know how they work yet! But I could have a go at splicing all 
the Parsec goodness into the Haddoc pages...)


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


Re: [Haskell-cafe] Sparse documentation

2007-07-04 Thread Andrew Coppin

Jules Bean wrote:

Andrew Coppin wrote:
Essentially I want to run a parser on top of a parser, and I think 
maybe this is the way to do it.


I doubt monad transformers are the answer.

I imagine you just want to one run parser over the result of the 
previous, which is just function composition, modulo a sensible way of 
handling errors.


If you give more details on what you're trying, people may have 
helpful insights. Or not :)


Yeah, running one parser on top of another isn't inherently hard. The 
*hard* thing is that I want to stack several parsers on top of each 
other, and *change* that stack at various points in the parsing.


After many hours of trying, I did eventually get working code. But 
*damn* it's complicated! (Especially the type signatures.) Hopefully 
I'll find a way to simplify it gradually...


As for asking here... I did, and nobody had anything interesting to say. :-(

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


Re: [Haskell-cafe] Haskell's partial application (not currying!) versus Business Objects Gem Cutter's burning

2007-07-04 Thread Conor McBride

Hi Marc

Thanks for giving it a go!

On 4 Jul 2007, at 17:33, Marc A. Ziegert wrote:


exercise done. :D
there is still a problem with the functional dependencies. see last  
line of code.

- marc


Looks like a good start. Quite different from the way I did it. I can  
assure you that it's possible to be less explicit about the types of  
the pieces. You might think about computing a typed context for the  
holes, rather than just counting them.


I should add that my solution is here, if/when you feel like looking:

  http://www.e-pig.org/idle/ctm/Emmental.lhs

I'm still fiddling with it in odd moments, hoping for something  
neater. I don't like the explicit P, or the explicit :$. I have  
another slightly clunky, non-nesting version which works like idiom  
brackets


  hH elem O (P aeiou) Hh 'x' = False

but I don't really like it much. The connection with idiom brackets  
isn't an accident, but that's another story.


All the best

Conor

___
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 Andrew Coppin

Philip Armstrong wrote:

[1] Which sick application *needs* intermixed endianness?


*Clearly* you've never been to Singapore...



...er, I mean, Ever tried playing with networking protocol stacks?

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


Re: [Haskell-cafe] Deadlock in real number multiplication (Was: Where's the problem ?)

2007-07-04 Thread Rome

 A friend of mine compiled it under Linux and got:
 .
 .
 .
 32779 :  1   1 ---32776--  0
 32780 :  1   0 ---32777-- -1
 Main: Ix{Integer}.index: Index (32766) out of range ((0,32765))

 If I convert every Integer into Int and use instead of the generic list
 functions the prelude-list functions, it works.

--... and the result is right?

 I don't have any idea, where the problem might be...

--Stupid question: Did you pay enough attentation to carries? There might be
--an unresolvable dependency if you request a digit which depends on
--infinitely many carries from following digits.

Thx for your reply.
The next output-digit depends on several digits of the input, which are
determined by the rectangles defined in module /Schedule/. Every coordinate
of a single rectangle is unique by definition.
Because I use Signed-Digit-Representation, carries are only local in a
single call of the multiplication -subroutine. Further my program is the
implementation of an online-algorithm, leading digits are computed first, so
an infinte number of carries shouldn't be the reason, I think.
In my opinion there is something wrong with the use of Integer because of
the Linux-error message. 
I can only verify the correctness of the result of the first 30
output-digits, and these are okay in both cases: Int and Integer.
-- 
View this message in context: 
http://www.nabble.com/Where%27s-the-problem---tf4022913.html#a11435728
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Deadlock in real number multiplication (Was: Where's the problem ?)

2007-07-04 Thread Henning Thielemann

On Wed, 4 Jul 2007, Rome wrote:

  A friend of mine compiled it under Linux and got:
  .
  .
  .
  32779 :  1   1 ---32776--  0
  32780 :  1   0 ---32777-- -1
  Main: Ix{Integer}.index: Index (32766) out of range ((0,32765))
 
  If I convert every Integer into Int and use instead of the generic list
  functions the prelude-list functions, it works.

 --... and the result is right?

  I don't have any idea, where the problem might be...

 --Stupid question: Did you pay enough attentation to carries? There might be
 --an unresolvable dependency if you request a digit which depends on
 --infinitely many carries from following digits.

 Thx for your reply.

You are probably aware of the common problems related to computation with
real numbers, thus my replies below might not be of much help. I assume
that your problem is specific to your code and the solution requires
understanding your algorithm and your implementation, I didn't invested
time in either of these, so far.

 The next output-digit depends on several digits of the input, which are
 determined by the rectangles defined in module /Schedule/. Every coordinate
 of a single rectangle is unique by definition.
 Because I use Signed-Digit-Representation, carries are only local in a
 single call of the multiplication -subroutine.

If you add at least 100 numbers in base 10 computation, then two carry
steps become necessary, both with signed and unsigned digits.

 Further my program is the implementation of an online-algorithm, leading
 digits are computed first, so an infinte number of carries shouldn't be
 the reason, I think.

At some time, you have to apply carries, otherwise digits will get out of
range. You might want to make perfect carries by processing the digit
stream from the right to left - which is obviously impossible and you have
to follow a different strategy.

 In my opinion there is something wrong with the use of Integer because of
 the Linux-error message.
 I can only verify the correctness of the result of the first 30
 output-digits, and these are okay in both cases: Int and Integer.

You can verify correctness for any multiplication by multiplying huge
Integers.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very simple parser

2007-07-04 Thread Ilya Tsindlekht
On Thu, Jul 05, 2007 at 12:58:06AM +1000, Alexis Hazell wrote:
 On Tuesday 03 July 2007 09:51, Arie Peterson wrote:
 
  No, there is a 'State s' monad provided (for arbitrary state type 's'),
  which implements the 'get' and 'put' methods. In other words, 'State s' is
  an instance of the 'MonadState s' class. This terminology can be really
  confusing at first.
 
  For now, you may forget about the MonadState class. Simply use 'get' 
  friends and everything will work fine.
 
 This may be a stupid question, but i don't understand how (indeed, if) one 
 can 
 maintain multiple states using the State monad, since 'get' etc. don't seem 
 to require that one specify which particular copy of a State monad one wishes 
 to 'get' from, 'put' to etc.? Does one have to use (say) a tuple or a list to 
 contain all the states, and when one wishes to change only one of those 
 states, pass that entire tuple or list to 'put' with one element changed and 
 the rest unchanged?
 
 
 Alexis.
A value of type 'State t' contains an incapsulated function can be
de-encapsulated using runState and when evaluated, performs the actual
computation. This function maintains state internally, so for each
invocation of this function (such functions from other values of type
'State t') state is preserved separately. 

Hope this clarifies your confusion.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-07-04 Thread Bulat Ziganshin
Hello Philip,

Wednesday, July 4, 2007, 9:41:27 PM, you wrote:

 I'm thinking of the elimination of the boxing of values drawn out of
 the input stream where possible, eg if I was writing a stream
 processor that folded across the values in the input stream, it would
 (presumably) be more efficient if the compiler noticed that the
 function in question was (say) just reading Int values at offsets
 within the stream, and could pass those as unboxed references in the
 compiled code rather than freshly constructed values.

it will depend on your code. the library doesn't make unnecessary
boxing, but (unlike Data.Binary?) it supports only monadic
(de)serialization. so there is no room for ByteString-like fusion
which pass unboxed data through several transformations. with my lib,
you can only read whole unboxed structure and then process it:

data T = C !Int32 !Word16

do x - get h :: IO T
   processT $! x

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Parsec - collecting patches - How to contact maintainer Daan Leijen ?

2007-07-04 Thread Marc Weber
Paresc is a great piece of software. But there are some things which
do bother me occasionally.

A short list:

Things I'd like to change:

a) custom location tracking. (I've already written a patch, but I
   haven't tested how much speed will suffer? Which would be a nice test?)

b) Add a function returning a monadic result
   (thus   either (fail . show) return  each time .. )
   because I feel like doing this all the time.

c) make some functions more generic
   examples:

 module Text.ParserCombinators.Parsec.Char 
 (these functions should work with any token type):
   anyChar - anyToken
   char - expectToken
   string - expectTokens
   satisfy 

d) export some simple functions such as nat decimal etc..
   Sometimes all I just want to get an integer without importing
   Tokens and specifying a language..

shapr / sorear suggested asking SPJ to contact Daan Leijen.

Perhaps there are different approaches to address the issues above?

Do you also have some patches / suggestions ?

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


[Haskell-cafe] A very nontrivial parser

2007-07-04 Thread Andrew Coppin

Well, I eventually got it to work correctly... (!)

My goal is to be able to stack multiple parsers one on top of the other 
- but be able to *change* the stack half way through parsing if needed. 
This I eventually succeeded in doing. The external interface is fairly 
simple, but the type signatures are NOT. (!!)




My basic idea was to abstract the data source that a parser gets its 
data from:


 class Source s where
   empty :: s x - Bool
   fetch :: s x - (x, s x)

 instance Source [] where   -- Nice syntax... :-S
   empty = null
   fetch xs = (head xs, tail xs)

Now I can define a parser type. But... uh... there's a slight glitch. 
What I *want* to say is


 Parser state in out = ...

But what I ended up with is

 newtype Parser state src x y = Parser ((state, src x) - (state, src 
x, y))


I then make Parser a monad, write some functions to get/set the state 
parameter, and


 token_get :: (Source src) = Parser state src x x
 token_get = Parser (\(state, tokens) - let (t,ts) = fetch tokens in 
(state, ts, t))


Anyway, all of that more or less works. Then I begin the utterly 
psychopathic stuff:


 data Stack state0 src0 t0 t1 = ...

 instance Source (Stack state0 src0 t0) where ...

 stacked :: st0 - Parser st0 src0 t0 [t1] - st1 - Parser st1 (Stack 
st0 src0 t0) t1 x - Parser st9 src0 t0 x


By this point, my brain is in total agony! _

But, almost unbelievably, all this psychotic code actually *works*... 
(Well, there were a few bugs, they're fixed now.)


Essentially, I have the stacked function, where if I do

 x - stacked foo parser1 bar parser2
 y - parser3

then it runs parser2, but it uses parser1 to transform the data first. 
Which is what I actually wanted in the first place... Most critically, 
when parser2 *stops* demanding tokens, parser3 is run, picking up from 
where parser1 left off. (Confused yet? Wait til you see the code to 
implement this insanity!)




One problem remains... That pesky source type. Every time I mention a 
parser, I have to say what kind of course object it reads from - even 
though all parsers work with *any* source object! (That's the whole 
point of the Source class.) I really want to get rid of this. (See, for 
example, the type signature for stacked. Yuck!) Also, every time I 
write a simple parser, I get a compile-time error saying something about 
a monomorphism restriction or something... If I add an explicit type 
it goes away, but it's very annoying to keep typing things like


 test7 :: (Source src) = Parser state src Int Int

and so forth. And I can't help thinking if I could just get *rid* of 
that stupid source type in the signature, there wouldn't be a problem...


Anybody have a solution to this?

___
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-04 Thread Jonathan Cast
On Wednesday 04 July 2007, Andrew Coppin wrote:
 Well, I eventually got it to work correctly... (!)

 My goal is to be able to stack multiple parsers one on top of the other
 - but be able to *change* the stack half way through parsing if needed.
 This I eventually succeeded in doing. The external interface is fairly
 simple, but the type signatures are NOT. (!!)



 My basic idea was to abstract the data source that a parser gets its
 data from:

   class Source s where
 empty :: s x - Bool
 fetch :: s x - (x, s x)

   instance Source [] where   -- Nice syntax... :-S
 empty = null
 fetch xs = (head xs, tail xs)

 Now I can define a parser type. But... uh... there's a slight glitch.
 What I *want* to say is

   Parser state in out = ...

 But what I ended up with is

   newtype Parser state src x y = Parser ((state, src x) - (state, src
 x, y))

snip

 One problem remains... That pesky source type. Every time I mention a
 parser, I have to say what kind of course object it reads from - even
 though all parsers work with *any* source object! (That's the whole
 point of the Source class.) I really want to get rid of this. (See, for
 example, the type signature for stacked. Yuck!) Also, every time I
 write a simple parser, I get a compile-time error saying something about
 a monomorphism restriction or something... If I add an explicit type
 it goes away, but it's very annoying to keep typing things like

   test7 :: (Source src) = Parser state src Int Int

 and so forth. And I can't help thinking if I could just get *rid* of
 that stupid source type in the signature, there wouldn't be a problem...

 Anybody have a solution to this?

newtype Parser state x y
  = Parser (forall src. Source src = (state, src x) - (state, src x, y))

Definition of monad functions, etc, works exactly as for your version, but 
this way all your parsers have polymorphic implementation types, but none has 
a type that trips the monomorphism restriction.  There's some kind of 
argument here in the debate about the monomorphism restriction, but I'm not 
sure if it's for or against . . . [1]

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs

[1] http://www.lysator.liu.se/c/duffs-device.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The Garbage Collector Ate My Homework

2007-07-04 Thread Tim Chevalier

On 7/3/07, Thomas Conway [EMAIL PROTECTED] wrote:

Okay, so a bit of a tweak of the RTS flags, I got a DRAMATIC improvement:

239,434,077,460 bytes allocated in the heap
9,034,063,712 bytes copied during GC (scavenged)
132,748,740 bytes copied during GC (not scavenged)
226,313,736 bytes maximum residency (7 sample(s))

   5992 collections in generation 0 (136.16s)
 38 collections in generation 1 ( 62.69s)
  7 collections in generation 2 (  1.38s)

792 Mb total memory in use

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time  417.54s  (673.69s elapsed)
  GCtime  200.23s  (205.86s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time  617.78s  (879.55s elapsed)

  %GC time  32.4%  (23.4% elapsed)

  Alloc rate573,432,968 bytes per MUT second

  Productivity  67.6% of total user, 47.5% of total elapsed

The flags I used were: -H500M -G3



Nice -- but did you compare the results if you just add -H500M and not -G3?

Cheers,
Tim

--
Tim Chevalier* catamorphism.org *Often in error, never in doubt
Aw, honey, you can keep what's in my pockets, but send me back my
pants.  --Greg Brown
___
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 Philip Armstrong

On Wed, Jul 04, 2007 at 07:36:11PM +0100, Andrew Coppin wrote:

Philip Armstrong wrote:

[1] Which sick application *needs* intermixed endianness?


*Clearly* you've never been to Singapore...

...er, I mean, Ever tried playing with networking protocol stacks?


No (thankfully?).

Phil

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
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


[Haskell-cafe] folds with escapes

2007-07-04 Thread Michael Vanier
I'm sure this has been done a hundred times before, but a simple generalization of foldl just 
occurred to me and I wonder if there's anything like it in the standard libraries (I couldn't find 
anything).  Basically, I was trying to define the any function in terms of a fold, and my first 
try was this:


 any :: (a - Bool) - [a] - Bool
 any p = foldl (\b x - b || p x) False

This is inefficient, because if (p x) is ever True the rest of the list is scanned unnecessarily. 
So I wrote a more general foldl with an escape predicate which terminates the evaluation, along 
with a function which tells what to return in that case (given an argument of the running total 'z'):


 foldle :: (b - Bool) - (a - a) - (a - b - a) - a - [b] - a
 foldle _ _ _ z [] = z
 foldle p h f z (x:xs) = if p x then h z else foldle p h f (f z x) xs

Using this function, foldl is:

 foldl' = foldle (const False) id

and any is just:

 any p = foldle p (const True) const False

I also thought of an even more general fold:

 foldle' :: (b - Bool) - (a - b - [b] - a) - (a - b - a) - a - [b] 
- a
 foldle' _ _ _ z [] = z
 foldle' p h f z (x:xs) = if p x then h z x xs else foldle' p h f (f z x) xs

Using this definition, you can write dropWhile as:

 dropWhile :: (a - Bool) - [a] - [a]
 dropWhile p = foldle' (not . p) (\_ x xs - x:xs) const []

Again, I'm sure this has been done before (and no doubt better); I'd appreciate any pointers to 
previous work along these lines.


Mike




___
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 Stefan O'Rear
On Wed, Jul 04, 2007 at 04:20:20PM -0700, Michael Vanier wrote:
 I'm sure this has been done a hundred times before, but a simple 
 generalization of foldl just occurred to me and I wonder if there's 
 anything like it in the standard libraries (I couldn't find anything).
 Basically, I was trying to define the any function in terms of a fold, 
 and my first try was this:

  any :: (a - Bool) - [a] - Bool
  any p = foldl (\b x - b || p x) False

 This is inefficient, because if (p x) is ever True the rest of the list is 
 scanned unnecessarily.

Rather than create a new escape fold, it's much easier, simpler, and
faster just to use a right fold:

any p = foldr (\x b - p x || b) False

That will short-ciruit well by laziness, and is made tailrecursive by
same.

Stefan
___
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 Michael Vanier

That's cool -- good point.  takeWhile is also trivially defined in terms of 
foldr:

 takeWhile p = foldr (\x r - if p x then x:r else []) []

Can you do dropWhile in terms of foldr?  I don't see how.

Mike

Stefan O'Rear wrote:

On Wed, Jul 04, 2007 at 04:20:20PM -0700, Michael Vanier wrote:
I'm sure this has been done a hundred times before, but a simple 
generalization of foldl just occurred to me and I wonder if there's 
anything like it in the standard libraries (I couldn't find anything).
Basically, I was trying to define the any function in terms of a fold, 
and my first try was this:



any :: (a - Bool) - [a] - Bool
any p = foldl (\b x - b || p x) False
This is inefficient, because if (p x) is ever True the rest of the list is 
scanned unnecessarily.


Rather than create a new escape fold, it's much easier, simpler, and
faster just to use a right fold:

any p = foldr (\x b - p x || b) False

That will short-ciruit well by laziness, and is made tailrecursive by
same.

Stefan

___
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 Stefan O'Rear
On Wed, Jul 04, 2007 at 05:08:01PM -0700, Michael Vanier wrote:
 That's cool -- good point.  takeWhile is also trivially defined in terms of 
 foldr:

  takeWhile p = foldr (\x r - if p x then x:r else []) []

 Can you do dropWhile in terms of foldr?  I don't see how.

dropWhile cannot be expressed (with full sharing semantics) in terms of
foldr alone, but it can be done nicely as a so-called paramorphism using
foldr and tails.

dropWhile p = foldr (\l cont - case l of { (x:xs) | p x - cont ; _ - l }) [] 
. tails

Stefan
___
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 Daniel McAllansmith
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.

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


Re: [Haskell-cafe] Parsers are monadic?

2007-07-04 Thread Claus Reinke

(b) i like my combinator grammars to be reversible, so that a single
grammar specification can be used for both parsing and
unparsing/pretty-printing.  that means i have to define the
details myself anyway.


Oh cool - this is something I have wanted for a long time.  Anything
released or otherwise available?


and i thought noone had noticed!-) nothing really released - i first used 
that technique in haskell for a prototype of the reduction system i was
modifying for my phd, many years ago. since reduction sytems had 
syntax oriented editors as interfaces, which i needed to model in my

prototype to get the right design context for the language extensions
i was working on, i needed parsing/unparsing/editing, and i didn't want 
three separate specifications to maintain for one and the same grammar. 

unfortunately, i ultimately had to implement things into the existing 
reduction systems (think the complexity of ghc and gdh combined, 
but written in .. c), so i had to put the haskell prototype aside while 
finishing my phd. when i finally emerged from that work, haskell had 
long moved on from 1.2, including substantial language changes, and 
as usual offering no tool support for porting large applications from 
one language version to the next (will haskell'  finally do better in 
this important aspect?-). 

i never got around to porting that prototype, and so i had shelved 
any idea of writing about the technique until recently, when i used it
again in a much smaller framework. but i have used the same basic 
technique, adapted to monadic combinators, for many years, and

every time i reimplement the ideas, i tend to play with alternative
ways of representing things, especially as the ways of combining
the parser and unparser aspects or error handling are concerned.

the latest such experiment is not necessarily the simplest variant, 
but i've just added some text explaining the basic ideas of grammar

combinators to the project log (fathom.txt, starting from line 482,
or search for 'grammar combinators'), and there's a grammar for 
a simple lambda-calculus (Lambda.hs, from line 210, or search 
for 'grammar'), so it should (might?-) be possible to work out the

basics from there. the more awkward bits (basic lexing/unlexing,
error handling, in Syntax.hs) are without documentation so far, 
but you might want to write those in a different way anyhow;-).


you can get the haskell code and project log via

   darcs get http://www.cs.kent.ac.uk/~cr3/fathom

or the project log directly at

   http://www.cs.kent.ac.uk/~cr3/fathom/fathom.txt

the experiment itself, dubbed 'fathom', might be interesting for 
other reasons, as it includes a straightforward embedding of 
conditional rewrite systems in haskell, extended to contextual 
rewriting, and used to specify normal-order and call-by-need 
lambda-calculi via a direct embedding of their reduction rules. 

this gives rather inefficient executable semantics, which are 
however very close to the operational semantics specifications 
one tends to find in papers/textbooks. and since they work as 
monadic text transformers (parse/reduce/unparse), one gets 
trivial little reduction systems for these calculi (there are even

some vim files, as i'm using vim as my user interface to those
mini-reduction systems, or am i using haskell to extend vim?-).

i doubt that everything will be obvious - there's a lot of text
explanation already in the project log, but not all of the code
is easily readable (Lambda.hs should be accessible, with the
help of the project log), and there's no other documentation yet.
please try the project log first, then feel free to ask questions!

oh, and please let me know if you like what you see?-)
claus

___
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 Guido Genzone

2007/7/4, Michael Vanier [EMAIL PROTECTED]:

That's cool -- good point.  takeWhile is also trivially defined in terms of 
foldr:

  takeWhile p = foldr (\x r - if p x then x:r else []) []

Can you do dropWhile in terms of foldr?  I don't see how.



I 'm very bad in english, sorry.

Here is a solution
dropWhile in terms of fordr

Author : Graham Hutton
www.cs.nott.ac.uk/~gmh/fold.ps
___
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] folds with escapes

2007-07-04 Thread Bernie Pope


On 05/07/2007, at 10:08 AM, Michael Vanier wrote:



Can you do dropWhile in terms of foldr?  I don't see how.

Mike


I considered that very question in an article I wrote for the  
Monad.Reader magazine:


   http://www.haskell.org/sitewiki/images/1/14/TMR-Issue6.pdf

If you are really keen, you might want to try altering the working  
backwards with tuples version into one which is properly lazy (many  
people who read the paper pointed out the omission).


Cheers,
Bernie.
___
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 Thomas Conway

On 7/5/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote:

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



Which, if I read it correctly is not safe in a concurrent/multitasking
environment, since it wraps the underlying mmapped region. In many
programs, I'm sure this won't be a problem. Unfortunately, the system
I'm working on is multi-threaded, and we definitely want to update
regions. Perhaps I'll have to bite the bullet and implement the
Mapping thing I described. The really unfortunate thing is that I'd
really like to be able to do it within the STM monad, with rollback,
etc - escaping to the IO monad is annoying.

FWIW, the technique I use to handle this kind of situation may be of
general interest. Consider a cache of structures reconstituted from an
external file.  If a requested item is not in the cache, then we throw
an exception which is caught in a wrapper function which is in the IO
monad, read the requested structure, stick it in the cache, then rerun
the transaction. There are a few details you have to get right,
including making sure none of the items you require to complete the
operation get evicted by another thread, but it works very nicely.

T.
--
Dr Thomas Conway
[EMAIL PROTECTED]

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


[Haskell-cafe] System.Exit

2007-07-04 Thread Thomas Conway

Hi All,

Can anyone tell me what System.Exit.exitWith is actually supposed to
do? As far as I can tell, it seems to be a synonym of (return ()).

Okay, I'll stop being provocative and try and be helpful.

So I have a web server, which like the one in The Literature(TM),
essentially has a main loop:

doit sok = do
   (reqSok,reqAddr) - Network.Socket.accept sok
   forkIO (handleRequest reqSok reqAddr)
   doit sok

This is all well and good, but how do you *stop* a server? Well, you
have a request (blah blash auth blah blah) which tells it to shut
down, /quit for example.

I have a function to handle the quit request that looks something like:

quitHandler sok addr  = do
   tidyUpEverything 
   sendOkResponse sok
   sClose sok
   System.Exit.exitWith ExitSuccess

All nice and simple. All except one detail: it doesn't actually work.

It prints

exit: ExitSuccess

but the doit loop keeps going. Of course, it goes totally spacko,
because of the call to tidyUpEverything, but it doesn't exit.

So, if I set an IORef/TVar inside quitHandler which I inspect either
just before or just after the call to Network.Socket.accept, I could
exit the loop, but that only helps once the next request comes in.

I contemplated a solution involving Control.Exception.throwTo, but I
actually read the doco (!) which states the following:

quote
If the target thread is currently making a foreign call, then the
exception will not be raised (and hence throwTo will not return) until
the call has completed. This is the case regardless of whether the
call is inside a block or not.
/quote

So no joy there.

Ideas anyone?

And is exitWith broken, or is it the doco that's broken?

cheers,
T.
--
Dr Thomas Conway
[EMAIL PROTECTED]

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


Re: [Haskell-cafe] System.Exit

2007-07-04 Thread Brandon S. Allbery KF8NH


On Jul 5, 2007, at 0:04 , Thomas Conway wrote:


quitHandler sok addr  = do
   tidyUpEverything 
   sendOkResponse sok
   sClose sok
   System.Exit.exitWith ExitSuccess

All nice and simple. All except one detail: it doesn't actually work.

It prints

exit: ExitSuccess

but the doit loop keeps going. Of course, it goes totally spacko,
because of the call to tidyUpEverything, but it doesn't exit.

So, if I set an IORef/TVar inside quitHandler which I inspect either
just before or just after the call to Network.Socket.accept, I could
exit the loop, but that only helps once the next request comes in.

I contemplated a solution involving Control.Exception.throwTo, but I
actually read the doco (!) which states the following:

quote
If the target thread is currently making a foreign call, then the


If you're making foreign calls and using forkIO, then there will be  
at least two OS threads running.  In this case, the process generally  
won't exit until all the OS threads do.  Since this is the OS's  
doing, as far as the Haskell runtime is concerned System.Exit has  
done the right thing, but the other OS thread(s) won't have been  
notified to shut down so they'll just keep going until told otherwise.


I think the proper action here is that your quitHandler sets an MVar/ 
TVar to indicate that things should start shutting down, then either  
shut down its thread or, if it's in the main thread, wait for the  
other threads to terminate and then invoke System.Exit.


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


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