[Haskell-cafe] advantages of using fix to define rcursive functions

2007-07-26 Thread Harald ROTTER

Hi,

I read about the usage of fix to define recursive functions. Although I
think that I understood how to use fix, I still wonder what the
advantages of fix are (as compared to the conventional approach to
define recursive functions).

Any hints are appreciated.

Thanks

Harald.



 Ce courriel et les documents qui y sont attaches peuvent contenir des 
informations confidentielles. Si vous n'etes  pas le destinataire escompte, 
merci d'en informer l'expediteur immediatement et de detruire ce courriel  
ainsi que tous les documents attaches de votre systeme informatique. Toute 
divulgation, distribution ou copie du present courriel et des documents 
attaches sans autorisation prealable de son emetteur est interdite. 

 This e-mail and any attached documents may contain confidential or 
proprietary information. If you are not the intended recipient, please advise 
the sender immediately and delete this e-mail and all attached documents from 
your computer system. Any unauthorised disclosure, distribution or copying 
hereof is prohibited.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] advantages of using fix to define rcursive functions

2007-07-26 Thread Donald Bruce Stewart
voigt:
 Donald Bruce Stewart wrote:
 harald.rotter:
 
 Hi,
 
 I read about the usage of fix to define recursive functions. Although I
 think that I understood how to use fix, I still wonder what the
 advantages of fix are (as compared to the conventional approach to
 define recursive functions).
 
 Any hints are appreciated.
 
 So actually, I suppose it is useful for small, anonymous recursive 
 definitions.
 
 It also exposes the recursive computation structure for direct
 manipulation, enabling one to perform certain program
 transformations/refactorings. Search for fixpoint fusion and fixed
 point promotion. While one might say: that's the business of a
 compiler, actually existing ones are not very sophisticated in that
 regard, so one might want to do such transformations by hand...

Oh, excellent point. Just as naming particular loop structures (such as
'map' or 'unfoldr') enable more precise optimisations, such as fusion,
so naming recursive functions saves the compiler some work discovering
the name. 

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


Re: [Haskell-cafe] Space usage and CSE in Haskell

2007-07-26 Thread Melissa O'Neill

Richard O'Keefe [EMAIL PROTECTED] wrote:
Another change to the order to give us MORE sharing takes less time  
AND less space.  The surprise is how much less time.


Interesting stuff. My students and I briefly chatted about powerset  
this morning and came up with the same function, but the very  
significant time differences you pointed out aren't something that  
shows up on a whiteboard, so thanks for all those timings.


The really scary thing about this example is that so much depends  
on the order in which the subsets are returned, which in many cases  
does not matter.


(I'm going a bit off main topic from Richard's (informative) post  
here, but hey...)


Saying something like let's improve space performance by doing it  
backwards and then reversing the list, while great in ML, won't  
(always) cut it in Haskell.  The need to preserve laziness/strictness  
can tie our hands.


For example, consider yet another variant of power_list:

power_list l = [] : pow [[]] l where
pow acc [] = []
pow acc (x:xs) = acc_x ++ pow (acc ++ acc_x) xs
   where acc_x = map (++ [x]) acc

By many standards, this version is inefficient, with plenty of  
appends and lots of transient space usage.


BUT, it generates the output in an order that'll accommodate infinite  
lists, thus we can say:


   power_list [1..]

