Re: [Haskell-cafe] Clearly, Haskell is ill-founded

2007-07-09 Thread Daniel McAllansmith
On Monday 09 July 2007 17:42, Thomas Conway wrote:
 I don't know if you saw the following linked off /.

 http://www.itwire.com.au/content/view/13339/53/

 An amazon link for the book is here:

 http://www.amazon.com/Computer-Science-Reconsidered-Invocation-Expression/d
p/0471798142

 The basic claim appears to be that discrete mathematics is a bad
 foundation for computer science. I suspect the subscribers to this
 list would beg to disagree.

I wouldn't want to comment on the validity of his claim, maybe he's wrong, or 
maybe he's... well, anyway... what I will say is I got a chuckle out of 
the 'Citations' that Amazon lists.

I especially like it that Mr. Fant's book is apparently cited in 'The 
Essential Guide to Psychiatric Drugs: Includes The Most Recent Information 
On: Antidepressants, Tranquilizers and Antianxiety Drugs, 
Antipsychotics, ...'

I shudder to think of the creative processes involved in the creation of the 
book.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-07-09 Thread Ketil Malde
On Mon, 2007-07-09 at 10:30 +1000, Donald Bruce Stewart wrote:

 Another idea I've been pondering is allowing people to add links to
 documentation for libraries

My main worry about Hackage is that it is often hard to tell the current
status of packages - it could easily develop into a huge list of mostly
dead projects.

The current deliverables seem to consist of a tar file and a package
description, neither of them accurately dated.  I'd like to see links to
project home pages, darcs (devel) repositories, and email address of
maintainers.  I'd also like browsable README and ChangeLog or similar.
And what about a darcs-graph plot?

-k

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


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

2007-07-09 Thread Donald Bruce Stewart
ketil:
 On Mon, 2007-07-09 at 10:30 +1000, Donald Bruce Stewart wrote:
 
  Another idea I've been pondering is allowing people to add links to
  documentation for libraries
 
 My main worry about Hackage is that it is often hard to tell the current
 status of packages - it could easily develop into a huge list of mostly
 dead projects.
 
 The current deliverables seem to consist of a tar file and a package
 description, neither of them 
 accurately dated.  

Yes, I'd like uploader dates/names too. Something like:

xmonad-0.3  - July 2007

 I'd like to see: 
   links to project home pages, 

That's already provided via the 'homepage: ' field, see, e.g.

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

   darcs (devel) repositories, 

yes, I'd support a 'repository: ' field.

   email address of maintainers.  

handled by the 'maintainer: ' field

 I'd also like browsable README and ChangeLog or similar. And what about a 
 darcs-graph plot?

a link to the README might be good. If there was a 'repository'
field, we could automatically compute the darcs-graph, a la,

http://www.cse.unsw.edu.au/~dons/images/commits/community/

Who's our SoC hackage guy? To do list right here!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-07-09 Thread Thomas Conway

On 7/9/07, Ketil Malde [EMAIL PROTECTED] wrote:

The current deliverables seem to consist of a tar file and a package
description, neither of them accurately dated.


Clearly we need to store them in a treap. :-)

--
Dr Thomas Conway
[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Clearly, Haskell is ill-founded

2007-07-09 Thread Stephen Forrest

On 7/9/07, Daniel McAllansmith [EMAIL PROTECTED] wrote:


I wouldn't want to comment on the validity of his claim, maybe he's wrong, or
maybe he's... well, anyway... what I will say is I got a chuckle out of
the 'Citations' that Amazon lists.


As amusing as that thought is, it seems that this is regrettably an
error on Amazon's part.  After looking at the actual page images where
the alleged citations occur, there is nowhere any mention of this
book.  (How could there be?  It was just published.)

It looks like Amazon's citation database is mistakenly using the index
for the book _Beating Depression_ by John Rush (Toronto: John Wiley 
Sons, Canada Ltd., 1983).

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


Re[2]: [Haskell-cafe] Toy compression algorithms [was: A very edgy language]

2007-07-09 Thread Bulat Ziganshin
Hello Andrew,

Sunday, July 8, 2007, 7:07:59 PM, you wrote:

 Actually, LZW works surprisingly well for such a trivial little
 algorithm... When you compare it to the complexity of an arithmetic 
 coder driven by a high-order adaptive PPM model (theoretically the best
 general-purpose algorithm that exists), it's amazing that anything so 
 simple as LZW should work at all!

i don't think that ppm is so complex - it's just probability of
symbol in some context. it's just too slow in naive implementation

 there is no much meaning to use huffman with lzw because many words
 will have only one or two occurrences

 (The downside of course is that now we need a Huffman table in the 
 output - and any rare symbols might end up with rather long codewords.
 But remember: Huffman *guarantees* 0% compression or higher on the 
 payload itself. A Huffman-compressed payload can *never* be bigger, only
 smaller or same size. So long as you can encode the Huffman table 
 efficiently, you should be fine...)

the devil in details. just imagine size of huffman table with 64k
entries :)  huffman encoding is inappropriate for lzw output simply
because most words will have only a few occurrences and economy on
their optimal encoding doesn't justify price of their entries in the table

 .ru = Russia?

of course

 (Realistically though. My program takes a [Word8] and turns it into a
 [Bool] before running a parser over it. The GHC optimiser doesn't really
 stand a hope in hell of optimising that into a program that reads a 
 machine word into a CPU register and starts playing with bit flips on it...)

 as time goes, those terrible compilers becomes smarter and smarter :)
   

 Oh hey, I think GHC is already pretty smart. But no optimiser can ever
 hope to cover *every* possible case. And transforming [Bool] - [Bool]
 into UArray Word8 - UArray Word8 just seems a little bit
 optimistic, methinks. ;-)

15 years ago i've written very smart asm program (btw, it was ARJ
unpacker) with handmade function inlining, loop unrolling, register
allocation, cpu recognition and so on. now, most of these tricks are
standard for C compilers. times changes and now it's hard to imagine which
optimizations will be available 10 years later

 The way I heard it is that it *does* native code generation, but it's
 not as good as the via-C version. (Can't imagine why... You would have
 thought directly implementing functional primitives would be much easier
 than trying to mangle them to fit C's multitude of limitations. Still,
 what do I know?)

ghc's native and via-C modes are blind vs lame. in native mode, its
codegenerator is comparable with 20 years-old C codegenerators. see
above how much modern C compilers changed in these years. in via-C
mode it generates unnatural C code which is hard to optimize for any C
compiler. the jhc is very different story - it generates natural C
code, so for simple, low-level programs its speed is the same as
with C. but it lacks huge base of high-level GHC optimizations. as you
may guess, in order to have C-like speed, compiler should implement
both good high-level and low-level optimization. there are
(low-priority) plans to provide LLVM backend for ghc which may solve
this problem. but actually speed of generated code isn't number 1
priority for ghc users



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Constraints on data-types, mis-feature?

2007-07-09 Thread Daniil Elovkov

Hello

In the archives of haskell-cafe I found a mention of constraints on
datatypes as a mis-feature of Haskell. In particular, that they're not
propagated well. Can someone elaborate on that?

Also, are they still considered a mis-feature with the emergence of GADTs ?

If I have

data GADT a where
  ...
  Alt :: (a - b - c) - GADT a - GADT b - GADT c
  ...

and I want to constrain all a, b, c.

Would it be better to expose all of them as type vars, rather than
constrain in-place? It would lead to a rather verbose code.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Clearly, Haskell is ill-founded

2007-07-09 Thread Puneet

It looks like Amazon's citation database is mistakenly using the index
for the book _Beating Depression_ by John Rush (Toronto: John Wiley 
Sons, Canada Ltd., 1983).



Yes it is so. Amazon.com mistakenly thinks that the given book is a
new edition of the book titled beating depression.

Amazon also links hardcover and softcover editions of beating
depression just below where the price and availability of the book is
mentioned.

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


Re: [Haskell-cafe] Lambdabot web interface

2007-07-09 Thread Donald Bruce Stewart
voigt:
 Hi,
 
 I can't get http://lambdabot.codersbase.com/ to work for me. Whatever 
 input = No lambdabot process
 
 Is that a known issue, not the right URL, ...?
 
 Thanks,
 Janis.

Right URL, but Jason's not running lambdabot at the moment. You can
access our bot via IRC though.  http://haskell.org/haskellwiki/IRC_channel

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


Re: [Haskell-cafe] More binary IO, compression, bytestrings and FFI fun

2007-07-09 Thread Philip Armstrong

On Mon, Jul 09, 2007 at 02:42:49PM +1000, Donald Bruce Stewart wrote:

Processing larger amounts of data, compression, serialisation and calling C.


Just a thought: is it worth sticking this up on the wiki?

Phil

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


