Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Tomasz Zielonka
On Mon, May 28, 2007 at 11:43:47AM +0100, Andrew Coppin wrote:
 - Chapter 2 is... puzzling. Personally I've never seen the point of 
 trying to check a program against a specification. If you find a 
 mismatch then which thing is wrong - the program, or the spec?

Knowing that one of them is wrong is already a very useful information,
don't you think?

 - Chapter 12 is incomprehensible (to me at least). Fun with Phantom 
 Types I've read it several times, and I still couldn't tell you what a 
 phantom type is...

Ironically, this chapter contains the following (at least the version
at http://www.informatik.uni-bonn.de/~ralf/publications/With.pdf):

 Of course, whenever you add a new feature to a language, you should
 throw out an existing one (especially if the language at hand is
 named after a logician). Now, for this chapter we abandon type
 classes - judge for yourself how well we get along without
 Haskell's most beloved feature.

You've found a language extension soulmate! ;-)

BTW, I really liked Ralf's chapter.

 There are some bits that are sort-of interesting but not really to do
 with anything I'm passionate about, and then there are bits that I
 can't comprehend...

Passionate... perhaps this is the root of the problem? Different people
are passionate about different things.

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


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

2007-05-29 Thread kahl
  
  P.S. Have some cute code:
  
  Control.Monad.Fix.fix ((1:) . scanl (+) 1)


Cute!

But what an un-cute qualified name:

:t Control.Monad.Fix.fix
Control.Monad.Fix.fix :: (a - a) - a


Has nothing to do with monads,
and would perhaps be considered as ``out of Control'' in any case...

;-)


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


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

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

I see it has moved into Data.Function,

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

A much better place.

-- Don

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


RE: [Haskell-cafe] Yet another top-level state proposal

2007-05-29 Thread Simon Peyton-Jones
At the risk of becoming repetitious, let's keep refining the Wiki to give these 
competing proposals in their most up-to-date form.  I'm not arguing against 
email -- it's an excellent medium for discussion -- but having the outcomes 
recorded makes them accessible to a much wider audience who have not followed 
the detailed discussion.

Simon

| -Original Message-
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Judah
| Jacobson
| Sent: 28 May 2007 19:50
| To: Adrian Hey
| Cc: haskell-cafe@haskell.org
| Subject: Re: [Haskell-cafe] Yet another top-level state proposal
|
| On 5/26/07, Adrian Hey [EMAIL PROTECTED] wrote:
| 
|  Judah Jacobson wrote:
|   In contrast to recent proposals, this one requires no extra syntax or
|   use of unsafe functions by the programmer.
| 
|  I'm not aware of any proposals (recent or ancient:-) that require the
|  use of unsafe functions by the programmer (well apart from the
|  unsafePerformIO hack itself).
|
| I was referring to the proposal to make that hack somewhat safer by
| adding a NO_INLINE_OR_CSE pragma.
|
|  Also adding extra syntax is no problem
|  these days. It's trivially simple (and indeed desirable in this case
|  IMHO). It's the underlying compiler magic requires significant extra
|  work I think.
|
| Reading last week's conversation on the topic, I got the impression
| that the debate is still ongoing with respect to that point.  Although
| this proposal is a little less aesthetic than those for mdo or ACIO, I
| think the fact that it touches so few parts of the language might make
| some people more comfortable with it.  In particular, an
| implementation only needs to:
|
| - add the OnceInit/OnceIO class declarations (trivial)
| - add the OnceIO deriving clause logic (in GHC, this would be
| isolated to one module)
| - add a NO_CSE pragma at the Core syntax level. (already suggested for
| other conservative proposals).
|
| But whether that's being *too* conservative is a matter of opinion, of course.
|
|   
|   Under this proposal, we would write instead:
|   
|   newtype UniqueRef = UniqueRef (IORef Integer)
|  deriving OnceIO
|  
|   instance OnceInit UniqueRef where
|  onceInit = liftM UniqueRef (newIORef 0)
| 
|  A purely aesthetic objection, but to me it looks quite obfuscated
|  compared to:
| 
|  uniqueRef :: IORef Integer
|  uniqueRef - ACIO.newIORef 0
| 
|  But I guess perhaps what's going on here could be made clearer with
|  the right syntactic sugar :-)
|
| If you're going to use syntactic sugar anyway, I think that negates
| the main appeal of this proposal.  Instead, we could ignore deriving
| clauses altogether, and add an optional keyword oneshot to type
| declarations, e.g.:
|
| oneshot uniqueRef :: IO (IORef Integer)
| uniqueRef = newIORef 0
|
| Now that I mention it, that idea's not too bad either...
|
|  Finally, the useage problem I mentioned. Having to create a distinct
|  type for each top level thing with identity (my terminology)
|  seems like it could cause difficulties (probably not insoluble
|  problems though).
|
| My feeling is that most programs would use few enough TWIs that having
| to declare extra types would not be a big hastle.  But I see you're
| challenging that point below:
|
|  If you look at the wiki page you'll see the device driver example I
|  put there. This has two device handles at the top level (both same
|  type), with a device driver API that takes either the device handle
|  itself or a device session handle (which will contain the corresponding
|  device handle) as parameters (so in principle it can be used with any
|  number of devices provided the corresponding device handles are
|  available).
| 
|  My question is, what would this example look like using the solution
|  you propose? I can think of at least two possibilities, both of which
|  seem quite awkward. But I'll leave it to you to think about this
|  with a bit more care than perhaps I have. It'd be nice to see the
|  solution on the Wiki too.
| 
|
| If you want several different devices, you could wrap them all in one
| large type:
|
| data DeviceHandle = ...
| createDeviceHandle :: BaseAddress - IO DeviceHandle
|
| data AllHandles = AllHandles {handle1, handle2 :: DeviceHandle} deriving 
OnceIO
|
| instance OnceInit AllHandles where
| onceInit = liftM2 AllHandles
|  (createDeviceHandle baseAddress1)
|  (createDeviceHandle baseAddress2)
|
| device1, device2 :: IO DeviceHandle
| device1 = liftM handle1 runOnce
| device2 = liftM handle2 runOnce
|
| This proposal does seem to encourage consolidating TWIs into one part
| of the program; from a design perspective, that may not be entirely a
| bad thing.
|
| Best,
| -Judah
| ___
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| 

[Haskell-cafe] data PLZ a

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

data PLZ a = AWSUM_THX a | O_NOES String

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

Thanks to mauke on #haskell.

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


Re: [Haskell-cafe] data PLZ a

2007-05-29 Thread Dan Mead

is that your implementation of LOLCODE?

:P

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


We got the names wrong!

data PLZ a = AWSUM_THX a | O_NOES String

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

Thanks to mauke on #haskell.

-- Don
___
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] data PLZ a

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

  data PLZ a = AWSUM_THX a | O_NOES String

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

  Thanks to mauke on #haskell.
  -- Don

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

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


Re: [Haskell-cafe] Re: Slower with ByteStrings?

2007-05-29 Thread Mirko Rahn



from the letters of that word.  A letter can be used at most as many
times as it appears in the input word.  So, letter can only match
words with 0, 1, or 2 t's in them.



   frequencies = map (\x - (head x, length x)) . group . sort
   superset xs = \ys - let y = frequencies ys in
length y == lx 
and (zipWith (\(c,i) (d,j) - c == d  i = j) x y)
  where
  x  = frequencies xs
  lx = length x


As far as I understand the spec, this algorithm is not correct:

superset ubuntu tun == False

Is at least one 'b' necessary, yes or no? If the answer is no, the 
following algorithm solves the problem and is faster then the one above:


del y = del_acc []
where del_acc _ []  = mzero
  del_acc v (x:xs) | x == y = return (v++xs)
  del_acc v (x:xs)  = del_acc (x:v) xs

super u = not . null . foldM (flip del) u

main = interact $ unlines . filter (ubuntu `super`) . lines

BR,

--
-- Mirko Rahn -- Tel +49-721 608 7504 --
--- http://liinwww.ira.uka.de/~rahn/ ---
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-05-29 Thread Vincent Kraeutler
Donald Bruce Stewart wrote:
 P.S. Have some cute code:

 Control.Monad.Fix.fix ((1:) . scanl (+) 1)
   

this is cute indeed! (do you keep an emergency reserve of those around
for situations like this? ;-))

ever the interested amateur, i admittedly remain stumped by fix (there's
evidence i'm not the only one [1]), though a little digging turned up
two very nice links, which might be interesting for those who share my
situation (hence this post). namely, an old LtU thread [2], in which you
will find a short oleg-post [3] (i'd give it about a hundred
milli-olegs), and a paper on practical applications of Y [4]. it seems
that the examples given in the latter two (scheme and ML) are
essentially trivial to translate to haskell, so with the help of ghci, i
suppose i will finally get a grip on Y. ;-)

either way, if one of the Masters Of The Shadow Y Style on this list
feels like throwing in another koan or two, you'll have at least one
thankful audience member ;-)

kind regards,
v.

[1] http://www.haskell.org/pipermail/haskell-cafe/2007-March/023662.html
[2] http://lambda-the-ultimate.org/classic/message5463.html
[3] http://okmij.org/ftp/Computation/overriding-selfapplication.html
[4] http://citeseer.ist.psu.edu/mcadams01practical.html



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


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

2007-05-29 Thread David House

On 29/05/07, Daniel McAllansmith [EMAIL PROTECTED] wrote:

Just in case there was some sort of miscommunication, the actual answer to
your question is (/=) :: a - a - Bool, as Neil said.


Almost, (/=) :: Eq a = a - a.

(Just for completeness.)

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-05-29 Thread Antti-Juhani Kaijanaho
On Tue, May 29, 2007 at 11:20:27AM +0100, David House wrote:
 Almost, (/=) :: Eq a = a - a.