(none of the other versions had this property -- they'd just die here)

So, the moral for optimizations is that any transformation we do to  
improve space performance shouldn't make our program stricter than it  
was before.  (I think the paper by David Sands and Joergen Gustavsson  
that Janis Voigtlaender mentioned covers this too, but I haven't had  
a chance to look at it closely yet.)


Melissa.

P.S.   For fun, I'll also note that yes, it *is* possible to code a  
lazy-list-friendly power_list function in a way that doesn't drag  
saved lists around, although it doesn't run as nearly as quickly as  
some of the others seen.


-- Count in binary and use that to create power set
power_list xs = loop zero where
   loop n = case select xs n of
Nothing  - []
Just set - set : loop (inc n)

   select xs []   = Just []
   select [] nat  = Nothing
   select (x:xs) (True:nat')  = select xs nat' = \l - Just (x:l)
   select (x:xs) (False:nat') = select xs nat'

   zero = []
   inc []   = [True]
   inc (False:bits) = True  : bits
   inc (True :bits) = False : inc bits

No doubt this can be coded better yet...

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


[Haskell-cafe] Re: advantages of using fix to define rcursive functions

2007-07-26 Thread Chung-chieh Shan
Harald ROTTER [EMAIL PROTECTED] wrote in article [EMAIL PROTECTED] in 
gmane.comp.lang.haskell.cafe:
 I read about the usage of fix to define recursive functions. Although I
 think that I understood how to use fix, I still wonder what the
 advantages of fix are (as compared to the conventional approach to
 define recursive functions).

You might enjoy this paper:

Bruce J. McAdam, 1997. That about wraps it up: Using FIX to handle
errors without exceptions, and other programming tricks. Tech. Rep.
ECS-LFCS-97-375, Laboratory for Foundations of Computer Science,
Department of Computer Science, University of Edinburgh.
http://www.lfcs.informatics.ed.ac.uk/reports/97/ECS-LFCS-97-375/

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
It is the first responsibility of every citizen to question authority.
Benjamin Franklin

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


RE: [Haskell-cafe] UTF-16

2007-07-26 Thread Bayley, Alistair
 From: [EMAIL PROTECTED] 
 [mailto:[EMAIL PROTECTED] On Behalf Of Donald 
 Bruce Stewart
 
 andrewcoppin:
  I don't know if anybody cares, but... Today a wrote some 
 trivial code to 
  decode (not encode) UTF-16.
  
  I believe somebody out there has a UTF-8 decoder, but I 
 needed UTF-16 as it happens.
 
 Perhaps you could polish it up, and provide it in a form suitable for
 use as a patch to:
 
 http://code.haskell.org/utf8-string/
 
 that is, put it in a module:
 
 Codec.Binary.UTF16.String
 
 and provide the functions:
 
 encode :: String - [Word8]
 decode :: [Word8] - String
 
 ? And then submit that as a patch to Eric, the utf8 maintainer.
 
 -- Don

There is a UTF16 en/decoder in Foreign.C.String (see cWcharsToChars 
charsToCWchars):
  http://darcs.haskell.org/libraries/base/Foreign/C/String.hs

but it only seems to be available for Windows users, via the CWSTring
functions.

In Takusen we also have a UTF8 module (it's about the fourth or fifth
out there, after HXML and John Meacham's, and someone else's - Graham
Klyne?, and one hidden away in GHC's internals). It has pure en/decode
functions (String - [Word8]), naturally (which we ripped off from John
Meacham), but we were more interested in efficient marshalling from
CStrings (or data buffers, if you like), so we wrote specific code to
marshall CString - String fairly quickly, and space efficiently (see
fromUTF8Ptr, which is wrapped by peekUTF8String{Len}):
  http://darcs.haskell.org/takusen/Foreign/C/UTF8.hs

We stuck it in the Foreign.C namespace, rather than Codec, because we're
doing more FFI related stuff. I'm not sure what the best location is;
perhaps there should be a split, with FFI functions (withUTF8String,
peekUTF8String) in Foreign.C, and pure functions in Codec.

(Also, is there a wiki page somewhere which gives advice as to how to
locate/name library modules, and what the currently occupied namespace
is, including user libs like those on Hackage? It's sometimes a bit
tricky to try to figure out where to put a new module.)

Obviously a proliferation of UTF8 modules isn't great for code re-use.
Is there a plan to consolidate and expose UTF8 and UTF16 de- and
encoders in the libraries? I note that the various UTF8 modules have
fairly similar implementations, and differ mainly w.r.t. how much of the
UTF8 codepoint space they handle (for example, HXML's decodes up to 6
bytes, which isn't strictly standards compliant). Also, some choice as
how to handle errors in the byte stream might be nice i.e. the user
could choose between functions which raise errors, or introduce
substition chars.

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] HDBC or HSQL

2007-07-26 Thread Bayley, Alistair
 From: [EMAIL PROTECTED] 
 [mailto:[EMAIL PROTECTED] On Behalf Of Donald 
 Bruce Stewart
 
 Does anyone know why Takusen isn't on hackage yet? It appears to be
 cabalised, and have a tarball:
 
 http://hackage.haskell.org/packages/archive/pkg-list.html#cat:Database
 http://darcs.haskell.org/takusen/


Simply because it's (yet) another thing that neither Oleg nor I have got
around to doing, or figuring out how/what to do. (Looking now...) Seems
pretty simple. I see there's just one option to cabal's sdist:
--snapshot. Can anyone tell me if I should use this or not? Does it
matter much?

BTW, an ODBC implementation for Takusen is in the pipeline. The latest
patches in our darcs repo include some ODBC modules, although they're
far from finished. There are still quite a few issues to sort out.

After ODBC I think a FreeTDS (http://www.freetds.org/) implementation
would be a good idea, as this ought to give native (i.e. not via ODBC)
access to both MS Sql Server and Sybase.

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] advantages of using fix to define rcursive functions

2007-07-26 Thread Donald Bruce Stewart
harald.rotter:
 
 Hi,
 
 I read about the usage of fix to define recursive functions. Although I
 think that I understood how to use fix, I still wonder what the
 advantages of fix are (as compared to the conventional approach to
 define recursive functions).
 
 Any hints are appreciated.
 

There's no obvious advantage that I know of, other than being cute.
An example from xmonad:

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

So actually, I suppose it is useful for small, anonymous recursive definitions.

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


Re: [Haskell-cafe] advantages of using fix to define rcursive functions

2007-07-26 Thread Jonathan Cast
On Thursday 26 July 2007, Harald ROTTER wrote:
 Hi,

 I read about the usage of fix to define recursive functions. Although I
 think that I understood how to use fix, I still wonder what the
 advantages of fix are (as compared to the conventional approach to
 define recursive functions).

As others have said, it allows you to define anonymous recursive functions 
(not necessarily small!).  FPers have traditionally advocated using lots of 
small, named, top-level functions, but I think it's amazing how much more 
readable code becomes when some of those single-use functions are inlined.  
You can't inline a recursive function, but you can inline an application of 
fix.

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


pgpmuHDVlwwsm.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Indentation woes

2007-07-26 Thread Nicolas Frisby

A bandaid suggestion:

longFunctionName various and sundry arguments = f where
f | guard1 = body1
f | guard2 = body2
  | ...
   where declarations

(Disclaimer: untested)

As I understand it, there can be guards on the definition of f even if
it takes no arguments. Those guards can reference your the various and
sundry arguments.

On 7/26/07, Stefan O'Rear [EMAIL PROTECTED] wrote:

On Thu, Jul 26, 2007 at 02:56:57PM -0400, anon wrote:
 Greetings,
 I wish to be able to indent my code like so:
 longFunctionName various and sundry arguments
 | guard1 = body1
 | guard2 = body2
 | ...
 where declarations
 That is, with guards and where clauses indented to the same level as
 the function name.

 This seems like a perfectly reasonable indentation style to me. It
 also happens to be the preferred style in Clean, another
 layout-sensitive functional language. I believe it is not uncommon in
 ML dialects as well. So why is it that I'm not allowed to use it in
 Haskell?

Because in Haskell everything that is lined up is a new logical line.
Haskell requires all continuation lines to be indented:

longFunctonName various and sundry arguments
 | guard1 = body1
 | guard2 = body2
 | ..
 where declarations

As for why, it's just a matter of Haskell Committee taste.  Nothing
too deep, just an arbitrary set of rules.

Stefan

-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)

iD8DBQFGqPS5FBz7OZ2P+dIRAgwbAKCl3ssl6X42VqSZJnhgKVH7WSzRXwCaA3x5
Ze0lGvx17IDrFXxBEvVxGeI=
=5/To
-END PGP SIGNATURE-

___
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] Indentation woes

2007-07-26 Thread Stefan O'Rear
On Thu, Jul 26, 2007 at 02:58:21PM -0500, Nicolas Frisby wrote:
 A bandaid suggestion:

 longFunctionName various and sundry arguments = f where
 f | guard1 = body1
 f | guard2 = body2
   | ...
where declarations

 (Disclaimer: untested)

 As I understand it, there can be guards on the definition of f even if
 it takes no arguments. Those guards can reference your the various and
 sundry arguments.

Eh?  Mine doesn't use up a where clause and doesn't use a f noise symbol.
Why do you need a band-aid?

longFunctionName\32=\n\32|\32guard\32=\32body\n\32|\32guard\32=\32body\n\32...

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: advantages of using fix to define rcursive functions

2007-07-26 Thread Nicolas Frisby

Another advantage here - an analog I'm always eager to point out - is
that just as we can augment functions if they haven't yet been fixed,
we can augment functors. One can extend datatypes and functions (a la
open functions) or generically generate constructs such as (co-)free
(co-)monads in this way.

On 7/26/07, Dan Piponi [EMAIL PROTECTED] wrote:

On 7/26/07, Nicolas Frisby [EMAIL PROTECTED] wrote:
 Trying to summarize in one phrase: you can do interesting
 manipulations to functions before applying fix that you cannot do to
 functions after applying fix (conventional functions fall in this
 second category).

Something similar holds for types where we can use something like

data Fix s a = In{out :: s a (Fix s a)}

to construct fixed points of functors, as opposed to functions. Any
recursive type can be expressed using Fix, so the question is, why
would you do it? Well, associated to every recursive type is a
corresponding fold and unfold, of which the familiar foldr and unfoldr
are special cases for the List type. If we define our types using Fix
of some functor, then we can also have fold and unfold built for us
automatically from the functor, alongside the actual type.

There are a number of papers that discuss this, including The Essence
of the Iterator Pattern by Jeremy Gibbons and Bruno C. d. S.
Oliveira.
--
Dan
___
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] Lazy in either argument?

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

Dan Weston wrote:

1) Commenting out the type annotation f :: Bool makes the program hang


Turning on code optimizations (e.g., ghc -O) helps. I don't know why.

2) If I replace f = f by f = undefined, I get an annoying print of 
LazyOr: Prelude.undefined before it returns the correct value.


The error message is a manifestation of an unhandled exception. Look for 
exception handling tools in Control.Exception and use one to your 
liking. You should do this to be very general anyway, since _|_ can be 
infinite loops or exceptions.


Beware that parallelizing the two arguments (making them compete) is 
still different from laziness in either argument. Laziness does not only 
include waiting less, but also includes leaving thunks untouched. 
Competition leads to waiting less certainly, but it also forces both 
thunks. A user may or may not want this.


That said, parallel disjunction is interesting in its own right, mainly 
because it restores the symmetry found in logical disjunction that has 
been lost in short-circuiting. There was a paper using it for 
programming language semantics, but I have long forgotten it.

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


Re: [Haskell-cafe] Identifier generators with QuickCheck

2007-07-26 Thread J. Pablo Fernández
Thank you Jonathan for your answer, it really helped me find the solution, 
which, just for the record, was:

correctLabelGenerator =
do s - choose (1, 63 :: Int)
   liftM2 (:) (elements validFirstChars) (replicateM (s - 1) (elements 
validChars))
where validFirstChars = ['a'..'z'] ++ ['A'..'Z']
  validChars = validFirstChars ++ _- ++ ['0'..'9']

Thank you.

On Tuesday 24 July 2007 14:55:33 Jonathan Cast wrote:
 On Tuesday 24 July 2007, J. Pablo Fernández wrote:
  Hello Haskellers,
 
  I want to make a QuickCheck generator that creates identifiers, basically
  [a-zA-Z] as the first character and then [a-zA-Z0-9-_] for a total of 63
  characters. So, I've got up to:
 
  do s - choose (1, 63 :: Int)
  elements validFirstChars
  where validFirstChars = ['a'..'z'] ++ ['A'..'Z']
validChars = validFirstChars ++ _- ++ ['0'..'9']
 
  which of course only gives me one random character. I want both, the
  characters, and the length to be random.

 do
n - choose (1, 63)
replicateM $ elements validFirstChars

 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



-- 
J. Pablo Fernández [EMAIL PROTECTED] (http://pupeno.com)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re : [Haskell-cafe] Indentation woes

2007-07-26 Thread Tillmann Rendel

Stefan O'Rear wrote:

Out of curiousity, what do you find objectionable about (legal):

function argument argument2
 | guard = body
 | guard = body

as compared to (currently illegal):

function argument argument2
| guard = body
| guard = body


I see the vertical strokes as visually lining up, pointing at something. 
In the legal example, they are pointing to the second character of the 
function name, wich has no meaning, but in the currently illegal 
example, they are pointing to the function name as a whole, wich has a 
meaning: To see wich function we are defining here, follow the vertical 
strokes upwards. (I don't need the strokes to show me that, of course, I 
just don't want them to distract me by pointing at a random position).


As I understand it, the idea behind layout is to use indention to 
express tree-like structures in plain text:


  root
first level node
  second level node
  another second level node
another first level node
  second level node in a different subtree

This is fine as long as no vertical strokes show up at the beginning of 
lines, since vertical strokes are sometimes used to express

tree-like structures in plain text, too:

  root
  | first level
  | | second level
  | | another second level node
  | another first level node
  | | second level node in a different subtree

The plain text parser embedded into my eyes seems to expect something 
like the latter tree encoding when it sees vertical strokes at the 
beginning of lines, but Haskell layout works more like the former.


To help my eyes, I try to write the whole pattern in a single line.

  function argument argument2 | guard1 = body1
  | guard2 = body2

If lines get too long this way, I wrap the body, not the pattern:

  function argument argument2 | guard1 =
  body1

  function argument argument2 | guard2 =
  body2

Of course, if I want to have local definitions visible to both bodies, I 
have to write something like this:


  function argument argument2 = result where
  result | guard1 = body1
  result | guard2 = body2
  helper = ...
  other_stuff = ...


I don't think this is a layout problem, I think this is a pattern syntax 
problem. (Or it may be a problem of my eyes). As I understand it, the 
layout rule is not made for stuff starting with keywords, but for stuff 
starting with identifiers, to avoid having to use keywords. But | is 
clearly a keyword here. So if I were to design it, I would try to get 
rid of the repeated | keyword, maybe allowing the running example to 
be written as


  function argument argument2 |
  guard1 = body1
  guard2 = body2

wich seems to be much clearer for my eyes. Another option would be

  function argument argument2 = guard1 - body1
  | guard2 - body2

wich is good because | now works like in data defintions, meaning 
alternatively, but bad because the pattern matching stops when 
crossing the equals sign-rule no longer holds.


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


Re: Re : Re : [Haskell-cafe] Indentation woes

2007-07-26 Thread Ian Lynagh
On Thu, Jul 26, 2007 at 08:17:06PM -0400, anon wrote:
 
 but one could likewise dismiss the entire layout business as a
 needlessly complicated way to save a few keystrokes if one were so
 inclined.

The main point of layout, in my eyes, is to make code more readable.
It achieves this both by removing noise (i.e. {;}) and by forcing you to
align your code so it is clear (or at least clear/er/) what is going on.

It's also important that the rules are easily understood by programmers,
and easily implemented by Haskell implementations and tools.

The current rules aren't perfect. For example, they fail the last point.
I thought there was a Haskell' ticket about that, but I can't see it
now.


Thanks
Ian

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


Re: Re : Re : [Haskell-cafe] Indentation woes

2007-07-26 Thread ok

Concerning


function argument argument2
| guard = body
| guard = body


I feel that anything that prevents that kind of horror is
a great benefit of the current rules and that this benefit
must not be lost by any revision of the rules.

The Fundamental Law of Indentation is
  If major syntactic unit X is a proper part of major syntactic
   unit Y, then every visible character of X is strictly to the
   right[%] of the leftmost[%] visible character of Y.
[%] If you are using a right-to-left script, switch left and
right in that sentence.

That is how indentation makes structure visible, and if you
break that, you just plain aren't indenting.  This isn't fuzzy,
and it isn't aesthetic, it's simply that if you start things in
the same column you are making it obvious to the reader than
neither is part of the other.  In the example about, that's not
true.  You might as well go around ending sentences with
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re : Re : [Haskell-cafe] Indentation woes

2007-07-26 Thread anon

2007/7/26, Stefan O'Rear [EMAIL PROTECTED]:

Out of curiousity, what do you find objectionable about (legal):

function argument argument2
 | guard = body
 | guard = body

as compared to (currently illegal):

function argument argument2
| guard = body
| guard = body


The extra space, obviously :-)
I'm well aware that this is an issue of vanishingly small consequence,
but one could likewise dismiss the entire layout business as a
needlessly complicated way to save a few keystrokes if one were so
inclined. If language complexity is the chief concern, why not
dispense with layout altogether (and a few more things beside)?
Perhaps fuzzy notions of aesthetics and intuitiveness should weigh
into the equation as well unless you don't mind programming in the
unadorned lambda calculus.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy in either argument?

2007-07-26 Thread Tim Chevalier

On 7/26/07, Lennart Augustsson [EMAIL PROTECTED] wrote:

The non-termination is (probably) due to the fact that you can have 
uninterruptible threads in ghc.
If a thread never allocates it will never be preempted. :(



To elaborate on that, the different behavior between the two versions
of Dan's code, one with and one without a type signature, happens
because f compiles like so if the type signature isn't given (this is
the STG code):

f_ri5 = \u [] let-no-escape { f1_sPY = NO_CCS[] \u [] f1_sPY; } in  f1_sPY;
SRT(f_ri5): []

and like so if the type signature is given:

f_ri5 = \u srt:(0,*bitmap*) [] f_ri5;
SRT(f_ri5): [f_ri5]

If you look at the resulting asm code, the second version of f_ri5
compiles to a loop that allocates on each iteration, whereas the body
of the let in the first version of f_ri5 compiles to just:
sPY_info:
jmp sPY_info

(Adding f to the export list so that its SRT is empty doesn't change
anything, btw.)

This is all with -Onot.

So I find this a little confusing. Why is f = let f_1 = f_1 in f_1
compiled so differently from f = f? It seems like f = f should also
compile to a loop that doesn't allocate anything. And from the user's
perspective, it seems somewhat strange that adding or removing a type
signature changes the semantics of their code (although I guess you
could make the argument that if you're dealing with threads and
nonterminating code, all bets are off.) Can someone better acquainted
with the code generator than me explain the rationale behind this?

Cheers,
Tim

--
Tim Chevalier* catamorphism.org *Often in error, never in doubt
Religion is just a fancy word for the Stockholm Syndrome.  -- lj
user=pure_agnostic
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Order of evaluation

2007-07-26 Thread Derek Elkins
On Thu, 2007-07-26 at 12:04 -0500, Spencer Janssen wrote:
 On Thursday 26 July 2007 11:02:00 Jon Harrop wrote:
  On Thursday 26 July 2007 17:03:31 C.M.Brown wrote:
   Hi Jon,
  
   On Thu, 26 Jul 2007, Jon Harrop wrote:
If you have a boolean-or expression:
   
  a || b
   
will a be evaluated before b in Haskell as it is in other
languages?
  
   Yes, I believe it is defined thus:
  
   True || _= True
   _|| True = True
   _|| _= False
  
   Therefore it is strict in its first argument (it needs to evaluate its
   first argument in order to know which pattern match to take).
 
  Wonderful, thanks guys. The reason I ask is that I'm just looking over the
  Haskell ray tracer and it occurred to me that evaluation order makes an
  asymptotic difference to performance. The reason is simply that one order
  considers near spheres first and culls far spheres whereas the opposite
  order ends up traversing all spheres.
 
  Do foldl and foldr reduce from the first and last elements of a list,
  respectively?
 
 Well, beginning and end are somewhat fuzzy concepts when laziness is 
 involved.  
 Consider this example:
 
  foldr (||) False [a, b, c] === (a || (b || (c || False)))
  foldl (||) False [a, b, c] === (((False || a) || b) || c)
 
 Note that the least-nested application with foldr is (a || ...) -- this means 
 that foldr can potentially yield some result after looking at the first 
 element of the input.  This is especially useful with (||), because it only 
 uses the second argument when the first is False.
 
 In contrast, foldl's least-nested application is (... || c) -- foldl must 
 traverse to the end of the input before giving an answer.  As it is traveling 
 to the end, it will also build up the expression seen in the example.  On the 
 surface, it seems we'll require O(n) heap to build this thunk.  However, if 
 the compiler is sufficiently smart, bits of this expression will be evaluated 
 as you go along, requiring only O(1) memory, rather than O(n).  We can also 
 force this incremental evaluation with Data.List.foldl'.
 
 Now, imagine folding (+) instead of (||).  (+) evaluates both arguments 
 before 
 computing a result.  In that case, foldr will take O(n) stack.  With a 
 sufficiently smart compiler, foldl will only use O(1) memory.
 
 To summarize:
  Use foldr when the operator is lazy (||, , ++, :).
  Use foldl when the operator is strict (*, +).
  Use foldl' when you don't trust the compiler to optimize foldl.

To unsummarize, see http://www.haskell.org/haskellwiki/Stack_overflow

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


Re: [Haskell-cafe] Indentation woes

2007-07-26 Thread Nicolas Frisby

Whoops, read too fast. Sorry for the noise.

On 7/26/07, Stefan O'Rear [EMAIL PROTECTED] wrote:

On Thu, Jul 26, 2007 at 02:58:21PM -0500, Nicolas Frisby wrote:
 A bandaid suggestion:

 longFunctionName various and sundry arguments = f where
 f | guard1 = body1
 f | guard2 = body2
   | ...
where declarations

 (Disclaimer: untested)

 As I understand it, there can be guards on the definition of f even if
 it takes no arguments. Those guards can reference your the various and
 sundry arguments.

Eh?  Mine doesn't use up a where clause and doesn't use a f noise symbol.
Why do you need a band-aid?

longFunctionName\32=\n\32|\32guard\32=\32body\n\32|\32guard\32=\32body\n\32...

Stefan

-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)

iD8DBQFGqP3jFBz7OZ2P+dIRAgGhAKC3X7hV/vLElQelqCtjZ7XlZQDvdACfftJc
R2g03ScWG33jSzGJ8yxJvUM=
=rq9Y
-END PGP SIGNATURE-



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


Re: [Haskell-cafe] Order of evaluation

2007-07-26 Thread Spencer Janssen
On Thursday 26 July 2007 11:02:00 Jon Harrop wrote:
 On Thursday 26 July 2007 17:03:31 C.M.Brown wrote:
  Hi Jon,
 
  On Thu, 26 Jul 2007, Jon Harrop wrote:
   If you have a boolean-or expression:
  
 a || b
  
   will a be evaluated before b in Haskell as it is in other
   languages?
 
  Yes, I believe it is defined thus:
 
  True || _= True
  _|| True = True
  _|| _= False
 
  Therefore it is strict in its first argument (it needs to evaluate its
  first argument in order to know which pattern match to take).

 Wonderful, thanks guys. The reason I ask is that I'm just looking over the
 Haskell ray tracer and it occurred to me that evaluation order makes an
 asymptotic difference to performance. The reason is simply that one order
 considers near spheres first and culls far spheres whereas the opposite
 order ends up traversing all spheres.

 Do foldl and foldr reduce from the first and last elements of a list,
 respectively?

Well, beginning and end are somewhat fuzzy concepts when laziness is involved.  
Consider this example:

 foldr (||) False [a, b, c] === (a || (b || (c || False)))
 foldl (||) False [a, b, c] === (((False || a) || b) || c)

Note that the least-nested application with foldr is (a || ...) -- this means 
that foldr can potentially yield some result after looking at the first 
element of the input.  This is especially useful with (||), because it only 
uses the second argument when the first is False.

In contrast, foldl's least-nested application is (... || c) -- foldl must 
traverse to the end of the input before giving an answer.  As it is traveling 
to the end, it will also build up the expression seen in the example.  On the 
surface, it seems we'll require O(n) heap to build this thunk.  However, if 
the compiler is sufficiently smart, bits of this expression will be evaluated 
as you go along, requiring only O(1) memory, rather than O(n).  We can also 
force this incremental evaluation with Data.List.foldl'.

Now, imagine folding (+) instead of (||).  (+) evaluates both arguments before 
computing a result.  In that case, foldr will take O(n) stack.  With a 
sufficiently smart compiler, foldl will only use O(1) memory.

To summarize:
 Use foldr when the operator is lazy (||, , ++, :).
 Use foldl when the operator is strict (*, +).
 Use foldl' when you don't trust the compiler to optimize foldl.

 Specifically, I'm wondering if this has an effect on the foldr optimization
 that Spencer proposed (that certainly gives a ~50% speedup here) that was
 attributed to avoiding lazy accumulators, IIRC.

Did I propose something?  I recall looking at this code before, but I can't 
remember the details.


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


Re: [Haskell-cafe] Space usage and CSE in Haskell

2007-07-26 Thread Bertram Felgenhauer
Melissa O'Neill wrote:
 BUT, it generates the output in an order that'll accommodate infinite  
 lists, thus we can say:
 
power_list [1..]
 
 -- Count in binary and use that to create power set
 power_list xs = loop zero where

[snip code that works lazily without wasting memory and supporting
infinite lists.]

 No doubt this can be coded better yet...

How about this: Start with

  power_list :: [a] - [[a]]
  power_list [] = [[]]
  power_list (x:xs) = add_x (power_list xs)
 where add_x [] = []
   add_x (y:ys) = y : (x:y) : foo ys

Note that this puts the empty list first. The only change that is
necessary to make this work for infinite list is to tell the compiler
to assert that the recursive call does the same thing - this can be
done with a lazy pattern:

  power_list :: [a] - [[a]]
  power_list [] = [[]]
  power_list (x:xs) = add_x (assert_first_empty $ power_list xs) x
 where assert_first_empty ~([]:xs) = []:xs
   add_x [] _ = []
   add_x (y:ys) x = y : (x:y) : add_x ys x

It's safe to replace the ~([]:xs) by ~(_:xs) - this should result in
slightly more efficient code (but I did no timings).

Finally for lovers of oneliners, here's the same code with foldr,
slightly obscured by using = for concatMap:

  power_list :: [a] - [[a]]
  power_list = foldr (\x ~(_:xs) - []:xs = \ys - [ys, x:ys]) [[]]

Enjoy,

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


Re: [Haskell-cafe] Re: advantages of using fix to define rcursive functions

2007-07-26 Thread Dan Piponi
On 7/26/07, Nicolas Frisby [EMAIL PROTECTED] wrote:
 Trying to summarize in one phrase: you can do interesting
 manipulations to functions before applying fix that you cannot do to
 functions after applying fix (conventional functions fall in this
 second category).

Something similar holds for types where we can use something like

data Fix s a = In{out :: s a (Fix s a)}

to construct fixed points of functors, as opposed to functions. Any
recursive type can be expressed using Fix, so the question is, why
would you do it? Well, associated to every recursive type is a
corresponding fold and unfold, of which the familiar foldr and unfoldr
are special cases for the List type. If we define our types using Fix
of some functor, then we can also have fold and unfold built for us
automatically from the functor, alongside the actual type.

There are a number of papers that discuss this, including The Essence
of the Iterator Pattern by Jeremy Gibbons and Bruno C. d. S.
Oliveira.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Finance.Quote.Yahoo-0.2

2007-07-26 Thread Thomas Hartman
I installed this and ran the sample program at 

 
http://www.b7j0c.org/content/haddock/finance-quote-yahoo/Finance-Quote-Yahoo.html

This timed out. I suspect, because I am behind a corporate proxy server.

$ env | grep -i http
http_proxy=http://myproxy.com:3128
https_proxy=http://myproxy.com:3128

This works to get unix utilities like w3m and lynx working, but I guess 
not the haskell machinery.

Before I try to fix this myself, can anyone point me to a solution? (and 
also confirm that the above code works when not firewalled :) )

