Re: [Haskell-cafe] Trying to make a Typeable instance

2007-07-07 Thread Adrian Hey

Adrian Hey wrote:

Hello,

I'm trying to make the type (ListGT map k a) an instance of Typeable,
where map is kind (* - *).

data ListGT map k a
 = Empt
 | BraF ![k] a !(map (ListGT map k a))
 | BraE ![k]   !(map (ListGT map k a))

I thought I'd cracked it with something like this..

instance (Typeable (map (ListGT map k a)), Typeable k, Typeable a) =
 Typeable (ListGT map k a) where
   typeOf lgt = mkTyConApp (mkTyCon Data.Trie.General.ListGT)
   [mTypeRep, kTypeRep, aTypeRep]
 where BraF [k] a m = lgt -- This is just to get types for k a m !!
   kTypeRep = typeOf k
   aTypeRep = typeOf a
   mTypeRep = typeOf m

However, showing the resulting TypRep gives a stack overflow. I wasn't
too surprised about this, so I tried replacing the last line with..
   mTypeRep = mkTyConApp (typeRepTyCon (typeOf m)) []
..thinking that this would make it terminate. But it doesn't.

Could someone explain how to do this?


(Answering my own question) this seems to do the trick..

instance (Typeable1 map, Typeable k, Typeable a) =
 Typeable (ListGT map k a) where
   typeOf lgt = mkTyConApp (mkTyCon Data.Trie.General.ListGT)
   [mTypeRep, kTypeRep, aTypeRep]
 where BraF [k] a m = lgt -- This is just to get types for k a m !!
   kTypeRep = typeOf k
   aTypeRep = typeOf a
   mTypeRep = typeOf1 m

Regards
--
Adrian Hey


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


Re: [Haskell-cafe] A very edgy language

2007-07-07 Thread Andrew Coppin

Donald Bruce Stewart wrote:

Give #haskell is a far larger community than:

#lisp
#erlang
#scheme
#ocaml

As well as

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

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


Yeah, #haskell is pretty big - 300 people idling and 1-3 people actually 
talking. :-P


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


Re: [Haskell-cafe] A very edgy language

2007-07-07 Thread Donald Bruce Stewart
andrewcoppin:
 Donald Bruce Stewart wrote:
 Give #haskell is a far larger community than:
 
 #lisp
 #erlang
 #scheme
 #ocaml
 
 As well as
 
 #java
 #javascript
 #ruby
 #lua
 #d
 #perl6
 
 Maybe we need to reconsider where the (FP) mainstream is now? :-)
   
 
 Yeah, #haskell is pretty big - 300 people idling and 1-3 people actually 
 talking. :-P

Hey! We answer questions and write code for free, and you misrepresent
the population anyway:

Maximum users seen in #haskell: 354, currently: 318 (97.8%), active: 53 
(16.7%)
 
^^

In fact, a lot of your exploratory/introductory questions would be most
efficiently answered on irc. Do drop by!

http://haskell.org/haskellwiki/IRC_channel

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


Re: [Haskell-cafe] A very edgy language

2007-07-07 Thread Andrew Coppin

Donald Bruce Stewart wrote:

andrewcoppin:
  

Yeah, #haskell is pretty big - 300 people idling and 1-3 people actually
talking. :-P



Hey! We answer questions and write code for free, and you misrepresent
the population anyway:

Maximum users seen in #haskell: 354, currently: 318 (97.8%), active: 53 
(16.7%)
 
^^

In fact, a lot of your exploratory/introductory questions would be most
efficiently answered on irc. Do drop by!

http://haskell.org/haskellwiki/IRC_channel
  


Unfortunately, when I ask questions most people seem to either ignore me 
or not know what the answer is. :-(


Also, it's quite fiddly to ask long and/or complicated question in IRC. 
Gotta type really fast. ;-)


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


Re: [Haskell-cafe] Trying to make a Typeable instance

2007-07-07 Thread Neil Mitchell

Hi Adrian

You can use Data.Derive to do this for you:
http://www-users.cs.york.ac.uk/~ndm/derive/

Or DrIFT: http://repetae.net/~john/computer/haskell/DrIFT/

Thanks

Neil

On 7/7/07, Adrian Hey [EMAIL PROTECTED] wrote:

Adrian Hey wrote:
 Hello,

 I'm trying to make the type (ListGT map k a) an instance of Typeable,
 where map is kind (* - *).

 data ListGT map k a
  = Empt
  | BraF ![k] a !(map (ListGT map k a))
  | BraE ![k]   !(map (ListGT map k a))

 I thought I'd cracked it with something like this..

 instance (Typeable (map (ListGT map k a)), Typeable k, Typeable a) =
  Typeable (ListGT map k a) where
typeOf lgt = mkTyConApp (mkTyCon Data.Trie.General.ListGT)
[mTypeRep, kTypeRep, aTypeRep]
  where BraF [k] a m = lgt -- This is just to get types for k a m !!
kTypeRep = typeOf k
aTypeRep = typeOf a
mTypeRep = typeOf m

 However, showing the resulting TypRep gives a stack overflow. I wasn't
 too surprised about this, so I tried replacing the last line with..
mTypeRep = mkTyConApp (typeRepTyCon (typeOf m)) []
 ..thinking that this would make it terminate. But it doesn't.

 Could someone explain how to do this?

(Answering my own question) this seems to do the trick..

instance (Typeable1 map, Typeable k, Typeable a) =
  Typeable (ListGT map k a) where
typeOf lgt = mkTyConApp (mkTyCon Data.Trie.General.ListGT)
[mTypeRep, kTypeRep, aTypeRep]
  where BraF [k] a m = lgt -- This is just to get types for k a m !!
kTypeRep = typeOf k
aTypeRep = typeOf a
mTypeRep = typeOf1 m

Regards
--
Adrian Hey


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


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