Well, not quite :)  You forgot - Bool at the end :)

 (Just for completeness.)

Exactly :)

-- 
Antti-Juhani Kaijanaho, Jyväskylä
http://antti-juhani.kaijanaho.fi/newblog/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-29 Thread Henning Thielemann

Hi Andrew!

I share your concerns about the simplicity of the language. Once
extensions exists, they are used widely, and readers of programs must
understand them, also if the extensions are used without need. I
understand the motivations for many type extensions, but library writers
tend to use language extensions instead of thinking hard how to avoid
them. At least people should separate advanced code from simple one.
  http://www.haskell.org/haskellwiki/Use_of_language_extensions
 Indeed the State monad and State monad transformer are quite simple and
fit very well into Haskell 98. The langaguage extension is only needed
because there shall be class methods like 'get' and 'put' that can be used
without modification on both the State monad and its transformer variant.
It would be easy to separate the concrete types State and StateT from the
class MonadState, but this has not been done.
 I wish the compilers would allow more fine grained switches on languages
extensions. -fglasgow-exts switches them all on, but in most cases I'm
interested only in one. Then typing errors or design flaws (like 'type
Synonym = Type', instead of wanted 'type Synonym a = Type a'; extended
instance declarations) are accepted without warnings.



On Sun, 27 May 2007, Andrew Coppin wrote:

  Keep in mind also that many of these extensions are part of Haskell
  Prime, which last I checked is supposed to become official sometime
  later this year.

 This worries me greatly. I'm really afraid that Haskell will go from
 being this wonderful, simple language that you can explain in a page or
 two of text to being this incomprehensible mass of complex type
 machinery that I and most other human beings will never be able to learn
 or use. :-(

I hope that compilers will have a Prime switch in order to distinguish
Haskell 98 programs from Haskell' ones. This way I could reliably test,
whether my programs use simple or advanced language features.


Let me cite from the book
  Programming in Modula-3: An Introduction in Programming with Style,
  Conclusion / Why programming?, page 425:
 In a lecture in March 1995 at the University of Klagenfurt, Niklaus
Wirth analyzed the phenomenon of software chaos. He challenged that the
ever rising complexity of software is not necessary, and indeed that it is
bound to the loss of certain engineering qualities, such as an
appreciation of efficiency and simplicity.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-05-29 Thread David House

On 29/05/07, Antti-Juhani Kaijanaho [EMAIL PROTECTED] wrote:

Well, not quite :)  You forgot - Bool at the end :)


Ha! Sorry, what a lovely ironic typo. :)

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-05-29 Thread Tomasz Zielonka
On Tue, May 29, 2007 at 11:20:27AM +0100, David House wrote:
 On 29/05/07, Daniel McAllansmith [EMAIL PROTECTED] wrote:
 Just in case there was some sort of miscommunication, the actual answer to
 your question is (/=) :: a - a - Bool, as Neil said.
 
 Almost, (/=) :: Eq a = a - a.

Almost again!

(/=) :: Eq a = a - a - Bool

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


Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Henning Thielemann

On Sun, 27 May 2007, Andrew Coppin wrote:

 Personally, I try to avoid ever using list comprehensions.

Me too. Successfully, I have to add.

 But every now and then I discover an expression which is apparently not
 expressible without them - which is odd, considering they're only
 sugar...

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


Re: [Haskell-cafe] Distributing a program with support files

2007-05-29 Thread Neil Mitchell

Hi Isaac


Why?  If it's a binary package, the IO will return the compiled-in path,
which on the same distribution/whatever, should be the correct path.  In
particular, on Windows, I assume that the IO returns something that is
in fact relative to the current position of the executable at the time
of its running (am I wrong?)


Yhc has cross-platform bytecode. Thats pretty useless if people are
going to have to recompile anyway...

On Windows the path is relative to the current binary, but not
relative in a good way - in practice if you haven't installed it in
C:\Program Files a precompiled binary isn't going to work.

Thanks

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


Re: [Haskell-cafe] Yet another top-level state proposal

2007-05-29 Thread Claus Reinke



At the risk of becoming repetitious, let's keep refining the Wiki to
give these competing proposals in their most up-to-date form.  I'm not
arguing against email -- it's an excellent medium for discussion -- but
having the outcomes recorded makes them accessible to a much wider
audience who have not followed the detailed discussion.


i would have preferred some discussion here first, but to keep 
it from getting lost, i've now added my own proposal (different
thread, in case you're wondering;) to 


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

as '5 Proposal 4: Shared on-demand IO actions (oneShots)'.

claus

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


Re: [Haskell-cafe] Mysterious monads

2007-05-29 Thread Henning Thielemann

On Sun, 27 May 2007, Andrew Coppin wrote:

 such that a Reader is created with an initial list, and the read
 function fetches 1 element out of that list. That is, the expression x
 - read will take the head element of the list and put it into x,
 keeping the tail to be read later.

 (Oh yeah - and apparently that clashes with Prelude.read. Oh well!)

 I can't figure out how to implement this... The closest I managed was to
 make a Reader object also contain a function that tells (=) what to do
 to the Reader object you're binding against... But that seems to be
 horribly buggy.

Confusingly MonadReader and MonadWriter in the Monad Template Library are
not quite counterparts. Reader does not consume its input, Writer does not
overwrite its output.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-05-29 Thread Tomasz Zielonka
On Tue, May 29, 2007 at 12:15:23PM +0200, Vincent Kraeutler wrote:
 Donald Bruce Stewart wrote:
  P.S. Have some cute code:
 
  Control.Monad.Fix.fix ((1:) . scanl (+) 1)
 
 this is cute indeed! (do you keep an emergency reserve of those around
 for situations like this? ;-))
 
 ever the interested amateur, i admittedly remain stumped by fix (there's
 evidence i'm not the only one [1])

The above code is equivalent to

let l = 1 : scanl (+) 1 l in l

which is a bit easier to decipher.

The rest is maths and the subtleties of lazy evaluation.

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


Re: [Haskell-cafe] data PLZ a

2007-05-29 Thread ajb
G'day all.

Quoting Dan Mead [EMAIL PROTECTED]:

 is that your implementation of LOLCODE?

O HAI IM IN UR CODE





REDUCIN' UR REDEKZEZ
BURNIN' UR MEGAHURTZ

Cheers,
Andrew Bromage

P.S. This is harder than writing l33t.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Cabal can't install in home directory

2007-05-29 Thread Grzegorz
Hi,

It seems that if GHC is installed non-user-writable directory, and you want to
install a package in the home directory (using runghc Setup configure
--prefix=$HOME) this isn't possible: when running runghc Setup install you
get an error like this: 
Unable to rename /usr/lib/ghc-6.6.1/package.conf to
/usr/lib/ghc-6.6.1/package.conf.old
Saving old package config file... ghc-pkg.bin: /usr/lib/ghc-6.6.1/package.conf:
renameFile: permission denied (Permission denied)

Shouldn't that be fixed?

Best,
--
Grzegorz


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


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

2007-05-29 Thread Tomasz Zielonka
On Tue, May 29, 2007 at 02:19:31PM +0200, Tomasz Zielonka wrote:
 On Tue, May 29, 2007 at 12:15:23PM +0200, Vincent Kraeutler wrote:
  ever the interested amateur, i admittedly remain stumped by fix (there's
  evidence i'm not the only one [1])
 
 The above code is equivalent to
 
 let l = 1 : scanl (+) 1 l in l
 
 which is a bit easier to decipher.
 
 The rest is maths and the subtleties of lazy evaluation.
... and these are the things you need to focus on to understand this
code. In this case the use of fix is almost a small syntactic issue -
you can eliminate it by inlining its definition.

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


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

2007-05-29 Thread Jules Bean

Doug Kirk wrote:

No offense to the darcs creators, but

1) Only current Haskellers use it; everyone else either uses
Subversion or is migrating to it;



If that is true, then they have missed the point. DVC is a real win for 
most workflows.


The applicable alternatives to darcs are : bzr, git, mercurial, tla. 
They have different pros and cons which are discussed at length on 
various blogs.


svn just doesn't make the list; it's not a comparable project, because 
it's centralised. SVK is more plausible but since it is essentially a 
hack to implement decentralisation on top of centralisation, it has 
different design constraints than things designed from the bottom-up as 
decentralised.


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


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

2007-05-29 Thread Vincent Kraeutler
Tomasz Zielonka wrote:
 On Tue, May 29, 2007 at 02:19:31PM +0200, Tomasz Zielonka wrote:
   
 On Tue, May 29, 2007 at 12:15:23PM +0200, Vincent Kraeutler wrote:
 
 ever the interested amateur, i admittedly remain stumped by fix (there's
 evidence i'm not the only one [1])
   
 The above code is equivalent to

 let l = 1 : scanl (+) 1 l in l

 which is a bit easier to decipher.

 The rest is maths and the subtleties of lazy evaluation.
 
 ... and these are the things you need to focus on to understand this
 code. In this case the use of fix is almost a small syntactic issue -
 you can eliminate it by inlining its definition.

 Best regards
 Tomek


   
i see that the definition of fix (from Control.Monad.Fix) could not be
any simpler:

 fix f = let x = f x in x

same goes for the type:

Prelude :t Control.Monad.Fix.fix
Control.Monad.Fix.fix :: (a - a) - a

it's just that i find it difficult to get concrete intellectual mileage
out of it.
i can reproduce results for specific examples (and even manipulate them
a bit), but feel like i'm missing something deep yet simple. say, i
would not know where and how to apply it. so obviously true
understanding is still missing. reminds me of my first encounters with
$H \psi = E \psi$. ;-)

most likely, i should just more carefully read the references i cited
myself ;-)

anyhow. if someone has a pedestrian's guide to the fixed point
operator lying around, a link would be much appreciated.

kind regards,
v.



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


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