Before I go around changing the library source code, or make a copy 
thereof and put in my working directory, is there a more elegant way to 
approach this?

thomas.




brad clawsie [EMAIL PROTECTED] 
Sent by: [EMAIL PROTECTED]
07/26/2007 01:39 AM

To
haskell-cafe@haskell.org
cc

Subject
[Haskell-cafe] ANN: Finance.Quote.Yahoo-0.2






i have released Finance.Quote.Yahoo 0.2

i have broken the 0.1 api, be careful if you use it

i have added support for historical quotes which some people requested

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Finance-Quote-Yahoo-0.2


i received useful input from dale jordan and aaron tomb on this list
in particular
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fixity of

2007-07-26 Thread Donald Bruce Stewart
ross:
 On Fri, Jul 27, 2007 at 12:08:30AM +1000, Donald Bruce Stewart wrote:
  There's a theory this should work:
  
  getContents = lines  map read  sum  print
  
  But unfortunately we have:
  
   `(=)' [infixl 1] 
   `()' [infixr 1]
  
  Meaning we must write:
  
  getContents = (lines  map read  sum  print)
  
  Indeed, all Arrow ops are infixr. 
  Are there any technical/compelling reasons for this?
 
 Not that I can recall.  But it's the precedence rather than the
 associativity that's bothering you here.