Re: [Haskell-cafe] Lambdabot web interface

2007-07-09 Thread Janis Voigtlaender

Donald Bruce Stewart wrote:

Right URL, but Jason's not running lambdabot at the moment. You can
access our bot via IRC though.  http://haskell.org/haskellwiki/IRC_channel


Yup, but I assume that would mean bothering others with my experiments 
with some lambdabot features ;-)


I'll better try out the offline version, then.

Thanks, Janis.

--
Dr. Janis Voigtlaender
http://wwwtcs.inf.tu-dresden.de/~voigt/
mailto:[EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Is Haskell well-founded? was: Clearly, Haskell is ill-founded

2007-07-09 Thread Pasqualino 'Titto' Assini
Doesn't Haskell already implement the 3-valued logic (True, False, NULL), that 
Karl Fant proposes (see papers at 
http://www.theseusresearch.com/invocation%20model.htm) as an alternative to 
centralised clock-based coordination, by postulating that every data type 
includes the bottom value?

I like his concept that:

concurrency is simple and primitive and sequentiality is a complex and risky 
derivative of concurrency.

Can someone remind me why, in a language like Haskell that is referentially 
transparent and therefore inherently 'concurrent', we need explicit 
concurrency (threads, etc.) ?

titto


On Monday 09 July 2007 06:48:03 Donald Bruce Stewart wrote:
 drtomc:
  I don't know if you saw the following linked off /.
 
  http://www.itwire.com.au/content/view/13339/53/
 
  An amazon link for the book is here:
 
  http://www.amazon.com/Computer-Science-Reconsidered-Invocation-Expression
 /dp/0471798142
 
  The basic claim appears to be that discrete mathematics is a bad
  foundation for computer science. I suspect the subscribers to this
  list would beg to disagree.
 
  Enjoy,
 
 :-)

 And he's patented it...

 http://www.patentstorm.us/patents/5355496-description.html

 SUMMARY OF THE INVENTION

 A method and system for process expression and resolution is described.
 A first language structure comprising a possibility expression having at
 least one definition which is inherently and generally concurrent is
 provided. Further, a second language structure comprising an actuality
 expression including a fully formed input data name to be resolved is
 provided. Furthermore, a third language structure comprising an active
 expression initially having at least one invocation, the invocation
 comprising an association with a particular definition and the fully formed
 input data name of the actuality expression is provided. Subsequently, the
 process of resolving invocations begins in the active expression with fully
 formed input data names in relation to their associated definition to
 produce at least one or both of the following: (1) an invocation with a
 fully formed input data name and (2) a result data name.

 Interesting...

 -- 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] Clearly, Haskell is ill-founded

2007-07-09 Thread Conor McBride

Hi all

On 9 Jul 2007, at 06:42, Thomas Conway wrote:


I don't know if you saw the following linked off /.

http://www.itwire.com.au/content/view/13339/53/


[..]


The basic claim appears to be that discrete mathematics is a bad
foundation for computer science. I suspect the subscribers to this
list would beg to disagree.


It's true that some systems are better characterised as corecursive
coprograms, rather than as recursive programs. This is not a
popular or well-understood distinction. In my career as an advocate
for total programming (in some carefully delineated fragment of a
language) I have many times been gotcha'ed thus: but an operating
system is a program which isn't supposed to terminate. No, an
operating system is supposed to remain responsive. And that's what
total coprograms do.

By the looks of this article, the program versus coprogram distinction
seems to have occasioned an unprecedented degree of existential angst
for this individual.

Even so, I'd say that it's worth raising awareness of it. Haskell's
identification of inductive data with coinductive data, however well
motivated, has allowed people to be lazy. People aren't so likely to
be thinking do I mean inductive or coinductive here?, is this
function productive? etc. The usual style is to write as if
everything is inductive, and if it still works on infinite data, to
pat ourselves on the back for using Haskell rather than ML. I'm
certainly guilty of that.

I'd go as far as to suggest that codata be made a keyword, at
present doubling for data, but with the documentary purpose of
indicating that a different mode of (co)programming is in order. It
might also be the basis of better warnings, optimisations, etc.
Moreover, it becomes a necessary distinction if we ever need
to identify a total fragment of Haskell. Overkill, perhaps, but
I often find it's something I want to express.

Just a thought

Conor

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


Re: [Haskell-cafe] Clearly, Haskell is ill-founded

2007-07-09 Thread Asumu Takikawa
On 15:42 Mon 09 Jul , Thomas Conway wrote:
 I don't know if you saw the following linked off /.
 
 http://www.itwire.com.au/content/view/13339/53/
 

I read that earlier and his comments, such as

  This concept of 'process expression' is, he says, a common thread
  running through the various disciplines of computer science,

made me think of arrows and category theory. 

And I wonder what kind of aberration a monte-carlo algorithm would be if
this excerpt is to be taken seriously:

 Any program utilising random input to carry out its process, such...is
 not an algorithm.

Cheers,
Asumu Takikawa


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


Re: [Haskell-cafe] Gtk2Hs, Glade, Multiple windows/dialog in one interface file.

2007-07-09 Thread Duncan Coutts
On Sun, 2007-07-08 at 16:40 -0400, Brandon S. Allbery KF8NH wrote:
 On Jul 8, 2007, at 16:36 , D.V. wrote:
 
  I finally got it to work with onResponse : I traced each possible
  response to see which one was fired when clicking the close button

And what was the result?

 Great, another place where the documentation's wrong.  :/   
 (onActivateLeaf vs. onActivateItem (and after- versions) also found  
 to be wrong.  Must submit a bug report at some point.)

That would be most appreciated. Or even better would be to darcs send a
patch with your suggested documentation improvements :-).

Duncan

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


[Haskell-cafe] ANNOUNCE: Haskell XML Toolbox Version 7.2

2007-07-09 Thread Uwe Schmidt
Haskell XML Toolbox 7.2

I would like to announce a new version of the Haskell XML Toolbox.

This is mainly a bug fix release, but there is one new module
for converting data between user defined types and the
HXT DOM structure.

This new modules enables the simple persistent storage and retrieval of
arbitrary data with XML documents. See example 
directory examples/arrows/pickle in the distribution
for a none trivial example of these picklers. These functions are an 
adaptation of Andrew Kennedy's pickler combinators.
( http://research.microsoft.com/~akenn/fun/picklercombinators.pdf )

The darcs repo for HXT is at
http://darcs.fh-wedel.de/hxt

More information and download:
http://www.fh-wedel.de/~si/HXmlToolbox/index.html

Please email comments, bugs, etc. to [EMAIL PROTECTED]

Uwe

--

University of Applied Sciences, Wedel, Germany
http://www.fh-wedel.de/~si/index.html

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


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

2007-07-09 Thread Sascha Böhme
Hello,

 Who's our SoC hackage guy? To do list right here!

The HackageDB project is for now concentrating on another subject. I see
the necessity of adding search features and additionally tags, but in
the moment I work on automatic generation of Haddock documentation.

The progress and a to do list can be found from here:

  http://hackage.haskell.org/trac/summer-of-code/wiki/SoC2007Hackage

A more complete ToDo list can be found here:

  http://hackage.haskell.org/trac/hackage/wiki/HackageToDo
  
This also covers your wishes, and, as soon as automatic Haddock
documentation is working, I'll turn towards that.

Ciao,
Sascha

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


[Haskell-cafe] Elementary question about Type Constraints

2007-07-09 Thread lassoken

Hi,

I'm trying to translate Example 2.3.3 (simple symbolic differentation) from
Structure and Interpretation of Computer Programs into Haskell.

Here is code that works (as far as see):
---
data Term b = Var String | Const b | Sum (Term b) (Term b) | Prod (Term b)
(Term b)

newSum (Const a) (Const b) = Const (a+b)
newSum (Const 0) [EMAIL PROTECTED] = t
newSum [EMAIL PROTECTED] (Const 0) = t
newSum a b = Sum a b

newProd (Const a) (Const b) = Const (a*b)
newProd (Const 1) [EMAIL PROTECTED] = t
newProd [EMAIL PROTECTED] (Const 1) = t
newProd (Const 0) [EMAIL PROTECTED] = Const 0
newProd [EMAIL PROTECTED] (Const 0) = Const 0
newProd a b = Prod a b

deriv (Var x) (Const c) = Const 0
deriv (Var x) (Var y)
   | x == y = Const 1
   | otherwise = Const 0
deriv x@(Var _) (Sum u v) = newSum (deriv x u) (deriv x v)
deriv x@(Var _) (Prod u v) = newSum (newProd u (deriv x v)) (newProd (deriv
x u) v)

--instance Show (Term b) where show = showTerm
showTerm (Var x) = x
showTerm (Const c) = show c
showTerm (Sum a b) = ( ++ showTerm a ++ + ++ showTerm b ++ )
showTerm (Prod a b) = ( ++ showTerm a ++ showTerm b ++ )
---

Where should I put type constraint (Show b) to be able to define Term b as
an instance of Show class?

Actually, I would like to say that Term b is an instance of Show iff b is
and not to put constraint on b.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] reading existential types