2007-05-29 Thread Hakim Cassimally

On 29/05/07, Jules Bean [EMAIL PROTECTED] wrote:

Doug Kirk wrote:
 No offense to the darcs creators, but

 1) Only current Haskellers use it; everyone else either uses
 Subversion or is migrating to it;


If that is true, then they have missed the point. DVC is a real win for
most workflows.

The applicable alternatives to darcs are : bzr, git, mercurial, tla.
They have different pros and cons which are discussed at length on
various blogs.

svn just doesn't make the list; it's not a comparable project, because
it's centralised. SVK is more plausible but since it is essentially a
hack to implement decentralisation on top of centralisation, it has
different design constraints than things designed from the bottom-up as
decentralised.


How do the differing design constraints make svk not comparable?
As far as I understood it, it's a decentralised version control system
that happens to layer over a very popular existing system, and which
therefore gets some of its goodies like working over http.

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


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

2007-05-29 Thread Vincent Kraeutler
Vincent Kraeutler wrote:
 Tomasz Zielonka wrote:
   
 [snip]

 anyhow. if someone has a pedestrian's guide to the fixed point
 operator lying around, a link would be much appreciated.

   

i see that dons has very recently provided an answer for this on reddit:

http://programming.reddit.com/info/1uabt/comments

eternally indebted,
v.



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


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

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

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

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

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

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

TMTOWTDI with recursion :-)

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


Re: [Haskell-cafe] Cabal can't install in home directory

2007-05-29 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Grzegorz wrote:
 Hi,
 
 It seems that if GHC is installed non-user-writable directory, and you want to
 install a package in the home directory (using runghc Setup configure
 --prefix=$HOME) this isn't possible: when running runghc Setup install you
 get an error like this: 
 Unable to rename /usr/lib/ghc-6.6.1/package.conf to
 /usr/lib/ghc-6.6.1/package.conf.old
 Saving old package config file... ghc-pkg.bin: 
 /usr/lib/ghc-6.6.1/package.conf:
 renameFile: permission denied (Permission denied)
 
 Shouldn't that be fixed?

You don't have permission to install it in a way that all users of that
GHC will then be able to use it.  You should pass --user to runghc
Setup install for your desired effect.  (whereas I shouldn't because my
GHC itself is also compiled by my user and in my home directory - which
confused me once upon a time)

Isaac
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGXC1gHgcxvIWYTTURArjxAJ0YLb94o4DAif8TuEqWpuhj8M5juQCgjkkE
aOZl3x/6h5r0bHvD2hEvccs=
=IqgU
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-05-29 Thread David House

On 29/05/07, Vincent Kraeutler [EMAIL PROTECTED] wrote:

anyhow. if someone has a pedestrian's guide to the fixed point
operator lying around, a link would be much appreciated.


Here's a paraphrased quotation from Pierce's Types and Programming Languages:

Suppose we want to write a recursive function definition of the form h
= (body containing h) -- i.e., we want to write a definition where the
term on the right-hand side of the = uses the very function that we
are defining. The intention is that the recursive definition should be
unrolled at the point where it occurs; for example, the definition
of factorial would intuitively be

if n=0 then 1
else n * (if n-1=0 then 1
 else (n-1) * (if n-2=0 then 1
   else (n-2) * ...))

This affect can be achieved using the fix combinator by first defining
g = \f. (body containing f) and then h = fix g. For example, we can
define the factorial function be

g = \fct n. if n == 0 then 1 else n * (fct (n-1))
factorial = fix g

Figure 5-2 shows what happens to the term factorial 3 during evaluation:

factorial 3
fix g 3
g (fix g) 3   --  Using fix f = f (fix f)
if 3 == 0 then 1 else 3 * (fix g 2)  -- Using the definition of g
3 * (fix g 2)
3 * (g (fix g) 2)
3 * (if 2 == 0 then 1 else 2 * (fix g 1))
3 * (2 * (fix g 1))
3 * (2 * (g (fix g) 1))
3 * (2 * (if 1 == 0 then 1 else 1 * (fix g 0)))
3 * (2 * (1 * (fix g 0))
3 * (2 * (1 * (g (fix g) 0)))
3 * (2 * (1 * (if 0 == 0 then 1 else 0 * (fix g -1
3 * (2 * (1 * 1)))
6

The key fact that makes this calculation work is that fix g n
evaluates to g (fix g) n. That is, fix g is a kind of
self-replicator that, when applied to an argument, supplies _itself_
and n as arguments to g. Wherever the first argument appears in the
body of g, we will get another copy of fix g, which, when applied to
an argument, will again pass itself and that argument to g, etc. Each
time we make a recursive call using fix g, we unroll one more copy of
the body of g and equip it with new copies of fix g that are ready to
do the unrolling again.

(Adapted from pp59-60, Types and Programming Languages, Benjamin C. Pierce.)

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Frisby grammars that have context

2007-05-29 Thread Mark T.B. Carroll
I've been playing with Text.Parsers.Frisby to see how it stacks against
other options and, while it's been great so far, I am finding that I
can't encode a grammar where what's acceptable depends on what's already
been parsed in some nontrivial way. To take a simple example, imagine a
grammar where the only lower-case letters that are acceptable are those
where their upper-case equivalent occurred earlier in the text.

In Parsec I'd code this sort of thing as,

nextChar =
do allowed - getState
   char - oneOf $ ['A'..'Z'] ++ allowed
   updateState (union [toLower char])
   return char

test = runParser (many1 nextChar) [] 

Is this supposed to not be possible in Frisby, or (quite likely) am I
missing something that allows me to? I've thought about things like
trying to fmap further calls to apply runPeg to rest, but I've not
figured out a trick that will actually work.

-- Mark

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


[Haskell-cafe] Re: Slower with ByteStrings?

2007-05-29 Thread apfelmus
Mirko Rahn wrote:
 from the letters of that word.  A letter can be used at most as many
 times as it appears in the input word.  So, letter can only match
 words with 0, 1, or 2 t's in them.
 
frequencies = map (\x - (head x, length x)) . group . sort
superset xs = \ys - let y = frequencies ys in
 length y == lx 
 and (zipWith (\(c,i) (d,j) - c == d  i = j) x y)
   where
   x  = frequencies xs
   lx = length x
 
 As far as I understand the spec, this algorithm is not correct:
 
 superset ubuntu tun == False
 
 Is at least one 'b' necessary, yes or no?

Oops, you are indeed right, the answer should be no. I thought I'd
came away without primitive recursion, but here's a correct version

  superset xs = superset' x . sort ys
where
x = sort xs

_  `superset`  [] = True
[] `superset`  _  = False
(x:xs) `superset'` (y:ys)
| x == y= xs `superset` ys
| x   y= xs `superset` (y:ys)
| otherwise = False

 If the answer is no, the
 following algorithm solves the problem and is faster then the one above:
 
 del y = del_acc []
 where del_acc _ []  = mzero
   del_acc v (x:xs) | x == y = return (v++xs)
   del_acc v (x:xs)  = del_acc (x:v) xs
 
 super u = not . null . foldM (flip del) u
 
 main = interact $ unlines . filter (ubuntu `super`) . lines

The algorithm is correct but it's not faster, xs `super` ys  takes
O(n*m) time whereas superset takes O(n * log n + m * log m) time given a
proper sorting algorithm. Here, n = length xs and m = length ys.

Actually, both algorithms are essentially the same except for the
sorting that allows to drop some equality tests.

(Note that memoizing x = sort xs over different ys speeds things up a
bit for the intended application. This way, (sort ubuntu) is only
computed once and the running time over many ys approaches O(n + m*log m).)

Regards,
apfelmus

PS: Some exercises for the interested reader:
1) Still, the algorithm super has an advantage over superset. Which one?
2) Put xs into a good data structure and achieve a O(m * log n) time for
multiple ys.
3) Is this running time always better than the aforementioned O(n +
m*log m)? What about very large m  n?

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


Re: [Haskell-cafe] Frisby grammars that have context

2007-05-29 Thread Mark T.B. Carroll
Actually, while I'm at it, another thing I was wondering:

Text.ParserCombinators.Parsec.Char offers us nice things like `lower'.
However, where's this stuff in Frisby? I could use something horrific
like oneOf [filter isLower [minBound .. maxBound ]] or something, but
how best to get internationalisation-aware character classes into it I'm
not sure.

-- Mark

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


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

2007-05-29 Thread Jon Fairbairn
Vincent Kraeutler [EMAIL PROTECTED] writes:
 anyhow. if someone has a pedestrian's guide to the fixed point
 operator lying around, a link would be much appreciated.

At the risk of increasing rather than decreasing your
confusion (but in the hope that once you get over it you
will be enlightened), here's another approach to the
subject:

Suppose we have a language (either untyped or cleverly typed
-- the following won't typecheck in Haskell, but there are
ways around it) that allows non-recursive definitions
only. We want to define factorial, but it needs to call
itself.  How about we try to define a function that /when
applied to itself/ is factorial?

 half_fact me n = 
if n = 1
then 1
else n * ? (n-1)
   ^
   |
what goes here? Well, we know that we are trying to arrange
that

 half_fact half_fact == factorial

so when we use it, the me parameter is going to be
half_fact, which implies that (me me) will be (half_fact
half_fact), which is factorial.  So we write:

 half_fact me n = 
if n = 1
then 1
else n * me me (n-1)

 factorial = half_fact half_fact

Now, in such a language we might write all our recursive
functions that way, or we might prefer not to have to double
up the names to get recursion, and abstract away the
operator that ties the knot: define a function that, given
the factorial function makes a step of the evaluation and
then lets factorial do the rest:

 step_towards_factorial factorial n =
if n =1 
then 1
else n * factorial (n-1)

put

 stf = step_towards_factorial

and observe that
 
stf (error too deep) 1 == 1
stf (stf (error too deep)) 2 == 2
stf (stf (stf (error too deep))) 3 == 6

fix just does that as many times as necessary, so we can
define

 factorial = fix step_towards_factorial

The connection between the half function approach and the
fix operator is this: we want fix f = (f (fix f)), which is
a recursive definition, so we can use the half function
technique to make it:

 half_fix me f = f (me me f)
 fix = half_fix half_fix



-- 
Jón Fairbairn [EMAIL PROTECTED]

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


[Haskell-cafe] Re: Cabal can't install in home directory

2007-05-29 Thread Grzegorz
Isaac Dupree isaacdupree at charter.net writes:

 
 You don't have permission to install it in a way that all users of that
 GHC will then be able to use it.  You should pass --user to runghc
 Setup install for your desired effect.  (whereas I shouldn't because my
 GHC itself is also compiled by my user and in my home directory - which
 confused me once upon a time)

OK makes sense. Thanks!

--
Grzegorz

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


[Haskell-cafe] Re: Frisby grammars that have context

2007-05-29 Thread apfelmus
Mark T.B. Carroll wrote:
 I've been playing with Text.Parsers.Frisby to see how it stacks against
 other options and, while it's been great so far, I am finding that I
 can't encode a grammar where what's acceptable depends on what's already
 been parsed in some nontrivial way.
 [...]
 Is this supposed to not be possible in Frisby, or (quite likely) am I
 missing something that allows me to?

It's intentionally impossible. Frisby uses a dynamic programming
approach that crucially depends on the fact that the grammar in question
is context-free (actually something related, but the effect is the
same). You're trying to parse a context-sensitive language.

Sometimes, you can avoid context-sensitivity if there's a way to parse
the token in question regardless of whether it's valid. For example,
Pascal is a context-sensitive language because you may not use a
variable before it has been declared:

  procedure Foo(x:Integer)
  begin
y := 1;
  end;

This not a correct Pascal program, nevertheless the parse succeeds just
fine. The missing declaration for y will be detected when processing the
abstract syntax tree further. The key point is that the shape of the
abstract syntax tree doesn't depend on whether y is declared or not.

Regards,
apfelmus

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


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

2007-05-29 Thread Bayley, Alistair
 From: [EMAIL PROTECTED] 
 [mailto:[EMAIL PROTECTED] On Behalf Of 
 Vincent Kraeutler
 
 anyhow. if someone has a pedestrian's guide to the fixed point
 operator lying around, a link would be much appreciated.

Just to add to the noise... I've always quite liked Richard Gabriel's
The Why of Y essay:
  http://www.dreamsongs.com/Files/WhyOfY.pdf

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


RE: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-29 Thread Simon Peyton-Jones
|  I wish the compilers would allow more fine grained switches on languages
| extensions. -fglasgow-exts switches them all on, but in most cases I'm
| interested only in one. Then typing errors or design flaws (like 'type
| Synonym = Type', instead of wanted 'type Synonym a = Type a'; extended
| instance declarations) are accepted without warnings.

Yes, we have an open Trac feature request for exactly this.  We keep not doing 
it for lack of bandwidth. Does anyone feel like taking it on?

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


Re: [Haskell-cafe] Re: Frisby grammars that have context

2007-05-29 Thread Mark T.B. Carroll
apfelmus [EMAIL PROTECTED] writes:
(snip)
 It's intentionally impossible. Frisby uses a dynamic programming
 approach that crucially depends on the fact that the grammar in question
 is context-free (actually something related, but the effect is the
 same). You're trying to parse a context-sensitive language.

Aha, thanks, that makes sense: I am glad that for once I wasn't missing
the obvious after all. Presumably this restriction allows it to gain
other benefits. I hadn't realised that the different implementations of
Frisby and Parsec had such far-reaching consequences.

(snip)
 This not a correct Pascal program, nevertheless the parse succeeds just
 fine. The missing declaration for y will be detected when processing the
 abstract syntax tree further. The key point is that the shape of the
 abstract syntax tree doesn't depend on whether y is declared or not.

M, indeed it was a missing-declaration sort of problem I had in
mind. Thanks for the example.

-- Mark

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


[Haskell-cafe] Re: Frisby grammars that have context

2007-05-29 Thread apfelmus
Mark T.B. Carroll wrote:
 apfelmus [EMAIL PROTECTED] writes:
 (snip)
 This not a correct Pascal program, nevertheless the parse succeeds just
 fine. The missing declaration for y will be detected when processing the
 abstract syntax tree further. The key point is that the shape of the
 abstract syntax tree doesn't depend on whether y is declared or not.
 
 M, indeed it was a missing-declaration sort of problem I had in
 mind. Thanks for the example.

(I'm not sure whether I've been clear: this probably allows you to use a
context-free grammar. I wanted to say that the language of all valid
Pascal programs is context-sensitive but that you can parse it with a
context-free grammar and decide semantic validity later on.)

Regards,
apfelmus

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


Re: [Haskell-cafe] Re: Slower with ByteStrings?

2007-05-29 Thread Mirko Rahn


[fixed some typos, mainly missing primes]


  superset xs = superset' x . sort
where
x = sort xs

_  `superset'`  [] = True
[] `superset'`  _  = False
(x:xs) `superset'` (y:ys)
| x == y= xs `superset'` ys
| x   y= xs `superset'` (y:ys)
| otherwise = False



del y = del_acc []
   where del_acc _ []  = mzero
 del_acc v (x:xs) | x == y = return (v++xs)
 del_acc v (x:xs)  = del_acc (x:v) xs



The algorithm is correct but it's not faster, xs `super` ys  takes
O(n*m) time whereas superset takes O(n * log n + m * log m) time given a
proper sorting algorithm. Here, n = length xs and m = length ys.


Of course, you are right. In worst case super is much slower than 
superset. In average case (for some assumptions about the inputs) it 
could perform quite well because of the chance to detect non-subset 
words early.



2) Put xs into a good data structure and achieve a O(m * log n) time for
multiple ys.