Yes, I suppose it is a vote for 0.5 precedence, if they're not to
behave as for  and = ? Which are:

infixl 1  , =

So I can write:

print 'x'  getChar = ord  print 

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


Re: [Haskell-cafe] Fixity of

2007-07-26 Thread Ross Paterson
On Fri, Jul 27, 2007 at 12:08:30AM +1000, Donald Bruce Stewart wrote:
 There's a theory this should work:
 
 getContents = lines  map read  sum  print
 
 But unfortunately we have:
 
  `(=)' [infixl 1] 
  `()' [infixr 1]
 
 Meaning we must write:
 
 getContents = (lines  map read  sum  print)
 
 Indeed, all Arrow ops are infixr. 
 Are there any technical/compelling reasons for this?

Not that I can recall.  But it's the precedence rather than the
associativity that's bothering you here.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Fixity of

2007-07-26 Thread Donald Bruce Stewart
There's a theory this should work:

getContents = lines  map read  sum  print

But unfortunately we have:

 `(=)' [infixl 1] 
 `()' [infixr 1]

Meaning we must write:

getContents = (lines  map read  sum  print)

Indeed, all Arrow ops are infixr. 
Are there any technical/compelling reasons for this?

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


[Haskell-cafe] Re: Space usage and CSE in Haskell

2007-07-26 Thread ChrisK

Melissa O'Neill wrote:

For example, consider yet another variant of power_list:

power_list l = [] : pow [[]] l where
pow acc [] = []
pow acc (x:xs) = acc_x ++ pow (acc ++ acc_x) xs
   where acc_x = map (++ [x]) acc

By many standards, this version is inefficient, with plenty of appends 
and lots of transient space usage.


BUT, it generates the output in an order that'll accommodate infinite 
lists, thus we can say:


   power_list [1..]