2007-07-09 Thread Claus Reinke

I'd like to be able to use MT to build a list like:
[MT (T1a,1), MT (T1b,3)]
And I'd like to read str with:
read $ show str



Substituting return (m) with return (MT m) leads to error messages
like: Ambiguous type variable `e' in the constraints


which is the important hint! the parser used for 'read' depends on
the return type, but the existential type _hides_ the internal type
which would be needed to select a read parser.


readMT :: ReadPrec MyType
readMT = prec 10 $ do
  Ident MT - lexP
  parens $ do m - readPrec
  return (m) 


if your hidden types have distinguishable 'show'-representations,
you could write your own typecase like this (making use of the
fact that 'read' parsers with incorrect type will fail, and that the
internal type can be hidden after parsing)

   readMT :: ReadPrec MyType
   readMT = prec 10 $ do
  Ident MT - lexP
  parens $ (do { m - readPrec; return (MT (m::(TipoA,Int))) })
   `mplus` (do { m - readPrec; return (MT (m::(TipoB,Int))) })

   *Test read (show [MT (T1a,1),MT (T1b,3)]) :: [MyType]
   [MT (T1a,1),MT (T1b,3)]

(if necessary, you could have 'show' embed a type representation 
for the hidden type, and dispatch on that representation in 'read')


claus

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


Re: [Haskell-cafe] Evaluation of IO actions in record assignment

2007-07-09 Thread haskell

Try liftM3 from Control.Monad

let get = xmlGetWidget xml castToEntry

liftM3 UserPanel (get signatureEntry) (get passwordEntry) (get 
repeatEntry)


Adde wrote:

Hi.
I'm toying around with GTK2Hs and one of the things I'm doing 
is stuffing a bunch of widgets in a record. 
The problem is that the function that fetches a widget from the 
Glade file returns IO Widget while my structure contains Widget's.
The best I've come up with is simply evaluating the actions by 
putting the result in temporaries and then building the record. 
Is there an easier way to accomplish this?


signatureEntry - xmlGetWidget xml castToEntry signatureEntry
passwordEntry - xmlGetWidget xml castToEntry passwordEntry
repeatEntry - xmlGetWidget xml castToEntry repeatEntry
return UserPanel {userPanelSignatureEntry = signatureEntry,
  userPanelPasswordEntry = passwordEntry,
  userPanelRepeatEntry = repeatEntry}

Thanks,
Adde

___
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] Constraints on data-types, mis-feature?

2007-07-09 Thread Jonathan Cast
On Monday 09 July 2007, Daniil Elovkov wrote:
 Hello

 In the archives of haskell-cafe I found a mention of constraints on
 datatypes as a mis-feature of Haskell. In particular, that they're not
 propagated well. Can someone elaborate on that?

 Also, are they still considered a mis-feature with the emergence of GADTs ?

 If I have

 data GADT a where
...
Alt :: (a - b - c) - GADT a - GADT b - GADT c
...

 and I want to constrain all a, b, c.

 Would it be better to expose all of them as type vars, rather than
 constrain in-place? It would lead to a rather verbose code.

GADTs don't change anything (at least, not the last time I checked).  If you 
say

class C a where
  ...

data GADT a where
  ...
  Alt :: (C a, C b, C c) = (a - b - c) - GADT a - GADT b - GADT c
  ...

when you pattern match on Alt, the compiler finds the instances for C a and C 
b, but the constraint C c is ignored.  So constraints on data types work 
exactly the same way they always have, and the standard arguments against 
them all still work.  (Although now I think the status of this `feature' can 
be down-graded to wart: after all, if you say

newtype Id a = Id a
data GADT a where
  ...
  Alt :: (C a, C b, C c) = (a - b - c)
  - GADT (Id a) - GADT (Id b) - GADT (Id c)
  ...

pattern-matching on Alt introduces all three constraints into the current 
context. . .)

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Evaluation of IO actions in record assignment

2007-07-09 Thread Tillmann Rendel

Adde wrote:

signatureEntry - xmlGetWidget xml castToEntry signatureEntry
passwordEntry - xmlGetWidget xml castToEntry passwordEntry
repeatEntry - xmlGetWidget xml castToEntry repeatEntry
return UserPanel {userPanelSignatureEntry = signatureEntry,
  userPanelPasswordEntry = passwordEntry,
  userPanelRepeatEntry = repeatEntry}


Use one of the general monadic combinators given in Control.Monad:

liftM3 UserPanel (xmlGetWidget xml castToEntry signatureEntry)
 (xmlGetWidget xml castToEntry passwordEntry)
 (xmlGetWidget xml castToEntry repeatEntry)

or

return UserPanel
  `ap` xmlGetWidget xml castToEntry signatureEntry
  `ap` xmlGetWidget xml castToEntry passwordEntry
  `ap` xmlGetWidget xml castToEntry repeatEntry

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


Re: [Haskell-cafe] Haskell's prefix exprs

2007-07-09 Thread Stefan O'Rear
On Mon, Jul 09, 2007 at 03:55:52PM +0200, Christian Maeder wrote:
 Hi,

 I would like haskell to accept the following (currently illegal)
 expressions as syntactically valid prefix applications:

 f = id \ _ - []
 g = id let x = [] in x
 h = id case [] of [] - []
 i = id do []
 j = id if True then [] else []

 The rational is that expressions starting with a keyword should extend
 as far as possible (to the right and over several lines within their
 layout).

 In this case the above right hand sides (rhs) are unique juxtapositions
 of two expressions. (This extension should of course apply to more than
 two expressions, i. e. f a do [])

 Furthermore the above rhs are all valid if written as infix expressions:

 f = id $ \ _ - []
 g = id $ let x = [] in x
 h = id $ case [] of [] - []
 i = id $ do []
 j = id $ if True then [] else []

False.

f = runST $ do return ()

is a type error.

f = runST (do return ())

is legal.

So your proposal isn't as pointless as you think :)

 (In fact, maybe for haskell-prime $ could be changed to a keyword.)

 Does this pose any problems that I haven't considered?

Not that I know of.  Indeed, the status quo is a (minor) pain to parse,
and in my Haskell compiler project I *wanted* to implement your
proposal.

 I think only more (and shorter) illegal haskell programs will become legal.

 Cheers Christian

 Maybe someone else can work out the details for Haskell's grammar

Not hard at all.  In http://haskell.org/onlinereport/syntax-iso.html,
change:

exp^10 -  \ apat[1] ... apat[n] - exp (lambda abstraction, n=1)
   |   let decls in exp (let expression)
   |   if exp then exp else exp (conditional)
   |   case exp of { alts } (case expression)
   |   do { stmts } (do expression)
   |   fexp
fexp   -  [fexp] aexp  (function application)

aexp   -  qvar   (variable)
   |   gcon   (general constructor)
   |   literal
   |   ( exp )(parenthesized expression)
   |   ( exp[1] , ... , exp[k] )  (tuple, k=2)
   |   [ exp[1] , ... , exp[k] ]  (list, k=1)
   |   [ exp[1] [, exp[2]] .. [exp[3]] ]  (arithmetic sequence)
   |   [ exp | qual[1] , ... , qual[n] ]  (list comprehension, n=1)
   |   ( exp^i+1 qop^(a,i) )  (left section)
   |   ( lexp^i qop^(l,i) )   (left section)
   |   ( qop^(a,i)[-] exp^i+1 ) (right section)
   |   ( qop^(r,i)[-] rexp^i )  (right section)
   |   qcon { fbind[1] , ... , fbind[n] } (labeled construction, 
n=0)
   |   aexp[qcon] { fbind[1] , ... , fbind[n] } (labeled update, n = 1)

to:

exp^10 -  [exp^10] aexp(function application)
aexp   -  \ apat[1] ... apat[n] - exp (lambda abstraction, n=1)
   |   let decls in exp (let expression)
   |   if exp then exp else exp (conditional)
   |   case exp of { alts } (case expression)
   |   do { stmts } (do expression)
   |   qvar   (variable)
   |   gcon   (general constructor)
   |   literal
   |   ( exp )(parenthesized expression)
   |   ( exp[1] , ... , exp[k] )  (tuple, k=2)
   |   [ exp[1] , ... , exp[k] ]  (list, k=1)
   |   [ exp[1] [, exp[2]] .. [exp[3]] ]  (arithmetic sequence)
   |   [ exp | qual[1] , ... , qual[n] ]  (list comprehension, n=1)
   |   ( exp^i+1 qop^(a,i) )  (left section)
   |   ( lexp^i qop^(l,i) )   (left section)
   |   ( qop^(a,i)[-] exp^i+1 ) (right section)
   |   ( qop^(r,i)[-] rexp^i )  (right section)
   |   qcon { fbind[1] , ... , fbind[n] } (labeled construction, 
n=0)
   |   aexp[qcon] { fbind[1] , ... , fbind[n] } (labeled update, n = 1)