You mean something along

supermap xs =
let mx  = Map.fromListWith (+) [ (x,1) | x - xs ]
ins _ 1 = Nothing
ins _ v = Just (v-1)
upd m y = case Map.updateLookupWithKey ins y m of
   (Nothing,_ ) - mzero
   (_  ,m') - return m'
in not . null . foldM upd mx

Thanks for your time,

BR,

--
-- Mirko Rahn -- Tel +49-721 608 7504 --
--- http://liinwww.ira.uka.de/~rahn/ ---
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Frisby grammars that have context

2007-05-29 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

apfelmus wrote:
 Mark T.B. Carroll wrote:
 I've been playing with Text.Parsers.Frisby to see how it stacks against
 other options and, while it's been great so far, I am finding that I
 can't encode a grammar where what's acceptable depends on what's already
 been parsed in some nontrivial way.
 [...]
 Is this supposed to not be possible in Frisby, or (quite likely) am I
 missing something that allows me to?
 
 It's intentionally impossible. Frisby uses a dynamic programming
 approach that crucially depends on the fact that the grammar in question
 is context-free (actually something related, but the effect is the
 same).

Is that dependence crucial? What if it gained Monad operations that just
weren't intended to be used very often, and maybe locally harmed
performance a little where they are used?

BTW: (P s) should be an instance of Applicative (which is already
possible with Frisby's current code, just not there) (I prefer the
aesthetics of Frisby-applicative code to many of the combinators it
provides - I tried it a little sometime, not enough to send a darcs patch)

Isaac
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGXFZVHgcxvIWYTTURApl+AKClt8J1m+qkEG+qNSI4RSATmZfSkACfdJN8
4gLKaM/hKS85UgMsERoItRM=
=dJx9
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-29 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Simon Peyton-Jones wrote:
 |  I wish the compilers would allow more fine grained switches on languages
 | extensions. -fglasgow-exts switches them all on, but in most cases I'm
 | interested only in one. Then typing errors or design flaws (like 'type
 | Synonym = Type', instead of wanted 'type Synonym a = Type a'; extended
 | instance declarations) are accepted without warnings.
 
 Yes, we have an open Trac feature request for exactly this.
 We keep not doing it for lack of bandwidth. Does anyone feel like taking it 
 on?

(not me in the immediate future, maybe later)

ticket # what?

I would think that preferable to inventing lots of compiler flags is
reusing some of the names from the LANGUAGE pragma, where practical.
(To some extent, this goes along with Cabal needing help, and the idea
of compilers offering a standard interface to it, I guess)

Isaac
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGXFeuHgcxvIWYTTURAscAAJ9pR57h5Gi/8cdSzNEAnClIJbwyiwCdGGE9
wRBJZf46GarajlroryJ7wMw=
=FVe+
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-05-29 Thread Roberto Zunino

(re-joining the list -- I forgot to reply all)

Vincent Kraeutler wrote:

Roberto Zunino wrote:

Vincent Kraeutler wrote:

i see that the definition of fix (from Control.Monad.Fix) could not be
any simpler:


fix f = let x = f x in x


I actually consider

fix f = f (fix f)

to be simpler. Alas, it breaks sharing...


;-)
sharing?
v.


The two functions

fix1 f = let x = f x in x
fix2 f = f (fix2 f)

have the same semantics. However I believe many implementations run them 
with different performance.


Consider

y = fix1 (2:)

This would be expanded to

y = let x = 2:x in x

A typical implementation would then represent the infinite list using 
(roughly) a circular pointer-list, i.e. x = cons(2, pointer-to-x) .
So, the tail of the list is shared with the list itself, causing a 
constant space to be allocated for the list, even if a large portion of 
the list is demanded as in (take 100 y).


On the contrary,

y = fix2 (2:)

would be

y = 2 : fix2 (2:)

and, unless some optimization magic kicks in, the representation for y 
is not a circular list. Each time a new list element is demanded, a new 
cons cell will be allocated. Running (take 1000 y) would then waste 
space for 1000 copies of 2. This is because the tail is not shared.


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


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