(none of the other versions had this property -- they'd just die here)

So, the moral for optimizations is that any transformation we do to 
improve space performance shouldn't make our program stricter than it 
was before.  (I think the paper by David Sands and Joergen Gustavsson 
that Janis Voigtlaender mentioned covers this too, but I haven't had a 
chance to look at it closely yet.)


Melissa.

P.S.   For fun, I'll also note that yes, it *is* possible to code a 
lazy-list-friendly power_list function in a way that doesn't drag saved 
lists around, although it doesn't run as nearly as quickly as some of 
the others seen.


-- Count in binary and use that to create power set
power_list xs = loop zero where
   loop n = case select xs n of
Nothing  - []
Just set - set : loop (inc n)

   select xs []   = Just []
   select [] nat  = Nothing
   select (x:xs) (True:nat')  = select xs nat' = \l - Just (x:l)
   select (x:xs) (False:nat') = select xs nat'

   zero = []
   inc []   = [True]
   inc (False:bits) = True  : bits
   inc (True :bits) = False : inc bits

No doubt this can be coded better yet...


And it can.  Though the speed depends on whether you use and Int or Integer to 
keep track of the length of the input list.  (If you want a power set of a list 
with 2^31 elements then you can change to Integer).


Your code for power_list and mine for powerBin and powerBin2 work in infinite 
lists:


*Main take 10 (power_list [1..])
[[],[1],[2],[1,2],[3],[1,3],[2,3],[1,2,3],[4],[1,4]]
*Main take 10 (powerBin [1..])
[[],[1],[2],[1,2],[3],[2,3],[1,3],[1,2,3],[4],[3,4]]
*Main take 10 (powerBin2 [1..])
[[],[1],[1,2],[2],[1,2,3],[1,3],[2,3],[3],[1,2,3,4],[1,2,4]]


Though they all disagree about the order involved.  My actual code:


powerBin [] = [[]]
powerBin xs = [] : upto (0 :: Int)
  where upto limit = fromTo limit id (upto (succ limit)) xs
  where fromTo  n  acc  cont[]  = [] -- reached past end of input list, now done 
fromTo  0  acc  cont (y:_) = (acc . (y:) $ []) : cont

fromTo  n  acc  cont (y:ys) =
let n' = pred n
acc' = acc . (y:)
cont' = fromTo n' acc' cont ys
in fromTo n' acc cont' ys


And a version with acc' and acc switched:


powerBin2 [] = [[]]
powerBin2 xs = [] : upto (0 :: Int)
  where upto limit = fromTo limit id (upto (succ limit)) xs
  where fromTo  n  acc  cont[]  = [] -- reached past end of input list, now done 
fromTo  0  acc  cont (y:_) = (acc . (y:) $ []) : cont

fromTo  n  acc  cont (y:ys) =
let n' = pred n
acc' = acc . (y:)
cont' = fromTo n' acc cont ys
in fromTo n' acc' cont' ys



The above never uses (++) or 'reverse' but does build a DList of (y:) for 'acc'. 
 If you do not care if the returned lists are individually reversed then you 
can use List for acc with (acc' = (y:acc)).


The performance on ghc-6.6.1 with -O2 on PPC G4 applied to


main = print (length (power_list [1..22]))


real0m8.592s
user0m7.017s
sys 0m0.687s

main = print (length (powerBin [1..22])) 


real0m3.245s
user0m2.768s
sys 0m0.073s

main = print (length (powerBin2 [1..22])) 


real0m3.305s
user0m2.835s
sys 0m0.071s

--
Chris Kuklewicz

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


Re[2]: [Haskell-cafe] UTF-16

2007-07-26 Thread Bulat Ziganshin
Hello Alistair,

Thursday, July 26, 2007, 12:29:06 PM, you wrote:

 Obviously a proliferation of UTF8 modules isn't great for code re-use.
 Is there a plan to consolidate and expose UTF8 and UTF16 de- and
 encoders in the libraries?

afair there is utf-string module, which provides utf-8 functionality.
may be we should just add utf-16 support there?

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] UTF-16

2007-07-26 Thread Bulat Ziganshin
Hello Donald,

Thursday, July 26, 2007, 8:13:37 AM, you wrote:
 I don't know if anybody cares, but... Today a wrote some trivial code to
 decode (not encode) UTF-16.

These functions already exist in win-specific part of base:

cWcharsToChars :: [CWchar] - [Char]
charsToCWchars :: [Char] - [CWchar]

#ifdef mingw32_HOST_OS

-- On Windows, wchar_t is 16 bits wide and CWString uses the UTF-16 encoding.

-- coding errors generate Chars in the surrogate range
cWcharsToChars = map chr . fromUTF16 . map fromIntegral
 where
  fromUTF16 (c1:c2:wcs)
| 0xd800 = c1  c1 = 0xdbff  0xdc00 = c2  c2 = 0xdfff =
  ((c1 - 0xd800)*0x400 + (c2 - 0xdc00) + 0x1) : fromUTF16 wcs
  fromUTF16 (c:wcs) = c : fromUTF16 wcs
  fromUTF16 [] = []

charsToCWchars = foldr utf16Char [] . map ord
 where
  utf16Char c wcs
| c  0x1 = fromIntegral c : wcs
| otherwise   = let c' = c - 0x1 in
fromIntegral (c' `div` 0x400 + 0xd800) :
fromIntegral (c' `mod` 0x400 + 0xdc00) : wcs




-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-26 Thread ChrisK

Jon Fairbairn wrote:

I currently only get f :: [t] - something, so if I later
discover that I need to change the input representation to
be more efficient than lists, I have to rewrite f. Wouldn't
it be so much nicer if I could simply add a declaration


f:: Stream s = s t - something


and get a function that works on anything in the Stream
class?

The core of the idea would be to allow classes to include
constructors (and associated destructors) so the definition
of Stream would include something for : and [] and their
inverses, though I've no real idea of the details; can
anyone come up with a plan?


I had been avoiding adding my two cents, but I must object to this.

Because this is starting to sound like one of the maddening things about C++.

Namely, the automatic implicit casting conversions of classes via their single 
argument constructors.  This is one of the (several) things that makes reading 
and understanding a function or method call in C++ incredibly difficult.


What if the 'f' in the quoted message above is itself part of a type class. 
Then one has to decide which instance 'f' is being called and what 
constructors/destructors are being called to view the 's t' parameter as the 
correct concrete type.  That way lies madness.


Any magical view logic is dangerous in this respect.  Thus I would probably not 
want any special implicit (class View a b) or (call View a b | a - b), etc.


At least the proposal that (= _) is (- Just _) makes you change the syntax 
instead of overloading (-).


--
Chris

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


Re: [Haskell-cafe] HDBC or HSQL

2007-07-26 Thread George Moschovitis


Ok, I am evaluating HDBC. I wrote a simple test program:
...
Can I get a more specific error? Is there a way to inspect this exception
more deeply?



handleSqlError does the trick, for other newbies:

main =
 handleSqlError $
 do
   dbc - connectPostgreSQL dbname=test user=postgres password=,psql51e
   putStrLn done

Everything works ok now, I cann access my psql database and run basic sql
queries/updates.

-g.

--
http://www.me.gr
http://phidz.com
http://blog.gmosx.com
http://cull.gr
http://www.joy.gr
http://nitroproject.org
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re : Re : [Haskell-cafe] Indentation woes

2007-07-26 Thread Stefan O'Rear
On Thu, Jul 26, 2007 at 08:17:06PM -0400, anon wrote:
 2007/7/26, Stefan O'Rear [EMAIL PROTECTED]:
 Out of curiousity, what do you find objectionable about (legal):

 function argument argument2
  | guard = body
  | guard = body

 as compared to (currently illegal):

 function argument argument2
 | guard = body
 | guard = body

 The extra space, obviously :-)
 I'm well aware that this is an issue of vanishingly small consequence,
 but one could likewise dismiss the entire layout business as a
 needlessly complicated way to save a few keystrokes if one were so
 inclined. If language complexity is the chief concern, why not
 dispense with layout altogether (and a few more things beside)?
 Perhaps fuzzy notions of aesthetics and intuitiveness should weigh
 into the equation as well unless you don't mind programming in the
 unadorned lambda calculus.

Definitely, and Haskell *was* designed to be aesthetic.  I suppose what
I'm really trying to ask is *why* you think the second should be legal.
To me it just seems like an ugly ad-hoc generalization, and ad-hoc
generalizations are something Haskell tries to avoid.

(There's a bit of background on the syntax design process in SPJ's
History of Haskell paper, page 10 of
http://research.microsoft.com/~simonpj/papers/history-of-haskell/history.pdf).

Stefan


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


Re: Re : [Haskell-cafe] Indentation woes

2007-07-26 Thread Neil Mitchell

Hi


Why do you think it should be allowed?  The current rules are arbitrary,
but they are quite simple; we don't want to add an ad-hoc exception just
for this.


The current rules are already quite complex, I believe there is some
thought being given as to how to simplify them.


Out of curiousity, what do you find objectionable about (legal):

function argument argument2
 | guard = body
 | guard = body

as compared to (currently illegal):

function argument argument2
| guard = body
| guard = body


Personally, I have no problem with the current way (and would consider
anything other than 4 leading spaces in the first example to be evil).
However, if you are using a text editor which doesn't automatically
indent the start of following lines, it might be a bit more annoying.
Of course, if your editor is that bad you should consider changing to
virtually anything which isn't notepad.

Thanks

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


Re: [Haskell-cafe] Lazy in either argument?

2007-07-26 Thread Lennart Augustsson
The non-termination is (probably) due to the fact that you can have
uninterruptible threads in ghc.
If a thread never allocates it will never be preempted. :(

  -- Lennart

On 7/24/07, Dan Weston [EMAIL PROTECTED] wrote:

 I am trying to get my feet wet with Haskell threads with the following
 problem, inspired by a recent post
 (http://www.haskell.org/pipermail/haskell-cafe/2007-July/029408.html)
 saying that:

  Since there's no way to have a function be lazy in both arguments, the
  implicit convention is to make functions strict in the first arguments
  and, if applicable, lazy in the last arguments. In other words, the
  convention is
 
True || _|_ = True   but not  _|_ || True = True
 
1 + _|_ = Succ _|_   but not  _|_ + 1 = Succ _|_
 
  Regards,
  apfelmus

 Maybe not lazy in both arguments, but how about lazy in either argument?

 The idea is to fork a thread for each of the two functions, (||) and
 flip (||), pick the winner, then kill off both threads. I can wrap this
 up in a pure function using unsafePerformIO (given the proof obligation
 that the results of both threads will always be equal where both are
 defined).

 The code below seems to work, except for the following problems:

 1) Commenting out the type annotation f :: Bool makes the program hang
 2) If I replace f = f by f = undefined, I get an annoying print of
 LazyOr: Prelude.undefined before it returns the correct value.

 Does anyone know why the type annotation is needed in #1, and/or how to
 suppress the error message in #2?

 Dan Weston

 ---
 import Control.Monad(when)
 import Control.Concurrent(forkIO,killThread)
 import Control.Concurrent.Chan(newChan,readChan,writeChan,isEmptyChan)
 import Foreign(unsafePerformIO)

 f :: Bool
 f = f

 main = putStrLn . show $ lazyBinaryOp (||) f True

 lazyBinaryOp p x y = unsafePerformIO $ do
  c  - newChan
  p2 - forkIO (lazyBinaryOpThread c p x y)
  p1 - forkIO (lazyBinaryOpThread c p y x)
  z  - readChan c
  killThread p1
  killThread p2
  return z

where

  lazyBinaryOpThread c p x y = do
case (p x y) of True  - writeChan c True
False - writeChan c False

 ___
 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] Indentation woes

2007-07-26 Thread Stefan O'Rear
On Thu, Jul 26, 2007 at 02:56:57PM -0400, anon wrote:
 Greetings,
 I wish to be able to indent my code like so:
 longFunctionName various and sundry arguments
 | guard1 = body1
 | guard2 = body2
 | ...
 where declarations
 That is, with guards and where clauses indented to the same level as
 the function name.

 This seems like a perfectly reasonable indentation style to me. It
 also happens to be the preferred style in Clean, another
 layout-sensitive functional language. I believe it is not uncommon in
 ML dialects as well. So why is it that I'm not allowed to use it in
 Haskell?

Because in Haskell everything that is lined up is a new logical line.
Haskell requires all continuation lines to be indented:

longFunctonName various and sundry arguments
 | guard1 = body1
 | guard2 = body2
 | ..
 where declarations

As for why, it's just a matter of Haskell Committee taste.  Nothing
too deep, just an arbitrary set of rules.

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] ANN: Finance.Quote.Yahoo-0.2

2007-07-26 Thread brad clawsie
On Thu, Jul 26, 2007 at 01:34:24PM -0400, Thomas Hartman wrote:
 I installed this and ran the sample program at 
 
  
 http://www.b7j0c.org/content/haddock/finance-quote-yahoo/Finance-Quote-Yahoo.html
 
 This timed out. I suspect, because I am behind a corporate proxy server.

i am sorry you are having difficulty thomas

i use the HTTP module as the basis for making webservice requests

i am not sure how proxying is handled by that package

i believe some people maintaining the HTTP package read this list

many operating systems allow users to stipulate a proxy through an
environment variable as you note

please let me know if my code breaks for some other reason, i will
work hard to fix any legitimate bugs immediately
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Optimizing Haskell compilers

2007-07-26 Thread Stefan O'Rear
On Thu, Jul 26, 2007 at 05:08:33PM +0100, Jon Harrop wrote:
 
 I've heard that there are a plethora of Haskell compilers available. Which 
 others give performance comparable to GHC?

Jhc - experimental whole program compiler.  slightly better than jhc,
  but not by much due to a lack of manpower.  in the spirit of get
  it right, then optimize currently takes several minutes to
  compile 10-line programs. :)

Hbc - The haskell compiler.  Augustsson and Johnsson's pioneering work
  on compiling lazy languages is embodied in hbc, a direct
  descendant of the Lazy ML compiler.  Generally ~30% slower than
  GHC, and occasionally faster - rather suprising for a compiler
  that hasn't been improved in over a decade.

http://www.cse.unsw.edu.au/~dons/nobench/x86_64/results.html

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] Optimizing Haskell compilers

2007-07-26 Thread Neil Mitchell

Hi


I've heard that there are a plethora of Haskell compilers available. Which
others give performance comparable to GHC?


None. If you want a stable, well supported, currently maintained, fast
Haskell compiler, then that's GHC. (in fact, if you drop fast from
that list, you are still left with GHC...)