Re: [Haskell-cafe] Two-continuation `monads' and MonadMinus

2007-07-07 Thread oleg

 I was initially skeptical about defining Foldable for the direct-style
 LogicT transformer, but now I suspect that it is definable.

 Now that I think about it, you're losing the ability to work with monad
 transformers.

I think you're right. The particular point of msplit is that it is a
monad transformer method and provides certain guarantees on the order
and occurrences of _effects_. It seems the interface of Foldable, at
brief glance, makes no assurances as to how foldr may behave. The
implementation of foldr may decide to `look ahead' of the foldable
data structure for optimization purposes and only then start invoking
the folding function. That is sound so long as `looking ahead' does
not entail any effect. The function `msplit' is designed to operate on
a `data structure' where examining each element may be accompanied by
an effect. It becomes important then not to look ahead and be careful
not to re-do an effect if we need to re-examine some previously seen
value. In short, msplit in LogicT does provide guarantees about the
effect. The Foldable interface leaves this issue unspecified, or so it
seems. So, they can't be considered equivalent.


And speaking of non-determinism in general, it seem from experience
FBackTrackT is a quite a better solver: it finds solutions where List
and similar monads fail to find them; compared to the breadth-first
search (which is too, complete), FBackTrackT takes far less
resources. So, here too FBackTrackT finds solutions where
breadth-first search just runs out of memory.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] runInteractiveCommand and command not found

2007-07-07 Thread Ketil Malde

I notice that when I try to execute a non-existing command with
runInteractiveProcess, nasty things happen when I close the input.  To
be exact, the whole program terminates.  Is this the intended behavior,
and if so, what is the correct way to work around it?

Sample sessions below, cat is a valid executable, while asdf is not.

-k

% ghci   
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 6.6, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Prelude :m + System.IO
Prelude System.IO :m + System.Process
Prelude System.IO System.Process (i,o,e,p) - runInteractiveCommand asdf
Prelude System.IO System.Process hPutStr i foo
Prelude System.IO System.Process hClose i

% ghci   
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 6.6, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Prelude :m + System.Process
Prelude System.Process :m + System.IO
Prelude System.Process System.IO (i,o,e,p) - runInteractiveCommand cat
Prelude System.Process System.IO hPutStr i foo
Prelude System.Process System.IO hClose i
Prelude System.Process System.IO 
Prelude System.Process System.IO x- waitForProcess p
ExitSuccess


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


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

2007-07-07 Thread Ketil Malde
On Sat, 2007-07-07 at 13:39 +1000, Donald Bruce Stewart wrote:

 Give #haskell is a far larger community than:

Well, Haskell clearly has a well developed IRC community.
Using Google to search Usenet posts in 2007:

Haskell:21000
Lisp:   29000
Erlang:  2500
Ocaml:   7000

Ruby:  145000
Python:154000
Perl:  39

(This includes fa.haskell and probably other mailing list gateways as
well.)

Using Google Scholar to search for papers from 2007:

Haskell:1310
Ruby:   1670
Lisp:316
Ocaml:38

Java:   7650

Unfortunately, all this proves is that if your language shares its name
with a large number of people, it will be mentioned a lot in scientific
papers :-)

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

Getting there, at least.

-k


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


Re: [Haskell-cafe] Trying to make a Typeable instance

2007-07-07 Thread Hugh Perkins

Can you just write:

data ListGT map k a
 = Empt
 | BraF ![k] a !(map (ListGT map k a))
 | BraE ![k]   !(map (ListGT map k a))
  deriving( Typeable )

?

On 7/7/07, Adrian Hey [EMAIL PROTECTED] wrote:


Hello,

I'm trying to make the type (ListGT map k a) an instance of Typeable,
where map is kind (* - *).

data ListGT map k a
  = Empt
  | BraF ![k] a !(map (ListGT map k a))
  | BraE ![k]   !(map (ListGT map k a))

I thought I'd cracked it with something like this..

instance (Typeable (map (ListGT map k a)), Typeable k, Typeable a) =
  Typeable (ListGT map k a) where
typeOf lgt = mkTyConApp (mkTyCon Data.Trie.General.ListGT)
[mTypeRep, kTypeRep, aTypeRep]
  where BraF [k] a m = lgt -- This is just to get types for k a m !!
kTypeRep = typeOf k
aTypeRep = typeOf a
mTypeRep = typeOf m

However, showing the resulting TypRep gives a stack overflow. I wasn't
too surprised about this, so I tried replacing the last line with..
mTypeRep = mkTyConApp (typeRepTyCon (typeOf m)) []
..thinking that this would make it terminate. But it doesn't.

Could someone explain how to do this?

Thanks
--
Adrian Hey


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

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


Re: [Haskell-cafe] Trying to make a Typeable instance

2007-07-07 Thread Neil Mitchell

Hi


data ListGT map k a
  = Empt
  | BraF ![k] a !(map (ListGT map k a))
  | BraE ![k]   !(map (ListGT map k a))
   deriving( Typeable )


Not in Haskell, only in GHC.

Thanks

Neil



?

On 7/7/07, Adrian Hey [EMAIL PROTECTED] wrote:
 Hello,

 I'm trying to make the type (ListGT map k a) an instance of Typeable,
 where map is kind (* - *).

 data ListGT map k a
   = Empt
   | BraF ![k] a !(map (ListGT map k a))
   | BraE ![k]   !(map (ListGT map k a))

 I thought I'd cracked it with something like this..

 instance (Typeable (map (ListGT map k a)), Typeable k, Typeable a) =
   Typeable (ListGT map k a) where
 typeOf lgt = mkTyConApp (mkTyCon  Data.Trie.General.ListGT)
 [mTypeRep, kTypeRep, aTypeRep]
   where BraF [k] a m = lgt -- This is just to get types for k a m !!
 kTypeRep = typeOf k
 aTypeRep = typeOf a
 mTypeRep = typeOf m

 However, showing the resulting TypRep gives a stack overflow. I wasn't
 too surprised about this, so I tried replacing the last line with..
 mTypeRep = mkTyConApp (typeRepTyCon (typeOf m)) []
 ..thinking that this would make it terminate. But it doesn't.

 Could someone explain how to do this?

 Thanks
 --
 Adrian Hey


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



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



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


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

2007-07-07 Thread Thomas Conway

On 7/7/07, Albert Y. C. Lai [EMAIL PROTECTED] wrote:

Non-strict (most implementations lazy): rarely useful if you ask the
mainstream.


mild-rant

Of your propositions, I must say this one has the most merit, though
not exactly as stated. :-) Being non-strict does allow some nice
expressiveness, but has one teeny tiny downside - the performance
model for haskell programs is at best inscrutable. Even using the
decent profiling tools in GHC, it can be almost impossible to
understand why a non-trivial program behaves the way it does. In my
current project, we restart the server periodically because there's a
memory leak in there somewhere that I can't track down. Now, I'm not
saying that someone else might not spot it easily, but I hope you see
my point:

I can look at the source code of a C function, and I can pretty much
guess what machine code will be generated for it (issues like
instruction scheduling and register allocation aside). The same is
essentially true for C++, Lisp, Prolog, Java, Mercury, c, c, c, but
not for Haskell.

I wind up using -prof -auto-all as standard GHC flags so that if error
gets called, I have a vague chance of figuring out what's going on.

/mild-rant


Static typing: extreme paranoia.


I've been working in a mostly Python shop this last year, and it
reinforces my belief that people who don't like strong static typing
are yahoos, not professionals interested in producing high quality
code. Maybe I just don't get the line between professionalism and
paranoia. ;-)


Purely functional: vocal minority of edgy people.


Ever used Prolog? Compromising purity in a declarative language can
seem like a good idea in the short term, but in the long term, it
usually causes untold grief. Especially, in the case of Prolog, the
cut operator which interferes with the natural operation of
backtracking. It overflows into the operation of negation, and creates
all kinds of bother.

war-story
So I did my PhD in the Mercury group at .mu.oz.au. Mercury is a retake
on logic programing. It is pure.

In 1995 I arrived in the US for my first logic programming conference,
and on the first evening, before the conference proper began, went out
with a bunch of attendees. I got chatting with a really nice Canadian
guy, Jamie Andrews, and five minutes into the conversation, on finding
out he was a semantics researcher, asked what I thought was a terribly
witty question So are you presenting *another* semantics for the
'cut' operator?

Um, well, yes, actually was his reply.

Apart from showing what a precocious prat I was, OMG 12 years ago, it
tells you something about what happens when you ride rough-shod over
purity. It creates gainful employment for hundreds of researchers for
decades trying to put the genie back in the bottle.
/war-story

ML and friends have had a much easier time of it than Prolog, I
concede, but the problem of finding practical paradigms of programming
in pure languages that combine expressiveness with clean semantics is
actually well worth the short term inconvenience. Those with good
memories will know that the use of monads to express IO took some
time, and that there were several less successful, though more-or-less
pure attempts before. There was the pair of lazy streams model; the
continuation passing model; the linear types model (deployed by Clean,
of course); and maybe others. The cool thing is that they were all
fairly painful to use, and rather than give up, the researchers kept
trying new things and came upon monads. The extra cool thing is that
monads have turned out to be really useful for a whole lot of other
things than just a way of expressing IO or even IO and mutable state
(which linear types captures).

As SPJ notes in his Hair Shirt talk, monads are not perfect, since
they are often used in ways which over-sequentialize code using them,
so we have people working on arrows, and other more sophisticated
mechanisms, which in time will probably lead to more expressive
paradigms.

cheers,
T.
--
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] runInteractiveCommand and command not found

2007-07-07 Thread Lukas Mai
Am Samstag, 7. Juli 2007 11:27 schrieb Ketil Malde:
 I notice that when I try to execute a non-existing command with
 runInteractiveProcess, nasty things happen when I close the input.  To
 be exact, the whole program terminates.  Is this the intended behavior,
 and if so, what is the correct way to work around it?

 Loading package base ... linking ... done.
 Prelude :m + System.IO
 Prelude System.IO :m + System.Process
 Prelude System.IO System.Process (i,o,e,p) - runInteractiveCommand asdf
 Prelude System.IO System.Process hPutStr i foo
 Prelude System.IO System.Process hClose i

If you look at the exit status of ghci, you'll see that it was
terminated by SIGPIPE. This happens because you're trying to write
to a pipe that has no reader on the other end (because asdf
doesn't exist/run). It happens in hClose because i is buffered, so
the hPutStr doesn't actually send anything. hClose tries to flush
the buffer, which triggers the SIGPIPE.

The solution is to install a signal handler for SIGPIPE, even if it
just ignores the signal; something like:
  installHandler sigPIPE Ignore Nothing
This should make write() fail with EPIPE, which should be turned
into an IO exception by hClose (ok, so you still need to catch that
but at least it doesn't kill your whole program).

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


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

2007-07-07 Thread Lukas Mai
Am Freitag, 6. Juli 2007 01:24 schrieb Lukas Mai:
 Hello, cafe!

 I have the following code (paraphrased):

 ...
 forkIO spin
 ...
 spin = do
 (t, _) - accept s   -- (*)
 forkIO $ dealWith t  -- (**)
 spin

 My problem is that I want to stop spin from another thread. The obvious
 solution would be to throw it an exception. However, that leaks a socket
 (t) if the exception arrives between (*) and (**). I could wrap the whole
 thing in block, but from looking at the source of Network.Socket it seems
 that accept itself is not exception safe; so no matter what I do, I can't
 use asynchronous exceptions to make spin exit.

 (Is this actually true? Should accept be fixed (along with a lot of other
 library functions)?)

Answering myself: I now think that the above isn't true. :-)

Quoting Control.Exception:

 Some operations are interruptible, which means that they can receive
 asynchronous exceptions even in the scope of a block. Any function which
 may itself block is defined as interruptible; this includes takeMVar (but
 not tryTakeMVar), and most operations which perform some I/O with the
 outside world. The reason for having interruptible operations is so that we
 can write things like

   block (
  a - takeMVar m
  catch (unblock (...))
(\e - ...)
   )

 if the takeMVar was not interruptible, then this particular combination
 could lead to deadlock, because the thread itself would be blocked in a
 state where it can't receive any asynchronous exceptions. With takeMVar
 interruptible, however, we can be safe in the knowledge that the thread can
 receive exceptions right up until the point when the takeMVar succeeds.
 Similar arguments apply for other interruptible operations like openFile.

If I understand this correctly, spin should be written as:

spin = do
block $ do
(t, _) - accept s
unblock (forkIO $ doStuff t) `finally` sClose t
spin

Now t can't leak from spin because it's protected by block, while
the underlying accept() syscall is still interruptible by
asynchronous exceptions.

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


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

2007-07-07 Thread Rich Neswold

On 7/7/07, Lukas Mai [EMAIL PROTECTED] wrote:


If I understand this correctly, spin should be written as:

spin = do
block $ do
(t, _) - accept s
unblock (forkIO $ doStuff t) `finally` sClose t
spin



I think the `finally` portion should be done in the forked process context.
Otherwise once the process is forked, the socket gets closed by the parent
process. Something more along the lines of:

unblock (forkIO $ doStuff t `finally` sClose t)

--
Rich

JID: [EMAIL PROTECTED]
AIM: rnezzy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Playing with delimited continuations

2007-07-07 Thread Claus Reinke
Anyhow, thanks for the input, and the pointers to the papers and such (and 
writing so many of them in the first place. :) Incidentally, I really enjoyed 
your Delimited continuations in operating systems paper. Reading that one 
really made things click for me as to how delimited continuations can 
actually show up in real systems, as opposed to just being an esoteric, 
abstract construct).


i'd like to chime in there!-) just as i hadn't been comfortable with
call/cc before someone made the link to negation, i hadn't been
thinking much about delimited continuations before your paper
made the (now obvious;-) connection to (nested) evaluation 
contexts, which i tend to use all the time. sometimes, such 
simple connections are all that is needed.


btw, for me call/cc and delimited continuations, in contrast to
continuations in general, were not esoteric, abstract, but 
entirely too pragmatic, looking like powerful hacks, able to 
be bent to any purpose, seemingly lacking in foundations,

though not in applications.

makes me wonder if non-haskellers see monads and
monadic i/o in the same way as non-schemers see 
continuations and call/cc (the one too abstract, the other

too hacky?-).

thanks,
claus

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


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

2007-07-07 Thread Dave Bayer

On Jul 7, 2007, at 4:23 AM, Thomas Conway wrote:


the performance model for haskell programs is at best inscrutable


I punched my first Basic program by hand with a paper clip, in my  
high school library. Even after experiencing an APL interpreter at  
19, it has taken half my life to fully internalize that how long a  
language takes with a machine isn't the issue, what matters is how  
long a language takes with ME. I was beginning to accept that I might  
die before clearing my pipeline of research projects I want to code  
up. Haskell has given me new hope.


Haskell is like ice sailing, where one can reach 100 mph on a 15 mph  
breeze. A few months ago, I watched a colleague write a significant  
code experiment in Haskell in an hour, and I was stunned. Now, I  
routinely write reasonable code experiments in an hour to help learn  
the language, and I'm still a beginner. It pays to time all  
executions, one can sometimes knock a factor of ten out of a given  
algorithm with a modest amount of tweaking. One learns in the process  
how to write faster code next time on the first try. GHC is very  
impressive if one pays a little attention to one's code.


This of course sets up the best answer to this debate: For a hard  
problem, one can express better algorithms in Haskell that would  
simply be too painful to code in other languages, swamping any  
considerations about the speed of Haskell versus C for a given  
algorithm.


This is not where I'm personally at. I want Haskell to work math  
examples for me that would take months to work by hand. With current  
processor speeds, the bottleneck is how quickly I can specify to the  
computer what I want. Haskell is the perfect language for this. For  
this purpose, concise readable code I can understand later beats hell  
out of a better algorithm. My evolution as a Haskell programmer is to  
say things more clearly with less fuss, not to get the machine to go  
faster.


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


Re: [Haskell-cafe] A very edgy language

2007-07-07 Thread Andrew Coppin

Dave Bayer wrote:
I was beginning to accept that I might die before clearing my pipeline 
of research projects I want to code up.


...so it's *not* just me!


Haskell has given me new hope.


Indeed. ;-)


Today I hve implemented encoders and decoders for RLE, MTF, Fibonacci 
codes, and LZW. Next on my list is BWT, Huffman codes and arithmetic 
coding. (That last is *very* hard though...)


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


Re: [Haskell-cafe] A very edgy language

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

Donald Bruce Stewart wrote:

trebla:
I don't know. #math is larger than #accounting. Is it because math is 
more mainstream than accounting? I bet it is because math is more 


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


With all due respect to accounting, which is a fine profession and a 
great contributor to society, it is still pretty much secular. Math and 
Haskell are more ideal interests. That is why we like them, and that is 
also why they are less known.


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


Re: [Haskell-cafe] A very edgy language

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

Thomas Conway wrote:
[great comments on non-strict, static typing, purely functional]

Don't worry, I was just writing a sarcasm to an apparent attitude of X 
is rare edge iff I can't figure out X. I have always been believing in 
all the points you make.


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


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

2007-07-07 Thread Thomas Conway

On 7/8/07, Dave Bayer [EMAIL PROTECTED] wrote:

This of course sets up the best answer to this debate: For a hard
problem, one can express better algorithms in Haskell that would
simply be too painful to code in other languages, swamping any
considerations about the speed of Haskell versus C for a given
algorithm.


This is certainly true. I've coded up in less than six months,
something that uses better algorithms and finer grained concurrency
than the software I used to work on, and the latter represented 5 or
more man-years of coding. However this is server software, which is
long running so performance and memory usage are pretty important, and
these are relatively hard to get right in Haskell. OTOH, you can tell,
I think it's a good trade off - I did convince the mgt to let me doit
in Haskell in the first place. :-)

--
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] A very nontrivial parser

2007-07-07 Thread Claus Reinke
Now take decodeRLEb and feed it's output to some nontrivial parser, and 
then feed the remainder of the input, unmodified, into another parser:


so the code as posted didn't exhibit a full use case. that specification is 
still a bit vague. assuming that p1: decodeRLE, p2: nontrivial parser, and 
p3: another parser, it could be interpreted simply as parser combination:


   do { output - p1; x - p2 output; y - p3; return (x,y) }

or perhaps you meant to run p2 over the output of p1 in a separate parser 
chain, with the remaining input left by p1, not by p2, being fed into p3?


   do { output - p1; Just  x - return $ evalStateT p2 output; y - p3; return 
(x,y) }

then we'd have something like

   p2 `stack` p1 = do { out - p1; Just x - return $ evalStateT p2 out; return 
x }

Since I don't know how much data other_stuff is going to consume - let 
alone how much of the raw data you have to feed to decodeRLEb to make 
that much data - we arrive at the structure shown.


ah, that suggests yet another specification, a variation of the second 
version above, where the parser in control is not p1 itself, but p2, with 
p1 acting as an input transformation for p2, and p3 resuming where 
p1 left off. the difference being that p2's demand is supposed to drive

p1's input processing. which is a bit of a problem.

parsers are usually data- and grammar-driven, not demand-driven,
ie the input consumed by p1 does not usually depend on the demands
on p1's output. one could let p1 generate results of increasing length, 
and let p2 pick a result that fits, but that would involve rerunning p2 
on the complete prefix of too-short results, backtracking into p1 until 
it produces an output useable by p2 - not exactly elegant or efficient, 
but it would fit the second variant above (one would have to ensure

that p1 backtracked only over the length of input consumed, eg, an
outermost 'many', and that the shortest alternative was produced first). 

looking a little bit more closely, however, p1 is used more as a 
piecewise input transformation for p2 than as a separate parser. 
so it makes more sense to integrate p1 into p2 (or rather: parts 
of p1 - if p1 is 'many group', then we should integrate only 'group'; 
in other words, we'd like to run p1 repeatedly, in minimal-much 
mode, rather than the more typical once, in maximal-munch mode), 
so that the latter uses some part of p1 as its item parser (which, 
in turn, assumes that p2 has a single, identifiable item parser - 
called 'fetch' here, and no other way to access the parse state). 


that seems to be what you have in mind with your stacked
approach, where the state is read exclusively through the fetch
method in the Source interface, and a Source can either be a
plain list or buffered item parser stacked on top of a Source
(where fetch is served from the buffer, which is replenished 
by running the item parser over the inner Source; btw, are 
unused buffer contents discarded when p2 finishes? they 
can't be transformed back into p1/p3's input format..).


instead of using a type class, one could also parameterise p2
by its item parser, 'fetch'. that might make it easier to see that
this stacking is a kind of parser composition. unlike the 
standard function and monad compositions, this one relies 
on the compositional nature of combinator parsers: there's an 
item parser, which accesses the input and produces output, 
and there is a coordination framework (the combinatorial 
grammar) specifying how the item parser is to be used. 


function composition allows us to abstract over each part of
the composed function, including the inner function in a 'stack'
of functions:

   \x-f (g x) 
   == -- abstract over g

   (f .)

we can try to view parsers as composed from a grammar
and an item parser, where the latter is the 'inner' part of
this composition: 

   \s-(item  item) s `mplus` item s 
   == -- abstract over item

   \item s-(item  item) s `mplus` item s

turning item/fetch into a type class method is just another
way of composing the grammar with an item parser.

i had to implement it myself to understand what you were
trying to do, and how.. if indeed i have understood?-)

hth,
claus


(This makes it, what, the 5th time I've explained this? LOL...)


with problem specifications, it isn't quantity that counts.
the more ambiguous the specification, the more likely it
is that replies interpret it in ways that do not answer the
question. the fewer replies seem to address the question,
the more likely it is that the specification needs to be clearer.

on a high-volume list where readers might dip into and out
of long threads at any point, repetition in the form of concise
summaries can be helpful, even to those readers who might 
follow every post in every thread.


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


[Haskell-cafe] Parsing and Coding

2007-07-07 Thread Brandon Michael Moore
On Sat, Jul 07, 2007 at 06:49:25PM +0100, Andrew Coppin wrote:
 Dave Bayer wrote:
 I was beginning to accept that I might die before clearing my pipeline 
 of research projects I want to code up.
 
 ...so it's *not* just me!
 
 Haskell has given me new hope.
 
 Indeed. ;-)
 
 
 Today I hve implemented encoders and decoders for RLE, MTF, Fibonacci 
 codes, and LZW. Next on my list is BWT, Huffman codes and arithmetic 
 coding. (That last is *very* hard though...)

You should look at Jeremy Gibbons' paper Arithmetic coding with folds and 
unfolds. www.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/arith.pdf

For your more general parsing troubles, have you considered making you lower
level parsers copy the rest of the underlying input stream into each token
they produce? After that transformation a simple string might look something
like [(c,rest) | (c:rest) - init (tails Some characters of input)].

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


[Haskell-cafe] ANNOUNCE: logict-0.2

2007-07-07 Thread Dan Doel
Hello all,

I've just completed a library adapting the logic programming monad from 
the Backtracking, Interleaving, and Terminating Monad Transformers paper[1] 
into a format typical of the hierarchical libraries (based on MTL). It uses 
the two-continuation passing implementation described therein.

Hackage: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/logict-0.2
Tarball: 
http://hackage.haskell.org/packages/archive/logict/0.2/logict-0.2.tar.gz

Feel free to let me know if your find any bugs, or have suggestions.

Dan Doel

[1]: http://okmij.org/ftp/papers/LogicT.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: GHC threads and SMP

2007-07-07 Thread Donald Bruce Stewart
ninegua:
 replying to my own message... the behavior is only when -O is used
 during compilation, otherwise they both run on 2 cores but at a much
 lower (1/100) speed.

Hmm, any change with -O2? Is the optimiser changing the code such that
the scheduler doesn't get to switch threads as often? If you change
the thread scheduler switching rate does that change anything?

See the GHC user's guide for more details:

7.12.1.3.?Scheduling policy for concurrent threads

Runnable threads are scheduled in round-robin fashion. Context switches are
signalled by the generation of new sparks or by the expiry of a virtual 
timer
(the timer interval is configurable with the -C[num] RTS option). 
However, a
context switch doesn't really happen until the current heap block is full. 
You
can't get any faster context switching than this.

When a context switch occurs, pending sparks which have not already been
reduced to weak head normal form are turned into new threads. However, 
there is
a limit to the number of active threads (runnable or blocked) which are 
allowed
at any given time. This limit can be adjusted with the -t num RTS option 
(the
default is 32). Once the thread limit is reached, any remaining sparks are
deferred until some of the currently active threads are completed.

Perhaps SimonM can shed some light here?

 
 On 7/6/07, Paul L [EMAIL PROTECTED] wrote:
 I have two parallel algorithms that use the lightweight GHC thread and
 forkIO. I compile them using the -threaded (or -smp) option, and run
 both with +RTS -N2 -RTS command line option.
 
 QSort is able to make use of the dual cores on my laptop -- top
 shows that two threads show up and both CPUs are utilized, and time
 it will give something like this:
 
   real0m0.502s
   user0m0.872s
   sys 0m0.004s
 
 But Prime can only make use of one core, as shown by top. time gives
 
   real0m9.112s
   user0m9.093s
   sys 0m0.028s
 
 Because forkOS is not used anywhere, the decision of running them on 1
 or 2 OS threads seem rather arbitary. Why?
 
 Regards,
 Paul L
 
 
 
  import Control.Concurrent
  import System.Random
  import Data.Array.MArray
  import Data.Array.IO
  import System.IO.Unsafe
  import Control.Exception
 
 1. Quick Sort
 
  testQSort' n verbose = do
let b = (0, n - 1)
arr - newArray b 0  :: IO (IOUArray Int Int)
initM' (mkStdGen 0) b arr
waitForChildren
qsortM' b arr
waitForChildren
if verbose then getElems arr = putStrLn . show else return ()
 
 Initialize an array with random numbers.
 
  initM' g (i, j) arr | j - i  1 = fillArr g i j
where
  fillArr g i j = if i  j then return () else do
let (v, g') = next g
writeArray arr i v  fillArr g' (i + 1) j
  initM' g (i, j) arr = do
let k = (i + j) `div` 2
(g1, g2) = split g
forkChild $ initM' g1 (i, k) arr
forkChild $ initM' g2 (k + 1, j) arr
return ()
 
  qsortM' (i, j) arr = qsort' (i, j)
where
  qsort' (i, j) =
if j = i then return () else do
  k - split i j
  if j - i  1 then (forkChild $ qsort' (i, k - 1))  return 
 ()
  else qsort' (i, k - 1)
  qsort' (k + 1, j)
  split left right = do
v - readArray arr right
let split' i j = if j == right then swap i right v  return i 
 else do
  b - readArray arr j
  if b = v
then (swap i j b)  split' (i + 1) (j + 1)
else split' i (j + 1)
split' left left
  swap i j b = do
a - readArray arr i
writeArray arr i b
writeArray arr j a
 
 2. Prime
 
  testPrime' n verbose = do
arr - newArray (0, n) True :: IO (IOUArray Int Bool)
primeM' arr n
waitForChildren
if verbose
  then getElems arr = putStrLn . show . map fst . filter snd . zip 
 [0..]
  else return ()
 
  primeM' arr n = do
let p = truncate $ sqrt (fromIntegral n) + 1
remove i = if i  p then return () else do
  spawnRemover (i + 1)
  remove' (i + i)
 where
  remove' j = if j  n then return () else do
writeArray arr j False
remove' (j + i)
  spawnRemover j = if j  n then return () else do
t - readArray arr j
if t then forkChild (remove j) else spawnRemover (j + 1)
remove 2
 
 Manage thread termination
 
  children :: MVar [MVar ()]
  children = unsafePerformIO (newMVar [])
 
  waitForChildren :: IO ()
  waitForChildren = do
cs - takeMVar children
case cs of
  []   - putMVar children cs
  m:ms - do
putMVar children ms
takeMVar m
waitForChildren
 
  forkChild :: IO () - IO ()
  forkChild io = do
mvar - newEmptyMVar
childs - takeMVar children
putMVar children (mvar:childs)
forkIO (io `finally` putMVar mvar ())
return ()
 
 ___
 Haskell-Cafe mailing 

[Haskell-cafe] Too many packages on hackage? :-)

2007-07-07 Thread Donald Bruce Stewart
Hackage hackers,

Looks like there's too many packages on hackage.haskell.org now for a
single page listing:

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

Perhaps we can have a page with just the categories, with subpages
hanging off?

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