2007-05-29 Thread Bryan O'Sullivan

Jules Bean wrote:


No offense to the darcs creators, but

1) Only current Haskellers use it; everyone else either uses
Subversion or is migrating to it;


If that is true, then they have missed the point. DVC is a real win for 
most workflows.


We are indeed using darcs, so this discussion is a bit moot.

Regards,

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


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-29 Thread Ian Lynagh
On Tue, May 29, 2007 at 12:41:19PM -0400, Isaac Dupree wrote:
 Simon Peyton-Jones wrote:
  |  I wish the compilers would allow more fine grained switches on languages
  | extensions. -fglasgow-exts switches them all on, but in most cases I'm
  | interested only in one. Then typing errors or design flaws (like 'type
  | Synonym = Type', instead of wanted 'type Synonym a = Type a'; extended
  | instance declarations) are accepted without warnings.
  
  Yes, we have an open Trac feature request for exactly this.
 
 ticket # what?

http://hackage.haskell.org/trac/ghc/ticket/16

 I would think that preferable to inventing lots of compiler flags is
 reusing some of the names from the LANGUAGE pragma, where practical.

Agreed, as discussed in
http://www.haskell.org/pipermail/cabal-devel/2007-March/000460.html

I've also just added a note from an offline discussion that we should
use shorter names than I suggest in the above URL, and make them the
primary/only names.


Thanks
Ian

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


Re: [Haskell-cafe] shared oneShot IO (was top-level state proposals)

2007-05-29 Thread Dan Weston
I was wondering why, since IO is an instance of MonadFix [1], and 
therefore of ArrowLoop (Kleisli m), and since The loop operator 
expresses computations in which an output value is fed back as input, 
even though the computation occurs only once. [2], the MonadFix or 
ArrowLoop class (through use of mfix or loop, respectively) doesn't 
appear in anyone's suggestion, where the top-level state was the thing 
looped over.


Or is this more or less what is going on in the function

oneShot :: IO a - ACIO (IO a)
oneShot io = mdo mv - newMVar $ do a - io
let loop = do putMVar mv loop
  return a
loop
 return $ do act - takeMVar mv
 act

but without explicitly using the MonadFix or ArrowLoop classes?

Dan

[1] 
http://www.haskell.org/ghc/docs/6.4.1/html/libraries/base/Control-Monad-Fix.html
[2] 
http://www.haskell.org/ghc/docs/6.4.1/html/libraries/base/Control-Arrow.html


Claus Reinke wrote:


what we do not know is how to share IO actions themselves in a
demand-driven way, ie how to describe an IO action that is executed at
most once, only on demand, with shared result.



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


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

2007-05-29 Thread Doug Kirk

I didn't say there weren't others, simply that I didn't know of any
others (I don't just go looking for things online all the
time...having a real job really gets in the way of these things)! So I
wasn't really trying to disparage darcs. But here's another statistic:

http://www.google.com/search?rls=enq=darcs+inurl:_darcsie=UTF-8oe=UTF-8

Results 1 - 50 of about 54,100 for darcs inurl:_darcs. (0.38 seconds)

http://www.google.com/search?rls=enq=svn+inurl:svnie=UTF-8oe=UTF-8

Results 1 - 50 of about 995,000 for svn inurl:svn. (0.14 seconds)

That's 54,000 pages vs. 995,000 pages. That really was more my point.
(BTW, cvs is still [Results 1 - 50 of about 2,920,000 for cvs
inurl:cvs. (0.17 seconds)])

I *want* people (and companies) to move to Haskell; therefore, I want
to lower the entry price. The goal is to introduce a new language,
not a new SCM tool. You certainly wouldn't want to leave the
impression that one MUST use darcs in order to use Haskell!



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

On 26/05/07, Matthew Sackman [EMAIL PROTECTED] wrote:
(On the other hand, I don't know of anyone outside immediate
haskellers using Darcs.)

Good idea to get some data on this, instead of speculating. Let's do that.
A quick google reveals the Haskell crew is far from alone as users.

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

Here's the first 20 hits google finds:

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

Of which only 5/20 are Haskell repos.

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


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


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

2007-05-29 Thread Doug Kirk

OTOH, I work for companies, and they really value their assets,
especially software assets. So they *want* centralized stuff, so they
can ensure they have consistent backups (in the U.S.A. there is a lot
of regulation under Sarbanes-Oxley that requires this stuff). Right
now we're using ClearCase, which I abhor because it's so
heavyweight...but it is centralized control.

And as for the workflow, svn plugins are built in (as in free beer!) to:

-Xcode
-Eclipse
-TextMate
-Mac OS X (via DAV)
-HTML browser

and for

-Windows (if I really MUST use it)

via a download/install. So I can usually view, edit, and commit files
(or my favorite svn feature, a set of files atomically) from wherever
I happen to be working.


On 5/29/07, Jules Bean [EMAIL PROTECTED] wrote:

Doug Kirk wrote:
 No offense to the darcs creators, but

 1) Only current Haskellers use it; everyone else either uses
 Subversion or is migrating to it;


If that is true, then they have missed the point. DVC is a real win for
most workflows.

The applicable alternatives to darcs are : bzr, git, mercurial, tla.
They have different pros and cons which are discussed at length on
various blogs.

svn just doesn't make the list; it's not a comparable project, because
it's centralised. SVK is more plausible but since it is essentially a
hack to implement decentralisation on top of centralisation, it has
different design constraints than things designed from the bottom-up as
decentralised.

Jules


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


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-29 Thread Andrew Coppin

Claus Reinke wrote:


I'm thinking more about things like phantom types, rank-N 
polymorphism, functional dependencies, GADTs, etc etc etc that nobody 
actually understands.


this seems to be overly polymorphic in generalising over all types of
Haskell programmers, rather than admitting the existence of some types
of programmers who might have different values. qualifying such
generalisations by grouping types of programmers into classes with
different methods would seem a more Haskellish way, don't you think?-)

and although it isn't nice to typecast people, sometimes one only needs
to know the type, not the person, and sometime one needs even less
information, such as a property of a type or its relation to other
types. and especially if one is interested in relationships between
different types, it is helpful to know if one type of person in such a
relationship always occurs in combination with one and the same other
type. and if there are times when one might even generalise over
generalisations (although one doesn't like to generalise over so many
people all at once;-), there are other times when one might need to be
rather specific about which of several possible alternative types one is
putting together in a single construction.

there, does that cover everything in that list? sorry, couldn't
resist!-)


Hahahaha!

Thanks for a good laugh! I should print this out and *frame* it or 
something...



in exchange, below is a quick summary (didn't we have a
dictionary/quick-reference somewhere at haskell.org? i can't seem to 
find it right now, but if you know where it is, and it doesn't
already contain better explanations, feel free to add the text below - 
but check the draft for errors first, please;)


claus

--
phantom types:
 the types of ghost values (in other words, we are only interested in
 the type, not in any value of that type).


Mmm... Still not seeing a great amount of use for this one.


quantified types (forall/exist):
 an easy way to memorize this is to think of 'forall' as a big 'and'
 and of 'exists' as a big 'or'.
   e :: forall a. a  -- e has type 'Int' and type 'Bool' and type ..
   e :: exists a. a  -- e has type 'Int' or  type 'Bool' or  type ..


That doesn't entirely make sense. (What am I on about? That doesn't make 
*any* sense...)



rank-N polymorphism:
 in rank-1 polymorphism, type variables can only stand for monomorphic
 types (so, '($) :: (a-b) - a - b' can only apply monomorphic
 functions to their arguments, and polymorphic functions are not
 first-class citizens, as they cannot be passed as parameters without
 their types being instantiated). in rank-N (N1) polymorphism,
 type-variables can stand for rank-(N-1) polymorphic types (in other
 words, polymorphic functions can now be passed as parameters, and used
 polymorphically in the body of another function).

   f :: (forall a. [a]-Int) - ([c],[d]) - (Int,Int)
   f g (c,d) = (g c,g d)

   f length ([1..4],[True,False])


It's actually news to me that you can't do this already... (!)


functional dependencies:
 when using multi-parameter type classes, we specify relations between
 types (taken from the cartesian product of type class parameters).

 without additional measures, that tends to lead to ambiguities (some
 of the type class parameters can not be deduced unambiguously from the
 context, so no specific type class instance can be selected).

 functional dependencies are one such measure to reduce ambiguities,
 allowing us to specify that some subset A of type-class parameters
 functionally determines another subset B (so if we know the types of
 the parameters in subset A, there is only a single choice for the
 types of the parameters in subset B).


Functional dependancies kind of make sense. Personally I like the idea 
of associated types better, but never mind.



gadts:
 what really makes them different is that
 the explicit type signatures for the data constructors can give more
 specific return types for the data constructs, and such more specific
 types can be propagated through pattern matching


Finally, a definition of GADTs that actually makes some kind of sense...

(I find it highly unlikely I'll ever need these, but at least I have 
some idea now what they're supposed to do.)


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


Re: [Haskell-cafe] Mysterious monads

2007-05-29 Thread Andrew Coppin

Nicolas Frisby wrote:

Your intended behavior for Reader indicates stateful computational
features. The read later roughly expands to be read by some monadic
action on the rhs of a = as in

(read = \x - read {-this  is later-} = ...)

Recognizing the stateful nature gives you two options:

1) Implement yours as a restricted version of Control.Monad.State

   type ReaderAC = State
   readAC = get = \x - put (tail x)  return (head x)


I'll at least have a look at that...


2) or (as Isaac demonstrated) look to the definition of
Control.Monad.State.State for guidance own how to structure your
monad.


Ah yes. I just sat down to do this, and... oh look. There in the first 
few lines, a non-standard language extension that I don't understand.