hbc is faster than GHC for some stuff, but hasn't been maintained in a while.

Jhc is being worked on, with the goal of beating GHC. They have good
performance, but don't really work on many programs, and I'd buy a
server farm before compiling the Prelude.

Supero is in development, and has promising initial benchmarks. I'm
hoping to give a presentation at AngloHaskell on Supero, so hopefully
by then I'll have some good benchmarks. I'm actually hacking it as we
speak. http://www-users.cs.york.ac.uk/~ndm/supero/ (look at the blog
posts)

So realistically, at the moment you have only GHC. The future may open
up more options.

Thanks

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


[Haskell-cafe] Optimizing Haskell compilers

2007-07-26 Thread Jon Harrop

I've heard that there are a plethora of Haskell compilers available. Which 
others give performance comparable to GHC?

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
OCaml for Scientists
http://www.ffconsultancy.com/products/ocaml_for_scientists/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] HDBC or HSQL

2007-07-26 Thread Thomas Hartman
I think we got this to work. We had to connect to MS SQL Server via odbc.





Geoffrey Zhu [EMAIL PROTECTED] 
Sent by: [EMAIL PROTECTED]
07/25/2007 06:11 PM

To

cc
haskell-cafe@haskell.org
Subject
Re: [Haskell-cafe] HDBC or HSQL






Hi,


 I use HSQL with PostgreSQL bindings. It works great and I found it very 
easy
 to use.

 --
 Rich


I don't mean to hijack the thread. Does anyone have experience in
using either HDBC or HSQL with Microsoft SQL server?

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



---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Order of evaluation

2007-07-26 Thread apfelmus
Jon Harrop wrote:
 If you have a boolean-or expression:
 
   a || b
 
 will a be evaluated before b in Haskell as it is in other languages?

Yes, although the meaning of the phrase evaluated before is a bit
tricky in a lazy language, so it's probably better to state it with
denotational semantics alone:

   _|_  ||  b  = _|_

Maybe you also want to know whether the second argument is evaluated.
This is answered by

  True  || _|_ = True
  False || _|_ = _|_


Regards,
apfelmus

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


Re: [Haskell-cafe] Order of evaluation

2007-07-26 Thread Jon Harrop
On Thursday 26 July 2007 17:03:31 C.M.Brown wrote:
 Hi Jon,

 On Thu, 26 Jul 2007, Jon Harrop wrote:
  If you have a boolean-or expression:
 
a || b
 
  will a be evaluated before b in Haskell as it is in other languages?

 Yes, I believe it is defined thus:

 True || _= True
 _|| True = True
 _|| _= False

 Therefore it is strict in its first argument (it needs to evaluate its
 first argument in order to know which pattern match to take).

Wonderful, thanks guys. The reason I ask is that I'm just looking over the 
Haskell ray tracer and it occurred to me that evaluation order makes an 
asymptotic difference to performance. The reason is simply that one order 
considers near spheres first and culls far spheres whereas the opposite order 
ends up traversing all spheres.

Do foldl and foldr reduce from the first and last elements of a list, 
respectively?

Specifically, I'm wondering if this has an effect on the foldr optimization 
that Spencer proposed (that certainly gives a ~50% speedup here) that was 
attributed to avoiding lazy accumulators, IIRC.

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
OCaml for Scientists
http://www.ffconsultancy.com/products/ocaml_for_scientists/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Order of evaluation

2007-07-26 Thread C.M.Brown
Hi Jon,

On Thu, 26 Jul 2007, Jon Harrop wrote:


 If you have a boolean-or expression:

   a || b

 will a be evaluated before b in Haskell as it is in other languages?


Yes, I believe it is defined thus:

True || _= True
_|| True = True
_|| _= False

Therefore it is strict in its first argument (it needs to evaluate its
first argument in order to know which pattern match to take).

Chris.


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


Re: [Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-26 Thread Dan Licata
I think what you're describing is equivalent to making the implicit
view function syntax so terse that you don't write anything at all.  So
the pattern 'p' is always (view - p).  This seems like a pretty
invasive change: 

I don't think the version with the functional dependency works (unless
you adopt some form of scoped type class instances, as you suggest
below), because then if you want to use a datatype as a view, you can no
longer pattern match on the datatype itself at all!  Even with some form
of scoping, you can't decompose the view datatype as itself and as a
view in the same scope.  

The non-functional type class will make everything very polymorphic
(e.g., where we used to infer a type based on the datatype constructors
that occurred, we will now say that it's anything that can be viewed as
that datatype).

So, this syntax affects a lot of code, existing or otherwise, that
doesn't use view patterns, which is something we're trying to avoid.

-Dan