All new ambiguities are resolved adequately by the let/lambda meta rule.

 (I've posted this message to glasgow-haskell-users before, but it
 applies to every Haskell implementation and should be discussed here.)

[EMAIL PROTECTED] would be even better.

Stefan


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


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

2007-07-09 Thread Philip Armstrong

On Mon, Jul 09, 2007 at 06:05:44PM +0200, Marc Weber wrote:


Another idea I've been pondering is allowing people to add links to
documentation for libraries, from their hackage page. We have a fair 
few libs documented in blog form, here,


Beeing able adding some comments (wiki style) would be cool.
This way we could add comments such like:
Have a look at ... which does the same thing but better.
Unmaintaned etc..


CPAN has something much like this, plus user ratings which together
with the comment system help sort through the endless perl extensions.

Phil

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


Re: [Haskell-cafe] More binary IO, compression, bytestrings and FFI fun

2007-07-09 Thread Philip Armstrong

On Mon, Jul 09, 2007 at 06:53:15PM +1000, Donald Bruce Stewart wrote:

phil:

On Mon, Jul 09, 2007 at 02:42:49PM +1000, Donald Bruce Stewart wrote:
Processing larger amounts of data, compression, serialisation and calling 
C.


Just a thought: is it worth sticking this up on the wiki?


   http://haskell.org/haskellwiki/Serialisation_and_compression_with_Data_Binary

:-)


I should have had more faith :)

Phil

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


Re: [Haskell-cafe] Haskell's prefix exprs

2007-07-09 Thread Isaac Dupree

Stefan O'Rear wrote:

On Mon, Jul 09, 2007 at 03:55:52PM +0200, Christian Maeder wrote:

Hi,

I would like haskell to accept the following (currently illegal)
expressions as syntactically valid prefix applications:

f = id \ _ - []
g = id let x = [] in x
h = id case [] of [] - []
i = id do []
j = id if True then [] else []


I agree.  The only (minor) concern I have is: that syntax is hard to 
read (by humans) without syntax-hilighting of keywords.


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


Re: [Haskell-cafe] Toy compression algorithms [was: A very edgy language]

2007-07-09 Thread Andrew Coppin

Bulat Ziganshin wrote:

Hello Andrew,

Sunday, July 8, 2007, 7:07:59 PM, you wrote:

i don't think that ppm is so complex - it's just probability of
symbol in some context. it's just too slow in naive implementation

  


Oh, sure, the *idea* is simple enough. Trying to actually *implement* it 
correctly is something else... ;-)


(Same statemenst go for arithmetic coding, really.)

(The downside of course is that now we need a Huffman table in the 
output - and any rare symbols might end up with rather long codewords.
But remember: Huffman *guarantees* 0% compression or higher on the 
payload itself. A Huffman-compressed payload can *never* be bigger, only
smaller or same size. So long as you can encode the Huffman table 
efficiently, you should be fine...)



the devil in details. just imagine size of huffman table with 64k
entries :)  huffman encoding is inappropriate for lzw output simply
because most words will have only a few occurrences and economy on
their optimal encoding doesn't justify price of their entries in the table
  


...which is why you need to encode the Huffman table efficiently, to 
quote myself. ;-)


Using canonical Huffman, you only actually need to know how many bits 
were assigned to each symbol. This information is probably very 
ameanable to RLE. (Which, incidentally, is why I started this whole 
parser on top of a phaser crazyness in the first place.) So, yeah, 
there may be 64k symbols - but if only 1k of them are ever *used*... ;-)



.ru = Russia?



of course
  


My Russian is very rusty. ;-)


Oh hey, I think GHC is already pretty smart. But no optimiser can ever
hope to cover *every* possible case. And transforming [Bool] - [Bool]
into UArray Word8 - UArray Word8 just seems a little bit
optimistic, methinks. ;-)



15 years ago i've written very smart asm program (btw, it was ARJ
unpacker) with handmade function inlining, loop unrolling, register
allocation, cpu recognition and so on. now, most of these tricks are
standard for C compilers. times changes and now it's hard to imagine which
optimizations will be available 10 years later
  


Yes, but there are limits to what an optimiser can hope to accomplish.

For example, you wouldn't implement a bubble sort and seriously expect 
the compiler to be able to optimise that into a merge sort, would you? ;-)



ghc's native and via-C modes are blind vs lame. in native mode, its
codegenerator is comparable with 20 years-old C codegenerators. see
above how much modern C compilers changed in these years. in via-C
mode it generates unnatural C code which is hard to optimize for any C
compiler.


I'll take your word for it. ;-)

(I have made cursory attempts to comprehend the inner workings of GHC - 
but this is apparently drastically beyond my powers of comprehension.)



the jhc is very different story


Yes - last I heard, it's an experimental research project rather than a 
production-ready compiler...


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


Re: [Haskell-cafe] Type system madness

2007-07-09 Thread Stefan O'Rear
On Mon, Jul 09, 2007 at 09:05:55PM +0100, Andrew Coppin wrote:
 OK, can somebody explain to me *really slowly* exactly what the difference 
 between an existential type and a rank-N type is?

 (I couldn't find much of use on the wiki. I have now in fact written some 
 stuff there myself, but since I don't understand it in the first place, I'm 
 having difficulty trying to explain it to anybody else...)

There isn't really such a thing as existential types.  Rank-N types
exist, but they are more of an implementation detail.

All users should worry about is Quantifiers.

A quantifier is an operator on types which defines a variable in some
way.

id has type :: ∀α. α → α

This means that id has type Int → Int, Bool → Bool, [Char] → [Char], etc
etc etc.  FOR ALL

toUpper (can) have type :: ∃α. α → α

toUpper has ONE of Int → Int, Char → Char, etc etc etc.  a type α EXISTS
such that toUpper has type α → α.  Yes, I know toUpper has a more
specific type - bare with me, it was the best example I could think of.

If you're at all familiar with mathematics logic, don't hesistate to
apply your intuitions about forall and exists - type systems and logics
really are the same things.

If you have a value of existential type, you can only do things with it
that you can do with any type, because you don't know the actual type.
Existential types hide information from the users.

If you have a value of universal type, you can do things with it as if
it had any matching type of your choice, because it doesn't know and
can't care about the actual use type.  Universal types hide information
from the implementors.

In Haskell 98, existential quantification is not supported at all, and
universal quantification is not first class - values can have universal
types if and only if they are bound by let.  You cannot pass universally
typed values to functions.

Stefan


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


Re: [Haskell-cafe] Toy compression algorithms [was: A very edgy language]

2007-07-09 Thread Stefan O'Rear
On Mon, Jul 09, 2007 at 09:15:07PM +0100, Andrew Coppin wrote:
 Bulat Ziganshin wrote:
 Hello Andrew,

 Sunday, July 8, 2007, 7:07:59 PM, you wrote:

 i don't think that ppm is so complex - it's just probability of
 symbol in some context. it's just too slow in naive implementation

   

 Oh, sure, the *idea* is simple enough. Trying to actually *implement* it 
 correctly is something else... ;-)

Took me about an hour and 50 lines of code (about a year ago - this was
one of my first Haskell programs) to implement a PPM (de)compressor that
didn't crash, always generated the same output as input, and achieved
50% ratios on its own source code (not quite as good as gzip, but what
do you expect from a completely untuned compressor?).

Peak throughput: 2 bits / sec. :)

 the jhc is very different story

 Yes - last I heard, it's an experimental research project rather than a 
 production-ready compiler...

Correct.  It requires 5 minutes and 600MB of RAM to compile Hello,
World, and fails with internal pattern match errors on anything
significantly larger.

Stefan


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


[Haskell-cafe] Type system madness

2007-07-09 Thread Andrew Coppin
OK, can somebody explain to me *really slowly* exactly what the 
difference between an existential type and a rank-N type is?