...which neatly brings us back to the reason I'm trying to reimplement 
this by hand in the first place. ;-)


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


Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Andrew Coppin

Tomasz Zielonka wrote:

On Mon, May 28, 2007 at 11:43:47AM +0100, Andrew Coppin wrote:
  
- Chapter 2 is... puzzling. Personally I've never seen the point of 
trying to check a program against a specification. If you find a 
mismatch then which thing is wrong - the program, or the spec?



Knowing that one of them is wrong is already a very useful information,
don't you think?
  


My point is for most programs, trying to figure out exactly what you 
want the program to do is going to be much harder than implementing a 
program that does it.


Also, for most programs the spec is far more complicated (and hence 
prone to error) than the actual program, so...


- Chapter 12 is incomprehensible (to me at least). Fun with Phantom 
Types I've read it several times, and I still couldn't tell you what a 
phantom type is...



Ironically, this chapter contains the following (at least the version
at http://www.informatik.uni-bonn.de/~ralf/publications/With.pdf):

 Of course, whenever you add a new feature to a language, you should
 throw out an existing one (especially if the language at hand is
 named after a logician). Now, for this chapter we abandon type
 classes - judge for yourself how well we get along without
 Haskell's most beloved feature.

You've found a language extension soulmate! ;-)
  


It amazes me that anybody would think removing type classes is a good 
idea... but there we are. :-}



BTW, I really liked Ralf's chapter.
  


It's a free country. ;-)


There are some bits that are sort-of interesting but not really to do
with anything I'm passionate about, and then there are bits that I
can't comprehend...



Passionate... perhaps this is the root of the problem? Different people
are passionate about different things.
  


Well, more that some things make more sense to me than others. It's 
difficult to decide whether you're passionate about something or not if 
you can't understand what it is.


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


Re: [Haskell-cafe] data PLZ a

2007-05-29 Thread Andrew Coppin

Donald Bruce Stewart wrote:

We got the names wrong!

data PLZ a = AWSUM_THX a | O_NOES String

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

Thanks to mauke on #haskell.
  


OMG... Genius!

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


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

2007-05-29 Thread Andrew Coppin

Vincent Kraeutler wrote:

Donald Bruce Stewart wrote:
  

P.S. Have some cute code:

Control.Monad.Fix.fix ((1:) . scanl (+) 1)
  



this is cute indeed! (do you keep an emergency reserve of those around
for situations like this? ;-))
  


LOL! I bet he does as well...

I don't know. I try to tell people Haskell can be beautifully readable 
and concise. But there is no denying that Haskell can *also* be cryptic 
beyond belief! Even *I* am unable to figure out how the hell that works. 
Heck I only even know what it *does* because I got the computer to 
execute it for me... o_O


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


Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Andrew Coppin

Henning Thielemann wrote:

On Sun, 27 May 2007, Andrew Coppin wrote:

  

Personally, I try to avoid ever using list comprehensions.



Me too. Successfully, I have to add.

  

But every now and then I discover an expression which is apparently not
expressible without them - which is odd, considering they're only
sugar...



Example?
  


Until I learned the trick of using lists as monads, I was utterly 
perplexed as to how to get a Cartesian product - or why there's no 
library function to do this!


Thanks to the chapter on Logic Combinators, I've learned a trick or two 
about monadic list trickery... muhuhuhuhu!


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


Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Tim Chevalier

On 5/29/07, Andrew Coppin [EMAIL PROTECTED] wrote:

My point is for most programs, trying to figure out exactly what you
want the program to do is going to be much harder than implementing a
program that does it.


Writing a spec can help with figuring out what you want your program to do.



Also, for most programs the spec is far more complicated (and hence
prone to error) than the actual program, so...


Really? That might be a good sign that there's something wrong with
the spec, the program, or your understanding of the problem. In
Haskell, the most common form of specification is probably type
signatures. Those are usually simpler than the corresponding
implementations.

Cheers,
Tim

--
Tim Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cute code

2007-05-29 Thread Andrew Coppin

Donald Bruce Stewart wrote:

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

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


That is, keep sucking up X events till there's no 'more'.
  


My God... that's almost as cute as the first thing!

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


Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Andrew Coppin

Tim Chevalier wrote:

On 5/29/07, Andrew Coppin [EMAIL PROTECTED] wrote:

My point is for most programs, trying to figure out exactly what you
want the program to do is going to be much harder than implementing a
program that does it.


Writing a spec can help with figuring out what you want your program 
to do.


True in principle. But if writing the spec is harder than writing the 
actual program, all it means is you spend longer trying to figure out 
how to express intuitively simple concepts using advanced and very 
abstract and subtle predicate calculus.




Also, for most programs the spec is far more complicated (and hence
prone to error) than the actual program, so...


Really? That might be a good sign that there's something wrong with
the spec, the program, or your understanding of the problem. In
Haskell, the most common form of specification is probably type
signatures. Those are usually simpler than the corresponding
implementations.


One of the things I love about Haskell is the way the type signature 
alone almost tells you what the function actually does. I've never 
come across this in any other language - but then, I've never seen any 
other language with a type system as powerful as Haskell.


OTOH, how many function can you write with :: [Int] - Int? I can think 
of a few...


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


[Haskell-cafe] Re: Language extensions

2007-05-29 Thread Jon Fairbairn
Andrew Coppin [EMAIL PROTECTED] writes:
 OTOH, how many function can you write with :: [Int] - Int?

Quite a lot, but if you'd asked how many functions can you
write :: Integer - Integer, the answer would be all of
them (think about it).


-- 
Jón Fairbairn [EMAIL PROTECTED]


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


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

2007-05-29 Thread Albert Y. C. Lai

Vincent Kraeutler wrote:

Donald Bruce Stewart wrote:

P.S. Have some cute code:

Control.Monad.Fix.fix ((1:) . scanl (+) 1)
  

either way, if one of the Masters Of The Shadow Y Style on this list
feels like throwing in another koan or two, you'll have at least one
thankful audience member ;-)


Rewriting in a more beginner form:

s = 1 : scanl (+) 1 s

Recursively defined lists are sometimes hard to predict. Here is a 
systematic way of watching what it does. Inspired by a theorem about 
fixed points, the following sequence gets closer and closer to the 
solution to s = f s:


_|_, f _|_, f (f _|_), f (f (f _|_)), ...

Applying this to our example,

_|_
1 : scanl (+) 1 _|_ = 1:1:_|_
1 : scanl (+) 1 (1:1:_|_) = 1:1:2:3:_|_
1 : scanl (+) 1 (1:1:2:3:_|_) = 1:1:2:3:5:8:_|_

You can continue the process until you run out of patience or you see 
the pattern. It is an alternative way to execute the recursion. It is 
harder in some cases (e.g., recursive functions) but easier in some 
others (e.g., recursive lists).


Executing a program to look for a pattern is the hardest way to 
understand it. (Sadly, in most schools it is the only way taught.) 
Deriving it from a specification provides more insight, answers the 
itching question so how did you come up with this magic, takes away 
the mysticism, teaches more lessons, and moves programming closer to 
science-based engineering and further from secret-based guild.


We wish to compute a fibonacci-like sequence s with given s0 and s1, and 
s(n+2) = s(n+1) + sn afterwards. We already know a million ways, but 
today we add one more. After some exploration, we find


s(n+1) = s1 + (s0 + s1 + s2 + ... + s(n-1))
   = scanl (+) s1 s !! n

(This applies to s1 too: scanl (+) s1 s !! 0 = s1.)

Let me abbreviate scanl (+) s1 s as f s. So s(n+1) = f s !! n.

s = [s0, s1, s2, s3, ...]
  = [s0, f s !! 0, f s !! 1, f s !! 2, ...]
  = s0 : f s
  = s0 : scanl (+) s1 s

Now we have it.

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


[Haskell-cafe] Re: Frisby grammars that have context

2007-05-29 Thread apfelmus
Isaac Dupree wrote:
 apfelmus wrote:
 Mark T.B. Carroll wrote:
 I've been playing with Text.Parsers.Frisby to see how it stacks against
 other options and, while it's been great so far, I am finding that I
 can't encode a grammar where what's acceptable depends on what's already
 been parsed in some nontrivial way.
 [...]
 Is this supposed to not be possible in Frisby, or (quite likely) am I
 missing something that allows me to?
 It's intentionally impossible. Frisby uses a dynamic programming
 approach that crucially depends on the fact that the grammar in question
 is context-free (actually something related, but the effect is the
 same).
 
 Is that dependence crucial? What if it gained Monad operations that just
 weren't intended to be used very often, and maybe locally harmed
 performance a little where they are used?

Now that you ask, I become unsure :) The actual details of packrat
parsing are written down in

   B. Ford. Packrat Parsing: Simple, Powerful, Lazy, Linear Time.
   http://pdos.csail.mit.edu/~baford/packrat/icfp02/

There's a small section about Monadic Packrat Parsing but I'm not sure
about its significance. The following discussion may shed light on this.