On Jul25, Stefan O'Rear wrote:
 On Wed, Jul 25, 2007 at 09:35:32PM +0200, apfelmus wrote:
  Integer
   = (forall a . ViewInt a = a)
  
  can even be done implicitly and for all types. Together with the magic
  class View, this would give real views.
  
  
  Jón Fairbairn wrote:
   It's essential to this idea that it doesn't involve any new
   pattern matching syntax; the meaning of pattern matching for
   overloaded functions should be just as transparent as for
   non-overloaded ones.
  
  That's what the real views would do modulo the probably minor
  inconvenience that one would need to use (:) and (EmptyL) instead of
  (:) and []. I doubt that the latter can be reused.
 
 It's possible to go even simpler, and implement views via a simple
 desugaring without altering the typechecking kernel at all.
 
 (for simplicity of exposition, assume pattern matches have already been
 compiled to flat cases using Johnsson's algorithm; in particular the
 patterns mentioned consist of exactly one constructor, not zero)
 
 case scrut of
   pat - a
   _   - b
 
 ==
 
 realcase (Prelude.view scrut) of
   pat - a
   _   - b
 
 Where in the Prelude (or the current type environment, if
 -fno-implicit-prelude) we have:
 
 class View a c | c - a where
 view :: a - c
 
 and we provide a deriving-form for View which generates View Foo Foo
 where view = id.
 
 Or, a rule which does that automatically if no explicit instance of View
 _ Foo is in the current module.
 
 Or, remove the fundep and add an instance View a a where view = id to
 the Prelude.
 
 Option 3 makes definitions more polymorphic.  Options 1 and 2 keep the
 same level of polymorphism as before; 1 is simpler but breaks old code.
 
 Note that none of these options supports the value input feature; we
 need new syntax to support non-binding identifiers in patterns!
 
 Stefan



 ___
 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] advantages of using fix to define rcursive functions

2007-07-26 Thread Dan Doel
On Thursday 26 July 2007, Harald ROTTER wrote:
 Hi,

 I read about the usage of fix to define recursive functions. Although I
 think that I understood how to use fix, I still wonder what the
 advantages of fix are (as compared to the conventional approach to
 define recursive functions).

 Any hints are appreciated.

It may not be using fix per-se, but one interesting thing you can do with a 
fixed-point combinator is write one that memoizes the produced function:

 table bounds f = array bounds [(i, f i) | i - range bounds]

 dp bounds f = (memo!)
  where
  memo = table bounds (f (memo!))

Then you can write something like:

 fib' _  1 = 1
 fib' _  2 = 1
 fib' me n = me (n - 1) + me (n - 2)
 fib = dp (1, 30) fib'

And fib will only ever compute the nth fibonacci number once, saving it 
thereafter. Of course, with arrays, this only works over a fixed range, but 
you can write structures that will allow you to memoize over arbitrary 
domains this way (either lazy lists of exponentially sized arrays, or 
infinite, lazy tries will get you O(lg n) lookup on integers, for example; 
and the latter should be able to memoize over strings, among other things).

The advantage being, you can write a library that will automatically do 
dynamic programming for you, instead of having to write the same knot-tying 
array/map code every time.

So, that's not an example of why fix is directly useful, but it's certainly 
useful to understand how to use it for this reason.

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


[Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-26 Thread apfelmus
Dan Licata wrote:
 apfelmus wrote:
 The idea is to introduce a new language extension, namely the ability to
 pattern match a polymorphic type. For demonstration, let

   class ViewInt a where
 view :: Integer - a

   instance ViewInt [Bool] where
 view n = ... -- binary representation

   data Nat = Zero | Succ Nat

   instance ViewInt Nat where
 view n = ... -- representation as peano number

 be some views of the integers. Now, I'd like to be able to write

   bar :: (forall a . ViewInt a = a) - String
   bar Zero  = ...
   bar (True:xs) = ...
 
 This doesn't make sense to me:
 
 Zero :: Nat 
 
 and therefore
 
 Zero :: ViewInt Nat = Nat
 
 but you can't generalize from that to 
 
 Zero :: forall a. ViewInt a = a
 
 E.g., Zero does not have type ViewInt [Bool] = Bool

Yes, the types of the patterns don't unify. But each one is a
specialization of the argument type. Note that the type signature is

  bar :: (forall a . ViewInt a = a) - String

which is very different from

  bar :: forall a . ViewInt a = a - String

Without the extension, we would write  bar  as follows

  bar :: (forall a . ViewInt a = a) - String
  bar x = let xNat = x :: Nat in
 case xNat of
   Zero - ...
   _- let xListBool = x :: [Bool] in
  case xListBool of
 True:xs - ...

In other words, we can specialize the polymorphic argument to each
pattern type and each equation may match successfully.

 Maybe you wanted an existential instead

No. That would indeed mean to pick the matching equation by analysing
the packed type, i.e. some equations don't match since their patterns
have the wrong type. I think that such a thing violates parametricity.

Regards,
apfelmus

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


Re: [Haskell-cafe] advantages of using fix to define rcursive functions

2007-07-26 Thread Janis Voigtlaender

Donald Bruce Stewart wrote:

harald.rotter:


Hi,

I read about the usage of fix to define recursive functions. Although I
think that I understood how to use fix, I still wonder what the
advantages of fix are (as compared to the conventional approach to
define recursive functions).

Any hints are appreciated.



So actually, I suppose it is useful for small, anonymous recursive definitions.


It also exposes the recursive computation structure for direct
manipulation, enabling one to perform certain program
transformations/refactorings. Search for fixpoint fusion and fixed
point promotion. While one might say: that's the business of a
compiler, actually existing ones are not very sophisticated in that
regard, so one might want to do such transformations by hand...

Ciao, 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] Indentation woes

2007-07-26 Thread anon

Greetings,
I wish to be able to indent my code like so:

longFunctionName various and sundry arguments
| guard1 = body1
| guard2 = body2
| ...
where declarations

That is, with guards and where clauses indented to the same level as
the function name.

This seems like a perfectly reasonable indentation style to me. It
also happens to be the preferred style in Clean, another
layout-sensitive functional language. I believe it is not uncommon in
ML dialects as well. So why is it that I'm not allowed to use it in
Haskell?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Order of evaluation

2007-07-26 Thread Jon Harrop

If you have a boolean-or expression:

  a || b

will a be evaluated before b in Haskell as it is in other languages?

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
OCaml for Scientists
http://www.ffconsultancy.com/products/ocaml_for_scientists/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy in either argument?

2007-07-26 Thread Tim Chevalier

On 7/26/07, Tim Chevalier [EMAIL PROTECTED] wrote:

To elaborate on that, the different behavior between the two versions
of Dan's code, one with and one without a type signature, happens
because f compiles like so if the type signature isn't given (this is
the STG code):

f_ri5 = \u [] let-no-escape { f1_sPY = NO_CCS[] \u [] f1_sPY; } in  f1_sPY;
SRT(f_ri5): []



Also (talking to myself), in the lambda-form that is the rhs of f1_sPY
above, shouldn't f1_sPY be contained in the free-variable list for
itself?

Cheers,
Tim

--
Tim Chevalier* catamorphism.org *Often in error, never in doubt
Programming is like sex; one mistake and you have to support for a
lifetime. -- anonymous
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re : [Haskell-cafe] Indentation woes

2007-07-26 Thread anon

2007/7/26, Stefan O'Rear [EMAIL PROTECTED]:

As for why, it's just a matter of Haskell Committee taste.  Nothing
too deep, just an arbitrary set of rules.

That's not much of an explanation, is it? I imagine someone must have
given the matter some thought before describing the layout rule in
great details in the language report. Perhaps there was a perfectly
good reason to preclude this kind of code, but I'm afraid I do need a
reason if I am to understand why. And if it turns out that there
really is no such reason, would it be terribly presumptuous of me to
suggest that the rules be changed to accomodate this particular style
in Haskell' or a future revision of the language? I guess it would,
but one can always hope.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re : [Haskell-cafe] Indentation woes

2007-07-26 Thread Stefan O'Rear
On Thu, Jul 26, 2007 at 05:34:32PM -0400, anon wrote:
 2007/7/26, Stefan O'Rear [EMAIL PROTECTED]:
 As for why, it's just a matter of Haskell Committee taste.  Nothing
 too deep, just an arbitrary set of rules.
 That's not much of an explanation, is it? I imagine someone must have
 given the matter some thought before describing the layout rule in
 great details in the language report. Perhaps there was a perfectly
 good reason to preclude this kind of code, but I'm afraid I do need a
 reason if I am to understand why. And if it turns out that there
 really is no such reason, would it be terribly presumptuous of me to
 suggest that the rules be changed to accomodate this particular style
 in Haskell' or a future revision of the language? I guess it would,
 but one can always hope.

Why do you think it should be allowed?  The current rules are arbitrary,
but they are quite simple; we don't want to add an ad-hoc exception just
for this.

Out of curiousity, what do you find objectionable about (legal):

function argument argument2
 | guard = body
 | guard = body

as compared to (currently illegal):

function argument argument2
| guard = body
| guard = body

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] Order of evaluation

2007-07-26 Thread Jonathan Cast
On Thursday 26 July 2007, Jon Harrop wrote:
 If you have a boolean-or expression:

   a || b

 will a be evaluated before b in Haskell as it is in other languages?

Yes.

The definition of (||) is roughly

True || b = True
False || b = b

Which de-sugars to

(||) = \ a b - case a of
  True - True
  False - b