(I couldn't find much of use on the wiki. I have now in fact written 
some stuff there myself, but since I don't understand it in the first 
place, I'm having difficulty trying to explain it to anybody else...)


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


Re: [Haskell-cafe] reading existential types

2007-07-09 Thread Claus Reinke

 which is the important hint! the parser used for 'read' depends on
 the return type, but the existential type _hides_ the internal type
 which would be needed to select a read parser.


forall e . (MyClass e, Show e, Read e) = MT (e,Int)


the 'Read' there ensures that we only inject types that have a reader,
but it doesn't help us select one of the many possible types which
have such a reader.


readMT :: ReadPrec MyType
readMT = prec 10 $ do
   Ident MT - lexP
   parens $ (do { m - readPrec; return (MT (m::(TipoA,Int))) })
`mplus` (do { m - readPrec; return (MT (m::(TipoB,Int))) })


The problem is that I was trying to find a way to define the class
(MyClass) and not writing a parser for every possible type (or even
using their show-representation): I wanted a polymorphic list of types
over which I could use the method defined for their class, but, as far
as I can get it, this is not possible.


i'm not sure i understand the problem correctly, but note that the branches
in 'readMT' have identical implementations, the only difficulty is instantiating
them at different hidden types, so that they try the appropriate 'Read' 
instances for those types. there's no need for different parsers beyond 
the 'Read' instances for every possible type.


hiding concrete types in existentials sometimes only defers problems
instead of solving them, but exposing class interfaces instead of types 
is a useful way to mitigate that effect. it just so happens that this 
particular problem, reading an existential type, slightly exceeds that 
pattern, as 'read' needs to know the hidden type to do its job ('read' 
does not determine the type from the input form, but uses the type 
to determine what form.the input should have). 

a workaround is to try to read all possible types, then hide the type 
again once a match is found. the main disadvantage of this method 
is that we need a list of all the types that could possibly be hidden

in 'MyType' (or at least a list of all the types that we expect to
find hidden in 'MyType' when we read it).

we can, however, abstract out that list of types, and write a general
type-level recursion to try reading every type in such a list:

 class ReadAsAnyOf ts ex -- read an existential as any of hidden types ts
   where readAsAnyOf :: ts - ReadPrec ex

 instance ReadAsAnyOf () ex
   where readAsAnyOf ~() = mzero

 instance (Read t, Show t, MyClass t, ReadAsAnyOf ts MyType) 
   = ReadAsAnyOf (t,ts) MyType

   where readAsAnyOf ~(t,ts) = r t `mplus` readAsAnyOf ts
   where r t = do { m - readPrec; return (MT (m `asTypeOf` (t,0))) }

 -- a list of hidden types
 hidden = undefined :: (TipoA,(TipoB,()))

 readMT :: ReadPrec MyType
 readMT = prec 10 $ do
Ident MT - lexP
parens $ readAsAnyOf hidden -- r T1a `mplus` r T1b


Thanks for your kind attention.


you're welcome!-) reading existentials (or gadts, for that matter) 
is an interesting problem. sometimes too interesting..


claus

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


Re: [Haskell-cafe] Toy compression algorithms [was: A very edgy language]

2007-07-09 Thread Andrew Coppin

Stefan O'Rear wrote:

On Mon, Jul 09, 2007 at 09:15:07PM +0100, Andrew Coppin wrote:
  
Oh, sure, the *idea* is simple enough. Trying to actually *implement* it 
correctly is something else... ;-)



Took me about an hour and 50 lines of code (about a year ago - this was
one of my first Haskell programs) to implement a PPM (de)compressor that
didn't crash, always generated the same output as input, and achieved
50% ratios on its own source code (not quite as good as gzip, but what
do you expect from a completely untuned compressor?).
  


...aren't you one of those insanely intelligent people working on GHC? :-P

Actually, I wrote a working compressor in JavaScript. (You know, as an 
interactive web page. No, I don't still have it...) At least, I presume 
it works... I never had occasion to try to decompress the output! (I 
remember it had no underflow handling though...)


Now, writing one that works in binary rather than decimal, and isn't 
absurdly inefficient? (I.e., it *doesn't* work by converting every thing 
to decimal strings, jiggling the characters around, and then parsing 
back to machine integers.) That is something I haven't managed yet...



Peak throughput: 2 bits / sec. :)
  


How fast can you click buttons? That was mine's peak output. ;-)


the jhc is very different story
  
Yes - last I heard, it's an experimental research project rather than a 
production-ready compiler...



Correct.  It requires 5 minutes and 600MB of RAM to compile Hello,
World, and fails with internal pattern match errors on anything
significantly larger.
  


Ouch. That's pretty advanced... :-D

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


Re: [Haskell-cafe] Type system madness

2007-07-09 Thread Andrew Coppin

Stefan O'Rear wrote:

All users should worry about is Quantifiers.

A quantifier is an operator on types which defines a variable in some
way.
  


OK...


id has type :: ∀α. α → α

toUpper (can) have type :: ∃α. α → α
  


So... you're saying that id:: x - x works for *every* possible choice 
of x, but toUpper :: x - x works for *one* possible choice of x?


(BTW... How in the hell do you get symbols like that in plain ASCII??)


If you're at all familiar with mathematics logic, don't hesistate to
apply your intuitions about forall and exists - type systems and logics
really are the same things.
  


I have wide interests in diverse areas of science, mathematics and 
computing, covering everything from cryptology to group theory to data 
compression - but formal logic is something I've never been able to bend 
my mind around. :-(



If you have a value of existential type, you can only do things with it
that you can do with any type, because you don't know the actual type.
Existential types hide information from the users.

If you have a value of universal type, you can do things with it as if
it had any matching type of your choice, because it doesn't know and
can't care about the actual use type.  Universal types hide information
from the implementors.
  


I stand in awe of people who actually understand what universal and 
existential actually mean... To me, these are just very big words that 
sound impressive.


So, are you saying that if x is existential, it must work for any 
possible x, but if x is universal, I can choose what x is?



In Haskell 98, existential quantification is not supported at all, and
universal quantification is not first class - values can have universal
types if and only if they are bound by let.  You cannot pass universally
typed values to functions.
  


Erm...

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


Re: [Haskell-cafe] In-place modification

2007-07-09 Thread Stefan O'Rear
On Mon, Jul 09, 2007 at 10:01:06PM +0100, Andrew Coppin wrote:
 Bulat Ziganshin wrote:
 Hello Andrew,

 Monday, July 9, 2007, 12:36:25 AM, you wrote:
   
 OK. So that's just the GHC binary itself, right?
 

 it's INSTALLER
   

 Ah. That explains the size then...

 Is it safe to install two versions of GHC at once? :-.

Certainly.  I have no less than twelve.

[EMAIL PROTECTED]:~$ ls -l /usr/bin/ghc-6* /usr/local/bin/ghc-6*
lrwxrwxrwx 1 root root   30 2007-05-26 08:50 /usr/bin/ghc-6.6.1 - 
../lib/ghc-6.6.1/bin/ghc-6.6.1
-rwxr-xr-x 1 root staff 385 2006-12-24 13:43 /usr/local/bin/ghc-6.4.2
-rwxr-xr-x 1 root staff 145 2007-01-13 16:52 /usr/local/bin/ghc-6.7
-rwxr-xr-x 1 root staff 172 2007-02-13 18:20 /usr/local/bin/ghc-6.7.20070213
-rwxr-xr-x 1 root staff 172 2007-02-24 01:29 /usr/local/bin/ghc-6.7.20070223
-rwxr-xr-x 1 root staff 172 2007-03-25 19:53 /usr/local/bin/ghc-6.7.20070323
-rwxr-xr-x 1 root staff 172 2007-04-01 14:04 /usr/local/bin/ghc-6.7.20070402
-rwxr-xr-x 1 root staff 172 2007-04-14 10:35 /usr/local/bin/ghc-6.7.20070413
-rwxr-xr-x 1 root staff 172 2007-05-02 18:46 /usr/local/bin/ghc-6.7.20070502
-rwxr-xr-x 1 root staff 172 2007-05-19 16:01 /usr/local/bin/ghc-6.7.20070518
-rwxr-xr-x 1 root staff 172 2007-06-02 23:41 /usr/local/bin/ghc-6.7.20070601
-rwxr-xr-x 1 root staff 144 2007-06-12 20:20 /usr/local/bin/ghc-6.7.20070612

The worst problem that comes of this is a slow loss of disk space, but
I don't think I'll ever be able to fill this 80G disk :) 

Stefan


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


Re: [Haskell-cafe] Type system madness

2007-07-09 Thread Stefan O'Rear
On Mon, Jul 09, 2007 at 09:57:14PM +0100, Andrew Coppin wrote:
 Stefan O'Rear wrote:
 id has type :: ∀α. α → α

 toUpper (can) have type :: ∃α. α → α
   

 So... you're saying that id:: x - x works for *every* possible choice of 
 x, but toUpper :: x - x works for *one* possible choice of x?

[JonCast answered this one]

 (BTW... How in the hell do you get symbols like that in plain ASCII??)