First a different explanation of packrat parsing. It can be understood
as a variant of the O(n^3) Cocke, Younger, Kasami parsing algorithm for
context-free grammars (coincidentially recently discussed at
http://article.gmane.org/gmane.comp.lang.haskell.cafe/22850). First, we
rearrange the table

  gs i j nt = substring starting at position j of length i
  can be derived by nonterminal nt
= function of gs i' j' nt' for j'=j, j+i=j'+i'
  and any nt' ¹

as

  fs j nt = [i | the substring starting at j with a length i
 is a derivation from the nonterminal nt]

Then, packrat parsing basically throws out non-determinism (which
changes the semantics of the context-free grammar):

  packrat j nt = minimum (fs j nt)
   = function of (packrat j' nt') for j'=j
 and any nt' ¹

and that's about it. In the aforementioned paper, this table is very
implicit but it's there: the indices i and j are present as memory
pointers to different incarnations of the data structure Derivs. Also,
the constructed values (i.e. values of type a for P s a) are stored in
the table.


Now, declaring a parser in the Frisby library builds up the table
structure. Every newRule introduces a new non-terminal and an associated
column in the table. This means that at least every non-terminal must be
side-effect free, i.e. the result (packrat j nt) may only depend on
the substring starting at j but not on the results from previous parses.
But it seems that the dependence itself indeed may incorporate
context-sensitive behavior. In other words, you may decide freely how
(packrat j nt) is calculated from (packrat j' nt'). In particular, you
can choose the j' to incorporate based on parsing resulsts from them.
Here's an artificial pseudo-code example:

  weird   - newRule $ do
b - parse boolean
if b == True
   then parse number
   else parse date

-- assumed helper stuff
  boolean - newRule $ ...
  number  - newRule $ ...
  date- newRule $ ...

The decision of constructing the result of the nonterminal 'weird' from
parsing a date or parsing a number depends on whether we parsed True or
False before. In this case, there are no unexpected run-time penalities
and it appears that this can already be implemented using the bare-hands
machinery from the paper but that this cannot be implemented in Frisby (?).

However, it's not possible to assign non-terminals to the parts that
parse differently depending on context. In the example, we cannot factorize

  weird   - newRule $ do
b - parse boolean
parse (helper b)

  helper  - newRule $ \b - do
if b == True
   then parse number
   else parse date

and assign 'helper' a non-terminal. Somehow, this apparently doesn't
work anyway because newRule doesn't accept functions as arguments. So,
it seems that we can just turn (P s) into a monad without regret!
Run-time penalities should only occur if we recurse on something that
didn't get memoized via newRule. In a sense, is 'newRule' the only
primitive (should probably get a different name like 'memoize') that
makes packrat parsing different and faster than other monadic parsers?

 BTW: (P s) should be an instance of Applicative (which is already
 possible with Frisby's current code, just not there) (I prefer the
 aesthetics of Frisby-applicative code to many of the combinators it
 provides - I tried it a little sometime, not enough to send a darcs patch)

Yes, I think too that it definitely should be made an instance of
Applicative. For parsing, I prefer that to Monad anyway :)


Regards,
apfelmus

¹ The = sometimes must be  to avoid a loop, but that's immaterial
here.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org

Re: [Haskell-cafe] shared oneShot IO (was top-level state proposals)

2007-05-29 Thread Claus Reinke
I was wondering why, since IO is an instance of MonadFix [1], and 
therefore of ArrowLoop (Kleisli m), and since The loop operator 
expresses computations in which an output value is fed back as input, 
even though the computation occurs only once. [2], the MonadFix or 
ArrowLoop class (through use of mfix or loop, respectively) doesn't 
appear in anyone's suggestion, where the top-level state was the thing 
looped over.


oh, but it does!-) see 'proposal 2: top-level -', and especially John
Meacham's elaboration. 'mdo' is recursive do-notation, based on 
'MonadFix', which for 'IO' is based on 'fixIO' (John's email gives

references). (*)

the problem with that is what happens to multiple bindings: according
to the usual 'mdo'-translation, they are interpreted as a *sequence*,
so order matters, which is kind of a big change for top-level bindings
spread over a hierarchy of modules. as is the potential for allowing 
arbitrary IO actions to be performed as part of evaluating a set of
recursive bindings and imports. see the wiki page for some of the 
issues and proposed workarounds.


what is different about the variation i proposed is that the only thing
that is merged into the evaluation of top-level bindings is the creation
of some mutable variables, which are not even explicitly accessible,
but are only used behind the scenes, to realise sharing. this is a kind
of effect for which the ordering is immaterial, and since this effect
does not depend on the actual IO action being shared, we do not
need to know anything about that IO action either to guarantee
that we can order bindings any way we like.

and since the actual IO action being shared is not performed unsafely,
it remains in the IO monad, and has to be invoked explicitly, so this 
variation should also be safer (no side-effects due to mere module

import, for instance).

it might still make sense to interpret '='-bindings via 'mdo', to allow
for mutual recursion in the bindings. but since all top-level bindings
are now either of the form 'var = io', where 'io' will not be executed
until 'var' is invoked within the 'IO' monad, or of the form 'let var = expr',
where no 'IO' effects are involved, the ordering of the bindings does
no longer matter. as i think it should be.

hth,
claus

(*)

Or is this more or less what is going on in the function 
 .. oneShot :: IO a - ACIO (IO a) ..

but without explicitly using the MonadFix or ArrowLoop classes?


oneShot, mkOnceIO, and fixIO, have an implementation technique
in common, which is to allocate space for a result, then executing
some code to figure out what that result might be. by passing the
reference to where the result will be stored to the code computing
it, cyclic representations of recursive structures can be constructed.


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


Re: [Haskell-cafe] Control.Monad.State.Strict, mdo and let

2007-05-29 Thread Albert Y. C. Lai

Gracjan Polak wrote:

Hi,

I stumbled at some interaction of Control.Monad.State.Strict, mdo and let I do
not understand. The following program:


{-# OPTIONS_GHC -fglasgow-exts #-}
module Main where
import Control.Monad.State.Strict

thenumber :: Float
thenumber = flip execState 1.3 $ mdo
c - donothing []  
let donothing x = return x

return ()

main = print thenumber

Says (in GHC 6.6.1):

Stack space overflow: current size 8388608 bytes.
Use `+RTS -Ksize' to increase it.

Why is this so?



This mdo block goes into an infinite loop if the body is strict on 
donothing.


In Control.Monad.State.Strict, m=k is strict on m. This m happens to 
be donothing[]. So the body is strict on donothing, and mdo goes into an 
infinite loop.


(Control.Monad.State.Lazy postpones m until k really wants m's return 
value. If, like this example, k doesn't want it, everyone happily goes 
home.)


It takes a lot more analysis and peaking into the implementation of 
Control.Monad.State.Strict to see why this infinite loop also consumes 
infinite stack space.

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


Re: [Haskell-cafe] Re: Frisby grammars that have context

2007-05-29 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

apfelmus wrote:
 Isaac Dupree wrote:
 apfelmus wrote:
 Mark T.B. Carroll wrote:
 I've been playing with Text.Parsers.Frisby to see how it stacks against
 other options and, while it's been great so far, I am finding that I
 can't encode a grammar where what's acceptable depends on what's already
 been parsed in some nontrivial way.
 [...]
 Is this supposed to not be possible in Frisby, or (quite likely) am I
 missing something that allows me to?
 It's intentionally impossible. Frisby uses a dynamic programming
 approach that crucially depends on the fact that the grammar in question
 is context-free (actually something related, but the effect is the
 same).
 Is that dependence crucial? What if it gained Monad operations that just
 weren't intended to be used very often, and maybe locally harmed
 performance a little where they are used?
 
 Now that you ask, I become unsure

Luckily, Haskell's laziness means that doing an extra postprocessing
pass doesn't necessarily yield two traversals requiring the whole file
to be stored in memory, nor worse hacks.  (For grammars that aren't too
wild / sequential)

Isaac
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGXLcBHgcxvIWYTTURArCuAJ9mR8HFqiRNT7teWjhvAtRwXYgjfwCgu7hi
YEXGLGvMVHQwlZpfxTDi0FI=
=b3Q7
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] teaming up for the IFCP contest

2007-05-29 Thread Tim Docker
I've put aside the weekend of July 20-23 for the ICFP contest (http:// 
www.icfpcontest.org/), and am looking to form or join a haskell  
wielding team. Any interest? Geographically I'm in Sydney, but have  
entered in a previous year with a team of 3 from around the globe  
which worked fine.


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


Re: [Haskell-cafe] Re: Frisby grammars that have context

2007-05-29 Thread Robin Green
On Tue, 29 May 2007 19:28:02 -0400
Isaac Dupree [EMAIL PROTECTED] wrote:
 Luckily, Haskell's laziness means that doing an extra postprocessing
 pass doesn't necessarily yield two traversals requiring the whole
 file to be stored in memory, nor worse hacks.  (For grammars that
 aren't too wild / sequential)

But the suggested code fragment on the frisby homepage:

  -- parse complete file, returning 'Nothing' if parse fails
  fmap Just (myParser - eof) // unit Nothing

does require one traversal of the file all by itself. Obviously, in
order to know whether the file was fully parsed without error, you need
to read in the whole file, before you can write out anything. Hence
you end up with *some* representation of the whole file in memory. So,
yes, it doesn't necessarily yield two traversals, but you need to be
careful if you want to avoid two traversals.
-- 
Robin
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Help with terminal IO

2007-05-29 Thread Jason Dagit

On 5/27/07, Ryan Ingram [EMAIL PROTECTED] wrote:

I was hoping that hSetBuffering would turn off the line buffering for stdin,
but it doesn't seem to work.


module Main where
import System.IO

main :: IO ()
main = do
hSetBuffering stdin NoBuffering
hSetBuffering stdout NoBuffering

hPutChar stdout ''
c - hGetChar stdin
hPutChar stdout ''


This program should terminate immediately after the first character is typed
into the terminal, but it waits until I type a newline.  It also looks like
it's using GNU readline (it handles the up  down arrow keys.)

How do I turn this off and use raw character-based IO?  I'm using GHC6.6 on
Win32 if that makes a difference.


Using the same platform but I get essentially the same behavior.  I
too have to type enter to get the program to accept the input, but
then it exits immediately so I don't know how you tested the up and
down arrows.

When I compile this on debian it works as you expected.  Perhaps this
is a windows bug?

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


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

2007-05-29 Thread Jason Dagit

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

This thread should end, guys. It is inappropriate for the Haskell lists,
and appears to have been a simple misunderstanding anyway.

Thanks everyone. Please stay friendly!

-- Don

P.S. Have some cute code:

Control.Monad.Fix.fix ((1:) . scanl (+) 1)


Speaking of cute code, I'm fond of this:

map length . List.group . Control.Monad.Fix.fix $ show

And other (longer) variations which generate only powers of two.  It's
a great conversation starter for teaching about fix.

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


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

2007-05-29 Thread Jason Dagit

On 5/29/07, Doug Kirk [EMAIL PROTECTED] wrote:

OTOH, I work for companies, and they really value their assets,
especially software assets. So they *want* centralized stuff, so they
can ensure they have consistent backups (in the U.S.A. there is a lot
of regulation under Sarbanes-Oxley that requires this stuff). Right
now we're using ClearCase, which I abhor because it's so
heavyweight...but it is centralized control.


Interestingly, using a decentralized version control does not rule out
the possibility of centralized control and development.  For example,
darcs itself has a very centralized development even though the tool
allows decentralization.  The advantage is that people working on, for
example, a feature branch can easily share patches via cherry picking.
When the feature branch is ready to be merged darcs handles this in a
way superior to svn[1] by doing the merge almost completely
transparently.  We're currently developing a feature branch at work
under svn and every merge is a book keeping headache and at least one
day of lost development time.  In this respect, svn seems primitive,
tedious and error-prone.  Just check the svn red bean book for details
on merging in svn.  We have learned you need to manually track version
numbers so you don't merge things twice.  Perhaps my argument is more
about svn vs. darcs, but those are the two version control systems I
know best.

[1] I will happily concede that darcs is not currently perfect in it's
automated merging, especially in the case of conflicting patches.
Just ask the ghc developers if this is a problem for them.  But, that
is also why there is a summer of code project this year to fix the
problem.  With a fair bit of retooling, darcs will handle this case
better in the future and I'm confident this will become a problem of
the past.

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


[Haskell-cafe] ffi linking problem

2007-05-29 Thread jeff p

Hello,

 Can anyone give me some tips concerning the following error:

   myPrompt ghc --make -fffi f.hs -l mylib.lib
   ghc --make -fffi f.hs -l mylib.lib
   [1 of 1] Compiling Main ( f.hs, f.o )
   Linking f.exe ...
   d:\ghc\ghc6.6\gcc-lib\ld.exe: cannot find -l-Ld:/ghc/ghc6.6
   collect2: ld returned 1 exit status

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


Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread Brandon S. Allbery KF8NH


On May 29, 2007, at 23:01 , jeff p wrote:


   myPrompt ghc --make -fffi f.hs -l mylib.lib


For historical reasons, you can't have a space between the -l and the  
library name.  It's inserting an empty library name into the link  
command, which is producing the odd cannot find error.


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


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


Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread jeff p

Hello,

On 5/29/07, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:


On May 29, 2007, at 23:01 , jeff p wrote:

myPrompt ghc --make -fffi f.hs -l mylib.lib

For historical reasons, you can't have a space between the -l and the
library name.  It's inserting an empty library name into the link
command, which is producing the odd cannot find error.


Ok. Now I get another error:

   myPrompt ghc --make -fffi f.hs -lmylib.lib
   ghc --make -fffi f.hs -lmylib.lib
   Linking f.exe ...
   d:\ghc\ghc6.6\gcc-lib\ld.exe: cannot find -lmylib.lib
   collect2: ld returned 1 exit status

which is strange because the file mylib.lib is in the same directory
as the haskell code.

Any thoughts?

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


Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread Brandon S. Allbery KF8NH


On May 29, 2007, at 23:09 , jeff p wrote:


   d:\ghc\ghc6.6\gcc-lib\ld.exe: cannot find -lmylib.lib
   collect2: ld returned 1 exit status

which is strange because the file mylib.lib is in the same directory
as the haskell code.


Typically -l appends the necessary extension itself (.lib on  
Windows, .a or .so on Unix, .a or .dylib on OSX).  You may also need - 
L. (again, no space) to make it check the current directory.


It may be easier to see if ghc has an option to pass through the next  
argument straight to the linker, or even recognizes .lib files and  
passes them through unchanged (then you'd not need any option to  
include it, just the filename).  Unfortunately my knowledge of ghc on  
Windows is rather sketchy.


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


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


Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread Stefan O'Rear
On Tue, May 29, 2007 at 11:09:15PM -0400, jeff p wrote:
 Hello,
 
 On 5/29/07, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:
 
 On May 29, 2007, at 23:01 , jeff p wrote:
 
 myPrompt ghc --make -fffi f.hs -l mylib.lib
 
 For historical reasons, you can't have a space between the -l and the
 library name.  It's inserting an empty library name into the link
 command, which is producing the odd cannot find error.
 
 Ok. Now I get another error:
 
myPrompt ghc --make -fffi f.hs -lmylib.lib
ghc --make -fffi f.hs -lmylib.lib
Linking f.exe ...
d:\ghc\ghc6.6\gcc-lib\ld.exe: cannot find -lmylib.lib
collect2: ld returned 1 exit status
 
 which is strange because the file mylib.lib is in the same directory
 as the haskell code.

Don't know about Windows, but on traditional Unix systems -l appends
an extension and prepands /library/path/lib, so -lc links
/lib/libc.so; if your library does not follow the naming conventions,
you must omit -l and directly reference ./foobarlib.so as a file to
link (GHC will link any object code files listed on the command line). 

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


Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread Stefan O'Rear
On Tue, May 29, 2007 at 11:12:14PM -0400, Brandon S. Allbery KF8NH wrote:
 It may be easier to see if ghc has an option to pass through the next  
 argument straight to the linker, or even recognizes .lib files and  

-Wl,foobar

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


Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread jeff p

Hello,

 Thanks for the tips. I've gotten to the point where linking fails on
an undefined reference. The strange thing about this is that when I
make a C program to call the library function and compile with:

   myPrompt gcc f.c mylib.lib

everything works fine. I think ghc is using it's own version of gcc
and ld which aren't happy about my library. Does this seem possible?

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


Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread Stefan O'Rear
On Tue, May 29, 2007 at 11:48:18PM -0400, jeff p wrote:
 Hello,
 
  Thanks for the tips. I've gotten to the point where linking fails on
 an undefined reference. The strange thing about this is that when I
 make a C program to call the library function and compile with:
 
myPrompt gcc f.c mylib.lib
 
 everything works fine. I think ghc is using it's own version of gcc
 and ld which aren't happy about my library. Does this seem possible?

No, but ghc does pass a lot of funny flags...

Double check ccall v. stdcall in the import declaration.  That bites a
lot of people on Windows. 

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


Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread jeff p

Hello,


No, but ghc does pass a lot of funny flags...

Double check ccall v. stdcall in the import declaration.  That bites a
lot of people on Windows.


My import statement originally looked like:

   foreign import ccall mylib.h myFun my_fun :: CDouble - IO (Ptr CDouble)

and my original linker error was an undefined reference to 'myFun'.

Changing the import statement to:

   foreign import stdcall mylib.h myFun my_fun :: CDouble - IO (Ptr CDouble)

results in the linker complaining about undefined reference to '[EMAIL 
PROTECTED]'.

I also tried throwing in static but it seems to have no effect.

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


Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Stefan Holdermans
True in principle. But if writing the spec is harder than writing  
the actual program, all it means is you spend longer trying to  
figure out how to express intuitively simple concepts using  
advanced and very abstract and subtle predicate calculus.


As it turns out, Haskell sometimes makes a suitable specification  
language:


  Paul Hudak and Mark P. Jones.
  Haskell vs. Ada vs. C++ vs. Awk vs:
  An experiment in software prototyping productivity.
  1994.
  http://haskell.org/papers/NSWC/jfp.ps

Cheers,

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


Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread Stefan O'Rear
On Wed, May 30, 2007 at 12:28:43AM -0400, jeff p wrote:
 Hello,
 
 No, but ghc does pass a lot of funny flags...
 
 Double check ccall v. stdcall in the import declaration.  That bites a
 lot of people on Windows.
 
 My import statement originally looked like:
 
foreign import ccall mylib.h myFun my_fun :: CDouble - IO (Ptr 
CDouble)
 
 and my original linker error was an undefined reference to 'myFun'.
 
 Changing the import statement to:
 
foreign import stdcall mylib.h myFun my_fun :: CDouble - IO (Ptr 
CDouble)
 
 results in the linker complaining about undefined reference to '[EMAIL 
 PROTECTED]'.

That is very very very suspicious.  the number after the @ is the
number of bytes of argument data, which should be 8 for a single
CDouble on x86 - not 24. 

 I also tried throwing in static but it seems to have no effect.

What does the definition in the library look like?  To be compatible
with that import it should be:

double *myFun(double);

NOT any of:

double *my_fun(double);

static double *myFun(double);

double myFun(double);

I suspect you may have the two names in the import statement swapped.

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


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

2007-05-29 Thread Ketil Malde
On Tue, 2007-05-29 at 14:05 -0500, Doug Kirk wrote:

 I *want* people (and companies) to move to Haskell; therefore, I want
 to lower the entry price. The goal is to introduce a new language,
 not a new SCM tool. You certainly wouldn't want to leave the
 impression that one MUST use darcs in order to use Haskell!

Fair enough.  But you do not want to leave the impression that one must
use SVN in order to use Haskell (or any other language, for that matter)
either?  Anyway, I am sure that can be avoided by a reasonable phrasing
of the relevant chapter - caveat scriptor.

Now, darcs is:

 a) really simple to get started with

 b) ubiquitous for Haskell programs - if you download something to
install yourself, you will - as likely as not - use darcs to do the
downloading.

 c) written in Haskell, serving as both an example of a 'real world'
application, and as a possible target for the enterprising hacker.

You could make a similar argument for the build system - should a
Haskell book teach make instead of Cabal, just because it is more
familar?

-k

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