Which does exactly what you want.

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


pgpHiL6AGRotf.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: advantages of using fix to define rcursive functions

2007-07-26 Thread Nicolas Frisby

Just casting my vote for the helpfulness of this reference.

Trying to summarize in one phrase: you can do interesting
manipulations to functions before applying fix that you cannot do to
functions after applying fix (conventional functions fall in this
second category).

On 7/26/07, Chung-chieh Shan [EMAIL PROTECTED] wrote:

You might enjoy this paper:

Bruce J. McAdam, 1997. That about wraps it up: Using FIX to handle
errors without exceptions, and other programming tricks. Tech. Rep.
ECS-LFCS-97-375, Laboratory for Foundations of Computer Science,
Department of Computer Science, University of Edinburgh.
http://www.lfcs.informatics.ed.ac.uk/reports/97/ECS-LFCS-97-375/

--
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
It is the first responsibility of every citizen to question authority.
Benjamin Franklin

___
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] Indentation woes

2007-07-26 Thread Jonathan Cast
On Thursday 26 July 2007, anon wrote:
 2007/7/26, Stefan O'Rear [EMAIL PROTECTED]:
  Out of curiousity, what do you find objectionable about (legal):
 
  function argument argument2
 
   | guard = body
   | guard = body
 
  as compared to (currently illegal):
 
  function argument argument2
 
  | guard = body
  | guard = body

 The extra space, obviously :-)
 I'm well aware that this is an issue of vanishingly small consequence,
 but one could likewise dismiss the entire layout business as a
 needlessly complicated way to save a few keystrokes

On the contrary.  Layout, by itself, strictly reduces the number of ways to 
write any given program.  It makes things more consistent across coding 
styles.  That's not an inconsequential benefit.

 if one were so 
 inclined. If language complexity is the chief concern, why not
 dispense with layout altogether (and a few more things beside)?
 Perhaps fuzzy notions of aesthetics and intuitiveness should weigh
 into the equation as well unless you don't mind programming in the
 unadorned lambda calculus.



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


pgpeckjf9FBbq.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re : Re : Re : [Haskell-cafe] Indentation woes

2007-07-26 Thread anon
2007/7/26, ok [EMAIL PROTECTED]:
 The Fundamental Law of Indentation is
If major syntactic unit X is a proper part of major syntactic
 unit Y, then every visible character of X is strictly to the
 right[%] of the leftmost[%] visible character of Y.
 [%] If you are using a right-to-left script, switch left and
 right in that sentence.

What makes this a law? If you notice a pattern where beginners trip
against this rule because they don't indent the arms of conditionals
properly inside do blocks, should strict adherence to this principle
take precendence over the intuition of prospective users of the
language? Oddly enough, members of the Haskell' committee seem to
think we should amend the rules for the benefit of programmers rather
the other way around, but I guess they never heard of the Fundamental
Law of Indentation.

 That is how indentation makes structure visible, and if you
 break that, you just plain aren't indenting.  This isn't fuzzy,
 and it isn't aesthetic, it's simply that if you start things in
 the same column you are making it obvious to the reader than
 neither is part of the other.  In the example about, that's not
 true.  You might as well go around ending sentences with

I see what you did there. But you really might as well end sentences
with prepositions. Or begin them with conjunction. Or indent your code
whichever way seems most natural and elegant because to do otherwise
is just prescriptivism for its own sake. In general, people don't much
care for arbitrary rules; they like to understand the rationale behind
them before they get on board, which is all I'm really asking for
here.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-26 Thread Conor McBride

Hi Dan

On 25 Jul 2007, at 15:18, Dan Licata wrote:


Hi Conor,



[..]


Why are you so fatalistic about with in Haskell?


I guess I'm just fatalistic, generally. Plausibility is not something
I'm especially talented at.


  Is it harder to
implement than it looks?


For Haskell, it ought to be very easy.


It seems to be roughly in the same category as
our view pattern proposal, in that it's just an addition to the syntax
of pattern matching, and it has a straightforward elaboration into the
internal language.


Even on the source level, the with-blocks just expand as helper
functions. I wonder if I have the time and energy to knock up a
preprocessor...


  (Well, for Haskell it's more straightforward than
for Epigram, because we don't need to construct the evidence for  
ruling

out contradictory branches, etc., necessary to translate to inductive
family elims.)


In the dependently typed setting, it's often the case that the
with-scrutinee is an expression of interest precisely because it  
occurs

in the *type* of the function being defined. Correspondingly, an
Epigram implementation should (and the Agda 2 implementation now does)
abstract occurrences of the expression from the type. That makes things
a bit trickier to implement, but it's just the thing you need to replace
stuck computations in types with actual values. The with construct
is what makes it possible to keep all the layers of computation in step.

It's so often exactly the thing you need in dependently typed  
programming,

so maybe that's a point in its favour as a conceivable Haskell feature,
given the flow of the type-level computation tide.

All the best

Conor

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


Re: Re : [Haskell-cafe] Indentation woes

2007-07-26 Thread Thomas Conway
On 7/27/07, Neil Mitchell [EMAIL PROTECTED] wrote:
 Personally, I have no problem with the current way (and would consider
 anything other than 4 leading spaces in the first example to be evil).
 However, if you are using a text editor which doesn't automatically
 indent the start of following lines, it might be a bit more annoying.
 Of course, if your editor is that bad you should consider changing to
 virtually anything which isn't notepad.

Or pico. :-) You'd be amazed the number of undergraduates I taught who
refused to learn to use gvim, emacs, or any other *programming*
editor, and instead spent 75% of their time battling the editor.
sigh

I must say, I agree about the indentation question. My experience is
that if you use 4 space indentation and run out of columns, then it's
time to refactor, and think more about how your logical structure is
working (you may recall, this list recently introduced me to the Maybe
monad transformer for exactly this reason). It's actually a pretty
effective rule of thumb.

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


[Haskell-cafe] Avoiding boilerplate retrieving GetOpt cmd line args

2007-07-26 Thread Dave Bayer
Ok, I'm writing a command line tool, using System.Console.GetOpt to  
handle command line arguments. My Flags structure so far is



data Flag
= Filter String
| DateFormat String
| DocStart String
| DocEnd String

...

and I want to write accessor functions that return the strings if  
specified, otherwise returning a default. The best I've been able to  
do is this:



getFilter = getString f Markdown.pl
where f (Filter s) = Just s
  f _ = Nothing

getDateFormat = getString f %B %e, %Y
where f (DateFormat s) = Just s
  f _ = Nothing

getDocStart = getString f ^{-$
where f (DocStart s) = Just s
  f _ = Nothing

getDocEnd = getString f ^-}$
where f (DocEnd s) = Just s
  f _ = Nothing


using a generic accessor function `getString`.

There are eight (and growing) needless lines here, where what I  
really want to do is to pass the constructors `Filter`, `DateFormat`,  
`DocStart`, or `DocEnd` to the function `getString`. ghci types each  
of these as `String - Flag`, so one at least knows how to type such  
a `getString`, but using a constructor-passed-as-an-argument in a  
pattern match is of course a Parse error in pattern. (I expected as  
much, but I had to try... `String - Flag` is not enough information  
to make it clear we're passing a constructor, rather than some hairy  
arbitrary function, so such a pattern match would be undecidable in  
general.)


So what's the right idiom for avoiding this boilerplate?

Thanks,
Dave

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


Re: [Haskell-cafe] Avoiding boilerplate retrieving GetOpt cmd line args

2007-07-26 Thread Levi Stephen

Hi,

Not sure if this will help avoid the boilerplate, but I've always liked 
the approach at 
http://leiffrenzel.de/papers/commandline-options-in-haskell.html 
(particularly the section Towards a higher level) for being able to 
specify defaults. It's the best resource I've found on command line 
options in Haskell so far.


Levi
Ok, I'm writing a command line tool, using System.Console.GetOpt to 
handle command line arguments. My Flags structure so far is



data Flag
= Filter String
| DateFormat String
| DocStart String
| DocEnd String

...

and I want to write accessor functions that return the strings if 
specified, otherwise returning a default. The best I've been able to 
do is this:



getFilter = getString f Markdown.pl
where f (Filter s) = Just s
  f _ = Nothing

getDateFormat = getString f %B %e, %Y
where f (DateFormat s) = Just s
  f _ = Nothing

getDocStart = getString f ^{-$
where f (DocStart s) = Just s
  f _ = Nothing

getDocEnd = getString f ^-}$
where f (DocEnd s) = Just s
  f _ = Nothing


using a generic accessor function `getString`.

There are eight (and growing) needless lines here, where what I really 
want to do is to pass the constructors `Filter`, `DateFormat`, 
`DocStart`, or `DocEnd` to the function `getString`. ghci types each 
of these as `String - Flag`, so one at least knows how to type such a 
`getString`, but using a constructor-passed-as-an-argument in a 
pattern match is of course a Parse error in pattern. (I expected as 
much, but I had to try... `String - Flag` is not enough information 
to make it clear we're passing a constructor, rather than some hairy 
arbitrary function, so such a pattern match would be undecidable in 
general.)


So what's the right idiom for avoiding this boilerplate?

Thanks,
Dave

___
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