You can't, but the most commonly used replacement for ASCII
(Unicode-UTF8) supports them just fine.  As for actually *entering* the
characters, I have a file with the code numbers of the characters I use
most often:

039B Λ big lambda
03BB λ little lambda
2203 ∃ existensial quant
2200 ∀ universal quant
2192 → right arrow
03B2 β beta
22A5 ⊥ bottom
00F6 ö o-umlaut

(alpha isn't on there, but I guessed (correctly) it would be right
before beta)

 If you're at all familiar with mathematics logic, don't hesistate to
 apply your intuitions about forall and exists - type systems and logics
 really are the same things.
   

 I have wide interests in diverse areas of science, mathematics and 
 computing, covering everything from cryptology to group theory to data 
 compression - but formal logic is something I've never been able to bend my 
 mind around. :-(

Don't worry - you can understand the material equally well from either
direction.  Personally I didn't really understand logic until seeing
type systems and then the Curry-Howard isomorphism (types are
propositions, programs are proofs).

 If you have a value of existential type, you can only do things with it
 that you can do with any type, because you don't know the actual type.
 Existential types hide information from the users.

 If you have a value of universal type, you can do things with it as if
 it had any matching type of your choice, because it doesn't know and
 can't care about the actual use type.  Universal types hide information
 from the implementors.
   

 I stand in awe of people who actually understand what universal and 
 existential actually mean... To me, these are just very big words that 
 sound impressive.

 So, are you saying that if x is existential, it must work for any possible 
 x, but if x is universal, I can choose what x is?

[JonCast answered this one]

 In Haskell 98, existential quantification is not supported at all, and
 universal quantification is not first class - values can have universal
 types if and only if they are bound by let.  You cannot pass universally
 typed values to functions.
   

 Erm...

Consider the ST monad, which lets you use update-in-place, but is
escapable (unlike IO).  ST actions have the form:

ST s α

Meaning that they return a value of type α, and execute in thread s.
All reference types are tagged with the thread, so that actions can only
affect references in their own thread.

Now, the type of the function used to escape ST is:

runST :: ∀ α. (∀ s. ST s α) → α

The action you pass must be universal in s, so inside your action you
don't know what thread, thus you cannot access any other threads, thus
runST is pure.  This is very useful, since it allows you to implement
externally pure things like in-place quicksort, and present them as pure
functions ∀ e. Ord e ⇒ Array e → Array e; without using any unsafe
functions.

But that type of runST is illegal in Haskell-98, because it needs a
universal quantifier *inside* the function-arrow!  In the jargon, that
type has rank 2; haskell 98 types may have rank at most 1.

Stefan


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


Re: [Haskell-cafe] Type system madness

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

Andrew Coppin wrote:
I stand in awe of people who actually understand what universal and 
existential actually mean... To me, these are just very big words that 
sound impressive.


I offer to relieve that with http://www.vex.net/~trebla/allsome.txt

I think of formal logic as clarifying thought and semantics, cleaning up 
the mess caused by idiosyncracies in natural languages (both syntax and 
semantics) such as English. But not many people realize they are in a 
mess needing cleanup.


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


[Haskell-cafe] no-coding functional data structures via lazyness

2007-07-09 Thread Dave Bayer
Learning Haskell, the Prelude.ShowS type stood out as odd, exploiting  
the implementation of lazy evaluation to avoid explicitly writing an  
efficient concatenable list data structure. This felt like cheating,  
or at least like using a screwdriver as a crowbar, to be less  
judgmental.


Recently I was playing with prime sieves and various heap data  
structures, while rereading Chris Okasaki's Purely Functional Data  
Structures, and it dawned on me:



merge xs@(x:xt) ys@(y:yt) = case compare x y of
LT - x : (merge xt ys)
EQ - x : (merge xt yt)
GT - y : (merge xs yt)

diff xs@(x:xt) ys@(y:yt) = case compare x y of
LT - x : (diff xt ys)
EQ - diff xt yt
GT - diff xs yt

merge' (x:xt) ys = x : (merge xt ys)

primes = ps ++ (diff ns $ foldr1 merge' $ map f $ tail primes)
where ps  = [2,3,5]
  ns  = [7,9..]
  f p = [ m*p | m - [p,p+2..]]


The code is very fast for its size; I haven't seen Haskell code  
posted on the web that comes close, and it is faster than any of my  
other tries (I posted this code to http://www.haskell.org/haskellwiki/ 
Prime_numbers). Effectively, it steals a heap data structure out of  
thin air by exploiting the implementation of lazy evaluation. It  
would seem that GHC's core data structures are coded closer to the  
machine that anything I can write _in_ Haskell. So much for studying  
how to explicitly write a good heap!


So is there a name for this idiom, no-coding a classic data  
structure through lazy evaluation? Are there other good examples?


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


Re: [Haskell-cafe] no-coding functional data structures via lazyness

2007-07-09 Thread Jonathan Cast
On Monday 09 July 2007, Dave Bayer wrote:
 Learning Haskell, the Prelude.ShowS type stood out as odd, exploiting
 the implementation of lazy evaluation to avoid explicitly writing an
 efficient concatenable list data structure. This felt like cheating,
 or at least like using a screwdriver as a crowbar, to be less
 judgmental.

 Recently I was playing with prime sieves and various heap data
 structures, while rereading Chris Okasaki's Purely Functional Data

 Structures, and it dawned on me:
  merge xs@(x:xt) ys@(y:yt) = case compare x y of
  LT - x : (merge xt ys)
  EQ - x : (merge xt yt)
  GT - y : (merge xs yt)
 
  diff xs@(x:xt) ys@(y:yt) = case compare x y of
  LT - x : (diff xt ys)
  EQ - diff xt yt
  GT - diff xs yt
 
  merge' (x:xt) ys = x : (merge xt ys)
 
  primes = ps ++ (diff ns $ foldr1 merge' $ map f $ tail primes)
  where ps  = [2,3,5]
ns  = [7,9..]
f p = [ m*p | m - [p,p+2..]]

 The code is very fast for its size; I haven't seen Haskell code
 posted on the web that comes close, and it is faster than any of my
 other tries (I posted this code to http://www.haskell.org/haskellwiki/
 Prime_numbers). Effectively, it steals a heap data structure out of
 thin air by exploiting the implementation of lazy evaluation. It
 would seem that GHC's core data structures are coded closer to the
 machine that anything I can write _in_ Haskell. So much for studying
 how to explicitly write a good heap!

 So is there a name for this idiom, no-coding a classic data
 structure through lazy evaluation? Are there other good examples?

I think we usually call it `exploiting laziness'. . .

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] xkcd #287 NP-Complete

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

http://xkcd.com/c287.html

import Data.Array
import Control.Monad

-- exactly n v
-- items in v that sum to exactly n
-- returns list of solutions, each solution list of items
exactly :: (Real a) = a - Array Int a - [[a]]
exactly 0 v = return []
exactly n v = do
  i - indices v
  guard (v!i = n)
  liftM (v!i :) (exactly (n - v!i) (v `without` i))
-- for solutions that use items multiple times,
-- change (v `without` i) to v

-- v `without` i
-- new array like v except one shorter with v!i missing
without :: Array Int a - Int - Array Int a
without v i = ixmap (lo, hi-1) f v
where (lo, hi) = bounds v
  f j | j = i = j+1
  | otherwise = j

play = exactly 1505 menu
menu = listArray (1,6) [215, 275, 335, 355, 420, 580]

test = exactly 10 (listArray (1,5) [1,1,2,3,4])

It disappoints me that there is no solution if each item is used at most 
once. However, do change the code to allow multiple uses, then there are 
many solutions.

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


[Haskell-cafe] ANNOUNCE: HCL v1.0 -High-level library for building command line interfaces

2007-07-09 Thread Justin Bailey

I'm please to announce HCL 1.0 - a library for building command line
interfaces. The library exports a mix of low and high-level functions
for building programs which gather simple values, ask yes/no
questions, or present hierarchical menus. The library is not intended
to do complex, full-screen UIs ala ncurses - it is intended for
line-oriented interfaces.

Included with the library is a hangman game, so if nothing else you
can enjoy that.

Where do I get it?
=

Download from Hackage at:

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

How do I use it it?
=

It's Cabal-ized so, after downloading and unpacking:

 runghc Setup.hs configure
 runghc Setup.hs build
 runghc Setup.hs install

Note I had some inconsistent results building with HEAD cabal, but the
version distributed with GHC works great (1.1.6.2).

To play hangman, execute 'hangman'. Once installed, you can look at it
in GHCi by loading the HCL module.

Tell me more!
==

This library lets you do a lot of cool things. For example, here's a
simple guess a number game:

guess_num_fun =
  do
target - reqIO $ getStdRandom (randomR (1::Integer,100))
let guessed val =
  case compare target val of
GT - do { reqIO $ putStrLn Too low!; return False }
LT - do { reqIO $ putStrLn Too high!; return False }
EQ - do { reqIO $ putStrLn You win!; return True }
reqUntil guessed (prompt Enter a number between 1 and 100: 
reqInteger)

reqUntil takes a predicate and asks for a response until the
predicate is true. In the case above, the user is asked to enter an
integer. Once they guess the number, the program ends.

The library makes it easy to gather structured values. For example,
imagine this data structure:

 data Taxpayer = Taxpayer { name :: String, age :: Int, ssn :: String }
deriving (Read, Show)

One way to use HCL to get Taxpayer values from the user is to take
advantage of its Read instance:

reqTaxpayer :: Request Taxpayer
reqTaxpayer = prompt Please enter tax payer information:  (reqRead reqResp)

But that is ugly because the user has to type a Read-able string:

 getTaxpayer reqTaxpayer
Please enter tax payer information: Taxpayer {name=John, age = 30, ssn =  }

However, we can build a form of sorts and make life much easier for the user:

reqTaxpayerEasy :: Request Taxpayer
reqTaxpayerEasy =
  do
name - prompt Please enter the tax payer's name:  reqResp
age - prompt Please enter their age:  reqInt
ssn - prompt What is their SSN/ASN:  reqResp
return (Taxpayer name age ssn)

Which looks like this:

 getTaxpayer reqTaxpayerEasy
Please enter the tax payer's name: Bob
Please enter their age: 50
Please enter their SSN/ASN: 111-11-

The library also makes simple hierarchical menus easy to build. The
below defines the menu structure for a hypothetical PIM:

  reqMenu $
  reqSubMenu topMenu Manage contacts manageContactsMenu $
  reqSubMenu topMenu Manage calendar
(reqMenuItem Add an event ... $
  ...
  reqMenuExit Return to previous menu
  reqMenuEnd) $
  -- End the menu definition
  reqMenuEnd

-- Defines a partial menu
manageContactsMenu =
  reqMenuItem Add a contact ... $
  ...
  reqMenuExit Return to previous menu
  reqMenuEnd

These and more examples are distributed with the library in the
examples directory.

Anything else?
===

Feedback, praise and criticism are welcome. Feedback regarding
'idiomatic' usage is especially desired. This is a first for me so any
responses are appreciated.

The library was developed on Windows using GHC - please let me know of
any odd *nix and Hugs bugs.

This library was inspired in part by the Ruby HighLine library
(http://highline.rubyforge.org/).  Many thanks Mark Jones for his
input on HCL's design and implementation.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Testing parsing failures with Parsec

2007-07-09 Thread Sean Smith
All -
I tried emailing this to Daan, but I can't find an up-to-date
email address, so I hope this is an acceptable alternative :).  I'm
looking for someone who knows the guts of Parsec a bit, or has done some
automated testing of a Parsec parser.

I'm interested in using Parsec for a number of projects, so I'm
giving it a try.  So far, it has really served me well.  However, I've
run into an issue with testing for proper parsing failures.  As an
example, I've been parsing a simplified version of scheme's
s-expressions.  When parsing (1 2n3), I expect a parse error
unexpected \n\.  Therefore, I've made a test case which attempts to
inspect the resulting ParseError to make sure it's correct.  However,
I'm confused by this list of Messages:

[SysUnExpect \n\,SysUnExpect \n\,Expect space,Expect \)\]

Why is SysUnExpect \n\ in the list twice?  I can't figure that out
from looking over the source for Parsec.  It seems like the following
rules should hold, but I can't be sure:
1) There should only be one occurrence of SysUnExpect *or* UnExpect in
the list
2) UnExpect is only used for an unexpected reserved word or operator,
and SysUnExpect is used for parse errors
3) There can be any number of Expect in the list, which indicate what
was expected to occur in the stream

If the above rules are correct, I was thinking it might make more sense
to use a type with more structure than a list to hold those data.

Also, the fact that neither Message nor ParseError derives Eq makes it
difficult to test values of those types.  Why not derive Eq?

Finally, do you have any suggestions as to how I might better test for
correct parse errors from Parsec?

Thanks very much for your help!

- Sean Smith

P.S. I'm more than willing to dig into the Parsec source and provide
patches for any changes I might make, if someone will accept them!

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


Re: [Haskell-cafe] Type system madness

2007-07-09 Thread David Menendez

On 7/9/07, Andrew Coppin [EMAIL PROTECTED] wrote:

OK, can somebody explain to me *really slowly* exactly what the
difference between an existential type and a rank-N type is?


One important difference is that Hugs supports existential
quantification, but not rank-N types. (It does support rank-2 types,
which are more common.)

The ExistentialQuantification and PolymorphicComponents extensions
have to do with what's allowed when defining datatypes.

The ExistentialQuantification extension allows you to define datatypes
like this:

   data Stream a = forall b. MkStream b (b - a) (b - b)
   s_head (Stream b h t) = h b
   s_tail (Stream b h t) = Stream (t b) h t

A Stream has a seed of SOME type, and functions which get the current
element or update the seed.

The type of MkStream is a rank-1 type:

   MkStream :: forall a b. b - (b - a) - (b - b) - Stream a

(Normally, the forall a b. would be implicit, because it's always at
the beginning for rank-1 types, and Haskell can distinguish type
variables from constructors.)

A destructor for Stream would have a rank-2 type:

   unMkStream :: forall a w. (forall b. b - (b - a) - (b - b) -
w) - Stream a - w
   unMkStream k (Stream b h t) = k b h t

(The destructor illustrates how pattern-matching works. either and
maybe are examples of destructors in the Prelude.)

Functions which look inside the MkStream constructor have to be
defined for ALL possible seed types.

--

PolymorphicComponents (a.k.a. universal quantification) lets you use
rank 1 values as components of a datatype.

   data Iterator f = MkIterator
   { it_head :: forall a. f a - a
   , it_tail :: forall a. f a - f a
   }

An Iterator has two functions that return the head or tail of a
collection, which may have ANY type.

Now the constructor is rank 2:

   MkIterator :: forall f. (forall a. f a - a) - (forall a. f a -
f a) - Iterator f

The field selectors are rank 1:

   it_head :: forall f a. Iterator f - f a - a
   it_tail :: forall f a. Iterator f - f a - f a

And the destructor is rank 3:

   unMkIterator :: forall f w. ((forall a. f a - a) - (forall a. f
a - f a) - w) - Iterator f - w

It's rank 3, because the type forall a. f a - a is rank 1, and it's
the argument to a function (which is rank 2), that is the argument to
another function (which is rank 3).

Because Hugs only supports rank-2 polymorphism, it won't accept
unMkIterator. GHC's rank-N polymorphism means that it will, because it
will accept types of any rank.

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


[Haskell-cafe] Re: Evaluation of IO actions in record assignment

2007-07-09 Thread Adde
 Use one of the general monadic combinators given in Control.Monad:
 
 liftM3 UserPanel (xmlGetWidget xml castToEntry signatureEntry)
   (xmlGetWidget xml castToEntry passwordEntry)
   (xmlGetWidget xml castToEntry repeatEntry)
 
 or
 
 return UserPanel
`ap` xmlGetWidget xml castToEntry signatureEntry
`ap` xmlGetWidget xml castToEntry passwordEntry
`ap` xmlGetWidget xml castToEntry repeatEntry
 
Tillmann

Thanks!

The problem is i really like specifying which fields in the record are assigned
what. It's pretty easy to mess things up and for example assign the
password-entry to the signature-field using your examples.

Is there nothing I can do to xmlGetWidget to evaluate the actions when 
assigning?

return UserPanel {
  userPanelSignatureEntry = *magic* xmlGetWidget xml castToEntry 
signatureEntry,
  userPanelPasswordEntry = *magic* xmlGetWidget xml castToEntry passwordEntry,
  userPanelRepeatEntry = *magic* xmlGetWidget xml castToEntry repeatEntry}

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


[Haskell-cafe] Multiple instancing of functions with FFI

2007-07-09 Thread Lewis-Sandy, Darrell
I am having trouble exporting multiple instances of a polymorphic function
similar to the example in the Haskell 98 Foreign Function Interface 1.0
addendum (page 6).  My specific code is below:

---begin test.hs-

module Test() where

 

import Foreign

import Foreign.C

 

foreign export stdcall addByte (+):: Int8-Int8-Int8

foreign export stdcall addInt  (+):: Int16-Int16-Int16

foreign export stdcall addLong (+):: Int32-Int32-Int32

---end test.hs-

 

This somewhat contrived example should export three foreign implementations
of integer addition (one for each of 8, 16 and 32 byte integers).   I am
compiling to a Win 32 DLL with GHC 6.61 using the following set of commands:

 



ghc -c adder.hs -fglasgow-exts -ffi

ghc -c dllMain.c

ghc -static --mk-dll -optdll--def=test.def -o test.dll test.o test_stub.o
dllMain.o



 

where dllMain.c declares my entry point for the DLL, and is as follows

begin dllMain.c

#include windows.h

#include Rts.h

 

extern void __stginit_Adder(void);

 

static char* args[] = { ghcDll, NULL };

 

BOOL STDCALL DllMain ( HANDLE hModule, DWORD reason, void* reserved )

{

  if (reason == DLL_PROCESS_ATTACH) {

  startupHaskell(1, args, __stginit_Adder);

  return TRUE;

  }

 

  if (reason == DLL_PROCESS_DETACH) {

shutdownHaskell();

return TRUE;

  }

 

 

  return TRUE;

}

end dllMain.c

 

and I have declared the exported function names explicitly in test.def: 

---begin test.def-

EXPORTS

   addByte

   addInt

   addLong

end test.def

 

Upon compilation, I receive a long list of errors including things like
error:redefinition of 'stginit_export_Test_zdfzp' was here, etc.  Any help
would be appreciated.

 

Darrell

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


[Haskell-cafe] where's yi available?

2007-07-09 Thread Vadim
I'm trying to get 'hide' but failed to install 'yi'.

I followed instructions at page http://haskell.org/hawiki/hIDE_2fDesign but
can't succeed in executing

  darcs get http://scannedinavian.org/repos/yi/

the mentioned http isn't responding.

Can you please advise where can I get yi?

TIA.
Vadim.

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


Re: [Haskell-cafe] no-coding functional data structures via lazyness

2007-07-09 Thread Donald Bruce Stewart
bayer:
 Learning Haskell, the Prelude.ShowS type stood out as odd, exploiting  
 the implementation of lazy evaluation to avoid explicitly writing an  
 efficient concatenable list data structure. This felt like cheating,  
 or at least like using a screwdriver as a crowbar, to be less  
 judgmental.

See also
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/dlist-0.3

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


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

2007-07-09 Thread Donald Bruce Stewart
sascha.boehme:
 Hello,
 
  Who's our SoC hackage guy? To do list right here!
 
 The HackageDB project is for now concentrating on another subject. I see
 the necessity of adding search features and additionally tags, but in
 the moment I work on automatic generation of Haddock documentation.
 
 The progress and a to do list can be found from here:
 
   http://hackage.haskell.org/trac/summer-of-code/wiki/SoC2007Hackage
 
 A more complete ToDo list can be found here:
 
   http://hackage.haskell.org/trac/hackage/wiki/HackageToDo
   
 This also covers your wishes, and, as soon as automatic Haddock
 documentation is working, I'll turn towards that.

Great Sascha.

We often discuss how to improve hackage on the #haskell irc channel --
perhaps you could just idle there while you're doing your SoC project,
as there's quite a community of users there with ideas/questions about
hackage, and how to best use and improve it?

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


Re: [Haskell-cafe] where's yi available?

2007-07-09 Thread Stefan O'Rear
On Mon, Jul 09, 2007 at 08:43:03PM +0400, Vadim wrote:
 I'm trying to get 'hide' but failed to install 'yi'.
 
 I followed instructions at page http://haskell.org/hawiki/hIDE_2fDesign but
 can't succeed in executing

HaWiki is no longer used, has not been updated for months, and on the
FrontPage says Please consider this Wiki as out-of-date.

   darcs get http://scannedinavian.org/repos/yi/
 
 the mentioned http isn't responding.
 
 Can you please advise where can I get yi?

The Yi page on the new wiki (http://haskell.org/haskellwiki/Yi) specifies:

darcs get --partial http://darcs.haskell.org/yi/

Stefan


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


[Haskell-cafe] Data.ByteString.dropWhile

2007-07-09 Thread Thomas Conway

Hi All,

I notice that Data.ByteString has span and spanEnd. Is there a known
particular reason why dropWhile and takeWhile don't have corresponding
*End functions? If not, what is the protocol for adding them?

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

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


Re: [Haskell-cafe] Data.ByteString.dropWhile

2007-07-09 Thread Donald Bruce Stewart
drtomc:
 Hi All,
 
 I notice that Data.ByteString has span and spanEnd. Is there a known

and break/breakEnd.

 particular reason why dropWhile and takeWhile don't have corresponding
 *End functions? If not, what is the protocol for adding them?

There's no reason -- we couldn't decide on whether to support
'end/-right' versions of most traversals. To add them you'd implement
them, send the patch to Duncan and I, for inclusion in bytestring 1.0.

Duncan -- did we ever sort out a policy on the left/right normal/-end
versions of things? breakEnd I use all the time, but perhaps we should
fix upon what api we are to provide.

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


Re: [Haskell-cafe] Data.ByteString.dropWhile

2007-07-09 Thread Donald Bruce Stewart
drtomc:
 Well, maybe I shoud be asking a higher level question then.
 
 I have a function
 
 tidy = reverse . dropWhile punk . reverse . dropWhile punk
where
punk = isPunctuation . chr . fromIntegral
 
 which is leading to a significant amount of allocation, and you can see why.
 
 The way I'd like to write it is
 
 tidy = dropWhile punk . dropWhileEnd punk
where 
 
 which has the obvious advantage of avoiding quite a bit of
 intermediate allocation.
 
 Is there a another way?
 
 I note that since I'm using a nice declarative language, the compiler
 CLEARLY should be transforming the first form into the second. :-)

I'd just manually write a 'tidy' loop (in the Data.ByteString style) (which
would avoid all allocations), since it seems pretty useful.

Something in this style:

findIndexOrEnd :: (Word8 - Bool) - ByteString - Int
findIndexOrEnd k (PS x s l) =
 inlinePerformIO $ withForeignPtr x $ \f - go (f `plusPtr` s) 0
  where
go !ptr !n | n = l= return l
   | otherwise = do w - peek ptr
if k w
then return n
else go (ptr `plusPtr` 1) (n+1)

If its costly, since that'll make it non-costly.

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


Re: [Haskell-cafe] Data.ByteString.dropWhile

2007-07-09 Thread Bryan O'Sullivan

Donald Bruce Stewart wrote:


I'd just manually write a 'tidy' loop (in the Data.ByteString style) (which
would avoid all allocations), since it seems pretty useful.


That would indeed be very useful to have as a library function.  I've 
pined for Python's strip() string method (removes leading and trailing 
whitespace) for a while.


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


Re: [Haskell-cafe] no-coding functional data structures via lazyness

2007-07-09 Thread Dave Bayer


On Jul 9, 2007, at 6:52 PM, Donald Bruce Stewart wrote:


bayer:

Learning Haskell, the Prelude.ShowS type stood out as odd, exploiting
the implementation of lazy evaluation to avoid explicitly writing an
efficient concatenable list data structure.



See also
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ 
dlist-0.3


Thanks; I added a link to the dlist package from my discussion of  
this idiom on the Wiki page

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

On Jul 9, 2007, at 3:19 PM, Jonathan Cast wrote:

I think we usually call it `exploiting laziness'. . .


My motivation in asking for a name was to be able to find other  
Haskell one-liners adequately replacing chapters of data structure  
books for problems of modest scale, e.g. finding the 5,000,000th  
prime. So far, I know concatenable lists, and heaps.  Is there a Wiki  
page where someone teaches this principle for a dozen other classic  
data structures? Your one-liner made me laugh, but it didn't help  
me in googling, I would have preferred a one-liner teaching me  
another classic data structure, or an explanation of why burrowing  
into the GHC implementation gives such a speed advantage over a  
carefully written explicit data structure.


People in other camps don't really get lazy evaluation, even many  
of our ML neighbors. It would pay to communicate this better to the  
outside world.



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


Re: [Haskell-cafe] Data.ByteString.dropWhile

2007-07-09 Thread Roman Leshchinskiy

Thomas Conway wrote:

Well, maybe I shoud be asking a higher level question then.

I have a function

tidy = reverse . dropWhile punk . reverse . dropWhile punk
   where
   punk = isPunctuation . chr . fromIntegral

which is leading to a significant amount of allocation, and you can see 
why.


The way I'd like to write it is

tidy = dropWhile punk . dropWhileEnd punk
   where 

which has the obvious advantage of avoiding quite a bit of
intermediate allocation.

Is there a another way?

I note that since I'm using a nice declarative language, the compiler
CLEARLY should be transforming the first form into the second. :-)


The NDP library will implement this kind of fusion at some point 
(hopefully this year). We have a fairly clear idea of how to do it but 
not enough time.


Roman

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